1*440a403fSchristos; Toshiba MeP Media Engine architecture description.  -*- Scheme -*-
2*440a403fSchristos; Copyright 2011 Free Software Foundation, Inc.
3*440a403fSchristos;
4*440a403fSchristos; Contributed by Red Hat Inc;
5*440a403fSchristos;
6*440a403fSchristos; This file is part of the GNU Binutils.
7*440a403fSchristos;
8*440a403fSchristos; This program is free software; you can redistribute it and/or modify
9*440a403fSchristos; it under the terms of the GNU General Public License as published by
10*440a403fSchristos; the Free Software Foundation; either version 3 of the License, or
11*440a403fSchristos; (at your option) any later version.
12*440a403fSchristos;
13*440a403fSchristos; This program is distributed in the hope that it will be useful,
14*440a403fSchristos; but WITHOUT ANY WARRANTY; without even the implied warranty of
15*440a403fSchristos; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16*440a403fSchristos; GNU General Public License for more details.
17*440a403fSchristos;
18*440a403fSchristos; You should have received a copy of the GNU General Public License
19*440a403fSchristos; along with this program; if not, write to the Free Software
20*440a403fSchristos; Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
21*440a403fSchristos; MA 02110-1301, USA.
22*440a403fSchristos
23*440a403fSchristos(include "simplify.inc")
24*440a403fSchristos
25*440a403fSchristos(define-pmacro isa-enum ()
26*440a403fSchristos  (isas mep
27*440a403fSchristos; begin-isa-enum
28*440a403fSchristos	ext_core1 ext_cop1_16 ext_cop1_32 ext_cop1_48 ext_cop1_64
29*440a403fSchristos; end-isa-enum
30*440a403fSchristos  )
31*440a403fSchristos)
32*440a403fSchristos
33*440a403fSchristos(define-arch
34*440a403fSchristos  (name mep)
35*440a403fSchristos  (comment "Toshiba MeP Media Engine")
36*440a403fSchristos  (insn-lsb0? #f) ;; work around cgen limitation
37*440a403fSchristos  (machs mep h1 c5)
38*440a403fSchristos  isa-enum
39*440a403fSchristos)
40*440a403fSchristos
41*440a403fSchristos(define-isa
42*440a403fSchristos  (name mep)
43*440a403fSchristos  (comment "MeP core instruction set")
44*440a403fSchristos  (default-insn-word-bitsize 32)
45*440a403fSchristos  (default-insn-bitsize 32)
46*440a403fSchristos  (base-insn-bitsize 32)
47*440a403fSchristos)
48*440a403fSchristos
49*440a403fSchristos; begin-isas
50*440a403fSchristos(define-isa
51*440a403fSchristos  (name ext_core1)
52*440a403fSchristos  (comment "MeP core extension instruction set")
53*440a403fSchristos  (default-insn-word-bitsize 32)
54*440a403fSchristos  (default-insn-bitsize 32)
55*440a403fSchristos  (base-insn-bitsize 32)
56*440a403fSchristos)
57*440a403fSchristos
58*440a403fSchristos(define-isa
59*440a403fSchristos  (name ext_cop1_16)
60*440a403fSchristos  (comment "MeP coprocessor instruction set")
61*440a403fSchristos  (default-insn-word-bitsize 32)
62*440a403fSchristos  (default-insn-bitsize 32)
63*440a403fSchristos  (base-insn-bitsize 32)
64*440a403fSchristos)
65*440a403fSchristos
66*440a403fSchristos(define-isa
67*440a403fSchristos  (name ext_cop1_32)
68*440a403fSchristos  (comment "MeP coprocessor instruction set")
69*440a403fSchristos  (default-insn-word-bitsize 32)
70*440a403fSchristos  (default-insn-bitsize 32)
71*440a403fSchristos  (base-insn-bitsize 32)
72*440a403fSchristos)
73*440a403fSchristos
74*440a403fSchristos(define-isa
75*440a403fSchristos  (name ext_cop1_48)
76*440a403fSchristos  (comment "MeP coprocessor instruction set")
77*440a403fSchristos  (default-insn-word-bitsize 32)
78*440a403fSchristos  (default-insn-bitsize 32)
79*440a403fSchristos  (base-insn-bitsize 32)
80*440a403fSchristos)
81*440a403fSchristos
82*440a403fSchristos(define-isa
83*440a403fSchristos  (name ext_cop1_64)
84*440a403fSchristos  (comment "MeP coprocessor instruction set")
85*440a403fSchristos  (default-insn-word-bitsize 32)
86*440a403fSchristos  (default-insn-bitsize 32)
87*440a403fSchristos  (base-insn-bitsize 32)
88*440a403fSchristos)
89*440a403fSchristos
90*440a403fSchristos(define-pmacro all-mep-isas () (ISA mep,ext_core1,ext_cop1_16,ext_cop1_32,ext_cop1_48,ext_cop1_64))
91*440a403fSchristos
92*440a403fSchristos(define-pmacro all-mep-core-isas () (ISA mep,ext_core1,ext_cop1_32))
93*440a403fSchristos
94*440a403fSchristos(define-pmacro all-core-isa-list () mep,ext_core1)
95*440a403fSchristos; end-isas
96*440a403fSchristos
97*440a403fSchristos(define-cpu
98*440a403fSchristos  (name mepf)
99*440a403fSchristos  (comment "MeP family")
100*440a403fSchristos  (endian either)
101*440a403fSchristos  (insn-chunk-bitsize 16)
102*440a403fSchristos  (word-bitsize 32)
103*440a403fSchristos)
104*440a403fSchristos
105*440a403fSchristos(define-mach
106*440a403fSchristos  (name mep)
107*440a403fSchristos  (comment "MeP media engine")
108*440a403fSchristos  (cpu mepf)
109*440a403fSchristos  isa-enum
110*440a403fSchristos)
111*440a403fSchristos
112*440a403fSchristos(define-mach
113*440a403fSchristos  (name h1)
114*440a403fSchristos  (comment "H1 media engine")
115*440a403fSchristos  (cpu mepf)
116*440a403fSchristos  isa-enum
117*440a403fSchristos)
118*440a403fSchristos
119*440a403fSchristos(define-mach
120*440a403fSchristos  (name c5)
121*440a403fSchristos  (comment "C5 media engine")
122*440a403fSchristos  (cpu mepf)
123*440a403fSchristos  isa-enum
124*440a403fSchristos)
125*440a403fSchristos
126*440a403fSchristos(define-model
127*440a403fSchristos  (name mep)
128*440a403fSchristos  (comment "MeP media engine processor")
129*440a403fSchristos  (mach c5) ; mach gets changed by MeP-Integrator
130*440a403fSchristos
131*440a403fSchristos  (unit u-exec "execution unit" ()
132*440a403fSchristos	1 1 ; issue done
133*440a403fSchristos	() () () ())
134*440a403fSchristos
135*440a403fSchristos  ; Branch unit
136*440a403fSchristos  (unit u-branch "Branch Unit" ()
137*440a403fSchristos	0 0 ; issue done
138*440a403fSchristos	() ; state
139*440a403fSchristos	() ; inputs
140*440a403fSchristos	((pc)) ; outputs
141*440a403fSchristos	() ; profile action (default)
142*440a403fSchristos	)
143*440a403fSchristos
144*440a403fSchristos  ; Multiply unit
145*440a403fSchristos  (unit u-multiply "Multiply Unit" ()
146*440a403fSchristos	0 0 ; issue done
147*440a403fSchristos	() ; state
148*440a403fSchristos	() ; inputs
149*440a403fSchristos	() ; outputs
150*440a403fSchristos	() ; profile action (default)
151*440a403fSchristos	)
152*440a403fSchristos
153*440a403fSchristos  ; Divide unit
154*440a403fSchristos  (unit u-divide "Divide Unit" ()
155*440a403fSchristos	0 0 ; issue done
156*440a403fSchristos	() ; state
157*440a403fSchristos	() ; inputs
158*440a403fSchristos	() ; outputs
159*440a403fSchristos	() ; profile action (default)
160*440a403fSchristos	)
161*440a403fSchristos
162*440a403fSchristos  ; Stcb unit
163*440a403fSchristos  (unit u-stcb "stcb Unit" ()
164*440a403fSchristos	0 0 ; issue done
165*440a403fSchristos	() ; state
166*440a403fSchristos	() ; inputs
167*440a403fSchristos	() ; outputs
168*440a403fSchristos	() ; profile action (default)
169*440a403fSchristos	)
170*440a403fSchristos
171*440a403fSchristos  ; Ldcb unit
172*440a403fSchristos  (unit u-ldcb "ldcb Unit" ()
173*440a403fSchristos	0 0 ; issue done
174*440a403fSchristos	() ; state
175*440a403fSchristos	() ; inputs
176*440a403fSchristos	() ; outputs
177*440a403fSchristos	() ; profile action (default)
178*440a403fSchristos	)
179*440a403fSchristos
180*440a403fSchristos  ; Load gpr unit
181*440a403fSchristos  (unit u-load-gpr "Load into GPR Unit" ()
182*440a403fSchristos	0 0 ; issue done
183*440a403fSchristos	() ; state
184*440a403fSchristos	() ; inputs
185*440a403fSchristos	((loadreg INT -1)) ; outputs
186*440a403fSchristos	() ; profile action (default)
187*440a403fSchristos	)
188*440a403fSchristos
189*440a403fSchristos  (unit u-ldcb-gpr "Ldcb into GPR Unit" ()
190*440a403fSchristos	0 0 ; issue done
191*440a403fSchristos	() ; state
192*440a403fSchristos	() ; inputs
193*440a403fSchristos	((loadreg INT -1)) ; outputs
194*440a403fSchristos	() ; profile action (default)
195*440a403fSchristos	)
196*440a403fSchristos
197*440a403fSchristos  ; Multiply into GPR unit
198*440a403fSchristos  (unit u-mul-gpr "Multiply into GPR Unit" ()
199*440a403fSchristos	0 0 ; issue done
200*440a403fSchristos	() ; state
201*440a403fSchristos	() ; inputs
202*440a403fSchristos	((resultreg INT -1)) ; outputs
203*440a403fSchristos	() ; profile action (default)
204*440a403fSchristos	)
205*440a403fSchristos
206*440a403fSchristos  ; Use gpr unit -- stalls if GPR not ready
207*440a403fSchristos  (unit u-use-gpr "Use GPR Unit" ()
208*440a403fSchristos	0 0 ; issue done
209*440a403fSchristos	() ; state
210*440a403fSchristos	((usereg INT -1)) ; inputs
211*440a403fSchristos	() ; outputs
212*440a403fSchristos	() ; profile action (default)
213*440a403fSchristos	)
214*440a403fSchristos
215*440a403fSchristos  ; Use ctrl-reg unit -- stalls if CTRL-REG not ready
216*440a403fSchristos  (unit u-use-ctrl-reg "Use CTRL-REG Unit" ()
217*440a403fSchristos	0 0 ; issue done
218*440a403fSchristos	() ; state
219*440a403fSchristos	((usereg INT -1)) ; inputs
220*440a403fSchristos	() ; outputs
221*440a403fSchristos	() ; profile action (default)
222*440a403fSchristos	)
223*440a403fSchristos
224*440a403fSchristos  ; Store ctrl-reg unit -- stalls if CTRL-REG not ready
225*440a403fSchristos  (unit u-store-ctrl-reg "Store CTRL-REG Unit" ()
226*440a403fSchristos	0 0 ; issue done
227*440a403fSchristos	() ; state
228*440a403fSchristos	() ; inputs
229*440a403fSchristos	((storereg INT -1)) ; outputs
230*440a403fSchristos	() ; profile action (default)
231*440a403fSchristos	)
232*440a403fSchristos)
233*440a403fSchristos
234*440a403fSchristos; Hardware elements.
235*440a403fSchristos
236*440a403fSchristos(dnh h-pc "program counter" (PC PROFILE all-mep-isas) (pc) () () ())
237*440a403fSchristos
238*440a403fSchristos(define-hardware
239*440a403fSchristos  (name h-gpr)
240*440a403fSchristos  (comment "General purpose registers")
241*440a403fSchristos  (attrs all-mep-isas CACHE-ADDR PROFILE)
242*440a403fSchristos  (type register SI (16))
243*440a403fSchristos  (indices keyword "$"
244*440a403fSchristos	   (("0" 0) ("1" 1) ("2" 2) ("3" 3) ("4" 4) ("5" 5)
245*440a403fSchristos	    ("6" 6) ("7" 7) ("8" 8) ("9" 9) ("10" 10) ("11" 11)
246*440a403fSchristos	    ; "$8" is the preferred name for register 8, but "$tp", "$gp"
247*440a403fSchristos	    ; and "$sp" are preferred for their respective registers.
248*440a403fSchristos	    (fp  8) (tp 13) (gp 14) (sp 15)
249*440a403fSchristos	    ("12" 12) ("13" 13) ("14" 14) ("15" 15)))
250*440a403fSchristos)
251*440a403fSchristos
252*440a403fSchristos(define-hardware
253*440a403fSchristos  (name h-csr)
254*440a403fSchristos  (comment "Control/special registers")
255*440a403fSchristos  (attrs all-mep-isas PROFILE)
256*440a403fSchristos  (type register SI (32))
257*440a403fSchristos  (indices keyword "$"
258*440a403fSchristos	   ((pc 0)   (lp 1)   (sar 2)   (rpb  4) (rpe 5)   (rpc 6)
259*440a403fSchristos	    (hi 7)   (lo 8)   (mb0 12)  (me0 13) (mb1 14)  (me1 15)
260*440a403fSchristos	    (psw 16) (id 17)  (tmp 18)  (epc 19) (exc 20)  (cfg 21)
261*440a403fSchristos	    (npc 23) (dbg 24) (depc 25) (opt 26) (rcfg 27) (ccfg 28)
262*440a403fSchristos; begin-extra-csr-registers
263*440a403fSchristos	    (vid 22)
264*440a403fSchristos; end-extra-csr-registers
265*440a403fSchristos  ))
266*440a403fSchristos  (get (index) (c-call SI "cgen_get_csr_value" index))
267*440a403fSchristos  (set (index newval) (c-call VOID "cgen_set_csr_value" index newval))
268*440a403fSchristos)
269*440a403fSchristos
270*440a403fSchristos(define-pmacro (-reg-pair n) ((.sym n) n))
271*440a403fSchristos(define-hardware
272*440a403fSchristos  (name h-cr64)
273*440a403fSchristos  (comment "64-bit coprocessor registers")
274*440a403fSchristos  (attrs all-mep-isas)
275*440a403fSchristos  ; This assumes that the data path of the co-pro is 64 bits.
276*440a403fSchristos  (type register DI (32))
277*440a403fSchristos  (indices keyword "$c" (.map -reg-pair (.iota 32)))
278*440a403fSchristos  (set (index newval) (c-call VOID "h_cr64_queue_set" index newval))
279*440a403fSchristos)
280*440a403fSchristos(define-hardware
281*440a403fSchristos  (name h-cr64-w)
282*440a403fSchristos  (comment "64-bit coprocessor registers, pending writes")
283*440a403fSchristos  (attrs all-mep-isas)
284*440a403fSchristos  ; This assumes that the data path of the co-pro is 64 bits.
285*440a403fSchristos  (type register DI (32))
286*440a403fSchristos)
287*440a403fSchristos
288*440a403fSchristos(define-hardware
289*440a403fSchristos  (name h-cr)
290*440a403fSchristos  (comment "32-bit coprocessor registers")
291*440a403fSchristos  (attrs all-mep-isas VIRTUAL)
292*440a403fSchristos  (type register SI (32))
293*440a403fSchristos  (indices keyword "$c" (.map -reg-pair (.iota 32)))
294*440a403fSchristos  (set (index newval) (c-call VOID "h_cr64_set" index (ext DI newval)))
295*440a403fSchristos  (get (index) (trunc SI (c-call DI "h_cr64_get" index)))
296*440a403fSchristos)
297*440a403fSchristos
298*440a403fSchristos;; Given a coprocessor control register number N, expand to a
299*440a403fSchristos;; name/index pair: ($ccrN N)
300*440a403fSchristos(define-pmacro (-ccr-reg-pair n) ((.sym "$ccr" n) n))
301*440a403fSchristos
302*440a403fSchristos(define-hardware
303*440a403fSchristos  (name h-ccr)
304*440a403fSchristos  (comment "Coprocessor control registers")
305*440a403fSchristos  (attrs all-mep-isas)
306*440a403fSchristos  (type register SI (64))
307*440a403fSchristos  (indices keyword "" (.map -ccr-reg-pair (.iota 64)))
308*440a403fSchristos  (set (index newval) (c-call VOID "h_ccr_queue_set" index newval))
309*440a403fSchristos)
310*440a403fSchristos(define-hardware
311*440a403fSchristos  (name h-ccr-w)
312*440a403fSchristos  (comment "Coprocessor control registers, pending writes")
313*440a403fSchristos  (attrs all-mep-isas)
314*440a403fSchristos  (type register SI (64))
315*440a403fSchristos)
316*440a403fSchristos
317*440a403fSchristos
318*440a403fSchristos; Instruction fields.  Bit numbering reversed.
319*440a403fSchristos
320*440a403fSchristos; Conventions:
321*440a403fSchristos;
322*440a403fSchristos; N = number of bits in value
323*440a403fSchristos; A = alignment (2 or 4, omit for 1)
324*440a403fSchristos; B = leftmost (i.e. closest to zero) bit position
325*440a403fSchristos;
326*440a403fSchristos; -- Generic Fields (f-*) --
327*440a403fSchristos; N		number of bits in *value* (1-24)
328*440a403fSchristos; [us]		signed vs unsigned
329*440a403fSchristos; B		position of left-most bit (4-16)
330*440a403fSchristos; aA		opt. alignment (2=drop 1 lsb, 4=drop 2 lsbs, etc)
331*440a403fSchristos; n		opt. for noncontiguous fields
332*440a403fSchristos; f-foo-{hi,lo}	msb/lsb parts of field f-foo
333*440a403fSchristos;
334*440a403fSchristos; -- Operands --
335*440a403fSchristos; pcrelNaA	PC-relative branch target (signed)
336*440a403fSchristos; pcabsNaA	Absolute branch target (unsigned)
337*440a403fSchristos;
338*440a403fSchristos; [us]dispNaA	[un]signed displacement
339*440a403fSchristos; [us]immN	[un]signed immediate value
340*440a403fSchristos; addrNaA	absolute address (unsigned)
341*440a403fSchristos;
342*440a403fSchristos; Additional prefixes may be used for special cases.
343*440a403fSchristos
344*440a403fSchristos(dnf f-major   "major opcode"            (all-mep-core-isas)    0  4)
345*440a403fSchristos
346*440a403fSchristos(dnf f-rn      "register n"              (all-mep-core-isas)    4  4)
347*440a403fSchristos(dnf f-rn3     "register 0-7"            (all-mep-core-isas)    5  3)
348*440a403fSchristos(dnf f-rm      "register m"              (all-mep-core-isas)    8  4)
349*440a403fSchristos(dnf f-rl      "register l"              (all-mep-core-isas)   12  4)
350*440a403fSchristos(dnf f-sub2    "sub opcode (2 bits)"     (all-mep-core-isas)   14  2)
351*440a403fSchristos(dnf f-sub3    "sub opcode (3 bits)"     (all-mep-core-isas)   13  3)
352*440a403fSchristos(dnf f-sub4    "sub opcode (4 bits)"     (all-mep-core-isas)   12  4)
353*440a403fSchristos(dnf f-ext     "extended field"          (all-mep-core-isas)   16  8)
354*440a403fSchristos(dnf f-ext4    "extended field 16:4"     (all-mep-core-isas)   16  4)
355*440a403fSchristos(dnf f-ext62   "extended field 20:2"     (all-mep-core-isas)   20  2)
356*440a403fSchristos(dnf f-crn     "copro register n"        (all-mep-core-isas)    4  4)
357*440a403fSchristos
358*440a403fSchristos(df f-csrn-hi "cr hi 1u15" (all-mep-core-isas) 15 1 UINT #f #f)
359*440a403fSchristos(df f-csrn-lo "cr lo 4u8"  (all-mep-core-isas)  8 4 UINT #f #f)
360*440a403fSchristos(define-multi-ifield
361*440a403fSchristos  (name f-csrn)
362*440a403fSchristos  (comment "control reg")
363*440a403fSchristos  (attrs all-mep-core-isas)
364*440a403fSchristos  (mode UINT)
365*440a403fSchristos  (subfields f-csrn-hi f-csrn-lo)
366*440a403fSchristos  (insert (sequence ()
367*440a403fSchristos		    (set (ifield f-csrn-lo) (and (ifield f-csrn) #xf))
368*440a403fSchristos		    (set (ifield f-csrn-hi) (srl (ifield f-csrn) 4))))
369*440a403fSchristos  (extract (set (ifield f-csrn)
370*440a403fSchristos		(or (sll (ifield f-csrn-hi) 4) (ifield f-csrn-lo))))
371*440a403fSchristos  )
372*440a403fSchristos
373*440a403fSchristos(df f-crnx-hi "crx hi 1u28" (all-mep-core-isas) 28 1 UINT #f #f)
374*440a403fSchristos(df f-crnx-lo "crx lo 4u4"  (all-mep-core-isas)  4 4 UINT #f #f)
375*440a403fSchristos(define-multi-ifield
376*440a403fSchristos  (name f-crnx)
377*440a403fSchristos  (comment "copro register n (0-31)")
378*440a403fSchristos  (attrs all-mep-core-isas)
379*440a403fSchristos  (mode UINT)
380*440a403fSchristos  (subfields f-crnx-hi f-crnx-lo)
381*440a403fSchristos  (insert (sequence ()
382*440a403fSchristos		    (set (ifield f-crnx-lo) (and (ifield f-crnx) #xf))
383*440a403fSchristos		    (set (ifield f-crnx-hi) (srl (ifield f-crnx) 4))))
384*440a403fSchristos  (extract (set (ifield f-crnx)
385*440a403fSchristos		(or (sll (ifield f-crnx-hi) 4) (ifield f-crnx-lo))))
386*440a403fSchristos  )
387*440a403fSchristos
388*440a403fSchristos; Miscellaneous fields.
389*440a403fSchristos
390*440a403fSchristos(define-pmacro (dnfb n)
391*440a403fSchristos  (dnf (.sym f- n) (.str "bit " n) (all-mep-isas) n 1))
392*440a403fSchristos
393*440a403fSchristos; Define small fields used throughout the instruction set description.
394*440a403fSchristos; Each field (eg. `f-N') is at single bit field at position N.
395*440a403fSchristos
396*440a403fSchristos(dnfb  0)
397*440a403fSchristos(dnfb  1)
398*440a403fSchristos(dnfb  2)
399*440a403fSchristos(dnfb  3)
400*440a403fSchristos(dnfb  4)
401*440a403fSchristos(dnfb  5)
402*440a403fSchristos(dnfb  6)
403*440a403fSchristos(dnfb  7)
404*440a403fSchristos(dnfb  8)
405*440a403fSchristos(dnfb  9)
406*440a403fSchristos(dnfb  10)
407*440a403fSchristos(dnfb  11)
408*440a403fSchristos(dnfb  12)
409*440a403fSchristos(dnfb  13)
410*440a403fSchristos(dnfb  14)
411*440a403fSchristos(dnfb  15)
412*440a403fSchristos(dnfb  16)
413*440a403fSchristos(dnfb  17)
414*440a403fSchristos(dnfb  18)
415*440a403fSchristos(dnfb  19)
416*440a403fSchristos(dnfb  20)
417*440a403fSchristos(dnfb  21)
418*440a403fSchristos(dnfb  22)
419*440a403fSchristos(dnfb  23)
420*440a403fSchristos(dnfb  24)
421*440a403fSchristos(dnfb  25)
422*440a403fSchristos(dnfb  26)
423*440a403fSchristos(dnfb  27)
424*440a403fSchristos(dnfb  28)
425*440a403fSchristos(dnfb  29)
426*440a403fSchristos(dnfb  30)
427*440a403fSchristos(dnfb  31)
428*440a403fSchristos
429*440a403fSchristos; Branch/Jump target addresses
430*440a403fSchristos
431*440a403fSchristos(df f-8s8a2 "pc-rel addr (8 bits)"    (all-mep-core-isas PCREL-ADDR)  8  7 INT
432*440a403fSchristos    ((value pc) (sra SI (sub SI value    pc) 1))
433*440a403fSchristos    ((value pc) (add SI (sll SI value 1) pc)))
434*440a403fSchristos
435*440a403fSchristos(df f-12s4a2 "pc-rel addr (12 bits)"  (all-mep-core-isas PCREL-ADDR)  4 11 INT
436*440a403fSchristos    ((value pc) (sra SI (sub SI value    pc) 1))
437*440a403fSchristos    ((value pc) (add SI (sll SI value 1) pc)))
438*440a403fSchristos
439*440a403fSchristos(df f-17s16a2 "pc-rel addr (17 bits)" (all-mep-core-isas PCREL-ADDR) 16 16 INT
440*440a403fSchristos    ((value pc) (sra SI (sub SI value    pc) 1))
441*440a403fSchristos    ((value pc) (add SI (sll SI value 1) pc)))
442*440a403fSchristos
443*440a403fSchristos(df f-24s5a2n-hi "24s5a2n hi 16s16" (all-mep-core-isas PCREL-ADDR) 16 16  INT #f #f)
444*440a403fSchristos(df f-24s5a2n-lo "24s5a2n lo 7s5a2" (all-mep-core-isas PCREL-ADDR)  5  7 UINT #f #f)
445*440a403fSchristos(define-multi-ifield
446*440a403fSchristos  (name f-24s5a2n)
447*440a403fSchristos  (comment "pc-rel addr (24 bits align 2)")
448*440a403fSchristos  (attrs all-mep-core-isas PCREL-ADDR)
449*440a403fSchristos  (mode INT)
450*440a403fSchristos  (subfields f-24s5a2n-hi f-24s5a2n-lo)
451*440a403fSchristos  (insert (sequence ()
452*440a403fSchristos		    (set (ifield f-24s5a2n)
453*440a403fSchristos			 (sub (ifield f-24s5a2n) pc))
454*440a403fSchristos		    (set (ifield f-24s5a2n-lo)
455*440a403fSchristos			 (srl (and (ifield f-24s5a2n) #xfe) 1))
456*440a403fSchristos		    (set (ifield f-24s5a2n-hi)
457*440a403fSchristos			 (sra INT (ifield f-24s5a2n) 8))))
458*440a403fSchristos  (extract (set (ifield f-24s5a2n)
459*440a403fSchristos		(add SI (or (sll (ifield f-24s5a2n-hi) 8)
460*440a403fSchristos			    (sll (ifield f-24s5a2n-lo) 1))
461*440a403fSchristos		     pc)))
462*440a403fSchristos  )
463*440a403fSchristos
464*440a403fSchristos(df f-24u5a2n-hi "24u5a2n hi 16u16" (all-mep-core-isas) 16 16 UINT #f #f)
465*440a403fSchristos(df f-24u5a2n-lo "24u5a2n lo 7u5a2" (all-mep-core-isas)  5  7 UINT #f #f)
466*440a403fSchristos(define-multi-ifield
467*440a403fSchristos  (name f-24u5a2n)
468*440a403fSchristos  (comment "abs jump target (24 bits, alignment 2)")
469*440a403fSchristos  (attrs all-mep-core-isas ABS-ADDR)
470*440a403fSchristos  (mode UINT)
471*440a403fSchristos  (subfields f-24u5a2n-hi f-24u5a2n-lo)
472*440a403fSchristos  (insert (sequence ()
473*440a403fSchristos		    (set (ifield f-24u5a2n-lo)
474*440a403fSchristos			 (srl (and (ifield f-24u5a2n) #xff) 1))
475*440a403fSchristos		    (set (ifield f-24u5a2n-hi)
476*440a403fSchristos			 (srl (ifield f-24u5a2n) 8))
477*440a403fSchristos		    ))
478*440a403fSchristos  (extract (set (ifield f-24u5a2n)
479*440a403fSchristos		(or (sll (ifield f-24u5a2n-hi) 8)
480*440a403fSchristos		    (sll (ifield f-24u5a2n-lo) 1))))
481*440a403fSchristos  )
482*440a403fSchristos
483*440a403fSchristos; Displacement fields.
484*440a403fSchristos
485*440a403fSchristos(df f-2u6     "SAR offset (2 bits)"    (all-mep-core-isas)  6  2 UINT #f #f)
486*440a403fSchristos(df f-7u9     "tp-rel b (7 bits)"      (all-mep-core-isas)  9  7 UINT #f #f)
487*440a403fSchristos(df f-7u9a2   "tp-rel h (7 bits)"      (all-mep-core-isas)  9  6 UINT
488*440a403fSchristos    ((value pc) (srl SI value 1))
489*440a403fSchristos    ((value pc) (sll SI value 1)))
490*440a403fSchristos(df f-7u9a4   "tp/sp-rel w (7 bits)"   (all-mep-core-isas)  9  5 UINT
491*440a403fSchristos    ((value pc) (srl SI value 2))
492*440a403fSchristos    ((value pc) (sll SI value 2)))
493*440a403fSchristos(df f-16s16   "general 16-bit s-val"   (all-mep-core-isas) 16 16  INT #f #f)
494*440a403fSchristos
495*440a403fSchristos; Immediate fields.
496*440a403fSchristos
497*440a403fSchristos(df f-2u10   "swi level (2 bits)"      (all-mep-core-isas) 10  2 UINT #f #f)
498*440a403fSchristos(df f-3u5    "bit offset (3 bits)"     (all-mep-core-isas)  5  3 UINT #f #f)
499*440a403fSchristos(df f-4u8    "bCC const (4 bits)"      (all-mep-core-isas)  8  4 UINT #f #f)
500*440a403fSchristos(df f-5u8    "slt & shifts (5 bits)"   (all-mep-core-isas)  8  5 UINT #f #f)
501*440a403fSchristos(df f-5u24   "clip immediate (5 bits)" (all-mep-core-isas) 24  5 UINT #f #f)
502*440a403fSchristos(df f-6s8    "add immediate (6 bits)"  (all-mep-core-isas)  8  6  INT #f #f)
503*440a403fSchristos(df f-8s8    "add imm (8 bits)"        (all-mep-core-isas)  8  8  INT #f #f)
504*440a403fSchristos(df f-16u16  "general 16-bit u-val"    (all-mep-core-isas) 16 16 UINT #f #f)
505*440a403fSchristos(df f-12u16  "cmov fixed 1"            (all-mep-core-isas) 16 12 UINT #f #f)
506*440a403fSchristos(df f-3u29   "cmov fixed 2"            (all-mep-core-isas) 29  3 UINT #f #f)
507*440a403fSchristos
508*440a403fSchristos
509*440a403fSchristos; These are all for the coprocessor opcodes
510*440a403fSchristos
511*440a403fSchristos; The field is like IJKiiiiiii where I and J are toggled if K is set,
512*440a403fSchristos; for compatibility with older cores.
513*440a403fSchristos(define-pmacro (compute-cdisp10 val)
514*440a403fSchristos  (cond SI
515*440a403fSchristos	((and SI (cond SI ((and SI val #x80) (xor SI val #x300)) (else val)) #x200)
516*440a403fSchristos	 (sub (cond SI ((and SI val #x80) (xor SI val #x300)) (else val)) #x400))
517*440a403fSchristos	(else
518*440a403fSchristos	 (cond SI ((and SI val #x80) (xor SI val #x300)) (else val)))
519*440a403fSchristos	)
520*440a403fSchristos  )
521*440a403fSchristos(define-pmacro (extend-cdisp10 val)
522*440a403fSchristos  (cond SI
523*440a403fSchristos	((and SI (compute-cdisp10 val) #x200)
524*440a403fSchristos	 (sub (and SI (compute-cdisp10 val) #x3ff) #x400))
525*440a403fSchristos	(else
526*440a403fSchristos	 (and SI (compute-cdisp10 val) #x3ff))
527*440a403fSchristos	)
528*440a403fSchristos  )
529*440a403fSchristos
530*440a403fSchristos(df f-cdisp10    "cop imm10"          (all-mep-core-isas)   22  10 INT
531*440a403fSchristos    ((value pc) (extend-cdisp10 value))
532*440a403fSchristos    ((value pc) (extend-cdisp10 value))
533*440a403fSchristos    )
534*440a403fSchristos
535*440a403fSchristos; Non-contiguous fields.
536*440a403fSchristos
537*440a403fSchristos(df f-24u8a4n-hi "24u8a4n hi 16u16" (all-mep-core-isas) 16 16 UINT #f #f)
538*440a403fSchristos(df f-24u8a4n-lo "24u8a4n lo 8u8a4" (all-mep-core-isas)  8  6 UINT #f #f)
539*440a403fSchristos(define-multi-ifield
540*440a403fSchristos  (name f-24u8a4n)
541*440a403fSchristos  (comment "absolute 24-bit address")
542*440a403fSchristos  (attrs all-mep-core-isas)
543*440a403fSchristos  (mode UINT)
544*440a403fSchristos  (subfields f-24u8a4n-hi f-24u8a4n-lo)
545*440a403fSchristos  (insert (sequence ()
546*440a403fSchristos		    (set (ifield f-24u8a4n-hi) (srl (ifield f-24u8a4n) 8))
547*440a403fSchristos		    (set (ifield f-24u8a4n-lo) (srl (and (ifield f-24u8a4n) #xfc) 2))))
548*440a403fSchristos  (extract (set (ifield f-24u8a4n)
549*440a403fSchristos		(or (sll (ifield f-24u8a4n-hi) 8)
550*440a403fSchristos		    (sll (ifield f-24u8a4n-lo) 2))))
551*440a403fSchristos  )
552*440a403fSchristos
553*440a403fSchristos(df f-24u8n-hi "24u8n hi 16u16" (all-mep-core-isas) 16 16 UINT #f #f)
554*440a403fSchristos(df f-24u8n-lo "24u8n lo  8u8"  (all-mep-core-isas)  8  8 UINT #f #f)
555*440a403fSchristos(define-multi-ifield
556*440a403fSchristos  (name f-24u8n)
557*440a403fSchristos  (comment "24-bit constant")
558*440a403fSchristos  (attrs all-mep-core-isas)
559*440a403fSchristos  (mode UINT)
560*440a403fSchristos  (subfields f-24u8n-hi f-24u8n-lo)
561*440a403fSchristos  (insert (sequence ()
562*440a403fSchristos		    (set (ifield f-24u8n-hi) (srl (ifield f-24u8n) 8))
563*440a403fSchristos		    (set (ifield f-24u8n-lo) (and (ifield f-24u8n) #xff))))
564*440a403fSchristos  (extract (set (ifield f-24u8n)
565*440a403fSchristos		(or (sll (ifield f-24u8n-hi) 8)
566*440a403fSchristos		    (ifield f-24u8n-lo))))
567*440a403fSchristos  )
568*440a403fSchristos
569*440a403fSchristos(df f-24u4n-hi "24u4n hi  8u4"  (all-mep-core-isas)  4  8 UINT #f #f)
570*440a403fSchristos(df f-24u4n-lo "24u4n lo 16u16" (all-mep-core-isas) 16 16 UINT #f #f)
571*440a403fSchristos(define-multi-ifield
572*440a403fSchristos  (name f-24u4n)
573*440a403fSchristos  (comment "coprocessor code")
574*440a403fSchristos  (attrs all-mep-core-isas)
575*440a403fSchristos  (mode UINT)
576*440a403fSchristos  (subfields f-24u4n-hi f-24u4n-lo)
577*440a403fSchristos  (insert (sequence ()
578*440a403fSchristos		    (set (ifield f-24u4n-hi) (srl (ifield f-24u4n) 16))
579*440a403fSchristos		    (set (ifield f-24u4n-lo) (and (ifield f-24u4n) #xffff))))
580*440a403fSchristos  (extract (set (ifield f-24u4n)
581*440a403fSchristos		(or (sll (ifield f-24u4n-hi) 16)
582*440a403fSchristos		    (ifield f-24u4n-lo))))
583*440a403fSchristos  )
584*440a403fSchristos
585*440a403fSchristos(define-multi-ifield
586*440a403fSchristos  (name f-callnum)
587*440a403fSchristos  (comment "system call number field")
588*440a403fSchristos  (attrs all-mep-core-isas)
589*440a403fSchristos  (mode UINT)
590*440a403fSchristos  (subfields f-5 f-6 f-7 f-11)
591*440a403fSchristos  (insert (sequence ()
592*440a403fSchristos		    (set (ifield f-5)  (and (srl (ifield f-callnum) 3) 1))
593*440a403fSchristos		    (set (ifield f-6)  (and (srl (ifield f-callnum) 2) 1))
594*440a403fSchristos		    (set (ifield f-7)  (and (srl (ifield f-callnum) 1) 1))
595*440a403fSchristos		    (set (ifield f-11) (and (ifield f-callnum) 1))))
596*440a403fSchristos  (extract (set (ifield f-callnum)
597*440a403fSchristos		(or (sll (ifield f-5) 3)
598*440a403fSchristos		    (or (sll (ifield f-6) 2)
599*440a403fSchristos			(or (sll (ifield f-7) 1)
600*440a403fSchristos			    (ifield f-11))))))
601*440a403fSchristos  )
602*440a403fSchristos
603*440a403fSchristos(df f-ccrn-hi "ccrn hi  2u28" (all-mep-core-isas) 28 2 UINT #f #f)
604*440a403fSchristos(df f-ccrn-lo "ccrn lo  4u4"  (all-mep-core-isas)  4 4 UINT #f #f)
605*440a403fSchristos(define-multi-ifield
606*440a403fSchristos  (name f-ccrn)
607*440a403fSchristos  (comment "Coprocessor register number field")
608*440a403fSchristos  (attrs all-mep-core-isas)
609*440a403fSchristos  (mode UINT)
610*440a403fSchristos  (subfields f-ccrn-hi f-ccrn-lo)
611*440a403fSchristos  (insert (sequence ()
612*440a403fSchristos		    (set (ifield f-ccrn-hi)  (and (srl (ifield f-ccrn) 4) #x3))
613*440a403fSchristos		    (set (ifield f-ccrn-lo)  (and (ifield f-ccrn) #xf))))
614*440a403fSchristos  (extract (set (ifield f-ccrn)
615*440a403fSchristos		(or (sll (ifield f-ccrn-hi) 4)
616*440a403fSchristos		    (ifield f-ccrn-lo))))
617*440a403fSchristos  )
618*440a403fSchristos
619*440a403fSchristos; Operands.
620*440a403fSchristos
621*440a403fSchristos;; Only LABEL, REGNUM, FMAX_FLOAT and FMAX_INT are now relevant for correct
622*440a403fSchristos;; operation.  The others are mostly kept for backwards compatibility,
623*440a403fSchristos;; although they do affect the dummy prototypes in
624*440a403fSchristos;; gcc/config/mep/intrinsics.h.
625*440a403fSchristos(define-attr
626*440a403fSchristos  (type enum)
627*440a403fSchristos  (for operand)
628*440a403fSchristos  (name CDATA)
629*440a403fSchristos  (comment "datatype to use for C intrinsics mapping")
630*440a403fSchristos  (values LABEL REGNUM FMAX_FLOAT FMAX_INT
631*440a403fSchristos	  POINTER LONG ULONG SHORT USHORT CHAR UCHAR CP_DATA_BUS_INT)
632*440a403fSchristos  (default LONG))
633*440a403fSchristos
634*440a403fSchristos(define-attr
635*440a403fSchristos  (type enum)
636*440a403fSchristos  (for insn)
637*440a403fSchristos  (name CPTYPE)
638*440a403fSchristos  (comment "datatype to use for coprocessor values")
639*440a403fSchristos  (values CP_DATA_BUS_INT VECT V2SI V4HI V8QI V2USI V4UHI V8UQI)
640*440a403fSchristos  (default CP_DATA_BUS_INT))
641*440a403fSchristos
642*440a403fSchristos(define-attr
643*440a403fSchristos  (type enum)
644*440a403fSchristos  (for insn)
645*440a403fSchristos  (name CRET)
646*440a403fSchristos  ;; VOID - all arguments are passed as parameters; if any are written, pointers to them are passed.
647*440a403fSchristos  ;; FIRST - the first argument is the return value.
648*440a403fSchristos  ;; FIRSTCOPY - the first argument is the return value, but a copy is also the first parameter.
649*440a403fSchristos  (values VOID FIRST FIRSTCOPY)
650*440a403fSchristos  (default VOID)
651*440a403fSchristos  (comment "Insn's intrinsic returns void, or the first argument rather than (or in addition to) passing it."))
652*440a403fSchristos
653*440a403fSchristos(define-attr
654*440a403fSchristos  (type integer)
655*440a403fSchristos  (for operand)
656*440a403fSchristos  (name ALIGN)
657*440a403fSchristos  (comment "alignment of immediate operands")
658*440a403fSchristos  (default 1))
659*440a403fSchristos
660*440a403fSchristos(define-attr
661*440a403fSchristos  (for operand)
662*440a403fSchristos  (type boolean)
663*440a403fSchristos  (name RELOC_IMPLIES_OVERFLOW)
664*440a403fSchristos  (comment "Operand should not be considered as a candidate for relocs"))
665*440a403fSchristos
666*440a403fSchristos(define-attr
667*440a403fSchristos  (for hardware)
668*440a403fSchristos  (type boolean)
669*440a403fSchristos  (name IS_FLOAT)
670*440a403fSchristos  (comment "Register contains a floating point value"))
671*440a403fSchristos
672*440a403fSchristos(define-pmacro (dpop name commment attrib hwr field func)
673*440a403fSchristos  (define-full-operand name comment attrib
674*440a403fSchristos    hwr DFLT field ((parse func)) () ()))
675*440a403fSchristos(define-pmacro (dprp name commment attrib hwr field pafunc prfunc)
676*440a403fSchristos  (define-full-operand name comment attrib
677*440a403fSchristos    hwr DFLT field ((parse pafunc) (print prfunc)) () ()))
678*440a403fSchristos
679*440a403fSchristos(dnop r0        "register 0"              (all-mep-core-isas) h-gpr   0)
680*440a403fSchristos(dnop rn        "register Rn"             (all-mep-core-isas) h-gpr   f-rn)
681*440a403fSchristos(dnop rm        "register Rm"             (all-mep-core-isas) h-gpr   f-rm)
682*440a403fSchristos(dnop rl        "register Rl"             (all-mep-core-isas) h-gpr   f-rl)
683*440a403fSchristos(dnop rn3       "register 0-7"            (all-mep-core-isas) h-gpr   f-rn3)
684*440a403fSchristos
685*440a403fSchristos;; Variants of RM/RN with different CDATA attributes.  See comment above
686*440a403fSchristos;; CDATA for more details.
687*440a403fSchristos
688*440a403fSchristos(dnop rma       "register Rm holding pointer"          (all-mep-core-isas (CDATA POINTER)) h-gpr   f-rm)
689*440a403fSchristos
690*440a403fSchristos(dnop rnc       "register Rn holding char"             (all-mep-core-isas (CDATA LONG))    h-gpr   f-rn)
691*440a403fSchristos(dnop rnuc      "register Rn holding unsigned char"    (all-mep-core-isas (CDATA LONG))    h-gpr   f-rn)
692*440a403fSchristos(dnop rns       "register Rn holding short"            (all-mep-core-isas (CDATA LONG))    h-gpr   f-rn)
693*440a403fSchristos(dnop rnus      "register Rn holding unsigned short"   (all-mep-core-isas (CDATA LONG))    h-gpr   f-rn)
694*440a403fSchristos(dnop rnl       "register Rn holding long"             (all-mep-core-isas (CDATA LONG))    h-gpr   f-rn)
695*440a403fSchristos(dnop rnul      "register Rn holding unsigned  long"   (all-mep-core-isas (CDATA ULONG))   h-gpr   f-rn)
696*440a403fSchristos
697*440a403fSchristos(dnop rn3c       "register 0-7 holding unsigned char"    (all-mep-core-isas (CDATA LONG))  h-gpr   f-rn3)
698*440a403fSchristos(dnop rn3uc      "register 0-7 holding byte"             (all-mep-core-isas (CDATA LONG))  h-gpr   f-rn3)
699*440a403fSchristos(dnop rn3s       "register 0-7 holding unsigned short"   (all-mep-core-isas (CDATA LONG))  h-gpr   f-rn3)
700*440a403fSchristos(dnop rn3us      "register 0-7 holding short"            (all-mep-core-isas (CDATA LONG))  h-gpr   f-rn3)
701*440a403fSchristos(dnop rn3l       "register 0-7 holding unsigned long"    (all-mep-core-isas (CDATA LONG))  h-gpr   f-rn3)
702*440a403fSchristos(dnop rn3ul      "register 0-7 holding long"             (all-mep-core-isas (CDATA ULONG)) h-gpr   f-rn3)
703*440a403fSchristos
704*440a403fSchristos
705*440a403fSchristos(dnop lp        "link pointer"            (all-mep-core-isas) h-csr   1)
706*440a403fSchristos(dnop sar       "shift amount register"   (all-mep-core-isas) h-csr   2)
707*440a403fSchristos(dnop hi        "high result"             (all-mep-core-isas) h-csr   7)
708*440a403fSchristos(dnop lo        "low result"              (all-mep-core-isas) h-csr   8)
709*440a403fSchristos(dnop mb0       "modulo begin register 0" (all-mep-core-isas) h-csr  12)
710*440a403fSchristos(dnop me0       "modulo end register 0"   (all-mep-core-isas) h-csr  13)
711*440a403fSchristos(dnop mb1       "modulo begin register 1" (all-mep-core-isas) h-csr  14)
712*440a403fSchristos(dnop me1       "modulo end register 1"   (all-mep-core-isas) h-csr  15)
713*440a403fSchristos(dnop psw       "program status word"     (all-mep-core-isas) h-csr  16)
714*440a403fSchristos(dnop epc	"exception prog counter"  (all-mep-core-isas) h-csr  19)
715*440a403fSchristos(dnop exc       "exception cause"         (all-mep-core-isas) h-csr  20)
716*440a403fSchristos(dnop npc       "nmi program counter"     (all-mep-core-isas) h-csr  23)
717*440a403fSchristos(dnop dbg       "debug register"          (all-mep-core-isas) h-csr  24)
718*440a403fSchristos(dnop depc      "debug exception pc"      (all-mep-core-isas) h-csr  25)
719*440a403fSchristos(dnop opt       "option register"         (all-mep-core-isas) h-csr  26)
720*440a403fSchristos(dnop r1        "register 1"              (all-mep-core-isas) h-gpr   1)
721*440a403fSchristos(dnop tp        "tiny data area pointer"  (all-mep-core-isas) h-gpr  13)
722*440a403fSchristos(dnop sp        "stack pointer"           (all-mep-core-isas) h-gpr  15)
723*440a403fSchristos(dprp tpr       "TP register"             (all-mep-core-isas) h-gpr  13       "tpreg" "tpreg")
724*440a403fSchristos(dprp spr       "SP register"             (all-mep-core-isas) h-gpr  15       "spreg" "spreg")
725*440a403fSchristos
726*440a403fSchristos(define-full-operand
727*440a403fSchristos  csrn "control/special register" (all-mep-core-isas (CDATA REGNUM)) h-csr
728*440a403fSchristos  DFLT f-csrn ((parse "csrn")) () ()
729*440a403fSchristos)
730*440a403fSchristos
731*440a403fSchristos(dnop csrn-idx  "control/special reg idx" (all-mep-core-isas) h-uint  f-csrn)
732*440a403fSchristos(dnop crn64     "copro Rn (64-bit)"       (all-mep-core-isas (CDATA CP_DATA_BUS_INT)) h-cr64  f-crn)
733*440a403fSchristos(dnop crn       "copro Rn (32-bit)"       (all-mep-core-isas (CDATA CP_DATA_BUS_INT)) h-cr    f-crn)
734*440a403fSchristos(dnop crnx64    "copro Rn (0-31, 64-bit)" (all-mep-core-isas (CDATA CP_DATA_BUS_INT)) h-cr64  f-crnx)
735*440a403fSchristos(dnop crnx      "copro Rn (0-31, 32-bit)" (all-mep-core-isas (CDATA CP_DATA_BUS_INT)) h-cr    f-crnx)
736*440a403fSchristos(dnop ccrn      "copro control reg CCRn"  (all-mep-core-isas (CDATA REGNUM)) h-ccr   f-ccrn)
737*440a403fSchristos(dnop cccc      "copro flags"             (all-mep-core-isas) h-uint  f-rm)
738*440a403fSchristos
739*440a403fSchristos(dprp pcrel8a2  "pc-rel addr (8 bits)"    (all-mep-core-isas (CDATA LABEL) RELAX) h-sint  f-8s8a2   "mep_align" "address")
740*440a403fSchristos(dprp pcrel12a2 "pc-rel addr (12 bits)"   (all-mep-core-isas (CDATA LABEL) RELAX) h-sint  f-12s4a2  "mep_align" "address")
741*440a403fSchristos(dprp pcrel17a2 "pc-rel addr (17 bits)"   (all-mep-core-isas (CDATA LABEL) RELAX) h-sint  f-17s16a2 "mep_align" "address")
742*440a403fSchristos(dprp pcrel24a2 "pc-rel addr (24 bits)"   (all-mep-core-isas (CDATA LABEL))       h-sint  f-24s5a2n "mep_align" "address")
743*440a403fSchristos(dprp pcabs24a2 "pc-abs addr (24 bits)"   (all-mep-core-isas (CDATA LABEL))       h-uint  f-24u5a2n "mep_alignu" "address")
744*440a403fSchristos
745*440a403fSchristos(dpop sdisp16   "displacement (16 bits)"  (all-mep-core-isas) h-sint  f-16s16    "signed16")
746*440a403fSchristos(dpop simm16    "signed imm (16 bits)"    (all-mep-core-isas) h-sint  f-16s16    "signed16")
747*440a403fSchristos(dpop uimm16    "unsigned imm (16 bits)"  (all-mep-core-isas) h-uint  f-16u16    "unsigned16")
748*440a403fSchristos(dnop code16    "uci/dsp code (16 bits)"  (all-mep-core-isas) h-uint  f-16u16)
749*440a403fSchristos
750*440a403fSchristos(dnop udisp2    "SSARB addend (2 bits)"   (all-mep-core-isas) h-sint  f-2u6)
751*440a403fSchristos(dnop uimm2     "interrupt (2 bits)"      (all-mep-core-isas) h-uint  f-2u10)
752*440a403fSchristos
753*440a403fSchristos(dnop simm6     "add const (6 bits)"      (all-mep-core-isas) h-sint  f-6s8)
754*440a403fSchristos(dnop simm8     "mov const (8 bits)"      (all-mep-core-isas RELOC_IMPLIES_OVERFLOW)
755*440a403fSchristos                                             h-sint  f-8s8)
756*440a403fSchristos
757*440a403fSchristos(dpop addr24a4  "sw/lw addr (24 bits)"    (all-mep-core-isas (ALIGN 4)) h-uint  f-24u8a4n  "mep_alignu")
758*440a403fSchristos(dnop code24    "coprocessor code"        (all-mep-core-isas) h-uint  f-24u4n)
759*440a403fSchristos
760*440a403fSchristos(dnop callnum   "system call number"      (all-mep-core-isas) h-uint  f-callnum)
761*440a403fSchristos(dnop uimm3     "bit immediate (3 bits)"  (all-mep-core-isas) h-uint  f-3u5)
762*440a403fSchristos(dnop uimm4     "bCC const (4 bits)"      (all-mep-core-isas) h-uint  f-4u8)
763*440a403fSchristos(dnop uimm5     "bit/shift val (5 bits)"  (all-mep-core-isas) h-uint  f-5u8)
764*440a403fSchristos
765*440a403fSchristos(dpop udisp7    "tp-rel b (7 bits)"       (all-mep-core-isas)           h-uint  f-7u9      "unsigned7")
766*440a403fSchristos(dpop udisp7a2  "tp-rel h (7 bits)"       (all-mep-core-isas (ALIGN 2)) h-uint  f-7u9a2    "unsigned7")
767*440a403fSchristos(dpop udisp7a4  "tp/sp-rel w (7 bits)"    (all-mep-core-isas (ALIGN 4)) h-uint  f-7u9a4    "unsigned7")
768*440a403fSchristos(dpop uimm7a4   "sp w-addend (7 bits)"    (all-mep-core-isas (ALIGN 4)) h-uint  f-7u9a4    "mep_alignu")
769*440a403fSchristos
770*440a403fSchristos(dnop uimm24    "immediate (24 bits)"     (all-mep-core-isas) h-uint  f-24u8n)
771*440a403fSchristos
772*440a403fSchristos(dnop cimm4     "cache immed'te (4 bits)" (all-mep-core-isas) h-uint  f-rn)
773*440a403fSchristos(dnop cimm5     "clip immediate (5 bits)" (all-mep-core-isas) h-uint  f-5u24)
774*440a403fSchristos
775*440a403fSchristos(dpop cdisp10   "copro addend (8/10 bits)" (all-mep-core-isas) h-sint  f-cdisp10  "cdisp10")
776*440a403fSchristos(dpop cdisp10a2 "copro addend (8/10 bits)" (all-mep-core-isas) h-sint  f-cdisp10  "cdisp10")
777*440a403fSchristos(dpop cdisp10a4 "copro addend (8/10 bits)" (all-mep-core-isas) h-sint  f-cdisp10  "cdisp10")
778*440a403fSchristos(dpop cdisp10a8 "copro addend (8/10 bits)" (all-mep-core-isas) h-sint  f-cdisp10  "cdisp10")
779*440a403fSchristos
780*440a403fSchristos; Special operand representing the various ways that the literal zero can be
781*440a403fSchristos; specified.
782*440a403fSchristos(define-full-operand
783*440a403fSchristos  zero "Zero operand" (all-mep-core-isas) h-sint DFLT f-nil
784*440a403fSchristos  ((parse "zero")) () ()
785*440a403fSchristos)
786*440a403fSchristos
787*440a403fSchristos; Attributes.
788*440a403fSchristos
789*440a403fSchristos(define-attr
790*440a403fSchristos  (for insn)
791*440a403fSchristos  (type boolean)
792*440a403fSchristos  (name OPTIONAL_BIT_INSN)
793*440a403fSchristos  (comment "optional bit manipulation instruction"))
794*440a403fSchristos
795*440a403fSchristos(define-attr
796*440a403fSchristos  (for insn)
797*440a403fSchristos  (type boolean)
798*440a403fSchristos  (name OPTIONAL_MUL_INSN)
799*440a403fSchristos  (comment "optional 32-bit multiply instruction"))
800*440a403fSchristos
801*440a403fSchristos(define-attr
802*440a403fSchristos  (for insn)
803*440a403fSchristos  (type boolean)
804*440a403fSchristos  (name OPTIONAL_DIV_INSN)
805*440a403fSchristos  (comment "optional 32-bit divide instruction"))
806*440a403fSchristos
807*440a403fSchristos(define-attr
808*440a403fSchristos  (for insn)
809*440a403fSchristos  (type boolean)
810*440a403fSchristos  (name OPTIONAL_DEBUG_INSN)
811*440a403fSchristos  (comment "optional debug instruction"))
812*440a403fSchristos
813*440a403fSchristos(define-attr
814*440a403fSchristos  (for insn)
815*440a403fSchristos  (type boolean)
816*440a403fSchristos  (name OPTIONAL_LDZ_INSN)
817*440a403fSchristos  (comment "optional leading zeroes instruction"))
818*440a403fSchristos
819*440a403fSchristos(define-attr
820*440a403fSchristos  (for insn)
821*440a403fSchristos  (type boolean)
822*440a403fSchristos  (name OPTIONAL_ABS_INSN)
823*440a403fSchristos  (comment "optional absolute difference instruction"))
824*440a403fSchristos
825*440a403fSchristos(define-attr
826*440a403fSchristos  (for insn)
827*440a403fSchristos  (type boolean)
828*440a403fSchristos  (name OPTIONAL_AVE_INSN)
829*440a403fSchristos  (comment "optional average instruction"))
830*440a403fSchristos
831*440a403fSchristos(define-attr
832*440a403fSchristos  (for insn)
833*440a403fSchristos  (type boolean)
834*440a403fSchristos  (name OPTIONAL_MINMAX_INSN)
835*440a403fSchristos  (comment "optional min/max instruction"))
836*440a403fSchristos
837*440a403fSchristos(define-attr
838*440a403fSchristos  (for insn)
839*440a403fSchristos  (type boolean)
840*440a403fSchristos  (name OPTIONAL_CLIP_INSN)
841*440a403fSchristos  (comment "optional clipping instruction"))
842*440a403fSchristos
843*440a403fSchristos(define-attr
844*440a403fSchristos  (for insn)
845*440a403fSchristos  (type boolean)
846*440a403fSchristos  (name OPTIONAL_SAT_INSN)
847*440a403fSchristos  (comment "optional saturation instruction"))
848*440a403fSchristos
849*440a403fSchristos(define-attr
850*440a403fSchristos  (for insn)
851*440a403fSchristos  (type boolean)
852*440a403fSchristos  (name OPTIONAL_UCI_INSN)
853*440a403fSchristos  (comment "optional UCI instruction"))
854*440a403fSchristos
855*440a403fSchristos(define-attr
856*440a403fSchristos  (for insn)
857*440a403fSchristos  (type boolean)
858*440a403fSchristos  (name OPTIONAL_DSP_INSN)
859*440a403fSchristos  (comment "optional DSP instruction"))
860*440a403fSchristos
861*440a403fSchristos(define-attr
862*440a403fSchristos  (for insn)
863*440a403fSchristos  (type boolean)
864*440a403fSchristos  (name OPTIONAL_CP_INSN)
865*440a403fSchristos  (comment "optional coprocessor-related instruction"))
866*440a403fSchristos
867*440a403fSchristos(define-attr
868*440a403fSchristos  (for insn)
869*440a403fSchristos  (type boolean)
870*440a403fSchristos  (name OPTIONAL_CP64_INSN)
871*440a403fSchristos  (comment "optional coprocessor-related 64 data bit instruction"))
872*440a403fSchristos
873*440a403fSchristos(define-attr
874*440a403fSchristos  (for insn)
875*440a403fSchristos  (type boolean)
876*440a403fSchristos  (name OPTIONAL_VLIW64)
877*440a403fSchristos  (comment "optional vliw64 mode (vliw32 is default)"))
878*440a403fSchristos
879*440a403fSchristos(define-attr
880*440a403fSchristos  (for insn)
881*440a403fSchristos  (type enum)
882*440a403fSchristos  (name STALL)
883*440a403fSchristos  (attrs META)
884*440a403fSchristos  (values NONE SHIFTI INT2 LOAD STORE LDC STC LDCB STCB SSARB FSFT RET
885*440a403fSchristos	  ADVCK MUL MULR DIV)
886*440a403fSchristos  (default NONE)
887*440a403fSchristos  (comment "gcc stall attribute"))
888*440a403fSchristos
889*440a403fSchristos(define-attr
890*440a403fSchristos  (for insn)
891*440a403fSchristos  (type string)
892*440a403fSchristos  (name INTRINSIC)
893*440a403fSchristos  (attrs META)
894*440a403fSchristos  (comment "gcc intrinsic name"))
895*440a403fSchristos
896*440a403fSchristos(define-attr
897*440a403fSchristos  (for insn)
898*440a403fSchristos  (type enum)
899*440a403fSchristos  (name SLOT)
900*440a403fSchristos  (attrs META)
901*440a403fSchristos  (values NONE C3 V1 V3 P0S P0 P1)
902*440a403fSchristos  (default NONE)
903*440a403fSchristos  (comment "coprocessor slot type"))
904*440a403fSchristos
905*440a403fSchristos(define-attr
906*440a403fSchristos  (for insn)
907*440a403fSchristos  (type boolean)
908*440a403fSchristos  (name MAY_TRAP)
909*440a403fSchristos  (comment "instruction may generate an exception"))
910*440a403fSchristos
911*440a403fSchristos; Attributes for scheduling restrictions in vliw mode
912*440a403fSchristos
913*440a403fSchristos(define-attr
914*440a403fSchristos  (for insn)
915*440a403fSchristos  (type boolean)
916*440a403fSchristos  (name VLIW_ALONE)
917*440a403fSchristos  (comment "instruction can be scheduled alone in vliw mode"))
918*440a403fSchristos
919*440a403fSchristos(define-attr
920*440a403fSchristos  (for insn)
921*440a403fSchristos  (type boolean)
922*440a403fSchristos  (name VLIW_NO_CORE_NOP)
923*440a403fSchristos  (comment "there is no corresponding nop core instruction"))
924*440a403fSchristos
925*440a403fSchristos(define-attr
926*440a403fSchristos  (for insn)
927*440a403fSchristos  (type boolean)
928*440a403fSchristos  (name VLIW_NO_COP_NOP)
929*440a403fSchristos  (comment "there is no corresponding nop coprocessor instruction"))
930*440a403fSchristos
931*440a403fSchristos(define-attr
932*440a403fSchristos  (for insn)
933*440a403fSchristos  (type boolean)
934*440a403fSchristos  (name VLIW64_NO_MATCHING_NOP)
935*440a403fSchristos  (comment "there is no corresponding nop coprocessor instruction"))
936*440a403fSchristos(define-attr
937*440a403fSchristos  (for insn)
938*440a403fSchristos  (type boolean)
939*440a403fSchristos  (name VLIW32_NO_MATCHING_NOP)
940*440a403fSchristos  (comment "there is no corresponding nop coprocessor instruction"))
941*440a403fSchristos
942*440a403fSchristos(define-attr
943*440a403fSchristos  (for insn)
944*440a403fSchristos  (type boolean)
945*440a403fSchristos  (name VOLATILE)
946*440a403fSchristos  (comment "Insn is volatile."))
947*440a403fSchristos
948*440a403fSchristos(define-attr
949*440a403fSchristos  (for insn)
950*440a403fSchristos  (type integer)
951*440a403fSchristos  (name LATENCY)
952*440a403fSchristos  (comment "The latency of this insn, used for scheduling as an intrinsic in gcc")
953*440a403fSchristos  (default 0))
954*440a403fSchristos
955*440a403fSchristos; The MeP config tool will edit this.
956*440a403fSchristos(define-attr
957*440a403fSchristos  (type enum)
958*440a403fSchristos  (for insn)
959*440a403fSchristos  (name CONFIG)
960*440a403fSchristos  (values NONE ; config-attr-start
961*440a403fSchristos	default
962*440a403fSchristos	  ) ; config-attr-end
963*440a403fSchristos)
964*440a403fSchristos
965*440a403fSchristos
966*440a403fSchristos; Enumerations.
967*440a403fSchristos
968*440a403fSchristos(define-normal-insn-enum major "major opcodes" (all-mep-core-isas) MAJ_
969*440a403fSchristos  f-major
970*440a403fSchristos  (.map .str (.iota 16))
971*440a403fSchristos)
972*440a403fSchristos
973*440a403fSchristos
974*440a403fSchristos(define-pmacro (dni-isa xname xcomment xattrs xsyntax xformat xsemantics xtiming isa)
975*440a403fSchristos  (define-insn
976*440a403fSchristos    (name xname)
977*440a403fSchristos    (comment xcomment)
978*440a403fSchristos    (.splice attrs (.unsplice xattrs) (ISA isa))
979*440a403fSchristos    (syntax xsyntax)
980*440a403fSchristos    (format xformat)
981*440a403fSchristos    (semantics xsemantics)
982*440a403fSchristos    (.splice timing (.unsplice xtiming))
983*440a403fSchristos    )
984*440a403fSchristos)
985*440a403fSchristos
986*440a403fSchristos(define-pmacro (dnmi-isa xname xcomment xattrs xsyntax xemit isa)
987*440a403fSchristos  (dnmi xname xcomment (.splice (.unsplice xattrs) (ISA isa)) xsyntax xemit)
988*440a403fSchristos)
989*440a403fSchristos
990*440a403fSchristos; For making profiling calls and dynamic configuration
991*440a403fSchristos(define-pmacro (cg-profile caller callee)
992*440a403fSchristos  (c-call "cg_profile" caller callee)
993*440a403fSchristos)
994*440a403fSchristos; For dynamic configuration only
995*440a403fSchristos(define-pmacro (cg-profile-jump caller callee)
996*440a403fSchristos  (c-call "cg_profile_jump" caller callee)
997*440a403fSchristos)
998*440a403fSchristos
999*440a403fSchristos; For defining Core Instructions
1000*440a403fSchristos(define-pmacro (dnci xname xcomment xattrs xsyntax xformat xsemantics xtiming)
1001*440a403fSchristos  (dni-isa xname xcomment xattrs xsyntax xformat xsemantics xtiming all-core-isa-list)
1002*440a403fSchristos)
1003*440a403fSchristos(define-pmacro (dncmi xname xcomment xattrs xsyntax xemit)
1004*440a403fSchristos  (dnmi-isa xname xcomment xattrs xsyntax xemit all-core-isa-list)
1005*440a403fSchristos)
1006*440a403fSchristos
1007*440a403fSchristos; For defining Coprocessor Instructions
1008*440a403fSchristos;(define-pmacro (dncpi xname xcomment xattrs xsyntax xformat xsemantics xtiming)  (dni-isa xname xcomment xattrs xsyntax xformat xsemantics xtiming cop)
1009*440a403fSchristos;)
1010*440a403fSchristos
1011*440a403fSchristos;; flag setting macro
1012*440a403fSchristos(define-pmacro (set-bit xop xbitnum xval)
1013*440a403fSchristos  (set xop (or
1014*440a403fSchristos	    (and xop (inv (sll 1 xbitnum)))
1015*440a403fSchristos	    (and (sll 1 xbitnum) (sll xval xbitnum)))))
1016*440a403fSchristos
1017*440a403fSchristos;; some flags we commonly use in vliw reasoning / mode-switching etc.
1018*440a403fSchristos(define-pmacro (get-opt.vliw64) (and (srl opt 6) 1))
1019*440a403fSchristos(define-pmacro (get-opt.vliw32) (and (srl opt 5) 1))
1020*440a403fSchristos(define-pmacro (get-rm.lsb) (and rm 1))
1021*440a403fSchristos(define-pmacro (get-psw.om) (and (srl psw 12) 1))
1022*440a403fSchristos(define-pmacro (get-psw.nmi) (and (srl psw 9) 1))
1023*440a403fSchristos(define-pmacro (get-psw.iep) (and (srl psw 1) 1))
1024*440a403fSchristos(define-pmacro (get-psw.ump) (and (srl psw 3) 1))
1025*440a403fSchristos(define-pmacro (get-epc.etom) (and epc 1))
1026*440a403fSchristos(define-pmacro (get-npc.ntom) (and npc 1))
1027*440a403fSchristos(define-pmacro (get-lp.ltom) (and lp 1))
1028*440a403fSchristos
1029*440a403fSchristos(define-pmacro (set-psw.om zval) (set-bit (raw-reg h-csr 16) 12 zval))
1030*440a403fSchristos(define-pmacro (set-psw.nmi zval) (set-bit (raw-reg h-csr 16) 9 zval))
1031*440a403fSchristos(define-pmacro (set-psw.umc zval) (set-bit (raw-reg h-csr 16) 2 zval))
1032*440a403fSchristos(define-pmacro (set-psw.iec zval) (set-bit (raw-reg h-csr 16) 0 zval))
1033*440a403fSchristos(define-pmacro (set-rpe.elr zval) (set-bit (raw-reg h-csr 5) 0 zval))
1034*440a403fSchristos
1035*440a403fSchristos
1036*440a403fSchristos;; the "3 way switch" depending on our current operating mode and vliw status flags
1037*440a403fSchristos(define-pmacro (core-vliw-switch core-rtl vliw32-rtl vliw64-rtl)
1038*440a403fSchristos  (cond
1039*440a403fSchristos   ((andif (get-psw.om) (get-opt.vliw64)) vliw64-rtl)
1040*440a403fSchristos   ((andif (get-psw.om) (get-opt.vliw32)) vliw32-rtl)
1041*440a403fSchristos   (else core-rtl)))
1042*440a403fSchristos
1043*440a403fSchristos;; the varying-pcrel idiom
1044*440a403fSchristos(define-pmacro (set-vliw-modified-pcrel-offset xtarg xa xb xc)
1045*440a403fSchristos  (core-vliw-switch (set xtarg (add pc xa))
1046*440a403fSchristos		    (set xtarg (add pc xb))
1047*440a403fSchristos		    (set xtarg (add pc xc))))
1048*440a403fSchristos
1049*440a403fSchristos;; the increasing-alignment idiom in branch displacements
1050*440a403fSchristos(define-pmacro (set-vliw-alignment-modified xtarg zaddr)
1051*440a403fSchristos  (core-vliw-switch (set xtarg (and zaddr (inv 1)))
1052*440a403fSchristos		    (set xtarg (and zaddr (inv 3)))
1053*440a403fSchristos		    (set xtarg (and zaddr (inv 7)))))
1054*440a403fSchristos
1055*440a403fSchristos;; the increasing-alignment idiom in option-only form
1056*440a403fSchristos(define-pmacro (set-vliw-aliignment-modified-by-option xtarg zaddr)
1057*440a403fSchristos  (if (get-opt.vliw32)
1058*440a403fSchristos      (set xtarg (and zaddr (inv 3)))
1059*440a403fSchristos      (set xtarg (and zaddr (inv 7)))))
1060*440a403fSchristos
1061*440a403fSchristos
1062*440a403fSchristos
1063*440a403fSchristos; pmacros needed for coprocessor modulo addressing.
1064*440a403fSchristos
1065*440a403fSchristos; Taken from supplement ``The operation of the modulo addressing'' in
1066*440a403fSchristos; Toshiba documentation rev 2.2, p. 34.
1067*440a403fSchristos
1068*440a403fSchristos(define-pmacro (compute-mask0)
1069*440a403fSchristos  (sequence SI ((SI temp))
1070*440a403fSchristos    (set temp (or mb0 me0))
1071*440a403fSchristos    (srl (const SI -1) (c-call SI "do_ldz" temp))))
1072*440a403fSchristos
1073*440a403fSchristos(define-pmacro (mod0 immed)
1074*440a403fSchristos  (sequence SI ((SI modulo-mask))
1075*440a403fSchristos	    (set modulo-mask (compute-mask0))
1076*440a403fSchristos	    (if SI (eq (and rma modulo-mask) me0)
1077*440a403fSchristos		(or (and rma (inv modulo-mask)) mb0)
1078*440a403fSchristos		(add rma (ext SI immed)))))
1079*440a403fSchristos
1080*440a403fSchristos(define-pmacro (compute-mask1)
1081*440a403fSchristos  (sequence SI ((SI temp))
1082*440a403fSchristos    (set temp (or mb1 me1))
1083*440a403fSchristos    (srl (const SI -1) (c-call SI "do_ldz" temp))))
1084*440a403fSchristos
1085*440a403fSchristos(define-pmacro (mod1 immed)
1086*440a403fSchristos  (sequence SI ((SI modulo-mask))
1087*440a403fSchristos	    (set modulo-mask (compute-mask1))
1088*440a403fSchristos	    (if SI (eq (and rma modulo-mask) me1)
1089*440a403fSchristos		(or (and rma (inv modulo-mask)) mb1)
1090*440a403fSchristos		(add rma (ext SI immed)))))
1091*440a403fSchristos
1092*440a403fSchristos
1093*440a403fSchristos; Instructions.
1094*440a403fSchristos
1095*440a403fSchristos; A pmacro for use in semantic bodies of unimplemented insns.
1096*440a403fSchristos(define-pmacro (unimp mnemonic) (nop))
1097*440a403fSchristos
1098*440a403fSchristos; Core specific instructions
1099*440a403fSchristos; (include "mep-h1.cpu") ; -- exposed by MeP-Integrator
1100*440a403fSchristos(include "mep-c5.cpu") ; -- exposed by MeP-Integrator
1101*440a403fSchristos
1102*440a403fSchristos; Load/store instructions.
1103*440a403fSchristos
1104*440a403fSchristos(dnci sb "store byte (register indirect)" ((STALL STORE))
1105*440a403fSchristos     "sb $rnc,($rma)"
1106*440a403fSchristos     (+ MAJ_0 rnc rma (f-sub4 8))
1107*440a403fSchristos     (sequence ()
1108*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
1109*440a403fSchristos	       (set (mem UQI rma) (and rnc #xff)))
1110*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnc))
1111*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1112*440a403fSchristos	   (unit u-exec))))
1113*440a403fSchristos
1114*440a403fSchristos(dnci sh "store half-word (register indirect)" ((STALL STORE))
1115*440a403fSchristos     "sh $rns,($rma)"
1116*440a403fSchristos     (+ MAJ_0 rns rma (f-sub4 9))
1117*440a403fSchristos     (sequence ()
1118*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv 1)))
1119*440a403fSchristos	       (set (mem UHI (and rma (inv 1))) (and rns #xffff)))
1120*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rns))
1121*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1122*440a403fSchristos	   (unit u-exec))))
1123*440a403fSchristos
1124*440a403fSchristos(dnci sw "store word (register indirect)" ((STALL STORE))
1125*440a403fSchristos     "sw $rnl,($rma)"
1126*440a403fSchristos     (+ MAJ_0 rnl rma (f-sub4 10))
1127*440a403fSchristos     (sequence ()
1128*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv 3)))
1129*440a403fSchristos	       (set (mem USI (and rma (inv 3))) rnl))
1130*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnl))
1131*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1132*440a403fSchristos	   (unit u-exec))))
1133*440a403fSchristos
1134*440a403fSchristos(dnci lb "load byte (register indirect)" ((STALL LOAD) (LATENCY 2))
1135*440a403fSchristos     "lb $rnc,($rma)"
1136*440a403fSchristos     (+ MAJ_0 rnc rma (f-sub4 12))
1137*440a403fSchristos     (set rnc (ext SI (mem QI rma)))
1138*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1139*440a403fSchristos	   (unit u-exec)
1140*440a403fSchristos	   (unit u-load-gpr (out loadreg rnc)))))
1141*440a403fSchristos
1142*440a403fSchristos(dnci lh "load half-word (register indirect)" ((STALL LOAD) (LATENCY 2))
1143*440a403fSchristos     "lh $rns,($rma)"
1144*440a403fSchristos     (+ MAJ_0 rns rma (f-sub4 13))
1145*440a403fSchristos     (set rns (ext SI (mem HI (and rma (inv 1)))))
1146*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1147*440a403fSchristos	   (unit u-exec)
1148*440a403fSchristos	   (unit u-load-gpr (out loadreg rns)))))
1149*440a403fSchristos
1150*440a403fSchristos(dnci lw "load word (register indirect)" ((STALL LOAD) (LATENCY 2))
1151*440a403fSchristos     "lw $rnl,($rma)"
1152*440a403fSchristos     (+ MAJ_0 rnl rma (f-sub4 14))
1153*440a403fSchristos     (set rnl (mem SI (and rma (inv 3))))
1154*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1155*440a403fSchristos	   (unit u-exec)
1156*440a403fSchristos	   (unit u-load-gpr (out loadreg rnl)))))
1157*440a403fSchristos
1158*440a403fSchristos(dnci lbu "load unsigned byte (register indirect)" ((STALL LOAD) (LATENCY 2))
1159*440a403fSchristos     "lbu $rnuc,($rma)"
1160*440a403fSchristos     (+ MAJ_0 rnuc rma (f-sub4 11))
1161*440a403fSchristos     (set rnuc (zext SI (mem UQI rma)))
1162*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1163*440a403fSchristos	   (unit u-exec)
1164*440a403fSchristos	   (unit u-load-gpr (out loadreg rnuc)))))
1165*440a403fSchristos
1166*440a403fSchristos(dnci lhu "load unsigned half-word (register indirect)" ((STALL LOAD) (LATENCY 2))
1167*440a403fSchristos     "lhu $rnus,($rma)"
1168*440a403fSchristos     (+ MAJ_0 rnus rma (f-sub4 15))
1169*440a403fSchristos     (set rnus (zext SI (mem UHI (and rma (inv 1)))))
1170*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1171*440a403fSchristos	   (unit u-exec)
1172*440a403fSchristos	   (unit u-load-gpr (out loadreg rnus)))))
1173*440a403fSchristos
1174*440a403fSchristos(dnci sw-sp "store word (sp relative)" ((STALL STORE))
1175*440a403fSchristos     "sw $rnl,$udisp7a4($spr)"
1176*440a403fSchristos     (+ MAJ_4 rnl (f-8 0) udisp7a4 (f-sub2 2))
1177*440a403fSchristos     (sequence ()
1178*440a403fSchristos	       (c-call VOID "check_write_to_text" (and (add udisp7a4 sp) (inv 3)))
1179*440a403fSchristos	       (set (mem SI (and (add udisp7a4 sp) (inv 3))) rnl))
1180*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnl))
1181*440a403fSchristos	   (unit u-use-gpr (in usereg sp))
1182*440a403fSchristos	   (unit u-exec))))
1183*440a403fSchristos
1184*440a403fSchristos
1185*440a403fSchristos(dnci lw-sp "load word (sp relative)" ((STALL LOAD) (LATENCY 2))
1186*440a403fSchristos     "lw $rnl,$udisp7a4($spr)"
1187*440a403fSchristos     (+ MAJ_4 rnl (f-8 0) udisp7a4 (f-sub2 3))
1188*440a403fSchristos     (set rnl (mem SI (and (add udisp7a4 sp) (inv 3))))
1189*440a403fSchristos     ((mep (unit u-use-gpr (in usereg sp))
1190*440a403fSchristos	   (unit u-exec)
1191*440a403fSchristos	   (unit u-load-gpr (out loadreg rnl)))))
1192*440a403fSchristos
1193*440a403fSchristos(dnci sb-tp "store byte (tp relative)" ((STALL STORE))
1194*440a403fSchristos     "sb $rn3c,$udisp7($tpr)"
1195*440a403fSchristos     (+ MAJ_8 (f-4 0) rn3c (f-8 0) udisp7)
1196*440a403fSchristos     (sequence ()
1197*440a403fSchristos	       (c-call VOID "check_write_to_text" (add (zext SI udisp7) tp))
1198*440a403fSchristos	       (set (mem QI (add (zext SI udisp7) tp)) (and rn3c #xff)))
1199*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn3c))
1200*440a403fSchristos	   (unit u-use-gpr (in usereg tp))
1201*440a403fSchristos	   (unit u-exec))))
1202*440a403fSchristos
1203*440a403fSchristos(dnci sh-tp "store half-word (tp relative)" ((STALL STORE))
1204*440a403fSchristos     "sh $rn3s,$udisp7a2($tpr)"
1205*440a403fSchristos     (+ MAJ_8 (f-4 0) rn3s (f-8 1) udisp7a2 (f-15 0))
1206*440a403fSchristos     (sequence ()
1207*440a403fSchristos	       (c-call VOID "check_write_to_text" (and (add (zext SI udisp7a2) tp) (inv 1)))
1208*440a403fSchristos	       (set (mem HI (and (add (zext SI udisp7a2) tp) (inv 1))) (and rn3s #xffff)))
1209*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn3s))
1210*440a403fSchristos	   (unit u-use-gpr (in usereg tp))
1211*440a403fSchristos	   (unit u-exec))))
1212*440a403fSchristos
1213*440a403fSchristos(dnci sw-tp "store word (tp relative)" ((STALL STORE))
1214*440a403fSchristos     "sw $rn3l,$udisp7a4($tpr)"
1215*440a403fSchristos     (+ MAJ_4 (f-4 0) rn3l (f-8 1) udisp7a4 (f-sub2 2))
1216*440a403fSchristos     (sequence ()
1217*440a403fSchristos	       (c-call VOID "check_write_to_text" (and (add (zext SI udisp7a4) tp) (inv 3)))
1218*440a403fSchristos	       (set (mem SI (and (add (zext SI udisp7a4) tp) (inv 3))) rn3l))
1219*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn3l))
1220*440a403fSchristos	   (unit u-use-gpr (in usereg tp))
1221*440a403fSchristos	   (unit u-exec))))
1222*440a403fSchristos
1223*440a403fSchristos(dnci lb-tp "load byte (tp relative)" ((STALL LOAD) (LATENCY 2))
1224*440a403fSchristos     "lb $rn3c,$udisp7($tpr)"
1225*440a403fSchristos     (+ MAJ_8 (f-4 1) rn3c (f-8 0) udisp7)
1226*440a403fSchristos     (set rn3c (ext SI (mem QI (add (zext SI udisp7) tp))))
1227*440a403fSchristos     ((mep (unit u-use-gpr (in usereg tp))
1228*440a403fSchristos	   (unit u-exec)
1229*440a403fSchristos	   (unit u-load-gpr (out loadreg rn3c)))))
1230*440a403fSchristos
1231*440a403fSchristos(dnci lh-tp "load half-word (tp relative)" ((STALL LOAD) (LATENCY 2))
1232*440a403fSchristos     "lh $rn3s,$udisp7a2($tpr)"
1233*440a403fSchristos     (+ MAJ_8 (f-4 1) rn3s (f-8 1) udisp7a2 (f-15 0))
1234*440a403fSchristos     (set rn3s (ext SI (mem HI (and (add (zext SI udisp7a2) tp) (inv 1)))))
1235*440a403fSchristos     ((mep (unit u-use-gpr (in usereg tp))
1236*440a403fSchristos	   (unit u-exec)
1237*440a403fSchristos	   (unit u-load-gpr (out loadreg rn3s)))))
1238*440a403fSchristos
1239*440a403fSchristos(dnci lw-tp "load word (tp relative)" ((STALL LOAD) (LATENCY 2))
1240*440a403fSchristos     "lw $rn3l,$udisp7a4($tpr)"
1241*440a403fSchristos     (+ MAJ_4 (f-4 0) rn3l (f-8 1) udisp7a4 (f-sub2 3))
1242*440a403fSchristos     (set rn3l (mem SI (and (add (zext SI udisp7a4) tp) (inv 3))))
1243*440a403fSchristos     ((mep (unit u-use-gpr (in usereg tp))
1244*440a403fSchristos	   (unit u-exec)
1245*440a403fSchristos	   (unit u-load-gpr (out loadreg rn3l)))))
1246*440a403fSchristos
1247*440a403fSchristos(dnci lbu-tp "load unsigned byte (tp relative)" ((STALL LOAD) (LATENCY 2))
1248*440a403fSchristos     "lbu $rn3uc,$udisp7($tpr)"
1249*440a403fSchristos     (+ MAJ_4 (f-4 1) rn3uc (f-8 1) udisp7)
1250*440a403fSchristos     (set rn3uc (zext SI (mem QI (add (zext SI udisp7) tp))))
1251*440a403fSchristos     ((mep (unit u-use-gpr (in usereg tp))
1252*440a403fSchristos	   (unit u-exec)
1253*440a403fSchristos	   (unit u-load-gpr (out loadreg rn3uc)))))
1254*440a403fSchristos
1255*440a403fSchristos(dnci lhu-tp "load unsigned half-word (tp relative)" ((STALL LOAD) (LATENCY 2))
1256*440a403fSchristos     "lhu $rn3us,$udisp7a2($tpr)"
1257*440a403fSchristos     (+ MAJ_8 (f-4 1) rn3us (f-8 1) udisp7a2 (f-15 1))
1258*440a403fSchristos     (set rn3us (zext SI (mem HI (and (add (zext SI udisp7a2) tp) (inv 1)))))
1259*440a403fSchristos     ((mep (unit u-use-gpr (in usereg tp))
1260*440a403fSchristos	   (unit u-exec)
1261*440a403fSchristos	   (unit u-load-gpr (out loadreg rn3us)))))
1262*440a403fSchristos
1263*440a403fSchristos(dnci sb16 "store byte (16 bit displacement)" ((STALL STORE))
1264*440a403fSchristos     "sb $rnc,$sdisp16($rma)"
1265*440a403fSchristos     (+ MAJ_12 rnc rma (f-sub4 8) sdisp16)
1266*440a403fSchristos     (sequence ()
1267*440a403fSchristos	       (c-call VOID "check_write_to_text" (add rma (ext SI sdisp16)))
1268*440a403fSchristos	       (set (mem QI (add rma (ext SI sdisp16))) (and rnc #xff)))
1269*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnc))
1270*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1271*440a403fSchristos	   (unit u-exec))))
1272*440a403fSchristos
1273*440a403fSchristos(dnci sh16 "store half-word (16 bit displacement)" ((STALL STORE))
1274*440a403fSchristos     "sh $rns,$sdisp16($rma)"
1275*440a403fSchristos     (+ MAJ_12 rns rma (f-sub4 9) sdisp16)
1276*440a403fSchristos     (sequence ()
1277*440a403fSchristos	       (c-call VOID "check_write_to_text" (and (add rma (ext SI sdisp16)) (inv 1)))
1278*440a403fSchristos	       (set (mem HI (and (add rma (ext SI sdisp16)) (inv 1))) (and rns #xffff)))
1279*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rns))
1280*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1281*440a403fSchristos	   (unit u-exec))))
1282*440a403fSchristos
1283*440a403fSchristos(dnci sw16 "store word (16 bit displacement)" ((STALL STORE))
1284*440a403fSchristos     "sw $rnl,$sdisp16($rma)"
1285*440a403fSchristos     (+ MAJ_12 rnl rma (f-sub4 10) sdisp16)
1286*440a403fSchristos     (sequence ()
1287*440a403fSchristos	       (c-call "check_write_to_text" (and (add rma (ext SI sdisp16)) (inv 3)))
1288*440a403fSchristos	       (set (mem SI (and (add rma (ext SI sdisp16)) (inv 3))) rnl))
1289*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnl))
1290*440a403fSchristos	   (unit u-use-gpr (in usereg rma))
1291*440a403fSchristos	   (unit u-exec))))
1292*440a403fSchristos
1293*440a403fSchristos(dnci lb16 "load byte (16 bit displacement)" ((STALL LOAD) (LATENCY 2))
1294*440a403fSchristos     "lb $rnc,$sdisp16($rma)"
1295*440a403fSchristos     (+ MAJ_12 rnc rma (f-sub4 12) sdisp16)
1296*440a403fSchristos     (set rnc (ext SI (mem QI (add rma (ext SI sdisp16)))))
1297*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1298*440a403fSchristos	   (unit u-exec)
1299*440a403fSchristos	   (unit u-load-gpr (out loadreg rnc)))))
1300*440a403fSchristos
1301*440a403fSchristos(dnci lh16 "load half-word (16 bit displacement)" ((STALL LOAD) (LATENCY 2))
1302*440a403fSchristos     "lh $rns,$sdisp16($rma)"
1303*440a403fSchristos     (+ MAJ_12 rns rma (f-sub4 13) sdisp16)
1304*440a403fSchristos     (set rns (ext SI (mem HI (and (add rma (ext SI sdisp16)) (inv 1)))))
1305*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1306*440a403fSchristos	   (unit u-exec)
1307*440a403fSchristos	   (unit u-load-gpr (out loadreg rns)))))
1308*440a403fSchristos
1309*440a403fSchristos(dnci lw16 "load word (16 bit displacement)" ((STALL LOAD) (LATENCY 2))
1310*440a403fSchristos     "lw $rnl,$sdisp16($rma)"
1311*440a403fSchristos     (+ MAJ_12 rnl rma (f-sub4 14) sdisp16)
1312*440a403fSchristos     (set rnl (mem SI (and (add rma (ext SI sdisp16)) (inv 3))))
1313*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1314*440a403fSchristos	   (unit u-exec)
1315*440a403fSchristos	   (unit u-load-gpr (out loadreg rnl)))))
1316*440a403fSchristos
1317*440a403fSchristos(dnci lbu16 "load unsigned byte (16 bit displacement)" ((STALL LOAD) (LATENCY 2))
1318*440a403fSchristos     "lbu $rnuc,$sdisp16($rma)"
1319*440a403fSchristos     (+ MAJ_12 rnuc rma (f-sub4 11) sdisp16)
1320*440a403fSchristos     (set rnuc (zext SI (mem QI (add rma (ext SI sdisp16)))))
1321*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1322*440a403fSchristos	   (unit u-exec)
1323*440a403fSchristos	   (unit u-load-gpr (out loadreg rnuc)))))
1324*440a403fSchristos
1325*440a403fSchristos(dnci lhu16 "load unsigned half-word (16 bit displacement)" ((STALL LOAD) (LATENCY 2))
1326*440a403fSchristos     "lhu $rnus,$sdisp16($rma)"
1327*440a403fSchristos     (+ MAJ_12 rnus rma (f-sub4 15) sdisp16)
1328*440a403fSchristos     (set rnus (zext SI (mem HI (and (add rma (ext SI sdisp16)) (inv 1)))))
1329*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
1330*440a403fSchristos	   (unit u-exec)
1331*440a403fSchristos	   (unit u-load-gpr (out loadreg rnus)))))
1332*440a403fSchristos
1333*440a403fSchristos(dnci sw24 "store word (24 bit absolute addressing)" ((STALL STORE))
1334*440a403fSchristos     "sw $rnl,($addr24a4)"
1335*440a403fSchristos     (+ MAJ_14 rnl addr24a4 (f-sub2 2))
1336*440a403fSchristos     (sequence ()
1337*440a403fSchristos	       (c-call VOID "check_write_to_text" (zext SI addr24a4))
1338*440a403fSchristos	       (set (mem SI (zext SI addr24a4)) rnl))
1339*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rnl))
1340*440a403fSchristos	   (unit u-exec))))
1341*440a403fSchristos
1342*440a403fSchristos(dnci lw24 "load word (24 bit absolute addressing)" ((STALL LOAD) (LATENCY 2))
1343*440a403fSchristos     "lw $rnl,($addr24a4)"
1344*440a403fSchristos     (+ MAJ_14 rnl addr24a4 (f-sub2 3))
1345*440a403fSchristos     (set rnl (mem SI (zext SI addr24a4)))
1346*440a403fSchristos     ((mep (unit u-exec)
1347*440a403fSchristos	   (unit u-load-gpr (out loadreg rnl)))))
1348*440a403fSchristos
1349*440a403fSchristos
1350*440a403fSchristos; Extension instructions.
1351*440a403fSchristos
1352*440a403fSchristos(dnci extb "sign extend byte" ()
1353*440a403fSchristos     "extb $rn"
1354*440a403fSchristos     (+ MAJ_1 rn (f-rm 0) (f-sub4 13))
1355*440a403fSchristos     (set rn (ext SI (and QI rn #xff)))
1356*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1357*440a403fSchristos	   (unit u-exec))))
1358*440a403fSchristos
1359*440a403fSchristos(dnci exth "sign extend half-word" ()
1360*440a403fSchristos     "exth $rn"
1361*440a403fSchristos     (+ MAJ_1 rn (f-rm 2) (f-sub4 13))
1362*440a403fSchristos     (set rn (ext SI (and HI rn #xffff)))
1363*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1364*440a403fSchristos	   (unit u-exec))))
1365*440a403fSchristos
1366*440a403fSchristos(dnci extub "zero extend byte" ()
1367*440a403fSchristos     "extub $rn"
1368*440a403fSchristos     (+ MAJ_1 rn (f-rm 8) (f-sub4 13))
1369*440a403fSchristos     (set rn (zext SI (and rn #xff)))
1370*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1371*440a403fSchristos	   (unit u-exec))))
1372*440a403fSchristos
1373*440a403fSchristos(dnci extuh "zero extend half-word" ()
1374*440a403fSchristos     "extuh $rn"
1375*440a403fSchristos     (+ MAJ_1 rn (f-rm 10) (f-sub4 13))
1376*440a403fSchristos     (set rn (zext SI (and rn #xffff)))
1377*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1378*440a403fSchristos	   (unit u-exec))))
1379*440a403fSchristos
1380*440a403fSchristos
1381*440a403fSchristos; Shift amount manipulation instructions.
1382*440a403fSchristos
1383*440a403fSchristos(dnci ssarb "set sar to bytes" ((STALL SSARB) VOLATILE)
1384*440a403fSchristos     "ssarb $udisp2($rm)"
1385*440a403fSchristos     (+ MAJ_1 (f-4 0) (f-5 0) udisp2 rm (f-sub4 12))
1386*440a403fSchristos     (if (c-call BI "big_endian_p")
1387*440a403fSchristos         (set sar (zext SI (mul (and (add udisp2 rm) 3) 8)))
1388*440a403fSchristos         (set sar (sub 32 (zext SI (mul (and (add udisp2 rm) 3) 8)))))
1389*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1390*440a403fSchristos	   (unit u-exec))))
1391*440a403fSchristos
1392*440a403fSchristos
1393*440a403fSchristos; Move instructions.
1394*440a403fSchristos
1395*440a403fSchristos(dnci mov "move" ()
1396*440a403fSchristos     "mov $rn,$rm"
1397*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 0))
1398*440a403fSchristos     (set rn rm)
1399*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1400*440a403fSchristos	   (unit u-exec))))
1401*440a403fSchristos
1402*440a403fSchristos(dnci movi8 "move 8-bit immediate" ()
1403*440a403fSchristos     "mov $rn,$simm8"
1404*440a403fSchristos     (+ MAJ_5 rn simm8)
1405*440a403fSchristos     (set rn (ext SI simm8))
1406*440a403fSchristos     ())
1407*440a403fSchristos
1408*440a403fSchristos(dnci movi16 "move 16-bit immediate" ()
1409*440a403fSchristos     "mov $rn,$simm16"
1410*440a403fSchristos     (+ MAJ_12 rn (f-rm 0) (f-sub4 1) simm16)
1411*440a403fSchristos     (set rn (ext SI simm16))
1412*440a403fSchristos     ())
1413*440a403fSchristos
1414*440a403fSchristos(dnci movu24 "move 24-bit unsigned immediate" ()
1415*440a403fSchristos     "movu $rn3,$uimm24"
1416*440a403fSchristos     (+ MAJ_13 (f-4 0) rn3 uimm24)
1417*440a403fSchristos     (set rn3 (zext SI uimm24))
1418*440a403fSchristos     ())
1419*440a403fSchristos
1420*440a403fSchristos(dnci movu16 "move 16-bit unsigned immediate" ()
1421*440a403fSchristos     "movu $rn,$uimm16"
1422*440a403fSchristos     (+ MAJ_12 rn (f-rm 1) (f-sub4 1) uimm16)
1423*440a403fSchristos     (set rn (zext SI uimm16))
1424*440a403fSchristos     ())
1425*440a403fSchristos
1426*440a403fSchristos(dnci movh "move high 16-bit immediate" ()
1427*440a403fSchristos     "movh $rn,$uimm16"
1428*440a403fSchristos     (+ MAJ_12 rn (f-rm 2) (f-sub4 1) uimm16)
1429*440a403fSchristos     (set rn (sll uimm16 16))
1430*440a403fSchristos     ())
1431*440a403fSchristos
1432*440a403fSchristos
1433*440a403fSchristos; Arithmetic instructions.
1434*440a403fSchristos
1435*440a403fSchristos(dnci add3 "add three registers" ()
1436*440a403fSchristos     "add3 $rl,$rn,$rm"
1437*440a403fSchristos     (+ MAJ_9 rn rm rl)
1438*440a403fSchristos     (set rl (add rn rm))
1439*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1440*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1441*440a403fSchristos	   (unit u-exec))))
1442*440a403fSchristos
1443*440a403fSchristos(dnci add "add" ()
1444*440a403fSchristos     "add $rn,$simm6"
1445*440a403fSchristos     (+ MAJ_6 rn simm6 (f-sub2 0))
1446*440a403fSchristos     (set rn (add rn (ext SI simm6)))
1447*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1448*440a403fSchristos	   (unit u-exec))))
1449*440a403fSchristos
1450*440a403fSchristos(dnci add3i "add two registers and immediate" ()
1451*440a403fSchristos     "add3 $rn,$spr,$uimm7a4"
1452*440a403fSchristos     (+ MAJ_4 rn (f-8 0) uimm7a4 (f-sub2 0))
1453*440a403fSchristos     (set rn (add sp (zext SI uimm7a4)))
1454*440a403fSchristos     ((mep (unit u-use-gpr (in usereg sp))
1455*440a403fSchristos	   (unit u-exec))))
1456*440a403fSchristos
1457*440a403fSchristos(dnci advck3 "add overflow check" ((STALL ADVCK))
1458*440a403fSchristos     "advck3 \\$0,$rn,$rm"
1459*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 7))
1460*440a403fSchristos     (if (add-oflag rn rm 0)
1461*440a403fSchristos	 (set r0 1)
1462*440a403fSchristos	 (set r0 0))
1463*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1464*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1465*440a403fSchristos	   (unit u-exec))))
1466*440a403fSchristos
1467*440a403fSchristos(dnci sub "subtract" ()
1468*440a403fSchristos     "sub $rn,$rm"
1469*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 4))
1470*440a403fSchristos     (set rn (sub rn rm))
1471*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1472*440a403fSchristos           (unit u-use-gpr (in usereg rm)))))
1473*440a403fSchristos
1474*440a403fSchristos(dnci sbvck3 "subtraction overflow check" ((STALL ADVCK))
1475*440a403fSchristos     "sbvck3 \\$0,$rn,$rm"
1476*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 5))
1477*440a403fSchristos     (if (sub-oflag rn rm 0)
1478*440a403fSchristos	 (set r0 1)
1479*440a403fSchristos	 (set r0 0))
1480*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1481*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1482*440a403fSchristos	   (unit u-exec))))
1483*440a403fSchristos
1484*440a403fSchristos(dnci neg "negate" ()
1485*440a403fSchristos     "neg $rn,$rm"
1486*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 1))
1487*440a403fSchristos     (set rn (neg rm))
1488*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1489*440a403fSchristos	   (unit u-exec))))
1490*440a403fSchristos
1491*440a403fSchristos(dnci slt3 "set if less than" ()
1492*440a403fSchristos     "slt3 \\$0,$rn,$rm"
1493*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 2))
1494*440a403fSchristos     (if (lt rn rm)
1495*440a403fSchristos	 (set r0 1)
1496*440a403fSchristos	 (set r0 0))
1497*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1498*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1499*440a403fSchristos	   (unit u-exec))))
1500*440a403fSchristos
1501*440a403fSchristos(dnci sltu3 "set less than unsigned" ()
1502*440a403fSchristos     "sltu3 \\$0,$rn,$rm"
1503*440a403fSchristos     (+ MAJ_0 rn rm (f-sub4 3))
1504*440a403fSchristos     (if (ltu rn rm)
1505*440a403fSchristos	 (set r0 1)
1506*440a403fSchristos	 (set r0 0))
1507*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1508*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1509*440a403fSchristos	   (unit u-exec))))
1510*440a403fSchristos
1511*440a403fSchristos(dnci slt3i "set if less than immediate" ()
1512*440a403fSchristos     "slt3 \\$0,$rn,$uimm5"
1513*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 1))
1514*440a403fSchristos     (if (lt rn (zext SI uimm5))
1515*440a403fSchristos	 (set r0 1)
1516*440a403fSchristos	 (set r0 0))
1517*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1518*440a403fSchristos	   (unit u-exec))))
1519*440a403fSchristos
1520*440a403fSchristos(dnci sltu3i "set if less than unsigned immediate" ()
1521*440a403fSchristos     "sltu3 \\$0,$rn,$uimm5"
1522*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 5))
1523*440a403fSchristos     (if (ltu rn (zext SI uimm5))
1524*440a403fSchristos	 (set r0 1)
1525*440a403fSchristos	 (set r0 0))
1526*440a403fSchristos     ())
1527*440a403fSchristos
1528*440a403fSchristos(dnci sl1ad3 "shift left one and add" ((STALL INT2))
1529*440a403fSchristos     "sl1ad3 \\$0,$rn,$rm"
1530*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 6))
1531*440a403fSchristos     (set r0 (add (sll rn 1) rm))
1532*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1533*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1534*440a403fSchristos	   (unit u-exec))))
1535*440a403fSchristos
1536*440a403fSchristos(dnci sl2ad3 "shift left two and add" ((STALL INT2))
1537*440a403fSchristos     "sl2ad3 \\$0,$rn,$rm"
1538*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 7))
1539*440a403fSchristos     (set r0 (add (sll rn 2) rm))
1540*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1541*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1542*440a403fSchristos	   (unit u-exec))))
1543*440a403fSchristos
1544*440a403fSchristos(dnci add3x "three operand add (extended)" ()
1545*440a403fSchristos     "add3 $rn,$rm,$simm16"
1546*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 0) simm16)
1547*440a403fSchristos     (set rn (add rm (ext SI simm16)))
1548*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1549*440a403fSchristos	   (unit u-exec))))
1550*440a403fSchristos
1551*440a403fSchristos(dnci slt3x "set if less than (extended)" ()
1552*440a403fSchristos     "slt3 $rn,$rm,$simm16"
1553*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 2) simm16)
1554*440a403fSchristos     (if (lt rm (ext SI simm16))
1555*440a403fSchristos	 (set rn 1)
1556*440a403fSchristos	 (set rn 0))
1557*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1558*440a403fSchristos	   (unit u-exec))))
1559*440a403fSchristos
1560*440a403fSchristos(dnci sltu3x "set if less than unsigned (extended)" ()
1561*440a403fSchristos     "sltu3 $rn,$rm,$uimm16"
1562*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 3) uimm16)
1563*440a403fSchristos     (if (ltu rm (zext SI uimm16))
1564*440a403fSchristos	 (set rn 1)
1565*440a403fSchristos	 (set rn 0))
1566*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1567*440a403fSchristos	   (unit u-exec))))
1568*440a403fSchristos
1569*440a403fSchristos
1570*440a403fSchristos; Logical instructions.
1571*440a403fSchristos
1572*440a403fSchristos(dnci or "bitwise or" ()
1573*440a403fSchristos     "or $rn,$rm"
1574*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 0))
1575*440a403fSchristos     (set rn (or rn rm))
1576*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1577*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1578*440a403fSchristos	   (unit u-exec))))
1579*440a403fSchristos
1580*440a403fSchristos(dnci and "bitwise and" ()
1581*440a403fSchristos     "and $rn,$rm"
1582*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 1))
1583*440a403fSchristos     (set rn (and rn rm))
1584*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1585*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1586*440a403fSchristos	   (unit u-exec))))
1587*440a403fSchristos
1588*440a403fSchristos(dnci xor "bitwise exclusive or" ()
1589*440a403fSchristos     "xor $rn,$rm"
1590*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 2))
1591*440a403fSchristos     (set rn (xor rn rm))
1592*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1593*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1594*440a403fSchristos	   (unit u-exec))))
1595*440a403fSchristos
1596*440a403fSchristos(dnci nor "bitwise negated or" ()
1597*440a403fSchristos     "nor $rn,$rm"
1598*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 3))
1599*440a403fSchristos     (set rn (inv (or rn rm)))
1600*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1601*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1602*440a403fSchristos	   (unit u-exec))))
1603*440a403fSchristos
1604*440a403fSchristos(dnci or3 "or three operand" ()
1605*440a403fSchristos     "or3 $rn,$rm,$uimm16"
1606*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 4) uimm16)
1607*440a403fSchristos     (set rn (or rm (zext SI uimm16)))
1608*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1609*440a403fSchristos	   (unit u-exec))))
1610*440a403fSchristos
1611*440a403fSchristos(dnci and3 "and three operand" ()
1612*440a403fSchristos     "and3 $rn,$rm,$uimm16"
1613*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 5) uimm16)
1614*440a403fSchristos     (set rn (and rm (zext SI uimm16)))
1615*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1616*440a403fSchristos	   (unit u-exec))))
1617*440a403fSchristos
1618*440a403fSchristos(dnci xor3 "exclusive or three operand" ()
1619*440a403fSchristos     "xor3 $rn,$rm,$uimm16"
1620*440a403fSchristos     (+ MAJ_12 rn rm (f-sub4 6) uimm16)
1621*440a403fSchristos     (set rn (xor rm (zext SI uimm16)))
1622*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1623*440a403fSchristos	   (unit u-exec))))
1624*440a403fSchristos
1625*440a403fSchristos
1626*440a403fSchristos; Shift instructions.
1627*440a403fSchristos
1628*440a403fSchristos(dnci sra "shift right arithmetic" ((STALL INT2))
1629*440a403fSchristos     "sra $rn,$rm"
1630*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 13))
1631*440a403fSchristos     (set rn (sra rn (and rm #x1f)))
1632*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1633*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1634*440a403fSchristos	   (unit u-exec))))
1635*440a403fSchristos
1636*440a403fSchristos(dnci srl "shift right logical" ((STALL INT2))
1637*440a403fSchristos     "srl $rn,$rm"
1638*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 12))
1639*440a403fSchristos     (set rn (srl rn (and rm #x1f)))
1640*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1641*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1642*440a403fSchristos	   (unit u-exec))))
1643*440a403fSchristos
1644*440a403fSchristos(dnci sll "shift left logical" ((STALL INT2))
1645*440a403fSchristos     "sll $rn,$rm"
1646*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 14))
1647*440a403fSchristos     (set rn (sll rn (and rm #x1f)))
1648*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1649*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1650*440a403fSchristos	   (unit u-exec))))
1651*440a403fSchristos
1652*440a403fSchristos(dnci srai "shift right arithmetic (immediate)" ((STALL SHIFTI))
1653*440a403fSchristos     "sra $rn,$uimm5"
1654*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 3))
1655*440a403fSchristos     (set rn (sra rn uimm5))
1656*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1657*440a403fSchristos	   (unit u-exec))))
1658*440a403fSchristos
1659*440a403fSchristos(dnci srli "shift right logical (immediate)" ((STALL SHIFTI))
1660*440a403fSchristos     "srl $rn,$uimm5"
1661*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 2))
1662*440a403fSchristos     (set rn (srl rn uimm5))
1663*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1664*440a403fSchristos	   (unit u-exec))))
1665*440a403fSchristos
1666*440a403fSchristos(dnci slli "shift left logical (immediate)" ((STALL SHIFTI))
1667*440a403fSchristos     "sll $rn,$uimm5"
1668*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 6))
1669*440a403fSchristos     (set rn (sll rn uimm5))
1670*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1671*440a403fSchristos	   (unit u-exec))))
1672*440a403fSchristos
1673*440a403fSchristos(dnci sll3 "three-register shift left logical" ((STALL INT2))
1674*440a403fSchristos     "sll3 \\$0,$rn,$uimm5"
1675*440a403fSchristos     (+ MAJ_6 rn uimm5 (f-sub3 7))
1676*440a403fSchristos     (set r0 (sll rn uimm5))
1677*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1678*440a403fSchristos	   (unit u-exec))))
1679*440a403fSchristos
1680*440a403fSchristos(dnci fsft "field shift" ((STALL FSFT) VOLATILE)
1681*440a403fSchristos     "fsft $rn,$rm"
1682*440a403fSchristos     (+ MAJ_2 rn rm (f-sub4 15))
1683*440a403fSchristos     (sequence ((DI temp) (QI shamt))
1684*440a403fSchristos	       (set shamt (and sar #x3f))
1685*440a403fSchristos	       (set temp (sll (or (sll (zext DI rn) 32) (zext DI rm)) shamt))
1686*440a403fSchristos	       (set rn (subword SI (srl temp 32) 1)))
1687*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1688*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1689*440a403fSchristos	   (unit u-exec))))
1690*440a403fSchristos
1691*440a403fSchristos
1692*440a403fSchristos; Branch/jump instructions.
1693*440a403fSchristos
1694*440a403fSchristos(dnci bra "branch" (RELAXABLE)
1695*440a403fSchristos     "bra $pcrel12a2"
1696*440a403fSchristos     (+ MAJ_11 pcrel12a2 (f-15 0))
1697*440a403fSchristos     (set-vliw-alignment-modified pc pcrel12a2)
1698*440a403fSchristos     ((mep (unit u-branch)
1699*440a403fSchristos	   (unit u-exec))))
1700*440a403fSchristos
1701*440a403fSchristos(dnci beqz "branch if equal zero" (RELAXABLE)
1702*440a403fSchristos     "beqz $rn,$pcrel8a2"
1703*440a403fSchristos     (+ MAJ_10 rn pcrel8a2 (f-15 0))
1704*440a403fSchristos     (if (eq rn 0)
1705*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel8a2))
1706*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1707*440a403fSchristos	   (unit u-exec)
1708*440a403fSchristos	   (unit u-branch))))
1709*440a403fSchristos
1710*440a403fSchristos(dnci bnez "branch if not equal zero" (RELAXABLE)
1711*440a403fSchristos     "bnez $rn,$pcrel8a2"
1712*440a403fSchristos     (+ MAJ_10 rn pcrel8a2 (f-15 1))
1713*440a403fSchristos     (if (ne rn 0)
1714*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel8a2))
1715*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1716*440a403fSchristos	   (unit u-exec)
1717*440a403fSchristos	   (unit u-branch))))
1718*440a403fSchristos
1719*440a403fSchristos(dnci beqi "branch equal immediate" (RELAXABLE)
1720*440a403fSchristos     "beqi $rn,$uimm4,$pcrel17a2"
1721*440a403fSchristos     (+ MAJ_14 rn uimm4 (f-sub4 0) pcrel17a2)
1722*440a403fSchristos     (if (eq rn (zext SI uimm4))
1723*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1724*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1725*440a403fSchristos	   (unit u-exec)
1726*440a403fSchristos	   (unit u-branch))))
1727*440a403fSchristos
1728*440a403fSchristos(dnci bnei "branch not equal immediate" (RELAXABLE)
1729*440a403fSchristos     "bnei $rn,$uimm4,$pcrel17a2"
1730*440a403fSchristos     (+ MAJ_14 rn uimm4 (f-sub4 4) pcrel17a2)
1731*440a403fSchristos     (if (ne rn (zext SI uimm4))
1732*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1733*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1734*440a403fSchristos	   (unit u-exec)
1735*440a403fSchristos	   (unit u-branch))))
1736*440a403fSchristos
1737*440a403fSchristos(dnci blti "branch less than immediate" (RELAXABLE)
1738*440a403fSchristos     "blti $rn,$uimm4,$pcrel17a2"
1739*440a403fSchristos     (+ MAJ_14 rn uimm4 (f-sub4 12) pcrel17a2)
1740*440a403fSchristos     (if (lt rn (zext SI uimm4))
1741*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1742*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1743*440a403fSchristos	   (unit u-exec)
1744*440a403fSchristos	   (unit u-branch))))
1745*440a403fSchristos
1746*440a403fSchristos(dnci bgei "branch greater than immediate" (RELAXABLE)
1747*440a403fSchristos     "bgei $rn,$uimm4,$pcrel17a2"
1748*440a403fSchristos     (+ MAJ_14 rn uimm4 (f-sub4 8) pcrel17a2)
1749*440a403fSchristos     (if (ge rn (zext SI uimm4))
1750*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1751*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1752*440a403fSchristos	   (unit u-exec)
1753*440a403fSchristos	   (unit u-branch))))
1754*440a403fSchristos
1755*440a403fSchristos(dnci beq "branch equal" ()
1756*440a403fSchristos     "beq $rn,$rm,$pcrel17a2"
1757*440a403fSchristos     (+ MAJ_14 rn rm (f-sub4 1) pcrel17a2)
1758*440a403fSchristos     (if (eq rn rm)
1759*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1760*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1761*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1762*440a403fSchristos	   (unit u-exec)
1763*440a403fSchristos	   (unit u-branch))))
1764*440a403fSchristos
1765*440a403fSchristos(dnci bne "branch not equal" ()
1766*440a403fSchristos     "bne $rn,$rm,$pcrel17a2"
1767*440a403fSchristos     (+ MAJ_14 rn rm (f-sub4 5) pcrel17a2)
1768*440a403fSchristos     (if (ne rn rm)
1769*440a403fSchristos	 (set-vliw-alignment-modified pc pcrel17a2))
1770*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1771*440a403fSchristos           (unit u-use-gpr (in usereg rm))
1772*440a403fSchristos	   (unit u-exec)
1773*440a403fSchristos	   (unit u-branch))))
1774*440a403fSchristos
1775*440a403fSchristos(dnci bsr12 "branch to subroutine (12 bit displacement)" (RELAXABLE)
1776*440a403fSchristos     "bsr $pcrel12a2"
1777*440a403fSchristos     (+ MAJ_11 pcrel12a2 (f-15 1))
1778*440a403fSchristos     (sequence ()
1779*440a403fSchristos	       (cg-profile pc pcrel12a2)
1780*440a403fSchristos	       (set-vliw-modified-pcrel-offset lp 2 4 8)
1781*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel12a2))
1782*440a403fSchristos     ((mep (unit u-exec)
1783*440a403fSchristos	   (unit u-branch))))
1784*440a403fSchristos
1785*440a403fSchristos(dnci bsr24 "branch to subroutine (24 bit displacement)" ()
1786*440a403fSchristos     "bsr $pcrel24a2"
1787*440a403fSchristos     (+ MAJ_13 (f-4 1) (f-sub4 9) pcrel24a2)
1788*440a403fSchristos     (sequence ()
1789*440a403fSchristos	       (cg-profile pc pcrel24a2)
1790*440a403fSchristos	       (set-vliw-modified-pcrel-offset lp 4 4 8)
1791*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel24a2))
1792*440a403fSchristos     ((mep (unit u-exec)
1793*440a403fSchristos	   (unit u-branch))))
1794*440a403fSchristos
1795*440a403fSchristos(dnci jmp "jump" ()
1796*440a403fSchristos     "jmp $rm"
1797*440a403fSchristos     (+ MAJ_1 (f-rn 0) rm (f-sub4 14))
1798*440a403fSchristos     (sequence ()
1799*440a403fSchristos	       (if (eq (get-psw.om) 0)
1800*440a403fSchristos		   ;; core mode
1801*440a403fSchristos		   (if (get-rm.lsb)
1802*440a403fSchristos		       (sequence ()
1803*440a403fSchristos				 (set-psw.om 1) ;; enter VLIW mode
1804*440a403fSchristos				 (set-vliw-aliignment-modified-by-option pc rm))
1805*440a403fSchristos		       (set pc (and rm (inv 1))))
1806*440a403fSchristos		   ;; VLIW mode
1807*440a403fSchristos		   (if (get-rm.lsb)
1808*440a403fSchristos		       (sequence ()
1809*440a403fSchristos				 (set-psw.om 0) ;; enter core mode
1810*440a403fSchristos				 (set pc (and rm (inv 1))))
1811*440a403fSchristos		       (set-vliw-aliignment-modified-by-option pc rm)))
1812*440a403fSchristos	       (cg-profile-jump pc rm))
1813*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1814*440a403fSchristos	   (unit u-exec)
1815*440a403fSchristos	   (unit u-branch))))
1816*440a403fSchristos
1817*440a403fSchristos(dnci jmp24 "jump (24 bit target)" ()
1818*440a403fSchristos     "jmp $pcabs24a2"
1819*440a403fSchristos     (+ MAJ_13 (f-4 1) (f-sub4 8) pcabs24a2)
1820*440a403fSchristos     (sequence ()
1821*440a403fSchristos	       (set-vliw-alignment-modified pc (or (and pc #xf0000000) pcabs24a2))
1822*440a403fSchristos	       (cg-profile-jump pc pcabs24a2))
1823*440a403fSchristos     ((mep (unit u-exec)
1824*440a403fSchristos	   (unit u-branch))))
1825*440a403fSchristos
1826*440a403fSchristos(dnci jsr "jump to subroutine" ()
1827*440a403fSchristos     "jsr $rm"
1828*440a403fSchristos     (+ MAJ_1 (f-rn 0) rm (f-sub4 15))
1829*440a403fSchristos     (sequence ()
1830*440a403fSchristos	       (cg-profile pc rm)
1831*440a403fSchristos	       (set-vliw-modified-pcrel-offset lp 2 4 8)
1832*440a403fSchristos	       (set-vliw-alignment-modified pc rm))
1833*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
1834*440a403fSchristos	   (unit u-exec)
1835*440a403fSchristos	   (unit u-branch))))
1836*440a403fSchristos
1837*440a403fSchristos(dnci ret "return from subroutine" ((STALL RET))
1838*440a403fSchristos     "ret"
1839*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 0) (f-sub4 2))
1840*440a403fSchristos     (sequence ()
1841*440a403fSchristos	       (if (eq (get-psw.om) 0)
1842*440a403fSchristos		   ;; core mode
1843*440a403fSchristos		   (if (get-lp.ltom) ;; link-pointer "toggle mode" bit
1844*440a403fSchristos		       (sequence ()
1845*440a403fSchristos				 (set-psw.om 1) ;; enter VLIW mode
1846*440a403fSchristos				 (set-vliw-aliignment-modified-by-option pc lp))
1847*440a403fSchristos		       (set pc (and lp (inv 1))))
1848*440a403fSchristos		   ;; VLIW mode
1849*440a403fSchristos		   (if (get-lp.ltom) ;; link-pointer "toggle mode" bit
1850*440a403fSchristos		       (sequence ()
1851*440a403fSchristos				 (set-psw.om 0) ;; enter VLIW mode
1852*440a403fSchristos				 (set pc (and lp (inv 1))))
1853*440a403fSchristos		       (set-vliw-aliignment-modified-by-option pc lp)))
1854*440a403fSchristos	       (c-call VOID "notify_ret" pc))
1855*440a403fSchristos     ((mep (unit u-exec)
1856*440a403fSchristos	   (unit u-branch))))
1857*440a403fSchristos
1858*440a403fSchristos
1859*440a403fSchristos; Repeat instructions.
1860*440a403fSchristos
1861*440a403fSchristos(dnci repeat "repeat specified repeat block" ()
1862*440a403fSchristos     "repeat $rn,$pcrel17a2"
1863*440a403fSchristos     (+ MAJ_14 rn (f-rm 0) (f-sub4 9) pcrel17a2)
1864*440a403fSchristos     (sequence ()
1865*440a403fSchristos	       (set-vliw-modified-pcrel-offset (reg h-csr 4) 4 4 8)
1866*440a403fSchristos	       (set-vliw-alignment-modified (reg h-csr 5) pcrel17a2)
1867*440a403fSchristos	       (set (reg h-csr 6) rn))
1868*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1869*440a403fSchristos	   (unit u-exec))))
1870*440a403fSchristos
1871*440a403fSchristos(dnci erepeat "endless repeat" ()
1872*440a403fSchristos     "erepeat $pcrel17a2"
1873*440a403fSchristos     (+ MAJ_14 (f-rn 0) (f-rm 1) (f-sub4 9) pcrel17a2)
1874*440a403fSchristos     (sequence ()
1875*440a403fSchristos	       (set-vliw-modified-pcrel-offset (reg h-csr 4) 4 4 8)
1876*440a403fSchristos	       (set-vliw-alignment-modified (reg h-csr 5) pcrel17a2)
1877*440a403fSchristos	       (set-rpe.elr 1)
1878*440a403fSchristos	       ; rpc may be undefined for erepeat
1879*440a403fSchristos	       ; use 1 to trigger repeat logic in the sim's main loop
1880*440a403fSchristos	       (set (reg h-csr 6) 1))
1881*440a403fSchristos     ())
1882*440a403fSchristos
1883*440a403fSchristos
1884*440a403fSchristos; Control instructions.
1885*440a403fSchristos
1886*440a403fSchristos;; special store variants
1887*440a403fSchristos
1888*440a403fSchristos(dnci stc_lp "store to control register lp" ((STALL STC))
1889*440a403fSchristos      "stc $rn,\\$lp"
1890*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 1) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 0))
1891*440a403fSchristos      (set lp rn)
1892*440a403fSchristos      ((mep (unit u-use-gpr (in usereg rn))
1893*440a403fSchristos	    (unit u-store-ctrl-reg (out storereg lp))
1894*440a403fSchristos	    (unit u-exec))))
1895*440a403fSchristos
1896*440a403fSchristos(dnci stc_hi "store to control register hi" ((STALL STC))
1897*440a403fSchristos      "stc $rn,\\$hi"
1898*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 7) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 0))
1899*440a403fSchristos      (set hi rn)
1900*440a403fSchristos      ((mep (unit u-use-gpr (in usereg rn))
1901*440a403fSchristos	    (unit u-store-ctrl-reg (out storereg hi))
1902*440a403fSchristos	    (unit u-exec))))
1903*440a403fSchristos
1904*440a403fSchristos(dnci stc_lo "store to control register lo" ((STALL STC))
1905*440a403fSchristos      "stc $rn,\\$lo"
1906*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 8) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 0))
1907*440a403fSchristos      (set lo rn)
1908*440a403fSchristos      ((mep (unit u-use-gpr (in usereg rn))
1909*440a403fSchristos	    (unit u-store-ctrl-reg (out storereg lo))
1910*440a403fSchristos	    (unit u-exec))))
1911*440a403fSchristos
1912*440a403fSchristos;; general store
1913*440a403fSchristos
1914*440a403fSchristos(dnci stc "store to control register" (VOLATILE (STALL STC))
1915*440a403fSchristos     "stc $rn,$csrn"
1916*440a403fSchristos     (+ MAJ_7 rn csrn (f-12 1) (f-13 0) (f-14 0))
1917*440a403fSchristos     (set csrn rn)
1918*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
1919*440a403fSchristos	   (unit u-store-ctrl-reg (out storereg csrn))
1920*440a403fSchristos	   (unit u-exec))))
1921*440a403fSchristos
1922*440a403fSchristos;; special load variants
1923*440a403fSchristos
1924*440a403fSchristos(dnci ldc_lp "load from control register lp" ((STALL LDC))
1925*440a403fSchristos      "ldc $rn,\\$lp"
1926*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 1) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 1))
1927*440a403fSchristos      (set rn lp)
1928*440a403fSchristos      ((mep (unit u-use-ctrl-reg (in usereg lp))
1929*440a403fSchristos	    (unit u-exec)
1930*440a403fSchristos	    (unit u-load-gpr (out loadreg rn)))))
1931*440a403fSchristos
1932*440a403fSchristos
1933*440a403fSchristos(dnci ldc_hi "load from control register hi" ((STALL LDC))
1934*440a403fSchristos      "ldc $rn,\\$hi"
1935*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 7) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 1))
1936*440a403fSchristos      (set rn hi)
1937*440a403fSchristos      ((mep (unit u-use-ctrl-reg (in usereg hi))
1938*440a403fSchristos	    (unit u-exec)
1939*440a403fSchristos	    (unit u-load-gpr (out loadreg rn)))))
1940*440a403fSchristos
1941*440a403fSchristos(dnci ldc_lo "load from control register lo" ((STALL LDC))
1942*440a403fSchristos      "ldc $rn,\\$lo"
1943*440a403fSchristos      (+ MAJ_7 rn (f-csrn-lo 8) (f-csrn-hi 0) (f-12 1) (f-13 0) (f-14 1))
1944*440a403fSchristos      (set rn lo)
1945*440a403fSchristos      ((mep (unit u-use-ctrl-reg (in usereg lo))
1946*440a403fSchristos	    (unit u-exec)
1947*440a403fSchristos	    (unit u-load-gpr (out loadreg rn)))))
1948*440a403fSchristos
1949*440a403fSchristos;; general load
1950*440a403fSchristos
1951*440a403fSchristos(dnci ldc "load from control register" (VOLATILE (STALL LDC) (LATENCY 2))
1952*440a403fSchristos     "ldc $rn,$csrn"
1953*440a403fSchristos     (+ MAJ_7 rn csrn (f-12 1) (f-13 0) (f-14 1))
1954*440a403fSchristos     (if (eq (ifield f-csrn) 0)
1955*440a403fSchristos	 ;; loading from the pc
1956*440a403fSchristos	 (set-vliw-modified-pcrel-offset rn 2 4 8)
1957*440a403fSchristos	 ;; loading from something else
1958*440a403fSchristos	 (set rn csrn))
1959*440a403fSchristos      ((mep (unit u-use-ctrl-reg (in usereg csrn))
1960*440a403fSchristos	    (unit u-exec)
1961*440a403fSchristos	    (unit u-load-gpr (out loadreg rn)))))
1962*440a403fSchristos
1963*440a403fSchristos(dnci di "disable interrupt" (VOLATILE)
1964*440a403fSchristos     "di"
1965*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 0) (f-sub4 0))
1966*440a403fSchristos     ; clear psw.iec
1967*440a403fSchristos     (set psw (sll (srl psw 1) 1))
1968*440a403fSchristos     ())
1969*440a403fSchristos
1970*440a403fSchristos(dnci ei "enable interrupt" (VOLATILE)
1971*440a403fSchristos     "ei"
1972*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 1) (f-sub4 0))
1973*440a403fSchristos     ; set psw.iec
1974*440a403fSchristos     (set psw (or psw 1))
1975*440a403fSchristos     ())
1976*440a403fSchristos
1977*440a403fSchristos(dnci reti "return from interrupt" ((STALL RET))
1978*440a403fSchristos     "reti"
1979*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 1) (f-sub4 2))
1980*440a403fSchristos     (if (eq (get-psw.om) 0)
1981*440a403fSchristos	 ;; core operation mode
1982*440a403fSchristos	 (if (get-psw.nmi)
1983*440a403fSchristos	     ;; return from NMI
1984*440a403fSchristos	     (if (get-npc.ntom)
1985*440a403fSchristos		 ;; return in VLIW operation mode
1986*440a403fSchristos		 (sequence ()
1987*440a403fSchristos			   (set-psw.om 1)
1988*440a403fSchristos			   (set-vliw-aliignment-modified-by-option pc npc)
1989*440a403fSchristos			   (set-psw.nmi 0))
1990*440a403fSchristos		 ;; return in core mode
1991*440a403fSchristos		 (sequence ()
1992*440a403fSchristos			   (set pc (and npc (inv 1)))
1993*440a403fSchristos			   (set-psw.nmi 0)))
1994*440a403fSchristos	     ;; return from non-NMI
1995*440a403fSchristos	     (if (get-epc.etom)
1996*440a403fSchristos		 ;; return in VLIW mode
1997*440a403fSchristos		 (sequence ()
1998*440a403fSchristos			   (set-psw.om 1)
1999*440a403fSchristos			   (set-vliw-aliignment-modified-by-option pc epc)
2000*440a403fSchristos			   (set-psw.umc (get-psw.ump))
2001*440a403fSchristos			   (set-psw.iec (get-psw.iep)))
2002*440a403fSchristos		 ;; return in core mode
2003*440a403fSchristos		 (sequence ()
2004*440a403fSchristos			   (set pc (and epc (inv 1)))
2005*440a403fSchristos			   (set-psw.umc (get-psw.ump))
2006*440a403fSchristos			   (set-psw.iec (get-psw.iep)))))
2007*440a403fSchristos	 ;; VLIW operation mode
2008*440a403fSchristos	 ;; xxx undefined
2009*440a403fSchristos	 (nop))
2010*440a403fSchristos     ((mep (unit u-exec)
2011*440a403fSchristos	   (unit u-branch))))
2012*440a403fSchristos
2013*440a403fSchristos(dnci halt "halt pipeline" (VOLATILE)
2014*440a403fSchristos     "halt"
2015*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 2) (f-sub4 2))
2016*440a403fSchristos     ; set psw.halt
2017*440a403fSchristos     (set (raw-reg h-csr 16) (or psw (sll 1 11)))
2018*440a403fSchristos     ())
2019*440a403fSchristos
2020*440a403fSchristos(dnci sleep "sleep pipeline" (VOLATILE)
2021*440a403fSchristos     "sleep"
2022*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 6) (f-sub4 2))
2023*440a403fSchristos     (c-call VOID "do_sleep")
2024*440a403fSchristos     ())
2025*440a403fSchristos
2026*440a403fSchristos(dnci swi "software interrupt" (MAY_TRAP VOLATILE)
2027*440a403fSchristos     "swi $uimm2"
2028*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-8 0) (f-9 0) uimm2 (f-sub4 6))
2029*440a403fSchristos     (cond
2030*440a403fSchristos      ((eq uimm2 0) (set exc (or exc (sll 1 4))))
2031*440a403fSchristos      ((eq uimm2 1) (set exc (or exc (sll 1 5))))
2032*440a403fSchristos      ((eq uimm2 2) (set exc (or exc (sll 1 6))))
2033*440a403fSchristos      ((eq uimm2 3) (set exc (or exc (sll 1 7)))))
2034*440a403fSchristos     ())
2035*440a403fSchristos
2036*440a403fSchristos(dnci break "break exception" (MAY_TRAP VOLATILE)
2037*440a403fSchristos     "break"
2038*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 3) (f-sub4 2))
2039*440a403fSchristos     (set pc (c-call USI "break_exception" pc))
2040*440a403fSchristos     ((mep (unit u-exec)
2041*440a403fSchristos	   (unit u-branch))))
2042*440a403fSchristos
2043*440a403fSchristos(dnci syncm "synchronise with memory" (VOLATILE)
2044*440a403fSchristos     "syncm"
2045*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 1) (f-sub4 1))
2046*440a403fSchristos     (unimp "syncm")
2047*440a403fSchristos     ())
2048*440a403fSchristos
2049*440a403fSchristos(dnci stcb "store in control bus space" (VOLATILE (STALL STCB))
2050*440a403fSchristos     "stcb $rn,$uimm16"
2051*440a403fSchristos     (+ MAJ_15 rn (f-rm 0) (f-sub4 4) uimm16)
2052*440a403fSchristos     (c-call VOID "do_stcb" rn uimm16)
2053*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2054*440a403fSchristos	   (unit u-exec)
2055*440a403fSchristos	   (unit u-stcb))))
2056*440a403fSchristos
2057*440a403fSchristos(dnci ldcb "load from control bus space" (VOLATILE (STALL LDCB) (LATENCY 3))
2058*440a403fSchristos     "ldcb $rn,$uimm16"
2059*440a403fSchristos     (+ MAJ_15 rn (f-rm 1) (f-sub4 4) uimm16)
2060*440a403fSchristos     (set rn (c-call SI "do_ldcb" uimm16))
2061*440a403fSchristos      ((mep (unit u-ldcb)
2062*440a403fSchristos	    (unit u-exec)
2063*440a403fSchristos	    (unit u-ldcb-gpr (out loadreg rn)))))
2064*440a403fSchristos
2065*440a403fSchristos
2066*440a403fSchristos; Bit manipulation instructions.
2067*440a403fSchristos; The following instructions become the reserved instruction when the
2068*440a403fSchristos; bit manipulation option is off.
2069*440a403fSchristos
2070*440a403fSchristos(dnci bsetm "set bit in memory" (OPTIONAL_BIT_INSN)
2071*440a403fSchristos     "bsetm ($rma),$uimm3"
2072*440a403fSchristos     (+ MAJ_2 (f-4 0) uimm3 rma (f-sub4 0))
2073*440a403fSchristos     (sequence ()
2074*440a403fSchristos	       (c-call "check_option_bit" pc)
2075*440a403fSchristos	       (set (mem UQI rma) (or (mem UQI rma) (sll 1 uimm3))))
2076*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2077*440a403fSchristos	   (unit u-exec))))
2078*440a403fSchristos
2079*440a403fSchristos(dnci bclrm "clear bit in memory" (OPTIONAL_BIT_INSN)
2080*440a403fSchristos     "bclrm ($rma),$uimm3"
2081*440a403fSchristos     (+ MAJ_2 (f-4 0) uimm3 rma (f-sub4 1))
2082*440a403fSchristos     (sequence ()
2083*440a403fSchristos	       (c-call "check_option_bit" pc)
2084*440a403fSchristos	       (set (mem UQI rma) (and (mem UQI rma) (inv (sll 1 uimm3)))))
2085*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2086*440a403fSchristos	   (unit u-exec))))
2087*440a403fSchristos
2088*440a403fSchristos(dnci bnotm "toggle bit in memory" (OPTIONAL_BIT_INSN)
2089*440a403fSchristos     "bnotm ($rma),$uimm3"
2090*440a403fSchristos     (+ MAJ_2 (f-4 0) uimm3 rma (f-sub4 2))
2091*440a403fSchristos     (sequence ()
2092*440a403fSchristos	       (c-call "check_option_bit" pc)
2093*440a403fSchristos	       (set (mem UQI rma) (xor (mem UQI rma) (sll 1 uimm3))))
2094*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2095*440a403fSchristos	   (unit u-exec))))
2096*440a403fSchristos
2097*440a403fSchristos(dnci btstm "test bit in memory" (OPTIONAL_BIT_INSN)
2098*440a403fSchristos     "btstm \\$0,($rma),$uimm3"
2099*440a403fSchristos     (+ MAJ_2 (f-4 0) uimm3 rma (f-sub4 3))
2100*440a403fSchristos     (sequence ()
2101*440a403fSchristos	       (c-call "check_option_bit" pc)
2102*440a403fSchristos	       (set r0 (zext SI (and UQI (mem UQI rma) (sll 1 uimm3)))))
2103*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2104*440a403fSchristos	   (unit u-exec))))
2105*440a403fSchristos
2106*440a403fSchristos(dnci tas "test and set" (OPTIONAL_BIT_INSN)
2107*440a403fSchristos     "tas $rn,($rma)"
2108*440a403fSchristos     (+ MAJ_2 rn rma (f-sub4 4))
2109*440a403fSchristos     (sequence ((SI result))
2110*440a403fSchristos	       (c-call "check_option_bit" pc)
2111*440a403fSchristos	       (set result (zext SI (mem UQI rma)))
2112*440a403fSchristos	       (set (mem UQI rma) 1)
2113*440a403fSchristos	       (set rn result))
2114*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2115*440a403fSchristos	   (unit u-exec))))
2116*440a403fSchristos
2117*440a403fSchristos
2118*440a403fSchristos; Data cache instruction.
2119*440a403fSchristos
2120*440a403fSchristos(dnci cache "cache operations" (VOLATILE)
2121*440a403fSchristos     "cache $cimm4,($rma)"
2122*440a403fSchristos     (+ MAJ_7 cimm4 rma (f-sub4 4))
2123*440a403fSchristos     (c-call VOID "do_cache" cimm4 rma pc)
2124*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2125*440a403fSchristos	   (unit u-exec))))
2126*440a403fSchristos
2127*440a403fSchristos
2128*440a403fSchristos; Multiply instructions.
2129*440a403fSchristos; These instructions become the RI when the 32-bit multiply
2130*440a403fSchristos; instruction option is off.
2131*440a403fSchristos
2132*440a403fSchristos(dnci mul "multiply" (OPTIONAL_MUL_INSN (STALL MUL))
2133*440a403fSchristos     "mul $rn,$rm"
2134*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 4))
2135*440a403fSchristos     (sequence ((DI result))
2136*440a403fSchristos	       (c-call "check_option_mul" pc)
2137*440a403fSchristos	       (set result (mul (ext DI rn) (ext DI rm)))
2138*440a403fSchristos	       (set hi (subword SI result 0))
2139*440a403fSchristos	       (set lo (subword SI result 1)))
2140*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2141*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2142*440a403fSchristos	   (unit u-exec)
2143*440a403fSchristos	   (unit u-multiply))))
2144*440a403fSchristos
2145*440a403fSchristos(dnci mulu "multiply unsigned" (OPTIONAL_MUL_INSN (STALL MUL))
2146*440a403fSchristos     "mulu $rn,$rm"
2147*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 5))
2148*440a403fSchristos     (sequence ((DI result))
2149*440a403fSchristos	       (c-call "check_option_mul" pc)
2150*440a403fSchristos	       (set result (mul (zext UDI rn) (zext UDI rm)))
2151*440a403fSchristos	       (set hi (subword SI result 0))
2152*440a403fSchristos	       (set lo (subword SI result 1)))
2153*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2154*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2155*440a403fSchristos	   (unit u-exec)
2156*440a403fSchristos	   (unit u-multiply))))
2157*440a403fSchristos
2158*440a403fSchristos(dnci mulr "multiply, lo -> reg" (OPTIONAL_MUL_INSN (STALL MULR) (LATENCY 3))
2159*440a403fSchristos     "mulr $rn,$rm"
2160*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 6))
2161*440a403fSchristos     (sequence ((DI result))
2162*440a403fSchristos	       (c-call "check_option_mul" pc)
2163*440a403fSchristos	       (set result (mul (ext DI rn) (ext DI rm)))
2164*440a403fSchristos	       (set hi (subword SI result 0))
2165*440a403fSchristos	       (set lo (subword SI result 1))
2166*440a403fSchristos	       (set rn (subword SI result 1)))
2167*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2168*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2169*440a403fSchristos	   (unit u-exec)
2170*440a403fSchristos	   (unit u-multiply)
2171*440a403fSchristos	   (unit u-mul-gpr (out resultreg rn)))))
2172*440a403fSchristos
2173*440a403fSchristos(dnci mulru "multiply unsigned, lo -> reg" (OPTIONAL_MUL_INSN (STALL MULR) (LATENCY 3))
2174*440a403fSchristos     "mulru $rn,$rm"
2175*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 7))
2176*440a403fSchristos     (sequence ((DI result))
2177*440a403fSchristos	       (c-call "check_option_mul" pc)
2178*440a403fSchristos	       (set result (mul (zext UDI rn) (zext UDI rm)))
2179*440a403fSchristos	       (set hi (subword SI result 0))
2180*440a403fSchristos	       (set lo (subword SI result 1))
2181*440a403fSchristos	       (set rn (subword SI result 1)))
2182*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2183*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2184*440a403fSchristos	   (unit u-exec)
2185*440a403fSchristos	   (unit u-multiply)
2186*440a403fSchristos	   (unit u-mul-gpr (out resultreg rn)))))
2187*440a403fSchristos
2188*440a403fSchristos(dnci madd "multiply accumulate" (OPTIONAL_MUL_INSN (STALL MUL))
2189*440a403fSchristos     "madd $rn,$rm"
2190*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 #x3004))
2191*440a403fSchristos     (sequence ((DI result))
2192*440a403fSchristos	       (c-call "check_option_mul" pc)
2193*440a403fSchristos	       (set result (or (sll (zext DI hi) 32) (zext DI lo)))
2194*440a403fSchristos	       (set result (add result (mul (ext DI rn) (ext DI rm))))
2195*440a403fSchristos	       (set hi (subword SI result 0))
2196*440a403fSchristos	       (set lo (subword SI result 1)))
2197*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2198*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2199*440a403fSchristos	   (unit u-exec)
2200*440a403fSchristos	   (unit u-multiply))))
2201*440a403fSchristos
2202*440a403fSchristos(dnci maddu "multiply accumulate unsigned" (OPTIONAL_MUL_INSN (STALL MUL))
2203*440a403fSchristos     "maddu $rn,$rm"
2204*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 #x3005))
2205*440a403fSchristos     (sequence ((DI result))
2206*440a403fSchristos	       (c-call "check_option_mul" pc)
2207*440a403fSchristos	       (set result (or (sll (zext DI hi) 32) (zext DI lo)))
2208*440a403fSchristos	       (set result (add result (mul (zext UDI rn) (zext UDI rm))))
2209*440a403fSchristos	       (set hi (subword SI result 0))
2210*440a403fSchristos	       (set lo (subword SI result 1)))
2211*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2212*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2213*440a403fSchristos	   (unit u-exec)
2214*440a403fSchristos	   (unit u-multiply))))
2215*440a403fSchristos
2216*440a403fSchristos
2217*440a403fSchristos(dnci maddr "multiply accumulate, lo -> reg" (OPTIONAL_MUL_INSN (STALL MULR) (LATENCY 3))
2218*440a403fSchristos     "maddr $rn,$rm"
2219*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 #x3006))
2220*440a403fSchristos     (sequence ((DI result))
2221*440a403fSchristos	       (c-call "check_option_mul" pc)
2222*440a403fSchristos	       (set result (or (sll (zext DI hi) 32) (zext DI lo)))
2223*440a403fSchristos	       (set result (add result (mul (ext DI rn) (ext DI rm))))
2224*440a403fSchristos	       (set hi (subword SI result 0))
2225*440a403fSchristos	       (set lo (subword SI result 1))
2226*440a403fSchristos	       (set rn (subword SI result 1)))
2227*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2228*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2229*440a403fSchristos	   (unit u-exec)
2230*440a403fSchristos	   (unit u-multiply)
2231*440a403fSchristos	   (unit u-mul-gpr (out resultreg rn)))))
2232*440a403fSchristos
2233*440a403fSchristos(dnci maddru "multiple accumulate unsigned, lo -> reg" (OPTIONAL_MUL_INSN (STALL MULR) (LATENCY 3))
2234*440a403fSchristos     "maddru $rn,$rm"
2235*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 #x3007))
2236*440a403fSchristos     (sequence ((DI result))
2237*440a403fSchristos	       (c-call "check_option_mul" pc)
2238*440a403fSchristos	       (set result (or (sll (zext DI hi) 32) (zext DI lo)))
2239*440a403fSchristos	       (set result (add result (mul (zext UDI rn) (zext UDI rm))))
2240*440a403fSchristos	       (set hi (subword SI result 0))
2241*440a403fSchristos	       (set lo (subword SI result 1))
2242*440a403fSchristos	       (set rn (subword SI result 1)))
2243*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2244*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2245*440a403fSchristos	   (unit u-exec)
2246*440a403fSchristos	   (unit u-multiply)
2247*440a403fSchristos	   (unit u-mul-gpr (out resultreg rn)))))
2248*440a403fSchristos
2249*440a403fSchristos
2250*440a403fSchristos; Divide instructions.
2251*440a403fSchristos; These instructions become the RI when the 32-bit divide instruction
2252*440a403fSchristos; option is off.
2253*440a403fSchristos
2254*440a403fSchristos(dnci div "divide" (OPTIONAL_DIV_INSN (STALL DIV) (LATENCY 34) MAY_TRAP)
2255*440a403fSchristos     "div $rn,$rm"
2256*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 8))
2257*440a403fSchristos     (sequence ()
2258*440a403fSchristos	       (c-call "check_option_div" pc)
2259*440a403fSchristos	       (if (eq rm 0)
2260*440a403fSchristos		   (set pc (c-call USI "zdiv_exception" pc))
2261*440a403fSchristos		   ; Special case described on p. 76.
2262*440a403fSchristos		   (if (and (eq rn #x80000000)
2263*440a403fSchristos			    (eq rm #xffffffff))
2264*440a403fSchristos		       (sequence ()
2265*440a403fSchristos				 (set lo #x80000000)
2266*440a403fSchristos				 (set hi 0))
2267*440a403fSchristos		       (sequence ()
2268*440a403fSchristos				 (set lo (div rn rm))
2269*440a403fSchristos				 (set hi (mod rn rm))))))
2270*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2271*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2272*440a403fSchristos	   (unit u-exec)
2273*440a403fSchristos	   (unit u-divide)
2274*440a403fSchristos           (unit u-branch))))
2275*440a403fSchristos
2276*440a403fSchristos(dnci divu "divide unsigned" (OPTIONAL_DIV_INSN (STALL DIV) (LATENCY 34) MAY_TRAP)
2277*440a403fSchristos     "divu $rn,$rm"
2278*440a403fSchristos     (+ MAJ_1 rn rm (f-sub4 9))
2279*440a403fSchristos     (sequence ()
2280*440a403fSchristos	       (c-call "check_option_div" pc)
2281*440a403fSchristos	       (if (eq rm 0)
2282*440a403fSchristos		   (set pc (c-call USI "zdiv_exception" pc))
2283*440a403fSchristos		   (sequence ()
2284*440a403fSchristos			     (set lo (udiv rn rm))
2285*440a403fSchristos			     (set hi (umod rn rm)))))
2286*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2287*440a403fSchristos	   (unit u-use-gpr (in usereg rm))
2288*440a403fSchristos	   (unit u-exec)
2289*440a403fSchristos	   (unit u-divide)
2290*440a403fSchristos           (unit u-branch))))
2291*440a403fSchristos
2292*440a403fSchristos
2293*440a403fSchristos; Debug functions.
2294*440a403fSchristos; These instructions become the RI when the debug function option is
2295*440a403fSchristos; off.
2296*440a403fSchristos
2297*440a403fSchristos(dnci dret "return from debug exception" (OPTIONAL_DEBUG_INSN)
2298*440a403fSchristos     "dret"
2299*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 1) (f-sub4 3))
2300*440a403fSchristos     (sequence ()
2301*440a403fSchristos	       (c-call "check_option_debug" pc)
2302*440a403fSchristos	       ; set DBG.DM.
2303*440a403fSchristos	       (set dbg (and dbg (inv (sll SI 1 15))))
2304*440a403fSchristos	       (set pc depc))
2305*440a403fSchristos     ((mep (unit u-exec)
2306*440a403fSchristos	   (unit u-branch))))
2307*440a403fSchristos
2308*440a403fSchristos(dnci dbreak "generate debug exception" (OPTIONAL_DEBUG_INSN MAY_TRAP VOLATILE)
2309*440a403fSchristos     "dbreak"
2310*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 3) (f-sub4 3))
2311*440a403fSchristos     (sequence ()
2312*440a403fSchristos	       (c-call "check_option_debug" pc)
2313*440a403fSchristos	       ; set DBG.DPB.
2314*440a403fSchristos	       (set dbg (or dbg 1)))
2315*440a403fSchristos     ())
2316*440a403fSchristos
2317*440a403fSchristos
2318*440a403fSchristos; Leading zero instruction.
2319*440a403fSchristos
2320*440a403fSchristos(dnci ldz "leading zeroes" (OPTIONAL_LDZ_INSN (STALL INT2))
2321*440a403fSchristos     "ldz $rn,$rm"
2322*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 0))
2323*440a403fSchristos     (sequence ()
2324*440a403fSchristos	       (c-call "check_option_ldz" pc)
2325*440a403fSchristos	       (set rn (c-call SI "do_ldz" rm)))
2326*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2327*440a403fSchristos	   (unit u-exec))))
2328*440a403fSchristos
2329*440a403fSchristos
2330*440a403fSchristos; Absolute difference instruction.
2331*440a403fSchristos
2332*440a403fSchristos(dnci abs "absolute difference" (OPTIONAL_ABS_INSN (STALL INT2))
2333*440a403fSchristos     "abs $rn,$rm"
2334*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 3))
2335*440a403fSchristos     (sequence ()
2336*440a403fSchristos	       (c-call "check_option_abs" pc)
2337*440a403fSchristos	       (set rn (abs (sub rn rm))))
2338*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2339*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2340*440a403fSchristos	   (unit u-exec))))
2341*440a403fSchristos
2342*440a403fSchristos
2343*440a403fSchristos; Average instruction.
2344*440a403fSchristos
2345*440a403fSchristos(dnci ave "average" (OPTIONAL_AVE_INSN (STALL INT2))
2346*440a403fSchristos     "ave $rn,$rm"
2347*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 2))
2348*440a403fSchristos     (sequence ()
2349*440a403fSchristos	       (c-call "check_option_ave" pc)
2350*440a403fSchristos	       (set rn (sra (add (add rn rm) 1) 1)))
2351*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2352*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2353*440a403fSchristos	   (unit u-exec))))
2354*440a403fSchristos
2355*440a403fSchristos
2356*440a403fSchristos; MIN/MAX instructions.
2357*440a403fSchristos
2358*440a403fSchristos(dnci min "minimum" (OPTIONAL_MINMAX_INSN (STALL INT2))
2359*440a403fSchristos     "min $rn,$rm"
2360*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 4))
2361*440a403fSchristos     (sequence ()
2362*440a403fSchristos	       (c-call "check_option_minmax" pc)
2363*440a403fSchristos	       (if (gt rn rm)
2364*440a403fSchristos		   (set rn rm)))
2365*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2366*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2367*440a403fSchristos	   (unit u-exec))))
2368*440a403fSchristos
2369*440a403fSchristos(dnci max "maximum" (OPTIONAL_MINMAX_INSN (STALL INT2))
2370*440a403fSchristos     "max $rn,$rm"
2371*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 5))
2372*440a403fSchristos     (sequence ()
2373*440a403fSchristos	       (c-call "check_option_minmax" pc)
2374*440a403fSchristos	       (if (lt rn rm)
2375*440a403fSchristos		   (set rn rm)))
2376*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2377*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2378*440a403fSchristos	   (unit u-exec))))
2379*440a403fSchristos
2380*440a403fSchristos(dnci minu "minimum unsigned" (OPTIONAL_MINMAX_INSN (STALL INT2))
2381*440a403fSchristos     "minu $rn,$rm"
2382*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 6))
2383*440a403fSchristos     (sequence ()
2384*440a403fSchristos	       (c-call "check_option_minmax" pc)
2385*440a403fSchristos	       (if (gtu rn rm)
2386*440a403fSchristos		   (set rn rm)))
2387*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2388*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2389*440a403fSchristos	   (unit u-exec))))
2390*440a403fSchristos
2391*440a403fSchristos(dnci maxu "maximum unsigned" (OPTIONAL_MINMAX_INSN (STALL INT2))
2392*440a403fSchristos     "maxu $rn,$rm"
2393*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 7))
2394*440a403fSchristos     (sequence ()
2395*440a403fSchristos	       (c-call "check_option_minmax" pc)
2396*440a403fSchristos	       (if (ltu rn rm)
2397*440a403fSchristos		   (set rn rm)))
2398*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2399*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2400*440a403fSchristos	   (unit u-exec))))
2401*440a403fSchristos
2402*440a403fSchristos
2403*440a403fSchristos; Clipping instruction.
2404*440a403fSchristos
2405*440a403fSchristos(dnci clip "clip" (OPTIONAL_CLIP_INSN (STALL INT2))
2406*440a403fSchristos     "clip $rn,$cimm5"
2407*440a403fSchristos     (+ MAJ_15 rn (f-rm 0) (f-sub4 1) (f-ext #x10) cimm5 (f-29 0) (f-30 0) (f-31 0))
2408*440a403fSchristos     (sequence ((SI min) (SI max))
2409*440a403fSchristos	       (c-call "check_option_clip" pc)
2410*440a403fSchristos	       (set max (sub (sll 1 (sub cimm5 1)) 1))
2411*440a403fSchristos	       (set min (neg (sll 1 (sub cimm5 1))))
2412*440a403fSchristos	       (cond
2413*440a403fSchristos		((eq cimm5 0) (set rn 0))
2414*440a403fSchristos		((gt rn max) (set rn max))
2415*440a403fSchristos		((lt rn min) (set rn min))))
2416*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2417*440a403fSchristos	   (unit u-exec))))
2418*440a403fSchristos
2419*440a403fSchristos(dnci clipu "clip unsigned" (OPTIONAL_CLIP_INSN (STALL INT2))
2420*440a403fSchristos     "clipu $rn,$cimm5"
2421*440a403fSchristos     (+ MAJ_15 rn (f-rm 0) (f-sub4 1) (f-ext #x10) cimm5 (f-29 0) (f-30 0) (f-31 1))
2422*440a403fSchristos     (sequence ((SI max))
2423*440a403fSchristos	       (c-call "check_option_clip" pc)
2424*440a403fSchristos	       (set max (sub (sll 1 cimm5) 1))
2425*440a403fSchristos	       (cond
2426*440a403fSchristos		((eq cimm5 0) (set rn 0))
2427*440a403fSchristos		((gt rn max) (set rn max))
2428*440a403fSchristos		((lt rn 0) (set rn 0))))
2429*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rn))
2430*440a403fSchristos	   (unit u-exec))))
2431*440a403fSchristos
2432*440a403fSchristos
2433*440a403fSchristos; Saturation instructions.
2434*440a403fSchristos
2435*440a403fSchristos(dnci sadd "saturating addition" (OPTIONAL_SAT_INSN (STALL INT2))
2436*440a403fSchristos     "sadd $rn,$rm"
2437*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 8))
2438*440a403fSchristos     (sequence ()
2439*440a403fSchristos	       (c-call "check_option_sat" pc)
2440*440a403fSchristos	       (if (add-oflag rn rm 0)
2441*440a403fSchristos		   (if (nflag rn)
2442*440a403fSchristos		       ; underflow
2443*440a403fSchristos		       (set rn (neg (sll 1 31)))
2444*440a403fSchristos		       ; overflow
2445*440a403fSchristos		       (set rn (sub (sll 1 31) 1)))
2446*440a403fSchristos		   (set rn (add rn rm))))
2447*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2448*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2449*440a403fSchristos	   (unit u-exec))))
2450*440a403fSchristos
2451*440a403fSchristos(dnci ssub "saturating subtraction" (OPTIONAL_SAT_INSN (STALL INT2))
2452*440a403fSchristos     "ssub $rn,$rm"
2453*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 10))
2454*440a403fSchristos     (sequence ()
2455*440a403fSchristos	       (c-call "check_option_sat" pc)
2456*440a403fSchristos	       (if (sub-oflag rn rm 0)
2457*440a403fSchristos		   (if (nflag rn)
2458*440a403fSchristos		       ; underflow
2459*440a403fSchristos		       (set rn (neg (sll 1 31)))
2460*440a403fSchristos		       ; overflow
2461*440a403fSchristos		       (set rn (sub (sll 1 31) 1)))
2462*440a403fSchristos		   (set rn (sub rn rm))))
2463*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2464*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2465*440a403fSchristos	   (unit u-exec))))
2466*440a403fSchristos
2467*440a403fSchristos(dnci saddu "saturating unsigned addition" (OPTIONAL_SAT_INSN (STALL INT2))
2468*440a403fSchristos     "saddu $rn,$rm"
2469*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 9))
2470*440a403fSchristos     (sequence ()
2471*440a403fSchristos	       (c-call "check_option_sat" pc)
2472*440a403fSchristos	       (if (add-cflag rn rm 0)
2473*440a403fSchristos		   (set rn (inv 0))
2474*440a403fSchristos		   (set rn (add rn rm))))
2475*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2476*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2477*440a403fSchristos	   (unit u-exec))))
2478*440a403fSchristos
2479*440a403fSchristos(dnci ssubu "saturating unsigned subtraction" (OPTIONAL_SAT_INSN (STALL INT2))
2480*440a403fSchristos     "ssubu $rn,$rm"
2481*440a403fSchristos     (+ MAJ_15 rn rm (f-sub4 1) (f-16u16 11))
2482*440a403fSchristos     (sequence ()
2483*440a403fSchristos	       (c-call "check_option_sat" pc)
2484*440a403fSchristos	       (if (sub-cflag rn rm 0)
2485*440a403fSchristos		   (set rn 0)
2486*440a403fSchristos		   (set rn (sub rn rm))))
2487*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2488*440a403fSchristos	   (unit u-use-gpr (in usereg rn))
2489*440a403fSchristos	   (unit u-exec))))
2490*440a403fSchristos
2491*440a403fSchristos
2492*440a403fSchristos; UCI and DSP options are defined in an external file.
2493*440a403fSchristos; See `mep-sample-ucidsp.cpu' for a sample.
2494*440a403fSchristos
2495*440a403fSchristos
2496*440a403fSchristos; Coprocessor instructions.
2497*440a403fSchristos
2498*440a403fSchristos(dnci swcp "store word coprocessor" (OPTIONAL_CP_INSN (STALL STORE))
2499*440a403fSchristos     "swcp $crn,($rma)"
2500*440a403fSchristos     (+ MAJ_3 crn rma (f-sub4 8))
2501*440a403fSchristos     (sequence ()
2502*440a403fSchristos	       (c-call "check_option_cp" pc)
2503*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 3)))
2504*440a403fSchristos	       (set (mem SI (and rma (inv SI 3))) crn))
2505*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2506*440a403fSchristos	   (unit u-exec))))
2507*440a403fSchristos
2508*440a403fSchristos(dnci lwcp "load word coprocessor" (OPTIONAL_CP_INSN (STALL LOAD))
2509*440a403fSchristos     "lwcp $crn,($rma)"
2510*440a403fSchristos     (+ MAJ_3 crn rma (f-sub4 9))
2511*440a403fSchristos     (sequence ()
2512*440a403fSchristos	       (c-call "check_option_cp" pc)
2513*440a403fSchristos	       (set crn (mem SI (and rma (inv SI 3)))))
2514*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2515*440a403fSchristos	   (unit u-exec))))
2516*440a403fSchristos
2517*440a403fSchristos(dnci smcp "smcp" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL STORE))
2518*440a403fSchristos     "smcp $crn64,($rma)"
2519*440a403fSchristos     (+ MAJ_3 crn64 rma (f-sub4 10))
2520*440a403fSchristos     (sequence ()
2521*440a403fSchristos	       (c-call "check_option_cp" pc)
2522*440a403fSchristos	       (c-call "check_option_cp64" pc)
2523*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2524*440a403fSchristos	       (c-call "do_smcp" rma crn64 pc))
2525*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2526*440a403fSchristos	   (unit u-exec))))
2527*440a403fSchristos
2528*440a403fSchristos(dnci lmcp "lmcp" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL LOAD))
2529*440a403fSchristos     "lmcp $crn64,($rma)"
2530*440a403fSchristos     (+ MAJ_3 crn64 rma (f-sub4 11))
2531*440a403fSchristos     (sequence ()
2532*440a403fSchristos	       (c-call "check_option_cp" pc)
2533*440a403fSchristos	       (c-call "check_option_cp64" pc)
2534*440a403fSchristos	       (set crn64 (c-call DI "do_lmcp" rma pc)))
2535*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2536*440a403fSchristos	   (unit u-exec))))
2537*440a403fSchristos
2538*440a403fSchristos(dnci swcpi "swcp (post-increment)" (OPTIONAL_CP_INSN (STALL STORE))
2539*440a403fSchristos     "swcpi $crn,($rma+)"
2540*440a403fSchristos     (+ MAJ_3 crn rma (f-sub4 0))
2541*440a403fSchristos     (sequence ()
2542*440a403fSchristos	       (c-call "check_option_cp" pc)
2543*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 3)))
2544*440a403fSchristos	       (set (mem SI (and rma (inv SI 3))) crn)
2545*440a403fSchristos	       (set rma (add rma 4)))
2546*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2547*440a403fSchristos	   (unit u-exec))))
2548*440a403fSchristos
2549*440a403fSchristos(dnci lwcpi "lwcp (post-increment)" (OPTIONAL_CP_INSN (STALL LOAD))
2550*440a403fSchristos     "lwcpi $crn,($rma+)"
2551*440a403fSchristos     (+ MAJ_3 crn rma (f-sub4 1))
2552*440a403fSchristos     (sequence ()
2553*440a403fSchristos	       (c-call "check_option_cp" pc)
2554*440a403fSchristos	       (set crn (mem SI (and rma (inv SI 3))))
2555*440a403fSchristos	       (set rma (add rma 4)))
2556*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2557*440a403fSchristos	   (unit u-exec))))
2558*440a403fSchristos
2559*440a403fSchristos(dnci smcpi "smcp (post-increment)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL STORE))
2560*440a403fSchristos     "smcpi $crn64,($rma+)"
2561*440a403fSchristos     (+ MAJ_3 crn64 rma (f-sub4 2))
2562*440a403fSchristos     (sequence ()
2563*440a403fSchristos	       (c-call "check_option_cp" pc)
2564*440a403fSchristos	       (c-call "check_option_cp64" pc)
2565*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2566*440a403fSchristos	       (c-call "do_smcpi" (index-of rma) crn64 pc)
2567*440a403fSchristos	       (set rma rma)) ; reference as output for intrinsic generation
2568*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2569*440a403fSchristos	   (unit u-exec))))
2570*440a403fSchristos
2571*440a403fSchristos(dnci lmcpi "lmcp (post-increment)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL LOAD))
2572*440a403fSchristos     "lmcpi $crn64,($rma+)"
2573*440a403fSchristos     (+ MAJ_3 crn64 rma (f-sub4 3))
2574*440a403fSchristos     (sequence ()
2575*440a403fSchristos	       (c-call "check_option_cp" pc)
2576*440a403fSchristos	       (c-call "check_option_cp64" pc)
2577*440a403fSchristos	       (set crn64 (c-call DI "do_lmcpi" (index-of rma) pc))
2578*440a403fSchristos	       (set rma rma)) ; reference as output for intrinsic generation
2579*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2580*440a403fSchristos	   (unit u-exec))))
2581*440a403fSchristos
2582*440a403fSchristos(dnci swcp16 "swcp (16-bit displacement)" (OPTIONAL_CP_INSN (STALL STORE))
2583*440a403fSchristos     "swcp $crn,$sdisp16($rma)"
2584*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 12) sdisp16)
2585*440a403fSchristos     (sequence ()
2586*440a403fSchristos	       (c-call "check_option_cp" pc)
2587*440a403fSchristos	       (set (mem SI (and (add rma sdisp16) (inv SI 3))) crn))
2588*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2589*440a403fSchristos	   (unit u-exec))))
2590*440a403fSchristos
2591*440a403fSchristos(dnci lwcp16 "lwcp (16-bit displacement)" (OPTIONAL_CP_INSN (STALL LOAD))
2592*440a403fSchristos     "lwcp $crn,$sdisp16($rma)"
2593*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 13) sdisp16)
2594*440a403fSchristos     (sequence ()
2595*440a403fSchristos	       (c-call "check_option_cp" pc)
2596*440a403fSchristos	       (set crn (mem SI (and (add rma sdisp16) (inv SI 3)))))
2597*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2598*440a403fSchristos	   (unit u-exec))))
2599*440a403fSchristos
2600*440a403fSchristos(dnci smcp16 "smcp (16-bit displacement)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL STORE))
2601*440a403fSchristos     "smcp $crn64,$sdisp16($rma)"
2602*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 14) sdisp16)
2603*440a403fSchristos     (sequence ()
2604*440a403fSchristos	       (c-call "check_option_cp" pc)
2605*440a403fSchristos	       (c-call "check_option_cp64" pc)
2606*440a403fSchristos	       (c-call "do_smcp16" rma sdisp16 crn64 pc))
2607*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2608*440a403fSchristos	   (unit u-exec))))
2609*440a403fSchristos
2610*440a403fSchristos(dnci lmcp16 "lmcp (16-bit displacement)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL LOAD))
2611*440a403fSchristos     "lmcp $crn64,$sdisp16($rma)"
2612*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 15) sdisp16)
2613*440a403fSchristos     (sequence ()
2614*440a403fSchristos	       (c-call "check_option_cp" pc)
2615*440a403fSchristos	       (c-call "check_option_cp64" pc)
2616*440a403fSchristos	       (set crn64 (c-call DI "do_lmcp16" rma sdisp16 pc)))
2617*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2618*440a403fSchristos	   (unit u-exec))))
2619*440a403fSchristos
2620*440a403fSchristos(dnci sbcpa "store byte coprocessor" (OPTIONAL_CP_INSN (STALL STORE))
2621*440a403fSchristos     "sbcpa $crn,($rma+),$cdisp10"
2622*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 0) (f-ext62 0) cdisp10)
2623*440a403fSchristos     (sequence ()
2624*440a403fSchristos	       (c-call "check_option_cp" pc)
2625*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2626*440a403fSchristos	       (set (mem QI rma) (and crn #xff))
2627*440a403fSchristos	       (set rma (add rma (ext SI cdisp10))))
2628*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2629*440a403fSchristos	   (unit u-exec))))
2630*440a403fSchristos
2631*440a403fSchristos(dnci lbcpa "load byte coprocessor" (OPTIONAL_CP_INSN (STALL LOAD))
2632*440a403fSchristos     "lbcpa $crn,($rma+),$cdisp10"
2633*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x4) (f-ext62 #x0) cdisp10)
2634*440a403fSchristos     (sequence ()
2635*440a403fSchristos	       (c-call "check_option_cp" pc)
2636*440a403fSchristos	       (set crn (ext SI (mem QI rma)))
2637*440a403fSchristos	       (set rma (add rma (ext SI cdisp10))))
2638*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2639*440a403fSchristos	   (unit u-exec))))
2640*440a403fSchristos
2641*440a403fSchristos(dnci shcpa "store half-word coprocessor" (OPTIONAL_CP_INSN (STALL STORE))
2642*440a403fSchristos     "shcpa $crn,($rma+),$cdisp10a2"
2643*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x1) (f-ext62 #x0) cdisp10a2)
2644*440a403fSchristos     (sequence ()
2645*440a403fSchristos	       (c-call "check_option_cp" pc)
2646*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 1)))
2647*440a403fSchristos	       (set (mem HI (and rma (inv SI 1))) (and crn #xffff))
2648*440a403fSchristos	       (set rma (add rma (ext SI cdisp10a2))))
2649*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2650*440a403fSchristos	   (unit u-exec))))
2651*440a403fSchristos
2652*440a403fSchristos(dnci lhcpa "load half-word coprocessor" (OPTIONAL_CP_INSN (STALL LOAD))
2653*440a403fSchristos     "lhcpa $crn,($rma+),$cdisp10a2"
2654*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x5) (f-ext62 #x0) cdisp10a2)
2655*440a403fSchristos     (sequence ()
2656*440a403fSchristos	       (c-call "check_option_cp" pc)
2657*440a403fSchristos	       (set crn (ext SI (mem HI (and rma (inv SI 1)))))
2658*440a403fSchristos	       (set rma (add rma (ext SI cdisp10a2))))
2659*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2660*440a403fSchristos	   (unit u-exec))))
2661*440a403fSchristos
2662*440a403fSchristos(dnci swcpa "store word coprocessor" (OPTIONAL_CP_INSN (STALL STORE))
2663*440a403fSchristos     "swcpa $crn,($rma+),$cdisp10a4"
2664*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x2) (f-ext62 #x0) cdisp10a4)
2665*440a403fSchristos     (sequence ()
2666*440a403fSchristos	       (c-call "check_option_cp" pc)
2667*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 3)))
2668*440a403fSchristos	       (set (mem SI (and rma (inv SI 3))) crn)
2669*440a403fSchristos	       (set rma (add rma (ext SI cdisp10a4))))
2670*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2671*440a403fSchristos	   (unit u-exec))))
2672*440a403fSchristos
2673*440a403fSchristos(dnci lwcpa "load word coprocessor" (OPTIONAL_CP_INSN (STALL LOAD))
2674*440a403fSchristos     "lwcpa $crn,($rma+),$cdisp10a4"
2675*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x6) (f-ext62 #x0) cdisp10a4)
2676*440a403fSchristos     (sequence ()
2677*440a403fSchristos	       (c-call "check_option_cp" pc)
2678*440a403fSchristos	       (set crn (mem SI (and rma (inv SI 3))))
2679*440a403fSchristos	       (set rma (add rma (ext SI cdisp10a4))))
2680*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2681*440a403fSchristos	   (unit u-exec))))
2682*440a403fSchristos
2683*440a403fSchristos(dnci smcpa "smcpa" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL STORE))
2684*440a403fSchristos     "smcpa $crn64,($rma+),$cdisp10a8"
2685*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x3) (f-ext62 #x0) cdisp10a8)
2686*440a403fSchristos     (sequence ()
2687*440a403fSchristos	       (c-call "check_option_cp" pc)
2688*440a403fSchristos	       (c-call "check_option_cp64" pc)
2689*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2690*440a403fSchristos	       (c-call "do_smcpa" (index-of rma) cdisp10a8 crn64 pc)
2691*440a403fSchristos	       (set rma rma)) ; reference as output for intrinsic generation
2692*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2693*440a403fSchristos	   (unit u-exec))))
2694*440a403fSchristos
2695*440a403fSchristos(dnci lmcpa "lmcpa" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN (STALL LOAD))
2696*440a403fSchristos     "lmcpa $crn64,($rma+),$cdisp10a8"
2697*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x7) (f-ext62 #x0) cdisp10a8)
2698*440a403fSchristos     (sequence ()
2699*440a403fSchristos	       (c-call "check_option_cp" pc)
2700*440a403fSchristos	       (c-call "check_option_cp64" pc)
2701*440a403fSchristos	       (set crn64 (c-call DI "do_lmcpa" (index-of rma) cdisp10a8 pc))
2702*440a403fSchristos	       (set rma rma)) ; reference as output for intrinsic generation
2703*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2704*440a403fSchristos	   (unit u-exec))))
2705*440a403fSchristos
2706*440a403fSchristos
2707*440a403fSchristos(dnci sbcpm0 "sbcpm0" (OPTIONAL_CP_INSN)
2708*440a403fSchristos     "sbcpm0 $crn,($rma+),$cdisp10"
2709*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x0) (f-ext62 #x2) cdisp10)
2710*440a403fSchristos     (sequence ()
2711*440a403fSchristos	       (c-call "check_option_cp" pc)
2712*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2713*440a403fSchristos	       (set (mem QI rma) (and crn #xff))
2714*440a403fSchristos	       (set rma (mod0 cdisp10)))
2715*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2716*440a403fSchristos	   (unit u-exec))))
2717*440a403fSchristos
2718*440a403fSchristos(dnci lbcpm0 "lbcpm0" (OPTIONAL_CP_INSN)
2719*440a403fSchristos     "lbcpm0 $crn,($rma+),$cdisp10"
2720*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x4) (f-ext62 #x2) cdisp10)
2721*440a403fSchristos     (sequence ()
2722*440a403fSchristos	       (c-call "check_option_cp" pc)
2723*440a403fSchristos	       (set crn (ext SI (mem QI rma)))
2724*440a403fSchristos	       (set rma (mod0 cdisp10)))
2725*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2726*440a403fSchristos	   (unit u-exec))))
2727*440a403fSchristos
2728*440a403fSchristos(dnci shcpm0 "shcpm0" (OPTIONAL_CP_INSN)
2729*440a403fSchristos     "shcpm0 $crn,($rma+),$cdisp10a2"
2730*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x1) (f-ext62 #x2) cdisp10a2)
2731*440a403fSchristos     (sequence ()
2732*440a403fSchristos	       (c-call "check_option_cp" pc)
2733*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 1)))
2734*440a403fSchristos	       (set (mem HI (and rma (inv SI 1))) (and crn #xffff))
2735*440a403fSchristos	       (set rma (mod0 cdisp10a2)))
2736*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2737*440a403fSchristos	   (unit u-exec))))
2738*440a403fSchristos
2739*440a403fSchristos(dnci lhcpm0 "lhcpm0" (OPTIONAL_CP_INSN)
2740*440a403fSchristos     "lhcpm0 $crn,($rma+),$cdisp10a2"
2741*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x5) (f-ext62 #x2) cdisp10a2)
2742*440a403fSchristos     (sequence ()
2743*440a403fSchristos	       (c-call "check_option_cp" pc)
2744*440a403fSchristos	       (set crn (ext SI (mem HI (and rma (inv SI 1)))))
2745*440a403fSchristos	       (set rma (mod0 cdisp10a2)))
2746*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2747*440a403fSchristos	   (unit u-exec))))
2748*440a403fSchristos
2749*440a403fSchristos(dnci swcpm0 "swcpm0" (OPTIONAL_CP_INSN)
2750*440a403fSchristos     "swcpm0 $crn,($rma+),$cdisp10a4"
2751*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x2) (f-ext62 #x2) cdisp10a4)
2752*440a403fSchristos     (sequence ()
2753*440a403fSchristos	       (c-call "check_option_cp" pc)
2754*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 3)))
2755*440a403fSchristos	       (set (mem SI (and rma (inv SI 3))) crn)
2756*440a403fSchristos	       (set rma (mod0 cdisp10a4)))
2757*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2758*440a403fSchristos	   (unit u-exec))))
2759*440a403fSchristos
2760*440a403fSchristos(dnci lwcpm0 "lwcpm0" (OPTIONAL_CP_INSN)
2761*440a403fSchristos     "lwcpm0 $crn,($rma+),$cdisp10a4"
2762*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x6) (f-ext62 #x2) cdisp10a4)
2763*440a403fSchristos     (sequence ()
2764*440a403fSchristos	       (c-call "check_option_cp" pc)
2765*440a403fSchristos	       (set crn (mem SI (and rma (inv SI 3))))
2766*440a403fSchristos	       (set rma (mod0 cdisp10a4)))
2767*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2768*440a403fSchristos	   (unit u-exec))))
2769*440a403fSchristos
2770*440a403fSchristos(dnci smcpm0 "smcpm0" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN)
2771*440a403fSchristos     "smcpm0 $crn64,($rma+),$cdisp10a8"
2772*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x3) (f-ext62 #x2) cdisp10a8)
2773*440a403fSchristos     (sequence ()
2774*440a403fSchristos	       (c-call "check_option_cp" pc)
2775*440a403fSchristos	       (c-call "check_option_cp64" pc)
2776*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2777*440a403fSchristos	       (c-call "do_smcp" rma crn64 pc)
2778*440a403fSchristos	       (set rma (mod0 cdisp10a8)))
2779*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2780*440a403fSchristos	   (unit u-exec))))
2781*440a403fSchristos
2782*440a403fSchristos(dnci lmcpm0 "lmcpm0" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN)
2783*440a403fSchristos     "lmcpm0 $crn64,($rma+),$cdisp10a8"
2784*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x7) (f-ext62 #x2) cdisp10a8)
2785*440a403fSchristos     (sequence ()
2786*440a403fSchristos	       (c-call "check_option_cp" pc)
2787*440a403fSchristos	       (c-call "check_option_cp64" pc)
2788*440a403fSchristos	       (set crn64 (c-call DI "do_lmcp" rma pc))
2789*440a403fSchristos	       (set rma (mod0 cdisp10a8)))
2790*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2791*440a403fSchristos	   (unit u-exec))))
2792*440a403fSchristos
2793*440a403fSchristos(dnci sbcpm1 "sbcpm1" (OPTIONAL_CP_INSN)
2794*440a403fSchristos     "sbcpm1 $crn,($rma+),$cdisp10"
2795*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x0) (f-ext62 #x3) cdisp10)
2796*440a403fSchristos     (sequence ()
2797*440a403fSchristos	       (c-call "check_option_cp" pc)
2798*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2799*440a403fSchristos	       (set (mem QI rma) (and crn #xff))
2800*440a403fSchristos	       (set rma (mod1 cdisp10)))
2801*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2802*440a403fSchristos	   (unit u-exec))))
2803*440a403fSchristos
2804*440a403fSchristos(dnci lbcpm1 "lbcpm1" (OPTIONAL_CP_INSN)
2805*440a403fSchristos     "lbcpm1 $crn,($rma+),$cdisp10"
2806*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x4) (f-ext62 #x3) cdisp10)
2807*440a403fSchristos     (sequence ()
2808*440a403fSchristos	       (c-call "check_option_cp" pc)
2809*440a403fSchristos	       (set crn (ext SI (mem QI rma)))
2810*440a403fSchristos	       (set rma (mod1 cdisp10)))
2811*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2812*440a403fSchristos	   (unit u-exec))))
2813*440a403fSchristos
2814*440a403fSchristos(dnci shcpm1 "shcpm1" (OPTIONAL_CP_INSN)
2815*440a403fSchristos     "shcpm1 $crn,($rma+),$cdisp10a2"
2816*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x1) (f-ext62 #x3) cdisp10a2)
2817*440a403fSchristos     (sequence ()
2818*440a403fSchristos	       (c-call "check_option_cp" pc)
2819*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 1)))
2820*440a403fSchristos	       (set (mem HI (and rma (inv SI 1))) (and crn #xffff))
2821*440a403fSchristos	       (set rma (mod1 cdisp10a2)))
2822*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2823*440a403fSchristos	   (unit u-exec))))
2824*440a403fSchristos
2825*440a403fSchristos(dnci lhcpm1 "lhcpm1" (OPTIONAL_CP_INSN)
2826*440a403fSchristos     "lhcpm1 $crn,($rma+),$cdisp10a2"
2827*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x5) (f-ext62 #x3) cdisp10a2)
2828*440a403fSchristos     (sequence ()
2829*440a403fSchristos	       (c-call "check_option_cp" pc)
2830*440a403fSchristos	       (set crn (ext SI (mem HI (and rma (inv SI 1)))))
2831*440a403fSchristos	       (set rma (mod1 cdisp10a2)))
2832*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2833*440a403fSchristos	   (unit u-exec))))
2834*440a403fSchristos
2835*440a403fSchristos(dnci swcpm1 "swcpm1" (OPTIONAL_CP_INSN)
2836*440a403fSchristos     "swcpm1 $crn,($rma+),$cdisp10a4"
2837*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x2) (f-ext62 #x3) cdisp10a4)
2838*440a403fSchristos     (sequence ()
2839*440a403fSchristos	       (c-call "check_option_cp" pc)
2840*440a403fSchristos	       (c-call VOID "check_write_to_text" (and rma (inv SI 3)))
2841*440a403fSchristos	       (set (mem SI (and rma (inv SI 3))) crn)
2842*440a403fSchristos	       (set rma (mod1 cdisp10a4)))
2843*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2844*440a403fSchristos	   (unit u-exec))))
2845*440a403fSchristos
2846*440a403fSchristos(dnci lwcpm1 "lwcpm1" (OPTIONAL_CP_INSN)
2847*440a403fSchristos     "lwcpm1 $crn,($rma+),$cdisp10a4"
2848*440a403fSchristos     (+ MAJ_15 crn rma (f-sub4 5) (f-ext4 #x6) (f-ext62 #x3) cdisp10a4)
2849*440a403fSchristos     (sequence ()
2850*440a403fSchristos	       (c-call "check_option_cp" pc)
2851*440a403fSchristos	       (set crn (ext SI (mem SI (and rma (inv SI 3)))))
2852*440a403fSchristos	       (set rma (mod1 cdisp10a4)))
2853*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2854*440a403fSchristos	   (unit u-exec))))
2855*440a403fSchristos
2856*440a403fSchristos(dnci smcpm1 "smcpm1" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN)
2857*440a403fSchristos     "smcpm1 $crn64,($rma+),$cdisp10a8"
2858*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x3) (f-ext62 #x3) cdisp10a8)
2859*440a403fSchristos     (sequence ()
2860*440a403fSchristos	       (c-call "check_option_cp" pc)
2861*440a403fSchristos	       (c-call "check_option_cp64" pc)
2862*440a403fSchristos	       (c-call "do_smcp" rma crn64 pc)
2863*440a403fSchristos	       (c-call VOID "check_write_to_text" rma)
2864*440a403fSchristos	       (set rma (mod1 cdisp10a8)))
2865*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2866*440a403fSchristos	   (unit u-exec))))
2867*440a403fSchristos
2868*440a403fSchristos(dnci lmcpm1 "lmcpm1" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN)
2869*440a403fSchristos     "lmcpm1 $crn64,($rma+),$cdisp10a8"
2870*440a403fSchristos     (+ MAJ_15 crn64 rma (f-sub4 5) (f-ext4 #x7) (f-ext62 #x3) cdisp10a8)
2871*440a403fSchristos     (sequence ()
2872*440a403fSchristos	       (c-call "check_option_cp" pc)
2873*440a403fSchristos	       (c-call "check_option_cp64" pc)
2874*440a403fSchristos	       (set crn64 (c-call DI "do_lmcp" rma pc))
2875*440a403fSchristos	       (set rma (mod1 cdisp10a8)))
2876*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rma))
2877*440a403fSchristos	   (unit u-exec))))
2878*440a403fSchristos
2879*440a403fSchristos(dnop cp_flag       "branch condition register"  (all-mep-isas) h-ccr   1)
2880*440a403fSchristos
2881*440a403fSchristos(dnci bcpeq "branch coprocessor equal" (OPTIONAL_CP_INSN RELAXABLE)
2882*440a403fSchristos     "bcpeq $cccc,$pcrel17a2"
2883*440a403fSchristos     (+ MAJ_13 (f-rn 8) cccc (f-sub4 4) pcrel17a2)
2884*440a403fSchristos     (sequence ()
2885*440a403fSchristos	       (c-call "check_option_cp" pc)
2886*440a403fSchristos	       (if (eq (xor cccc cp_flag) 0)
2887*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel17a2)))
2888*440a403fSchristos     ())
2889*440a403fSchristos
2890*440a403fSchristos(dnci bcpne "branch coprocessor not equal" (OPTIONAL_CP_INSN RELAXABLE)
2891*440a403fSchristos     "bcpne $cccc,$pcrel17a2"
2892*440a403fSchristos     (+ MAJ_13 (f-rn 8) cccc (f-sub4 5) pcrel17a2)
2893*440a403fSchristos     (sequence ()
2894*440a403fSchristos	       (c-call "check_option_cp" pc)
2895*440a403fSchristos	       (if (ne (xor cccc cp_flag) 0)
2896*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel17a2)))
2897*440a403fSchristos     ())
2898*440a403fSchristos
2899*440a403fSchristos(dnci bcpat "branch coprocessor and true" (OPTIONAL_CP_INSN RELAXABLE)
2900*440a403fSchristos     "bcpat $cccc,$pcrel17a2"
2901*440a403fSchristos     (+ MAJ_13 (f-rn 8) cccc (f-sub4 6) pcrel17a2)
2902*440a403fSchristos     (sequence ()
2903*440a403fSchristos	       (c-call "check_option_cp" pc)
2904*440a403fSchristos	       (if (ne (and cccc cp_flag) 0)
2905*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel17a2)))
2906*440a403fSchristos     ())
2907*440a403fSchristos
2908*440a403fSchristos(dnci bcpaf "branch coprocessor and false" (OPTIONAL_CP_INSN RELAXABLE)
2909*440a403fSchristos     "bcpaf $cccc,$pcrel17a2"
2910*440a403fSchristos     (+ MAJ_13 (f-rn 8) cccc (f-sub4 7) pcrel17a2)
2911*440a403fSchristos     (sequence ()
2912*440a403fSchristos	       (c-call "check_option_cp" pc)
2913*440a403fSchristos	       (if (eq (and cccc cp_flag) 0)
2914*440a403fSchristos	       (set-vliw-alignment-modified pc pcrel17a2)))
2915*440a403fSchristos     ())
2916*440a403fSchristos
2917*440a403fSchristos(dnci synccp "synchronise with coprocessor" (OPTIONAL_CP_INSN)
2918*440a403fSchristos     "synccp"
2919*440a403fSchristos     (+ MAJ_7 (f-rn 0) (f-rm 2) (f-sub4 1))
2920*440a403fSchristos     (sequence ()
2921*440a403fSchristos	       (c-call "check_option_cp" pc)
2922*440a403fSchristos	       (unimp "synccp"))
2923*440a403fSchristos     ())
2924*440a403fSchristos
2925*440a403fSchristos(dnci jsrv "jump to vliw subroutine " (OPTIONAL_CP_INSN)
2926*440a403fSchristos     "jsrv $rm"
2927*440a403fSchristos     (+ MAJ_1 (f-rn 8) rm (f-sub4 15))
2928*440a403fSchristos     (sequence ()
2929*440a403fSchristos	       (cg-profile pc rm)
2930*440a403fSchristos	       (c-call "check_option_cp" pc)
2931*440a403fSchristos	       (core-vliw-switch
2932*440a403fSchristos
2933*440a403fSchristos		;; in core operating mode
2934*440a403fSchristos		(sequence ()
2935*440a403fSchristos			  (set lp (or (add pc 2) 1))
2936*440a403fSchristos			  (set-vliw-aliignment-modified-by-option pc rm)
2937*440a403fSchristos			  (set-psw.om 1)) ;; to VLIW operation mode
2938*440a403fSchristos
2939*440a403fSchristos		;; in VLIW32 operating mode
2940*440a403fSchristos		(sequence ()
2941*440a403fSchristos			  (set lp (or (add pc 4) 1))
2942*440a403fSchristos			  (set pc (and rm (inv 1)))
2943*440a403fSchristos			  (set-psw.om 0)) ;; to core operation mode
2944*440a403fSchristos
2945*440a403fSchristos		;; in VLIW64 operating mode
2946*440a403fSchristos		(sequence ()
2947*440a403fSchristos			  (set lp (or (add pc 8) 1))
2948*440a403fSchristos			  (set pc (and rm (inv 1)))
2949*440a403fSchristos			  (set-psw.om 0)))) ;; to core operation mode
2950*440a403fSchristos     ((mep (unit u-use-gpr (in usereg rm))
2951*440a403fSchristos	   (unit u-exec)
2952*440a403fSchristos	   (unit u-branch))))
2953*440a403fSchristos
2954*440a403fSchristos(dnci bsrv "branch to vliw subroutine" (OPTIONAL_CP_INSN)
2955*440a403fSchristos     "bsrv $pcrel24a2"
2956*440a403fSchristos     (+ MAJ_13 (f-4 1) (f-sub4 11) pcrel24a2)
2957*440a403fSchristos     (sequence ()
2958*440a403fSchristos	       (cg-profile pc pcrel24a2)
2959*440a403fSchristos	       (c-call "check_option_cp" pc)
2960*440a403fSchristos	       (core-vliw-switch
2961*440a403fSchristos
2962*440a403fSchristos		;; in core operating mode
2963*440a403fSchristos		(sequence ()
2964*440a403fSchristos			  (set lp (or (add pc 4) 1))
2965*440a403fSchristos			  (set-vliw-aliignment-modified-by-option pc pcrel24a2)
2966*440a403fSchristos			  (set-psw.om 1)) ;; to VLIW operation mode
2967*440a403fSchristos
2968*440a403fSchristos		;; in VLIW32 operating mode
2969*440a403fSchristos		(sequence ()
2970*440a403fSchristos			  (set lp (or (add pc 4) 1))
2971*440a403fSchristos			  (set pc (and pcrel24a2 (inv 1)))
2972*440a403fSchristos			  (set-psw.om 0)) ;; to core operation mode
2973*440a403fSchristos
2974*440a403fSchristos		;; in VLIW64 operating mode
2975*440a403fSchristos		(sequence ()
2976*440a403fSchristos			  (set lp (or (add pc 8) 1))
2977*440a403fSchristos			  (set pc (and pcrel24a2 (inv 1)))
2978*440a403fSchristos			  (set-psw.om 0)))) ;; to core operation mode
2979*440a403fSchristos     ((mep (unit u-exec)
2980*440a403fSchristos	   (unit u-branch))))
2981*440a403fSchristos
2982*440a403fSchristos
2983*440a403fSchristos; An instruction for test instrumentation.
2984*440a403fSchristos; Using a reserved opcode.
2985*440a403fSchristos
2986*440a403fSchristos(dnci sim-syscall "simulator system call" ()
2987*440a403fSchristos     "--syscall--"
2988*440a403fSchristos     (+ MAJ_7 (f-4 1) callnum (f-8 0) (f-9 0) (f-10 0) (f-sub4 0))
2989*440a403fSchristos     (c-call "do_syscall" pc callnum)
2990*440a403fSchristos     ())
2991*440a403fSchristos
2992*440a403fSchristos(define-pmacro (dnri n major minor)
2993*440a403fSchristos  (dnci (.sym ri- n) "reserved instruction" ()
2994*440a403fSchristos	"--reserved--"
2995*440a403fSchristos	(+ major rn rm (f-sub4 minor))
2996*440a403fSchristos	(set pc (c-call USI "ri_exception" pc))
2997*440a403fSchristos	((mep (unit u-exec)
2998*440a403fSchristos	      (unit u-branch)))))
2999*440a403fSchristos
3000*440a403fSchristos(dnri 0  MAJ_0   6)
3001*440a403fSchristos(dnri 1  MAJ_1  10)
3002*440a403fSchristos(dnri 2  MAJ_1  11)
3003*440a403fSchristos(dnri 3  MAJ_2   5)
3004*440a403fSchristos(dnri 4  MAJ_2   8)
3005*440a403fSchristos(dnri 5  MAJ_2   9)
3006*440a403fSchristos(dnri 6  MAJ_2  10)
3007*440a403fSchristos(dnri 7  MAJ_2  11)
3008*440a403fSchristos(dnri 8  MAJ_3   4)
3009*440a403fSchristos(dnri 9  MAJ_3   5)
3010*440a403fSchristos(dnri 10 MAJ_3   6)
3011*440a403fSchristos(dnri 11 MAJ_3   7)
3012*440a403fSchristos(dnri 12 MAJ_3  12)
3013*440a403fSchristos(dnri 13 MAJ_3  13)
3014*440a403fSchristos(dnri 14 MAJ_3  14)
3015*440a403fSchristos(dnri 15 MAJ_3  15)
3016*440a403fSchristos(dnri 17 MAJ_7   7)
3017*440a403fSchristos(dnri 20 MAJ_7  14)
3018*440a403fSchristos(dnri 21 MAJ_7  15)
3019*440a403fSchristos(dnri 22 MAJ_12  7)
3020*440a403fSchristos(dnri 23 MAJ_14 13)
3021*440a403fSchristos;(dnri 24 MAJ_15  3)
3022*440a403fSchristos(dnri 26 MAJ_15  8)
3023*440a403fSchristos; begin core-specific reserved insns
3024*440a403fSchristos; end core-specific reserved insns
3025*440a403fSchristos
3026*440a403fSchristos
3027*440a403fSchristos; Macro instructions.
3028*440a403fSchristos
3029*440a403fSchristos(dnmi nop "nop"
3030*440a403fSchristos      ()
3031*440a403fSchristos      "nop"
3032*440a403fSchristos      (emit mov (rn 0) (rm 0)))
3033*440a403fSchristos
3034*440a403fSchristos; Emit the 16 bit form of these 32 bit insns when the displacement is zero.
3035*440a403fSchristos;
3036*440a403fSchristos(dncmi sb16-0 "store byte (explicit 16 bit displacement of zero)" (NO-DIS)
3037*440a403fSchristos     "sb $rnc,$zero($rma)"
3038*440a403fSchristos     (emit sb rnc rma))
3039*440a403fSchristos
3040*440a403fSchristos(dncmi sh16-0 "store half (explicit 16 bit displacement of zero)" (NO-DIS)
3041*440a403fSchristos     "sh $rns,$zero($rma)"
3042*440a403fSchristos     (emit sh rns rma))
3043*440a403fSchristos
3044*440a403fSchristos(dncmi sw16-0 "store word (explicit 16 bit displacement of zero)" (NO-DIS)
3045*440a403fSchristos     "sw $rnl,$zero($rma)"
3046*440a403fSchristos     (emit sw rnl rma))
3047*440a403fSchristos
3048*440a403fSchristos(dncmi lb16-0 "load byte (explicit 16 bit displacement of zero)" (NO-DIS)
3049*440a403fSchristos     "lb $rnc,$zero($rma)"
3050*440a403fSchristos     (emit lb rnc rma))
3051*440a403fSchristos
3052*440a403fSchristos(dncmi lh16-0 "load half (explicit 16 bit displacement of zero)" (NO-DIS)
3053*440a403fSchristos     "lh $rns,$zero($rma)"
3054*440a403fSchristos     (emit lh rns rma))
3055*440a403fSchristos
3056*440a403fSchristos(dncmi lw16-0 "load word (explicit 16 bit displacement of zero)" (NO-DIS)
3057*440a403fSchristos     "lw $rnl,$zero($rma)"
3058*440a403fSchristos     (emit lw rnl rma))
3059*440a403fSchristos
3060*440a403fSchristos(dncmi lbu16-0 "load unsigned byte (explicit 16 bit displacement of zero)" (NO-DIS)
3061*440a403fSchristos     "lbu $rnuc,$zero($rma)"
3062*440a403fSchristos     (emit lbu rnuc rma))
3063*440a403fSchristos
3064*440a403fSchristos(dncmi lhu16-0 "load unsigned half (explicit 16 bit displacement of zero)" (NO-DIS)
3065*440a403fSchristos     "lhu $rnus,$zero($rma)"
3066*440a403fSchristos     (emit lhu rnus rma))
3067*440a403fSchristos
3068*440a403fSchristos(dncmi swcp16-0 "swcp (explicit 16-bit displacement of zero)" (OPTIONAL_CP_INSN NO-DIS)
3069*440a403fSchristos     "swcp $crn,$zero($rma)"
3070*440a403fSchristos     (emit swcp crn rma))
3071*440a403fSchristos
3072*440a403fSchristos(dncmi lwcp16-0 "lwcp (explicit 16-bit displacement of zero)" (OPTIONAL_CP_INSN NO-DIS)
3073*440a403fSchristos     "lwcp $crn,$zero($rma)"
3074*440a403fSchristos     (emit lwcp crn rma))
3075*440a403fSchristos
3076*440a403fSchristos(dncmi smcp16-0 "smcp (explicit 16-bit displacement of zero)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN NO-DIS)
3077*440a403fSchristos     "smcp $crn64,$zero($rma)"
3078*440a403fSchristos     (emit smcp crn64 rma))
3079*440a403fSchristos
3080*440a403fSchristos(dncmi lmcp16-0 "lmcp (explicit 16-bit displacement of zero)" (OPTIONAL_CP_INSN OPTIONAL_CP64_INSN NO-DIS)
3081*440a403fSchristos     "lmcp $crn64,$zero($rma)"
3082*440a403fSchristos     (emit lmcp crn64 rma))
3083