V10/cmd/gcc/internals-4



File: internals,  Node: Side Effects,  Next: Incdec,  Prev: RTL Declarations,  Up: RTL

Side Effect Expressions
=======================

The expression codes described so far represent values, not actions.  But
machine instructions never produce values; they are meaningful only for
their side effects on the state of the machine.  Special expression codes
are used to represent side effects.

The body of an instruction is always one of these side effect codes; the
codes described above, which represent values, appear only as the operands
of these.

`(set LVAL X)'
     Represents the action of storing the value of X into the place
     represented by LVAL.  LVAL must be an expression representing a place
     that can be stored in: `reg' (or `subreg' or `strict_low_part'),
     `mem', `pc' or `cc0'.

     If LVAL is a `reg', `subreg' or `mem', it has a machine mode; then X
     must be valid for that mode.

     If LVAL is a `reg' whose machine mode is less than the full width of
     the register, then it means that the part of the register specified by
     the machine mode is given the specified value and the rest of the
     register receives an undefined value.  Likewise, if LVAL is a `subreg'
     whose machine mode is narrower than `SImode', the rest of the register
     can be changed in an undefined way.

     If LVAL is a `strict_low_part' of a `subreg', then the part of the
     register specified by the machine mode of the `subreg' is given the
     value X and the rest of the register is not changed.

     If LVAL is `(cc0)', it has no machine mode, and X may have any mode. 
     This represents a ``test'' or ``compare'' instruction.

     If LVAL is `(pc)', we have a jump instruction, and the possibilities
     for X are very limited.  It may be a `label_ref' expression
     (unconditional jump).  It may be an `if_then_else' (conditional jump),
     in which case either the second or the third operand must be `(pc)'
     (for the case which does not jump) and the other of the two must be a
     `label_ref' (for the case which does jump).  X may also be a `mem' or
     `(plus:SI (pc) Y)', where Y may be a `reg' or a `mem'; these unusual
     patterns are used to represent jumps through branch tables.

`(return)'
     Represents a return from the current function, on machines where this
     can be done with one instruction, such as Vaxes.  On machines where a
     multi-instruction ``epilogue'' must be executed in order to return
     from the function, returning is done by jumping to a label which
     precedes the epilogue, and the `return' expression code is never used.

`(call FUNCTION NARGS)'
     Represents a function call.  FUNCTION is a `mem' expression whose
     address is the address of the function to be called.  NARGS is an
     expression representing the number of words of argument.

     Each machine has a standard machine mode which FUNCTION must have. 
     The machine description defines macro `FUNCTION_MODE' to expand into
     the requisite mode name.  The purpose of this mode is to specify what
     kind of addressing is allowed, on machines where the allowed kinds of
     addressing depend on the machine mode being addressed.

`(clobber X)'
     Represents the storing or possible storing of an unpredictable,
     undescribed value into X, which must be a `reg' or `mem' expression.

     One place this is used is in string instructions that store standard
     values into particular hard registers.  It may not be worth the
     trouble to describe the values that are stored, but it is essential to
     inform the compiler that the registers will be altered, lest it
     attempt to keep data in them across the string instruction.

     X may also be null---a null C pointer, no expression at all.  Such a
     `(clobber (null))' expression means that all memory locations must be
     presumed clobbered.

     Note that the machine description classifies certain hard registers as
     ``call-clobbered''.  All function call instructions are assumed by
     default to clobber these registers, so there is no need to use
     `clobber' expressions to indicate this fact.  Also, each function call
     is assumed to have the potential to alter any memory location.

`(use X)'
     Represents the use of the value of X.  It indicates that the value in
     X at this point in the program is needed, even though it may not be
     apparent why this is so.  Therefore, the compiler will not attempt to
     delete instructions whose only effect is to store a value in X.  X
     must be a `reg' expression.

`(parallel [X0 X1 ...])'
     Represents several side effects performed in parallel.  The square
     brackets stand for a vector; the operand of `parallel' is a vector of
     expressions.  X0, X1 and so on are individual side
     effects---expressions of code `set', `call', `return', `clobber' or
     `use'.

     ``In parallel'' means that first all the values used in the individual
     side-effects are computed, and second all the actual side-effects are
     performed.  For example,

          (parallel [(set (reg:SI 1) (mem:SI (reg:SI 1)))
                     (set (mem:SI (reg:SI 1)) (reg:SI 1))])

     says unambiguously that the values of hard register 1 and the memory
     location addressed by it are interchanged.  In both places where
     `(reg:SI 1)' appears as a memory address it refers to the value in
     register 1 *before* the execution of the instruction.

`(sequence [INSNS ...])'
     Represents a sequence of insns.  Each of the INSNS that appears in the
     vector is suitable for appearing in the chain of insns, so it must be
     an `insn', `jump_insn', `call_insn', `code_label', `barrier' or `note'.

     A `sequence' RTX never appears in an actual insn.  It represents the
     sequence of insns that result from a `define_expand' *before* those
     insns are passed to `emit_insn' to insert them in the chain of insns. 
     When actually inserted, the individual sub-insns are separated out and
     the `sequence' is forgotten.

