OSDN Git Service

* unwind-dw2-fde.c (__deregister_frame_info): Stringize use
[pf3gnuchains/gcc-fork.git] / gcc / rtl.texi
index 539d420..026172c 100644 (file)
@@ -1,4 +1,5 @@
-@c Copyright (C) 1988, 1989, 1992, 1994, 1997 Free Software Foundation, Inc.
+@c Copyright (C) 1988, 1989, 1992, 1994, 1997, 1998, 1999, 2000, 2001
+@c Free Software Foundation, Inc.
 @c This is part of the GCC manual.
 @c For copying conditions, see the file gcc.texi.
 
@@ -20,6 +21,7 @@ form uses nested parentheses to indicate the pointers in the internal form.
 
 @menu
 * RTL Objects::       Expressions vs vectors vs strings vs integers.
+* RTL Classes::       Categories of RTL expresion objects, and their structure.
 * Accessors::         Macros to access expression operands or vector elts.
 * Flags::             Other flags in an RTL expression.
 * Machine Modes::     Describing the size and format of a datum.
@@ -28,6 +30,7 @@ form uses nested parentheses to indicate the pointers in the internal form.
 * Arithmetic::        Expressions representing arithmetic on other expressions.
 * Comparisons::       Expressions representing comparison of expressions.
 * Bit Fields::        Expressions representing bitfields in memory or reg.
+* Vector Operations:: Expressions involving vector datatypes.
 * Conversions::       Extending, truncating, floating or fixing.
 * RTL Declarations::  Declaring volatility, constancy, etc.
 * Side Effects::      Expressions for storing in registers, etc.
@@ -39,7 +42,7 @@ form uses nested parentheses to indicate the pointers in the internal form.
 * Reading RTL::       Reading textual RTL from a file.
 @end menu
 
-@node RTL Objects, Accessors, RTL, RTL
+@node RTL Objects
 @section RTL Object Types
 @cindex RTL object types
 
@@ -108,11 +111,72 @@ manual, they are shown as follows: @code{const_int}.
 In a few contexts a null pointer is valid where an expression is normally
 wanted.  The written form of this is @code{(nil)}.
 
-@node Accessors, Flags, RTL Objects, RTL
-@section Access to Operands
-@cindex accessors
-@cindex access to operands
-@cindex operand access
+@node RTL Classes
+@section RTL Classes and Formats
+@cindex RTL classes
+@cindex classes of RTX codes
+@cindex RTX codes, classes of
+@findex GET_RTX_CLASS
+
+The various expression codes are divided into several @dfn{classes},
+which are represented by single characters.  You can determine the class
+of an RTX code with the macro @code{GET_RTX_CLASS (@var{code})}.
+Currently, @file{rtx.def} defines these classes:
+
+@table @code
+@item o
+An RTX code that represents an actual object, such as a register
+(@code{REG}) or a memory location (@code{MEM}, @code{SYMBOL_REF}).
+Constants and basic transforms on objects (@code{ADDRESSOF},
+@code{HIGH}, @code{LO_SUM}) are also included.  Note that @code{SUBREG}
+and @code{STRICT_LOW_PART} are not in this class, but in class @code{x}.
+
+@item <
+An RTX code for a comparison, such as @code{NE} or @code{LT}.
+
+@item 1
+An RTX code for a unary arithmetic operation, such as @code{NEG},
+@code{NOT}, or @code{ABS}.  This category also includes value extension
+(sign or zero) and conversions between integer and floating point.
+
+@item c
+An RTX code for a commutative binary operation, such as @code{PLUS} or
+@code{AND}.  @code{NE} and @code{EQ} are comparisons, so they have class
+@code{<}.
+
+@item 2
+An RTX code for a non-commutative binary operation, such as @code{MINUS},
+@code{DIV}, or @code{ASHIFTRT}.
+
+@item b
+An RTX code for a bitfield operation.  Currently only
+@code{ZERO_EXTRACT} and @code{SIGN_EXTRACT}.  These have three inputs
+and are lvalues (so they can be used for insertion as well).  @xref{Bit
+Fields}.
+
+@item 3
+An RTX code for other three input operations.  Currently only
+@code{IF_THEN_ELSE}.
+
+@item i
+An RTX code for an entire instruction:  @code{INSN}, @code{JUMP_INSN}, and
+@code{CALL_INSN}. @xref{Insns}.
+
+@item m
+An RTX code for something that matches in insns, such as
+@code{MATCH_DUP}.  These only occur in machine descriptions.
+
+@item a
+An RTX code for an auto-increment addressing mode, such as
+@code{POST_INC}.
+
+@item x
+All other RTX codes.  This category includes the remaining codes used
+only in machine descriptions (@code{DEFINE_*}, etc.).  It also includes
+all the codes describing side effects (@code{SET}, @code{USE},
+@code{CLOBBER}, etc.) and the non-insns that may appear on an insn
+chain, such as @code{NOTE}, @code{BARRIER}, and @code{CODE_LABEL}.
+@end table
 
 @cindex RTL format
 For each expression type @file{rtl.def} specifies the number of
@@ -120,7 +184,7 @@ contained objects and their kinds, with four possibilities: @samp{e} for
 expression (actually a pointer to an expression), @samp{i} for integer,
 @samp{w} for wide integer, @samp{s} for string, and @samp{E} for vector
 of expressions.  The sequence of letters for an expression code is
-called its @dfn{format}.  Thus, the format of @code{subreg} is
+called its @dfn{format}.  For example, the format of @code{subreg} is
 @samp{ei}.@refill
 
 @cindex RTL format characters
@@ -154,8 +218,8 @@ An omitted vector is effectively the same as a vector of no elements.
 special ways by small parts of the compiler.
 @end table
 
