OSDN Git Service

* config/arm/arm.c (arm_init_libfuncs): Clear mod optabs.
[pf3gnuchains/gcc-fork.git] / gcc / doc / rtl.texi
index e243582..9858e47 100644 (file)
@@ -1,4 +1,5 @@
-@c Copyright (C) 1988, 1989, 1992, 1994, 1997, 1998, 1999, 2000, 2001
+@c Copyright (C) 1988, 1989, 1992, 1994, 1997, 1998, 1999, 2000, 2001, 2002,
+@c 2003, 2004, 2005
 @c Free Software Foundation, Inc.
 @c This is part of the GCC manual.
 @c For copying conditions, see the file gcc.texi.
@@ -23,6 +24,7 @@ form uses nested parentheses to indicate the pointers in the internal form.
 * RTL Objects::       Expressions vs vectors vs strings vs integers.
 * RTL Classes::       Categories of RTL expression objects, and their structure.
 * Accessors::         Macros to access expression operands or vector elts.
+* Special Accessors:: Macros to access specific annotations on RTL.
 * Flags::             Other flags in an RTL expression.
 * Machine Modes::     Describing the size and format of a datum.
 * Constants::         Expressions with constant values.
@@ -57,9 +59,9 @@ expression (``RTX'', for short) is a C structure, but it is usually
 referred to with a pointer; a type that is given the typedef name
 @code{rtx}.
 
-An integer is simply an @code{int}; their written form uses decimal digits.
-A wide integer is an integral object whose type is @code{HOST_WIDE_INT}
-(@pxref{Config}); their written form uses decimal digits.
+An integer is simply an @code{int}; their written form uses decimal
+digits.  A wide integer is an integral object whose type is
+@code{HOST_WIDE_INT}; their written form uses decimal digits.
 
 A string is a sequence of characters.  In core it is represented as a
 @code{char *} in usual C fashion, and it is written in C syntax as well.
@@ -70,6 +72,21 @@ pointers instead of strings are valid.  Within RTL code, strings are most
 commonly found inside @code{symbol_ref} expressions, but they appear in
 other contexts in the RTL expressions that make up machine descriptions.
 
+In a machine description, strings are normally written with double
+quotes, as you would in C@.  However, strings in machine descriptions may
+extend over many lines, which is invalid C, and adjacent string
+constants are not concatenated as they are in C@.  Any string constant
+may be surrounded with a single set of parentheses.  Sometimes this
+makes the machine description easier to read.
+
+There is also a special syntax for strings, which can be useful when C
+code is embedded in a machine description.  Wherever a string can
+appear, it is also valid to write a C-style brace block.  The entire
+brace block, including the outermost pair of braces, is considered to be
+the string constant.  Double quote characters inside the braces are not
+special.  Therefore, if you write string constants in the C code, you
+need not escape each quote character with a backslash.
+
 A vector contains an arbitrary number of pointers to expressions.  The
 number of elements in the vector is explicitly present in the vector.
 The written form of a vector consists of square brackets
@@ -83,7 +100,7 @@ null pointers are used instead.
 @findex PUT_CODE
 Expressions are classified by @dfn{expression codes} (also called RTX
 codes).  The expression code is a name defined in @file{rtl.def}, which is
-also (in upper case) a C enumeration constant.  The possible expression
+also (in uppercase) a C enumeration constant.  The possible expression
 codes and their meanings are machine-independent.  The code of an RTX can
 be extracted with the macro @code{GET_CODE (@var{x})} and altered with
 @code{PUT_CODE (@var{x}, @var{newcode})}.
@@ -102,8 +119,8 @@ Expressions are written as parentheses containing the name of the
 expression type, its flags and machine mode if any, and then the operands
 of the expression (separated by spaces).
 
-Expression code names in the @samp{md} file are written in lower case,
-but when they appear in C code they are written in upper case.  In this
+Expression code names in the @samp{md} file are written in lowercase,
+but when they appear in C code they are written in uppercase.  In this
 manual, they are shown as follows: @code{const_int}.
 
 @cindex (nil)
@@ -124,70 +141,95 @@ of an RTX code with the macro @code{GET_RTX_CLASS (@var{code})}.
 Currently, @file{rtx.def} defines these classes:
 
 @table @code
-@item o
+@item RTX_OBJ
 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}.
+@code{LO_SUM}) is also included; instead, @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 RTX_CONST_OBJ
+An RTX code that represents a constant object.  @code{HIGH} is also
+included in this class.
 
-@item 1
+@item RTX_COMPARE
+An RTX code for a non-symmetric comparison, such as @code{GEU} or
+@code{LT}.
+
+@item RTX_COMM_COMPARE
+An RTX code for a symmetric (commutative) comparison, such as @code{EQ}
+or @code{ORDERED}.
+
+@item RTX_UNARY
 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
+@item RTX_COMM_ARITH
 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
+@item RTX_BIN_ARITH
 An RTX code for a non-commutative binary operation, such as @code{MINUS},
 @code{DIV}, or @code{ASHIFTRT}.
 
-@item b
+@item RTX_BITFIELD_OPS
 An RTX code for a bit-field 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
+@item RTX_TERNARY
 An RTX code for other three input operations.  Currently only
-@code{IF_THEN_ELSE}.
+@code{IF_THEN_ELSE} and @code{VEC_MERGE}.
 
-@item i
+@item RTX_INSN
 An RTX code for an entire instruction:  @code{INSN}, @code{JUMP_INSN}, and
-@code{CALL_INSN}. @xref{Insns}.
+@code{CALL_INSN}.  @xref{Insns}.
 
-@item m
+@item RTX_MATCH
 An RTX code for something that matches in insns, such as
 @code{MATCH_DUP}.  These only occur in machine descriptions.
 
-@item a
+@item RTX_AUTOINC
 An RTX code for an auto-increment addressing mode, such as
 @code{POST_INC}.
 
-@item x
+@item RTX_EXTRA
 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}.
+@code{SUBREG} is also part of this class.
 @end table
 
 @cindex RTL format
-For each expression type @file{rtl.def} specifies the number of
-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}.  For example, the format of @code{subreg} is
-@samp{ei}.@refill
+For each expression code, @file{rtl.def} specifies the number of
+contained objects and their kinds using a sequence of characters
+called the @dfn{format} of the expression code.  For example,
+the format of @code{subreg} is @samp{ei}.
 
 @cindex RTL format characters
+These are the most commonly used format characters:
+
+@table @code
+@item e
+An expression (actually a pointer to an expression).
+
+@item i
+An integer.
+
+@item w
+A wide integer.
+
+@item s
+A string.
+
+@item E
+A vector of expressions.
+@end table
+
 A few other format characters are used occasionally:
 
 @table @code
@@ -212,6 +254,9 @@ core, @samp{V} is equivalent to @samp{E}, but when the object is read
 from an @samp{md} file, the vector value of this operand may be omitted.
 An omitted vector is effectively the same as a vector of no elements.
 
+@item B
+@samp{B} indicates a pointer to basic block structure.
+
 @item 0
 @samp{0} means a slot whose contents do not fit any normal category.
 @samp{0} slots are not printed at all in dumps, and are often used in
@@ -271,18 +316,18 @@ You can make no assumptions about the format of these codes.
 Operands of expressions are accessed using the macros @code{XEXP},
 @code{XINT}, @code{XWINT} and @code{XSTR}.  Each of these macros takes
 two arguments: an expression-pointer (RTX) and an operand number
-(counting from zero).  Thus,@refill
+(counting from zero).  Thus,
 
-@example
+@smallexample
 XEXP (@var{x}, 2)
-@end example
+@end smallexample
 
 @noindent
 accesses operand 2 of expression @var{x}, as an expression.
 
-@example
+@smallexample
 XINT (@var{x}, 2)
-@end example
+@end smallexample
 
 @noindent
 accesses the same operand as an integer.  @code{XSTR}, used in the same
@@ -304,7 +349,7 @@ compile without error, and would return the second, integer operand cast as
 an expression pointer, which would probably result in a crash when
 accessed.  Nothing stops you from writing @code{XEXP (@var{x}, 28)} either,
 but this will access memory past the end of the expression with
-unpredictable results.@refill
+unpredictable results.
 
 Access to operands which are vectors is more complicated.  You can use the
 macro @code{XVEC} to get the vector-pointer itself, or the macros
@@ -324,7 +369,7 @@ in operand number @var{idx} in @var{exp}.  This value is an @code{int}.
 @findex XVECEXP
 @item XVECEXP (@var{exp}, @var{idx}, @var{eltnum})
 Access element number @var{eltnum} in the vector which is
-in operand number @var{idx} in @var{exp}.  This value is an RTX.
+in operand number @var{idx} in @var{exp}.  This value is an RTX@.
 
 It is up to you to make sure that @var{eltnum} is not negative
 and is less than @code{XVECLEN (@var{exp}, @var{idx})}.
