xref: /openbsd-src/gnu/usr.bin/perl/regen/opcodes (revision 91f110e064cd7c194e59e019b83bb7496c1c84d4)
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_open		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
220
221aeach		each on array		ck_each		%	A
222akeys		keys on array		ck_each		t%	A
223avalues		values on array		ck_each		t%	A
224
225# Hashes.
226
227each		each			ck_each		%	H
228values		values			ck_each		t%	H
229keys		keys			ck_each		t%	H
230delete		delete			ck_delete	%	S
231exists		exists			ck_exists	is%	S
232rv2hv		hash dereference	ck_rvconst	dt1
233helem		hash element		ck_null		s2	H S
234hslice		hash slice		ck_null		m@	H L
235
236# Explosives and implosives.
237
238unpack		unpack			ck_fun		u@	S S?
239pack		pack			ck_fun		fmst@	S L
240split		split			ck_split	t@	S S S
241join		join or string		ck_join		mst@	S L
242
243# List operators.
244
245list		list			ck_null		m@	L
246lslice		list slice		ck_null		2	H L L
247anonlist	anonymous list ([])	ck_fun		ms@	L
248anonhash	anonymous hash ({})	ck_fun		ms@	L
249
250splice		splice			ck_fun		m@	A S? S? L
251push		push			ck_fun		imsT@	A L
252pop		pop			ck_shift	s%	A?
253shift		shift			ck_shift	s%	A?
254unshift		unshift			ck_fun		imsT@	A L
255sort		sort			ck_sort		dm@	C? L
256reverse		reverse			ck_fun		mt@	L
257
258grepstart	grep			ck_grep		dm@	C L
259grepwhile	grep iterator		ck_null		dt|
260
261mapstart	map			ck_grep		dm@	C L
262mapwhile	map iterator		ck_null		dt|
263
264# Range stuff.
265
266range		flipflop		ck_null		|	S S
267flip		range (or flip)		ck_null		1	S S
268flop		range (or flop)		ck_null		1
269
270# Control.
271
272and		logical and (&&)		ck_null		|
273or		logical or (||)			ck_null		|
274xor		logical xor			ck_null		fs2	S S
275dor		defined or (//)			ck_null		|
276cond_expr	conditional expression		ck_null		d|
277andassign	logical and assignment (&&=)	ck_null		s|
278orassign	logical or assignment (||=)	ck_null		s|
279dorassign	defined or assignment (//=)	ck_null		s|
280
281method		method lookup		ck_method	d1
282entersub	subroutine entry	ck_subr		dmt1	L
283leavesub	subroutine exit		ck_null		1
284leavesublv	lvalue subroutine return	ck_null		1
285caller		caller			ck_fun		t%	S?
286warn		warn			ck_fun		imst@	L
287die		die			ck_die		dimst@	L
288reset		symbol reset		ck_fun		is%	S?
289
290lineseq		line sequence		ck_null		@
291nextstate	next statement		ck_null		s;
292dbstate		debug next statement	ck_null		s;
293unstack		iteration finalizer	ck_null		s0
294enter		block entry		ck_null		0
295leave		block exit		ck_null		@
296scope		block			ck_null		@
297enteriter	foreach loop entry	ck_null		d{
298iter		foreach loop iterator	ck_null		0
299enterloop	loop entry		ck_null		d{
300leaveloop	loop exit		ck_null		2
301return		return			ck_return	dm@	L
302last		last			ck_null		ds}
303next		next			ck_null		ds}
304redo		redo			ck_null		ds}
305dump		dump			ck_null		ds}
306goto		goto			ck_null		ds}
307exit		exit			ck_exit		ds%	S?
308method_named	method with known name	ck_null		d$
309
310entergiven	given()			ck_null		d|
311leavegiven	leave given block	ck_null		1
312enterwhen	when()			ck_null		d|
313leavewhen	leave when block	ck_null		1
314break		break			ck_null		0
315continue	continue		ck_null		0
316
317# I/O.
318
319open		open			ck_open		ismt@	F S? L
320close		close			ck_fun		is%	F?
321pipe_op		pipe			ck_fun		is@	F F
322
323fileno		fileno			ck_fun		ist%	F
324umask		umask			ck_fun		ist%	S?
325binmode		binmode			ck_fun		s@	F S?
326
327tie		tie			ck_fun		idms@	R S L
328untie		untie			ck_fun		is%	R
329tied		tied			ck_fun		s%	R
330dbmopen		dbmopen			ck_fun		is@	H S S
331dbmclose	dbmclose		ck_fun		is%	H
332
333sselect		select system call	ck_select	t@	S S S S
334select		select			ck_select	st@	F?
335
336getc		getc			ck_eof		st%	F?
337read		read			ck_fun		imst@	F R S S?
338enterwrite	write			ck_fun		dis%	F?
339leavewrite	write exit		ck_null		1
340
341prtf		printf			ck_listiob	ims@	F? L
342print		print			ck_listiob	ims@	F? L
343say		say			ck_listiob	ims@	F? L
344
345sysopen		sysopen			ck_fun		s@	F S S S?
346sysseek		sysseek			ck_fun		s@	F S S
347sysread		sysread			ck_fun		imst@	F R S S?
348syswrite	syswrite		ck_fun		imst@	F S S? S?
349
350eof		eof			ck_eof		is%	F?
351tell		tell			ck_tell		st%	F?
352seek		seek			ck_tell		s@	F S S
353# truncate really behaves as if it had both "S S" and "F S"
354truncate	truncate		ck_trunc	is@	S S
355
356fcntl		fcntl			ck_fun		st@	F S S
357ioctl		ioctl			ck_fun		st@	F S S
358flock		flock			ck_fun		isT@	F S
359
360# Sockets.  OP_IS_SOCKET wants them consecutive (so moved 1st 2)
361
362send		send			ck_fun		imst@	Fs S S S?
363recv		recv			ck_fun		imst@	Fs R S S
364
365socket		socket			ck_fun		is@	Fs S S S
366sockpair	socketpair		ck_fun		is@	Fs Fs S S S
367
368bind		bind			ck_fun		is@	Fs S
369connect		connect			ck_fun		is@	Fs S
370listen		listen			ck_fun		is@	Fs S
371accept		accept			ck_fun		ist@	Fs Fs
372shutdown	shutdown		ck_fun		ist@	Fs S
373
374gsockopt	getsockopt		ck_fun		is@	Fs S S
375ssockopt	setsockopt		ck_fun		is@	Fs S S S
376
377getsockname	getsockname		ck_fun		is%	Fs
378getpeername	getpeername		ck_fun		is%	Fs
379
380# Stat calls.  OP_IS_FILETEST wants them consecutive.
381
382lstat		lstat			ck_ftst		u-	F?
383stat		stat			ck_ftst		u-	F?
384ftrread		-R			ck_ftst		isu-	F-+
385ftrwrite	-W			ck_ftst		isu-	F-+
386ftrexec		-X			ck_ftst		isu-	F-+
387fteread		-r			ck_ftst		isu-	F-+
388ftewrite	-w			ck_ftst		isu-	F-+
389fteexec		-x			ck_ftst		isu-	F-+
390ftis		-e			ck_ftst		isu-	F-
391ftsize		-s			ck_ftst		istu-	F-
392ftmtime		-M			ck_ftst		stu-	F-
393ftatime		-A			ck_ftst		stu-	F-
394ftctime		-C			ck_ftst		stu-	F-
395ftrowned	-O			ck_ftst		isu-	F-
396fteowned	-o			ck_ftst		isu-	F-
397ftzero		-z			ck_ftst		isu-	F-
398ftsock		-S			ck_ftst		isu-	F-
399ftchr		-c			ck_ftst		isu-	F-
400ftblk		-b			ck_ftst		isu-	F-
401ftfile		-f			ck_ftst		isu-	F-
402ftdir		-d			ck_ftst		isu-	F-
403ftpipe		-p			ck_ftst		isu-	F-
404ftsuid		-u			ck_ftst		isu-	F-
405ftsgid		-g			ck_ftst		isu-	F-
406ftsvtx		-k			ck_ftst		isu-	F-
407ftlink		-l			ck_ftst		isu-	F-
408fttty		-t			ck_ftst		is-	F-
409fttext		-T			ck_ftst		isu-	F-
410ftbinary	-B			ck_ftst		isu-	F-
411
412# File calls.
413
414# chdir really behaves as if it had both "S?" and "F?"
415chdir		chdir			ck_trunc	isT%	S?
416chown		chown			ck_fun		imsT@	L
417chroot		chroot			ck_fun		isTu%	S?
418unlink		unlink			ck_fun		imsTu@	L
419chmod		chmod			ck_fun		imsT@	L
420utime		utime			ck_fun		imsT@	L
421rename		rename			ck_fun		isT@	S S
422link		link			ck_fun		isT@	S S
423symlink		symlink			ck_fun		isT@	S S
424readlink	readlink		ck_fun		stu%	S?
425mkdir		mkdir			ck_fun		isTu@	S? S?
426rmdir		rmdir			ck_fun		isTu%	S?
427
428# Directory calls.
429
430open_dir	opendir			ck_fun		is@	F S
431readdir		readdir			ck_fun		%	DF
432telldir		telldir			ck_fun		st%	DF
433seekdir		seekdir			ck_fun		s@	DF S
434rewinddir	rewinddir		ck_fun		s%	DF
435closedir	closedir		ck_fun		is%	DF
436
437# Process control.
438
439fork		fork			ck_null		ist0
440wait		wait			ck_null		isT0
441waitpid		waitpid			ck_fun		isT@	S S
442system		system			ck_exec		imsT@	S? L
443exec		exec			ck_exec		dimsT@	S? L
444kill		kill			ck_fun		dimsT@	L
445getppid		getppid			ck_null		isT0
446getpgrp		getpgrp			ck_fun		isT%	S?
447setpgrp		setpgrp			ck_fun		isT@	S? S?
448getpriority	getpriority		ck_fun		isT@	S S
449setpriority	setpriority		ck_fun		isT@	S S S
450
451# Time calls.
452
453time		time			ck_null		isT0
454tms		times			ck_null		0
455localtime	localtime		ck_fun		t%	S?
456gmtime		gmtime			ck_fun		t%	S?
457alarm		alarm			ck_fun		istu%	S?
458sleep		sleep			ck_fun		isT%	S?
459
460# Shared memory.
461
462shmget		shmget			ck_fun		imst@	S S S
463shmctl		shmctl			ck_fun		imst@	S S S
464shmread		shmread			ck_fun		imst@	S S S S
465shmwrite	shmwrite		ck_fun		imst@	S S S S
466
467# Message passing.
468
469msgget		msgget			ck_fun		imst@	S S
470msgctl		msgctl			ck_fun		imst@	S S S
471msgsnd		msgsnd			ck_fun		imst@	S S S
472msgrcv		msgrcv			ck_fun		imst@	S S S S S
473
474# Semaphores.
475
476semop		semop			ck_fun		imst@	S S
477semget		semget			ck_fun		imst@	S S S
478semctl		semctl			ck_fun		imst@	S S S S
479
480# Eval.
481
482require		require			ck_require	du%	S?
483dofile		do "file"		ck_fun		d1	S
484hintseval	eval hints		ck_svconst	s$
485entereval	eval "string"		ck_eval		du%	S?
486leaveeval	eval "string" exit	ck_null		1	S
487entertry	eval {block}		ck_eval		d|
488leavetry	eval {block} exit	ck_null		@
489
490# Get system info.
491
492ghbyname	gethostbyname		ck_fun		%	S
493ghbyaddr	gethostbyaddr		ck_fun		@	S S
494ghostent	gethostent		ck_null		0
495gnbyname	getnetbyname		ck_fun		%	S
496gnbyaddr	getnetbyaddr		ck_fun		@	S S
497gnetent		getnetent		ck_null		0
498gpbyname	getprotobyname		ck_fun		%	S
499gpbynumber	getprotobynumber	ck_fun		@	S
500gprotoent	getprotoent		ck_null		0
501gsbyname	getservbyname		ck_fun		@	S S
502gsbyport	getservbyport		ck_fun		@	S S
503gservent	getservent		ck_null		0
504shostent	sethostent		ck_fun		is%	S
505snetent		setnetent		ck_fun		is%	S
506sprotoent	setprotoent		ck_fun		is%	S
507sservent	setservent		ck_fun		is%	S
508ehostent	endhostent		ck_null		is0
509enetent		endnetent		ck_null		is0
510eprotoent	endprotoent		ck_null		is0
511eservent	endservent		ck_null		is0
512gpwnam		getpwnam		ck_fun		%	S
513gpwuid		getpwuid		ck_fun		%	S
514gpwent		getpwent		ck_null		0
515spwent		setpwent		ck_null		is0
516epwent		endpwent		ck_null		is0
517ggrnam		getgrnam		ck_fun		%	S
518ggrgid		getgrgid		ck_fun		%	S
519ggrent		getgrent		ck_null		0
520sgrent		setgrent		ck_null		is0
521egrent		endgrent		ck_null		is0
522getlogin	getlogin		ck_null		st0
523
524# Miscellaneous.
525
526syscall		syscall			ck_fun		imst@	S L
527
528# For multi-threading
529lock		lock			ck_rfun		s%	R
530
531# For state support
532
533once		once			ck_null		|
534
535custom		unknown custom operator		ck_null		0
536
537# For smart dereference for each/keys/values
538reach		each on reference			ck_each		%	S
539rkeys		keys on reference			ck_each		t%	S
540rvalues		values on reference			ck_each		t%	S
541
542# For CORE:: subs
543coreargs	CORE:: subroutine	ck_null		$
544
545runcv		__SUB__			ck_null		s0
546
547# fc and \F
548fc		fc			ck_fun		fstu%	S?
549
550padcv		private subroutine	ck_null		d0
551introcv		private subroutine	ck_null		d0
552clonecv		private subroutine	ck_null		d0
553padrange	list of private variables	ck_null		d0
554