1@c Copyright (C) 1988-2015 Free Software Foundation, Inc.
2@c This is part of the GCC manual.
3@c For copying conditions, see the file gcc.texi.
4
5@ifset INTERNALS
6@node Machine Desc
7@chapter Machine Descriptions
8@cindex machine descriptions
9
10A machine description has two parts: a file of instruction patterns
11(@file{.md} file) and a C header file of macro definitions.
12
13The @file{.md} file for a target machine contains a pattern for each
14instruction that the target machine supports (or at least each instruction
15that is worth telling the compiler about).  It may also contain comments.
16A semicolon causes the rest of the line to be a comment, unless the semicolon
17is inside a quoted string.
18
19See the next chapter for information on the C header file.
20
21@menu
22* Overview::            How the machine description is used.
23* Patterns::            How to write instruction patterns.
24* Example::             An explained example of a @code{define_insn} pattern.
25* RTL Template::        The RTL template defines what insns match a pattern.
26* Output Template::     The output template says how to make assembler code
27                        from such an insn.
28* Output Statement::    For more generality, write C code to output
29                        the assembler code.
30* Predicates::          Controlling what kinds of operands can be used
31                        for an insn.
32* Constraints::         Fine-tuning operand selection.
33* Standard Names::      Names mark patterns to use for code generation.
34* Pattern Ordering::    When the order of patterns makes a difference.
35* Dependent Patterns::  Having one pattern may make you need another.
36* Jump Patterns::       Special considerations for patterns for jump insns.
37* Looping Patterns::    How to define patterns for special looping insns.
38* Insn Canonicalizations::Canonicalization of Instructions
39* Expander Definitions::Generating a sequence of several RTL insns
40                        for a standard operation.
41* Insn Splitting::      Splitting Instructions into Multiple Instructions.
42* Including Patterns::  Including Patterns in Machine Descriptions.
43* Peephole Definitions::Defining machine-specific peephole optimizations.
44* Insn Attributes::     Specifying the value of attributes for generated insns.
45* Conditional Execution::Generating @code{define_insn} patterns for
46                         predication.
47* Define Subst::	Generating @code{define_insn} and @code{define_expand}
48			patterns from other patterns.
49* Constant Definitions::Defining symbolic constants that can be used in the
50                        md file.
51* Iterators::           Using iterators to generate patterns from a template.
52@end menu
53
54@node Overview
55@section Overview of How the Machine Description is Used
56
57There are three main conversions that happen in the compiler:
58
59@enumerate
60
61@item
62The front end reads the source code and builds a parse tree.
63
64@item
65The parse tree is used to generate an RTL insn list based on named
66instruction patterns.
67
68@item
69The insn list is matched against the RTL templates to produce assembler
70code.
71
72@end enumerate
73
74For the generate pass, only the names of the insns matter, from either a
75named @code{define_insn} or a @code{define_expand}.  The compiler will
76choose the pattern with the right name and apply the operands according
77to the documentation later in this chapter, without regard for the RTL
78template or operand constraints.  Note that the names the compiler looks
79for are hard-coded in the compiler---it will ignore unnamed patterns and
80patterns with names it doesn't know about, but if you don't provide a
81named pattern it needs, it will abort.
82
83If a @code{define_insn} is used, the template given is inserted into the
84insn list.  If a @code{define_expand} is used, one of three things
85happens, based on the condition logic.  The condition logic may manually
86create new insns for the insn list, say via @code{emit_insn()}, and
87invoke @code{DONE}.  For certain named patterns, it may invoke @code{FAIL} to tell the
88compiler to use an alternate way of performing that task.  If it invokes
89neither @code{DONE} nor @code{FAIL}, the template given in the pattern
90is inserted, as if the @code{define_expand} were a @code{define_insn}.
91
92Once the insn list is generated, various optimization passes convert,
93replace, and rearrange the insns in the insn list.  This is where the
94@code{define_split} and @code{define_peephole} patterns get used, for
95example.
96
97Finally, the insn list's RTL is matched up with the RTL templates in the
98@code{define_insn} patterns, and those patterns are used to emit the
99final assembly code.  For this purpose, each named @code{define_insn}
100acts like it's unnamed, since the names are ignored.
101
102@node Patterns
103@section Everything about Instruction Patterns
104@cindex patterns
105@cindex instruction patterns
106
107@findex define_insn
108A @code{define_insn} expression is used to define instruction patterns
109to which insns may be matched.  A @code{define_insn} expression contains
110an incomplete RTL expression, with pieces to be filled in later, operand
111constraints that restrict how the pieces can be filled in, and an output
112template or C code to generate the assembler output.
113
114A @code{define_insn} is an RTL expression containing four or five operands:
115
116@enumerate
117@item
118An optional name.  The presence of a name indicate that this instruction
119pattern can perform a certain standard job for the RTL-generation
120pass of the compiler.  This pass knows certain names and will use
121the instruction patterns with those names, if the names are defined
122in the machine description.
123
124The absence of a name is indicated by writing an empty string
125where the name should go.  Nameless instruction patterns are never
126used for generating RTL code, but they may permit several simpler insns
127to be combined later on.
128
129Names that are not thus known and used in RTL-generation have no
130effect; they are equivalent to no name at all.
131
132For the purpose of debugging the compiler, you may also specify a
133name beginning with the @samp{*} character.  Such a name is used only
134for identifying the instruction in RTL dumps; it is equivalent to having
135a nameless pattern for all other purposes.  Names beginning with the
136@samp{*} character are not required to be unique.
137
138@item
139The @dfn{RTL template}: This is a vector of incomplete RTL expressions
140which describe the semantics of the instruction (@pxref{RTL Template}).
141It is incomplete because it may contain @code{match_operand},
142@code{match_operator}, and @code{match_dup} expressions that stand for
143operands of the instruction.
144
145If the vector has multiple elements, the RTL template is treated as a
146@code{parallel} expression.
147
148@item
149@cindex pattern conditions
150@cindex conditions, in patterns
151The condition: This is a string which contains a C expression.  When the
152compiler attempts to match RTL against a pattern, the condition is
153evaluated.  If the condition evaluates to @code{true}, the match is
154permitted.  The condition may be an empty string, which is treated
155as always @code{true}.
156
157@cindex named patterns and conditions
158For a named pattern, the condition may not depend on the data in the
159insn being matched, but only the target-machine-type flags.  The compiler
160needs to test these conditions during initialization in order to learn
161exactly which named instructions are available in a particular run.
162
163@findex operands
164For nameless patterns, the condition is applied only when matching an
165individual insn, and only after the insn has matched the pattern's
166recognition template.  The insn's operands may be found in the vector
167@code{operands}.
168
169For an insn where the condition has once matched, it
170cannot later be used to control register allocation by excluding
171certain register or value combinations.
172
173@item
174The @dfn{output template} or @dfn{output statement}: This is either
175a string, or a fragment of C code which returns a string.
176
177When simple substitution isn't general enough, you can specify a piece
178of C code to compute the output.  @xref{Output Statement}.
179
180@item
181The @dfn{insn attributes}: This is an optional vector containing the values of
182attributes for insns matching this pattern (@pxref{Insn Attributes}).
183@end enumerate
184
185@node Example
186@section Example of @code{define_insn}
187@cindex @code{define_insn} example
188
189Here is an example of an instruction pattern, taken from the machine
190description for the 68000/68020.
191
192@smallexample
193(define_insn "tstsi"
194  [(set (cc0)
195        (match_operand:SI 0 "general_operand" "rm"))]
196  ""
197  "*
198@{
199  if (TARGET_68020 || ! ADDRESS_REG_P (operands[0]))
200    return \"tstl %0\";
201  return \"cmpl #0,%0\";
202@}")
203@end smallexample
204
205@noindent
206This can also be written using braced strings:
207
208@smallexample
209(define_insn "tstsi"
210  [(set (cc0)
211        (match_operand:SI 0 "general_operand" "rm"))]
212  ""
213@{
214  if (TARGET_68020 || ! ADDRESS_REG_P (operands[0]))
215    return "tstl %0";
216  return "cmpl #0,%0";
217@})
218@end smallexample
219
220This describes an instruction which sets the condition codes based on the
221value of a general operand.  It has no condition, so any insn with an RTL
222description of the form shown may be matched to this pattern.  The name
223@samp{tstsi} means ``test a @code{SImode} value'' and tells the RTL
224generation pass that, when it is necessary to test such a value, an insn
225to do so can be constructed using this pattern.
226
227The output control string is a piece of C code which chooses which
228output template to return based on the kind of operand and the specific
229type of CPU for which code is being generated.
230
231@samp{"rm"} is an operand constraint.  Its meaning is explained below.
232
233@node RTL Template
234@section RTL Template
235@cindex RTL insn template
236@cindex generating insns
237@cindex insns, generating
238@cindex recognizing insns
239@cindex insns, recognizing
240
241The RTL template is used to define which insns match the particular pattern
242and how to find their operands.  For named patterns, the RTL template also
243says how to construct an insn from specified operands.
244
245Construction involves substituting specified operands into a copy of the
246template.  Matching involves determining the values that serve as the
247operands in the insn being matched.  Both of these activities are
248controlled by special expression types that direct matching and
249substitution of the operands.
250
251@table @code
252@findex match_operand
253@item (match_operand:@var{m} @var{n} @var{predicate} @var{constraint})
254This expression is a placeholder for operand number @var{n} of
255the insn.  When constructing an insn, operand number @var{n}
256will be substituted at this point.  When matching an insn, whatever
257appears at this position in the insn will be taken as operand
258number @var{n}; but it must satisfy @var{predicate} or this instruction
259pattern will not match at all.
260
261Operand numbers must be chosen consecutively counting from zero in
262each instruction pattern.  There may be only one @code{match_operand}
263expression in the pattern for each operand number.  Usually operands
264are numbered in the order of appearance in @code{match_operand}
265expressions.  In the case of a @code{define_expand}, any operand numbers
266used only in @code{match_dup} expressions have higher values than all
267other operand numbers.
268
269@var{predicate} is a string that is the name of a function that
270accepts two arguments, an expression and a machine mode.
271@xref{Predicates}.  During matching, the function will be called with
272the putative operand as the expression and @var{m} as the mode
273argument (if @var{m} is not specified, @code{VOIDmode} will be used,
274which normally causes @var{predicate} to accept any mode).  If it
275returns zero, this instruction pattern fails to match.
276@var{predicate} may be an empty string; then it means no test is to be
277done on the operand, so anything which occurs in this position is
278valid.
279
280Most of the time, @var{predicate} will reject modes other than @var{m}---but
281not always.  For example, the predicate @code{address_operand} uses
282@var{m} as the mode of memory ref that the address should be valid for.
283Many predicates accept @code{const_int} nodes even though their mode is
284@code{VOIDmode}.
285
286@var{constraint} controls reloading and the choice of the best register
287class to use for a value, as explained later (@pxref{Constraints}).
288If the constraint would be an empty string, it can be omitted.
289
290People are often unclear on the difference between the constraint and the
291predicate.  The predicate helps decide whether a given insn matches the
292pattern.  The constraint plays no role in this decision; instead, it
293controls various decisions in the case of an insn which does match.
294
295@findex match_scratch
296@item (match_scratch:@var{m} @var{n} @var{constraint})
297This expression is also a placeholder for operand number @var{n}
298and indicates that operand must be a @code{scratch} or @code{reg}
299expression.
300
301When matching patterns, this is equivalent to
302
303@smallexample
304(match_operand:@var{m} @var{n} "scratch_operand" @var{constraint})
305@end smallexample
306
307but, when generating RTL, it produces a (@code{scratch}:@var{m})
308expression.
309
310If the last few expressions in a @code{parallel} are @code{clobber}
311expressions whose operands are either a hard register or
312@code{match_scratch}, the combiner can add or delete them when
313necessary.  @xref{Side Effects}.
314
315@findex match_dup
316@item (match_dup @var{n})
317This expression is also a placeholder for operand number @var{n}.
318It is used when the operand needs to appear more than once in the
319insn.
320
321In construction, @code{match_dup} acts just like @code{match_operand}:
322the operand is substituted into the insn being constructed.  But in
323matching, @code{match_dup} behaves differently.  It assumes that operand
324number @var{n} has already been determined by a @code{match_operand}
325appearing earlier in the recognition template, and it matches only an
326identical-looking expression.
327
328Note that @code{match_dup} should not be used to tell the compiler that
329a particular register is being used for two operands (example:
330@code{add} that adds one register to another; the second register is
331both an input operand and the output operand).  Use a matching
332constraint (@pxref{Simple Constraints}) for those.  @code{match_dup} is for the cases where one
333operand is used in two places in the template, such as an instruction
334that computes both a quotient and a remainder, where the opcode takes
335two input operands but the RTL template has to refer to each of those
336twice; once for the quotient pattern and once for the remainder pattern.
337
338@findex match_operator
339@item (match_operator:@var{m} @var{n} @var{predicate} [@var{operands}@dots{}])
340This pattern is a kind of placeholder for a variable RTL expression
341code.
342
343When constructing an insn, it stands for an RTL expression whose
344expression code is taken from that of operand @var{n}, and whose
345operands are constructed from the patterns @var{operands}.
346
347When matching an expression, it matches an expression if the function
348@var{predicate} returns nonzero on that expression @emph{and} the
349patterns @var{operands} match the operands of the expression.
350
351Suppose that the function @code{commutative_operator} is defined as
352follows, to match any expression whose operator is one of the
353commutative arithmetic operators of RTL and whose mode is @var{mode}:
354
355@smallexample
356int
357commutative_integer_operator (x, mode)
358     rtx x;
359     machine_mode mode;
360@{
361  enum rtx_code code = GET_CODE (x);
362  if (GET_MODE (x) != mode)
363    return 0;
364  return (GET_RTX_CLASS (code) == RTX_COMM_ARITH
365          || code == EQ || code == NE);
366@}
367@end smallexample
368
369Then the following pattern will match any RTL expression consisting
370of a commutative operator applied to two general operands:
371
372@smallexample
373(match_operator:SI 3 "commutative_operator"
374  [(match_operand:SI 1 "general_operand" "g")
375   (match_operand:SI 2 "general_operand" "g")])
376@end smallexample
377
378Here the vector @code{[@var{operands}@dots{}]} contains two patterns
379because the expressions to be matched all contain two operands.
380
381When this pattern does match, the two operands of the commutative
382operator are recorded as operands 1 and 2 of the insn.  (This is done
383by the two instances of @code{match_operand}.)  Operand 3 of the insn
384will be the entire commutative expression: use @code{GET_CODE
385(operands[3])} to see which commutative operator was used.
386
387The machine mode @var{m} of @code{match_operator} works like that of
388@code{match_operand}: it is passed as the second argument to the
389predicate function, and that function is solely responsible for
390deciding whether the expression to be matched ``has'' that mode.
391
392When constructing an insn, argument 3 of the gen-function will specify
393the operation (i.e.@: the expression code) for the expression to be
394made.  It should be an RTL expression, whose expression code is copied
395into a new expression whose operands are arguments 1 and 2 of the
396gen-function.  The subexpressions of argument 3 are not used;
397only its expression code matters.
398
399When @code{match_operator} is used in a pattern for matching an insn,
400it usually best if the operand number of the @code{match_operator}
401is higher than that of the actual operands of the insn.  This improves
402register allocation because the register allocator often looks at
403operands 1 and 2 of insns to see if it can do register tying.
404
405There is no way to specify constraints in @code{match_operator}.  The
406operand of the insn which corresponds to the @code{match_operator}
407never has any constraints because it is never reloaded as a whole.
408However, if parts of its @var{operands} are matched by
409@code{match_operand} patterns, those parts may have constraints of
410their own.
411
412@findex match_op_dup
413@item (match_op_dup:@var{m} @var{n}[@var{operands}@dots{}])
414Like @code{match_dup}, except that it applies to operators instead of
415operands.  When constructing an insn, operand number @var{n} will be
416substituted at this point.  But in matching, @code{match_op_dup} behaves
417differently.  It assumes that operand number @var{n} has already been
418determined by a @code{match_operator} appearing earlier in the
419recognition template, and it matches only an identical-looking
420expression.
421
422@findex match_parallel
423@item (match_parallel @var{n} @var{predicate} [@var{subpat}@dots{}])
424This pattern is a placeholder for an insn that consists of a
425@code{parallel} expression with a variable number of elements.  This
426expression should only appear at the top level of an insn pattern.
427
428When constructing an insn, operand number @var{n} will be substituted at
429this point.  When matching an insn, it matches if the body of the insn
430is a @code{parallel} expression with at least as many elements as the
431vector of @var{subpat} expressions in the @code{match_parallel}, if each
432@var{subpat} matches the corresponding element of the @code{parallel},
433@emph{and} the function @var{predicate} returns nonzero on the
434@code{parallel} that is the body of the insn.  It is the responsibility
435of the predicate to validate elements of the @code{parallel} beyond
436those listed in the @code{match_parallel}.
437
438A typical use of @code{match_parallel} is to match load and store
439multiple expressions, which can contain a variable number of elements
440in a @code{parallel}.  For example,
441
442@smallexample
443(define_insn ""
444  [(match_parallel 0 "load_multiple_operation"
445     [(set (match_operand:SI 1 "gpc_reg_operand" "=r")
446           (match_operand:SI 2 "memory_operand" "m"))
447      (use (reg:SI 179))
448      (clobber (reg:SI 179))])]
449  ""
450  "loadm 0,0,%1,%2")
451@end smallexample
452
453This example comes from @file{a29k.md}.  The function
454@code{load_multiple_operation} is defined in @file{a29k.c} and checks
455that subsequent elements in the @code{parallel} are the same as the
456@code{set} in the pattern, except that they are referencing subsequent
457registers and memory locations.
458
459An insn that matches this pattern might look like:
460
461@smallexample
462(parallel
463 [(set (reg:SI 20) (mem:SI (reg:SI 100)))
464  (use (reg:SI 179))
465  (clobber (reg:SI 179))
466  (set (reg:SI 21)
467       (mem:SI (plus:SI (reg:SI 100)
468                        (const_int 4))))
469  (set (reg:SI 22)
470       (mem:SI (plus:SI (reg:SI 100)
471                        (const_int 8))))])
472@end smallexample
473
474@findex match_par_dup
475@item (match_par_dup @var{n} [@var{subpat}@dots{}])
476Like @code{match_op_dup}, but for @code{match_parallel} instead of
477@code{match_operator}.
478
479@end table
480
481@node Output Template
482@section Output Templates and Operand Substitution
483@cindex output templates
484@cindex operand substitution
485
486@cindex @samp{%} in template
487@cindex percent sign
488The @dfn{output template} is a string which specifies how to output the
489assembler code for an instruction pattern.  Most of the template is a
490fixed string which is output literally.  The character @samp{%} is used
491to specify where to substitute an operand; it can also be used to
492identify places where different variants of the assembler require
493different syntax.
494
495In the simplest case, a @samp{%} followed by a digit @var{n} says to output
496operand @var{n} at that point in the string.
497
498@samp{%} followed by a letter and a digit says to output an operand in an
499alternate fashion.  Four letters have standard, built-in meanings described
500below.  The machine description macro @code{PRINT_OPERAND} can define
501additional letters with nonstandard meanings.
502
503@samp{%c@var{digit}} can be used to substitute an operand that is a
504constant value without the syntax that normally indicates an immediate
505operand.
506
507@samp{%n@var{digit}} is like @samp{%c@var{digit}} except that the value of
508the constant is negated before printing.
509
510@samp{%a@var{digit}} can be used to substitute an operand as if it were a
511memory reference, with the actual operand treated as the address.  This may
512be useful when outputting a ``load address'' instruction, because often the
513assembler syntax for such an instruction requires you to write the operand
514as if it were a memory reference.
515
516@samp{%l@var{digit}} is used to substitute a @code{label_ref} into a jump
517instruction.
518
519@samp{%=} outputs a number which is unique to each instruction in the
520entire compilation.  This is useful for making local labels to be
521referred to more than once in a single template that generates multiple
522assembler instructions.
523
524@samp{%} followed by a punctuation character specifies a substitution that
525does not use an operand.  Only one case is standard: @samp{%%} outputs a
526@samp{%} into the assembler code.  Other nonstandard cases can be
527defined in the @code{PRINT_OPERAND} macro.  You must also define
528which punctuation characters are valid with the
529@code{PRINT_OPERAND_PUNCT_VALID_P} macro.
530
531@cindex \
532@cindex backslash
533The template may generate multiple assembler instructions.  Write the text
534for the instructions, with @samp{\;} between them.
535
536@cindex matching operands
537When the RTL contains two operands which are required by constraint to match
538each other, the output template must refer only to the lower-numbered operand.
539Matching operands are not always identical, and the rest of the compiler
540arranges to put the proper RTL expression for printing into the lower-numbered
541operand.
542
543One use of nonstandard letters or punctuation following @samp{%} is to
544distinguish between different assembler languages for the same machine; for
545example, Motorola syntax versus MIT syntax for the 68000.  Motorola syntax
546requires periods in most opcode names, while MIT syntax does not.  For
547example, the opcode @samp{movel} in MIT syntax is @samp{move.l} in Motorola
548syntax.  The same file of patterns is used for both kinds of output syntax,
549but the character sequence @samp{%.} is used in each place where Motorola
550syntax wants a period.  The @code{PRINT_OPERAND} macro for Motorola syntax
551defines the sequence to output a period; the macro for MIT syntax defines
552it to do nothing.
553
554@cindex @code{#} in template
555As a special case, a template consisting of the single character @code{#}
556instructs the compiler to first split the insn, and then output the
557resulting instructions separately.  This helps eliminate redundancy in the
558output templates.   If you have a @code{define_insn} that needs to emit
559multiple assembler instructions, and there is a matching @code{define_split}
560already defined, then you can simply use @code{#} as the output template
561instead of writing an output template that emits the multiple assembler
562instructions.
563
564If the macro @code{ASSEMBLER_DIALECT} is defined, you can use construct
565of the form @samp{@{option0|option1|option2@}} in the templates.  These
566describe multiple variants of assembler language syntax.
567@xref{Instruction Output}.
568
569@node Output Statement
570@section C Statements for Assembler Output
571@cindex output statements
572@cindex C statements for assembler output
573@cindex generating assembler output
574
575Often a single fixed template string cannot produce correct and efficient
576assembler code for all the cases that are recognized by a single
577instruction pattern.  For example, the opcodes may depend on the kinds of
578operands; or some unfortunate combinations of operands may require extra
579machine instructions.
580
581If the output control string starts with a @samp{@@}, then it is actually
582a series of templates, each on a separate line.  (Blank lines and
583leading spaces and tabs are ignored.)  The templates correspond to the
584pattern's constraint alternatives (@pxref{Multi-Alternative}).  For example,
585if a target machine has a two-address add instruction @samp{addr} to add
586into a register and another @samp{addm} to add a register to memory, you
587might write this pattern:
588
589@smallexample
590(define_insn "addsi3"
591  [(set (match_operand:SI 0 "general_operand" "=r,m")
592        (plus:SI (match_operand:SI 1 "general_operand" "0,0")
593                 (match_operand:SI 2 "general_operand" "g,r")))]
594  ""
595  "@@
596   addr %2,%0
597   addm %2,%0")
598@end smallexample
599
600@cindex @code{*} in template
601@cindex asterisk in template
602If the output control string starts with a @samp{*}, then it is not an
603output template but rather a piece of C program that should compute a
604template.  It should execute a @code{return} statement to return the
605template-string you want.  Most such templates use C string literals, which
606require doublequote characters to delimit them.  To include these
607doublequote characters in the string, prefix each one with @samp{\}.
608
609If the output control string is written as a brace block instead of a
610double-quoted string, it is automatically assumed to be C code.  In that
611case, it is not necessary to put in a leading asterisk, or to escape the
612doublequotes surrounding C string literals.
613
614The operands may be found in the array @code{operands}, whose C data type
615is @code{rtx []}.
616
617It is very common to select different ways of generating assembler code
618based on whether an immediate operand is within a certain range.  Be
619careful when doing this, because the result of @code{INTVAL} is an
620integer on the host machine.  If the host machine has more bits in an
621@code{int} than the target machine has in the mode in which the constant
622will be used, then some of the bits you get from @code{INTVAL} will be
623superfluous.  For proper results, you must carefully disregard the
624values of those bits.
625
626@findex output_asm_insn
627It is possible to output an assembler instruction and then go on to output
628or compute more of them, using the subroutine @code{output_asm_insn}.  This
629receives two arguments: a template-string and a vector of operands.  The
630vector may be @code{operands}, or it may be another array of @code{rtx}
631that you declare locally and initialize yourself.
632
633@findex which_alternative
634When an insn pattern has multiple alternatives in its constraints, often
635the appearance of the assembler code is determined mostly by which alternative
636was matched.  When this is so, the C code can test the variable
637@code{which_alternative}, which is the ordinal number of the alternative
638that was actually satisfied (0 for the first, 1 for the second alternative,
639etc.).
640
641For example, suppose there are two opcodes for storing zero, @samp{clrreg}
642for registers and @samp{clrmem} for memory locations.  Here is how
643a pattern could use @code{which_alternative} to choose between them:
644
645@smallexample
646(define_insn ""
647  [(set (match_operand:SI 0 "general_operand" "=r,m")
648        (const_int 0))]
649  ""
650  @{
651  return (which_alternative == 0
652          ? "clrreg %0" : "clrmem %0");
653  @})
654@end smallexample
655
656The example above, where the assembler code to generate was
657@emph{solely} determined by the alternative, could also have been specified
658as follows, having the output control string start with a @samp{@@}:
659
660@smallexample
661@group
662(define_insn ""
663  [(set (match_operand:SI 0 "general_operand" "=r,m")
664        (const_int 0))]
665  ""
666  "@@
667   clrreg %0
668   clrmem %0")
669@end group
670@end smallexample
671
672If you just need a little bit of C code in one (or a few) alternatives,
673you can use @samp{*} inside of a @samp{@@} multi-alternative template:
674
675@smallexample
676@group
677(define_insn ""
678  [(set (match_operand:SI 0 "general_operand" "=r,<,m")
679        (const_int 0))]
680  ""
681  "@@
682   clrreg %0
683   * return stack_mem_p (operands[0]) ? \"push 0\" : \"clrmem %0\";
684   clrmem %0")
685@end group
686@end smallexample
687
688@node Predicates
689@section Predicates
690@cindex predicates
691@cindex operand predicates
692@cindex operator predicates
693
694A predicate determines whether a @code{match_operand} or
695@code{match_operator} expression matches, and therefore whether the
696surrounding instruction pattern will be used for that combination of
697operands.  GCC has a number of machine-independent predicates, and you
698can define machine-specific predicates as needed.  By convention,
699predicates used with @code{match_operand} have names that end in
700@samp{_operand}, and those used with @code{match_operator} have names
701that end in @samp{_operator}.
702
703All predicates are Boolean functions (in the mathematical sense) of
704two arguments: the RTL expression that is being considered at that
705position in the instruction pattern, and the machine mode that the
706@code{match_operand} or @code{match_operator} specifies.  In this
707section, the first argument is called @var{op} and the second argument
708@var{mode}.  Predicates can be called from C as ordinary two-argument
709functions; this can be useful in output templates or other
710machine-specific code.
711
712Operand predicates can allow operands that are not actually acceptable
713to the hardware, as long as the constraints give reload the ability to
714fix them up (@pxref{Constraints}).  However, GCC will usually generate
715better code if the predicates specify the requirements of the machine
716instructions as closely as possible.  Reload cannot fix up operands
717that must be constants (``immediate operands''); you must use a
718predicate that allows only constants, or else enforce the requirement
719in the extra condition.
720
721@cindex predicates and machine modes
722@cindex normal predicates
723@cindex special predicates
724Most predicates handle their @var{mode} argument in a uniform manner.
725If @var{mode} is @code{VOIDmode} (unspecified), then @var{op} can have
726any mode.  If @var{mode} is anything else, then @var{op} must have the
727same mode, unless @var{op} is a @code{CONST_INT} or integer
728@code{CONST_DOUBLE}.  These RTL expressions always have
729@code{VOIDmode}, so it would be counterproductive to check that their
730mode matches.  Instead, predicates that accept @code{CONST_INT} and/or
731integer @code{CONST_DOUBLE} check that the value stored in the
732constant will fit in the requested mode.
733
734Predicates with this behavior are called @dfn{normal}.
735@command{genrecog} can optimize the instruction recognizer based on
736knowledge of how normal predicates treat modes.  It can also diagnose
737certain kinds of common errors in the use of normal predicates; for
738instance, it is almost always an error to use a normal predicate
739without specifying a mode.
740
741Predicates that do something different with their @var{mode} argument
742are called @dfn{special}.  The generic predicates
743@code{address_operand} and @code{pmode_register_operand} are special
744predicates.  @command{genrecog} does not do any optimizations or
745diagnosis when special predicates are used.
746
747@menu
748* Machine-Independent Predicates::  Predicates available to all back ends.
749* Defining Predicates::             How to write machine-specific predicate
750                                    functions.
751@end menu
752
753@node Machine-Independent Predicates
754@subsection Machine-Independent Predicates
755@cindex machine-independent predicates
756@cindex generic predicates
757
758These are the generic predicates available to all back ends.  They are
759defined in @file{recog.c}.  The first category of predicates allow
760only constant, or @dfn{immediate}, operands.
761
762@defun immediate_operand
763This predicate allows any sort of constant that fits in @var{mode}.
764It is an appropriate choice for instructions that take operands that
765must be constant.
766@end defun
767
768@defun const_int_operand
769This predicate allows any @code{CONST_INT} expression that fits in
770@var{mode}.  It is an appropriate choice for an immediate operand that
771does not allow a symbol or label.
772@end defun
773
774@defun const_double_operand
775This predicate accepts any @code{CONST_DOUBLE} expression that has
776exactly @var{mode}.  If @var{mode} is @code{VOIDmode}, it will also
777accept @code{CONST_INT}.  It is intended for immediate floating point
778constants.
779@end defun
780
781@noindent
782The second category of predicates allow only some kind of machine
783register.
784
785@defun register_operand
786This predicate allows any @code{REG} or @code{SUBREG} expression that
787is valid for @var{mode}.  It is often suitable for arithmetic
788instruction operands on a RISC machine.
789@end defun
790
791@defun pmode_register_operand
792This is a slight variant on @code{register_operand} which works around
793a limitation in the machine-description reader.
794
795@smallexample
796(match_operand @var{n} "pmode_register_operand" @var{constraint})
797@end smallexample
798
799@noindent
800means exactly what
801
802@smallexample
803(match_operand:P @var{n} "register_operand" @var{constraint})
804@end smallexample
805
806@noindent
807would mean, if the machine-description reader accepted @samp{:P}
808mode suffixes.  Unfortunately, it cannot, because @code{Pmode} is an
809alias for some other mode, and might vary with machine-specific
810options.  @xref{Misc}.
811@end defun
812
813@defun scratch_operand
814This predicate allows hard registers and @code{SCRATCH} expressions,
815but not pseudo-registers.  It is used internally by @code{match_scratch};
816it should not be used directly.
817@end defun
818
819@noindent
820The third category of predicates allow only some kind of memory reference.
821
822@defun memory_operand
823This predicate allows any valid reference to a quantity of mode
824@var{mode} in memory, as determined by the weak form of
825@code{GO_IF_LEGITIMATE_ADDRESS} (@pxref{Addressing Modes}).
826@end defun
827
828@defun address_operand
829This predicate is a little unusual; it allows any operand that is a
830valid expression for the @emph{address} of a quantity of mode
831@var{mode}, again determined by the weak form of
832@code{GO_IF_LEGITIMATE_ADDRESS}.  To first order, if
833@samp{@w{(mem:@var{mode} (@var{exp}))}} is acceptable to
834@code{memory_operand}, then @var{exp} is acceptable to
835@code{address_operand}.  Note that @var{exp} does not necessarily have
836the mode @var{mode}.
837@end defun
838
839@defun indirect_operand
840This is a stricter form of @code{memory_operand} which allows only
841memory references with a @code{general_operand} as the address
842expression.  New uses of this predicate are discouraged, because
843@code{general_operand} is very permissive, so it's hard to tell what
844an @code{indirect_operand} does or does not allow.  If a target has
845different requirements for memory operands for different instructions,
846it is better to define target-specific predicates which enforce the
847hardware's requirements explicitly.
848@end defun
849
850@defun push_operand
851This predicate allows a memory reference suitable for pushing a value
852onto the stack.  This will be a @code{MEM} which refers to
853@code{stack_pointer_rtx}, with a side-effect in its address expression
854(@pxref{Incdec}); which one is determined by the
855@code{STACK_PUSH_CODE} macro (@pxref{Frame Layout}).
856@end defun
857
858@defun pop_operand
859This predicate allows a memory reference suitable for popping a value
860off the stack.  Again, this will be a @code{MEM} referring to
861@code{stack_pointer_rtx}, with a side-effect in its address
862expression.  However, this time @code{STACK_POP_CODE} is expected.
863@end defun
864
865@noindent
866The fourth category of predicates allow some combination of the above
867operands.
868
869@defun nonmemory_operand
870This predicate allows any immediate or register operand valid for @var{mode}.
871@end defun
872
873@defun nonimmediate_operand
874This predicate allows any register or memory operand valid for @var{mode}.
875@end defun
876
877@defun general_operand
878This predicate allows any immediate, register, or memory operand
879valid for @var{mode}.
880@end defun
881
882@noindent
883Finally, there are two generic operator predicates.
884
885@defun comparison_operator
886This predicate matches any expression which performs an arithmetic
887comparison in @var{mode}; that is, @code{COMPARISON_P} is true for the
888expression code.
889@end defun
890
891@defun ordered_comparison_operator
892This predicate matches any expression which performs an arithmetic
893comparison in @var{mode} and whose expression code is valid for integer
894modes; that is, the expression code will be one of @code{eq}, @code{ne},
895@code{lt}, @code{ltu}, @code{le}, @code{leu}, @code{gt}, @code{gtu},
896@code{ge}, @code{geu}.
897@end defun
898
899@node Defining Predicates
900@subsection Defining Machine-Specific Predicates
901@cindex defining predicates
902@findex define_predicate
903@findex define_special_predicate
904
905Many machines have requirements for their operands that cannot be
906expressed precisely using the generic predicates.  You can define
907additional predicates using @code{define_predicate} and
908@code{define_special_predicate} expressions.  These expressions have
909three operands:
910
911@itemize @bullet
912@item
913The name of the predicate, as it will be referred to in
914@code{match_operand} or @code{match_operator} expressions.
915
916@item
917An RTL expression which evaluates to true if the predicate allows the
918operand @var{op}, false if it does not.  This expression can only use
919the following RTL codes:
920
921@table @code
922@item MATCH_OPERAND
923When written inside a predicate expression, a @code{MATCH_OPERAND}
924expression evaluates to true if the predicate it names would allow
925@var{op}.  The operand number and constraint are ignored.  Due to
926limitations in @command{genrecog}, you can only refer to generic
927predicates and predicates that have already been defined.
928
929@item MATCH_CODE
930This expression evaluates to true if @var{op} or a specified
931subexpression of @var{op} has one of a given list of RTX codes.
932
933The first operand of this expression is a string constant containing a
934comma-separated list of RTX code names (in lower case).  These are the
935codes for which the @code{MATCH_CODE} will be true.
936
937The second operand is a string constant which indicates what
938subexpression of @var{op} to examine.  If it is absent or the empty
939string, @var{op} itself is examined.  Otherwise, the string constant
940must be a sequence of digits and/or lowercase letters.  Each character
941indicates a subexpression to extract from the current expression; for
942the first character this is @var{op}, for the second and subsequent
943characters it is the result of the previous character.  A digit
944@var{n} extracts @samp{@w{XEXP (@var{e}, @var{n})}}; a letter @var{l}
945extracts @samp{@w{XVECEXP (@var{e}, 0, @var{n})}} where @var{n} is the
946alphabetic ordinal of @var{l} (0 for `a', 1 for 'b', and so on).  The
947@code{MATCH_CODE} then examines the RTX code of the subexpression
948extracted by the complete string.  It is not possible to extract
949components of an @code{rtvec} that is not at position 0 within its RTX
950object.
951
952@item MATCH_TEST
953This expression has one operand, a string constant containing a C
954expression.  The predicate's arguments, @var{op} and @var{mode}, are
955available with those names in the C expression.  The @code{MATCH_TEST}
956evaluates to true if the C expression evaluates to a nonzero value.
957@code{MATCH_TEST} expressions must not have side effects.
958
959@item  AND
960@itemx IOR
961@itemx NOT
962@itemx IF_THEN_ELSE
963The basic @samp{MATCH_} expressions can be combined using these
964logical operators, which have the semantics of the C operators
965@samp{&&}, @samp{||}, @samp{!}, and @samp{@w{? :}} respectively.  As
966in Common Lisp, you may give an @code{AND} or @code{IOR} expression an
967arbitrary number of arguments; this has exactly the same effect as
968writing a chain of two-argument @code{AND} or @code{IOR} expressions.
969@end table
970
971@item
972An optional block of C code, which should execute
973@samp{@w{return true}} if the predicate is found to match and
974@samp{@w{return false}} if it does not.  It must not have any side
975effects.  The predicate arguments, @var{op} and @var{mode}, are
976available with those names.
977
978If a code block is present in a predicate definition, then the RTL
979expression must evaluate to true @emph{and} the code block must
980execute @samp{@w{return true}} for the predicate to allow the operand.
981The RTL expression is evaluated first; do not re-check anything in the
982code block that was checked in the RTL expression.
983@end itemize
984
985The program @command{genrecog} scans @code{define_predicate} and
986@code{define_special_predicate} expressions to determine which RTX
987codes are possibly allowed.  You should always make this explicit in
988the RTL predicate expression, using @code{MATCH_OPERAND} and
989@code{MATCH_CODE}.
990
991Here is an example of a simple predicate definition, from the IA64
992machine description:
993
994@smallexample
995@group
996;; @r{True if @var{op} is a @code{SYMBOL_REF} which refers to the sdata section.}
997(define_predicate "small_addr_symbolic_operand"
998  (and (match_code "symbol_ref")
999       (match_test "SYMBOL_REF_SMALL_ADDR_P (op)")))
1000@end group
1001@end smallexample
1002
1003@noindent
1004And here is another, showing the use of the C block.
1005
1006@smallexample
1007@group
1008;; @r{True if @var{op} is a register operand that is (or could be) a GR reg.}
1009(define_predicate "gr_register_operand"
1010  (match_operand 0 "register_operand")
1011@{
1012  unsigned int regno;
1013  if (GET_CODE (op) == SUBREG)
1014    op = SUBREG_REG (op);
1015
1016  regno = REGNO (op);
1017  return (regno >= FIRST_PSEUDO_REGISTER || GENERAL_REGNO_P (regno));
1018@})
1019@end group
1020@end smallexample
1021
1022Predicates written with @code{define_predicate} automatically include
1023a test that @var{mode} is @code{VOIDmode}, or @var{op} has the same
1024mode as @var{mode}, or @var{op} is a @code{CONST_INT} or
1025@code{CONST_DOUBLE}.  They do @emph{not} check specifically for
1026integer @code{CONST_DOUBLE}, nor do they test that the value of either
1027kind of constant fits in the requested mode.  This is because
1028target-specific predicates that take constants usually have to do more
1029stringent value checks anyway.  If you need the exact same treatment
1030of @code{CONST_INT} or @code{CONST_DOUBLE} that the generic predicates
1031provide, use a @code{MATCH_OPERAND} subexpression to call
1032@code{const_int_operand}, @code{const_double_operand}, or
1033@code{immediate_operand}.
1034
1035Predicates written with @code{define_special_predicate} do not get any
1036automatic mode checks, and are treated as having special mode handling
1037by @command{genrecog}.
1038
1039The program @command{genpreds} is responsible for generating code to
1040test predicates.  It also writes a header file containing function
1041declarations for all machine-specific predicates.  It is not necessary
1042to declare these predicates in @file{@var{cpu}-protos.h}.
1043@end ifset
1044
1045@c Most of this node appears by itself (in a different place) even
1046@c when the INTERNALS flag is clear.  Passages that require the internals
1047@c manual's context are conditionalized to appear only in the internals manual.
1048@ifset INTERNALS
1049@node Constraints
1050@section Operand Constraints
1051@cindex operand constraints
1052@cindex constraints
1053
1054Each @code{match_operand} in an instruction pattern can specify
1055constraints for the operands allowed.  The constraints allow you to
1056fine-tune matching within the set of operands allowed by the
1057predicate.
1058
1059@end ifset
1060@ifclear INTERNALS
1061@node Constraints
1062@section Constraints for @code{asm} Operands
1063@cindex operand constraints, @code{asm}
1064@cindex constraints, @code{asm}
1065@cindex @code{asm} constraints
1066
1067Here are specific details on what constraint letters you can use with
1068@code{asm} operands.
1069@end ifclear
1070Constraints can say whether
1071an operand may be in a register, and which kinds of register; whether the
1072operand can be a memory reference, and which kinds of address; whether the
1073operand may be an immediate constant, and which possible values it may
1074have.  Constraints can also require two operands to match.
1075Side-effects aren't allowed in operands of inline @code{asm}, unless
1076@samp{<} or @samp{>} constraints are used, because there is no guarantee
1077that the side-effects will happen exactly once in an instruction that can update
1078the addressing register.
1079
1080@ifset INTERNALS
1081@menu
1082* Simple Constraints::  Basic use of constraints.
1083* Multi-Alternative::   When an insn has two alternative constraint-patterns.
1084* Class Preferences::   Constraints guide which hard register to put things in.
1085* Modifiers::           More precise control over effects of constraints.
1086* Machine Constraints:: Existing constraints for some particular machines.
1087* Disable Insn Alternatives:: Disable insn alternatives using attributes.
1088* Define Constraints::  How to define machine-specific constraints.
1089* C Constraint Interface:: How to test constraints from C code.
1090@end menu
1091@end ifset
1092
1093@ifclear INTERNALS
1094@menu
1095* Simple Constraints::  Basic use of constraints.
1096* Multi-Alternative::   When an insn has two alternative constraint-patterns.
1097* Modifiers::           More precise control over effects of constraints.
1098* Machine Constraints:: Special constraints for some particular machines.
1099@end menu
1100@end ifclear
1101
1102@node Simple Constraints
1103@subsection Simple Constraints
1104@cindex simple constraints
1105
1106The simplest kind of constraint is a string full of letters, each of
1107which describes one kind of operand that is permitted.  Here are
1108the letters that are allowed:
1109
1110@table @asis
1111@item whitespace
1112Whitespace characters are ignored and can be inserted at any position
1113except the first.  This enables each alternative for different operands to
1114be visually aligned in the machine description even if they have different
1115number of constraints and modifiers.
1116
1117@cindex @samp{m} in constraint
1118@cindex memory references in constraints
1119@item @samp{m}
1120A memory operand is allowed, with any kind of address that the machine
1121supports in general.
1122Note that the letter used for the general memory constraint can be
1123re-defined by a back end using the @code{TARGET_MEM_CONSTRAINT} macro.
1124
1125@cindex offsettable address
1126@cindex @samp{o} in constraint
1127@item @samp{o}
1128A memory operand is allowed, but only if the address is
1129@dfn{offsettable}.  This means that adding a small integer (actually,
1130the width in bytes of the operand, as determined by its machine mode)
1131may be added to the address and the result is also a valid memory
1132address.
1133
1134@cindex autoincrement/decrement addressing
1135For example, an address which is constant is offsettable; so is an
1136address that is the sum of a register and a constant (as long as a
1137slightly larger constant is also within the range of address-offsets
1138supported by the machine); but an autoincrement or autodecrement
1139address is not offsettable.  More complicated indirect/indexed
1140addresses may or may not be offsettable depending on the other
1141addressing modes that the machine supports.
1142
1143Note that in an output operand which can be matched by another
1144operand, the constraint letter @samp{o} is valid only when accompanied
1145by both @samp{<} (if the target machine has predecrement addressing)
1146and @samp{>} (if the target machine has preincrement addressing).
1147
1148@cindex @samp{V} in constraint
1149@item @samp{V}
1150A memory operand that is not offsettable.  In other words, anything that
1151would fit the @samp{m} constraint but not the @samp{o} constraint.
1152
1153@cindex @samp{<} in constraint
1154@item @samp{<}
1155A memory operand with autodecrement addressing (either predecrement or
1156postdecrement) is allowed.  In inline @code{asm} this constraint is only
1157allowed if the operand is used exactly once in an instruction that can
1158handle the side-effects.  Not using an operand with @samp{<} in constraint
1159string in the inline @code{asm} pattern at all or using it in multiple
1160instructions isn't valid, because the side-effects wouldn't be performed
1161or would be performed more than once.  Furthermore, on some targets
1162the operand with @samp{<} in constraint string must be accompanied by
1163special instruction suffixes like @code{%U0} instruction suffix on PowerPC
1164or @code{%P0} on IA-64.
1165
1166@cindex @samp{>} in constraint
1167@item @samp{>}
1168A memory operand with autoincrement addressing (either preincrement or
1169postincrement) is allowed.  In inline @code{asm} the same restrictions
1170as for @samp{<} apply.
1171
1172@cindex @samp{r} in constraint
1173@cindex registers in constraints
1174@item @samp{r}
1175A register operand is allowed provided that it is in a general
1176register.
1177
1178@cindex constants in constraints
1179@cindex @samp{i} in constraint
1180@item @samp{i}
1181An immediate integer operand (one with constant value) is allowed.
1182This includes symbolic constants whose values will be known only at
1183assembly time or later.
1184
1185@cindex @samp{n} in constraint
1186@item @samp{n}
1187An immediate integer operand with a known numeric value is allowed.
1188Many systems cannot support assembly-time constants for operands less
1189than a word wide.  Constraints for these operands should use @samp{n}
1190rather than @samp{i}.
1191
1192@cindex @samp{I} in constraint
1193@item @samp{I}, @samp{J}, @samp{K}, @dots{} @samp{P}
1194Other letters in the range @samp{I} through @samp{P} may be defined in
1195a machine-dependent fashion to permit immediate integer operands with
1196explicit integer values in specified ranges.  For example, on the
119768000, @samp{I} is defined to stand for the range of values 1 to 8.
1198This is the range permitted as a shift count in the shift
1199instructions.
1200
1201@cindex @samp{E} in constraint
1202@item @samp{E}
1203An immediate floating operand (expression code @code{const_double}) is
1204allowed, but only if the target floating point format is the same as
1205that of the host machine (on which the compiler is running).
1206
1207@cindex @samp{F} in constraint
1208@item @samp{F}
1209An immediate floating operand (expression code @code{const_double} or
1210@code{const_vector}) is allowed.
1211
1212@cindex @samp{G} in constraint
1213@cindex @samp{H} in constraint
1214@item @samp{G}, @samp{H}
1215@samp{G} and @samp{H} may be defined in a machine-dependent fashion to
1216permit immediate floating operands in particular ranges of values.
1217
1218@cindex @samp{s} in constraint
1219@item @samp{s}
1220An immediate integer operand whose value is not an explicit integer is
1221allowed.
1222
1223This might appear strange; if an insn allows a constant operand with a
1224value not known at compile time, it certainly must allow any known
1225value.  So why use @samp{s} instead of @samp{i}?  Sometimes it allows
1226better code to be generated.
1227
1228For example, on the 68000 in a fullword instruction it is possible to
1229use an immediate operand; but if the immediate value is between @minus{}128
1230and 127, better code results from loading the value into a register and
1231using the register.  This is because the load into the register can be
1232done with a @samp{moveq} instruction.  We arrange for this to happen
1233by defining the letter @samp{K} to mean ``any integer outside the
1234range @minus{}128 to 127'', and then specifying @samp{Ks} in the operand
1235constraints.
1236
1237@cindex @samp{g} in constraint
1238@item @samp{g}
1239Any register, memory or immediate integer operand is allowed, except for
1240registers that are not general registers.
1241
1242@cindex @samp{X} in constraint
1243@item @samp{X}
1244@ifset INTERNALS
1245Any operand whatsoever is allowed, even if it does not satisfy
1246@code{general_operand}.  This is normally used in the constraint of
1247a @code{match_scratch} when certain alternatives will not actually
1248require a scratch register.
1249@end ifset
1250@ifclear INTERNALS
1251Any operand whatsoever is allowed.
1252@end ifclear
1253
1254@cindex @samp{0} in constraint
1255@cindex digits in constraint
1256@item @samp{0}, @samp{1}, @samp{2}, @dots{} @samp{9}
1257An operand that matches the specified operand number is allowed.  If a
1258digit is used together with letters within the same alternative, the
1259digit should come last.
1260
1261This number is allowed to be more than a single digit.  If multiple
1262digits are encountered consecutively, they are interpreted as a single
1263decimal integer.  There is scant chance for ambiguity, since to-date
1264it has never been desirable that @samp{10} be interpreted as matching
1265either operand 1 @emph{or} operand 0.  Should this be desired, one
1266can use multiple alternatives instead.
1267
1268@cindex matching constraint
1269@cindex constraint, matching
1270This is called a @dfn{matching constraint} and what it really means is
1271that the assembler has only a single operand that fills two roles
1272@ifset INTERNALS
1273considered separate in the RTL insn.  For example, an add insn has two
1274input operands and one output operand in the RTL, but on most CISC
1275@end ifset
1276@ifclear INTERNALS
1277which @code{asm} distinguishes.  For example, an add instruction uses
1278two input operands and an output operand, but on most CISC
1279@end ifclear
1280machines an add instruction really has only two operands, one of them an
1281input-output operand:
1282
1283@smallexample
1284addl #35,r12
1285@end smallexample
1286
1287Matching constraints are used in these circumstances.
1288More precisely, the two operands that match must include one input-only
1289operand and one output-only operand.  Moreover, the digit must be a
1290smaller number than the number of the operand that uses it in the
1291constraint.
1292
1293@ifset INTERNALS
1294For operands to match in a particular case usually means that they
1295are identical-looking RTL expressions.  But in a few special cases
1296specific kinds of dissimilarity are allowed.  For example, @code{*x}
1297as an input operand will match @code{*x++} as an output operand.
1298For proper results in such cases, the output template should always
1299use the output-operand's number when printing the operand.
1300@end ifset
1301
1302@cindex load address instruction
1303@cindex push address instruction
1304@cindex address constraints
1305@cindex @samp{p} in constraint
1306@item @samp{p}
1307An operand that is a valid memory address is allowed.  This is
1308for ``load address'' and ``push address'' instructions.
1309
1310@findex address_operand
1311@samp{p} in the constraint must be accompanied by @code{address_operand}
1312as the predicate in the @code{match_operand}.  This predicate interprets
1313the mode specified in the @code{match_operand} as the mode of the memory
1314reference for which the address would be valid.
1315
1316@cindex other register constraints
1317@cindex extensible constraints
1318@item @var{other-letters}
1319Other letters can be defined in machine-dependent fashion to stand for
1320particular classes of registers or other arbitrary operand types.
1321@samp{d}, @samp{a} and @samp{f} are defined on the 68000/68020 to stand
1322for data, address and floating point registers.
1323@end table
1324
1325@ifset INTERNALS
1326In order to have valid assembler code, each operand must satisfy
1327its constraint.  But a failure to do so does not prevent the pattern
1328from applying to an insn.  Instead, it directs the compiler to modify
1329the code so that the constraint will be satisfied.  Usually this is
1330done by copying an operand into a register.
1331
1332Contrast, therefore, the two instruction patterns that follow:
1333
1334@smallexample
1335(define_insn ""
1336  [(set (match_operand:SI 0 "general_operand" "=r")
1337        (plus:SI (match_dup 0)
1338                 (match_operand:SI 1 "general_operand" "r")))]
1339  ""
1340  "@dots{}")
1341@end smallexample
1342
1343@noindent
1344which has two operands, one of which must appear in two places, and
1345
1346@smallexample
1347(define_insn ""
1348  [(set (match_operand:SI 0 "general_operand" "=r")
1349        (plus:SI (match_operand:SI 1 "general_operand" "0")
1350                 (match_operand:SI 2 "general_operand" "r")))]
1351  ""
1352  "@dots{}")
1353@end smallexample
1354
1355@noindent
1356which has three operands, two of which are required by a constraint to be
1357identical.  If we are considering an insn of the form
1358
1359@smallexample
1360(insn @var{n} @var{prev} @var{next}
1361  (set (reg:SI 3)
1362       (plus:SI (reg:SI 6) (reg:SI 109)))
1363  @dots{})
1364@end smallexample
1365
1366@noindent
1367the first pattern would not apply at all, because this insn does not
1368contain two identical subexpressions in the right place.  The pattern would
1369say, ``That does not look like an add instruction; try other patterns''.
1370The second pattern would say, ``Yes, that's an add instruction, but there
1371is something wrong with it''.  It would direct the reload pass of the
1372compiler to generate additional insns to make the constraint true.  The
1373results might look like this:
1374
1375@smallexample
1376(insn @var{n2} @var{prev} @var{n}
1377  (set (reg:SI 3) (reg:SI 6))
1378  @dots{})
1379
1380(insn @var{n} @var{n2} @var{next}
1381  (set (reg:SI 3)
1382       (plus:SI (reg:SI 3) (reg:SI 109)))
1383  @dots{})
1384@end smallexample
1385
1386It is up to you to make sure that each operand, in each pattern, has
1387constraints that can handle any RTL expression that could be present for
1388that operand.  (When multiple alternatives are in use, each pattern must,
1389for each possible combination of operand expressions, have at least one
1390alternative which can handle that combination of operands.)  The
1391constraints don't need to @emph{allow} any possible operand---when this is
1392the case, they do not constrain---but they must at least point the way to
1393reloading any possible operand so that it will fit.
1394
1395@itemize @bullet
1396@item
1397If the constraint accepts whatever operands the predicate permits,
1398there is no problem: reloading is never necessary for this operand.
1399
1400For example, an operand whose constraints permit everything except
1401registers is safe provided its predicate rejects registers.
1402
1403An operand whose predicate accepts only constant values is safe
1404provided its constraints include the letter @samp{i}.  If any possible
1405constant value is accepted, then nothing less than @samp{i} will do;
1406if the predicate is more selective, then the constraints may also be
1407more selective.
1408
1409@item
1410Any operand expression can be reloaded by copying it into a register.
1411So if an operand's constraints allow some kind of register, it is
1412certain to be safe.  It need not permit all classes of registers; the
1413compiler knows how to copy a register into another register of the
1414proper class in order to make an instruction valid.
1415
1416@cindex nonoffsettable memory reference
1417@cindex memory reference, nonoffsettable
1418@item
1419A nonoffsettable memory reference can be reloaded by copying the
1420address into a register.  So if the constraint uses the letter
1421@samp{o}, all memory references are taken care of.
1422
1423@item
1424A constant operand can be reloaded by allocating space in memory to
1425hold it as preinitialized data.  Then the memory reference can be used
1426in place of the constant.  So if the constraint uses the letters
1427@samp{o} or @samp{m}, constant operands are not a problem.
1428
1429@item
1430If the constraint permits a constant and a pseudo register used in an insn
1431was not allocated to a hard register and is equivalent to a constant,
1432the register will be replaced with the constant.  If the predicate does
1433not permit a constant and the insn is re-recognized for some reason, the
1434compiler will crash.  Thus the predicate must always recognize any
1435objects allowed by the constraint.
1436@end itemize
1437
1438If the operand's predicate can recognize registers, but the constraint does
1439not permit them, it can make the compiler crash.  When this operand happens
1440to be a register, the reload pass will be stymied, because it does not know
1441how to copy a register temporarily into memory.
1442
1443If the predicate accepts a unary operator, the constraint applies to the
1444operand.  For example, the MIPS processor at ISA level 3 supports an
1445instruction which adds two registers in @code{SImode} to produce a
1446@code{DImode} result, but only if the registers are correctly sign
1447extended.  This predicate for the input operands accepts a
1448@code{sign_extend} of an @code{SImode} register.  Write the constraint
1449to indicate the type of register that is required for the operand of the
1450@code{sign_extend}.
1451@end ifset
1452
1453@node Multi-Alternative
1454@subsection Multiple Alternative Constraints
1455@cindex multiple alternative constraints
1456
1457Sometimes a single instruction has multiple alternative sets of possible
1458operands.  For example, on the 68000, a logical-or instruction can combine
1459register or an immediate value into memory, or it can combine any kind of
1460operand into a register; but it cannot combine one memory location into
1461another.
1462
1463These constraints are represented as multiple alternatives.  An alternative
1464can be described by a series of letters for each operand.  The overall
1465constraint for an operand is made from the letters for this operand
1466from the first alternative, a comma, the letters for this operand from
1467the second alternative, a comma, and so on until the last alternative.
1468@ifset INTERNALS
1469Here is how it is done for fullword logical-or on the 68000:
1470
1471@smallexample
1472(define_insn "iorsi3"
1473  [(set (match_operand:SI 0 "general_operand" "=m,d")
1474        (ior:SI (match_operand:SI 1 "general_operand" "%0,0")
1475                (match_operand:SI 2 "general_operand" "dKs,dmKs")))]
1476  @dots{})
1477@end smallexample
1478
1479The first alternative has @samp{m} (memory) for operand 0, @samp{0} for
1480operand 1 (meaning it must match operand 0), and @samp{dKs} for operand
14812.  The second alternative has @samp{d} (data register) for operand 0,
1482@samp{0} for operand 1, and @samp{dmKs} for operand 2.  The @samp{=} and
1483@samp{%} in the constraints apply to all the alternatives; their
1484meaning is explained in the next section (@pxref{Class Preferences}).
1485@end ifset
1486
1487@c FIXME Is this ? and ! stuff of use in asm()?  If not, hide unless INTERNAL
1488If all the operands fit any one alternative, the instruction is valid.
1489Otherwise, for each alternative, the compiler counts how many instructions
1490must be added to copy the operands so that that alternative applies.
1491The alternative requiring the least copying is chosen.  If two alternatives
1492need the same amount of copying, the one that comes first is chosen.
1493These choices can be altered with the @samp{?} and @samp{!} characters:
1494
1495@table @code
1496@cindex @samp{?} in constraint
1497@cindex question mark
1498@item ?
1499Disparage slightly the alternative that the @samp{?} appears in,
1500as a choice when no alternative applies exactly.  The compiler regards
1501this alternative as one unit more costly for each @samp{?} that appears
1502in it.
1503
1504@cindex @samp{!} in constraint
1505@cindex exclamation point
1506@item !
1507Disparage severely the alternative that the @samp{!} appears in.
1508This alternative can still be used if it fits without reloading,
1509but if reloading is needed, some other alternative will be used.
1510
1511@cindex @samp{^} in constraint
1512@cindex caret
1513@item ^
1514This constraint is analogous to @samp{?} but it disparages slightly
1515the alternative only if the operand with the @samp{^} needs a reload.
1516
1517@cindex @samp{$} in constraint
1518@cindex dollar sign
1519@item $
1520This constraint is analogous to @samp{!} but it disparages severely
1521the alternative only if the operand with the @samp{$} needs a reload.
1522@end table
1523
1524@ifset INTERNALS
1525When an insn pattern has multiple alternatives in its constraints, often
1526the appearance of the assembler code is determined mostly by which
1527alternative was matched.  When this is so, the C code for writing the
1528assembler code can use the variable @code{which_alternative}, which is
1529the ordinal number of the alternative that was actually satisfied (0 for
1530the first, 1 for the second alternative, etc.).  @xref{Output Statement}.
1531@end ifset
1532
1533@ifset INTERNALS
1534@node Class Preferences
1535@subsection Register Class Preferences
1536@cindex class preference constraints
1537@cindex register class preference constraints
1538
1539@cindex voting between constraint alternatives
1540The operand constraints have another function: they enable the compiler
1541to decide which kind of hardware register a pseudo register is best
1542allocated to.  The compiler examines the constraints that apply to the
1543insns that use the pseudo register, looking for the machine-dependent
1544letters such as @samp{d} and @samp{a} that specify classes of registers.
1545The pseudo register is put in whichever class gets the most ``votes''.
1546The constraint letters @samp{g} and @samp{r} also vote: they vote in
1547favor of a general register.  The machine description says which registers
1548are considered general.
1549
1550Of course, on some machines all registers are equivalent, and no register
1551classes are defined.  Then none of this complexity is relevant.
1552@end ifset
1553
1554@node Modifiers
1555@subsection Constraint Modifier Characters
1556@cindex modifiers in constraints
1557@cindex constraint modifier characters
1558
1559@c prevent bad page break with this line
1560Here are constraint modifier characters.
1561
1562@table @samp
1563@cindex @samp{=} in constraint
1564@item =
1565Means that this operand is written to by this instruction:
1566the previous value is discarded and replaced by new data.
1567
1568@cindex @samp{+} in constraint
1569@item +
1570Means that this operand is both read and written by the instruction.
1571
1572When the compiler fixes up the operands to satisfy the constraints,
1573it needs to know which operands are read by the instruction and
1574which are written by it.  @samp{=} identifies an operand which is only
1575written; @samp{+} identifies an operand that is both read and written; all
1576other operands are assumed to only be read.
1577
1578If you specify @samp{=} or @samp{+} in a constraint, you put it in the
1579first character of the constraint string.
1580
1581@cindex @samp{&} in constraint
1582@cindex earlyclobber operand
1583@item &
1584Means (in a particular alternative) that this operand is an
1585@dfn{earlyclobber} operand, which is written before the instruction is
1586finished using the input operands.  Therefore, this operand may not lie
1587in a register that is read by the instruction or as part of any memory
1588address.
1589
1590@samp{&} applies only to the alternative in which it is written.  In
1591constraints with multiple alternatives, sometimes one alternative
1592requires @samp{&} while others do not.  See, for example, the
1593@samp{movdf} insn of the 68000.
1594
1595A operand which is read by the instruction can be tied to an earlyclobber
1596operand if its only use as an input occurs before the early result is
1597written.  Adding alternatives of this form often allows GCC to produce
1598better code when only some of the read operands can be affected by the
1599earlyclobber. See, for example, the @samp{mulsi3} insn of the ARM@.
1600
1601Furthermore, if the @dfn{earlyclobber} operand is also a read/write
1602operand, then that operand is written only after it's used.
1603
1604@samp{&} does not obviate the need to write @samp{=} or @samp{+}.  As
1605@dfn{earlyclobber} operands are always written, a read-only
1606@dfn{earlyclobber} operand is ill-formed and will be rejected by the
1607compiler.
1608
1609@cindex @samp{%} in constraint
1610@item %
1611Declares the instruction to be commutative for this operand and the
1612following operand.  This means that the compiler may interchange the
1613two operands if that is the cheapest way to make all operands fit the
1614constraints.  @samp{%} applies to all alternatives and must appear as
1615the first character in the constraint.  Only read-only operands can use
1616@samp{%}.
1617
1618@ifset INTERNALS
1619This is often used in patterns for addition instructions
1620that really have only two operands: the result must go in one of the
1621arguments.  Here for example, is how the 68000 halfword-add
1622instruction is defined:
1623
1624@smallexample
1625(define_insn "addhi3"
1626  [(set (match_operand:HI 0 "general_operand" "=m,r")
1627     (plus:HI (match_operand:HI 1 "general_operand" "%0,0")
1628              (match_operand:HI 2 "general_operand" "di,g")))]
1629  @dots{})
1630@end smallexample
1631@end ifset
1632GCC can only handle one commutative pair in an asm; if you use more,
1633the compiler may fail.  Note that you need not use the modifier if
1634the two alternatives are strictly identical; this would only waste
1635time in the reload pass.  The modifier is not operational after
1636register allocation, so the result of @code{define_peephole2}
1637and @code{define_split}s performed after reload cannot rely on
1638@samp{%} to make the intended insn match.
1639
1640@cindex @samp{#} in constraint
1641@item #
1642Says that all following characters, up to the next comma, are to be
1643ignored as a constraint.  They are significant only for choosing
1644register preferences.
1645
1646@cindex @samp{*} in constraint
1647@item *
1648Says that the following character should be ignored when choosing
1649register preferences.  @samp{*} has no effect on the meaning of the
1650constraint as a constraint, and no effect on reloading.  For LRA
1651@samp{*} additionally disparages slightly the alternative if the
1652following character matches the operand.
1653
1654@ifset INTERNALS
1655Here is an example: the 68000 has an instruction to sign-extend a
1656halfword in a data register, and can also sign-extend a value by
1657copying it into an address register.  While either kind of register is
1658acceptable, the constraints on an address-register destination are
1659less strict, so it is best if register allocation makes an address
1660register its goal.  Therefore, @samp{*} is used so that the @samp{d}
1661constraint letter (for data register) is ignored when computing
1662register preferences.
1663
1664@smallexample
1665(define_insn "extendhisi2"
1666  [(set (match_operand:SI 0 "general_operand" "=*d,a")
1667        (sign_extend:SI
1668         (match_operand:HI 1 "general_operand" "0,g")))]
1669  @dots{})
1670@end smallexample
1671@end ifset
1672@end table
1673
1674@node Machine Constraints
1675@subsection Constraints for Particular Machines
1676@cindex machine specific constraints
1677@cindex constraints, machine specific
1678
1679Whenever possible, you should use the general-purpose constraint letters
1680in @code{asm} arguments, since they will convey meaning more readily to
1681people reading your code.  Failing that, use the constraint letters
1682that usually have very similar meanings across architectures.  The most
1683commonly used constraints are @samp{m} and @samp{r} (for memory and
1684general-purpose registers respectively; @pxref{Simple Constraints}), and
1685@samp{I}, usually the letter indicating the most common
1686immediate-constant format.
1687
1688Each architecture defines additional constraints.  These constraints
1689are used by the compiler itself for instruction generation, as well as
1690for @code{asm} statements; therefore, some of the constraints are not
1691particularly useful for @code{asm}.  Here is a summary of some of the
1692machine-dependent constraints available on some particular machines;
1693it includes both constraints that are useful for @code{asm} and
1694constraints that aren't.  The compiler source file mentioned in the
1695table heading for each architecture is the definitive reference for
1696the meanings of that architecture's constraints.
1697
1698@c Please keep this table alphabetized by target!
1699@table @emph
1700@item AArch64 family---@file{config/aarch64/constraints.md}
1701@table @code
1702@item k
1703The stack pointer register (@code{SP})
1704
1705@item w
1706Floating point or SIMD vector register
1707
1708@item I
1709Integer constant that is valid as an immediate operand in an @code{ADD}
1710instruction
1711
1712@item J
1713Integer constant that is valid as an immediate operand in a @code{SUB}
1714instruction (once negated)
1715
1716@item K
1717Integer constant that can be used with a 32-bit logical instruction
1718
1719@item L
1720Integer constant that can be used with a 64-bit logical instruction
1721
1722@item M
1723Integer constant that is valid as an immediate operand in a 32-bit @code{MOV}
1724pseudo instruction. The @code{MOV} may be assembled to one of several different
1725machine instructions depending on the value
1726
1727@item N
1728Integer constant that is valid as an immediate operand in a 64-bit @code{MOV}
1729pseudo instruction
1730
1731@item S
1732An absolute symbolic address or a label reference
1733
1734@item Y
1735Floating point constant zero
1736
1737@item Z
1738Integer constant zero
1739
1740@item Ush
1741The high part (bits 12 and upwards) of the pc-relative address of a symbol
1742within 4GB of the instruction
1743
1744@item Q
1745A memory address which uses a single base register with no offset
1746
1747@item Ump
1748A memory address suitable for a load/store pair instruction in SI, DI, SF and
1749DF modes
1750
1751@end table
1752
1753
1754@item ARC ---@file{config/arc/constraints.md}
1755@table @code
1756@item q
1757Registers usable in ARCompact 16-bit instructions: @code{r0}-@code{r3},
1758@code{r12}-@code{r15}.  This constraint can only match when the @option{-mq}
1759option is in effect.
1760
1761@item e
1762Registers usable as base-regs of memory addresses in ARCompact 16-bit memory
1763instructions: @code{r0}-@code{r3}, @code{r12}-@code{r15}, @code{sp}.
1764This constraint can only match when the @option{-mq}
1765option is in effect.
1766@item D
1767ARC FPX (dpfp) 64-bit registers. @code{D0}, @code{D1}.
1768
1769@item I
1770A signed 12-bit integer constant.
1771
1772@item Cal
1773constant for arithmetic/logical operations.  This might be any constant
1774that can be put into a long immediate by the assmbler or linker without
1775involving a PIC relocation.
1776
1777@item K
1778A 3-bit unsigned integer constant.
1779
1780@item L
1781A 6-bit unsigned integer constant.
1782
1783@item CnL
1784One's complement of a 6-bit unsigned integer constant.
1785
1786@item CmL
1787Two's complement of a 6-bit unsigned integer constant.
1788
1789@item M
1790A 5-bit unsigned integer constant.
1791
1792@item O
1793A 7-bit unsigned integer constant.
1794
1795@item P
1796A 8-bit unsigned integer constant.
1797
1798@item H
1799Any const_double value.
1800@end table
1801
1802@item ARM family---@file{config/arm/constraints.md}
1803@table @code
1804
1805@item h
1806In Thumb state, the core registers @code{r8}-@code{r15}.
1807
1808@item k
1809The stack pointer register.
1810
1811@item l
1812In Thumb State the core registers @code{r0}-@code{r7}.  In ARM state this
1813is an alias for the @code{r} constraint.
1814
1815@item t
1816VFP floating-point registers @code{s0}-@code{s31}.  Used for 32 bit values.
1817
1818@item w
1819VFP floating-point registers @code{d0}-@code{d31} and the appropriate
1820subset @code{d0}-@code{d15} based on command line options.
1821Used for 64 bit values only.  Not valid for Thumb1.
1822
1823@item y
1824The iWMMX co-processor registers.
1825
1826@item z
1827The iWMMX GR registers.
1828
1829@item G
1830The floating-point constant 0.0
1831
1832@item I
1833Integer that is valid as an immediate operand in a data processing
1834instruction.  That is, an integer in the range 0 to 255 rotated by a
1835multiple of 2
1836
1837@item J
1838Integer in the range @minus{}4095 to 4095
1839
1840@item K
1841Integer that satisfies constraint @samp{I} when inverted (ones complement)
1842
1843@item L
1844Integer that satisfies constraint @samp{I} when negated (twos complement)
1845
1846@item M
1847Integer in the range 0 to 32
1848
1849@item Q
1850A memory reference where the exact address is in a single register
1851(`@samp{m}' is preferable for @code{asm} statements)
1852
1853@item R
1854An item in the constant pool
1855
1856@item S
1857A symbol in the text segment of the current file
1858
1859@item Uv
1860A memory reference suitable for VFP load/store insns (reg+constant offset)
1861
1862@item Uy
1863A memory reference suitable for iWMMXt load/store instructions.
1864
1865@item Uq
1866A memory reference suitable for the ARMv4 ldrsb instruction.
1867@end table
1868
1869@item AVR family---@file{config/avr/constraints.md}
1870@table @code
1871@item l
1872Registers from r0 to r15
1873
1874@item a
1875Registers from r16 to r23
1876
1877@item d
1878Registers from r16 to r31
1879
1880@item w
1881Registers from r24 to r31.  These registers can be used in @samp{adiw} command
1882
1883@item e
1884Pointer register (r26--r31)
1885
1886@item b
1887Base pointer register (r28--r31)
1888
1889@item q
1890Stack pointer register (SPH:SPL)
1891
1892@item t
1893Temporary register r0
1894
1895@item x
1896Register pair X (r27:r26)
1897
1898@item y
1899Register pair Y (r29:r28)
1900
1901@item z
1902Register pair Z (r31:r30)
1903
1904@item I
1905Constant greater than @minus{}1, less than 64
1906
1907@item J
1908Constant greater than @minus{}64, less than 1
1909
1910@item K
1911Constant integer 2
1912
1913@item L
1914Constant integer 0
1915
1916@item M
1917Constant that fits in 8 bits
1918
1919@item N
1920Constant integer @minus{}1
1921
1922@item O
1923Constant integer 8, 16, or 24
1924
1925@item P
1926Constant integer 1
1927
1928@item G
1929A floating point constant 0.0
1930
1931@item Q
1932A memory address based on Y or Z pointer with displacement.
1933@end table
1934
1935@item Blackfin family---@file{config/bfin/constraints.md}
1936@table @code
1937@item a
1938P register
1939
1940@item d
1941D register
1942
1943@item z
1944A call clobbered P register.
1945
1946@item q@var{n}
1947A single register.  If @var{n} is in the range 0 to 7, the corresponding D
1948register.  If it is @code{A}, then the register P0.
1949
1950@item D
1951Even-numbered D register
1952
1953@item W
1954Odd-numbered D register
1955
1956@item e
1957Accumulator register.
1958
1959@item A
1960Even-numbered accumulator register.
1961
1962@item B
1963Odd-numbered accumulator register.
1964
1965@item b
1966I register
1967
1968@item v
1969B register
1970
1971@item f
1972M register
1973
1974@item c
1975Registers used for circular buffering, i.e. I, B, or L registers.
1976
1977@item C
1978The CC register.
1979
1980@item t
1981LT0 or LT1.
1982
1983@item k
1984LC0 or LC1.
1985
1986@item u
1987LB0 or LB1.
1988
1989@item x
1990Any D, P, B, M, I or L register.
1991
1992@item y
1993Additional registers typically used only in prologues and epilogues: RETS,
1994RETN, RETI, RETX, RETE, ASTAT, SEQSTAT and USP.
1995
1996@item w
1997Any register except accumulators or CC.
1998
1999@item Ksh
2000Signed 16 bit integer (in the range @minus{}32768 to 32767)
2001
2002@item Kuh
2003Unsigned 16 bit integer (in the range 0 to 65535)
2004
2005@item Ks7
2006Signed 7 bit integer (in the range @minus{}64 to 63)
2007
2008@item Ku7
2009Unsigned 7 bit integer (in the range 0 to 127)
2010
2011@item Ku5
2012Unsigned 5 bit integer (in the range 0 to 31)
2013
2014@item Ks4
2015Signed 4 bit integer (in the range @minus{}8 to 7)
2016
2017@item Ks3
2018Signed 3 bit integer (in the range @minus{}3 to 4)
2019
2020@item Ku3
2021Unsigned 3 bit integer (in the range 0 to 7)
2022
2023@item P@var{n}
2024Constant @var{n}, where @var{n} is a single-digit constant in the range 0 to 4.
2025
2026@item PA
2027An integer equal to one of the MACFLAG_XXX constants that is suitable for
2028use with either accumulator.
2029
2030@item PB
2031An integer equal to one of the MACFLAG_XXX constants that is suitable for
2032use only with accumulator A1.
2033
2034@item M1
2035Constant 255.
2036
2037@item M2
2038Constant 65535.
2039
2040@item J
2041An integer constant with exactly a single bit set.
2042
2043@item L
2044An integer constant with all bits set except exactly one.
2045
2046@item H
2047
2048@item Q
2049Any SYMBOL_REF.
2050@end table
2051
2052@item CR16 Architecture---@file{config/cr16/cr16.h}
2053@table @code
2054
2055@item b
2056Registers from r0 to r14 (registers without stack pointer)
2057
2058@item t
2059Register from r0 to r11 (all 16-bit registers)
2060
2061@item p
2062Register from r12 to r15 (all 32-bit registers)
2063
2064@item I
2065Signed constant that fits in 4 bits
2066
2067@item J
2068Signed constant that fits in 5 bits
2069
2070@item K
2071Signed constant that fits in 6 bits
2072
2073@item L
2074Unsigned constant that fits in 4 bits
2075
2076@item M
2077Signed constant that fits in 32 bits
2078
2079@item N
2080Check for 64 bits wide constants for add/sub instructions
2081
2082@item G
2083Floating point constant that is legal for store immediate
2084@end table
2085
2086@item Epiphany---@file{config/epiphany/constraints.md}
2087@table @code
2088@item U16
2089An unsigned 16-bit constant.
2090
2091@item K
2092An unsigned 5-bit constant.
2093
2094@item L
2095A signed 11-bit constant.
2096
2097@item Cm1
2098A signed 11-bit constant added to @minus{}1.
2099Can only match when the @option{-m1reg-@var{reg}} option is active.
2100
2101@item Cl1
2102Left-shift of @minus{}1, i.e., a bit mask with a block of leading ones, the rest
2103being a block of trailing zeroes.
2104Can only match when the @option{-m1reg-@var{reg}} option is active.
2105
2106@item Cr1
2107Right-shift of @minus{}1, i.e., a bit mask with a trailing block of ones, the
2108rest being zeroes.  Or to put it another way, one less than a power of two.
2109Can only match when the @option{-m1reg-@var{reg}} option is active.
2110
2111@item Cal
2112Constant for arithmetic/logical operations.
2113This is like @code{i}, except that for position independent code,
2114no symbols / expressions needing relocations are allowed.
2115
2116@item Csy
2117Symbolic constant for call/jump instruction.
2118
2119@item Rcs
2120The register class usable in short insns.  This is a register class
2121constraint, and can thus drive register allocation.
2122This constraint won't match unless @option{-mprefer-short-insn-regs} is
2123in effect.
2124
2125@item Rsc
2126The the register class of registers that can be used to hold a
2127sibcall call address.  I.e., a caller-saved register.
2128
2129@item Rct
2130Core control register class.
2131
2132@item Rgs
2133The register group usable in short insns.
2134This constraint does not use a register class, so that it only
2135passively matches suitable registers, and doesn't drive register allocation.
2136
2137@ifset INTERNALS
2138@item Car
2139Constant suitable for the addsi3_r pattern.  This is a valid offset
2140For byte, halfword, or word addressing.
2141@end ifset
2142
2143@item Rra
2144Matches the return address if it can be replaced with the link register.
2145
2146@item Rcc
2147Matches the integer condition code register.
2148
2149@item Sra
2150Matches the return address if it is in a stack slot.
2151
2152@item Cfm
2153Matches control register values to switch fp mode, which are encapsulated in
2154@code{UNSPEC_FP_MODE}.
2155@end table
2156
2157@item FRV---@file{config/frv/frv.h}
2158@table @code
2159@item a
2160Register in the class @code{ACC_REGS} (@code{acc0} to @code{acc7}).
2161
2162@item b
2163Register in the class @code{EVEN_ACC_REGS} (@code{acc0} to @code{acc7}).
2164
2165@item c
2166Register in the class @code{CC_REGS} (@code{fcc0} to @code{fcc3} and
2167@code{icc0} to @code{icc3}).
2168
2169@item d
2170Register in the class @code{GPR_REGS} (@code{gr0} to @code{gr63}).
2171
2172@item e
2173Register in the class @code{EVEN_REGS} (@code{gr0} to @code{gr63}).
2174Odd registers are excluded not in the class but through the use of a machine
2175mode larger than 4 bytes.
2176
2177@item f
2178Register in the class @code{FPR_REGS} (@code{fr0} to @code{fr63}).
2179
2180@item h
2181Register in the class @code{FEVEN_REGS} (@code{fr0} to @code{fr63}).
2182Odd registers are excluded not in the class but through the use of a machine
2183mode larger than 4 bytes.
2184
2185@item l
2186Register in the class @code{LR_REG} (the @code{lr} register).
2187
2188@item q
2189Register in the class @code{QUAD_REGS} (@code{gr2} to @code{gr63}).
2190Register numbers not divisible by 4 are excluded not in the class but through
2191the use of a machine mode larger than 8 bytes.
2192
2193@item t
2194Register in the class @code{ICC_REGS} (@code{icc0} to @code{icc3}).
2195
2196@item u
2197Register in the class @code{FCC_REGS} (@code{fcc0} to @code{fcc3}).
2198
2199@item v
2200Register in the class @code{ICR_REGS} (@code{cc4} to @code{cc7}).
2201
2202@item w
2203Register in the class @code{FCR_REGS} (@code{cc0} to @code{cc3}).
2204
2205@item x
2206Register in the class @code{QUAD_FPR_REGS} (@code{fr0} to @code{fr63}).
2207Register numbers not divisible by 4 are excluded not in the class but through
2208the use of a machine mode larger than 8 bytes.
2209
2210@item z
2211Register in the class @code{SPR_REGS} (@code{lcr} and @code{lr}).
2212
2213@item A
2214Register in the class @code{QUAD_ACC_REGS} (@code{acc0} to @code{acc7}).
2215
2216@item B
2217Register in the class @code{ACCG_REGS} (@code{accg0} to @code{accg7}).
2218
2219@item C
2220Register in the class @code{CR_REGS} (@code{cc0} to @code{cc7}).
2221
2222@item G
2223Floating point constant zero
2224
2225@item I
22266-bit signed integer constant
2227
2228@item J
222910-bit signed integer constant
2230
2231@item L
223216-bit signed integer constant
2233
2234@item M
223516-bit unsigned integer constant
2236
2237@item N
223812-bit signed integer constant that is negative---i.e.@: in the
2239range of @minus{}2048 to @minus{}1
2240
2241@item O
2242Constant zero
2243
2244@item P
224512-bit signed integer constant that is greater than zero---i.e.@: in the
2246range of 1 to 2047.
2247
2248@end table
2249
2250@item Hewlett-Packard PA-RISC---@file{config/pa/pa.h}
2251@table @code
2252@item a
2253General register 1
2254
2255@item f
2256Floating point register
2257
2258@item q
2259Shift amount register
2260
2261@item x
2262Floating point register (deprecated)
2263
2264@item y
2265Upper floating point register (32-bit), floating point register (64-bit)
2266
2267@item Z
2268Any register
2269
2270@item I
2271Signed 11-bit integer constant
2272
2273@item J
2274Signed 14-bit integer constant
2275
2276@item K
2277Integer constant that can be deposited with a @code{zdepi} instruction
2278
2279@item L
2280Signed 5-bit integer constant
2281
2282@item M
2283Integer constant 0
2284
2285@item N
2286Integer constant that can be loaded with a @code{ldil} instruction
2287
2288@item O
2289Integer constant whose value plus one is a power of 2
2290
2291@item P
2292Integer constant that can be used for @code{and} operations in @code{depi}
2293and @code{extru} instructions
2294
2295@item S
2296Integer constant 31
2297
2298@item U
2299Integer constant 63
2300
2301@item G
2302Floating-point constant 0.0
2303
2304@item A
2305A @code{lo_sum} data-linkage-table memory operand
2306
2307@item Q
2308A memory operand that can be used as the destination operand of an
2309integer store instruction
2310
2311@item R
2312A scaled or unscaled indexed memory operand
2313
2314@item T
2315A memory operand for floating-point loads and stores
2316
2317@item W
2318A register indirect memory operand
2319@end table
2320
2321@item Intel IA-64---@file{config/ia64/ia64.h}
2322@table @code
2323@item a
2324General register @code{r0} to @code{r3} for @code{addl} instruction
2325
2326@item b
2327Branch register
2328
2329@item c
2330Predicate register (@samp{c} as in ``conditional'')
2331
2332@item d
2333Application register residing in M-unit
2334
2335@item e
2336Application register residing in I-unit
2337
2338@item f
2339Floating-point register
2340
2341@item m
2342Memory operand.  If used together with @samp{<} or @samp{>},
2343the operand can have postincrement and postdecrement which
2344require printing with @samp{%Pn} on IA-64.
2345
2346@item G
2347Floating-point constant 0.0 or 1.0
2348
2349@item I
235014-bit signed integer constant
2351
2352@item J
235322-bit signed integer constant
2354
2355@item K
23568-bit signed integer constant for logical instructions
2357
2358@item L
23598-bit adjusted signed integer constant for compare pseudo-ops
2360
2361@item M
23626-bit unsigned integer constant for shift counts
2363
2364@item N
23659-bit signed integer constant for load and store postincrements
2366
2367@item O
2368The constant zero
2369
2370@item P
23710 or @minus{}1 for @code{dep} instruction
2372
2373@item Q
2374Non-volatile memory for floating-point loads and stores
2375
2376@item R
2377Integer constant in the range 1 to 4 for @code{shladd} instruction
2378
2379@item S
2380Memory operand except postincrement and postdecrement.  This is
2381now roughly the same as @samp{m} when not used together with @samp{<}
2382or @samp{>}.
2383@end table
2384
2385@item M32C---@file{config/m32c/m32c.c}
2386@table @code
2387@item Rsp
2388@itemx Rfb
2389@itemx Rsb
2390@samp{$sp}, @samp{$fb}, @samp{$sb}.
2391
2392@item Rcr
2393Any control register, when they're 16 bits wide (nothing if control
2394registers are 24 bits wide)
2395
2396@item Rcl
2397Any control register, when they're 24 bits wide.
2398
2399@item R0w
2400@itemx R1w
2401@itemx R2w
2402@itemx R3w
2403$r0, $r1, $r2, $r3.
2404
2405@item R02
2406$r0 or $r2, or $r2r0 for 32 bit values.
2407
2408@item R13
2409$r1 or $r3, or $r3r1 for 32 bit values.
2410
2411@item Rdi
2412A register that can hold a 64 bit value.
2413
2414@item Rhl
2415$r0 or $r1 (registers with addressable high/low bytes)
2416
2417@item R23
2418$r2 or $r3
2419
2420@item Raa
2421Address registers
2422
2423@item Raw
2424Address registers when they're 16 bits wide.
2425
2426@item Ral
2427Address registers when they're 24 bits wide.
2428
2429@item Rqi
2430Registers that can hold QI values.
2431
2432@item Rad
2433Registers that can be used with displacements ($a0, $a1, $sb).
2434
2435@item Rsi
2436Registers that can hold 32 bit values.
2437
2438@item Rhi
2439Registers that can hold 16 bit values.
2440
2441@item Rhc
2442Registers chat can hold 16 bit values, including all control
2443registers.
2444
2445@item Rra
2446$r0 through R1, plus $a0 and $a1.
2447
2448@item Rfl
2449The flags register.
2450
2451@item Rmm
2452The memory-based pseudo-registers $mem0 through $mem15.
2453
2454@item Rpi
2455Registers that can hold pointers (16 bit registers for r8c, m16c; 24
2456bit registers for m32cm, m32c).
2457
2458@item Rpa
2459Matches multiple registers in a PARALLEL to form a larger register.
2460Used to match function return values.
2461
2462@item Is3
2463@minus{}8 @dots{} 7
2464
2465@item IS1
2466@minus{}128 @dots{} 127
2467
2468@item IS2
2469@minus{}32768 @dots{} 32767
2470
2471@item IU2
24720 @dots{} 65535
2473
2474@item In4
2475@minus{}8 @dots{} @minus{}1 or 1 @dots{} 8
2476
2477@item In5
2478@minus{}16 @dots{} @minus{}1 or 1 @dots{} 16
2479
2480@item In6
2481@minus{}32 @dots{} @minus{}1 or 1 @dots{} 32
2482
2483@item IM2
2484@minus{}65536 @dots{} @minus{}1
2485
2486@item Ilb
2487An 8 bit value with exactly one bit set.
2488
2489@item Ilw
2490A 16 bit value with exactly one bit set.
2491
2492@item Sd
2493The common src/dest memory addressing modes.
2494
2495@item Sa
2496Memory addressed using $a0 or $a1.
2497
2498@item Si
2499Memory addressed with immediate addresses.
2500
2501@item Ss
2502Memory addressed using the stack pointer ($sp).
2503
2504@item Sf
2505Memory addressed using the frame base register ($fb).
2506
2507@item Ss
2508Memory addressed using the small base register ($sb).
2509
2510@item S1
2511$r1h
2512@end table
2513
2514@item MeP---@file{config/mep/constraints.md}
2515@table @code
2516
2517@item a
2518The $sp register.
2519
2520@item b
2521The $tp register.
2522
2523@item c
2524Any control register.
2525
2526@item d
2527Either the $hi or the $lo register.
2528
2529@item em
2530Coprocessor registers that can be directly loaded ($c0-$c15).
2531
2532@item ex
2533Coprocessor registers that can be moved to each other.
2534
2535@item er
2536Coprocessor registers that can be moved to core registers.
2537
2538@item h
2539The $hi register.
2540
2541@item j
2542The $rpc register.
2543
2544@item l
2545The $lo register.
2546
2547@item t
2548Registers which can be used in $tp-relative addressing.
2549
2550@item v
2551The $gp register.
2552
2553@item x
2554The coprocessor registers.
2555
2556@item y
2557The coprocessor control registers.
2558
2559@item z
2560The $0 register.
2561
2562@item A
2563User-defined register set A.
2564
2565@item B
2566User-defined register set B.
2567
2568@item C
2569User-defined register set C.
2570
2571@item D
2572User-defined register set D.
2573
2574@item I
2575Offsets for $gp-rel addressing.
2576
2577@item J
2578Constants that can be used directly with boolean insns.
2579
2580@item K
2581Constants that can be moved directly to registers.
2582
2583@item L
2584Small constants that can be added to registers.
2585
2586@item M
2587Long shift counts.
2588
2589@item N
2590Small constants that can be compared to registers.
2591
2592@item O
2593Constants that can be loaded into the top half of registers.
2594
2595@item S
2596Signed 8-bit immediates.
2597
2598@item T
2599Symbols encoded for $tp-rel or $gp-rel addressing.
2600
2601@item U
2602Non-constant addresses for loading/saving coprocessor registers.
2603
2604@item W
2605The top half of a symbol's value.
2606
2607@item Y
2608A register indirect address without offset.
2609
2610@item Z
2611Symbolic references to the control bus.
2612
2613@end table
2614
2615@item MicroBlaze---@file{config/microblaze/constraints.md}
2616@table @code
2617@item d
2618A general register (@code{r0} to @code{r31}).
2619
2620@item z
2621A status register (@code{rmsr}, @code{$fcc1} to @code{$fcc7}).
2622
2623@end table
2624
2625@item MIPS---@file{config/mips/constraints.md}
2626@table @code
2627@item d
2628An address register.  This is equivalent to @code{r} unless
2629generating MIPS16 code.
2630
2631@item f
2632A floating-point register (if available).
2633
2634@item h
2635Formerly the @code{hi} register.  This constraint is no longer supported.
2636
2637@item l
2638The @code{lo} register.  Use this register to store values that are
2639no bigger than a word.
2640
2641@item x
2642The concatenated @code{hi} and @code{lo} registers.  Use this register
2643to store doubleword values.
2644
2645@item c
2646A register suitable for use in an indirect jump.  This will always be
2647@code{$25} for @option{-mabicalls}.
2648
2649@item v
2650Register @code{$3}.  Do not use this constraint in new code;
2651it is retained only for compatibility with glibc.
2652
2653@item y
2654Equivalent to @code{r}; retained for backwards compatibility.
2655
2656@item z
2657A floating-point condition code register.
2658
2659@item I
2660A signed 16-bit constant (for arithmetic instructions).
2661
2662@item J
2663Integer zero.
2664
2665@item K
2666An unsigned 16-bit constant (for logic instructions).
2667
2668@item L
2669A signed 32-bit constant in which the lower 16 bits are zero.
2670Such constants can be loaded using @code{lui}.
2671
2672@item M
2673A constant that cannot be loaded using @code{lui}, @code{addiu}
2674or @code{ori}.
2675
2676@item N
2677A constant in the range @minus{}65535 to @minus{}1 (inclusive).
2678
2679@item O
2680A signed 15-bit constant.
2681
2682@item P
2683A constant in the range 1 to 65535 (inclusive).
2684
2685@item G
2686Floating-point zero.
2687
2688@item R
2689An address that can be used in a non-macro load or store.
2690
2691@item ZC
2692A memory operand whose address is formed by a base register and offset
2693that is suitable for use in instructions with the same addressing mode
2694as @code{ll} and @code{sc}.
2695
2696@item ZD
2697An address suitable for a @code{prefetch} instruction, or for any other
2698instruction with the same addressing mode as @code{prefetch}.
2699@end table
2700
2701@item Motorola 680x0---@file{config/m68k/constraints.md}
2702@table @code
2703@item a
2704Address register
2705
2706@item d
2707Data register
2708
2709@item f
271068881 floating-point register, if available
2711
2712@item I
2713Integer in the range 1 to 8
2714
2715@item J
271616-bit signed number
2717
2718@item K
2719Signed number whose magnitude is greater than 0x80
2720
2721@item L
2722Integer in the range @minus{}8 to @minus{}1
2723
2724@item M
2725Signed number whose magnitude is greater than 0x100
2726
2727@item N
2728Range 24 to 31, rotatert:SI 8 to 1 expressed as rotate
2729
2730@item O
273116 (for rotate using swap)
2732
2733@item P
2734Range 8 to 15, rotatert:HI 8 to 1 expressed as rotate
2735
2736@item R
2737Numbers that mov3q can handle
2738
2739@item G
2740Floating point constant that is not a 68881 constant
2741
2742@item S
2743Operands that satisfy 'm' when -mpcrel is in effect
2744
2745@item T
2746Operands that satisfy 's' when -mpcrel is not in effect
2747
2748@item Q
2749Address register indirect addressing mode
2750
2751@item U
2752Register offset addressing
2753
2754@item W
2755const_call_operand
2756
2757@item Cs
2758symbol_ref or const
2759
2760@item Ci
2761const_int
2762
2763@item C0
2764const_int 0
2765
2766@item Cj
2767Range of signed numbers that don't fit in 16 bits
2768
2769@item Cmvq
2770Integers valid for mvq
2771
2772@item Capsw
2773Integers valid for a moveq followed by a swap
2774
2775@item Cmvz
2776Integers valid for mvz
2777
2778@item Cmvs
2779Integers valid for mvs
2780
2781@item Ap
2782push_operand
2783
2784@item Ac
2785Non-register operands allowed in clr
2786
2787@end table
2788
2789@item Moxie---@file{config/moxie/constraints.md}
2790@table @code
2791@item A
2792An absolute address
2793
2794@item B
2795An offset address
2796
2797@item W
2798A register indirect memory operand
2799
2800@item I
2801A constant in the range of 0 to 255.
2802
2803@item N
2804A constant in the range of 0 to @minus{}255.
2805
2806@end table
2807
2808@item MSP430--@file{config/msp430/constraints.md}
2809@table @code
2810
2811@item R12
2812Register R12.
2813
2814@item R13
2815Register R13.
2816
2817@item K
2818Integer constant 1.
2819
2820@item L
2821Integer constant -1^20..1^19.
2822
2823@item M
2824Integer constant 1-4.
2825
2826@item Ya
2827Memory references which do not require an extended MOVX instruction.
2828
2829@item Yl
2830Memory reference, labels only.
2831
2832@item Ys
2833Memory reference, stack only.
2834
2835@end table
2836
2837@item NDS32---@file{config/nds32/constraints.md}
2838@table @code
2839@item w
2840LOW register class $r0 to $r7 constraint for V3/V3M ISA.
2841@item l
2842LOW register class $r0 to $r7.
2843@item d
2844MIDDLE register class $r0 to $r11, $r16 to $r19.
2845@item h
2846HIGH register class $r12 to $r14, $r20 to $r31.
2847@item t
2848Temporary assist register $ta (i.e.@: $r15).
2849@item k
2850Stack register $sp.
2851@item Iu03
2852Unsigned immediate 3-bit value.
2853@item In03
2854Negative immediate 3-bit value in the range of @minus{}7--0.
2855@item Iu04
2856Unsigned immediate 4-bit value.
2857@item Is05
2858Signed immediate 5-bit value.
2859@item Iu05
2860Unsigned immediate 5-bit value.
2861@item In05
2862Negative immediate 5-bit value in the range of @minus{}31--0.
2863@item Ip05
2864Unsigned immediate 5-bit value for movpi45 instruction with range 16--47.
2865@item Iu06
2866Unsigned immediate 6-bit value constraint for addri36.sp instruction.
2867@item Iu08
2868Unsigned immediate 8-bit value.
2869@item Iu09
2870Unsigned immediate 9-bit value.
2871@item Is10
2872Signed immediate 10-bit value.
2873@item Is11
2874Signed immediate 11-bit value.
2875@item Is15
2876Signed immediate 15-bit value.
2877@item Iu15
2878Unsigned immediate 15-bit value.
2879@item Ic15
2880A constant which is not in the range of imm15u but ok for bclr instruction.
2881@item Ie15
2882A constant which is not in the range of imm15u but ok for bset instruction.
2883@item It15
2884A constant which is not in the range of imm15u but ok for btgl instruction.
2885@item Ii15
2886A constant whose compliment value is in the range of imm15u
2887and ok for bitci instruction.
2888@item Is16
2889Signed immediate 16-bit value.
2890@item Is17
2891Signed immediate 17-bit value.
2892@item Is19
2893Signed immediate 19-bit value.
2894@item Is20
2895Signed immediate 20-bit value.
2896@item Ihig
2897The immediate value that can be simply set high 20-bit.
2898@item Izeb
2899The immediate value 0xff.
2900@item Izeh
2901The immediate value 0xffff.
2902@item Ixls
2903The immediate value 0x01.
2904@item Ix11
2905The immediate value 0x7ff.
2906@item Ibms
2907The immediate value with power of 2.
2908@item Ifex
2909The immediate value with power of 2 minus 1.
2910@item U33
2911Memory constraint for 333 format.
2912@item U45
2913Memory constraint for 45 format.
2914@item U37
2915Memory constraint for 37 format.
2916@end table
2917
2918@item Nios II family---@file{config/nios2/constraints.md}
2919@table @code
2920
2921@item I
2922Integer that is valid as an immediate operand in an
2923instruction taking a signed 16-bit number. Range
2924@minus{}32768 to 32767.
2925
2926@item J
2927Integer that is valid as an immediate operand in an
2928instruction taking an unsigned 16-bit number. Range
29290 to 65535.
2930
2931@item K
2932Integer that is valid as an immediate operand in an
2933instruction taking only the upper 16-bits of a
293432-bit number. Range 32-bit numbers with the lower
293516-bits being 0.
2936
2937@item L
2938Integer that is valid as an immediate operand for a 
2939shift instruction. Range 0 to 31.
2940
2941@item M
2942Integer that is valid as an immediate operand for
2943only the value 0. Can be used in conjunction with
2944the format modifier @code{z} to use @code{r0}
2945instead of @code{0} in the assembly output.
2946
2947@item N
2948Integer that is valid as an immediate operand for
2949a custom instruction opcode. Range 0 to 255.
2950
2951@item S
2952Matches immediates which are addresses in the small
2953data section and therefore can be added to @code{gp}
2954as a 16-bit immediate to re-create their 32-bit value.
2955
2956@ifset INTERNALS
2957@item T
2958A @code{const} wrapped @code{UNSPEC} expression,
2959representing a supported PIC or TLS relocation.
2960@end ifset
2961
2962@end table
2963
2964@item PDP-11---@file{config/pdp11/constraints.md}
2965@table @code
2966@item a
2967Floating point registers AC0 through AC3.  These can be loaded from/to
2968memory with a single instruction.
2969
2970@item d
2971Odd numbered general registers (R1, R3, R5).  These are used for
297216-bit multiply operations.
2973
2974@item f
2975Any of the floating point registers (AC0 through AC5).
2976
2977@item G
2978Floating point constant 0.
2979
2980@item I
2981An integer constant that fits in 16 bits.
2982
2983@item J
2984An integer constant whose low order 16 bits are zero.
2985
2986@item K
2987An integer constant that does not meet the constraints for codes
2988@samp{I} or @samp{J}.
2989
2990@item L
2991The integer constant 1.
2992
2993@item M
2994The integer constant @minus{}1.
2995
2996@item N
2997The integer constant 0.
2998
2999@item O
3000Integer constants @minus{}4 through @minus{}1 and 1 through 4; shifts by these
3001amounts are handled as multiple single-bit shifts rather than a single
3002variable-length shift.
3003
3004@item Q
3005A memory reference which requires an additional word (address or
3006offset) after the opcode.
3007
3008@item R
3009A memory reference that is encoded within the opcode.
3010
3011@end table
3012
3013@item PowerPC and IBM RS6000---@file{config/rs6000/constraints.md}
3014@table @code
3015@item b
3016Address base register
3017
3018@item d
3019Floating point register (containing 64-bit value)
3020
3021@item f
3022Floating point register (containing 32-bit value)
3023
3024@item v
3025Altivec vector register
3026
3027@item wa
3028Any VSX register if the -mvsx option was used or NO_REGS.
3029
3030When using any of the register constraints (@code{wa}, @code{wd},
3031@code{wf}, @code{wg}, @code{wh}, @code{wi}, @code{wj}, @code{wk},
3032@code{wl}, @code{wm}, @code{ws}, @code{wt}, @code{wu}, @code{wv},
3033@code{ww}, or @code{wy}) that take VSX registers, you must use
3034@code{%x<n>} in the template so that the correct register is used.
3035Otherwise the register number output in the assembly file will be
3036incorrect if an Altivec register is an operand of a VSX instruction
3037that expects VSX register numbering.
3038
3039@smallexample
3040asm ("xvadddp %x0,%x1,%x2" : "=wa" (v1) : "wa" (v2), "wa" (v3));
3041@end smallexample
3042
3043is correct, but:
3044
3045@smallexample
3046asm ("xvadddp %0,%1,%2" : "=wa" (v1) : "wa" (v2), "wa" (v3));
3047@end smallexample
3048
3049is not correct.
3050
3051@item wd
3052VSX vector register to hold vector double data or NO_REGS.
3053
3054@item wf
3055VSX vector register to hold vector float data or NO_REGS.
3056
3057@item wg
3058If @option{-mmfpgpr} was used, a floating point register or NO_REGS.
3059
3060@item wh
3061Floating point register if direct moves are available, or NO_REGS.
3062
3063@item wi
3064FP or VSX register to hold 64-bit integers for VSX insns or NO_REGS.
3065
3066@item wj
3067FP or VSX register to hold 64-bit integers for direct moves or NO_REGS.
3068
3069@item wk
3070FP or VSX register to hold 64-bit doubles for direct moves or NO_REGS.
3071
3072@item wl
3073Floating point register if the LFIWAX instruction is enabled or NO_REGS.
3074
3075@item wm
3076VSX register if direct move instructions are enabled, or NO_REGS.
3077
3078@item wn
3079No register (NO_REGS).
3080
3081@item wr
3082General purpose register if 64-bit instructions are enabled or NO_REGS.
3083
3084@item ws
3085VSX vector register to hold scalar double values or NO_REGS.
3086
3087@item wt
3088VSX vector register to hold 128 bit integer or NO_REGS.
3089
3090@item wu
3091Altivec register to use for float/32-bit int loads/stores  or NO_REGS.
3092
3093@item wv
3094Altivec register to use for double loads/stores  or NO_REGS.
3095
3096@item ww
3097FP or VSX register to perform float operations under @option{-mvsx} or NO_REGS.
3098
3099@item wx
3100Floating point register if the STFIWX instruction is enabled or NO_REGS.
3101
3102@item wy
3103FP or VSX register to perform ISA 2.07 float ops or NO_REGS.
3104
3105@item wz
3106Floating point register if the LFIWZX instruction is enabled or NO_REGS.
3107
3108@item wD
3109Int constant that is the element number of the 64-bit scalar in a vector.
3110
3111@item wQ
3112A memory address that will work with the @code{lq} and @code{stq}
3113instructions.
3114
3115@item h
3116@samp{MQ}, @samp{CTR}, or @samp{LINK} register
3117
3118@item q
3119@samp{MQ} register
3120
3121@item c
3122@samp{CTR} register
3123
3124@item l
3125@samp{LINK} register
3126
3127@item x
3128@samp{CR} register (condition register) number 0
3129
3130@item y
3131@samp{CR} register (condition register)
3132
3133@item z
3134@samp{XER[CA]} carry bit (part of the XER register)
3135
3136@item I
3137Signed 16-bit constant
3138
3139@item J
3140Unsigned 16-bit constant shifted left 16 bits (use @samp{L} instead for
3141@code{SImode} constants)
3142
3143@item K
3144Unsigned 16-bit constant
3145
3146@item L
3147Signed 16-bit constant shifted left 16 bits
3148
3149@item M
3150Constant larger than 31
3151
3152@item N
3153Exact power of 2
3154
3155@item O
3156Zero
3157
3158@item P
3159Constant whose negation is a signed 16-bit constant
3160
3161@item G
3162Floating point constant that can be loaded into a register with one
3163instruction per word
3164
3165@item H
3166Integer/Floating point constant that can be loaded into a register using
3167three instructions
3168
3169@item m
3170Memory operand.
3171Normally, @code{m} does not allow addresses that update the base register.
3172If @samp{<} or @samp{>} constraint is also used, they are allowed and
3173therefore on PowerPC targets in that case it is only safe
3174to use @samp{m<>} in an @code{asm} statement if that @code{asm} statement
3175accesses the operand exactly once.  The @code{asm} statement must also
3176use @samp{%U@var{<opno>}} as a placeholder for the ``update'' flag in the
3177corresponding load or store instruction.  For example:
3178
3179@smallexample
3180asm ("st%U0 %1,%0" : "=m<>" (mem) : "r" (val));
3181@end smallexample
3182
3183is correct but:
3184
3185@smallexample
3186asm ("st %1,%0" : "=m<>" (mem) : "r" (val));
3187@end smallexample
3188
3189is not.
3190
3191@item es
3192A ``stable'' memory operand; that is, one which does not include any
3193automodification of the base register.  This used to be useful when
3194@samp{m} allowed automodification of the base register, but as those are now only
3195allowed when @samp{<} or @samp{>} is used, @samp{es} is basically the same
3196as @samp{m} without @samp{<} and @samp{>}.
3197
3198@item Q
3199Memory operand that is an offset from a register (it is usually better
3200to use @samp{m} or @samp{es} in @code{asm} statements)
3201
3202@item Z
3203Memory operand that is an indexed or indirect from a register (it is
3204usually better to use @samp{m} or @samp{es} in @code{asm} statements)
3205
3206@item R
3207AIX TOC entry
3208
3209@item a
3210Address operand that is an indexed or indirect from a register (@samp{p} is
3211preferable for @code{asm} statements)
3212
3213@item S
3214Constant suitable as a 64-bit mask operand
3215
3216@item T
3217Constant suitable as a 32-bit mask operand
3218
3219@item U
3220System V Release 4 small data area reference
3221
3222@item t
3223AND masks that can be performed by two rldic@{l, r@} instructions
3224
3225@item W
3226Vector constant that does not require memory
3227
3228@item j
3229Vector constant that is all zeros.
3230
3231@end table
3232
3233@item RL78---@file{config/rl78/constraints.md}
3234@table @code
3235
3236@item Int3
3237An integer constant in the range 1 @dots{} 7.
3238@item Int8
3239An integer constant in the range 0 @dots{} 255.
3240@item J
3241An integer constant in the range @minus{}255 @dots{} 0
3242@item K
3243The integer constant 1.
3244@item L
3245The integer constant -1.
3246@item M
3247The integer constant 0.
3248@item N
3249The integer constant 2.
3250@item O
3251The integer constant -2.
3252@item P
3253An integer constant in the range 1 @dots{} 15.
3254@item Qbi
3255The built-in compare types--eq, ne, gtu, ltu, geu, and leu.
3256@item Qsc
3257The synthetic compare types--gt, lt, ge, and le.
3258@item Wab
3259A memory reference with an absolute address.
3260@item Wbc
3261A memory reference using @code{BC} as a base register, with an optional offset.
3262@item Wca
3263A memory reference using @code{AX}, @code{BC}, @code{DE}, or @code{HL} for the address, for calls.
3264@item Wcv
3265A memory reference using any 16-bit register pair for the address, for calls.
3266@item Wd2
3267A memory reference using @code{DE} as a base register, with an optional offset.
3268@item Wde
3269A memory reference using @code{DE} as a base register, without any offset.
3270@item Wfr
3271Any memory reference to an address in the far address space.
3272@item Wh1
3273A memory reference using @code{HL} as a base register, with an optional one-byte offset.
3274@item Whb
3275A memory reference using @code{HL} as a base register, with @code{B} or @code{C} as the index register.
3276@item Whl
3277A memory reference using @code{HL} as a base register, without any offset.
3278@item Ws1
3279A memory reference using @code{SP} as a base register, with an optional one-byte offset.
3280@item Y
3281Any memory reference to an address in the near address space.
3282@item A
3283The @code{AX} register.
3284@item B
3285The @code{BC} register.
3286@item D
3287The @code{DE} register.
3288@item R
3289@code{A} through @code{L} registers.
3290@item S
3291The @code{SP} register.
3292@item T
3293The @code{HL} register.
3294@item Z08W
3295The 16-bit @code{R8} register.
3296@item Z10W
3297The 16-bit @code{R10} register.
3298@item Zint
3299The registers reserved for interrupts (@code{R24} to @code{R31}).
3300@item a
3301The @code{A} register.
3302@item b
3303The @code{B} register.
3304@item c
3305The @code{C} register.
3306@item d
3307The @code{D} register.
3308@item e
3309The @code{E} register.
3310@item h
3311The @code{H} register.
3312@item l
3313The @code{L} register.
3314@item v
3315The virtual registers.
3316@item w
3317The @code{PSW} register.
3318@item x
3319The @code{X} register.
3320
3321@end table
3322
3323@item RX---@file{config/rx/constraints.md}
3324@table @code
3325@item Q
3326An address which does not involve register indirect addressing or
3327pre/post increment/decrement addressing.
3328
3329@item Symbol
3330A symbol reference.
3331
3332@item Int08
3333A constant in the range @minus{}256 to 255, inclusive.
3334
3335@item Sint08
3336A constant in the range @minus{}128 to 127, inclusive.
3337
3338@item Sint16
3339A constant in the range @minus{}32768 to 32767, inclusive.
3340
3341@item Sint24
3342A constant in the range @minus{}8388608 to 8388607, inclusive.
3343
3344@item Uint04
3345A constant in the range 0 to 15, inclusive.
3346
3347@end table
3348
3349@item S/390 and zSeries---@file{config/s390/s390.h}
3350@table @code
3351@item a
3352Address register (general purpose register except r0)
3353
3354@item c
3355Condition code register
3356
3357@item d
3358Data register (arbitrary general purpose register)
3359
3360@item f
3361Floating-point register
3362
3363@item I
3364Unsigned 8-bit constant (0--255)
3365
3366@item J
3367Unsigned 12-bit constant (0--4095)
3368
3369@item K
3370Signed 16-bit constant (@minus{}32768--32767)
3371
3372@item L
3373Value appropriate as displacement.
3374@table @code
3375@item (0..4095)
3376for short displacement
3377@item (@minus{}524288..524287)
3378for long displacement
3379@end table
3380
3381@item M
3382Constant integer with a value of 0x7fffffff.
3383
3384@item N
3385Multiple letter constraint followed by 4 parameter letters.
3386@table @code
3387@item 0..9:
3388number of the part counting from most to least significant
3389@item H,Q:
3390mode of the part
3391@item D,S,H:
3392mode of the containing operand
3393@item 0,F:
3394value of the other parts (F---all bits set)
3395@end table
3396The constraint matches if the specified part of a constant
3397has a value different from its other parts.
3398
3399@item Q
3400Memory reference without index register and with short displacement.
3401
3402@item R
3403Memory reference with index register and short displacement.
3404
3405@item S
3406Memory reference without index register but with long displacement.
3407
3408@item T
3409Memory reference with index register and long displacement.
3410
3411@item U
3412Pointer with short displacement.
3413
3414@item W
3415Pointer with long displacement.
3416
3417@item Y
3418Shift count operand.
3419
3420@end table
3421
3422@need 1000
3423@item SPARC---@file{config/sparc/sparc.h}
3424@table @code
3425@item f
3426Floating-point register on the SPARC-V8 architecture and
3427lower floating-point register on the SPARC-V9 architecture.
3428
3429@item e
3430Floating-point register.  It is equivalent to @samp{f} on the
3431SPARC-V8 architecture and contains both lower and upper
3432floating-point registers on the SPARC-V9 architecture.
3433
3434@item c
3435Floating-point condition code register.
3436
3437@item d
3438Lower floating-point register.  It is only valid on the SPARC-V9
3439architecture when the Visual Instruction Set is available.
3440
3441@item b
3442Floating-point register.  It is only valid on the SPARC-V9 architecture
3443when the Visual Instruction Set is available.
3444
3445@item h
344664-bit global or out register for the SPARC-V8+ architecture.
3447
3448@item C
3449The constant all-ones, for floating-point.
3450
3451@item A
3452Signed 5-bit constant
3453
3454@item D
3455A vector constant
3456
3457@item I
3458Signed 13-bit constant
3459
3460@item J
3461Zero
3462
3463@item K
346432-bit constant with the low 12 bits clear (a constant that can be
3465loaded with the @code{sethi} instruction)
3466
3467@item L
3468A constant in the range supported by @code{movcc} instructions (11-bit
3469signed immediate)
3470
3471@item M
3472A constant in the range supported by @code{movrcc} instructions (10-bit
3473signed immediate)
3474
3475@item N
3476Same as @samp{K}, except that it verifies that bits that are not in the
3477lower 32-bit range are all zero.  Must be used instead of @samp{K} for
3478modes wider than @code{SImode}
3479
3480@item O
3481The constant 4096
3482
3483@item G
3484Floating-point zero
3485
3486@item H
3487Signed 13-bit constant, sign-extended to 32 or 64 bits
3488
3489@item P
3490The constant -1
3491
3492@item Q
3493Floating-point constant whose integral representation can
3494be moved into an integer register using a single sethi
3495instruction
3496
3497@item R
3498Floating-point constant whose integral representation can
3499be moved into an integer register using a single mov
3500instruction
3501
3502@item S
3503Floating-point constant whose integral representation can
3504be moved into an integer register using a high/lo_sum
3505instruction sequence
3506
3507@item T
3508Memory address aligned to an 8-byte boundary
3509
3510@item U
3511Even register
3512
3513@item W
3514Memory address for @samp{e} constraint registers
3515
3516@item w
3517Memory address with only a base register
3518
3519@item Y
3520Vector zero
3521
3522@end table
3523
3524@item SPU---@file{config/spu/spu.h}
3525@table @code
3526@item a
3527An immediate which can be loaded with the il/ila/ilh/ilhu instructions.  const_int is treated as a 64 bit value.
3528
3529@item c
3530An immediate for and/xor/or instructions.  const_int is treated as a 64 bit value.
3531
3532@item d
3533An immediate for the @code{iohl} instruction.  const_int is treated as a 64 bit value.
3534
3535@item f
3536An immediate which can be loaded with @code{fsmbi}.
3537
3538@item A
3539An immediate which can be loaded with the il/ila/ilh/ilhu instructions.  const_int is treated as a 32 bit value.
3540
3541@item B
3542An immediate for most arithmetic instructions.  const_int is treated as a 32 bit value.
3543
3544@item C
3545An immediate for and/xor/or instructions.  const_int is treated as a 32 bit value.
3546
3547@item D
3548An immediate for the @code{iohl} instruction.  const_int is treated as a 32 bit value.
3549
3550@item I
3551A constant in the range [@minus{}64, 63] for shift/rotate instructions.
3552
3553@item J
3554An unsigned 7-bit constant for conversion/nop/channel instructions.
3555
3556@item K
3557A signed 10-bit constant for most arithmetic instructions.
3558
3559@item M
3560A signed 16 bit immediate for @code{stop}.
3561
3562@item N
3563An unsigned 16-bit constant for @code{iohl} and @code{fsmbi}.
3564
3565@item O
3566An unsigned 7-bit constant whose 3 least significant bits are 0.
3567
3568@item P
3569An unsigned 3-bit constant for 16-byte rotates and shifts
3570
3571@item R
3572Call operand, reg, for indirect calls
3573
3574@item S
3575Call operand, symbol, for relative calls.
3576
3577@item T
3578Call operand, const_int, for absolute calls.
3579
3580@item U
3581An immediate which can be loaded with the il/ila/ilh/ilhu instructions.  const_int is sign extended to 128 bit.
3582
3583@item W
3584An immediate for shift and rotate instructions.  const_int is treated as a 32 bit value.
3585
3586@item Y
3587An immediate for and/xor/or instructions.  const_int is sign extended as a 128 bit.
3588
3589@item Z
3590An immediate for the @code{iohl} instruction.  const_int is sign extended to 128 bit.
3591
3592@end table
3593
3594@item TI C6X family---@file{config/c6x/constraints.md}
3595@table @code
3596@item a
3597Register file A (A0--A31).
3598
3599@item b
3600Register file B (B0--B31).
3601
3602@item A
3603Predicate registers in register file A (A0--A2 on C64X and
3604higher, A1 and A2 otherwise).
3605
3606@item B
3607Predicate registers in register file B (B0--B2).
3608
3609@item C
3610A call-used register in register file B (B0--B9, B16--B31).
3611
3612@item Da
3613Register file A, excluding predicate registers (A3--A31,
3614plus A0 if not C64X or higher).
3615
3616@item Db
3617Register file B, excluding predicate registers (B3--B31).
3618
3619@item Iu4
3620Integer constant in the range 0 @dots{} 15.
3621
3622@item Iu5
3623Integer constant in the range 0 @dots{} 31.
3624
3625@item In5
3626Integer constant in the range @minus{}31 @dots{} 0.
3627
3628@item Is5
3629Integer constant in the range @minus{}16 @dots{} 15.
3630
3631@item I5x
3632Integer constant that can be the operand of an ADDA or a SUBA insn.
3633
3634@item IuB
3635Integer constant in the range 0 @dots{} 65535.
3636
3637@item IsB
3638Integer constant in the range @minus{}32768 @dots{} 32767.
3639
3640@item IsC
3641Integer constant in the range @math{-2^{20}} @dots{} @math{2^{20} - 1}.
3642
3643@item Jc
3644Integer constant that is a valid mask for the clr instruction.
3645
3646@item Js
3647Integer constant that is a valid mask for the set instruction.
3648
3649@item Q
3650Memory location with A base register.
3651
3652@item R
3653Memory location with B base register.
3654
3655@ifset INTERNALS
3656@item S0
3657On C64x+ targets, a GP-relative small data reference.
3658
3659@item S1
3660Any kind of @code{SYMBOL_REF}, for use in a call address.
3661
3662@item Si
3663Any kind of immediate operand, unless it matches the S0 constraint.
3664
3665@item T
3666Memory location with B base register, but not using a long offset.
3667
3668@item W
3669A memory operand with an address that can't be used in an unaligned access.
3670
3671@end ifset
3672@item Z
3673Register B14 (aka DP).
3674
3675@end table
3676
3677@item TILE-Gx---@file{config/tilegx/constraints.md}
3678@table @code
3679@item R00
3680@itemx R01
3681@itemx R02
3682@itemx R03
3683@itemx R04
3684@itemx R05
3685@itemx R06
3686@itemx R07
3687@itemx R08
3688@itemx R09
3689@itemx R10
3690Each of these represents a register constraint for an individual
3691register, from r0 to r10.
3692
3693@item I
3694Signed 8-bit integer constant.
3695
3696@item J
3697Signed 16-bit integer constant.
3698
3699@item K
3700Unsigned 16-bit integer constant.
3701
3702@item L
3703Integer constant that fits in one signed byte when incremented by one
3704(@minus{}129 @dots{} 126).
3705
3706@item m
3707Memory operand.  If used together with @samp{<} or @samp{>}, the
3708operand can have postincrement which requires printing with @samp{%In}
3709and @samp{%in} on TILE-Gx.  For example:
3710
3711@smallexample
3712asm ("st_add %I0,%1,%i0" : "=m<>" (*mem) : "r" (val));
3713@end smallexample
3714
3715@item M
3716A bit mask suitable for the BFINS instruction.
3717
3718@item N
3719Integer constant that is a byte tiled out eight times.
3720
3721@item O
3722The integer zero constant.
3723
3724@item P
3725Integer constant that is a sign-extended byte tiled out as four shorts.
3726
3727@item Q
3728Integer constant that fits in one signed byte when incremented
3729(@minus{}129 @dots{} 126), but excluding -1.
3730
3731@item S
3732Integer constant that has all 1 bits consecutive and starting at bit 0.
3733
3734@item T
3735A 16-bit fragment of a got, tls, or pc-relative reference.
3736
3737@item U
3738Memory operand except postincrement.  This is roughly the same as
3739@samp{m} when not used together with @samp{<} or @samp{>}.
3740
3741@item W
3742An 8-element vector constant with identical elements.
3743
3744@item Y
3745A 4-element vector constant with identical elements.
3746
3747@item Z0
3748The integer constant 0xffffffff.
3749
3750@item Z1
3751The integer constant 0xffffffff00000000.
3752
3753@end table
3754
3755@item TILEPro---@file{config/tilepro/constraints.md}
3756@table @code
3757@item R00
3758@itemx R01
3759@itemx R02
3760@itemx R03
3761@itemx R04
3762@itemx R05
3763@itemx R06
3764@itemx R07
3765@itemx R08
3766@itemx R09
3767@itemx R10
3768Each of these represents a register constraint for an individual
3769register, from r0 to r10.
3770
3771@item I
3772Signed 8-bit integer constant.
3773
3774@item J
3775Signed 16-bit integer constant.
3776
3777@item K
3778Nonzero integer constant with low 16 bits zero.
3779
3780@item L
3781Integer constant that fits in one signed byte when incremented by one
3782(@minus{}129 @dots{} 126).
3783
3784@item m
3785Memory operand.  If used together with @samp{<} or @samp{>}, the
3786operand can have postincrement which requires printing with @samp{%In}
3787and @samp{%in} on TILEPro.  For example:
3788
3789@smallexample
3790asm ("swadd %I0,%1,%i0" : "=m<>" (mem) : "r" (val));
3791@end smallexample
3792
3793@item M
3794A bit mask suitable for the MM instruction.
3795
3796@item N
3797Integer constant that is a byte tiled out four times.
3798
3799@item O
3800The integer zero constant.
3801
3802@item P
3803Integer constant that is a sign-extended byte tiled out as two shorts.
3804
3805@item Q
3806Integer constant that fits in one signed byte when incremented
3807(@minus{}129 @dots{} 126), but excluding -1.
3808
3809@item T
3810A symbolic operand, or a 16-bit fragment of a got, tls, or pc-relative
3811reference.
3812
3813@item U
3814Memory operand except postincrement.  This is roughly the same as
3815@samp{m} when not used together with @samp{<} or @samp{>}.
3816
3817@item W
3818A 4-element vector constant with identical elements.
3819
3820@item Y
3821A 2-element vector constant with identical elements.
3822
3823@end table
3824
3825@item Visium---@file{config/visium/constraints.md}
3826@table @code
3827@item b
3828EAM register @code{mdb}
3829
3830@item c
3831EAM register @code{mdc}
3832
3833@item f
3834Floating point register
3835
3836@ifset INTERNALS
3837@item k
3838Register for sibcall optimization
3839@end ifset
3840
3841@item l
3842General register, but not @code{r29}, @code{r30} and @code{r31}
3843
3844@item t
3845Register @code{r1}
3846
3847@item u
3848Register @code{r2}
3849
3850@item v
3851Register @code{r3}
3852
3853@item G
3854Floating-point constant 0.0
3855
3856@item J
3857Integer constant in the range 0 .. 65535 (16-bit immediate)
3858
3859@item K
3860Integer constant in the range 1 .. 31 (5-bit immediate)
3861
3862@item L
3863Integer constant in the range @minus{}65535 .. @minus{}1 (16-bit negative immediate)
3864
3865@item M
3866Integer constant @minus{}1
3867
3868@item O
3869Integer constant 0
3870
3871@item P
3872Integer constant 32
3873@end table
3874
3875@item x86 family---@file{config/i386/constraints.md}
3876@table @code
3877@item R
3878Legacy register---the eight integer registers available on all
3879i386 processors (@code{a}, @code{b}, @code{c}, @code{d},
3880@code{si}, @code{di}, @code{bp}, @code{sp}).
3881
3882@item q
3883Any register accessible as @code{@var{r}l}.  In 32-bit mode, @code{a},
3884@code{b}, @code{c}, and @code{d}; in 64-bit mode, any integer register.
3885
3886@item Q
3887Any register accessible as @code{@var{r}h}: @code{a}, @code{b},
3888@code{c}, and @code{d}.
3889
3890@ifset INTERNALS
3891@item l
3892Any register that can be used as the index in a base+index memory
3893access: that is, any general register except the stack pointer.
3894@end ifset
3895
3896@item a
3897The @code{a} register.
3898
3899@item b
3900The @code{b} register.
3901
3902@item c
3903The @code{c} register.
3904
3905@item d
3906The @code{d} register.
3907
3908@item S
3909The @code{si} register.
3910
3911@item D
3912The @code{di} register.
3913
3914@item A
3915The @code{a} and @code{d} registers.  This class is used for instructions
3916that return double word results in the @code{ax:dx} register pair.  Single
3917word values will be allocated either in @code{ax} or @code{dx}.
3918For example on i386 the following implements @code{rdtsc}:
3919
3920@smallexample
3921unsigned long long rdtsc (void)
3922@{
3923  unsigned long long tick;
3924  __asm__ __volatile__("rdtsc":"=A"(tick));
3925  return tick;
3926@}
3927@end smallexample
3928
3929This is not correct on x86-64 as it would allocate tick in either @code{ax}
3930or @code{dx}.  You have to use the following variant instead:
3931
3932@smallexample
3933unsigned long long rdtsc (void)
3934@{
3935  unsigned int tickl, tickh;
3936  __asm__ __volatile__("rdtsc":"=a"(tickl),"=d"(tickh));
3937  return ((unsigned long long)tickh << 32)|tickl;
3938@}
3939@end smallexample
3940
3941
3942@item f
3943Any 80387 floating-point (stack) register.
3944
3945@item t
3946Top of 80387 floating-point stack (@code{%st(0)}).
3947
3948@item u
3949Second from top of 80387 floating-point stack (@code{%st(1)}).
3950
3951@item y
3952Any MMX register.
3953
3954@item x
3955Any SSE register.
3956
3957@item Yz
3958First SSE register (@code{%xmm0}).
3959
3960@ifset INTERNALS
3961@item Y2
3962Any SSE register, when SSE2 is enabled.
3963
3964@item Yi
3965Any SSE register, when SSE2 and inter-unit moves are enabled.
3966
3967@item Ym
3968Any MMX register, when inter-unit moves are enabled.
3969@end ifset
3970
3971@item I
3972Integer constant in the range 0 @dots{} 31, for 32-bit shifts.
3973
3974@item J
3975Integer constant in the range 0 @dots{} 63, for 64-bit shifts.
3976
3977@item K
3978Signed 8-bit integer constant.
3979
3980@item L
3981@code{0xFF} or @code{0xFFFF}, for andsi as a zero-extending move.
3982
3983@item M
39840, 1, 2, or 3 (shifts for the @code{lea} instruction).
3985
3986@item N
3987Unsigned 8-bit integer constant (for @code{in} and @code{out}
3988instructions).
3989
3990@ifset INTERNALS
3991@item O
3992Integer constant in the range 0 @dots{} 127, for 128-bit shifts.
3993@end ifset
3994
3995@item G
3996Standard 80387 floating point constant.
3997
3998@item C
3999SSE constant zero operand.
4000
4001@item e
400232-bit signed integer constant, or a symbolic reference known
4003to fit that range (for immediate operands in sign-extending x86-64
4004instructions).
4005
4006@item Z
400732-bit unsigned integer constant, or a symbolic reference known
4008to fit that range (for immediate operands in zero-extending x86-64
4009instructions).
4010
4011@end table
4012
4013@item Xstormy16---@file{config/stormy16/stormy16.h}
4014@table @code
4015@item a
4016Register r0.
4017
4018@item b
4019Register r1.
4020
4021@item c
4022Register r2.
4023
4024@item d
4025Register r8.
4026
4027@item e
4028Registers r0 through r7.
4029
4030@item t
4031Registers r0 and r1.
4032
4033@item y
4034The carry register.
4035
4036@item z
4037Registers r8 and r9.
4038
4039@item I
4040A constant between 0 and 3 inclusive.
4041
4042@item J
4043A constant that has exactly one bit set.
4044
4045@item K
4046A constant that has exactly one bit clear.
4047
4048@item L
4049A constant between 0 and 255 inclusive.
4050
4051@item M
4052A constant between @minus{}255 and 0 inclusive.
4053
4054@item N
4055A constant between @minus{}3 and 0 inclusive.
4056
4057@item O
4058A constant between 1 and 4 inclusive.
4059
4060@item P
4061A constant between @minus{}4 and @minus{}1 inclusive.
4062
4063@item Q
4064A memory reference that is a stack push.
4065
4066@item R
4067A memory reference that is a stack pop.
4068
4069@item S
4070A memory reference that refers to a constant address of known value.
4071
4072@item T
4073The register indicated by Rx (not implemented yet).
4074
4075@item U
4076A constant that is not between 2 and 15 inclusive.
4077
4078@item Z
4079The constant 0.
4080
4081@end table
4082
4083@item Xtensa---@file{config/xtensa/constraints.md}
4084@table @code
4085@item a
4086General-purpose 32-bit register
4087
4088@item b
4089One-bit boolean register
4090
4091@item A
4092MAC16 40-bit accumulator register
4093
4094@item I
4095Signed 12-bit integer constant, for use in MOVI instructions
4096
4097@item J
4098Signed 8-bit integer constant, for use in ADDI instructions
4099
4100@item K
4101Integer constant valid for BccI instructions
4102
4103@item L
4104Unsigned constant valid for BccUI instructions
4105
4106@end table
4107
4108@end table
4109
4110@ifset INTERNALS
4111@node Disable Insn Alternatives
4112@subsection Disable insn alternatives using the @code{enabled} attribute
4113@cindex enabled
4114
4115There are three insn attributes that may be used to selectively disable
4116instruction alternatives:
4117
4118@table @code
4119@item enabled
4120Says whether an alternative is available on the current subtarget.
4121
4122@item preferred_for_size
4123Says whether an enabled alternative should be used in code that is
4124optimized for size.
4125
4126@item preferred_for_speed
4127Says whether an enabled alternative should be used in code that is
4128optimized for speed.
4129@end table
4130
4131All these attributes should use @code{(const_int 1)} to allow an alternative
4132or @code{(const_int 0)} to disallow it.  The attributes must be a static
4133property of the subtarget; they cannot for example depend on the
4134current operands, on the current optimization level, on the location
4135of the insn within the body of a loop, on whether register allocation
4136has finished, or on the current compiler pass.
4137
4138The @code{enabled} attribute is a correctness property.  It tells GCC to act
4139as though the disabled alternatives were never defined in the first place.
4140This is useful when adding new instructions to an existing pattern in
4141cases where the new instructions are only available for certain cpu
4142architecture levels (typically mapped to the @code{-march=} command-line
4143option).
4144
4145In contrast, the @code{preferred_for_size} and @code{preferred_for_speed}
4146attributes are strong optimization hints rather than correctness properties.
4147@code{preferred_for_size} tells GCC which alternatives to consider when
4148adding or modifying an instruction that GCC wants to optimize for size.
4149@code{preferred_for_speed} does the same thing for speed.  Note that things
4150like code motion can lead to cases where code optimized for size uses
4151alternatives that are not preferred for size, and similarly for speed.
4152
4153Although @code{define_insn}s can in principle specify the @code{enabled}
4154attribute directly, it is often clearer to have subsiduary attributes
4155for each architectural feature of interest.  The @code{define_insn}s
4156can then use these subsiduary attributes to say which alternatives
4157require which features.  The example below does this for @code{cpu_facility}.
4158
4159E.g. the following two patterns could easily be merged using the @code{enabled}
4160attribute:
4161
4162@smallexample
4163
4164(define_insn "*movdi_old"
4165  [(set (match_operand:DI 0 "register_operand" "=d")
4166        (match_operand:DI 1 "register_operand" " d"))]
4167  "!TARGET_NEW"
4168  "lgr %0,%1")
4169
4170(define_insn "*movdi_new"
4171  [(set (match_operand:DI 0 "register_operand" "=d,f,d")
4172        (match_operand:DI 1 "register_operand" " d,d,f"))]
4173  "TARGET_NEW"
4174  "@@
4175   lgr  %0,%1
4176   ldgr %0,%1
4177   lgdr %0,%1")
4178
4179@end smallexample
4180
4181to:
4182
4183@smallexample
4184
4185(define_insn "*movdi_combined"
4186  [(set (match_operand:DI 0 "register_operand" "=d,f,d")
4187        (match_operand:DI 1 "register_operand" " d,d,f"))]
4188  ""
4189  "@@
4190   lgr  %0,%1
4191   ldgr %0,%1
4192   lgdr %0,%1"
4193  [(set_attr "cpu_facility" "*,new,new")])
4194
4195@end smallexample
4196
4197with the @code{enabled} attribute defined like this:
4198
4199@smallexample
4200
4201(define_attr "cpu_facility" "standard,new" (const_string "standard"))
4202
4203(define_attr "enabled" ""
4204  (cond [(eq_attr "cpu_facility" "standard") (const_int 1)
4205         (and (eq_attr "cpu_facility" "new")
4206              (ne (symbol_ref "TARGET_NEW") (const_int 0)))
4207         (const_int 1)]
4208        (const_int 0)))
4209
4210@end smallexample
4211
4212@end ifset
4213
4214@ifset INTERNALS
4215@node Define Constraints
4216@subsection Defining Machine-Specific Constraints
4217@cindex defining constraints
4218@cindex constraints, defining
4219
4220Machine-specific constraints fall into two categories: register and
4221non-register constraints.  Within the latter category, constraints
4222which allow subsets of all possible memory or address operands should
4223be specially marked, to give @code{reload} more information.
4224
4225Machine-specific constraints can be given names of arbitrary length,
4226but they must be entirely composed of letters, digits, underscores
4227(@samp{_}), and angle brackets (@samp{< >}).  Like C identifiers, they
4228must begin with a letter or underscore.
4229
4230In order to avoid ambiguity in operand constraint strings, no
4231constraint can have a name that begins with any other constraint's
4232name.  For example, if @code{x} is defined as a constraint name,
4233@code{xy} may not be, and vice versa.  As a consequence of this rule,
4234no constraint may begin with one of the generic constraint letters:
4235@samp{E F V X g i m n o p r s}.
4236
4237Register constraints correspond directly to register classes.
4238@xref{Register Classes}.  There is thus not much flexibility in their
4239definitions.
4240
4241@deffn {MD Expression} define_register_constraint name regclass docstring
4242All three arguments are string constants.
4243@var{name} is the name of the constraint, as it will appear in
4244@code{match_operand} expressions.  If @var{name} is a multi-letter
4245constraint its length shall be the same for all constraints starting
4246with the same letter.  @var{regclass} can be either the
4247name of the corresponding register class (@pxref{Register Classes}),
4248or a C expression which evaluates to the appropriate register class.
4249If it is an expression, it must have no side effects, and it cannot
4250look at the operand.  The usual use of expressions is to map some
4251register constraints to @code{NO_REGS} when the register class
4252is not available on a given subarchitecture.
4253
4254@var{docstring} is a sentence documenting the meaning of the
4255constraint.  Docstrings are explained further below.
4256@end deffn
4257
4258Non-register constraints are more like predicates: the constraint
4259definition gives a Boolean expression which indicates whether the
4260constraint matches.
4261
4262@deffn {MD Expression} define_constraint name docstring exp
4263The @var{name} and @var{docstring} arguments are the same as for
4264@code{define_register_constraint}, but note that the docstring comes
4265immediately after the name for these expressions.  @var{exp} is an RTL
4266expression, obeying the same rules as the RTL expressions in predicate
4267definitions.  @xref{Defining Predicates}, for details.  If it
4268evaluates true, the constraint matches; if it evaluates false, it
4269doesn't. Constraint expressions should indicate which RTL codes they
4270might match, just like predicate expressions.
4271
4272@code{match_test} C expressions have access to the
4273following variables:
4274
4275@table @var
4276@item op
4277The RTL object defining the operand.
4278@item mode
4279The machine mode of @var{op}.
4280@item ival
4281@samp{INTVAL (@var{op})}, if @var{op} is a @code{const_int}.
4282@item hval
4283@samp{CONST_DOUBLE_HIGH (@var{op})}, if @var{op} is an integer
4284@code{const_double}.
4285@item lval
4286@samp{CONST_DOUBLE_LOW (@var{op})}, if @var{op} is an integer
4287@code{const_double}.
4288@item rval
4289@samp{CONST_DOUBLE_REAL_VALUE (@var{op})}, if @var{op} is a floating-point
4290@code{const_double}.
4291@end table
4292
4293The @var{*val} variables should only be used once another piece of the
4294expression has verified that @var{op} is the appropriate kind of RTL
4295object.
4296@end deffn
4297
4298Most non-register constraints should be defined with
4299@code{define_constraint}.  The remaining two definition expressions
4300are only appropriate for constraints that should be handled specially
4301by @code{reload} if they fail to match.
4302
4303@deffn {MD Expression} define_memory_constraint name docstring exp
4304Use this expression for constraints that match a subset of all memory
4305operands: that is, @code{reload} can make them match by converting the
4306operand to the form @samp{@w{(mem (reg @var{X}))}}, where @var{X} is a
4307base register (from the register class specified by
4308@code{BASE_REG_CLASS}, @pxref{Register Classes}).
4309
4310For example, on the S/390, some instructions do not accept arbitrary
4311memory references, but only those that do not make use of an index
4312register.  The constraint letter @samp{Q} is defined to represent a
4313memory address of this type.  If @samp{Q} is defined with
4314@code{define_memory_constraint}, a @samp{Q} constraint can handle any
4315memory operand, because @code{reload} knows it can simply copy the
4316memory address into a base register if required.  This is analogous to
4317the way an @samp{o} constraint can handle any memory operand.
4318
4319The syntax and semantics are otherwise identical to
4320@code{define_constraint}.
4321@end deffn
4322
4323@deffn {MD Expression} define_address_constraint name docstring exp
4324Use this expression for constraints that match a subset of all address
4325operands: that is, @code{reload} can make the constraint match by
4326converting the operand to the form @samp{@w{(reg @var{X})}}, again
4327with @var{X} a base register.
4328
4329Constraints defined with @code{define_address_constraint} can only be
4330used with the @code{address_operand} predicate, or machine-specific
4331predicates that work the same way.  They are treated analogously to
4332the generic @samp{p} constraint.
4333
4334The syntax and semantics are otherwise identical to
4335@code{define_constraint}.
4336@end deffn
4337
4338For historical reasons, names beginning with the letters @samp{G H}
4339are reserved for constraints that match only @code{const_double}s, and
4340names beginning with the letters @samp{I J K L M N O P} are reserved
4341for constraints that match only @code{const_int}s.  This may change in
4342the future.  For the time being, constraints with these names must be
4343written in a stylized form, so that @code{genpreds} can tell you did
4344it correctly:
4345
4346@smallexample
4347@group
4348(define_constraint "[@var{GHIJKLMNOP}]@dots{}"
4349  "@var{doc}@dots{}"
4350  (and (match_code "const_int")  ; @r{@code{const_double} for G/H}
4351       @var{condition}@dots{}))            ; @r{usually a @code{match_test}}
4352@end group
4353@end smallexample
4354@c the semicolons line up in the formatted manual
4355
4356It is fine to use names beginning with other letters for constraints
4357that match @code{const_double}s or @code{const_int}s.
4358
4359Each docstring in a constraint definition should be one or more complete
4360sentences, marked up in Texinfo format.  @emph{They are currently unused.}
4361In the future they will be copied into the GCC manual, in @ref{Machine
4362Constraints}, replacing the hand-maintained tables currently found in
4363that section.  Also, in the future the compiler may use this to give
4364more helpful diagnostics when poor choice of @code{asm} constraints
4365causes a reload failure.
4366
4367If you put the pseudo-Texinfo directive @samp{@@internal} at the
4368beginning of a docstring, then (in the future) it will appear only in
4369the internals manual's version of the machine-specific constraint tables.
4370Use this for constraints that should not appear in @code{asm} statements.
4371
4372@node C Constraint Interface
4373@subsection Testing constraints from C
4374@cindex testing constraints
4375@cindex constraints, testing
4376
4377It is occasionally useful to test a constraint from C code rather than
4378implicitly via the constraint string in a @code{match_operand}.  The
4379generated file @file{tm_p.h} declares a few interfaces for working
4380with constraints.  At present these are defined for all constraints
4381except @code{g} (which is equivalent to @code{general_operand}).
4382
4383Some valid constraint names are not valid C identifiers, so there is a
4384mangling scheme for referring to them from C@.  Constraint names that
4385do not contain angle brackets or underscores are left unchanged.
4386Underscores are doubled, each @samp{<} is replaced with @samp{_l}, and
4387each @samp{>} with @samp{_g}.  Here are some examples:
4388
4389@c the @c's prevent double blank lines in the printed manual.
4390@example
4391@multitable {Original} {Mangled}
4392@item @strong{Original} @tab @strong{Mangled}  @c
4393@item @code{x}     @tab @code{x}       @c
4394@item @code{P42x}  @tab @code{P42x}    @c
4395@item @code{P4_x}  @tab @code{P4__x}   @c
4396@item @code{P4>x}  @tab @code{P4_gx}   @c
4397@item @code{P4>>}  @tab @code{P4_g_g}  @c
4398@item @code{P4_g>} @tab @code{P4__g_g} @c
4399@end multitable
4400@end example
4401
4402Throughout this section, the variable @var{c} is either a constraint
4403in the abstract sense, or a constant from @code{enum constraint_num};
4404the variable @var{m} is a mangled constraint name (usually as part of
4405a larger identifier).
4406
4407@deftp Enum constraint_num
4408For each constraint except @code{g}, there is a corresponding
4409enumeration constant: @samp{CONSTRAINT_} plus the mangled name of the
4410constraint.  Functions that take an @code{enum constraint_num} as an
4411argument expect one of these constants.
4412@end deftp
4413
4414@deftypefun {inline bool} satisfies_constraint_@var{m} (rtx @var{exp})
4415For each non-register constraint @var{m} except @code{g}, there is
4416one of these functions; it returns @code{true} if @var{exp} satisfies the
4417constraint.  These functions are only visible if @file{rtl.h} was included
4418before @file{tm_p.h}.
4419@end deftypefun
4420
4421@deftypefun bool constraint_satisfied_p (rtx @var{exp}, enum constraint_num @var{c})
4422Like the @code{satisfies_constraint_@var{m}} functions, but the
4423constraint to test is given as an argument, @var{c}.  If @var{c}
4424specifies a register constraint, this function will always return
4425@code{false}.
4426@end deftypefun
4427
4428@deftypefun {enum reg_class} reg_class_for_constraint (enum constraint_num @var{c})
4429Returns the register class associated with @var{c}.  If @var{c} is not
4430a register constraint, or those registers are not available for the
4431currently selected subtarget, returns @code{NO_REGS}.
4432@end deftypefun
4433
4434Here is an example use of @code{satisfies_constraint_@var{m}}.  In
4435peephole optimizations (@pxref{Peephole Definitions}), operand
4436constraint strings are ignored, so if there are relevant constraints,
4437they must be tested in the C condition.  In the example, the
4438optimization is applied if operand 2 does @emph{not} satisfy the
4439@samp{K} constraint.  (This is a simplified version of a peephole
4440definition from the i386 machine description.)
4441
4442@smallexample
4443(define_peephole2
4444  [(match_scratch:SI 3 "r")
4445   (set (match_operand:SI 0 "register_operand" "")
4446        (mult:SI (match_operand:SI 1 "memory_operand" "")
4447                 (match_operand:SI 2 "immediate_operand" "")))]
4448
4449  "!satisfies_constraint_K (operands[2])"
4450
4451  [(set (match_dup 3) (match_dup 1))
4452   (set (match_dup 0) (mult:SI (match_dup 3) (match_dup 2)))]
4453
4454  "")
4455@end smallexample
4456
4457@node Standard Names
4458@section Standard Pattern Names For Generation
4459@cindex standard pattern names
4460@cindex pattern names
4461@cindex names, pattern
4462
4463Here is a table of the instruction names that are meaningful in the RTL
4464generation pass of the compiler.  Giving one of these names to an
4465instruction pattern tells the RTL generation pass that it can use the
4466pattern to accomplish a certain task.
4467
4468@table @asis
4469@cindex @code{mov@var{m}} instruction pattern
4470@item @samp{mov@var{m}}
4471Here @var{m} stands for a two-letter machine mode name, in lowercase.
4472This instruction pattern moves data with that machine mode from operand
44731 to operand 0.  For example, @samp{movsi} moves full-word data.
4474
4475If operand 0 is a @code{subreg} with mode @var{m} of a register whose
4476own mode is wider than @var{m}, the effect of this instruction is
4477to store the specified value in the part of the register that corresponds
4478to mode @var{m}.  Bits outside of @var{m}, but which are within the
4479same target word as the @code{subreg} are undefined.  Bits which are
4480outside the target word are left unchanged.
4481
4482This class of patterns is special in several ways.  First of all, each
4483of these names up to and including full word size @emph{must} be defined,
4484because there is no other way to copy a datum from one place to another.
4485If there are patterns accepting operands in larger modes,
4486@samp{mov@var{m}} must be defined for integer modes of those sizes.
4487
4488Second, these patterns are not used solely in the RTL generation pass.
4489Even the reload pass can generate move insns to copy values from stack
4490slots into temporary registers.  When it does so, one of the operands is
4491a hard register and the other is an operand that can need to be reloaded
4492into a register.
4493
4494@findex force_reg
4495Therefore, when given such a pair of operands, the pattern must generate
4496RTL which needs no reloading and needs no temporary registers---no
4497registers other than the operands.  For example, if you support the
4498pattern with a @code{define_expand}, then in such a case the
4499@code{define_expand} mustn't call @code{force_reg} or any other such
4500function which might generate new pseudo registers.
4501
4502This requirement exists even for subword modes on a RISC machine where
4503fetching those modes from memory normally requires several insns and
4504some temporary registers.
4505
4506@findex change_address
4507During reload a memory reference with an invalid address may be passed
4508as an operand.  Such an address will be replaced with a valid address
4509later in the reload pass.  In this case, nothing may be done with the
4510address except to use it as it stands.  If it is copied, it will not be
4511replaced with a valid address.  No attempt should be made to make such
4512an address into a valid address and no routine (such as
4513@code{change_address}) that will do so may be called.  Note that
4514@code{general_operand} will fail when applied to such an address.
4515
4516@findex reload_in_progress
4517The global variable @code{reload_in_progress} (which must be explicitly
4518declared if required) can be used to determine whether such special
4519handling is required.
4520
4521The variety of operands that have reloads depends on the rest of the
4522machine description, but typically on a RISC machine these can only be
4523pseudo registers that did not get hard registers, while on other
4524machines explicit memory references will get optional reloads.
4525
4526If a scratch register is required to move an object to or from memory,
4527it can be allocated using @code{gen_reg_rtx} prior to life analysis.
4528
4529If there are cases which need scratch registers during or after reload,
4530you must provide an appropriate secondary_reload target hook.
4531
4532@findex can_create_pseudo_p
4533The macro @code{can_create_pseudo_p} can be used to determine if it
4534is unsafe to create new pseudo registers.  If this variable is nonzero, then
4535it is unsafe to call @code{gen_reg_rtx} to allocate a new pseudo.
4536
4537The constraints on a @samp{mov@var{m}} must permit moving any hard
4538register to any other hard register provided that
4539@code{HARD_REGNO_MODE_OK} permits mode @var{m} in both registers and
4540@code{TARGET_REGISTER_MOVE_COST} applied to their classes returns a value
4541of 2.
4542
4543It is obligatory to support floating point @samp{mov@var{m}}
4544instructions into and out of any registers that can hold fixed point
4545values, because unions and structures (which have modes @code{SImode} or
4546@code{DImode}) can be in those registers and they may have floating
4547point members.
4548
4549There may also be a need to support fixed point @samp{mov@var{m}}
4550instructions in and out of floating point registers.  Unfortunately, I
4551have forgotten why this was so, and I don't know whether it is still
4552true.  If @code{HARD_REGNO_MODE_OK} rejects fixed point values in
4553floating point registers, then the constraints of the fixed point
4554@samp{mov@var{m}} instructions must be designed to avoid ever trying to
4555reload into a floating point register.
4556
4557@cindex @code{reload_in} instruction pattern
4558@cindex @code{reload_out} instruction pattern
4559@item @samp{reload_in@var{m}}
4560@itemx @samp{reload_out@var{m}}
4561These named patterns have been obsoleted by the target hook
4562@code{secondary_reload}.
4563
4564Like @samp{mov@var{m}}, but used when a scratch register is required to
4565move between operand 0 and operand 1.  Operand 2 describes the scratch
4566register.  See the discussion of the @code{SECONDARY_RELOAD_CLASS}
4567macro in @pxref{Register Classes}.
4568
4569There are special restrictions on the form of the @code{match_operand}s
4570used in these patterns.  First, only the predicate for the reload
4571operand is examined, i.e., @code{reload_in} examines operand 1, but not
4572the predicates for operand 0 or 2.  Second, there may be only one
4573alternative in the constraints.  Third, only a single register class
4574letter may be used for the constraint; subsequent constraint letters
4575are ignored.  As a special exception, an empty constraint string
4576matches the @code{ALL_REGS} register class.  This may relieve ports
4577of the burden of defining an @code{ALL_REGS} constraint letter just
4578for these patterns.
4579
4580@cindex @code{movstrict@var{m}} instruction pattern
4581@item @samp{movstrict@var{m}}
4582Like @samp{mov@var{m}} except that if operand 0 is a @code{subreg}
4583with mode @var{m} of a register whose natural mode is wider,
4584the @samp{movstrict@var{m}} instruction is guaranteed not to alter
4585any of the register except the part which belongs to mode @var{m}.
4586
4587@cindex @code{movmisalign@var{m}} instruction pattern
4588@item @samp{movmisalign@var{m}}
4589This variant of a move pattern is designed to load or store a value
4590from a memory address that is not naturally aligned for its mode.
4591For a store, the memory will be in operand 0; for a load, the memory
4592will be in operand 1.  The other operand is guaranteed not to be a
4593memory, so that it's easy to tell whether this is a load or store.
4594
4595This pattern is used by the autovectorizer, and when expanding a
4596@code{MISALIGNED_INDIRECT_REF} expression.
4597
4598@cindex @code{load_multiple} instruction pattern
4599@item @samp{load_multiple}
4600Load several consecutive memory locations into consecutive registers.
4601Operand 0 is the first of the consecutive registers, operand 1
4602is the first memory location, and operand 2 is a constant: the
4603number of consecutive registers.
4604
4605Define this only if the target machine really has such an instruction;
4606do not define this if the most efficient way of loading consecutive
4607registers from memory is to do them one at a time.
4608
4609On some machines, there are restrictions as to which consecutive
4610registers can be stored into memory, such as particular starting or
4611ending register numbers or only a range of valid counts.  For those
4612machines, use a @code{define_expand} (@pxref{Expander Definitions})
4613and make the pattern fail if the restrictions are not met.
4614
4615Write the generated insn as a @code{parallel} with elements being a
4616@code{set} of one register from the appropriate memory location (you may
4617also need @code{use} or @code{clobber} elements).  Use a
4618@code{match_parallel} (@pxref{RTL Template}) to recognize the insn.  See
4619@file{rs6000.md} for examples of the use of this insn pattern.
4620
4621@cindex @samp{store_multiple} instruction pattern
4622@item @samp{store_multiple}
4623Similar to @samp{load_multiple}, but store several consecutive registers
4624into consecutive memory locations.  Operand 0 is the first of the
4625consecutive memory locations, operand 1 is the first register, and
4626operand 2 is a constant: the number of consecutive registers.
4627
4628@cindex @code{vec_load_lanes@var{m}@var{n}} instruction pattern
4629@item @samp{vec_load_lanes@var{m}@var{n}}
4630Perform an interleaved load of several vectors from memory operand 1
4631into register operand 0.  Both operands have mode @var{m}.  The register
4632operand is viewed as holding consecutive vectors of mode @var{n},
4633while the memory operand is a flat array that contains the same number
4634of elements.  The operation is equivalent to:
4635
4636@smallexample
4637int c = GET_MODE_SIZE (@var{m}) / GET_MODE_SIZE (@var{n});
4638for (j = 0; j < GET_MODE_NUNITS (@var{n}); j++)
4639  for (i = 0; i < c; i++)
4640    operand0[i][j] = operand1[j * c + i];
4641@end smallexample
4642
4643For example, @samp{vec_load_lanestiv4hi} loads 8 16-bit values
4644from memory into a register of mode @samp{TI}@.  The register
4645contains two consecutive vectors of mode @samp{V4HI}@.
4646
4647This pattern can only be used if:
4648@smallexample
4649TARGET_ARRAY_MODE_SUPPORTED_P (@var{n}, @var{c})
4650@end smallexample
4651is true.  GCC assumes that, if a target supports this kind of
4652instruction for some mode @var{n}, it also supports unaligned
4653loads for vectors of mode @var{n}.
4654
4655@cindex @code{vec_store_lanes@var{m}@var{n}} instruction pattern
4656@item @samp{vec_store_lanes@var{m}@var{n}}
4657Equivalent to @samp{vec_load_lanes@var{m}@var{n}}, with the memory
4658and register operands reversed.  That is, the instruction is
4659equivalent to:
4660
4661@smallexample
4662int c = GET_MODE_SIZE (@var{m}) / GET_MODE_SIZE (@var{n});
4663for (j = 0; j < GET_MODE_NUNITS (@var{n}); j++)
4664  for (i = 0; i < c; i++)
4665    operand0[j * c + i] = operand1[i][j];
4666@end smallexample
4667
4668for a memory operand 0 and register operand 1.
4669
4670@cindex @code{vec_set@var{m}} instruction pattern
4671@item @samp{vec_set@var{m}}
4672Set given field in the vector value.  Operand 0 is the vector to modify,
4673operand 1 is new value of field and operand 2 specify the field index.
4674
4675@cindex @code{vec_extract@var{m}} instruction pattern
4676@item @samp{vec_extract@var{m}}
4677Extract given field from the vector value.  Operand 1 is the vector, operand 2
4678specify field index and operand 0 place to store value into.
4679
4680@cindex @code{vec_init@var{m}} instruction pattern
4681@item @samp{vec_init@var{m}}
4682Initialize the vector to given values.  Operand 0 is the vector to initialize
4683and operand 1 is parallel containing values for individual fields.
4684
4685@cindex @code{vcond@var{m}@var{n}} instruction pattern
4686@item @samp{vcond@var{m}@var{n}}
4687Output a conditional vector move.  Operand 0 is the destination to
4688receive a combination of operand 1 and operand 2, which are of mode @var{m},
4689dependent on the outcome of the predicate in operand 3 which is a
4690vector comparison with operands of mode @var{n} in operands 4 and 5.  The
4691modes @var{m} and @var{n} should have the same size.  Operand 0
4692will be set to the value @var{op1} & @var{msk} | @var{op2} & ~@var{msk}
4693where @var{msk} is computed by element-wise evaluation of the vector
4694comparison with a truth value of all-ones and a false value of all-zeros.
4695
4696@cindex @code{vec_perm@var{m}} instruction pattern
4697@item @samp{vec_perm@var{m}}
4698Output a (variable) vector permutation.  Operand 0 is the destination
4699to receive elements from operand 1 and operand 2, which are of mode
4700@var{m}.  Operand 3 is the @dfn{selector}.  It is an integral mode
4701vector of the same width and number of elements as mode @var{m}.
4702
4703The input elements are numbered from 0 in operand 1 through
4704@math{2*@var{N}-1} in operand 2.  The elements of the selector must
4705be computed modulo @math{2*@var{N}}.  Note that if
4706@code{rtx_equal_p(operand1, operand2)}, this can be implemented
4707with just operand 1 and selector elements modulo @var{N}.
4708
4709In order to make things easy for a number of targets, if there is no
4710@samp{vec_perm} pattern for mode @var{m}, but there is for mode @var{q}
4711where @var{q} is a vector of @code{QImode} of the same width as @var{m},
4712the middle-end will lower the mode @var{m} @code{VEC_PERM_EXPR} to
4713mode @var{q}.
4714
4715@cindex @code{vec_perm_const@var{m}} instruction pattern
4716@item @samp{vec_perm_const@var{m}}
4717Like @samp{vec_perm} except that the permutation is a compile-time
4718constant.  That is, operand 3, the @dfn{selector}, is a @code{CONST_VECTOR}.
4719
4720Some targets cannot perform a permutation with a variable selector,
4721but can efficiently perform a constant permutation.  Further, the
4722target hook @code{vec_perm_ok} is queried to determine if the 
4723specific constant permutation is available efficiently; the named
4724pattern is never expanded without @code{vec_perm_ok} returning true.
4725
4726There is no need for a target to supply both @samp{vec_perm@var{m}}
4727and @samp{vec_perm_const@var{m}} if the former can trivially implement
4728the operation with, say, the vector constant loaded into a register.
4729
4730@cindex @code{push@var{m}1} instruction pattern
4731@item @samp{push@var{m}1}
4732Output a push instruction.  Operand 0 is value to push.  Used only when
4733@code{PUSH_ROUNDING} is defined.  For historical reason, this pattern may be
4734missing and in such case an @code{mov} expander is used instead, with a
4735@code{MEM} expression forming the push operation.  The @code{mov} expander
4736method is deprecated.
4737
4738@cindex @code{add@var{m}3} instruction pattern
4739@item @samp{add@var{m}3}
4740Add operand 2 and operand 1, storing the result in operand 0.  All operands
4741must have mode @var{m}.  This can be used even on two-address machines, by
4742means of constraints requiring operands 1 and 0 to be the same location.
4743
4744@cindex @code{ssadd@var{m}3} instruction pattern
4745@cindex @code{usadd@var{m}3} instruction pattern
4746@cindex @code{sub@var{m}3} instruction pattern
4747@cindex @code{sssub@var{m}3} instruction pattern
4748@cindex @code{ussub@var{m}3} instruction pattern
4749@cindex @code{mul@var{m}3} instruction pattern
4750@cindex @code{ssmul@var{m}3} instruction pattern
4751@cindex @code{usmul@var{m}3} instruction pattern
4752@cindex @code{div@var{m}3} instruction pattern
4753@cindex @code{ssdiv@var{m}3} instruction pattern
4754@cindex @code{udiv@var{m}3} instruction pattern
4755@cindex @code{usdiv@var{m}3} instruction pattern
4756@cindex @code{mod@var{m}3} instruction pattern
4757@cindex @code{umod@var{m}3} instruction pattern
4758@cindex @code{umin@var{m}3} instruction pattern
4759@cindex @code{umax@var{m}3} instruction pattern
4760@cindex @code{and@var{m}3} instruction pattern
4761@cindex @code{ior@var{m}3} instruction pattern
4762@cindex @code{xor@var{m}3} instruction pattern
4763@item @samp{ssadd@var{m}3}, @samp{usadd@var{m}3}
4764@itemx @samp{sub@var{m}3}, @samp{sssub@var{m}3}, @samp{ussub@var{m}3}
4765@itemx @samp{mul@var{m}3}, @samp{ssmul@var{m}3}, @samp{usmul@var{m}3}
4766@itemx @samp{div@var{m}3}, @samp{ssdiv@var{m}3}
4767@itemx @samp{udiv@var{m}3}, @samp{usdiv@var{m}3}
4768@itemx @samp{mod@var{m}3}, @samp{umod@var{m}3}
4769@itemx @samp{umin@var{m}3}, @samp{umax@var{m}3}
4770@itemx @samp{and@var{m}3}, @samp{ior@var{m}3}, @samp{xor@var{m}3}
4771Similar, for other arithmetic operations.
4772
4773@cindex @code{addv@var{m}4} instruction pattern
4774@item @samp{addv@var{m}4}
4775Like @code{add@var{m}3} but takes a @code{code_label} as operand 3 and
4776emits code to jump to it if signed overflow occurs during the addition.
4777This pattern is used to implement the built-in functions performing
4778signed integer addition with overflow checking.
4779
4780@cindex @code{subv@var{m}4} instruction pattern
4781@cindex @code{mulv@var{m}4} instruction pattern
4782@item @samp{subv@var{m}4}, @samp{mulv@var{m}4}
4783Similar, for other signed arithmetic operations.
4784
4785@cindex @code{umulv@var{m}4} instruction pattern
4786@item @samp{umulv@var{m}4}
4787Like @code{mulv@var{m}4} but for unsigned multiplication.  That is to
4788say, the operation is the same as signed multiplication but the jump
4789is taken only on unsigned overflow.
4790
4791@cindex @code{addptr@var{m}3} instruction pattern
4792@item @samp{addptr@var{m}3}
4793Like @code{add@var{m}3} but is guaranteed to only be used for address
4794calculations.  The expanded code is not allowed to clobber the
4795condition code.  It only needs to be defined if @code{add@var{m}3}
4796sets the condition code.  If adds used for address calculations and
4797normal adds are not compatible it is required to expand a distinct
4798pattern (e.g. using an unspec).  The pattern is used by LRA to emit
4799address calculations.  @code{add@var{m}3} is used if
4800@code{addptr@var{m}3} is not defined.
4801
4802@cindex @code{fma@var{m}4} instruction pattern
4803@item @samp{fma@var{m}4}
4804Multiply operand 2 and operand 1, then add operand 3, storing the
4805result in operand 0 without doing an intermediate rounding step.  All
4806operands must have mode @var{m}.  This pattern is used to implement
4807the @code{fma}, @code{fmaf}, and @code{fmal} builtin functions from
4808the ISO C99 standard.
4809
4810@cindex @code{fms@var{m}4} instruction pattern
4811@item @samp{fms@var{m}4}
4812Like @code{fma@var{m}4}, except operand 3 subtracted from the
4813product instead of added to the product.  This is represented
4814in the rtl as
4815
4816@smallexample
4817(fma:@var{m} @var{op1} @var{op2} (neg:@var{m} @var{op3}))
4818@end smallexample
4819
4820@cindex @code{fnma@var{m}4} instruction pattern
4821@item @samp{fnma@var{m}4}
4822Like @code{fma@var{m}4} except that the intermediate product
4823is negated before being added to operand 3.  This is represented
4824in the rtl as
4825
4826@smallexample
4827(fma:@var{m} (neg:@var{m} @var{op1}) @var{op2} @var{op3})
4828@end smallexample
4829
4830@cindex @code{fnms@var{m}4} instruction pattern
4831@item @samp{fnms@var{m}4}
4832Like @code{fms@var{m}4} except that the intermediate product
4833is negated before subtracting operand 3.  This is represented
4834in the rtl as
4835
4836@smallexample
4837(fma:@var{m} (neg:@var{m} @var{op1}) @var{op2} (neg:@var{m} @var{op3}))
4838@end smallexample
4839
4840@cindex @code{min@var{m}3} instruction pattern
4841@cindex @code{max@var{m}3} instruction pattern
4842@item @samp{smin@var{m}3}, @samp{smax@var{m}3}
4843Signed minimum and maximum operations.  When used with floating point,
4844if both operands are zeros, or if either operand is @code{NaN}, then
4845it is unspecified which of the two operands is returned as the result.
4846
4847@cindex @code{reduc_smin_@var{m}} instruction pattern
4848@cindex @code{reduc_smax_@var{m}} instruction pattern
4849@item @samp{reduc_smin_@var{m}}, @samp{reduc_smax_@var{m}}
4850Find the signed minimum/maximum of the elements of a vector. The vector is
4851operand 1, and the result is stored in the least significant bits of
4852operand 0 (also a vector). The output and input vector should have the same
4853modes. These are legacy optabs, and platforms should prefer to implement
4854@samp{reduc_smin_scal_@var{m}} and @samp{reduc_smax_scal_@var{m}}.
4855
4856@cindex @code{reduc_umin_@var{m}} instruction pattern
4857@cindex @code{reduc_umax_@var{m}} instruction pattern
4858@item @samp{reduc_umin_@var{m}}, @samp{reduc_umax_@var{m}}
4859Find the unsigned minimum/maximum of the elements of a vector. The vector is
4860operand 1, and the result is stored in the least significant bits of
4861operand 0 (also a vector). The output and input vector should have the same
4862modes. These are legacy optabs, and platforms should prefer to implement
4863@samp{reduc_umin_scal_@var{m}} and @samp{reduc_umax_scal_@var{m}}.
4864
4865@cindex @code{reduc_splus_@var{m}} instruction pattern
4866@cindex @code{reduc_uplus_@var{m}} instruction pattern
4867@item @samp{reduc_splus_@var{m}}, @samp{reduc_uplus_@var{m}}
4868Compute the sum of the signed/unsigned elements of a vector. The vector is
4869operand 1, and the result is stored in the least significant bits of operand 0
4870(also a vector). The output and input vector should have the same modes.
4871These are legacy optabs, and platforms should prefer to implement
4872@samp{reduc_plus_scal_@var{m}}.
4873
4874@cindex @code{reduc_smin_scal_@var{m}} instruction pattern
4875@cindex @code{reduc_smax_scal_@var{m}} instruction pattern
4876@item @samp{reduc_smin_scal_@var{m}}, @samp{reduc_smax_scal_@var{m}}
4877Find the signed minimum/maximum of the elements of a vector. The vector is
4878operand 1, and operand 0 is the scalar result, with mode equal to the mode of
4879the elements of the input vector.
4880
4881@cindex @code{reduc_umin_scal_@var{m}} instruction pattern
4882@cindex @code{reduc_umax_scal_@var{m}} instruction pattern
4883@item @samp{reduc_umin_scal_@var{m}}, @samp{reduc_umax_scal_@var{m}}
4884Find the unsigned minimum/maximum of the elements of a vector. The vector is
4885operand 1, and operand 0 is the scalar result, with mode equal to the mode of
4886the elements of the input vector.
4887
4888@cindex @code{reduc_plus_scal_@var{m}} instruction pattern
4889@item @samp{reduc_plus_scal_@var{m}}
4890Compute the sum of the elements of a vector. The vector is operand 1, and
4891operand 0 is the scalar result, with mode equal to the mode of the elements of
4892the input vector.
4893
4894@cindex @code{sdot_prod@var{m}} instruction pattern
4895@item @samp{sdot_prod@var{m}}
4896@cindex @code{udot_prod@var{m}} instruction pattern
4897@itemx @samp{udot_prod@var{m}}
4898Compute the sum of the products of two signed/unsigned elements.
4899Operand 1 and operand 2 are of the same mode. Their product, which is of a
4900wider mode, is computed and added to operand 3. Operand 3 is of a mode equal or
4901wider than the mode of the product. The result is placed in operand 0, which
4902is of the same mode as operand 3.
4903
4904@cindex @code{ssad@var{m}} instruction pattern
4905@item @samp{ssad@var{m}}
4906@cindex @code{usad@var{m}} instruction pattern
4907@item @samp{usad@var{m}}
4908Compute the sum of absolute differences of two signed/unsigned elements.
4909Operand 1 and operand 2 are of the same mode. Their absolute difference, which
4910is of a wider mode, is computed and added to operand 3. Operand 3 is of a mode
4911equal or wider than the mode of the absolute difference. The result is placed
4912in operand 0, which is of the same mode as operand 3.
4913
4914@cindex @code{ssum_widen@var{m3}} instruction pattern
4915@item @samp{ssum_widen@var{m3}}
4916@cindex @code{usum_widen@var{m3}} instruction pattern
4917@itemx @samp{usum_widen@var{m3}}
4918Operands 0 and 2 are of the same mode, which is wider than the mode of
4919operand 1. Add operand 1 to operand 2 and place the widened result in
4920operand 0. (This is used express accumulation of elements into an accumulator
4921of a wider mode.)
4922
4923@cindex @code{vec_shr_@var{m}} instruction pattern
4924@item @samp{vec_shr_@var{m}}
4925Whole vector right shift in bits, i.e. towards element 0.
4926Operand 1 is a vector to be shifted.
4927Operand 2 is an integer shift amount in bits.
4928Operand 0 is where the resulting shifted vector is stored.
4929The output and input vectors should have the same modes.
4930
4931@cindex @code{vec_pack_trunc_@var{m}} instruction pattern
4932@item @samp{vec_pack_trunc_@var{m}}
4933Narrow (demote) and merge the elements of two vectors. Operands 1 and 2
4934are vectors of the same mode having N integral or floating point elements
4935of size S@.  Operand 0 is the resulting vector in which 2*N elements of
4936size N/2 are concatenated after narrowing them down using truncation.
4937
4938@cindex @code{vec_pack_ssat_@var{m}} instruction pattern
4939@cindex @code{vec_pack_usat_@var{m}} instruction pattern
4940@item @samp{vec_pack_ssat_@var{m}}, @samp{vec_pack_usat_@var{m}}
4941Narrow (demote) and merge the elements of two vectors.  Operands 1 and 2
4942are vectors of the same mode having N integral elements of size S.
4943Operand 0 is the resulting vector in which the elements of the two input
4944vectors are concatenated after narrowing them down using signed/unsigned
4945saturating arithmetic.
4946
4947@cindex @code{vec_pack_sfix_trunc_@var{m}} instruction pattern
4948@cindex @code{vec_pack_ufix_trunc_@var{m}} instruction pattern
4949@item @samp{vec_pack_sfix_trunc_@var{m}}, @samp{vec_pack_ufix_trunc_@var{m}}
4950Narrow, convert to signed/unsigned integral type and merge the elements
4951of two vectors.  Operands 1 and 2 are vectors of the same mode having N
4952floating point elements of size S@.  Operand 0 is the resulting vector
4953in which 2*N elements of size N/2 are concatenated.
4954
4955@cindex @code{vec_unpacks_hi_@var{m}} instruction pattern
4956@cindex @code{vec_unpacks_lo_@var{m}} instruction pattern
4957@item @samp{vec_unpacks_hi_@var{m}}, @samp{vec_unpacks_lo_@var{m}}
4958Extract and widen (promote) the high/low part of a vector of signed
4959integral or floating point elements.  The input vector (operand 1) has N
4960elements of size S@.  Widen (promote) the high/low elements of the vector
4961using signed or floating point extension and place the resulting N/2
4962values of size 2*S in the output vector (operand 0).
4963
4964@cindex @code{vec_unpacku_hi_@var{m}} instruction pattern
4965@cindex @code{vec_unpacku_lo_@var{m}} instruction pattern
4966@item @samp{vec_unpacku_hi_@var{m}}, @samp{vec_unpacku_lo_@var{m}}
4967Extract and widen (promote) the high/low part of a vector of unsigned
4968integral elements.  The input vector (operand 1) has N elements of size S.
4969Widen (promote) the high/low elements of the vector using zero extension and
4970place the resulting N/2 values of size 2*S in the output vector (operand 0).
4971
4972@cindex @code{vec_unpacks_float_hi_@var{m}} instruction pattern
4973@cindex @code{vec_unpacks_float_lo_@var{m}} instruction pattern
4974@cindex @code{vec_unpacku_float_hi_@var{m}} instruction pattern
4975@cindex @code{vec_unpacku_float_lo_@var{m}} instruction pattern
4976@item @samp{vec_unpacks_float_hi_@var{m}}, @samp{vec_unpacks_float_lo_@var{m}}
4977@itemx @samp{vec_unpacku_float_hi_@var{m}}, @samp{vec_unpacku_float_lo_@var{m}}
4978Extract, convert to floating point type and widen the high/low part of a
4979vector of signed/unsigned integral elements.  The input vector (operand 1)
4980has N elements of size S@.  Convert the high/low elements of the vector using
4981floating point conversion and place the resulting N/2 values of size 2*S in
4982the output vector (operand 0).
4983
4984@cindex @code{vec_widen_umult_hi_@var{m}} instruction pattern
4985@cindex @code{vec_widen_umult_lo_@var{m}} instruction pattern
4986@cindex @code{vec_widen_smult_hi_@var{m}} instruction pattern
4987@cindex @code{vec_widen_smult_lo_@var{m}} instruction pattern
4988@cindex @code{vec_widen_umult_even_@var{m}} instruction pattern
4989@cindex @code{vec_widen_umult_odd_@var{m}} instruction pattern
4990@cindex @code{vec_widen_smult_even_@var{m}} instruction pattern
4991@cindex @code{vec_widen_smult_odd_@var{m}} instruction pattern
4992@item @samp{vec_widen_umult_hi_@var{m}}, @samp{vec_widen_umult_lo_@var{m}}
4993@itemx @samp{vec_widen_smult_hi_@var{m}}, @samp{vec_widen_smult_lo_@var{m}}
4994@itemx @samp{vec_widen_umult_even_@var{m}}, @samp{vec_widen_umult_odd_@var{m}}
4995@itemx @samp{vec_widen_smult_even_@var{m}}, @samp{vec_widen_smult_odd_@var{m}}
4996Signed/Unsigned widening multiplication.  The two inputs (operands 1 and 2)
4997are vectors with N signed/unsigned elements of size S@.  Multiply the high/low
4998or even/odd elements of the two vectors, and put the N/2 products of size 2*S
4999in the output vector (operand 0). A target shouldn't implement even/odd pattern
5000pair if it is less efficient than lo/hi one.
5001
5002@cindex @code{vec_widen_ushiftl_hi_@var{m}} instruction pattern
5003@cindex @code{vec_widen_ushiftl_lo_@var{m}} instruction pattern
5004@cindex @code{vec_widen_sshiftl_hi_@var{m}} instruction pattern
5005@cindex @code{vec_widen_sshiftl_lo_@var{m}} instruction pattern
5006@item @samp{vec_widen_ushiftl_hi_@var{m}}, @samp{vec_widen_ushiftl_lo_@var{m}}
5007@itemx @samp{vec_widen_sshiftl_hi_@var{m}}, @samp{vec_widen_sshiftl_lo_@var{m}}
5008Signed/Unsigned widening shift left.  The first input (operand 1) is a vector
5009with N signed/unsigned elements of size S@.  Operand 2 is a constant.  Shift
5010the high/low elements of operand 1, and put the N/2 results of size 2*S in the
5011output vector (operand 0).
5012
5013@cindex @code{mulhisi3} instruction pattern
5014@item @samp{mulhisi3}
5015Multiply operands 1 and 2, which have mode @code{HImode}, and store
5016a @code{SImode} product in operand 0.
5017
5018@cindex @code{mulqihi3} instruction pattern
5019@cindex @code{mulsidi3} instruction pattern
5020@item @samp{mulqihi3}, @samp{mulsidi3}
5021Similar widening-multiplication instructions of other widths.
5022
5023@cindex @code{umulqihi3} instruction pattern
5024@cindex @code{umulhisi3} instruction pattern
5025@cindex @code{umulsidi3} instruction pattern
5026@item @samp{umulqihi3}, @samp{umulhisi3}, @samp{umulsidi3}
5027Similar widening-multiplication instructions that do unsigned
5028multiplication.
5029
5030@cindex @code{usmulqihi3} instruction pattern
5031@cindex @code{usmulhisi3} instruction pattern
5032@cindex @code{usmulsidi3} instruction pattern
5033@item @samp{usmulqihi3}, @samp{usmulhisi3}, @samp{usmulsidi3}
5034Similar widening-multiplication instructions that interpret the first
5035operand as unsigned and the second operand as signed, then do a signed
5036multiplication.
5037
5038@cindex @code{smul@var{m}3_highpart} instruction pattern
5039@item @samp{smul@var{m}3_highpart}
5040Perform a signed multiplication of operands 1 and 2, which have mode
5041@var{m}, and store the most significant half of the product in operand 0.
5042The least significant half of the product is discarded.
5043
5044@cindex @code{umul@var{m}3_highpart} instruction pattern
5045@item @samp{umul@var{m}3_highpart}
5046Similar, but the multiplication is unsigned.
5047
5048@cindex @code{madd@var{m}@var{n}4} instruction pattern
5049@item @samp{madd@var{m}@var{n}4}
5050Multiply operands 1 and 2, sign-extend them to mode @var{n}, add
5051operand 3, and store the result in operand 0.  Operands 1 and 2
5052have mode @var{m} and operands 0 and 3 have mode @var{n}.
5053Both modes must be integer or fixed-point modes and @var{n} must be twice
5054the size of @var{m}.
5055
5056In other words, @code{madd@var{m}@var{n}4} is like
5057@code{mul@var{m}@var{n}3} except that it also adds operand 3.
5058
5059These instructions are not allowed to @code{FAIL}.
5060
5061@cindex @code{umadd@var{m}@var{n}4} instruction pattern
5062@item @samp{umadd@var{m}@var{n}4}
5063Like @code{madd@var{m}@var{n}4}, but zero-extend the multiplication
5064operands instead of sign-extending them.
5065
5066@cindex @code{ssmadd@var{m}@var{n}4} instruction pattern
5067@item @samp{ssmadd@var{m}@var{n}4}
5068Like @code{madd@var{m}@var{n}4}, but all involved operations must be
5069signed-saturating.
5070
5071@cindex @code{usmadd@var{m}@var{n}4} instruction pattern
5072@item @samp{usmadd@var{m}@var{n}4}
5073Like @code{umadd@var{m}@var{n}4}, but all involved operations must be
5074unsigned-saturating.
5075
5076@cindex @code{msub@var{m}@var{n}4} instruction pattern
5077@item @samp{msub@var{m}@var{n}4}
5078Multiply operands 1 and 2, sign-extend them to mode @var{n}, subtract the
5079result from operand 3, and store the result in operand 0.  Operands 1 and 2
5080have mode @var{m} and operands 0 and 3 have mode @var{n}.
5081Both modes must be integer or fixed-point modes and @var{n} must be twice
5082the size of @var{m}.
5083
5084In other words, @code{msub@var{m}@var{n}4} is like
5085@code{mul@var{m}@var{n}3} except that it also subtracts the result
5086from operand 3.
5087
5088These instructions are not allowed to @code{FAIL}.
5089
5090@cindex @code{umsub@var{m}@var{n}4} instruction pattern
5091@item @samp{umsub@var{m}@var{n}4}
5092Like @code{msub@var{m}@var{n}4}, but zero-extend the multiplication
5093operands instead of sign-extending them.
5094
5095@cindex @code{ssmsub@var{m}@var{n}4} instruction pattern
5096@item @samp{ssmsub@var{m}@var{n}4}
5097Like @code{msub@var{m}@var{n}4}, but all involved operations must be
5098signed-saturating.
5099
5100@cindex @code{usmsub@var{m}@var{n}4} instruction pattern
5101@item @samp{usmsub@var{m}@var{n}4}
5102Like @code{umsub@var{m}@var{n}4}, but all involved operations must be
5103unsigned-saturating.
5104
5105@cindex @code{divmod@var{m}4} instruction pattern
5106@item @samp{divmod@var{m}4}
5107Signed division that produces both a quotient and a remainder.
5108Operand 1 is divided by operand 2 to produce a quotient stored
5109in operand 0 and a remainder stored in operand 3.
5110
5111For machines with an instruction that produces both a quotient and a
5112remainder, provide a pattern for @samp{divmod@var{m}4} but do not
5113provide patterns for @samp{div@var{m}3} and @samp{mod@var{m}3}.  This
5114allows optimization in the relatively common case when both the quotient
5115and remainder are computed.
5116
5117If an instruction that just produces a quotient or just a remainder
5118exists and is more efficient than the instruction that produces both,
5119write the output routine of @samp{divmod@var{m}4} to call
5120@code{find_reg_note} and look for a @code{REG_UNUSED} note on the
5121quotient or remainder and generate the appropriate instruction.
5122
5123@cindex @code{udivmod@var{m}4} instruction pattern
5124@item @samp{udivmod@var{m}4}
5125Similar, but does unsigned division.
5126
5127@anchor{shift patterns}
5128@cindex @code{ashl@var{m}3} instruction pattern
5129@cindex @code{ssashl@var{m}3} instruction pattern
5130@cindex @code{usashl@var{m}3} instruction pattern
5131@item @samp{ashl@var{m}3}, @samp{ssashl@var{m}3}, @samp{usashl@var{m}3}
5132Arithmetic-shift operand 1 left by a number of bits specified by operand
51332, and store the result in operand 0.  Here @var{m} is the mode of
5134operand 0 and operand 1; operand 2's mode is specified by the
5135instruction pattern, and the compiler will convert the operand to that
5136mode before generating the instruction.  The meaning of out-of-range shift
5137counts can optionally be specified by @code{TARGET_SHIFT_TRUNCATION_MASK}.
5138@xref{TARGET_SHIFT_TRUNCATION_MASK}.  Operand 2 is always a scalar type.
5139
5140@cindex @code{ashr@var{m}3} instruction pattern
5141@cindex @code{lshr@var{m}3} instruction pattern
5142@cindex @code{rotl@var{m}3} instruction pattern
5143@cindex @code{rotr@var{m}3} instruction pattern
5144@item @samp{ashr@var{m}3}, @samp{lshr@var{m}3}, @samp{rotl@var{m}3}, @samp{rotr@var{m}3}
5145Other shift and rotate instructions, analogous to the
5146@code{ashl@var{m}3} instructions.  Operand 2 is always a scalar type.
5147
5148@cindex @code{vashl@var{m}3} instruction pattern
5149@cindex @code{vashr@var{m}3} instruction pattern
5150@cindex @code{vlshr@var{m}3} instruction pattern
5151@cindex @code{vrotl@var{m}3} instruction pattern
5152@cindex @code{vrotr@var{m}3} instruction pattern
5153@item @samp{vashl@var{m}3}, @samp{vashr@var{m}3}, @samp{vlshr@var{m}3}, @samp{vrotl@var{m}3}, @samp{vrotr@var{m}3}
5154Vector shift and rotate instructions that take vectors as operand 2
5155instead of a scalar type.
5156
5157@cindex @code{bswap@var{m}2} instruction pattern
5158@item @samp{bswap@var{m}2}
5159Reverse the order of bytes of operand 1 and store the result in operand 0.
5160
5161@cindex @code{neg@var{m}2} instruction pattern
5162@cindex @code{ssneg@var{m}2} instruction pattern
5163@cindex @code{usneg@var{m}2} instruction pattern
5164@item @samp{neg@var{m}2}, @samp{ssneg@var{m}2}, @samp{usneg@var{m}2}
5165Negate operand 1 and store the result in operand 0.
5166
5167@cindex @code{negv@var{m}3} instruction pattern
5168@item @samp{negv@var{m}3}
5169Like @code{neg@var{m}2} but takes a @code{code_label} as operand 2 and
5170emits code to jump to it if signed overflow occurs during the negation.
5171
5172@cindex @code{abs@var{m}2} instruction pattern
5173@item @samp{abs@var{m}2}
5174Store the absolute value of operand 1 into operand 0.
5175
5176@cindex @code{sqrt@var{m}2} instruction pattern
5177@item @samp{sqrt@var{m}2}
5178Store the square root of operand 1 into operand 0.
5179
5180The @code{sqrt} built-in function of C always uses the mode which
5181corresponds to the C data type @code{double} and the @code{sqrtf}
5182built-in function uses the mode which corresponds to the C data
5183type @code{float}.
5184
5185@cindex @code{fmod@var{m}3} instruction pattern
5186@item @samp{fmod@var{m}3}
5187Store the remainder of dividing operand 1 by operand 2 into
5188operand 0, rounded towards zero to an integer.
5189
5190The @code{fmod} built-in function of C always uses the mode which
5191corresponds to the C data type @code{double} and the @code{fmodf}
5192built-in function uses the mode which corresponds to the C data
5193type @code{float}.
5194
5195@cindex @code{remainder@var{m}3} instruction pattern
5196@item @samp{remainder@var{m}3}
5197Store the remainder of dividing operand 1 by operand 2 into
5198operand 0, rounded to the nearest integer.
5199
5200The @code{remainder} built-in function of C always uses the mode
5201which corresponds to the C data type @code{double} and the
5202@code{remainderf} built-in function uses the mode which corresponds
5203to the C data type @code{float}.
5204
5205@cindex @code{cos@var{m}2} instruction pattern
5206@item @samp{cos@var{m}2}
5207Store the cosine of operand 1 into operand 0.
5208
5209The @code{cos} built-in function of C always uses the mode which
5210corresponds to the C data type @code{double} and the @code{cosf}
5211built-in function uses the mode which corresponds to the C data
5212type @code{float}.
5213
5214@cindex @code{sin@var{m}2} instruction pattern
5215@item @samp{sin@var{m}2}
5216Store the sine of operand 1 into operand 0.
5217
5218The @code{sin} built-in function of C always uses the mode which
5219corresponds to the C data type @code{double} and the @code{sinf}
5220built-in function uses the mode which corresponds to the C data
5221type @code{float}.
5222
5223@cindex @code{sincos@var{m}3} instruction pattern
5224@item @samp{sincos@var{m}3}
5225Store the cosine of operand 2 into operand 0 and the sine of
5226operand 2 into operand 1.
5227
5228The @code{sin} and @code{cos} built-in functions of C always use the
5229mode which corresponds to the C data type @code{double} and the
5230@code{sinf} and @code{cosf} built-in function use the mode which
5231corresponds to the C data type @code{float}.
5232Targets that can calculate the sine and cosine simultaneously can
5233implement this pattern as opposed to implementing individual
5234@code{sin@var{m}2} and @code{cos@var{m}2} patterns.  The @code{sin}
5235and @code{cos} built-in functions will then be expanded to the
5236@code{sincos@var{m}3} pattern, with one of the output values
5237left unused.
5238
5239@cindex @code{exp@var{m}2} instruction pattern
5240@item @samp{exp@var{m}2}
5241Store the exponential of operand 1 into operand 0.
5242
5243The @code{exp} built-in function of C always uses the mode which
5244corresponds to the C data type @code{double} and the @code{expf}
5245built-in function uses the mode which corresponds to the C data
5246type @code{float}.
5247
5248@cindex @code{log@var{m}2} instruction pattern
5249@item @samp{log@var{m}2}
5250Store the natural logarithm of operand 1 into operand 0.
5251
5252The @code{log} built-in function of C always uses the mode which
5253corresponds to the C data type @code{double} and the @code{logf}
5254built-in function uses the mode which corresponds to the C data
5255type @code{float}.
5256
5257@cindex @code{pow@var{m}3} instruction pattern
5258@item @samp{pow@var{m}3}
5259Store the value of operand 1 raised to the exponent operand 2
5260into operand 0.
5261
5262The @code{pow} built-in function of C always uses the mode which
5263corresponds to the C data type @code{double} and the @code{powf}
5264built-in function uses the mode which corresponds to the C data
5265type @code{float}.
5266
5267@cindex @code{atan2@var{m}3} instruction pattern
5268@item @samp{atan2@var{m}3}
5269Store the arc tangent (inverse tangent) of operand 1 divided by
5270operand 2 into operand 0, using the signs of both arguments to
5271determine the quadrant of the result.
5272
5273The @code{atan2} built-in function of C always uses the mode which
5274corresponds to the C data type @code{double} and the @code{atan2f}
5275built-in function uses the mode which corresponds to the C data
5276type @code{float}.
5277
5278@cindex @code{floor@var{m}2} instruction pattern
5279@item @samp{floor@var{m}2}
5280Store the largest integral value not greater than argument.
5281
5282The @code{floor} built-in function of C always uses the mode which
5283corresponds to the C data type @code{double} and the @code{floorf}
5284built-in function uses the mode which corresponds to the C data
5285type @code{float}.
5286
5287@cindex @code{btrunc@var{m}2} instruction pattern
5288@item @samp{btrunc@var{m}2}
5289Store the argument rounded to integer towards zero.
5290
5291The @code{trunc} built-in function of C always uses the mode which
5292corresponds to the C data type @code{double} and the @code{truncf}
5293built-in function uses the mode which corresponds to the C data
5294type @code{float}.
5295
5296@cindex @code{round@var{m}2} instruction pattern
5297@item @samp{round@var{m}2}
5298Store the argument rounded to integer away from zero.
5299
5300The @code{round} built-in function of C always uses the mode which
5301corresponds to the C data type @code{double} and the @code{roundf}
5302built-in function uses the mode which corresponds to the C data
5303type @code{float}.
5304
5305@cindex @code{ceil@var{m}2} instruction pattern
5306@item @samp{ceil@var{m}2}
5307Store the argument rounded to integer away from zero.
5308
5309The @code{ceil} built-in function of C always uses the mode which
5310corresponds to the C data type @code{double} and the @code{ceilf}
5311built-in function uses the mode which corresponds to the C data
5312type @code{float}.
5313
5314@cindex @code{nearbyint@var{m}2} instruction pattern
5315@item @samp{nearbyint@var{m}2}
5316Store the argument rounded according to the default rounding mode
5317
5318The @code{nearbyint} built-in function of C always uses the mode which
5319corresponds to the C data type @code{double} and the @code{nearbyintf}
5320built-in function uses the mode which corresponds to the C data
5321type @code{float}.
5322
5323@cindex @code{rint@var{m}2} instruction pattern
5324@item @samp{rint@var{m}2}
5325Store the argument rounded according to the default rounding mode and
5326raise the inexact exception when the result differs in value from
5327the argument
5328
5329The @code{rint} built-in function of C always uses the mode which
5330corresponds to the C data type @code{double} and the @code{rintf}
5331built-in function uses the mode which corresponds to the C data
5332type @code{float}.
5333
5334@cindex @code{lrint@var{m}@var{n}2}
5335@item @samp{lrint@var{m}@var{n}2}
5336Convert operand 1 (valid for floating point mode @var{m}) to fixed
5337point mode @var{n} as a signed number according to the current
5338rounding mode and store in operand 0 (which has mode @var{n}).
5339
5340@cindex @code{lround@var{m}@var{n}2}
5341@item @samp{lround@var{m}@var{n}2}
5342Convert operand 1 (valid for floating point mode @var{m}) to fixed
5343point mode @var{n} as a signed number rounding to nearest and away
5344from zero and store in operand 0 (which has mode @var{n}).
5345
5346@cindex @code{lfloor@var{m}@var{n}2}
5347@item @samp{lfloor@var{m}@var{n}2}
5348Convert operand 1 (valid for floating point mode @var{m}) to fixed
5349point mode @var{n} as a signed number rounding down and store in
5350operand 0 (which has mode @var{n}).
5351
5352@cindex @code{lceil@var{m}@var{n}2}
5353@item @samp{lceil@var{m}@var{n}2}
5354Convert operand 1 (valid for floating point mode @var{m}) to fixed
5355point mode @var{n} as a signed number rounding up and store in
5356operand 0 (which has mode @var{n}).
5357
5358@cindex @code{copysign@var{m}3} instruction pattern
5359@item @samp{copysign@var{m}3}
5360Store a value with the magnitude of operand 1 and the sign of operand
53612 into operand 0.
5362
5363The @code{copysign} built-in function of C always uses the mode which
5364corresponds to the C data type @code{double} and the @code{copysignf}
5365built-in function uses the mode which corresponds to the C data
5366type @code{float}.
5367
5368@cindex @code{ffs@var{m}2} instruction pattern
5369@item @samp{ffs@var{m}2}
5370Store into operand 0 one plus the index of the least significant 1-bit
5371of operand 1.  If operand 1 is zero, store zero.  @var{m} is the mode
5372of operand 0; operand 1's mode is specified by the instruction
5373pattern, and the compiler will convert the operand to that mode before
5374generating the instruction.
5375
5376The @code{ffs} built-in function of C always uses the mode which
5377corresponds to the C data type @code{int}.
5378
5379@cindex @code{clrsb@var{m}2} instruction pattern
5380@item @samp{clrsb@var{m}2}
5381Count leading redundant sign bits.
5382Store into operand 0 the number of redundant sign bits in operand 1, starting
5383at the most significant bit position.
5384A redundant sign bit is defined as any sign bit after the first. As such,
5385this count will be one less than the count of leading sign bits.
5386
5387@cindex @code{clz@var{m}2} instruction pattern
5388@item @samp{clz@var{m}2}
5389Store into operand 0 the number of leading 0-bits in operand 1, starting
5390at the most significant bit position.  If operand 1 is 0, the
5391@code{CLZ_DEFINED_VALUE_AT_ZERO} (@pxref{Misc}) macro defines if
5392the result is undefined or has a useful value.
5393@var{m} is the mode of operand 0; operand 1's mode is
5394specified by the instruction pattern, and the compiler will convert the
5395operand to that mode before generating the instruction.
5396
5397@cindex @code{ctz@var{m}2} instruction pattern
5398@item @samp{ctz@var{m}2}
5399Store into operand 0 the number of trailing 0-bits in operand 1, starting
5400at the least significant bit position.  If operand 1 is 0, the
5401@code{CTZ_DEFINED_VALUE_AT_ZERO} (@pxref{Misc}) macro defines if
5402the result is undefined or has a useful value.
5403@var{m} is the mode of operand 0; operand 1's mode is
5404specified by the instruction pattern, and the compiler will convert the
5405operand to that mode before generating the instruction.
5406
5407@cindex @code{popcount@var{m}2} instruction pattern
5408@item @samp{popcount@var{m}2}
5409Store into operand 0 the number of 1-bits in operand 1.  @var{m} is the
5410mode of operand 0; operand 1's mode is specified by the instruction
5411pattern, and the compiler will convert the operand to that mode before
5412generating the instruction.
5413
5414@cindex @code{parity@var{m}2} instruction pattern
5415@item @samp{parity@var{m}2}
5416Store into operand 0 the parity of operand 1, i.e.@: the number of 1-bits
5417in operand 1 modulo 2.  @var{m} is the mode of operand 0; operand 1's mode
5418is specified by the instruction pattern, and the compiler will convert
5419the operand to that mode before generating the instruction.
5420
5421@cindex @code{one_cmpl@var{m}2} instruction pattern
5422@item @samp{one_cmpl@var{m}2}
5423Store the bitwise-complement of operand 1 into operand 0.
5424
5425@cindex @code{movmem@var{m}} instruction pattern
5426@item @samp{movmem@var{m}}
5427Block move instruction.  The destination and source blocks of memory
5428are the first two operands, and both are @code{mem:BLK}s with an
5429address in mode @code{Pmode}.
5430
5431The number of bytes to move is the third operand, in mode @var{m}.
5432Usually, you specify @code{Pmode} for @var{m}.  However, if you can
5433generate better code knowing the range of valid lengths is smaller than
5434those representable in a full Pmode pointer, you should provide
5435a pattern with a
5436mode corresponding to the range of values you can handle efficiently
5437(e.g., @code{QImode} for values in the range 0--127; note we avoid numbers
5438that appear negative) and also a pattern with @code{Pmode}.
5439
5440The fourth operand is the known shared alignment of the source and
5441destination, in the form of a @code{const_int} rtx.  Thus, if the
5442compiler knows that both source and destination are word-aligned,
5443it may provide the value 4 for this operand.
5444
5445Optional operands 5 and 6 specify expected alignment and size of block
5446respectively.  The expected alignment differs from alignment in operand 4
5447in a way that the blocks are not required to be aligned according to it in
5448all cases. This expected alignment is also in bytes, just like operand 4.
5449Expected size, when unknown, is set to @code{(const_int -1)}.
5450
5451Descriptions of multiple @code{movmem@var{m}} patterns can only be
5452beneficial if the patterns for smaller modes have fewer restrictions
5453on their first, second and fourth operands.  Note that the mode @var{m}
5454in @code{movmem@var{m}} does not impose any restriction on the mode of
5455individually moved data units in the block.
5456
5457These patterns need not give special consideration to the possibility
5458that the source and destination strings might overlap.
5459
5460@cindex @code{movstr} instruction pattern
5461@item @samp{movstr}
5462String copy instruction, with @code{stpcpy} semantics.  Operand 0 is
5463an output operand in mode @code{Pmode}.  The addresses of the
5464destination and source strings are operands 1 and 2, and both are
5465@code{mem:BLK}s with addresses in mode @code{Pmode}.  The execution of
5466the expansion of this pattern should store in operand 0 the address in
5467which the @code{NUL} terminator was stored in the destination string.
5468
5469This patern has also several optional operands that are same as in
5470@code{setmem}.
5471
5472@cindex @code{setmem@var{m}} instruction pattern
5473@item @samp{setmem@var{m}}
5474Block set instruction.  The destination string is the first operand,
5475given as a @code{mem:BLK} whose address is in mode @code{Pmode}.  The
5476number of bytes to set is the second operand, in mode @var{m}.  The value to
5477initialize the memory with is the third operand. Targets that only support the
5478clearing of memory should reject any value that is not the constant 0.  See
5479@samp{movmem@var{m}} for a discussion of the choice of mode.
5480
5481The fourth operand is the known alignment of the destination, in the form
5482of a @code{const_int} rtx.  Thus, if the compiler knows that the
5483destination is word-aligned, it may provide the value 4 for this
5484operand.
5485
5486Optional operands 5 and 6 specify expected alignment and size of block
5487respectively.  The expected alignment differs from alignment in operand 4
5488in a way that the blocks are not required to be aligned according to it in
5489all cases. This expected alignment is also in bytes, just like operand 4.
5490Expected size, when unknown, is set to @code{(const_int -1)}.
5491Operand 7 is the minimal size of the block and operand 8 is the
5492maximal size of the block (NULL if it can not be represented as CONST_INT).
5493Operand 9 is the probable maximal size (i.e. we can not rely on it for correctness,
5494but it can be used for choosing proper code sequence for a given size).
5495
5496The use for multiple @code{setmem@var{m}} is as for @code{movmem@var{m}}.
5497
5498@cindex @code{cmpstrn@var{m}} instruction pattern
5499@item @samp{cmpstrn@var{m}}
5500String compare instruction, with five operands.  Operand 0 is the output;
5501it has mode @var{m}.  The remaining four operands are like the operands
5502of @samp{movmem@var{m}}.  The two memory blocks specified are compared
5503byte by byte in lexicographic order starting at the beginning of each
5504string.  The instruction is not allowed to prefetch more than one byte
5505at a time since either string may end in the first byte and reading past
5506that may access an invalid page or segment and cause a fault.  The
5507comparison terminates early if the fetched bytes are different or if
5508they are equal to zero.  The effect of the instruction is to store a
5509value in operand 0 whose sign indicates the result of the comparison.
5510
5511@cindex @code{cmpstr@var{m}} instruction pattern
5512@item @samp{cmpstr@var{m}}
5513String compare instruction, without known maximum length.  Operand 0 is the
5514output; it has mode @var{m}.  The second and third operand are the blocks of
5515memory to be compared; both are @code{mem:BLK} with an address in mode
5516@code{Pmode}.
5517
5518The fourth operand is the known shared alignment of the source and
5519destination, in the form of a @code{const_int} rtx.  Thus, if the
5520compiler knows that both source and destination are word-aligned,
5521it may provide the value 4 for this operand.
5522
5523The two memory blocks specified are compared byte by byte in lexicographic
5524order starting at the beginning of each string.  The instruction is not allowed
5525to prefetch more than one byte at a time since either string may end in the
5526first byte and reading past that may access an invalid page or segment and
5527cause a fault.  The comparison will terminate when the fetched bytes
5528are different or if they are equal to zero.  The effect of the
5529instruction is to store a value in operand 0 whose sign indicates the
5530result of the comparison.
5531
5532@cindex @code{cmpmem@var{m}} instruction pattern
5533@item @samp{cmpmem@var{m}}
5534Block compare instruction, with five operands like the operands
5535of @samp{cmpstr@var{m}}.  The two memory blocks specified are compared
5536byte by byte in lexicographic order starting at the beginning of each
5537block.  Unlike @samp{cmpstr@var{m}} the instruction can prefetch
5538any bytes in the two memory blocks.  Also unlike @samp{cmpstr@var{m}}
5539the comparison will not stop if both bytes are zero.  The effect of
5540the instruction is to store a value in operand 0 whose sign indicates
5541the result of the comparison.
5542
5543@cindex @code{strlen@var{m}} instruction pattern
5544@item @samp{strlen@var{m}}
5545Compute the length of a string, with three operands.
5546Operand 0 is the result (of mode @var{m}), operand 1 is
5547a @code{mem} referring to the first character of the string,
5548operand 2 is the character to search for (normally zero),
5549and operand 3 is a constant describing the known alignment
5550of the beginning of the string.
5551
5552@cindex @code{float@var{m}@var{n}2} instruction pattern
5553@item @samp{float@var{m}@var{n}2}
5554Convert signed integer operand 1 (valid for fixed point mode @var{m}) to
5555floating point mode @var{n} and store in operand 0 (which has mode
5556@var{n}).
5557
5558@cindex @code{floatuns@var{m}@var{n}2} instruction pattern
5559@item @samp{floatuns@var{m}@var{n}2}
5560Convert unsigned integer operand 1 (valid for fixed point mode @var{m})
5561to floating point mode @var{n} and store in operand 0 (which has mode
5562@var{n}).
5563
5564@cindex @code{fix@var{m}@var{n}2} instruction pattern
5565@item @samp{fix@var{m}@var{n}2}
5566Convert operand 1 (valid for floating point mode @var{m}) to fixed
5567point mode @var{n} as a signed number and store in operand 0 (which
5568has mode @var{n}).  This instruction's result is defined only when
5569the value of operand 1 is an integer.
5570
5571If the machine description defines this pattern, it also needs to
5572define the @code{ftrunc} pattern.
5573
5574@cindex @code{fixuns@var{m}@var{n}2} instruction pattern
5575@item @samp{fixuns@var{m}@var{n}2}
5576Convert operand 1 (valid for floating point mode @var{m}) to fixed
5577point mode @var{n} as an unsigned number and store in operand 0 (which
5578has mode @var{n}).  This instruction's result is defined only when the
5579value of operand 1 is an integer.
5580
5581@cindex @code{ftrunc@var{m}2} instruction pattern
5582@item @samp{ftrunc@var{m}2}
5583Convert operand 1 (valid for floating point mode @var{m}) to an
5584integer value, still represented in floating point mode @var{m}, and
5585store it in operand 0 (valid for floating point mode @var{m}).
5586
5587@cindex @code{fix_trunc@var{m}@var{n}2} instruction pattern
5588@item @samp{fix_trunc@var{m}@var{n}2}
5589Like @samp{fix@var{m}@var{n}2} but works for any floating point value
5590of mode @var{m} by converting the value to an integer.
5591
5592@cindex @code{fixuns_trunc@var{m}@var{n}2} instruction pattern
5593@item @samp{fixuns_trunc@var{m}@var{n}2}
5594Like @samp{fixuns@var{m}@var{n}2} but works for any floating point
5595value of mode @var{m} by converting the value to an integer.
5596
5597@cindex @code{trunc@var{m}@var{n}2} instruction pattern
5598@item @samp{trunc@var{m}@var{n}2}
5599Truncate operand 1 (valid for mode @var{m}) to mode @var{n} and
5600store in operand 0 (which has mode @var{n}).  Both modes must be fixed
5601point or both floating point.
5602
5603@cindex @code{extend@var{m}@var{n}2} instruction pattern
5604@item @samp{extend@var{m}@var{n}2}
5605Sign-extend operand 1 (valid for mode @var{m}) to mode @var{n} and
5606store in operand 0 (which has mode @var{n}).  Both modes must be fixed
5607point or both floating point.
5608
5609@cindex @code{zero_extend@var{m}@var{n}2} instruction pattern
5610@item @samp{zero_extend@var{m}@var{n}2}
5611Zero-extend operand 1 (valid for mode @var{m}) to mode @var{n} and
5612store in operand 0 (which has mode @var{n}).  Both modes must be fixed
5613point.
5614
5615@cindex @code{fract@var{m}@var{n}2} instruction pattern
5616@item @samp{fract@var{m}@var{n}2}
5617Convert operand 1 of mode @var{m} to mode @var{n} and store in
5618operand 0 (which has mode @var{n}).  Mode @var{m} and mode @var{n}
5619could be fixed-point to fixed-point, signed integer to fixed-point,
5620fixed-point to signed integer, floating-point to fixed-point,
5621or fixed-point to floating-point.
5622When overflows or underflows happen, the results are undefined.
5623
5624@cindex @code{satfract@var{m}@var{n}2} instruction pattern
5625@item @samp{satfract@var{m}@var{n}2}
5626Convert operand 1 of mode @var{m} to mode @var{n} and store in
5627operand 0 (which has mode @var{n}).  Mode @var{m} and mode @var{n}
5628could be fixed-point to fixed-point, signed integer to fixed-point,
5629or floating-point to fixed-point.
5630When overflows or underflows happen, the instruction saturates the
5631results to the maximum or the minimum.
5632
5633@cindex @code{fractuns@var{m}@var{n}2} instruction pattern
5634@item @samp{fractuns@var{m}@var{n}2}
5635Convert operand 1 of mode @var{m} to mode @var{n} and store in
5636operand 0 (which has mode @var{n}).  Mode @var{m} and mode @var{n}
5637could be unsigned integer to fixed-point, or
5638fixed-point to unsigned integer.
5639When overflows or underflows happen, the results are undefined.
5640
5641@cindex @code{satfractuns@var{m}@var{n}2} instruction pattern
5642@item @samp{satfractuns@var{m}@var{n}2}
5643Convert unsigned integer operand 1 of mode @var{m} to fixed-point mode
5644@var{n} and store in operand 0 (which has mode @var{n}).
5645When overflows or underflows happen, the instruction saturates the
5646results to the maximum or the minimum.
5647
5648@cindex @code{extv@var{m}} instruction pattern
5649@item @samp{extv@var{m}}
5650Extract a bit-field from register operand 1, sign-extend it, and store
5651it in operand 0.  Operand 2 specifies the width of the field in bits
5652and operand 3 the starting bit, which counts from the most significant
5653bit if @samp{BITS_BIG_ENDIAN} is true and from the least significant bit
5654otherwise.
5655
5656Operands 0 and 1 both have mode @var{m}.  Operands 2 and 3 have a
5657target-specific mode.
5658
5659@cindex @code{extvmisalign@var{m}} instruction pattern
5660@item @samp{extvmisalign@var{m}}
5661Extract a bit-field from memory operand 1, sign extend it, and store
5662it in operand 0.  Operand 2 specifies the width in bits and operand 3
5663the starting bit.  The starting bit is always somewhere in the first byte of
5664operand 1; it counts from the most significant bit if @samp{BITS_BIG_ENDIAN}
5665is true and from the least significant bit otherwise.
5666
5667Operand 0 has mode @var{m} while operand 1 has @code{BLK} mode.
5668Operands 2 and 3 have a target-specific mode.
5669
5670The instruction must not read beyond the last byte of the bit-field.
5671
5672@cindex @code{extzv@var{m}} instruction pattern
5673@item @samp{extzv@var{m}}
5674Like @samp{extv@var{m}} except that the bit-field value is zero-extended.
5675
5676@cindex @code{extzvmisalign@var{m}} instruction pattern
5677@item @samp{extzvmisalign@var{m}}
5678Like @samp{extvmisalign@var{m}} except that the bit-field value is
5679zero-extended.
5680
5681@cindex @code{insv@var{m}} instruction pattern
5682@item @samp{insv@var{m}}
5683Insert operand 3 into a bit-field of register operand 0.  Operand 1
5684specifies the width of the field in bits and operand 2 the starting bit,
5685which counts from the most significant bit if @samp{BITS_BIG_ENDIAN}
5686is true and from the least significant bit otherwise.
5687
5688Operands 0 and 3 both have mode @var{m}.  Operands 1 and 2 have a
5689target-specific mode.
5690
5691@cindex @code{insvmisalign@var{m}} instruction pattern
5692@item @samp{insvmisalign@var{m}}
5693Insert operand 3 into a bit-field of memory operand 0.  Operand 1
5694specifies the width of the field in bits and operand 2 the starting bit.
5695The starting bit is always somewhere in the first byte of operand 0;
5696it counts from the most significant bit if @samp{BITS_BIG_ENDIAN}
5697is true and from the least significant bit otherwise.
5698
5699Operand 3 has mode @var{m} while operand 0 has @code{BLK} mode.
5700Operands 1 and 2 have a target-specific mode.
5701
5702The instruction must not read or write beyond the last byte of the bit-field.
5703
5704@cindex @code{extv} instruction pattern
5705@item @samp{extv}
5706Extract a bit-field from operand 1 (a register or memory operand), where
5707operand 2 specifies the width in bits and operand 3 the starting bit,
5708and store it in operand 0.  Operand 0 must have mode @code{word_mode}.
5709Operand 1 may have mode @code{byte_mode} or @code{word_mode}; often
5710@code{word_mode} is allowed only for registers.  Operands 2 and 3 must
5711be valid for @code{word_mode}.
5712
5713The RTL generation pass generates this instruction only with constants
5714for operands 2 and 3 and the constant is never zero for operand 2.
5715
5716The bit-field value is sign-extended to a full word integer
5717before it is stored in operand 0.
5718
5719This pattern is deprecated; please use @samp{extv@var{m}} and
5720@code{extvmisalign@var{m}} instead.
5721
5722@cindex @code{extzv} instruction pattern
5723@item @samp{extzv}
5724Like @samp{extv} except that the bit-field value is zero-extended.
5725
5726This pattern is deprecated; please use @samp{extzv@var{m}} and
5727@code{extzvmisalign@var{m}} instead.
5728
5729@cindex @code{insv} instruction pattern
5730@item @samp{insv}
5731Store operand 3 (which must be valid for @code{word_mode}) into a
5732bit-field in operand 0, where operand 1 specifies the width in bits and
5733operand 2 the starting bit.  Operand 0 may have mode @code{byte_mode} or
5734@code{word_mode}; often @code{word_mode} is allowed only for registers.
5735Operands 1 and 2 must be valid for @code{word_mode}.
5736
5737The RTL generation pass generates this instruction only with constants
5738for operands 1 and 2 and the constant is never zero for operand 1.
5739
5740This pattern is deprecated; please use @samp{insv@var{m}} and
5741@code{insvmisalign@var{m}} instead.
5742
5743@cindex @code{mov@var{mode}cc} instruction pattern
5744@item @samp{mov@var{mode}cc}
5745Conditionally move operand 2 or operand 3 into operand 0 according to the
5746comparison in operand 1.  If the comparison is true, operand 2 is moved
5747into operand 0, otherwise operand 3 is moved.
5748
5749The mode of the operands being compared need not be the same as the operands
5750being moved.  Some machines, sparc64 for example, have instructions that
5751conditionally move an integer value based on the floating point condition
5752codes and vice versa.
5753
5754If the machine does not have conditional move instructions, do not
5755define these patterns.
5756
5757@cindex @code{add@var{mode}cc} instruction pattern
5758@item @samp{add@var{mode}cc}
5759Similar to @samp{mov@var{mode}cc} but for conditional addition.  Conditionally
5760move operand 2 or (operands 2 + operand 3) into operand 0 according to the
5761comparison in operand 1.  If the comparison is false, operand 2 is moved into
5762operand 0, otherwise (operand 2 + operand 3) is moved.
5763
5764@cindex @code{cstore@var{mode}4} instruction pattern
5765@item @samp{cstore@var{mode}4}
5766Store zero or nonzero in operand 0 according to whether a comparison
5767is true.  Operand 1 is a comparison operator.  Operand 2 and operand 3
5768are the first and second operand of the comparison, respectively.
5769You specify the mode that operand 0 must have when you write the
5770@code{match_operand} expression.  The compiler automatically sees which
5771mode you have used and supplies an operand of that mode.
5772
5773The value stored for a true condition must have 1 as its low bit, or
5774else must be negative.  Otherwise the instruction is not suitable and
5775you should omit it from the machine description.  You describe to the
5776compiler exactly which value is stored by defining the macro
5777@code{STORE_FLAG_VALUE} (@pxref{Misc}).  If a description cannot be
5778found that can be used for all the possible comparison operators, you
5779should pick one and use a @code{define_expand} to map all results
5780onto the one you chose.
5781
5782These operations may @code{FAIL}, but should do so only in relatively
5783uncommon cases; if they would @code{FAIL} for common cases involving
5784integer comparisons, it is best to restrict the predicates to not
5785allow these operands.  Likewise if a given comparison operator will
5786always fail, independent of the operands (for floating-point modes, the
5787@code{ordered_comparison_operator} predicate is often useful in this case).
5788
5789If this pattern is omitted, the compiler will generate a conditional
5790branch---for example, it may copy a constant one to the target and branching
5791around an assignment of zero to the target---or a libcall.  If the predicate
5792for operand 1 only rejects some operators, it will also try reordering the
5793operands and/or inverting the result value (e.g.@: by an exclusive OR).
5794These possibilities could be cheaper or equivalent to the instructions
5795used for the @samp{cstore@var{mode}4} pattern followed by those required
5796to convert a positive result from @code{STORE_FLAG_VALUE} to 1; in this
5797case, you can and should make operand 1's predicate reject some operators
5798in the @samp{cstore@var{mode}4} pattern, or remove the pattern altogether
5799from the machine description.
5800
5801@cindex @code{cbranch@var{mode}4} instruction pattern
5802@item @samp{cbranch@var{mode}4}
5803Conditional branch instruction combined with a compare instruction.
5804Operand 0 is a comparison operator.  Operand 1 and operand 2 are the
5805first and second operands of the comparison, respectively.  Operand 3
5806is the @code{code_label} to jump to.
5807
5808@cindex @code{jump} instruction pattern
5809@item @samp{jump}
5810A jump inside a function; an unconditional branch.  Operand 0 is the
5811@code{code_label} to jump to.  This pattern name is mandatory on all
5812machines.
5813
5814@cindex @code{call} instruction pattern
5815@item @samp{call}
5816Subroutine call instruction returning no value.  Operand 0 is the
5817function to call; operand 1 is the number of bytes of arguments pushed
5818as a @code{const_int}; operand 2 is the number of registers used as
5819operands.
5820
5821On most machines, operand 2 is not actually stored into the RTL
5822pattern.  It is supplied for the sake of some RISC machines which need
5823to put this information into the assembler code; they can put it in
5824the RTL instead of operand 1.
5825
5826Operand 0 should be a @code{mem} RTX whose address is the address of the
5827function.  Note, however, that this address can be a @code{symbol_ref}
5828expression even if it would not be a legitimate memory address on the
5829target machine.  If it is also not a valid argument for a call
5830instruction, the pattern for this operation should be a
5831@code{define_expand} (@pxref{Expander Definitions}) that places the
5832address into a register and uses that register in the call instruction.
5833
5834@cindex @code{call_value} instruction pattern
5835@item @samp{call_value}
5836Subroutine call instruction returning a value.  Operand 0 is the hard
5837register in which the value is returned.  There are three more
5838operands, the same as the three operands of the @samp{call}
5839instruction (but with numbers increased by one).
5840
5841Subroutines that return @code{BLKmode} objects use the @samp{call}
5842insn.
5843
5844@cindex @code{call_pop} instruction pattern
5845@cindex @code{call_value_pop} instruction pattern
5846@item @samp{call_pop}, @samp{call_value_pop}
5847Similar to @samp{call} and @samp{call_value}, except used if defined and
5848if @code{RETURN_POPS_ARGS} is nonzero.  They should emit a @code{parallel}
5849that contains both the function call and a @code{set} to indicate the
5850adjustment made to the frame pointer.
5851
5852For machines where @code{RETURN_POPS_ARGS} can be nonzero, the use of these
5853patterns increases the number of functions for which the frame pointer
5854can be eliminated, if desired.
5855
5856@cindex @code{untyped_call} instruction pattern
5857@item @samp{untyped_call}
5858Subroutine call instruction returning a value of any type.  Operand 0 is
5859the function to call; operand 1 is a memory location where the result of
5860calling the function is to be stored; operand 2 is a @code{parallel}
5861expression where each element is a @code{set} expression that indicates
5862the saving of a function return value into the result block.
5863
5864This instruction pattern should be defined to support
5865@code{__builtin_apply} on machines where special instructions are needed
5866to call a subroutine with arbitrary arguments or to save the value
5867returned.  This instruction pattern is required on machines that have
5868multiple registers that can hold a return value
5869(i.e.@: @code{FUNCTION_VALUE_REGNO_P} is true for more than one register).
5870
5871@cindex @code{return} instruction pattern
5872@item @samp{return}
5873Subroutine return instruction.  This instruction pattern name should be
5874defined only if a single instruction can do all the work of returning
5875from a function.
5876
5877Like the @samp{mov@var{m}} patterns, this pattern is also used after the
5878RTL generation phase.  In this case it is to support machines where
5879multiple instructions are usually needed to return from a function, but
5880some class of functions only requires one instruction to implement a
5881return.  Normally, the applicable functions are those which do not need
5882to save any registers or allocate stack space.
5883
5884It is valid for this pattern to expand to an instruction using
5885@code{simple_return} if no epilogue is required.
5886
5887@cindex @code{simple_return} instruction pattern
5888@item @samp{simple_return}
5889Subroutine return instruction.  This instruction pattern name should be
5890defined only if a single instruction can do all the work of returning
5891from a function on a path where no epilogue is required.  This pattern
5892is very similar to the @code{return} instruction pattern, but it is emitted
5893only by the shrink-wrapping optimization on paths where the function
5894prologue has not been executed, and a function return should occur without
5895any of the effects of the epilogue.  Additional uses may be introduced on
5896paths where both the prologue and the epilogue have executed.
5897
5898@findex reload_completed
5899@findex leaf_function_p
5900For such machines, the condition specified in this pattern should only
5901be true when @code{reload_completed} is nonzero and the function's
5902epilogue would only be a single instruction.  For machines with register
5903windows, the routine @code{leaf_function_p} may be used to determine if
5904a register window push is required.
5905
5906Machines that have conditional return instructions should define patterns
5907such as
5908
5909@smallexample
5910(define_insn ""
5911  [(set (pc)
5912        (if_then_else (match_operator
5913                         0 "comparison_operator"
5914                         [(cc0) (const_int 0)])
5915                      (return)
5916                      (pc)))]
5917  "@var{condition}"
5918  "@dots{}")
5919@end smallexample
5920
5921where @var{condition} would normally be the same condition specified on the
5922named @samp{return} pattern.
5923
5924@cindex @code{untyped_return} instruction pattern
5925@item @samp{untyped_return}
5926Untyped subroutine return instruction.  This instruction pattern should
5927be defined to support @code{__builtin_return} on machines where special
5928instructions are needed to return a value of any type.
5929
5930Operand 0 is a memory location where the result of calling a function
5931with @code{__builtin_apply} is stored; operand 1 is a @code{parallel}
5932expression where each element is a @code{set} expression that indicates
5933the restoring of a function return value from the result block.
5934
5935@cindex @code{nop} instruction pattern
5936@item @samp{nop}
5937No-op instruction.  This instruction pattern name should always be defined
5938to output a no-op in assembler code.  @code{(const_int 0)} will do as an
5939RTL pattern.
5940
5941@cindex @code{indirect_jump} instruction pattern
5942@item @samp{indirect_jump}
5943An instruction to jump to an address which is operand zero.
5944This pattern name is mandatory on all machines.
5945
5946@cindex @code{casesi} instruction pattern
5947@item @samp{casesi}
5948Instruction to jump through a dispatch table, including bounds checking.
5949This instruction takes five operands:
5950
5951@enumerate
5952@item
5953The index to dispatch on, which has mode @code{SImode}.
5954
5955@item
5956The lower bound for indices in the table, an integer constant.
5957
5958@item
5959The total range of indices in the table---the largest index
5960minus the smallest one (both inclusive).
5961
5962@item
5963A label that precedes the table itself.
5964
5965@item
5966A label to jump to if the index has a value outside the bounds.
5967@end enumerate
5968
5969The table is an @code{addr_vec} or @code{addr_diff_vec} inside of a
5970@code{jump_table_data}.  The number of elements in the table is one plus the
5971difference between the upper bound and the lower bound.
5972
5973@cindex @code{tablejump} instruction pattern
5974@item @samp{tablejump}
5975Instruction to jump to a variable address.  This is a low-level
5976capability which can be used to implement a dispatch table when there
5977is no @samp{casesi} pattern.
5978
5979This pattern requires two operands: the address or offset, and a label
5980which should immediately precede the jump table.  If the macro
5981@code{CASE_VECTOR_PC_RELATIVE} evaluates to a nonzero value then the first
5982operand is an offset which counts from the address of the table; otherwise,
5983it is an absolute address to jump to.  In either case, the first operand has
5984mode @code{Pmode}.
5985
5986The @samp{tablejump} insn is always the last insn before the jump
5987table it uses.  Its assembler code normally has no need to use the
5988second operand, but you should incorporate it in the RTL pattern so
5989that the jump optimizer will not delete the table as unreachable code.
5990
5991
5992@cindex @code{decrement_and_branch_until_zero} instruction pattern
5993@item @samp{decrement_and_branch_until_zero}
5994Conditional branch instruction that decrements a register and
5995jumps if the register is nonzero.  Operand 0 is the register to
5996decrement and test; operand 1 is the label to jump to if the
5997register is nonzero.  @xref{Looping Patterns}.
5998
5999This optional instruction pattern is only used by the combiner,
6000typically for loops reversed by the loop optimizer when strength
6001reduction is enabled.
6002
6003@cindex @code{doloop_end} instruction pattern
6004@item @samp{doloop_end}
6005Conditional branch instruction that decrements a register and
6006jumps if the register is nonzero.  Operand 0 is the register to
6007decrement and test; operand 1 is the label to jump to if the
6008register is nonzero.
6009@xref{Looping Patterns}.
6010
6011This optional instruction pattern should be defined for machines with
6012low-overhead looping instructions as the loop optimizer will try to
6013modify suitable loops to utilize it.  The target hook
6014@code{TARGET_CAN_USE_DOLOOP_P} controls the conditions under which
6015low-overhead loops can be used.
6016
6017@cindex @code{doloop_begin} instruction pattern
6018@item @samp{doloop_begin}
6019Companion instruction to @code{doloop_end} required for machines that
6020need to perform some initialization, such as loading a special counter
6021register.  Operand 1 is the associated @code{doloop_end} pattern and
6022operand 0 is the register that it decrements.
6023
6024If initialization insns do not always need to be emitted, use a
6025@code{define_expand} (@pxref{Expander Definitions}) and make it fail.
6026
6027@cindex @code{canonicalize_funcptr_for_compare} instruction pattern
6028@item @samp{canonicalize_funcptr_for_compare}
6029Canonicalize the function pointer in operand 1 and store the result
6030into operand 0.
6031
6032Operand 0 is always a @code{reg} and has mode @code{Pmode}; operand 1
6033may be a @code{reg}, @code{mem}, @code{symbol_ref}, @code{const_int}, etc
6034and also has mode @code{Pmode}.
6035
6036Canonicalization of a function pointer usually involves computing
6037the address of the function which would be called if the function
6038pointer were used in an indirect call.
6039
6040Only define this pattern if function pointers on the target machine
6041can have different values but still call the same function when
6042used in an indirect call.
6043
6044@cindex @code{save_stack_block} instruction pattern
6045@cindex @code{save_stack_function} instruction pattern
6046@cindex @code{save_stack_nonlocal} instruction pattern
6047@cindex @code{restore_stack_block} instruction pattern
6048@cindex @code{restore_stack_function} instruction pattern
6049@cindex @code{restore_stack_nonlocal} instruction pattern
6050@item @samp{save_stack_block}
6051@itemx @samp{save_stack_function}
6052@itemx @samp{save_stack_nonlocal}
6053@itemx @samp{restore_stack_block}
6054@itemx @samp{restore_stack_function}
6055@itemx @samp{restore_stack_nonlocal}
6056Most machines save and restore the stack pointer by copying it to or
6057from an object of mode @code{Pmode}.  Do not define these patterns on
6058such machines.
6059
6060Some machines require special handling for stack pointer saves and
6061restores.  On those machines, define the patterns corresponding to the
6062non-standard cases by using a @code{define_expand} (@pxref{Expander
6063Definitions}) that produces the required insns.  The three types of
6064saves and restores are:
6065
6066@enumerate
6067@item
6068@samp{save_stack_block} saves the stack pointer at the start of a block
6069that allocates a variable-sized object, and @samp{restore_stack_block}
6070restores the stack pointer when the block is exited.
6071
6072@item
6073@samp{save_stack_function} and @samp{restore_stack_function} do a
6074similar job for the outermost block of a function and are used when the
6075function allocates variable-sized objects or calls @code{alloca}.  Only
6076the epilogue uses the restored stack pointer, allowing a simpler save or
6077restore sequence on some machines.
6078
6079@item
6080@samp{save_stack_nonlocal} is used in functions that contain labels
6081branched to by nested functions.  It saves the stack pointer in such a
6082way that the inner function can use @samp{restore_stack_nonlocal} to
6083restore the stack pointer.  The compiler generates code to restore the
6084frame and argument pointer registers, but some machines require saving
6085and restoring additional data such as register window information or
6086stack backchains.  Place insns in these patterns to save and restore any
6087such required data.
6088@end enumerate
6089
6090When saving the stack pointer, operand 0 is the save area and operand 1
6091is the stack pointer.  The mode used to allocate the save area defaults
6092to @code{Pmode} but you can override that choice by defining the
6093@code{STACK_SAVEAREA_MODE} macro (@pxref{Storage Layout}).  You must
6094specify an integral mode, or @code{VOIDmode} if no save area is needed
6095for a particular type of save (either because no save is needed or
6096because a machine-specific save area can be used).  Operand 0 is the
6097stack pointer and operand 1 is the save area for restore operations.  If
6098@samp{save_stack_block} is defined, operand 0 must not be
6099@code{VOIDmode} since these saves can be arbitrarily nested.
6100
6101A save area is a @code{mem} that is at a constant offset from
6102@code{virtual_stack_vars_rtx} when the stack pointer is saved for use by
6103nonlocal gotos and a @code{reg} in the other two cases.
6104
6105@cindex @code{allocate_stack} instruction pattern
6106@item @samp{allocate_stack}
6107Subtract (or add if @code{STACK_GROWS_DOWNWARD} is undefined) operand 1 from
6108the stack pointer to create space for dynamically allocated data.
6109
6110Store the resultant pointer to this space into operand 0.  If you
6111are allocating space from the main stack, do this by emitting a
6112move insn to copy @code{virtual_stack_dynamic_rtx} to operand 0.
6113If you are allocating the space elsewhere, generate code to copy the
6114location of the space to operand 0.  In the latter case, you must
6115ensure this space gets freed when the corresponding space on the main
6116stack is free.
6117
6118Do not define this pattern if all that must be done is the subtraction.
6119Some machines require other operations such as stack probes or
6120maintaining the back chain.  Define this pattern to emit those
6121operations in addition to updating the stack pointer.
6122
6123@cindex @code{check_stack} instruction pattern
6124@item @samp{check_stack}
6125If stack checking (@pxref{Stack Checking}) cannot be done on your system by
6126probing the stack, define this pattern to perform the needed check and signal
6127an error if the stack has overflowed.  The single operand is the address in
6128the stack farthest from the current stack pointer that you need to validate.
6129Normally, on platforms where this pattern is needed, you would obtain the
6130stack limit from a global or thread-specific variable or register.
6131
6132@cindex @code{probe_stack_address} instruction pattern
6133@item @samp{probe_stack_address}
6134If stack checking (@pxref{Stack Checking}) can be done on your system by
6135probing the stack but without the need to actually access it, define this
6136pattern and signal an error if the stack has overflowed.  The single operand
6137is the memory address in the stack that needs to be probed.
6138
6139@cindex @code{probe_stack} instruction pattern
6140@item @samp{probe_stack}
6141If stack checking (@pxref{Stack Checking}) can be done on your system by
6142probing the stack but doing it with a ``store zero'' instruction is not valid
6143or optimal, define this pattern to do the probing differently and signal an
6144error if the stack has overflowed.  The single operand is the memory reference
6145in the stack that needs to be probed.
6146
6147@cindex @code{nonlocal_goto} instruction pattern
6148@item @samp{nonlocal_goto}
6149Emit code to generate a non-local goto, e.g., a jump from one function
6150to a label in an outer function.  This pattern has four arguments,
6151each representing a value to be used in the jump.  The first
6152argument is to be loaded into the frame pointer, the second is
6153the address to branch to (code to dispatch to the actual label),
6154the third is the address of a location where the stack is saved,
6155and the last is the address of the label, to be placed in the
6156location for the incoming static chain.
6157
6158On most machines you need not define this pattern, since GCC will
6159already generate the correct code, which is to load the frame pointer
6160and static chain, restore the stack (using the
6161@samp{restore_stack_nonlocal} pattern, if defined), and jump indirectly
6162to the dispatcher.  You need only define this pattern if this code will
6163not work on your machine.
6164
6165@cindex @code{nonlocal_goto_receiver} instruction pattern
6166@item @samp{nonlocal_goto_receiver}
6167This pattern, if defined, contains code needed at the target of a
6168nonlocal goto after the code already generated by GCC@.  You will not
6169normally need to define this pattern.  A typical reason why you might
6170need this pattern is if some value, such as a pointer to a global table,
6171must be restored when the frame pointer is restored.  Note that a nonlocal
6172goto only occurs within a unit-of-translation, so a global table pointer
6173that is shared by all functions of a given module need not be restored.
6174There are no arguments.
6175
6176@cindex @code{exception_receiver} instruction pattern
6177@item @samp{exception_receiver}
6178This pattern, if defined, contains code needed at the site of an
6179exception handler that isn't needed at the site of a nonlocal goto.  You
6180will not normally need to define this pattern.  A typical reason why you
6181might need this pattern is if some value, such as a pointer to a global
6182table, must be restored after control flow is branched to the handler of
6183an exception.  There are no arguments.
6184
6185@cindex @code{builtin_setjmp_setup} instruction pattern
6186@item @samp{builtin_setjmp_setup}
6187This pattern, if defined, contains additional code needed to initialize
6188the @code{jmp_buf}.  You will not normally need to define this pattern.
6189A typical reason why you might need this pattern is if some value, such
6190as a pointer to a global table, must be restored.  Though it is
6191preferred that the pointer value be recalculated if possible (given the
6192address of a label for instance).  The single argument is a pointer to
6193the @code{jmp_buf}.  Note that the buffer is five words long and that
6194the first three are normally used by the generic mechanism.
6195
6196@cindex @code{builtin_setjmp_receiver} instruction pattern
6197@item @samp{builtin_setjmp_receiver}
6198This pattern, if defined, contains code needed at the site of a
6199built-in setjmp that isn't needed at the site of a nonlocal goto.  You
6200will not normally need to define this pattern.  A typical reason why you
6201might need this pattern is if some value, such as a pointer to a global
6202table, must be restored.  It takes one argument, which is the label
6203to which builtin_longjmp transferred control; this pattern may be emitted
6204at a small offset from that label.
6205
6206@cindex @code{builtin_longjmp} instruction pattern
6207@item @samp{builtin_longjmp}
6208This pattern, if defined, performs the entire action of the longjmp.
6209You will not normally need to define this pattern unless you also define
6210@code{builtin_setjmp_setup}.  The single argument is a pointer to the
6211@code{jmp_buf}.
6212
6213@cindex @code{eh_return} instruction pattern
6214@item @samp{eh_return}
6215This pattern, if defined, affects the way @code{__builtin_eh_return},
6216and thence the call frame exception handling library routines, are
6217built.  It is intended to handle non-trivial actions needed along
6218the abnormal return path.
6219
6220The address of the exception handler to which the function should return
6221is passed as operand to this pattern.  It will normally need to copied by
6222the pattern to some special register or memory location.
6223If the pattern needs to determine the location of the target call
6224frame in order to do so, it may use @code{EH_RETURN_STACKADJ_RTX},
6225if defined; it will have already been assigned.
6226
6227If this pattern is not defined, the default action will be to simply
6228copy the return address to @code{EH_RETURN_HANDLER_RTX}.  Either
6229that macro or this pattern needs to be defined if call frame exception
6230handling is to be used.
6231
6232@cindex @code{prologue} instruction pattern
6233@anchor{prologue instruction pattern}
6234@item @samp{prologue}
6235This pattern, if defined, emits RTL for entry to a function.  The function
6236entry is responsible for setting up the stack frame, initializing the frame
6237pointer register, saving callee saved registers, etc.
6238
6239Using a prologue pattern is generally preferred over defining
6240@code{TARGET_ASM_FUNCTION_PROLOGUE} to emit assembly code for the prologue.
6241
6242The @code{prologue} pattern is particularly useful for targets which perform
6243instruction scheduling.
6244
6245@cindex @code{window_save} instruction pattern
6246@anchor{window_save instruction pattern}
6247@item @samp{window_save}
6248This pattern, if defined, emits RTL for a register window save.  It should
6249be defined if the target machine has register windows but the window events
6250are decoupled from calls to subroutines.  The canonical example is the SPARC
6251architecture.
6252
6253@cindex @code{epilogue} instruction pattern
6254@anchor{epilogue instruction pattern}
6255@item @samp{epilogue}
6256This pattern emits RTL for exit from a function.  The function
6257exit is responsible for deallocating the stack frame, restoring callee saved
6258registers and emitting the return instruction.
6259
6260Using an epilogue pattern is generally preferred over defining
6261@code{TARGET_ASM_FUNCTION_EPILOGUE} to emit assembly code for the epilogue.
6262
6263The @code{epilogue} pattern is particularly useful for targets which perform
6264instruction scheduling or which have delay slots for their return instruction.
6265
6266@cindex @code{sibcall_epilogue} instruction pattern
6267@item @samp{sibcall_epilogue}
6268This pattern, if defined, emits RTL for exit from a function without the final
6269branch back to the calling function.  This pattern will be emitted before any
6270sibling call (aka tail call) sites.
6271
6272The @code{sibcall_epilogue} pattern must not clobber any arguments used for
6273parameter passing or any stack slots for arguments passed to the current
6274function.
6275
6276@cindex @code{trap} instruction pattern
6277@item @samp{trap}
6278This pattern, if defined, signals an error, typically by causing some
6279kind of signal to be raised.  Among other places, it is used by the Java
6280front end to signal `invalid array index' exceptions.
6281
6282@cindex @code{ctrap@var{MM}4} instruction pattern
6283@item @samp{ctrap@var{MM}4}
6284Conditional trap instruction.  Operand 0 is a piece of RTL which
6285performs a comparison, and operands 1 and 2 are the arms of the
6286comparison.  Operand 3 is the trap code, an integer.
6287
6288A typical @code{ctrap} pattern looks like
6289
6290@smallexample
6291(define_insn "ctrapsi4"
6292  [(trap_if (match_operator 0 "trap_operator"
6293             [(match_operand 1 "register_operand")
6294              (match_operand 2 "immediate_operand")])
6295            (match_operand 3 "const_int_operand" "i"))]
6296  ""
6297  "@dots{}")
6298@end smallexample
6299
6300@cindex @code{prefetch} instruction pattern
6301@item @samp{prefetch}
6302This pattern, if defined, emits code for a non-faulting data prefetch
6303instruction.  Operand 0 is the address of the memory to prefetch.  Operand 1
6304is a constant 1 if the prefetch is preparing for a write to the memory
6305address, or a constant 0 otherwise.  Operand 2 is the expected degree of
6306temporal locality of the data and is a value between 0 and 3, inclusive; 0
6307means that the data has no temporal locality, so it need not be left in the
6308cache after the access; 3 means that the data has a high degree of temporal
6309locality and should be left in all levels of cache possible;  1 and 2 mean,
6310respectively, a low or moderate degree of temporal locality.
6311
6312Targets that do not support write prefetches or locality hints can ignore
6313the values of operands 1 and 2.
6314
6315@cindex @code{blockage} instruction pattern
6316@item @samp{blockage}
6317This pattern defines a pseudo insn that prevents the instruction
6318scheduler and other passes from moving instructions and using register
6319equivalences across the boundary defined by the blockage insn.
6320This needs to be an UNSPEC_VOLATILE pattern or a volatile ASM.
6321
6322@cindex @code{memory_barrier} instruction pattern
6323@item @samp{memory_barrier}
6324If the target memory model is not fully synchronous, then this pattern
6325should be defined to an instruction that orders both loads and stores
6326before the instruction with respect to loads and stores after the instruction.
6327This pattern has no operands.
6328
6329@cindex @code{sync_compare_and_swap@var{mode}} instruction pattern
6330@item @samp{sync_compare_and_swap@var{mode}}
6331This pattern, if defined, emits code for an atomic compare-and-swap
6332operation.  Operand 1 is the memory on which the atomic operation is
6333performed.  Operand 2 is the ``old'' value to be compared against the
6334current contents of the memory location.  Operand 3 is the ``new'' value
6335to store in the memory if the compare succeeds.  Operand 0 is the result
6336of the operation; it should contain the contents of the memory
6337before the operation.  If the compare succeeds, this should obviously be
6338a copy of operand 2.
6339
6340This pattern must show that both operand 0 and operand 1 are modified.
6341
6342This pattern must issue any memory barrier instructions such that all
6343memory operations before the atomic operation occur before the atomic
6344operation and all memory operations after the atomic operation occur
6345after the atomic operation.
6346
6347For targets where the success or failure of the compare-and-swap
6348operation is available via the status flags, it is possible to
6349avoid a separate compare operation and issue the subsequent
6350branch or store-flag operation immediately after the compare-and-swap.
6351To this end, GCC will look for a @code{MODE_CC} set in the
6352output of @code{sync_compare_and_swap@var{mode}}; if the machine
6353description includes such a set, the target should also define special
6354@code{cbranchcc4} and/or @code{cstorecc4} instructions.  GCC will then
6355be able to take the destination of the @code{MODE_CC} set and pass it
6356to the @code{cbranchcc4} or @code{cstorecc4} pattern as the first
6357operand of the comparison (the second will be @code{(const_int 0)}).
6358
6359For targets where the operating system may provide support for this
6360operation via library calls, the @code{sync_compare_and_swap_optab}
6361may be initialized to a function with the same interface as the
6362@code{__sync_val_compare_and_swap_@var{n}} built-in.  If the entire
6363set of @var{__sync} builtins are supported via library calls, the
6364target can initialize all of the optabs at once with
6365@code{init_sync_libfuncs}.
6366For the purposes of C++11 @code{std::atomic::is_lock_free}, it is
6367assumed that these library calls do @emph{not} use any kind of
6368interruptable locking.
6369
6370@cindex @code{sync_add@var{mode}} instruction pattern
6371@cindex @code{sync_sub@var{mode}} instruction pattern
6372@cindex @code{sync_ior@var{mode}} instruction pattern
6373@cindex @code{sync_and@var{mode}} instruction pattern
6374@cindex @code{sync_xor@var{mode}} instruction pattern
6375@cindex @code{sync_nand@var{mode}} instruction pattern
6376@item @samp{sync_add@var{mode}}, @samp{sync_sub@var{mode}}
6377@itemx @samp{sync_ior@var{mode}}, @samp{sync_and@var{mode}}
6378@itemx @samp{sync_xor@var{mode}}, @samp{sync_nand@var{mode}}
6379These patterns emit code for an atomic operation on memory.
6380Operand 0 is the memory on which the atomic operation is performed.
6381Operand 1 is the second operand to the binary operator.
6382
6383This pattern must issue any memory barrier instructions such that all
6384memory operations before the atomic operation occur before the atomic
6385operation and all memory operations after the atomic operation occur
6386after the atomic operation.
6387
6388If these patterns are not defined, the operation will be constructed
6389from a compare-and-swap operation, if defined.
6390
6391@cindex @code{sync_old_add@var{mode}} instruction pattern
6392@cindex @code{sync_old_sub@var{mode}} instruction pattern
6393@cindex @code{sync_old_ior@var{mode}} instruction pattern
6394@cindex @code{sync_old_and@var{mode}} instruction pattern
6395@cindex @code{sync_old_xor@var{mode}} instruction pattern
6396@cindex @code{sync_old_nand@var{mode}} instruction pattern
6397@item @samp{sync_old_add@var{mode}}, @samp{sync_old_sub@var{mode}}
6398@itemx @samp{sync_old_ior@var{mode}}, @samp{sync_old_and@var{mode}}
6399@itemx @samp{sync_old_xor@var{mode}}, @samp{sync_old_nand@var{mode}}
6400These patterns emit code for an atomic operation on memory,
6401and return the value that the memory contained before the operation.
6402Operand 0 is the result value, operand 1 is the memory on which the
6403atomic operation is performed, and operand 2 is the second operand
6404to the binary operator.
6405
6406This pattern must issue any memory barrier instructions such that all
6407memory operations before the atomic operation occur before the atomic
6408operation and all memory operations after the atomic operation occur
6409after the atomic operation.
6410
6411If these patterns are not defined, the operation will be constructed
6412from a compare-and-swap operation, if defined.
6413
6414@cindex @code{sync_new_add@var{mode}} instruction pattern
6415@cindex @code{sync_new_sub@var{mode}} instruction pattern
6416@cindex @code{sync_new_ior@var{mode}} instruction pattern
6417@cindex @code{sync_new_and@var{mode}} instruction pattern
6418@cindex @code{sync_new_xor@var{mode}} instruction pattern
6419@cindex @code{sync_new_nand@var{mode}} instruction pattern
6420@item @samp{sync_new_add@var{mode}}, @samp{sync_new_sub@var{mode}}
6421@itemx @samp{sync_new_ior@var{mode}}, @samp{sync_new_and@var{mode}}
6422@itemx @samp{sync_new_xor@var{mode}}, @samp{sync_new_nand@var{mode}}
6423These patterns are like their @code{sync_old_@var{op}} counterparts,
6424except that they return the value that exists in the memory location
6425after the operation, rather than before the operation.
6426
6427@cindex @code{sync_lock_test_and_set@var{mode}} instruction pattern
6428@item @samp{sync_lock_test_and_set@var{mode}}
6429This pattern takes two forms, based on the capabilities of the target.
6430In either case, operand 0 is the result of the operand, operand 1 is
6431the memory on which the atomic operation is performed, and operand 2
6432is the value to set in the lock.
6433
6434In the ideal case, this operation is an atomic exchange operation, in
6435which the previous value in memory operand is copied into the result
6436operand, and the value operand is stored in the memory operand.
6437
6438For less capable targets, any value operand that is not the constant 1
6439should be rejected with @code{FAIL}.  In this case the target may use
6440an atomic test-and-set bit operation.  The result operand should contain
64411 if the bit was previously set and 0 if the bit was previously clear.
6442The true contents of the memory operand are implementation defined.
6443
6444This pattern must issue any memory barrier instructions such that the
6445pattern as a whole acts as an acquire barrier, that is all memory
6446operations after the pattern do not occur until the lock is acquired.
6447
6448If this pattern is not defined, the operation will be constructed from
6449a compare-and-swap operation, if defined.
6450
6451@cindex @code{sync_lock_release@var{mode}} instruction pattern
6452@item @samp{sync_lock_release@var{mode}}
6453This pattern, if defined, releases a lock set by
6454@code{sync_lock_test_and_set@var{mode}}.  Operand 0 is the memory
6455that contains the lock; operand 1 is the value to store in the lock.
6456
6457If the target doesn't implement full semantics for
6458@code{sync_lock_test_and_set@var{mode}}, any value operand which is not
6459the constant 0 should be rejected with @code{FAIL}, and the true contents
6460of the memory operand are implementation defined.
6461
6462This pattern must issue any memory barrier instructions such that the
6463pattern as a whole acts as a release barrier, that is the lock is
6464released only after all previous memory operations have completed.
6465
6466If this pattern is not defined, then a @code{memory_barrier} pattern
6467will be emitted, followed by a store of the value to the memory operand.
6468
6469@cindex @code{atomic_compare_and_swap@var{mode}} instruction pattern
6470@item @samp{atomic_compare_and_swap@var{mode}} 
6471This pattern, if defined, emits code for an atomic compare-and-swap
6472operation with memory model semantics.  Operand 2 is the memory on which
6473the atomic operation is performed.  Operand 0 is an output operand which
6474is set to true or false based on whether the operation succeeded.  Operand
64751 is an output operand which is set to the contents of the memory before
6476the operation was attempted.  Operand 3 is the value that is expected to
6477be in memory.  Operand 4 is the value to put in memory if the expected
6478value is found there.  Operand 5 is set to 1 if this compare and swap is to
6479be treated as a weak operation.  Operand 6 is the memory model to be used
6480if the operation is a success.  Operand 7 is the memory model to be used
6481if the operation fails.
6482
6483If memory referred to in operand 2 contains the value in operand 3, then
6484operand 4 is stored in memory pointed to by operand 2 and fencing based on
6485the memory model in operand 6 is issued.  
6486
6487If memory referred to in operand 2 does not contain the value in operand 3,
6488then fencing based on the memory model in operand 7 is issued.
6489
6490If a target does not support weak compare-and-swap operations, or the port
6491elects not to implement weak operations, the argument in operand 5 can be
6492ignored.  Note a strong implementation must be provided.
6493
6494If this pattern is not provided, the @code{__atomic_compare_exchange}
6495built-in functions will utilize the legacy @code{sync_compare_and_swap}
6496pattern with an @code{__ATOMIC_SEQ_CST} memory model.
6497
6498@cindex @code{atomic_load@var{mode}} instruction pattern
6499@item @samp{atomic_load@var{mode}}
6500This pattern implements an atomic load operation with memory model
6501semantics.  Operand 1 is the memory address being loaded from.  Operand 0
6502is the result of the load.  Operand 2 is the memory model to be used for
6503the load operation.
6504
6505If not present, the @code{__atomic_load} built-in function will either
6506resort to a normal load with memory barriers, or a compare-and-swap
6507operation if a normal load would not be atomic.
6508
6509@cindex @code{atomic_store@var{mode}} instruction pattern
6510@item @samp{atomic_store@var{mode}}
6511This pattern implements an atomic store operation with memory model
6512semantics.  Operand 0 is the memory address being stored to.  Operand 1
6513is the value to be written.  Operand 2 is the memory model to be used for
6514the operation.
6515
6516If not present, the @code{__atomic_store} built-in function will attempt to
6517perform a normal store and surround it with any required memory fences.  If
6518the store would not be atomic, then an @code{__atomic_exchange} is
6519attempted with the result being ignored.
6520
6521@cindex @code{atomic_exchange@var{mode}} instruction pattern
6522@item @samp{atomic_exchange@var{mode}}
6523This pattern implements an atomic exchange operation with memory model
6524semantics.  Operand 1 is the memory location the operation is performed on.
6525Operand 0 is an output operand which is set to the original value contained
6526in the memory pointed to by operand 1.  Operand 2 is the value to be
6527stored.  Operand 3 is the memory model to be used.
6528
6529If this pattern is not present, the built-in function
6530@code{__atomic_exchange} will attempt to preform the operation with a
6531compare and swap loop.
6532
6533@cindex @code{atomic_add@var{mode}} instruction pattern
6534@cindex @code{atomic_sub@var{mode}} instruction pattern
6535@cindex @code{atomic_or@var{mode}} instruction pattern
6536@cindex @code{atomic_and@var{mode}} instruction pattern
6537@cindex @code{atomic_xor@var{mode}} instruction pattern
6538@cindex @code{atomic_nand@var{mode}} instruction pattern
6539@item @samp{atomic_add@var{mode}}, @samp{atomic_sub@var{mode}}
6540@itemx @samp{atomic_or@var{mode}}, @samp{atomic_and@var{mode}}
6541@itemx @samp{atomic_xor@var{mode}}, @samp{atomic_nand@var{mode}}
6542These patterns emit code for an atomic operation on memory with memory
6543model semantics. Operand 0 is the memory on which the atomic operation is
6544performed.  Operand 1 is the second operand to the binary operator.
6545Operand 2 is the memory model to be used by the operation.
6546
6547If these patterns are not defined, attempts will be made to use legacy
6548@code{sync} patterns, or equivalent patterns which return a result.  If
6549none of these are available a compare-and-swap loop will be used.
6550
6551@cindex @code{atomic_fetch_add@var{mode}} instruction pattern
6552@cindex @code{atomic_fetch_sub@var{mode}} instruction pattern
6553@cindex @code{atomic_fetch_or@var{mode}} instruction pattern
6554@cindex @code{atomic_fetch_and@var{mode}} instruction pattern
6555@cindex @code{atomic_fetch_xor@var{mode}} instruction pattern
6556@cindex @code{atomic_fetch_nand@var{mode}} instruction pattern
6557@item @samp{atomic_fetch_add@var{mode}}, @samp{atomic_fetch_sub@var{mode}}
6558@itemx @samp{atomic_fetch_or@var{mode}}, @samp{atomic_fetch_and@var{mode}}
6559@itemx @samp{atomic_fetch_xor@var{mode}}, @samp{atomic_fetch_nand@var{mode}}
6560These patterns emit code for an atomic operation on memory with memory
6561model semantics, and return the original value. Operand 0 is an output 
6562operand which contains the value of the memory location before the 
6563operation was performed.  Operand 1 is the memory on which the atomic 
6564operation is performed.  Operand 2 is the second operand to the binary
6565operator.  Operand 3 is the memory model to be used by the operation.
6566
6567If these patterns are not defined, attempts will be made to use legacy
6568@code{sync} patterns.  If none of these are available a compare-and-swap
6569loop will be used.
6570
6571@cindex @code{atomic_add_fetch@var{mode}} instruction pattern
6572@cindex @code{atomic_sub_fetch@var{mode}} instruction pattern
6573@cindex @code{atomic_or_fetch@var{mode}} instruction pattern
6574@cindex @code{atomic_and_fetch@var{mode}} instruction pattern
6575@cindex @code{atomic_xor_fetch@var{mode}} instruction pattern
6576@cindex @code{atomic_nand_fetch@var{mode}} instruction pattern
6577@item @samp{atomic_add_fetch@var{mode}}, @samp{atomic_sub_fetch@var{mode}}
6578@itemx @samp{atomic_or_fetch@var{mode}}, @samp{atomic_and_fetch@var{mode}}
6579@itemx @samp{atomic_xor_fetch@var{mode}}, @samp{atomic_nand_fetch@var{mode}}
6580These patterns emit code for an atomic operation on memory with memory
6581model semantics and return the result after the operation is performed.
6582Operand 0 is an output operand which contains the value after the
6583operation.  Operand 1 is the memory on which the atomic operation is
6584performed.  Operand 2 is the second operand to the binary operator.
6585Operand 3 is the memory model to be used by the operation.
6586
6587If these patterns are not defined, attempts will be made to use legacy
6588@code{sync} patterns, or equivalent patterns which return the result before
6589the operation followed by the arithmetic operation required to produce the
6590result.  If none of these are available a compare-and-swap loop will be
6591used.
6592
6593@cindex @code{atomic_test_and_set} instruction pattern
6594@item @samp{atomic_test_and_set}
6595This pattern emits code for @code{__builtin_atomic_test_and_set}.
6596Operand 0 is an output operand which is set to true if the previous
6597previous contents of the byte was "set", and false otherwise.  Operand 1
6598is the @code{QImode} memory to be modified.  Operand 2 is the memory
6599model to be used.
6600
6601The specific value that defines "set" is implementation defined, and
6602is normally based on what is performed by the native atomic test and set
6603instruction.
6604
6605@cindex @code{mem_thread_fence@var{mode}} instruction pattern
6606@item @samp{mem_thread_fence@var{mode}}
6607This pattern emits code required to implement a thread fence with
6608memory model semantics.  Operand 0 is the memory model to be used.
6609
6610If this pattern is not specified, all memory models except
6611@code{__ATOMIC_RELAXED} will result in issuing a @code{sync_synchronize}
6612barrier pattern.
6613
6614@cindex @code{mem_signal_fence@var{mode}} instruction pattern
6615@item @samp{mem_signal_fence@var{mode}}
6616This pattern emits code required to implement a signal fence with
6617memory model semantics.  Operand 0 is the memory model to be used.
6618
6619This pattern should impact the compiler optimizers the same way that
6620mem_signal_fence does, but it does not need to issue any barrier
6621instructions.
6622
6623If this pattern is not specified, all memory models except
6624@code{__ATOMIC_RELAXED} will result in issuing a @code{sync_synchronize}
6625barrier pattern.
6626
6627@cindex @code{get_thread_pointer@var{mode}} instruction pattern
6628@cindex @code{set_thread_pointer@var{mode}} instruction pattern
6629@item @samp{get_thread_pointer@var{mode}}
6630@itemx @samp{set_thread_pointer@var{mode}}
6631These patterns emit code that reads/sets the TLS thread pointer. Currently,
6632these are only needed if the target needs to support the
6633@code{__builtin_thread_pointer} and @code{__builtin_set_thread_pointer}
6634builtins.
6635
6636The get/set patterns have a single output/input operand respectively,
6637with @var{mode} intended to be @code{Pmode}.
6638
6639@cindex @code{stack_protect_set} instruction pattern
6640@item @samp{stack_protect_set}
6641This pattern, if defined, moves a @code{ptr_mode} value from the memory
6642in operand 1 to the memory in operand 0 without leaving the value in
6643a register afterward.  This is to avoid leaking the value some place
6644that an attacker might use to rewrite the stack guard slot after
6645having clobbered it.
6646
6647If this pattern is not defined, then a plain move pattern is generated.
6648
6649@cindex @code{stack_protect_test} instruction pattern
6650@item @samp{stack_protect_test}
6651This pattern, if defined, compares a @code{ptr_mode} value from the
6652memory in operand 1 with the memory in operand 0 without leaving the
6653value in a register afterward and branches to operand 2 if the values
6654were equal.
6655
6656If this pattern is not defined, then a plain compare pattern and
6657conditional branch pattern is used.
6658
6659@cindex @code{clear_cache} instruction pattern
6660@item @samp{clear_cache}
6661This pattern, if defined, flushes the instruction cache for a region of
6662memory.  The region is bounded to by the Pmode pointers in operand 0
6663inclusive and operand 1 exclusive.
6664
6665If this pattern is not defined, a call to the library function
6666@code{__clear_cache} is used.
6667
6668@end table
6669
6670@end ifset
6671@c Each of the following nodes are wrapped in separate
6672@c "@ifset INTERNALS" to work around memory limits for the default
6673@c configuration in older tetex distributions.  Known to not work:
6674@c tetex-1.0.7, known to work: tetex-2.0.2.
6675@ifset INTERNALS
6676@node Pattern Ordering
6677@section When the Order of Patterns Matters
6678@cindex Pattern Ordering
6679@cindex Ordering of Patterns
6680
6681Sometimes an insn can match more than one instruction pattern.  Then the
6682pattern that appears first in the machine description is the one used.
6683Therefore, more specific patterns (patterns that will match fewer things)
6684and faster instructions (those that will produce better code when they
6685do match) should usually go first in the description.
6686
6687In some cases the effect of ordering the patterns can be used to hide
6688a pattern when it is not valid.  For example, the 68000 has an
6689instruction for converting a fullword to floating point and another
6690for converting a byte to floating point.  An instruction converting
6691an integer to floating point could match either one.  We put the
6692pattern to convert the fullword first to make sure that one will
6693be used rather than the other.  (Otherwise a large integer might
6694be generated as a single-byte immediate quantity, which would not work.)
6695Instead of using this pattern ordering it would be possible to make the
6696pattern for convert-a-byte smart enough to deal properly with any
6697constant value.
6698
6699@end ifset
6700@ifset INTERNALS
6701@node Dependent Patterns
6702@section Interdependence of Patterns
6703@cindex Dependent Patterns
6704@cindex Interdependence of Patterns
6705
6706In some cases machines support instructions identical except for the
6707machine mode of one or more operands.  For example, there may be
6708``sign-extend halfword'' and ``sign-extend byte'' instructions whose
6709patterns are
6710
6711@smallexample
6712(set (match_operand:SI 0 @dots{})
6713     (extend:SI (match_operand:HI 1 @dots{})))
6714
6715(set (match_operand:SI 0 @dots{})
6716     (extend:SI (match_operand:QI 1 @dots{})))
6717@end smallexample
6718
6719@noindent
6720Constant integers do not specify a machine mode, so an instruction to
6721extend a constant value could match either pattern.  The pattern it
6722actually will match is the one that appears first in the file.  For correct
6723results, this must be the one for the widest possible mode (@code{HImode},
6724here).  If the pattern matches the @code{QImode} instruction, the results
6725will be incorrect if the constant value does not actually fit that mode.
6726
6727Such instructions to extend constants are rarely generated because they are
6728optimized away, but they do occasionally happen in nonoptimized
6729compilations.
6730
6731If a constraint in a pattern allows a constant, the reload pass may
6732replace a register with a constant permitted by the constraint in some
6733cases.  Similarly for memory references.  Because of this substitution,
6734you should not provide separate patterns for increment and decrement
6735instructions.  Instead, they should be generated from the same pattern
6736that supports register-register add insns by examining the operands and
6737generating the appropriate machine instruction.
6738
6739@end ifset
6740@ifset INTERNALS
6741@node Jump Patterns
6742@section Defining Jump Instruction Patterns
6743@cindex jump instruction patterns
6744@cindex defining jump instruction patterns
6745
6746GCC does not assume anything about how the machine realizes jumps.
6747The machine description should define a single pattern, usually
6748a @code{define_expand}, which expands to all the required insns.
6749
6750Usually, this would be a comparison insn to set the condition code
6751and a separate branch insn testing the condition code and branching
6752or not according to its value.  For many machines, however,
6753separating compares and branches is limiting, which is why the
6754more flexible approach with one @code{define_expand} is used in GCC.
6755The machine description becomes clearer for architectures that
6756have compare-and-branch instructions but no condition code.  It also
6757works better when different sets of comparison operators are supported
6758by different kinds of conditional branches (e.g. integer vs. floating-point),
6759or by conditional branches with respect to conditional stores.
6760
6761Two separate insns are always used if the machine description represents
6762a condition code register using the legacy RTL expression @code{(cc0)},
6763and on most machines that use a separate condition code register
6764(@pxref{Condition Code}).  For machines that use @code{(cc0)}, in
6765fact, the set and use of the condition code must be separate and
6766adjacent@footnote{@code{note} insns can separate them, though.}, thus
6767allowing flags in @code{cc_status} to be used (@pxref{Condition Code}) and
6768so that the comparison and branch insns could be located from each other
6769by using the functions @code{prev_cc0_setter} and @code{next_cc0_user}.
6770
6771Even in this case having a single entry point for conditional branches
6772is advantageous, because it handles equally well the case where a single
6773comparison instruction records the results of both signed and unsigned
6774comparison of the given operands (with the branch insns coming in distinct
6775signed and unsigned flavors) as in the x86 or SPARC, and the case where
6776there are distinct signed and unsigned compare instructions and only
6777one set of conditional branch instructions as in the PowerPC.
6778
6779@end ifset
6780@ifset INTERNALS
6781@node Looping Patterns
6782@section Defining Looping Instruction Patterns
6783@cindex looping instruction patterns
6784@cindex defining looping instruction patterns
6785
6786Some machines have special jump instructions that can be utilized to
6787make loops more efficient.  A common example is the 68000 @samp{dbra}
6788instruction which performs a decrement of a register and a branch if the
6789result was greater than zero.  Other machines, in particular digital
6790signal processors (DSPs), have special block repeat instructions to
6791provide low-overhead loop support.  For example, the TI TMS320C3x/C4x
6792DSPs have a block repeat instruction that loads special registers to
6793mark the top and end of a loop and to count the number of loop
6794iterations.  This avoids the need for fetching and executing a
6795@samp{dbra}-like instruction and avoids pipeline stalls associated with
6796the jump.
6797
6798GCC has three special named patterns to support low overhead looping.
6799They are @samp{decrement_and_branch_until_zero}, @samp{doloop_begin},
6800and @samp{doloop_end}.  The first pattern,
6801@samp{decrement_and_branch_until_zero}, is not emitted during RTL
6802generation but may be emitted during the instruction combination phase.
6803This requires the assistance of the loop optimizer, using information
6804collected during strength reduction, to reverse a loop to count down to
6805zero.  Some targets also require the loop optimizer to add a
6806@code{REG_NONNEG} note to indicate that the iteration count is always
6807positive.  This is needed if the target performs a signed loop
6808termination test.  For example, the 68000 uses a pattern similar to the
6809following for its @code{dbra} instruction:
6810
6811@smallexample
6812@group
6813(define_insn "decrement_and_branch_until_zero"
6814  [(set (pc)
6815        (if_then_else
6816          (ge (plus:SI (match_operand:SI 0 "general_operand" "+d*am")
6817                       (const_int -1))
6818              (const_int 0))
6819          (label_ref (match_operand 1 "" ""))
6820          (pc)))
6821   (set (match_dup 0)
6822        (plus:SI (match_dup 0)
6823                 (const_int -1)))]
6824  "find_reg_note (insn, REG_NONNEG, 0)"
6825  "@dots{}")
6826@end group
6827@end smallexample
6828
6829Note that since the insn is both a jump insn and has an output, it must
6830deal with its own reloads, hence the `m' constraints.  Also note that
6831since this insn is generated by the instruction combination phase
6832combining two sequential insns together into an implicit parallel insn,
6833the iteration counter needs to be biased by the same amount as the
6834decrement operation, in this case @minus{}1.  Note that the following similar
6835pattern will not be matched by the combiner.
6836
6837@smallexample
6838@group
6839(define_insn "decrement_and_branch_until_zero"
6840  [(set (pc)
6841        (if_then_else
6842          (ge (match_operand:SI 0 "general_operand" "+d*am")
6843              (const_int 1))
6844          (label_ref (match_operand 1 "" ""))
6845          (pc)))
6846   (set (match_dup 0)
6847        (plus:SI (match_dup 0)
6848                 (const_int -1)))]
6849  "find_reg_note (insn, REG_NONNEG, 0)"
6850  "@dots{}")
6851@end group
6852@end smallexample
6853
6854The other two special looping patterns, @samp{doloop_begin} and
6855@samp{doloop_end}, are emitted by the loop optimizer for certain
6856well-behaved loops with a finite number of loop iterations using
6857information collected during strength reduction.
6858
6859The @samp{doloop_end} pattern describes the actual looping instruction
6860(or the implicit looping operation) and the @samp{doloop_begin} pattern
6861is an optional companion pattern that can be used for initialization
6862needed for some low-overhead looping instructions.
6863
6864Note that some machines require the actual looping instruction to be
6865emitted at the top of the loop (e.g., the TMS320C3x/C4x DSPs).  Emitting
6866the true RTL for a looping instruction at the top of the loop can cause
6867problems with flow analysis.  So instead, a dummy @code{doloop} insn is
6868emitted at the end of the loop.  The machine dependent reorg pass checks
6869for the presence of this @code{doloop} insn and then searches back to
6870the top of the loop, where it inserts the true looping insn (provided
6871there are no instructions in the loop which would cause problems).  Any
6872additional labels can be emitted at this point.  In addition, if the
6873desired special iteration counter register was not allocated, this
6874machine dependent reorg pass could emit a traditional compare and jump
6875instruction pair.
6876
6877The essential difference between the
6878@samp{decrement_and_branch_until_zero} and the @samp{doloop_end}
6879patterns is that the loop optimizer allocates an additional pseudo
6880register for the latter as an iteration counter.  This pseudo register
6881cannot be used within the loop (i.e., general induction variables cannot
6882be derived from it), however, in many cases the loop induction variable
6883may become redundant and removed by the flow pass.
6884
6885
6886@end ifset
6887@ifset INTERNALS
6888@node Insn Canonicalizations
6889@section Canonicalization of Instructions
6890@cindex canonicalization of instructions
6891@cindex insn canonicalization
6892
6893There are often cases where multiple RTL expressions could represent an
6894operation performed by a single machine instruction.  This situation is
6895most commonly encountered with logical, branch, and multiply-accumulate
6896instructions.  In such cases, the compiler attempts to convert these
6897multiple RTL expressions into a single canonical form to reduce the
6898number of insn patterns required.
6899
6900In addition to algebraic simplifications, following canonicalizations
6901are performed:
6902
6903@itemize @bullet
6904@item
6905For commutative and comparison operators, a constant is always made the
6906second operand.  If a machine only supports a constant as the second
6907operand, only patterns that match a constant in the second operand need
6908be supplied.
6909
6910@item
6911For associative operators, a sequence of operators will always chain
6912to the left; for instance, only the left operand of an integer @code{plus}
6913can itself be a @code{plus}.  @code{and}, @code{ior}, @code{xor},
6914@code{plus}, @code{mult}, @code{smin}, @code{smax}, @code{umin}, and
6915@code{umax} are associative when applied to integers, and sometimes to
6916floating-point.
6917
6918@item
6919@cindex @code{neg}, canonicalization of
6920@cindex @code{not}, canonicalization of
6921@cindex @code{mult}, canonicalization of
6922@cindex @code{plus}, canonicalization of
6923@cindex @code{minus}, canonicalization of
6924For these operators, if only one operand is a @code{neg}, @code{not},
6925@code{mult}, @code{plus}, or @code{minus} expression, it will be the
6926first operand.
6927
6928@item
6929In combinations of @code{neg}, @code{mult}, @code{plus}, and
6930@code{minus}, the @code{neg} operations (if any) will be moved inside
6931the operations as far as possible.  For instance,
6932@code{(neg (mult A B))} is canonicalized as @code{(mult (neg A) B)}, but
6933@code{(plus (mult (neg B) C) A)} is canonicalized as
6934@code{(minus A (mult B C))}.
6935
6936@cindex @code{compare}, canonicalization of
6937@item
6938For the @code{compare} operator, a constant is always the second operand
6939if the first argument is a condition code register or @code{(cc0)}.
6940
6941@item
6942An operand of @code{neg}, @code{not}, @code{mult}, @code{plus}, or
6943@code{minus} is made the first operand under the same conditions as
6944above.
6945
6946@item
6947@code{(ltu (plus @var{a} @var{b}) @var{b})} is converted to
6948@code{(ltu (plus @var{a} @var{b}) @var{a})}. Likewise with @code{geu} instead
6949of @code{ltu}.
6950
6951@item
6952@code{(minus @var{x} (const_int @var{n}))} is converted to
6953@code{(plus @var{x} (const_int @var{-n}))}.
6954
6955@item
6956Within address computations (i.e., inside @code{mem}), a left shift is
6957converted into the appropriate multiplication by a power of two.
6958
6959@cindex @code{ior}, canonicalization of
6960@cindex @code{and}, canonicalization of
6961@cindex De Morgan's law
6962@item
6963De Morgan's Law is used to move bitwise negation inside a bitwise
6964logical-and or logical-or operation.  If this results in only one
6965operand being a @code{not} expression, it will be the first one.
6966
6967A machine that has an instruction that performs a bitwise logical-and of one
6968operand with the bitwise negation of the other should specify the pattern
6969for that instruction as
6970
6971@smallexample
6972(define_insn ""
6973  [(set (match_operand:@var{m} 0 @dots{})
6974        (and:@var{m} (not:@var{m} (match_operand:@var{m} 1 @dots{}))
6975                     (match_operand:@var{m} 2 @dots{})))]
6976  "@dots{}"
6977  "@dots{}")
6978@end smallexample
6979
6980@noindent
6981Similarly, a pattern for a ``NAND'' instruction should be written
6982
6983@smallexample
6984(define_insn ""
6985  [(set (match_operand:@var{m} 0 @dots{})
6986        (ior:@var{m} (not:@var{m} (match_operand:@var{m} 1 @dots{}))
6987                     (not:@var{m} (match_operand:@var{m} 2 @dots{}))))]
6988  "@dots{}"
6989  "@dots{}")
6990@end smallexample
6991
6992In both cases, it is not necessary to include patterns for the many
6993logically equivalent RTL expressions.
6994
6995@cindex @code{xor}, canonicalization of
6996@item
6997The only possible RTL expressions involving both bitwise exclusive-or
6998and bitwise negation are @code{(xor:@var{m} @var{x} @var{y})}
6999and @code{(not:@var{m} (xor:@var{m} @var{x} @var{y}))}.
7000
7001@item
7002The sum of three items, one of which is a constant, will only appear in
7003the form
7004
7005@smallexample
7006(plus:@var{m} (plus:@var{m} @var{x} @var{y}) @var{constant})
7007@end smallexample
7008
7009@cindex @code{zero_extract}, canonicalization of
7010@cindex @code{sign_extract}, canonicalization of
7011@item
7012Equality comparisons of a group of bits (usually a single bit) with zero
7013will be written using @code{zero_extract} rather than the equivalent
7014@code{and} or @code{sign_extract} operations.
7015
7016@cindex @code{mult}, canonicalization of
7017@item
7018@code{(sign_extend:@var{m1} (mult:@var{m2} (sign_extend:@var{m2} @var{x})
7019(sign_extend:@var{m2} @var{y})))} is converted to @code{(mult:@var{m1}
7020(sign_extend:@var{m1} @var{x}) (sign_extend:@var{m1} @var{y}))}, and likewise
7021for @code{zero_extend}.
7022
7023@item
7024@code{(sign_extend:@var{m1} (mult:@var{m2} (ashiftrt:@var{m2}
7025@var{x} @var{s}) (sign_extend:@var{m2} @var{y})))} is converted
7026to @code{(mult:@var{m1} (sign_extend:@var{m1} (ashiftrt:@var{m2}
7027@var{x} @var{s})) (sign_extend:@var{m1} @var{y}))}, and likewise for
7028patterns using @code{zero_extend} and @code{lshiftrt}.  If the second
7029operand of @code{mult} is also a shift, then that is extended also.
7030This transformation is only applied when it can be proven that the
7031original operation had sufficient precision to prevent overflow.
7032
7033@end itemize
7034
7035Further canonicalization rules are defined in the function
7036@code{commutative_operand_precedence} in @file{gcc/rtlanal.c}.
7037
7038@end ifset
7039@ifset INTERNALS
7040@node Expander Definitions
7041@section Defining RTL Sequences for Code Generation
7042@cindex expander definitions
7043@cindex code generation RTL sequences
7044@cindex defining RTL sequences for code generation
7045
7046On some target machines, some standard pattern names for RTL generation
7047cannot be handled with single insn, but a sequence of RTL insns can
7048represent them.  For these target machines, you can write a
7049@code{define_expand} to specify how to generate the sequence of RTL@.
7050
7051@findex define_expand
7052A @code{define_expand} is an RTL expression that looks almost like a
7053@code{define_insn}; but, unlike the latter, a @code{define_expand} is used
7054only for RTL generation and it can produce more than one RTL insn.
7055
7056A @code{define_expand} RTX has four operands:
7057
7058@itemize @bullet
7059@item
7060The name.  Each @code{define_expand} must have a name, since the only
7061use for it is to refer to it by name.
7062
7063@item
7064The RTL template.  This is a vector of RTL expressions representing
7065a sequence of separate instructions.  Unlike @code{define_insn}, there
7066is no implicit surrounding @code{PARALLEL}.
7067
7068@item
7069The condition, a string containing a C expression.  This expression is
7070used to express how the availability of this pattern depends on
7071subclasses of target machine, selected by command-line options when GCC
7072is run.  This is just like the condition of a @code{define_insn} that
7073has a standard name.  Therefore, the condition (if present) may not
7074depend on the data in the insn being matched, but only the
7075target-machine-type flags.  The compiler needs to test these conditions
7076during initialization in order to learn exactly which named instructions
7077are available in a particular run.
7078
7079@item
7080The preparation statements, a string containing zero or more C
7081statements which are to be executed before RTL code is generated from
7082the RTL template.
7083
7084Usually these statements prepare temporary registers for use as
7085internal operands in the RTL template, but they can also generate RTL
7086insns directly by calling routines such as @code{emit_insn}, etc.
7087Any such insns precede the ones that come from the RTL template.
7088
7089@item
7090Optionally, a vector containing the values of attributes. @xref{Insn
7091Attributes}.
7092@end itemize
7093
7094Every RTL insn emitted by a @code{define_expand} must match some
7095@code{define_insn} in the machine description.  Otherwise, the compiler
7096will crash when trying to generate code for the insn or trying to optimize
7097it.
7098
7099The RTL template, in addition to controlling generation of RTL insns,
7100also describes the operands that need to be specified when this pattern
7101is used.  In particular, it gives a predicate for each operand.
7102
7103A true operand, which needs to be specified in order to generate RTL from
7104the pattern, should be described with a @code{match_operand} in its first
7105occurrence in the RTL template.  This enters information on the operand's
7106predicate into the tables that record such things.  GCC uses the
7107information to preload the operand into a register if that is required for
7108valid RTL code.  If the operand is referred to more than once, subsequent
7109references should use @code{match_dup}.
7110
7111The RTL template may also refer to internal ``operands'' which are
7112temporary registers or labels used only within the sequence made by the
7113@code{define_expand}.  Internal operands are substituted into the RTL
7114template with @code{match_dup}, never with @code{match_operand}.  The
7115values of the internal operands are not passed in as arguments by the
7116compiler when it requests use of this pattern.  Instead, they are computed
7117within the pattern, in the preparation statements.  These statements
7118compute the values and store them into the appropriate elements of
7119@code{operands} so that @code{match_dup} can find them.
7120
7121There are two special macros defined for use in the preparation statements:
7122@code{DONE} and @code{FAIL}.  Use them with a following semicolon,
7123as a statement.
7124
7125@table @code
7126
7127@findex DONE
7128@item DONE
7129Use the @code{DONE} macro to end RTL generation for the pattern.  The
7130only RTL insns resulting from the pattern on this occasion will be
7131those already emitted by explicit calls to @code{emit_insn} within the
7132preparation statements; the RTL template will not be generated.
7133
7134@findex FAIL
7135@item FAIL
7136Make the pattern fail on this occasion.  When a pattern fails, it means
7137that the pattern was not truly available.  The calling routines in the
7138compiler will try other strategies for code generation using other patterns.
7139
7140Failure is currently supported only for binary (addition, multiplication,
7141shifting, etc.) and bit-field (@code{extv}, @code{extzv}, and @code{insv})
7142operations.
7143@end table
7144
7145If the preparation falls through (invokes neither @code{DONE} nor
7146@code{FAIL}), then the @code{define_expand} acts like a
7147@code{define_insn} in that the RTL template is used to generate the
7148insn.
7149
7150The RTL template is not used for matching, only for generating the
7151initial insn list.  If the preparation statement always invokes
7152@code{DONE} or @code{FAIL}, the RTL template may be reduced to a simple
7153list of operands, such as this example:
7154
7155@smallexample
7156@group
7157(define_expand "addsi3"
7158  [(match_operand:SI 0 "register_operand" "")
7159   (match_operand:SI 1 "register_operand" "")
7160   (match_operand:SI 2 "register_operand" "")]
7161@end group
7162@group
7163  ""
7164  "
7165@{
7166  handle_add (operands[0], operands[1], operands[2]);
7167  DONE;
7168@}")
7169@end group
7170@end smallexample
7171
7172Here is an example, the definition of left-shift for the SPUR chip:
7173
7174@smallexample
7175@group
7176(define_expand "ashlsi3"
7177  [(set (match_operand:SI 0 "register_operand" "")
7178        (ashift:SI
7179@end group
7180@group
7181          (match_operand:SI 1 "register_operand" "")
7182          (match_operand:SI 2 "nonmemory_operand" "")))]
7183  ""
7184  "
7185@end group
7186@end smallexample
7187
7188@smallexample
7189@group
7190@{
7191  if (GET_CODE (operands[2]) != CONST_INT
7192      || (unsigned) INTVAL (operands[2]) > 3)
7193    FAIL;
7194@}")
7195@end group
7196@end smallexample
7197
7198@noindent
7199This example uses @code{define_expand} so that it can generate an RTL insn
7200for shifting when the shift-count is in the supported range of 0 to 3 but
7201fail in other cases where machine insns aren't available.  When it fails,
7202the compiler tries another strategy using different patterns (such as, a
7203library call).
7204
7205If the compiler were able to handle nontrivial condition-strings in
7206patterns with names, then it would be possible to use a
7207@code{define_insn} in that case.  Here is another case (zero-extension
7208on the 68000) which makes more use of the power of @code{define_expand}:
7209
7210@smallexample
7211(define_expand "zero_extendhisi2"
7212  [(set (match_operand:SI 0 "general_operand" "")
7213        (const_int 0))
7214   (set (strict_low_part
7215          (subreg:HI
7216            (match_dup 0)
7217            0))
7218        (match_operand:HI 1 "general_operand" ""))]
7219  ""
7220  "operands[1] = make_safe_from (operands[1], operands[0]);")
7221@end smallexample
7222
7223@noindent
7224@findex make_safe_from
7225Here two RTL insns are generated, one to clear the entire output operand
7226and the other to copy the input operand into its low half.  This sequence
7227is incorrect if the input operand refers to [the old value of] the output
7228operand, so the preparation statement makes sure this isn't so.  The
7229function @code{make_safe_from} copies the @code{operands[1]} into a
7230temporary register if it refers to @code{operands[0]}.  It does this
7231by emitting another RTL insn.
7232
7233Finally, a third example shows the use of an internal operand.
7234Zero-extension on the SPUR chip is done by @code{and}-ing the result
7235against a halfword mask.  But this mask cannot be represented by a
7236@code{const_int} because the constant value is too large to be legitimate
7237on this machine.  So it must be copied into a register with
7238@code{force_reg} and then the register used in the @code{and}.
7239
7240@smallexample
7241(define_expand "zero_extendhisi2"
7242  [(set (match_operand:SI 0 "register_operand" "")
7243        (and:SI (subreg:SI
7244                  (match_operand:HI 1 "register_operand" "")
7245                  0)
7246                (match_dup 2)))]
7247  ""
7248  "operands[2]
7249     = force_reg (SImode, GEN_INT (65535)); ")
7250@end smallexample
7251
7252@emph{Note:} If the @code{define_expand} is used to serve a
7253standard binary or unary arithmetic operation or a bit-field operation,
7254then the last insn it generates must not be a @code{code_label},
7255@code{barrier} or @code{note}.  It must be an @code{insn},
7256@code{jump_insn} or @code{call_insn}.  If you don't need a real insn
7257at the end, emit an insn to copy the result of the operation into
7258itself.  Such an insn will generate no code, but it can avoid problems
7259in the compiler.
7260
7261@end ifset
7262@ifset INTERNALS
7263@node Insn Splitting
7264@section Defining How to Split Instructions
7265@cindex insn splitting
7266@cindex instruction splitting
7267@cindex splitting instructions
7268
7269There are two cases where you should specify how to split a pattern
7270into multiple insns.  On machines that have instructions requiring
7271delay slots (@pxref{Delay Slots}) or that have instructions whose
7272output is not available for multiple cycles (@pxref{Processor pipeline
7273description}), the compiler phases that optimize these cases need to
7274be able to move insns into one-instruction delay slots.  However, some
7275insns may generate more than one machine instruction.  These insns
7276cannot be placed into a delay slot.
7277
7278Often you can rewrite the single insn as a list of individual insns,
7279each corresponding to one machine instruction.  The disadvantage of
7280doing so is that it will cause the compilation to be slower and require
7281more space.  If the resulting insns are too complex, it may also
7282suppress some optimizations.  The compiler splits the insn if there is a
7283reason to believe that it might improve instruction or delay slot
7284scheduling.
7285
7286The insn combiner phase also splits putative insns.  If three insns are
7287merged into one insn with a complex expression that cannot be matched by
7288some @code{define_insn} pattern, the combiner phase attempts to split
7289the complex pattern into two insns that are recognized.  Usually it can
7290break the complex pattern into two patterns by splitting out some
7291subexpression.  However, in some other cases, such as performing an
7292addition of a large constant in two insns on a RISC machine, the way to
7293split the addition into two insns is machine-dependent.
7294
7295@findex define_split
7296The @code{define_split} definition tells the compiler how to split a
7297complex insn into several simpler insns.  It looks like this:
7298
7299@smallexample
7300(define_split
7301  [@var{insn-pattern}]
7302  "@var{condition}"
7303  [@var{new-insn-pattern-1}
7304   @var{new-insn-pattern-2}
7305   @dots{}]
7306  "@var{preparation-statements}")
7307@end smallexample
7308
7309@var{insn-pattern} is a pattern that needs to be split and
7310@var{condition} is the final condition to be tested, as in a
7311@code{define_insn}.  When an insn matching @var{insn-pattern} and
7312satisfying @var{condition} is found, it is replaced in the insn list
7313with the insns given by @var{new-insn-pattern-1},
7314@var{new-insn-pattern-2}, etc.
7315
7316The @var{preparation-statements} are similar to those statements that
7317are specified for @code{define_expand} (@pxref{Expander Definitions})
7318and are executed before the new RTL is generated to prepare for the
7319generated code or emit some insns whose pattern is not fixed.  Unlike
7320those in @code{define_expand}, however, these statements must not
7321generate any new pseudo-registers.  Once reload has completed, they also
7322must not allocate any space in the stack frame.
7323
7324Patterns are matched against @var{insn-pattern} in two different
7325circumstances.  If an insn needs to be split for delay slot scheduling
7326or insn scheduling, the insn is already known to be valid, which means
7327that it must have been matched by some @code{define_insn} and, if
7328@code{reload_completed} is nonzero, is known to satisfy the constraints
7329of that @code{define_insn}.  In that case, the new insn patterns must
7330also be insns that are matched by some @code{define_insn} and, if
7331@code{reload_completed} is nonzero, must also satisfy the constraints
7332of those definitions.
7333
7334As an example of this usage of @code{define_split}, consider the following
7335example from @file{a29k.md}, which splits a @code{sign_extend} from
7336@code{HImode} to @code{SImode} into a pair of shift insns:
7337
7338@smallexample
7339(define_split
7340  [(set (match_operand:SI 0 "gen_reg_operand" "")
7341        (sign_extend:SI (match_operand:HI 1 "gen_reg_operand" "")))]
7342  ""
7343  [(set (match_dup 0)
7344        (ashift:SI (match_dup 1)
7345                   (const_int 16)))
7346   (set (match_dup 0)
7347        (ashiftrt:SI (match_dup 0)
7348                     (const_int 16)))]
7349  "
7350@{ operands[1] = gen_lowpart (SImode, operands[1]); @}")
7351@end smallexample
7352
7353When the combiner phase tries to split an insn pattern, it is always the
7354case that the pattern is @emph{not} matched by any @code{define_insn}.
7355The combiner pass first tries to split a single @code{set} expression
7356and then the same @code{set} expression inside a @code{parallel}, but
7357followed by a @code{clobber} of a pseudo-reg to use as a scratch
7358register.  In these cases, the combiner expects exactly two new insn
7359patterns to be generated.  It will verify that these patterns match some
7360@code{define_insn} definitions, so you need not do this test in the
7361@code{define_split} (of course, there is no point in writing a
7362@code{define_split} that will never produce insns that match).
7363
7364Here is an example of this use of @code{define_split}, taken from
7365@file{rs6000.md}:
7366
7367@smallexample
7368(define_split
7369  [(set (match_operand:SI 0 "gen_reg_operand" "")
7370        (plus:SI (match_operand:SI 1 "gen_reg_operand" "")
7371                 (match_operand:SI 2 "non_add_cint_operand" "")))]
7372  ""
7373  [(set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))
7374   (set (match_dup 0) (plus:SI (match_dup 0) (match_dup 4)))]
7375"
7376@{
7377  int low = INTVAL (operands[2]) & 0xffff;
7378  int high = (unsigned) INTVAL (operands[2]) >> 16;
7379
7380  if (low & 0x8000)
7381    high++, low |= 0xffff0000;
7382
7383  operands[3] = GEN_INT (high << 16);
7384  operands[4] = GEN_INT (low);
7385@}")
7386@end smallexample
7387
7388Here the predicate @code{non_add_cint_operand} matches any
7389@code{const_int} that is @emph{not} a valid operand of a single add
7390insn.  The add with the smaller displacement is written so that it
7391can be substituted into the address of a subsequent operation.
7392
7393An example that uses a scratch register, from the same file, generates
7394an equality comparison of a register and a large constant:
7395
7396@smallexample
7397(define_split
7398  [(set (match_operand:CC 0 "cc_reg_operand" "")
7399        (compare:CC (match_operand:SI 1 "gen_reg_operand" "")
7400                    (match_operand:SI 2 "non_short_cint_operand" "")))
7401   (clobber (match_operand:SI 3 "gen_reg_operand" ""))]
7402  "find_single_use (operands[0], insn, 0)
7403   && (GET_CODE (*find_single_use (operands[0], insn, 0)) == EQ
7404       || GET_CODE (*find_single_use (operands[0], insn, 0)) == NE)"
7405  [(set (match_dup 3) (xor:SI (match_dup 1) (match_dup 4)))
7406   (set (match_dup 0) (compare:CC (match_dup 3) (match_dup 5)))]
7407  "
7408@{
7409  /* @r{Get the constant we are comparing against, C, and see what it
7410     looks like sign-extended to 16 bits.  Then see what constant
7411     could be XOR'ed with C to get the sign-extended value.}  */
7412
7413  int c = INTVAL (operands[2]);
7414  int sextc = (c << 16) >> 16;
7415  int xorv = c ^ sextc;
7416
7417  operands[4] = GEN_INT (xorv);
7418  operands[5] = GEN_INT (sextc);
7419@}")
7420@end smallexample
7421
7422To avoid confusion, don't write a single @code{define_split} that
7423accepts some insns that match some @code{define_insn} as well as some
7424insns that don't.  Instead, write two separate @code{define_split}
7425definitions, one for the insns that are valid and one for the insns that
7426are not valid.
7427
7428The splitter is allowed to split jump instructions into sequence of
7429jumps or create new jumps in while splitting non-jump instructions.  As
7430the central flowgraph and branch prediction information needs to be updated,
7431several restriction apply.
7432
7433Splitting of jump instruction into sequence that over by another jump
7434instruction is always valid, as compiler expect identical behavior of new
7435jump.  When new sequence contains multiple jump instructions or new labels,
7436more assistance is needed.  Splitter is required to create only unconditional
7437jumps, or simple conditional jump instructions.  Additionally it must attach a
7438@code{REG_BR_PROB} note to each conditional jump.  A global variable
7439@code{split_branch_probability} holds the probability of the original branch in case
7440it was a simple conditional jump, @minus{}1 otherwise.  To simplify
7441recomputing of edge frequencies, the new sequence is required to have only
7442forward jumps to the newly created labels.
7443
7444@findex define_insn_and_split
7445For the common case where the pattern of a define_split exactly matches the
7446pattern of a define_insn, use @code{define_insn_and_split}.  It looks like
7447this:
7448
7449@smallexample
7450(define_insn_and_split
7451  [@var{insn-pattern}]
7452  "@var{condition}"
7453  "@var{output-template}"
7454  "@var{split-condition}"
7455  [@var{new-insn-pattern-1}
7456   @var{new-insn-pattern-2}
7457   @dots{}]
7458  "@var{preparation-statements}"
7459  [@var{insn-attributes}])
7460
7461@end smallexample
7462
7463@var{insn-pattern}, @var{condition}, @var{output-template}, and
7464@var{insn-attributes} are used as in @code{define_insn}.  The
7465@var{new-insn-pattern} vector and the @var{preparation-statements} are used as
7466in a @code{define_split}.  The @var{split-condition} is also used as in
7467@code{define_split}, with the additional behavior that if the condition starts
7468with @samp{&&}, the condition used for the split will be the constructed as a
7469logical ``and'' of the split condition with the insn condition.  For example,
7470from i386.md:
7471
7472@smallexample
7473(define_insn_and_split "zero_extendhisi2_and"
7474  [(set (match_operand:SI 0 "register_operand" "=r")
7475     (zero_extend:SI (match_operand:HI 1 "register_operand" "0")))
7476   (clobber (reg:CC 17))]
7477  "TARGET_ZERO_EXTEND_WITH_AND && !optimize_size"
7478  "#"
7479  "&& reload_completed"
7480  [(parallel [(set (match_dup 0)
7481                   (and:SI (match_dup 0) (const_int 65535)))
7482              (clobber (reg:CC 17))])]
7483  ""
7484  [(set_attr "type" "alu1")])
7485
7486@end smallexample
7487
7488In this case, the actual split condition will be
7489@samp{TARGET_ZERO_EXTEND_WITH_AND && !optimize_size && reload_completed}.
7490
7491The @code{define_insn_and_split} construction provides exactly the same
7492functionality as two separate @code{define_insn} and @code{define_split}
7493patterns.  It exists for compactness, and as a maintenance tool to prevent
7494having to ensure the two patterns' templates match.
7495
7496@end ifset
7497@ifset INTERNALS
7498@node Including Patterns
7499@section Including Patterns in Machine Descriptions.
7500@cindex insn includes
7501
7502@findex include
7503The @code{include} pattern tells the compiler tools where to
7504look for patterns that are in files other than in the file
7505@file{.md}.  This is used only at build time and there is no preprocessing allowed.
7506
7507It looks like:
7508
7509@smallexample
7510
7511(include
7512  @var{pathname})
7513@end smallexample
7514
7515For example:
7516
7517@smallexample
7518
7519(include "filestuff")
7520
7521@end smallexample
7522
7523Where @var{pathname} is a string that specifies the location of the file,
7524specifies the include file to be in @file{gcc/config/target/filestuff}.  The
7525directory @file{gcc/config/target} is regarded as the default directory.
7526
7527
7528Machine descriptions may be split up into smaller more manageable subsections
7529and placed into subdirectories.
7530
7531By specifying:
7532
7533@smallexample
7534
7535(include "BOGUS/filestuff")
7536
7537@end smallexample
7538
7539the include file is specified to be in @file{gcc/config/@var{target}/BOGUS/filestuff}.
7540
7541Specifying an absolute path for the include file such as;
7542@smallexample
7543
7544(include "/u2/BOGUS/filestuff")
7545
7546@end smallexample
7547is permitted but is not encouraged.
7548
7549@subsection RTL Generation Tool Options for Directory Search
7550@cindex directory options .md
7551@cindex options, directory search
7552@cindex search options
7553
7554The @option{-I@var{dir}} option specifies directories to search for machine descriptions.
7555For example:
7556
7557@smallexample
7558
7559genrecog -I/p1/abc/proc1 -I/p2/abcd/pro2 target.md
7560
7561@end smallexample
7562
7563
7564Add the directory @var{dir} to the head of the list of directories to be
7565searched for header files.  This can be used to override a system machine definition
7566file, substituting your own version, since these directories are
7567searched before the default machine description file directories.  If you use more than
7568one @option{-I} option, the directories are scanned in left-to-right
7569order; the standard default directory come after.
7570
7571
7572@end ifset
7573@ifset INTERNALS
7574@node Peephole Definitions
7575@section Machine-Specific Peephole Optimizers
7576@cindex peephole optimizer definitions
7577@cindex defining peephole optimizers
7578
7579In addition to instruction patterns the @file{md} file may contain
7580definitions of machine-specific peephole optimizations.
7581
7582The combiner does not notice certain peephole optimizations when the data
7583flow in the program does not suggest that it should try them.  For example,
7584sometimes two consecutive insns related in purpose can be combined even
7585though the second one does not appear to use a register computed in the
7586first one.  A machine-specific peephole optimizer can detect such
7587opportunities.
7588
7589There are two forms of peephole definitions that may be used.  The
7590original @code{define_peephole} is run at assembly output time to
7591match insns and substitute assembly text.  Use of @code{define_peephole}
7592is deprecated.
7593
7594A newer @code{define_peephole2} matches insns and substitutes new
7595insns.  The @code{peephole2} pass is run after register allocation
7596but before scheduling, which may result in much better code for
7597targets that do scheduling.
7598
7599@menu
7600* define_peephole::     RTL to Text Peephole Optimizers
7601* define_peephole2::    RTL to RTL Peephole Optimizers
7602@end menu
7603
7604@end ifset
7605@ifset INTERNALS
7606@node define_peephole
7607@subsection RTL to Text Peephole Optimizers
7608@findex define_peephole
7609
7610@need 1000
7611A definition looks like this:
7612
7613@smallexample
7614(define_peephole
7615  [@var{insn-pattern-1}
7616   @var{insn-pattern-2}
7617   @dots{}]
7618  "@var{condition}"
7619  "@var{template}"
7620  "@var{optional-insn-attributes}")
7621@end smallexample
7622
7623@noindent
7624The last string operand may be omitted if you are not using any
7625machine-specific information in this machine description.  If present,
7626it must obey the same rules as in a @code{define_insn}.
7627
7628In this skeleton, @var{insn-pattern-1} and so on are patterns to match
7629consecutive insns.  The optimization applies to a sequence of insns when
7630@var{insn-pattern-1} matches the first one, @var{insn-pattern-2} matches
7631the next, and so on.
7632
7633Each of the insns matched by a peephole must also match a
7634@code{define_insn}.  Peepholes are checked only at the last stage just
7635before code generation, and only optionally.  Therefore, any insn which
7636would match a peephole but no @code{define_insn} will cause a crash in code
7637generation in an unoptimized compilation, or at various optimization
7638stages.
7639
7640The operands of the insns are matched with @code{match_operands},
7641@code{match_operator}, and @code{match_dup}, as usual.  What is not
7642usual is that the operand numbers apply to all the insn patterns in the
7643definition.  So, you can check for identical operands in two insns by
7644using @code{match_operand} in one insn and @code{match_dup} in the
7645other.
7646
7647The operand constraints used in @code{match_operand} patterns do not have
7648any direct effect on the applicability of the peephole, but they will
7649be validated afterward, so make sure your constraints are general enough
7650to apply whenever the peephole matches.  If the peephole matches
7651but the constraints are not satisfied, the compiler will crash.
7652
7653It is safe to omit constraints in all the operands of the peephole; or
7654you can write constraints which serve as a double-check on the criteria
7655previously tested.
7656
7657Once a sequence of insns matches the patterns, the @var{condition} is
7658checked.  This is a C expression which makes the final decision whether to
7659perform the optimization (we do so if the expression is nonzero).  If
7660@var{condition} is omitted (in other words, the string is empty) then the
7661optimization is applied to every sequence of insns that matches the
7662patterns.
7663
7664The defined peephole optimizations are applied after register allocation
7665is complete.  Therefore, the peephole definition can check which
7666operands have ended up in which kinds of registers, just by looking at
7667the operands.
7668
7669@findex prev_active_insn
7670The way to refer to the operands in @var{condition} is to write
7671@code{operands[@var{i}]} for operand number @var{i} (as matched by
7672@code{(match_operand @var{i} @dots{})}).  Use the variable @code{insn}
7673to refer to the last of the insns being matched; use
7674@code{prev_active_insn} to find the preceding insns.
7675
7676@findex dead_or_set_p
7677When optimizing computations with intermediate results, you can use
7678@var{condition} to match only when the intermediate results are not used
7679elsewhere.  Use the C expression @code{dead_or_set_p (@var{insn},
7680@var{op})}, where @var{insn} is the insn in which you expect the value
7681to be used for the last time (from the value of @code{insn}, together
7682with use of @code{prev_nonnote_insn}), and @var{op} is the intermediate
7683value (from @code{operands[@var{i}]}).
7684
7685Applying the optimization means replacing the sequence of insns with one
7686new insn.  The @var{template} controls ultimate output of assembler code
7687for this combined insn.  It works exactly like the template of a
7688@code{define_insn}.  Operand numbers in this template are the same ones
7689used in matching the original sequence of insns.
7690
7691The result of a defined peephole optimizer does not need to match any of
7692the insn patterns in the machine description; it does not even have an
7693opportunity to match them.  The peephole optimizer definition itself serves
7694as the insn pattern to control how the insn is output.
7695
7696Defined peephole optimizers are run as assembler code is being output,
7697so the insns they produce are never combined or rearranged in any way.
7698
7699Here is an example, taken from the 68000 machine description:
7700
7701@smallexample
7702(define_peephole
7703  [(set (reg:SI 15) (plus:SI (reg:SI 15) (const_int 4)))
7704   (set (match_operand:DF 0 "register_operand" "=f")
7705        (match_operand:DF 1 "register_operand" "ad"))]
7706  "FP_REG_P (operands[0]) && ! FP_REG_P (operands[1])"
7707@{
7708  rtx xoperands[2];
7709  xoperands[1] = gen_rtx_REG (SImode, REGNO (operands[1]) + 1);
7710#ifdef MOTOROLA
7711  output_asm_insn ("move.l %1,(sp)", xoperands);
7712  output_asm_insn ("move.l %1,-(sp)", operands);
7713  return "fmove.d (sp)+,%0";
7714#else
7715  output_asm_insn ("movel %1,sp@@", xoperands);
7716  output_asm_insn ("movel %1,sp@@-", operands);
7717  return "fmoved sp@@+,%0";
7718#endif
7719@})
7720@end smallexample
7721
7722@need 1000
7723The effect of this optimization is to change
7724
7725@smallexample
7726@group
7727jbsr _foobar
7728addql #4,sp
7729movel d1,sp@@-
7730movel d0,sp@@-
7731fmoved sp@@+,fp0
7732@end group
7733@end smallexample
7734
7735@noindent
7736into
7737
7738@smallexample
7739@group
7740jbsr _foobar
7741movel d1,sp@@
7742movel d0,sp@@-
7743fmoved sp@@+,fp0
7744@end group
7745@end smallexample
7746
7747@ignore
7748@findex CC_REVERSED
7749If a peephole matches a sequence including one or more jump insns, you must
7750take account of the flags such as @code{CC_REVERSED} which specify that the
7751condition codes are represented in an unusual manner.  The compiler
7752automatically alters any ordinary conditional jumps which occur in such
7753situations, but the compiler cannot alter jumps which have been replaced by
7754peephole optimizations.  So it is up to you to alter the assembler code
7755that the peephole produces.  Supply C code to write the assembler output,
7756and in this C code check the condition code status flags and change the
7757assembler code as appropriate.
7758@end ignore
7759
7760@var{insn-pattern-1} and so on look @emph{almost} like the second
7761operand of @code{define_insn}.  There is one important difference: the
7762second operand of @code{define_insn} consists of one or more RTX's
7763enclosed in square brackets.  Usually, there is only one: then the same
7764action can be written as an element of a @code{define_peephole}.  But
7765when there are multiple actions in a @code{define_insn}, they are
7766implicitly enclosed in a @code{parallel}.  Then you must explicitly
7767write the @code{parallel}, and the square brackets within it, in the
7768@code{define_peephole}.  Thus, if an insn pattern looks like this,
7769
7770@smallexample
7771(define_insn "divmodsi4"
7772  [(set (match_operand:SI 0 "general_operand" "=d")
7773        (div:SI (match_operand:SI 1 "general_operand" "0")
7774                (match_operand:SI 2 "general_operand" "dmsK")))
7775   (set (match_operand:SI 3 "general_operand" "=d")
7776        (mod:SI (match_dup 1) (match_dup 2)))]
7777  "TARGET_68020"
7778  "divsl%.l %2,%3:%0")
7779@end smallexample
7780
7781@noindent
7782then the way to mention this insn in a peephole is as follows:
7783
7784@smallexample
7785(define_peephole
7786  [@dots{}
7787   (parallel
7788    [(set (match_operand:SI 0 "general_operand" "=d")
7789          (div:SI (match_operand:SI 1 "general_operand" "0")
7790                  (match_operand:SI 2 "general_operand" "dmsK")))
7791     (set (match_operand:SI 3 "general_operand" "=d")
7792          (mod:SI (match_dup 1) (match_dup 2)))])
7793   @dots{}]
7794  @dots{})
7795@end smallexample
7796
7797@end ifset
7798@ifset INTERNALS
7799@node define_peephole2
7800@subsection RTL to RTL Peephole Optimizers
7801@findex define_peephole2
7802
7803The @code{define_peephole2} definition tells the compiler how to
7804substitute one sequence of instructions for another sequence,
7805what additional scratch registers may be needed and what their
7806lifetimes must be.
7807
7808@smallexample
7809(define_peephole2
7810  [@var{insn-pattern-1}
7811   @var{insn-pattern-2}
7812   @dots{}]
7813  "@var{condition}"
7814  [@var{new-insn-pattern-1}
7815   @var{new-insn-pattern-2}
7816   @dots{}]
7817  "@var{preparation-statements}")
7818@end smallexample
7819
7820The definition is almost identical to @code{define_split}
7821(@pxref{Insn Splitting}) except that the pattern to match is not a
7822single instruction, but a sequence of instructions.
7823
7824It is possible to request additional scratch registers for use in the
7825output template.  If appropriate registers are not free, the pattern
7826will simply not match.
7827
7828@findex match_scratch
7829@findex match_dup
7830Scratch registers are requested with a @code{match_scratch} pattern at
7831the top level of the input pattern.  The allocated register (initially) will
7832be dead at the point requested within the original sequence.  If the scratch
7833is used at more than a single point, a @code{match_dup} pattern at the
7834top level of the input pattern marks the last position in the input sequence
7835at which the register must be available.
7836
7837Here is an example from the IA-32 machine description:
7838
7839@smallexample
7840(define_peephole2
7841  [(match_scratch:SI 2 "r")
7842   (parallel [(set (match_operand:SI 0 "register_operand" "")
7843                   (match_operator:SI 3 "arith_or_logical_operator"
7844                     [(match_dup 0)
7845                      (match_operand:SI 1 "memory_operand" "")]))
7846              (clobber (reg:CC 17))])]
7847  "! optimize_size && ! TARGET_READ_MODIFY"
7848  [(set (match_dup 2) (match_dup 1))
7849   (parallel [(set (match_dup 0)
7850                   (match_op_dup 3 [(match_dup 0) (match_dup 2)]))
7851              (clobber (reg:CC 17))])]
7852  "")
7853@end smallexample
7854
7855@noindent
7856This pattern tries to split a load from its use in the hopes that we'll be
7857able to schedule around the memory load latency.  It allocates a single
7858@code{SImode} register of class @code{GENERAL_REGS} (@code{"r"}) that needs
7859to be live only at the point just before the arithmetic.
7860
7861A real example requiring extended scratch lifetimes is harder to come by,
7862so here's a silly made-up example:
7863
7864@smallexample
7865(define_peephole2
7866  [(match_scratch:SI 4 "r")
7867   (set (match_operand:SI 0 "" "") (match_operand:SI 1 "" ""))
7868   (set (match_operand:SI 2 "" "") (match_dup 1))
7869   (match_dup 4)
7870   (set (match_operand:SI 3 "" "") (match_dup 1))]
7871  "/* @r{determine 1 does not overlap 0 and 2} */"
7872  [(set (match_dup 4) (match_dup 1))
7873   (set (match_dup 0) (match_dup 4))
7874   (set (match_dup 2) (match_dup 4))
7875   (set (match_dup 3) (match_dup 4))]
7876  "")
7877@end smallexample
7878
7879@noindent
7880If we had not added the @code{(match_dup 4)} in the middle of the input
7881sequence, it might have been the case that the register we chose at the
7882beginning of the sequence is killed by the first or second @code{set}.
7883
7884@end ifset
7885@ifset INTERNALS
7886@node Insn Attributes
7887@section Instruction Attributes
7888@cindex insn attributes
7889@cindex instruction attributes
7890
7891In addition to describing the instruction supported by the target machine,
7892the @file{md} file also defines a group of @dfn{attributes} and a set of
7893values for each.  Every generated insn is assigned a value for each attribute.
7894One possible attribute would be the effect that the insn has on the machine's
7895condition code.  This attribute can then be used by @code{NOTICE_UPDATE_CC}
7896to track the condition codes.
7897
7898@menu
7899* Defining Attributes:: Specifying attributes and their values.
7900* Expressions::         Valid expressions for attribute values.
7901* Tagging Insns::       Assigning attribute values to insns.
7902* Attr Example::        An example of assigning attributes.
7903* Insn Lengths::        Computing the length of insns.
7904* Constant Attributes:: Defining attributes that are constant.
7905* Mnemonic Attribute::  Obtain the instruction mnemonic as attribute value.
7906* Delay Slots::         Defining delay slots required for a machine.
7907* Processor pipeline description:: Specifying information for insn scheduling.
7908@end menu
7909
7910@end ifset
7911@ifset INTERNALS
7912@node Defining Attributes
7913@subsection Defining Attributes and their Values
7914@cindex defining attributes and their values
7915@cindex attributes, defining
7916
7917@findex define_attr
7918The @code{define_attr} expression is used to define each attribute required
7919by the target machine.  It looks like:
7920
7921@smallexample
7922(define_attr @var{name} @var{list-of-values} @var{default})
7923@end smallexample
7924
7925@var{name} is a string specifying the name of the attribute being
7926defined.  Some attributes are used in a special way by the rest of the
7927compiler. The @code{enabled} attribute can be used to conditionally
7928enable or disable insn alternatives (@pxref{Disable Insn
7929Alternatives}). The @code{predicable} attribute, together with a
7930suitable @code{define_cond_exec} (@pxref{Conditional Execution}), can
7931be used to automatically generate conditional variants of instruction
7932patterns. The @code{mnemonic} attribute can be used to check for the
7933instruction mnemonic (@pxref{Mnemonic Attribute}).  The compiler
7934internally uses the names @code{ce_enabled} and @code{nonce_enabled},
7935so they should not be used elsewhere as alternative names.
7936
7937@var{list-of-values} is either a string that specifies a comma-separated
7938list of values that can be assigned to the attribute, or a null string to
7939indicate that the attribute takes numeric values.
7940
7941@var{default} is an attribute expression that gives the value of this
7942attribute for insns that match patterns whose definition does not include
7943an explicit value for this attribute.  @xref{Attr Example}, for more
7944information on the handling of defaults.  @xref{Constant Attributes},
7945for information on attributes that do not depend on any particular insn.
7946
7947@findex insn-attr.h
7948For each defined attribute, a number of definitions are written to the
7949@file{insn-attr.h} file.  For cases where an explicit set of values is
7950specified for an attribute, the following are defined:
7951
7952@itemize @bullet
7953@item
7954A @samp{#define} is written for the symbol @samp{HAVE_ATTR_@var{name}}.
7955
7956@item
7957An enumerated class is defined for @samp{attr_@var{name}} with
7958elements of the form @samp{@var{upper-name}_@var{upper-value}} where
7959the attribute name and value are first converted to uppercase.
7960
7961@item
7962A function @samp{get_attr_@var{name}} is defined that is passed an insn and
7963returns the attribute value for that insn.
7964@end itemize
7965
7966For example, if the following is present in the @file{md} file:
7967
7968@smallexample
7969(define_attr "type" "branch,fp,load,store,arith" @dots{})
7970@end smallexample
7971
7972@noindent
7973the following lines will be written to the file @file{insn-attr.h}.
7974
7975@smallexample
7976#define HAVE_ATTR_type 1
7977enum attr_type @{TYPE_BRANCH, TYPE_FP, TYPE_LOAD,
7978                 TYPE_STORE, TYPE_ARITH@};
7979extern enum attr_type get_attr_type ();
7980@end smallexample
7981
7982If the attribute takes numeric values, no @code{enum} type will be
7983defined and the function to obtain the attribute's value will return
7984@code{int}.
7985
7986There are attributes which are tied to a specific meaning.  These
7987attributes are not free to use for other purposes:
7988
7989@table @code
7990@item length
7991The @code{length} attribute is used to calculate the length of emitted
7992code chunks.  This is especially important when verifying branch
7993distances. @xref{Insn Lengths}.
7994
7995@item enabled
7996The @code{enabled} attribute can be defined to prevent certain
7997alternatives of an insn definition from being used during code
7998generation. @xref{Disable Insn Alternatives}.
7999
8000@item mnemonic
8001The @code{mnemonic} attribute can be defined to implement instruction
8002specific checks in e.g. the pipeline description.
8003@xref{Mnemonic Attribute}.
8004@end table
8005
8006For each of these special attributes, the corresponding
8007@samp{HAVE_ATTR_@var{name}} @samp{#define} is also written when the
8008attribute is not defined; in that case, it is defined as @samp{0}.
8009
8010@findex define_enum_attr
8011@anchor{define_enum_attr}
8012Another way of defining an attribute is to use:
8013
8014@smallexample
8015(define_enum_attr "@var{attr}" "@var{enum}" @var{default})
8016@end smallexample
8017
8018This works in just the same way as @code{define_attr}, except that
8019the list of values is taken from a separate enumeration called
8020@var{enum} (@pxref{define_enum}).  This form allows you to use
8021the same list of values for several attributes without having to
8022repeat the list each time.  For example:
8023
8024@smallexample
8025(define_enum "processor" [
8026  model_a
8027  model_b
8028  @dots{}
8029])
8030(define_enum_attr "arch" "processor"
8031  (const (symbol_ref "target_arch")))
8032(define_enum_attr "tune" "processor"
8033  (const (symbol_ref "target_tune")))
8034@end smallexample
8035
8036defines the same attributes as:
8037
8038@smallexample
8039(define_attr "arch" "model_a,model_b,@dots{}"
8040  (const (symbol_ref "target_arch")))
8041(define_attr "tune" "model_a,model_b,@dots{}"
8042  (const (symbol_ref "target_tune")))
8043@end smallexample
8044
8045but without duplicating the processor list.  The second example defines two
8046separate C enums (@code{attr_arch} and @code{attr_tune}) whereas the first
8047defines a single C enum (@code{processor}).
8048@end ifset
8049@ifset INTERNALS
8050@node Expressions
8051@subsection Attribute Expressions
8052@cindex attribute expressions
8053
8054RTL expressions used to define attributes use the codes described above
8055plus a few specific to attribute definitions, to be discussed below.
8056Attribute value expressions must have one of the following forms:
8057
8058@table @code
8059@cindex @code{const_int} and attributes
8060@item (const_int @var{i})
8061The integer @var{i} specifies the value of a numeric attribute.  @var{i}
8062must be non-negative.
8063
8064The value of a numeric attribute can be specified either with a
8065@code{const_int}, or as an integer represented as a string in
8066@code{const_string}, @code{eq_attr} (see below), @code{attr},
8067@code{symbol_ref}, simple arithmetic expressions, and @code{set_attr}
8068overrides on specific instructions (@pxref{Tagging Insns}).
8069
8070@cindex @code{const_string} and attributes
8071@item (const_string @var{value})
8072The string @var{value} specifies a constant attribute value.
8073If @var{value} is specified as @samp{"*"}, it means that the default value of
8074the attribute is to be used for the insn containing this expression.
8075@samp{"*"} obviously cannot be used in the @var{default} expression
8076of a @code{define_attr}.
8077
8078If the attribute whose value is being specified is numeric, @var{value}
8079must be a string containing a non-negative integer (normally
8080@code{const_int} would be used in this case).  Otherwise, it must
8081contain one of the valid values for the attribute.
8082
8083@cindex @code{if_then_else} and attributes
8084@item (if_then_else @var{test} @var{true-value} @var{false-value})
8085@var{test} specifies an attribute test, whose format is defined below.
8086The value of this expression is @var{true-value} if @var{test} is true,
8087otherwise it is @var{false-value}.
8088
8089@cindex @code{cond} and attributes
8090@item (cond [@var{test1} @var{value1} @dots{}] @var{default})
8091The first operand of this expression is a vector containing an even
8092number of expressions and consisting of pairs of @var{test} and @var{value}
8093expressions.  The value of the @code{cond} expression is that of the
8094@var{value} corresponding to the first true @var{test} expression.  If
8095none of the @var{test} expressions are true, the value of the @code{cond}
8096expression is that of the @var{default} expression.
8097@end table
8098
8099@var{test} expressions can have one of the following forms:
8100
8101@table @code
8102@cindex @code{const_int} and attribute tests
8103@item (const_int @var{i})
8104This test is true if @var{i} is nonzero and false otherwise.
8105
8106@cindex @code{not} and attributes
8107@cindex @code{ior} and attributes
8108@cindex @code{and} and attributes
8109@item (not @var{test})
8110@itemx (ior @var{test1} @var{test2})
8111@itemx (and @var{test1} @var{test2})
8112These tests are true if the indicated logical function is true.
8113
8114@cindex @code{match_operand} and attributes
8115@item (match_operand:@var{m} @var{n} @var{pred} @var{constraints})
8116This test is true if operand @var{n} of the insn whose attribute value
8117is being determined has mode @var{m} (this part of the test is ignored
8118if @var{m} is @code{VOIDmode}) and the function specified by the string
8119@var{pred} returns a nonzero value when passed operand @var{n} and mode
8120@var{m} (this part of the test is ignored if @var{pred} is the null
8121string).
8122
8123The @var{constraints} operand is ignored and should be the null string.
8124
8125@cindex @code{match_test} and attributes
8126@item (match_test @var{c-expr})
8127The test is true if C expression @var{c-expr} is true.  In non-constant
8128attributes, @var{c-expr} has access to the following variables:
8129
8130@table @var
8131@item insn
8132The rtl instruction under test.
8133@item which_alternative
8134The @code{define_insn} alternative that @var{insn} matches.
8135@xref{Output Statement}.
8136@item operands
8137An array of @var{insn}'s rtl operands.
8138@end table
8139
8140@var{c-expr} behaves like the condition in a C @code{if} statement,
8141so there is no need to explicitly convert the expression into a boolean
81420 or 1 value.  For example, the following two tests are equivalent:
8143
8144@smallexample
8145(match_test "x & 2")
8146(match_test "(x & 2) != 0")
8147@end smallexample
8148
8149@cindex @code{le} and attributes
8150@cindex @code{leu} and attributes
8151@cindex @code{lt} and attributes
8152@cindex @code{gt} and attributes
8153@cindex @code{gtu} and attributes
8154@cindex @code{ge} and attributes
8155@cindex @code{geu} and attributes
8156@cindex @code{ne} and attributes
8157@cindex @code{eq} and attributes
8158@cindex @code{plus} and attributes
8159@cindex @code{minus} and attributes
8160@cindex @code{mult} and attributes
8161@cindex @code{div} and attributes
8162@cindex @code{mod} and attributes
8163@cindex @code{abs} and attributes
8164@cindex @code{neg} and attributes
8165@cindex @code{ashift} and attributes
8166@cindex @code{lshiftrt} and attributes
8167@cindex @code{ashiftrt} and attributes
8168@item (le @var{arith1} @var{arith2})
8169@itemx (leu @var{arith1} @var{arith2})
8170@itemx (lt @var{arith1} @var{arith2})
8171@itemx (ltu @var{arith1} @var{arith2})
8172@itemx (gt @var{arith1} @var{arith2})
8173@itemx (gtu @var{arith1} @var{arith2})
8174@itemx (ge @var{arith1} @var{arith2})
8175@itemx (geu @var{arith1} @var{arith2})
8176@itemx (ne @var{arith1} @var{arith2})
8177@itemx (eq @var{arith1} @var{arith2})
8178These tests are true if the indicated comparison of the two arithmetic
8179expressions is true.  Arithmetic expressions are formed with
8180@code{plus}, @code{minus}, @code{mult}, @code{div}, @code{mod},
8181@code{abs}, @code{neg}, @code{and}, @code{ior}, @code{xor}, @code{not},
8182@code{ashift}, @code{lshiftrt}, and @code{ashiftrt} expressions.
8183
8184@findex get_attr
8185@code{const_int} and @code{symbol_ref} are always valid terms (@pxref{Insn
8186Lengths},for additional forms).  @code{symbol_ref} is a string
8187denoting a C expression that yields an @code{int} when evaluated by the
8188@samp{get_attr_@dots{}} routine.  It should normally be a global
8189variable.
8190
8191@findex eq_attr
8192@item (eq_attr @var{name} @var{value})
8193@var{name} is a string specifying the name of an attribute.
8194
8195@var{value} is a string that is either a valid value for attribute
8196@var{name}, a comma-separated list of values, or @samp{!} followed by a
8197value or list.  If @var{value} does not begin with a @samp{!}, this
8198test is true if the value of the @var{name} attribute of the current
8199insn is in the list specified by @var{value}.  If @var{value} begins
8200with a @samp{!}, this test is true if the attribute's value is
8201@emph{not} in the specified list.
8202
8203For example,
8204
8205@smallexample
8206(eq_attr "type" "load,store")
8207@end smallexample
8208
8209@noindent
8210is equivalent to
8211
8212@smallexample
8213(ior (eq_attr "type" "load") (eq_attr "type" "store"))
8214@end smallexample
8215
8216If @var{name} specifies an attribute of @samp{alternative}, it refers to the
8217value of the compiler variable @code{which_alternative}
8218(@pxref{Output Statement}) and the values must be small integers.  For
8219example,
8220
8221@smallexample
8222(eq_attr "alternative" "2,3")
8223@end smallexample
8224
8225@noindent
8226is equivalent to
8227
8228@smallexample
8229(ior (eq (symbol_ref "which_alternative") (const_int 2))
8230     (eq (symbol_ref "which_alternative") (const_int 3)))
8231@end smallexample
8232
8233Note that, for most attributes, an @code{eq_attr} test is simplified in cases
8234where the value of the attribute being tested is known for all insns matching
8235a particular pattern.  This is by far the most common case.
8236
8237@findex attr_flag
8238@item (attr_flag @var{name})
8239The value of an @code{attr_flag} expression is true if the flag
8240specified by @var{name} is true for the @code{insn} currently being
8241scheduled.
8242
8243@var{name} is a string specifying one of a fixed set of flags to test.
8244Test the flags @code{forward} and @code{backward} to determine the
8245direction of a conditional branch.
8246
8247This example describes a conditional branch delay slot which
8248can be nullified for forward branches that are taken (annul-true) or
8249for backward branches which are not taken (annul-false).
8250
8251@smallexample
8252(define_delay (eq_attr "type" "cbranch")
8253  [(eq_attr "in_branch_delay" "true")
8254   (and (eq_attr "in_branch_delay" "true")
8255        (attr_flag "forward"))
8256   (and (eq_attr "in_branch_delay" "true")
8257        (attr_flag "backward"))])
8258@end smallexample
8259
8260The @code{forward} and @code{backward} flags are false if the current
8261@code{insn} being scheduled is not a conditional branch.
8262
8263@code{attr_flag} is only used during delay slot scheduling and has no
8264meaning to other passes of the compiler.
8265
8266@findex attr
8267@item (attr @var{name})
8268The value of another attribute is returned.  This is most useful
8269for numeric attributes, as @code{eq_attr} and @code{attr_flag}
8270produce more efficient code for non-numeric attributes.
8271@end table
8272
8273@end ifset
8274@ifset INTERNALS
8275@node Tagging Insns
8276@subsection Assigning Attribute Values to Insns
8277@cindex tagging insns
8278@cindex assigning attribute values to insns
8279
8280The value assigned to an attribute of an insn is primarily determined by
8281which pattern is matched by that insn (or which @code{define_peephole}
8282generated it).  Every @code{define_insn} and @code{define_peephole} can
8283have an optional last argument to specify the values of attributes for
8284matching insns.  The value of any attribute not specified in a particular
8285insn is set to the default value for that attribute, as specified in its
8286@code{define_attr}.  Extensive use of default values for attributes
8287permits the specification of the values for only one or two attributes
8288in the definition of most insn patterns, as seen in the example in the
8289next section.
8290
8291The optional last argument of @code{define_insn} and
8292@code{define_peephole} is a vector of expressions, each of which defines
8293the value for a single attribute.  The most general way of assigning an
8294attribute's value is to use a @code{set} expression whose first operand is an
8295@code{attr} expression giving the name of the attribute being set.  The
8296second operand of the @code{set} is an attribute expression
8297(@pxref{Expressions}) giving the value of the attribute.
8298
8299When the attribute value depends on the @samp{alternative} attribute
8300(i.e., which is the applicable alternative in the constraint of the
8301insn), the @code{set_attr_alternative} expression can be used.  It
8302allows the specification of a vector of attribute expressions, one for
8303each alternative.
8304
8305@findex set_attr
8306When the generality of arbitrary attribute expressions is not required,
8307the simpler @code{set_attr} expression can be used, which allows
8308specifying a string giving either a single attribute value or a list
8309of attribute values, one for each alternative.
8310
8311The form of each of the above specifications is shown below.  In each case,
8312@var{name} is a string specifying the attribute to be set.
8313
8314@table @code
8315@item (set_attr @var{name} @var{value-string})
8316@var{value-string} is either a string giving the desired attribute value,
8317or a string containing a comma-separated list giving the values for
8318succeeding alternatives.  The number of elements must match the number
8319of alternatives in the constraint of the insn pattern.
8320
8321Note that it may be useful to specify @samp{*} for some alternative, in
8322which case the attribute will assume its default value for insns matching
8323that alternative.
8324
8325@findex set_attr_alternative
8326@item (set_attr_alternative @var{name} [@var{value1} @var{value2} @dots{}])
8327Depending on the alternative of the insn, the value will be one of the
8328specified values.  This is a shorthand for using a @code{cond} with
8329tests on the @samp{alternative} attribute.
8330
8331@findex attr
8332@item (set (attr @var{name}) @var{value})
8333The first operand of this @code{set} must be the special RTL expression
8334@code{attr}, whose sole operand is a string giving the name of the
8335attribute being set.  @var{value} is the value of the attribute.
8336@end table
8337
8338The following shows three different ways of representing the same
8339attribute value specification:
8340
8341@smallexample
8342(set_attr "type" "load,store,arith")
8343
8344(set_attr_alternative "type"
8345                      [(const_string "load") (const_string "store")
8346                       (const_string "arith")])
8347
8348(set (attr "type")
8349     (cond [(eq_attr "alternative" "1") (const_string "load")
8350            (eq_attr "alternative" "2") (const_string "store")]
8351           (const_string "arith")))
8352@end smallexample
8353
8354@need 1000
8355@findex define_asm_attributes
8356The @code{define_asm_attributes} expression provides a mechanism to
8357specify the attributes assigned to insns produced from an @code{asm}
8358statement.  It has the form:
8359
8360@smallexample
8361(define_asm_attributes [@var{attr-sets}])
8362@end smallexample
8363
8364@noindent
8365where @var{attr-sets} is specified the same as for both the
8366@code{define_insn} and the @code{define_peephole} expressions.
8367
8368These values will typically be the ``worst case'' attribute values.  For
8369example, they might indicate that the condition code will be clobbered.
8370
8371A specification for a @code{length} attribute is handled specially.  The
8372way to compute the length of an @code{asm} insn is to multiply the
8373length specified in the expression @code{define_asm_attributes} by the
8374number of machine instructions specified in the @code{asm} statement,
8375determined by counting the number of semicolons and newlines in the
8376string.  Therefore, the value of the @code{length} attribute specified
8377in a @code{define_asm_attributes} should be the maximum possible length
8378of a single machine instruction.
8379
8380@end ifset
8381@ifset INTERNALS
8382@node Attr Example
8383@subsection Example of Attribute Specifications
8384@cindex attribute specifications example
8385@cindex attribute specifications
8386
8387The judicious use of defaulting is important in the efficient use of
8388insn attributes.  Typically, insns are divided into @dfn{types} and an
8389attribute, customarily called @code{type}, is used to represent this
8390value.  This attribute is normally used only to define the default value
8391for other attributes.  An example will clarify this usage.
8392
8393Assume we have a RISC machine with a condition code and in which only
8394full-word operations are performed in registers.  Let us assume that we
8395can divide all insns into loads, stores, (integer) arithmetic
8396operations, floating point operations, and branches.
8397
8398Here we will concern ourselves with determining the effect of an insn on
8399the condition code and will limit ourselves to the following possible
8400effects:  The condition code can be set unpredictably (clobbered), not
8401be changed, be set to agree with the results of the operation, or only
8402changed if the item previously set into the condition code has been
8403modified.
8404
8405Here is part of a sample @file{md} file for such a machine:
8406
8407@smallexample
8408(define_attr "type" "load,store,arith,fp,branch" (const_string "arith"))
8409
8410(define_attr "cc" "clobber,unchanged,set,change0"
8411             (cond [(eq_attr "type" "load")
8412                        (const_string "change0")
8413                    (eq_attr "type" "store,branch")
8414                        (const_string "unchanged")
8415                    (eq_attr "type" "arith")
8416                        (if_then_else (match_operand:SI 0 "" "")
8417                                      (const_string "set")
8418                                      (const_string "clobber"))]
8419                   (const_string "clobber")))
8420
8421(define_insn ""
8422  [(set (match_operand:SI 0 "general_operand" "=r,r,m")
8423        (match_operand:SI 1 "general_operand" "r,m,r"))]
8424  ""
8425  "@@
8426   move %0,%1
8427   load %0,%1
8428   store %0,%1"
8429  [(set_attr "type" "arith,load,store")])
8430@end smallexample
8431
8432Note that we assume in the above example that arithmetic operations
8433performed on quantities smaller than a machine word clobber the condition
8434code since they will set the condition code to a value corresponding to the
8435full-word result.
8436
8437@end ifset
8438@ifset INTERNALS
8439@node Insn Lengths
8440@subsection Computing the Length of an Insn
8441@cindex insn lengths, computing
8442@cindex computing the length of an insn
8443
8444For many machines, multiple types of branch instructions are provided, each
8445for different length branch displacements.  In most cases, the assembler
8446will choose the correct instruction to use.  However, when the assembler
8447cannot do so, GCC can when a special attribute, the @code{length}
8448attribute, is defined.  This attribute must be defined to have numeric
8449values by specifying a null string in its @code{define_attr}.
8450
8451In the case of the @code{length} attribute, two additional forms of
8452arithmetic terms are allowed in test expressions:
8453
8454@table @code
8455@cindex @code{match_dup} and attributes
8456@item (match_dup @var{n})
8457This refers to the address of operand @var{n} of the current insn, which
8458must be a @code{label_ref}.
8459
8460@cindex @code{pc} and attributes
8461@item (pc)
8462For non-branch instructions and backward branch instructions, this refers
8463to the address of the current insn.  But for forward branch instructions,
8464this refers to the address of the next insn, because the length of the
8465current insn is to be computed.
8466@end table
8467
8468@cindex @code{addr_vec}, length of
8469@cindex @code{addr_diff_vec}, length of
8470For normal insns, the length will be determined by value of the
8471@code{length} attribute.  In the case of @code{addr_vec} and
8472@code{addr_diff_vec} insn patterns, the length is computed as
8473the number of vectors multiplied by the size of each vector.
8474
8475Lengths are measured in addressable storage units (bytes).
8476
8477Note that it is possible to call functions via the @code{symbol_ref}
8478mechanism to compute the length of an insn.  However, if you use this
8479mechanism you must provide dummy clauses to express the maximum length
8480without using the function call.  You can an example of this in the
8481@code{pa} machine description for the @code{call_symref} pattern.
8482
8483The following macros can be used to refine the length computation:
8484
8485@table @code
8486@findex ADJUST_INSN_LENGTH
8487@item ADJUST_INSN_LENGTH (@var{insn}, @var{length})
8488If defined, modifies the length assigned to instruction @var{insn} as a
8489function of the context in which it is used.  @var{length} is an lvalue
8490that contains the initially computed length of the insn and should be
8491updated with the correct length of the insn.
8492
8493This macro will normally not be required.  A case in which it is
8494required is the ROMP@.  On this machine, the size of an @code{addr_vec}
8495insn must be increased by two to compensate for the fact that alignment
8496may be required.
8497@end table
8498
8499@findex get_attr_length
8500The routine that returns @code{get_attr_length} (the value of the
8501@code{length} attribute) can be used by the output routine to
8502determine the form of the branch instruction to be written, as the
8503example below illustrates.
8504
8505As an example of the specification of variable-length branches, consider
8506the IBM 360.  If we adopt the convention that a register will be set to
8507the starting address of a function, we can jump to labels within 4k of
8508the start using a four-byte instruction.  Otherwise, we need a six-byte
8509sequence to load the address from memory and then branch to it.
8510
8511On such a machine, a pattern for a branch instruction might be specified
8512as follows:
8513
8514@smallexample
8515(define_insn "jump"
8516  [(set (pc)
8517        (label_ref (match_operand 0 "" "")))]
8518  ""
8519@{
8520   return (get_attr_length (insn) == 4
8521           ? "b %l0" : "l r15,=a(%l0); br r15");
8522@}
8523  [(set (attr "length")
8524        (if_then_else (lt (match_dup 0) (const_int 4096))
8525                      (const_int 4)
8526                      (const_int 6)))])
8527@end smallexample
8528
8529@end ifset
8530@ifset INTERNALS
8531@node Constant Attributes
8532@subsection Constant Attributes
8533@cindex constant attributes
8534
8535A special form of @code{define_attr}, where the expression for the
8536default value is a @code{const} expression, indicates an attribute that
8537is constant for a given run of the compiler.  Constant attributes may be
8538used to specify which variety of processor is used.  For example,
8539
8540@smallexample
8541(define_attr "cpu" "m88100,m88110,m88000"
8542 (const
8543  (cond [(symbol_ref "TARGET_88100") (const_string "m88100")
8544         (symbol_ref "TARGET_88110") (const_string "m88110")]
8545        (const_string "m88000"))))
8546
8547(define_attr "memory" "fast,slow"
8548 (const
8549  (if_then_else (symbol_ref "TARGET_FAST_MEM")
8550                (const_string "fast")
8551                (const_string "slow"))))
8552@end smallexample
8553
8554The routine generated for constant attributes has no parameters as it
8555does not depend on any particular insn.  RTL expressions used to define
8556the value of a constant attribute may use the @code{symbol_ref} form,
8557but may not use either the @code{match_operand} form or @code{eq_attr}
8558forms involving insn attributes.
8559
8560@end ifset
8561@ifset INTERNALS
8562@node Mnemonic Attribute
8563@subsection Mnemonic Attribute
8564@cindex mnemonic attribute
8565
8566The @code{mnemonic} attribute is a string type attribute holding the
8567instruction mnemonic for an insn alternative.  The attribute values
8568will automatically be generated by the machine description parser if
8569there is an attribute definition in the md file:
8570
8571@smallexample
8572(define_attr "mnemonic" "unknown" (const_string "unknown"))
8573@end smallexample
8574
8575The default value can be freely chosen as long as it does not collide
8576with any of the instruction mnemonics.  This value will be used
8577whenever the machine description parser is not able to determine the
8578mnemonic string.  This might be the case for output templates
8579containing more than a single instruction as in
8580@code{"mvcle\t%0,%1,0\;jo\t.-4"}.
8581
8582The @code{mnemonic} attribute set is not generated automatically if the
8583instruction string is generated via C code.
8584
8585An existing @code{mnemonic} attribute set in an insn definition will not
8586be overriden by the md file parser.  That way it is possible to
8587manually set the instruction mnemonics for the cases where the md file
8588parser fails to determine it automatically.
8589
8590The @code{mnemonic} attribute is useful for dealing with instruction
8591specific properties in the pipeline description without defining
8592additional insn attributes.
8593
8594@smallexample
8595(define_attr "ooo_expanded" ""
8596  (cond [(eq_attr "mnemonic" "dlr,dsgr,d,dsgf,stam,dsgfr,dlgr")
8597         (const_int 1)]
8598        (const_int 0)))
8599@end smallexample
8600
8601@end ifset
8602@ifset INTERNALS
8603@node Delay Slots
8604@subsection Delay Slot Scheduling
8605@cindex delay slots, defining
8606
8607The insn attribute mechanism can be used to specify the requirements for
8608delay slots, if any, on a target machine.  An instruction is said to
8609require a @dfn{delay slot} if some instructions that are physically
8610after the instruction are executed as if they were located before it.
8611Classic examples are branch and call instructions, which often execute
8612the following instruction before the branch or call is performed.
8613
8614On some machines, conditional branch instructions can optionally
8615@dfn{annul} instructions in the delay slot.  This means that the
8616instruction will not be executed for certain branch outcomes.  Both
8617instructions that annul if the branch is true and instructions that
8618annul if the branch is false are supported.
8619
8620Delay slot scheduling differs from instruction scheduling in that
8621determining whether an instruction needs a delay slot is dependent only
8622on the type of instruction being generated, not on data flow between the
8623instructions.  See the next section for a discussion of data-dependent
8624instruction scheduling.
8625
8626@findex define_delay
8627The requirement of an insn needing one or more delay slots is indicated
8628via the @code{define_delay} expression.  It has the following form:
8629
8630@smallexample
8631(define_delay @var{test}
8632              [@var{delay-1} @var{annul-true-1} @var{annul-false-1}
8633               @var{delay-2} @var{annul-true-2} @var{annul-false-2}
8634               @dots{}])
8635@end smallexample
8636
8637@var{test} is an attribute test that indicates whether this
8638@code{define_delay} applies to a particular insn.  If so, the number of
8639required delay slots is determined by the length of the vector specified
8640as the second argument.  An insn placed in delay slot @var{n} must
8641satisfy attribute test @var{delay-n}.  @var{annul-true-n} is an
8642attribute test that specifies which insns may be annulled if the branch
8643is true.  Similarly, @var{annul-false-n} specifies which insns in the
8644delay slot may be annulled if the branch is false.  If annulling is not
8645supported for that delay slot, @code{(nil)} should be coded.
8646
8647For example, in the common case where branch and call insns require
8648a single delay slot, which may contain any insn other than a branch or
8649call, the following would be placed in the @file{md} file:
8650
8651@smallexample
8652(define_delay (eq_attr "type" "branch,call")
8653              [(eq_attr "type" "!branch,call") (nil) (nil)])
8654@end smallexample
8655
8656Multiple @code{define_delay} expressions may be specified.  In this
8657case, each such expression specifies different delay slot requirements
8658and there must be no insn for which tests in two @code{define_delay}
8659expressions are both true.
8660
8661For example, if we have a machine that requires one delay slot for branches
8662but two for calls,  no delay slot can contain a branch or call insn,
8663and any valid insn in the delay slot for the branch can be annulled if the
8664branch is true, we might represent this as follows:
8665
8666@smallexample
8667(define_delay (eq_attr "type" "branch")
8668   [(eq_attr "type" "!branch,call")
8669    (eq_attr "type" "!branch,call")
8670    (nil)])
8671
8672(define_delay (eq_attr "type" "call")
8673              [(eq_attr "type" "!branch,call") (nil) (nil)
8674               (eq_attr "type" "!branch,call") (nil) (nil)])
8675@end smallexample
8676@c the above is *still* too long.  --mew 4feb93
8677
8678@end ifset
8679@ifset INTERNALS
8680@node Processor pipeline description
8681@subsection Specifying processor pipeline description
8682@cindex processor pipeline description
8683@cindex processor functional units
8684@cindex instruction latency time
8685@cindex interlock delays
8686@cindex data dependence delays
8687@cindex reservation delays
8688@cindex pipeline hazard recognizer
8689@cindex automaton based pipeline description
8690@cindex regular expressions
8691@cindex deterministic finite state automaton
8692@cindex automaton based scheduler
8693@cindex RISC
8694@cindex VLIW
8695
8696To achieve better performance, most modern processors
8697(super-pipelined, superscalar @acronym{RISC}, and @acronym{VLIW}
8698processors) have many @dfn{functional units} on which several
8699instructions can be executed simultaneously.  An instruction starts
8700execution if its issue conditions are satisfied.  If not, the
8701instruction is stalled until its conditions are satisfied.  Such
8702@dfn{interlock (pipeline) delay} causes interruption of the fetching
8703of successor instructions (or demands nop instructions, e.g.@: for some
8704MIPS processors).
8705
8706There are two major kinds of interlock delays in modern processors.
8707The first one is a data dependence delay determining @dfn{instruction
8708latency time}.  The instruction execution is not started until all
8709source data have been evaluated by prior instructions (there are more
8710complex cases when the instruction execution starts even when the data
8711are not available but will be ready in given time after the
8712instruction execution start).  Taking the data dependence delays into
8713account is simple.  The data dependence (true, output, and
8714anti-dependence) delay between two instructions is given by a
8715constant.  In most cases this approach is adequate.  The second kind
8716of interlock delays is a reservation delay.  The reservation delay
8717means that two instructions under execution will be in need of shared
8718processors resources, i.e.@: buses, internal registers, and/or
8719functional units, which are reserved for some time.  Taking this kind
8720of delay into account is complex especially for modern @acronym{RISC}
8721processors.
8722
8723The task of exploiting more processor parallelism is solved by an
8724instruction scheduler.  For a better solution to this problem, the
8725instruction scheduler has to have an adequate description of the
8726processor parallelism (or @dfn{pipeline description}).  GCC
8727machine descriptions describe processor parallelism and functional
8728unit reservations for groups of instructions with the aid of
8729@dfn{regular expressions}.
8730
8731The GCC instruction scheduler uses a @dfn{pipeline hazard recognizer} to
8732figure out the possibility of the instruction issue by the processor
8733on a given simulated processor cycle.  The pipeline hazard recognizer is
8734automatically generated from the processor pipeline description.  The
8735pipeline hazard recognizer generated from the machine description
8736is based on a deterministic finite state automaton (@acronym{DFA}):
8737the instruction issue is possible if there is a transition from one
8738automaton state to another one.  This algorithm is very fast, and
8739furthermore, its speed is not dependent on processor
8740complexity@footnote{However, the size of the automaton depends on
8741processor complexity.  To limit this effect, machine descriptions
8742can split orthogonal parts of the machine description among several
8743automata: but then, since each of these must be stepped independently,
8744this does cause a small decrease in the algorithm's performance.}.
8745
8746@cindex automaton based pipeline description
8747The rest of this section describes the directives that constitute
8748an automaton-based processor pipeline description.  The order of
8749these constructions within the machine description file is not
8750important.
8751
8752@findex define_automaton
8753@cindex pipeline hazard recognizer
8754The following optional construction describes names of automata
8755generated and used for the pipeline hazards recognition.  Sometimes
8756the generated finite state automaton used by the pipeline hazard
8757recognizer is large.  If we use more than one automaton and bind functional
8758units to the automata, the total size of the automata is usually
8759less than the size of the single automaton.  If there is no one such
8760construction, only one finite state automaton is generated.
8761
8762@smallexample
8763(define_automaton @var{automata-names})
8764@end smallexample
8765
8766@var{automata-names} is a string giving names of the automata.  The
8767names are separated by commas.  All the automata should have unique names.
8768The automaton name is used in the constructions @code{define_cpu_unit} and
8769@code{define_query_cpu_unit}.
8770
8771@findex define_cpu_unit
8772@cindex processor functional units
8773Each processor functional unit used in the description of instruction
8774reservations should be described by the following construction.
8775
8776@smallexample
8777(define_cpu_unit @var{unit-names} [@var{automaton-name}])
8778@end smallexample
8779
8780@var{unit-names} is a string giving the names of the functional units
8781separated by commas.  Don't use name @samp{nothing}, it is reserved
8782for other goals.
8783
8784@var{automaton-name} is a string giving the name of the automaton with
8785which the unit is bound.  The automaton should be described in
8786construction @code{define_automaton}.  You should give
8787@dfn{automaton-name}, if there is a defined automaton.
8788
8789The assignment of units to automata are constrained by the uses of the
8790units in insn reservations.  The most important constraint is: if a
8791unit reservation is present on a particular cycle of an alternative
8792for an insn reservation, then some unit from the same automaton must
8793be present on the same cycle for the other alternatives of the insn
8794reservation.  The rest of the constraints are mentioned in the
8795description of the subsequent constructions.
8796
8797@findex define_query_cpu_unit
8798@cindex querying function unit reservations
8799The following construction describes CPU functional units analogously
8800to @code{define_cpu_unit}.  The reservation of such units can be
8801queried for an automaton state.  The instruction scheduler never
8802queries reservation of functional units for given automaton state.  So
8803as a rule, you don't need this construction.  This construction could
8804be used for future code generation goals (e.g.@: to generate
8805@acronym{VLIW} insn templates).
8806
8807@smallexample
8808(define_query_cpu_unit @var{unit-names} [@var{automaton-name}])
8809@end smallexample
8810
8811@var{unit-names} is a string giving names of the functional units
8812separated by commas.
8813
8814@var{automaton-name} is a string giving the name of the automaton with
8815which the unit is bound.
8816
8817@findex define_insn_reservation
8818@cindex instruction latency time
8819@cindex regular expressions
8820@cindex data bypass
8821The following construction is the major one to describe pipeline
8822characteristics of an instruction.
8823
8824@smallexample
8825(define_insn_reservation @var{insn-name} @var{default_latency}
8826                         @var{condition} @var{regexp})
8827@end smallexample
8828
8829@var{default_latency} is a number giving latency time of the
8830instruction.  There is an important difference between the old
8831description and the automaton based pipeline description.  The latency
8832time is used for all dependencies when we use the old description.  In
8833the automaton based pipeline description, the given latency time is only
8834used for true dependencies.  The cost of anti-dependencies is always
8835zero and the cost of output dependencies is the difference between
8836latency times of the producing and consuming insns (if the difference
8837is negative, the cost is considered to be zero).  You can always
8838change the default costs for any description by using the target hook
8839@code{TARGET_SCHED_ADJUST_COST} (@pxref{Scheduling}).
8840
8841@var{insn-name} is a string giving the internal name of the insn.  The
8842internal names are used in constructions @code{define_bypass} and in
8843the automaton description file generated for debugging.  The internal
8844name has nothing in common with the names in @code{define_insn}.  It is a
8845good practice to use insn classes described in the processor manual.
8846
8847@var{condition} defines what RTL insns are described by this
8848construction.  You should remember that you will be in trouble if
8849@var{condition} for two or more different
8850@code{define_insn_reservation} constructions is TRUE for an insn.  In
8851this case what reservation will be used for the insn is not defined.
8852Such cases are not checked during generation of the pipeline hazards
8853recognizer because in general recognizing that two conditions may have
8854the same value is quite difficult (especially if the conditions
8855contain @code{symbol_ref}).  It is also not checked during the
8856pipeline hazard recognizer work because it would slow down the
8857recognizer considerably.
8858
8859@var{regexp} is a string describing the reservation of the cpu's functional
8860units by the instruction.  The reservations are described by a regular
8861expression according to the following syntax:
8862
8863@smallexample
8864       regexp = regexp "," oneof
8865              | oneof
8866
8867       oneof = oneof "|" allof
8868             | allof
8869
8870       allof = allof "+" repeat
8871             | repeat
8872
8873       repeat = element "*" number
8874              | element
8875
8876       element = cpu_function_unit_name
8877               | reservation_name
8878               | result_name
8879               | "nothing"
8880               | "(" regexp ")"
8881@end smallexample
8882
8883@itemize @bullet
8884@item
8885@samp{,} is used for describing the start of the next cycle in
8886the reservation.
8887
8888@item
8889@samp{|} is used for describing a reservation described by the first
8890regular expression @strong{or} a reservation described by the second
8891regular expression @strong{or} etc.
8892
8893@item
8894@samp{+} is used for describing a reservation described by the first
8895regular expression @strong{and} a reservation described by the
8896second regular expression @strong{and} etc.
8897
8898@item
8899@samp{*} is used for convenience and simply means a sequence in which
8900the regular expression are repeated @var{number} times with cycle
8901advancing (see @samp{,}).
8902
8903@item
8904@samp{cpu_function_unit_name} denotes reservation of the named
8905functional unit.
8906
8907@item
8908@samp{reservation_name} --- see description of construction
8909@samp{define_reservation}.
8910
8911@item
8912@samp{nothing} denotes no unit reservations.
8913@end itemize
8914
8915@findex define_reservation
8916Sometimes unit reservations for different insns contain common parts.
8917In such case, you can simplify the pipeline description by describing
8918the common part by the following construction
8919
8920@smallexample
8921(define_reservation @var{reservation-name} @var{regexp})
8922@end smallexample
8923
8924@var{reservation-name} is a string giving name of @var{regexp}.
8925Functional unit names and reservation names are in the same name
8926space.  So the reservation names should be different from the
8927functional unit names and can not be the reserved name @samp{nothing}.
8928
8929@findex define_bypass
8930@cindex instruction latency time
8931@cindex data bypass
8932The following construction is used to describe exceptions in the
8933latency time for given instruction pair.  This is so called bypasses.
8934
8935@smallexample
8936(define_bypass @var{number} @var{out_insn_names} @var{in_insn_names}
8937               [@var{guard}])
8938@end smallexample
8939
8940@var{number} defines when the result generated by the instructions
8941given in string @var{out_insn_names} will be ready for the
8942instructions given in string @var{in_insn_names}.  Each of these
8943strings is a comma-separated list of filename-style globs and
8944they refer to the names of @code{define_insn_reservation}s.
8945For example:
8946@smallexample
8947(define_bypass 1 "cpu1_load_*, cpu1_store_*" "cpu1_load_*")
8948@end smallexample
8949defines a bypass between instructions that start with
8950@samp{cpu1_load_} or @samp{cpu1_store_} and those that start with
8951@samp{cpu1_load_}.
8952
8953@var{guard} is an optional string giving the name of a C function which
8954defines an additional guard for the bypass.  The function will get the
8955two insns as parameters.  If the function returns zero the bypass will
8956be ignored for this case.  The additional guard is necessary to
8957recognize complicated bypasses, e.g.@: when the consumer is only an address
8958of insn @samp{store} (not a stored value).
8959
8960If there are more one bypass with the same output and input insns, the
8961chosen bypass is the first bypass with a guard in description whose
8962guard function returns nonzero.  If there is no such bypass, then
8963bypass without the guard function is chosen.
8964
8965@findex exclusion_set
8966@findex presence_set
8967@findex final_presence_set
8968@findex absence_set
8969@findex final_absence_set
8970@cindex VLIW
8971@cindex RISC
8972The following five constructions are usually used to describe
8973@acronym{VLIW} processors, or more precisely, to describe a placement
8974of small instructions into @acronym{VLIW} instruction slots.  They
8975can be used for @acronym{RISC} processors, too.
8976
8977@smallexample
8978(exclusion_set @var{unit-names} @var{unit-names})
8979(presence_set @var{unit-names} @var{patterns})
8980(final_presence_set @var{unit-names} @var{patterns})
8981(absence_set @var{unit-names} @var{patterns})
8982(final_absence_set @var{unit-names} @var{patterns})
8983@end smallexample
8984
8985@var{unit-names} is a string giving names of functional units
8986separated by commas.
8987
8988@var{patterns} is a string giving patterns of functional units
8989separated by comma.  Currently pattern is one unit or units
8990separated by white-spaces.
8991
8992The first construction (@samp{exclusion_set}) means that each
8993functional unit in the first string can not be reserved simultaneously
8994with a unit whose name is in the second string and vice versa.  For
8995example, the construction is useful for describing processors
8996(e.g.@: some SPARC processors) with a fully pipelined floating point
8997functional unit which can execute simultaneously only single floating
8998point insns or only double floating point insns.
8999
9000The second construction (@samp{presence_set}) means that each
9001functional unit in the first string can not be reserved unless at
9002least one of pattern of units whose names are in the second string is
9003reserved.  This is an asymmetric relation.  For example, it is useful
9004for description that @acronym{VLIW} @samp{slot1} is reserved after
9005@samp{slot0} reservation.  We could describe it by the following
9006construction
9007
9008@smallexample
9009(presence_set "slot1" "slot0")
9010@end smallexample
9011
9012Or @samp{slot1} is reserved only after @samp{slot0} and unit @samp{b0}
9013reservation.  In this case we could write
9014
9015@smallexample
9016(presence_set "slot1" "slot0 b0")
9017@end smallexample
9018
9019The third construction (@samp{final_presence_set}) is analogous to
9020@samp{presence_set}.  The difference between them is when checking is
9021done.  When an instruction is issued in given automaton state
9022reflecting all current and planned unit reservations, the automaton
9023state is changed.  The first state is a source state, the second one
9024is a result state.  Checking for @samp{presence_set} is done on the
9025source state reservation, checking for @samp{final_presence_set} is
9026done on the result reservation.  This construction is useful to
9027describe a reservation which is actually two subsequent reservations.
9028For example, if we use
9029
9030@smallexample
9031(presence_set "slot1" "slot0")
9032@end smallexample
9033
9034the following insn will be never issued (because @samp{slot1} requires
9035@samp{slot0} which is absent in the source state).
9036
9037@smallexample
9038(define_reservation "insn_and_nop" "slot0 + slot1")
9039@end smallexample
9040
9041but it can be issued if we use analogous @samp{final_presence_set}.
9042
9043The forth construction (@samp{absence_set}) means that each functional
9044unit in the first string can be reserved only if each pattern of units
9045whose names are in the second string is not reserved.  This is an
9046asymmetric relation (actually @samp{exclusion_set} is analogous to
9047this one but it is symmetric).  For example it might be useful in a
9048@acronym{VLIW} description to say that @samp{slot0} cannot be reserved
9049after either @samp{slot1} or @samp{slot2} have been reserved.  This
9050can be described as:
9051
9052@smallexample
9053(absence_set "slot0" "slot1, slot2")
9054@end smallexample
9055
9056Or @samp{slot2} can not be reserved if @samp{slot0} and unit @samp{b0}
9057are reserved or @samp{slot1} and unit @samp{b1} are reserved.  In
9058this case we could write
9059
9060@smallexample
9061(absence_set "slot2" "slot0 b0, slot1 b1")
9062@end smallexample
9063
9064All functional units mentioned in a set should belong to the same
9065automaton.
9066
9067The last construction (@samp{final_absence_set}) is analogous to
9068@samp{absence_set} but checking is done on the result (state)
9069reservation.  See comments for @samp{final_presence_set}.
9070
9071@findex automata_option
9072@cindex deterministic finite state automaton
9073@cindex nondeterministic finite state automaton
9074@cindex finite state automaton minimization
9075You can control the generator of the pipeline hazard recognizer with
9076the following construction.
9077
9078@smallexample
9079(automata_option @var{options})
9080@end smallexample
9081
9082@var{options} is a string giving options which affect the generated
9083code.  Currently there are the following options:
9084
9085@itemize @bullet
9086@item
9087@dfn{no-minimization} makes no minimization of the automaton.  This is
9088only worth to do when we are debugging the description and need to
9089look more accurately at reservations of states.
9090
9091@item
9092@dfn{time} means printing time statistics about the generation of
9093automata.
9094
9095@item
9096@dfn{stats} means printing statistics about the generated automata
9097such as the number of DFA states, NDFA states and arcs.
9098
9099@item
9100@dfn{v} means a generation of the file describing the result automata.
9101The file has suffix @samp{.dfa} and can be used for the description
9102verification and debugging.
9103
9104@item
9105@dfn{w} means a generation of warning instead of error for
9106non-critical errors.
9107
9108@item
9109@dfn{no-comb-vect} prevents the automaton generator from generating
9110two data structures and comparing them for space efficiency.  Using
9111a comb vector to represent transitions may be better, but it can be
9112very expensive to construct.  This option is useful if the build
9113process spends an unacceptably long time in genautomata.
9114
9115@item
9116@dfn{ndfa} makes nondeterministic finite state automata.  This affects
9117the treatment of operator @samp{|} in the regular expressions.  The
9118usual treatment of the operator is to try the first alternative and,
9119if the reservation is not possible, the second alternative.  The
9120nondeterministic treatment means trying all alternatives, some of them
9121may be rejected by reservations in the subsequent insns.
9122
9123@item
9124@dfn{collapse-ndfa} modifies the behaviour of the generator when
9125producing an automaton.  An additional state transition to collapse a
9126nondeterministic @acronym{NDFA} state to a deterministic @acronym{DFA}
9127state is generated.  It can be triggered by passing @code{const0_rtx} to
9128state_transition.  In such an automaton, cycle advance transitions are
9129available only for these collapsed states.  This option is useful for
9130ports that want to use the @code{ndfa} option, but also want to use
9131@code{define_query_cpu_unit} to assign units to insns issued in a cycle.
9132
9133@item
9134@dfn{progress} means output of a progress bar showing how many states
9135were generated so far for automaton being processed.  This is useful
9136during debugging a @acronym{DFA} description.  If you see too many
9137generated states, you could interrupt the generator of the pipeline
9138hazard recognizer and try to figure out a reason for generation of the
9139huge automaton.
9140@end itemize
9141
9142As an example, consider a superscalar @acronym{RISC} machine which can
9143issue three insns (two integer insns and one floating point insn) on
9144the cycle but can finish only two insns.  To describe this, we define
9145the following functional units.
9146
9147@smallexample
9148(define_cpu_unit "i0_pipeline, i1_pipeline, f_pipeline")
9149(define_cpu_unit "port0, port1")
9150@end smallexample
9151
9152All simple integer insns can be executed in any integer pipeline and
9153their result is ready in two cycles.  The simple integer insns are
9154issued into the first pipeline unless it is reserved, otherwise they
9155are issued into the second pipeline.  Integer division and
9156multiplication insns can be executed only in the second integer
9157pipeline and their results are ready correspondingly in 8 and 4
9158cycles.  The integer division is not pipelined, i.e.@: the subsequent
9159integer division insn can not be issued until the current division
9160insn finished.  Floating point insns are fully pipelined and their
9161results are ready in 3 cycles.  Where the result of a floating point
9162insn is used by an integer insn, an additional delay of one cycle is
9163incurred.  To describe all of this we could specify
9164
9165@smallexample
9166(define_cpu_unit "div")
9167
9168(define_insn_reservation "simple" 2 (eq_attr "type" "int")
9169                         "(i0_pipeline | i1_pipeline), (port0 | port1)")
9170
9171(define_insn_reservation "mult" 4 (eq_attr "type" "mult")
9172                         "i1_pipeline, nothing*2, (port0 | port1)")
9173
9174(define_insn_reservation "div" 8 (eq_attr "type" "div")
9175                         "i1_pipeline, div*7, div + (port0 | port1)")
9176
9177(define_insn_reservation "float" 3 (eq_attr "type" "float")
9178                         "f_pipeline, nothing, (port0 | port1))
9179
9180(define_bypass 4 "float" "simple,mult,div")
9181@end smallexample
9182
9183To simplify the description we could describe the following reservation
9184
9185@smallexample
9186(define_reservation "finish" "port0|port1")
9187@end smallexample
9188
9189and use it in all @code{define_insn_reservation} as in the following
9190construction
9191
9192@smallexample
9193(define_insn_reservation "simple" 2 (eq_attr "type" "int")
9194                         "(i0_pipeline | i1_pipeline), finish")
9195@end smallexample
9196
9197
9198@end ifset
9199@ifset INTERNALS
9200@node Conditional Execution
9201@section Conditional Execution
9202@cindex conditional execution
9203@cindex predication
9204
9205A number of architectures provide for some form of conditional
9206execution, or predication.  The hallmark of this feature is the
9207ability to nullify most of the instructions in the instruction set.
9208When the instruction set is large and not entirely symmetric, it
9209can be quite tedious to describe these forms directly in the
9210@file{.md} file.  An alternative is the @code{define_cond_exec} template.
9211
9212@findex define_cond_exec
9213@smallexample
9214(define_cond_exec
9215  [@var{predicate-pattern}]
9216  "@var{condition}"
9217  "@var{output-template}"
9218  "@var{optional-insn-attribues}")
9219@end smallexample
9220
9221@var{predicate-pattern} is the condition that must be true for the
9222insn to be executed at runtime and should match a relational operator.
9223One can use @code{match_operator} to match several relational operators
9224at once.  Any @code{match_operand} operands must have no more than one
9225alternative.
9226
9227@var{condition} is a C expression that must be true for the generated
9228pattern to match.
9229
9230@findex current_insn_predicate
9231@var{output-template} is a string similar to the @code{define_insn}
9232output template (@pxref{Output Template}), except that the @samp{*}
9233and @samp{@@} special cases do not apply.  This is only useful if the
9234assembly text for the predicate is a simple prefix to the main insn.
9235In order to handle the general case, there is a global variable
9236@code{current_insn_predicate} that will contain the entire predicate
9237if the current insn is predicated, and will otherwise be @code{NULL}.
9238
9239@var{optional-insn-attributes} is an optional vector of attributes that gets
9240appended to the insn attributes of the produced cond_exec rtx. It can
9241be used to add some distinguishing attribute to cond_exec rtxs produced
9242that way. An example usage would be to use this attribute in conjunction
9243with attributes on the main pattern to disable particular alternatives under
9244certain conditions.
9245
9246When @code{define_cond_exec} is used, an implicit reference to
9247the @code{predicable} instruction attribute is made.
9248@xref{Insn Attributes}.  This attribute must be a boolean (i.e.@: have
9249exactly two elements in its @var{list-of-values}), with the possible
9250values being @code{no} and @code{yes}.  The default and all uses in
9251the insns must be a simple constant, not a complex expressions.  It
9252may, however, depend on the alternative, by using a comma-separated
9253list of values.  If that is the case, the port should also define an
9254@code{enabled} attribute (@pxref{Disable Insn Alternatives}), which
9255should also allow only @code{no} and @code{yes} as its values.
9256
9257For each @code{define_insn} for which the @code{predicable}
9258attribute is true, a new @code{define_insn} pattern will be
9259generated that matches a predicated version of the instruction.
9260For example,
9261
9262@smallexample
9263(define_insn "addsi"
9264  [(set (match_operand:SI 0 "register_operand" "r")
9265        (plus:SI (match_operand:SI 1 "register_operand" "r")
9266                 (match_operand:SI 2 "register_operand" "r")))]
9267  "@var{test1}"
9268  "add %2,%1,%0")
9269
9270(define_cond_exec
9271  [(ne (match_operand:CC 0 "register_operand" "c")
9272       (const_int 0))]
9273  "@var{test2}"
9274  "(%0)")
9275@end smallexample
9276
9277@noindent
9278generates a new pattern
9279
9280@smallexample
9281(define_insn ""
9282  [(cond_exec
9283     (ne (match_operand:CC 3 "register_operand" "c") (const_int 0))
9284     (set (match_operand:SI 0 "register_operand" "r")
9285          (plus:SI (match_operand:SI 1 "register_operand" "r")
9286                   (match_operand:SI 2 "register_operand" "r"))))]
9287  "(@var{test2}) && (@var{test1})"
9288  "(%3) add %2,%1,%0")
9289@end smallexample
9290
9291@end ifset
9292@ifset INTERNALS
9293@node Define Subst
9294@section RTL Templates Transformations
9295@cindex define_subst
9296
9297For some hardware architectures there are common cases when the RTL
9298templates for the instructions can be derived from the other RTL
9299templates using simple transformations.  E.g., @file{i386.md} contains
9300an RTL template for the ordinary @code{sub} instruction---
9301@code{*subsi_1}, and for the @code{sub} instruction with subsequent
9302zero-extension---@code{*subsi_1_zext}.  Such cases can be easily
9303implemented by a single meta-template capable of generating a modified
9304case based on the initial one:
9305
9306@findex define_subst
9307@smallexample
9308(define_subst "@var{name}"
9309  [@var{input-template}]
9310  "@var{condition}"
9311  [@var{output-template}])
9312@end smallexample
9313@var{input-template} is a pattern describing the source RTL template,
9314which will be transformed.
9315
9316@var{condition} is a C expression that is conjunct with the condition
9317from the input-template to generate a condition to be used in the
9318output-template.
9319
9320@var{output-template} is a pattern that will be used in the resulting
9321template.
9322
9323@code{define_subst} mechanism is tightly coupled with the notion of the
9324subst attribute (@pxref{Subst Iterators}).  The use of
9325@code{define_subst} is triggered by a reference to a subst attribute in
9326the transforming RTL template.  This reference initiates duplication of
9327the source RTL template and substitution of the attributes with their
9328values.  The source RTL template is left unchanged, while the copy is
9329transformed by @code{define_subst}.  This transformation can fail in the
9330case when the source RTL template is not matched against the
9331input-template of the @code{define_subst}.  In such case the copy is
9332deleted.
9333
9334@code{define_subst} can be used only in @code{define_insn} and
9335@code{define_expand}, it cannot be used in other expressions (e.g. in
9336@code{define_insn_and_split}).
9337
9338@menu
9339* Define Subst Example::	    Example of @code{define_subst} work.
9340* Define Subst Pattern Matching::   Process of template comparison.
9341* Define Subst Output Template::    Generation of output template.
9342@end menu
9343
9344@node Define Subst Example
9345@subsection @code{define_subst} Example
9346@cindex define_subst
9347
9348To illustrate how @code{define_subst} works, let us examine a simple
9349template transformation.
9350
9351Suppose there are two kinds of instructions: one that touches flags and
9352the other that does not.  The instructions of the second type could be
9353generated with the following @code{define_subst}:
9354
9355@smallexample
9356(define_subst "add_clobber_subst"
9357  [(set (match_operand:SI 0 "" "")
9358        (match_operand:SI 1 "" ""))]
9359  ""
9360  [(set (match_dup 0)
9361        (match_dup 1))
9362   (clobber (reg:CC FLAGS_REG))]
9363@end smallexample
9364
9365This @code{define_subst} can be applied to any RTL pattern containing
9366@code{set} of mode SI and generates a copy with clobber when it is
9367applied.
9368
9369Assume there is an RTL template for a @code{max} instruction to be used
9370in @code{define_subst} mentioned above:
9371
9372@smallexample
9373(define_insn "maxsi"
9374  [(set (match_operand:SI 0 "register_operand" "=r")
9375        (max:SI
9376          (match_operand:SI 1 "register_operand" "r")
9377          (match_operand:SI 2 "register_operand" "r")))]
9378  ""
9379  "max\t@{%2, %1, %0|%0, %1, %2@}"
9380 [@dots{}])
9381@end smallexample
9382
9383To mark the RTL template for @code{define_subst} application,
9384subst-attributes are used.  They should be declared in advance:
9385
9386@smallexample
9387(define_subst_attr "add_clobber_name" "add_clobber_subst" "_noclobber" "_clobber")
9388@end smallexample
9389
9390Here @samp{add_clobber_name} is the attribute name,
9391@samp{add_clobber_subst} is the name of the corresponding
9392@code{define_subst}, the third argument (@samp{_noclobber}) is the
9393attribute value that would be substituted into the unchanged version of
9394the source RTL template, and the last argument (@samp{_clobber}) is the
9395value that would be substituted into the second, transformed,
9396version of the RTL template.
9397
9398Once the subst-attribute has been defined, it should be used in RTL
9399templates which need to be processed by the @code{define_subst}.  So,
9400the original RTL template should be changed:
9401
9402@smallexample
9403(define_insn "maxsi<add_clobber_name>"
9404  [(set (match_operand:SI 0 "register_operand" "=r")
9405        (max:SI
9406          (match_operand:SI 1 "register_operand" "r")
9407          (match_operand:SI 2 "register_operand" "r")))]
9408  ""
9409  "max\t@{%2, %1, %0|%0, %1, %2@}"
9410 [@dots{}])
9411@end smallexample
9412
9413The result of the @code{define_subst} usage would look like the following:
9414
9415@smallexample
9416(define_insn "maxsi_noclobber"
9417  [(set (match_operand:SI 0 "register_operand" "=r")
9418        (max:SI
9419          (match_operand:SI 1 "register_operand" "r")
9420          (match_operand:SI 2 "register_operand" "r")))]
9421  ""
9422  "max\t@{%2, %1, %0|%0, %1, %2@}"
9423 [@dots{}])
9424(define_insn "maxsi_clobber"
9425  [(set (match_operand:SI 0 "register_operand" "=r")
9426        (max:SI
9427          (match_operand:SI 1 "register_operand" "r")
9428          (match_operand:SI 2 "register_operand" "r")))
9429   (clobber (reg:CC FLAGS_REG))]
9430  ""
9431  "max\t@{%2, %1, %0|%0, %1, %2@}"
9432 [@dots{}])
9433@end smallexample
9434
9435@node Define Subst Pattern Matching
9436@subsection Pattern Matching in @code{define_subst}
9437@cindex define_subst
9438
9439All expressions, allowed in @code{define_insn} or @code{define_expand},
9440are allowed in the input-template of @code{define_subst}, except
9441@code{match_par_dup}, @code{match_scratch}, @code{match_parallel}. The
9442meanings of expressions in the input-template were changed:
9443
9444@code{match_operand} matches any expression (possibly, a subtree in
9445RTL-template), if modes of the @code{match_operand} and this expression
9446are the same, or mode of the @code{match_operand} is @code{VOIDmode}, or
9447this expression is @code{match_dup}, @code{match_op_dup}.  If the
9448expression is @code{match_operand} too, and predicate of
9449@code{match_operand} from the input pattern is not empty, then the
9450predicates are compared.  That can be used for more accurate filtering
9451of accepted RTL-templates.
9452
9453@code{match_operator} matches common operators (like @code{plus},
9454@code{minus}), @code{unspec}, @code{unspec_volatile} operators and
9455@code{match_operator}s from the original pattern if the modes match and
9456@code{match_operator} from the input pattern has the same number of
9457operands as the operator from the original pattern.
9458
9459@node Define Subst Output Template
9460@subsection Generation of output template in @code{define_subst}
9461@cindex define_subst
9462
9463If all necessary checks for @code{define_subst} application pass, a new
9464RTL-pattern, based on the output-template, is created to replace the old
9465template.  Like in input-patterns, meanings of some RTL expressions are
9466changed when they are used in output-patterns of a @code{define_subst}.
9467Thus, @code{match_dup} is used for copying the whole expression from the
9468original pattern, which matched corresponding @code{match_operand} from
9469the input pattern.
9470
9471@code{match_dup N} is used in the output template to be replaced with
9472the expression from the original pattern, which matched
9473@code{match_operand N} from the input pattern.  As a consequence,
9474@code{match_dup} cannot be used to point to @code{match_operand}s from
9475the output pattern, it should always refer to a @code{match_operand}
9476from the input pattern.
9477
9478In the output template one can refer to the expressions from the
9479original pattern and create new ones.  For instance, some operands could
9480be added by means of standard @code{match_operand}.
9481
9482After replacing @code{match_dup} with some RTL-subtree from the original
9483pattern, it could happen that several @code{match_operand}s in the
9484output pattern have the same indexes.  It is unknown, how many and what
9485indexes would be used in the expression which would replace
9486@code{match_dup}, so such conflicts in indexes are inevitable.  To
9487overcome this issue, @code{match_operands} and @code{match_operators},
9488which were introduced into the output pattern, are renumerated when all
9489@code{match_dup}s are replaced.
9490
9491Number of alternatives in @code{match_operand}s introduced into the
9492output template @code{M} could differ from the number of alternatives in
9493the original pattern @code{N}, so in the resultant pattern there would
9494be @code{N*M} alternatives.  Thus, constraints from the original pattern
9495would be duplicated @code{N} times, constraints from the output pattern
9496would be duplicated @code{M} times, producing all possible combinations.
9497@end ifset
9498
9499@ifset INTERNALS
9500@node Constant Definitions
9501@section Constant Definitions
9502@cindex constant definitions
9503@findex define_constants
9504
9505Using literal constants inside instruction patterns reduces legibility and
9506can be a maintenance problem.
9507
9508To overcome this problem, you may use the @code{define_constants}
9509expression.  It contains a vector of name-value pairs.  From that
9510point on, wherever any of the names appears in the MD file, it is as
9511if the corresponding value had been written instead.  You may use
9512@code{define_constants} multiple times; each appearance adds more
9513constants to the table.  It is an error to redefine a constant with
9514a different value.
9515
9516To come back to the a29k load multiple example, instead of
9517
9518@smallexample
9519(define_insn ""
9520  [(match_parallel 0 "load_multiple_operation"
9521     [(set (match_operand:SI 1 "gpc_reg_operand" "=r")
9522           (match_operand:SI 2 "memory_operand" "m"))
9523      (use (reg:SI 179))
9524      (clobber (reg:SI 179))])]
9525  ""
9526  "loadm 0,0,%1,%2")
9527@end smallexample
9528
9529You could write:
9530
9531@smallexample
9532(define_constants [
9533    (R_BP 177)
9534    (R_FC 178)
9535    (R_CR 179)
9536    (R_Q  180)
9537])
9538
9539(define_insn ""
9540  [(match_parallel 0 "load_multiple_operation"
9541     [(set (match_operand:SI 1 "gpc_reg_operand" "=r")
9542           (match_operand:SI 2 "memory_operand" "m"))
9543      (use (reg:SI R_CR))
9544      (clobber (reg:SI R_CR))])]
9545  ""
9546  "loadm 0,0,%1,%2")
9547@end smallexample
9548
9549The constants that are defined with a define_constant are also output
9550in the insn-codes.h header file as #defines.
9551
9552@cindex enumerations
9553@findex define_c_enum
9554You can also use the machine description file to define enumerations.
9555Like the constants defined by @code{define_constant}, these enumerations
9556are visible to both the machine description file and the main C code.
9557
9558The syntax is as follows:
9559
9560@smallexample
9561(define_c_enum "@var{name}" [
9562  @var{value0}
9563  @var{value1}
9564  @dots{}
9565  @var{valuen}
9566])
9567@end smallexample
9568
9569This definition causes the equivalent of the following C code to appear
9570in @file{insn-constants.h}:
9571
9572@smallexample
9573enum @var{name} @{
9574  @var{value0} = 0,
9575  @var{value1} = 1,
9576  @dots{}
9577  @var{valuen} = @var{n}
9578@};
9579#define NUM_@var{cname}_VALUES (@var{n} + 1)
9580@end smallexample
9581
9582where @var{cname} is the capitalized form of @var{name}.
9583It also makes each @var{valuei} available in the machine description
9584file, just as if it had been declared with:
9585
9586@smallexample
9587(define_constants [(@var{valuei} @var{i})])
9588@end smallexample
9589
9590Each @var{valuei} is usually an upper-case identifier and usually
9591begins with @var{cname}.
9592
9593You can split the enumeration definition into as many statements as
9594you like.  The above example is directly equivalent to:
9595
9596@smallexample
9597(define_c_enum "@var{name}" [@var{value0}])
9598(define_c_enum "@var{name}" [@var{value1}])
9599@dots{}
9600(define_c_enum "@var{name}" [@var{valuen}])
9601@end smallexample
9602
9603Splitting the enumeration helps to improve the modularity of each
9604individual @code{.md} file.  For example, if a port defines its
9605synchronization instructions in a separate @file{sync.md} file,
9606it is convenient to define all synchronization-specific enumeration
9607values in @file{sync.md} rather than in the main @file{.md} file.
9608
9609Some enumeration names have special significance to GCC:
9610
9611@table @code
9612@item unspecv
9613@findex unspec_volatile
9614If an enumeration called @code{unspecv} is defined, GCC will use it
9615when printing out @code{unspec_volatile} expressions.  For example:
9616
9617@smallexample
9618(define_c_enum "unspecv" [
9619  UNSPECV_BLOCKAGE
9620])
9621@end smallexample
9622
9623causes GCC to print @samp{(unspec_volatile @dots{} 0)} as:
9624
9625@smallexample
9626(unspec_volatile ... UNSPECV_BLOCKAGE)
9627@end smallexample
9628
9629@item unspec
9630@findex unspec
9631If an enumeration called @code{unspec} is defined, GCC will use
9632it when printing out @code{unspec} expressions.  GCC will also use
9633it when printing out @code{unspec_volatile} expressions unless an
9634@code{unspecv} enumeration is also defined.  You can therefore
9635decide whether to keep separate enumerations for volatile and
9636non-volatile expressions or whether to use the same enumeration
9637for both.
9638@end table
9639
9640@findex define_enum
9641@anchor{define_enum}
9642Another way of defining an enumeration is to use @code{define_enum}:
9643
9644@smallexample
9645(define_enum "@var{name}" [
9646  @var{value0}
9647  @var{value1}
9648  @dots{}
9649  @var{valuen}
9650])
9651@end smallexample
9652
9653This directive implies:
9654
9655@smallexample
9656(define_c_enum "@var{name}" [
9657  @var{cname}_@var{cvalue0}
9658  @var{cname}_@var{cvalue1}
9659  @dots{}
9660  @var{cname}_@var{cvaluen}
9661])
9662@end smallexample
9663
9664@findex define_enum_attr
9665where @var{cvaluei} is the capitalized form of @var{valuei}.
9666However, unlike @code{define_c_enum}, the enumerations defined
9667by @code{define_enum} can be used in attribute specifications
9668(@pxref{define_enum_attr}).
9669@end ifset
9670@ifset INTERNALS
9671@node Iterators
9672@section Iterators
9673@cindex iterators in @file{.md} files
9674
9675Ports often need to define similar patterns for more than one machine
9676mode or for more than one rtx code.  GCC provides some simple iterator
9677facilities to make this process easier.
9678
9679@menu
9680* Mode Iterators::         Generating variations of patterns for different modes.
9681* Code Iterators::         Doing the same for codes.
9682* Int Iterators::          Doing the same for integers.
9683* Subst Iterators::	   Generating variations of patterns for define_subst.
9684@end menu
9685
9686@node Mode Iterators
9687@subsection Mode Iterators
9688@cindex mode iterators in @file{.md} files
9689
9690Ports often need to define similar patterns for two or more different modes.
9691For example:
9692
9693@itemize @bullet
9694@item
9695If a processor has hardware support for both single and double
9696floating-point arithmetic, the @code{SFmode} patterns tend to be
9697very similar to the @code{DFmode} ones.
9698
9699@item
9700If a port uses @code{SImode} pointers in one configuration and
9701@code{DImode} pointers in another, it will usually have very similar
9702@code{SImode} and @code{DImode} patterns for manipulating pointers.
9703@end itemize
9704
9705Mode iterators allow several patterns to be instantiated from one
9706@file{.md} file template.  They can be used with any type of
9707rtx-based construct, such as a @code{define_insn},
9708@code{define_split}, or @code{define_peephole2}.
9709
9710@menu
9711* Defining Mode Iterators:: Defining a new mode iterator.
9712* Substitutions::           Combining mode iterators with substitutions
9713* Examples::                Examples
9714@end menu
9715
9716@node Defining Mode Iterators
9717@subsubsection Defining Mode Iterators
9718@findex define_mode_iterator
9719
9720The syntax for defining a mode iterator is:
9721
9722@smallexample
9723(define_mode_iterator @var{name} [(@var{mode1} "@var{cond1}") @dots{} (@var{moden} "@var{condn}")])
9724@end smallexample
9725
9726This allows subsequent @file{.md} file constructs to use the mode suffix
9727@code{:@var{name}}.  Every construct that does so will be expanded
9728@var{n} times, once with every use of @code{:@var{name}} replaced by
9729@code{:@var{mode1}}, once with every use replaced by @code{:@var{mode2}},
9730and so on.  In the expansion for a particular @var{modei}, every
9731C condition will also require that @var{condi} be true.
9732
9733For example:
9734
9735@smallexample
9736(define_mode_iterator P [(SI "Pmode == SImode") (DI "Pmode == DImode")])
9737@end smallexample
9738
9739defines a new mode suffix @code{:P}.  Every construct that uses
9740@code{:P} will be expanded twice, once with every @code{:P} replaced
9741by @code{:SI} and once with every @code{:P} replaced by @code{:DI}.
9742The @code{:SI} version will only apply if @code{Pmode == SImode} and
9743the @code{:DI} version will only apply if @code{Pmode == DImode}.
9744
9745As with other @file{.md} conditions, an empty string is treated
9746as ``always true''.  @code{(@var{mode} "")} can also be abbreviated
9747to @code{@var{mode}}.  For example:
9748
9749@smallexample
9750(define_mode_iterator GPR [SI (DI "TARGET_64BIT")])
9751@end smallexample
9752
9753means that the @code{:DI} expansion only applies if @code{TARGET_64BIT}
9754but that the @code{:SI} expansion has no such constraint.
9755
9756Iterators are applied in the order they are defined.  This can be
9757significant if two iterators are used in a construct that requires
9758substitutions.  @xref{Substitutions}.
9759
9760@node Substitutions
9761@subsubsection Substitution in Mode Iterators
9762@findex define_mode_attr
9763
9764If an @file{.md} file construct uses mode iterators, each version of the
9765construct will often need slightly different strings or modes.  For
9766example:
9767
9768@itemize @bullet
9769@item
9770When a @code{define_expand} defines several @code{add@var{m}3} patterns
9771(@pxref{Standard Names}), each expander will need to use the
9772appropriate mode name for @var{m}.
9773
9774@item
9775When a @code{define_insn} defines several instruction patterns,
9776each instruction will often use a different assembler mnemonic.
9777
9778@item
9779When a @code{define_insn} requires operands with different modes,
9780using an iterator for one of the operand modes usually requires a specific
9781mode for the other operand(s).
9782@end itemize
9783
9784GCC supports such variations through a system of ``mode attributes''.
9785There are two standard attributes: @code{mode}, which is the name of
9786the mode in lower case, and @code{MODE}, which is the same thing in
9787upper case.  You can define other attributes using:
9788
9789@smallexample
9790(define_mode_attr @var{name} [(@var{mode1} "@var{value1}") @dots{} (@var{moden} "@var{valuen}")])
9791@end smallexample
9792
9793where @var{name} is the name of the attribute and @var{valuei}
9794is the value associated with @var{modei}.
9795
9796When GCC replaces some @var{:iterator} with @var{:mode}, it will scan
9797each string and mode in the pattern for sequences of the form
9798@code{<@var{iterator}:@var{attr}>}, where @var{attr} is the name of a
9799mode attribute.  If the attribute is defined for @var{mode}, the whole
9800@code{<@dots{}>} sequence will be replaced by the appropriate attribute
9801value.
9802
9803For example, suppose an @file{.md} file has:
9804
9805@smallexample
9806(define_mode_iterator P [(SI "Pmode == SImode") (DI "Pmode == DImode")])
9807(define_mode_attr load [(SI "lw") (DI "ld")])
9808@end smallexample
9809
9810If one of the patterns that uses @code{:P} contains the string
9811@code{"<P:load>\t%0,%1"}, the @code{SI} version of that pattern
9812will use @code{"lw\t%0,%1"} and the @code{DI} version will use
9813@code{"ld\t%0,%1"}.
9814
9815Here is an example of using an attribute for a mode:
9816
9817@smallexample
9818(define_mode_iterator LONG [SI DI])
9819(define_mode_attr SHORT [(SI "HI") (DI "SI")])
9820(define_insn @dots{}
9821  (sign_extend:LONG (match_operand:<LONG:SHORT> @dots{})) @dots{})
9822@end smallexample
9823
9824The @code{@var{iterator}:} prefix may be omitted, in which case the
9825substitution will be attempted for every iterator expansion.
9826
9827@node Examples
9828@subsubsection Mode Iterator Examples
9829
9830Here is an example from the MIPS port.  It defines the following
9831modes and attributes (among others):
9832
9833@smallexample
9834(define_mode_iterator GPR [SI (DI "TARGET_64BIT")])
9835(define_mode_attr d [(SI "") (DI "d")])
9836@end smallexample
9837
9838and uses the following template to define both @code{subsi3}
9839and @code{subdi3}:
9840
9841@smallexample
9842(define_insn "sub<mode>3"
9843  [(set (match_operand:GPR 0 "register_operand" "=d")
9844        (minus:GPR (match_operand:GPR 1 "register_operand" "d")
9845                   (match_operand:GPR 2 "register_operand" "d")))]
9846  ""
9847  "<d>subu\t%0,%1,%2"
9848  [(set_attr "type" "arith")
9849   (set_attr "mode" "<MODE>")])
9850@end smallexample
9851
9852This is exactly equivalent to:
9853
9854@smallexample
9855(define_insn "subsi3"
9856  [(set (match_operand:SI 0 "register_operand" "=d")
9857        (minus:SI (match_operand:SI 1 "register_operand" "d")
9858                  (match_operand:SI 2 "register_operand" "d")))]
9859  ""
9860  "subu\t%0,%1,%2"
9861  [(set_attr "type" "arith")
9862   (set_attr "mode" "SI")])
9863
9864(define_insn "subdi3"
9865  [(set (match_operand:DI 0 "register_operand" "=d")
9866        (minus:DI (match_operand:DI 1 "register_operand" "d")
9867                  (match_operand:DI 2 "register_operand" "d")))]
9868  ""
9869  "dsubu\t%0,%1,%2"
9870  [(set_attr "type" "arith")
9871   (set_attr "mode" "DI")])
9872@end smallexample
9873
9874@node Code Iterators
9875@subsection Code Iterators
9876@cindex code iterators in @file{.md} files
9877@findex define_code_iterator
9878@findex define_code_attr
9879
9880Code iterators operate in a similar way to mode iterators.  @xref{Mode Iterators}.
9881
9882The construct:
9883
9884@smallexample
9885(define_code_iterator @var{name} [(@var{code1} "@var{cond1}") @dots{} (@var{coden} "@var{condn}")])
9886@end smallexample
9887
9888defines a pseudo rtx code @var{name} that can be instantiated as
9889@var{codei} if condition @var{condi} is true.  Each @var{codei}
9890must have the same rtx format.  @xref{RTL Classes}.
9891
9892As with mode iterators, each pattern that uses @var{name} will be
9893expanded @var{n} times, once with all uses of @var{name} replaced by
9894@var{code1}, once with all uses replaced by @var{code2}, and so on.
9895@xref{Defining Mode Iterators}.
9896
9897It is possible to define attributes for codes as well as for modes.
9898There are two standard code attributes: @code{code}, the name of the
9899code in lower case, and @code{CODE}, the name of the code in upper case.
9900Other attributes are defined using:
9901
9902@smallexample
9903(define_code_attr @var{name} [(@var{code1} "@var{value1}") @dots{} (@var{coden} "@var{valuen}")])
9904@end smallexample
9905
9906Here's an example of code iterators in action, taken from the MIPS port:
9907
9908@smallexample
9909(define_code_iterator any_cond [unordered ordered unlt unge uneq ltgt unle ungt
9910                                eq ne gt ge lt le gtu geu ltu leu])
9911
9912(define_expand "b<code>"
9913  [(set (pc)
9914        (if_then_else (any_cond:CC (cc0)
9915                                   (const_int 0))
9916                      (label_ref (match_operand 0 ""))
9917                      (pc)))]
9918  ""
9919@{
9920  gen_conditional_branch (operands, <CODE>);
9921  DONE;
9922@})
9923@end smallexample
9924
9925This is equivalent to:
9926
9927@smallexample
9928(define_expand "bunordered"
9929  [(set (pc)
9930        (if_then_else (unordered:CC (cc0)
9931                                    (const_int 0))
9932                      (label_ref (match_operand 0 ""))
9933                      (pc)))]
9934  ""
9935@{
9936  gen_conditional_branch (operands, UNORDERED);
9937  DONE;
9938@})
9939
9940(define_expand "bordered"
9941  [(set (pc)
9942        (if_then_else (ordered:CC (cc0)
9943                                  (const_int 0))
9944                      (label_ref (match_operand 0 ""))
9945                      (pc)))]
9946  ""
9947@{
9948  gen_conditional_branch (operands, ORDERED);
9949  DONE;
9950@})
9951
9952@dots{}
9953@end smallexample
9954
9955@node Int Iterators
9956@subsection Int Iterators
9957@cindex int iterators in @file{.md} files
9958@findex define_int_iterator
9959@findex define_int_attr
9960
9961Int iterators operate in a similar way to code iterators.  @xref{Code Iterators}.
9962
9963The construct:
9964
9965@smallexample
9966(define_int_iterator @var{name} [(@var{int1} "@var{cond1}") @dots{} (@var{intn} "@var{condn}")])
9967@end smallexample
9968
9969defines a pseudo integer constant @var{name} that can be instantiated as
9970@var{inti} if condition @var{condi} is true.  Each @var{int}
9971must have the same rtx format.  @xref{RTL Classes}. Int iterators can appear
9972in only those rtx fields that have 'i' as the specifier. This means that
9973each @var{int} has to be a constant defined using define_constant or
9974define_c_enum.
9975
9976As with mode and code iterators, each pattern that uses @var{name} will be
9977expanded @var{n} times, once with all uses of @var{name} replaced by
9978@var{int1}, once with all uses replaced by @var{int2}, and so on.
9979@xref{Defining Mode Iterators}.
9980
9981It is possible to define attributes for ints as well as for codes and modes.
9982Attributes are defined using:
9983
9984@smallexample
9985(define_int_attr @var{name} [(@var{int1} "@var{value1}") @dots{} (@var{intn} "@var{valuen}")])
9986@end smallexample
9987
9988Here's an example of int iterators in action, taken from the ARM port:
9989
9990@smallexample
9991(define_int_iterator QABSNEG [UNSPEC_VQABS UNSPEC_VQNEG])
9992
9993(define_int_attr absneg [(UNSPEC_VQABS "abs") (UNSPEC_VQNEG "neg")])
9994
9995(define_insn "neon_vq<absneg><mode>"
9996  [(set (match_operand:VDQIW 0 "s_register_operand" "=w")
9997	(unspec:VDQIW [(match_operand:VDQIW 1 "s_register_operand" "w")
9998		       (match_operand:SI 2 "immediate_operand" "i")]
9999		      QABSNEG))]
10000  "TARGET_NEON"
10001  "vq<absneg>.<V_s_elem>\t%<V_reg>0, %<V_reg>1"
10002  [(set_attr "type" "neon_vqneg_vqabs")]
10003)
10004
10005@end smallexample
10006
10007This is equivalent to:
10008
10009@smallexample
10010(define_insn "neon_vqabs<mode>"
10011  [(set (match_operand:VDQIW 0 "s_register_operand" "=w")
10012	(unspec:VDQIW [(match_operand:VDQIW 1 "s_register_operand" "w")
10013		       (match_operand:SI 2 "immediate_operand" "i")]
10014		      UNSPEC_VQABS))]
10015  "TARGET_NEON"
10016  "vqabs.<V_s_elem>\t%<V_reg>0, %<V_reg>1"
10017  [(set_attr "type" "neon_vqneg_vqabs")]
10018)
10019
10020(define_insn "neon_vqneg<mode>"
10021  [(set (match_operand:VDQIW 0 "s_register_operand" "=w")
10022	(unspec:VDQIW [(match_operand:VDQIW 1 "s_register_operand" "w")
10023		       (match_operand:SI 2 "immediate_operand" "i")]
10024		      UNSPEC_VQNEG))]
10025  "TARGET_NEON"
10026  "vqneg.<V_s_elem>\t%<V_reg>0, %<V_reg>1"
10027  [(set_attr "type" "neon_vqneg_vqabs")]
10028)
10029
10030@end smallexample
10031
10032@node Subst Iterators
10033@subsection Subst Iterators
10034@cindex subst iterators in @file{.md} files
10035@findex define_subst
10036@findex define_subst_attr
10037
10038Subst iterators are special type of iterators with the following
10039restrictions: they could not be declared explicitly, they always have
10040only two values, and they do not have explicit dedicated name.
10041Subst-iterators are triggered only when corresponding subst-attribute is
10042used in RTL-pattern.
10043
10044Subst iterators transform templates in the following way: the templates
10045are duplicated, the subst-attributes in these templates are replaced
10046with the corresponding values, and a new attribute is implicitly added
10047to the given @code{define_insn}/@code{define_expand}.  The name of the
10048added attribute matches the name of @code{define_subst}.  Such
10049attributes are declared implicitly, and it is not allowed to have a
10050@code{define_attr} named as a @code{define_subst}.
10051
10052Each subst iterator is linked to a @code{define_subst}.  It is declared
10053implicitly by the first appearance of the corresponding
10054@code{define_subst_attr}, and it is not allowed to define it explicitly.
10055
10056Declarations of subst-attributes have the following syntax:
10057
10058@findex define_subst_attr
10059@smallexample
10060(define_subst_attr "@var{name}"
10061  "@var{subst-name}"
10062  "@var{no-subst-value}"
10063  "@var{subst-applied-value}")
10064@end smallexample
10065
10066@var{name} is a string with which the given subst-attribute could be
10067referred to.
10068
10069@var{subst-name} shows which @code{define_subst} should be applied to an
10070RTL-template if the given subst-attribute is present in the
10071RTL-template.
10072
10073@var{no-subst-value} is a value with which subst-attribute would be
10074replaced in the first copy of the original RTL-template.
10075
10076@var{subst-applied-value} is a value with which subst-attribute would be
10077replaced in the second copy of the original RTL-template.
10078
10079@end ifset
10080