@@ -334,74 +379,271 @@ 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 Special Accessors
+@section Access to Special Operands
+@cindex access to special operands
+
+Some RTL nodes have special annotations associated with them.
+
+@table @code
+@item MEM
+@table @code
+@findex MEM_ALIAS_SET
+@item MEM_ALIAS_SET (@var{x})
+If 0, @var{x} is not in any alias set, and may alias anything.  Otherwise,
+@var{x} can only alias @code{MEM}s in a conflicting alias set.  This value
+is set in a language-dependent manner in the front-end, and should not be
+altered in the back-end.  In some front-ends, these numbers may correspond
+in some way to types, or other language-level entities, but they need not,
+and the back-end makes no such assumptions.
+These set numbers are tested with @code{alias_sets_conflict_p}.
+
+@findex MEM_EXPR
+@item MEM_EXPR (@var{x})
+If this register is known to hold the value of some user-level
+declaration, this is that tree node.  It may also be a
+@code{COMPONENT_REF}, in which case this is some field reference,
+and @code{TREE_OPERAND (@var{x}, 0)} contains the declaration,
+or another @code{COMPONENT_REF}, or null if there is no compile-time
+object associated with the reference.
+
+@findex MEM_OFFSET
+@item MEM_OFFSET (@var{x})
+The offset from the start of @code{MEM_EXPR} as a @code{CONST_INT} rtx.
+
+@findex MEM_SIZE
+@item MEM_SIZE (@var{x})
+The size in bytes of the memory reference as a @code{CONST_INT} rtx.
+This is mostly relevant for @code{BLKmode} references as otherwise
+the size is implied by the mode.
+
+@findex MEM_ALIGN
+@item MEM_ALIGN (@var{x})
+The known alignment in bits of the memory reference.
+@end table
+
+@item REG
+@table @code
+@findex ORIGINAL_REGNO
+@item ORIGINAL_REGNO (@var{x})
+This field holds the number the register ``originally'' had; for a
+pseudo register turned into a hard reg this will hold the old pseudo
+register number.
+
+@findex REG_EXPR
+@item REG_EXPR (@var{x})
+If this register is known to hold the value of some user-level
+declaration, this is that tree node.
+
+@findex REG_OFFSET
+@item REG_OFFSET (@var{x})
+If this register is known to hold the value of some user-level
+declaration, this is the offset into that logical storage.
+@end table
+
+@item SYMBOL_REF
+@table @code
+@findex SYMBOL_REF_DECL
+@item SYMBOL_REF_DECL (@var{x})
+If the @code{symbol_ref} @var{x} was created for a @code{VAR_DECL} or
+a @code{FUNCTION_DECL}, that tree is recorded here.  If this value is
+null, then @var{x} was created by back end code generation routines,
+and there is no associated front end symbol table entry.
+
+@code{SYMBOL_REF_DECL} may also point to a tree of class @code{'c'},
+that is, some sort of constant.  In this case, the @code{symbol_ref}
+is an entry in the per-file constant pool; again, there is no associated
+front end symbol table entry.
+
+@findex SYMBOL_REF_FLAGS
+@item SYMBOL_REF_FLAGS (@var{x})
+In a @code{symbol_ref}, this is used to communicate various predicates
+about the symbol.  Some of these are common enough to be computed by
+common code, some are specific to the target.  The common bits are:
+
+@table @code
+@findex SYMBOL_REF_FUNCTION_P
+@findex SYMBOL_FLAG_FUNCTION
+@item SYMBOL_FLAG_FUNCTION
+Set if the symbol refers to a function.
+
+@findex SYMBOL_REF_LOCAL_P
+@findex SYMBOL_FLAG_LOCAL
+@item SYMBOL_FLAG_LOCAL
+Set if the symbol is local to this ``module''.
+See @code{TARGET_BINDS_LOCAL_P}.
+
+@findex SYMBOL_REF_EXTERNAL_P
+@findex SYMBOL_FLAG_EXTERNAL
+@item SYMBOL_FLAG_EXTERNAL
+Set if this symbol is not defined in this translation unit.
+Note that this is not the inverse of @code{SYMBOL_FLAG_LOCAL}.
+
+@findex SYMBOL_REF_SMALL_P
+@findex SYMBOL_FLAG_SMALL
+@item SYMBOL_FLAG_SMALL
+Set if the symbol is located in the small data section.
+See @code{TARGET_IN_SMALL_DATA_P}.
+
+@findex SYMBOL_FLAG_TLS_SHIFT
+@findex SYMBOL_REF_TLS_MODEL
+@item SYMBOL_REF_TLS_MODEL (@var{x})
+This is a multi-bit field accessor that returns the @code{tls_model}
+to be used for a thread-local storage symbol.  It returns zero for
+non-thread-local symbols.
+@end table
+
+Bits beginning with @code{SYMBOL_FLAG_MACH_DEP} are available for
+the target's use.
+@end table
+@end table
+
 @node Flags
 @section Flags in an RTL Expression
 @cindex flags in RTL expression
 
-RTL expressions contain several flags (one-bit bit-fields) and other
-values that are used in certain types of expression.  Most often they
-are accessed with the following macros:
+RTL expressions contain several flags (one-bit bit-fields)
+that are used in certain types of expression.  Most often they
+are accessed with the following macros, which expand into lvalues.
 
 @table @code
-@findex MEM_VOLATILE_P
-@cindex @code{mem} and @samp{/v}
-@cindex @code{volatil}, in @code{mem}
-@cindex @samp{/v} in RTL dump
-@item MEM_VOLATILE_P (@var{x})
-In @code{mem} expressions, nonzero for volatile memory references.
+@findex CONSTANT_POOL_ADDRESS_P
+@cindex @code{symbol_ref} and @samp{/u}
+@cindex @code{unchanging}, in @code{symbol_ref}
+@item CONSTANT_POOL_ADDRESS_P (@var{x})
+Nonzero in a @code{symbol_ref} if it refers to part of the current
+function's constant pool.  For most targets these addresses are in a
+@code{.rodata} section entirely separate from the function, but for
+some targets the addresses are close to the beginning of the function.
+In either case GCC assumes these addresses can be addressed directly,
+perhaps with the help of base registers.
+Stored in the @code{unchanging} field and printed as @samp{/u}.
+
+@findex CONST_OR_PURE_CALL_P
+@cindex @code{call_insn} and @samp{/u}
+@cindex @code{unchanging}, in @code{call_insn}
+@item CONST_OR_PURE_CALL_P (@var{x})
+In a @code{call_insn}, @code{note}, or an @code{expr_list} for notes,
+indicates that the insn represents a call to a const or pure function.
+Stored in the @code{unchanging} field and printed as @samp{/u}.
+
+@findex INSN_ANNULLED_BRANCH_P
+@cindex @code{jump_insn} and @samp{/u}
+@cindex @code{call_insn} and @samp{/u}
+@cindex @code{insn} and @samp{/u}
+@cindex @code{unchanging}, in @code{jump_insn}, @code{call_insn} and @code{insn}
+@item INSN_ANNULLED_BRANCH_P (@var{x})
+In a @code{jump_insn}, @code{call_insn}, or @code{insn} indicates
+that the branch is an annulling one.  See the discussion under
+@code{sequence} below.  Stored in the @code{unchanging} field and
+printed as @samp{/u}.
+
+@findex INSN_DELETED_P
+@cindex @code{insn} and @samp{/v}
+@cindex @code{call_insn} and @samp{/v}
+@cindex @code{jump_insn} and @samp{/v}
+@cindex @code{code_label} and @samp{/v}
+@cindex @code{barrier} and @samp{/v}
+@cindex @code{note} and @samp{/v}
+@cindex @code{volatil}, in @code{insn}, @code{call_insn}, @code{jump_insn}, @code{code_label}, @code{barrier}, and @code{note}
+@item INSN_DELETED_P (@var{x})
+In an @code{insn}, @code{call_insn}, @code{jump_insn}, @code{code_label},
+@code{barrier}, or @code{note},
+nonzero if the insn has been deleted.  Stored in the
+@code{volatil} field and printed as @samp{/v}.
+
+@findex INSN_FROM_TARGET_P
+@cindex @code{insn} and @samp{/s}
+@cindex @code{jump_insn} and @samp{/s}
+@cindex @code{call_insn} and @samp{/s}
+@cindex @code{in_struct}, in @code{insn} and @code{jump_insn} and @code{call_insn}
+@item INSN_FROM_TARGET_P (@var{x})
+In an @code{insn} or @code{jump_insn} or @code{call_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 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 LABEL_OUTSIDE_LOOP_P
+@cindex @code{label_ref} and @samp{/s}
+@cindex @code{in_struct}, in @code{label_ref}
+@item LABEL_OUTSIDE_LOOP_P (@var{x})
+In @code{label_ref} expressions, nonzero if this is a reference to a
+label that is outside the innermost loop containing the reference to the
+label.  Stored in the @code{in_struct} field and printed as @samp{/s}.
+
+@findex LABEL_PRESERVE_P
+@cindex @code{code_label} and @samp{/i}
+@cindex @code{note} and @samp{/i}
+@cindex @code{in_struct}, in @code{code_label} and @code{note}
+@item LABEL_PRESERVE_P (@var{x})
+In a @code{code_label} or @code{note}, indicates that the label is referenced by
+code or data not visible to the RTL of a given function.
+Labels referenced by a non-local goto will have this bit set.  Stored
+in the @code{in_struct} field and printed as @samp{/s}.
+
+@findex LABEL_REF_NONLOCAL_P
+@cindex @code{label_ref} and @samp{/v}
+@cindex @code{reg_label} and @samp{/v}
+@cindex @code{volatil}, in @code{label_ref} and @code{reg_label}
+@item LABEL_REF_NONLOCAL_P (@var{x})
+In @code{label_ref} and @code{reg_label} expressions, nonzero if this is
+a reference to a non-local label.
 Stored in the @code{volatil} field and printed as @samp{/v}.
 
 @findex MEM_IN_STRUCT_P
 @cindex @code{mem} and @samp{/s}
 @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}.  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.
+scalar variable or through a pointer to a scalar.  If both this flag and
+@code{MEM_SCALAR_P} are clear, then we don't know whether this @code{mem}
+is in a structure or not.  Both flags should never be simultaneously set.
+Stored in the @code{in_struct} field and printed as @samp{/s}.
+
+@findex MEM_KEEP_ALIAS_SET_P
+@cindex @code{mem} and @samp{/j}
+@cindex @code{jump}, in @code{mem}
+@item MEM_KEEP_ALIAS_SET_P (@var{x})
+In @code{mem} expressions, 1 if we should keep the alias set for this
+mem unchanged when we access a component.  Set to 1, for example, when we
+are already in a non-addressable component of an aggregate.
+Stored in the @code{jump} field and printed as @samp{/j}.
 
 @findex MEM_SCALAR_P
 @cindex @code{mem} and @samp{/f}
-@cindex @code{frame_related}, in@code{mem}
-@cindex @samp{/f} in RTL dump
+@cindex @code{frame_related}, in @code{mem}
 @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.
+to scalar types.  If both this flag and @code{MEM_IN_STRUCT_P} are clear,
+then we don't know whether this @code{mem} is in a structure or not.
+Both flags should never be simultaneously set.
+Stored in the @code{frame_related} field and printed as @samp{/f}.
 
-@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}
-@cindex @code{in_struct}, in @code{reg}
-@item REG_LOOP_TEST_P
-In @code{reg} expressions, nonzero if this register's entire life is
-contained in the exit test code for some loop.  Stored in the
-@code{in_struct} field and printed as @samp{/s}.
+@findex MEM_VOLATILE_P
+@cindex @code{mem} and @samp{/v}
+@cindex @code{asm_input} and @samp{/v}
+@cindex @code{asm_operands} and @samp{/v}
+@cindex @code{volatil}, in @code{mem}, @code{asm_operands}, and @code{asm_input}
+@item MEM_VOLATILE_P (@var{x})
+In @code{mem}, @code{asm_operands}, and @code{asm_input} expressions,
+nonzero for volatile memory references.
+Stored in the @code{volatil} field and printed as @samp{/v}.
 
-@findex REG_USERVAR_P
-@cindex @code{reg} and @samp{/v}
-@cindex @code{volatil}, in @code{reg}
-@item REG_USERVAR_P (@var{x})
-In a @code{reg}, nonzero if it corresponds to a variable present in
-the user's source code.  Zero for temporaries generated internally by
-the compiler.  Stored in the @code{volatil} field and printed as
-@samp{/v}.
+@findex MEM_NOTRAP_P
+@cindex @code{mem} and @samp{/c}
+@cindex @code{call}, in @code{mem}
+@item MEM_NOTRAP_P (@var{x})
+In @code{mem}, nonzero for memory references that will not trap.
+Stored in the @code{call} field and printed as @samp{/c}.
 