-There are macros to get the number of operands, the format, and the
-class of an expression code:
+There are macros to get the number of operands and the format
+of an expression code:
 
 @table @code
 @findex GET_RTX_LENGTH
@@ -165,54 +229,41 @@ Number of operands of an RTX of code @var{code}.
 @findex GET_RTX_FORMAT
 @item GET_RTX_FORMAT (@var{code})
 The format of an RTX of code @var{code}, as a C string.
+@end table
 
-@findex GET_RTX_CLASS
-@cindex classes of RTX codes
-@item GET_RTX_CLASS (@var{code})
-A single character representing the type of RTX operation that code
-@var{code} performs.
-
-The following classes are defined:
+Some classes of RTX codes always have the same format.  For example, it
+is safe to assume that all comparison operations have format @code{ee}.
 
 @table @code
-@item o
-An RTX code that represents an actual object, such as @code{reg} or
-@code{mem}.  @code{subreg} is not in this class.
-
-@item <
-An RTX code for a comparison.  The codes in this class are
-@code{NE}, @code{EQ}, @code{LE}, @code{LT}, @code{GE}, @code{GT},
-@code{LEU}, @code{LTU}, @code{GEU}, @code{GTU}.@refill
-
 @item 1
-An RTX code for a unary arithmetic operation, such as @code{neg}.
-
-@item c
-An RTX code for a commutative binary operation, other than @code{NE}
-and @code{EQ} (which have class @samp{<}).
+All codes of this class have format @code{e}.
 
-@item 2
-An RTX code for a noncommutative binary operation, such as @code{MINUS}.
+@item <
+@itemx c
+@itemx 2
+All codes of these classes have format @code{ee}.
 
 @item b
-An RTX code for a bitfield operation, either @code{ZERO_EXTRACT} or
-@code{SIGN_EXTRACT}.
-
-@item 3
-An RTX code for other three input operations, such as @code{IF_THEN_ELSE}.
+@itemx 3
+All codes of these classes have format @code{eee}.
 
 @item i
-An RTX code for a machine insn (@code{INSN}, @code{JUMP_INSN}, and
-@code{CALL_INSN}).@refill
+All codes of this class have formats that begin with @code{iuueiee}.
+@xref{Insns}.  Note that not all RTL objects linked onto an insn chain
+are of class @code{i}.
 
-@item m
-An RTX code for something that matches in insns, such as @code{MATCH_DUP}.
-
-@item x
-All other RTX codes.
-@end table
+@item o
+@itemx m
+@itemx x
+You can make no assumptions about the format of these codes.
 @end table
 
+@node Accessors
+@section Access to Operands
+@cindex accessors
+@cindex access to operands
+@cindex operand access
+
 @findex XEXP
 @findex XINT
 @findex XWINT
@@ -283,13 +334,13 @@ All the macros defined in this section expand into lvalues and therefore
 can be used to assign the operands, lengths and vector elements as well as
 to access them.
 
-@node Flags, Machine Modes, Accessors, RTL
+@node Flags
 @section Flags in an RTL Expression
 @cindex flags in RTL expression
 
-RTL expressions contain several flags (one-bit bitfields) that are used
-in certain types of expression.  Most often they are accessed with the
-following macros:
+RTL expressions contain several flags (one-bit bitfields) and other
+values that are used in certain types of expression.  Most often they
+are accessed with the following macros:
 
 @table @code
 @findex MEM_VOLATILE_P
@@ -305,10 +356,33 @@ Stored in the @code{volatil} field and printed as @samp{/v}.
 @cindex @code{in_struct}, in @code{mem}
 @cindex @samp{/s} in RTL dump
 @item MEM_IN_STRUCT_P (@var{x})
-In @code{mem} expressions, nonzero for reference to an entire
-structure, union or array, or to a component of one.  Zero for
-references to a scalar variable or through a pointer to a scalar.
-Stored in the @code{in_struct} field and printed as @samp{/s}.
+In @code{mem} expressions, nonzero for reference to an entire structure,
+union or array, or to a component of one.  Zero for references to a
+scalar variable or through a pointer to a scalar.  Stored in the
+@code{in_struct} field and printed as @samp{/s}.  If both this flag and
+MEM_SCALAR_P are clear, then we don't know whether this MEM is in a
+structure or not.  Both flags should never be simultaneously set.
+
+@findex MEM_SCALAR_P
+@cindex @code{mem} and @samp{/f}
+@cindex @code{frame_related}, in@code{mem}
+@cindex @samp{/f} in RTL dump
+@item MEM_SCALAR_P (@var{x})
+In @code{mem} expressions, nonzero for reference to a scalar known not
+to be a member of a structure, union, or array.  Zero for such
+references and for indirections through pointers, even pointers pointing
+to scalar types.  If both this flag and MEM_STRUCT_P are clear, then we
+don't know whether this MEM is in a structure or not.  Both flags should
+never be simultaneously set.
+
+@findex MEM_ALIAS_SET
+@item MEM_ALIAS_SET (@var{x})
+In @code{mem} expressions, the alias set to which @var{x} belongs.  If
+zero, @var{x} is not in any alias set, and may alias anything.  If
+nonzero, @var{x} may only alias objects in the same alias set.  This
+value is set (in a language-specific manner) by the front-end.  This
+field is not a bit-field; it is in an integer, found as the second
+argument to the @code{mem}.
 
 @findex REG_LOOP_TEST_P
 @cindex @code{reg} and @samp{/s}
@@ -380,8 +454,33 @@ other functions or by aliasing.)  Stored in the
 @cindex @code{integrated}, in @code{insn}
 @item RTX_INTEGRATED_P (@var{insn})
 Nonzero in an insn if it resulted from an in-line function call.
