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