-@cindex @samp{/i} in RTL dump
 @findex REG_FUNCTION_VALUE_P
 @cindex @code{reg} and @samp{/i}
 @cindex @code{integrated}, in @code{reg}
@@ -411,57 +653,40 @@ value is going to be returned.  (This happens only in a hard
 register.)  Stored in the @code{integrated} field and printed as
 @samp{/i}.
 
+@findex REG_POINTER
+@cindex @code{reg} and @samp{/f}
+@cindex @code{frame_related}, in @code{reg}
+@item REG_POINTER (@var{x})
+Nonzero in a @code{reg} if the register holds a pointer.  Stored in the
+@code{frame_related} field and printed as @samp{/f}.
+
+@findex REG_USERVAR_P
+@cindex @code{reg} and @samp{/v}
+@cindex @code{volatil}, in @code{reg}
+@item REG_USERVAR_P (@var{x})
+In a @code{reg}, nonzero if it corresponds to a variable present in
+the user's source code.  Zero for temporaries generated internally by
+the compiler.  Stored in the @code{volatil} field and printed as
+@samp{/v}.
+
 The same hard register may be used also for collecting the values of
 functions called by this one, but @code{REG_FUNCTION_VALUE_P} is zero
 in this kind of use.
 
-@findex SUBREG_PROMOTED_VAR_P
-@cindex @code{subreg} and @samp{/s}
-@cindex @code{in_struct}, in @code{subreg}
-@item SUBREG_PROMOTED_VAR_P
-Nonzero in a @code{subreg} if it was made when accessing an object that
-was promoted to a wider mode in accord with the @code{PROMOTED_MODE} machine
-description macro (@pxref{Storage Layout}).  In this case, the mode of
-the @code{subreg} is the declared mode of the object and the mode of
-@code{SUBREG_REG} is the mode of the register that holds the object.
-Promoted variables are always either sign- or zero-extended to the wider
-mode on every assignment.  Stored in the @code{in_struct} field and
-printed as @samp{/s}.
-
-@findex SUBREG_PROMOTED_UNSIGNED_P
-@cindex @code{subreg} and @samp{/u}
-@cindex @code{unchanging}, in @code{subreg}
-@item SUBREG_PROMOTED_UNSIGNED_P
-Nonzero in a @code{subreg} that has @code{SUBREG_PROMOTED_VAR_P} nonzero
-if the object being referenced is kept zero-extended and zero if it
-is kept sign-extended.  Stored in the @code{unchanging} field and
-printed as @samp{/u}.
-
-@findex RTX_UNCHANGING_P
-@cindex @code{reg} and @samp{/u}
-@cindex @code{mem} and @samp{/u}
-@cindex @code{unchanging}, in @code{reg} and @code{mem}
-@cindex @samp{/u} in RTL dump
-@item RTX_UNCHANGING_P (@var{x})
-Nonzero in a @code{reg} or @code{mem} if the value is not changed.
-(This flag is not set for memory references via pointers to constants.
-Such pointers only guarantee that the object will not be changed
-explicitly by the current function.  The object might be changed by
-other functions or by aliasing.)  Stored in the
-@code{unchanging} field and printed as @samp{/u}.
-
-@findex RTX_INTEGRATED_P
-@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}.
-
 @findex RTX_FRAME_RELATED_P
+@cindex @code{insn} and @samp{/f}
+@cindex @code{call_insn} and @samp{/f}
+@cindex @code{jump_insn} and @samp{/f}
+@cindex @code{barrier} and @samp{/f}
+@cindex @code{set} and @samp{/f}
+@cindex @code{frame_related}, in @code{insn}, @code{call_insn}, @code{jump_insn}, @code{barrier}, and @code{set}
 @item RTX_FRAME_RELATED_P (@var{x})
-Nonzero in an insn or expression which is part of a function prologue
+Nonzero in an @code{insn}, @code{call_insn}, @code{jump_insn},
+@code{barrier}, or @code{set} 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.
+Stored in the @code{frame_related} field and printed as @samp{/f}.
 
 In particular, on RISC targets where there are limits on the sizes of
 immediate constants, it is sometimes impossible to reach the register
@@ -482,6 +707,108 @@ computation performed by this instruction, i.e., one that
 This flag is required for exception handling support on targets with RTL
 prologues.
 
+@cindex @code{insn} and @samp{/i}
+@cindex @code{call_insn} and @samp{/i}
+@cindex @code{jump_insn} and @samp{/i}
+@cindex @code{barrier} and @samp{/i}
+@cindex @code{code_label} and @samp{/i}
+@cindex @code{insn_list} and @samp{/i}
+@cindex @code{const} and @samp{/i}
+@cindex @code{note} and @samp{/i}
+@cindex @code{integrated}, in @code{insn}, @code{call_insn}, @code{jump_insn}, @code{barrier}, @code{code_label}, @code{insn_list}, @code{const}, and @code{note}
+@code{code_label}, @code{insn_list}, @code{const}, or @code{note} if it
+resulted from an in-line function call.
+Stored in the @code{integrated} field and printed as @samp{/i}.
+
+@findex MEM_READONLY_P
+@cindex @code{mem} and @samp{/u}
+@cindex @code{unchanging}, in @code{mem}
+@item MEM_READONLY_P (@var{x})
+Nonzero in a @code{mem}, if the memory is statically allocated and read-only.
+
+Read-only in this context means never modified during the lifetime of the
+program, not necessarily in ROM or in write-disabled pages.  A common
+example of the later is a shared library's global offset table.  This
+table is initialized by the runtime loader, so the memory is technically
+writable, but after control is transfered from the runtime loader to the
+application, this memory will never be subsequently modified.
+
+Stored in the @code{unchanging} field and printed as @samp{/u}.
+
+@findex SCHED_GROUP_P
+@cindex @code{insn} and @samp{/s}
+@cindex @code{call_insn} and @samp{/s}
+@cindex @code{jump_insn} and @samp{/s}
+@cindex @code{in_struct}, in @code{insn}, @code{jump_insn} and @code{call_insn}
+@item SCHED_GROUP_P (@var{x})
+During instruction scheduling, in an @code{insn}, @code{call_insn} or
+@code{jump_insn}, indicates that the
+previous insn must be scheduled together with this insn.  This is used to
+ensure that certain groups of instructions will not be split up by the
+instruction scheduling pass, for example, @code{use} insns before
+a @code{call_insn} may not be separated from the @code{call_insn}.
+Stored in the @code{in_struct} field and printed as @samp{/s}.
+
+@findex SET_IS_RETURN_P
+@cindex @code{insn} and @samp{/j}
+@cindex @code{jump}, in @code{insn}
+@item SET_IS_RETURN_P (@var{x})
+For a @code{set}, nonzero if it is for a return.
+Stored in the @code{jump} field and printed as @samp{/j}.
+
+@findex SIBLING_CALL_P
+@cindex @code{call_insn} and @samp{/j}
+@cindex @code{jump}, in @code{call_insn}
+@item SIBLING_CALL_P (@var{x})
+For a @code{call_insn}, nonzero if the insn is a sibling call.
+Stored in the @code{jump} field and printed as @samp{/j}.
+
+@findex STRING_POOL_ADDRESS_P
+@cindex @code{symbol_ref} and @samp{/f}
+@cindex @code{frame_related}, in @code{symbol_ref}
+@item STRING_POOL_ADDRESS_P (@var{x})
+For a @code{symbol_ref} expression, nonzero if it addresses this function's
+string constant pool.
+Stored in the @code{frame_related} field and printed as @samp{/f}.
+
+@findex SUBREG_PROMOTED_UNSIGNED_P
+@cindex @code{subreg} and @samp{/u} and @samp{/v}
+@cindex @code{unchanging}, in @code{subreg}
+@cindex @code{volatil}, in @code{subreg}
+@item SUBREG_PROMOTED_UNSIGNED_P (@var{x})
+Returns a value greater then zero for a @code{subreg} that has
+@code{SUBREG_PROMOTED_VAR_P} nonzero if the object being referenced is kept
+zero-extended, zero if it is kept sign-extended, and less then zero if it is
+extended some other way via the @code{ptr_extend} instruction.
+Stored in the @code{unchanging}
+field and @code{volatil} field, printed as @samp{/u} and @samp{/v}.
+This macro may only be used to get the value it may not be used to change
+the value.  Use @code{SUBREG_PROMOTED_UNSIGNED_SET} to change the value.
+
+@findex SUBREG_PROMOTED_UNSIGNED_SET
+@cindex @code{subreg} and @samp{/u}
+@cindex @code{unchanging}, in @code{subreg}
+@cindex @code{volatil}, in @code{subreg}
+@item SUBREG_PROMOTED_UNSIGNED_SET (@var{x})
+Set the @code{unchanging} and @code{volatil} fields in a @code{subreg}
+to reflect zero, sign, or other extension.  If @code{volatil} is
+zero, then @code{unchanging} as nonzero means zero extension and as
+zero means sign extension.  If @code{volatil} is nonzero then some
+other type of extension was done via the @code{ptr_extend} instruction.
+
+@findex SUBREG_PROMOTED_VAR_P
+@cindex @code{subreg} and @samp{/s}
+@cindex @code{in_struct}, in @code{subreg}
+@item SUBREG_PROMOTED_VAR_P (@var{x})
+Nonzero in a @code{subreg} if it was made when accessing an object that
+was promoted to a wider mode in accord with the @code{PROMOTED_MODE} machine
+description macro (@pxref{Storage Layout}).  In this case, the mode of
+the @code{subreg} is the declared mode of the object and the mode of
+@code{SUBREG_REG} is the mode of the register that holds the object.
+Promoted variables are always either sign- or zero-extended to the wider
+mode on every assignment.  Stored in the @code{in_struct} field and
+printed as @samp{/s}.
+
 @findex SYMBOL_REF_USED
 @cindex @code{used}, in @code{symbol_ref}
 @item SYMBOL_REF_USED (@var{x})
@@ -489,13 +816,6 @@ In a @code{symbol_ref}, indicates that @var{x} has been used.  This is
 normally only used to ensure that @var{x} is only declared external
 once.  Stored in the @code{used} field.
 
-@findex SYMBOL_REF_FLAG
-@cindex @code{symbol_ref} and @samp{/v}
-@cindex @code{volatil}, in @code{symbol_ref}
-@item SYMBOL_REF_FLAG (@var{x})
-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}
@@ -503,115 +823,47 @@ Stored in the @code{volatil} field and printed as @samp{/v}.
 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}
