118334Speter/* This file contains the definitions and documentation for the
218334Speter   Register Transfer Expressions (rtx's) that make up the
318334Speter   Register Transfer Language (rtl) used in the Back End of the GNU compiler.
4169689Skan   Copyright (C) 1987, 1988, 1992, 1994, 1995, 1997, 1998, 1999, 2000, 2004,
5169689Skan   2005, 2006
690075Sobrien   Free Software Foundation, Inc.
718334Speter
890075SobrienThis file is part of GCC.
918334Speter
1090075SobrienGCC is free software; you can redistribute it and/or modify it under
1190075Sobrienthe terms of the GNU General Public License as published by the Free
1290075SobrienSoftware Foundation; either version 2, or (at your option) any later
1390075Sobrienversion.
1418334Speter
1590075SobrienGCC is distributed in the hope that it will be useful, but WITHOUT ANY
1690075SobrienWARRANTY; without even the implied warranty of MERCHANTABILITY or
1790075SobrienFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
1890075Sobrienfor more details.
1918334Speter
2018334SpeterYou should have received a copy of the GNU General Public License
2190075Sobrienalong with GCC; see the file COPYING.  If not, write to the Free
22169689SkanSoftware Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
23169689Skan02110-1301, USA.  */
2418334Speter
2518334Speter
2618334Speter/* Expression definitions and descriptions for all targets are in this file.
2718334Speter   Some will not be used for some targets.
2818334Speter
2918334Speter   The fields in the cpp macro call "DEF_RTL_EXPR()"
3018334Speter   are used to create declarations in the C source of the compiler.
3118334Speter
3218334Speter   The fields are:
3318334Speter
3418334Speter   1.  The internal name of the rtx used in the C source.
3518334Speter   It is a tag in the enumeration "enum rtx_code" defined in "rtl.h".
3618334Speter   By convention these are in UPPER_CASE.
3718334Speter
3818334Speter   2.  The name of the rtx in the external ASCII format read by
3918334Speter   read_rtx(), and printed by print_rtx().
4018334Speter   These names are stored in rtx_name[].
4118334Speter   By convention these are the internal (field 1) names in lower_case.
4218334Speter
43132718Skan   3.  The print format, and type of each rtx->u.fld[] (field) in this rtx.
4418334Speter   These formats are stored in rtx_format[].
4518334Speter   The meaning of the formats is documented in front of this array in rtl.c
4618334Speter   
4718334Speter   4.  The class of the rtx.  These are stored in rtx_class and are accessed
4818334Speter   via the GET_RTX_CLASS macro.  They are defined as follows:
4918334Speter
50169689Skan     RTX_CONST_OBJ
51169689Skan         an rtx code that can be used to represent a constant object
52169689Skan         (e.g, CONST_INT)
53169689Skan     RTX_OBJ
54169689Skan         an rtx code that can be used to represent an object (e.g, REG, MEM)
55169689Skan     RTX_COMPARE
56169689Skan         an rtx code for a comparison (e.g, LT, GT)
57169689Skan     RTX_COMM_COMPARE
58169689Skan         an rtx code for a commutative comparison (e.g, EQ, NE, ORDERED)
59169689Skan     RTX_UNARY
60169689Skan         an rtx code for a unary arithmetic expression (e.g, NEG, NOT)
61169689Skan     RTX_COMM_ARITH
62169689Skan         an rtx code for a commutative binary operation (e.g,, PLUS, MULT)
63169689Skan     RTX_TERNARY
64169689Skan         an rtx code for a non-bitfield three input operation (IF_THEN_ELSE)
65169689Skan     RTX_BIN_ARITH
66169689Skan         an rtx code for a non-commutative binary operation (e.g., MINUS, DIV)
67169689Skan     RTX_BITFIELD_OPS
68169689Skan         an rtx code for a bit-field operation (ZERO_EXTRACT, SIGN_EXTRACT)
69169689Skan     RTX_INSN
70169689Skan         an rtx code for a machine insn (INSN, JUMP_INSN, CALL_INSN)
71169689Skan     RTX_MATCH
72169689Skan         an rtx code for something that matches in insns (e.g, MATCH_DUP)
73169689Skan     RTX_AUTOINC
74169689Skan         an rtx code for autoincrement addressing modes (e.g. POST_DEC)
75169689Skan     RTX_EXTRA
76169689Skan         everything else
7718334Speter
78169689Skan   All of the expressions that appear only in machine descriptions,
79169689Skan   not in RTL used by the compiler itself, are at the end of the file.  */
8018334Speter
81169689Skan/* Unknown, or no such operation; the enumeration constant should have
82169689Skan   value zero.  */
83169689SkanDEF_RTL_EXPR(UNKNOWN, "UnKnown", "*", RTX_EXTRA)
8418334Speter
8518334Speter/* ---------------------------------------------------------------------
8618334Speter   Expressions used in constructing lists.
8718334Speter   --------------------------------------------------------------------- */
8818334Speter
8918334Speter/* a linked list of expressions */
90169689SkanDEF_RTL_EXPR(EXPR_LIST, "expr_list", "ee", RTX_EXTRA)
9118334Speter
9218334Speter/* a linked list of instructions.
9318334Speter   The insns are represented in print by their uids.  */
94169689SkanDEF_RTL_EXPR(INSN_LIST, "insn_list", "ue", RTX_EXTRA)
9518334Speter
96169689Skan/* a linked list of dependencies. 
97169689Skan   The insns are represented in print by their uids. 
98169689Skan   Operand 2 is the status of a dependence (see sched-int.h for more).  */
99169689SkanDEF_RTL_EXPR(DEPS_LIST, "deps_list", "uei", RTX_EXTRA)
10018334Speter
10118334Speter/* SEQUENCE appears in the result of a `gen_...' function
10218334Speter   for a DEFINE_EXPAND that wants to make several insns.
10318334Speter   Its elements are the bodies of the insns that should be made.
10418334Speter   `emit_insn' takes the SEQUENCE apart and makes separate insns.  */
105169689SkanDEF_RTL_EXPR(SEQUENCE, "sequence", "E", RTX_EXTRA)
10618334Speter
10790075Sobrien/* Refers to the address of its argument.  This is only used in alias.c.  */
108169689SkanDEF_RTL_EXPR(ADDRESS, "address", "e", RTX_MATCH)
10918334Speter
11018334Speter/* ----------------------------------------------------------------------
11118334Speter   Expression types used for things in the instruction chain.
11218334Speter
11318334Speter   All formats must start with "iuu" to handle the chain.
11418334Speter   Each insn expression holds an rtl instruction and its semantics
11518334Speter   during back-end processing.
116132718Skan   See macros's in "rtl.h" for the meaning of each rtx->u.fld[].
11718334Speter
11818334Speter   ---------------------------------------------------------------------- */
11918334Speter
12018334Speter/* An instruction that cannot jump.  */
121169689SkanDEF_RTL_EXPR(INSN, "insn", "iuuBieiee", RTX_INSN)
12218334Speter
12318334Speter/* An instruction that can possibly jump.
124132718Skan   Fields ( rtx->u.fld[] ) have exact same meaning as INSN's.  */
125169689SkanDEF_RTL_EXPR(JUMP_INSN, "jump_insn", "iuuBieiee0", RTX_INSN)
12618334Speter
12718334Speter/* An instruction that can possibly call a subroutine
12818334Speter   but which will not change which instruction comes next
12918334Speter   in the current function.
130132718Skan   Field ( rtx->u.fld[9] ) is CALL_INSN_FUNCTION_USAGE.
131132718Skan   All other fields ( rtx->u.fld[] ) have exact same meaning as INSN's.  */
132169689SkanDEF_RTL_EXPR(CALL_INSN, "call_insn", "iuuBieieee", RTX_INSN)
13318334Speter
13418334Speter/* A marker that indicates that control will not flow through.  */
135169689SkanDEF_RTL_EXPR(BARRIER, "barrier", "iuu000000", RTX_EXTRA)
13618334Speter
13718334Speter/* Holds a label that is followed by instructions.
13818334Speter   Operand:
139132718Skan   4: is used in jump.c for the use-count of the label.
140132718Skan   5: is used in flow.c to point to the chain of label_ref's to this label.
141132718Skan   6: is a number that is unique in the entire compilation.
142132718Skan   7: is the user-given name of the label, if any.  */
143169689SkanDEF_RTL_EXPR(CODE_LABEL, "code_label", "iuuB00is", RTX_EXTRA)
144117395Skan
145169689Skan#ifdef USE_MAPPED_LOCATION
14618334Speter/* Say where in the code a source line starts, for symbol table's sake.
14790075Sobrien   Operand:
148169689Skan   4: unused if line number > 0, note-specific data otherwise.
149169689Skan   5: line number if > 0, enum note_insn otherwise.
150169689Skan   6: CODE_LABEL_NUMBER if line number == NOTE_INSN_DELETED_LABEL.  */
151169689Skan#else
152169689Skan/* Say where in the code a source line starts, for symbol table's sake.
153169689Skan   Operand:
154132718Skan   4: filename, if line number > 0, note-specific data otherwise.
155132718Skan   5: line number if > 0, enum note_insn otherwise.
156132718Skan   6: unique number if line number == note_insn_deleted_label.  */
157169689Skan#endif
158169689SkanDEF_RTL_EXPR(NOTE, "note", "iuuB0ni", RTX_EXTRA)
15918334Speter
16018334Speter/* ----------------------------------------------------------------------
16118334Speter   Top level constituents of INSN, JUMP_INSN and CALL_INSN.
16218334Speter   ---------------------------------------------------------------------- */
16318334Speter   
16490075Sobrien/* Conditionally execute code.
16590075Sobrien   Operand 0 is the condition that if true, the code is executed.
16690075Sobrien   Operand 1 is the code to be executed (typically a SET). 
16790075Sobrien
16890075Sobrien   Semantics are that there are no side effects if the condition
16990075Sobrien   is false.  This pattern is created automatically by the if_convert
17090075Sobrien   pass run after reload or by target-specific splitters.  */
171169689SkanDEF_RTL_EXPR(COND_EXEC, "cond_exec", "ee", RTX_EXTRA)
17290075Sobrien
17390075Sobrien/* Several operations to be done in parallel (perhaps under COND_EXEC).  */
174169689SkanDEF_RTL_EXPR(PARALLEL, "parallel", "E", RTX_EXTRA)
17518334Speter
17618334Speter/* A string that is passed through to the assembler as input.
17718334Speter     One can obviously pass comments through by using the
17818334Speter     assembler comment syntax.
17918334Speter     These occur in an insn all by themselves as the PATTERN.
18018334Speter     They also appear inside an ASM_OPERANDS
18118334Speter     as a convenient way to hold a string.  */
182169689SkanDEF_RTL_EXPR(ASM_INPUT, "asm_input", "s", RTX_EXTRA)
18318334Speter
184169689Skan#ifdef USE_MAPPED_LOCATION
18518334Speter/* An assembler instruction with operands.
18618334Speter   1st operand is the instruction template.
18718334Speter   2nd operand is the constraint for the output.
18818334Speter   3rd operand is the number of the output this expression refers to.
18918334Speter     When an insn stores more than one value, a separate ASM_OPERANDS
19018334Speter     is made for each output; this integer distinguishes them.
19118334Speter   4th is a vector of values of input operands.
19218334Speter   5th is a vector of modes and constraints for the input operands.
19318334Speter     Each element is an ASM_INPUT containing a constraint string
19418334Speter     and whose mode indicates the mode of the input operand.
195169689Skan   6th is the source line number.  */
196169689SkanDEF_RTL_EXPR(ASM_OPERANDS, "asm_operands", "ssiEEi", RTX_EXTRA)
197169689Skan#else
198169689Skan/* An assembler instruction with operands.
199169689Skan   1st operand is the instruction template.
200169689Skan   2nd operand is the constraint for the output.
201169689Skan   3rd operand is the number of the output this expression refers to.
202169689Skan     When an insn stores more than one value, a separate ASM_OPERANDS
203169689Skan     is made for each output; this integer distinguishes them.
204169689Skan   4th is a vector of values of input operands.
205169689Skan   5th is a vector of modes and constraints for the input operands.
206169689Skan     Each element is an ASM_INPUT containing a constraint string
207169689Skan     and whose mode indicates the mode of the input operand.
20818334Speter   6th is the name of the containing source file.
20918334Speter   7th is the source line number.  */
210169689SkanDEF_RTL_EXPR(ASM_OPERANDS, "asm_operands", "ssiEEsi", RTX_EXTRA)
211169689Skan#endif
21218334Speter
21318334Speter/* A machine-specific operation.
21418334Speter   1st operand is a vector of operands being used by the operation so that
21518334Speter     any needed reloads can be done.
21618334Speter   2nd operand is a unique value saying which of a number of machine-specific
21718334Speter     operations is to be performed.
21818334Speter   (Note that the vector must be the first operand because of the way that
21918334Speter   genrecog.c record positions within an insn.)
22018334Speter   This can occur all by itself in a PATTERN, as a component of a PARALLEL,
22118334Speter   or inside an expression.  */
222169689SkanDEF_RTL_EXPR(UNSPEC, "unspec", "Ei", RTX_EXTRA)
22318334Speter
22418334Speter/* Similar, but a volatile operation and one which may trap.  */
225169689SkanDEF_RTL_EXPR(UNSPEC_VOLATILE, "unspec_volatile", "Ei", RTX_EXTRA)
22618334Speter
22718334Speter/* Vector of addresses, stored as full words.  */
22818334Speter/* Each element is a LABEL_REF to a CODE_LABEL whose address we want.  */
229169689SkanDEF_RTL_EXPR(ADDR_VEC, "addr_vec", "E", RTX_EXTRA)
23018334Speter
23118334Speter/* Vector of address differences X0 - BASE, X1 - BASE, ...
23218334Speter   First operand is BASE; the vector contains the X's.
23318334Speter   The machine mode of this rtx says how much space to leave
23450397Sobrien   for each difference and is adjusted by branch shortening if
23550397Sobrien   CASE_VECTOR_SHORTEN_MODE is defined.
23650397Sobrien   The third and fourth operands store the target labels with the
23750397Sobrien   minimum and maximum addresses respectively.
23850397Sobrien   The fifth operand stores flags for use by branch shortening.
23950397Sobrien  Set at the start of shorten_branches:
24050397Sobrien   min_align: the minimum alignment for any of the target labels.
24150397Sobrien   base_after_vec: true iff BASE is after the ADDR_DIFF_VEC.
24250397Sobrien   min_after_vec: true iff minimum addr target label is after the ADDR_DIFF_VEC.
24350397Sobrien   max_after_vec: true iff maximum addr target label is after the ADDR_DIFF_VEC.
24450397Sobrien   min_after_base: true iff minimum address target label is after BASE.
24550397Sobrien   max_after_base: true iff maximum address target label is after BASE.
24650397Sobrien  Set by the actual branch shortening process:
24750397Sobrien   offset_unsigned: true iff offsets have to be treated as unsigned.
24850397Sobrien   scale: scaling that is necessary to make offsets fit into the mode.
24918334Speter
25050397Sobrien   The third, fourth and fifth operands are only valid when
25150397Sobrien   CASE_VECTOR_SHORTEN_MODE is defined, and only in an optimizing
25250397Sobrien   compilations.  */
25350397Sobrien     
254169689SkanDEF_RTL_EXPR(ADDR_DIFF_VEC, "addr_diff_vec", "eEee0", RTX_EXTRA)
25550397Sobrien
25690075Sobrien/* Memory prefetch, with attributes supported on some targets.
25790075Sobrien   Operand 1 is the address of the memory to fetch.
25890075Sobrien   Operand 2 is 1 for a write access, 0 otherwise.
25990075Sobrien   Operand 3 is the level of temporal locality; 0 means there is no
26090075Sobrien   temporal locality and 1, 2, and 3 are for increasing levels of temporal
26190075Sobrien   locality.
26290075Sobrien
26390075Sobrien   The attributes specified by operands 2 and 3 are ignored for targets
26490075Sobrien   whose prefetch instructions do not support them.  */
265169689SkanDEF_RTL_EXPR(PREFETCH, "prefetch", "eee", RTX_EXTRA)
26690075Sobrien
26718334Speter/* ----------------------------------------------------------------------
26818334Speter   At the top level of an instruction (perhaps under PARALLEL).
26918334Speter   ---------------------------------------------------------------------- */
27018334Speter
27118334Speter/* Assignment.
27218334Speter   Operand 1 is the location (REG, MEM, PC, CC0 or whatever) assigned to.
27318334Speter   Operand 2 is the value stored there.
27418334Speter   ALL assignment must use SET.
27518334Speter   Instructions that do multiple assignments must use multiple SET,
27618334Speter   under PARALLEL.  */
277169689SkanDEF_RTL_EXPR(SET, "set", "ee", RTX_EXTRA)
27818334Speter
27918334Speter/* Indicate something is used in a way that we don't want to explain.
28018334Speter   For example, subroutine calls will use the register
28118334Speter   in which the static chain is passed.  */
282169689SkanDEF_RTL_EXPR(USE, "use", "e", RTX_EXTRA)
28318334Speter
28418334Speter/* Indicate something is clobbered in a way that we don't want to explain.
28518334Speter   For example, subroutine calls will clobber some physical registers
28618334Speter   (the ones that are by convention not saved).  */
287169689SkanDEF_RTL_EXPR(CLOBBER, "clobber", "e", RTX_EXTRA)
28818334Speter
28918334Speter/* Call a subroutine.
29018334Speter   Operand 1 is the address to call.
29118334Speter   Operand 2 is the number of arguments.  */
29218334Speter
293169689SkanDEF_RTL_EXPR(CALL, "call", "ee", RTX_EXTRA)
29418334Speter
29518334Speter/* Return from a subroutine.  */
29618334Speter
297169689SkanDEF_RTL_EXPR(RETURN, "return", "", RTX_EXTRA)
29818334Speter
29918334Speter/* Conditional trap.
30018334Speter   Operand 1 is the condition.
30118334Speter   Operand 2 is the trap code.
30218334Speter   For an unconditional trap, make the condition (const_int 1).  */
303169689SkanDEF_RTL_EXPR(TRAP_IF, "trap_if", "ee", RTX_EXTRA)
30418334Speter
30590075Sobrien/* Placeholder for _Unwind_Resume before we know if a function call
30690075Sobrien   or a branch is needed.  Operand 1 is the exception region from
30790075Sobrien   which control is flowing.  */
308169689SkanDEF_RTL_EXPR(RESX, "resx", "i", RTX_EXTRA)
30990075Sobrien
31018334Speter/* ----------------------------------------------------------------------
31118334Speter   Primitive values for use in expressions.
31218334Speter   ---------------------------------------------------------------------- */
31318334Speter
31418334Speter/* numeric integer constant */
315169689SkanDEF_RTL_EXPR(CONST_INT, "const_int", "w", RTX_CONST_OBJ)
31618334Speter
31790075Sobrien/* numeric floating point constant.
318117395Skan   Operands hold the value.  They are all 'w' and there may be from 2 to 6;
319117395Skan   see real.h.  */
320169689SkanDEF_RTL_EXPR(CONST_DOUBLE, "const_double", CONST_DOUBLE_FORMAT, RTX_CONST_OBJ)
32118334Speter
32296263Sobrien/* Describes a vector constant.  */
323169689SkanDEF_RTL_EXPR(CONST_VECTOR, "const_vector", "E", RTX_CONST_OBJ)
32496263Sobrien
325169689Skan/* String constant.  Used for attributes in machine descriptions and
326169689Skan   for special cases in DWARF2 debug output.  NOT used for source-
327169689Skan   language string constants.  */
328169689SkanDEF_RTL_EXPR(CONST_STRING, "const_string", "s", RTX_OBJ)
32918334Speter
33018334Speter/* This is used to encapsulate an expression whose value is constant
33118334Speter   (such as the sum of a SYMBOL_REF and a CONST_INT) so that it will be
33218334Speter   recognized as a constant operand rather than by arithmetic instructions.  */
33318334Speter
334169689SkanDEF_RTL_EXPR(CONST, "const", "e", RTX_CONST_OBJ)
33518334Speter
33618334Speter/* program counter.  Ordinary jumps are represented
33718334Speter   by a SET whose first operand is (PC).  */
338169689SkanDEF_RTL_EXPR(PC, "pc", "", RTX_OBJ)
33918334Speter
340169689Skan/* Used in the cselib routines to describe a value.  Objects of this
341169689Skan   kind are only allocated in cselib.c, in an alloc pool instead of
342169689Skan   in GC memory.  The only operand of a VALUE is a cselib_val_struct.  */
343169689SkanDEF_RTL_EXPR(VALUE, "value", "0", RTX_OBJ)
34490075Sobrien
34550397Sobrien/* A register.  The "operand" is the register number, accessed with
34650397Sobrien   the REGNO macro.  If this number is less than FIRST_PSEUDO_REGISTER
34750397Sobrien   than a hardware register is being referred to.  The second operand
34890075Sobrien   holds the original register number - this will be different for a
349169689Skan   pseudo register that got turned into a hard register.  The third
350169689Skan   operand points to a reg_attrs structure.
35190075Sobrien   This rtx needs to have as many (or more) fields as a MEM, since we
35290075Sobrien   can change REG rtx's into MEMs during reload.  */
353169689SkanDEF_RTL_EXPR(REG, "reg", "i00", RTX_OBJ)
35418334Speter
35518334Speter/* A scratch register.  This represents a register used only within a
35618334Speter   single insn.  It will be turned into a REG during register allocation
35718334Speter   or reload unless the constraint indicates that the register won't be
35818334Speter   needed, in which case it can remain a SCRATCH.  This code is
35918334Speter   marked as having one operand so it can be turned into a REG.  */
360169689SkanDEF_RTL_EXPR(SCRATCH, "scratch", "0", RTX_OBJ)
36118334Speter
36218334Speter/* One word of a multi-word value.
36318334Speter   The first operand is the complete value; the second says which word.
36418334Speter   The WORDS_BIG_ENDIAN flag controls whether word number 0
36518334Speter   (as numbered in a SUBREG) is the most or least significant word.
36618334Speter
36718334Speter   This is also used to refer to a value in a different machine mode.
36818334Speter   For example, it can be used to refer to a SImode value as if it were
36918334Speter   Qimode, or vice versa.  Then the word number is always 0.  */
370169689SkanDEF_RTL_EXPR(SUBREG, "subreg", "ei", RTX_EXTRA)
37118334Speter
37218334Speter/* This one-argument rtx is used for move instructions
37318334Speter   that are guaranteed to alter only the low part of a destination.
37418334Speter   Thus, (SET (SUBREG:HI (REG...)) (MEM:HI ...))
37518334Speter   has an unspecified effect on the high part of REG,
37618334Speter   but (SET (STRICT_LOW_PART (SUBREG:HI (REG...))) (MEM:HI ...))
37718334Speter   is guaranteed to alter only the bits of REG that are in HImode.
37818334Speter
37918334Speter   The actual instruction used is probably the same in both cases,
38018334Speter   but the register constraints may be tighter when STRICT_LOW_PART
38118334Speter   is in use.  */
38218334Speter
383169689SkanDEF_RTL_EXPR(STRICT_LOW_PART, "strict_low_part", "e", RTX_EXTRA)
38418334Speter
38518334Speter/* (CONCAT a b) represents the virtual concatenation of a and b
38618334Speter   to make a value that has as many bits as a and b put together.
38718334Speter   This is used for complex values.  Normally it appears only
38818334Speter   in DECL_RTLs and during RTL generation, but not in the insn chain.  */
389169689SkanDEF_RTL_EXPR(CONCAT, "concat", "ee", RTX_OBJ)
39018334Speter
39190075Sobrien/* A memory location; operand is the address.  The second operand is the
39290075Sobrien   alias set to which this MEM belongs.  We use `0' instead of `w' for this
39390075Sobrien   field so that the field need not be specified in machine descriptions.  */
394169689SkanDEF_RTL_EXPR(MEM, "mem", "e0", RTX_OBJ)
39518334Speter
39618334Speter/* Reference to an assembler label in the code for this function.
397169689Skan   The operand is a CODE_LABEL found in the insn chain.  */
398169689SkanDEF_RTL_EXPR(LABEL_REF, "label_ref", "u", RTX_CONST_OBJ)
39918334Speter
400132718Skan/* Reference to a named label: 
401132718Skan   Operand 0: label name
402132718Skan   Operand 1: flags (see SYMBOL_FLAG_* in rtl.h)
403132718Skan   Operand 2: tree from which this symbol is derived, or null.
404132718Skan   This is either a DECL node, or some kind of constant.  */
405169689SkanDEF_RTL_EXPR(SYMBOL_REF, "symbol_ref", "s00", RTX_CONST_OBJ)
40618334Speter
40718334Speter/* The condition code register is represented, in our imagination,
40818334Speter   as a register holding a value that can be compared to zero.
40918334Speter   In fact, the machine has already compared them and recorded the
41018334Speter   results; but instructions that look at the condition code
41118334Speter   pretend to be looking at the entire value and comparing it.  */
412169689SkanDEF_RTL_EXPR(CC0, "cc0", "", RTX_OBJ)
41318334Speter
41418334Speter/* ----------------------------------------------------------------------
41518334Speter   Expressions for operators in an rtl pattern
41618334Speter   ---------------------------------------------------------------------- */
41718334Speter
41818334Speter/* if_then_else.  This is used in representing ordinary
41918334Speter   conditional jump instructions.
42018334Speter     Operand:
42118334Speter     0:  condition
42218334Speter     1:  then expr
42318334Speter     2:  else expr */
424169689SkanDEF_RTL_EXPR(IF_THEN_ELSE, "if_then_else", "eee", RTX_TERNARY)
42518334Speter
42618334Speter/* Comparison, produces a condition code result.  */
427169689SkanDEF_RTL_EXPR(COMPARE, "compare", "ee", RTX_BIN_ARITH)
42818334Speter
42918334Speter/* plus */
430169689SkanDEF_RTL_EXPR(PLUS, "plus", "ee", RTX_COMM_ARITH)
43118334Speter
43218334Speter/* Operand 0 minus operand 1.  */
433169689SkanDEF_RTL_EXPR(MINUS, "minus", "ee", RTX_BIN_ARITH)
43418334Speter
43518334Speter/* Minus operand 0.  */
436169689SkanDEF_RTL_EXPR(NEG, "neg", "e", RTX_UNARY)
43718334Speter
438169689SkanDEF_RTL_EXPR(MULT, "mult", "ee", RTX_COMM_ARITH)
43918334Speter
44018334Speter/* Operand 0 divided by operand 1.  */
441169689SkanDEF_RTL_EXPR(DIV, "div", "ee", RTX_BIN_ARITH)
44218334Speter/* Remainder of operand 0 divided by operand 1.  */
443169689SkanDEF_RTL_EXPR(MOD, "mod", "ee", RTX_BIN_ARITH)
44418334Speter
44518334Speter/* Unsigned divide and remainder.  */
446169689SkanDEF_RTL_EXPR(UDIV, "udiv", "ee", RTX_BIN_ARITH)
447169689SkanDEF_RTL_EXPR(UMOD, "umod", "ee", RTX_BIN_ARITH)
44818334Speter
44918334Speter/* Bitwise operations.  */
450169689SkanDEF_RTL_EXPR(AND, "and", "ee", RTX_COMM_ARITH)
451169689SkanDEF_RTL_EXPR(IOR, "ior", "ee", RTX_COMM_ARITH)
452169689SkanDEF_RTL_EXPR(XOR, "xor", "ee", RTX_COMM_ARITH)
453169689SkanDEF_RTL_EXPR(NOT, "not", "e", RTX_UNARY)
45418334Speter
45518334Speter/* Operand:
45618334Speter     0:  value to be shifted.
45718334Speter     1:  number of bits.  */
458169689SkanDEF_RTL_EXPR(ASHIFT, "ashift", "ee", RTX_BIN_ARITH) /* shift left */
459169689SkanDEF_RTL_EXPR(ROTATE, "rotate", "ee", RTX_BIN_ARITH) /* rotate left */
460169689SkanDEF_RTL_EXPR(ASHIFTRT, "ashiftrt", "ee", RTX_BIN_ARITH) /* arithmetic shift right */
461169689SkanDEF_RTL_EXPR(LSHIFTRT, "lshiftrt", "ee", RTX_BIN_ARITH) /* logical shift right */
462169689SkanDEF_RTL_EXPR(ROTATERT, "rotatert", "ee", RTX_BIN_ARITH) /* rotate right */
46318334Speter
46418334Speter/* Minimum and maximum values of two operands.  We need both signed and
46518334Speter   unsigned forms.  (We cannot use MIN for SMIN because it conflicts
466169689Skan   with a macro of the same name.)   The signed variants should be used
467169689Skan   with floating point.  Further, if both operands are zeros, or if either
468169689Skan   operand is NaN, then it is unspecified which of the two operands is
469169689Skan   returned as the result.  */
47018334Speter
471169689SkanDEF_RTL_EXPR(SMIN, "smin", "ee", RTX_COMM_ARITH)
472169689SkanDEF_RTL_EXPR(SMAX, "smax", "ee", RTX_COMM_ARITH)
473169689SkanDEF_RTL_EXPR(UMIN, "umin", "ee", RTX_COMM_ARITH)
474169689SkanDEF_RTL_EXPR(UMAX, "umax", "ee", RTX_COMM_ARITH)
47518334Speter
47618334Speter/* These unary operations are used to represent incrementation
47718334Speter   and decrementation as they occur in memory addresses.
47818334Speter   The amount of increment or decrement are not represented
47918334Speter   because they can be understood from the machine-mode of the
48018334Speter   containing MEM.  These operations exist in only two cases:
48118334Speter   1. pushes onto the stack.
48218334Speter   2. created automatically by the life_analysis pass in flow.c.  */
483169689SkanDEF_RTL_EXPR(PRE_DEC, "pre_dec", "e", RTX_AUTOINC)
484169689SkanDEF_RTL_EXPR(PRE_INC, "pre_inc", "e", RTX_AUTOINC)
485169689SkanDEF_RTL_EXPR(POST_DEC, "post_dec", "e", RTX_AUTOINC)
486169689SkanDEF_RTL_EXPR(POST_INC, "post_inc", "e", RTX_AUTOINC)
48718334Speter
48852284Sobrien/* These binary operations are used to represent generic address
48952284Sobrien   side-effects in memory addresses, except for simple incrementation
49052284Sobrien   or decrementation which use the above operations.  They are
49190075Sobrien   created automatically by the life_analysis pass in flow.c.
49290075Sobrien   The first operand is a REG which is used as the address.
49390075Sobrien   The second operand is an expression that is assigned to the
49490075Sobrien   register, either before (PRE_MODIFY) or after (POST_MODIFY)
49590075Sobrien   evaluating the address.
49690075Sobrien   Currently, the compiler can only handle second operands of the
49790075Sobrien   form (plus (reg) (reg)) and (plus (reg) (const_int)), where
49890075Sobrien   the first operand of the PLUS has to be the same register as
49990075Sobrien   the first operand of the *_MODIFY.  */
500169689SkanDEF_RTL_EXPR(PRE_MODIFY, "pre_modify", "ee", RTX_AUTOINC)
501169689SkanDEF_RTL_EXPR(POST_MODIFY, "post_modify", "ee", RTX_AUTOINC)
50252284Sobrien
50318334Speter/* Comparison operations.  The ordered comparisons exist in two
50418334Speter   flavors, signed and unsigned.  */
505169689SkanDEF_RTL_EXPR(NE, "ne", "ee", RTX_COMM_COMPARE)
506169689SkanDEF_RTL_EXPR(EQ, "eq", "ee", RTX_COMM_COMPARE)
507169689SkanDEF_RTL_EXPR(GE, "ge", "ee", RTX_COMPARE)
508169689SkanDEF_RTL_EXPR(GT, "gt", "ee", RTX_COMPARE)
509169689SkanDEF_RTL_EXPR(LE, "le", "ee", RTX_COMPARE)
510169689SkanDEF_RTL_EXPR(LT, "lt", "ee", RTX_COMPARE)
511169689SkanDEF_RTL_EXPR(GEU, "geu", "ee", RTX_COMPARE)
512169689SkanDEF_RTL_EXPR(GTU, "gtu", "ee", RTX_COMPARE)
513169689SkanDEF_RTL_EXPR(LEU, "leu", "ee", RTX_COMPARE)
514169689SkanDEF_RTL_EXPR(LTU, "ltu", "ee", RTX_COMPARE)
51518334Speter
516132718Skan/* Additional floating point unordered comparison flavors.  */
517169689SkanDEF_RTL_EXPR(UNORDERED, "unordered", "ee", RTX_COMM_COMPARE)
518169689SkanDEF_RTL_EXPR(ORDERED, "ordered", "ee", RTX_COMM_COMPARE)
51990075Sobrien
520117395Skan/* These are equivalent to unordered or ...  */
521169689SkanDEF_RTL_EXPR(UNEQ, "uneq", "ee", RTX_COMM_COMPARE)
522169689SkanDEF_RTL_EXPR(UNGE, "unge", "ee", RTX_COMPARE)
523169689SkanDEF_RTL_EXPR(UNGT, "ungt", "ee", RTX_COMPARE)
524169689SkanDEF_RTL_EXPR(UNLE, "unle", "ee", RTX_COMPARE)
525169689SkanDEF_RTL_EXPR(UNLT, "unlt", "ee", RTX_COMPARE)
52690075Sobrien
52790075Sobrien/* This is an ordered NE, ie !UNEQ, ie false for NaN.  */
528169689SkanDEF_RTL_EXPR(LTGT, "ltgt", "ee", RTX_COMM_COMPARE)
52990075Sobrien
53018334Speter/* Represents the result of sign-extending the sole operand.
53118334Speter   The machine modes of the operand and of the SIGN_EXTEND expression
53218334Speter   determine how much sign-extension is going on.  */
533169689SkanDEF_RTL_EXPR(SIGN_EXTEND, "sign_extend", "e", RTX_UNARY)
53418334Speter
53518334Speter/* Similar for zero-extension (such as unsigned short to int).  */
536169689SkanDEF_RTL_EXPR(ZERO_EXTEND, "zero_extend", "e", RTX_UNARY)
53718334Speter
53818334Speter/* Similar but here the operand has a wider mode.  */
539169689SkanDEF_RTL_EXPR(TRUNCATE, "truncate", "e", RTX_UNARY)
54018334Speter
54118334Speter/* Similar for extending floating-point values (such as SFmode to DFmode).  */
542169689SkanDEF_RTL_EXPR(FLOAT_EXTEND, "float_extend", "e", RTX_UNARY)
543169689SkanDEF_RTL_EXPR(FLOAT_TRUNCATE, "float_truncate", "e", RTX_UNARY)
54418334Speter
54518334Speter/* Conversion of fixed point operand to floating point value.  */
546169689SkanDEF_RTL_EXPR(FLOAT, "float", "e", RTX_UNARY)
54718334Speter
54818334Speter/* With fixed-point machine mode:
54918334Speter   Conversion of floating point operand to fixed point value.
55018334Speter   Value is defined only when the operand's value is an integer.
55118334Speter   With floating-point machine mode (and operand with same mode):
55218334Speter   Operand is rounded toward zero to produce an integer value
55318334Speter   represented in floating point.  */
554169689SkanDEF_RTL_EXPR(FIX, "fix", "e", RTX_UNARY)
55518334Speter
55618334Speter/* Conversion of unsigned fixed point operand to floating point value.  */
557169689SkanDEF_RTL_EXPR(UNSIGNED_FLOAT, "unsigned_float", "e", RTX_UNARY)
55818334Speter
55918334Speter/* With fixed-point machine mode:
56018334Speter   Conversion of floating point operand to *unsigned* fixed point value.
56118334Speter   Value is defined only when the operand's value is an integer.  */
562169689SkanDEF_RTL_EXPR(UNSIGNED_FIX, "unsigned_fix", "e", RTX_UNARY)
56318334Speter
56418334Speter/* Absolute value */
565169689SkanDEF_RTL_EXPR(ABS, "abs", "e", RTX_UNARY)
56618334Speter
56718334Speter/* Square root */
568169689SkanDEF_RTL_EXPR(SQRT, "sqrt", "e", RTX_UNARY)
56918334Speter
57018334Speter/* Find first bit that is set.
57118334Speter   Value is 1 + number of trailing zeros in the arg.,
57218334Speter   or 0 if arg is 0.  */
573169689SkanDEF_RTL_EXPR(FFS, "ffs", "e", RTX_UNARY)
57418334Speter
575132718Skan/* Count leading zeros.  */
576169689SkanDEF_RTL_EXPR(CLZ, "clz", "e", RTX_UNARY)
577132718Skan
578132718Skan/* Count trailing zeros.  */
579169689SkanDEF_RTL_EXPR(CTZ, "ctz", "e", RTX_UNARY)
580132718Skan
581132718Skan/* Population count (number of 1 bits).  */
582169689SkanDEF_RTL_EXPR(POPCOUNT, "popcount", "e", RTX_UNARY)
583132718Skan
584132718Skan/* Population parity (number of 1 bits modulo 2).  */
585169689SkanDEF_RTL_EXPR(PARITY, "parity", "e", RTX_UNARY)
586132718Skan
58718334Speter/* Reference to a signed bit-field of specified size and position.
58818334Speter   Operand 0 is the memory unit (usually SImode or QImode) which
58918334Speter   contains the field's first bit.  Operand 1 is the width, in bits.
59018334Speter   Operand 2 is the number of bits in the memory unit before the
59118334Speter   first bit of this field.
59218334Speter   If BITS_BIG_ENDIAN is defined, the first bit is the msb and
59318334Speter   operand 2 counts from the msb of the memory unit.
59418334Speter   Otherwise, the first bit is the lsb and operand 2 counts from
595169689Skan   the lsb of the memory unit.
596169689Skan   This kind of expression can not appear as an lvalue in RTL.  */
597169689SkanDEF_RTL_EXPR(SIGN_EXTRACT, "sign_extract", "eee", RTX_BITFIELD_OPS)
59818334Speter
599169689Skan/* Similar for unsigned bit-field.
600169689Skan   But note!  This kind of expression _can_ appear as an lvalue.  */
601169689SkanDEF_RTL_EXPR(ZERO_EXTRACT, "zero_extract", "eee", RTX_BITFIELD_OPS)
60218334Speter
60318334Speter/* For RISC machines.  These save memory when splitting insns.  */
60418334Speter
60518334Speter/* HIGH are the high-order bits of a constant expression.  */
606169689SkanDEF_RTL_EXPR(HIGH, "high", "e", RTX_CONST_OBJ)
60718334Speter
60818334Speter/* LO_SUM is the sum of a register and the low-order bits
60918334Speter   of a constant expression.  */
610169689SkanDEF_RTL_EXPR(LO_SUM, "lo_sum", "ee", RTX_OBJ)
61118334Speter
61290075Sobrien/* Describes a merge operation between two vector values.
61390075Sobrien   Operands 0 and 1 are the vectors to be merged, operand 2 is a bitmask
61490075Sobrien   that specifies where the parts of the result are taken from.  Set bits
61590075Sobrien   indicate operand 0, clear bits indicate operand 1.  The parts are defined
61690075Sobrien   by the mode of the vectors.  */
617169689SkanDEF_RTL_EXPR(VEC_MERGE, "vec_merge", "eee", RTX_TERNARY)
61890075Sobrien
61990075Sobrien/* Describes an operation that selects parts of a vector.
62090075Sobrien   Operands 0 is the source vector, operand 1 is a PARALLEL that contains
62190075Sobrien   a CONST_INT for each of the subparts of the result vector, giving the
62290075Sobrien   number of the source subpart that should be stored into it.  */
623169689SkanDEF_RTL_EXPR(VEC_SELECT, "vec_select", "ee", RTX_BIN_ARITH)
62490075Sobrien
62590075Sobrien/* Describes a vector concat operation.  Operands 0 and 1 are the source
62690075Sobrien   vectors, the result is a vector that is as long as operands 0 and 1
62790075Sobrien   combined and is the concatenation of the two source vectors.  */
628169689SkanDEF_RTL_EXPR(VEC_CONCAT, "vec_concat", "ee", RTX_BIN_ARITH)
62990075Sobrien
63090075Sobrien/* Describes an operation that converts a small vector into a larger one by
63190075Sobrien   duplicating the input values.  The output vector mode must have the same
63290075Sobrien   submodes as the input vector mode, and the number of output parts must be
63390075Sobrien   an integer multiple of the number of input parts.  */
634169689SkanDEF_RTL_EXPR(VEC_DUPLICATE, "vec_duplicate", "e", RTX_UNARY)
63590075Sobrien     
63690075Sobrien/* Addition with signed saturation */
637169689SkanDEF_RTL_EXPR(SS_PLUS, "ss_plus", "ee", RTX_COMM_ARITH)
63890075Sobrien
63990075Sobrien/* Addition with unsigned saturation */
640169689SkanDEF_RTL_EXPR(US_PLUS, "us_plus", "ee", RTX_COMM_ARITH)
64190075Sobrien
64290075Sobrien/* Operand 0 minus operand 1, with signed saturation.  */
643169689SkanDEF_RTL_EXPR(SS_MINUS, "ss_minus", "ee", RTX_BIN_ARITH)
64490075Sobrien
645169689Skan/* Negation with signed saturation.  */
646169689SkanDEF_RTL_EXPR(SS_NEG, "ss_neg", "e", RTX_UNARY)
647169689Skan
648169689Skan/* Shift left with signed saturation.  */
649169689SkanDEF_RTL_EXPR(SS_ASHIFT, "ss_ashift", "ee", RTX_BIN_ARITH)
650169689Skan
65190075Sobrien/* Operand 0 minus operand 1, with unsigned saturation.  */
652169689SkanDEF_RTL_EXPR(US_MINUS, "us_minus", "ee", RTX_BIN_ARITH)
65390075Sobrien
65490075Sobrien/* Signed saturating truncate.  */
655169689SkanDEF_RTL_EXPR(SS_TRUNCATE, "ss_truncate", "e", RTX_UNARY)
65690075Sobrien
65790075Sobrien/* Unsigned saturating truncate.  */
658169689SkanDEF_RTL_EXPR(US_TRUNCATE, "us_truncate", "e", RTX_UNARY)
65990075Sobrien
660169689Skan/* Information about the variable and its location.  */
661169689SkanDEF_RTL_EXPR(VAR_LOCATION, "var_location", "te", RTX_EXTRA)
66290075Sobrien
663169689Skan/* All expressions from this point forward appear only in machine
664169689Skan   descriptions.  */
665169689Skan#ifdef GENERATOR_FILE
666169689Skan
667169689Skan/* Include a secondary machine-description file at this point.  */
668169689SkanDEF_RTL_EXPR(INCLUDE, "include", "s", RTX_EXTRA)
669169689Skan
670169689Skan/* Pattern-matching operators:  */
671169689Skan
672169689Skan/* Use the function named by the second arg (the string)
673169689Skan   as a predicate; if matched, store the structure that was matched
674169689Skan   in the operand table at index specified by the first arg (the integer).
675169689Skan   If the second arg is the null string, the structure is just stored.
676169689Skan
677169689Skan   A third string argument indicates to the register allocator restrictions
678169689Skan   on where the operand can be allocated.
679169689Skan
680169689Skan   If the target needs no restriction on any instruction this field should
681169689Skan   be the null string.
682169689Skan
683169689Skan   The string is prepended by:
684169689Skan   '=' to indicate the operand is only written to.
685169689Skan   '+' to indicate the operand is both read and written to.
686169689Skan
687169689Skan   Each character in the string represents an allocable class for an operand.
688169689Skan   'g' indicates the operand can be any valid class.
689169689Skan   'i' indicates the operand can be immediate (in the instruction) data.
690169689Skan   'r' indicates the operand can be in a register.
691169689Skan   'm' indicates the operand can be in memory.
692169689Skan   'o' a subset of the 'm' class.  Those memory addressing modes that
693169689Skan       can be offset at compile time (have a constant added to them).
694169689Skan
695169689Skan   Other characters indicate target dependent operand classes and
696169689Skan   are described in each target's machine description.
697169689Skan
698169689Skan   For instructions with more than one operand, sets of classes can be
699169689Skan   separated by a comma to indicate the appropriate multi-operand constraints.
700169689Skan   There must be a 1 to 1 correspondence between these sets of classes in
701169689Skan   all operands for an instruction.
702169689Skan   */
703169689SkanDEF_RTL_EXPR(MATCH_OPERAND, "match_operand", "iss", RTX_MATCH)
704169689Skan
705169689Skan/* Match a SCRATCH or a register.  When used to generate rtl, a
706169689Skan   SCRATCH is generated.  As for MATCH_OPERAND, the mode specifies
707169689Skan   the desired mode and the first argument is the operand number.
708169689Skan   The second argument is the constraint.  */
709169689SkanDEF_RTL_EXPR(MATCH_SCRATCH, "match_scratch", "is", RTX_MATCH)
710169689Skan
711169689Skan/* Apply a predicate, AND match recursively the operands of the rtx.
712169689Skan   Operand 0 is the operand-number, as in match_operand.
713169689Skan   Operand 1 is a predicate to apply (as a string, a function name).
714169689Skan   Operand 2 is a vector of expressions, each of which must match
715169689Skan   one subexpression of the rtx this construct is matching.  */
716169689SkanDEF_RTL_EXPR(MATCH_OPERATOR, "match_operator", "isE", RTX_MATCH)
717169689Skan
718169689Skan/* Match a PARALLEL of arbitrary length.  The predicate is applied
719169689Skan   to the PARALLEL and the initial expressions in the PARALLEL are matched.
720169689Skan   Operand 0 is the operand-number, as in match_operand.
721169689Skan   Operand 1 is a predicate to apply to the PARALLEL.
722169689Skan   Operand 2 is a vector of expressions, each of which must match the 
723169689Skan   corresponding element in the PARALLEL.  */
724169689SkanDEF_RTL_EXPR(MATCH_PARALLEL, "match_parallel", "isE", RTX_MATCH)
725169689Skan
726169689Skan/* Match only something equal to what is stored in the operand table
727169689Skan   at the index specified by the argument.  Use with MATCH_OPERAND.  */
728169689SkanDEF_RTL_EXPR(MATCH_DUP, "match_dup", "i", RTX_MATCH)
729169689Skan
730169689Skan/* Match only something equal to what is stored in the operand table
731169689Skan   at the index specified by the argument.  Use with MATCH_OPERATOR.  */
732169689SkanDEF_RTL_EXPR(MATCH_OP_DUP, "match_op_dup", "iE", RTX_MATCH)
733169689Skan
734169689Skan/* Match only something equal to what is stored in the operand table
735169689Skan   at the index specified by the argument.  Use with MATCH_PARALLEL.  */
736169689SkanDEF_RTL_EXPR(MATCH_PAR_DUP, "match_par_dup", "iE", RTX_MATCH)
737169689Skan
738169689Skan/* Appears only in define_predicate/define_special_predicate
739169689Skan   expressions.  Evaluates true only if the operand has an RTX code
740169689Skan   from the set given by the argument (a comma-separated list).  If the
741169689Skan   second argument is present and nonempty, it is a sequence of digits
742169689Skan   and/or letters which indicates the subexpression to test, using the
743169689Skan   same syntax as genextract/genrecog's location strings: 0-9 for
744169689Skan   XEXP (op, n), a-z for XVECEXP (op, 0, n); each character applies to
745169689Skan   the result of the one before it.  */
746169689SkanDEF_RTL_EXPR(MATCH_CODE, "match_code", "ss", RTX_MATCH)
747169689Skan
748169689Skan/* Appears only in define_predicate/define_special_predicate
749169689Skan    expressions.  The argument is a C expression to be injected at this
750169689Skan    point in the predicate formula.  */
751169689SkanDEF_RTL_EXPR(MATCH_TEST, "match_test", "s", RTX_MATCH)
752169689Skan
753169689Skan/* Insn (and related) definitions.  */
754169689Skan
755169689Skan/* Definition of the pattern for one kind of instruction.
756169689Skan   Operand:
757169689Skan   0: names this instruction.
758169689Skan      If the name is the null string, the instruction is in the
759169689Skan      machine description just to be recognized, and will never be emitted by
760169689Skan      the tree to rtl expander.
761169689Skan   1: is the pattern.
762169689Skan   2: is a string which is a C expression
763169689Skan      giving an additional condition for recognizing this pattern.
764169689Skan      A null string means no extra condition.
765169689Skan   3: is the action to execute if this pattern is matched.
766169689Skan      If this assembler code template starts with a * then it is a fragment of
767169689Skan      C code to run to decide on a template to use.  Otherwise, it is the
768169689Skan      template to use.
769169689Skan   4: optionally, a vector of attributes for this insn.
770169689Skan     */
771169689SkanDEF_RTL_EXPR(DEFINE_INSN, "define_insn", "sEsTV", RTX_EXTRA)
772169689Skan
773169689Skan/* Definition of a peephole optimization.
774169689Skan   1st operand: vector of insn patterns to match
775169689Skan   2nd operand: C expression that must be true
776169689Skan   3rd operand: template or C code to produce assembler output.
777169689Skan   4: optionally, a vector of attributes for this insn.
778169689Skan
779169689Skan   This form is deprecated; use define_peephole2 instead.  */
780169689SkanDEF_RTL_EXPR(DEFINE_PEEPHOLE, "define_peephole", "EsTV", RTX_EXTRA)
781169689Skan
782169689Skan/* Definition of a split operation.
783169689Skan   1st operand: insn pattern to match
784169689Skan   2nd operand: C expression that must be true
785169689Skan   3rd operand: vector of insn patterns to place into a SEQUENCE
786169689Skan   4th operand: optionally, some C code to execute before generating the
787169689Skan	insns.  This might, for example, create some RTX's and store them in
788169689Skan	elements of `recog_data.operand' for use by the vector of
789169689Skan	insn-patterns.
790169689Skan	(`operands' is an alias here for `recog_data.operand').  */
791169689SkanDEF_RTL_EXPR(DEFINE_SPLIT, "define_split", "EsES", RTX_EXTRA)
792169689Skan
793169689Skan/* Definition of an insn and associated split.
794169689Skan   This is the concatenation, with a few modifications, of a define_insn
795169689Skan   and a define_split which share the same pattern.
796169689Skan   Operand:
797169689Skan   0: names this instruction.
798169689Skan      If the name is the null string, the instruction is in the
799169689Skan      machine description just to be recognized, and will never be emitted by
800169689Skan      the tree to rtl expander.
801169689Skan   1: is the pattern.
802169689Skan   2: is a string which is a C expression
803169689Skan      giving an additional condition for recognizing this pattern.
804169689Skan      A null string means no extra condition.
805169689Skan   3: is the action to execute if this pattern is matched.
806169689Skan      If this assembler code template starts with a * then it is a fragment of
807169689Skan      C code to run to decide on a template to use.  Otherwise, it is the
808169689Skan      template to use.
809169689Skan   4: C expression that must be true for split.  This may start with "&&"
810169689Skan      in which case the split condition is the logical and of the insn 
811169689Skan      condition and what follows the "&&" of this operand.
812169689Skan   5: vector of insn patterns to place into a SEQUENCE
813169689Skan   6: optionally, some C code to execute before generating the
814169689Skan	insns.  This might, for example, create some RTX's and store them in
815169689Skan	elements of `recog_data.operand' for use by the vector of
816169689Skan	insn-patterns.
817169689Skan	(`operands' is an alias here for `recog_data.operand').  
818169689Skan   7: optionally, a vector of attributes for this insn.  */
819169689SkanDEF_RTL_EXPR(DEFINE_INSN_AND_SPLIT, "define_insn_and_split", "sEsTsESV", RTX_EXTRA)
820169689Skan
821169689Skan/* Definition of an RTL peephole operation.
822169689Skan   Follows the same arguments as define_split.  */
823169689SkanDEF_RTL_EXPR(DEFINE_PEEPHOLE2, "define_peephole2", "EsES", RTX_EXTRA)
824169689Skan
825169689Skan/* Define how to generate multiple insns for a standard insn name.
826169689Skan   1st operand: the insn name.
827169689Skan   2nd operand: vector of insn-patterns.
828169689Skan	Use match_operand to substitute an element of `recog_data.operand'.
829169689Skan   3rd operand: C expression that must be true for this to be available.
830169689Skan	This may not test any operands.
831169689Skan   4th operand: Extra C code to execute before generating the insns.
832169689Skan	This might, for example, create some RTX's and store them in
833169689Skan	elements of `recog_data.operand' for use by the vector of
834169689Skan	insn-patterns.
835169689Skan	(`operands' is an alias here for `recog_data.operand').  */
836169689SkanDEF_RTL_EXPR(DEFINE_EXPAND, "define_expand", "sEss", RTX_EXTRA)
837169689Skan   
838169689Skan/* Define a requirement for delay slots.
839169689Skan   1st operand: Condition involving insn attributes that, if true,
840169689Skan	        indicates that the insn requires the number of delay slots
841169689Skan		shown.
842169689Skan   2nd operand: Vector whose length is the three times the number of delay
843169689Skan		slots required.
844169689Skan	        Each entry gives three conditions, each involving attributes.
845169689Skan		The first must be true for an insn to occupy that delay slot
846169689Skan		location.  The second is true for all insns that can be
847169689Skan		annulled if the branch is true and the third is true for all
848169689Skan		insns that can be annulled if the branch is false. 
849169689Skan
850169689Skan   Multiple DEFINE_DELAYs may be present.  They indicate differing
851169689Skan   requirements for delay slots.  */
852169689SkanDEF_RTL_EXPR(DEFINE_DELAY, "define_delay", "eE", RTX_EXTRA)
853169689Skan
854169689Skan/* Define attribute computation for `asm' instructions.  */
855169689SkanDEF_RTL_EXPR(DEFINE_ASM_ATTRIBUTES, "define_asm_attributes", "V", RTX_EXTRA)
856169689Skan
857169689Skan/* Definition of a conditional execution meta operation.  Automatically
858169689Skan   generates new instances of DEFINE_INSN, selected by having attribute
859169689Skan   "predicable" true.  The new pattern will contain a COND_EXEC and the
860169689Skan   predicate at top-level.
861169689Skan
862169689Skan   Operand:
863169689Skan   0: The predicate pattern.  The top-level form should match a
864169689Skan      relational operator.  Operands should have only one alternative.
865169689Skan   1: A C expression giving an additional condition for recognizing
866169689Skan      the generated pattern.
867169689Skan   2: A template or C code to produce assembler output.  */
868169689SkanDEF_RTL_EXPR(DEFINE_COND_EXEC, "define_cond_exec", "Ess", RTX_EXTRA)
869169689Skan
870169689Skan/* Definition of an operand predicate.  The difference between
871169689Skan   DEFINE_PREDICATE and DEFINE_SPECIAL_PREDICATE is that genrecog will
872169689Skan   not warn about a match_operand with no mode if it has a predicate
873169689Skan   defined with DEFINE_SPECIAL_PREDICATE.
874169689Skan
875169689Skan   Operand:
876169689Skan   0: The name of the predicate.
877169689Skan   1: A boolean expression which computes whether or not the predicate
878169689Skan      matches.  This expression can use IOR, AND, NOT, MATCH_OPERAND,
879169689Skan      MATCH_CODE, and MATCH_TEST.  It must be specific enough that genrecog
880169689Skan      can calculate the set of RTX codes that can possibly match.
881169689Skan   2: A C function body which must return true for the predicate to match.
882169689Skan      Optional.  Use this when the test is too complicated to fit into a
883169689Skan      match_test expression.  */
884169689SkanDEF_RTL_EXPR(DEFINE_PREDICATE, "define_predicate", "ses", RTX_EXTRA)
885169689SkanDEF_RTL_EXPR(DEFINE_SPECIAL_PREDICATE, "define_special_predicate", "ses", RTX_EXTRA)
886169689Skan
887169689Skan/* Definition of a register operand constraint.  This simply maps the
888169689Skan   constraint string to a register class.
889169689Skan
890169689Skan   Operand:
891169689Skan   0: The name of the constraint (often, but not always, a single letter).
892169689Skan   1: A C expression which evaluates to the appropriate register class for
893169689Skan      this constraint.  If this is not just a constant, it should look only
894169689Skan      at -m switches and the like.
895169689Skan   2: A docstring for this constraint, in Texinfo syntax; not currently
896169689Skan      used, in future will be incorporated into the manual's list of
897169689Skan      machine-specific operand constraints.  */
898169689SkanDEF_RTL_EXPR(DEFINE_REGISTER_CONSTRAINT, "define_register_constraint", "sss", RTX_EXTRA)
899169689Skan
900169689Skan/* Definition of a non-register operand constraint.  These look at the
901169689Skan   operand and decide whether it fits the constraint.
902169689Skan
903169689Skan   DEFINE_CONSTRAINT gets no special treatment if it fails to match.
904169689Skan   It is appropriate for constant-only constraints, and most others.
905169689Skan
906169689Skan   DEFINE_MEMORY_CONSTRAINT tells reload that this constraint can be made
907169689Skan   to match, if it doesn't already, by converting the operand to the form
908169689Skan   (mem (reg X)) where X is a base register.  It is suitable for constraints
909169689Skan   that describe a subset of all memory references.
910169689Skan
911169689Skan   DEFINE_ADDRESS_CONSTRAINT tells reload that this constraint can be made
912169689Skan   to match, if it doesn't already, by converting the operand to the form
913169689Skan   (reg X) where X is a base register.  It is suitable for constraints that
914169689Skan   describe a subset of all address references.
915169689Skan
916169689Skan   When in doubt, use plain DEFINE_CONSTRAINT.  
917169689Skan
918169689Skan   Operand:
919169689Skan   0: The name of the constraint (often, but not always, a single letter).
920169689Skan   1: A docstring for this constraint, in Texinfo syntax; not currently
921169689Skan      used, in future will be incorporated into the manual's list of
922169689Skan      machine-specific operand constraints.
923169689Skan   2: A boolean expression which computes whether or not the constraint
924169689Skan      matches.  It should follow the same rules as a define_predicate
925169689Skan      expression, including the bit about specifying the set of RTX codes
926169689Skan      that could possibly match.  MATCH_TEST subexpressions may make use of
927169689Skan      these variables:
928169689Skan        `op'    - the RTL object defining the operand.
929169689Skan        `mode'  - the mode of `op'.
930169689Skan	`ival'  - INTVAL(op), if op is a CONST_INT.
931169689Skan        `hval'  - CONST_DOUBLE_HIGH(op), if op is an integer CONST_DOUBLE.
932169689Skan        `lval'  - CONST_DOUBLE_LOW(op), if op is an integer CONST_DOUBLE.
933169689Skan        `rval'  - CONST_DOUBLE_REAL_VALUE(op), if op is a floating-point
934169689Skan                  CONST_DOUBLE.
935169689Skan      Do not use ival/hval/lval/rval if op is not the appropriate kind of
936169689Skan      RTL object.  */
937169689SkanDEF_RTL_EXPR(DEFINE_CONSTRAINT, "define_constraint", "sse", RTX_EXTRA)
938169689SkanDEF_RTL_EXPR(DEFINE_MEMORY_CONSTRAINT, "define_memory_constraint", "sse", RTX_EXTRA)
939169689SkanDEF_RTL_EXPR(DEFINE_ADDRESS_CONSTRAINT, "define_address_constraint", "sse", RTX_EXTRA)
940169689Skan   
941169689Skan
942169689Skan/* Constructions for CPU pipeline description described by NDFAs.  */
943169689Skan
944169689Skan/* (define_cpu_unit string [string]) describes cpu functional
945169689Skan   units (separated by comma).
946169689Skan
947169689Skan   1st operand: Names of cpu functional units.
948169689Skan   2nd operand: Name of automaton (see comments for DEFINE_AUTOMATON).
949169689Skan
950169689Skan   All define_reservations, define_cpu_units, and
951169689Skan   define_query_cpu_units should have unique names which may not be
952169689Skan   "nothing".  */
953169689SkanDEF_RTL_EXPR(DEFINE_CPU_UNIT, "define_cpu_unit", "sS", RTX_EXTRA)
954169689Skan
955169689Skan/* (define_query_cpu_unit string [string]) describes cpu functional
956169689Skan   units analogously to define_cpu_unit.  The reservation of such
957169689Skan   units can be queried for automaton state.  */
958169689SkanDEF_RTL_EXPR(DEFINE_QUERY_CPU_UNIT, "define_query_cpu_unit", "sS", RTX_EXTRA)
959169689Skan
960169689Skan/* (exclusion_set string string) means that each CPU functional unit
961169689Skan   in the first string can not be reserved simultaneously with any
962169689Skan   unit whose name is in the second string and vise versa.  CPU units
963169689Skan   in the string are separated by commas.  For example, it is useful
964169689Skan   for description CPU with fully pipelined floating point functional
965169689Skan   unit which can execute simultaneously only single floating point
966169689Skan   insns or only double floating point insns.  All CPU functional
967169689Skan   units in a set should belong to the same automaton.  */
968169689SkanDEF_RTL_EXPR(EXCLUSION_SET, "exclusion_set", "ss", RTX_EXTRA)
969169689Skan
970169689Skan/* (presence_set string string) means that each CPU functional unit in
971169689Skan   the first string can not be reserved unless at least one of pattern
972169689Skan   of units whose names are in the second string is reserved.  This is
973169689Skan   an asymmetric relation.  CPU units or unit patterns in the strings
974169689Skan   are separated by commas.  Pattern is one unit name or unit names
975169689Skan   separated by white-spaces.
976169689Skan 
977169689Skan   For example, it is useful for description that slot1 is reserved
978169689Skan   after slot0 reservation for a VLIW processor.  We could describe it
979169689Skan   by the following construction
980169689Skan
981169689Skan      (presence_set "slot1" "slot0")
982169689Skan
983169689Skan   Or slot1 is reserved only after slot0 and unit b0 reservation.  In
984169689Skan   this case we could write
985169689Skan
986169689Skan      (presence_set "slot1" "slot0 b0")
987169689Skan
988169689Skan   All CPU functional units in a set should belong to the same
989169689Skan   automaton.  */
990169689SkanDEF_RTL_EXPR(PRESENCE_SET, "presence_set", "ss", RTX_EXTRA)
991169689Skan
992169689Skan/* (final_presence_set string string) is analogous to `presence_set'.
993169689Skan   The difference between them is when checking is done.  When an
994169689Skan   instruction is issued in given automaton state reflecting all
995169689Skan   current and planned unit reservations, the automaton state is
996169689Skan   changed.  The first state is a source state, the second one is a
997169689Skan   result state.  Checking for `presence_set' is done on the source
998169689Skan   state reservation, checking for `final_presence_set' is done on the
999169689Skan   result reservation.  This construction is useful to describe a
1000169689Skan   reservation which is actually two subsequent reservations.  For
1001169689Skan   example, if we use 
1002169689Skan
1003169689Skan      (presence_set "slot1" "slot0")
1004169689Skan
1005169689Skan   the following insn will be never issued (because slot1 requires
1006169689Skan   slot0 which is absent in the source state).
1007169689Skan
1008169689Skan      (define_reservation "insn_and_nop" "slot0 + slot1")
1009169689Skan
1010169689Skan   but it can be issued if we use analogous `final_presence_set'.  */
1011169689SkanDEF_RTL_EXPR(FINAL_PRESENCE_SET, "final_presence_set", "ss", RTX_EXTRA)
1012169689Skan
1013169689Skan/* (absence_set string string) means that each CPU functional unit in
1014169689Skan   the first string can be reserved only if each pattern of units
1015169689Skan   whose names are in the second string is not reserved.  This is an
1016169689Skan   asymmetric relation (actually exclusion set is analogous to this
1017169689Skan   one but it is symmetric).  CPU units or unit patterns in the string
1018169689Skan   are separated by commas.  Pattern is one unit name or unit names
1019169689Skan   separated by white-spaces.
1020169689Skan
1021169689Skan   For example, it is useful for description that slot0 can not be
1022169689Skan   reserved after slot1 or slot2 reservation for a VLIW processor.  We
1023169689Skan   could describe it by the following construction
1024169689Skan
1025169689Skan      (absence_set "slot2" "slot0, slot1")
1026169689Skan
1027169689Skan   Or slot2 can not be reserved if slot0 and unit b0 are reserved or
1028169689Skan   slot1 and unit b1 are reserved .  In this case we could write
1029169689Skan
1030169689Skan      (absence_set "slot2" "slot0 b0, slot1 b1")
1031169689Skan
1032169689Skan   All CPU functional units in a set should to belong the same
1033169689Skan   automaton.  */
1034169689SkanDEF_RTL_EXPR(ABSENCE_SET, "absence_set", "ss", RTX_EXTRA)
1035169689Skan
1036169689Skan/* (final_absence_set string string) is analogous to `absence_set' but
1037169689Skan   checking is done on the result (state) reservation.  See comments
1038169689Skan   for `final_presence_set'.  */
1039169689SkanDEF_RTL_EXPR(FINAL_ABSENCE_SET, "final_absence_set", "ss", RTX_EXTRA)
1040169689Skan
1041169689Skan/* (define_bypass number out_insn_names in_insn_names) names bypass
1042169689Skan   with given latency (the first number) from insns given by the first
1043169689Skan   string (see define_insn_reservation) into insns given by the second
1044169689Skan   string.  Insn names in the strings are separated by commas.  The
1045169689Skan   third operand is optional name of function which is additional
1046169689Skan   guard for the bypass.  The function will get the two insns as
1047169689Skan   parameters.  If the function returns zero the bypass will be
1048169689Skan   ignored for this case.  Additional guard is necessary to recognize
1049169689Skan   complicated bypasses, e.g. when consumer is load address.  */
1050169689SkanDEF_RTL_EXPR(DEFINE_BYPASS, "define_bypass", "issS", RTX_EXTRA)
1051169689Skan
1052169689Skan/* (define_automaton string) describes names of automata generated and
1053169689Skan   used for pipeline hazards recognition.  The names are separated by
1054169689Skan   comma.  Actually it is possibly to generate the single automaton
1055169689Skan   but unfortunately it can be very large.  If we use more one
1056169689Skan   automata, the summary size of the automata usually is less than the
1057169689Skan   single one.  The automaton name is used in define_cpu_unit and
1058169689Skan   define_query_cpu_unit.  All automata should have unique names.  */
1059169689SkanDEF_RTL_EXPR(DEFINE_AUTOMATON, "define_automaton", "s", RTX_EXTRA)
1060169689Skan
1061169689Skan/* (automata_option string) describes option for generation of
1062169689Skan   automata.  Currently there are the following options:
1063169689Skan
1064169689Skan   o "no-minimization" which makes no minimization of automata.  This
1065169689Skan     is only worth to do when we are debugging the description and
1066169689Skan     need to look more accurately at reservations of states.
1067169689Skan
1068169689Skan   o "time" which means printing additional time statistics about
1069169689Skan      generation of automata.
1070169689Skan  
1071169689Skan   o "v" which means generation of file describing the result
1072169689Skan     automata.  The file has suffix `.dfa' and can be used for the
1073169689Skan     description verification and debugging.
1074169689Skan
1075169689Skan   o "w" which means generation of warning instead of error for
1076169689Skan     non-critical errors.
1077169689Skan
1078169689Skan   o "ndfa" which makes nondeterministic finite state automata.
1079169689Skan
1080169689Skan   o "progress" which means output of a progress bar showing how many
1081169689Skan     states were generated so far for automaton being processed.  */
1082169689SkanDEF_RTL_EXPR(AUTOMATA_OPTION, "automata_option", "s", RTX_EXTRA)
1083169689Skan
1084169689Skan/* (define_reservation string string) names reservation (the first
1085169689Skan   string) of cpu functional units (the 2nd string).  Sometimes unit
1086169689Skan   reservations for different insns contain common parts.  In such
1087169689Skan   case, you can describe common part and use its name (the 1st
1088169689Skan   parameter) in regular expression in define_insn_reservation.  All
1089169689Skan   define_reservations, define_cpu_units, and define_query_cpu_units
1090169689Skan   should have unique names which may not be "nothing".  */
1091169689SkanDEF_RTL_EXPR(DEFINE_RESERVATION, "define_reservation", "ss", RTX_EXTRA)
1092169689Skan
1093169689Skan/* (define_insn_reservation name default_latency condition regexpr)
1094169689Skan   describes reservation of cpu functional units (the 3nd operand) for
1095169689Skan   instruction which is selected by the condition (the 2nd parameter).
1096169689Skan   The first parameter is used for output of debugging information.
1097169689Skan   The reservations are described by a regular expression according
1098169689Skan   the following syntax:
1099169689Skan
1100169689Skan       regexp = regexp "," oneof
1101169689Skan              | oneof
1102169689Skan
1103169689Skan       oneof = oneof "|" allof
1104169689Skan             | allof
1105169689Skan
1106169689Skan       allof = allof "+" repeat
1107169689Skan             | repeat
1108169689Skan 
1109169689Skan       repeat = element "*" number
1110169689Skan              | element
1111169689Skan
1112169689Skan       element = cpu_function_unit_name
1113169689Skan               | reservation_name
1114169689Skan               | result_name
1115169689Skan               | "nothing"
1116169689Skan               | "(" regexp ")"
1117169689Skan
1118169689Skan       1. "," is used for describing start of the next cycle in
1119169689Skan       reservation.
1120169689Skan
1121169689Skan       2. "|" is used for describing the reservation described by the
1122169689Skan       first regular expression *or* the reservation described by the
1123169689Skan       second regular expression *or* etc.
1124169689Skan
1125169689Skan       3. "+" is used for describing the reservation described by the
1126169689Skan       first regular expression *and* the reservation described by the
1127169689Skan       second regular expression *and* etc.
1128169689Skan
1129169689Skan       4. "*" is used for convenience and simply means sequence in
1130169689Skan       which the regular expression are repeated NUMBER times with
1131169689Skan       cycle advancing (see ",").
1132169689Skan
1133169689Skan       5. cpu functional unit name which means its reservation.
1134169689Skan
1135169689Skan       6. reservation name -- see define_reservation.
1136169689Skan
1137169689Skan       7. string "nothing" means no units reservation.  */
1138169689Skan
1139169689SkanDEF_RTL_EXPR(DEFINE_INSN_RESERVATION, "define_insn_reservation", "sies", RTX_EXTRA)
1140169689Skan
1141169689Skan/* Expressions used for insn attributes.  */
1142169689Skan
1143169689Skan/* Definition of an insn attribute.
1144169689Skan   1st operand: name of the attribute
1145169689Skan   2nd operand: comma-separated list of possible attribute values
1146169689Skan   3rd operand: expression for the default value of the attribute.  */
1147169689SkanDEF_RTL_EXPR(DEFINE_ATTR, "define_attr", "sse", RTX_EXTRA)
1148169689Skan
1149169689Skan/* Marker for the name of an attribute.  */
1150169689SkanDEF_RTL_EXPR(ATTR, "attr", "s", RTX_EXTRA)
1151169689Skan
1152169689Skan/* For use in the last (optional) operand of DEFINE_INSN or DEFINE_PEEPHOLE and
1153169689Skan   in DEFINE_ASM_INSN to specify an attribute to assign to insns matching that
1154169689Skan   pattern.
1155169689Skan
1156169689Skan   (set_attr "name" "value") is equivalent to
1157169689Skan   (set (attr "name") (const_string "value"))  */
1158169689SkanDEF_RTL_EXPR(SET_ATTR, "set_attr", "ss", RTX_EXTRA)
1159169689Skan
1160169689Skan/* In the last operand of DEFINE_INSN and DEFINE_PEEPHOLE, this can be used to
1161169689Skan   specify that attribute values are to be assigned according to the
1162169689Skan   alternative matched.
1163169689Skan
1164169689Skan   The following three expressions are equivalent:
1165169689Skan
1166169689Skan   (set (attr "att") (cond [(eq_attrq "alternative" "1") (const_string "a1")
1167169689Skan			    (eq_attrq "alternative" "2") (const_string "a2")]
1168169689Skan			   (const_string "a3")))
1169169689Skan   (set_attr_alternative "att" [(const_string "a1") (const_string "a2")
1170169689Skan				 (const_string "a3")])
1171169689Skan   (set_attr "att" "a1,a2,a3")
1172169689Skan */
1173169689SkanDEF_RTL_EXPR(SET_ATTR_ALTERNATIVE, "set_attr_alternative", "sE", RTX_EXTRA)
1174169689Skan
1175169689Skan/* A conditional expression true if the value of the specified attribute of
1176169689Skan   the current insn equals the specified value.  The first operand is the
1177169689Skan   attribute name and the second is the comparison value.  */
1178169689SkanDEF_RTL_EXPR(EQ_ATTR, "eq_attr", "ss", RTX_EXTRA)
1179169689Skan
1180169689Skan/* A special case of the above representing a set of alternatives.  The first
1181169689Skan   operand is bitmap of the set, the second one is the default value.  */
1182169689SkanDEF_RTL_EXPR(EQ_ATTR_ALT, "eq_attr_alt", "ii", RTX_EXTRA)
1183169689Skan
1184169689Skan/* A conditional expression which is true if the specified flag is
1185169689Skan   true for the insn being scheduled in reorg.
1186169689Skan
1187169689Skan   genattr.c defines the following flags which can be tested by
1188169689Skan   (attr_flag "foo") expressions in eligible_for_delay.
1189169689Skan
1190169689Skan   forward, backward, very_likely, likely, very_unlikely, and unlikely.  */
1191169689Skan
1192169689SkanDEF_RTL_EXPR (ATTR_FLAG, "attr_flag", "s", RTX_EXTRA)
1193169689Skan
1194169689Skan/* General conditional. The first operand is a vector composed of pairs of
1195169689Skan   expressions.  The first element of each pair is evaluated, in turn.
1196169689Skan   The value of the conditional is the second expression of the first pair
1197169689Skan   whose first expression evaluates nonzero.  If none of the expressions is
1198169689Skan   true, the second operand will be used as the value of the conditional.  */
1199169689SkanDEF_RTL_EXPR(COND, "cond", "Ee", RTX_EXTRA)
1200169689Skan
1201169689Skan#endif /* GENERATOR_FILE */
1202169689Skan
120318334Speter/*
120418334SpeterLocal variables:
120518334Spetermode:c
120618334SpeterEnd:
120718334Speter*/
1208