xref: /dflybsd-src/contrib/gcc-8.0/gcc/rtl.def (revision 38fd149817dfbff97799f62fcb70be98c4e32523)
1*38fd1498Szrj/* This file contains the definitions and documentation for the
2*38fd1498Szrj   Register Transfer Expressions (rtx's) that make up the
3*38fd1498Szrj   Register Transfer Language (rtl) used in the Back End of the GNU compiler.
4*38fd1498Szrj   Copyright (C) 1987-2018 Free Software Foundation, Inc.
5*38fd1498Szrj
6*38fd1498SzrjThis file is part of GCC.
7*38fd1498Szrj
8*38fd1498SzrjGCC is free software; you can redistribute it and/or modify it under
9*38fd1498Szrjthe terms of the GNU General Public License as published by the Free
10*38fd1498SzrjSoftware Foundation; either version 3, or (at your option) any later
11*38fd1498Szrjversion.
12*38fd1498Szrj
13*38fd1498SzrjGCC is distributed in the hope that it will be useful, but WITHOUT ANY
14*38fd1498SzrjWARRANTY; without even the implied warranty of MERCHANTABILITY or
15*38fd1498SzrjFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16*38fd1498Szrjfor more details.
17*38fd1498Szrj
18*38fd1498SzrjYou should have received a copy of the GNU General Public License
19*38fd1498Szrjalong with GCC; see the file COPYING3.  If not see
20*38fd1498Szrj<http://www.gnu.org/licenses/>.  */
21*38fd1498Szrj
22*38fd1498Szrj
23*38fd1498Szrj/* Expression definitions and descriptions for all targets are in this file.
24*38fd1498Szrj   Some will not be used for some targets.
25*38fd1498Szrj
26*38fd1498Szrj   The fields in the cpp macro call "DEF_RTL_EXPR()"
27*38fd1498Szrj   are used to create declarations in the C source of the compiler.
28*38fd1498Szrj
29*38fd1498Szrj   The fields are:
30*38fd1498Szrj
31*38fd1498Szrj   1.  The internal name of the rtx used in the C source.
32*38fd1498Szrj   It is a tag in the enumeration "enum rtx_code" defined in "rtl.h".
33*38fd1498Szrj   By convention these are in UPPER_CASE.
34*38fd1498Szrj
35*38fd1498Szrj   2.  The name of the rtx in the external ASCII format read by
36*38fd1498Szrj   read_rtx(), and printed by print_rtx().
37*38fd1498Szrj   These names are stored in rtx_name[].
38*38fd1498Szrj   By convention these are the internal (field 1) names in lower_case.
39*38fd1498Szrj
40*38fd1498Szrj   3.  The print format, and type of each rtx->u.fld[] (field) in this rtx.
41*38fd1498Szrj   These formats are stored in rtx_format[].
42*38fd1498Szrj   The meaning of the formats is documented in front of this array in rtl.c
43*38fd1498Szrj
44*38fd1498Szrj   4.  The class of the rtx.  These are stored in rtx_class and are accessed
45*38fd1498Szrj   via the GET_RTX_CLASS macro.  They are defined as follows:
46*38fd1498Szrj
47*38fd1498Szrj     RTX_CONST_OBJ
48*38fd1498Szrj         an rtx code that can be used to represent a constant object
49*38fd1498Szrj         (e.g, CONST_INT)
50*38fd1498Szrj     RTX_OBJ
51*38fd1498Szrj         an rtx code that can be used to represent an object (e.g, REG, MEM)
52*38fd1498Szrj     RTX_COMPARE
53*38fd1498Szrj         an rtx code for a comparison (e.g, LT, GT)
54*38fd1498Szrj     RTX_COMM_COMPARE
55*38fd1498Szrj         an rtx code for a commutative comparison (e.g, EQ, NE, ORDERED)
56*38fd1498Szrj     RTX_UNARY
57*38fd1498Szrj         an rtx code for a unary arithmetic expression (e.g, NEG, NOT)
58*38fd1498Szrj     RTX_COMM_ARITH
59*38fd1498Szrj         an rtx code for a commutative binary operation (e.g,, PLUS, MULT)
60*38fd1498Szrj     RTX_TERNARY
61*38fd1498Szrj         an rtx code for a non-bitfield three input operation (IF_THEN_ELSE)
62*38fd1498Szrj     RTX_BIN_ARITH
63*38fd1498Szrj         an rtx code for a non-commutative binary operation (e.g., MINUS, DIV)
64*38fd1498Szrj     RTX_BITFIELD_OPS
65*38fd1498Szrj         an rtx code for a bit-field operation (ZERO_EXTRACT, SIGN_EXTRACT)
66*38fd1498Szrj     RTX_INSN
67*38fd1498Szrj         an rtx code for a machine insn (INSN, JUMP_INSN, CALL_INSN) or
68*38fd1498Szrj	 data that will be output as assembly pseudo-ops (DEBUG_INSN)
69*38fd1498Szrj     RTX_MATCH
70*38fd1498Szrj         an rtx code for something that matches in insns (e.g, MATCH_DUP)
71*38fd1498Szrj     RTX_AUTOINC
72*38fd1498Szrj         an rtx code for autoincrement addressing modes (e.g. POST_DEC)
73*38fd1498Szrj     RTX_EXTRA
74*38fd1498Szrj         everything else
75*38fd1498Szrj
76*38fd1498Szrj   All of the expressions that appear only in machine descriptions,
77*38fd1498Szrj   not in RTL used by the compiler itself, are at the end of the file.  */
78*38fd1498Szrj
79*38fd1498Szrj/* Unknown, or no such operation; the enumeration constant should have
80*38fd1498Szrj   value zero.  */
81*38fd1498SzrjDEF_RTL_EXPR(UNKNOWN, "UnKnown", "*", RTX_EXTRA)
82*38fd1498Szrj
83*38fd1498Szrj/* Used in the cselib routines to describe a value.  Objects of this
84*38fd1498Szrj   kind are only allocated in cselib.c, in an alloc pool instead of in
85*38fd1498Szrj   GC memory.  The only operand of a VALUE is a cselib_val.
86*38fd1498Szrj   var-tracking requires this to have a distinct integral value from
87*38fd1498Szrj   DECL codes in trees.  */
88*38fd1498SzrjDEF_RTL_EXPR(VALUE, "value", "0", RTX_OBJ)
89*38fd1498Szrj
90*38fd1498Szrj/* The RTL generated for a DEBUG_EXPR_DECL.  It links back to the
91*38fd1498Szrj   DEBUG_EXPR_DECL in the first operand.  */
92*38fd1498SzrjDEF_RTL_EXPR(DEBUG_EXPR, "debug_expr", "0", RTX_OBJ)
93*38fd1498Szrj
94*38fd1498Szrj/* ---------------------------------------------------------------------
95*38fd1498Szrj   Expressions used in constructing lists.
96*38fd1498Szrj   --------------------------------------------------------------------- */
97*38fd1498Szrj
98*38fd1498Szrj/* A linked list of expressions.  */
99*38fd1498SzrjDEF_RTL_EXPR(EXPR_LIST, "expr_list", "ee", RTX_EXTRA)
100*38fd1498Szrj
101*38fd1498Szrj/* A linked list of instructions.
102*38fd1498Szrj   The insns are represented in print by their uids.  */
103*38fd1498SzrjDEF_RTL_EXPR(INSN_LIST, "insn_list", "ue", RTX_EXTRA)
104*38fd1498Szrj
105*38fd1498Szrj/* A linked list of integers.  */
106*38fd1498SzrjDEF_RTL_EXPR(INT_LIST, "int_list", "ie", RTX_EXTRA)
107*38fd1498Szrj
108*38fd1498Szrj/* SEQUENCE is used in late passes of the compiler to group insns for
109*38fd1498Szrj   one reason or another.
110*38fd1498Szrj
111*38fd1498Szrj   For example, after delay slot filling, branch instructions with filled
112*38fd1498Szrj   delay slots are represented as a SEQUENCE of length 1 + n_delay_slots,
113*38fd1498Szrj   with the branch instruction in XEXPVEC(seq, 0, 0) and the instructions
114*38fd1498Szrj   occupying the delay slots in the remaining XEXPVEC slots.
115*38fd1498Szrj
116*38fd1498Szrj   Another place where a SEQUENCE may appear, is in REG_FRAME_RELATED_EXPR
117*38fd1498Szrj   notes, to express complex operations that are not obvious from the insn
118*38fd1498Szrj   to which the REG_FRAME_RELATED_EXPR note is attached.  In this usage of
119*38fd1498Szrj   SEQUENCE, the sequence vector slots do not hold real instructions but
120*38fd1498Szrj   only pseudo-instructions that can be translated to DWARF CFA expressions.
121*38fd1498Szrj
122*38fd1498Szrj   Some back ends also use SEQUENCE to group insns in bundles.
123*38fd1498Szrj
124*38fd1498Szrj   Much of the compiler infrastructure is not prepared to handle SEQUENCE
125*38fd1498Szrj   objects.  Only passes after pass_free_cfg are expected to handle them.  */
126*38fd1498SzrjDEF_RTL_EXPR(SEQUENCE, "sequence", "E", RTX_EXTRA)
127*38fd1498Szrj
128*38fd1498Szrj/* Represents a non-global base address.  This is only used in alias.c.  */
129*38fd1498SzrjDEF_RTL_EXPR(ADDRESS, "address", "i", RTX_EXTRA)
130*38fd1498Szrj
131*38fd1498Szrj/* ----------------------------------------------------------------------
132*38fd1498Szrj   Expression types used for things in the instruction chain.
133*38fd1498Szrj
134*38fd1498Szrj   All formats must start with "uu" to handle the chain.
135*38fd1498Szrj   Each insn expression holds an rtl instruction and its semantics
136*38fd1498Szrj   during back-end processing.
137*38fd1498Szrj   See macros in "rtl.h" for the meaning of each rtx->u.fld[].
138*38fd1498Szrj
139*38fd1498Szrj   ---------------------------------------------------------------------- */
140*38fd1498Szrj
141*38fd1498Szrj/* An annotation for variable assignment tracking.  */
142*38fd1498SzrjDEF_RTL_EXPR(DEBUG_INSN, "debug_insn", "uuBeiie", RTX_INSN)
143*38fd1498Szrj
144*38fd1498Szrj/* An instruction that cannot jump.  */
145*38fd1498SzrjDEF_RTL_EXPR(INSN, "insn", "uuBeiie", RTX_INSN)
146*38fd1498Szrj
147*38fd1498Szrj/* An instruction that can possibly jump.
148*38fd1498Szrj   Fields ( rtx->u.fld[] ) have exact same meaning as INSN's.  */
149*38fd1498SzrjDEF_RTL_EXPR(JUMP_INSN, "jump_insn", "uuBeiie0", RTX_INSN)
150*38fd1498Szrj
151*38fd1498Szrj/* An instruction that can possibly call a subroutine
152*38fd1498Szrj   but which will not change which instruction comes next
153*38fd1498Szrj   in the current function.
154*38fd1498Szrj   Field ( rtx->u.fld[8] ) is CALL_INSN_FUNCTION_USAGE.
155*38fd1498Szrj   All other fields ( rtx->u.fld[] ) have exact same meaning as INSN's.  */
156*38fd1498SzrjDEF_RTL_EXPR(CALL_INSN, "call_insn", "uuBeiiee", RTX_INSN)
157*38fd1498Szrj
158*38fd1498Szrj/* Placeholder for tablejump JUMP_INSNs.  The pattern of this kind
159*38fd1498Szrj   of rtx is always either an ADDR_VEC or an ADDR_DIFF_VEC.  These
160*38fd1498Szrj   placeholders do not appear as real instructions inside a basic
161*38fd1498Szrj   block, but are considered active_insn_p instructions for historical
162*38fd1498Szrj   reasons, when jump table data was represented with JUMP_INSNs.  */
163*38fd1498SzrjDEF_RTL_EXPR(JUMP_TABLE_DATA, "jump_table_data", "uuBe0000", RTX_INSN)
164*38fd1498Szrj
165*38fd1498Szrj/* A marker that indicates that control will not flow through.  */
166*38fd1498SzrjDEF_RTL_EXPR(BARRIER, "barrier", "uu00000", RTX_EXTRA)
167*38fd1498Szrj
168*38fd1498Szrj/* Holds a label that is followed by instructions.
169*38fd1498Szrj   Operand:
170*38fd1498Szrj   3: is used in jump.c for the use-count of the label.
171*38fd1498Szrj   4: is used in the sh backend.
172*38fd1498Szrj   5: is a number that is unique in the entire compilation.
173*38fd1498Szrj   6: is the user-given name of the label, if any.  */
174*38fd1498SzrjDEF_RTL_EXPR(CODE_LABEL, "code_label", "uuB00is", RTX_EXTRA)
175*38fd1498Szrj
176*38fd1498Szrj/* Say where in the code a source line starts, for symbol table's sake.
177*38fd1498Szrj   Operand:
178*38fd1498Szrj   3: note-specific data
179*38fd1498Szrj   4: enum insn_note
180*38fd1498Szrj   5: unique number if insn_note == note_insn_deleted_label.  */
181*38fd1498SzrjDEF_RTL_EXPR(NOTE, "note", "uuB0ni", RTX_EXTRA)
182*38fd1498Szrj
183*38fd1498Szrj/* ----------------------------------------------------------------------
184*38fd1498Szrj   Top level constituents of INSN, JUMP_INSN and CALL_INSN.
185*38fd1498Szrj   ---------------------------------------------------------------------- */
186*38fd1498Szrj
187*38fd1498Szrj/* Conditionally execute code.
188*38fd1498Szrj   Operand 0 is the condition that if true, the code is executed.
189*38fd1498Szrj   Operand 1 is the code to be executed (typically a SET).
190*38fd1498Szrj
191*38fd1498Szrj   Semantics are that there are no side effects if the condition
192*38fd1498Szrj   is false.  This pattern is created automatically by the if_convert
193*38fd1498Szrj   pass run after reload or by target-specific splitters.  */
194*38fd1498SzrjDEF_RTL_EXPR(COND_EXEC, "cond_exec", "ee", RTX_EXTRA)
195*38fd1498Szrj
196*38fd1498Szrj/* Several operations to be done in parallel (perhaps under COND_EXEC).  */
197*38fd1498SzrjDEF_RTL_EXPR(PARALLEL, "parallel", "E", RTX_EXTRA)
198*38fd1498Szrj
199*38fd1498Szrj/* A string that is passed through to the assembler as input.
200*38fd1498Szrj     One can obviously pass comments through by using the
201*38fd1498Szrj     assembler comment syntax.
202*38fd1498Szrj     These occur in an insn all by themselves as the PATTERN.
203*38fd1498Szrj     They also appear inside an ASM_OPERANDS
204*38fd1498Szrj     as a convenient way to hold a string.  */
205*38fd1498SzrjDEF_RTL_EXPR(ASM_INPUT, "asm_input", "si", RTX_EXTRA)
206*38fd1498Szrj
207*38fd1498Szrj/* An assembler instruction with operands.
208*38fd1498Szrj   1st operand is the instruction template.
209*38fd1498Szrj   2nd operand is the constraint for the output.
210*38fd1498Szrj   3rd operand is the number of the output this expression refers to.
211*38fd1498Szrj     When an insn stores more than one value, a separate ASM_OPERANDS
212*38fd1498Szrj     is made for each output; this integer distinguishes them.
213*38fd1498Szrj   4th is a vector of values of input operands.
214*38fd1498Szrj   5th is a vector of modes and constraints for the input operands.
215*38fd1498Szrj     Each element is an ASM_INPUT containing a constraint string
216*38fd1498Szrj     and whose mode indicates the mode of the input operand.
217*38fd1498Szrj   6th is a vector of labels that may be branched to by the asm.
218*38fd1498Szrj   7th is the source line number.  */
219*38fd1498SzrjDEF_RTL_EXPR(ASM_OPERANDS, "asm_operands", "ssiEEEi", RTX_EXTRA)
220*38fd1498Szrj
221*38fd1498Szrj/* A machine-specific operation.
222*38fd1498Szrj   1st operand is a vector of operands being used by the operation so that
223*38fd1498Szrj     any needed reloads can be done.
224*38fd1498Szrj   2nd operand is a unique value saying which of a number of machine-specific
225*38fd1498Szrj     operations is to be performed.
226*38fd1498Szrj   (Note that the vector must be the first operand because of the way that
227*38fd1498Szrj   genrecog.c record positions within an insn.)
228*38fd1498Szrj
229*38fd1498Szrj   UNSPEC can occur all by itself in a PATTERN, as a component of a PARALLEL,
230*38fd1498Szrj   or inside an expression.
231*38fd1498Szrj   UNSPEC by itself or as a component of a PARALLEL
232*38fd1498Szrj   is currently considered not deletable.
233*38fd1498Szrj
234*38fd1498Szrj   FIXME: Replace all uses of UNSPEC that appears by itself or as a component
235*38fd1498Szrj   of a PARALLEL with USE.
236*38fd1498Szrj   */
237*38fd1498SzrjDEF_RTL_EXPR(UNSPEC, "unspec", "Ei", RTX_EXTRA)
238*38fd1498Szrj
239*38fd1498Szrj/* Similar, but a volatile operation and one which may trap.  */
240*38fd1498SzrjDEF_RTL_EXPR(UNSPEC_VOLATILE, "unspec_volatile", "Ei", RTX_EXTRA)
241*38fd1498Szrj
242*38fd1498Szrj/* ----------------------------------------------------------------------
243*38fd1498Szrj   Table jump addresses.
244*38fd1498Szrj   ---------------------------------------------------------------------- */
245*38fd1498Szrj
246*38fd1498Szrj/* Vector of addresses, stored as full words.
247*38fd1498Szrj   Each element is a LABEL_REF to a CODE_LABEL whose address we want.  */
248*38fd1498SzrjDEF_RTL_EXPR(ADDR_VEC, "addr_vec", "E", RTX_EXTRA)
249*38fd1498Szrj
250*38fd1498Szrj/* Vector of address differences X0 - BASE, X1 - BASE, ...
251*38fd1498Szrj   First operand is BASE; the vector contains the X's.
252*38fd1498Szrj   The machine mode of this rtx says how much space to leave
253*38fd1498Szrj   for each difference and is adjusted by branch shortening if
254*38fd1498Szrj   CASE_VECTOR_SHORTEN_MODE is defined.
255*38fd1498Szrj   The third and fourth operands store the target labels with the
256*38fd1498Szrj   minimum and maximum addresses respectively.
257*38fd1498Szrj   The fifth operand stores flags for use by branch shortening.
258*38fd1498Szrj  Set at the start of shorten_branches:
259*38fd1498Szrj   min_align: the minimum alignment for any of the target labels.
260*38fd1498Szrj   base_after_vec: true iff BASE is after the ADDR_DIFF_VEC.
261*38fd1498Szrj   min_after_vec: true iff minimum addr target label is after the ADDR_DIFF_VEC.
262*38fd1498Szrj   max_after_vec: true iff maximum addr target label is after the ADDR_DIFF_VEC.
263*38fd1498Szrj   min_after_base: true iff minimum address target label is after BASE.
264*38fd1498Szrj   max_after_base: true iff maximum address target label is after BASE.
265*38fd1498Szrj  Set by the actual branch shortening process:
266*38fd1498Szrj   offset_unsigned: true iff offsets have to be treated as unsigned.
267*38fd1498Szrj   scale: scaling that is necessary to make offsets fit into the mode.
268*38fd1498Szrj
269*38fd1498Szrj   The third, fourth and fifth operands are only valid when
270*38fd1498Szrj   CASE_VECTOR_SHORTEN_MODE is defined, and only in an optimizing
271*38fd1498Szrj   compilation.  */
272*38fd1498SzrjDEF_RTL_EXPR(ADDR_DIFF_VEC, "addr_diff_vec", "eEee0", RTX_EXTRA)
273*38fd1498Szrj
274*38fd1498Szrj/* Memory prefetch, with attributes supported on some targets.
275*38fd1498Szrj   Operand 1 is the address of the memory to fetch.
276*38fd1498Szrj   Operand 2 is 1 for a write access, 0 otherwise.
277*38fd1498Szrj   Operand 3 is the level of temporal locality; 0 means there is no
278*38fd1498Szrj   temporal locality and 1, 2, and 3 are for increasing levels of temporal
279*38fd1498Szrj   locality.
280*38fd1498Szrj
281*38fd1498Szrj   The attributes specified by operands 2 and 3 are ignored for targets
282*38fd1498Szrj   whose prefetch instructions do not support them.  */
283*38fd1498SzrjDEF_RTL_EXPR(PREFETCH, "prefetch", "eee", RTX_EXTRA)
284*38fd1498Szrj
285*38fd1498Szrj/* ----------------------------------------------------------------------
286*38fd1498Szrj   At the top level of an instruction (perhaps under PARALLEL).
287*38fd1498Szrj   ---------------------------------------------------------------------- */
288*38fd1498Szrj
289*38fd1498Szrj/* Assignment.
290*38fd1498Szrj   Operand 1 is the location (REG, MEM, PC, CC0 or whatever) assigned to.
291*38fd1498Szrj   Operand 2 is the value stored there.
292*38fd1498Szrj   ALL assignment must use SET.
293*38fd1498Szrj   Instructions that do multiple assignments must use multiple SET,
294*38fd1498Szrj   under PARALLEL.  */
295*38fd1498SzrjDEF_RTL_EXPR(SET, "set", "ee", RTX_EXTRA)
296*38fd1498Szrj
297*38fd1498Szrj/* Indicate something is used in a way that we don't want to explain.
298*38fd1498Szrj   For example, subroutine calls will use the register
299*38fd1498Szrj   in which the static chain is passed.
300*38fd1498Szrj
301*38fd1498Szrj   USE can not appear as an operand of other rtx except for PARALLEL.
302*38fd1498Szrj   USE is not deletable, as it indicates that the operand
303*38fd1498Szrj   is used in some unknown way.  */
304*38fd1498SzrjDEF_RTL_EXPR(USE, "use", "e", RTX_EXTRA)
305*38fd1498Szrj
306*38fd1498Szrj/* Indicate something is clobbered in a way that we don't want to explain.
307*38fd1498Szrj   For example, subroutine calls will clobber some physical registers
308*38fd1498Szrj   (the ones that are by convention not saved).
309*38fd1498Szrj
310*38fd1498Szrj   CLOBBER can not appear as an operand of other rtx except for PARALLEL.
311*38fd1498Szrj   CLOBBER of a hard register appearing by itself (not within PARALLEL)
312*38fd1498Szrj   is considered undeletable before reload.  */
313*38fd1498SzrjDEF_RTL_EXPR(CLOBBER, "clobber", "e", RTX_EXTRA)
314*38fd1498Szrj
315*38fd1498Szrj/* Call a subroutine.
316*38fd1498Szrj   Operand 1 is the address to call.
317*38fd1498Szrj   Operand 2 is the number of arguments.  */
318*38fd1498Szrj
319*38fd1498SzrjDEF_RTL_EXPR(CALL, "call", "ee", RTX_EXTRA)
320*38fd1498Szrj
321*38fd1498Szrj/* Return from a subroutine.  */
322*38fd1498Szrj
323*38fd1498SzrjDEF_RTL_EXPR(RETURN, "return", "", RTX_EXTRA)
324*38fd1498Szrj
325*38fd1498Szrj/* Like RETURN, but truly represents only a function return, while
326*38fd1498Szrj   RETURN may represent an insn that also performs other functions
327*38fd1498Szrj   of the function epilogue.  Like RETURN, this may also occur in
328*38fd1498Szrj   conditional jumps.  */
329*38fd1498SzrjDEF_RTL_EXPR(SIMPLE_RETURN, "simple_return", "", RTX_EXTRA)
330*38fd1498Szrj
331*38fd1498Szrj/* Special for EH return from subroutine.  */
332*38fd1498Szrj
333*38fd1498SzrjDEF_RTL_EXPR(EH_RETURN, "eh_return", "", RTX_EXTRA)
334*38fd1498Szrj
335*38fd1498Szrj/* Conditional trap.
336*38fd1498Szrj   Operand 1 is the condition.
337*38fd1498Szrj   Operand 2 is the trap code.
338*38fd1498Szrj   For an unconditional trap, make the condition (const_int 1).  */
339*38fd1498SzrjDEF_RTL_EXPR(TRAP_IF, "trap_if", "ee", RTX_EXTRA)
340*38fd1498Szrj
341*38fd1498Szrj/* ----------------------------------------------------------------------
342*38fd1498Szrj   Primitive values for use in expressions.
343*38fd1498Szrj   ---------------------------------------------------------------------- */
344*38fd1498Szrj
345*38fd1498Szrj/* numeric integer constant */
346*38fd1498SzrjDEF_RTL_EXPR(CONST_INT, "const_int", "w", RTX_CONST_OBJ)
347*38fd1498Szrj
348*38fd1498Szrj/* numeric integer constant */
349*38fd1498SzrjDEF_RTL_EXPR(CONST_WIDE_INT, "const_wide_int", "", RTX_CONST_OBJ)
350*38fd1498Szrj
351*38fd1498Szrj/* An rtx representation of a poly_wide_int.  */
352*38fd1498SzrjDEF_RTL_EXPR(CONST_POLY_INT, "const_poly_int", "", RTX_CONST_OBJ)
353*38fd1498Szrj
354*38fd1498Szrj/* fixed-point constant */
355*38fd1498SzrjDEF_RTL_EXPR(CONST_FIXED, "const_fixed", "www", RTX_CONST_OBJ)
356*38fd1498Szrj
357*38fd1498Szrj/* numeric floating point or integer constant.  If the mode is
358*38fd1498Szrj   VOIDmode it is an int otherwise it has a floating point mode and a
359*38fd1498Szrj   floating point value.  Operands hold the value.  They are all 'w'
360*38fd1498Szrj   and there may be from 2 to 6; see real.h.  */
361*38fd1498SzrjDEF_RTL_EXPR(CONST_DOUBLE, "const_double", CONST_DOUBLE_FORMAT, RTX_CONST_OBJ)
362*38fd1498Szrj
363*38fd1498Szrj/* Describes a vector constant.  */
364*38fd1498SzrjDEF_RTL_EXPR(CONST_VECTOR, "const_vector", "E", RTX_CONST_OBJ)
365*38fd1498Szrj
366*38fd1498Szrj/* String constant.  Used for attributes in machine descriptions and
367*38fd1498Szrj   for special cases in DWARF2 debug output.  NOT used for source-
368*38fd1498Szrj   language string constants.  */
369*38fd1498SzrjDEF_RTL_EXPR(CONST_STRING, "const_string", "s", RTX_OBJ)
370*38fd1498Szrj
371*38fd1498Szrj/* This is used to encapsulate an expression whose value is constant
372*38fd1498Szrj   (such as the sum of a SYMBOL_REF and a CONST_INT) so that it will be
373*38fd1498Szrj   recognized as a constant operand rather than by arithmetic instructions.  */
374*38fd1498Szrj
375*38fd1498SzrjDEF_RTL_EXPR(CONST, "const", "e", RTX_CONST_OBJ)
376*38fd1498Szrj
377*38fd1498Szrj/* program counter.  Ordinary jumps are represented
378*38fd1498Szrj   by a SET whose first operand is (PC).  */
379*38fd1498SzrjDEF_RTL_EXPR(PC, "pc", "", RTX_OBJ)
380*38fd1498Szrj
381*38fd1498Szrj/* A register.  The "operand" is the register number, accessed with
382*38fd1498Szrj   the REGNO macro.  If this number is less than FIRST_PSEUDO_REGISTER
383*38fd1498Szrj   than a hardware register is being referred to.  The second operand
384*38fd1498Szrj   points to a reg_attrs structure.
385*38fd1498Szrj   This rtx needs to have as many (or more) fields as a MEM, since we
386*38fd1498Szrj   can change REG rtx's into MEMs during reload.  */
387*38fd1498SzrjDEF_RTL_EXPR(REG, "reg", "r", RTX_OBJ)
388*38fd1498Szrj
389*38fd1498Szrj/* A scratch register.  This represents a register used only within a
390*38fd1498Szrj   single insn.  It will be replaced by a REG during register allocation
391*38fd1498Szrj   or reload unless the constraint indicates that the register won't be
392*38fd1498Szrj   needed, in which case it can remain a SCRATCH.  */
393*38fd1498SzrjDEF_RTL_EXPR(SCRATCH, "scratch", "", RTX_OBJ)
394*38fd1498Szrj
395*38fd1498Szrj/* A reference to a part of another value.  The first operand is the
396*38fd1498Szrj   complete value and the second is the byte offset of the selected part.   */
397*38fd1498SzrjDEF_RTL_EXPR(SUBREG, "subreg", "ep", RTX_EXTRA)
398*38fd1498Szrj
399*38fd1498Szrj/* This one-argument rtx is used for move instructions
400*38fd1498Szrj   that are guaranteed to alter only the low part of a destination.
401*38fd1498Szrj   Thus, (SET (SUBREG:HI (REG...)) (MEM:HI ...))
402*38fd1498Szrj   has an unspecified effect on the high part of REG,
403*38fd1498Szrj   but (SET (STRICT_LOW_PART (SUBREG:HI (REG...))) (MEM:HI ...))
404*38fd1498Szrj   is guaranteed to alter only the bits of REG that are in HImode.
405*38fd1498Szrj
406*38fd1498Szrj   The actual instruction used is probably the same in both cases,
407*38fd1498Szrj   but the register constraints may be tighter when STRICT_LOW_PART
408*38fd1498Szrj   is in use.  */
409*38fd1498Szrj
410*38fd1498SzrjDEF_RTL_EXPR(STRICT_LOW_PART, "strict_low_part", "e", RTX_EXTRA)
411*38fd1498Szrj
412*38fd1498Szrj/* (CONCAT a b) represents the virtual concatenation of a and b
413*38fd1498Szrj   to make a value that has as many bits as a and b put together.
414*38fd1498Szrj   This is used for complex values.  Normally it appears only
415*38fd1498Szrj   in DECL_RTLs and during RTL generation, but not in the insn chain.  */
416*38fd1498SzrjDEF_RTL_EXPR(CONCAT, "concat", "ee", RTX_OBJ)
417*38fd1498Szrj
418*38fd1498Szrj/* (CONCATN [a1 a2 ... an]) represents the virtual concatenation of
419*38fd1498Szrj   all An to make a value.  This is an extension of CONCAT to larger
420*38fd1498Szrj   number of components.  Like CONCAT, it should not appear in the
421*38fd1498Szrj   insn chain.  Every element of the CONCATN is the same size.  */
422*38fd1498SzrjDEF_RTL_EXPR(CONCATN, "concatn", "E", RTX_OBJ)
423*38fd1498Szrj
424*38fd1498Szrj/* A memory location; operand is the address.  The second operand is the
425*38fd1498Szrj   alias set to which this MEM belongs.  We use `0' instead of `w' for this
426*38fd1498Szrj   field so that the field need not be specified in machine descriptions.  */
427*38fd1498SzrjDEF_RTL_EXPR(MEM, "mem", "e0", RTX_OBJ)
428*38fd1498Szrj
429*38fd1498Szrj/* Reference to an assembler label in the code for this function.
430*38fd1498Szrj   The operand is a CODE_LABEL found in the insn chain.  */
431*38fd1498SzrjDEF_RTL_EXPR(LABEL_REF, "label_ref", "u", RTX_CONST_OBJ)
432*38fd1498Szrj
433*38fd1498Szrj/* Reference to a named label:
434*38fd1498Szrj   Operand 0: label name
435*38fd1498Szrj   Operand 1: tree from which this symbol is derived, or null.
436*38fd1498Szrj   This is either a DECL node, or some kind of constant.  */
437*38fd1498SzrjDEF_RTL_EXPR(SYMBOL_REF, "symbol_ref", "s0", RTX_CONST_OBJ)
438*38fd1498Szrj
439*38fd1498Szrj/* The condition code register is represented, in our imagination,
440*38fd1498Szrj   as a register holding a value that can be compared to zero.
441*38fd1498Szrj   In fact, the machine has already compared them and recorded the
442*38fd1498Szrj   results; but instructions that look at the condition code
443*38fd1498Szrj   pretend to be looking at the entire value and comparing it.  */
444*38fd1498SzrjDEF_RTL_EXPR(CC0, "cc0", "", RTX_OBJ)
445*38fd1498Szrj
446*38fd1498Szrj/* ----------------------------------------------------------------------
447*38fd1498Szrj   Expressions for operators in an rtl pattern
448*38fd1498Szrj   ---------------------------------------------------------------------- */
449*38fd1498Szrj
450*38fd1498Szrj/* if_then_else.  This is used in representing ordinary
451*38fd1498Szrj   conditional jump instructions.
452*38fd1498Szrj     Operand:
453*38fd1498Szrj     0:  condition
454*38fd1498Szrj     1:  then expr
455*38fd1498Szrj     2:  else expr */
456*38fd1498SzrjDEF_RTL_EXPR(IF_THEN_ELSE, "if_then_else", "eee", RTX_TERNARY)
457*38fd1498Szrj
458*38fd1498Szrj/* Comparison, produces a condition code result.  */
459*38fd1498SzrjDEF_RTL_EXPR(COMPARE, "compare", "ee", RTX_BIN_ARITH)
460*38fd1498Szrj
461*38fd1498Szrj/* plus */
462*38fd1498SzrjDEF_RTL_EXPR(PLUS, "plus", "ee", RTX_COMM_ARITH)
463*38fd1498Szrj
464*38fd1498Szrj/* Operand 0 minus operand 1.  */
465*38fd1498SzrjDEF_RTL_EXPR(MINUS, "minus", "ee", RTX_BIN_ARITH)
466*38fd1498Szrj
467*38fd1498Szrj/* Minus operand 0.  */
468*38fd1498SzrjDEF_RTL_EXPR(NEG, "neg", "e", RTX_UNARY)
469*38fd1498Szrj
470*38fd1498SzrjDEF_RTL_EXPR(MULT, "mult", "ee", RTX_COMM_ARITH)
471*38fd1498Szrj
472*38fd1498Szrj/* Multiplication with signed saturation */
473*38fd1498SzrjDEF_RTL_EXPR(SS_MULT, "ss_mult", "ee", RTX_COMM_ARITH)
474*38fd1498Szrj/* Multiplication with unsigned saturation */
475*38fd1498SzrjDEF_RTL_EXPR(US_MULT, "us_mult", "ee", RTX_COMM_ARITH)
476*38fd1498Szrj
477*38fd1498Szrj/* Operand 0 divided by operand 1.  */
478*38fd1498SzrjDEF_RTL_EXPR(DIV, "div", "ee", RTX_BIN_ARITH)
479*38fd1498Szrj/* Division with signed saturation */
480*38fd1498SzrjDEF_RTL_EXPR(SS_DIV, "ss_div", "ee", RTX_BIN_ARITH)
481*38fd1498Szrj/* Division with unsigned saturation */
482*38fd1498SzrjDEF_RTL_EXPR(US_DIV, "us_div", "ee", RTX_BIN_ARITH)
483*38fd1498Szrj
484*38fd1498Szrj/* Remainder of operand 0 divided by operand 1.  */
485*38fd1498SzrjDEF_RTL_EXPR(MOD, "mod", "ee", RTX_BIN_ARITH)
486*38fd1498Szrj
487*38fd1498Szrj/* Unsigned divide and remainder.  */
488*38fd1498SzrjDEF_RTL_EXPR(UDIV, "udiv", "ee", RTX_BIN_ARITH)
489*38fd1498SzrjDEF_RTL_EXPR(UMOD, "umod", "ee", RTX_BIN_ARITH)
490*38fd1498Szrj
491*38fd1498Szrj/* Bitwise operations.  */
492*38fd1498SzrjDEF_RTL_EXPR(AND, "and", "ee", RTX_COMM_ARITH)
493*38fd1498SzrjDEF_RTL_EXPR(IOR, "ior", "ee", RTX_COMM_ARITH)
494*38fd1498SzrjDEF_RTL_EXPR(XOR, "xor", "ee", RTX_COMM_ARITH)
495*38fd1498SzrjDEF_RTL_EXPR(NOT, "not", "e", RTX_UNARY)
496*38fd1498Szrj
497*38fd1498Szrj/* Operand:
498*38fd1498Szrj     0:  value to be shifted.
499*38fd1498Szrj     1:  number of bits.  */
500*38fd1498SzrjDEF_RTL_EXPR(ASHIFT, "ashift", "ee", RTX_BIN_ARITH) /* shift left */
501*38fd1498SzrjDEF_RTL_EXPR(ROTATE, "rotate", "ee", RTX_BIN_ARITH) /* rotate left */
502*38fd1498SzrjDEF_RTL_EXPR(ASHIFTRT, "ashiftrt", "ee", RTX_BIN_ARITH) /* arithmetic shift right */
503*38fd1498SzrjDEF_RTL_EXPR(LSHIFTRT, "lshiftrt", "ee", RTX_BIN_ARITH) /* logical shift right */
504*38fd1498SzrjDEF_RTL_EXPR(ROTATERT, "rotatert", "ee", RTX_BIN_ARITH) /* rotate right */
505*38fd1498Szrj
506*38fd1498Szrj/* Minimum and maximum values of two operands.  We need both signed and
507*38fd1498Szrj   unsigned forms.  (We cannot use MIN for SMIN because it conflicts
508*38fd1498Szrj   with a macro of the same name.)   The signed variants should be used
509*38fd1498Szrj   with floating point.  Further, if both operands are zeros, or if either
510*38fd1498Szrj   operand is NaN, then it is unspecified which of the two operands is
511*38fd1498Szrj   returned as the result.  */
512*38fd1498Szrj
513*38fd1498SzrjDEF_RTL_EXPR(SMIN, "smin", "ee", RTX_COMM_ARITH)
514*38fd1498SzrjDEF_RTL_EXPR(SMAX, "smax", "ee", RTX_COMM_ARITH)
515*38fd1498SzrjDEF_RTL_EXPR(UMIN, "umin", "ee", RTX_COMM_ARITH)
516*38fd1498SzrjDEF_RTL_EXPR(UMAX, "umax", "ee", RTX_COMM_ARITH)
517*38fd1498Szrj
518*38fd1498Szrj/* These unary operations are used to represent incrementation
519*38fd1498Szrj   and decrementation as they occur in memory addresses.
520*38fd1498Szrj   The amount of increment or decrement are not represented
521*38fd1498Szrj   because they can be understood from the machine-mode of the
522*38fd1498Szrj   containing MEM.  These operations exist in only two cases:
523*38fd1498Szrj   1. pushes onto the stack.
524*38fd1498Szrj   2. created automatically by the auto-inc-dec pass.  */
525*38fd1498SzrjDEF_RTL_EXPR(PRE_DEC, "pre_dec", "e", RTX_AUTOINC)
526*38fd1498SzrjDEF_RTL_EXPR(PRE_INC, "pre_inc", "e", RTX_AUTOINC)
527*38fd1498SzrjDEF_RTL_EXPR(POST_DEC, "post_dec", "e", RTX_AUTOINC)
528*38fd1498SzrjDEF_RTL_EXPR(POST_INC, "post_inc", "e", RTX_AUTOINC)
529*38fd1498Szrj
530*38fd1498Szrj/* These binary operations are used to represent generic address
531*38fd1498Szrj   side-effects in memory addresses, except for simple incrementation
532*38fd1498Szrj   or decrementation which use the above operations.  They are
533*38fd1498Szrj   created automatically by the life_analysis pass in flow.c.
534*38fd1498Szrj   The first operand is a REG which is used as the address.
535*38fd1498Szrj   The second operand is an expression that is assigned to the
536*38fd1498Szrj   register, either before (PRE_MODIFY) or after (POST_MODIFY)
537*38fd1498Szrj   evaluating the address.
538*38fd1498Szrj   Currently, the compiler can only handle second operands of the
539*38fd1498Szrj   form (plus (reg) (reg)) and (plus (reg) (const_int)), where
540*38fd1498Szrj   the first operand of the PLUS has to be the same register as
541*38fd1498Szrj   the first operand of the *_MODIFY.  */
542*38fd1498SzrjDEF_RTL_EXPR(PRE_MODIFY, "pre_modify", "ee", RTX_AUTOINC)
543*38fd1498SzrjDEF_RTL_EXPR(POST_MODIFY, "post_modify", "ee", RTX_AUTOINC)
544*38fd1498Szrj
545*38fd1498Szrj/* Comparison operations.  The ordered comparisons exist in two
546*38fd1498Szrj   flavors, signed and unsigned.  */
547*38fd1498SzrjDEF_RTL_EXPR(NE, "ne", "ee", RTX_COMM_COMPARE)
548*38fd1498SzrjDEF_RTL_EXPR(EQ, "eq", "ee", RTX_COMM_COMPARE)
549*38fd1498SzrjDEF_RTL_EXPR(GE, "ge", "ee", RTX_COMPARE)
550*38fd1498SzrjDEF_RTL_EXPR(GT, "gt", "ee", RTX_COMPARE)
551*38fd1498SzrjDEF_RTL_EXPR(LE, "le", "ee", RTX_COMPARE)
552*38fd1498SzrjDEF_RTL_EXPR(LT, "lt", "ee", RTX_COMPARE)
553*38fd1498SzrjDEF_RTL_EXPR(GEU, "geu", "ee", RTX_COMPARE)
554*38fd1498SzrjDEF_RTL_EXPR(GTU, "gtu", "ee", RTX_COMPARE)
555*38fd1498SzrjDEF_RTL_EXPR(LEU, "leu", "ee", RTX_COMPARE)
556*38fd1498SzrjDEF_RTL_EXPR(LTU, "ltu", "ee", RTX_COMPARE)
557*38fd1498Szrj
558*38fd1498Szrj/* Additional floating point unordered comparison flavors.  */
559*38fd1498SzrjDEF_RTL_EXPR(UNORDERED, "unordered", "ee", RTX_COMM_COMPARE)
560*38fd1498SzrjDEF_RTL_EXPR(ORDERED, "ordered", "ee", RTX_COMM_COMPARE)
561*38fd1498Szrj
562*38fd1498Szrj/* These are equivalent to unordered or ...  */
563*38fd1498SzrjDEF_RTL_EXPR(UNEQ, "uneq", "ee", RTX_COMM_COMPARE)
564*38fd1498SzrjDEF_RTL_EXPR(UNGE, "unge", "ee", RTX_COMPARE)
565*38fd1498SzrjDEF_RTL_EXPR(UNGT, "ungt", "ee", RTX_COMPARE)
566*38fd1498SzrjDEF_RTL_EXPR(UNLE, "unle", "ee", RTX_COMPARE)
567*38fd1498SzrjDEF_RTL_EXPR(UNLT, "unlt", "ee", RTX_COMPARE)
568*38fd1498Szrj
569*38fd1498Szrj/* This is an ordered NE, ie !UNEQ, ie false for NaN.  */
570*38fd1498SzrjDEF_RTL_EXPR(LTGT, "ltgt", "ee", RTX_COMM_COMPARE)
571*38fd1498Szrj
572*38fd1498Szrj/* Represents the result of sign-extending the sole operand.
573*38fd1498Szrj   The machine modes of the operand and of the SIGN_EXTEND expression
574*38fd1498Szrj   determine how much sign-extension is going on.  */
575*38fd1498SzrjDEF_RTL_EXPR(SIGN_EXTEND, "sign_extend", "e", RTX_UNARY)
576*38fd1498Szrj
577*38fd1498Szrj/* Similar for zero-extension (such as unsigned short to int).  */
578*38fd1498SzrjDEF_RTL_EXPR(ZERO_EXTEND, "zero_extend", "e", RTX_UNARY)
579*38fd1498Szrj
580*38fd1498Szrj/* Similar but here the operand has a wider mode.  */
581*38fd1498SzrjDEF_RTL_EXPR(TRUNCATE, "truncate", "e", RTX_UNARY)
582*38fd1498Szrj
583*38fd1498Szrj/* Similar for extending floating-point values (such as SFmode to DFmode).  */
584*38fd1498SzrjDEF_RTL_EXPR(FLOAT_EXTEND, "float_extend", "e", RTX_UNARY)
585*38fd1498SzrjDEF_RTL_EXPR(FLOAT_TRUNCATE, "float_truncate", "e", RTX_UNARY)
586*38fd1498Szrj
587*38fd1498Szrj/* Conversion of fixed point operand to floating point value.  */
588*38fd1498SzrjDEF_RTL_EXPR(FLOAT, "float", "e", RTX_UNARY)
589*38fd1498Szrj
590*38fd1498Szrj/* With fixed-point machine mode:
591*38fd1498Szrj   Conversion of floating point operand to fixed point value.
592*38fd1498Szrj   Value is defined only when the operand's value is an integer.
593*38fd1498Szrj   With floating-point machine mode (and operand with same mode):
594*38fd1498Szrj   Operand is rounded toward zero to produce an integer value
595*38fd1498Szrj   represented in floating point.  */
596*38fd1498SzrjDEF_RTL_EXPR(FIX, "fix", "e", RTX_UNARY)
597*38fd1498Szrj
598*38fd1498Szrj/* Conversion of unsigned fixed point operand to floating point value.  */
599*38fd1498SzrjDEF_RTL_EXPR(UNSIGNED_FLOAT, "unsigned_float", "e", RTX_UNARY)
600*38fd1498Szrj
601*38fd1498Szrj/* With fixed-point machine mode:
602*38fd1498Szrj   Conversion of floating point operand to *unsigned* fixed point value.
603*38fd1498Szrj   Value is defined only when the operand's value is an integer.  */
604*38fd1498SzrjDEF_RTL_EXPR(UNSIGNED_FIX, "unsigned_fix", "e", RTX_UNARY)
605*38fd1498Szrj
606*38fd1498Szrj/* Conversions involving fractional fixed-point types without saturation,
607*38fd1498Szrj   including:
608*38fd1498Szrj     fractional to fractional (of different precision),
609*38fd1498Szrj     signed integer to fractional,
610*38fd1498Szrj     fractional to signed integer,
611*38fd1498Szrj     floating point to fractional,
612*38fd1498Szrj     fractional to floating point.
613*38fd1498Szrj   NOTE: fractional can be either signed or unsigned for conversions.  */
614*38fd1498SzrjDEF_RTL_EXPR(FRACT_CONVERT, "fract_convert", "e", RTX_UNARY)
615*38fd1498Szrj
616*38fd1498Szrj/* Conversions involving fractional fixed-point types and unsigned integer
617*38fd1498Szrj   without saturation, including:
618*38fd1498Szrj     unsigned integer to fractional,
619*38fd1498Szrj     fractional to unsigned integer.
620*38fd1498Szrj   NOTE: fractional can be either signed or unsigned for conversions.  */
621*38fd1498SzrjDEF_RTL_EXPR(UNSIGNED_FRACT_CONVERT, "unsigned_fract_convert", "e", RTX_UNARY)
622*38fd1498Szrj
623*38fd1498Szrj/* Conversions involving fractional fixed-point types with saturation,
624*38fd1498Szrj   including:
625*38fd1498Szrj     fractional to fractional (of different precision),
626*38fd1498Szrj     signed integer to fractional,
627*38fd1498Szrj     floating point to fractional.
628*38fd1498Szrj   NOTE: fractional can be either signed or unsigned for conversions.  */
629*38fd1498SzrjDEF_RTL_EXPR(SAT_FRACT, "sat_fract", "e", RTX_UNARY)
630*38fd1498Szrj
631*38fd1498Szrj/* Conversions involving fractional fixed-point types and unsigned integer
632*38fd1498Szrj   with saturation, including:
633*38fd1498Szrj     unsigned integer to fractional.
634*38fd1498Szrj   NOTE: fractional can be either signed or unsigned for conversions.  */
635*38fd1498SzrjDEF_RTL_EXPR(UNSIGNED_SAT_FRACT, "unsigned_sat_fract", "e", RTX_UNARY)
636*38fd1498Szrj
637*38fd1498Szrj/* Absolute value */
638*38fd1498SzrjDEF_RTL_EXPR(ABS, "abs", "e", RTX_UNARY)
639*38fd1498Szrj
640*38fd1498Szrj/* Square root */
641*38fd1498SzrjDEF_RTL_EXPR(SQRT, "sqrt", "e", RTX_UNARY)
642*38fd1498Szrj
643*38fd1498Szrj/* Swap bytes.  */
644*38fd1498SzrjDEF_RTL_EXPR(BSWAP, "bswap", "e", RTX_UNARY)
645*38fd1498Szrj
646*38fd1498Szrj/* Find first bit that is set.
647*38fd1498Szrj   Value is 1 + number of trailing zeros in the arg.,
648*38fd1498Szrj   or 0 if arg is 0.  */
649*38fd1498SzrjDEF_RTL_EXPR(FFS, "ffs", "e", RTX_UNARY)
650*38fd1498Szrj
651*38fd1498Szrj/* Count number of leading redundant sign bits (number of leading
652*38fd1498Szrj   sign bits minus one).  */
653*38fd1498SzrjDEF_RTL_EXPR(CLRSB, "clrsb", "e", RTX_UNARY)
654*38fd1498Szrj
655*38fd1498Szrj/* Count leading zeros.  */
656*38fd1498SzrjDEF_RTL_EXPR(CLZ, "clz", "e", RTX_UNARY)
657*38fd1498Szrj
658*38fd1498Szrj/* Count trailing zeros.  */
659*38fd1498SzrjDEF_RTL_EXPR(CTZ, "ctz", "e", RTX_UNARY)
660*38fd1498Szrj
661*38fd1498Szrj/* Population count (number of 1 bits).  */
662*38fd1498SzrjDEF_RTL_EXPR(POPCOUNT, "popcount", "e", RTX_UNARY)
663*38fd1498Szrj
664*38fd1498Szrj/* Population parity (number of 1 bits modulo 2).  */
665*38fd1498SzrjDEF_RTL_EXPR(PARITY, "parity", "e", RTX_UNARY)
666*38fd1498Szrj
667*38fd1498Szrj/* Reference to a signed bit-field of specified size and position.
668*38fd1498Szrj   Operand 0 is the memory unit (usually SImode or QImode) which
669*38fd1498Szrj   contains the field's first bit.  Operand 1 is the width, in bits.
670*38fd1498Szrj   Operand 2 is the number of bits in the memory unit before the
671*38fd1498Szrj   first bit of this field.
672*38fd1498Szrj   If BITS_BIG_ENDIAN is defined, the first bit is the msb and
673*38fd1498Szrj   operand 2 counts from the msb of the memory unit.
674*38fd1498Szrj   Otherwise, the first bit is the lsb and operand 2 counts from
675*38fd1498Szrj   the lsb of the memory unit.
676*38fd1498Szrj   This kind of expression can not appear as an lvalue in RTL.  */
677*38fd1498SzrjDEF_RTL_EXPR(SIGN_EXTRACT, "sign_extract", "eee", RTX_BITFIELD_OPS)
678*38fd1498Szrj
679*38fd1498Szrj/* Similar for unsigned bit-field.
680*38fd1498Szrj   But note!  This kind of expression _can_ appear as an lvalue.  */
681*38fd1498SzrjDEF_RTL_EXPR(ZERO_EXTRACT, "zero_extract", "eee", RTX_BITFIELD_OPS)
682*38fd1498Szrj
683*38fd1498Szrj/* For RISC machines.  These save memory when splitting insns.  */
684*38fd1498Szrj
685*38fd1498Szrj/* HIGH are the high-order bits of a constant expression.  */
686*38fd1498SzrjDEF_RTL_EXPR(HIGH, "high", "e", RTX_CONST_OBJ)
687*38fd1498Szrj
688*38fd1498Szrj/* LO_SUM is the sum of a register and the low-order bits
689*38fd1498Szrj   of a constant expression.  */
690*38fd1498SzrjDEF_RTL_EXPR(LO_SUM, "lo_sum", "ee", RTX_OBJ)
691*38fd1498Szrj
692*38fd1498Szrj/* Describes a merge operation between two vector values.
693*38fd1498Szrj   Operands 0 and 1 are the vectors to be merged, operand 2 is a bitmask
694*38fd1498Szrj   that specifies where the parts of the result are taken from.  Set bits
695*38fd1498Szrj   indicate operand 0, clear bits indicate operand 1.  The parts are defined
696*38fd1498Szrj   by the mode of the vectors.  */
697*38fd1498SzrjDEF_RTL_EXPR(VEC_MERGE, "vec_merge", "eee", RTX_TERNARY)
698*38fd1498Szrj
699*38fd1498Szrj/* Describes an operation that selects parts of a vector.
700*38fd1498Szrj   Operands 0 is the source vector, operand 1 is a PARALLEL that contains
701*38fd1498Szrj   a CONST_INT for each of the subparts of the result vector, giving the
702*38fd1498Szrj   number of the source subpart that should be stored into it.  */
703*38fd1498SzrjDEF_RTL_EXPR(VEC_SELECT, "vec_select", "ee", RTX_BIN_ARITH)
704*38fd1498Szrj
705*38fd1498Szrj/* Describes a vector concat operation.  Operands 0 and 1 are the source
706*38fd1498Szrj   vectors, the result is a vector that is as long as operands 0 and 1
707*38fd1498Szrj   combined and is the concatenation of the two source vectors.  */
708*38fd1498SzrjDEF_RTL_EXPR(VEC_CONCAT, "vec_concat", "ee", RTX_BIN_ARITH)
709*38fd1498Szrj
710*38fd1498Szrj/* Describes an operation that converts a small vector into a larger one by
711*38fd1498Szrj   duplicating the input values.  The output vector mode must have the same
712*38fd1498Szrj   submodes as the input vector mode, and the number of output parts must be
713*38fd1498Szrj   an integer multiple of the number of input parts.  */
714*38fd1498SzrjDEF_RTL_EXPR(VEC_DUPLICATE, "vec_duplicate", "e", RTX_UNARY)
715*38fd1498Szrj
716*38fd1498Szrj/* Creation of a vector in which element I has the value BASE + I * STEP,
717*38fd1498Szrj   where BASE is the first operand and STEP is the second.  The result
718*38fd1498Szrj   must have a vector integer mode.  */
719*38fd1498SzrjDEF_RTL_EXPR(VEC_SERIES, "vec_series", "ee", RTX_BIN_ARITH)
720*38fd1498Szrj
721*38fd1498Szrj/* Addition with signed saturation */
722*38fd1498SzrjDEF_RTL_EXPR(SS_PLUS, "ss_plus", "ee", RTX_COMM_ARITH)
723*38fd1498Szrj
724*38fd1498Szrj/* Addition with unsigned saturation */
725*38fd1498SzrjDEF_RTL_EXPR(US_PLUS, "us_plus", "ee", RTX_COMM_ARITH)
726*38fd1498Szrj
727*38fd1498Szrj/* Operand 0 minus operand 1, with signed saturation.  */
728*38fd1498SzrjDEF_RTL_EXPR(SS_MINUS, "ss_minus", "ee", RTX_BIN_ARITH)
729*38fd1498Szrj
730*38fd1498Szrj/* Negation with signed saturation.  */
731*38fd1498SzrjDEF_RTL_EXPR(SS_NEG, "ss_neg", "e", RTX_UNARY)
732*38fd1498Szrj/* Negation with unsigned saturation.  */
733*38fd1498SzrjDEF_RTL_EXPR(US_NEG, "us_neg", "e", RTX_UNARY)
734*38fd1498Szrj
735*38fd1498Szrj/* Absolute value with signed saturation.  */
736*38fd1498SzrjDEF_RTL_EXPR(SS_ABS, "ss_abs", "e", RTX_UNARY)
737*38fd1498Szrj
738*38fd1498Szrj/* Shift left with signed saturation.  */
739*38fd1498SzrjDEF_RTL_EXPR(SS_ASHIFT, "ss_ashift", "ee", RTX_BIN_ARITH)
740*38fd1498Szrj
741*38fd1498Szrj/* Shift left with unsigned saturation.  */
742*38fd1498SzrjDEF_RTL_EXPR(US_ASHIFT, "us_ashift", "ee", RTX_BIN_ARITH)
743*38fd1498Szrj
744*38fd1498Szrj/* Operand 0 minus operand 1, with unsigned saturation.  */
745*38fd1498SzrjDEF_RTL_EXPR(US_MINUS, "us_minus", "ee", RTX_BIN_ARITH)
746*38fd1498Szrj
747*38fd1498Szrj/* Signed saturating truncate.  */
748*38fd1498SzrjDEF_RTL_EXPR(SS_TRUNCATE, "ss_truncate", "e", RTX_UNARY)
749*38fd1498Szrj
750*38fd1498Szrj/* Unsigned saturating truncate.  */
751*38fd1498SzrjDEF_RTL_EXPR(US_TRUNCATE, "us_truncate", "e", RTX_UNARY)
752*38fd1498Szrj
753*38fd1498Szrj/* Floating point multiply/add combined instruction.  */
754*38fd1498SzrjDEF_RTL_EXPR(FMA, "fma", "eee", RTX_TERNARY)
755*38fd1498Szrj
756*38fd1498Szrj/* Information about the variable and its location.  */
757*38fd1498SzrjDEF_RTL_EXPR(VAR_LOCATION, "var_location", "te", RTX_EXTRA)
758*38fd1498Szrj
759*38fd1498Szrj/* Used in VAR_LOCATION for a pointer to a decl that is no longer
760*38fd1498Szrj   addressable.  */
761*38fd1498SzrjDEF_RTL_EXPR(DEBUG_IMPLICIT_PTR, "debug_implicit_ptr", "t", RTX_OBJ)
762*38fd1498Szrj
763*38fd1498Szrj/* Represents value that argument had on function entry.  The
764*38fd1498Szrj   single argument is the DECL_INCOMING_RTL of the corresponding
765*38fd1498Szrj   parameter.  */
766*38fd1498SzrjDEF_RTL_EXPR(ENTRY_VALUE, "entry_value", "0", RTX_OBJ)
767*38fd1498Szrj
768*38fd1498Szrj/* Used in VAR_LOCATION for a reference to a parameter that has
769*38fd1498Szrj   been optimized away completely.  */
770*38fd1498SzrjDEF_RTL_EXPR(DEBUG_PARAMETER_REF, "debug_parameter_ref", "t", RTX_OBJ)
771*38fd1498Szrj
772*38fd1498Szrj/* Used in marker DEBUG_INSNs to avoid being recognized as an insn.  */
773*38fd1498SzrjDEF_RTL_EXPR(DEBUG_MARKER, "debug_marker", "", RTX_EXTRA)
774*38fd1498Szrj
775*38fd1498Szrj/* All expressions from this point forward appear only in machine
776*38fd1498Szrj   descriptions.  */
777*38fd1498Szrj#ifdef GENERATOR_FILE
778*38fd1498Szrj
779*38fd1498Szrj/* Pattern-matching operators:  */
780*38fd1498Szrj
781*38fd1498Szrj/* Use the function named by the second arg (the string)
782*38fd1498Szrj   as a predicate; if matched, store the structure that was matched
783*38fd1498Szrj   in the operand table at index specified by the first arg (the integer).
784*38fd1498Szrj   If the second arg is the null string, the structure is just stored.
785*38fd1498Szrj
786*38fd1498Szrj   A third string argument indicates to the register allocator restrictions
787*38fd1498Szrj   on where the operand can be allocated.
788*38fd1498Szrj
789*38fd1498Szrj   If the target needs no restriction on any instruction this field should
790*38fd1498Szrj   be the null string.
791*38fd1498Szrj
792*38fd1498Szrj   The string is prepended by:
793*38fd1498Szrj   '=' to indicate the operand is only written to.
794*38fd1498Szrj   '+' to indicate the operand is both read and written to.
795*38fd1498Szrj
796*38fd1498Szrj   Each character in the string represents an allocable class for an operand.
797*38fd1498Szrj   'g' indicates the operand can be any valid class.
798*38fd1498Szrj   'i' indicates the operand can be immediate (in the instruction) data.
799*38fd1498Szrj   'r' indicates the operand can be in a register.
800*38fd1498Szrj   'm' indicates the operand can be in memory.
801*38fd1498Szrj   'o' a subset of the 'm' class.  Those memory addressing modes that
802*38fd1498Szrj       can be offset at compile time (have a constant added to them).
803*38fd1498Szrj
804*38fd1498Szrj   Other characters indicate target dependent operand classes and
805*38fd1498Szrj   are described in each target's machine description.
806*38fd1498Szrj
807*38fd1498Szrj   For instructions with more than one operand, sets of classes can be
808*38fd1498Szrj   separated by a comma to indicate the appropriate multi-operand constraints.
809*38fd1498Szrj   There must be a 1 to 1 correspondence between these sets of classes in
810*38fd1498Szrj   all operands for an instruction.
811*38fd1498Szrj   */
812*38fd1498SzrjDEF_RTL_EXPR(MATCH_OPERAND, "match_operand", "iss", RTX_MATCH)
813*38fd1498Szrj
814*38fd1498Szrj/* Match a SCRATCH or a register.  When used to generate rtl, a
815*38fd1498Szrj   SCRATCH is generated.  As for MATCH_OPERAND, the mode specifies
816*38fd1498Szrj   the desired mode and the first argument is the operand number.
817*38fd1498Szrj   The second argument is the constraint.  */
818*38fd1498SzrjDEF_RTL_EXPR(MATCH_SCRATCH, "match_scratch", "is", RTX_MATCH)
819*38fd1498Szrj
820*38fd1498Szrj/* Apply a predicate, AND match recursively the operands of the rtx.
821*38fd1498Szrj   Operand 0 is the operand-number, as in match_operand.
822*38fd1498Szrj   Operand 1 is a predicate to apply (as a string, a function name).
823*38fd1498Szrj   Operand 2 is a vector of expressions, each of which must match
824*38fd1498Szrj   one subexpression of the rtx this construct is matching.  */
825*38fd1498SzrjDEF_RTL_EXPR(MATCH_OPERATOR, "match_operator", "isE", RTX_MATCH)
826*38fd1498Szrj
827*38fd1498Szrj/* Match a PARALLEL of arbitrary length.  The predicate is applied
828*38fd1498Szrj   to the PARALLEL and the initial expressions in the PARALLEL are matched.
829*38fd1498Szrj   Operand 0 is the operand-number, as in match_operand.
830*38fd1498Szrj   Operand 1 is a predicate to apply to the PARALLEL.
831*38fd1498Szrj   Operand 2 is a vector of expressions, each of which must match the
832*38fd1498Szrj   corresponding element in the PARALLEL.  */
833*38fd1498SzrjDEF_RTL_EXPR(MATCH_PARALLEL, "match_parallel", "isE", RTX_MATCH)
834*38fd1498Szrj
835*38fd1498Szrj/* Match only something equal to what is stored in the operand table
836*38fd1498Szrj   at the index specified by the argument.  Use with MATCH_OPERAND.  */
837*38fd1498SzrjDEF_RTL_EXPR(MATCH_DUP, "match_dup", "i", RTX_MATCH)
838*38fd1498Szrj
839*38fd1498Szrj/* Match only something equal to what is stored in the operand table
840*38fd1498Szrj   at the index specified by the argument.  Use with MATCH_OPERATOR.  */
841*38fd1498SzrjDEF_RTL_EXPR(MATCH_OP_DUP, "match_op_dup", "iE", RTX_MATCH)
842*38fd1498Szrj
843*38fd1498Szrj/* Match only something equal to what is stored in the operand table
844*38fd1498Szrj   at the index specified by the argument.  Use with MATCH_PARALLEL.  */
845*38fd1498SzrjDEF_RTL_EXPR(MATCH_PAR_DUP, "match_par_dup", "iE", RTX_MATCH)
846*38fd1498Szrj
847*38fd1498Szrj/* Appears only in define_predicate/define_special_predicate
848*38fd1498Szrj   expressions.  Evaluates true only if the operand has an RTX code
849*38fd1498Szrj   from the set given by the argument (a comma-separated list).  If the
850*38fd1498Szrj   second argument is present and nonempty, it is a sequence of digits
851*38fd1498Szrj   and/or letters which indicates the subexpression to test, using the
852*38fd1498Szrj   same syntax as genextract/genrecog's location strings: 0-9 for
853*38fd1498Szrj   XEXP (op, n), a-z for XVECEXP (op, 0, n); each character applies to
854*38fd1498Szrj   the result of the one before it.  */
855*38fd1498SzrjDEF_RTL_EXPR(MATCH_CODE, "match_code", "ss", RTX_MATCH)
856*38fd1498Szrj
857*38fd1498Szrj/* Used to inject a C conditional expression into an .md file.  It can
858*38fd1498Szrj   appear in a predicate definition or an attribute expression.  */
859*38fd1498SzrjDEF_RTL_EXPR(MATCH_TEST, "match_test", "s", RTX_MATCH)
860*38fd1498Szrj
861*38fd1498Szrj/* Insn (and related) definitions.  */
862*38fd1498Szrj
863*38fd1498Szrj/* Definition of the pattern for one kind of instruction.
864*38fd1498Szrj   Operand:
865*38fd1498Szrj   0: names this instruction.
866*38fd1498Szrj      If the name is the null string, the instruction is in the
867*38fd1498Szrj      machine description just to be recognized, and will never be emitted by
868*38fd1498Szrj      the tree to rtl expander.
869*38fd1498Szrj   1: is the pattern.
870*38fd1498Szrj   2: is a string which is a C expression
871*38fd1498Szrj      giving an additional condition for recognizing this pattern.
872*38fd1498Szrj      A null string means no extra condition.
873*38fd1498Szrj   3: is the action to execute if this pattern is matched.
874*38fd1498Szrj      If this assembler code template starts with a * then it is a fragment of
875*38fd1498Szrj      C code to run to decide on a template to use.  Otherwise, it is the
876*38fd1498Szrj      template to use.
877*38fd1498Szrj   4: optionally, a vector of attributes for this insn.
878*38fd1498Szrj     */
879*38fd1498SzrjDEF_RTL_EXPR(DEFINE_INSN, "define_insn", "sEsTV", RTX_EXTRA)
880*38fd1498Szrj
881*38fd1498Szrj/* Definition of a peephole optimization.
882*38fd1498Szrj   1st operand: vector of insn patterns to match
883*38fd1498Szrj   2nd operand: C expression that must be true
884*38fd1498Szrj   3rd operand: template or C code to produce assembler output.
885*38fd1498Szrj   4: optionally, a vector of attributes for this insn.
886*38fd1498Szrj
887*38fd1498Szrj   This form is deprecated; use define_peephole2 instead.  */
888*38fd1498SzrjDEF_RTL_EXPR(DEFINE_PEEPHOLE, "define_peephole", "EsTV", RTX_EXTRA)
889*38fd1498Szrj
890*38fd1498Szrj/* Definition of a split operation.
891*38fd1498Szrj   1st operand: insn pattern to match
892*38fd1498Szrj   2nd operand: C expression that must be true
893*38fd1498Szrj   3rd operand: vector of insn patterns to place into a SEQUENCE
894*38fd1498Szrj   4th operand: optionally, some C code to execute before generating the
895*38fd1498Szrj	insns.  This might, for example, create some RTX's and store them in
896*38fd1498Szrj	elements of `recog_data.operand' for use by the vector of
897*38fd1498Szrj	insn-patterns.
898*38fd1498Szrj	(`operands' is an alias here for `recog_data.operand').  */
899*38fd1498SzrjDEF_RTL_EXPR(DEFINE_SPLIT, "define_split", "EsES", RTX_EXTRA)
900*38fd1498Szrj
901*38fd1498Szrj/* Definition of an insn and associated split.
902*38fd1498Szrj   This is the concatenation, with a few modifications, of a define_insn
903*38fd1498Szrj   and a define_split which share the same pattern.
904*38fd1498Szrj   Operand:
905*38fd1498Szrj   0: names this instruction.
906*38fd1498Szrj      If the name is the null string, the instruction is in the
907*38fd1498Szrj      machine description just to be recognized, and will never be emitted by
908*38fd1498Szrj      the tree to rtl expander.
909*38fd1498Szrj   1: is the pattern.
910*38fd1498Szrj   2: is a string which is a C expression
911*38fd1498Szrj      giving an additional condition for recognizing this pattern.
912*38fd1498Szrj      A null string means no extra condition.
913*38fd1498Szrj   3: is the action to execute if this pattern is matched.
914*38fd1498Szrj      If this assembler code template starts with a * then it is a fragment of
915*38fd1498Szrj      C code to run to decide on a template to use.  Otherwise, it is the
916*38fd1498Szrj      template to use.
917*38fd1498Szrj   4: C expression that must be true for split.  This may start with "&&"
918*38fd1498Szrj      in which case the split condition is the logical and of the insn
919*38fd1498Szrj      condition and what follows the "&&" of this operand.
920*38fd1498Szrj   5: vector of insn patterns to place into a SEQUENCE
921*38fd1498Szrj   6: optionally, some C code to execute before generating the
922*38fd1498Szrj	insns.  This might, for example, create some RTX's and store them in
923*38fd1498Szrj	elements of `recog_data.operand' for use by the vector of
924*38fd1498Szrj	insn-patterns.
925*38fd1498Szrj	(`operands' is an alias here for `recog_data.operand').
926*38fd1498Szrj   7: optionally, a vector of attributes for this insn.  */
927*38fd1498SzrjDEF_RTL_EXPR(DEFINE_INSN_AND_SPLIT, "define_insn_and_split", "sEsTsESV", RTX_EXTRA)
928*38fd1498Szrj
929*38fd1498Szrj/* Definition of an RTL peephole operation.
930*38fd1498Szrj   Follows the same arguments as define_split.  */
931*38fd1498SzrjDEF_RTL_EXPR(DEFINE_PEEPHOLE2, "define_peephole2", "EsES", RTX_EXTRA)
932*38fd1498Szrj
933*38fd1498Szrj/* Define how to generate multiple insns for a standard insn name.
934*38fd1498Szrj   1st operand: the insn name.
935*38fd1498Szrj   2nd operand: vector of insn-patterns.
936*38fd1498Szrj	Use match_operand to substitute an element of `recog_data.operand'.
937*38fd1498Szrj   3rd operand: C expression that must be true for this to be available.
938*38fd1498Szrj	This may not test any operands.
939*38fd1498Szrj   4th operand: Extra C code to execute before generating the insns.
940*38fd1498Szrj	This might, for example, create some RTX's and store them in
941*38fd1498Szrj	elements of `recog_data.operand' for use by the vector of
942*38fd1498Szrj	insn-patterns.
943*38fd1498Szrj	(`operands' is an alias here for `recog_data.operand').
944*38fd1498Szrj   5th: optionally, a vector of attributes for this expand.  */
945*38fd1498SzrjDEF_RTL_EXPR(DEFINE_EXPAND, "define_expand", "sEssV", RTX_EXTRA)
946*38fd1498Szrj
947*38fd1498Szrj/* Define a requirement for delay slots.
948*38fd1498Szrj   1st operand: Condition involving insn attributes that, if true,
949*38fd1498Szrj	        indicates that the insn requires the number of delay slots
950*38fd1498Szrj		shown.
951*38fd1498Szrj   2nd operand: Vector whose length is the three times the number of delay
952*38fd1498Szrj		slots required.
953*38fd1498Szrj	        Each entry gives three conditions, each involving attributes.
954*38fd1498Szrj		The first must be true for an insn to occupy that delay slot
955*38fd1498Szrj		location.  The second is true for all insns that can be
956*38fd1498Szrj		annulled if the branch is true and the third is true for all
957*38fd1498Szrj		insns that can be annulled if the branch is false.
958*38fd1498Szrj
959*38fd1498Szrj   Multiple DEFINE_DELAYs may be present.  They indicate differing
960*38fd1498Szrj   requirements for delay slots.  */
961*38fd1498SzrjDEF_RTL_EXPR(DEFINE_DELAY, "define_delay", "eE", RTX_EXTRA)
962*38fd1498Szrj
963*38fd1498Szrj/* Define attribute computation for `asm' instructions.  */
964*38fd1498SzrjDEF_RTL_EXPR(DEFINE_ASM_ATTRIBUTES, "define_asm_attributes", "V", RTX_EXTRA)
965*38fd1498Szrj
966*38fd1498Szrj/* Definition of a conditional execution meta operation.  Automatically
967*38fd1498Szrj   generates new instances of DEFINE_INSN, selected by having attribute
968*38fd1498Szrj   "predicable" true.  The new pattern will contain a COND_EXEC and the
969*38fd1498Szrj   predicate at top-level.
970*38fd1498Szrj
971*38fd1498Szrj   Operand:
972*38fd1498Szrj   0: The predicate pattern.  The top-level form should match a
973*38fd1498Szrj      relational operator.  Operands should have only one alternative.
974*38fd1498Szrj   1: A C expression giving an additional condition for recognizing
975*38fd1498Szrj      the generated pattern.
976*38fd1498Szrj   2: A template or C code to produce assembler output.
977*38fd1498Szrj   3: A vector of attributes to append to the resulting cond_exec insn.  */
978*38fd1498SzrjDEF_RTL_EXPR(DEFINE_COND_EXEC, "define_cond_exec", "EssV", RTX_EXTRA)
979*38fd1498Szrj
980*38fd1498Szrj/* Definition of an operand predicate.  The difference between
981*38fd1498Szrj   DEFINE_PREDICATE and DEFINE_SPECIAL_PREDICATE is that genrecog will
982*38fd1498Szrj   not warn about a match_operand with no mode if it has a predicate
983*38fd1498Szrj   defined with DEFINE_SPECIAL_PREDICATE.
984*38fd1498Szrj
985*38fd1498Szrj   Operand:
986*38fd1498Szrj   0: The name of the predicate.
987*38fd1498Szrj   1: A boolean expression which computes whether or not the predicate
988*38fd1498Szrj      matches.  This expression can use IOR, AND, NOT, MATCH_OPERAND,
989*38fd1498Szrj      MATCH_CODE, and MATCH_TEST.  It must be specific enough that genrecog
990*38fd1498Szrj      can calculate the set of RTX codes that can possibly match.
991*38fd1498Szrj   2: A C function body which must return true for the predicate to match.
992*38fd1498Szrj      Optional.  Use this when the test is too complicated to fit into a
993*38fd1498Szrj      match_test expression.  */
994*38fd1498SzrjDEF_RTL_EXPR(DEFINE_PREDICATE, "define_predicate", "ses", RTX_EXTRA)
995*38fd1498SzrjDEF_RTL_EXPR(DEFINE_SPECIAL_PREDICATE, "define_special_predicate", "ses", RTX_EXTRA)
996*38fd1498Szrj
997*38fd1498Szrj/* Definition of a register operand constraint.  This simply maps the
998*38fd1498Szrj   constraint string to a register class.
999*38fd1498Szrj
1000*38fd1498Szrj   Operand:
1001*38fd1498Szrj   0: The name of the constraint (often, but not always, a single letter).
1002*38fd1498Szrj   1: A C expression which evaluates to the appropriate register class for
1003*38fd1498Szrj      this constraint.  If this is not just a constant, it should look only
1004*38fd1498Szrj      at -m switches and the like.
1005*38fd1498Szrj   2: A docstring for this constraint, in Texinfo syntax; not currently
1006*38fd1498Szrj      used, in future will be incorporated into the manual's list of
1007*38fd1498Szrj      machine-specific operand constraints.  */
1008*38fd1498SzrjDEF_RTL_EXPR(DEFINE_REGISTER_CONSTRAINT, "define_register_constraint", "sss", RTX_EXTRA)
1009*38fd1498Szrj
1010*38fd1498Szrj/* Definition of a non-register operand constraint.  These look at the
1011*38fd1498Szrj   operand and decide whether it fits the constraint.
1012*38fd1498Szrj
1013*38fd1498Szrj   DEFINE_CONSTRAINT gets no special treatment if it fails to match.
1014*38fd1498Szrj   It is appropriate for constant-only constraints, and most others.
1015*38fd1498Szrj
1016*38fd1498Szrj   DEFINE_MEMORY_CONSTRAINT tells reload that this constraint can be made
1017*38fd1498Szrj   to match, if it doesn't already, by converting the operand to the form
1018*38fd1498Szrj   (mem (reg X)) where X is a base register.  It is suitable for constraints
1019*38fd1498Szrj   that describe a subset of all memory references.
1020*38fd1498Szrj
1021*38fd1498Szrj   DEFINE_ADDRESS_CONSTRAINT tells reload that this constraint can be made
1022*38fd1498Szrj   to match, if it doesn't already, by converting the operand to the form
1023*38fd1498Szrj   (reg X) where X is a base register.  It is suitable for constraints that
1024*38fd1498Szrj   describe a subset of all address references.
1025*38fd1498Szrj
1026*38fd1498Szrj   When in doubt, use plain DEFINE_CONSTRAINT.
1027*38fd1498Szrj
1028*38fd1498Szrj   Operand:
1029*38fd1498Szrj   0: The name of the constraint (often, but not always, a single letter).
1030*38fd1498Szrj   1: A docstring for this constraint, in Texinfo syntax; not currently
1031*38fd1498Szrj      used, in future will be incorporated into the manual's list of
1032*38fd1498Szrj      machine-specific operand constraints.
1033*38fd1498Szrj   2: A boolean expression which computes whether or not the constraint
1034*38fd1498Szrj      matches.  It should follow the same rules as a define_predicate
1035*38fd1498Szrj      expression, including the bit about specifying the set of RTX codes
1036*38fd1498Szrj      that could possibly match.  MATCH_TEST subexpressions may make use of
1037*38fd1498Szrj      these variables:
1038*38fd1498Szrj        `op'    - the RTL object defining the operand.
1039*38fd1498Szrj        `mode'  - the mode of `op'.
1040*38fd1498Szrj	`ival'  - INTVAL(op), if op is a CONST_INT.
1041*38fd1498Szrj        `hval'  - CONST_DOUBLE_HIGH(op), if op is an integer CONST_DOUBLE.
1042*38fd1498Szrj        `lval'  - CONST_DOUBLE_LOW(op), if op is an integer CONST_DOUBLE.
1043*38fd1498Szrj        `rval'  - CONST_DOUBLE_REAL_VALUE(op), if op is a floating-point
1044*38fd1498Szrj                  CONST_DOUBLE.
1045*38fd1498Szrj      Do not use ival/hval/lval/rval if op is not the appropriate kind of
1046*38fd1498Szrj      RTL object.  */
1047*38fd1498SzrjDEF_RTL_EXPR(DEFINE_CONSTRAINT, "define_constraint", "sse", RTX_EXTRA)
1048*38fd1498SzrjDEF_RTL_EXPR(DEFINE_MEMORY_CONSTRAINT, "define_memory_constraint", "sse", RTX_EXTRA)
1049*38fd1498SzrjDEF_RTL_EXPR(DEFINE_SPECIAL_MEMORY_CONSTRAINT, "define_special_memory_constraint", "sse", RTX_EXTRA)
1050*38fd1498SzrjDEF_RTL_EXPR(DEFINE_ADDRESS_CONSTRAINT, "define_address_constraint", "sse", RTX_EXTRA)
1051*38fd1498Szrj
1052*38fd1498Szrj
1053*38fd1498Szrj/* Constructions for CPU pipeline description described by NDFAs.  */
1054*38fd1498Szrj
1055*38fd1498Szrj/* (define_cpu_unit string [string]) describes cpu functional
1056*38fd1498Szrj   units (separated by comma).
1057*38fd1498Szrj
1058*38fd1498Szrj   1st operand: Names of cpu functional units.
1059*38fd1498Szrj   2nd operand: Name of automaton (see comments for DEFINE_AUTOMATON).
1060*38fd1498Szrj
1061*38fd1498Szrj   All define_reservations, define_cpu_units, and
1062*38fd1498Szrj   define_query_cpu_units should have unique names which may not be
1063*38fd1498Szrj   "nothing".  */
1064*38fd1498SzrjDEF_RTL_EXPR(DEFINE_CPU_UNIT, "define_cpu_unit", "sS", RTX_EXTRA)
1065*38fd1498Szrj
1066*38fd1498Szrj/* (define_query_cpu_unit string [string]) describes cpu functional
1067*38fd1498Szrj   units analogously to define_cpu_unit.  The reservation of such
1068*38fd1498Szrj   units can be queried for automaton state.  */
1069*38fd1498SzrjDEF_RTL_EXPR(DEFINE_QUERY_CPU_UNIT, "define_query_cpu_unit", "sS", RTX_EXTRA)
1070*38fd1498Szrj
1071*38fd1498Szrj/* (exclusion_set string string) means that each CPU functional unit
1072*38fd1498Szrj   in the first string can not be reserved simultaneously with any
1073*38fd1498Szrj   unit whose name is in the second string and vise versa.  CPU units
1074*38fd1498Szrj   in the string are separated by commas.  For example, it is useful
1075*38fd1498Szrj   for description CPU with fully pipelined floating point functional
1076*38fd1498Szrj   unit which can execute simultaneously only single floating point
1077*38fd1498Szrj   insns or only double floating point insns.  All CPU functional
1078*38fd1498Szrj   units in a set should belong to the same automaton.  */
1079*38fd1498SzrjDEF_RTL_EXPR(EXCLUSION_SET, "exclusion_set", "ss", RTX_EXTRA)
1080*38fd1498Szrj
1081*38fd1498Szrj/* (presence_set string string) means that each CPU functional unit in
1082*38fd1498Szrj   the first string can not be reserved unless at least one of pattern
1083*38fd1498Szrj   of units whose names are in the second string is reserved.  This is
1084*38fd1498Szrj   an asymmetric relation.  CPU units or unit patterns in the strings
1085*38fd1498Szrj   are separated by commas.  Pattern is one unit name or unit names
1086*38fd1498Szrj   separated by white-spaces.
1087*38fd1498Szrj
1088*38fd1498Szrj   For example, it is useful for description that slot1 is reserved
1089*38fd1498Szrj   after slot0 reservation for a VLIW processor.  We could describe it
1090*38fd1498Szrj   by the following construction
1091*38fd1498Szrj
1092*38fd1498Szrj      (presence_set "slot1" "slot0")
1093*38fd1498Szrj
1094*38fd1498Szrj   Or slot1 is reserved only after slot0 and unit b0 reservation.  In
1095*38fd1498Szrj   this case we could write
1096*38fd1498Szrj
1097*38fd1498Szrj      (presence_set "slot1" "slot0 b0")
1098*38fd1498Szrj
1099*38fd1498Szrj   All CPU functional units in a set should belong to the same
1100*38fd1498Szrj   automaton.  */
1101*38fd1498SzrjDEF_RTL_EXPR(PRESENCE_SET, "presence_set", "ss", RTX_EXTRA)
1102*38fd1498Szrj
1103*38fd1498Szrj/* (final_presence_set string string) is analogous to `presence_set'.
1104*38fd1498Szrj   The difference between them is when checking is done.  When an
1105*38fd1498Szrj   instruction is issued in given automaton state reflecting all
1106*38fd1498Szrj   current and planned unit reservations, the automaton state is
1107*38fd1498Szrj   changed.  The first state is a source state, the second one is a
1108*38fd1498Szrj   result state.  Checking for `presence_set' is done on the source
1109*38fd1498Szrj   state reservation, checking for `final_presence_set' is done on the
1110*38fd1498Szrj   result reservation.  This construction is useful to describe a
1111*38fd1498Szrj   reservation which is actually two subsequent reservations.  For
1112*38fd1498Szrj   example, if we use
1113*38fd1498Szrj
1114*38fd1498Szrj      (presence_set "slot1" "slot0")
1115*38fd1498Szrj
1116*38fd1498Szrj   the following insn will be never issued (because slot1 requires
1117*38fd1498Szrj   slot0 which is absent in the source state).
1118*38fd1498Szrj
1119*38fd1498Szrj      (define_reservation "insn_and_nop" "slot0 + slot1")
1120*38fd1498Szrj
1121*38fd1498Szrj   but it can be issued if we use analogous `final_presence_set'.  */
1122*38fd1498SzrjDEF_RTL_EXPR(FINAL_PRESENCE_SET, "final_presence_set", "ss", RTX_EXTRA)
1123*38fd1498Szrj
1124*38fd1498Szrj/* (absence_set string string) means that each CPU functional unit in
1125*38fd1498Szrj   the first string can be reserved only if each pattern of units
1126*38fd1498Szrj   whose names are in the second string is not reserved.  This is an
1127*38fd1498Szrj   asymmetric relation (actually exclusion set is analogous to this
1128*38fd1498Szrj   one but it is symmetric).  CPU units or unit patterns in the string
1129*38fd1498Szrj   are separated by commas.  Pattern is one unit name or unit names
1130*38fd1498Szrj   separated by white-spaces.
1131*38fd1498Szrj
1132*38fd1498Szrj   For example, it is useful for description that slot0 can not be
1133*38fd1498Szrj   reserved after slot1 or slot2 reservation for a VLIW processor.  We
1134*38fd1498Szrj   could describe it by the following construction
1135*38fd1498Szrj
1136*38fd1498Szrj      (absence_set "slot2" "slot0, slot1")
1137*38fd1498Szrj
1138*38fd1498Szrj   Or slot2 can not be reserved if slot0 and unit b0 are reserved or
1139*38fd1498Szrj   slot1 and unit b1 are reserved .  In this case we could write
1140*38fd1498Szrj
1141*38fd1498Szrj      (absence_set "slot2" "slot0 b0, slot1 b1")
1142*38fd1498Szrj
1143*38fd1498Szrj   All CPU functional units in a set should to belong the same
1144*38fd1498Szrj   automaton.  */
1145*38fd1498SzrjDEF_RTL_EXPR(ABSENCE_SET, "absence_set", "ss", RTX_EXTRA)
1146*38fd1498Szrj
1147*38fd1498Szrj/* (final_absence_set string string) is analogous to `absence_set' but
1148*38fd1498Szrj   checking is done on the result (state) reservation.  See comments
1149*38fd1498Szrj   for `final_presence_set'.  */
1150*38fd1498SzrjDEF_RTL_EXPR(FINAL_ABSENCE_SET, "final_absence_set", "ss", RTX_EXTRA)
1151*38fd1498Szrj
1152*38fd1498Szrj/* (define_bypass number out_insn_names in_insn_names) names bypass
1153*38fd1498Szrj   with given latency (the first number) from insns given by the first
1154*38fd1498Szrj   string (see define_insn_reservation) into insns given by the second
1155*38fd1498Szrj   string.  Insn names in the strings are separated by commas.  The
1156*38fd1498Szrj   third operand is optional name of function which is additional
1157*38fd1498Szrj   guard for the bypass.  The function will get the two insns as
1158*38fd1498Szrj   parameters.  If the function returns zero the bypass will be
1159*38fd1498Szrj   ignored for this case.  Additional guard is necessary to recognize
1160*38fd1498Szrj   complicated bypasses, e.g. when consumer is load address.  If there
1161*38fd1498Szrj   are more one bypass with the same output and input insns, the
1162*38fd1498Szrj   chosen bypass is the first bypass with a guard in description whose
1163*38fd1498Szrj   guard function returns nonzero.  If there is no such bypass, then
1164*38fd1498Szrj   bypass without the guard function is chosen.  */
1165*38fd1498SzrjDEF_RTL_EXPR(DEFINE_BYPASS, "define_bypass", "issS", RTX_EXTRA)
1166*38fd1498Szrj
1167*38fd1498Szrj/* (define_automaton string) describes names of automata generated and
1168*38fd1498Szrj   used for pipeline hazards recognition.  The names are separated by
1169*38fd1498Szrj   comma.  Actually it is possibly to generate the single automaton
1170*38fd1498Szrj   but unfortunately it can be very large.  If we use more one
1171*38fd1498Szrj   automata, the summary size of the automata usually is less than the
1172*38fd1498Szrj   single one.  The automaton name is used in define_cpu_unit and
1173*38fd1498Szrj   define_query_cpu_unit.  All automata should have unique names.  */
1174*38fd1498SzrjDEF_RTL_EXPR(DEFINE_AUTOMATON, "define_automaton", "s", RTX_EXTRA)
1175*38fd1498Szrj
1176*38fd1498Szrj/* (automata_option string) describes option for generation of
1177*38fd1498Szrj   automata.  Currently there are the following options:
1178*38fd1498Szrj
1179*38fd1498Szrj   o "no-minimization" which makes no minimization of automata.  This
1180*38fd1498Szrj     is only worth to do when we are debugging the description and
1181*38fd1498Szrj     need to look more accurately at reservations of states.
1182*38fd1498Szrj
1183*38fd1498Szrj   o "time" which means printing additional time statistics about
1184*38fd1498Szrj      generation of automata.
1185*38fd1498Szrj
1186*38fd1498Szrj   o "v" which means generation of file describing the result
1187*38fd1498Szrj     automata.  The file has suffix `.dfa' and can be used for the
1188*38fd1498Szrj     description verification and debugging.
1189*38fd1498Szrj
1190*38fd1498Szrj   o "w" which means generation of warning instead of error for
1191*38fd1498Szrj     non-critical errors.
1192*38fd1498Szrj
1193*38fd1498Szrj   o "ndfa" which makes nondeterministic finite state automata.
1194*38fd1498Szrj
1195*38fd1498Szrj   o "progress" which means output of a progress bar showing how many
1196*38fd1498Szrj     states were generated so far for automaton being processed.  */
1197*38fd1498SzrjDEF_RTL_EXPR(AUTOMATA_OPTION, "automata_option", "s", RTX_EXTRA)
1198*38fd1498Szrj
1199*38fd1498Szrj/* (define_reservation string string) names reservation (the first
1200*38fd1498Szrj   string) of cpu functional units (the 2nd string).  Sometimes unit
1201*38fd1498Szrj   reservations for different insns contain common parts.  In such
1202*38fd1498Szrj   case, you can describe common part and use its name (the 1st
1203*38fd1498Szrj   parameter) in regular expression in define_insn_reservation.  All
1204*38fd1498Szrj   define_reservations, define_cpu_units, and define_query_cpu_units
1205*38fd1498Szrj   should have unique names which may not be "nothing".  */
1206*38fd1498SzrjDEF_RTL_EXPR(DEFINE_RESERVATION, "define_reservation", "ss", RTX_EXTRA)
1207*38fd1498Szrj
1208*38fd1498Szrj/* (define_insn_reservation name default_latency condition regexpr)
1209*38fd1498Szrj   describes reservation of cpu functional units (the 3nd operand) for
1210*38fd1498Szrj   instruction which is selected by the condition (the 2nd parameter).
1211*38fd1498Szrj   The first parameter is used for output of debugging information.
1212*38fd1498Szrj   The reservations are described by a regular expression according
1213*38fd1498Szrj   the following syntax:
1214*38fd1498Szrj
1215*38fd1498Szrj       regexp = regexp "," oneof
1216*38fd1498Szrj              | oneof
1217*38fd1498Szrj
1218*38fd1498Szrj       oneof = oneof "|" allof
1219*38fd1498Szrj             | allof
1220*38fd1498Szrj
1221*38fd1498Szrj       allof = allof "+" repeat
1222*38fd1498Szrj             | repeat
1223*38fd1498Szrj
1224*38fd1498Szrj       repeat = element "*" number
1225*38fd1498Szrj              | element
1226*38fd1498Szrj
1227*38fd1498Szrj       element = cpu_function_unit_name
1228*38fd1498Szrj               | reservation_name
1229*38fd1498Szrj               | result_name
1230*38fd1498Szrj               | "nothing"
1231*38fd1498Szrj               | "(" regexp ")"
1232*38fd1498Szrj
1233*38fd1498Szrj       1. "," is used for describing start of the next cycle in
1234*38fd1498Szrj       reservation.
1235*38fd1498Szrj
1236*38fd1498Szrj       2. "|" is used for describing the reservation described by the
1237*38fd1498Szrj       first regular expression *or* the reservation described by the
1238*38fd1498Szrj       second regular expression *or* etc.
1239*38fd1498Szrj
1240*38fd1498Szrj       3. "+" is used for describing the reservation described by the
1241*38fd1498Szrj       first regular expression *and* the reservation described by the
1242*38fd1498Szrj       second regular expression *and* etc.
1243*38fd1498Szrj
1244*38fd1498Szrj       4. "*" is used for convenience and simply means sequence in
1245*38fd1498Szrj       which the regular expression are repeated NUMBER times with
1246*38fd1498Szrj       cycle advancing (see ",").
1247*38fd1498Szrj
1248*38fd1498Szrj       5. cpu functional unit name which means its reservation.
1249*38fd1498Szrj
1250*38fd1498Szrj       6. reservation name -- see define_reservation.
1251*38fd1498Szrj
1252*38fd1498Szrj       7. string "nothing" means no units reservation.  */
1253*38fd1498Szrj
1254*38fd1498SzrjDEF_RTL_EXPR(DEFINE_INSN_RESERVATION, "define_insn_reservation", "sies", RTX_EXTRA)
1255*38fd1498Szrj
1256*38fd1498Szrj/* Expressions used for insn attributes.  */
1257*38fd1498Szrj
1258*38fd1498Szrj/* Definition of an insn attribute.
1259*38fd1498Szrj   1st operand: name of the attribute
1260*38fd1498Szrj   2nd operand: comma-separated list of possible attribute values
1261*38fd1498Szrj   3rd operand: expression for the default value of the attribute.  */
1262*38fd1498SzrjDEF_RTL_EXPR(DEFINE_ATTR, "define_attr", "sse", RTX_EXTRA)
1263*38fd1498Szrj
1264*38fd1498Szrj/* Definition of an insn attribute that uses an existing enumerated type.
1265*38fd1498Szrj   1st operand: name of the attribute
1266*38fd1498Szrj   2nd operand: the name of the enumerated type
1267*38fd1498Szrj   3rd operand: expression for the default value of the attribute.  */
1268*38fd1498SzrjDEF_RTL_EXPR(DEFINE_ENUM_ATTR, "define_enum_attr", "sse", RTX_EXTRA)
1269*38fd1498Szrj
1270*38fd1498Szrj/* Marker for the name of an attribute.  */
1271*38fd1498SzrjDEF_RTL_EXPR(ATTR, "attr", "s", RTX_EXTRA)
1272*38fd1498Szrj
1273*38fd1498Szrj/* For use in the last (optional) operand of DEFINE_INSN or DEFINE_PEEPHOLE and
1274*38fd1498Szrj   in DEFINE_ASM_INSN to specify an attribute to assign to insns matching that
1275*38fd1498Szrj   pattern.
1276*38fd1498Szrj
1277*38fd1498Szrj   (set_attr "name" "value") is equivalent to
1278*38fd1498Szrj   (set (attr "name") (const_string "value"))  */
1279*38fd1498SzrjDEF_RTL_EXPR(SET_ATTR, "set_attr", "ss", RTX_EXTRA)
1280*38fd1498Szrj
1281*38fd1498Szrj/* In the last operand of DEFINE_INSN and DEFINE_PEEPHOLE, this can be used to
1282*38fd1498Szrj   specify that attribute values are to be assigned according to the
1283*38fd1498Szrj   alternative matched.
1284*38fd1498Szrj
1285*38fd1498Szrj   The following three expressions are equivalent:
1286*38fd1498Szrj
1287*38fd1498Szrj   (set (attr "att") (cond [(eq_attrq "alternative" "1") (const_string "a1")
1288*38fd1498Szrj			    (eq_attrq "alternative" "2") (const_string "a2")]
1289*38fd1498Szrj			   (const_string "a3")))
1290*38fd1498Szrj   (set_attr_alternative "att" [(const_string "a1") (const_string "a2")
1291*38fd1498Szrj				 (const_string "a3")])
1292*38fd1498Szrj   (set_attr "att" "a1,a2,a3")
1293*38fd1498Szrj */
1294*38fd1498SzrjDEF_RTL_EXPR(SET_ATTR_ALTERNATIVE, "set_attr_alternative", "sE", RTX_EXTRA)
1295*38fd1498Szrj
1296*38fd1498Szrj/* A conditional expression true if the value of the specified attribute of
1297*38fd1498Szrj   the current insn equals the specified value.  The first operand is the
1298*38fd1498Szrj   attribute name and the second is the comparison value.  */
1299*38fd1498SzrjDEF_RTL_EXPR(EQ_ATTR, "eq_attr", "ss", RTX_EXTRA)
1300*38fd1498Szrj
1301*38fd1498Szrj/* A special case of the above representing a set of alternatives.  The first
1302*38fd1498Szrj   operand is bitmap of the set, the second one is the default value.  */
1303*38fd1498SzrjDEF_RTL_EXPR(EQ_ATTR_ALT, "eq_attr_alt", "ii", RTX_EXTRA)
1304*38fd1498Szrj
1305*38fd1498Szrj/* A conditional expression which is true if the specified flag is
1306*38fd1498Szrj   true for the insn being scheduled in reorg.
1307*38fd1498Szrj
1308*38fd1498Szrj   genattr.c defines the following flags which can be tested by
1309*38fd1498Szrj   (attr_flag "foo") expressions in eligible_for_delay: forward, backward.  */
1310*38fd1498Szrj
1311*38fd1498SzrjDEF_RTL_EXPR (ATTR_FLAG, "attr_flag", "s", RTX_EXTRA)
1312*38fd1498Szrj
1313*38fd1498Szrj/* General conditional. The first operand is a vector composed of pairs of
1314*38fd1498Szrj   expressions.  The first element of each pair is evaluated, in turn.
1315*38fd1498Szrj   The value of the conditional is the second expression of the first pair
1316*38fd1498Szrj   whose first expression evaluates nonzero.  If none of the expressions is
1317*38fd1498Szrj   true, the second operand will be used as the value of the conditional.  */
1318*38fd1498SzrjDEF_RTL_EXPR(COND, "cond", "Ee", RTX_EXTRA)
1319*38fd1498Szrj
1320*38fd1498Szrj/* Definition of a pattern substitution meta operation on a DEFINE_EXPAND
1321*38fd1498Szrj   or a DEFINE_INSN.  Automatically generates new instances of DEFINE_INSNs
1322*38fd1498Szrj   that match the substitution pattern.
1323*38fd1498Szrj
1324*38fd1498Szrj   Operand:
1325*38fd1498Szrj   0: The name of the substitition template.
1326*38fd1498Szrj   1: Input template to match to see if a substitution is applicable.
1327*38fd1498Szrj   2: A C expression giving an additional condition for the generated
1328*38fd1498Szrj      new define_expand or define_insn.
1329*38fd1498Szrj   3: Output tempalate to generate via substitution.
1330*38fd1498Szrj
1331*38fd1498Szrj   Within a DEFINE_SUBST template, the meaning of some RTL expressions is
1332*38fd1498Szrj   different from their usual interpretation: a MATCH_OPERAND matches any
1333*38fd1498Szrj   expression tree with matching machine mode or with VOIDmode.  Likewise,
1334*38fd1498Szrj   MATCH_OP_DUP and MATCH_DUP match more liberally in a DEFINE_SUBST than
1335*38fd1498Szrj   in other RTL expressions.  MATCH_OPERATOR matches all common operators
1336*38fd1498Szrj   but also UNSPEC, UNSPEC_VOLATILE, and MATCH_OPERATORS from the input
1337*38fd1498Szrj   DEFINE_EXPAND or DEFINE_INSN.  */
1338*38fd1498SzrjDEF_RTL_EXPR(DEFINE_SUBST, "define_subst", "sEsE", RTX_EXTRA)
1339*38fd1498Szrj
1340*38fd1498Szrj/* Substitution attribute to apply a DEFINE_SUBST to a pattern.
1341*38fd1498Szrj
1342*38fd1498Szrj   Operand:
1343*38fd1498Szrj   0: The name of the subst-attribute.
1344*38fd1498Szrj   1: The name of the DEFINE_SUBST to be applied for this attribute.
1345*38fd1498Szrj   2: String to substitute for the subst-attribute name in the pattern
1346*38fd1498Szrj      name, for the case that the DEFINE_SUBST is not applied (i.e. the
1347*38fd1498Szrj      unmodified version of the pattern).
1348*38fd1498Szrj   3: String to substitute for the subst-attribute name in the pattern
1349*38fd1498Szrj      name, for the case that the DEFINE_SUBST is applied to the patten.
1350*38fd1498Szrj
1351*38fd1498Szrj   The use of DEFINE_SUBST and DEFINE_SUBST_ATTR is explained in the
1352*38fd1498Szrj   GCC internals manual, under "RTL Templates Transformations".  */
1353*38fd1498SzrjDEF_RTL_EXPR(DEFINE_SUBST_ATTR, "define_subst_attr", "ssss", RTX_EXTRA)
1354*38fd1498Szrj
1355*38fd1498Szrj#endif /* GENERATOR_FILE */
1356*38fd1498Szrj
1357*38fd1498Szrj/*
1358*38fd1498SzrjLocal variables:
1359*38fd1498Szrjmode:c
1360*38fd1498SzrjEnd:
1361*38fd1498Szrj*/
1362