-@item LABEL_OUTSIDE_LOOP_P
-In @code{label_ref} expressions, nonzero if this is a reference to a
-label that is outside the innermost loop containing the reference to the
-label.  Stored in the @code{in_struct} field and printed as @samp{/s}.
-
-@findex INSN_DELETED_P
-@cindex @code{volatil}, in @code{insn}
-@item INSN_DELETED_P (@var{insn})
-In an insn, nonzero if the insn has been deleted.  Stored in the
-@code{volatil} field and printed as @samp{/v}.
-
-@findex INSN_ANNULLED_BRANCH_P
-@cindex @code{insn} and @samp{/u}
-@cindex @code{unchanging}, in @code{insn}
-@item INSN_ANNULLED_BRANCH_P (@var{insn})
-In an @code{insn} in the delay slot of a branch insn, indicates that an
-annulling branch should be used.  See the discussion under
-@code{sequence} below.  Stored in the @code{unchanging} field and printed
-as @samp{/u}.
-
-@findex INSN_FROM_TARGET_P
-@cindex @code{insn} and @samp{/s}
-@cindex @code{in_struct}, in @code{insn}
-@cindex @samp{/s} in RTL dump
-@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 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}
-@cindex @code{unchanging}, in @code{symbol_ref}
-@item CONSTANT_POOL_ADDRESS_P (@var{x})
-Nonzero in a @code{symbol_ref} if it refers to part of the current
-function's ``constants pool''.  These are addresses close to the
-beginning of the function, and GNU CC assumes they can be addressed
-directly (perhaps with the help of base registers).  Stored in the
-@code{unchanging} field and printed as @samp{/u}.
-
-@findex CONST_CALL_P
-@cindex @code{call_insn} and @samp{/u}
-@cindex @code{unchanging}, in @code{call_insn}
-@item CONST_CALL_P (@var{x})
-In a @code{call_insn}, indicates that the insn represents a call to a const
-function.  Stored in the @code{unchanging} field and printed as @samp{/u}.
-
-@findex LABEL_PRESERVE_P
-@cindex @code{code_label} and @samp{/i}
-@cindex @code{in_struct}, in @code{code_label}
-@item LABEL_PRESERVE_P (@var{x})
-In a @code{code_label}, indicates that the label can never be deleted.
-Labels referenced by a non-local goto will have this bit set.  Stored
-in the @code{in_struct} field and printed as @samp{/s}.
+@findex SYMBOL_REF_FLAG
+@cindex @code{symbol_ref} and @samp{/v}
+@cindex @code{volatil}, in @code{symbol_ref}
+@item SYMBOL_REF_FLAG (@var{x})
+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 SCHED_GROUP_P
-@cindex @code{insn} and @samp{/i}
-@cindex @code{in_struct}, in @code{insn}
-@item SCHED_GROUP_P (@var{insn})
-During instruction scheduling, in an insn, indicates that the previous insn
-must be scheduled together with this insn.  This is used to ensure that
-certain groups of instructions will not be split up by the instruction
-scheduling pass, for example, @code{use} insns before a @code{call_insn} may
-not be separated from the @code{call_insn}.  Stored in the @code{in_struct}
-field and printed as @samp{/s}.
+Most uses of @code{SYMBOL_REF_FLAG} are historic and may be subsumed
+by @code{SYMBOL_REF_FLAGS}.  Certainly use of @code{SYMBOL_REF_FLAGS}
+is mandatory if the target requires more than one bit of storage.
 @end table
 
-These are the fields which the above macros refer to:
+These are the fields to which the above macros refer:
 
 @table @code
-@findex used
-@item used
-Normally, this flag is used only momentarily, at the end of RTL
-generation for a function, to count the number of times an expression
-appears in insns.  Expressions that appear more than once are copied,
-according to the rules for shared structure (@pxref{Sharing}).
-
-In a @code{symbol_ref}, it indicates that an external declaration for
-the symbol has already been written.
+@findex call
+@cindex @samp{/c} in RTL dump
+@item call
+In a @code{mem}, 1 means that the memory reference will not trap.
 
-In a @code{reg}, it is used by the leaf register renumbering code to ensure
-that each register is only renumbered once.
+In an RTL dump, this flag is represented as @samp{/c}.
 
-@findex volatil
-@item volatil
-This flag is used in @code{mem}, @code{symbol_ref} and @code{reg}
-expressions and in insns.  In RTL dump files, it is printed as
-@samp{/v}.
+@findex frame_related
+@cindex @samp{/f} in RTL dump
+@item frame_related
+In an @code{insn} or @code{set} expression, 1 means that it is part of
+a function prologue and sets the stack pointer, sets the frame pointer,
+saves a register, or sets up a temporary register to use in place of the
+frame pointer.
 
-@cindex volatile memory references
-In a @code{mem} expression, it is 1 if the memory reference is volatile.
-Volatile memory references may not be deleted, reordered or combined.
+In @code{reg} expressions, 1 means that the register holds a pointer.
 
-In a @code{symbol_ref} expression, it is used for machine-specific
-purposes.
+In @code{symbol_ref} expressions, 1 means that the reference addresses
+this function's string constant pool.
 
-In a @code{reg} expression, it is 1 if the value is a user-level variable.
-0 indicates an internal compiler temporary.
+In @code{mem} expressions, 1 means that the reference is to a scalar.
 
-In an insn, 1 means the insn has been deleted.
+In an RTL dump, this flag is represented as @samp{/f}.
 
 @findex in_struct
+@cindex @samp{/s} in RTL dump
 @item in_struct
 In @code{mem} expressions, it is 1 if the memory datum referred to is
 all or part of a structure or array; 0 if it is (or might be) a scalar
@@ -619,12 +871,6 @@ variable.  A reference through a C pointer has 0 because the pointer
 might point to a scalar variable.  This information allows the compiler
 to determine something about possible cases of aliasing.
 
-In an insn in the delay slot of a branch, 1 means that this insn is from
-the target of the branch.
-
-During instruction scheduling, in an insn, 1 means that this insn must be
-scheduled as part of a group together with the previous insn.
-
 In @code{reg} expressions, it is 1 if the register has its entire life
 contained within the test expression of some loop.
 
@@ -636,11 +882,52 @@ outside the innermost loop containing the insn in which the @code{label_ref}
 was found.
 
 In @code{code_label} expressions, it is 1 if the label may never be deleted.
-This is used for labels which are the target of non-local gotos.
+This is used for labels which are the target of non-local gotos.  Such a
+label that would have been deleted is replaced with a @code{note} of type
+@code{NOTE_INSN_DELETED_LABEL}.
+
+In an @code{insn} during dead-code elimination, 1 means that the insn is
+dead code.
+
+In an @code{insn} or @code{jump_insn} during reorg for an insn in the
+delay slot of a branch,
+1 means that this insn is from the target of the branch.
+
+In an @code{insn} during instruction scheduling, 1 means that this insn
+must be scheduled as part of a group together with the previous insn.
 
 In an RTL dump, this flag is represented as @samp{/s}.
 
+@findex integrated
+@cindex @samp{/i} in RTL dump
+@item integrated
+In an @code{insn}, @code{insn_list}, or @code{const}, 1 means the RTL was
+produced by procedure integration.
+
+In @code{reg} expressions, 1 means the register contains
+the value to be returned by the current function.  On
+machines that pass parameters in registers, the same register number
+may be used for parameters as well, but this flag is not set on such
+uses.
+
+In @code{symbol_ref} expressions, 1 means the referenced symbol is weak.
+
+In an RTL dump, this flag is represented as @samp{/i}.
+
+@findex jump
+@cindex @samp{/j} in RTL dump
+@item jump
+In a @code{mem} expression, 1 means we should keep the alias set for this
+mem unchanged when we access a component.
+
+In a @code{set}, 1 means it is for a return.
+
+In a @code{call_insn}, 1 means it is a sibling call.
+
+In an RTL dump, this flag is represented as @samp{/j}.
+
 @findex unchanging
+@cindex @samp{/u} in RTL dump
 @item unchanging
 In @code{reg} and @code{mem} expressions, 1 means
 that the value of the expression never changes.
@@ -648,26 +935,52 @@ that the value of the expression never changes.
 In @code{subreg} expressions, it is 1 if the @code{subreg} references an
 unsigned object whose mode has been promoted to a wider mode.
 
-In an insn, 1 means that this is an annulling branch.
+In an @code{insn} or @code{jump_insn} in the delay slot of a branch
+instruction, 1 means an annulling branch should be used.
 
 In a @code{symbol_ref} expression, 1 means that this symbol addresses
-something in the per-function constants pool.
+something in the per-function constant pool.
 
-In a @code{call_insn}, 1 means that this instruction is a call to a
-const function.
+In a @code{call_insn}, @code{note}, or an @code{expr_list} of notes,
+1 means that this instruction is a call to a const or pure function.
 
 In an RTL dump, this flag is represented as @samp{/u}.
 
-@findex integrated
-@item integrated
-In some kinds of expressions, including insns, this flag means the
-rtl was produced by procedure integration.
+@findex used
+@item used
+This flag is used directly (without an access macro) at the end of RTL
+generation for a function, to count the number of times an expression
+appears in insns.  Expressions that appear more than once are copied,
+according to the rules for shared structure (@pxref{Sharing}).
 
-In a @code{reg} expression, this flag indicates the register
-containing the value to be returned by the current function.  On
-machines that pass parameters in registers, the same register number
-may be used for parameters as well, but this flag is not set on such
-uses.
+For a @code{reg}, it is used directly (without an access macro) by the
+leaf register renumbering code to ensure that each register is only
+renumbered once.
+
+In a @code{symbol_ref}, it indicates that an external declaration for
+the symbol has already been written.
+
+@findex volatil
+@cindex @samp{/v} in RTL dump
+@item volatil
+@cindex volatile memory references
+In a @code{mem}, @code{asm_operands}, or @code{asm_input}
+expression, it is 1 if the memory
+reference is volatile.  Volatile memory references may not be deleted,
+reordered or combined.
+
+In a @code{symbol_ref} expression, it is used for machine-specific
+purposes.
+
+In a @code{reg} expression, it is 1 if the value is a user-level variable.
+0 indicates an internal compiler temporary.
+
+In an @code{insn}, 1 means the insn has been deleted.
+
+In @code{label_ref} and @code{reg_label} expressions, 1 means a reference
+to a non-local label.
+
+In an RTL dump, this flag is represented as @samp{/v}.
 @end table
 
 @node Machine Modes
@@ -732,27 +1045,47 @@ this is the right mode to use for certain pointers.
 @item OImode
 ``Octa Integer'' (?) mode represents a thirty-two-byte integer.
 
+@findex QFmode
+@item QFmode
+``Quarter-Floating'' mode represents a quarter-precision (single byte)
+floating point number.
+
+@findex HFmode
+@item HFmode
+``Half-Floating'' mode represents a half-precision (two byte) floating
+point number.
+
+@findex TQFmode
+@item TQFmode
+``Three-Quarter-Floating'' (?) mode represents a three-quarter-precision
+(three byte) floating point number.
+
 @findex SFmode
 @item SFmode