-Stored in the @code{integrated} field and printed as @samp{/i}.  This
-may be deleted; nothing currently depends on it.
+Stored in the @code{integrated} field and printed as @samp{/i}.
+
+@findex RTX_FRAME_RELATED_P
+@item RTX_FRAME_RELATED_P (@var{x})
+Nonzero in an insn or expression which is part of a function prologue
+and sets the stack pointer, sets the frame pointer, or saves a register.
+This flag should also be set on an instruction that sets up a temporary
+register to use in place of the frame pointer.
+
+In particular, on RISC targets where there are limits on the sizes of
+immediate constants, it is sometimes impossible to reach the register
+save area directly from the stack pointer.  In that case, a temporary
+register is used that is near enough to the register save area, and the
+Canonical Frame Address, i.e., DWARF2's logical frame pointer, register
+must (temporarily) be changed to be this temporary register.  So, the
+instruction that sets this temporary register must be marked as
+@code{RTX_FRAME_RELATED_P}.
+
+If the marked instruction is overly complex (defined in terms of what
+@code{dwarf2out_frame_debug_expr} can handle), you will also have to
+create a @code{REG_FRAME_RELATED_EXPR} note and attach it to the
+instruction.  This note should contain a simple expression of the
+computation performed by this instruction, i.e., one that
+@code{dwarf2out_frame_debug_expr} can handle.
+
+This flag is required for exception handling support on targets with RTL
+prologues.
 
 @findex SYMBOL_REF_USED
 @cindex @code{used}, in @code{symbol_ref}
@@ -397,6 +496,13 @@ once.  Stored in the @code{used} field.
 In a @code{symbol_ref}, this is used as a flag for machine-specific purposes.
 Stored in the @code{volatil} field and printed as @samp{/v}.
 
+@findex SYMBOL_REF_WEAK
+@cindex @code{symbol_ref} and @samp{/i}
+@cindex @code{integrated}, in @code{symbol_ref}
+@item SYMBOL_REF_WEAK (@var{x})
+In a @code{symbol_ref}, indicates that @var{x} has been declared weak.
+Stored in the @code{integrated} field and printed as @samp{/i}.
+
 @findex LABEL_OUTSIDE_LOOP_P
 @cindex @code{label_ref} and @samp{/s}
 @cindex @code{in_struct}, in @code{label_ref}
@@ -427,10 +533,12 @@ as @samp{/u}.
 @item INSN_FROM_TARGET_P (@var{insn})
 In an @code{insn} in a delay slot of a branch, indicates that the insn
 is from the target of the branch.  If the branch insn has
-@code{INSN_ANNULLED_BRANCH_P} set, this insn should only be executed if
-the branch is taken.  For annulled branches with this bit clear, the
-insn should be executed only if the branch is not taken.  Stored in the
-@code{in_struct} field and printed as @samp{/s}.
+@code{INSN_ANNULLED_BRANCH_P} set, this insn will only be executed if
+the branch is taken.  For annulled branches with
+@code{INSN_FROM_TARGET_P} clear, the insn will be executed only if the
+branch is not taken.  When @code{INSN_ANNULLED_BRANCH_P} is not set,
+this insn will always be executed.  Stored in the @code{in_struct}
+field and printed as @samp{/s}.
 
 @findex CONSTANT_POOL_ADDRESS_P 
 @cindex @code{symbol_ref} and @samp{/u}
@@ -562,7 +670,7 @@ may be used for parameters as well, but this flag is not set on such
 uses.
 @end table
 
-@node Machine Modes, Constants, Flags, RTL
+@node Machine Modes
 @section Machine Modes
 @cindex machine modes
 
@@ -584,6 +692,10 @@ Here is a table of machine modes.  The term ``byte'' below refers to an
 object of @code{BITS_PER_UNIT} bits (@pxref{Storage Layout}).
 
 @table @code
+@findex BImode
+@item BImode
+``Bit'' mode represents a single bit, for predicate registers.
+
 @findex QImode
 @item QImode
 ``Quarter-Integer'' mode represents a single byte treated as an integer.
@@ -616,6 +728,10 @@ this is the right mode to use for certain pointers.
 @item TImode
 ``Tetra Integer'' (?) mode represents a sixteen-byte integer.
 
+@findex OImode
+@item OImode
+``Octa Integer'' (?) mode represents a thirty-two-byte integer.
+
 @findex SFmode
 @item SFmode
 ``Single Floating'' mode represents a single-precision (four byte) floating
@@ -790,7 +906,7 @@ mode @var{m}.  This macro can only be used for modes whose bitsize is
 less than or equal to @code{HOST_BITS_PER_INT}.
 
 @findex GET_MODE_ALIGNMENT
-@item GET_MODE_ALIGNMENT (@var{m)})
+@item GET_MODE_ALIGNMENT (@var{m})
 Return the required alignment, in bits, for an object of mode @var{m}.
 
 @findex GET_MODE_UNIT_SIZE
@@ -817,7 +933,7 @@ whose classes are @code{MODE_INT} and whose bitsizes are either
 @code{BITS_PER_UNIT} or @code{BITS_PER_WORD}, respectively.  On 32-bit
 machines, these are @code{QImode} and @code{SImode}, respectively.
 
-@node Constants, Regs and Memory, Machine Modes, RTL
+@node Constants
 @section Constant Expression Types
 @cindex RTL constants
 @cindex RTL constant expression types
@@ -944,7 +1060,7 @@ reference a global memory location.
 @var{m} should be @code{Pmode}.
 @end table
 
