xref: /openbsd-src/gnu/usr.bin/perl/regen/opcodes (revision f2da64fbbbf1b03f09f390ab01267c93dfd77c4c)
1# New ops always go at the end
2# The restriction on having custom as the last op has been removed
3
4# A recapitulation of the format of this file:
5# The file consists of five columns: the name of the op, an English
6# description, the name of the "check" routine used to optimize this
7# operation, some flags, and a description of the operands.
8
9# The flags consist of options followed by a mandatory op class signifier
10
11# The classes are:
12# baseop      - 0            unop     - 1            binop      - 2
13# logop       - |            listop   - @            pmop       - /
14# padop/svop  - $            padop    - # (unused)   loop       - {
15# baseop/unop - %            loopexop - }            filestatop - -
16# pvop/svop   - "            cop      - ;
17
18# Other options are:
19#   needs stack mark                    - m
20#   needs constant folding              - f
21#   produces a scalar                   - s
22#   produces an integer                 - i
23#   needs a target                      - t
24#   target can be in a pad              - T
25#   has a corresponding integer version - I
26#   has side effects                    - d
27#   uses $_ if no argument given        - u
28
29# Values for the operands are:
30# scalar      - S            list     - L            array     - A
31# hash        - H            sub (CV) - C            file      - F
32# socket      - Fs           filetest - F-           filetest_access - F-+
33# num-compare - S<           dirhandle - DF
34
35# reference - R
36# "?" denotes an optional operand.
37
38# Nothing.
39
40null		null operation		ck_null		0
41stub		stub			ck_null		0
42scalar		scalar			ck_fun		s%	S
43
44# Pushy stuff.
45
46pushmark	pushmark		ck_null		s0
47wantarray	wantarray		ck_null		is0
48
49const		constant item		ck_svconst	s$
50
51gvsv		scalar variable		ck_null		ds$
52gv		glob value		ck_null		ds$
53gelem		glob elem		ck_null		d2	S S
54padsv		private variable	ck_null		ds0
55padav		private array		ck_null		d0
56padhv		private hash		ck_null		d0
57padany		private value		ck_null		d0
58
59pushre		push regexp		ck_null		d/
60
61# References and stuff.
62
63rv2gv		ref-to-glob cast	ck_rvconst	ds1
64rv2sv		scalar dereference	ck_rvconst	ds1
65av2arylen	array length		ck_null		is1
66rv2cv		subroutine dereference	ck_rvconst	d1
67anoncode	anonymous subroutine	ck_anoncode	$
68prototype	subroutine prototype	ck_null		s%	S
69refgen		reference constructor	ck_spair	m1	L
70srefgen		single ref constructor	ck_null		fs1	S
71ref		reference-type operator	ck_fun		stu%	S?
72bless		bless			ck_fun		s@	S S?
73
74# Pushy I/O.
75
76backtick	quoted execution (``, qx)	ck_backtick	tu%	S?
77# glob defaults its first arg to $_
78glob		glob			ck_glob		t@	S?
79readline	<HANDLE>		ck_readline	t%	F?
80rcatline	append I/O operator	ck_null		t$
81
82# Bindable operators.
83
84regcmaybe	regexp internal guard	ck_fun		s1	S
85regcreset	regexp internal reset	ck_fun		s1	S
86regcomp		regexp compilation	ck_null		s|	S
87match		pattern match (m//)	ck_match	d/
88qr		pattern quote (qr//)	ck_match	s/
89subst		substitution (s///)	ck_match	dis/	S
90substcont	substitution iterator	ck_null		dis|
91trans		transliteration (tr///)	ck_match	is"	S
92# y///r
93transr		transliteration (tr///)	ck_match	is"	S
94
95# Lvalue operators.
96# sassign is special-cased for op class
97
98sassign		scalar assignment	ck_sassign	s0
99aassign		list assignment		ck_null		t2	L L
100
101chop		chop			ck_spair	mts%	L
102schop		scalar chop		ck_null		stu%	S?
103chomp		chomp			ck_spair	mTs%	L
104schomp		scalar chomp		ck_null		sTu%	S?
105defined		defined operator	ck_defined	isu%	S?
106undef		undef operator		ck_fun		s%	R?
107study		study			ck_fun		su%	S?
108pos		match position		ck_fun		stu%	R?
109
110preinc		preincrement (++)		ck_lfun		dIs1	S
111i_preinc	integer preincrement (++)	ck_lfun		dis1	S
112predec		predecrement (--)		ck_lfun		dIs1	S
113i_predec	integer predecrement (--)	ck_lfun		dis1	S
114postinc		postincrement (++)		ck_lfun		dIst1	S
115i_postinc	integer postincrement (++)	ck_lfun		disT1	S
116postdec		postdecrement (--)		ck_lfun		dIst1	S
117i_postdec	integer postdecrement (--)	ck_lfun		disT1	S
118
119# Ordinary operators.
120
121pow		exponentiation (**)	ck_null		fsT2	S S
122
123multiply	multiplication (*)	ck_null		IfsT2	S S
124i_multiply	integer multiplication (*)	ck_null		ifsT2	S S
125divide		division (/)		ck_null		IfsT2	S S
126i_divide	integer division (/)	ck_null		ifsT2	S S
127modulo		modulus (%)		ck_null		IifsT2	S S
128i_modulo	integer modulus (%)	ck_null		ifsT2	S S
129repeat		repeat (x)		ck_repeat	fmt2	L S
130
131add		addition (+)		ck_null		IfsT2	S S
132i_add		integer addition (+)	ck_null		ifsT2	S S
133subtract	subtraction (-)		ck_null		IfsT2	S S
134i_subtract	integer subtraction (-)	ck_null		ifsT2	S S
135concat		concatenation (.) or string	ck_concat	fsT2	S S
136stringify	string			ck_fun		fsT@	S
137
138left_shift	left bitshift (<<)	ck_bitop	fsT2	S S
139right_shift	right bitshift (>>)	ck_bitop	fsT2	S S
140
141lt		numeric lt (<)		ck_cmp		Iifs2	S S<
142i_lt		integer lt (<)		ck_cmp		ifs2	S S<
143gt		numeric gt (>)		ck_cmp		Iifs2	S S<
144i_gt		integer gt (>)		ck_cmp		ifs2	S S<
145le		numeric le (<=)		ck_cmp		Iifs2	S S<
146i_le		integer le (<=)		ck_cmp		ifs2	S S<
147ge		numeric ge (>=)		ck_cmp		Iifs2	S S<
148i_ge		integer ge (>=)		ck_cmp		ifs2	S S<
149eq		numeric eq (==)		ck_null		Iifs2	S S<
150i_eq		integer eq (==)		ck_null		ifs2	S S<
151ne		numeric ne (!=)		ck_null		Iifs2	S S<
152i_ne		integer ne (!=)		ck_null		ifs2	S S<
153ncmp		numeric comparison (<=>)	ck_null		Iifst2	S S<
154i_ncmp		integer comparison (<=>)	ck_null		ifst2	S S<
155
156slt		string lt		ck_null		ifs2	S S
157sgt		string gt		ck_null		ifs2	S S
158sle		string le		ck_null		ifs2	S S
159sge		string ge		ck_null		ifs2	S S
160seq		string eq		ck_null		ifs2	S S
161sne		string ne		ck_null		ifs2	S S
162scmp		string comparison (cmp)	ck_null		ifst2	S S
163
164bit_and		bitwise and (&)		ck_bitop	fst2	S S
165bit_xor		bitwise xor (^)		ck_bitop	fst2	S S
166bit_or		bitwise or (|)		ck_bitop	fst2	S S
167
168negate		negation (-)		ck_null		Ifst1	S
169i_negate	integer negation (-)	ck_null		ifsT1	S
170not		not			ck_null		ifs1	S
171complement	1's complement (~)	ck_bitop	fst1	S
172
173smartmatch	smart match		ck_smartmatch	s2
174
175# High falutin' math.
176
177atan2		atan2			ck_fun		fsT@	S S
178sin		sin			ck_fun		fsTu%	S?
179cos		cos			ck_fun		fsTu%	S?
180rand		rand			ck_fun		sT%	S?
181srand		srand			ck_fun		sT%	S?
182exp		exp			ck_fun		fsTu%	S?
183log		log			ck_fun		fsTu%	S?
184sqrt		sqrt			ck_fun		fsTu%	S?
185
186# Lowbrow math.
187
188int		int			ck_fun		fsTu%	S?
189hex		hex			ck_fun		fsTu%	S?
190oct		oct			ck_fun		fsTu%	S?
191abs		abs			ck_fun		fsTu%	S?
192
193# String stuff.
194
195length		length			ck_length	ifsTu%	S?
196substr		substr			ck_substr	st@	S S S? S?
197vec		vec			ck_fun		ist@	S S S
198
199index		index			ck_index	isT@	S S S?
200rindex		rindex			ck_index	isT@	S S S?
201
202sprintf		sprintf			ck_lfun		fmst@	S L
203formline	formline		ck_fun		ms@	S L
204ord		ord			ck_fun		ifsTu%	S?
205chr		chr			ck_fun		fsTu%	S?
206crypt		crypt			ck_fun		fsT@	S S
207ucfirst		ucfirst			ck_fun		fstu%	S?
208lcfirst		lcfirst			ck_fun		fstu%	S?
209uc		uc			ck_fun		fstu%	S?
210lc		lc			ck_fun		fstu%	S?
211quotemeta	quotemeta		ck_fun		fstu%	S?
212
213# Arrays.
214
215rv2av		array dereference	ck_rvconst	dt1
216aelemfast	constant array element	ck_null		s$	A S
217aelemfast_lex	constant lexical array element	ck_null		d0	A S
218aelem		array element		ck_null		s2	A S
219aslice		array slice		ck_null		m@	A L
220kvaslice	index/value array slice	ck_null		m@	A L
221
222aeach		each on array		ck_each		%	A
223akeys		keys on array		ck_each		t%	A
224avalues		values on array		ck_each		t%	A
225
226# Hashes.
227
228each		each			ck_each		%	H
229values		values			ck_each		t%	H
230keys		keys			ck_each		t%	H
231delete		delete			ck_delete	%	S
232exists		exists			ck_exists	is%	S
233rv2hv		hash dereference	ck_rvconst	d1
234helem		hash element		ck_null		s2	H S
235hslice		hash slice		ck_null		m@	H L
236kvhslice	key/value hash slice	ck_null		m@	H L
237
238# Explosives and implosives.
239
240unpack		unpack			ck_fun		u@	S S?
241pack		pack			ck_fun		fmst@	S L
242split		split			ck_split	t@	S S S
243join		join or string		ck_join		mst@	S L
244
245# List operators.
246
247list		list			ck_null		m@	L
248lslice		list slice		ck_null		2	H L L
249anonlist	anonymous list ([])	ck_fun		ms@	L
250anonhash	anonymous hash ({})	ck_fun		ms@	L
251
252splice		splice			ck_fun		m@	A S? S? L
253push		push			ck_fun		imsT@	A L
254pop		pop			ck_shift	s%	A?
255shift		shift			ck_shift	s%	A?
256unshift		unshift			ck_fun		imsT@	A L
257sort		sort			ck_sort		dm@	C? L
258reverse		reverse			ck_fun		mt@	L
259
260grepstart	grep			ck_grep		dm@	C L
261grepwhile	grep iterator		ck_null		dt|
262
263mapstart	map			ck_grep		dm@	C L
264mapwhile	map iterator		ck_null		dt|
265
266# Range stuff.
267
268range		flipflop		ck_null		|	S S
269flip		range (or flip)		ck_null		1	S S
270flop		range (or flop)		ck_null		1
271
272# Control.
273
274and		logical and (&&)		ck_null		|
275or		logical or (||)			ck_null		|
276xor		logical xor			ck_null		fs2	S S
277dor		defined or (//)			ck_null		|
278cond_expr	conditional expression		ck_null		d|
279andassign	logical and assignment (&&=)	ck_null		s|
280orassign	logical or assignment (||=)	ck_null		s|
281dorassign	defined or assignment (//=)	ck_null		s|
282
283method		method lookup		ck_method	d1
284entersub	subroutine entry	ck_subr		dmt1	L
285leavesub	subroutine exit		ck_null		1
286leavesublv	lvalue subroutine return	ck_null		1
287caller		caller			ck_fun		t%	S?
288warn		warn			ck_fun		imst@	L
289die		die			ck_fun		dimst@	L
290reset		symbol reset		ck_fun		is%	S?
291
292lineseq		line sequence		ck_null		@
293nextstate	next statement		ck_null		s;
294dbstate		debug next statement	ck_null		s;
295unstack		iteration finalizer	ck_null		s0
296enter		block entry		ck_null		0
297leave		block exit		ck_null		@
298scope		block			ck_null		@
299enteriter	foreach loop entry	ck_null		d{
300iter		foreach loop iterator	ck_null		0
301enterloop	loop entry		ck_null		d{
302leaveloop	loop exit		ck_null		2
303return		return			ck_return	dm@	L
304last		last			ck_null		ds}
305next		next			ck_null		ds}
306redo		redo			ck_null		ds}
307dump		dump			ck_null		ds}
308goto		goto			ck_null		ds}
309exit		exit			ck_fun		ds%	S?
310method_named	method with known name	ck_null		d$
311
312entergiven	given()			ck_null		d|
313leavegiven	leave given block	ck_null		1
314enterwhen	when()			ck_null		d|
315leavewhen	leave when block	ck_null		1
316break		break			ck_null		0
317continue	continue		ck_null		0
318
319# I/O.
320
321open		open			ck_open		ismt@	F S? L
322close		close			ck_fun		is%	F?
323pipe_op		pipe			ck_fun		is@	F F
324
325fileno		fileno			ck_fun		ist%	F
326umask		umask			ck_fun		ist%	S?
327binmode		binmode			ck_fun		s@	F S?
328
329tie		tie			ck_fun		idms@	R S L
330untie		untie			ck_fun		is%	R
331tied		tied			ck_fun		s%	R
332dbmopen		dbmopen			ck_fun		is@	H S S
333dbmclose	dbmclose		ck_fun		is%	H
334
335sselect		select system call	ck_select	t@	S S S S
336select		select			ck_select	st@	F?
337
338getc		getc			ck_eof		st%	F?
339read		read			ck_fun		imst@	F R S S?
340enterwrite	write			ck_fun		dis%	F?
341leavewrite	write exit		ck_null		1
342
343prtf		printf			ck_listiob	ims@	F? L
344print		print			ck_listiob	ims@	F? L
345say		say			ck_listiob	ims@	F? L
346
347sysopen		sysopen			ck_fun		s@	F S S S?
348sysseek		sysseek			ck_fun		s@	F S S
349sysread		sysread			ck_fun		imst@	F R S S?
350syswrite	syswrite		ck_fun		imst@	F S S? S?
351
352eof		eof			ck_eof		is%	F?
353tell		tell			ck_tell		st%	F?
354seek		seek			ck_tell		s@	F S S
355# truncate really behaves as if it had both "S S" and "F S"
356truncate	truncate		ck_trunc	is@	S S
357
358fcntl		fcntl			ck_fun		st@	F S S
359ioctl		ioctl			ck_fun		st@	F S S
360flock		flock			ck_fun		isT@	F S
361
362# Sockets.  OP_IS_SOCKET wants them consecutive (so moved 1st 2)
363
364send		send			ck_fun		imst@	Fs S S S?
365recv		recv			ck_fun		imst@	Fs R S S
366
367socket		socket			ck_fun		is@	Fs S S S
368sockpair	socketpair		ck_fun		is@	Fs Fs S S S
369
370bind		bind			ck_fun		is@	Fs S
371connect		connect			ck_fun		is@	Fs S
372listen		listen			ck_fun		is@	Fs S
373accept		accept			ck_fun		ist@	Fs Fs
374shutdown	shutdown		ck_fun		ist@	Fs S
375
376gsockopt	getsockopt		ck_fun		is@	Fs S S
377ssockopt	setsockopt		ck_fun		is@	Fs S S S
378
379getsockname	getsockname		ck_fun		is%	Fs
380getpeername	getpeername		ck_fun		is%	Fs
381
382# Stat calls.  OP_IS_FILETEST wants them consecutive.
383
384lstat		lstat			ck_ftst		u-	F?
385stat		stat			ck_ftst		u-	F?
386ftrread		-R			ck_ftst		isu-	F-+
387ftrwrite	-W			ck_ftst		isu-	F-+
388ftrexec		-X			ck_ftst		isu-	F-+
389fteread		-r			ck_ftst		isu-	F-+
390ftewrite	-w			ck_ftst		isu-	F-+
391fteexec		-x			ck_ftst		isu-	F-+
392ftis		-e			ck_ftst		isu-	F-
393ftsize		-s			ck_ftst		istu-	F-
394ftmtime		-M			ck_ftst		stu-	F-
395ftatime		-A			ck_ftst		stu-	F-
396ftctime		-C			ck_ftst		stu-	F-
397ftrowned	-O			ck_ftst		isu-	F-
398fteowned	-o			ck_ftst		isu-	F-
399ftzero		-z			ck_ftst		isu-	F-
400ftsock		-S			ck_ftst		isu-	F-
401ftchr		-c			ck_ftst		isu-	F-
402ftblk		-b			ck_ftst		isu-	F-
403ftfile		-f			ck_ftst		isu-	F-
404ftdir		-d			ck_ftst		isu-	F-
405ftpipe		-p			ck_ftst		isu-	F-
406ftsuid		-u			ck_ftst		isu-	F-
407ftsgid		-g			ck_ftst		isu-	F-
408ftsvtx		-k			ck_ftst		isu-	F-
409ftlink		-l			ck_ftst		isu-	F-
410fttty		-t			ck_ftst		is-	F-
411fttext		-T			ck_ftst		isu-	F-
412ftbinary	-B			ck_ftst		isu-	F-
413
414# File calls.
415
416# chdir really behaves as if it had both "S?" and "F?"
417chdir		chdir			ck_trunc	isT%	S?
418chown		chown			ck_fun		imsT@	L
419chroot		chroot			ck_fun		isTu%	S?
420unlink		unlink			ck_fun		imsTu@	L
421chmod		chmod			ck_fun		imsT@	L
422utime		utime			ck_fun		imsT@	L
423rename		rename			ck_fun		isT@	S S
424link		link			ck_fun		isT@	S S
425symlink		symlink			ck_fun		isT@	S S
426readlink	readlink		ck_fun		stu%	S?
427mkdir		mkdir			ck_fun		isTu@	S? S?
428rmdir		rmdir			ck_fun		isTu%	S?
429
430# Directory calls.
431
432open_dir	opendir			ck_fun		is@	F S
433readdir		readdir			ck_fun		%	DF
434telldir		telldir			ck_fun		st%	DF
435seekdir		seekdir			ck_fun		s@	DF S
436rewinddir	rewinddir		ck_fun		s%	DF
437closedir	closedir		ck_fun		is%	DF
438
439# Process control.
440
441fork		fork			ck_null		ist0
442wait		wait			ck_null		isT0
443waitpid		waitpid			ck_fun		isT@	S S
444system		system			ck_exec		imsT@	S? L
445exec		exec			ck_exec		dimsT@	S? L
446kill		kill			ck_fun		dimsT@	L
447getppid		getppid			ck_null		isT0
448getpgrp		getpgrp			ck_fun		isT%	S?
449setpgrp		setpgrp			ck_fun		isT@	S? S?
450getpriority	getpriority		ck_fun		isT@	S S
451setpriority	setpriority		ck_fun		isT@	S S S
452
453# Time calls.
454
455time		time			ck_null		isT0
456tms		times			ck_null		0
457localtime	localtime		ck_fun		t%	S?
458gmtime		gmtime			ck_fun		t%	S?
459alarm		alarm			ck_fun		istu%	S?
460sleep		sleep			ck_fun		isT%	S?
461
462# Shared memory.
463
464shmget		shmget			ck_fun		imst@	S S S
465shmctl		shmctl			ck_fun		imst@	S S S
466shmread		shmread			ck_fun		imst@	S S S S
467shmwrite	shmwrite		ck_fun		imst@	S S S S
468
469# Message passing.
470
471msgget		msgget			ck_fun		imst@	S S
472msgctl		msgctl			ck_fun		imst@	S S S
473msgsnd		msgsnd			ck_fun		imst@	S S S
474msgrcv		msgrcv			ck_fun		imst@	S S S S S
475
476# Semaphores.
477
478semop		semop			ck_fun		imst@	S S
479semget		semget			ck_fun		imst@	S S S
480semctl		semctl			ck_fun		imst@	S S S S
481
482# Eval.
483
484require		require			ck_require	du%	S?
485dofile		do "file"		ck_fun		d1	S
486hintseval	eval hints		ck_svconst	s$
487entereval	eval "string"		ck_eval		du%	S?
488leaveeval	eval "string" exit	ck_null		1	S
489entertry	eval {block}		ck_eval		d|
490leavetry	eval {block} exit	ck_null		@
491
492# Get system info.
493
494ghbyname	gethostbyname		ck_fun		%	S
495ghbyaddr	gethostbyaddr		ck_fun		@	S S
496ghostent	gethostent		ck_null		0
497gnbyname	getnetbyname		ck_fun		%	S
498gnbyaddr	getnetbyaddr		ck_fun		@	S S
499gnetent		getnetent		ck_null		0
500gpbyname	getprotobyname		ck_fun		%	S
501gpbynumber	getprotobynumber	ck_fun		@	S
502gprotoent	getprotoent		ck_null		0
503gsbyname	getservbyname		ck_fun		@	S S
504gsbyport	getservbyport		ck_fun		@	S S
505gservent	getservent		ck_null		0
506shostent	sethostent		ck_fun		is%	S
507snetent		setnetent		ck_fun		is%	S
508sprotoent	setprotoent		ck_fun		is%	S
509sservent	setservent		ck_fun		is%	S
510ehostent	endhostent		ck_null		is0
511enetent		endnetent		ck_null		is0
512eprotoent	endprotoent		ck_null		is0
513eservent	endservent		ck_null		is0
514gpwnam		getpwnam		ck_fun		%	S
515gpwuid		getpwuid		ck_fun		%	S
516gpwent		getpwent		ck_null		0
517spwent		setpwent		ck_null		is0
518epwent		endpwent		ck_null		is0
519ggrnam		getgrnam		ck_fun		%	S
520ggrgid		getgrgid		ck_fun		%	S
521ggrent		getgrent		ck_null		0
522sgrent		setgrent		ck_null		is0
523egrent		endgrent		ck_null		is0
524getlogin	getlogin		ck_null		st0
525
526# Miscellaneous.
527
528syscall		syscall			ck_fun		imst@	S L
529
530# For multi-threading
531lock		lock			ck_rfun		s%	R
532
533# For state support
534
535once		once			ck_null		|
536
537custom		unknown custom operator		ck_null		0
538
539# For smart dereference for each/keys/values
540reach		each on reference			ck_each		%	S
541rkeys		keys on reference			ck_each		t%	S
542rvalues		values on reference			ck_each		t%	S
543
544# For CORE:: subs
545coreargs	CORE:: subroutine	ck_null		$
546
547runcv		__SUB__			ck_null		s0
548
549# fc and \F
550fc		fc			ck_fun		fstu%	S?
551
552padcv		private subroutine	ck_null		d0
553introcv		private subroutine	ck_null		d0
554clonecv		private subroutine	ck_null		d0
555padrange	list of private variables	ck_null		d0
556