-``Single Floating'' mode represents a single-precision (four byte) floating
-point number.
+``Single Floating'' mode represents a four byte floating point number.
+In the common case, of a processor with IEEE arithmetic and 8-bit bytes,
+this is a single-precision IEEE floating point number; it can also be
+used for double-precision (on processors with 16-bit bytes) and
+single-precision VAX and IBM types.
 
 @findex DFmode
 @item DFmode
-``Double Floating'' mode represents a double-precision (eight byte) floating
-point number.
+``Double Floating'' mode represents an eight byte floating point number.
+In the common case, of a processor with IEEE arithmetic and 8-bit bytes,
+this is a double-precision IEEE floating point number.
 
 @findex XFmode
 @item XFmode
-``Extended Floating'' mode represents a triple-precision (twelve byte)
-floating point number.  This mode is used for IEEE extended floating
-point.  On some systems not all bits within these bytes will actually
-be used.
+``Extended Floating'' mode represents an IEEE extended floating point
+number.  This mode only has 80 meaningful bits (ten bytes).  Some
+processors require such numbers to be padded to twelve bytes, others
+to sixteen; this mode is used for either.
 
 @findex TFmode
 @item TFmode
-``Tetra Floating'' mode represents a quadruple-precision (sixteen byte)
-floating point number.
+``Tetra Floating'' mode represents a sixteen byte floating point number
+all 128 of whose bits are meaningful.  One common use is the
+IEEE quad-precision format.
 
 @findex CCmode
 @item CCmode
@@ -767,7 +1100,7 @@ the condition code.  These modes are not used on machines that use
 ``Block'' mode represents values that are aggregates to which none of
 the other modes apply.  In RTL, only memory references can have this mode,
 and only if they appear in string-move or vector instructions.  On machines
-which have no such instructions, @code{BLKmode} will not appear in RTL.
+which have no such instructions, @code{BLKmode} will not appear in RTL@.
 
 @findex VOIDmode
 @item VOIDmode
@@ -777,14 +1110,17 @@ For example, RTL expressions of code @code{const_int} have mode
 requires.  In debugging dumps of RTL, @code{VOIDmode} is expressed by
 the absence of any mode.
 
+@findex QCmode
+@findex HCmode
 @findex SCmode
 @findex DCmode
 @findex XCmode
 @findex TCmode
-@item SCmode, DCmode, XCmode, TCmode
+@item QCmode, HCmode, SCmode, DCmode, XCmode, TCmode
 These modes stand for a complex number represented as a pair of floating
-point values.  The floating point values are in @code{SFmode},
-@code{DFmode}, @code{XFmode}, and @code{TFmode}, respectively.
+point values.  The floating point values are in @code{QFmode},
+@code{HFmode}, @code{SFmode}, @code{DFmode}, @code{XFmode}, and
+@code{TFmode}, respectively.
 
 @findex CQImode
 @findex CHImode
@@ -822,16 +1158,19 @@ mode classes are:
 @table @code
 @findex MODE_INT
 @item MODE_INT
-Integer modes.  By default these are @code{QImode}, @code{HImode},
-@code{SImode}, @code{DImode}, and @code{TImode}.
+Integer modes.  By default these are @code{BImode}, @code{QImode},
+@code{HImode}, @code{SImode}, @code{DImode}, @code{TImode}, and
+@code{OImode}.
 
 @findex MODE_PARTIAL_INT
 @item MODE_PARTIAL_INT
-The ``partial integer'' modes, @code{PSImode} and @code{PDImode}.
+The ``partial integer'' modes, @code{PQImode}, @code{PHImode},
+@code{PSImode} and @code{PDImode}.
 
 @findex MODE_FLOAT
 @item MODE_FLOAT
-floating point modes.  By default these are @code{SFmode}, @code{DFmode},
+Floating point modes.  By default these are @code{QFmode},
+@code{HFmode}, @code{TQFmode}, @code{SFmode}, @code{DFmode},
 @code{XFmode} and @code{TFmode}.
 
 @findex MODE_COMPLEX_INT
@@ -840,8 +1179,9 @@ Complex integer modes.  (These are not currently implemented).
 
 @findex MODE_COMPLEX_FLOAT
 @item MODE_COMPLEX_FLOAT
-Complex floating point modes.  By default these are @code{SCmode},
-@code{DCmode}, @code{XCmode}, and @code{TCmode}.
+Complex floating point modes.  By default these are @code{QCmode},
+@code{HCmode}, @code{SCmode}, @code{DCmode}, @code{XCmode}, and
+@code{TCmode}.
 
 @findex MODE_FUNCTION
 @item MODE_FUNCTION
@@ -947,6 +1287,9 @@ This type of expression represents the integer value @var{i}.  @var{i}
 is customarily accessed with the macro @code{INTVAL} as in
 @code{INTVAL (@var{exp})}, which is equivalent to @code{XWINT (@var{exp}, 0)}.
 
+Constants generated for modes with fewer bits than @code{HOST_WIDE_INT}
+must be sign extended to full width (e.g., with @code{gen_int_mode}).
+
 @findex const0_rtx
 @findex const1_rtx
 @findex const2_rtx
@@ -959,7 +1302,7 @@ only expression for integer value negative one is found in
 @code{constm1_rtx}.  Any attempt to create an expression of code
 @code{const_int} and value zero, one, two or negative one will return
 @code{const0_rtx}, @code{const1_rtx}, @code{const2_rtx} or
-@code{constm1_rtx} as appropriate.@refill
+@code{constm1_rtx} as appropriate.
 
 @findex const_true_rtx
 Similarly, there is only one object for the integer whose value is
@@ -967,16 +1310,30 @@ Similarly, there is only one object for the integer whose value is
 @code{STORE_FLAG_VALUE} is one, @code{const_true_rtx} and
 @code{const1_rtx} will point to the same object.  If
 @code{STORE_FLAG_VALUE} is @minus{}1, @code{const_true_rtx} and
-@code{constm1_rtx} will point to the same object.@refill
+@code{constm1_rtx} will point to the same object.
 
 @findex const_double
 @item (const_double:@var{m} @var{addr} @var{i0} @var{i1} @dots{})
 Represents either a floating-point constant of mode @var{m} or an
 integer constant too large to fit into @code{HOST_BITS_PER_WIDE_INT}
-bits but small enough to fit within twice that number of bits (GNU CC
+bits but small enough to fit within twice that number of bits (GCC
 does not provide a mechanism to represent even larger constants).  In
 the latter case, @var{m} will be @code{VOIDmode}.
 
+@findex const_vector
+@item (const_vector:@var{m} [@var{x0} @var{x1} @dots{}])
+Represents a vector constant.  The square brackets stand for the vector
+containing the constant elements.  @var{x0}, @var{x1} and so on are
+the @code{const_int} or @code{const_double} elements.
+
+The number of units in a @code{const_vector} is obtained with the macro
+@code{CONST_VECTOR_NUNITS} as in @code{CONST_VECTOR_NUNITS (@var{v})}.
+
+Individual elements in a vector constant are accessed with the macro
+@code{CONST_VECTOR_ELT} as in @code{CONST_VECTOR_ELT (@var{v}, @var{n})}
+where @var{v} is the vector constant and @var{n} is the element
+desired.
+
 @findex CONST_DOUBLE_MEM
 @findex CONST_DOUBLE_CHAIN
 @var{addr} is used to contain the @code{mem} expression that corresponds
@@ -986,7 +1343,7 @@ it has not been allocated a memory location, but is on the chain of all
 undisplayed field), @var{addr} contains @code{const0_rtx}.  If it is not
 on the chain, @var{addr} contains @code{cc0_rtx}.  @var{addr} is
 customarily accessed with the macro @code{CONST_DOUBLE_MEM} and the
-chain field via @code{CONST_DOUBLE_CHAIN}.@refill
+chain field via @code{CONST_DOUBLE_CHAIN}.
 
 @findex CONST_DOUBLE_LOW
 If @var{m} is @code{VOIDmode}, the bits of the value are stored in
@@ -995,7 +1352,7 @@ If @var{m} is @code{VOIDmode}, the bits of the value are stored in
 
 If the constant is floating point (regardless of its precision), then
 the number of integers used to store the value depends on the size of
-@code{REAL_VALUE_TYPE} (@pxref{Cross-compilation}).  The integers
+@code{REAL_VALUE_TYPE} (@pxref{Floating Point}).  The integers
 represent a floating point number, but not precisely in the target
 machine's or host machine's floating point format.  To convert them to
 the precise bit pattern used by the target machine, use the macro
@@ -1006,10 +1363,14 @@ the precise bit pattern used by the target machine, use the macro
 @findex CONST2_RTX
 The macro @code{CONST0_RTX (@var{mode})} refers to an expression with
 value 0 in mode @var{mode}.  If mode @var{mode} is of mode class
-@code{MODE_INT}, it returns @code{const0_rtx}.  Otherwise, it returns a
-@code{CONST_DOUBLE} expression in mode @var{mode}.  Similarly, the macro
+@code{MODE_INT}, it returns @code{const0_rtx}.  If mode @var{mode} is of
+mode class @code{MODE_FLOAT}, it returns a @code{CONST_DOUBLE}
+expression in mode @var{mode}.  Otherwise, it returns a
+@code{CONST_VECTOR} expression in mode @var{mode}.  Similarly, the macro
 @code{CONST1_RTX (@var{mode})} refers to an expression with value 1 in
-mode @var{mode} and similarly for @code{CONST2_RTX}.
+mode @var{mode} and similarly for @code{CONST2_RTX}.  The
+@code{CONST1_RTX} and @code{CONST2_RTX} macros are undefined
+for vector modes.
 
 @findex const_string
 @item (const_string @var{str})
@@ -1031,9 +1392,9 @@ Usually that is the only mode for which a symbol is directly valid.
 @findex label_ref
 @item (label_ref @var{label})
 Represents the value of an assembler label for code.  It contains one
-operand, an expression, which must be a @code{code_label} that appears
-in the instruction sequence to identify the place where the label
-should go.
+operand, an expression, which must be a @code{code_label} or a @code{note}
+of type @code{NOTE_INSN_DELETED_LABEL} that appears in the instruction
+sequence to identify the place where the label should go.
 
 The reason for using a distinct expression type for code label
 references is so that jump optimization can distinguish them.
@@ -1245,7 +1606,7 @@ It is also not valid to access a single word of a multi-word value in a
 hard register when less registers can hold the value than would be
 expected from its size.  For example, some 32-bit machines have
 floating-point registers that can hold an entire @code{DFmode} value.
-If register 10 were such a register @code{(subreg:SI (reg:DF 10) 1)}
+If register 10 were such a register @code{(subreg:SI (reg:DF 10) 4)}
 would be invalid because there is no way to convert that reference to
 a single machine register.  The reload pass prevents @code{subreg}
 expressions such as these from being formed.