-@node Regs and Memory, Arithmetic, Constants, RTL
+@node Regs and Memory
 @section Registers and Memory
 @cindex RTL register expressions
 @cindex RTL memory expressions
@@ -1057,16 +1173,16 @@ This virtual register is replaced by the sum of the register given by
 @end table
 
 @findex subreg
-@item (subreg:@var{m} @var{reg} @var{wordnum})
+@item (subreg:@var{m} @var{reg} @var{bytenum})
 @code{subreg} expressions are used to refer to a register in a machine
 mode other than its natural one, or to refer to one register of
-a multi-word @code{reg} that actually refers to several registers.
+a multi-part @code{reg} that actually refers to several registers.
 
 Each pseudo-register has a natural mode.  If it is necessary to
 operate on it in a different mode---for example, to perform a fullword
 move instruction on a pseudo-register that contains a single
 byte---the pseudo-register must be enclosed in a @code{subreg}.  In
-such a case, @var{wordnum} is zero.
+such a case, @var{bytenum} is zero.
 
 Usually @var{m} is at least as narrow as the mode of @var{reg}, in which
 case it is restricting consideration to only the bits of @var{reg} that
@@ -1083,7 +1199,7 @@ a multi-register value.  Machine modes such as @code{DImode} and
 @code{TImode} can indicate values longer than a word, values which
 usually require two or more consecutive registers.  To access one of the
 registers, use a @code{subreg} with mode @code{SImode} and a
-@var{wordnum} that says which register.
+@var{bytenum} offset that says which register.
 
 Storing in a non-paradoxical @code{subreg} has undefined results for
 bits belonging to the same word as the @code{subreg}.  This laxity makes
@@ -1093,8 +1209,22 @@ the @code{subreg}, use @code{strict_low_part} around the @code{subreg}.
 
 @cindex @code{WORDS_BIG_ENDIAN}, effect on @code{subreg}
 The compilation parameter @code{WORDS_BIG_ENDIAN}, if set to 1, says
-that word number zero is the most significant part; otherwise, it is
-the least significant part.
+that byte number zero is part of the most significant word; otherwise,
+it is part of the least significant word.
+
+@cindex @code{BYTES_BIG_ENDIAN}, effect on @code{subreg}
+The compilation parameter @code{BYTES_BIG_ENDIAN}, if set to 1, says
+that byte number zero is the most significant byte within a word;
+otherwise, it is the least significant byte within a word.
+
+@cindex @code{FLOAT_WORDS_BIG_ENDIAN}, (lack of) effect on @code{subreg}
+On a few targets, @code{FLOAT_WORDS_BIG_ENDIAN} disagrees with
+@code{WORDS_BIG_ENDIAN}.
+However, most parts of the compiler treat floating point values as if
+they had the same endianness as integer values.  This works because
+they handle them solely as a collection of integer values, with no
+particular numerical value.  Only real.c and the runtime libraries
+care about @code{FLOAT_WORDS_BIG_ENDIAN}.
 
 @cindex combiner pass
 @cindex reload pass
@@ -1121,10 +1251,10 @@ a single machine register.  The reload pass prevents @code{subreg}
 expressions such as these from being formed.
 
 @findex SUBREG_REG
-@findex SUBREG_WORD
+@findex SUBREG_BYTE
 The first operand of a @code{subreg} expression is customarily accessed 
 with the @code{SUBREG_REG} macro and the second operand is customarily
-accessed with the @code{SUBREG_WORD} macro.
+accessed with the @code{SUBREG_BYTE} macro.
 
 @findex scratch
 @cindex scratch operands
@@ -1208,13 +1338,23 @@ All instructions that do not jump alter the program counter implicitly
 by incrementing it, but there is no need to mention this in the RTL.
 
 @findex mem
-@item (mem:@var{m} @var{addr})
+@item (mem:@var{m} @var{addr} @var{alias})
 This RTX represents a reference to main memory at an address
 represented by the expression @var{addr}.  @var{m} specifies how large
-a unit of memory is accessed.
+a unit of memory is accessed. @var{alias} specifies an alias set for the
+reference. In general two items are in different alias sets if they cannot
+reference the same memory address.
+
+@findex addressof
+@item (addressof:@var{m} @var{reg})
+This RTX represents a request for the address of register @var{reg}.  Its mode
+is always @code{Pmode}.  If there are any @code{addressof}
+expressions left in the function after CSE, @var{reg} is forced into the
+stack and the @code{addressof} expression is replaced with a @code{plus}
+expression for the address of its stack slot.
 @end table
 
-@node Arithmetic, Comparisons, Regs and Memory, RTL
+@node Arithmetic
 @section RTL Expressions for Arithmetic
 @cindex arithmetic, in RTL
 @cindex math, in RTL
@@ -1252,6 +1392,30 @@ item minus the number of bits set by the @code{high} code
 @item (minus:@var{m} @var{x} @var{y})
 Like @code{plus} but represents subtraction.
 
+@findex ss_plus
+@cindex RTL addition with signed saturation
+@item (ss_plus:@var{m} @var{x} @var{y})
+
+Like @code{plus}, but using signed saturation in case of an overflow.
+
+@findex us_plus
+@cindex RTL addition with unsigned saturation
+@item (us_plus:@var{m} @var{x} @var{y})
+
+Like @code{plus}, but using unsigned saturation in case of an overflow.
+
+@findex ss_minus
+@cindex RTL addition with signed saturation
+@item (ss_minus:@var{m} @var{x} @var{y})
+
+Like @code{minus}, but using signed saturation in case of an overflow.
+
+@findex us_minus
+@cindex RTL addition with unsigned saturation
+@item (us_minus:@var{m} @var{x} @var{y})
+
+Like @code{minus}, but using unsigned saturation in case of an overflow.
+
 @findex compare
 @cindex RTL comparison
 @item (compare:@var{m} @var{x} @var{y})
