; Renesas M32R CPU description. -*- Scheme -*-
;
; Copyright 1998, 1999, 2000, 2001, 2003, 2007, 2009
; Free Software Foundation, Inc.
;
; Contributed by Red Hat Inc; developed under contract from Mitsubishi
; Electric Corporation.
;
; This file is part of the GNU Binutils.
;
; This program is free software; you can redistribute it and/or modify
; it under the terms of the GNU General Public License as published by
; the Free Software Foundation; either version 3 of the License, or
; (at your option) any later version.
;
; This program is distributed in the hope that it will be useful,
; but WITHOUT ANY WARRANTY; without even the implied warranty of
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
; GNU General Public License for more details.
;
; You should have received a copy of the GNU General Public License
; along with this program; if not, write to the Free Software
; Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
; MA 02110-1301, USA.
(include "simplify.inc")
; FIXME: Delete sign extension of accumulator results.
; Sign extension is done when accumulator is read.
; define-arch must appear first
(define-arch
(name m32r) ; name of cpu family
(comment "Renesas M32R")
(default-alignment aligned)
(insn-lsb0? #f)
(machs m32r m32rx m32r2)
(isas m32r)
)
; Attributes.
; An attribute to describe which pipeline an insn runs in.
; O_OS is a special attribute for sll, sra, sla, slli, srai, slai.
; These instructions have O attribute for m32rx and OS attribute for m32r2.
(define-attr
(for insn)
(type enum)
(name PIPE)
(comment "parallel execution pipeline selection")
(values NONE O S OS O_OS)
)
; A derived attribute that says which insns can be executed in parallel
; with others. This is a required attribute for architectures with
; parallel execution.
(define-attr
(for insn)
(type enum)
(name PARALLEL)
(attrs META) ; do not define in any generated file for now
(values NO YES)
(default (if (eq-attr (current-insn) PIPE NONE) (symbol NO) (symbol YES)))
)
; Instruction set parameters.
(define-isa
(name m32r)
; This is 32 because 16 bit insns always appear as pairs.
; ??? See if this can go away. It's only used by the disassembler (right?)
; to decide how long an unknown insn is. One value isn't sufficient (e.g. if
; on a 16 bit (and not 32 bit) boundary, will only want to advance pc by 16.)
(default-insn-bitsize 32)
; Number of bytes of insn we can initially fetch.
; The M32R is tricky in that insns are either two 16-bit insns
; (executed sequentially or in parallel) or one 32-bit insn.
; So on one hand the base insn size is 16 bits, but on another it's 32.
; 32 is chosen because:
; - if the chip were ever bi-endian it is believed that the byte order would
; be based on 32 bit quantities
; - 32 bit insns are always aligned on 32 bit boundaries
; - the pc will never stop on a 16 bit (and not 32 bit) boundary
; [well actually it can, but there are no branches to such places]
(base-insn-bitsize 32)
; Used in computing bit numbers.
(default-insn-word-bitsize 32)
; The m32r fetches 2 insns at a time.
(liw-insns 2)
; While the m32r can execute insns in parallel, the base mach can't
; (other than nop). The base mach is greatly handicapped by this, but
; we still need to cleanly handle it.
(parallel-insns 2)
; Classification of instructions that fit in the various frames.
; wip, not currently used
(insn-types (long ; name
31 ; length
(eq-attr (current-insn) LENGTH 31) ; matching insns
(0 1 2 7 8 9 10) ; decode-assist
)
(short
15
(eq-attr (current-insn) LENGTH 15) ; matching insns
(0 1 2 7 8 9 10)
)
)
; Instruction framing.
; Each m32r insn is either one 32 bit insn, two 16 bit insns executed
; serially (left->right), or two 16 bit insns executed parallelly.
; wip, not currently used
(frame long32 ; name
((long)) ; list of insns in frame, plus constraint
"$0" ; assembler
(+ (1 1) (31 $0)) ; value
(sequence () (execute $0)) ; action
)
(frame serial2x16
((short)
(short))
"$0 -> $1"
(+ (1 0) (15 $0) (1 0) (15 $1))
(sequence ()
(execute $0)
(execute $1))
)
(frame parallel2x16
((short (eq-attr (current-insn) PIPE "O,BOTH"))
(short (eq-attr (current-insn) PIPE "S,BOTH")))
"$0 || $1"
(+ (1 0) (15 $0) (1 1) (15 $1))
(parallel ()
(execute $0)
(execute $1))
)
)
; Cpu family definitions.
; ??? define-cpu-family [and in general "cpu-family"] might be clearer than
; define-cpu.
; ??? Have define-arch provide defaults for architecture that define-cpu can
; then override [reduces duplication in define-cpu].
; ??? Another way to go is to delete cpu-families entirely and have one mach
; able to inherit things from another mach (would also need the ability to
; not only override specific inherited things but also disable some,
; e.g. if an insn wasn't supported).
(define-cpu
; cpu names must be distinct from the architecture name and machine names.
; The "b" suffix stands for "base" and is the convention.
; The "f" suffix stands for "family" and is the convention.
(name m32rbf)
(comment "Renesas M32R base family")
(endian either)
(word-bitsize 32)
; Override isa spec (??? keeps things simpler, though it was more true
; in the early days and not so much now).
(parallel-insns 1)
)
(define-cpu
(name m32rxf)
(comment "Renesas M32Rx family")
(endian either)
(word-bitsize 32)
; Generated files have an "x" suffix.
(file-transform "x")
)
; The meaning of this value is wip but at the moment it's intended to describe
; the implementation (i.e. what -mtune=foo does in sparc gcc).
;
; Notes while wip:
; - format of pipeline entry:
; (pipeline name (stage1-name ...) (stage2-name ...) ...)
; The contents of a stage description is wip.
; - each mach must have at least one model
; - the default model must be the first one
;- maybe have `retire' support update total cycle count to handle current
; parallel insn cycle counting problems
; The instruction fetch/execute cycle.
; This is split into two parts as sometimes more than one instruction is
; decoded at once.
; The `const SI' argument to decode/execute is used to distinguish
; multiple instructions processed at the same time (e.g. m32r).
;
; ??? This is wip, and not currently used.
; ??? Needs to be moved to define-isa.
; This is how to fetch and decode an instruction.
;(define-extract
; (sequence VOID
; (if VOID (ne AI (and AI pc (const AI 3)) (const AI 0))
; (sequence VOID
; (set-quiet USI (scratch UHI insn1) (ifetch UHI pc))
; (decode VOID pc (and UHI insn1 (const UHI #x7fff))
; (const SI 0)))
; (sequence VOID
; (set-quiet USI (scratch USI insn) (ifetch USI pc))
; (if VOID (ne USI (and USI insn (const USI #x80000000))
; (const USI 0))
; (decode VOID pc (srl USI insn (const WI 16)) (const SI 0))
; (sequence VOID
; ; ??? parallel support
; (decode VOID pc (srl USI insn (const WI 16))
; (const SI 0))
; (decode VOID (add AI pc (const AI 2))
; (and USI insn (const WI #x7fff))
; (const SI 1))))))
; )
;)
; This is how to execute a decoded instruction.
;(define-execute
; (sequence VOID () ; () is empty option list
; ((AI new_pc))
; (set AI new_pc (execute: AI (const 0)) #:quiet)
; (set AI pc new_pc #:direct)
; )
;)
; FIXME: It might simplify things to separate the execute process from the
; one that updates the PC.
; Instruction fields.
;
; Attributes:
; PCREL-ADDR: pc relative value (for reloc and disassembly purposes)
; ABS-ADDR: absolute address (for reloc and disassembly purposes?)
; RESERVED: bits are not used to decode insn, must be all 0
; RELOC: there is a relocation associated with this field (experiment)
(define-attr
(for ifield operand)
(type boolean)
(name RELOC)
(comment "there is a reloc associated with this field (experiment)")
)
(dnf f-op1 "op1" () 0 4)
(dnf f-op2 "op2" () 8 4)
(dnf f-cond "cond" () 4 4)
(dnf f-r1 "r1" () 4 4)
(dnf f-r2 "r2" () 12 4)
(df f-simm8 "simm8" () 8 8 INT #f #f)
(df f-simm16 "simm16" () 16 16 INT #f #f)
(dnf f-shift-op2 "shift op2" () 8 3)
(dnf f-uimm3 "uimm3" () 5 3)
(dnf f-uimm4 "uimm4" () 12 4)
(dnf f-uimm5 "uimm5" () 11 5)
(dnf f-uimm8 "uimm8" () 8 8)
(dnf f-uimm16 "uimm16" () 16 16)
(dnf f-uimm24 "uimm24" (ABS-ADDR RELOC) 8 24)
(dnf f-hi16 "high 16 bits" (SIGN-OPT) 16 16)
(df f-disp8 "disp8, slot unknown" (PCREL-ADDR RELOC) 8 8 INT
((value pc) (sra WI (sub WI value (and WI pc (const -4))) (const 2)))
((value pc) (add WI (mul WI value (const 4)) (and WI pc (const -4)))))
(df f-disp16 "disp16" (PCREL-ADDR RELOC) 16 16 INT
((value pc) (sra WI (sub WI value pc) (const 2)))
((value pc) (add WI (mul WI value (const 4)) pc)))
(df f-disp24 "disp24" (PCREL-ADDR RELOC) 8 24 INT
((value pc) (sra WI (sub WI value pc) (const 2)))
((value pc) (add WI (mul WI value (const 4)) pc)))
(define-ifield (name f-imm1) (comment "1 bit immediate, 0->1 1->2")
(attrs)
(start 15) (length 1)
(encode (value pc) (sub WI value (const WI 1)))
(decode (value pc) (add WI value (const WI 1)))
)
; Enums.
; insn-op1: bits 0-3
; FIXME: should use die macro or some such
(define-normal-insn-enum insn-op1 "insn format enums" () OP1_ f-op1
("0" "1" "2" "3" "4" "5" "6" "7"
"8" "9" "10" "11" "12" "13" "14" "15")
)
; insn-op2: bits 8-11
; FIXME: should use die macro or some such
(define-normal-insn-enum insn-op2 "op2 enums" () OP2_ f-op2
("0" "1" "2" "3" "4" "5" "6" "7"
"8" "9" "10" "11" "12" "13" "14" "15")
)
; Hardware pieces.
; These entries list the elements of the raw hardware.
; They're also used to provide tables and other elements of the assembly
; language.
; These two aren't technically needed.
; They're here for illustration sake mostly.
; Plus they cause the value to be stored in the extraction buffers to only
; be 16 bits wide (vs 32 or 64). Whoopie ding. But it's fun.
(dnh h-slo16 "signed low 16 bits" ()
(immediate (INT 16))
() () ()
)
(dnh h-ulo16 "unsigned low 16 bits" ()
(immediate (UINT 16))
() () ()
)
; The actual accumulator is only 56 bits.
; The top 8 bits are sign extended from bit 8 (when counting msb = bit 0).
; To simplify the accumulator instructions, no attempt is made to keep the
; top 8 bits properly sign extended (currently there's no point since they
; all ignore them). When the value is read it is properly sign extended
; [in the `get' handler].
(define-hardware
(name h-accum)
(comment "accumulator")
(type register DI)
(get () (c-call DI "@cpu@_h_accum_get_handler"))
(set (newval) (c-call VOID "@cpu@_h_accum_set_handler" newval))
)
; FIXME: Revisit after sanitization can be removed. Remove h-accum.
(define-hardware
(name h-accums)
(comment "accumulators")
(attrs (MACH m32rx,m32r2))
(type register DI (2))
(indices keyword "" ((a0 0) (a1 1)))
; get/set so a0 accesses are redirected to h-accum.
; They're also so reads can properly sign extend the value.
; FIXME: Needn't be a function call.
(get (index) (c-call DI "@cpu@_h_accums_get_handler" index))
(set (index newval) (c-call VOID "@cpu@_h_accums_set_handler" index newval))
)
; For condbit operand. FIXME: Need to allow spec of get/set of operands.
; Having this separate from h-psw keeps the parts that use it simpler
; [since they greatly outnumber those that use h-psw].
(dsh h-cond "condition bit" () (register BI))
; The actual values of psw,bpsw,bbpsw are recorded here to allow access
; to them as a unit.
(define-hardware
(name h-psw)
(comment "psw part of psw")
(type register UQI)
; get/set to handle cond bit.
; FIXME: missing: use's and clobber's
; FIXME: remove c-call?
(get () (c-call UQI "@cpu@_h_psw_get_handler"))
(set (newval) (c-call VOID "@cpu@_h_psw_set_handler" newval))
)
(dsh h-bpsw "backup psw" () (register UQI))
(dsh h-bbpsw "backup bpsw" () (register UQI))
; FIXME: Later make add get/set specs and support SMP.
(dsh h-lock "lock" () (register BI))
; Instruction Operands.
; These entries provide a layer between the assembler and the raw hardware
; description, and are used to refer to hardware elements in the semantic
; code. Usually there's a bit of over-specification, but in more complicated
; instruction sets there isn't.
;; Print some operands take a hash prefix.
;; ??? Why don't we also handle one when parsing?
; ??? Convention says this should be o-sr, but then the insn definitions
; should refer to o-sr which is clumsy. The "o-" could be implicit, but
; then it should be implicit for all the symbols here, but then there would
; be confusion between (f-)simm8 and (h-)simm8.
; So for now the rule is exactly as it appears here.
(dnop sr "source register" () h-gr f-r2)
(dnop dr "destination register" () h-gr f-r1)
;; The assembler relies upon the fact that dr and src1 are the same field.
;; FIXME: Revisit.
(dnop src1 "source register 1" () h-gr f-r1)
(dnop src2 "source register 2" () h-gr f-r2)
(dnop scr "source control register" () h-cr f-r2)
(dnop dcr "destination control register" () h-cr f-r1)
(dshpo simm8 "8 bit signed immediate" () h-sint f-simm8)
(dshpo simm16 "16 bit signed immediate" () h-sint f-simm16)
(duhpo uimm3 "3 bit unsigned number" () h-uint f-uimm3)
(duhpo uimm4 "4 bit trap number" () h-uint f-uimm4)
(duhpo uimm5 "5 bit shift count" () h-uint f-uimm5)
(duhpo uimm8 "8 bit unsigned immediate" () h-uint f-uimm8)
(duhpo uimm16 "16 bit unsigned immediate" () h-uint f-uimm16)
(duhpo imm1 "1 bit immediate" ((MACH m32rx,m32r2)) h-uint f-imm1)
; slo16,ulo16 are used in both with-hash-prefix/no-hash-prefix cases.
; e.g. add3 r3,r3,#1 and ld r3,@(4,r4). We could use special handlers on
; the operands themselves.
; Instead we create a fake operand `hash'. The m32r is an illustration port,
; so we often try out various ways of doing things.
; For low(foo),sda(foo).
(define-operand
(name slo16)
(comment "16 bit signed immediate, for low()")
(attrs)
(type h-slo16)
(index f-simm16)
(handlers (parse "slo16"))
)
; For low(foo).
(define-operand
(name ulo16)
(comment "16 bit unsigned immediate, for low()")
(attrs)
(type h-ulo16)
(index f-uimm16)
(handlers (parse "ulo16"))
)
(dnop uimm24 "24 bit address" () h-addr f-uimm24)
(define-operand
(name disp8)
(comment "8 bit displacement")
(attrs RELAX)
(type h-iaddr)
(index f-disp8)
; ??? Early experiments had insert/extract fields here.
; Moving these to f-disp8 made things cleaner, but may wish to re-introduce
; fields here to handle more complicated cases.
)
(dnop disp16 "16 bit displacement" () h-iaddr f-disp16)
(dnop disp24 "24 bit displacement" (RELAX) h-iaddr f-disp24)
; These hardware elements are referred to frequently.
; Instruction definitions.
;
; Notes while wip:
; - dni is a cover macro to the real "this is an instruction" keyword.
; The syntax of the real one is yet to be determined.
; At the lowest level (i.e. the "real" one) it will probably take a variable
; list of arguments where each argument [perhaps after the standard three of
; name, comment, attrs] is "(keyword arg-to-keyword)". This syntax is simple
; and yet completely upward extensible. And given the macro facility, one
; needn't code at that low a level so even though it'll be more verbose than
; necessary it won't matter. This same reasoning can be applied to most
; types of entries in this file.
; M32R specific instruction attributes:
; FILL-SLOT: Need next insn to begin on 32 bit boundary.
; (A "slot" as used here is a 32 bit quantity that can either be filled with
; one 32 bit insn or two 16 bit insns which go in the "left bin" and "right
; bin" where the left bin is the one with a lower address).
(define-attr
(for insn)
(type boolean)
(name FILL-SLOT)
(comment "fill right bin with `nop' if insn is in left bin")
)
(dni addv "addv"
((PIPE OS) (IDOC ALU))
"addv $dr,$sr"
(+ OP1_0 OP2_8 dr sr)
(parallel ()
(set dr (add dr sr))
(set condbit (add-oflag dr sr (const 0))))
()
)
(dni addv3 "addv3"
((IDOC ALU))
"addv3 $dr,$sr,$simm16"
(+ OP1_8 OP2_8 dr sr simm16)
(parallel ()
(set dr (add sr simm16))
(set condbit (add-oflag sr simm16 (const 0))))
()
)
(dni addx "addx"
((PIPE OS) (IDOC ALU))
"addx $dr,$sr"
(+ OP1_0 OP2_9 dr sr)
(parallel ()
(set dr (addc dr sr condbit))
(set condbit (add-cflag dr sr condbit)))
()
)
(dni jmp "jmp"
(UNCOND-CTI (PIPE O) (IDOC BR))
"jmp $sr"
(+ OP1_1 (f-r1 15) OP2_12 sr)
(set pc (and sr (const -4)))
; The above works now so this kludge has been commented out.
; It's kept around because the f-r1 reference in the semantic part
; should work.
; FIXME: kludge, instruction decoding not finished.
; But this should work, so that's another FIXME.
;(sequence VOID (if VOID (eq SI f-r1 (const SI 14))
; FIXME: abuf->insn should be a macro of some sort.
;(sequence VOID
; (if VOID (eq SI (c-code SI "((abuf->insn >> 8) & 15)")
; (const SI 14))
; (set WI (reg WI h-gr 14)
; (add WI (and WI pc (const WI -4)) (const WI 4))))
; (set WI pc sr))
((m32r/d (unit u-cti))
(m32rx (unit u-cti))
(m32r2 (unit u-cti)))
)
(dni ld-plus "ld+"
((PIPE O) (IDOC MEM))
"ld $dr,@$sr+"
(+ OP1_2 dr OP2_14 sr)
(parallel ()
; wip: memory addresses in profiling support
;(set dr (name ld-mem (mem WI sr)))
(set dr (mem WI sr))
(set sr (add sr (const 4))))
; Note: `pred' is the constraint. Also useful here is (ref name)
; and returns true if operand <name> was referenced
; (where "referenced" means _read_ if input operand and _written_ if
; output operand).
; args to unit are "unit-name (name1 value1) ..."
; - cycles(done),issue,pred are also specified this way
; - if unspecified, default is used
; - for ins/outs, extra arg is passed that says what was specified
; - this is AND'd with `written' for outs
((m32r/d (unit u-load (pred (const 1)))
(unit u-exec (in sr #f) (in dr sr) (out dr sr) (cycles 0) (pred (const 1))))
(m32rx (unit u-load)
(unit u-exec (in sr #f) (in dr sr) (out dr sr) (cycles 0) (pred (const 1))))
(m32r2 (unit u-load)
(unit u-exec (in sr #f) (in dr sr) (out dr sr) (cycles 0) (pred (const 1))))
)
)
(dnmi pop "pop"
((PIPE O) (IDOC MEM))
"pop $dr"
(emit ld-plus dr (sr 15)) ; "ld %0,@sp+"
)
(dni ld24 "ld24"
((IDOC MEM))
"ld24 $dr,$uimm24"
(+ OP1_14 dr uimm24)
(set dr uimm24)
()
)
; ldi8 appears before ldi16 so we try the shorter version first
(dni ldi8 "ldi8"
((PIPE OS) (IDOC ALU))
"ldi8 $dr,$simm8"
(+ OP1_6 dr simm8)
(set dr simm8)
()
)
(dni lock "lock"
((PIPE O) (IDOC MISC))
"lock $dr,@$sr"
(+ OP1_2 OP2_13 dr sr)
(sequence ()
(set (reg h-lock) (const BI 1))
(set dr (mem WI sr)))
((m32r/d (unit u-load))
(m32rx (unit u-load))
(m32r2 (unit u-load)))
)
(dni machi "machi"
(
; (MACH m32r) is a temporary hack. This insn collides with machi-a
; in the simulator so disable it for m32rx.
(MACH m32r) (PIPE S) (IDOC MAC)
)
"machi $src1,$src2"
(+ OP1_3 OP2_4 src1 src2)
; FIXME: TRACE_RESULT will print the wrong thing since we
; alter one of the arguments.
(set accum
(sra DI
(sll DI
(add DI
accum
(mul DI
(ext DI (and WI src1 (const #xffff0000)))
(ext DI (trunc HI (sra WI src2 (const 16))))))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni machi-a "machi-a"
((MACH m32rx,m32r2) (PIPE S) (IDOC MAC))
"machi $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 4) src2)
(set acc
(sra DI
(sll DI
(add DI
acc
(mul DI
(ext DI (and WI src1 (const #xffff0000)))
(ext DI (trunc HI (sra WI src2 (const 16))))))
(const 8))
(const 8)))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni maclo "maclo"
((MACH m32r) (PIPE S) (IDOC MAC))
"maclo $src1,$src2"
(+ OP1_3 OP2_5 src1 src2)
(set accum
(sra DI
(sll DI
(add DI
accum
(mul DI
(ext DI (sll WI src1 (const 16)))
(ext DI (trunc HI src2))))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni maclo-a "maclo-a"
((MACH m32rx,m32r2) (PIPE S) (IDOC MAC))
"maclo $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 5) src2)
(set acc
(sra DI
(sll DI
(add DI
acc
(mul DI
(ext DI (sll WI src1 (const 16)))
(ext DI (trunc HI src2))))
(const 8))
(const 8)))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni macwhi "macwhi"
((MACH m32r) (PIPE S) (IDOC MAC))
"macwhi $src1,$src2"
(+ OP1_3 OP2_6 src1 src2)
(set accum
(sra DI
(sll DI
(add DI
accum
(mul DI
(ext DI src1)
(ext DI (trunc HI (sra WI src2 (const 16))))))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni macwhi-a "macwhi-a"
((MACH m32rx,m32r2) (PIPE S) SPECIAL (IDOC MAC))
"macwhi $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 6) src2)
; Note that this doesn't do the sign extension, which is correct.
(set acc
(add acc
(mul (ext DI src1)
(ext DI (trunc HI (sra src2 (const 16)))))))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni macwlo "macwlo"
((MACH m32r) (PIPE S) (IDOC MAC))
"macwlo $src1,$src2"
(+ OP1_3 OP2_7 src1 src2)
(set accum
(sra DI
(sll DI
(add DI
accum
(mul DI
(ext DI src1)
(ext DI (trunc HI src2))))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni macwlo-a "macwlo-a"
((MACH m32rx,m32r2) (PIPE S) SPECIAL (IDOC MAC))
"macwlo $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 7) src2)
; Note that this doesn't do the sign extension, which is correct.
(set acc
(add acc
(mul (ext DI src1)
(ext DI (trunc HI src2)))))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni mul "mul"
((PIPE S) (IDOC ALU))
"mul $dr,$sr"
(+ OP1_1 OP2_6 dr sr)
(set dr (mul dr sr))
((m32r/d (unit u-exec (cycles 4)))
(m32rx (unit u-exec (cycles 4)))
(m32r2 (unit u-exec (cycles 4))))
)
(dni mulhi "mulhi"
((MACH m32r) (PIPE S) (IDOC ACCUM))
"mulhi $src1,$src2"
(+ OP1_3 OP2_0 src1 src2)
(set accum
(sra DI
(sll DI
(mul DI
(ext DI (and WI src1 (const #xffff0000)))
(ext DI (trunc HI (sra WI src2 (const 16)))))
(const 16))
(const 16)))
((m32r/d (unit u-mac)))
)
(dni mulhi-a "mulhi-a"
((MACH m32rx,m32r2) (PIPE S) (IDOC ACCUM))
"mulhi $src1,$src2,$acc"
(+ OP1_3 (f-op23 0) src1 acc src2)
(set acc
(sra DI
(sll DI
(mul DI
(ext DI (and WI src1 (const #xffff0000)))
(ext DI (trunc HI (sra WI src2 (const 16)))))
(const 16))
(const 16)))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni mullo "mullo"
((MACH m32r) (PIPE S) (IDOC ACCUM))
"mullo $src1,$src2"
(+ OP1_3 OP2_1 src1 src2)
(set accum
(sra DI
(sll DI
(mul DI
(ext DI (sll WI src1 (const 16)))
(ext DI (trunc HI src2)))
(const 16))
(const 16)))
((m32r/d (unit u-mac)))
)
(dni mullo-a "mullo-a"
((MACH m32rx,m32r2) (PIPE S) (IDOC ACCUM))
"mullo $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 1) src2)
(set acc
(sra DI
(sll DI
(mul DI
(ext DI (sll WI src1 (const 16)))
(ext DI (trunc HI src2)))
(const 16))
(const 16)))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni mulwhi "mulwhi"
((MACH m32r) (PIPE S) (IDOC ACCUM))
"mulwhi $src1,$src2"
(+ OP1_3 OP2_2 src1 src2)
(set accum
(sra DI
(sll DI
(mul DI
(ext DI src1)
(ext DI (trunc HI (sra WI src2 (const 16)))))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni mulwhi-a "mulwhi-a"
((MACH m32rx,m32r2) (PIPE S) SPECIAL (IDOC ACCUM))
"mulwhi $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 2) src2)
; Note that this doesn't do the sign extension, which is correct.
(set acc
(mul (ext DI src1)
(ext DI (trunc HI (sra src2 (const 16))))))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni mulwlo "mulwlo"
((MACH m32r) (PIPE S) (IDOC ACCUM))
"mulwlo $src1,$src2"
(+ OP1_3 OP2_3 src1 src2)
(set accum
(sra DI
(sll DI
(mul DI
(ext DI src1)
(ext DI (trunc HI src2)))
(const 8))
(const 8)))
((m32r/d (unit u-mac)))
)
(dni mulwlo-a "mulwlo-a"
((MACH m32rx,m32r2) (PIPE S) SPECIAL (IDOC ACCUM))
"mulwlo $src1,$src2,$acc"
(+ OP1_3 src1 acc (f-op23 3) src2)
; Note that this doesn't do the sign extension, which is correct.
(set acc
(mul (ext DI src1)
(ext DI (trunc HI src2))))
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni mv "mv"
((PIPE OS) (IDOC ALU))
"mv $dr,$sr"
(+ OP1_1 OP2_8 dr sr)
(set dr sr)
()
)
(dni rach "rach"
((MACH m32r) (PIPE S) (IDOC MAC))
"rach"
(+ OP1_5 OP2_8 (f-r1 0) (f-r2 0))
(sequence ((DI tmp1))
; Lop off top 8 bits.
; The sign bit we want to use is bit 55 so the 64 bit value
; isn't properly signed which we deal with in the if's below.
(set tmp1 (and accum (const DI #xffffffffffffff)))
(if (andif (ge tmp1 (const DI #x003fff80000000))
(le tmp1 (const DI #x7fffffffffffff)))
(set tmp1 (const DI #x003fff80000000))
; else part
(if (andif (ge tmp1 (const DI #x80000000000000))
(le tmp1 (const DI #xffc00000000000)))
(set tmp1 (const DI #xffc00000000000))
(set tmp1 (and (add accum (const DI #x40000000))
(const DI #xffffffff80000000)))))
(set tmp1 (sll tmp1 (const 1)))
; Sign extend top 8 bits.
(set accum
; FIXME: 7?
(sra DI (sll DI tmp1 (const 7)) (const 7)))
)
((m32r/d (unit u-mac)))
)
(dni rach-dsi "rach-dsi"
((MACH m32rx,m32r2) (PIPE S) (IDOC MAC))
"rach $accd,$accs,$imm1"
(+ OP1_5 accd (f-bits67 0) OP2_8 accs (f-bit14 0) imm1)
(sequence ((DI tmp1))
(set tmp1 (sll accs imm1))
(set tmp1 (add tmp1 (const DI #x80000000)))
(set accd
(cond DI
((gt tmp1 (const DI #x00007fff00000000))
(const DI #x00007fff00000000))
((lt tmp1 (const DI #xffff800000000000))
(const DI #xffff800000000000))
(else (and tmp1 (const DI #xffffffff00000000)))))
)
((m32rx (unit u-mac))
(m32r2 (unit u-mac)))
)
(dni st-plus "st+"
((PIPE O) (IDOC MEM))
"st $src1,@+$src2"
(+ OP1_2 OP2_6 src1 src2)
; This has to be coded carefully to avoid an "earlyclobber" of src2.
(sequence ((WI new-src2))
(set new-src2 (add WI src2 (const WI 4)))
(set (mem WI new-src2) src1)
(set src2 new-src2))
((m32r/d (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32rx (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32r2 (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
)
)
(dni sth-plus "sth+"
((MACH m32rx,m32r2) (PIPE O) SPECIAL)
"sth $src1,@$src2+"
(+ OP1_2 OP2_3 src1 src2)
; This has to be coded carefully to avoid an "earlyclobber" of src2.
(sequence ((WI new-src2))
(set new-src2 src2)
(set (mem HI new-src2) src1)
(set src2 (add new-src2 (const 2))))
((m32rx (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32r2 (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
)
)
(dni stb-plus "stb+"
((MACH m32rx,m32r2) (PIPE O) SPECIAL)
"stb $src1,@$src2+"
(+ OP1_2 OP2_1 src1 src2)
; This has to be coded carefully to avoid an "earlyclobber" of src2.
(sequence ((WI new-src2))
(set new-src2 src2)
(set (mem QI new-src2) src1)
(set src2 (add new-src2 (const 1))))
((m32rx (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32r2 (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
)
)
(dni st-minus "st-"
((PIPE O) (IDOC MEM))
"st $src1,@-$src2"
(+ OP1_2 OP2_7 src1 src2)
; This is the original way. It doesn't work for parallel execution
; because of the earlyclobber of src2.
;(sequence ()
; (set src2 (sub src2 (const 4)))
; (set (mem WI src2) src1))
(sequence ((WI new-src2))
(set new-src2 (sub src2 (const 4)))
(set (mem WI new-src2) src1)
(set src2 new-src2))
((m32r/d (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32rx (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
(m32r2 (unit u-store)
(unit u-exec (in dr src2) (out dr src2) (cycles 0)))
)
)
(dni sub "sub"
((PIPE OS) (IDOC ALU))
"sub $dr,$sr"
(+ OP1_0 OP2_2 dr sr)
(set dr (sub dr sr))
()
)
(dni subv "sub:rv"
((PIPE OS) (IDOC ALU))
"subv $dr,$sr"
(+ OP1_0 OP2_0 dr sr)
(parallel ()
(set dr (sub dr sr))
(set condbit (sub-oflag dr sr (const 0))))
()
)
(dni subx "sub:rx"
((PIPE OS) (IDOC ALU))
"subx $dr,$sr"
(+ OP1_0 OP2_1 dr sr)
(parallel ()
(set dr (subc dr sr condbit))
(set condbit (sub-cflag dr sr condbit)))
()
)
(dni trap "trap"
(UNCOND-CTI FILL-SLOT (PIPE O) (IDOC MISC))
"trap $uimm4"
(+ OP1_1 OP2_15 (f-r1 0) uimm4)
(sequence ()
; bbpc = bpc
(set (reg h-cr 14) (reg h-cr 6))
; Set bpc to the return address. Actually it's not quite the
; return address as RTE rounds the address down to a word
; boundary.
(set (reg h-cr 6) (add pc (const 4)))
; bbpsw = bpsw
(set (reg h-bbpsw) (reg h-bpsw))
; bpsw = psw
(set (reg h-bpsw) (reg h-psw))
; sm is unchanged, ie,c are set to zero.
(set (reg h-psw) (and (reg h-psw) (const #x80)))
; m32r_trap handles operating vs user mode
(set WI pc (c-call WI "m32r_trap" pc uimm4))
)
()
)
; Saturate into byte.
(dni satb "satb"
((MACH m32rx,m32r2) (IDOC ALU))
"satb $dr,$sr"
(+ OP1_8 dr OP2_6 sr (f-uimm16 #x0300))
(set dr
; FIXME: min/max would simplify this nicely of course.
(cond WI
((ge sr (const 127)) (const 127))
((le sr (const -128)) (const -128))
(else sr)))
()
)
; Saturate into half word.
(dni sath "sath"
((MACH m32rx,m32r2) (IDOC ALU))
"sath $dr,$sr"
(+ OP1_8 dr OP2_6 sr (f-uimm16 #x0200))
(set dr
(cond WI
((ge sr (const 32767)) (const 32767))
((le sr (const -32768)) (const -32768))
(else sr)))
()
)
; Saturate word.
(dni sat "sat"
((MACH m32rx,m32r2) SPECIAL (IDOC ALU))
"sat $dr,$sr"
(+ OP1_8 dr OP2_6 sr (f-uimm16 0))
(set dr
(if WI condbit
(if WI (lt sr (const 0))
(const #x7fffffff)
(const #x80000000))
sr))
()
)
; Parallel compare byte zeros.
; Set C bit in condition register if any byte in source register is zero.
(dni pcmpbz "pcmpbz"
((MACH m32rx,m32r2) (PIPE OS) SPECIAL (IDOC ALU))
"pcmpbz $src2"
(+ OP1_0 (f-r1 3) OP2_7 src2)
(set condbit
(cond BI
((eq (and src2 (const #xff)) (const 0)) (const BI 1))
((eq (and src2 (const #xff00)) (const 0)) (const BI 1))
((eq (and src2 (const #xff0000)) (const 0)) (const BI 1))
((eq (and src2 (const #xff000000)) (const 0)) (const BI 1))
(else (const BI 0))))
((m32rx (unit u-cmp))
(m32r2 (unit u-cmp)))
)