@@ -1314,7 +1675,7 @@ preferable approach if only a small subset of instructions modify the
 condition code.  Other machines store condition codes in general
 registers; in such cases a pseudo register should be used.
 
-Some machines, such as the Sparc and RS/6000, have two sets of
+Some machines, such as the SPARC and RS/6000, have two sets of
 arithmetic instructions, one that sets and one that does not set the
 condition code.  This is best handled by normally generating the
 instruction that does not set the condition code, and making a pattern
@@ -1335,16 +1696,20 @@ of the variable @code{pc_rtx}.  Any attempt to create an expression of
 code @code{pc} will return @code{pc_rtx}.
 
 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.
+by incrementing it, but there is no need to mention this in the RTL@.
 
 @findex mem
 @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. @var{alias} specifies an alias set for the
-reference. In general two items are in different alias sets if they cannot
+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.
 
+The construct @code{(mem:BLK (scratch))} is considered to alias all
+other memories.  Thus it may be used as a memory barrier in epilogue
+stack deallocation patterns.
+
 @findex addressof
 @item (addressof:@var{m} @var{reg})
 This RTX represents a request for the address of register @var{reg}.  Its mode
@@ -1370,51 +1735,53 @@ second operand.
 
 @table @code
 @findex plus
-@cindex RTL addition
+@findex ss_plus
+@findex us_plus
 @cindex RTL sum
+@cindex RTL addition
+@cindex RTL addition with signed saturation
+@cindex RTL addition with unsigned saturation
 @item (plus:@var{m} @var{x} @var{y})
-Represents the sum of the values represented by @var{x} and @var{y}
-carried out in machine mode @var{m}.
-
-@findex lo_sum
-@item (lo_sum:@var{m} @var{x} @var{y})
-Like @code{plus}, except that it represents that sum of @var{x} and the
-low-order bits of @var{y}.  The number of low order bits is
-machine-dependent but is normally the number of bits in a @code{Pmode}
-item minus the number of bits set by the @code{high} code
-(@pxref{Constants}).
+@itemx (ss_plus:@var{m} @var{x} @var{y})
+@itemx (us_plus:@var{m} @var{x} @var{y})
 
-@var{m} should be @code{Pmode}.
+These three expressions all represent the sum of the values
+represented by @var{x} and @var{y} carried out in machine mode
+@var{m}.  They differ in their behavior on overflow of integer modes.
+@code{plus} wraps round modulo the width of @var{m}; @code{ss_plus}
+saturates at the maximum signed value representable in @var{m};
+@code{us_plus} saturates at the maximum unsigned value.
 
-@findex minus
-@cindex RTL subtraction
-@cindex RTL difference
-@item (minus:@var{m} @var{x} @var{y})
-Like @code{plus} but represents subtraction.
+@c ??? What happens on overflow of floating point modes?
 
-@findex ss_plus
-@cindex RTL addition with signed saturation
-@item (ss_plus:@var{m} @var{x} @var{y})
+@findex lo_sum
+@item (lo_sum:@var{m} @var{x} @var{y})
 
-Like @code{plus}, but using signed saturation in case of an overflow.
+This expression represents the sum of @var{x} and the low-order bits
+of @var{y}.  It is used with @code{high} (@pxref{Constants}) to
+represent the typical two-instruction sequence used in RISC machines
+to reference a global memory location.
 
-@findex us_plus
-@cindex RTL addition with unsigned saturation
-@item (us_plus:@var{m} @var{x} @var{y})
+The number of low order bits is machine-dependent but is
+normally the number of bits in a @code{Pmode} item minus the number of
+bits set by @code{high}.
 
-Like @code{plus}, but using unsigned saturation in case of an overflow.
+@var{m} should be @code{Pmode}.
 
+@findex minus
 @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})
+@cindex RTL difference
+@cindex RTL subtraction
+@cindex RTL subtraction with signed saturation
+@cindex RTL subtraction with unsigned saturation
+@item (minus:@var{m} @var{x} @var{y})
+@itemx (ss_minus:@var{m} @var{x} @var{y})
+@itemx (us_minus:@var{m} @var{x} @var{y})
 
-Like @code{minus}, but using unsigned saturation in case of an overflow.
+These three expressions represent the result of subtracting @var{y}
+from @var{x}, carried out in mode @var{M}.  Behavior on overflow is
+the same as for the three variants of @code{plus} (see above).
 
 @findex compare
 @cindex RTL comparison
@@ -1428,7 +1795,7 @@ 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}.
+@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
@@ -1471,15 +1838,15 @@ Represents the signed product of the values represented by @var{x} and
 Some machines support a multiplication that generates a product wider
 than the operands.  Write the pattern for this as
 
-@example
+@smallexample
 (mult:@var{m} (sign_extend:@var{m} @var{x}) (sign_extend:@var{m} @var{y}))
-@end example
+@end smallexample
 
 where @var{m} is wider than the modes of @var{x} and @var{y}, which need
 not be the same.
 
-Write patterns for unsigned widening multiplication similarly using
-@code{zero_extend}.
+For unsigned widening multiplication, use the same idiom, but with
+@code{zero_extend} instead of @code{sign_extend}.
 
 @findex div
 @cindex division
@@ -1495,9 +1862,9 @@ Some machines have division instructions in which the operands and
 quotient widths are not all the same; you should represent
 such instructions using @code{truncate} and @code{sign_extend} as in,
 
-@example
+@smallexample
 (truncate:@var{m1} (div:@var{m2} @var{x} (sign_extend:@var{m2} @var{y})))
-@end example
+@end smallexample
 
 @findex udiv
 @cindex unsigned division
@@ -1521,7 +1888,10 @@ the quotient.
 @item (smin:@var{m} @var{x} @var{y})
 @itemx (smax:@var{m} @var{x} @var{y})
 Represents the smaller (for @code{smin}) or larger (for @code{smax}) of
-@var{x} and @var{y}, interpreted as signed integers in mode @var{m}.
+@var{x} and @var{y}, interpreted as signed values in mode @var{m}.
+When used with floating point, if both operands are zeros, or if either
+operand is @code{NaN}, then it is unspecified which of the two operands
+is returned as the result.
 
 @findex umin
 @findex umax
@@ -1571,7 +1941,7 @@ Represents the result of arithmetically shifting @var{x} left by @var{c}
 places.  @var{x} have mode @var{m}, a fixed-point machine mode.  @var{c}
 be a fixed-point mode or be a constant with mode @code{VOIDmode}; which
 mode is determined by the mode called for in the machine description
-entry for the left-shift instruction.  For example, on the Vax, the mode
+entry for the left-shift instruction.  For example, on the VAX, the mode
 of @var{c} is @code{QImode} regardless of @var{m}.
 
 @findex lshiftrt
@@ -1610,6 +1980,35 @@ Represents one plus the index of the least significant 1-bit in
 zero if @var{x} is zero.)  The mode of @var{x} need not be @var{m};
 depending on the target machine, various mode combinations may be
 valid.
+
+@findex clz
+@item (clz:@var{m} @var{x})
+Represents the number of leading 0-bits in @var{x}, represented as an
+integer of mode @var{m}, starting at the most significant bit position.
+If @var{x} is zero, the value is determined by
+@code{CLZ_DEFINED_VALUE_AT_ZERO}.  Note that this is one of
+the few expressions that is not invariant under widening.  The mode of
+@var{x} will usually be an integer mode.
+
+@findex ctz
+@item (ctz:@var{m} @var{x})
+Represents the number of trailing 0-bits in @var{x}, represented as an
+integer of mode @var{m}, starting at the least significant bit position.
+If @var{x} is zero, the value is determined by
+@code{CTZ_DEFINED_VALUE_AT_ZERO}.  Except for this case,
+@code{ctz(x)} is equivalent to @code{ffs(@var{x}) - 1}.  The mode of
+@var{x} will usually be an integer mode.
+
+@findex popcount
+@item (popcount:@var{m} @var{x})
+Represents the number of 1-bits in @var{x}, represented as an integer of
+mode @var{m}.  The mode of @var{x} will usually be an integer mode.
+
+@findex parity
+@item (parity:@var{m} @var{x})
+Represents the number of 1-bits modulo 2 in @var{x}, represented as an
+integer of mode @var{m}.  The mode of @var{x} will usually be an integer
+mode.
 @end table
 
 @node Comparisons
@@ -1619,14 +2018,17 @@ valid.
 Comparison operators test a relation on two operands and are considered
 to represent a machine-dependent nonzero value described by, but not
 necessarily equal to, @code{STORE_FLAG_VALUE} (@pxref{Misc})
