1# ARMv7 Instruction Encodings
2#
3# This table is derived from the "ARM Architecture Reference Manual, ARMv7-A
4# and ARMv7-R edition" and is used here with the permission of ARM Limited.
5# Reproduction for purposes other than the development and distribution of
6# Native Client may require the explicit permission of ARM Limited.
7
8# This file defines the Native Client "instruction classes" assigned to every
9# possible ARMv7 instruction encoding.  It is organized into a series of tables,
10# and directly parallels the ARM Architecture Reference Manual cited above.
11#
12# Each table consists of
13# - A name,
14# - A citation in the Architecture Reference Manual,
15# - One or more columns defining bitfields to match, and
16# - One or more rows describing patterns in those bitfields.
17#
18# A leading tilde (~) negates a pattern.  A hyphen (-) is short for a string of
19# don't-care bits (x).  A double-quote (") indicates that a pattern is the same
20# as the row above it.
21#
22# Each row may specify a terminal instruction class ("=InstClass"), or forward
23# the reader to a different table ("->table_name").
24#
25# If an encoding is not valid in every ARM architecture rev, the instruction
26# class may indicate the rev or feature that makes the encoding valid in
27# parentheses.
28#
29# See dgen_input.py for more information on formatting "=InstClass".
30#
31# Patterns are sequences of 32 characters as follows:
32#   '1' - Bit must be value 1.
33#   '0' - Bit must be value 0.
34#   'cccc' - Bits defining condition.
35#   'dddd' - Bits defining register Rd.
36#   'ii...i' - Bits defining an immediate value.
37#   'II...I' - Bits defining an immediate value (test sampling only).
38#   'mmmm' - Bits defining register Rm.
39#   'nnnn' - Bits defining register Rn.
40#   'ssss' - Bits defining register Rs.
41#   'tttt' - Bits defining register Rt.
42#   'tt'   - Bits defining the shift type (for register operations).
43#   'u'    - Bit(20) defining whether register flags is updated (deprecated)
44#   's'    - Bit(20) defining whether register flags is updated.
45#   'w'    - Bit(21) defining writes flag.
46#   'r'    - Bit(22) defining if SPSR register is read.
47#   'd'    - Bit(23) Direction (add vs subtract) of offset. (deprecated)
48#   'u'    - Bit(23) Direction (add vs subtract) of offset.
49#   'p'    - Bit(24) defining if pre-indexing should be used.
50
51##############################################################
52# The following define common entries for each (action) row.
53#
54# base: The register used as the base for the effective address
55#       for reads and writes.
56# clears_bits: True implies that the masked bits are cleared.
57#       (defaults to false). Corresponds to virtual
58#       clears_bits. Assumes clears_mask() returns the mask to
59#       check against.
60# defs: The set of registers defined. (missing implies {}).
61# dynamic_code_replace_immediates: The set of immediate fields that
62#      should be zeroed out, when generating the dynamic code
63#      replacement sentinel. Corresponds to virtual
64#      dynamic_code_replacement_sentinel.
65# small_imm_base_wb: True if a small immediate is written back to the
66#       base register (missing implies false).
67# is_literal_load: Checks whether the instruction is a PC-relative
68#       load plus immediate.
69# is_literal_pool_head: Checks whether the instruction is a special
70#       bit sequence that marks the start of a literal pool.
71# is_load_tp: Checks if r9 is used to load a thread pointer (missing
72#       implies false).
73# relative: Defines if the instruction is a direct relative
74#       branch (R15 + constant offset). (missing implies false.)
75# relative_offset: Defines the constant offset used in a direct
76#       relative branch.
77# safety: How safety is defined for the class (missing implies true).
78# sets_Z_if_clear_bits: Defines the register that is tested if bits
79#       have been cleared. Corresponds to defining virtual
80#       sets_Z_if_clear_bits. Assumes clears_mask() returns the mask
81#       to check against, and test_register() returns the expected
82#       register that was used to set the Z bits.
83# target: The register use to compute an indirect branch,
84#       if defined (defaults to None).
85# uses: The set of registers  used. (missing implies {})
86##############################################################
87
88##############################################################
89# It should be noted that one can define a local dictionary at
90# the top of each table. The dictionary enties are prefixed by
91# "*n" which defines entry n. Each entry can be an action template.
92# These templates can then be referred to in actual rows by using
93# a "*n" in place of the action. When this is done, the action
94# inherits the corresponding action from the table's local dictionary.
95# Following the "*n" in the row, you can define additional fields.
96# If the fields were defined in the table local dictionary, it
97# overrides the field in the template.
98##############################################################
99
100##############################################################
101# Special actions needed by the validator.
102##############################################################
103
104*Nop
105  defs := {};
106  uses := {};
107
108*Deprecated *Nop
109  safety := true => DEPRECATED;
110
111*Forbidden *Nop
112  safety := true => FORBIDDEN;
113
114*Undefined *Nop
115  safety := true => UNDEFINED;
116
117*Unpredictable *Nop
118  safety := true => UNPREDICTABLE;
119
120*NotImplemented *Nop
121  # Used when instruction is not defined by any table entries.
122  safety := true => NOT_IMPLEMENTED;
123  rule := NOT_IMPLEMENTED;
124
125*FictitiousFirst *Nop
126  # Used to process the fictitious instruction before the "first" instruction
127  # in the code segment. The contents of this fictitious instruction is defined
128  # by macro src/include/arm_sandbox.h:NACL_INSTR_ARM_FAIL_VALIDATION
129  safety := true => FORBIDDEN;
130  rule := FICTITIOUS_FIRST;
131
132##############################################################
133# The following define decoder tables.
134##############################################################
135
136+-- ARMv7 (See Section A5.1)
137| cond(31:28) op1(27:25) op(4)
138| ~1111       00x        -     ->data_processing_and_miscellaneous_instructions
139| "           010        -     ->load_store_word_and_unsigned_byte
140| "           011        0     ->load_store_word_and_unsigned_byte
141| "           "          1     ->media_instructions
142| "           10x        -     ->branch_branch_with_link_and_block_data_transfer
143| "           11x        -     ->coprocessor_instructions_and_supervisor_call
144| 1111        -          -     ->unconditional_instructions
145+--
146
147+-- data_processing_and_miscellaneous_instructions (See Section A5.2)
148*mov
149  { cond(31:28), S(20), imm4(19:16), Rd(15:12), imm12(11:0) }
150  imm := imm4:imm12;
151  safety := Rd=1111 => UNPREDICTABLE;
152  defs := { Rd , NZCV if S else None };
153  uses := {};
154  dynamic_code_replace_immediates := {imm4, imm12};
155  arch := v6T2;
156+--
157| op(25) op1(24:20) op2(7:4)
158| 0      ~10xx0     xxx0     ->data_processing_register
159| "      "          0xx1     ->data_processing_register_shifted_register
160| "      10xx0      0xxx     ->miscellaneous_instructions
161| "      "          1xx0     ->halfword_multiply_and_multiply_accumulate
162| "      0xxxx      1001     ->multiply_and_multiply_accumulate
163| "      1xxxx      1001     ->synchronization_primitives
164| "      ~0xx1x     1011     ->extra_load_store_instructions
165| "      "          11x1     "
166| "      0xx1x      1011     = *Forbidden
167                               pattern := cccc0000xx1xxxxxxxxxxxxx1xx1xxxx;
168                               rule := extra_load_store_instructions_unpriviledged;
169| "      "          11x1     "
170| 1      ~10xx0     -        ->data_processing_immediate
171| "      10000      -        = *mov
172                                pattern := cccc00110000iiiiddddiiiiiiiiiiii;
173                                rule := MOVW;
174| "      10100      -        = *mov
175                                pattern := cccc00110100iiiiddddiiiiiiiiiiii;
176                                rule := MOVT;
177| "      10x10      -        ->msr_immediate_and_hints
178+--
179
180+-- data_processing_register (See Section A5.2.1)
181*RdRm
182   { cond(31:28), S(20), Rd(15:12), Rm(3:0) }
183   defs := { Rd , NZCV if S else None };
184   safety := (Rd=1111 & S=1) => DECODER_ERROR &  # ARM
185             Rd=1111 => FORBIDDEN_OPERANDS;  # NaCl
186   uses := { Rm };
187*RdRmSh *RdRm
188   { cond(31:28), S(20), Rd(15:12), imm5(11:7), type(6:5), Rm(3:0) }
189   shift := DecodeImmShift(type, imm5);
190*RnRmShTst
191   { cond(31:28), S(20), Rn(19:16), imm5(11:7), type(6:5), Rm(3:0) }
192   shift := DecodeImmShift(type, imm5);
193   defs := { NZCV if S else None };
194   uses := { Rn , Rm };
195*RdRmShInz *RdRmSh
196   safety := (Rd=1111 & S=1) => DECODER_ERROR &  # ARM
197             imm5=00000 => DECODER_ERROR &
198             Rd=1111 => FORBIDDEN_OPERANDS;      # NaCl
199*RdRnRmSh *RdRmSh
200   { cond(31:28), S(20), Rn(19:16), Rd(15:12), imm5(11:7), type(6:5), Rm(3:0) }
201   uses := { Rn , Rm };
202+--
203| op1(24:20) op2(11:7) op3(6:5)
204| 0000x      -         -        = *RdRnRmSh
205                                  pattern := cccc0000000snnnnddddiiiiitt0mmmm;
206                                  rule := AND_register;
207| 0001x      -         -        = *RdRnRmSh
208                                  pattern := cccc0000001snnnnddddiiiiitt0mmmm;
209                                  rule := EOR_register;
210| 0010x      -         -        = *RdRnRmSh
211                                   pattern := cccc0000010snnnnddddiiiiitt0mmmm;
212# Note: For arm, the case where Rn=SP is NOT a special case (only in thumb2).
213# Hence, this parse restriction does not apply (See SUB (SP minus register)).
214                                  rule := SUB_register;
215| 0011x      -         -        = *RdRnRmSh
216                                   pattern := cccc0000011snnnnddddiiiiitt0mmmm;
217                                   rule := RSB_register;
218| 0100x      -         -        = *RdRnRmSh
219                                   pattern := cccc0000100snnnnddddiiiiitt0mmmm;
220# Note: For arm, the case where Rn=SP is NOT a special case (only in thumb2).
221# Hence, this parse restriction does not apply (See ADD (SP plus register)).
222                                   rule := ADD_register;
223| 0101x      -         -        = *RdRnRmSh
224                                   pattern := cccc0000101snnnnddddiiiiitt0mmmm;
225                                   rule := ADC_register;
226| 0110x      -         -        = *RdRnRmSh
227                                   pattern := cccc0000110snnnnddddiiiiitt0mmmm;
228                                   rule := SBC_register;
229| 0111x      -         -        = *RdRnRmSh
230                                   pattern := cccc0000111snnnnddddiiiiitt0mmmm;
231                                   rule := RSC_register;
232| 10001      -         -        = *RnRmShTst
233                                   pattern := cccc00010001nnnn0000iiiiitt0mmmm;
234                                   rule := TST_register;
235| 10011      -         -        = *RnRmShTst
236                                   pattern := cccc00010011nnnn0000iiiiitt0mmmm;
237                                   rule := TEQ_register;
238| 10101      -         -        = *RnRmShTst
239                                   pattern := cccc00010101nnnn0000iiiiitt0mmmm;
240                                   rule := CMP_register;
241| 10111      -         -        = *RnRmShTst
242                                   pattern := cccc00010111nnnn0000iiiiitt0mmmm;
243                                   rule := CMN_register;
244# TODO(jfb) op==10xx0 should be unreachable from here:
245#           the previous table should handle it.
246| 1100x      -         -        = *RdRnRmSh
247                                   pattern := cccc0001100snnnnddddiiiiitt0mmmm;
248                                   rule := ORR_register;
249| 1101x      00000     00       = *RdRm
250                                   pattern := cccc0001101s0000dddd00000000mmmm;
251                                   rule := MOV_register;
252| "          ~00000    00       = *RdRmShInz
253                                   pattern := cccc0001101s0000ddddiiiii000mmmm;
254                                   rule := LSL_immediate;
255| "          -         01       = *RdRmSh
256                                   pattern := cccc0001101s0000ddddiiiii010mmmm;
257                                   rule := LSR_immediate;
258| "          -         10       = *RdRmSh
259                                   pattern := cccc0001101s0000ddddiiiii100mmmm;
260                                   rule := ASR_immediate;
261| "          00000     11       = *RdRm
262                                   pattern := cccc0001101s0000dddd00000110mmmm;
263                                   rule := RRX;
264| "          ~00000    11       = *RdRmShInz
265                                   pattern := cccc0001101s0000ddddiiiii110mmmm;
266                                   rule := ROR_immediate;
267| 1110x      -         -        = *RdRnRmSh
268                                   pattern := cccc0001110snnnnddddiiiiitt0mmmm;
269                                   rule := BIC_register;
270| 1111x      -         -        = *RdRmSh
271                                   pattern := cccc0001111s0000ddddiiiiitt0mmmm;
272                                   rule := MVN_register;
273+--
274
275+-- data_processing_register_shifted_register (See Section A5.2.2)
276*RdRsRm
277   { cond(31:28), S(20), Rd(15:12), Rs(11:8), type(6:5), Rm(3:0) }
278   setflags := S=1; shift_t := DecodeRegShift(type);
279   defs := {Rd, NZCV if setflags else None};
280   safety := Pc in {Rd, Rm, Rs} => UNPREDICTABLE;
281   uses := {Rm, Rs};
282*RnRdRsRm *RdRsRm
283   { cond(31:28), S(20), Rn(19:16), Rd(15:12), Rs(11:8), type(6:5), Rm(3:0) }
284   safety := Pc in {Rn, Rd, Rm, Rs} => UNPREDICTABLE;
285   uses := {Rn, Rm, Rs};
286*RnRsRm
287   { cond(31:28), Rn(19:16), Rs(11:8), type(6:5), Rm(3:0) }
288   shift_t := DecodeRegShift(type);
289   defs := {NZCV};  # S(20)=1
290   safety := Pc in {Rn, Rm, Rs} => UNPREDICTABLE;
291   uses := {Rn, Rm, Rs};
292*RdRmRn
293   { cond(31:28), S(20), Rd(15:12), Rm(11:8), Rn(3:0) }
294   setflags := S=1;
295   defs := {Rd, NZCV if setflags else None};
296   safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
297   uses := {Rn, Rm};
298+--
299| op1(24:20) op2(6:5)
300| 0000x      -        = *RnRdRsRm
301                         pattern := cccc0000000snnnnddddssss0tt1mmmm;
302                         rule := AND_register_shifted_register;
303| 0001x      -        = *RnRdRsRm
304                         pattern := cccc0000001snnnnddddssss0tt1mmmm;
305                         rule := EOR_register_shifted_register;
306| 0010x      -        = *RnRdRsRm
307                         pattern := cccc0000010snnnnddddssss0tt1mmmm;
308                        rule := SUB_register_shifted_register;
309| 0011x      -        = *RnRdRsRm
310                         pattern := cccc0000011snnnnddddssss0tt1mmmm;
311                         rule := RSB_register_shfited_register;
312| 0100x      -        = *RnRdRsRm
313                         pattern := cccc0000100snnnnddddssss0tt1mmmm;
314                         rule := ADD_register_shifted_register;
315| 0101x      -        = *RnRdRsRm
316                         pattern := cccc0000101snnnnddddssss0tt1mmmm;
317                         rule := ADC_register_shifted_register;
318| 0110x      -        = *RnRdRsRm
319                         pattern := cccc0000110snnnnddddssss0tt1mmmm;
320                         rule := SBC_register_shifted_register;
321| 0111x      -        = *RnRdRsRm
322                         pattern := cccc0000111snnnnddddssss0tt1mmmm;
323                         rule := RSC_register_shifted_register;
324# TODO(jfb) op==10xx0 should be unreachable from here:
325#           the previous table should handle it.
326| 10001      -        = *RnRsRm
327                         pattern := cccc00010001nnnn0000ssss0tt1mmmm;
328                         rule := TST_register_shifted_register;
329| 10011      -        = *RnRsRm
330                         pattern := cccc00010011nnnn0000ssss0tt1mmmm;
331                         rule := TEQ_register_shifted_register;
332| 10101      -        = *RnRsRm
333                         pattern := cccc00010101nnnn0000ssss0tt1mmmm;
334                         rule := CMP_register_shifted_register;
335| 10111      -        = *RnRsRm
336                         pattern := cccc00010111nnnn0000ssss0tt1mmmm;
337                         rule := CMN_register_shifted_register;
338| 1100x      -        = *RnRdRsRm
339                         pattern := cccc0001100snnnnddddssss0tt1mmmm;
340                         rule := ORR_register_shifted_register;
341| 1101x      00       = *RdRmRn
342                         pattern := cccc0001101s0000ddddmmmm0001nnnn;
343                         rule := LSL_register;
344| "          01       = *RdRmRn
345                         pattern := cccc0001101s0000ddddmmmm0011nnnn;
346                         rule := LSR_register;
347| "          10       = *RdRmRn
348                         pattern := cccc0001101s0000ddddmmmm0101nnnn;
349                         rule := ASR_register;
350| "          11       = *RdRmRn
351                         pattern := cccc0001101s0000ddddmmmm0111nnnn;
352                         rule := ROR_register;
353| 1110x      -        = *RnRdRsRm
354                         pattern := cccc0001110snnnnddddssss0tt1mmmm;
355                         rule := BIC_register_shifted_register;
356| 1111x      -        = *RdRsRm
357                         pattern := cccc0001111s0000ddddssss0tt1mmmm;
358                         rule := MVN_register_shifted_register;
359+--
360
361+-- data_processing_immediate (See Section A5.2.3)
362# Note: The two interesting instructions in this set are
363# TestIfAddressMasked and MaskAddress. These two instructions are the
364# ones that we allow testing/setting of bits to mask data addresses
365# appropriately.
366*U1R_12
367   { cond(31:28), S(20), Rd(15:12), imm12(11:0) }
368   setflags := S=1; imm32 := ARMExpandImm(imm12);
369   defs := {Rd, NZCV if setflags else None};
370   uses := {};
371   safety := (Rd=1111 & S=1) => DECODER_ERROR &
372             Rd=1111 => FORBIDDEN_OPERANDS;
373*U1R_12_DCR *U1R_12
374   dynamic_code_replace_immediates := {imm12};
375*B2R *U1R_12
376   { cond(31:28), S(20), Rn(19:16), Rd(15:12), imm12(11:0) }
377   uses := {Rn};
378*B2R_MASK *B2R
379   clears_bits := (imm32 & clears_mask()) == clears_mask();
380*B2R_DCR *B2R
381   dynamic_code_replace_immediates := {imm12};
382*B2R_ADDSUB *B2R
383   # Note: This is a variant of *B2R instructions, that is used
384   # to define add and subtract, and have additional decoding error
385   # safety checks.
386   safety := (Rd=1111 & S=1) => DECODER_ERROR &
387             (Rn=1111 & S=0) => DECODER_ERROR &
388             Rd=1111 => FORBIDDEN_OPERANDS;
389*TEST
390   { cond(31:28), Rn(19:16), imm12(11:0) }
391   imm32 := ARMExpandImm_C(imm12);
392   defs := {NZCV};
393   uses := {Rn};
394*TEST_MASK *TEST
395   sets_Z_if_clear_bits :=
396     Rn == RegIndex(test_register()) &
397     (imm32 & clears_mask()) == clears_mask();
398*U1R_PC
399   { cond(31:28), Rd(15:12), imm12(11:0) }
400   imm32 := ARMExpandImm(imm12);
401   defs := {Rd};
402   safety := Rd=1111 => FORBIDDEN_OPERANDS;
403   uses := {Pc};
404+--
405| op(24:20) Rn(19:16)
406| 0000x      -        = *B2R
407                        pattern := cccc0010000snnnnddddiiiiiiiiiiii;
408                        rule := AND_immediate;
409| 0001x      -        = *B2R
410                        pattern := cccc0010001snnnnddddiiiiiiiiiiii;
411                        rule := EOR_immediate;
412| 0010x      ~1111    = *B2R_ADDSUB
413                        pattern := cccc0010010snnnnddddiiiiiiiiiiii;
414                        rule := SUB_immediate;
415| 0010x      1111     = *U1R_PC
416                        pattern := cccc001001001111ddddiiiiiiiiiiii;
417                        rule := ADR_A2;
418| 0011x      -        = *B2R
419                        pattern := cccc0010011snnnnddddiiiiiiiiiiii;
420                        rule := RSB_immediate;
421| 0100x      ~1111    = *B2R_ADDSUB
422                        pattern := cccc0010100snnnnddddiiiiiiiiiiii;
423                        rule := ADD_immediate;
424| 0100x      1111     = *U1R_PC
425                        pattern := cccc001010001111ddddiiiiiiiiiiii;
426                        rule := ADR_A1;
427| 0101x      -        = *B2R
428                        pattern := cccc0010101snnnnddddiiiiiiiiiiii;
429                        rule := ADC_immediate;
430| 0110x      -        = *B2R
431                        pattern := cccc0010110snnnnddddiiiiiiiiiiii;
432                        rule := SBC_immediate;
433| 0111x      -        = *B2R
434                        pattern := cccc0010111snnnnddddiiiiiiiiiiii;
435                        rule := RSC_immediate;
436# TODO(jfb) op==10xx0 should be unreachable from here:
437#           the previous table should handle it.
438| 10001      -        = *TEST_MASK
439                        pattern := cccc00110001nnnn0000iiiiiiiiiiii;
440                        rule := TST_immediate;
441| 10011      -        = *TEST
442                        pattern := cccc00110011nnnn0000iiiiiiiiiiii;
443                        rule := TEQ_immediate;
444| 10101      -        = *TEST
445                        pattern := cccc00110101nnnn0000iiiiiiiiiiii;
446                        rule := CMP_immediate;
447| 10111      -        = *TEST
448                        pattern := cccc00110111nnnn0000iiiiiiiiiiii;
449                        rule := CMN_immediate;
450| 1100x      -        = *B2R_DCR
451                        pattern := cccc0011100snnnnddddiiiiiiiiiiii;
452                        rule := ORR_immediate;
453| 1101x      -        = *U1R_12_DCR
454                        pattern := cccc0011101s0000ddddiiiiiiiiiiii;
455                        rule := MOV_immediate_A1;
456| 1110x      -        = *B2R_MASK
457                        pattern := cccc0011110snnnnddddiiiiiiiiiiii;
458                        rule := BIC_immediate;
459| 1111x      -        = *U1R_12_DCR
460                        pattern := cccc0011111s0000ddddiiiiiiiiiiii;
461                        rule := MVN_immediate;
462+--
463
464+-- multiply_and_multiply_accumulate (See Section A5.2.5)
465*MUL
466   { cond(31:28), S(20), Rd(19:16), Rm(11:8), Rn(3:0) }
467   setflags := S=1;
468   defs := {Rd, NZCV if setflags else None};
469   safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE &
470             (ArchVersion() < 6 & Rd == Rn) => UNPREDICTABLE;
471   uses := {Rm, Rn};
472*MLS
473   { cond(31:28), Rd(19:16), Ra(15:12), Rm(11:8), Rn(3:0) }
474   defs := {Rd};
475   safety := Pc in {Rd, Rn, Rm, Ra} => UNPREDICTABLE;
476   uses := {Rn, Rm, Ra};
477   arch := v6T2;
478*MLA
479   { cond(31:28), S(20), Rd(19:16), Ra(15:12), Rm(11:8), Rn(3:0) }
480   setflags := S=1;
481   defs := {Rd, NZCV if setflags else None};
482   safety := Pc in {Rd, Rn, Rm, Ra} => UNPREDICTABLE &
483             (ArchVersion() < 6 & Rd == Rn) => UNPREDICTABLE;
484   uses := {Rn, Rm, Ra};
485*UMAAL
486   { cond(31:28), RdHi(19:16), RdLo(15:12), Rm(11:8), Rn(3:0) }
487   defs := {RdLo, RdHi};
488   safety := Pc in {RdLo, RdHi, Rn, Rm} => UNPREDICTABLE &
489             RdHi == RdLo => UNPREDICTABLE;
490   uses := {RdLo, RdHi, Rn, Rm};
491*MULL
492   { cond(31:28), S(20), RdHi(19:16), RdLo(15:12), Rm(11:8), Rn(3:0) }
493   setflags := S=1;
494   defs := {RdLo, RdHi, NZCV if setflags else None};
495   safety := Pc in {RdLo, RdHi, Rn, Rm} => UNPREDICTABLE &
496             RdHi == RdLo => UNPREDICTABLE &
497             (ArchVersion() < 6 & (RdHi == Rn | RdLo == Rn)) => UNPREDICTABLE;
498   uses := {Rn, Rm};
499*MLAL
500   { cond(31:28), S(20), RdHi(19:16), RdLo(15:12), Rm(11:8), Rn(3:0) }
501   setflags := S=1;
502   defs := {RdLo, RdHi, NZCV if setflags else None};
503   safety := Pc in {RdLo, RdHi, Rn, Rm} => UNPREDICTABLE &
504             RdHi == RdLo => UNPREDICTABLE &
505             (ArchVersion() < 6 & (RdHi == Rn | RdLo == Rn)) => UNPREDICTABLE;
506   uses := {RdLo, RdHi, Rn, Rm};
507+--
508| op(23:20)
509| 000x      = *MUL
510              pattern := cccc0000000sdddd0000mmmm1001nnnn;
511              rule := MUL_A1;
512| 001x      = *MLA
513              pattern := cccc0000001sddddaaaammmm1001nnnn;
514              rule := MLA_A1;
515| 0100      = *UMAAL
516              pattern := cccc00000100hhhhllllmmmm1001nnnn;
517              rule := UMAAL_A1;
518| 0101      = *Undefined  # No rule defined in table.
519              pattern := cccc00000101xxxxxxxxxxxx1001xxxx;
520| 0110      = *MLS
521              pattern := cccc00000110ddddaaaammmm1001nnnn;
522              rule := MLS_A1;
523| 0111      = *Undefined  # No rule defined in table.
524              pattern := cccc00000111xxxxxxxxxxxx1001xxxx;
525| 100x      = *MULL
526              pattern := cccc0000100shhhhllllmmmm1001nnnn;
527              rule := UMULL_A1;
528| 101x      = *MLAL
529              pattern := cccc0000101shhhhllllmmmm1001nnnn;
530              rule := UMLAL_A1;
531| 110x      = *MULL
532              pattern := cccc0000110shhhhllllmmmm1001nnnn;
533              rule := SMULL_A1;
534| 111x      = *MLAL
535              pattern := cccc0000111shhhhllllmmmm1001nnnn;
536              rule := SMLAL_A1;
537+--
538
539# None of the instructions in the following table set NZCV flags,
540# they only set the APSR's sticky Q bit (for saturation), but we
541# don't model it.
542+-- saturating_addition_and_subtraction (See Section A5.2.6)
543*RdRmRn
544   { Cond(31:28), Rn(19:16), Rd(15:12), Rm(3:0) }
545   defs := {Rd};
546   safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
547   uses := {Rn, Rm};
548   arch := v5TE;
549+--
550| op(22:21)
551| 00        = *RdRmRn
552               pattern := cccc00010000nnnndddd00000101mmmm;
553               rule := QADD;
554| 01        = *RdRmRn
555               pattern := cccc00010010nnnndddd00000101mmmm;
556               rule := QSUB;
557| 10        = *RdRmRn
558               pattern := cccc00010100nnnndddd00000101mmmm;
559               rule := QDADD;
560| 11        = *RdRmRn
561               pattern := cccc00010110nnnndddd00000101mmmm;
562               rule := QDSUB;
563+--
564
565+-- halfword_multiply_and_multiply_accumulate (See Section A5.2.7)
566*RdRnRm
567   {cond(31:28), Rd(19:16), Rm(11:8), M(6), N(5), Rn(3:0)}
568   n_high := N=1; m_high := M=1;
569   defs := {Rd};
570   uses := {Rn, Rm};
571   safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
572   arch := v5TE;
573*RdRnRmRa *RdRnRm
574   {cond(31:28), Rd(19:16), Ra(15:12), Rm(11:8), M(6), N(5), Rn(3:0)}
575   uses := {Rn, Rm, Ra};
576   safety := Pc in {Rd, Rn, Rm, Ra} => UNPREDICTABLE;
577*RdLoHiRnRm *RdRnRm
578   {cond(31:28), RdHi(19:16), RdLo(15:12), Rm(11:8), M(6), N(5), Rn(3:0)}
579   defs := {RdLo, RdHi};
580   uses := {RdLo, RdHi, Rn, Rm};
581   safety := Pc in {RdLo, RdHi, Rn, Rm} => UNPREDICTABLE &
582             RdHi == RdLo => UNPREDICTABLE;
583+--
584| op1(22:21) op(5)
585| 00         -     = *RdRnRmRa
586                     # Implements Smlabb, Smlabt, Smlatb, and Smlatt
587                     # where the t/b bits (xx) are in bits 5:6.
588                     pattern := cccc00010000ddddaaaammmm1xx0nnnn;
589                     rule := SMLABB_SMLABT_SMLATB_SMLATT;
590| 01         0     = *RdRnRmRa
591                     # Implements Smlawb and Smlawt where the t/b (X)
592                     # bit is in bit 6.
593                     pattern := cccc00010010ddddaaaammmm1x00nnnn;
594                     rule := SMLAWB_SMLAWT;
595| 01         1     = *RdRnRm
596                     # Implements Smulwb and Smulwt where the t/b (x)
597                     # bit is in bit 6.
598                     pattern := cccc00010010dddd0000mmmm1x10nnnn;
599                     rule := SMULWB_SMULWT;
600| 10         -     = *RdLoHiRnRm
601                     # Implements Smlalbb, Smlalbt, Smlaltb, and Smlaltt
602                     # where the t/b bits (xx) are in bits 5:6.
603                     pattern := cccc00010100hhhhllllmmmm1xx0nnnn;
604                     rule := SMLALBB_SMLALBT_SMLALTB_SMLALTT;
605| 11         -     = *RdRnRm
606                     # Implements Smulbb, Smulbt, Smultb, and Smultt
607                     # where the t/b bits (xx) are in bits 5:6.
608                     pattern := cccc00010110dddd0000mmmm1xx0nnnn;
609                     rule := SMULBB_SMULBT_SMULTB_SMULTT;
610+--
611
612+-- extra_load_store_instructions (See Section A5.2.8)
613*RtImm
614  {cond(31:28), P(24), U(23), W(21), Rt(15:12), imm4H(11:8), imm4L(3:0)}
615  imm32 := ZeroExtend(imm4H:imm4L, 32);
616  add := U=1;
617*LdrRtImm *RtImm
618  # Note: There is a problem here. The ARM manual defines 'base' as follows:
619  #   base := Align(PC, 4);
620  #   address := base + imm32 if add else base - imm32;
621  # However, 'base' is used as the name of a NaCl virtual, and hence, they
622  # conflict. As a result, the above two definitions are commented out.
623  # This doesn't create a problem in that they aren't used elsewhere within
624  # the table.
625  # TODO(karl): Find a way to deal with this problem so that we can fully
626  #    specify the ARM code.
627  base := Pc;
628  defs := {Rt};
629  uses := {Pc};
630  is_literal_load := true;
631  safety := P=0 & W=1 => DECODER_ERROR &
632            P == W => UNPREDICTABLE &
633            Rt == Pc => UNPREDICTABLE;
634*LdrRtRt2Imm *LdrRtImm
635  Rt2 := Rt + 1;
636  defs := {Rt, Rt2};
637  safety := Rt(0)=1 => UNPREDICTABLE &
638            Rt2 == Pc => UNPREDICTABLE;
639  arch := v5TE;
640
641*RtRnImm *RtImm
642  {cond(31:28), P(24), U(23), W(21), Rn(19:16), Rt(15:12), imm4H(11:8), imm4L(3:0)}
643  index := P=1; wback := (P=0) | (W=1);
644  offset_addr := Rn + imm32 if add else Rn - imm32;
645  address := offset_addr if index else Rn;
646  base := Rn;
647  small_imm_base_wb := wback;
648*LdrRtRnImm *RtRnImm
649  defs := {Rt, base if wback else None};
650  uses := {Rn};
651  safety := Rn=1111 => DECODER_ERROR &
652            P=0 & W=1 => DECODER_ERROR &
653            Rt == Pc | (wback & Rn==Rt) => UNPREDICTABLE &
654            Rt == Pc => FORBIDDEN_OPERANDS;
655*LdrRtRt2RnImm *LdrRtRnImm
656  Rt2 := Rt + 1;
657  defs := {Rt, Rt2, base if wback else None};
658  safety := Rn=1111 => DECODER_ERROR &
659            Rt(0)=1 => UNPREDICTABLE &
660            P=0 & W=1 => UNPREDICTABLE &
661            wback & (Rn == Rt | Rn == Rt2) => UNPREDICTABLE &
662            Rt2 == Pc => UNPREDICTABLE;
663  arch := v5TE;
664*StrRtRnImm *RtRnImm
665  defs := {base if wback else None};
666  uses := {Rt, Rn};
667  safety := P=0 & W=1 => DECODER_ERROR &
668            Rt == Pc => UNPREDICTABLE &
669            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE;
670*StrRtRt2RnImm *StrRtRnImm
671  Rt2 := Rt + 1;
672  uses := {Rt, Rt2, Rn};
673  safety := Rt(0)=1 => UNPREDICTABLE &
674            P=0 & W=1 => UNPREDICTABLE &
675            wback & (Rn == Pc | Rn == Rt | Rn == Rt2) => UNPREDICTABLE &
676            Rt2 == Pc => UNPREDICTABLE;
677
678*RtRnRm
679  {cond(31:28), P(24), U(23), W(21), Rn(19:16), Rt(15:12), Rm(3:0) }
680  index := P=1; add := U=1; wback := (P=0) | (W=1);
681  base := Rn;
682*LdrRtRt2RnRm *RtRnRm
683  Rt2 := Rt + 1;
684  defs := {Rt, Rt2, base if wback else None};
685  uses := {Rn, Rm};
686  safety := Rt(0)=1 => UNPREDICTABLE &
687            P=0 & W=1 => UNPREDICTABLE &
688            Rt2 == Pc | Rm == Pc | Rm == Rt | Rm == Rt2 => UNPREDICTABLE &
689            wback & (Rn == Pc | Rn == Rt | Rn == Rt2) => UNPREDICTABLE &
690            ArchVersion() < 6 & wback & Rm == Rn => UNPREDICTABLE &
691            # If indexing, load is computed as the sum of two registers,
692            # which NaCl doesn't allow.
693            index => FORBIDDEN;
694  arch := v5TE;
695*StrRtRt2RnRm *RtRnRm
696  Rt2 := Rt + 1;
697  defs := {base if wback else None};
698  uses := {Rt, Rt2, Rn, Rm};
699  safety := Rt(0)=1 => UNPREDICTABLE &
700            P=0 & W=1 => UNPREDICTABLE &
701            Rt2 == Pc | Rm == Pc => UNPREDICTABLE &
702            wback & (Rn == Pc | Rn == Rt | Rn == Rt2) => UNPREDICTABLE &
703            ArchVersion() < 6 & wback & Rm == Rn => UNPREDICTABLE &
704            # If indexing, load is computed as the sum of two registers,
705            # which NaCl doesn't allow.
706            index => FORBIDDEN;
707
708*RtRnRmSh *RtRnRm
709  shift_t := SRType_LSL(); shift_n := 0;
710*LdrRtRnRmSh *RtRnRmSh
711  defs := {Rt, base if wback else None};
712  uses := {Rn, Rm};
713  safety := P=0 & W=1 => DECODER_ERROR &
714            Pc in {Rt, Rm} => UNPREDICTABLE &
715            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
716            ArchVersion() < 6 & wback & Rm == Rn => UNPREDICTABLE &
717            # If indexing, load is computed as the sum of two registers,
718            # which NaCl doesn't allow.
719            index => FORBIDDEN;
720*StrRtRnRmSh *RtRnRmSh
721  defs := {base if wback else None};
722  uses := {Rt, Rn, Rm};
723  safety := P=0 & W=1 => DECODER_ERROR &
724            Pc in {Rt, Rm} => UNPREDICTABLE &
725            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
726            ArchVersion() < 6 & wback & Rm == Rn => UNPREDICTABLE &
727            # If indexing, load is computed as the sum of two registers,
728            # which NaCl doesn't allow.
729            index => FORBIDDEN;
730+--
731| op2(6:5) op1(24:20) Rn(19:16)
732# Note the following encodings which lead to a different table and aren't
733# handled in this table.
734# TODO(jfb) Should we mark them as unreachable?
735# 00       -          -         ->data_processing_and_miscellaneous_instructions
736# -        0xx11      -         "
737# 0x       0xx10      -         "
738#
739| 01       xx0x0      -         = *StrRtRnRmSh
740                                  pattern := cccc000pu0w0nnnntttt00001011mmmm;
741                                  rule := STRH_register;
742| "        xx0x1      -         = *LdrRtRnRmSh
743                                  pattern := cccc000pu0w1nnnntttt00001011mmmm;
744                                  rule := LDRH_register;
745| "        xx1x0      -         = *StrRtRnImm
746                                  pattern := cccc000pu1w0nnnnttttiiii1011iiii;
747                                  rule := STRH_immediate;
748| "        xx1x1      ~1111     = *LdrRtRnImm
749                                  pattern := cccc000pu1w1nnnnttttiiii1011iiii;
750                                  rule := LDRH_immediate;
751| "        "          1111      = *LdrRtImm
752                                  pattern := cccc000pu1w11111ttttiiii1011iiii;
753                                  rule := LDRH_literal;
754| 10       xx0x0      -         = *LdrRtRt2RnRm
755                                  pattern := cccc000pu0w0nnnntttt00001101mmmm;
756                                  rule := LDRD_register;
757| "        xx0x1      -         = *LdrRtRnRmSh
758                                  pattern := cccc000pu0w1nnnntttt00001101mmmm;
759                                  rule := LDRSB_register;
760| "        xx1x0      ~1111     = *LdrRtRt2RnImm
761                                  pattern := cccc000pu1w0nnnnttttiiii1101iiii;
762                                  rule := LDRD_immediate;
763| "        "          1111      = *LdrRtRt2Imm
764                                  pattern := cccc0001u1001111ttttiiii1101iiii;
765                                  rule := LDRD_literal;
766| "        xx1x1      ~1111     = *LdrRtRnImm
767                                  pattern := cccc000pu1w1nnnnttttiiii1101iiii;
768                                  rule := LDRSB_immediate;
769| "        "          1111      = *LdrRtImm
770                                  pattern := cccc0001u1011111ttttiiii1101iiii;
771                                  rule := LDRSB_literal;
772| 11       xx0x0      -         = *StrRtRt2RnRm
773                                   pattern := cccc000pu0w0nnnntttt00001111mmmm;
774                                   rule := STRD_register;
775| "        xx0x1      -         = *LdrRtRnRmSh
776                                  pattern := cccc000pu0w1nnnntttt00001111mmmm;
777                                  rule := LDRSH_register;
778| "        xx1x0      -         = *StrRtRt2RnImm
779                                   pattern := cccc000pu1w0nnnnttttiiii1111iiii;
780                                   rule := STRD_immediate;
781| "        xx1x1      ~1111     = *LdrRtRnImm
782                                   pattern := cccc000pu1w1nnnnttttiiii1111iiii;
783                                   rule := LDRSH_immediate;
784| "        "          1111      = *LdrRtImm
785                                   pattern := cccc0001u1011111ttttiiii1111iiii;
786                                   rule := LDRSH_literal;
787+--
788
789# Table omitted: extra_load_store_instructions_unpriviledged (See section A5.2.9)
790
791+-- synchronization_primitives (See Section A5.2.10)
792*LdRtRn
793  { cond(31:28), Rn(19:16), Rt(15:12) }
794  imm32 := Zeros((32));
795  base := Rn;
796  defs := {Rt};
797  uses := {Rn};
798  safety := Pc in {Rt, Rn} => UNPREDICTABLE;
799*LdRtRt2Rn *LdRtRn
800  Rt2 := Rt + 1;
801  defs := {Rt, Rt2};
802  safety := Rt(0)=1 | Rt == Lr | Rn == Pc => UNPREDICTABLE;
803*StRdRtRn
804  { cond(31:28), Rn(19:16), Rd(15:12), Rt(3:0) }
805  imm32 := Zeros((32));
806  base := Rn;
807  defs := {Rd};
808  uses := {Rn, Rt};
809  safety := Pc in {Rd, Rt, Rn} => UNPREDICTABLE &
810            Rd in {Rn, Rt} => UNPREDICTABLE;
811*StRdRtRt2Rn *StRdRtRn
812  Rt2 := Rt + 1;
813  uses := {Rn, Rt, Rt2};
814  safety := Pc in {Rd, Rn} | Rt(0)=1 | Rt == Lr  => UNPREDICTABLE &
815            Rd in {Rn, Rt, Rt2} => UNPREDICTABLE;
816+--
817| op(23:20)
818            # SWP/SWPB are OPTIONAL+deprecated in v7 with the Virtualization
819            # Extension, and OBSOLETE+UNDEFINED in v8 aarch32.
820| 0x00      = *Deprecated
821              pattern := cccc00010b00nnnntttt00001001tttt;
822              rule := SWP_SWPB;
823| 1000      = *StRdRtRn
824              pattern := cccc00011000nnnndddd11111001tttt;
825              rule := STREX;  arch := v6;
826| 1001      = *LdRtRn
827              pattern := cccc00011001nnnntttt111110011111;
828              rule := LDREX;  arch := v6;
829| 1010      = *StRdRtRt2Rn
830              pattern := cccc00011010nnnndddd11111001tttt;
831              rule := STREXD;  arch := v6K;
832| 1011      = *LdRtRt2Rn
833              pattern := cccc00011011nnnntttt111110011111;
834              rule := LDREXD;  arch := v6K;
835| 1100      = *StRdRtRn
836              pattern := cccc00011100nnnndddd11111001tttt;
837              rule := STREXB;  arch := v6K;
838| 1101      = *LdRtRn
839              pattern := cccc00011101nnnntttt111110011111;
840              rule := LDREXB;  arch := v6K;
841| 1110      = *StRdRtRn
842              pattern := cccc00011110nnnndddd11111001tttt;
843              rule := STREXH;  arch := v6K;
844| 1111      = *LdRtRn
845              pattern := cccc00011111nnnntttt111110011111;
846              rule := STREXH;  arch := v6K;
847| else:     = *Undefined  # Note on table description.
848+--
849
850+-- msr_immediate_and_hints (See Section A5.2.11)
851*Msr
852  { cond(31:28), mask(19:18), imm12(11:0) }
853  imm32 := ARMExpandImm(imm12);
854  write_nzcvq := mask(1)=1;
855  write_g := mask(0)=1;
856  defs := {NZCV if write_nzcvq else None};
857  uses := {};
858  # TODO(karl): model that ASPR.GE is set if write_g, and that
859  # ASPR.Q is set if write_nzcvq.
860  safety := mask=00 => DECODER_ERROR;
861+--
862| op(22) op1(19:16) op2(7:0)
863| 0      0000       0000_0000  = *Nop
864                                 pattern := cccc0011001000001111000000000000;
865                                 rule := NOP;
866                                 arch := (v6K, v6T2);
867| "      "          0000_0001  = *Nop
868                                 pattern := cccc0011001000001111000000000001;
869                                 rule := YIELD;
870                                 arch := v6K;
871| "      "          0000_0010  = *Forbidden
872                                 # Don't allow, may put hardware to sleep
873                                 # until a send event occurs.
874                                 pattern := cccc0011001000001111000000000010;
875                                 rule := WFE;
876                                 arch := v6K;
877| "      "          0000_0011  = *Forbidden
878                                 # Don't allow, may put hardware to sleep
879                                 # until a send event occurs.
880                                 pattern := cccc0011001000001111000000000011;
881                                 rule := WFI;
882                                 arch := v6K;
883| "      "          0000_0100  = *Forbidden
884                                 # Don't allow, causes an event to be
885                                 # signalled to all processors in the
886                                 # multiprocessor system.
887                                 pattern := cccc0011001000001111000000000100;
888                                 rule := SEV;
889                                 arch := v6K;
890| "      "          1111_xxxx  = *Forbidden
891                                 # Don't allow unless there is a good reason
892                                 # for it.
893                                 pattern := cccc001100100000111100001111iiii;
894                                 rule := DBG;
895                                 arch := v7;
896# Note: mask(19:18)=00 isn't allowed for MSR_immediate (checked by
897# following 2 rows).
898| "      0100       -          = *Msr
899                                 pattern := cccc00110010mm001111iiiiiiiiiiii;
900                                 rule := MSR_immediate;
901| "      1x00       "          "
902| "      xx01       -          = *Forbidden
903                                 # MSR(immediate), ring0 version
904                                 pattern := cccc00110r10mmmm1111iiiiiiiiiiii;
905                                 rule := MSR_immediate;
906| "      xx1x       -          "
907| 1      -          -          "
908# Unallocated hints, see note on table description.
909| else:                        = *Forbidden
910+--
911
912+-- miscellaneous_instructions (See Section A5.2.12)
913*RnSet
914   { cond(31:28), R(22), Rd(15:12) }
915   read_spsr := R=1;
916   safety := R=1 => FORBIDDEN_OPERANDS &
917             Rd=1111 => UNPREDICTABLE;
918   defs := { Rd };
919   uses := {};
920*RnUse
921   { cond(31:28), mask(19:18), Rn(3:0) }
922   write_nzcvq := mask(1)=1; write_g := mask(0)=1;
923   defs := { NZCV if write_nzcvq else None };
924   uses := { Rn };
925   safety := mask=00 => UNPREDICTABLE &
926             Rn == Pc => UNPREDICTABLE;
927*Bx
928   { cond(31:28), Rm(3:0) }
929   safety := Rm=1111 => FORBIDDEN_OPERANDS;
930   target := Rm;
931   defs := { Pc };
932   uses := { Rm };
933   arch := v4T;
934*Blx *Bx
935   defs := { Pc , Lr };
936   arch := v5T;
937*Clz
938   { cond(31:28), Rd(15:12), Rm(3:0) }
939   safety := Pc in {Rd, Rm} => UNPREDICTABLE;
940   defs := { Rd };
941   uses := { Rm };
942   arch := v5T;
943*Bkpt
944   { cond(31:28), imm12(19:8), imm4(3:0) }
945   imm32 := ZeroExtend(imm12:imm4, 32);
946   is_literal_pool_head := inst == LiteralPoolHeadConstant();
947   defs := {};
948   uses := {};
949   safety := cond=~1110 => UNPREDICTABLE &
950             not IsBreakPointAndConstantPoolHead(inst) => FORBIDDEN_OPERANDS;
951   arch := v5T;
952+--
953| op2(6:4) B(9) op(22:21) op1(19:16)
954| 000      1    x0        xxxx       = *Forbidden
955                                       pattern := cccc00010r00mmmmdddd001m00000000;
956                                       rule := MRS_Banked_register;
957                                       arch := v7VE;
958| "        "    x1        "          = *Forbidden
959                                       pattern := cccc00010r10mmmm1111001m0000nnnn;
960                                       rule := MRS_Banked_register;
961                                       arch := v7VE;
962| "        0    x0        xxxx       = *RnSet
963                                       pattern := cccc00010r001111dddd000000000000;
964                                       rule := MRS;
965| "        "    01        xx00       = *RnUse
966                                       pattern := cccc00010010mm00111100000000nnnn;
967                                       rule := MSR_register;
968| "        "    01        xx01       = *Forbidden
969                                       pattern := cccc00010r10mmmm111100000000nnnn;
970                                       rule := MSR_register;
971| "        "    "         xx1x       "
972| "        "    11        -          "
973| 001      -    01        -          = *Bx
974                                       pattern := cccc000100101111111111110001mmmm;
975                                       rule := Bx;
976| "        -    11        -          = *Clz
977                                       pattern := cccc000101101111dddd11110001mmmm;
978                                       rule := CLZ;
979| 010      -    01        -          = *Forbidden
980                                       pattern := cccc000100101111111111110010mmmm;
981                                       rule := BXJ;
982                                       arch := v5TEJ;
983| 011      -    01        -          = *Blx
984                                       pattern := cccc000100101111111111110011mmmm;
985                                       rule := BLX_register;
986| 101      -    -         -          ->saturating_addition_and_subtraction
987| 110      -    11        -          = *Forbidden
988                                       pattern := cccc0001011000000000000001101110;
989                                       rule := ERET;
990                                       arch := v7VE;
991| 111      -    01        -          = *Bkpt
992                                       pattern := cccc00010010iiiiiiiiiiii0111iiii;
993                                       rule := BKPT;
994| "        -    10        -          = *Forbidden
995                                       pattern := cccc00010100iiiiiiiiiiii0111iiii;
996                                       rule := HVC;
997                                       arch := v7VE;
998| "        -    11        -          = *Forbidden
999                                       pattern := cccc000101100000000000000111iiii;
1000                                       rule := SMC;
1001                                       arch := SE;
1002| else:                              = *Undefined     # Note on page A5-18
1003+--
1004
1005
1006+-- load_store_word_and_unsigned_byte (See Section A5.3)
1007# Instructions that use Rt and an immediate value.
1008*LdRtPcImm
1009  { cond(31:28), U(23), Rt(15:12), imm12(11:0) }
1010  imm32 := ZeroExtend(imm12, 32);
1011  add := U=1;
1012  base := Pc;
1013  defs := {Rt};
1014  uses := {Pc};
1015  is_literal_load := true;
1016  safety := Rt == Pc => FORBIDDEN_OPERANDS;
1017*LdRtPcImmB *LdRtPcImm
1018  safety := Rt == Pc => UNPREDICTABLE;
1019
1020# Instructions that use Rt, Rn, and an immediate value.
1021*RtRnImm
1022  { cond(31:28), P(24), U(23), W(21), Rn(19:16), Rt(15:12), imm12(11:0) }
1023  imm32 := ZeroExtend(imm12, 32);
1024  index := P=1; add := U=1; wback := P=0 | W=1;
1025  base := Rn;
1026  small_imm_base_wb := wback;
1027*LdRtRnImm *RtRnImm
1028  defs := {Rt, base if wback else None};
1029  uses := {Rn};
1030  safety := Rn == Pc => DECODER_ERROR &
1031            P=0 & W=1 => DECODER_ERROR &
1032            wback & Rn == Rt => UNPREDICTABLE &
1033            Rt == Pc => FORBIDDEN_OPERANDS;
1034  # Print constraint:
1035  #    Rn=1101 & P=0 & U=1 & W=0 & imm12=000000000100 => see POP;
1036*LdRtRnImmB *LdRtRnImm
1037  safety := Rn == Pc => DECODER_ERROR &
1038            P=0 & W=1 => DECODER_ERROR &
1039            Rt == Pc => UNPREDICTABLE &
1040            wback & Rn == Rt => UNPREDICTABLE;
1041*LdRtRnImmTpCheck *LdRtRnImm
1042  is_load_tp := Rn == Tp & index & not wback & add & imm12 in {0, 4};
1043*StRtRnImm *RtRnImm
1044  defs := {base if wback else None};
1045  uses := {Rn, Rt};
1046  safety := P=0 & W=1 => DECODER_ERROR &
1047            wback & (Rn == Pc | Rn == Rt)=> UNPREDICTABLE;
1048  # Print constraint:
1049  #    Rn=1101 & P=1 & U=0 & W=1 & imm12=000000000100 => see PUSH;
1050*StRtRnImmB *StRtRnImm
1051  safety := P=0 & W=1 => DECODER_ERROR &
1052            Rt == Pc => UNPREDICTABLE &
1053            wback & (Rn == Pc | Rn == Rt)=> UNPREDICTABLE;
1054
1055# Instructions that use Rt, Rn, and Rm with a shifted, immediate value.
1056*RtRnRmSh
1057  { cond(31:28), P(24), U(23), W(21), Rn(19:16), Rt(15:12),
1058    imm5(11:7), type(6:5), Rm(3:0) }
1059  index := P=1; add := U=1; wback := P=0 | W=1;
1060  shift := DecodeImmShift(type, imm5);
1061  base := Rn;
1062*LdRtRnRmSh *RtRnRmSh
1063  defs := {Rt, base if wback else None};
1064  uses := {Rm, Rn};
1065  safety := P=0 & W=1 => DECODER_ERROR &
1066            Rm == Pc => UNPREDICTABLE &
1067            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
1068            ArchVersion() < 6 & wback & Rn == Rm => UNPREDICTABLE &
1069            index => FORBIDDEN &
1070            Rt == Pc => FORBIDDEN_OPERANDS;
1071*LdRtRnRmShB *LdRtRnRmSh
1072  safety := P=0 & W=1 => DECODER_ERROR &
1073            Pc in { Rt, Rm} => UNPREDICTABLE &
1074            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
1075            ArchVersion() < 6 & wback & Rn == Rm => UNPREDICTABLE &
1076            index => FORBIDDEN;
1077*StRtRnRmSh *RtRnRmSh
1078  defs := {base if wback else None};
1079  uses := {Rm, Rn, Rt};
1080  safety := P=0 & W=1 => DECODER_ERROR &
1081            Rm == Pc => UNPREDICTABLE &
1082            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
1083            ArchVersion() < 6 & wback & Rn == Rm => UNPREDICTABLE &
1084            index => FORBIDDEN;
1085*StRtRnRmShB *StRtRnRmSh
1086  safety := P=0 & W=1 => DECODER_ERROR &
1087            Pc in {Rm, Rt} => UNPREDICTABLE &
1088            wback & (Rn == Pc | Rn == Rt) => UNPREDICTABLE &
1089            ArchVersion() < 6 & wback & Rn == Rm => UNPREDICTABLE &
1090            index => FORBIDDEN;
1091+--
1092# Note: Column op1 is repeated so that several rows can define
1093# (anded) multiple test conditions for this row.
1094| A(25) op1(24:20) B(4) Rn(19:16)  op1_repeated(24:20)
1095| 0     xx0x0      -    -          ~0x010
1096        = *StRtRnImm pattern := cccc010pu0w0nnnnttttiiiiiiiiiiii;
1097          rule := STR_immediate;
1098| 1     xx0x0      0    -          ~0x010
1099        = *StRtRnRmSh pattern := cccc011pd0w0nnnnttttiiiiitt0mmmm;
1100          rule := STR_register;
1101| 0     0x010      -    -          -
1102        = *Forbidden
1103          pattern := cccc0100u010nnnnttttiiiiiiiiiiii; rule := STRT_A1;
1104| 1     0x010      0    -          -
1105        = *Forbidden
1106          pattern := cccc0110u010nnnnttttiiiiitt0mmmm; rule := STRT_A2;
1107| 0     xx0x1      -    ~1111      ~0x011
1108        = *LdRtRnImmTpCheck pattern := cccc010pu0w1nnnnttttiiiiiiiiiiii;
1109          rule := LDR_immediate;
1110| "     xx0x1      "    1111       ~0x011
1111        = *LdRtPcImm pattern := cccc0101u0011111ttttiiiiiiiiiiii;
1112           rule := LDR_literal;
1113| 1     xx0x1      0    -          ~0x011
1114        = *LdRtRnRmSh pattern := cccc011pu0w1nnnnttttiiiiitt0mmmm;
1115          rule := LDR_register;
1116| 0     0x011      -    -          -
1117        = *Forbidden
1118          pattern := cccc0100u011nnnnttttiiiiiiiiiiii; rule := LDRT_A1;
1119| 1     0x011      0    -          -
1120        = *Forbidden
1121          pattern := cccc0110u011nnnnttttiiiiitt0mmmm; rule := LDRT_A2;
1122| 0     xx1x0      -    -          ~0x110
1123        = *StRtRnImmB pattern := cccc010pu1w0nnnnttttiiiiiiiiiiii;
1124          rule := STRB_immediate;
1125| 1     xx1x0      0    -          ~0x110
1126        = *StRtRnRmShB pattern := cccc011pu1w0nnnnttttiiiiitt0mmmm;
1127          rule := STRB_register;
1128| 0     0x110      -    -          -
1129        = *Forbidden
1130          pattern := cccc0100u110nnnnttttiiiiiiiiiiii; rule := STRBT_A1;
1131| 1     0x110      0    -          -
1132        = *Forbidden
1133          pattern := cccc0110u110nnnnttttiiiiitt0mmmm; rule := STRBT_A2;
1134| 0     xx1x1      -    ~1111      ~0x111
1135        = *LdRtRnImmB pattern := cccc010pu1w1nnnnttttiiiiiiiiiiii;
1136          rule := LDRB_immediate;
1137| "     xx1x1      "    1111       ~0x111
1138        = *LdRtPcImmB pattern := cccc0101u1011111ttttiiiiiiiiiiii;
1139          rule := LDRB_literal;
1140| 1     xx1x1      0    -          ~0x111
1141        = *LdRtRnRmShB pattern := cccc011pu1w1nnnnttttiiiiitt0mmmm;
1142          rule := LDRB_register;
1143| 0     0x111      -    -          -
1144        = *Forbidden
1145          pattern := cccc0100u111nnnnttttiiiiiiiiiiii; rule := LDRBT_A1;
1146| 1     0x111      0    -          -
1147        = *Forbidden
1148          pattern := cccc0110u111nnnnttttiiiiitt0mmmm; rule := LDRBT_A2;
1149# Instructions with A==1 and B==1 are in media_instructions.
1150# TODO(jfb) Should we mark them as unreachable?
1151+--
1152
1153+-- media_instructions (See Section A5.4)
1154*RdRnRm
1155  { cond(31:28), Rd(19:16), Rm(11:8), Rn(3:0) }
1156  defs := {Rd};
1157  uses := {Rn, Rm};
1158  safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1159*RdRnRmRa
1160  { cond(31:28), Rd(19:16), Ra(15:12), Rm(11:8), Rn(3:0) }
1161  defs := {Rd};
1162  uses := {Rn, Rm, Ra};
1163  safety := Ra == Pc => DECODER_ERROR &
1164            Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1165*RdRnLsbMsb
1166  { cond(31:28), msb(20:16), Rd(15:12), lsb(11:7), Rn(3:0) }
1167  defs := {Rd};
1168  uses := {Rn, Rd};
1169  safety := Rn == Pc => DECODER_ERROR &
1170            Rd == Pc => UNPREDICTABLE &
1171            msb < lsb => UNPREDICTABLE;
1172*RdRnLsbWidth
1173  { cond(31:28), widthm1(20:16), Rd(15:12), lsb(11:7), Rn(3:0) }
1174  defs := {Rd};
1175  uses := {Rn};
1176  safety := Pc in {Rd, Rn} => UNPREDICTABLE &
1177            lsb + widthm1 > 31 => UNPREDICTABLE;
1178*RdLsbWidth
1179  { cond(31:28), msb(20:16), Rd(15:12), lsb(11:7) }
1180  defs := {Rd};
1181  uses := {Rd};
1182  safety := Rd == Pc => UNPREDICTABLE &
1183            msb < lsb => UNPREDICTABLE;
1184*Udf
1185  defs := {};
1186  uses := {};
1187  safety := not IsUDFNaClSafe(inst) => FORBIDDEN_OPERANDS;
1188+--
1189| op1(24:20) op2(7:5) Rd(15:12) Rn(3:0)
1190| 000xx      -        -         -     ->parallel_addition_and_subtraction_signed
1191| 001xx      -        -         -     ->parallel_addition_and_subtraction_unsigned
1192| 01xxx      -        -         -     ->packing_unpacking_saturation_and_reversal
1193| 10xxx      -        -         -     ->signed_multiply_signed_and_unsigned_divide
1194| 11000      000      1111      -
1195                      = *RdRnRm
1196                        pattern := cccc01111000dddd1111mmmm0001nnnn;
1197                        rule := USAD8;  arch := v6;
1198| "          "        ~1111     -
1199                      = *RdRnRmRa
1200                        pattern := cccc01111000ddddaaaammmm0001nnnn;
1201                        rule := USADA8;  arch := v6;
1202| 1101x      x10      -         -
1203                      = *RdRnLsbWidth
1204                        pattern := cccc0111101wwwwwddddlllll101nnnn;
1205                        rule := SBFX;  arch := v6T2;
1206| 1110x      x00      -         1111
1207                      = *RdLsbWidth
1208                        pattern := cccc0111110mmmmmddddlllll0011111;
1209                        rule := BFC;  arch := v6T2;
1210| "          "        -         ~1111
1211                      = *RdRnLsbMsb
1212                        pattern := cccc0111110mmmmmddddlllll001nnnn;
1213                        rule := BFI; arch := v6T2;
1214| 1111x      x10      -         -
1215                      = *RdRnLsbWidth
1216                        pattern := cccc0111111mmmmmddddlllll101nnnn;
1217                        rule := UBFX;  arch := v6T2;
1218| 11111      111      -         -
1219                      = *Udf
1220                        pattern := cccc01111111iiiiiiiiiiii1111iiii;
1221                        # Note: the UDF mnemonic only applies
1222                        #   when cond == 0b1110, but all
1223                        #   encodings are permanently undefined.
1224                        rule := UDF;
1225| else:               = *Undefined  # Note on table a5.4
1226+--
1227
1228# None of the instructions in the following table set NZCV flags.
1229# Some do set the APSR's sticky Q bit (for saturation) or the GE bits,
1230# but we don't model them.
1231+-- parallel_addition_and_subtraction_signed (See Section A5.4.1)
1232*RdRnRm
1233  { cond(31:28), Rn(19:16), Rd(15:12), Rm(3:0) }
1234  defs := {Rd};
1235  uses := {Rn, Rm};
1236  safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1237  arch := v6;
1238+--
1239| op1(21:20) op2(7:5)
1240| 01         000      = *RdRnRm
1241                         pattern := cccc01100001nnnndddd11110001mmmm;
1242                         rule := SADD16;
1243| 01         001      = *RdRnRm
1244                         pattern := cccc01100001nnnndddd11110011mmmm;
1245                         rule := SASX;
1246| 01         010      = *RdRnRm
1247                         pattern := cccc01100001nnnndddd11110101mmmm;
1248                         rule := SSAX;
1249| 01         011      = *RdRnRm
1250                         pattern := cccc01100001nnnndddd11110111mmmm;
1251                         rule := SSSUB16;
1252| 01         100      = *RdRnRm
1253                         pattern := cccc01100001nnnndddd11111001mmmm;
1254                         rule := SADD8;
1255| 01         111      = *RdRnRm
1256                         pattern := cccc01100001nnnndddd11111111mmmm;
1257                         rule := SSUB8;
1258| 10         000      = *RdRnRm
1259                         pattern := cccc01100010nnnndddd11110001mmmm;
1260                         rule := QADD16;
1261| 10         001      = *RdRnRm
1262                         pattern := cccc01100010nnnndddd11110011mmmm;
1263                         rule := QASX;
1264| 10         010      = *RdRnRm
1265                         pattern := cccc01100010nnnndddd11110101mmmm;
1266                         rule := QSAX;
1267| 10         011      = *RdRnRm
1268                         pattern := cccc01100010nnnndddd11110111mmmm;
1269                         rule := QSUB16;
1270| 10         100      = *RdRnRm
1271                         pattern := cccc01100010nnnndddd11111001mmmm;
1272                         rule := QADD8;
1273| 10         111      = *RdRnRm
1274                         pattern := cccc01100010nnnndddd11111111mmmm;
1275                         rule := QSUB8;
1276| 11         000      = *RdRnRm
1277                         pattern := cccc01100011nnnndddd11110001mmmm;
1278                         rule := SHADD16;
1279| 11         001      = *RdRnRm
1280                         pattern := cccc01100011nnnndddd11110011mmmm;
1281                         rule := SHASX;
1282| 11         010      = *RdRnRm
1283                         pattern := cccc01100011nnnndddd11110101mmmm;
1284                         rule := SHSAX;
1285| 11         011      = *RdRnRm
1286                         pattern := cccc01100011nnnndddd11110111mmmm;
1287                         rule := SHSUB16;
1288| 11         100      = *RdRnRm
1289                         pattern := cccc01100011nnnndddd11111001mmmm;
1290                         rule := SHADD8;
1291| 11         111      = *RdRnRm
1292                         pattern := cccc01100011nnnndddd11111111mmmm;
1293                         rule := SHSUB8;
1294| else:               = *Undefined  # Note on table description.
1295+--
1296
1297# None of the instructions in the following table set NZCV flags.
1298# Some do set the APSR's sticky Q bit (for saturation) or the GE bits,
1299# but we don't model them.
1300+-- parallel_addition_and_subtraction_unsigned (See Section A5.4.2)
1301*RdRnRm
1302  { cond(31:28), Rn(19:16), Rd(15:12), Rm(3:0) }
1303  defs := {Rd};
1304  uses := {Rn, Rm};
1305  safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1306  arch := v6;
1307+--
1308| op1(21:20) op2(7:5)
1309| 01         000      = *RdRnRm
1310                         pattern := cccc01100101nnnndddd11110001mmmm;
1311                         rule := UADD16;
1312| 01         001      = *RdRnRm
1313                         pattern := cccc01100101nnnndddd11110011mmmm;
1314                         rule := UASX;
1315| 01         010      = *RdRnRm
1316                         pattern := cccc01100101nnnndddd11110101mmmm;
1317                         rule := USAX;
1318| 01         011      = *RdRnRm
1319                         pattern := cccc01100101nnnndddd11110111mmmm;
1320                         rule := USUB16;
1321| 01         100      = *RdRnRm
1322                         pattern := cccc01100101nnnndddd11111001mmmm;
1323                         rule := UADD8;
1324| 01         111      = *RdRnRm
1325                         pattern := cccc01100101nnnndddd11111111mmmm;
1326                         rule := USUB8;
1327| 10         000      = *RdRnRm
1328                         pattern := cccc01100110nnnndddd11110001mmmm;
1329                         rule := UQADD16;
1330| 10         001      = *RdRnRm
1331                         pattern := cccc01100110nnnndddd11110011mmmm;
1332                         rule := UQASX;
1333| 10         010      = *RdRnRm
1334                         pattern := cccc01100110nnnndddd11110101mmmm;
1335                         rule := UQSAX;
1336| 10         011      = *RdRnRm
1337                         pattern := cccc01100110nnnndddd11110111mmmm;
1338                         rule := UQSUB16;
1339| 10         100      = *RdRnRm
1340                         pattern := cccc01100110nnnndddd11111001mmmm;
1341                         rule := UQADD8;
1342| 10         111      = *RdRnRm
1343                         pattern := cccc01100110nnnndddd11111111mmmm;
1344                         rule := UQSUB8;
1345| 11         000      = *RdRnRm
1346                         pattern := cccc01100111nnnndddd11110001mmmm;
1347                         rule := UHADD16;
1348| 11         001      = *RdRnRm
1349                         pattern := cccc01100111nnnndddd11110011mmmm;
1350                         rule := UHASX;
1351| 11         010      = *RdRnRm
1352                         pattern := cccc01100111nnnndddd11110101mmmm;
1353                         rule := UHSAX;
1354| 11         011      = *RdRnRm
1355                         pattern := cccc01100111nnnndddd11110111mmmm;
1356                         rule := UHSUB16;
1357| 11         100      = *RdRnRm
1358                         pattern := cccc01100111nnnndddd11111001mmmm;
1359                         rule := UHADD8;
1360| 11         111      = *RdRnRm
1361                         pattern := cccc01100111nnnndddd11111111mmmm;
1362                         rule := UHSUB8;
1363| else:               = *Undefined  # Note on table description.
1364+--
1365
1366# None of the instructions in the following table set NZCV flags.
1367# Some do set the APSR's sticky Q bit (for saturation) or the GE bits,
1368# but we don't model them.
1369+-- packing_unpacking_saturation_and_reversal (See Section A5.4.3)
1370*RdRm
1371  { cond(31:28), Rd(15:12), Rm(3:0) }
1372  defs := {Rd};
1373  uses := {Rm};
1374  safety := Pc in {Rd, Rm} => UNPREDICTABLE;
1375  arch := v6;
1376*RdRmRbit *RdRm
1377  arch := v6T2;
1378*RdRnRm *RdRm
1379  { cond(31:28), Rn(19:16), Rd(15:12), Rm(3:0) }
1380  uses := {Rn, Rm};
1381  safety := Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1382*RdRnRmGE *RdRnRm
1383  # Note: This instruction uses APSR.GE.
1384*RdRnRmImm *RdRnRm
1385  { cond(31:28), Rn(19:16), Rd(15:12), imm5(11:7), tb(6), Rm(3:0) }
1386  tbform := tb=1;
1387  shift := DecodeImmShift(tb:'0', imm5);
1388*RdRmRot *RdRm
1389  { cond(31:28), Rd(15:12), rotate(11:10), Rm(3:0) }
1390  rotation := rotate:'000';
1391*RdRnRmRot *RdRnRm
1392  { cond(31:28), Rn(19:16), Rd(15:12), rotate(11:10), Rm(3:0) }
1393  rotation := rotate:'000';
1394  safety := Rn=1111 => DECODER_ERROR &
1395            Pc in {Rd, Rm} => UNPREDICTABLE;
1396*RdRn
1397  { cond(31:28), Rd(15:12), Rn(3:0) }
1398  # Note: Sets APSR.Q
1399  defs := {Rd};
1400  uses := {Rn};
1401  safety := Pc in {Rd, Rn} => UNPREDICTABLE;
1402  arch := v6;
1403*RdImmRn *RdRn
1404  { cond(31:28), sat_imm(19:16), Rd(15:12), Rn(3:0) }
1405  saturate_to := sat_imm + 1;
1406*URdImmRn *RdImmRn
1407  saturate_to := sat_imm;
1408*RdImmRnSh *RdRn
1409  { cond(31:28), sat_imm(20:16), Rd(15:12), imm5(11:7), sh(6), Rn(3:0) }
1410  saturate_to := sat_imm + 1;
1411  shift := DecodeImmShift(sh:'0', imm5);
1412*URdImmRnSh *RdImmRnSh
1413  saturate_to := sat_imm;
1414+--
1415| op1(22:20) op2(7:5) A(19:16)
1416| 000        xx0      -        = *RdRnRmImm
1417                                  pattern := cccc01101000nnnnddddiiiiit01mmmm;
1418                                  rule := PKH;
1419| "          011      ~1111    = *RdRnRmRot
1420                                  pattern := cccc01101000nnnnddddrr000111mmmm;
1421                                  rule := SXTAB16;
1422| "          "        1111     = *RdRmRot
1423                                  pattern := cccc011010001111ddddrr000111mmmm;
1424                                  rule := SXTB16;
1425| "          101      -        = *RdRnRmGE
1426                                  pattern := cccc01101000nnnndddd11111011mmmm;
1427                                  rule := SEL;
1428| 01x        xx0      -        = *RdImmRnSh
1429                                 pattern := cccc0110101iiiiiddddiiiiis01nnnn;
1430                                 rule := SSAT;
1431| 010        001      -        = *RdImmRn
1432                                 pattern := cccc01101010iiiidddd11110011nnnn;
1433                                 rule := SSAT16;
1434| "          011      ~1111    = *RdRnRmRot
1435                                 pattern := cccc01101010nnnnddddrr000111mmmm;
1436                                 rule := SXTAB;
1437| "          "        1111     = *RdRmRot
1438                                  pattern := cccc011010101111ddddrr000111mmmm;
1439                                  rule := SXTB;
1440| 011        001      -        = *RdRm
1441                                  pattern := cccc011010111111dddd11110011mmmm;
1442                                  rule := REV;
1443| "          011      ~1111    = *RdRnRmRot
1444                                  pattern := cccc01101011nnnnddddrr000111mmmm;
1445                                  rule := SXTAH;
1446| "          "        1111     = *RdRmRot
1447                                  pattern := cccc011010111111ddddrr000111mmmm;
1448                                  rule := SXTH;
1449| "          101      -        = *RdRm
1450                                  pattern := cccc011010111111dddd11111011mmmm;
1451                                  rule := REV16;
1452| 100        011      ~1111    = *RdRnRmRot
1453                                  pattern := cccc01101100nnnnddddrr000111mmmm;
1454                                  rule := UXTAB16;
1455| "          "        1111     = *RdRmRot
1456                                  pattern := cccc011011001111ddddrr000111mmmm;
1457                                  rule := UXTB16;
1458| 11x        xx0      -        = *URdImmRnSh
1459                                  pattern := cccc0110111iiiiiddddiiiiis01nnnn;
1460                                  rule := USAT;
1461| 110        001      -        = *URdImmRn
1462                                  pattern := cccc01101110iiiidddd11110011nnnn;
1463                                  rule := USAT16;
1464| "          011      ~1111    = *RdRnRmRot
1465                                  pattern := cccc01101110nnnnddddrr000111mmmm;
1466                                  rule := UXTAB;
1467| "          "        1111     = *RdRmRot
1468                                  pattern := cccc011011101111ddddrr000111mmmm;
1469                                  rule := UXTB;
1470| 111        001      -        = *RdRmRbit
1471                                  pattern := cccc011011111111dddd11110011mmmm;
1472                                  rule := RBIT;
1473| "          011      ~1111    = *RdRnRmRot
1474                                  pattern := cccc01101111nnnnddddrr000111mmmm;
1475                                  rule := UXTAH;
1476| "          "        1111     = *RdRmRot
1477                                  pattern := cccc011011111111ddddrr000111mmmm;
1478                                  rule := UXTH;
1479| "          101      -        = *RdRm
1480                                  pattern := cccc011011111111dddd11111011mmmm;
1481                                  rule := REVSH;
1482| else:                        = *Undefined  # Note on table description.
1483+--
1484
1485+-- signed_multiply_signed_and_unsigned_divide (See Section A5.4.4)
1486*RdRnRmRa
1487  { cond(31:28), Rd(19:16), Ra(15:12), Rm(11:8), M(5), Rn(3:0) }
1488  defs := {Rd};
1489  uses := {Rn, Rm, Ra};
1490  safety := Ra == Pc => DECODER_ERROR &
1491            Pc in {Rd, Rn, Rm} => UNPREDICTABLE;
1492  arch := v6;
1493*RdRnRm
1494  { cond(31:28), Rd(19:16), Rm(11:8), M(5), Rn(3:0) }
1495  defs := {Rd};
1496  uses := {Rm, Rn};
1497  safety := Pc in {Rd, Rm, Rn} => UNPREDICTABLE;
1498  arch := v6;
1499*RdLoHiRnRm
1500  { cond(31:28), RdHi(19:16), RdLo(15:12), Rm(11:8), M(5), Rn(3:0) }
1501  defs := {RdHi, RdLo};
1502  uses := {RdHi, RdLo, Rm, Rn};
1503  safety := Pc in { RdHi, RdLo, Rn, Rm} => UNPREDICTABLE &
1504            RdHi == RdLo => UNPREDICTABLE;
1505  arch := v6;
1506+--
1507| op1(22:20) op2(7:5) A(15:12)
1508                                 # Implements Smlad and Smladx, where
1509                                 # the x form is chosen if bit 5 is 1.
1510| 000        00x      ~1111    = *RdRnRmRa
1511                                 pattern := cccc01110000ddddaaaammmm00m1nnnn;
1512                                 rule := SMLAD;
1513                                 # Implements Smuad and Smuadx, where
1514                                 # the x form is chosen if bit 5 is 1.
1515| "          "        1111     = *RdRnRm
1516                                 pattern := cccc01110000dddd1111mmmm00m1nnnn;
1517                                 rule := SMUAD;
1518                                 # Implements Smlsd and Smlsdx, where
1519                                 # the x form is chosen if bit 5 is 1.
1520                                 # Note: This rule has the constraint that
1521                                 # Ra!=1111, but we did not test it since
1522                                 # its checked by the pattern (column A)
1523                                 # for this instruction.
1524| "          01x      ~1111    = *RdRnRmRa
1525                                 pattern := cccc01110000ddddaaaammmm01m1nnnn;
1526                                 rule := SMLSD;
1527                                 # Implements Smusd and Smusdx, where
1528                                 # the x form is chosen if bit 5 is 1.
1529| "          "        1111     = *RdRnRm
1530                                 pattern := cccc01110000dddd1111mmmm01m1nnnn;
1531                                 rule := SMUSD;
1532| 001        000      -        = *RdRnRm
1533                                 pattern := cccc01110001dddd1111mmmm0001nnnn;
1534                                 rule := SDIV;
1535                                 arch := v7VEoptv7A_v7R;
1536| 011        "        -        = *RdRnRm
1537                                 pattern := cccc01110011dddd1111mmmm0001nnnn;
1538                                 rule := UDIV;
1539                                 arch := v7VEoptv7A_v7R;
1540                                 # Implements Smalad and Smaladx, where
1541                                 # the x form is chosen if bit 5 is 1.
1542| 100        00x      -        = *RdLoHiRnRm
1543                                 pattern := cccc01110100hhhhllllmmmm00m1nnnn;
1544                                 rule := SMLALD;
1545                                 # Implements Smlsld and Smlsldx, where
1546                                 # the x form is chosen if bit 5 is 1.
1547| "          01x      -        = *RdLoHiRnRm
1548                                 pattern := cccc01110100hhhhllllmmmm01m1nnnn;
1549                                 rule := SMLSLD;
1550                                 # Implements Smmla and Smmlar, where
1551                                 # the r form is chosen if bit 5 is 1.
1552                                 # Note: This rule has the constraint that
1553                                 # Ra!=1111, but we did not test it since
1554                                 # it's checked by the pattern (column A)
1555                                 # for this instruction.
1556| 101        00x      ~1111    = *RdRnRmRa
1557                                 pattern := cccc01110101ddddaaaammmm00r1nnnn;
1558                                 rule := SMMLA;
1559                                 # Implements Smmul and Smmulr, where
1560                                 # the r form is chosen if bit 5 is 1.
1561| "          "        1111     = *RdRnRm
1562                                 pattern := cccc01110101dddd1111mmmm00r1nnnn;
1563                                 rule := SMMUL;
1564                                 # Implements Smmls and Smmlsr, where
1565                                 # the r form is chosen if bit 5 is 1.
1566| "          11x      -        = *RdRnRmRa
1567                                 pattern := cccc01110101ddddaaaammmm11r1nnnn;
1568                                 rule := SMMLS;
1569| else:                        = *Undefined  # Note associated with table.
1570+--
1571
1572+-- branch_branch_with_link_and_block_data_transfer (See Section A5.5)
1573*RnRegs
1574  { cond(31:28), W(21), Rn(19:16), register_list(15:0) }
1575  registers := RegisterList(register_list); wback := W=1;
1576  base := Rn;
1577  small_imm_base_wb := wback;
1578  safety := Rn == Pc | NumGPRs(registers) < 1 => UNPREDICTABLE;
1579*LdRnRegs *RnRegs
1580  defs := Union({Rn if wback else None}, registers);
1581  uses := {Rn};
1582  safety := super.safety &
1583            wback & Contains(registers, Rn) => UNKNOWN &
1584            Contains(registers, Pc) => FORBIDDEN_OPERANDS;
1585*StRnRegs *RnRegs
1586  defs := {Rn if wback else None};
1587  uses := Union({Rn}, registers);
1588  safety := super.safety &
1589            wback & Contains(registers, Rn) &
1590            Rn != SmallestGPR(registers) => UNKNOWN;
1591*Branch
1592  { Cond(31:28), imm24(23:0) }
1593  imm32 := SignExtend(imm24:'00', 32);
1594  defs := {Pc};
1595  uses := {Pc};
1596  relative := true;
1597  # The ARM manual states that "PC reads as the address of the current
1598  # instruction plus 8.
1599  relative_offset := imm32 + 8;
1600  safety := true => MAY_BE_SAFE;
1601*BranchLink *Branch
1602  defs := {Pc, Lr};
1603+--
1604| op(25:20) R(15) Rn(19:16)
1605| 0000x0    -     -         = *StRnRegs
1606                               pattern := cccc100000w0nnnnrrrrrrrrrrrrrrrr;
1607                               rule := STMDA_STMED;
1608| 0000x1    -     -         = *LdRnRegs
1609                               pattern := cccc100000w1nnnnrrrrrrrrrrrrrrrr;
1610                               rule := LDMDA_LDMFA;
1611| 0010x0    -     -         = *StRnRegs
1612                               pattern := cccc100010w0nnnnrrrrrrrrrrrrrrrr;
1613                               rule := STM_STMIA_STMEA;
1614# Note: The following three table rows should not be separated.
1615# They have the same semantics. Further, the separation (of the neumonic)
1616# involves the bit count in the register list (which is not specified in
1617# this table).
1618#| 001001    -     -         =  pattern := cccc100010w1nnnnrrrrrrrrrrrrrrrr;
1619#                               rule := LDM_LDMIA_LDMFD;
1620#| 001011    -     ~1101     =  pattern := cccc100010w1nnnnrrrrrrrrrrrrrrrr;
1621#                               rule := LDM_LDMIA_LDMFD;
1622#| "         -     1101      =  pattern := cccc100010111101rrrrrrrrrrrrrrrr;
1623#                               rule := POP;
1624#
1625# The following is the merged replacement for the three rows above.
1626| 0010w1    -     -         = *LdRnRegs
1627                               pattern := cccc100010w1nnnnrrrrrrrrrrrrrrrr;
1628                               rule := LDM_LDMIA_LDMFD;
1629# Note: The following three table rows should not be separated.
1630# They have the same semantics. Further, the separation (of the neumonic)
1631# involves the bit count in the register list (which is not specified in
1632# this table).
1633#| 010000    -     -         =  pattern := cccc100100w0nnnnrrrrrrrrrrrrrrrr;
1634#                               rule := STMDB_STMFD;
1635#| 010010    -     ~1101     =  pattern := cccc100100w0nnnnrrrrrrrrrrrrrrrr;
1636#                               rule := STMDB_STMFD;
1637#| "         -     1101      =  pattern := cccc100100101101rrrrrrrrrrrrrrrr;
1638#                               rule := PUSH;
1639#
1640# The following is the merged replacement for the three rows above.
1641| 0100w0    -     -         = *StRnRegs
1642                               pattern := cccc100100w0nnnnrrrrrrrrrrrrrrrr;
1643                               rule := STMDB_STMFD;
1644| 0100x1    -     -         = *LdRnRegs
1645                               pattern := cccc100100w1nnnnrrrrrrrrrrrrrrrr;
1646                               rule := LDMDB_LDMEA;
1647| 0110x0    -     -         = *StRnRegs
1648                               pattern := cccc100110w0nnnnrrrrrrrrrrrrrrrr;
1649                               rule := STMIB_STMFA;
1650| 0110x1    -     -         = *LdRnRegs
1651                               pattern := cccc100110w1nnnnrrrrrrrrrrrrrrrr;
1652                               rule := LDMIB_LDMED;
1653| 0xx1x0    -     -         = *Forbidden  # ring0 version
1654                               pattern := cccc100pu100nnnnrrrrrrrrrrrrrrrr;
1655                               rule := STM_User_registers;
1656| 0xx1x1    0     -         = *Forbidden  # ring0 version
1657                               pattern := cccc100pu101nnnn0rrrrrrrrrrrrrrr;
1658                               rule := LDM_User_registers;
1659| "         1     -         = *Forbidden
1660                               pattern := cccc100pu1w1nnnn1rrrrrrrrrrrrrrr;
1661                               rule := LDM_exception_return;
1662| 10xxxx    -     -         = *Branch
1663                               pattern := cccc1010iiiiiiiiiiiiiiiiiiiiiiii;
1664                               rule := B;
1665| 11xxxx    -     -         = *BranchLink
1666                               pattern := cccc1011iiiiiiiiiiiiiiiiiiiiiiii;
1667                               rule := BL_BLX_immediate;
1668+--
1669
1670+-- coprocessor_instructions_and_supervisor_call (See Section A5.6)
1671# Note: We currently only allow floating point (and advanced SIMD)
1672# coprocessor operations (coproc=101x).
1673# Note: Column op1 is repeated so that the first three rows can define
1674# (anded) multiple test conditions for this row.
1675|  coproc(11:8) op1(25:20) op(4) Rn(19:16) op1_repeated(25:20)
1676|  -            00000x     -     -          -      =
1677         *Undefined  # No rule defined in table.
1678          pattern := cccc1100000xnnnnxxxxccccxxxoxxxx;
1679|  -            11xxxx     -     -          -      =
1680         *Forbidden
1681          pattern := cccc1111iiiiiiiiiiiiiiiiiiiiiiii;
1682          rule := SVC;
1683| ~101x         0xxxx0     -     -         ~000x00 =
1684         *Forbidden
1685          pattern := cccc110pudw0nnnnddddcccciiiiiiii;
1686          rule := STC;
1687|  "            0xxxx1     -    ~1111      ~000x01 =
1688          *Forbidden
1689           pattern := cccc110pudw1nnnnddddcccciiiiiiii;
1690           rule := LDC_immediate;
1691|  "            "          -     1111       "      =
1692          *Forbidden
1693           pattern := cccc110pudw11111ddddcccciiiiiiii;
1694           rule := LDC_literal;
1695|  "            000100     -     -          -      =
1696          *Forbidden
1697           pattern := cccc11000100ttttttttccccoooommmm;
1698           rule := MCRR;
1699           arch := v5TE;
1700|  "            000101     -     -          -      =
1701          *Forbidden
1702           pattern := cccc11000101ttttttttccccoooommmm;
1703           rule := MRRC;
1704           arch := v5TE;
1705|  "            10xxxx     0     -          -      =
1706          *Forbidden
1707           pattern := cccc1110oooonnnnddddccccooo0mmmm;
1708           rule := CDP;
1709|  "            10xxx0     1     -          -      =
1710          *Forbidden
1711           pattern := cccc1110ooo0nnnnttttccccooo1mmmm;
1712           rule := MCR;
1713           # Following defines advice for "mcr p15, 0, rx, c7, c10, 5"
1714           # (memory barrier).
1715           violations := inst=cccc111000000111tttt111110111010 =>
1716                  error('Consider using DSB (defined in ARMv7) for memory barrier');
1717|  "            10xxx1     1     -          -      =
1718          *Forbidden
1719           pattern := cccc1110ooo1nnnnttttccccooo1mmmm;
1720           rule := MRC;
1721|  101x         0xxxxx     -     -         ~000x0x ->
1722           extension_register_load_store_instructions
1723|  "            00010x     -     -          -      ->
1724           transfer_between_arm_core_and_extension_registers_64_bit
1725|  "            10xxxx     0     -          -      ->
1726           floating_point_data_processing_instructions
1727|  "            10xxxx     1     -          -      ->
1728           transfer_between_arm_core_and_extension_register_8_16_and_32_bit
1729+--
1730
1731+-- floating_point_data_processing_instructions (A7.5 Table A7-16)
1732*base
1733   { cond(31:28), D(22), Vn(19:16), Vd(15:12), sz(8),
1734     N(7), op(6), M(5), Vm(3:0) }
1735   dp_operation := sz=1;
1736   d := D:Vd if dp_operation else Vd:D;
1737   n := N:Vn if dp_operation else Vn:N;
1738   m := M:Vm if dp_operation else Vm:M;
1739   # TODO(karl): Add vector defs/uses etc.
1740   defs := {};
1741   uses := {};
1742   # Note: we have explicitly added that cond(31:28)=~1111 to safety to meet
1743   # table (ARM) restriction.
1744   safety := cond=1111 => DECODER_ERROR;
1745   arch := VFPv2;
1746*Vml_a_s *base
1747   { cond(31:28), D(22), Vn(19:16), Vd(15:12), sz(8),
1748     N(7), op(6), M(5), Vm(3:0) }
1749   advsimd := false;  add := op=0;
1750*Vnml_a_s *base
1751   type := VFPNegMul_VNMLA if op=1 else VFPNegMul_VNMLS;
1752*Vnmul *base - { op }
1753   type := VFPNegMul_VNMUL;
1754*Vop *base - { op }
1755   advsimd := false;
1756*Vfnm_a_s *base
1757   op1_neg := op=1;
1758   arch := VFPv4;
1759*Vfm_a_s *Vfnm_a_s
1760   advsimd := false;
1761+--
1762| opc1(23:20) opc3(7:6)
1763| 0x00        -         = *Vml_a_s
1764                           pattern := cccc11100d00nnnndddd101snom0mmmm;
1765                           rule := VMLA_VMLS_floating_point;
1766| 0x01        -         = *Vnml_a_s
1767                           pattern := cccc11100d01nnnndddd101snom0mmmm;
1768                           rule := VNMLA_VNMLS;
1769| 0x10        x1        = *Vnmul
1770                           pattern := cccc11100d10nnnndddd101sn1m0mmmm;
1771                           rule := VNMUL;
1772| "           x0        = *Vop
1773                           pattern := cccc11100d10nnnndddd101sn0m0mmmm;
1774                           rule := VMUL_floating_point;
1775| 0x11        x0        = *Vop
1776                           pattern := cccc11100d11nnnndddd101sn0m0mmmm;
1777                           rule := VADD_floating_point;
1778| "           x1        = *Vop
1779                           pattern := cccc11100d11nnnndddd101sn1m0mmmm;
1780                           rule := VSUB_floating_point;
1781| 1x00        x0        = *Vop
1782                           pattern := cccc11101d00nnnndddd101sn0m0mmmm;
1783                           rule := VDIV;
1784| 1x01        -         = *Vfnm_a_s
1785                           pattern := cccc11101d01nnnndddd101snom0mmmm;
1786                           rule := VFNMA_VFNMS;
1787| 1x10        -         = *Vfm_a_s
1788                           pattern := cccc11101d10nnnndddd101snom0mmmm;
1789                           rule := VFMA_VFMS;
1790| 1x11        -         -> other_floating_point_data_processing_instructions
1791+--
1792
1793+-- other_floating_point_data_processing_instructions (A7.5 Table A7-17)
1794*Vbase
1795   # TODO(karl): Add vector defs/uses etc.
1796   defs := {};
1797   uses := {};
1798   safety := true => MAY_BE_SAFE;
1799*VdOp *Vbase
1800   { cond(31:28), D(22), Vd(15:12), sz(8) }
1801   d := Vd:D if sz=0 else D:Vd;
1802*VdVmOp *VdOp
1803   { cond(31:28), D(22), Vd(15:12), sz(8), M(5), Vm(3:0) }
1804   m := Vm:D if sz=0 else M:Vm;
1805*VmovImm *VdOp
1806   { cond(31:28), D(22), imm4H(19:16), Vd(15:12), sz(8), imm4L(3:0) }
1807   single_register := sz=0;  advsimd := false;
1808   imm32 := VFPExpandImm(imm4H:imm4L, 32);
1809   imm64 := VFPExpandImm(imm4H:imm4L, 64);
1810   regs := 1;
1811*VopBase *VdVmOp
1812   advsimd := false;
1813*VmovReg *VopBase
1814   single_register := sz=0;
1815   regs := 1;
1816*Vop *VopBase
1817   dp_operation := sz=1;
1818*VcvtFP *VdVmOp
1819   double_to_single := sz=1;
1820*VcvtInt *Vbase
1821   { cond(31:28), D(22), opc2(18:16), Vd(15:12), sz(8), op(7), M(5), Vm(3:0) }
1822   to_integer := opc2(2)=1;  dp_operation := sz=1;
1823   unsigned := opc2(0)=0 if to_integer else op=0;
1824   round_zero := to_integer & op=1;
1825   round_nearest := not to_integer;
1826   d := Vd:D if to_integer else D:Vd if dp_operation else Vd:D;
1827   m := Vm:M if not to_integer else M:Vm if dp_operation else Vm:M;
1828   safety := opc2=~000 & opc2=~10x => DECODER_ERROR;
1829*VcvtFixed *VdOp
1830   { cond(31:28), D(22), op(18), U(16), Vd(12:12), sf(8),
1831     sx(7), i(5), imm4(3:0) }
1832   to_fixed := op=1;  dp_operation:= sf=1;  unsigned := U=1;
1833   size := 16 if sx=0 else 32;
1834   # casts needed in following to allow negatives in C++.
1835   frac_bits := size - imm4:i;
1836   round_zero := to_fixed;
1837   round_nearest := not to_fixed;
1838   safety := frac_bits < 0 => UNPREDICTABLE;
1839*VcvtFP16 *Vbase
1840   { cond(31:28), D(22), op(16), Vd(15:12), T(7), M(5), Vm(3:0) }
1841   half_to_single := op=0;
1842   lowbit := 16 if T=1 else 0;
1843   m := Vm:M;
1844   d := Vd:D;
1845*Vcmp *VdOp
1846   { cond(31:28), D(22), Vd(15:12), sz(8), E(7) }
1847   # Sets FPSCR, not APSR.
1848   dp_operation := sz=1; quiet_nan_exc := E=1;
1849*VcmpWithZero *Vcmp
1850   with_zero := true;
1851*VcmpWithoutZero *Vcmp
1852   { cond(31:28), D(22), Vd(15:12), sz(8), E(7), M(5), Vm(3:0) }
1853   with_zero := false;
1854   m := M:Vm if dp_operation else Vm:M;
1855+--
1856| opc2(19:16) opc3(7:6)
1857| -           x0        = *VmovImm
1858                           pattern := cccc11101d11iiiidddd101s0000iiii;
1859                           rule := VMOV_immediate;
1860                           arch := VFPv3;
1861| 0000        01        = *VmovReg
1862                           pattern := cccc11101d110000dddd101s01m0mmmm;
1863                           rule := VMOV_register;
1864                           arch := VFPv2;
1865| "           11        = *Vop
1866                           pattern := cccc11101d110000dddd101s11m0mmmm;
1867                           rule := VABS;
1868                           arch := VFPv2;
1869| 0001        01        = *Vop
1870                           pattern := cccc11101d110001dddd101s01m0mmmm;
1871                           rule := VNEG;
1872                           arch := VFPv2;
1873| "           11        = *Vop
1874                           pattern := cccc11101d110001dddd101s11m0mmmm;
1875                           rule := VSQRT;
1876                           arch := VFPv2;
1877| 001x        x1        = *VcvtFP16
1878                           pattern := cccc11101d11001odddd1010t1m0mmmm;
1879                           rule := VCVTB_VCVTT;
1880                           arch := VFPv3HP;
1881# The two following entries aren't separate in the ARM manual, but separating
1882# them simplifies handling of default-zero bits.
1883| 0100        x1        = *VcmpWithoutZero
1884                           pattern := cccc11101d110100dddd101se1m0mmmm;
1885                           rule := VCMP_VCMPE;
1886                           arch := VFPv2;
1887| 0101        x1        = *VcmpWithZero
1888                           pattern := cccc11101d110101dddd101se1000000;
1889                           rule := VCMP_VCMPE;
1890                           arch := VFPv2;
1891| 0111        11        = *VcvtFP
1892                           pattern := cccc11101d110111dddd101s11m0mmmm;
1893        rule := VCVT_between_double_precision_and_single_precision;
1894                           arch := VFPv2;
1895| 1000        x1        = *VcvtInt
1896                           pattern := cccc11101d111ooodddd101sp1m0mmmm;
1897        rule := VCVT_VCVTR_between_floating_point_and_integer_Floating_point;
1898                           arch := VFPv2;
1899| 101x        x1        = *VcvtFixed
1900                           pattern := cccc11101d111o1udddd101fx1i0iiii;
1901        rule := VCVT_between_floating_point_and_fixed_point_Floating_point;
1902                           arch := VFPv3;
1903| 110x        x1        = *VcvtInt
1904                           pattern := cccc11101d111ooodddd101sp1m0mmmm;
1905        rule := VCVT_VCVTR_between_floating_point_and_integer_Floating_point;
1906                           arch := VFPv2;
1907| 111x        x1        = *VcvtFixed
1908                           pattern := cccc11101d111o1udddd101fx1i0iiii;
1909        rule := VCVT_between_floating_point_and_fixed_point_Floating_point;
1910                           arch := VFPv3;
1911+--
1912
1913+-- extension_register_load_store_instructions (A7.6)
1914*VdRegs
1915  { cond(31:28), D(22), Vd(15:12), imm8(7:0) }
1916  imm32 := ZeroExtend(imm8:'00', 32);
1917*VdRnImm *VdRegs
1918  { cond(31:28), U(23), D(22), Rn(19:16), Vd(15:12), imm8(7:0) }
1919  add := U=1;
1920  n := Rn;
1921  base := Rn;
1922  defs := {};
1923  uses := {Rn};
1924*Vldr *VdRnImm
1925  # TODO(karl): Add vector defs/uses etc.
1926  is_literal_load := Rn == Pc;
1927*Vldr32 *Vldr
1928  single_reg := true;
1929  d := D:Vd;
1930  arch := VFPv2;
1931*Vldr64 *Vldr
1932  single_reg := false;
1933  d := D:Vd;
1934  arch := (VFPv2, AdvSIMD);
1935*Vstr *VdRnImm
1936  # TODO(karl): Add vector defs/uses etc.
1937  safety := n == Pc => FORBIDDEN_OPERANDS;
1938*Vstr32 *Vstr
1939  single_reg := true;
1940  d := Vd:D;
1941  arch := VFPv2;
1942*Vstr64 *Vstr
1943  single_reg := false;
1944  d := D:Vd;
1945  arch := (VFPv2, AdvSIMD);
1946*Vstackop *VdRegs
1947  # TODO(karl): Add vector defs/uses etc.
1948  base := Sp;
1949  small_imm_base_wb := true;
1950  defs := {Sp};
1951  uses := {Sp};
1952*Vpop *Vstackop
1953*Vpop32 *Vpop
1954  single_regs := true; d := Vd:D;
1955  regs := imm8;
1956  safety := regs == 0 | d + regs > 32 => UNPREDICTABLE;
1957  arch := VFPv2;
1958*Vpop64 *Vpop
1959  single_regs := false; d := D:Vd;
1960  regs := imm8 / 2;
1961  safety := regs == 0 | regs > 16 | d + regs > 32 => UNPREDICTABLE &
1962            VFPSmallRegisterBank() & d + regs > 16 => UNPREDICTABLE &
1963            imm8(0) == 1 => DEPRECATED;
1964  arch := (VFPv2, AdvSIMD);
1965*Vpush *Vstackop
1966*Vpush32 *Vpush
1967  single_regs := true; d := Vd:D;
1968  regs := imm8;
1969  safety := regs == 0 | d + regs > 32 => UNPREDICTABLE;
1970  arch := VFPv2;
1971*Vpush64 *Vpush
1972  single_regs := false; d := D:Vd;
1973  regs := imm8 / 2;
1974  safety := regs == 0 | regs > 16 | d + regs > 32 => UNPREDICTABLE &
1975            VFPSmallRegisterBank() & d + regs > 16 => UNPREDICTABLE &
1976            imm8(0) == 1 => DEPRECATED;
1977  arch := (VFPv2, AdvSIMD);
1978*VdRnRegs *VdRegs
1979  { cond(31:28), P(24), U(23), D(22), W(21), Rn(19:16),
1980    Vd(15:12), imm8(7:0) }
1981  # Valid combinations are: PUW = 010 (IA without !)
1982  #                             = 011 (IA without !)
1983  #                             = 101 (IA ith !)
1984  add := U=1; wback := W=1;
1985  n := Rn;
1986  base := Rn;
1987  small_imm_base_wb := wback;
1988  defs := {Rn if wback else None};
1989  uses := {Rn};
1990  safety := P=0 & U=0 & W=0 => DECODER_ERROR &
1991            P=1 & W=0 => DECODER_ERROR &  # VLDR/VSTR
1992            P == U & W=1 => UNDEFINED &
1993            n == Pc & wback => UNPREDICTABLE;
1994*Vldm *VdRnRegs
1995  # TODO(karl): Add vector defs/uses etc.
1996  is_literal_load := Rn == Pc;
1997  safety := super.safety &
1998            P=0 & U=1 & W=1 & Rn == Sp => DECODER_ERROR;  # VPOP
1999*Vldm32 *Vldm
2000  single_regs := true;
2001  d := Vd:D;  regs := imm8;
2002  safety := super.safety &
2003            regs == 0 | d + regs > 32 => UNPREDICTABLE;
2004  arch := VFPv2;
2005*Vldm64 *Vldm
2006  single_regs := false;
2007  d := D:Vd;  regs := imm8 / 2;
2008  safety := super.safety &
2009            regs == 0 | regs > 16 | d + regs > 32 => UNPREDICTABLE &
2010            VFPSmallRegisterBank() & d + regs > 16 => UNPREDICTABLE &
2011            imm8(0) == 1 => DEPRECATED;
2012  arch := (VFPv2, AdvSIMD);
2013*Vstm *VdRnRegs
2014  # TODO(karl): Add vector defs/uses etc.
2015  safety := super.safety &
2016            P=1 & U=0 & W=1 & Rn == Sp => DECODER_ERROR &  # VPUSH
2017            Rn == Pc => FORBIDDEN_OPERANDS;
2018*Vstm32 *Vstm
2019  single_regs := true;
2020  d := Vd:D;  regs := imm8;
2021  safety := super.safety &
2022            regs == 0 | d + regs > 32 => UNPREDICTABLE;
2023  arch := VFPv2;
2024*Vstm64 *Vstm
2025  single_regs := false;
2026  d := D:Vd;  regs := imm8 / 2;
2027  safety := super.safety &
2028            regs == 0 | regs > 16 | d + regs > 32 => UNPREDICTABLE &
2029            VFPSmallRegisterBank() & d + regs > 16 => UNPREDICTABLE &
2030            imm8(0) == 1 => DEPRECATED;
2031  arch := (VFPv2, AdvSIMD);
2032+--
2033# TODO(jfb) The architecture for these instructions only includes Advanced SIMD
2034#           for the 64-bit variants (coproc==0b1011).
2035#
2036# Note: For ease of implementation, we have added field S(8) to capture
2037# whether the instruction is single (32) or double (64). This corresponds
2038# to matching coproc(11:8)=101x.
2039| opcode(24:20) Rn(19:16) S(8)
2040| 0010x         -         - -> transfer_between_arm_core_and_extension_registers_64_bit
2041| 01x00         -         0 = *Vstm32
2042                               pattern := cccc110pudw0nnnndddd1010iiiiiiii;
2043                               rule := VSTM;
2044| "             "         1 = *Vstm64
2045                               pattern := cccc110pudw0nnnndddd1011iiiiiiii;
2046                               rule := VSTM;
2047| 01x10         -         0 = *Vstm32
2048                               pattern := cccc110pudw0nnnndddd1010iiiiiiii;
2049                               rule := VSTM;
2050| "             "         1 = *Vstm64
2051                               pattern := cccc110pudw0nnnndddd1011iiiiiiii;
2052                               rule := VSTM;
2053| 1xx00         -         0 = *Vstr32
2054                               pattern := cccc1101ud00nnnndddd1010iiiiiiii;
2055                               rule := VSTR;
2056| "             "         1 = *Vstr64
2057                               pattern := cccc1101ud00nnnndddd1011iiiiiiii;
2058                               rule := VSTR;
2059| 10x10         ~1101     0 = *Vstm32
2060                               pattern := cccc110pudw0nnnndddd1010iiiiiiii;
2061                               rule := VSTM;
2062| "             "         1 = *Vstm64
2063                               pattern := cccc110pudw0nnnndddd1011iiiiiiii;
2064                               rule := VSTM;
2065| "             1101      0 = *Vpush32
2066                               pattern := cccc11010d101101dddd1010iiiiiiii;
2067                               rule := VPUSH;
2068| "             "         1 = *Vpush64
2069                               pattern := cccc11010d101101dddd1011iiiiiiii;
2070                               rule := VPUSH;
2071| 01x01         -         0 = *Vldm32
2072                               pattern := cccc110pudw1nnnndddd1010iiiiiiii;
2073                               rule := VLDM;
2074| "             "         1 = *Vldm64
2075                               pattern := cccc110pudw1nnnndddd1011iiiiiiii;
2076                               rule := VLDM;
2077| 01x11         ~1101     0 = *Vldm32
2078                               pattern := cccc110pudw1nnnndddd1010iiiiiiii;
2079                               rule := VLDM;
2080| "             "         1 = *Vldm64
2081                               pattern := cccc110pudw1nnnndddd1011iiiiiiii;
2082                               rule := VLDM;
2083| "             1101      0 = *Vpop32
2084                               pattern := cccc11001d111101dddd1010iiiiiiii;
2085                               rule := VPOP;
2086| "             "         1 = *Vpop64
2087                               pattern := cccc11001d111101dddd1011iiiiiiii;
2088                               rule := VPOP;
2089| 1xx01         -         0 = *Vldr32
2090                               pattern := cccc1101ud01nnnndddd1010iiiiiiii;
2091                               rule := VLDR;
2092| "             "         1 = *Vldr64
2093                               pattern := cccc1101ud01nnnndddd1011iiiiiiii;
2094                               rule := VLDR;
2095| 10x11         -         0 = *Vldm32
2096                               pattern := cccc110pudw1nnnndddd1010iiiiiiii;
2097                               rule := VLDM;
2098| "             "         1 = *Vldm64
2099                               pattern := cccc110pudw1nnnndddd1011iiiiiiii;
2100                               rule := VLDM;
2101+--
2102
2103+-- transfer_between_arm_core_and_extension_register_8_16_and_32_bit (A7.8)
2104*VmovSnRt
2105  { cond(31:28), op(20), Vn(19:16), Rt(15:12), N(7) }
2106  to_arm_register := op=1; t := Rt; n := Vn:N;
2107  defs := {Rt if to_arm_register else None};
2108  uses := {Rt if not to_arm_register else None};
2109  safety := t == Pc => UNPREDICTABLE;
2110  # TODO(karl): Add vector defs/uses etc.
2111*UsesRt
2112  { cond(31:28), Rt(15:12) }
2113  t := Rt;
2114  defs := {};
2115  uses := {Rt};
2116  safety := t == Pc => UNPREDICTABLE;
2117  # TODO(karl): Add vector defs/uses etc.
2118*Vdup
2119  { cond(31:28), B(22), Q(21), Vd(19:16), Rt(15:12), D(7), E(5) }
2120  d := D:Vd; t := Rt; regs := 1 if Q=0 else 2;
2121  sel := B:E;
2122  esize := 32  if sel=00 else
2123           16  if sel=01 else
2124           8   if sel=10 else
2125           0;  # i.e. undefined.
2126  elements := 2  if sel=00 else
2127              4  if sel=01 else
2128              8  if sel=10 else
2129              0; # i.e. undefined.
2130  defs := {};
2131  uses := {Rt};
2132  safety := cond != cond_AL => DEPRECATED &
2133            Q=1 & Vd(0)=1 => UNDEFINED &
2134            sel=11 => UNDEFINED &
2135            t == Pc => UNPREDICTABLE;
2136  # TODO(karl): Add vector defs/uses etc.
2137*VmovDdRt
2138  { cond(31:28), opc1(22:21), Vd(19:16), Rt(15:12), D(7), opc2(6:5) }
2139  sel := opc1:opc2;
2140  advsimd := sel in bitset {1xxx, 0xx1};
2141  esize := 8   if sel=1xxx else
2142           16  if sel=0xx1 else
2143           32  if sel=0x00 else
2144           0;  # i.e. undefined.
2145  index := opc1(0):opc2    if sel=1xxx else
2146           opc1(0):opc2(1) if sel=0xx1 else
2147           opc1(0)         if sel=0x00 else
2148           0;              # i.e undefined.
2149  d := D:Vd; t := Rt;
2150  defs := {};
2151  uses := {Rt};
2152  safety := sel=0x10 => UNDEFINED &
2153            t == Pc => UNPREDICTABLE;
2154  # TODO(karl): Add vector defs/uses etc.
2155*VmovRtFPSCR
2156  { cond(31:28), Rt(15:12) }
2157  t := Rt;
2158  defs := {NZCV if t == Pc else Rt};
2159  # TODO(karl): Add vector defs/uses etc.
2160*VmovRtDd
2161  { cond(31:28), U(23), opc1(22:21), Vn(19:16), Rt(15:12), N(7), opc2(6:5) }
2162  sel := U:opc1:opc2;
2163  advsimd := sel in bitset {x1xxx, x0xx1};
2164  esize := 8   if sel=x1xxx else
2165           16  if sel=x0xx1 else
2166           32  if sel=00x00 else
2167           0;  # i.e. undefined.
2168  index := opc1(0):opc2    if sel=x1xxx else
2169           opc1(0):opc2(1) if sel=x0xx1 else
2170           opc1(0)         if sel=00x00 else
2171           0;              # i.e. undefined
2172  t := Rt; n := N:Vn; unsigned := U=1;
2173  defs := {Rt};
2174  safety := sel in bitset {10x00, x0x10} => UNDEFINED &
2175            t == Pc => UNPREDICTABLE;
2176  # TODO(karl): Add vector defs/uses etc.
2177+--
2178| L(20) C(8) A(23:21) B(6:5)
2179| 0     0    000      -      =
2180        *VmovSnRt  pattern := cccc1110000onnnntttt1010n0010000;
2181        rule := VMOV_between_ARM_core_register_and_single_precision_register;
2182        arch := VFPv2;
2183| "     "    111      -      =
2184        *UsesRt  pattern := cccc111011100001tttt101000010000;
2185        rule := VMSR; arch := (VFPv2, AdvSIMD);
2186| 0     1    0xx      -      =
2187        *VmovDdRt  pattern := cccc11100ii0ddddtttt1011dii10000;
2188        rule := VMOV_ARM_core_register_to_scalar;  arch := (VFPv2, AdvSIMD);
2189| "     "    1xx      0x     =
2190        *Vdup  pattern := cccc11101bq0ddddtttt1011d0e10000;
2191        rule := VDUP_ARM_core_register;  arch := AdvSIMD;
2192| 1     0    000      -      =
2193        *VmovSnRt  pattern := cccc1110000xnnnntttt1010n0010000;
2194        rule := VMOV_between_ARM_core_register_and_single_precision_register;
2195        arch := VFPv2;
2196| "     "    111      -      =
2197        *VmovRtFPSCR  pattern := cccc111011110001tttt101000010000;
2198        rule := VMRS;  arch := (VFPv2, AdvSIMD);
2199| "     1    xxx      -      =
2200        *VmovRtDd pattern := cccc1110iii1nnnntttt1011nii10000;
2201        rule := MOVE_scalar_to_ARM_core_register;  arch := (VFPv2, AdvSIMD);
2202| else: = *Undefined  # Note on table description.
2203+--
2204
2205+-- transfer_between_arm_core_and_extension_registers_64_bit (A7.9)
2206*VmovXRtRt2
2207  { cond(31:28), op(20), Rt2(19:16), Rt(15:12), M(5), Vm(3:0) }
2208  to_arm_registers := op=1; t := Rt; t2 := Rt2;
2209  defs := {Rt, Rt2} if to_arm_registers else {};
2210  uses := {} if to_arm_registers else {Rt, Rt2};
2211*VmovSnRtRt2 *VmovXRtRt2
2212  m := Vm:M;
2213  safety := Pc in {t, t2} | m == 31 => UNPREDICTABLE &
2214            to_arm_registers & t == t2 => UNPREDICTABLE;
2215  # TODO(karl): Add vector defs/uses etc.
2216*VmovDmRtRt2 *VmovXRtRt2
2217  m := M:Vm;
2218  safety := Pc in {t, t2} => UNPREDICTABLE &
2219            to_arm_registers & t == t2 => UNPREDICTABLE;
2220  # TODO(karl): Add vector defs/uses etc.
2221+--
2222| C(8) op(7:4)
2223| 0    00x1    = *VmovSnRtRt2
2224                  pattern := cccc1100010otttttttt101000m1mmmm;
2225                  rule := VMOV_between_two_ARM_core_registers_and_two_single_precision_registers;
2226                  arch := (VFPv2);
2227| 1    00x1    = *VmovDmRtRt2
2228                  pattern := cccc1100010otttttttt101100m1mmmm;
2229                  rule := VMOV_between_two_ARM_core_registers_and_a_doubleword_extension_register;
2230                  arch := (VFPv2, AdvSIMD);
2231| else:        = *Undefined
2232+--
2233
2234+-- unconditional_instructions (See Section A5.7)
2235| op1(27:20) op(4) Rn(19:16) op1_repeated(27:20)
2236| 0xxx_xxxx  -     -         - ->
2237        memory_hints_advanced_simd_instructions_and_miscellaneous_instructions
2238| 100x_x1x0  -     -         - =
2239       *Forbidden  pattern := 1111100pu1w0110100000101000iiiii;
2240        rule := SRS;  arch := v6;
2241| 100x_x0x1  -     -         - =
2242       *Forbidden  pattern := 1111100pu0w1nnnn0000101000000000;
2243        rule := RFE;  arch := v6;
2244| 101x_xxxx  -     -         - =
2245       *Forbidden  pattern := 1111101hiiiiiiiiiiiiiiiiiiiiiiii;
2246        # Forbidden because it switches to Thumb.
2247        rule := BLX_immediate;  arch := v5;
2248| 110x_xxx0   -     -        ~1100_0x00 =
2249       *Forbidden  pattern := 1111110pudw0nnnniiiiiiiiiiiiiiii;
2250        rule := STC2;  arch := v5;
2251| 110x_xxx1  -     ~1111     ~1100_0x01 =
2252       *Forbidden  pattern := 1111110pudw1nnnniiiiiiiiiiiiiiii;
2253        rule := LDC2_immediate;  arch := v5;
2254| 110x_xxx1  -     1111      ~1100_0x01 =
2255       *Forbidden  pattern := 1111110pudw11111iiiiiiiiiiiiiiii;
2256        rule := LDC2_literal;  arch := v5;
2257| 1100_0100  -     -         - =
2258       *Forbidden  pattern := 111111000100ssssttttiiiiiiiiiiii;
2259        rule := MCRR2;  arch := v6;
2260| 1100_0101  -     -         - =
2261       *Forbidden  pattern := 111111000101ssssttttiiiiiiiiiiii;
2262        rule := MRRC2;  arch := v6;
2263| 1110_xxxx  0     -         - =
2264       *Forbidden  pattern := 11111110iiiiiiiiiiiiiiiiiii0iiii;
2265        rule := CDP2;  arch := v5;
2266| 1110_xxx0  1     -         - =
2267       *Forbidden  pattern := 11111110iii0iiiittttiiiiiii1iiii;
2268        rule := MCR2;  arch := v5;
2269| 1110_xxx1  1     -         - =
2270       *Forbidden  pattern := 11111110iii1iiiittttiiiiiii1iiii;
2271        rule := MRC2;  arch := v5;
2272| else:                        = *Undefined
2273+--
2274
2275+-- memory_hints_advanced_simd_instructions_and_miscellaneous_instructions
2276    (See Section A5.7.1)
2277*Barrier
2278  { option(3:0) }
2279  defs := {};
2280  uses := {};
2281*DataBarrier *Barrier
2282  safety := not option in
2283            {'1111', '1110', '1011', '1010',
2284             '0111', '0110', '0011', '0010'} => FORBIDDEN_OPERANDS;
2285*InstructionBarrier *Barrier
2286  safety := option=~1111 => FORBIDDEN_OPERANDS;
2287*PreloadLit
2288  { U(23), imm12(11:0) }
2289  imm32 := ZeroExtend(imm12, 32);  add := U=1;
2290  base := Pc;
2291  defs := {};
2292  uses := {Pc};
2293  is_literal_load := true;
2294  safety := true => MAY_BE_SAFE;
2295*PreloadData *PreloadLit
2296  { U(23), R(22), Rn(19:16), imm12(11:0) }
2297  is_pldw := R=0;
2298  base := Rn;
2299  uses := {Rn};
2300  safety := Rn=1111 => DECODER_ERROR;
2301  is_literal_load := base == Pc;
2302*PreloadDataReg
2303  { U(23), R(22), Rn(19:16), imm5(11:7), type(6:5), Rm(3:0) }
2304  add := U=1; is_pldw := R=1;
2305  shift := DecodeImmShift(type, imm5);
2306  base := Rn;
2307  defs := {};
2308  uses := {Rm, Rn};
2309  safety :=  Rm == Pc | (Rn == Pc & is_pldw) => UNPREDICTABLE &
2310             true => FORBIDDEN_OPERANDS;
2311*PreloadInst
2312  { U(23), Rn(19:16), imm12(11:0) }
2313  imm32 := ZeroExtend(imm12, 32);  add := U=1;
2314  base := Rn;
2315  defs := {};
2316  uses := {Rn};
2317  safety := true => MAY_BE_SAFE;
2318  is_literal_load := Rn == Pc;
2319*PreloadInstReg
2320  { U(23), Rn(19:16), imm5(11:7), type(6:5), Rm(3:0) }
2321  add := U=1;
2322  shift := DecodeImmShift(type, imm5);
2323  base := Rn;
2324  defs := {};
2325  uses := {Rm, Rn};
2326  safety :=  Rm == Pc => UNPREDICTABLE &
2327             true => FORBIDDEN_OPERANDS;
2328+--
2329| op1(26:20) op2(7:4) Rn(19:16)
2330| 001_0000   xx0x     xxx0  = *Forbidden
2331                               pattern := 111100010000iii00000000iii0iiiii;
2332                               rule := CPS;
2333                               arch := v6;
2334| 001_0000   0000     xxx1  = *Forbidden
2335                               pattern := 1111000100000001000000i000000000;
2336                               rule := SETEND;
2337                               arch := v6;
2338| 01x_xxxx   -        -     -> advanced_simd_data_processing_instructions
2339| 100_xxx0   -        -     ->
2340               advanced_simd_element_or_structure_load_store_instructions
2341| 100_x001   -        -     = *Forbidden
2342                               # Manual says these are treated as NOPs,
2343                               # disallow until proven necessary.
2344                               pattern := 11110100x001xxxxxxxxxxxxxxxxxxxx;
2345                               arch := MPExt;
2346| 100_x101   -        -     = *PreloadInst
2347                               pattern := 11110100u101nnnn1111iiiiiiiiiiii;
2348                               rule := PLI_immediate_literal;
2349                               arch := v7;
2350| 100_xx11   -        -     = *Unpredictable
2351                               pattern := 11110100xx11xxxxxxxxxxxxxxxxxxxx;
2352| 101_x001   -        ~1111 = *PreloadData
2353                               pattern := 11110101ur01nnnn1111iiiiiiiiiiii;
2354                               rule := PLD_PLDW_immediate;
2355                               arch := MPExt;
2356| "          -        1111  = *Unpredictable
2357                               pattern := 11110101x001xxxxxxxxxxxxxxxxxxxx;
2358| 101_x101   -        ~1111 = *PreloadData
2359                               pattern := 11110101ur01nnnn1111iiiiiiiiiiii;
2360                               rule := PLD_PLDW_immediate;
2361                               arch := v5TE;
2362| "          -        1111  = *PreloadLit
2363                               pattern := 11110101u10111111111iiiiiiiiiiii;
2364                               rule := PLD_literal;
2365                               arch := v5TE;
2366| 101_0011   -        -     = *Unpredictable
2367                               pattern := 111101010011xxxxxxxxxxxxxxxxxxxx;
2368| 101_0111   0000     -     = *Unpredictable
2369                               pattern := 111101010111xxxxxxxxxxxx0000xxxx;
2370| "          0001     -     = *Forbidden
2371                               # Might affect global exclusive access record.
2372                               # Disallow until proven useful.
2373                               pattern := 11110101011111111111000000011111;
2374                               rule := CLREX;
2375                               arch := V6K;
2376| "          001x     -     = *Unpredictable
2377                               pattern := 111101010111xxxxxxxxxxxx001xxxxx;
2378| "          0100     -     = *DataBarrier
2379                               pattern := 1111010101111111111100000100xxxx;
2380                               rule := DSB;
2381                               arch := v6T2;
2382| "          0101     -     = *DataBarrier
2383                               pattern := 1111010101111111111100000101xxxx;
2384                               rule := DMB;
2385                               arch := v7;
2386| "          0110     -     = *InstructionBarrier
2387                               pattern := 1111010101111111111100000110xxxx;
2388                               rule := ISB;
2389                               arch := v6T2;
2390| "          0111     -     = *Unpredictable
2391                               pattern := 111101010111xxxxxxxxxxxx0111xxxx;
2392| "          1xxx     -     = *Unpredictable
2393                               pattern := 111101010111xxxxxxxxxxxx1xxxxxxx;
2394| 101_1x11   -        -     = *Unpredictable
2395                               pattern := 111101011x11xxxxxxxxxxxxxxxxxxxx;
2396| 110_x001   xxx0     -     = *Forbidden
2397                               # Manual says these are treated as NOPs,
2398                               # disallow until proven necessary.
2399                               pattern := 11110110x001xxxxxxxxxxxxxxx0xxxx;
2400                               arch := MPExt;
2401| 110_x101   xxx0     -     = *PreloadInstReg
2402                               pattern := 11110110u101nnnn1111iiiiitt0mmmm;
2403                               rule := PLI_register;
2404                               arch := v7;
2405| 111_x001   xxx0     -     = *PreloadDataReg
2406                               pattern := 11110111u001nnnn1111iiiiitt0mmmm;
2407                               rule := PLD_PLDW_register;
2408                               arch := MPExt;
2409| 111_x101   xxx0     -     = *PreloadDataReg
2410                               pattern := 11110111u101nnnn1111iiiiitt0mmmm;
2411                               rule := PLD_PLDW_register;
2412                               arch := v5TE;
2413| 11x_xx11   xxx0     -     = *Unpredictable
2414                               pattern := 1111011xxx11xxxxxxxxxxxxxxx0xxxx;
2415| else:                     = *Undefined   # See note on ARM table.
2416+--
2417
2418+-- advanced_simd_data_processing_instructions (See Section A7.4)
2419*VdVm
2420   { D(22), Vd(15:12), M(5), Vm(3:0) }
2421   d := D:Vd; m := M:Vm;
2422   # TODO(karl): Add vector defs/uses etc.
2423   defs := {};
2424   uses := {};
2425*VdVnVm *VdVm
2426   { D(22), Vn(19:16), Vd(15:12), N(7), M(5), Vm(3:0) }
2427   n := N:Vn;
2428*Vext *VdVnVm
2429   { D(22), Vn(19:16), Vd(15:12), imm4(11:8), N(7), Q(6), M(5), Vm(3:0) }
2430   quadword_operation := Q=1;
2431   position := 8 * imm4;
2432   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED &
2433             Q=0 & imm4(3)=1 => UNDEFINED;
2434*Vtbl *VdVnVm
2435   { D(22), Vn(19:16), Vd(15:12), len(9:8), N(7), op(6), M(5), Vm(3:0) }
2436   is_vtbl := op=0; length := len+1;
2437   # TODO(karl): Add vector uses. Note: Uses quite different from othe
2438   # instructions in this table because it changes with len.
2439   safety := n+length > 32 => UNPREDICTABLE;
2440*Vdup *VdVm
2441   { D(22), imm4(19:16), Vd(15:12), Q(6), M(5), Vm(3:0) }
2442   esize :=       8 if imm4=xxx1
2443            else 16 if imm4=xx10
2444            else 32 if imm4=x100
2445            else  0;   # i.e. not defined.
2446   elements :=      8 if imm4=xxx1
2447               else 4 if imm4=xx10
2448               else 2 if imm4=x100
2449               else 0;   # i.e. not defined.
2450   index :=      imm4(3:1) if imm4=xxx1
2451            else imm4(3:2) if imm4=xx10
2452            else   imm4(3) if imm4=x100
2453            else         0;   # i.e. not defined.
2454   regs := 1 if Q=0 else 2;
2455   safety := imm4=x000 => UNDEFINED &
2456             Q=1 & Vd(0)=1 => UNDEFINED;
2457+--
2458| U(24) A(23:19) B(11:8) C(7:4)
2459| -     0xxxx    -       -      -> simd_dp_3same
2460| "     1x000    -       0xx1   -> simd_dp_1imm
2461| "     1x001    -       0xx1   -> simd_dp_2shift
2462| "     1x01x    -       0xx1   "
2463| "     1x1xx    -       0xx1   "
2464| "     1xxxx    -       1xx1   "
2465| "     1x0xx    -       x0x0   -> simd_dp_3diff
2466| "     1x10x    -       x0x0   "
2467| "     1x0xx    -       x1x0   -> simd_dp_2scalar
2468| "     1x10x    -       x1x0   "
2469| 0     1x11x    -       xxx0   = *Vext
2470                                   pattern := 111100101d11nnnnddddiiiinqm0mmmm;
2471                                   rule := VEXT;
2472| 1     1x11x    0xxx    xxx0   -> simd_dp_2misc
2473| "     "        10xx    xxx0   = *Vtbl
2474                                   pattern := 111100111d11nnnndddd10ccnpm0mmmm;
2475                                   rule := VTBL_VTBX;
2476| "     "        1100    0xx0   = *Vdup
2477                                   pattern := 111100111d11iiiidddd11000qm0mmmm;
2478                                   rule := VDUP_scalar;
2479| else:                         = *Undefined  # Note on table description.
2480+--
2481
2482+-- simd_dp_3same (See Section A7.4.1)
2483*V3RSL
2484   { U(24), D(22), size(21:20), Vn(19:16), Vd(15:12), op(9),
2485     N(7), Q(6), M(5), Vm(3:0) }
2486   d := D:Vd; n := N:Vn; m := M:Vm;
2487   defs := {};  # Doesn't affect general purpose registers.
2488   uses := {};
2489   # TODO(karl): Add vector defs/uses etc.
2490   arch := ASIMD;
2491*V3RSL_DQ *V3RSL  # Uses Q registers if Q=1, D registers otherwise.
2492   # TODO(karl): Add vector defs/uses etc.
2493   regs := 1 if Q=0 else 2;
2494   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED;
2495*V3RSL_DQI *V3RSL_DQ
2496   # Works on 8, 16, 32, and 64-bit integers;
2497   # TODO(karl): Add vector defs/uses etc.
2498   unsigned := U=1;
2499   esize := 8  << size; elements := 64 / esize;
2500*V3RSL_DQI16_32 *V3RSL_DQI
2501   # Works on 16 and 32-bit integers.
2502   # TODO(karl): Add vector defs/uses etc.
2503   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED &
2504             (size=11 | size=00) => UNDEFINED;
2505*V3RSL_DQI8_16_32 *V3RSL_DQI
2506   # Only works on 8, 16, and 32-bit integers.
2507   # TODO(karl): Add vector defs/uses etc.
2508   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED &
2509             size=11 => UNDEFINED;
2510*V3RSL_DQI8P *V3RSL_DQI
2511   # TODO(karl): Add vector defs/uses etc.
2512   # Operates on 8-bit and polynomials.
2513   unsigned := false;
2514   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED &
2515             size=~00 => UNDEFINED;
2516*V3RSL32 *V3RSL  # Operates on 32-bit values.
2517   sz := size(0); op1_neg := size(1);
2518   esize := 32; elements := 2;
2519*V3RSL32P *V3RSL32  # Operates on pairs of 32-bit values.
2520   safety := sz=1 | Q=1 => UNDEFINED;
2521*V3RSL32_DQ *V3RSL32  # Uses Q registers if Q=1, D registers otherwise.
2522   # TODO(karl): Add vector defs/uses etc.
2523   safety := Q=1 & (Vd(0)=1 | Vn(0)=1 | Vm(0)=1) => UNDEFINED &
2524             sz=1 =>UNDEFINED;
2525*V3RSL_DI *V3RSL  # double word (D registers) 8, 16, and 32 integers
2526   # TODO(karl): Add vector defs/uses etc.
2527   unsigned := U=1;
2528   esize := 8  << size; elements := 64 / esize;
2529   safety := size=11 => UNDEFINED & Q=1 => UNDEFINED;
2530+--
2531# To further separate instruction selection, we have duplicated
2532# some rows, filling in possible values for rows U and B and C.
2533| A(11:8) B(4) U(24) C(21:20)
2534| 0000    0    -     -        = *V3RSL_DQI8_16_32
2535                                pattern := 1111001u0dssnnnndddd0000nqm0mmmm;
2536                                rule := VHADD;
2537| "       1    -     -        = *V3RSL_DQI
2538                                pattern := 1111001u0dssnnnndddd0000nqm1mmmm;
2539                                rule := VQADD;
2540| 0001    0    -     -        = *V3RSL_DQI8_16_32
2541                                pattern := 1111001u0dssnnnndddd0001nqm0mmmm;
2542                                rule := VRHADD;
2543| "       1    0     00       = *V3RSL_DQ
2544                                pattern := 111100100d00nnnndddd0001nqm1mmmm;
2545                                rule := VAND_register;
2546| "       "    "     01       = *V3RSL_DQ
2547                                pattern := 111100100d01nnnndddd0001nqm1mmmm;
2548                                rule := VBIC_register;
2549| "       "    "     10       = *V3RSL_DQ
2550                                pattern := 111100100d10nnnndddd0001nqm1mmmm;
2551                                rule := VORR_register_or_VMOV_register_A1;
2552| "       "    "     11       = *V3RSL_DQ
2553                                pattern := 111100100d11nnnndddd0001nqm1mmmm;
2554                                rule := VORN_register;
2555| "       1    1     00       = *V3RSL_DQ
2556                                pattern := 111100110d00nnnndddd0001nqm1mmmm;
2557                                rule := VEOR;
2558| "       "    "     01       = *V3RSL_DQ
2559                                pattern := 111100110d01nnnndddd0001nqm1mmmm;
2560                                rule := VBSL;
2561| "       "    "     10       = *V3RSL_DQ
2562                                pattern := 111100110d10nnnndddd0001nqm1mmmm;
2563                                rule := VBIT;
2564| "       "    "     11       = *V3RSL_DQ
2565                                pattern := 111100110d11nnnndddd0001nqm1mmmm;
2566                                rule := VBIF;
2567| 0010    0    -     -        = *V3RSL_DQI8_16_32
2568                                pattern := 1111001u0dssnnnndddd0010nqm0mmmm;
2569                                rule := VHSUB;
2570| "       1    -     -        = *V3RSL_DQI
2571                                pattern := 1111001u0dssnnnndddd0010nqm1mmmm;
2572                                rule := VQSUB;
2573| 0011    0    -     -        = *V3RSL_DQI8_16_32
2574                                pattern := 1111001u0dssnnnndddd0011nqm0mmmm;
2575                                rule := VCGT_register_A1;
2576| "       1    -     -        = *V3RSL_DQI8_16_32
2577                                pattern := 1111001u0dssnnnndddd0011nqm1mmmm;
2578                                rule := VCGE_register_A1;
2579| 0100    0    -     -        = *V3RSL_DQI
2580                                pattern := 1111001u0dssnnnndddd0100nqm0mmmm;
2581                                rule := VSHL_register;
2582| "       1    -     -        = *V3RSL_DQI
2583                                pattern := 1111001u0dssnnnndddd0100nqm1mmmm;
2584                                rule := VQSHL_register;
2585| 0101    0    -     -        = *V3RSL_DQI
2586                                pattern := 1111001u0dssnnnndddd0101nqm0mmmm;
2587                                rule := VRSHL;
2588| "       1    -     -        = *V3RSL_DQI
2589                                pattern := 1111001u0dssnnnndddd0101nqm1mmmm;
2590                                rule := VQRSHL;
2591| 0110    0    -     -        = *V3RSL_DQI8_16_32
2592                                pattern := 1111001u0dssnnnndddd0110nqm0mmmm;
2593                                rule := VMAX;
2594| "       1    -     -        = *V3RSL_DQI8_16_32
2595                                pattern := 1111001u0dssnnnndddd0110nqm1mmmm;
2596                                rule := VMIN;
2597| 0111    0    -     -        = *V3RSL_DQI8_16_32
2598                                pattern := 1111001u0dssnnnndddd0111nqm0mmmm;
2599                                rule := VABD;
2600| "       1    -     -        = *V3RSL_DQI8_16_32
2601                                pattern := 1111001u0dssnnnndddd0111nqm1mmmm;
2602                                rule := VABA;
2603| 1000    0    0     -        = *V3RSL_DQI
2604                                pattern := 111100100dssnnnndddd1000nqm0mmmm;
2605                                rule := VADD_integer;
2606| "       "    1     -        = *V3RSL_DQI
2607                                pattern := 111100110dssnnnndddd1000nqm0mmmm;
2608                                rule := VSUB_integer;
2609| "       1    0     -        = *V3RSL_DQI8_16_32
2610                                pattern := 111100100dssnnnndddd1000nqm1mmmm;
2611                                rule := VTST;
2612| "       "    1     -        = *V3RSL_DQI8_16_32
2613                                pattern := 111100110dssnnnndddd1000nqm1mmmm;
2614                                rule := VCEQ_register_A1;
2615| 1001    0    0     -        = *V3RSL_DQI8_16_32
2616                                pattern := 1111001u0dssnnnndddd1001nqm0mmmm;
2617                                rule := VMLA_integer_A1;
2618| "       "    1     -        = *V3RSL_DQI8_16_32
2619                                pattern := 1111001u0dssnnnndddd1001nqm0mmmm;
2620                                rule := VMLS_integer_A1;
2621| "       1    0     -        = *V3RSL_DQI8_16_32
2622                                pattern := 1111001u0dssnnnndddd1001nqm1mmmm;
2623                                rule := VMUL_integer_A1;
2624| "       1    1     -        = *V3RSL_DQI8P
2625                                pattern := 1111001u0dssnnnndddd1001nqm1mmmm;
2626                                rule := VMUL_polynomial_A1;
2627| 1010    0    -     -        = *V3RSL_DI
2628                                pattern := 1111001u0dssnnnndddd1010n0m0mmmm;
2629                                rule := VPMAX;
2630| "       1    -     -        = *V3RSL_DI
2631                                pattern := 1111001u0dssnnnndddd1010n0m1mmmm;
2632                                rule := VPMIN;
2633| 1011    0    0     -        = *V3RSL_DQI16_32
2634                                pattern := 111100100dssnnnndddd1011nqm0mmmm;
2635                                rule := VQDMULH_A1;
2636| "       "    1     -        = *V3RSL_DQI16_32
2637                                pattern := 111100110dssnnnndddd1011nqm0mmmm;
2638                                rule := VQRDMULH_A1;
2639| "       1    0     -        = *V3RSL_DI
2640                                pattern := 111100100dssnnnndddd1011n0m1mmmm;
2641                                rule := VPADD_integer;
2642| 1100    1    0     0x       = *V3RSL32_DQ
2643                                pattern := 111100100d00nnnndddd1100nqm1mmmm;
2644                                rule := VFMA_A1;
2645                                arch := ASIMDv2;
2646| "       "    "     1x       = *V3RSL32_DQ
2647                                pattern := 111100100d10nnnndddd1100nqm1mmmm;
2648                                rule := VFMS_A1;
2649                                arch := ASIMDv2;
2650| 1101    0    0     0x       = *V3RSL32_DQ
2651                                pattern := 111100100d0snnnndddd1101nqm0mmmm;
2652                                rule := VADD_floating_point_A1;
2653| "       "    "     1x       = *V3RSL32_DQ
2654                                pattern := 111100100d1snnnndddd1101nqm0mmmm;
2655                                rule := VSUB_floating_point_A1;
2656| "       "    1     0x       = *V3RSL32P
2657                                pattern := 111100110d0snnnndddd1101nqm0mmmm;
2658                                rule := VPADD_floating_point;
2659| "       "    "     1x       = *V3RSL32_DQ
2660                                pattern := 111100110d1snnnndddd1101nqm0mmmm;
2661                                rule := VABD_floating_point;
2662| "       1    0     0x       = *V3RSL32_DQ
2663                                pattern := 111100100dpsnnnndddd1101nqm1mmmm;
2664                                rule := VMLA_floating_point_A1;
2665| "       "    "     1x       = *V3RSL32_DQ
2666                                pattern := 111100100dpsnnnndddd1101nqm1mmmm;
2667                                rule := VMLS_floating_point_A1;
2668| "       "    1     0x       = *V3RSL32_DQ
2669                                pattern := 111100110d0snnnndddd1101nqm1mmmm;
2670                                rule := VMUL_floating_point_A1;
2671| 1110    0    0     0x       = *V3RSL32_DQ
2672                                pattern := 111100100d0snnnndddd1110nqm0mmmm;
2673                                rule := VCEQ_register_A2;
2674| "       "    1     0x       = *V3RSL32_DQ
2675                                pattern := 111100110d0snnnndddd1110nqm0mmmm;
2676                                rule := VCGE_register_A2;
2677| "       "    "     1x       = *V3RSL32_DQ
2678                                pattern := 111100110d1snnnndddd1110nqm0mmmm;
2679                                rule := VCGT_register_A2;
2680| "       1    1     0x       = *V3RSL32_DQ
2681                                pattern := 111100110dssnnnndddd1110nqm1mmmm;
2682                                rule := VACGE;
2683| "       "    "     1x       = *V3RSL32_DQ
2684                                pattern := 111100110dssnnnndddd1110nqm1mmmm;
2685                                rule := VACGT;
2686| 1111    0    0     0x       = *V3RSL32_DQ
2687                                pattern := 111100100dssnnnndddd1111nqm0mmmm;
2688                                rule := VMAX_floating_point;
2689| "       "    "     1x       = *V3RSL32_DQ
2690                                pattern := 111100100dssnnnndddd1111nqm0mmmm;
2691                                rule := VMIN_floating_point;
2692| "       "    1     0x       = *V3RSL32P
2693                                pattern := 111100110dssnnnndddd1111nqm0mmmm;
2694                                rule := VPMAX;
2695| "       "    "     1x       = *V3RSL32P
2696                                pattern := 111100110dssnnnndddd1111nqm0mmmm;
2697                                rule := VPMIN;
2698| "       1    0     0x       = *V3RSL32_DQ
2699                                pattern := 111100100d0snnnndddd1111nqm1mmmm;
2700                                rule := VRECPS;
2701| "       "    "     1x       = *V3RSL32_DQ
2702                                pattern := 111100100d1snnnndddd1111nqm1mmmm;
2703                                rule := VRSQRTS;
2704| else:                       = *Undefined
2705+--
2706
2707+-- simd_dp_3diff (See Section A7.4.2)
2708*V3RDL
2709   { U(24), D(22), size(21:20), Vn(19:16), Vd(15:12), op(8),
2710     N(7), M(5), Vm(3:0) }
2711   d := D:Vd; n := N:Vn; m := M:Vm;
2712   unsigned := U=1;
2713   esize := 8  << size; elements := 64 / esize;
2714   defs := {};  # Doesn't affect general purpose registers.
2715   uses := {};
2716*V3RDL_I8_16_32 *V3RDL
2717   # Allows 8, 16, and 32-bit integer values (defined by size).
2718   # TODO(karl): Add vector defs/uses etc.
2719   is_w := op=1;
2720   safety := size=11 => DECODER_ERROR &
2721             Vd(0)=1 | (op=1 & Vn(0)=1) => UNDEFINED;
2722*V3RDL_I16_32_64 *V3RDL
2723   # Allows 16, 32, and 64-bit operands (defined by 2*size).
2724   # TODO(karl): Add vector defs/uses etc.
2725   safety := size=11 => DECODER_ERROR &
2726             Vn(0)=1 | Vm(0)=1 => UNDEFINED;
2727*V3RDL_I8_16_32L *V3RDL
2728   # Allows 8, 16, and 32-bit operands, and long (i.e. double
2729   # sized) results.
2730   # TODO(karl): Add vector defs/uses etc.
2731   safety := size=11 => DECODER_ERROR &
2732             Vd(0)=1 => UNDEFINED;
2733*V3RDL_I16_32L *V3RDL
2734   # Allows 16 and 32-bit operands, and long (i.e. double sized)
2735   # results.
2736   # TODO(karl): Add vector defs/uses etc.
2737   add := op=0;
2738   m := Vm(2:0) if size=01 else Vm;
2739   safety := size=11 => DECODER_ERROR &
2740             size=00 | Vd(0)=1 => UNDEFINED;
2741*V3RDL_P8 *V3RDL
2742   # Defines an 8-bit polynomial vector operation.
2743   # TODO(karl): Add vector defs/uses etc.
2744   safety := size=11 => DECODER_ERROR &
2745             U=1 | size=~00 => UNDEFINED &
2746             Vd(0)=1 => UNDEFINED;
2747+--
2748| A(11:8) U(24)
2749| 000x    -     = *V3RDL_I8_16_32
2750                  pattern := 1111001u1dssnnnndddd000pn0m0mmmm;
2751                  is_vaddw := U=1;
2752                  rule := VADDL_VADDW;
2753| 001x    -     = *V3RDL_I8_16_32
2754                  pattern := 1111001u1dssnnnndddd001pn0m0mmmm;
2755                  rule := VSUBL_VSUBW;
2756| 0100    0     = *V3RDL_I16_32_64
2757                  pattern := 111100101dssnnnndddd0100n0m0mmmm;
2758                  rule := VADDHN;
2759| "       1     = *V3RDL_I16_32_64
2760                  pattern := 111100111dssnnnndddd0100n0m0mmmm;
2761                  rule := VRADDHN;
2762| 0101    -     = *V3RDL_I8_16_32L
2763                  pattern := 1111001u1dssnnnndddd0101n0m0mmmm;
2764                  rule := VABAL_A2;
2765| 0110    0     = *V3RDL_I16_32_64
2766                  pattern := 111100101dssnnnndddd0110n0m0mmmm;
2767                  rule := VSUBHN;
2768| "       1     = *V3RDL_I16_32_64
2769                  pattern := 111100111dssnnnndddd0110n0m0mmmm;
2770                  rule := VRSUBHN;
2771| 0111    -     = *V3RDL_I8_16_32L
2772                  pattern := 1111001u1dssnnnndddd0111n0m0mmmm;
2773                  rule := VABDL_integer_A2;
2774| 10x0    -     = *V3RDL_I8_16_32L
2775                  pattern := 1111001u1dssnnnndddd10p0n0m0mmmm;
2776                  rule := VMLAL_VMLSL_integer_A2;
2777| 10x1    0     = *V3RDL_I16_32L
2778                  pattern := 111100101dssnnnndddd10p1n0m0mmmm;
2779                  rule := VQDMLAL_VQDMLSL_A1;
2780| 1100    -     = *V3RDL_I8_16_32L  # Note: inst(9)=0, implying not polynomial.
2781                  pattern := 1111001u1dssnnnndddd11p0n0m0mmmm;
2782                  rule := VMULL_integer_A2;
2783| 1101    0     = *V3RDL_I16_32L
2784                  pattern := 111100101dssnnnndddd1101n0m0mmmm;
2785                  rule := VQDMULL_A1;
2786| 1110    -     = *V3RDL_P8  # Note: inst(9)=1, implying polynomial.
2787                  pattern := 1111001u1dssnnnndddd11p0n0m0mmmm;
2788                  rule := VMULL_polynomial_A2;
2789| else:         = *Undefined
2790+--
2791
2792+-- simd_dp_2scalar (See Section A7.4.3)
2793*V2RS
2794   { Q(24), D(22), size(21:20), Vn(19:16), Vd(15:12), op(10),
2795     F(8), N(7), M(5), Vm(3:0) }
2796   d := D:Vd; n := N:Vn;
2797   # Allows 8, 16, and 32, and 64-bit values.
2798   esize := 8  << size; elements := 64 / esize;
2799   defs := {};  # Doesn't affect general purpose registers.
2800   uses := {};
2801   arch := ASIMD;
2802*V2RS_I16_32 *V2RS
2803   # Allows 16 and 32-bit integers (i.e. F=0).
2804   # TODO(karl): Add vector defs/uses etc.
2805   regs := 1 if Q=0 else 2;
2806   m  := Vm(2:0) if size=01 else Vm;
2807   index := M:Vm(3) if size=01 else M;
2808   safety := size=11 => DECODER_ERROR &
2809             size=00 => UNDEFINED &
2810             Q=1 & (Vd(0)=1 | Vn(0)=1) => UNDEFINED;
2811*V2RS_I16_32L *V2RS_I16_32
2812   # Allows 16 and 32-bit operands, and long (i.e. double sized) results.
2813   # TODO(karl): Add vector defs/uses etc.
2814   unsigned := Q=1;
2815   regs := 1;
2816   safety := size=11 => DECODER_ERROR &
2817             (size=00 | Vd(0)=1) => UNDEFINED;
2818*V2RS_F32 *V2RS
2819   # Allows 32-bit floating-point values.
2820   # TODO(karl): Add vector defs/uses etc.
2821   regs := 1 if Q=0 else 2;
2822   m  := Vm;
2823   index := M;
2824   safety := size=11 => DECODER_ERROR &
2825             (size=00 | size=01) => UNDEFINED &
2826             Q=1 & (Vd(0)=1 | Vn(0)=1) => UNDEFINED;
2827+--
2828# Note: for and/sub operations defined by bit 10, we have duplicated
2829# rows and back filled bit 10 into A.
2830| A(11:8) U(24)
2831| 0000    -     = *V2RS_I16_32
2832                  pattern := 1111001q1dssnnnndddd0p0fn1m0mmmm;
2833                  rule := VMLA_by_scalar_A1;
2834| 0001    -     = *V2RS_F32
2835                  pattern := 1111001q1dssnnnndddd0p0fn1m0mmmm;
2836                  rule := VMLA_by_scalar_A1;
2837| 0100    -     = *V2RS_I16_32
2838                  pattern := 1111001q1dssnnnndddd0p0fn1m0mmmm;
2839                  rule := VMLS_by_scalar_A1;
2840| 0101    -     = *V2RS_F32
2841                  pattern := 1111001q1dssnnnndddd0p0fn1m0mmmm;
2842                  rule := VMLS_by_scalar_A1;
2843| 0010    -     = *V2RS_I16_32L
2844                  pattern := 1111001u1dssnnnndddd0p10n1m0mmmm;
2845                  rule := VMLAL_by_scalar_A2;
2846| 0110    -     = *V2RS_I16_32L
2847                  pattern := 1111001u1dssnnnndddd0p10n1m0mmmm;
2848                  rule := VMLSL_by_scalar_A2;
2849| 0011    0     = *V2RS_I16_32L
2850                  pattern := 111100101dssnnnndddd0p11n1m0mmmm;
2851                  rule := VQDMLAL_A1;
2852| 0111    0     = *V2RS_I16_32L
2853                  pattern := 111100101dssnnnndddd0p11n1m0mmmm;
2854                  rule := VQDMLSL_A1;
2855| 1000    -     = *V2RS_I16_32
2856                  pattern := 1111001q1dssnnnndddd100fn1m0mmmm;
2857                  rule := VMUL_by_scalar_A1;
2858| 1001    -     = *V2RS_F32
2859                  pattern := 1111001q1dssnnnndddd100fn1m0mmmm;
2860                  rule := VMUL_by_scalar_A1;
2861| 1010    -     = *V2RS_I16_32L
2862                  pattern := 1111001u1dssnnnndddd1010n1m0mmmm;
2863                  rule := VMULL_by_scalar_A2;
2864| 1011    0     = *V2RS_I16_32L
2865                  pattern := 111100101dssnnnndddd1011n1m0mmmm;
2866                  rule := VQDMULL_A2;
2867| 1100    -     = *V2RS_I16_32
2868                  pattern := 1111001q1dssnnnndddd1100n1m0mmmm;
2869                  rule := VQDMULH_A2;
2870| 1101    -     = *V2RS_I16_32
2871                  pattern := 1111001q1dssnnnndddd1101n1m0mmmm;
2872                  rule := VQRDMULH;
2873| else:         = *Undefined
2874+--
2875
2876+-- simd_dp_2shift (See Section A7.4.4)
2877*V2RSA
2878   { U(24), D(22), imm6(21:16), Vd(15:12), op(8), L(7), Q(6), M(5), Vm(3:0) }
2879   d := D:Vd; n := M:Vm;
2880   regs := 1 if Q=0 else 2;
2881   defs := {};  # Doesn't affect general purpose registers.
2882   uses := {};
2883   arch := ASIMD;
2884*V2RSA_I *V2RSA
2885   # allows 8, 16, 32, or 64-bit integers.
2886   esize := 8  if L:imm6=0001xxx else
2887            16 if L:imm6=001xxxx else
2888            32 if L:imm6=01xxxxx else
2889            64 if L:imm6=1xxxxxx else
2890            0;  # i.e. error.
2891   elements := 8 if L:imm6=0001xxx else
2892               4 if L:imm6=001xxxx else
2893               2 if L:imm6=01xxxxx else
2894               1 if L:imm6=1xxxxxx else
2895               0;  # i.e. error.
2896   unsigned := U=1;
2897   safety := L:imm6=0000xxx => DECODER_ERROR &
2898             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
2899*V2RSA_IR *V2RSA_I
2900   # Shifts right 8, 16, 32, or 64-bit integers.
2901   # TODO(karl): Add vector defs/uses etc.
2902   shift_amount := 16 - imm6 if L:imm6=0001xxx else
2903                   32 - imm6 if L:imm6=001xxxx else
2904                   64 - imm6;
2905*V2RSA_IL *V2RSA_I
2906   # Shifts left 8, 16, 32, or 64-bit integers.
2907   # TODO(karl): Add vector defs/uses etc.
2908   shift_amount := imm6 - 8  if L:imm6=0001xxx else
2909                   imm6 - 16 if L:imm6=001xxxx else
2910                   imm6 - 32 if L:imm6=01xxxxx else
2911                   imm6      if L:imm6=1xxxxxx else
2912                   0;
2913*V2RSA_ILS *V2RSA_IL
2914   # Shifts left with signed/unsigned arguments.
2915   # TODO(karl): Add vector defs/uses etc.
2916   src_unsigned := U=1 & op=1;
2917   dest_unsigned := U=1;
2918   safety := L:imm6=0000xxx => DECODER_ERROR &
2919             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED &
2920             U=0 & op=0 => UNDEFINED;
2921*V2RSA_NE16_32_64 *V2RSA
2922   # Shifts 16, 32 or 64-bit integers when narrowing (right)
2923   # shifts 8, 16, and 32-bit integers when expanding (left)
2924   # these instructions narrow the result, resulting in
2925   # saving 8, 16, and 32-bit values.
2926   esize := 8  if imm6=001xxx else
2927            16 if imm6=01xxxx else
2928            32 if imm6=1xxxxx else
2929            0;  # i.e. error
2930   elements := 8 if imm6=001xxx else
2931               4 if imm6=01xxxx else
2932               2 if imm6=1xxxxx else
2933               0;  # i.e. error
2934*V2RSA_N16_32_64R *V2RSA_NE16_32_64
2935   # Shifts right.
2936   # TODO(karl): Add vector defs/uses etc.
2937   shift_amount := 16 - imm6 if imm6=001xxx else
2938                   32 - imm6 if imm6=01xxxx else
2939                   64 - imm6 if imm6=1xxxxx else
2940                   0;  # i.e. error
2941   safety := imm6=000xxx => DECODER_ERROR &
2942             Vm(0)=1 => UNDEFINED;
2943*V2RSA_N16_32_64RS *V2RSA_N16_32_64R
2944   # Shifts right narrows with signed/unsigned arguments.
2945   # TODO(karl): Add vector defs/uses etc.
2946   src_unsigned := U=1 & op=1;
2947   dest_unsigned := U=1;
2948   safety := imm6=000xxx => DECODER_ERROR &
2949             Vm(0)=1 => UNDEFINED &
2950             U=0 & op=0 => DECODER_ERROR;
2951*V2RSA_E8_16_32L *V2RSA_NE16_32_64
2952   # Shifts left 8, 16, or 32-bit integers, and expands
2953   # result to twice the length of the arguments.
2954   # shift_amount == 0 => VMOVL
2955   # TODO(karl): Add vector defs/uses etc.
2956   shift_amount := imm6 - 8  if imm6=001xxx else
2957                   imm6 - 16 if imm6=01xxxx else
2958                   imm6 - 32 if imm6=1xxxxx else
2959                   0;
2960   safety := imm6=000xxx => DECODER_ERROR &
2961             Vd(0)=1 => UNDEFINED;
2962*V2RSA_CVT *V2RSA
2963   # converts between floating-point and fixed-point.
2964   # TODO(karl): Add vector defs/uses etc.
2965   to_fixed := op=1;
2966   unsigned := U=1;
2967   esize := 32; frac_bits := 64 - imm6; elements := 2;
2968   safety := imm6=000xxx => DECODER_ERROR &
2969             imm6=0xxxxx => UNDEFINED &
2970             Q=1 & (Vd(0)=1 | Vm(0)=1)  => UNDEFINED;
2971+--
2972| A(11:8) U(24) B(6) L(7)
2973| 0000    -     -    -    = *V2RSA_IR
2974                            pattern := 1111001u1diiiiiidddd0000lqm1mmmm;
2975                            rule := VSHR;
2976| 0001    -     -    -    = *V2RSA_IR
2977                            pattern := 1111001u1diiiiiidddd0001lqm1mmmm;
2978                            rule := VSRA;
2979| 0010    -     -    -    = *V2RSA_IR
2980                            pattern := 1111001u1diiiiiidddd0010lqm1mmmm;
2981                            rule := VRSHR;
2982| 0011    -     -    -    = *V2RSA_IR
2983                            pattern := 1111001u1diiiiiidddd0011lqm1mmmm;
2984                            rule := VRSRA;
2985| 0100    1     -    -    = *V2RSA_IR
2986                            pattern := 111100111diiiiiidddd0100lqm1mmmm;
2987                            rule := VSRI;
2988| 0101    0     -    -    = *V2RSA_IL
2989                            pattern := 111100101diiiiiidddd0101lqm1mmmm;
2990                            rule := VSHL_immediate;
2991| "       1     -    -    = *V2RSA_IL
2992                            pattern := 111100111diiiiiidddd0101lqm1mmmm;
2993                            rule := VSLI;
2994| 011x    -     -    -    = *V2RSA_ILS
2995                            pattern := 1111001u1diiiiiidddd011plqm1mmmm;
2996                            rule := VQSHL_VQSHLU_immediate;
2997| 1000    0     0    0    = *V2RSA_N16_32_64R
2998                            pattern := 111100101diiiiiidddd100000m1mmmm;
2999                            rule := VSHRN;
3000| "       "     1    0    = *V2RSA_N16_32_64R
3001                            pattern := 111100101diiiiiidddd100001m1mmmm;
3002                            rule := VRSHRN;
3003| "       1     0    0    = *V2RSA_N16_32_64RS
3004                            pattern := 1111001u1diiiiiidddd100p00m1mmmm;
3005                            rule := VQRSHRUN;
3006| "       "     1    0    = *V2RSA_N16_32_64RS
3007                            pattern := 1111001u1diiiiiidddd100p01m1mmmm;
3008                            rule := VQRSHRUN;
3009| 1001    0     0    0    = *V2RSA_N16_32_64RS
3010                            pattern := 1111001u1diiiiiidddd100p00m1mmmm;
3011                            rule := VQSHRN;
3012| "       1     "    "    = *V2RSA_N16_32_64RS
3013                            pattern := 1111001u1diiiiiidddd100p00m1mmmm;
3014                            rule := VQSHRUN;
3015| "       0     1    0    = *V2RSA_N16_32_64RS
3016                            pattern := 1111001u1diiiiiidddd100p01m1mmmm;
3017                            rule := VQRSHRN;
3018| "       1     "    "    = *V2RSA_N16_32_64RS
3019                            pattern := 1111001u1diiiiiidddd100p01m1mmmm;
3020                            rule := VQRSHRN;
3021| 1010    -     0    0    = *V2RSA_E8_16_32L
3022                            pattern := 1111001u1diiiiiidddd101000m1mmmm;
3023                            rule := VSHLL_A1_or_VMOVL;
3024| 111x    -     -    0    = *V2RSA_CVT
3025                            pattern := 1111001u1diiiiiidddd111p0qm1mmmm;
3026                            rule := VCVT_between_floating_point_and_fixed_point;
3027| else:                   = *Undefined
3028+--
3029
3030+-- simd_dp_2misc (See Section A7.4.5)
3031*V2RM
3032   { D(22), size(19:18), Vd(15:12), F(10), op(8:7), Q(6), M(5), Vm(3:0) }
3033   esize := 8 << size;  elements := 64 / esize;
3034   d := D:Vd; m := M:Vm; regs := 1 if Q=0 else 2;
3035   defs := {};  # Doesn't affect general purpose registers.
3036   uses := {};
3037   arch := ASIMD;
3038*V2RM_RG *V2RM
3039   # Reverse a group of values.
3040   # TODO(karl): Add vector defs/uses etc.
3041   # Note: rev_groupsize(op, size) = 1 << (3 - op - size);
3042   # Uses rev_groupsize since the table generator can't handle non-constant
3043   # shifts.
3044   groupsize := rev_groupsize(op, size);
3045   # Note: rev_mask(groupsize, esize) = (groupsize-1)<esize-1:0>
3046   # Uses rev_mask since the table generator can't model non-constant bit ranges.
3047   reverse_mask := rev_mask(groupsize, esize);
3048   safety := op + size >= 3 => UNDEFINED &
3049             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3050*V2RM_V8_16_32 *V2RM
3051   # Operates on 8, 16, and 32-bit values.
3052   # TODO(karl): Add vector defs/uses etc.
3053   safety := size=11 => UNDEFINED &
3054             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3055*V2RM_V8_16_32L *V2RM_V8_16_32
3056   # Operates on 8, 16, and 32-bit values, and the result is twice the
3057   # length of the operands.
3058   # TODO(karl): Add vector defs/uses etc.
3059   unsigned := (op(0)=1);
3060*V2RM_V8 *V2RM
3061   # Operates on 8-bit values.
3062   # TODO(karl): Add vector defs/uses etc.
3063   safety := size=~00 => UNDEFINED &
3064             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3065*V2RM_F32 *V2RM
3066   # Operates on 32-bit floating-point values.
3067   # TODO(karl): Add vector defs/uses etc.
3068   safety := Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED &
3069             size=~10 => UNDEFINED;
3070*V2RM_IF32 *V2RM_F32
3071   # Operates on 32-bit integers or floating-point.
3072   floating_point := F=1;
3073*V2RM_V8S *V2RM
3074   # Swaps 8-bit values.
3075   # TODO(karl): Add vector defs/uses etc.
3076   safety := d == m => UNKNOWN &
3077             size=~00 => UNDEFINED &
3078             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3079*V2RM_V8_16_32T *V2RM
3080   # Transposes vectors of 8, 16, and 32-bit values.
3081   # TODO(karl): Add vector defs/uses etc.
3082   quadword_operation := Q=1;
3083   safety := d == m => UNKNOWN &
3084             size=11 => UNDEFINED &
3085             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3086*V2RM_V8_16_32I *V2RM
3087   # Interleaves vectors of 8, 16, and 32-bit values.
3088   # TODO(karl): Add vector defs/uses etc.
3089   quadword_operation := Q=1;
3090   safety := d == m => UNKNOWN &
3091             size=11 | (Q=0 & size=10) => UNDEFINED &
3092             Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED;
3093*V2RM_V16_32_64N *V2RM
3094   # Narrows 16, 32, or 64-bit values.
3095   # TODO(karl): Add vector defs/uses etc.
3096   safety := size=11 => UNDEFINED &
3097             Vm(0)=1 => UNDEFINED;
3098*V2RM_I8_16_32L *V2RM
3099   # Vector apply an immediate shift value to 8, 16, or 32-bit value,
3100   # expanding the result to twice the length of the argument.
3101   # TODO(karl): Add vector defs/uses etc.
3102   shift_amount := esize;
3103   safety := size=11 | Vd(0)=1 => UNDEFINED;
3104*V2RM_I16_32_64N
3105   # Narrow  16, 32, or 64-bit signed/unsigned values.
3106   { D(22), size(19:18), Vd(15:12), op(7:6), M(5), Vm(3:0) }
3107   # TODO(karl): Add vector defs/uses etc.
3108   src_unsigned := op=11; dest_unsigned := op(0)=1;
3109   d := D:Vd; m := M:Vm;
3110   defs := {};  # Doesn't affect general purpose registers.
3111   uses := {};
3112   safety := op=00 => DECODER_ERROR &
3113             size=11 | Vm(0)=1 => UNDEFINED;
3114   arch := ASIMD;
3115*V2RM_CVT_H2S
3116   { D(22), size(19:18), Vd(15:12), op(8), M(5), Vm(3:0) }
3117   # Convert between half-precision and single-precision.
3118   # TODO(karl): Add vector defs/uses etc.
3119   half_to_single := op=1;
3120   esize := 16; elements := 4;
3121   d := D:Vd; m := M:Vm;
3122   defs := {};  # Doesn't affect general purpose registers.
3123   uses := {};
3124   safety := size=~01 => UNDEFINED &
3125             half_to_single & Vd(0)=1 => UNDEFINED &
3126             not half_to_single & Vm(0)=1 => UNDEFINED;
3127   arch := ASIMDhp;
3128*V2RM_CVT_F2I *V2RM
3129   # Convert between floating-point and integer.
3130   # TODO(karl): Add vector defs/uses etc.
3131   to_integer := op(1)=1; unsigned := op(0)=1;
3132   safety := Q=1 & (Vd(0)=1 | Vm(0)=1) => UNDEFINED &
3133             size=~10 => UNDEFINED;
3134+--
3135| A(17:16) B(10:6)
3136| 00       0000x   = *V2RM_RG
3137                     pattern := 111100111d11ss00dddd000ppqm0mmmm;
3138                     rule := VREV64;
3139| "        0001x   = *V2RM_RG
3140                     pattern := 111100111d11ss00dddd000ppqm0mmmm;
3141                     rule := VREV32;
3142| "        0010x   = *V2RM_RG
3143                     pattern := 111100111d11ss00dddd000ppqm0mmmm;
3144                     rule := VREV16;
3145| "        010xx   = *V2RM_V8_16_32L
3146                     pattern := 111100111d11ss00dddd0010pqm0mmmm;
3147                     rule := VPADDL;
3148| "        1000x   = *V2RM_V8_16_32
3149                     pattern := 111100111d11ss00dddd01000qm0mmmm;
3150                     rule := VCLS;
3151| "        1001x   = *V2RM_V8_16_32
3152                     pattern := 111100111d11ss00dddd01001qm0mmmm;
3153                     rule := VCLZ;
3154| "        1010x   = *V2RM_V8
3155                     pattern := 111100111d11ss00dddd01010qm0mmmm;
3156                     rule := VCNT;
3157| "        1011x   = *V2RM_V8
3158                     pattern := 111100111d11ss00dddd01011qm0mmmm;
3159                     rule := VMVN_register;
3160| "        110xx   = *V2RM_V8_16_32L
3161                     pattern := 111100111d11ss00dddd0110pqm0mmmm;
3162                     rule := VPADAL;
3163| "        1110x   = *V2RM_V8_16_32
3164                     pattern := 111100111d11ss00dddd01110qm0mmmm;
3165                     rule := VQABS;
3166| "        1111x   = *V2RM_V8_16_32
3167                     pattern := 111100111d11ss00dddd01111qm0mmmm;
3168                     rule := VQNEG;
3169| 01       0000x   = *V2RM_V8_16_32
3170                     pattern := 111100111d11ss01dddd0f000qm0mmmm;
3171                     rule := VCGT_immediate_0;
3172| "        1000x   = *V2RM_F32
3173                     pattern := 111100111d11ss01dddd0f000qm0mmmm;
3174                     rule := VCGT_immediate_0;
3175| "        0001x   = *V2RM_V8_16_32
3176                     pattern := 111100111d11ss01dddd0f001qm0mmmm;
3177                     rule := VCGE_immediate_0;
3178| "        1001x   = *V2RM_F32
3179                     pattern := 111100111d11ss01dddd0f001qm0mmmm;
3180                     rule := VCGE_immediate_0;
3181| "        0010x   = *V2RM_V8_16_32
3182                     pattern := 111100111d11ss01dddd0f010qm0mmmm;
3183                     rule := VCEQ_immediate_0;
3184| "        1010x   = *V2RM_F32
3185                     pattern := 111100111d11ss01dddd0f010qm0mmmm;
3186                     rule := VCEQ_immediate_0;
3187| "        0011x   = *V2RM_V8_16_32
3188                     pattern := 111100111d11ss01dddd0f011qm0mmmm;
3189                     rule := VCLE_immediate_0;
3190| "        1011x   = *V2RM_F32
3191                     pattern := 111100111d11ss01dddd0f011qm0mmmm;
3192                     rule := VCLE_immediate_0;
3193| "        0100x   = *V2RM_V8_16_32
3194                     pattern := 111100111d11ss01dddd0f100qm0mmmm;
3195                     rule := VCLT_immediate_0;
3196| "        1100x   = *V2RM_F32
3197                     pattern := 111100111d11ss01dddd0f100qm0mmmm;
3198                     rule := VCLT_immediate_0;
3199| "        0110x   = *V2RM_V8_16_32
3200                     pattern := 111100111d11ss01dddd0f110qm0mmmm;
3201                     rule := VABS_A1;
3202| "        1110x   = *V2RM_F32
3203                     pattern := 111100111d11ss01dddd0f110qm0mmmm;
3204                     rule := VABS_A1;
3205| "        0111x   = *V2RM_V8_16_32
3206                     pattern := 111100111d11ss01dddd0f111qm0mmmm;
3207                     rule := VNEG;
3208| "        1111x   = *V2RM_F32
3209                     pattern := 111100111d11ss01dddd0f111qm0mmmm;
3210                     rule := VNEG;
3211| 10       0000x   = *V2RM_V8S
3212                     pattern := 111100111d11ss10dddd00000qm0mmmm;
3213                     rule := VSWP;
3214| "        0001x   = *V2RM_V8_16_32T
3215                     pattern := 111100111d11ss10dddd00001qm0mmmm;
3216                     rule := VTRN;
3217| "        0010x   = *V2RM_V8_16_32I
3218                     pattern := 111100111d11ss10dddd00010qm0mmmm;
3219                     rule := VUZP;
3220| "        0011x   = *V2RM_V8_16_32I
3221                     pattern := 111100111d11ss10dddd00011qm0mmmm;
3222                     rule := VZIP;
3223| "        01000   = *V2RM_V16_32_64N
3224                     pattern := 111100111d11ss10dddd001000m0mmmm;
3225                     rule := VMOVN;
3226| "        01001   = *V2RM_I16_32_64N
3227                     pattern := 111100111d11ss10dddd0010ppm0mmmm;
3228                     rule := VQMOVUN;
3229| "        0101x   = *V2RM_I16_32_64N
3230                     pattern := 111100111d11ss10dddd0010ppm0mmmm;
3231                     rule := VQMOVN;
3232| "        01100   = *V2RM_I8_16_32L
3233                     pattern := 111100111d11ss10dddd001100m0mmmm;
3234                     rule := VSHLL_A2;
3235| "        11x00   = *V2RM_CVT_H2S
3236                     pattern := 111100111d11ss10dddd011p00m0mmmm;
3237                     rule := CVT_between_half_precision_and_single_precision;
3238| 11       10x0x   = *V2RM_IF32
3239                     pattern := 111100111d11ss11dddd010f0qm0mmmm;
3240                     rule := VRECPE;
3241| "        10x1x   = *V2RM_IF32
3242                     pattern := 111100111d11ss11dddd010f1qm0mmmm;
3243                     rule := VRSQRTE;
3244| "        11xxx   = *V2RM_CVT_F2I
3245                     pattern := 111100111d11ss11dddd011ppqm0mmmm;
3246                     rule := VCVT;
3247| else:            = *Undefined
3248+--
3249
3250+-- simd_dp_1imm (See Section A7.4.6)
3251*V1RI
3252   { i(24), D(22), imm3(18:16), Vd(15:12), cmode(11:8), Q(6), op(5), imm4(3:0) }
3253   imm64 := AdvSIMDExpandImm(op, cmode, i:imm3:imm4);
3254   d := D:Vd; regs := 1 if Q=0 else 2;
3255   # TODO(karl): Add vector defs/uses etc.
3256   defs := {};
3257   uses := {};
3258   arch := ASIMD;
3259*V1RI_MOV *V1RI
3260   single_register := false;
3261   safety := op=0 & cmode(0)=1 & cmode(3:2)=~11 => DECODER_ERROR &
3262             op=1 & cmode=~1110 => DECODER_ERROR &
3263             Q=1 & Vd(0)=1 => UNDEFINED;
3264*V1RI_BIT *V1RI
3265   safety := cmode(0)=0 | cmode(3:2)=11 => DECODER_ERROR &
3266             Q=1 & Vd(0)=1 => UNDEFINED;
3267*V1RI_MVN *V1RI
3268   safety := (cmode(0)=1 & cmode(3:2)=~11) | cmode(3:1)=111 => DECODER_ERROR &
3269             Q=1 & Vd(0)=1 => UNDEFINED;
3270+--
3271| op(5) cmode(11:8)
3272| 0     0xx0        = *V1RI_MOV
3273                      pattern := 1111001m1d000mmmddddcccc0qp1mmmm;
3274                      rule := VMOV_immediate_A1;
3275| "     0xx1        = *V1RI_BIT
3276                      pattern := 1111001i1d000mmmddddcccc0q01mmmm;
3277                      rule := VORR_immediate;
3278| "     10x0        = *V1RI_MOV
3279                      pattern := 1111001m1d000mmmddddcccc0qp1mmmm;
3280                      rule := VMOV_immediate_A1;
3281| "     10x1        = *V1RI_BIT
3282                      pattern := 1111001i1d000mmmddddcccc0q01mmmm;
3283                      rule := VORR_immediate;
3284| "     11xx        = *V1RI_MOV
3285                      pattern := 1111001m1d000mmmddddcccc0qp1mmmm;
3286                      rule := VMOV_immediate_A1;
3287| 1     0xx0        = *V1RI_MVN
3288                      pattern := 1111001i1d000mmmddddcccc0q11mmmm;
3289                      rule := VMVN_immediate;
3290| "     0xx1        = *V1RI_BIT
3291                      pattern := 1111001i1d000mmmddddcccc0q11mmmm;
3292                      rule := VBIC_immediate;
3293| "     10x0        = *V1RI_MVN
3294                      pattern := 1111001i1d000mmmddddcccc0q11mmmm;
3295                      rule := VMVN_immediate;
3296| "     10x1        = *V1RI_BIT
3297                      pattern := 1111001i1d000mmmddddcccc0q11mmmm;
3298                      rule := VBIC_immediate;
3299| "     110x        = *V1RI_MVN
3300                      pattern := 1111001i1d000mmmddddcccc0q11mmmm;
3301                      rule := VMVN_immediate;
3302| "     1110        = *V1RI_MOV
3303                      pattern := 1111001m1d000mmmddddcccc0qp1mmmm;
3304                      rule := VMOV_immediate_A1;
3305| "     1111        = *Undefined
3306+--
3307
3308+-- advanced_simd_element_or_structure_load_store_instructions (See Section A7.7)
3309*VLSM
3310   { D(22), Rn(19:16), Vd(15:12), type(11:8), size(7:6), align(5:4), Rm(3:0) }
3311   alignment := 1 if align=00 else 4 << align;
3312   ebytes := 1 << size; esize := 8 * ebytes; elements := 8 / ebytes;
3313   d := D:Vd; n := Rn; m := Rm;
3314   wback := (m != Pc); register_index := (m != Pc & m != Sp);
3315   base := n;
3316   # TODO(karl): Add vector defs/uses etc.
3317   # defs ignores FPRs. It only models GPRs and conditions.
3318   defs := { base } if wback else {};
3319   # Note: register_index defines if Rm is used (rather than a small constant).
3320   small_imm_base_wb := wback & not register_index;
3321   # uses ignores FPRs. It only models GPRs.
3322   uses := { m if wback else None , n };
3323   arch := ASIMD;
3324*VLSM1 *VLSM
3325   regs := 1 if type=0111 else
3326           2 if type=1010 else
3327           3 if type=0110 else
3328           4 if type=0010 else
3329           0;  # Error value.
3330   safety := type=0111 & align(1)=1 => UNDEFINED &
3331             type=1010 & align=11 => UNDEFINED &
3332             type=0110 & align(1)=1 => UNDEFINED &
3333             not type in bitset {0111, 1010, 0110, 0010} => DECODER_ERROR &
3334             n == Pc | d + regs > 32 => UNPREDICTABLE;
3335*VLSM2 *VLSM
3336   regs := 1 if type in bitset {1000, 1001} else 2;
3337   inc  := 1 if type=1000 else 2;
3338   d2 := d + inc;
3339   safety := size=11 => UNDEFINED &
3340             type in bitset {1000, 1001} & align=11 => UNDEFINED &
3341             not type in bitset {1000, 1001, 0011} => DECODER_ERROR &
3342             n == Pc | d2 + regs > 32 => UNPREDICTABLE;
3343*VLSM3 *VLSM
3344   inc := 1 if type=0100 else 2;
3345   alignment := 1 if align(0)=0 else 8;
3346   d2 := d + inc; d3 := d2 + inc;
3347   safety := size=11 | align(1)=1 => UNDEFINED &
3348             not type in bitset {0100, 0101} => DECODER_ERROR &
3349             n == Pc | d3 > 31 => UNPREDICTABLE;
3350*VLSM4 *VLSM
3351   inc := 1 if type=0000 else 2;
3352   d2 := d + inc; d3 := d2 + inc; d4 := d3 + inc;
3353   safety := size=11 => UNDEFINED &
3354             not type in bitset {0000, 0001} => DECODER_ERROR &
3355             n == Pc | d4 > 31 => UNPREDICTABLE;
3356*VLSS
3357   { D(22), Rn(19:16), Vd(15:12), size(11:10), index_align(7:4), Rm(3:0) }
3358   ebytes := 1 << size; esize := 8 * ebytes;
3359   index := index_align(3:1) if size=00 else
3360            index_align(3:2) if size=01 else
3361            index_align(3)   if size=10 else
3362            0;  # error value.
3363   inc := 1 if size=00 else
3364          (1 if index_align(1)=0 else 2) if size=01 else
3365          (1 if index_align(2)=0 else 2) if size=10 else
3366          0;  # error value.
3367   d := D:Vd; n := Rn; m := Rm;
3368   wback := (m != Pc); register_index := (m != Pc & m != Sp);
3369   base := n;
3370   # TODO(karl): Add vector defs/uses etc.
3371   # defs ignores FPRs. It only models GPRs and conditions.
3372   defs := { base } if wback else {};
3373   # Note: register_index defines if Rm is used (rather than a small constant).
3374   small_imm_base_wb := wback & not register_index;
3375   # uses ignores FPRs. It only models GPRs.
3376   uses := { m if wback else None , n };
3377   arch := ASIMD;
3378*VLSS1 *VLSS
3379   alignment := 1 if size=00 else
3380                (1 if index_align(0)=0 else 2) if size=01 else
3381                (1 if index_align(1:0)=00 else 4) if size=10 else
3382                0;  # error value.
3383   safety := size=11 => UNDEFINED &
3384             size=00 & index_align(0)=~0 => UNDEFINED &
3385             size=01 & index_align(1)=~0 => UNDEFINED &
3386             size=10 & index_align(2)=~0 => UNDEFINED &
3387             size=10 & index_align(1:0)=~00
3388                     & index_align(1:0)=~11 => UNDEFINED &
3389             n == Pc => UNPREDICTABLE;
3390*VLSS2 *VLSS
3391   alignment := (1 if index_align(0)=0 else 2) if size=00 else
3392                (1 if index_align(0)=0 else 4) if size=01 else
3393                (1 if index_align(0)=0 else 8) if size=10 else
3394                0;  # error value.
3395   d2 := d + inc;
3396   safety := size=11 => UNDEFINED &
3397             size=10 & index_align(1)=~0 => UNDEFINED &
3398             n == Pc | d2 > 31 => UNPREDICTABLE;
3399*VLSS3 *VLSS
3400   alignment := 1;
3401   d2 := d + inc; d3 := d2 + inc;
3402   safety := size=11 => UNDEFINED &
3403             size=00 & index_align(0)=~0 => UNDEFINED &
3404             size=01 & index_align(0)=~0 => UNDEFINED &
3405             size=10 & index_align(1:0)=~00 => UNDEFINED &
3406             n == Pc | d3 > 31 => UNPREDICTABLE;
3407*VLSS4 *VLSS
3408   d2 := d + inc; d3 := d2 + inc; d4 := d3 + inc;
3409   alignment := (1 if index_align(0)=0 else 4) if size=00 else
3410                (1 if index_align(0)=0 else 8) if size=01 else
3411                (1 if index_align(1:0)=00 else 4 << index_align(1:0))
3412                   if size=10 else
3413                0;  # error value.
3414   safety := size=11 => UNDEFINED &
3415             size=10 & index_align(1:0)=11 => UNDEFINED &
3416             n == Pc | d4 > 31 => UNPREDICTABLE;
3417*VLSA
3418   { D(22), Rn(19:16), Vd(15:12), size(7:6), T(5), a(4), Rm(3:0) }
3419   ebytes := 1 << size; elements := 8 / ebytes;
3420   d := D:Vd; n := Rn; m := Rm;
3421   wback := (m != Pc); register_index := (m != Pc & m != Sp);
3422   base := n;
3423   # TODO(karl): Add vector defs/uses etc.
3424   # defs ignores FPRs. It only models GPRs and conditions.
3425   defs := { base } if wback else {};
3426   # Note: register_index defines if Rm is used (rather than a small constant).
3427   small_imm_base_wb := wback & not register_index;
3428   # uses ignores FPRs. It only models GPRs.
3429   uses := { m if wback else None , n };
3430   arch := ASIMD;
3431*VLS1A *VLSA
3432   alignment := 1 if a=0 else ebytes;
3433   regs := 1 if T=0 else 2;
3434   safety := size=11 | (size=00 & a=1) => UNDEFINED &
3435             n == Pc | d + regs > 32 => UNPREDICTABLE;
3436*VLS2A *VLSA
3437   alignment := 1 if a=0 else 2 * ebytes;
3438   inc := 1 if T=0 else 2;
3439   d2 := d + inc;
3440   safety := size=11 => UNDEFINED &
3441             n == Pc | d2 > 31 => UNPREDICTABLE;
3442*VLS3A *VLSA
3443   inc := 1 if T=0 else 2;
3444   alignment := 1;
3445   d2 := d + inc; d3 := d2 + inc;
3446   safety := size=11 | a=1 => UNDEFINED &
3447             n == Pc | d3 > 31 => UNPREDICTABLE;
3448*VLS4A *VLSA
3449   alignment := 16 if size=11 else
3450                (1 if a=0 else 8) if size=10 else
3451                (1 if a=0 else 4 * ebytes);
3452   inc := 1 if T=0 else 2;
3453   d2 := d + inc; d3 := d2 + inc; d4 := d3 + inc;
3454   safety := size=11 & a=0 => UNDEFINED &
3455             n == Pc | d4 > 31 => UNPREDICTABLE;
3456+--
3457| L(21) A(23) B(11:8)
3458| 0 0     0010    = *VLSM1
3459                    pattern := 111101000d00nnnnddddttttssaammmm;
3460                    rule := VST1_multiple_single_elements;
3461| " "     011x    "
3462| " "     1010    "
3463| " "     0011    = *VLSM2
3464                    pattern := 111101000d00nnnnddddttttssaammmm;
3465                    rule := VST2_multiple_2_element_structures;
3466| " "     100x    "
3467| " "     010x    = *VLSM3
3468                    pattern := 111101000d00nnnnddddttttssaammmm;
3469                    rule := VST3_multiple_3_element_structures;
3470| " "     000x    = *VLSM4
3471                    pattern := 111101000d00nnnnddddttttssaammmm;
3472                    rule := VST4_multiple_4_element_structures;
3473| " 1     0x00    = *VLSS1
3474                    pattern := 111101001d00nnnnddddss00aaaammmm;
3475                    rule := VST1_single_element_from_one_lane;
3476| " "     1000    "
3477| " "     0x01    = *VLSS2
3478                    pattern := 111101001d00nnnnddddss01aaaammmm;
3479                    rule := VST2_single_2_element_structure_from_one_lane;
3480| " "     1001    "
3481| " "     0x10    = *VLSS3
3482                    pattern := 111101001d00nnnnddddss10aaaammmm;
3483                    rule := VST3_single_3_element_structure_from_one_lane;
3484| " "     1010    "
3485| " "     0x11    = *VLSS4
3486                    pattern := 111101001d00nnnnddddss11aaaammmm;
3487                    rule := VST4_single_4_element_structure_form_one_lane;
3488| " "     1011    "
3489| 1 0     0010    = *VLSM1
3490                    pattern := 111101000d10nnnnddddttttssaammmm;
3491                    rule := VLD1_multiple_single_elements;
3492| " "     011x    "
3493| " "     1010    "
3494| " "     0011    = *VLSM2
3495                    pattern := 111101000d10nnnnddddttttssaammmm;
3496                    rule := VLD2_multiple_2_element_structures;
3497| " "     100x    "
3498| " "     010x    = *VLSM3
3499                    pattern := 111101000d10nnnnddddttttssaammmm;
3500                    rule := VLD3_multiple_3_element_structures;
3501| " "     000x    = *VLSM4
3502                    pattern := 111101000d10nnnnddddttttssaammmm;
3503                    rule := VLD4_multiple_4_element_structures;
3504| " 1     0x00    = *VLSS1
3505                    pattern := 111101001d10nnnnddddss00aaaammmm;
3506                    rule := VLD1_single_element_to_one_lane;
3507| " "     1000    "
3508| " "     1100    = *VLS1A
3509                    pattern := 111101001d10nnnndddd1100sstammmm;
3510                    rule := VLD1_single_element_to_all_lanes;
3511| " "     0x01    = *VLSS2
3512                    pattern := 111101001d10nnnnddddss01aaaammmm;
3513                    rule := VLD2_single_2_element_structure_to_one_lane;
3514| " "     1001    "
3515| " "     1101    = *VLS2A
3516                    pattern := 111101001d10nnnndddd1101sstammmm;
3517                    rule := VLD2_single_2_element_structure_to_all_lanes;
3518| " "     0x10    = *VLSS3
3519                    pattern := 111101001d10nnnnddddss10aaaammmm;
3520                    rule := VLD3_single_3_element_structure_to_one_lane;
3521| " "     1010    "
3522| " "     1110    = *VLS3A
3523                    pattern := 111101001d10nnnndddd1110sstammmm;
3524                    rule := VLD3_single_3_element_structure_to_all_lanes;
3525| " "     0x11    = *VLSS4
3526                    pattern := 111101001d10nnnnddddss11aaaammmm;
3527                    rule := VLD4_single_4_element_structure_to_one_lane;
3528| " "     1011    "
3529| " "     1111    = *VLS4A
3530                    pattern := 111101001d10nnnndddd1111sstammmm;
3531                    rule := VLD4_single_4_element_structure_to_all_lanes;
3532| else:           = *Undefined
3533+--
3534