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