@@ -1260,15 +1424,21 @@ of comparison.  The result is computed without overflow, as if with
 infinite precision.
 
 Of course, machines can't really subtract with infinite precision.
-However, they can pretend to do so when only the sign of the
-result will be used, which is the case when the result is stored
-in the condition code.   And that is the only way this kind of expression
-may validly be used: as a value to be stored in the condition codes.
-
-The mode @var{m} is not related to the modes of @var{x} and @var{y},
-but instead is the mode of the condition code value.  If @code{(cc0)}
-is used, it is @code{VOIDmode}.  Otherwise it is some mode in class
-@code{MODE_CC}, often @code{CCmode}.  @xref{Condition Code}.
+However, they can pretend to do so when only the sign of the result will
+be used, which is the case when the result is stored in the condition
+code.  And that is the @emph{only} way this kind of expression may
+validly be used: as a value to be stored in the condition codes, either
+@code{(cc0)} or a register. @xref{Comparisons}.
+
+The mode @var{m} is not related to the modes of @var{x} and @var{y}, but
+instead is the mode of the condition code value.  If @code{(cc0)} is
+used, it is @code{VOIDmode}.  Otherwise it is some mode in class
+@code{MODE_CC}, often @code{CCmode}.  @xref{Condition Code}.  If @var{m}
+is @code{VOIDmode} or @code{CCmode}, the operation returns sufficient
+information (in an unspecified format) so that any comparison operator
+can be applied to the result of the @code{COMPARE} operation.  For other
+modes in class @code{MODE_CC}, the operation only returns a subset of
+this information.
 
 Normally, @var{x} and @var{y} must have the same mode.  Otherwise,
 @code{compare} is valid only if the mode of @var{x} is in class
@@ -1442,7 +1612,7 @@ depending on the target machine, various mode combinations may be
 valid.
 @end table
 
-@node Comparisons, Bit Fields, Arithmetic, RTL
+@node Comparisons
 @section Comparison Operations
 @cindex RTL comparison operations
 
@@ -1463,7 +1633,7 @@ There are two ways that comparison operations may be used.  The
 comparison operators may be used to compare the condition codes
 @code{(cc0)} against zero, as in @code{(eq (cc0) (const_int 0))}.  Such
 a construct actually refers to the result of the preceding instruction
-in which the condition codes were set.  The instructing setting the
+in which the condition codes were set.  The instruction setting the
 condition code must be adjacent to the instruction using the condition
 code; only @code{note} insns may separate them.
 
@@ -1495,20 +1665,20 @@ point comparisons are distinguished by the machine modes of the operands.
 @findex eq
 @cindex equal
 @item (eq:@var{m} @var{x} @var{y})
-1 if the values represented by @var{x} and @var{y} are equal,
-otherwise 0.
+@code{STORE_FLAG_VALUE} if the values represented by @var{x} and @var{y}
+are equal, otherwise 0.
 
 @findex ne
 @cindex not equal
 @item (ne:@var{m} @var{x} @var{y})
-1 if the values represented by @var{x} and @var{y} are not equal,
-otherwise 0.
+@code{STORE_FLAG_VALUE} if the values represented by @var{x} and @var{y}
+are not equal, otherwise 0.
 
 @findex gt
 @cindex greater than
 @item (gt:@var{m} @var{x} @var{y})
-1 if the @var{x} is greater than @var{y}.  If they are fixed-point,
-the comparison is done in a signed sense.
+@code{STORE_FLAG_VALUE} if the @var{x} is greater than @var{y}.  If they
+are fixed-point, the comparison is done in a signed sense.
 
 @findex gtu
 @cindex greater than
@@ -1562,7 +1732,7 @@ This is currently not valid for instruction patterns and is supported only
 for insn attributes.  @xref{Insn Attributes}.
 @end table
 
-@node Bit Fields, Conversions, Comparisons, RTL
+@node Bit Fields
 @section Bit Fields
 @cindex bit fields
 
@@ -1600,7 +1770,53 @@ bit field.  The same sequence of bits are extracted, but they
 are filled to an entire word with zeros instead of by sign-extension.
 @end table
 
-@node Conversions, RTL Declarations, Bit Fields, RTL
+@node Vector Operations
+@section Vector Operations
+@cindex vector operations
+
+All normal rtl expressions can be used with vector modes; they are
+interpreted as operating on each part of the vector independently.
+Additionally, there are a few new expressions to describe specific vector
+operations.
+
+@table @code
+@findex vec_merge
+@item (vec_merge:@var{m} @var{vec1} @var{vec2} @var{items})
+This describes a merge operation between two vectors.  The result is a vector
+of mode @var{m}; its elements are selected from either @var{vec1} or
+@var{vec2}.  Which elements are selected is described by @var{items}, which
+is a bit mask represented by a @code{const_int}; a zero bit indicates the
+corresponding element in the result vector is taken from @var{vec2} while
+a set bit indicates it is taken from @var{vec1}.
+
+@findex vec_select
+@item (vec_select:@var{m} @var{vec1} @var{selection})
+This describes an operation that selects parts of a vector.  @var{vec1} is
+the source vector, @var{selection} is a @code{parallel} that contains a
+@code{const_int} for each of the subparts of the result vector, giving the
+number of the source subpart that should be stored into it.
+
+@findex vec_concat
+@item (vec_concat:@var{m} @var{vec1} @var{vec2})
+Describes a vector concat operation.  The result is a concatenation of the
+vectors @var{vec1} and @var{vec2}; its length is the sum of the lengths of
+the two inputs.
+
+@findex vec_const
+@item (vec_const:@var{m} @var{subparts})
+This describes a constant vector.  @var{subparts} is a @code{parallel} that
+contains a constant for each of the subparts of the vector.
+
+@findex vec_duplicate
+@item (vec_duplicate:@var{m} @var{vec})
+This operation converts a small vector into a larger one by duplicating the
+input values.  The output vector mode must have the same submodes as the
+input vector mode, and the number of output parts must be an integer multiple
+of the number of input parts.
+
+@end table
+
+@node Conversions
 @section Conversions
 @cindex conversions
 @cindex machine mode conversions