Three expression codes appear in place of a side effect, as the body of an
insn, though strictly speaking they do not describe side effects as such:

`(asm_input S)'
     Represents literal assembler code as described by the string S.

`(addr_vec:M [LR0 LR1 ...])'
     Represents a table of jump addresses.  The vector elements LR0, etc.,
     are `label_ref' expressions.  The mode M specifies how much space is
     given to each address; normally M would be `Pmode'.

`(addr_diff_vec:M BASE [LR0 LR1 ...])'
     Represents a table of jump addresses expressed as offsets from BASE. 
     The vector elements LR0, etc., are `label_ref' expressions and so is
     BASE.  The mode M specifies how much space is given to each
     address-difference.


File: internals,  Node: Incdec,  Next: Assembler,  Prev: Side Effects,  Up: RTL

Embedded Side-Effects on Addresses
==================================

Four special side-effect expression codes appear as memory addresses.

`(pre_dec:M X)'
     Represents the side effect of decrementing X by a standard amount and
     represents also the value that X has after being decremented.  X must
     be a `reg' or `mem', but most machines allow only a `reg'.  M must be
     the machine mode for pointers on the machine in use.  The amount X is
     decremented by is the length in bytes of the machine mode of the
     containing memory reference of which this expression serves as the
     address.  Here is an example of its use:

          (mem:DF (pre_dec:SI (reg:SI 39)))

     This says to decrement pseudo register 39 by the length of a `DFmode'
     value and use the result to address a `DFmode' value.

`(pre_inc:M X)'
     Similar, but specifies incrementing X instead of decrementing it.

`(post_dec:M X)'
     Represents the same side effect as `pre_decrement' but a different
     value.  The value represented here is the value X has before being
     decremented.

`(post_inc:M X)'
     Similar, but specifies incrementing X instead of decrementing it.

These embedded side effect expressions must be used with care.  Instruction
patterns may not use them.  Until the `flow' pass of the compiler, they may
occur only to represent pushes onto the stack.  The `flow' pass finds cases
where registers are incremented or decremented in one instruction and used
as an address shortly before or after; these cases are then transformed to
use pre- or post-increment or -decrement.

Explicit popping of the stack could be represented with these embedded side
effect operators, but that would not be safe; the instruction combination
pass could move the popping past pushes, thus changing the meaning of the
code.

An instruction that can be represented with an embedded side effect could
also be represented using `parallel' containing an additional `set' to
describe how the address register is altered.  This is not done because
machines that allow these operations at all typically allow them wherever a
memory address is called for.  Describing them as additional parallel
stores would require doubling the number of entries in the machine
description.


File: internals,  Node: Assembler,  Next: Insns,  Prev: IncDec,  Up: RTL

Assembler Instructions as Expressions
=====================================

The RTX code `asm_operands' represents a value produced by a user-specified
assembler instruction.  It is used to represent an `asm' statement with
arguments.  An `asm' statement with a single output operand, like this:

     asm ("foo %1,%2,%0" : "a" (outputvar) : "g" (x + y), "di" (*z));

is represented using a single `asm_operands' RTX which represents the value
that is stored in `outputvar':

     (set RTX-FOR-OUTPUTVAR
          (asm_operands "foo %1,%2,%0" "a" 0
                        [RTX-FOR-ADDITION-RESULT RTX-FOR-*Z]
                        [(asm_input:M1 "g")
                         (asm_input:M2 "di")]))

Here the operands of the `asm_operands' RTX are the assembler template
string, the output-operand's constraint, the index-number of the output
operand among the output operands specified, a vector of input operand
RTX's, and a vector of input-operand modes and constraints.  The mode M1 is
the mode of the sum `x+y'; M2 is that of `*z'.

When an `asm' statement has multiple output values, its insn has several
such `set' RTX's inside of a `parallel'.  Each `set' contains a
`asm_operands'; all of these share the same assembler template and vectors,
but each contains the constraint for the respective output operand.  They
are also distinguished by the output-operand index number, which is 0, 1,
... for successive output operands.


File: internals,  Node: Insns,  Next: Calls,  Prev: Assembler,  Up: RTL

Insns
=====

The RTL representation of the code for a function is a doubly-linked chain
of objects called "insns".  Insns are expressions with special codes that
are used for no other purpose.  Some insns are actual instructions; others
represent dispatch tables for `switch' statements; others represent labels
to jump to or various sorts of declarative information.

In addition to its own specific data, each insn must have a unique
id-number that distinguishes it from all other insns in the current
function, and chain pointers to the preceding and following insns.  These
three fields occupy the same position in every insn, independent of the
expression code of the insn.  They could be accessed with `XEXP' and
`XINT', but instead three special macros are always used:

`INSN_UID (I)'
     Accesses the unique id of insn I.

`PREV_INSN (I)'
     Accesses the chain pointer to the insn preceding I.  If I is the first
     insn, this is a null pointer.

`NEXT_INSN (I)'
     Accesses the chain pointer to the insn following I.  If I is the last
     insn, this is a null pointer.

The `NEXT_INSN' and `PREV_INSN' pointers must always correspond: if I is
not the first insn,

     NEXT_INSN (PREV_INSN (INSN)) == INSN

is always true.

Every insn has one of the following six expression codes:

`insn'
     The expression code `insn' is used for instructions that do not jump
     and do not do function calls.  Insns with code `insn' have four
     additional fields beyond the three mandatory ones listed above.  These
     four are described in a table below.

`jump_insn'
     The expression code `jump_insn' is used for instructions that may jump
     (or, more generally, may contain `label_ref' expressions). 
     `jump_insn' insns have the same extra fields as `insn' insns, accessed
     in the same way.

`call_insn'
     The expression code `call_insn' is used for instructions that may do
     function calls.  It is important to distinguish these instructions
     because they imply that certain registers and memory locations may be
     altered unpredictably.

     `call_insn' insns have the same extra fields as `insn' insns, accessed
     in the same way.

`code_label'
     A `code_label' insn represents a label that a jump insn can jump to. 
     It contains one special field of data in addition to the three
     standard ones.  It is used to hold the "label number", a number that
     identifies this label uniquely among all the labels in the compilation
     (not just in the current function).  Ultimately, the label is
     represented in the assembler output as an assembler label `LN' where N
     is the label number.

`barrier'
     Barriers are placed in the instruction stream after unconditional jump
     instructions to indicate that the jumps are unconditional.  They
     contain no information beyond the three standard fields.

`note'
     `note' insns are used to represent additional debugging and
     declarative information.  They contain two nonstandard fields, an
     integer which is accessed with the macro `NOTE_LINE_NUMBER' and a
     string accessed with `NOTE_SOURCE_FILE'.

     If `NOTE_LINE_NUMBER' is positive, the note represents the position of
     a source line and `NOTE_SOURCE_FILE' is the source file name that the
     line came from.  These notes control generation of line number data in
     the assembler output.

     Otherwise, `NOTE_LINE_NUMBER' is not really a line number but a code
     with one of the following values (and `NOTE_SOURCE_FILE' must contain
     a null pointer):

     `NOTE_INSN_DELETED'
          Such a note is completely ignorable.  Some passes of the compiler
          delete insns by altering them into notes of this kind.

     `NOTE_INSN_BLOCK_BEG'
     `NOTE_INSN_BLOCK_END'
          These types of notes indicate the position of the beginning and
          end of a level of scoping of variable names.  They control the
          output of debugging information.

     `NOTE_INSN_LOOP_BEG'
     `NOTE_INSN_LOOP_END'
          These types of notes indicate the position of the beginning and
          end of a `while' or `for' loop.  They enable the loop optimizer
          to find loops quickly.

Here is a table of the extra fields of `insn', `jump_insn' and `call_insn'
insns:

`PATTERN (I)'
     An expression for the side effect performed by this insn.

`REG_NOTES (I)'
     A list (chain of `expr_list' expressions) giving information about the
     usage of registers in this insn.  This list is set up by the flow
     analysis pass; it is a null pointer until then.

`LOG_LINKS (I)'
     A list (chain of `insn_list' expressions) of previous ``related''
     insns: insns which store into registers values that are used for the
     first time in this insn.  (An additional constraint is that neither a
     jump nor a label may come between the related insns).  This list is
     set up by the flow analysis pass; it is a null pointer until then.

`INSN_CODE (I)'
     An integer that says which pattern in the machine description matches
     this insn, or -1 if the matching has not yet been attempted.

     Such matching is never attempted and this field is not used on an insn
     whose pattern consists of a single `use', `clobber', `asm', `addr_vec'
     or `addr_diff_vec' expression.

The `LOG_LINKS' field of an insn is a chain of `insn_list' expressions. 
Each of these has two operands: the first is an insn, and the second is
another `insn_list' expression (the next one in the chain).  The last
`insn_list' in the chain has a null pointer as second operand.  The
significant thing about the chain is which insns appear in it (as first
operands of `insn_list' expressions).  Their order is not significant.

The `REG_NOTES' field of an insn is a similar chain but of `expr_list'
expressions instead of `insn_list'.  There are four kinds of register
notes, which are distinguished by the machine mode of the `expr_list',
which a register note is really understood as being an `enum reg_note'. 
The first operand OP of the `expr_list' is data whose meaning depends on
the kind of note.  Here are the four kinds:

`REG_DEAD'
     The register OP dies in this insn; that is to say, altering the value
     immediately after this insn would not affect the future behavior of
     the program.

`REG_INC'
     The register OP is incremented (or decremented; at this level there is
     no distinction) by an embedded side effect inside this insn.  This
     means it appears in a `POST_INC', `PRE_INC', `POST_DEC' or `PRE_DEC'
     RTX.

`REG_EQUIV'
     The register that is set by this insn will be equal to OP at run time,
     and could validly be replaced in all its occurrences by OP. 
     (``Validly'' here refers to the data flow of the program; simple
     replacement may make some insns invalid.)

     The value which the insn explicitly copies into the register may look
     different from OP, but they will be equal at run time.

     For example, when a constant is loaded into a register that is never
     assigned any other value, this kind of note is used.

     When a parameter is copied into a pseudo-register at entry to a
     function, a note of this kind records that the register is equivalent
     to the stack slot where the parameter was passed.  Although in this
     case the register may be set by other insns, it is still valid to
     replace the register by the stack slot throughout the function.

`REG_EQUAL'
     The register that is set by this insn will be equal to OP at run time
     at the end of this insn (but not necessarily elsewhere in the function).

     The RTX OP is typically an arithmetic expression.  For example, when a
     sequence of insns such as a library call is used to perform an
     arithmetic operation, this kind of note is attached to the insn that
     produces or copies the final value.  It tells the CSE pass how to
     think of that value.

`REG_RETVAL'
     This insn copies the value of a library call, and OP is the first insn
     that was generated to set up the arguments for the library call.

     Flow analysis uses this note to delete all of a library call whose
     result is dead.

`REG_WAS_0'
     The register OP contained zero before this insn.  You can rely on this
     note if it is present; its absence implies nothing.

(The only difference between the expression codes `insn_list' and
`expr_list' is that the first operand of an `insn_list' is assumed to be an
insn and is printed in debugging dumps as the insn's unique id; the first
operand of an `expr_list' is printed in the ordinary way as an expression.)


File: internals,  Node: Calls,  Next: Sharing,  Prev: Insns,  Up: RTL

RTL Representation of Function-Call Insns
=========================================

Insns that call subroutines have the RTL expression code `call_insn'. 
These insns must satisfy special rules, and their bodies must use a special
RTL expression code, `call'.

A `call' expression has two operands, as follows:

     (call NBYTES (mem:FM ADDR))

Here NBYTES is an operand that represents the number of bytes of argument
data being passed to the subroutine, FM is a machine mode (which must equal
as the definition of the `FUNCTION_MODE' macro in the machine description)
and ADDR represents the address of the subroutine.

For a subroutine that returns no value, the `call' RTX as shown above is
the entire body of the insn.

For a subroutine that returns a value whose mode is not `BLKmode', the
value is returned in a hard register.  If this register's number is R, then
the body of the call insn looks like this:

     (set (reg:M R)
          (call NBYTES (mem:FM ADDR)))

This RTL expression makes it clear (to the optimizer passes) that the
appropriate register receives a useful value in this insn.

Immediately after RTL generation, if the value of the subroutine is
actually used, this call insn is always followed closely by an insn which
refers to the register R.  This remains true through all the optimizer
passes until cross jumping occurs.

The following insn has one of two forms.  Either it copies the value into a
pseudo-register, like this:

     (set (reg:M P) (reg:M R))

or (in the case where the calling function will simply return whatever
value the call produced, and no operation is needed to do this):

     (use (reg:M R))

Between the call insn and this following insn there may intervene only a
stack-adjustment insn (and perhaps some `note' insns).

When a subroutine returns a `BLKmode' value, it is handled by passing to
the subroutine the address of a place to store the value.  So the call insn
itself does not ``return'' any value, and it has the same RTL form as a
call that returns nothing.


File: internals,  Node: Sharing,  Prev: Calls,  Up: RTL

Structure Sharing Assumptions
=============================

The compiler assumes that certain kinds of RTL expressions are unique;
there do not exist two distinct objects representing the same value.  In
other cases, it makes an opposite assumption: that no RTL expression object
of a certain kind appears in more than one place in the containing structure.

These assumptions refer to a single function; except for the RTL objects
that describe global variables and external functions, no RTL objects are
common to two functions.

   * Each pseudo-register has only a single `reg' object to represent it,
     and therefore only a single machine mode.

   * For any symbolic label, there is only one `symbol_ref' object
     referring to it.

   * There is only one `const_int' expression with value zero, and only one
     with value one.

   * There is only one `pc' expression.

   * There is only one `cc0' expression.

   * There is only one `const_double' expression with mode `SFmode' and
     value zero, and only one with mode `DFmode' and value zero.

   * No `label_ref' appears in more than one place in the RTL structure; in
     other words, it is safe to do a tree-walk of all the insns in the
     function and assume that each time a `label_ref' is seen it is
     distinct from all others that are seen.

   * Only one `mem' object is normally created for each static variable or
     stack slot, so these objects are frequently shared in all the places
     they appear.  However, separate but equal objects for these variables
     are occasionally made.

   * No RTL object appears in more than one place in the RTL structure
     except as described above.  Many passes of the compiler rely on this
     by assuming that they can modify RTL objects in place without unwanted
     side-effects on other insns.

   * During initial RTL generation, shared structure is freely introduced. 
     After all the RTL for a function has been generated, all shared
     structure is copied by `unshare_all_rtl' in `emit-rtl.c', after which
     the above rules are guaranteed to be followed.

   * During the combiner pass, shared structure with an insn can exist
     temporarily.  However, the shared structure is copied before the
     combiner is finished with the insn.  This is done by
     `copy_substitutions' in `combine.c'.


File: internals,  Node: Machine Desc,  Next: Machine Macros,  Prev: RTL,  Up: Top

Machine Descriptions
********************

A machine description has two parts: a file of instruction patterns (`.md'
file) and a C header file of macro definitions.

The `.md' file for a target machine contains a pattern for each instruction
that the target machine supports (or at least each instruction that is
worth telling the compiler about).  It may also contain comments.  A
semicolon causes the rest of the line to be a comment, unless the semicolon
is inside a quoted string.

See the next chapter for information on the C header file.

* Menu:

* Patterns::            How to write instruction patterns.
* Example::             An explained example of a `define_insn' pattern.
* RTL Template::        The RTL template defines what insns match a pattern.
* Output Template::     The output template says how to make assembler code
                          from such an insn.
* Output Statement::    For more generality, write C code to output 
                          the assembler code.
* Constraints::         When not all operands are general operands.
* Standard Names::      Names mark patterns to use for code generation.
* Pattern Ordering::    When the order of patterns makes a difference.
* Dependent Patterns::  Having one pattern may make you need another.
* Jump Patterns::       Special considerations for patterns for jump insns.
* Peephole Definitions::Defining machine-specific peephole optimizations.
* Expander Definitions::Generating a sequence of several RTL insns
                         for a standard operation.



File: internals,  Node: Patterns,  Next: Example,  Prev: Machine Desc,  Up: Machine Desc

Everything about Instruction Patterns
=====================================

Each instruction pattern contains an incomplete RTL expression, with pieces
to be filled in later, operand constraints that restrict how the pieces can
be filled in, and an output pattern or C code to generate the assembler
output, all wrapped up in a `define_insn' expression.

A `define_insn' is an RTL expression containing four operands:

  1. An optional name.  The presence of a name indicate that this instruction
     pattern can perform a certain standard job for the RTL-generation pass
     of the compiler.  This pass knows certain names and will use the
     instruction patterns with those names, if the names are defined in the
     machine description.

     The absence of a name is indicated by writing an empty string where
     the name should go.  Nameless instruction patterns are never used for
     generating RTL code, but they may permit several simpler insns to be
     combined later on.

     Names that are not thus known and used in RTL-generation have no
     effect; they are equivalent to no name at all.

  2. The "RTL template" (*Note RTL Template::.) is a vector of incomplete RTL
     expressions which show what the instruction should look like.  It is
     incomplete because it may contain `match_operand' and `match_dup'
     expressions that stand for operands of the instruction.

     If the vector has only one element, that element is what the
     instruction should look like.  If the vector has multiple elements,
     then the instruction looks like a `parallel' expression containing
     that many elements as described.

  3. A condition.  This is a string which contains a C expression that is the
     final test to decide whether an insn body matches this pattern.

     For a named pattern, the condition (if present) may not depend on the
     data in the insn being matched, but only the target-machine-type
     flags.  The compiler needs to test these conditions during
     initialization in order to learn exactly which named instructions are
     available in a particular run.

     For nameless patterns, the condition is applied only when matching an
     individual insn, and only after the insn has matched the pattern's
     recognition template.  The insn's operands may be found in the vector
     `operands'.

  4. The "output template": a string that says how to output matching insns
     as assembler code.  `%' in this string specifies where to substitute
     the value of an operand.  *note Output Template::.

     When simple substitution isn't general enough, you can specify a piece
     of C code to compute the output.  *note Output Statement::.


File: internals,  Node: Example,  Next: RTL Template,  Prev: Patterns,  Up: Machine Desc

Example of `define_insn'
========================

Here is an actual example of an instruction pattern, for the 68000/68020.

     (define_insn "tstsi"
       [(set (cc0)
             (match_operand:SI 0 "general_operand" "rm"))]
       ""
       "*
     { if (TARGET_68020 || ! ADDRESS_REG_P (operands[0]))
         return \"tstl %0\";
       return \"cmpl #0,%0\"; }")

This is an instruction that sets the condition codes based on the value of
a general operand.  It has no condition, so any insn whose RTL description
has the form shown may be handled according to this pattern.  The name
`tstsi' means ``test a `SImode' value'' and tells the RTL generation pass
that, when it is necessary to test such a value, an insn to do so can be
constructed using this pattern.

The output control string is a piece of C code which chooses which output
template to return based on the kind of operand and the specific type of
CPU for which code is being generated.

`"rm"' is an operand constraint.  Its meaning is explained below.


File: internals,  Node: RTL Template,  Next: Output Template,  Prev: Example,  Up: Machine Desc

RTL Template for Generating and Recognizing Insns
=================================================

The RTL template is used to define which insns match the particular pattern
and how to find their operands.  For named patterns, the RTL template also
says how to construct an insn from specified operands.

Construction involves substituting specified operands into a copy of the
template.  Matching involves determining the values that serve as the
operands in the insn being matched.  Both of these activities are
controlled by special expression types that direct matching and
substitution of the operands.

`(match_operand:M N TESTFN CONSTRAINT)'
     This expression is a placeholder for operand number N of the insn. 
     When constructing an insn, operand number N will be substituted at
     this point.  When matching an insn, whatever appears at this position
     in the insn will be taken as operand number N; but it must satisfy
     TESTFN or this instruction pattern will not match at all.

     Operand numbers must be chosen consecutively counting from zero in
     each instruction pattern.  There may be only one `match_operand'
     expression in the pattern for each expression number, and they must
     appear in order of increasing expression number.

     TESTFN is a string that is the name of a C function that accepts two
     arguments, a machine mode and an expression.  During matching, the
     function will be called with M as the mode argument and the putative
     operand as the other argument.  If it returns zero, this instruction
     pattern fails to match.  TESTFN may be an empty string; then it means
     no test is to be done on the operand.

     Most often, TESTFN is `"general_operand"'.  It checks that the
     putative operand is either a constant, a register or a memory
     reference, and that it is valid for mode M.

     For an operand that must be a register, TESTFN should be
     `"register_operand"'.  This prevents GNU CC from creating insns that
     have memory references in these operands, insns which would only have
     to be taken apart in the reload pass.

     For an operand that must be a constant, either TESTFN should be
     `"immediate_operand"', or the instruction pattern's extra condition
     should check for constants, or both.

     CONSTRAINT is explained later (*Note Constraints::.).

`(match_dup N)'
     This expression is also a placeholder for operand number N.  It is
     used when the operand needs to appear more than once in the insn.

     In construction, `match_dup' behaves exactly like `match_operand': the
     operand is substituted into the insn being constructed.  But in
     matching, `match_dup' behaves differently.  It assumes that operand
     number N has already been determined by a `match_operand' appearing
     earlier in the recognition template, and it matches only an
     identical-looking expression.

`(address (match_operand:M N "address_operand" ""))'
     This complex of expressions is a placeholder for an operand number N
     in a ``load address'' instruction: an operand which specifies a memory
     location in the usual way, but for which the actual operand value used
     is the address of the location, not the contents of the location.

     `address' expressions never appear in RTL code, only in machine
     descriptions.  And they are used only in machine descriptions that do
     not use the operand constraint feature.  When operand constraints are
     in use, the letter `p' in the constraint serves this purpose.

     M is the machine mode of the *memory location being addressed*, not
     the machine mode of the address itself.  That mode is always the same
     on a given target machine (it is `Pmode', which normally is `SImode'),
     so there is no point in mentioning it; thus, no machine mode is
     written in the `address' expression.  If some day support is added for
     machines in which addresses of different kinds of objects appear
     differently or are used differently (such as the PDP-10), different
     formats would perhaps need different machine modes and these modes
     might be written in the `address' expression.


File: internals,  Node: Output Template,  Next: Output Statement,  Prev: RTL Template,  Up: Machine Desc

Output Templates and Operand Substitution
=========================================

The "output template" is a string which specifies how to output the
assembler code for an instruction pattern.  Most of the template is a fixed
string which is output literally.  The character `%' is used to specify
where to substitute an operand; it can also be used to identify places
different variants of the assembler require different syntax.

In the simplest case, a `%' followed by a digit N says to output operand N
at that point in the string.

`%' followed by a letter and a digit says to output an operand in an
alternate fashion.  Four letters have standard, built-in meanings described
below.  The machine description macro `PRINT_OPERAND' can define additional
letters with nonstandard meanings.

`%cDIGIT' can be used to substitute an operand that is a constant value
without the syntax that normally indicates an immediate operand.

`%nDIGIT' is like `%cDIGIT' except that the value of the constant is
negated before printing.

`%aDIGIT' can be used to substitute an operand as if it were a memory
reference, with the actual operand treated as the address.  This may be
useful when outputting a ``load address'' instruction, because often the
assembler syntax for such an instruction requires you to write the operand
as if it were a memory reference.

`%lDIGIT' is used to substitute a `label_ref' into a jump instruction.

`%' followed by a punctuation character specifies a substitution that does
not use an operand.  Only one case is standard: `%%' outputs a `%' into the
assembler code.  Other nonstandard cases can be defined in the
`PRINT_OPERAND' macro.

The template may generate multiple assembler instructions.  Write the text
for the instructions, with `\;' between them.

When the RTL contains two operand which are required by constraint to match
each other, the output template must refer only to the lower-numbered
operand.  Matching operands are not always identical, and the rest of the
compiler arranges to put the proper RTL expression for printing into the
lower-numbered operand.

One use of nonstandard letters or punctuation following `%' is to
distinguish between different assembler languages for the same machine; for
example, Motorola syntax versus MIT syntax for the 68000.  Motorola syntax
requires periods in most opcode names, while MIT syntax does not.  For
example, the opcode `movel' in MIT syntax is `move.l' in Motorola syntax. 
The same file of patterns is used for both kinds of output syntax, but the
character sequence `%.' is used in each place where Motorola syntax wants a
period.  The `PRINT_OPERAND' macro for Motorola syntax defines the sequence
to output a period; the macro for MIT syntax defines it to do nothing.


File: internals,  Node: Output Statement,  Next: Constraints,  Prev: Output Template,  Up: Machine Desc

C Statements for Generating Assembler Output
============================================

Often a single fixed template string cannot produce correct and efficient
assembler code for all the cases that are recognized by a single
instruction pattern.  For example, the opcodes may depend on the kinds of
operands; or some unfortunate combinations of operands may require extra
machine instructions.

If the output control string starts with a `*', then it is not an output
template but rather a piece of C program that should compute a template. 
It should execute a `return' statement to return the template-string you
want.  Most such templates use C string literals, which require doublequote
characters to delimit them.  To include these doublequote characters in the
string, prefix each one with `\'.

The operands may be found in the array `operands', whose C data type is
`rtx []'.

It is possible to output an assembler instruction and then go on to output
or compute more of them, using the subroutine `output_asm_insn'.  This
receives two arguments: a template-string and a vector of operands.  The
vector may be `operands', or it may be another array of `rtx' that you
declare locally and initialize yourself.

When an insn pattern has multiple alternatives in its constraints, often
the appearance of the assembler code determined mostly by which alternative
was matched.  When this is so, the C code can test the variable
`which_alternative', which is the ordinal number of the alternative that
was actually satisfied (0 for the first, 1 for the second alternative, etc.).

For example, suppose there are two opcodes for storing zero, `clrreg' for
registers and `clrmem' for memory locations.  Here is how a pattern could
use `which_alternative' to choose between them:

     (define_insn ""
       [(set (match_operand:SI 0 "general_operand" "r,m")
             (const_int 0))]
       ""
       "*
       return (which_alternative == 0
               ? \"clrreg %0\" : \"clrmem %0\");
       ")


File: internals,  Node: Constraints,  Next: Standard Names,  Prev: Output Statement,  Up: Machine Desc

Operand Constraints
===================

Each `match_operand' in an instruction pattern can specify a constraint for
the type of operands allowed.  Constraints can say whether an operand may
be in a register, and which kinds of register; whether the operand can be a
memory reference, and which kinds of address; whether the operand may be an
immediate constant, and which possible values it may have.  Constraints can
also require two operands to match.

* Menu:

* Simple Constraints::  Basic use of constraints.
* Multi-Alternative::   When an insn has two alternative constraint-patterns.
* Class Preferences::   Constraints guide which hard register to put things in.
* Modifiers::           More precise control over effects of constraints.
* No Constraints::      Describing a clean machine without constraints.



File: internals,  Node: Simple Constraints,  Next: Multi-Alternative,  Prev: Constraints,  Up: Constraints

Simple Constraints
------------------

The simplest kind of constraint is a string full of letters, each of which
describes one kind of operand that is permitted.  Here are the letters that
are allowed:

`m'
     A memory operand is allowed, with any kind of address that the machine
     supports in general.

`o'
     A memory operand is allowed, but only if the address is "offsetable". 
     This means that adding a small integer (actually, the width in bytes
     of the operand, as determined by its machine mode) may be added to the
     address and the result is also a valid memory address.

     For example, an address which is constant is offsetable; so is an
     address that is the sum of a register and a constant (as long as a
     slightly larger constant is also within the range of address-offsets
     supported by the machine); but an autoincrement or autodecrement
     address is not offsetable.  More complicated indirect/indexed
     addresses may or may not be offsetable depending on the other
     addressing modes that the machine supports.

     Note that in an output operand which can be matched by another
     operand, the constraint letter `o' is valid only when accompanied by
     both `<' (if the target machine has predecrement addressing) and `>'
     (if the target machine has preincrement addressing).

`<'
     A memory operand with autodecrement addressing (either predecrement or
     postdecrement) is allowed.

`>'
     A memory operand with autoincrement addressing (either preincrement or
     postincrement) is allowed.

`r'
     A register operand is allowed provided that it is in a general register.

`d', `a', `f', ...
      Other letters can be defined in machine-dependent fashion to stand for
     particular classes of registers.  `d', `a' and `f' are defined on the
     68000/68020 to stand for data, address and floating point registers.

`i'
     An immediate integer operand (one with constant value) is allowed. 
     This includes symbolic constants whose values will be known only at
     assembly time.

`n'
     An immediate integer operand with a known numeric value is allowed. 
     Many systems cannot support assembly-time constants for operands less
     than a word wide.  Constraints for these operands should use `n'
     rather than `i'.

`I', `J', `K', ...
      Other letters in the range `I' through `M' may be defined in a
     machine-dependent fashion to permit immediate integer operands with
     explicit integer values in specified ranges.  For example, on the
     68000, `I' is defined to stand for the range of values 1 to 8.  This
     is the range permitted as a shift count in the shift instructions.

`F'
     An immediate floating operand (expression code `const_double') is
     allowed.

`G', `H'
     `G' and `H' may be defined in a machine-dependent fashion to permit
     immediate floating operands in particular ranges of values.

`s'
     An immediate integer operand whose value is not an explicit integer is
     allowed.

     This might appear strange; if an insn allows a constant operand with a
     value not known at compile time, it certainly must allow any known
     value.  So why use `s' instead of `i'?  Sometimes it allows better
     code to be generated.

     For example, on the 68000 in a fullword instruction it is possible to
     use an immediate operand; but if the immediate value is between -32
     and 31, better code results from loading the value into a register and
     using the register.  This is because the load into the register can be
     done with a `moveq' instruction.  We arrange for this to happen by
     defining the letter `K' to mean ``any integer outside the range -32 to
     31'', and then specifying `Ks' in the operand constraints.

`g'
     Any register, memory or immediate integer operand is allowed, except
     for registers that are not general registers.

`N' (a digit)
     An operand that matches operand number N is allowed.  If a digit is
     used together with letters, the digit should come last.

     This is called a "matching constraint" and what it really means is
     that the assembler has only a single operand that fills two roles
     considered separate in the RTL insn.  For example, an add insn has two
     input operands and one output operand in the RTL, but on most machines
     an add instruction really has only two operands, one of them an
     input-output operand.

     Matching constraints work only in circumstances like that add insn. 
     More precisely, the matching constraint must appear in an input-only
     operand and the operand that it matches must be an output-only operand
     with a lower number.

     For operands to match in a particular case usually means that they are
     identical-looking RTL expressions.  But in a few special cases
     specific kinds of dissimilarity are allowed.  For example, `*x' as an
     input operand will match `*x++' as an output operand.  For proper
     results in such cases, the output template should always use the
     output-operand's number when printing the operand.

`p'
     An operand that is a valid memory address is allowed.  This is for
     ``load address'' and ``push address'' instructions.

     If `p' is used in the constraint, the test-function in the
     `match_operand' must be `address_operand'.

In order to have valid assembler code, each operand must satisfy its
constraint.  But a failure to do so does not prevent the pattern from
applying to an insn.  Instead, it directs the compiler to modify the code
so that the constraint will be satisfied.  Usually this is done by copying
an operand into a register.

Contrast, therefore, the two instruction patterns that follow:

     (define_insn ""
       [(set (match_operand:SI 0 "general_operand" "r")
             (plus:SI (match_dup 0)
                      (match_operand:SI 1 "general_operand" "r")))]
       ""
       "...")

which has two operands, one of which must appear in two places, and

     (define_insn ""
       [(set (match_operand:SI 0 "general_operand" "r")
             (plus:SI (match_operand:SI 1 "general_operand" "0")
                      (match_operand:SI 2 "general_operand" "r")))]
       ""
       "...")

which has three operands, two of which are required by a constraint to be
identical.  If we are considering an insn of the form

     (insn N PREV NEXT
       (set (reg:SI 3)
            (plus:SI (reg:SI 6) (reg:SI 109)))
       ...)

the first pattern would not apply at all, because this insn does not
contain two identical subexpressions in the right place.  The pattern would
say, ``That does not look like an add instruction; try other patterns.''
The second pattern would say, ``Yes, that's an add instruction, but there
is something wrong with it.''  It would direct the reload pass of the
compiler to generate additional insns to make the constraint true.  The
results might look like this:

     (insn N2 PREV N
       (set (reg:SI 3) (reg:SI 6))
       ...)
     
     (insn N N2 NEXT
       (set (reg:SI 3)
            (plus:SI (reg:SI 3) (reg:SI 109)))
       ...)

Because insns that don't fit the constraints are fixed up by loading
operands into registers, every instruction pattern's constraints must
permit the case where all the operands are in registers.  It need not
permit all classes of registers; the compiler knows how to copy registers
into other registers of the proper class in order to make an instruction
valid.  But if no registers are permitted, the compiler will be stymied: it
does not know how to save a register in memory in order to make an
instruction valid.  Instruction patterns that reject registers can be made
valid by attaching a condition-expression that refuses to match an insn at
all if the crucial operand is a register.