-if the relation holds, or zero if it does not.  The mode of the
-comparison operation is independent of the mode of the data being
-compared.  If the comparison operation is being tested (e.g., the first
-operand of an @code{if_then_else}), the mode must be @code{VOIDmode}.
-If the comparison operation is producing data to be stored in some
-variable, the mode must be in class @code{MODE_INT}.  All comparison
-operations producing data must use the same mode, which is
-machine-specific.
+if the relation holds, or zero if it does not, for comparison operators
+whose results have a `MODE_INT' mode,
+@code{FLOAT_STORE_FLAG_VALUE} (@pxref{Misc}) if the relation holds, or
+zero if it does not, for comparison operators that return floating-point
+values, and a vector of either @code{VECTOR_STORE_FLAG_VALUE} (@pxref{Misc})
+if the relation holds, or of zeros if it does not, for comparison operators
+that return vector results.
+The mode of the comparison operation is independent of the mode
+of the data being compared.  If the comparison operation is being tested
+(e.g., the first operand of an @code{if_then_else}), the mode must be
+@code{VOIDmode}.
 
 @cindex condition codes
 There are two ways that comparison operations may be used.  The
@@ -1725,8 +2127,8 @@ to express conditional jumps.
 @item (cond [@var{test1} @var{value1} @var{test2} @var{value2} @dots{}] @var{default})
 Similar to @code{if_then_else}, but more general.  Each of @var{test1},
 @var{test2}, @dots{} is performed in turn.  The result of this expression is
-the @var{value} corresponding to the first non-zero test, or @var{default} if
-none of the tests are non-zero expressions.
+the @var{value} corresponding to the first nonzero test, or @var{default} if
+none of the tests are nonzero expressions.
 
 This is currently not valid for instruction patterns and is supported only
 for insn attributes.  @xref{Insn Attributes}.
@@ -1737,9 +2139,6 @@ for insn attributes.  @xref{Insn Attributes}.
 @cindex bit-fields
 
 Special expression codes exist to represent bit-field instructions.
-These types of expressions are lvalues in RTL; they may appear
-on the left side of an assignment, indicating insertion of a value
-into the specified bit-field.
 
 @table @code
 @findex sign_extract
@@ -1763,18 +2162,25 @@ in the @code{insv} or @code{extv} pattern.
 The mode @var{m} is the same as the mode that would be used for
 @var{loc} if it were a register.
 
+A @code{sign_extract} can not appear as an lvalue, or part thereof,
+in RTL.
+
 @findex zero_extract
 @item (zero_extract:@var{m} @var{loc} @var{size} @var{pos})
 Like @code{sign_extract} but refers to an unsigned or zero-extended
 bit-field.  The same sequence of bits are extracted, but they
 are filled to an entire word with zeros instead of by sign-extension.
+
+Unlike @code{sign_extract}, this type of expressions can be lvalues
+in RTL; they may appear on the left side of an assignment, indicating
+insertion of a value into the specified bit-field.
 @end table
 
 @node Vector Operations
 @section Vector Operations
 @cindex vector operations
 
-All normal rtl expressions can be used with vector modes; they are
+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.
@@ -1802,11 +2208,6 @@ 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
@@ -1829,9 +2230,9 @@ operation requires two operands of the same machine mode.
 Therefore, the byte-sized operand is enclosed in a conversion
 operation, as in
 
-@example
+@smallexample
 (plus:SI (sign_extend:SI (reg:QI 34)) (reg:SI 80))
-@end example
+@end smallexample
 
 The conversion operation is not a mere placeholder, because there
 may be more than one way of converting from a given starting mode
@@ -1960,12 +2361,12 @@ 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}, @code{parallel}, or
-@code{cc0}.@refill
+representing a place that can be stored in: @code{reg} (or @code{subreg},
+@code{strict_low_part} or @code{zero_extract}), @code{mem}, @code{pc},
+@code{parallel}, or @code{cc0}.
 
 If @var{lval} is a @code{reg}, @code{subreg} or @code{mem}, it has a
-machine mode; then @var{x} must be valid for that mode.@refill
+machine mode; then @var{x} must be valid for that mode.
 
 If @var{lval} is a @code{reg} whose machine mode is less than the full
 width of the register, then it means that the part of the register
@@ -1975,10 +2376,15 @@ rest of the register receives an undefined value.  Likewise, if
 the mode of the register, the rest of the register can be changed in
 an undefined way.
 
-If @var{lval} is a @code{strict_low_part} of a @code{subreg}, then the
-part of the register specified by the machine mode of the
-@code{subreg} is given the value @var{x} and the rest of the register
-is not changed.@refill
+If @var{lval} is a @code{strict_low_part} of a subreg, then the part
+of the register specified by the machine mode of the @code{subreg} is
+given the value @var{x} and the rest of the register is not changed.
+
+If @var{lval} is a @code{zero_extract}, then the referenced part of
+the bit-field (a memory or register reference) specified by the
+@code{zero_extract} is given the value @var{x} and the rest of the
+bit-field is not changed.  Note that @code{sign_extract} can not
+appear in @var{lval}.
 
 If @var{lval} is @code{(cc0)}, it has no machine mode, and @var{x} may
 be either a @code{compare} expression or a value that may have any mode.
@@ -2006,7 +2412,7 @@ does not jump) and the other of the two must be a @code{label_ref}
 (for the case which does jump).  @var{x} may also be a @code{mem} or
 @code{(plus:SI (pc) @var{y})}, where @var{y} may be a @code{reg} or a
 @code{mem}; these unusual patterns are used to represent jumps through
-branch tables.@refill
+branch tables.
 
 If @var{lval} is neither @code{(cc0)} nor @code{(pc)}, the mode of
 @var{lval} must not be @code{VOIDmode} and the mode of @var{x} must be
@@ -2021,7 +2427,7 @@ valid for the mode of @var{lval}.
 @item (return)
 As the sole expression in a pattern, 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
+instruction, such as VAXen.  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 @code{return} expression code is never used.
@@ -2059,7 +2465,8 @@ 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.
 
-If @var{x} is @code{(mem:BLK (const_int 0))}, it means that all memory
+If @var{x} is @code{(mem:BLK (const_int 0))} or
+@code{(mem:BLK (scratch))}, it means that all memory
 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.
 
@@ -2089,7 +2496,7 @@ insn.  However, the reload phase may allocate a register used for one of
 the inputs unless the @samp{&} constraint is specified for the selected
 alternative (@pxref{Modifiers}).  You can clobber either a specific hard
 register, a pseudo register, or a @code{scratch} expression; in the
-latter two cases, GNU CC will allocate a hard register that is available
+latter two cases, GCC will allocate a hard register that is available
 there for use as a temporary.
 
 For instructions that require a temporary register, you should use
@@ -2097,7 +2504,7 @@ For instructions that require a temporary register, you should use
 combiner phase to add the @code{clobber} when required.  You do this by
 coding (@code{clobber} (@code{match_scratch} @dots{})).  If you do
 clobber a pseudo register, use one which appears nowhere else---generate
-a new one each time.  Otherwise, you may confuse CSE.
+a new one each time.  Otherwise, you may confuse CSE@.
 
 There is one other known use for clobbering a pseudo register in a
 @code{parallel}: when one of the input operands of the insn is also
@@ -2114,15 +2521,16 @@ 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.
+of a special register will modify the behavior 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))
+@smallexample
+(parallel [(set (reg:SI 2) (unspec:SI [(reg:SI 3)
+                                       (reg:SI 4)] 0))
            (use (reg:SI 1))])
-@end example
+@end smallexample
 
 @noindent
 
@@ -2137,7 +2545,7 @@ that the register is live.  You should think twice before adding
 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
+of the whole pattern is variable, such as @samp{movmem@var{m}} or
 @samp{call} patterns.
 
 During the reload phase, an insn that has a @code{use} as pattern
@@ -2156,16 +2564,16 @@ Represents several side effects performed in parallel.  The square
 brackets stand for a vector; the operand of @code{parallel} is a
 vector of expressions.  @var{x0}, @var{x1} and so on are individual
 side effect expressions---expressions of code @code{set}, @code{call},
-@code{return}, @code{clobber} or @code{use}.@refill
+@code{return}, @code{clobber} or @code{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,
 
-@example
+@smallexample
 (parallel [(set (reg:SI 1) (mem:SI (reg:SI 1)))
            (set (mem:SI (reg:SI 1)) (reg:SI 1))])
-@end example
+@end smallexample
 
 @noindent
 says unambiguously that the values of hard register 1 and the memory
@@ -2178,13 +2586,13 @@ expect the result of one @code{set} to be available for the next one.
 For example, people sometimes attempt to represent a jump-if-zero
 instruction this way:
 
-@example
+@smallexample
 (parallel [(set (cc0) (reg:SI 34))
            (set (pc) (if_then_else
                         (eq (cc0) (const_int 0))
                         (label_ref @dots{})
                         (pc)))])
-@end example
+@end smallexample
 
 @noindent
 But this is incorrect, because it says that the jump condition depends
@@ -2204,7 +2612,7 @@ any, must deal with such insns if you define any peephole optimizations.
 @findex cond_exec
 @item (cond_exec [@var{cond} @var{expr}])
 Represents a conditionally executed expression.  The @var{expr} is
-executed only if the @var{cond} is non-zero.  The @var{cond} expression
+executed only if the @var{cond} is nonzero.  The @var{cond} expression
 must not have side-effects, but the @var{expr} may very well have
 side-effects.
 
@@ -2273,7 +2681,21 @@ 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
+and of @var{min} and @var{max} to @var{base}.  See rtl.def for details.
+
+@findex prefetch
+@item (prefetch:@var{m} @var{addr} @var{rw} @var{locality})
+Represents prefetch of memory at address @var{addr}.
+Operand @var{rw} is 1 if the prefetch is for data to be written, 0 otherwise;
+targets that do not support write prefetches should treat this as a normal
+prefetch.
+Operand @var{locality} specifies the amount of temporal locality; 0 if there
+is none or 1, 2, or 3 for increasing levels of temporal locality;
+targets that do not support locality hints should ignore this.
+
+This insn is used to minimize cache-miss latency by moving data into a
+cache before it is accessed.  It should use only non-faulting data prefetch
+instructions.
 @end table
 
 @node Incdec
@@ -2295,11 +2717,11 @@ 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.  Here is an
-example of its use:@refill
+example of its use:
 
-@example
+@smallexample
 (mem:DF (pre_dec:SI (reg:SI 39)))
-@end example
+@end smallexample
 
 @noindent
 This says to decrement pseudo register 39 by the length of a @code{DFmode}
@@ -2326,9 +2748,6 @@ 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
@@ -2338,16 +2757,17 @@ The expression @var{y} must be one of three forms:
 @end table
 where @var{z} is an index register and @var{i} is a constant.
 
-Here is an example of its use:@refill
+Here is an example of its use:
 
-@example
-(mem:SF (post_modify:SI (reg:SI 42) (plus (reg:SI 42) (reg:SI 48))))
-@end example
+@smallexample
+(mem:SF (post_modify:SI (reg:SI 42) (plus (reg:SI 42)
+                                          (reg:SI 48))))
+@end smallexample
 
 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
+@findex pre_modify
 @item (pre_modify:@var{m} @var{x} @var{expr})
 Similar except side effects happen before the use.
 @end table
@@ -2461,16 +2881,16 @@ chain delimited by these insns, the @code{NEXT_INSN} and
 @code{PREV_INSN} pointers must always correspond: if @var{insn} is not
 the first insn,
 
-@example
+@smallexample
 NEXT_INSN (PREV_INSN (@var{insn})) == @var{insn}
-@end example
+@end smallexample
 
 @noindent
 is always true and if @var{insn} is not the last insn,
 
-@example
+@smallexample
 PREV_INSN (NEXT_INSN (@var{insn})) == @var{insn}
-@end example
+@end smallexample
 
 @noindent
 is always true.
@@ -2486,9 +2906,9 @@ This means that the above invariants are not necessarily true for insns
 inside @code{sequence} expressions.  Specifically, if @var{insn} is the
 first insn in a @code{sequence}, @code{NEXT_INSN (PREV_INSN (@var{insn}))}
 is the insn containing the @code{sequence} expression, as is the value
-of @code{PREV_INSN (NEXT_INSN (@var{insn}))} is @var{insn} is the last
+of @code{PREV_INSN (NEXT_INSN (@var{insn}))} if @var{insn} is the last
 insn in the @code{sequence} expression.  You can use these expressions
-to find the containing @code{sequence} expression.@refill
+to find the containing @code{sequence} expression.
 
 Every insn has one of the following six expression codes:
 
@@ -2542,8 +2962,8 @@ 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}),
+TARGET_PASS_BY_REFERENCE}) are stored.  If the argument is
+caller-copied (@pxref{Register Arguments, TARGET_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
@@ -2574,15 +2994,37 @@ When a @code{code_label} appears in an RTL expression, it normally
 appears within a @code{label_ref} which represents the address of
 the label, as a number.
 
+Besides as a @code{code_label}, a label can also be represented as a
+@code{note} of type @code{NOTE_INSN_DELETED_LABEL}.
+
 @findex LABEL_NUSES
 The field @code{LABEL_NUSES} is only defined once the jump optimization
-phase is completed and contains the number of times this label is
+phase is completed.  It 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 LABEL_KIND
+@findex SET_LABEL_KIND
+@findex LABEL_ALT_ENTRY_P
+@cindex alternate entry points
+The field @code{LABEL_KIND} differentiates four different types of
+labels: @code{LABEL_NORMAL}, @code{LABEL_STATIC_ENTRY},
+@code{LABEL_GLOBAL_ENTRY}, and @code{LABEL_WEAK_ENTRY}.  The only labels
+that do not have type @code{LABEL_NORMAL} are @dfn{alternate entry
+points} to the current function.  These may be static (visible only in
+the containing translation unit), global (exposed to all translation
+units), or weak (global, but can be overridden by another symbol with the
+same name).
+
+Much of the compiler treats all four kinds of label identically.  Some
+of it needs to know whether or not a label is an alternate entry point;
+for this purpose, the macro @code{LABEL_ALT_ENTRY_P} is provided.  It is
+equivalent to testing whether @samp{LABEL_KIND (label) == LABEL_NORMAL}.
+The only place that cares about the distinction between static, global,
+and weak alternate entry points, besides the front-end code that creates
+them, is the function @code{output_alternate_entry_point}, in
+@file{final.c}.
+
+To set the kind of a label, use the @code{SET_LABEL_KIND} macro.
 
 @findex barrier
 @item barrier
@@ -2616,6 +3058,12 @@ must contain a null pointer):
 Such a note is completely ignorable.  Some passes of the compiler
 delete insns by altering them into notes of this kind.
 
+@findex NOTE_INSN_DELETED_LABEL
+@item NOTE_INSN_DELETED_LABEL
+This marks what used to be a @code{code_label}, but was not used for other
+purposes than taking its address and was transformed to mark that no
+code jumps to it.
+
 @findex NOTE_INSN_BLOCK_BEG
 @findex NOTE_INSN_BLOCK_END
 @item NOTE_INSN_BLOCK_BEG
@@ -2630,7 +3078,8 @@ of debugging information.
 @itemx NOTE_INSN_EH_REGION_END
 These types of notes indicate the position of the beginning and end of a
 level of scoping for exception handling.  @code{NOTE_BLOCK_NUMBER}
-identifies which @code{CODE_LABEL} is associated with the given region.
+identifies which @code{CODE_LABEL} or @code{note} of type
+@code{NOTE_INSN_DELETED_LABEL} is associated with the given region.
 
 @findex NOTE_INSN_LOOP_BEG
 @findex NOTE_INSN_LOOP_END
@@ -2651,6 +3100,11 @@ those loops in which the exit test has been duplicated.  This position
 becomes another virtual start of the loop when considering loop
 invariants.
 
+@findex NOTE_INSN_FUNCTION_BEG
+@item NOTE_INSN_FUNCTION_END
+Appears at the start of the function body, after the function
+prologue.
+
 @findex NOTE_INSN_FUNCTION_END
 @item NOTE_INSN_FUNCTION_END
 Appears near the end of the function body, just before the label that
@@ -2778,11 +3232,17 @@ The value in @var{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.
 
-This does not necessarily mean that the register @var{op} has no useful
-value after this insn since it may also be an output of the insn.  In
-such a case, however, a @code{REG_DEAD} note would be redundant and is
-usually not present until after the reload pass, but no code relies on
-this fact.
+It does not follow that the register @var{op} has no useful value after
+this insn since @var{op} is not necessarily modified by this insn.
+Rather, no subsequent instruction uses the contents of @var{op}.
+
+@findex REG_UNUSED
+@item REG_UNUSED
+The register @var{op} being set by this insn will not be used in a
+subsequent insn.  This differs from a @code{REG_DEAD} note, which
+indicates that the value in an input will not be used subsequently.
+These two notes are independent; both may be present for the same
+register.
 
 @findex REG_INC
 @item REG_INC
@@ -2819,11 +3279,22 @@ last insns, respectively.
 
 @findex REG_LABEL
 @item REG_LABEL
-This insn uses @var{op}, a @code{code_label}, but is not a
+This insn uses @var{op}, a @code{code_label} or a @code{note} of type
+@code{NOTE_INSN_DELETED_LABEL}, but is not a
 @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.
+
+@findex REG_CROSSING_JUMP
+@item REG_CROSSING_JUMP
+This insn is an branching instruction (either an unconditional jump or
+an indirect jump) which crosses between hot and cold sections, which
+could potentially be very far apart in the executable.  The presence
+of this note indicates to other optimizations that this this branching
+instruction should not be ``collapsed'' into a simpler branching
+construct.  It is used when the optimization to partition basic blocks
+into hot and cold sections is turned on.
 @end table
 
 The following notes describe attributes of outputs of an insn:
@@ -2886,7 +3357,7 @@ insufficient registers are available.
 Except for stack homes for parameters, which are indicated by a
 @code{REG_EQUIV} note and are not useful to the early optimization
 passes and pseudo registers that are equivalent to a memory location
-throughout there entire life, which is not detected until later in
+throughout their entire life, which is not detected until later in
 the compilation, all equivalences are initially indicated by an attached
 @code{REG_EQUAL} note.  In the early stages of register allocation, a
 @code{REG_EQUAL} note is changed into a @code{REG_EQUIV} note if
@@ -2896,21 +3367,6 @@ destination register.
 Thus, compiler passes prior to register allocation need only check for
 @code{REG_EQUAL} notes and passes subsequent to register allocation
 need only check for @code{REG_EQUIV} notes.
-
-@findex REG_UNUSED
-@item REG_UNUSED
-The register @var{op} being set by this insn will not be used in a
-subsequent insn.  This differs from a @code{REG_DEAD} note, which
-indicates that the value in an input will not be used subsequently.
-These two notes are independent; both may be present for the same
-register.
-
-@findex REG_WAS_0
-@item REG_WAS_0
-The single output of this insn contained zero before this insn.
-@var{op} is the insn that set it to zero.  You can rely on this note if
-it is present and @var{op} has not been deleted or turned into a @code{note};
-its absence implies nothing.
 @end table
 
 These notes describe linkages between insns.  They occur in pairs: one
@@ -2953,7 +3409,7 @@ filling is done, this may no longer be true.  In this case a
 @code{REG_CC_USER} note will be placed on the insn setting @code{cc0} to
 point to the insn using @code{cc0} and a @code{REG_CC_SETTER} note will
 be placed on the insn using @code{cc0} to point to the insn setting
-@code{cc0}.@refill
+@code{cc0}.
 @end table
 
 These values are only used in the @code{LOG_LINKS} field, and indicate
@@ -2977,12 +3433,6 @@ are stored in the @code{REG_NOTES} field of an insn as an
 @code{expr_list}.
 
 @table @code
-@findex REG_EXEC_COUNT
-@item REG_EXEC_COUNT
-This is used to indicate the number of times a basic block was executed
-according to the profile data.  The note is attached to the first insn in
-the basic block.
-
 @findex REG_BR_PROB
 @item REG_BR_PROB
 This is used to specify the ratio of branches to non-branches of a
@@ -2994,7 +3444,7 @@ probability that the branch will be taken.
 @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 likelihood
-of the JUMP.  The format is a bitmask of ATTR_FLAG_* values.
+of the JUMP@.  The format is a bitmask of ATTR_FLAG_* values.
 
 @findex REG_FRAME_RELATED_EXPR
 @item REG_FRAME_RELATED_EXPR
@@ -3027,9 +3477,9 @@ RTL expression code, @code{call}.
 @cindex @code{call} usage
 A @code{call} expression has two operands, as follows:
 
-@example
+@smallexample
 (call (mem:@var{fm} @var{addr}) @var{nbytes})
-@end example
+@end smallexample
 
 @noindent
 Here @var{nbytes} is an operand that represents the number of bytes of
@@ -3047,10 +3497,10 @@ For a subroutine that returns a value whose mode is not @code{BLKmode},
 the value is returned in a hard register.  If this register's number is
 @var{r}, then the body of the call insn looks like this:
 
-@example
+@smallexample
 (set (reg:@var{m} @var{r})
      (call (mem:@var{fm} @var{addr}) @var{nbytes}))
-@end example
+@end smallexample
 
 @noindent
 This RTL expression makes it clear (to the optimizer passes) that the
@@ -3067,7 +3517,7 @@ on these machines should have a body which is a @code{parallel}
 that contains both the @code{call} expression and @code{clobber}
 expressions that indicate which registers are destroyed.  Similarly,
 if the call instruction requires some register other than the stack
-pointer that is not explicitly mentioned it its RTL, a @code{use}
+pointer that is not explicitly mentioned in its RTL, a @code{use}
 subexpression should mention that register.
 
 Functions that are called are assumed to modify all registers listed in
@@ -3127,6 +3577,11 @@ There is only one @code{cc0} expression.
 There is only one @code{const_double} expression with value 0 for
 each floating point mode.  Likewise for values 1 and 2.
 
+@cindex @code{const_vector}, RTL sharing
+@item
+There is only one @code{const_vector} expression with value 0 for
+each vector mode, be it an integer or a double constant vector.
+
 @cindex @code{label_ref}, RTL sharing
 @cindex @code{scratch}, RTL sharing
 @item
@@ -3178,21 +3633,20 @@ combiner is finished with the insn.  This is done by calling
 @section Reading RTL
 
 To read an RTL object from a file, call @code{read_rtx}.  It takes one
-argument, a stdio stream, and returns a single RTL object.
-
-Reading RTL from a file is very slow.  This is not currently a
-problem since reading RTL occurs only as part of building the
-compiler.
+argument, a stdio stream, and returns a single RTL object.  This routine
+is defined in @file{read-rtl.c}.  It is not available in the compiler
+itself, only the various programs that generate the compiler back end
+from the machine description.
 
 People frequently have the idea of using RTL stored as text in a file as
-an interface between a language front end and the bulk of GNU CC.  This
+an interface between a language front end and the bulk of GCC@.  This
 idea is not feasible.
 
-GNU CC was designed to use RTL internally only.  Correct RTL for a given
+GCC was designed to use RTL internally only.  Correct RTL for a given
 program is very dependent on the particular target machine.  And the RTL
 does not contain all the information about the program.
 
-The proper way to interface GNU CC to a new language front end is with
+The proper way to interface GCC to a new language front end is with
 the ``tree'' data structure, described in the files @file{tree.h} and
 @file{tree.def}.  The documentation for this structure (@pxref{Trees})
 is incomplete.