@@ -1652,6 +1868,20 @@ Represents the result of truncating the value @var{x}
 to machine mode @var{m}.  @var{m} must be a fixed-point mode
 and @var{x} a fixed-point value of a mode wider than @var{m}.
 
+@findex ss_truncate
+@item (ss_truncate:@var{m} @var{x})
+Represents the result of truncating the value @var{x}
+to machine mode @var{m}, using signed saturation in the case of
+overflow.  Both @var{m} and the mode of @var{x} must be fixed-point
+modes.
+
+@findex us_truncate
+@item (us_truncate:@var{m} @var{x})
+Represents the result of truncating the value @var{x}
+to machine mode @var{m}, using unsigned saturation in the case of
+overflow.  Both @var{m} and the mode of @var{x} must be fixed-point
+modes.
+
 @findex float_truncate
 @item (float_truncate:@var{m} @var{x})
 Represents the result of truncating the value @var{x}
@@ -1689,7 +1919,7 @@ integer, still represented in floating point mode @var{m}, by rounding
 towards zero.
 @end table
 
-@node RTL Declarations, Side Effects, Conversions, RTL
+@node RTL Declarations
 @section Declarations
 @cindex RTL declarations
 @cindex declarations, RTL
@@ -1712,7 +1942,7 @@ a subreg is allowed to have undefined effects on the rest of the
 register when @var{m} is less than a word.
 @end table
 
-@node Side Effects, Incdec, RTL Declarations, RTL
+@node Side Effects
 @section Side Effect Expressions
 @cindex RTL side effect expressions
 
@@ -1730,8 +1960,8 @@ the operands of these.
 @item (set @var{lval} @var{x})
 Represents the action of storing the value of @var{x} into the place
 represented by @var{lval}.  @var{lval} must be an expression
-representing a place that can be stored in: @code{reg} (or
-@code{subreg} or @code{strict_low_part}), @code{mem}, @code{pc} or
+representing a place that can be stored in: @code{reg} (or @code{subreg}
+or @code{strict_low_part}), @code{mem}, @code{pc}, @code{parallel}, or
 @code{cc0}.@refill
 
 If @var{lval} is a @code{reg}, @code{subreg} or @code{mem}, it has a
@@ -1757,6 +1987,14 @@ The latter case represents a ``test'' instruction.  The expression
 @code{(set (cc0) (compare (reg:@var{m} @var{n}) (const_int 0)))}.
 Use the former expression to save space during the compilation.
 
+If @var{lval} is a @code{parallel}, it is used to represent the case of
+a function returning a structure in multiple registers.  Each element
+of the @code{paralllel} is an @code{expr_list} whose first operand is a
+@code{reg} and whose second operand is a @code{const_int} representing the
+offset (in bytes) into the structure at which the data in that register
+corresponds.  The first element may be null to indicate that the structure
+is also passed partly in memory.
+
 @cindex jump instructions and @code{set}
 @cindex @code{if_then_else} usage
 If @var{lval} is @code{(pc)}, we have a jump instruction, and the
@@ -1813,7 +2051,7 @@ addressed.
 @item (clobber @var{x})
 Represents the storing or possible storing of an unpredictable,
 undescribed value into @var{x}, which must be a @code{reg},
-@code{scratch} or @code{mem} expression.
+@code{scratch}, @code{parallel} or @code{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
@@ -1822,7 +2060,8 @@ inform the compiler that the registers will be altered, lest it
 attempt to keep data in them across the string instruction.
 
 If @var{x} is @code{(mem:BLK (const_int 0))}, it means that all memory
-locations must be presumed clobbered.
+locations must be presumed clobbered.  If @var{x} is a @code{parallel},
+it has the same meaning as a @code{parallel} in a @code{set} expression.
 
 Note that the machine description classifies certain hard registers as
 ``call-clobbered''.  All function call instructions are assumed by
@@ -1873,6 +2112,38 @@ it may not be apparent why this is so.  Therefore, the compiler will
 not attempt to delete previous instructions whose only effect is to
 store a value in @var{x}.  @var{x} must be a @code{reg} expression.
 
+In some situations, it may be tempting to add a @code{use} of a
+register in a @code{parallel} to describe a situation where the value
+of a special register will modify the behaviour of the instruction.
+An hypothetical example might be a pattern for an addition that can
+either wrap around or use saturating addition depending on the value
+of a special control register:
+
+@example
+(parallel [(set (reg:SI 2) (unspec:SI [(reg:SI 3) (reg:SI 4)] 0))
+           (use (reg:SI 1))])
+@end example
+
+@noindent
+
+This will not work, several of the optimizers only look at expressions
+locally; it is very likely that if you have multiple insns with
+identical inputs to the @code{unspec}, they will be optimized away even
+if register 1 changes in between.
+
+This means that @code{use} can @emph{only} be used to describe
+that the register is live.  You should think twice before adding
+@code{use} statements, more often you will want to use @code{unspec}
+instead.  The @code{use} RTX is most commonly useful to describe that
+a fixed register is implicitly used in an insn.  It is also safe to use
+in patterns where the compiler knows for other reasons that the result
+of the whole pattern is variable, such as @samp{movstr@var{m}} or
+@samp{call} patterns.
+
+During the reload phase, an insn that has a @code{use} as pattern
+can carry a reg_equal note.  These @code{use} insns will be deleted
+before the reload phase exits.
+
 During the delayed branch scheduling phase, @var{x} may be an insn.
 This indicates that @var{x} previously was located at this place in the
 code and its data dependencies need to be taken into account.  These
@@ -1987,21 +2258,25 @@ how much space is given to each address; normally @var{m} would be
 @code{Pmode}.
 
 @findex addr_diff_vec
-@item (addr_diff_vec:@var{m} @var{base} [@var{lr0} @var{lr1} @dots{}])
+@item (addr_diff_vec:@var{m} @var{base} [@var{lr0} @var{lr1} @dots{}] @var{min} @var{max} @var{flags})
 Represents a table of jump addresses expressed as offsets from
 @var{base}.  The vector elements @var{lr0}, etc., are @code{label_ref}
 expressions and so is @var{base}.  The mode @var{m} specifies how much
-space is given to each address-difference.@refill
+space is given to each address-difference.  @var{min} and @var{max}
+are set up by branch shortening and hold a label with a minimum and a
+maximum address, respectively.  @var{flags} indicates the relative
+position of @var{base}, @var{min} and @var{max} to the containing insn
+and of @var{min} and @var{max} to @var{base}.  See rtl.def for details.@refill
 @end table
 
-@node Incdec, Assembler, Side Effects, RTL
+@node Incdec
 @section Embedded Side-Effects on Addresses
 @cindex RTL preincrement
 @cindex RTL postincrement
 @cindex RTL predecrement
 @cindex RTL postdecrement
 
-Four special side-effect expression codes appear as memory addresses.
+Six special side-effect expression codes appear as memory addresses.
 
 @table @code
 @findex pre_dec
@@ -2036,6 +2311,38 @@ being decremented.
 @findex post_inc
 @item (post_inc:@var{m} @var{x})
 Similar, but specifies incrementing @var{x} instead of decrementing it.
+
+@findex post_modify
+@item (post_modify:@var{m} @var{x} @var{y})
+
+Represents the side effect of setting @var{x} to @var{y} and
+represents @var{x} before @var{x} is modified.  @var{x} must be a
+@code{reg} or @code{mem}, but most machines allow only a @code{reg}.
+@var{m} must be the machine mode for pointers on the machine in use.
+The amount @var{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.  Note that this is not currently implemented.
+
+The expression @var{y} must be one of three forms:
+@table @code
+@code{(plus:@var{m} @var{x} @var{z})},
+@code{(minus:@var{m} @var{x} @var{z})}, or
+@code{(plus:@var{m} @var{x} @var{i})},
+@end table
+where @var{z} is an index register and @var{i} is a constant.
+
+Here is an example of its use:@refill
+
+@example
+(mem:SF (post_modify:SI (reg:SI 42) (plus (reg:SI 42) (reg:SI 48))))
+@end example
+
+This says to modify pseudo register 42 by adding the contents of pseudo
+register 48 to it, after the use of what ever 42 points to.
+
+@findex post_modify
+@item (pre_modify:@var{m} @var{x} @var{expr})
+Similar except side effects happen before the use.
 @end table
 
 These embedded side effect expressions must be used with care.  Instruction
@@ -2060,7 +2367,7 @@ 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.
 
-@node Assembler, Insns, Incdec, RTL
+@node Assembler
 @section Assembler Instructions as Expressions
 @cindex assembler instructions in RTL
 
@@ -2101,7 +2408,7 @@ 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, @dots{} for successive output operands.
 
-@node Insns, Calls, Assembler, RTL
+@node Insns
 @section Insns
 @cindex insns
 
@@ -2201,14 +2508,15 @@ recorded as a @code{jump_insn}.
 accessed in the same way and in addition contain a field
 @code{JUMP_LABEL} which is defined once jump optimization has completed.
 
-For simple conditional and unconditional jumps, this field contains the
-@code{code_label} to which this insn will (possibly conditionally)
+For simple conditional and unconditional jumps, this field contains
+the @code{code_label} to which this insn will (possibly conditionally)
 branch.  In a more complex jump, @code{JUMP_LABEL} records one of the
-labels that the insn refers to; the only way to find the others
-is to scan the entire body of the insn.
+labels that the insn refers to; the only way to find the others is to
+scan the entire body of the insn.  In an @code{addr_vec},
+@code{JUMP_LABEL} is @code{NULL_RTX}.
 
-Return insns count as jumps, but since they do not refer to any labels,
-they have zero in the @code{JUMP_LABEL} field.
+Return insns count as jumps, but since they do not refer to any
+labels, their @code{JUMP_LABEL} is @code{NULL_RTX}.
 
 @findex call_insn
 @item call_insn
@@ -2222,12 +2530,25 @@ unpredictably.
 accessed in the same way and in addition contain a field
 @code{CALL_INSN_FUNCTION_USAGE}, which contains a list (chain of
 @code{expr_list} expressions) containing @code{use} and @code{clobber}
-expressions that denote hard registers used or clobbered by the called
-function.  A register specified in a @code{clobber} in this list is
-modified @emph{after} the execution of the @code{call_insn}, while a
-register in a @code{clobber} in the body of the @code{call_insn} is
-clobbered before the insn completes execution.  @code{clobber}
-expressions in this list augment registers specified in
+expressions that denote hard registers and @code{MEM}s used or
+clobbered by the called function.
+
+A @code{MEM} generally points to a stack slots in which arguments passed
+to the libcall by reference (@pxref{Register Arguments,
+FUNCTION_ARG_PASS_BY_REFERENCE}) are stored.  If the argument is
+caller-copied (@pxref{Register Arguments, FUNCTION_ARG_CALLEE_COPIES}),
+the stack slot will be mentioned in @code{CLOBBER} and @code{USE}
+entries; if it's callee-copied, only a @code{USE} will appear, and the
+@code{MEM} may point to addresses that are not stack slots.  These
+@code{MEM}s are used only in libcalls, because, unlike regular function
+calls, @code{CONST_CALL}s (which libcalls generally are, @pxref{Flags,
+CONST_CALL_P}) aren't assumed to read and write all memory, so flow
+would consider the stores dead and remove them.  Note that, since a
+libcall must never return values in memory (@pxref{Aggregate Return,
+RETURN_IN_MEMORY}), there will never be a @code{CLOBBER} for a memory
+address holding a return value.
+
+@code{CLOBBER}ed registers in this list augment registers specified in
 @code{CALL_USED_REGISTERS} (@pxref{Register Basics}).
 
 @findex code_label
@@ -2251,6 +2572,11 @@ The field @code{LABEL_NUSES} is only defined once the jump optimization
 phase is completed and contains the number of times this label is
 referenced in the current function.
 
+@findex LABEL_ALTERNATE_NAME
+The field @code{LABEL_ALTERNATE_NAME} is used to associate a name with
+a @code{code_label}.  If this field is defined, the alternate name will
+be emitted instead of an internally generated label name.
+
 @findex barrier
 @item barrier
 Barriers are placed in the instruction stream when control cannot flow
@@ -2333,14 +2659,21 @@ Appears following each call to @code{setjmp} or a related function.
 These codes are printed symbolically when they appear in debugging dumps.
 @end table
 
+@cindex @code{TImode}, in @code{insn}
 @cindex @code{HImode}, in @code{insn}
 @cindex @code{QImode}, in @code{insn}
 The machine mode of an insn is normally @code{VOIDmode}, but some
-phases use the mode for various purposes; for example, the reload pass
-sets it to @code{HImode} if the insn needs reloading but not register
-elimination and @code{QImode} if both are required.  The common
-subexpression elimination pass sets the mode of an insn to @code{QImode}
-when it is the first insn in a block that has already been processed.
+phases use the mode for various purposes. 
+
+The common subexpression elimination pass sets the mode of an insn to
+@code{QImode} when it is the first insn in a block that has already
+been processed.
+
+The second Haifa scheduling pass, for targets that can multiple issue,
+sets the mode of an insn to @code{TImode} when it is believed that the
+instruction begins an issue group.  That is, when the instruction 
+cannot issue simultaneously with the previous.  This may be relied on
+by later passes, in particular machine-dependant reorg.
 
 Here is a table of the extra fields of @code{insn}, @code{jump_insn}
 and @code{call_insn} insns:
@@ -2480,8 +2813,10 @@ last insns, respectively.
 @findex REG_LABEL
 @item REG_LABEL
 This insn uses @var{op}, a @code{code_label}, but is not a
-@code{jump_insn}.  The presence of this note allows jump optimization to
-be aware that @var{op} is, in fact, being used.
+@code{jump_insn}, or it is a @code{jump_insn} that required the label to
+be held in a register.  The presence of this note allows jump
+optimization to be aware that @var{op} is, in fact, being used, and flow
+optimization to build an accurate flow graph.
 @end table
 
 The following notes describe attributes of outputs of an insn:
@@ -2590,11 +2925,17 @@ delete such sequences whose results are dead.
 A @code{REG_EQUAL} note will also usually be attached to this insn to 
 provide the expression being computed by the sequence.
 
+These notes will be deleted after reload, since they are no longer
+accurate or useful.
+
 @findex REG_LIBCALL
 @item REG_LIBCALL
 This is the inverse of @code{REG_RETVAL}: it is placed on the first
 insn of a multi-insn sequence, and it points to the last one.
 
+These notes are deleted after reload, since they are no longer useful or 
+accurate.
+
 @findex REG_CC_SETTER
 @findex REG_CC_USER
 @item REG_CC_SETTER
@@ -2645,8 +2986,14 @@ probability that the branch will be taken.
 @findex REG_BR_PRED
 @item REG_BR_PRED
 These notes are found in JUMP insns after delayed branch scheduling
-has taken place.  They indicate both the direction and the likelyhood
+has taken place.  They indicate both the direction and the likelihood
 of the JUMP.  The format is a bitmask of ATTR_FLAG_* values.
+
+@findex REG_FRAME_RELATED_EXPR
+@item REG_FRAME_RELATED_EXPR
+This is used on an RTX_FRAME_RELATED_P insn wherein the attached expression
+is used in place of the actual insn pattern.  This is done in cases where
+the pattern is either complex or misleading.
 @end table
 
 For convenience, the machine mode in an @code{insn_list} or
@@ -2660,7 +3007,7 @@ assumed to be an insn and is printed in debugging dumps as the insn's
 unique id; the first operand of an @code{expr_list} is printed in the
 ordinary way as an expression.
 
-@node Calls, Sharing, Insns, RTL
+@node Calls
 @section RTL Representation of Function-Call Insns
 @cindex calling functions in RTL
 @cindex RTL function-call insns
@@ -2758,9 +3105,7 @@ referring to it.
 
 @cindex @code{const_int}, RTL sharing
 @item
-There is only one @code{const_int} expression with value 0, only
-one with value 1, and only one with value @minus{}1.
-Some other integer values are also stored uniquely.
+All @code{const_int} expressions with equal values are shared.
 
 @cindex @code{pc}, RTL sharing
 @item