Home | History | Annotate | Download | only in cpu
      1 ; Ubicom IP2K CPU description.  -*- Scheme -*-
      2 ; Copyright (C) 2002, 2009, 2011 Free Software Foundation, Inc.
      3 ;
      4 ; Contributed by Red Hat Inc;
      5 ;
      6 ; This file is part of the GNU Binutils.
      7 ;
      8 ; This program is free software; you can redistribute it and/or modify
      9 ; it under the terms of the GNU General Public License as published by
     10 ; the Free Software Foundation; either version 3 of the License, or
     11 ; (at your option) any later version.
     12 ;
     13 ; This program is distributed in the hope that it will be useful,
     14 ; but WITHOUT ANY WARRANTY; without even the implied warranty of
     15 ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
     16 ; GNU General Public License for more details.
     17 ;
     18 ; You should have received a copy of the GNU General Public License
     19 ; along with this program; if not, write to the Free Software
     20 ; Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
     21 ; MA 02110-1301, USA.
     22 
     23 (define-rtl-version 0 8)
     24 
     25 (include "simplify.inc")
     26 
     27 ; define-arch must appear first
     28 
     29 (define-arch
     30   (name ip2k) ; name of cpu family
     31   (comment "Ubicom IP2000 family")
     32   (default-alignment aligned)
     33   (insn-lsb0? #t)
     34   (machs ip2022 ip2022ext)
     35   (isas ip2k)
     36 )
     37 
     38 ; Attributes.
     39 
     40 (define-attr
     41   (for insn)
     42   (type boolean)
     43   (name EXT-SKIP-INSN)
     44   (comment "instruction is a PAGE, LOADL, LOADH or BREAKX instruction")
     45 )
     46 
     47 (define-attr
     48   (for insn)
     49   (type boolean)
     50   (name SKIPA)
     51   (comment "instruction is a SKIP instruction")
     52 )
     53 
     54 ; Instruction set parameters.
     55 
     56 (define-isa
     57   (name ip2k)
     58   (comment "Ubicom IP2000 ISA")
     59 
     60   (default-insn-word-bitsize 16)
     61   (default-insn-bitsize 16)
     62   (base-insn-bitsize 16)
     63 )
     64 
     66 ; Cpu family definitions.
     67 
     68 
     69 (define-cpu
     70   ; cpu names must be distinct from the architecture name and machine names.
     71   (name ip2kbf)
     72   (comment "Ubicom IP2000 Family")
     73   (endian big)
     74   (word-bitsize 16)
     75 )
     76 
     77 (define-mach
     78   (name ip2022)
     79   (comment "Ubicom IP2022")
     80   (cpu ip2kbf)
     81 )
     82 
     83 (define-mach
     84   (name ip2022ext)
     85   (comment "Ubicom IP2022 extended")
     86   (cpu ip2kbf)
     87 )
     88 
     89 
     91 ; Model descriptions.
     92 
     93 (define-model
     94   (name ip2k) (comment "VPE 2xxx") (attrs)
     95   (mach ip2022ext)
     96 
     97   (unit u-exec "Execution Unit" ()
     98 	1 1 ; issue done
     99 	() ; state
    100 	() ; inputs
    101 	() ; outputs
    102 	() ; profile action (default)
    103 	)
    104 )
    105 
    106 
    107 ; FIXME: It might simplify things to separate the execute process from the
    108 ; one that updates the PC.
    109 
    111 ; Instruction fields.
    112 ;
    113 ; Attributes:
    114 ; XXX: what VPE attrs
    115 ; PCREL-ADDR: pc relative value (for reloc and disassembly purposes)
    116 ; ABS-ADDR: absolute address (for reloc and disassembly purposes?)
    117 ; RESERVED: bits are not used to decode insn, must be all 0
    118 ; RELOC: there is a relocation associated with this field (experiment)
    119 
    120 
    121 (dnf f-imm8      "imm8"                () 7 8)
    122 (dnf f-reg       "reg"         (ABS-ADDR) 8 9)
    123 (dnf f-addr16cjp "addr16cjp"   (ABS-ADDR) 12 13)
    124 (dnf f-dir       "dir"                 () 9 1)
    125 (dnf f-bitno     "bit number"          () 11 3)
    126 (dnf f-op3       "op3"                 () 15 3)
    127 (dnf f-op4       "op4"                 () 15 4)
    128 (dnf f-op4mid    "op4mid"              () 11 4)
    129 (dnf f-op6       "op6"                 () 15 6)
    130 (dnf f-op8       "op8"                 () 15 8)
    131 (dnf f-op6-10low "op6-10low"           () 9 10)
    132 (dnf f-op6-7low  "op6-7low"            () 9 7)
    133 (dnf f-reti3     "reti3"               () 2 3)
    134 (dnf f-skipb     "sb/snb"      (ABS-ADDR) 12 1)
    135 (dnf f-page3     "page3"               ()  2 3)
    136 ;(define-ifield (name f-page3) (comment "page3") (attrs) (start 2) (length 3)
    137 ;  (encode (value pc) (srl WI value 13))
    138 ;  (decode (value pc) (sll WI value 13))
    139 ;)
    140 ; To fix the page/call asymmetry
    141 ;(define-ifield (name f-page3) (comment "page3") (attrs) (start 2) (length 3)
    142 ;  (encode (value pc) (srl WI value 13))
    143 ;  (decode (value pc) (sll WI value 13))
    144 ;)
    145 
    146 
    147 
    149 ; Enums.
    150 
    151 ; insn-op6: bits 15-10
    152 (define-normal-insn-enum insn-op6 "op6 enums" () OP6_ f-op6
    153   (OTHER1 OTHER2 SUB DEC OR AND XOR ADD 
    154    TEST NOT INC DECSZ RR RL SWAP INCSZ
    155    CSE POP SUBC DECSNZ MULU MULS INCSNZ  ADDC
    156    - - - - - - - -   
    157    - - - - - - - -
    158    - - - - - - - -
    159    - - - - - - - -
    160    - - - - - - - -   
    161    )
    162 )
    163 
    164 ; insn-dir: bit 9
    165 (define-normal-insn-enum insn-dir "dir enums" () DIR_ f-dir
    166   ; This bit specifies the polarity of many two-operand instructions:
    167   ; TO_W writes result to W regiser  (eg. ADDC W,$fr)
    168   ; NOTTO_W writes result in general register  (eg. ADDC $fr,W)
    169   (TO_W NOTTO_W)
    170 )
    171 
    172 
    173 ; insn-op4: bits 15-12
    174 (define-normal-insn-enum insn-op4 "op4 enums" () OP4_ f-op4
    175   (- - - - - - - LITERAL
    176    CLRB SETB SNB SB - - - -
    177    )
    178 )
    179 
    180 ; insn-op4mid: bits 11-8
    181 ; used for f-op4=LITERAL
    182 (define-normal-insn-enum insn-op4mid "op4mid enums" () OP4MID_ f-op4mid
    183   (LOADH_L LOADL_L MULU_L MULS_L PUSH_L  -  CSNE_L CSE_L
    184    RETW_L CMP_L SUB_L ADD_L MOV_L OR_L AND_L XOR_L)
    185 )
    186 
    187 ; insn-op3: bits 15-13
    188 (define-normal-insn-enum insn-op3 "op3 enums" () OP3_ f-op3
    189   (- - - - - - CALL JMP)
    190 )
    191 
    192 
    193   
    194 ; Hardware pieces.
    195 
    196 ; Bank-relative general purpose registers
    197 
    198 ; (define-pmacro (build-reg-name n) (.splice (.str "$" n) n))
    199 
    200 (define-keyword
    201   (name register-names)
    202   (enum-prefix H-REGISTERS-)
    203   (values
    204    ; These are the "Special Purpose Registers" that are not reserved
    205    ("ADDRSEL" #x2) ("ADDRX" #x3)
    206    ("IPH" #x4) ("IPL" #x5) ("SPH" #x6) ("SPL" #x7)
    207    ("PCH" #x8) ("PCL" #x9) ("WREG" #xA) ("STATUS" #xB)
    208    ("DPH" #xC) ("DPL" #xD) ("SPDREG" #xE) ("MULH" #xF)
    209    ("ADDRH" #x10) ("ADDRL" #x11) ("DATAH" #x12) ("DATAL" #x13)
    210    ("INTVECH" #x14) ("INTVECL" #x15) ("INTSPD" #x16) ("INTF" #x17)
    211    ("INTE" #x18) ("INTED" #x19) ("FCFG" #x1A) ("TCTRL" #x1B)
    212    ("XCFG" #x1C) ("EMCFG" #x1D) ("IPCH" #x1E) ("IPCL" #x1F)
    213    ("RAIN" #x20) ("RAOUT" #x21) ("RADIR" #x22) ("LFSRH" #x23)
    214    ("RBIN" #x24) ("RBOUT" #x25) ("RBDIR" #x26) ("LFSRL" #x27)
    215    ("RCIN" #x28) ("RCOUT" #x29) ("RCDIR" #x2A) ("LFSRA" #x2B)
    216    ("RDIN" #x2C) ("RDOUT" #x2D) ("RDDIR" #x2E)   
    217    ("REIN" #x30) ("REOUT" #x31) ("REDIR" #x32)   
    218    ("RFIN" #x34) ("RFOUT" #x35) ("RFDIR" #x36)
    219                  ("RGOUT" #x39) ("RGDIR" #x3A)
    220    ("RTTMR" #x40) ("RTCFG" #x41) ("T0TMR" #x42) ("T0CFG" #x43)
    221    ("T1CNTH" #x44) ("T1CNTL" #x45) ("T1CAP1H" #x46) ("T1CAP1L" #x47)
    222    ("T1CAP2H" #x48) ("T1CMP2H" #x48) ("T1CAP2L" #x49) ("T1CMP2L" #x49) ; note aliases
    223                                      ("T1CMP1H" #x4A) ("T1CMP1L" #x4B)
    224    ("T1CFG1H" #x4C) ("T1CFG1L" #x4D) ("T1CFG2H" #x4E) ("T1CFG2L" #x4F)
    225    ("ADCH" #x50) ("ADCL" #x51) ("ADCCFG" #x52) ("ADCTMR" #x53)
    226    ("T2CNTH" #x54) ("T2CNTL" #x55) ("T2CAP1H" #x56) ("T2CAP1L" #x57)
    227    ("T2CAP2H" #x58) ("T2CMP2H" #x58) ("T2CAP2L" #x59) ("T2CMP2L" #x59) ; note aliases
    228                                      ("T2CMP1H" #x5A) ("T2CMP1L" #x5B)
    229    ("T2CFG1H" #x5C) ("T2CFG1L" #x5D) ("T2CFG2H" #x5E) ("T2CFG2L" #x5F)
    230    ("S1TMRH" #x60) ("S1TMRL" #x61) ("S1TBUFH" #x62) ("S1TBUFL" #x63)
    231    ("S1TCFG" #x64) ("S1RCNT" #x65) ("S1RBUFH" #x66) ("S1RBUFL" #x67)
    232    ("S1RCFG" #x68) ("S1RSYNC" #x69) ("S1INTF" #x6A) ("S1INTE" #x6B)
    233    ("S1MODE" #x6C) ("S1SMASK" #x6D) ("PSPCFG" #x6E) ("CMPCFG" #x6F)
    234    ("S2TMRH" #x70) ("S2TMRL" #x71) ("S2TBUFH" #x72) ("S2TBUFL" #x73)
    235    ("S2TCFG" #x74) ("S2RCNT" #x75) ("S2RBUFH" #x76) ("S2RBUFL" #x77)
    236    ("S2RCFG" #x78) ("S2RSYNC" #x79) ("S2INTF" #x7A) ("S2INTE" #x7B)
    237    ("S2MODE" #x7C) ("S2SMASK" #x7D) ("CALLH" #x7E) ("CALLL" #x7F))
    238   )
    239 
    240 (define-hardware
    241   (name h-spr)
    242   (comment "special-purpose registers")
    243   (type register QI (128))
    244   (get (index) (c-call QI "get_spr" index ))
    245   (set (index newval) (c-call VOID "set_spr" index newval ))
    246 )
    247 
    248 
    249 ;;(define-hardware
    250 ;;  (name h-gpr-global)
    251 ;;  (comment "gpr registers - global")
    252 ;;  (type register QI (128))
    253 ;;)
    254 
    255 ; The general register
    256 
    257 (define-hardware
    258   (name h-registers)
    259   (comment "all addressable registers")
    260   (attrs VIRTUAL)
    261   (type register QI (512))
    262   (get (index) (c-call QI "get_h_registers" index ))
    263   (set (index newval) (c-call VOID "set_h_registers" index newval ))
    264 )
    265 
    266 ; The hardware stack.
    267 ; Use {push,pop}_pc_stack c-calls to operate on this hardware element.
    268 
    269 (define-hardware
    270   (name h-stack)
    271   (comment "hardware stack")
    272   (type register UHI (16))
    273 )
    274 
    275 (dsh h-pabits "page bits" () (register QI))
    276 (dsh h-zbit "zero bit" () (register BI))
    277 (dsh h-cbit "carry bit" () (register BI))
    278 (dsh h-dcbit "digit-carry bit" () (register BI))
    279 (dnh h-pc "program counter" (PC PROFILE) (pc) () () ())
    280 
    281 
    282 ; Operands
    283 
    284 (define-operand (name addr16cjp) (comment "13-bit address") (attrs) 
    285   (type h-uint) (index f-addr16cjp) (handlers (parse "addr16_cjp") (print "dollarhex_cj"))) ; overload lit8 printer
    286 (define-operand (name fr) (comment "register") (attrs) 
    287   (type h-registers) (index f-reg) (handlers (parse "fr") (print "fr")))
    288 (define-operand (name lit8) (comment "8-bit signed literal") (attrs)
    289   (type h-sint) (index f-imm8) (handlers (parse "lit8") (print "dollarhex8")))
    290 (define-operand (name bitno) (comment "bit number") (attrs)
    291   (type h-uint) (index f-bitno) (handlers (parse "bit3")(print "decimal")))
    292 (define-operand (name addr16p) (comment "page number") (attrs)
    293   (type h-uint) (index f-page3) (handlers (parse "addr16_cjp") (print "dollarhex_p")))
    294 (define-operand (name addr16h) (comment "high 8 bits of address") (attrs)
    295   (type h-uint) (index f-imm8) (handlers (parse "addr16") (print "dollarhex_addr16h")))
    296 (define-operand (name addr16l) (comment "low 8 bits of address") (attrs)
    297   (type h-uint) (index f-imm8) (handlers (parse "addr16") (print "dollarhex_addr16l")))
    298 (define-operand (name reti3) (comment "reti flags") (attrs)
    299   (type h-uint) (index f-reti3) (handlers (print "dollarhex")))
    300 (dnop pabits   "page bits"                 () h-pabits f-nil)
    301 (dnop zbit     "zero bit"                  () h-zbit f-nil)
    302 (dnop cbit     "carry bit"                 () h-cbit f-nil)
    303 (dnop dcbit    "digit carry bit"           () h-dcbit f-nil)
    304 ;;(dnop bank     "bank register"             () h-bank-no f-nil)
    305 
    306 (define-pmacro w     (reg h-spr #x0A))
    307 (define-pmacro mulh  (reg h-spr #x0F))
    308 (define-pmacro dph   (reg h-spr #x0C))
    309 (define-pmacro dpl   (reg h-spr #x0D))
    310 (define-pmacro sph   (reg h-spr #x06))
    311 (define-pmacro spl   (reg h-spr #x07))
    312 (define-pmacro iph   (reg h-spr #x04))
    313 (define-pmacro ipl   (reg h-spr #x05))
    314 (define-pmacro addrh (reg h-spr #x10))
    315 (define-pmacro addrl (reg h-spr #x11))
    316 
    317 
    318 
    319 ; Pseudo-RTL for DC flag calculations
    320 ; "DC" = "digit carry", ie carry between nibbles
    321 (define-pmacro (add-dcflag a b c)
    322   (add-cflag (sll QI a 4) (sll QI b 4) c)
    323 )
    324 
    325 (define-pmacro (sub-dcflag a b c)
    326   (sub-cflag (sll QI a 4) (sll QI b 4) c)
    327 )
    328 
    329 ; Check to see if an fr is one of IPL, SPL, DPL, ADDRL, PCL.
    330 (define-pmacro (LregCheck isLreg fr9bit)
    331    (sequence()
    332       (set isLreg #x0) ;; Assume it's not an Lreg
    333       (if (or (or (eq fr9bit #x5) (eq fr9bit #x7))
    334 	      (or (eq fr9bit #x9)
    335 		  (or (eq fr9bit #xd) (eq fr9bit #x11))))
    336           (set isLreg #x1)
    337       )
    338    )
    339 ) 
    340 
    341 
    342 ; Instructions, in order of the "Instruction Set Map" table on
    343 ; pp 19-20 of IP2022 spec V1.09
    344 
    345 (dni jmp "Jump"
    346      ()
    347      "jmp $addr16cjp"
    348      (+ OP3_JMP addr16cjp)
    349      (set pc (or (sll pabits 13) addr16cjp))
    350      ()
    351 )
    352 
    353 ; note that in call, we push pc instead of pc + 1 because the ip2k increments
    354 ; the pc prior to execution of the instruction
    355 (dni call "Call"
    356      ()
    357      "call $addr16cjp"
    358      (+ OP3_CALL addr16cjp)
    359      (sequence ()
    360 	       (c-call "push_pc_stack" pc)
    361 	       (set pc (or (sll pabits 13) addr16cjp)))
    362      ()
    363 )
    364 
    365 (dni sb "Skip if bit set"
    366      ()
    367      "sb $fr,$bitno"
    368      (+ OP4_SB bitno fr)
    369      (if (and fr (sll 1 bitno))
    370 	 (skip 1))
    371      ()
    372 )
    373 
    374 (dni snb "Skip if bit clear"
    375      ()
    376      "snb $fr,$bitno"
    377      (+ OP4_SNB bitno fr)
    378      (if (not (and fr (sll 1 bitno)))
    379 	 (skip 1))
    380      ()
    381 )
    382 
    383 (dni setb "Set bit"
    384      ()
    385      "setb $fr,$bitno"
    386      (+ OP4_SETB bitno fr)
    387      (set fr (or fr (sll 1 bitno)))
    388      ()
    389 )
    390 
    391 (dni clrb "Clear bit"
    392      ()
    393      "clrb $fr,$bitno"
    394      (+ OP4_CLRB bitno fr)
    395      (set fr (and fr (inv (sll 1 bitno))))
    396      ()
    397 )
    398 
    399 (dni xorw_l "XOR W,literal"
    400      ()
    401      "xor W,#$lit8"
    402      (+ OP4_LITERAL OP4MID_XOR_L lit8)
    403      (sequence ()
    404 	       (set w (xor w lit8))
    405 	       (set zbit (zflag w)))
    406      ()
    407 )
    408 
    409 (dni andw_l "AND W,literal"
    410      ()
    411      "and W,#$lit8"
    412      (+ OP4_LITERAL OP4MID_AND_L lit8)
    413      (sequence ()
    414 	       (set w (and w lit8))
    415 	       (set zbit (zflag w)))
    416      ()
    417 )
    418 
    419 (dni orw_l "OR W,literal"
    420      ()
    421      "or W,#$lit8"
    422      (+ OP4_LITERAL OP4MID_OR_L lit8)
    423      (sequence ()
    424 	       (set w (or w lit8))
    425 	       (set zbit (zflag w)))
    426      ()
    427 )
    428 
    429 (dni addw_l "ADD W,literal"
    430      ()
    431      "add W,#$lit8"
    432      (+ OP4_LITERAL OP4MID_ADD_L lit8)
    433      (sequence ()
    434 	       (set cbit (add-cflag w lit8 0))
    435 	       (set dcbit (add-dcflag w lit8 0))
    436 	       (set w (add w lit8))
    437 	       (set zbit (zflag w)))
    438      ()
    439 )
    440 
    441 (dni subw_l "SUB W,literal"
    442      ()
    443      "sub W,#$lit8"
    444      (+ OP4_LITERAL OP4MID_SUB_L lit8)
    445      (sequence ()
    446 	       (set cbit (not (sub-cflag lit8 w 0)))
    447 	       (set dcbit (not (sub-dcflag lit8 w 0)))
    448 	       (set zbit (zflag (sub w lit8)))
    449 	       (set w (sub lit8 w)))
    450      ()
    451 )
    452 
    453 (dni cmpw_l "CMP W,literal"
    454      ()
    455      "cmp W,#$lit8"
    456      (+ OP4_LITERAL OP4MID_CMP_L lit8)
    457      (sequence ()
    458 	       (set cbit (not (sub-cflag lit8 w 0)))
    459 	       (set dcbit (not (sub-dcflag lit8 w 0)))
    460 	       (set zbit (zflag (sub w lit8))))
    461      ()
    462 )
    463 
    464 (dni retw_l "RETW literal"
    465      ()
    466      "retw #$lit8"
    467      (+ OP4_LITERAL OP4MID_RETW_L lit8)
    468      (sequence ((USI new_pc))
    469 	       (set w lit8)
    470 	       (set new_pc (c-call UHI "pop_pc_stack"))
    471 	       (set pabits (srl new_pc 13))
    472 	       (set pc new_pc))
    473      ()
    474 )
    475 
    476 (dni csew_l "CSE W,literal"
    477      ()
    478      "cse W,#$lit8"
    479      (+ OP4_LITERAL OP4MID_CSE_L lit8)
    480      (if (eq w lit8)
    481 	 (skip 1))
    482      ()
    483 )
    484 
    485 (dni csnew_l "CSNE W,literal"
    486      ()
    487      "csne W,#$lit8"
    488      (+ OP4_LITERAL OP4MID_CSNE_L lit8)
    489      (if (not (eq w lit8))
    490 	 (skip 1))
    491      ()
    492 )
    493 
    494 (dni push_l "Push #lit8"
    495      ()
    496      "push #$lit8"
    497      (+ OP4_LITERAL OP4MID_PUSH_L lit8)
    498      (sequence ()
    499         (c-call "push" lit8)
    500         (c-call VOID "adjuststackptr" (const -1))
    501 
    502      )
    503      ()
    504 )
    505 
    506 (dni mulsw_l "Multiply W,literal (signed)"
    507      ()
    508      "muls W,#$lit8"
    509      (+ OP4_LITERAL OP4MID_MULS_L lit8)
    510      (sequence ((SI tmp))
    511 	       (set tmp (mul (ext SI w) (ext SI (and UQI #xff lit8))))
    512 	       (set w (and tmp #xFF))
    513 	       (set mulh (srl tmp 8)))
    514      ()
    515 )
    516 
    517 (dni muluw_l "Multiply W,literal (unsigned)"
    518      ()
    519      "mulu W,#$lit8"
    520      (+ OP4_LITERAL OP4MID_MULU_L lit8)
    521      (sequence ((USI tmp))
    522 	       (set tmp (and #xFFFF (mul (zext USI w) (zext USI lit8))))
    523 	       (set w (and tmp #xFF))
    524 	       (set mulh (srl tmp 8)))
    525      ()
    526 )
    527 
    528 (dni loadl_l "LoadL literal"
    529     (EXT-SKIP-INSN)
    530     "loadl #$lit8"
    531     (+ OP4_LITERAL OP4MID_LOADL_L lit8)
    532     (set dpl (and lit8 #x00FF))
    533     ()
    534 )
    535 
    536 (dni loadh_l "LoadH literal"
    537     (EXT-SKIP-INSN)
    538     "loadh #$lit8"
    539     (+ OP4_LITERAL OP4MID_LOADH_L lit8)
    540     (set dph (and lit8 #x00FF))
    541     ()
    542 )
    543 
    544 (dni loadl_a "LoadL addr16l"
    545     (EXT-SKIP-INSN)
    546     "loadl $addr16l"
    547     (+ OP4_LITERAL OP4MID_LOADL_L addr16l)
    548     (set dpl (and addr16l #x00FF))
    549     ()
    550 )
    551 
    552 (dni loadh_a "LoadH addr16h"
    553     (EXT-SKIP-INSN)
    554     "loadh $addr16h"
    555     (+ OP4_LITERAL OP4MID_LOADH_L addr16h)
    556     (set dph (and addr16l #x0FF00))
    557     ()
    558 )
    559 
    560 ;; THIS NO LONGER EXISTS -> Now LOADL
    561 ;;(dni bank_l "Bank literal"
    562 ;;     ()
    563 ;;     "bank #$lit8"
    564 ;;     (+ OP4_LITERAL OP4MID_BANK_L lit8)
    565 ;;     (set bank lit8)
    566 ;;     ()
    567 ;;)
    568 
    569 (dni addcfr_w "Add w/carry fr,W"
    570      ()
    571      "addc $fr,W"
    572      (+ OP6_ADDC DIR_NOTTO_W fr)
    573      (sequence ((QI result) (BI newcbit) (QI isLreg) (HI 16bval))
    574 	       (set newcbit (add-cflag w fr cbit))
    575 	       (set dcbit (add-dcflag w fr cbit))
    576                ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    577                ;; We can take advantage of the fact that by a lucky
    578                ;; coincidence, the address of register xxxH is always      
    579                ;; one lower than the address of register xxxL.
    580                (LregCheck isLreg (ifield f-reg))
    581 	       (if (eq isLreg #x1)
    582                   (sequence() 
    583                      (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    584 		     (set 16bval (sll 16bval 8))
    585 		     (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF))) 
    586                      (set 16bval (addc HI 16bval w cbit))
    587 		     (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    588 		     (set (reg h-spr (sub (ifield f-reg) 1)) 
    589                           (and (srl 16bval 8) #xFF))
    590                      (set result (reg h-spr (ifield f-reg)))
    591                   )      
    592 	       (set result (addc w fr cbit)) ;; else part
    593                )
    594 
    595 	       (set zbit (zflag result))
    596 	       (set cbit newcbit)
    597 	       (set fr result))
    598      ()
    599 )
    600 
    601 (dni addcw_fr "Add w/carry W,fr"
    602      ()
    603      "addc W,$fr"
    604      (+ OP6_ADDC DIR_TO_W fr)
    605      (sequence ((QI result) (BI newcbit))
    606 	       (set newcbit (add-cflag w fr cbit))
    607 	       (set dcbit (add-dcflag w fr cbit))
    608 	       (set result (addc w fr cbit))
    609 	       (set zbit (zflag result))
    610 	       (set cbit newcbit)
    611 	       (set w result))
    612      ()
    613 )
    614 
    615 
    616 (dni incsnz_fr "Skip if fr++ not zero"
    617      ()
    618      "incsnz $fr"
    619      (+ OP6_INCSNZ DIR_NOTTO_W fr)
    620      (sequence ((QI isLreg) (HI 16bval))
    621         (LregCheck isLreg (ifield f-reg))
    622         ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    623         ;; We can take advantage of the fact that by a lucky
    624         ;; coincidence, the address of register xxxH is always
    625         ;; one lower than the address of register xxxL.
    626         (if (eq isLreg #x1)
    627            (sequence()
    628               ; Create the 16 bit value
    629               (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    630               (set 16bval (sll 16bval 8))
    631               (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
    632               ; Do 16 bit arithmetic.
    633 	      (set 16bval (add HI 16bval 1))
    634               ; Separate the 16 bit values into the H and L regs
    635               (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    636               (set (reg h-spr (sub (ifield f-reg) 1))
    637                    (and (srl 16bval 8) #xFF))
    638               (set fr (reg h-spr (ifield f-reg)))
    639            )
    640 	   (set fr (add fr 1)) ; Do 8 bit arithmetic.
    641         )
    642 	(if (not (zflag fr))
    643 	   (skip 1)))
    644      ()
    645 )
    646 
    647 (dni incsnzw_fr "Skip if W=fr+1  not zero"
    648      ()
    649      "incsnz W,$fr"
    650      (+ OP6_INCSNZ DIR_TO_W fr)
    651      (sequence ()
    652 	       (set w (add fr 1))
    653 	       (if (not (zflag w))
    654 		   (skip 1)))
    655      ()
    656 )
    657 
    658 (dni mulsw_fr "Multiply W,fr (signed)"
    659      ()
    660      "muls W,$fr"
    661      (+ OP6_MULS DIR_TO_W fr)
    662      (sequence ((SI tmp))
    663 	       (set tmp (mul (ext SI w) (ext SI fr)))
    664 	       (set w (and tmp #xFF))
    665 	       (set mulh (srl tmp 8)))
    666      ()
    667 )
    668 
    669 (dni muluw_fr "Multiply W,fr (unsigned)"
    670      ()
    671      "mulu W,$fr"
    672      (+ OP6_MULU DIR_TO_W fr)
    673      (sequence ((USI tmp))
    674 	       (set tmp (and #xFFFF (mul (zext USI w) (zext USI fr))))
    675 	       (set w (and tmp #xFF))
    676 	       (set mulh (srl tmp 8)))
    677      ()
    678 )
    679 
    680 (dni decsnz_fr "Skip if fr-- not zero"
    681      ()
    682      "decsnz $fr"
    683      (+ OP6_DECSNZ DIR_NOTTO_W fr)
    684      (sequence ((QI isLreg) (HI 16bval))
    685          (LregCheck isLreg (ifield f-reg))
    686          ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    687          ;; We can take advantage of the fact that by a lucky
    688          ;; coincidence, the address of register xxxH is always
    689          ;; one lower than the address of register xxxL.
    690          (if (eq isLreg #x1)
    691             (sequence()
    692                ; Create the 16 bit value
    693                (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    694                (set 16bval (sll 16bval 8))
    695                (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
    696                ; New 16 bit instruction
    697                (set 16bval (sub HI 16bval 1))
    698                ; Separate the 16 bit values into the H and L regs
    699                (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    700                (set (reg h-spr (sub (ifield f-reg) 1))
    701                     (and (srl 16bval 8) #xFF))
    702                (set fr (reg h-spr (ifield f-reg)))
    703             )
    704             ; Original instruction
    705 	    (set fr (sub fr 1))
    706          )
    707 	    (if (not (zflag fr))
    708 	       (skip 1)))
    709      ()
    710 )
    711 
    712 (dni decsnzw_fr "Skip if W=fr-1 not zero"
    713      ()
    714      "decsnz W,$fr"
    715      (+ OP6_DECSNZ DIR_TO_W fr)
    716      (sequence ()
    717 	       (set w (sub fr 1))
    718 	       (if (not (zflag w))
    719 		   (skip 1)))
    720      ()
    721 )
    722 
    723 (dni subcw_fr "Subract w/carry W,fr"
    724      ()
    725      "subc W,$fr"
    726      (+ OP6_SUBC DIR_TO_W fr)
    727      (sequence ((QI result) (BI newcbit))
    728 	       (set newcbit (not (sub-cflag fr w (not cbit))))
    729 	       (set dcbit (not (sub-dcflag fr w (not cbit))))
    730 	       (set result (subc fr w (not cbit)))
    731 	       (set zbit (zflag result))
    732 	       (set cbit newcbit)
    733 	       (set w result))
    734      ()
    735 )
    736 
    737 (dni subcfr_w "Subtract w/carry fr,W"
    738      ()
    739      "subc $fr,W"
    740      (+ OP6_SUBC DIR_NOTTO_W fr)
    741      (sequence ((QI result) (BI newcbit) (QI isLreg) (HI 16bval))
    742 	       (set newcbit (not (sub-cflag fr w (not cbit))))
    743 	       (set dcbit (not (sub-dcflag fr w (not cbit))))
    744                (LregCheck isLreg (ifield f-reg))
    745                ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    746                ;; We can take advantage of the fact that by a lucky
    747                ;; coincidence, the address of register xxxH is always
    748                ;; one lower than the address of register xxxL.
    749                (if (eq isLreg #x1)
    750                   (sequence()
    751                      ; Create the 16 bit value
    752                      (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    753                      (set 16bval (sll 16bval 8))
    754                      (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
    755                      ; New 16 bit instruction
    756 	             (set 16bval (subc HI 16bval w (not cbit)))
    757                      ; Separate the 16 bit values into the H and L regs
    758                      (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    759                      (set (reg h-spr (sub (ifield f-reg) 1))
    760                           (and (srl 16bval 8) #xFF))
    761                      (set result (reg h-spr (ifield f-reg)))
    762                   )
    763                ; Original instruction
    764 	       (set result (subc fr w (not cbit)))
    765                )
    766 
    767 
    768 	       (set zbit (zflag result))
    769 	       (set cbit newcbit)
    770 	       (set fr result))
    771      ()
    772 )
    773 
    774 
    775 (dni pop_fr "Pop fr"
    776      ()
    777      "pop $fr"
    778      (+ OP6_POP (f-dir 1) fr)
    779      (sequence()
    780         (set fr (c-call QI "pop")) 
    781         (c-call VOID "adjuststackptr" (const 1))
    782      )
    783      ()
    784 )
    785 
    786 (dni push_fr "Push fr"
    787      ()
    788      "push $fr"
    789      (+ OP6_POP (f-dir 0) fr)
    790      (sequence()
    791         (c-call "push" fr)
    792         (c-call VOID "adjuststackptr" (const -1))
    793      )
    794      ()
    795 )
    796 
    797 (dni csew_fr "Skip if equal W,fr"
    798      ()
    799      "cse W,$fr"
    800      (+ OP6_CSE (f-dir 1) fr)
    801      (if (eq w fr)
    802 	 (skip 1))
    803      ()
    804 )
    805 
    806 (dni csnew_fr "Skip if not-equal W,fr"
    807      ()
    808      "csne W,$fr"
    809      (+ OP6_CSE (f-dir 0) fr)
    810      (if (not (eq w fr))
    811 	 (skip 1))
    812      ()
    813 )
    814 
    815 ;;(dni csaw_fr "Skip if W above fr"
    816 ;;     ((MACH ip2022ext))
    817 ;;     "csa W,$fr"
    818 ;;     (+ OP6_CSAB (f-dir 1) fr)
    819 ;;     (if (gt w fr)
    820 ;;	 (skip 1))
    821 ;;    ()
    822 ;;)
    823 
    824 ;;(dni csbw_fr "Skip if W below fr"
    825 ;;     ((MACH ip2022ext))
    826 ;;     "csb W,$fr"
    827 ;;     (+ OP6_CSAB (f-dir 0) fr)
    828 ;;     (if (lt w fr)
    829 ;;	 (skip 1))
    830 ;;    ()
    831 ;;)
    832 
    833 (dni incsz_fr "Skip if fr++ zero"
    834      ()
    835      "incsz $fr"
    836      (+ OP6_INCSZ DIR_NOTTO_W fr)
    837      (sequence ((QI isLreg) (HI 16bval))
    838           (LregCheck isLreg (ifield f-reg))
    839           ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    840           ;; We can take advantage of the fact that by a lucky
    841           ;; coincidence, the address of register xxxH is always
    842           ;; one lower than the address of register xxxL.
    843           (if (eq isLreg #x1)
    844              (sequence()
    845                 ; Create the 16 bit value
    846                 (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    847                 (set 16bval (sll 16bval 8))
    848                 (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
    849                 ; New 16 bit instruction
    850                 (set 16bval (add HI 16bval 1))
    851                 ; Separate the 16 bit values into the H and L regs
    852                 (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    853                 (set (reg h-spr (sub (ifield f-reg) 1))
    854                      (and (srl 16bval 8) #xFF))
    855                 (set fr (reg h-spr (ifield f-reg)))
    856              )
    857              ; Original instruction
    858 	     (set fr (add fr 1))
    859           )
    860 	       (if (zflag fr)
    861 		   (skip 1)))
    862      ()
    863 )
    864 
    865 (dni incszw_fr "Skip if W=fr+1 zero"
    866      ()
    867      "incsz W,$fr"
    868      (+ OP6_INCSZ DIR_TO_W fr)
    869      (sequence ()
    870 	       (set w (add fr 1))
    871 	       (if (zflag w)
    872 		   (skip 1)))
    873      ()
    874 )
    875 
    876 (dni swap_fr "Swap fr nibbles"
    877      ()
    878      "swap $fr"
    879      (+ OP6_SWAP DIR_NOTTO_W fr)
    880      (set fr (or (and (sll fr 4) #xf0)
    881 		 (and (srl fr 4) #x0f)))
    882      ()
    883 )
    884 
    885 (dni swapw_fr "Swap fr nibbles into W"
    886      ()
    887      "swap W,$fr"
    888      (+ OP6_SWAP DIR_TO_W fr)
    889      (set w (or (and (sll fr 4) #xf0)
    890 		(and (srl fr 4) #x0f)))
    891      ()
    892 )
    893 
    894 (dni rl_fr "Rotate fr left with carry"
    895      ()
    896      "rl $fr"
    897      (+ OP6_RL DIR_NOTTO_W fr)
    898      (sequence ((QI newfr) (BI newc))
    899 	       (set newc (and fr #x80))
    900 	       (set newfr (or (sll fr 1) (if QI cbit 1 0)))
    901 	       (set cbit (if QI newc 1 0))
    902 	       (set fr newfr))
    903      ()
    904 )
    905 
    906 (dni rlw_fr "Rotate fr left with carry into W"
    907      ()
    908      "rl W,$fr"
    909      (+ OP6_RL DIR_TO_W fr)
    910      (sequence ((QI newfr) (BI newc))
    911 	       (set newc (and fr #x80))
    912 	       (set newfr (or (sll fr 1) (if QI cbit 1 0)))
    913 	       (set cbit (if QI newc 1 0))
    914 	       (set w newfr))
    915      ()
    916 )
    917 
    918 (dni rr_fr "Rotate fr right with carry"
    919      ()
    920      "rr $fr"
    921      (+ OP6_RR DIR_NOTTO_W fr)
    922      (sequence ((QI newfr) (BI newc))
    923 	       (set newc (and fr #x01))
    924 	       (set newfr (or (srl fr 1) (if QI cbit #x80 #x00)))
    925 	       (set cbit (if QI newc 1 0))
    926 	       (set fr newfr))
    927      ()
    928 )
    929 
    930 (dni rrw_fr "Rotate fr right with carry into W"
    931      ()
    932      "rr W,$fr"
    933      (+ OP6_RR DIR_TO_W fr)
    934      (sequence ((QI newfr) (BI newc))
    935 	       (set newc (and fr #x01))
    936 	       (set newfr (or (srl fr 1) (if QI cbit #x80 #x00)))
    937 	       (set cbit (if QI newc 1 0))
    938 	       (set w newfr))
    939      ()
    940 )
    941 
    942 (dni decsz_fr "Skip if fr-- zero"
    943      ()
    944      "decsz $fr"
    945      (+ OP6_DECSZ DIR_NOTTO_W fr)
    946      (sequence ((QI isLreg) (HI 16bval))
    947           (LregCheck isLreg (ifield f-reg))
    948           ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    949           ;; We can take advantage of the fact that by a lucky
    950           ;; coincidence, the address of register xxxH is always
    951           ;; one lower than the address of register xxxL.
    952           (if (eq isLreg #x1)
    953              (sequence()
    954                 ; Create the 16 bit value
    955                 (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    956                 (set 16bval (sll 16bval 8))
    957                 (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
    958                 ; New 16 bit instruction
    959                 (set 16bval (sub HI 16bval 1))
    960                 ; Separate the 16 bit values into the H and L regs
    961                 (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
    962                 (set (reg h-spr (sub (ifield f-reg) 1))
    963                      (and (srl 16bval 8) #xFF))
    964                 (set fr (reg h-spr (ifield f-reg)))
    965              )
    966              ; Original instruction
    967 	     (set fr (sub fr 1))
    968           )
    969 	       (if (zflag fr)
    970 		   (skip 1)))
    971      ()
    972 )
    973 
    974 (dni decszw_fr "Skip if W=fr-1 zero"
    975      ()
    976      "decsz W,$fr"
    977      (+ OP6_DECSZ DIR_TO_W fr)
    978      (sequence ()
    979 	       (set w (sub fr 1))
    980 	       (if (zflag w)
    981 		   (skip 1)))
    982      ()
    983 )
    984 
    985 (dni inc_fr "Increment fr"
    986      ()
    987      "inc $fr"
    988      (+ OP6_INC DIR_NOTTO_W fr)
    989      (sequence ((QI isLreg) (HI 16bval))
    990           (LregCheck isLreg (ifield f-reg))
    991           ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
    992           ;; We can take advantage of the fact that by a lucky
    993           ;; coincidence, the address of register xxxH is always
    994           ;; one lower than the address of register xxxL.
    995           (if (eq isLreg #x1)
    996              (sequence()
    997                 ; Create the 16 bit value
    998                 (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
    999                 (set 16bval (sll 16bval 8))
   1000                 (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
   1001                 ; New 16 bit instruction
   1002 		(set 16bval (add HI 16bval 1))
   1003                 ; Separate the 16 bit values into the H and L regs
   1004                 (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
   1005                 (set (reg h-spr (sub (ifield f-reg) 1))
   1006                      (and (srl 16bval 8) #xFF))
   1007                 (set fr (reg h-spr (ifield f-reg)))
   1008              )
   1009              ; Original instruction
   1010 	     (set fr (add fr 1))
   1011            )
   1012 	       (set zbit (zflag fr)))
   1013      ()
   1014 )
   1015 
   1016 (dni incw_fr "Increment fr into w"
   1017      ()
   1018      "inc W,$fr"
   1019      (+ OP6_INC DIR_TO_W fr)
   1020      (sequence ()
   1021 	       (set w (add fr 1))
   1022 	       (set zbit (zflag w)))
   1023      ()
   1024 )
   1025 
   1026 (dni not_fr "Invert fr"
   1027      ()
   1028      "not $fr"
   1029      (+ OP6_NOT DIR_NOTTO_W fr)
   1030      (sequence ()
   1031 	       (set fr (inv fr))
   1032 	       (set zbit (zflag fr)))
   1033      ()
   1034 )
   1035 
   1036 (dni notw_fr "Invert fr into w"
   1037      ()
   1038      "not W,$fr"
   1039      (+ OP6_NOT DIR_TO_W fr)
   1040      (sequence ()
   1041 	       (set w (inv fr))
   1042 	       (set zbit (zflag w)))
   1043      ()
   1044 )
   1045 
   1046 (dni test_fr "Test fr"
   1047      ()
   1048      "test $fr"
   1049      (+ OP6_TEST DIR_NOTTO_W fr)
   1050      (sequence ()
   1051 	       (set zbit (zflag fr)))
   1052      ()
   1053 )
   1054 
   1055 (dni movw_l "MOV W,literal"
   1056      ()
   1057      "mov W,#$lit8"
   1058      (+ OP4_LITERAL OP4MID_MOV_L lit8)
   1059      (set w lit8)
   1060      ()
   1061 )
   1062 
   1063 (dni movfr_w "Move/test w into fr"
   1064      ()
   1065      "mov $fr,W"
   1066      (+ OP6_OTHER1 DIR_NOTTO_W fr)
   1067      (set fr w)
   1068      ()
   1069 )
   1070 
   1071 (dni movw_fr "Move/test fr into w"
   1072      ()
   1073      "mov W,$fr"
   1074      (+ OP6_TEST DIR_TO_W fr)
   1075      (sequence ()
   1076 	       (set w fr)
   1077 	       (set zbit (zflag w)))
   1078      ()
   1079 )
   1080 
   1081 
   1082 (dni addfr_w "Add fr,W"
   1083      ()
   1084      "add $fr,W"
   1085      (+ OP6_ADD DIR_NOTTO_W fr)
   1086      (sequence ((QI result) (QI isLreg) (HI 16bval))
   1087 	       (set cbit (add-cflag w fr 0))
   1088 	       (set dcbit (add-dcflag w fr 0))
   1089                (LregCheck isLreg (ifield f-reg))
   1090 
   1091                ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
   1092                ;; We can take advantage of the fact that by a lucky
   1093                ;; coincidence, the address of register xxxH is always 
   1094                ;; one lower than the address of register xxxL.
   1095                (if (eq isLreg #x1)
   1096                   (sequence()
   1097                      (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
   1098                      (set 16bval (sll 16bval 8))
   1099                      (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
   1100                      (set 16bval (add HI (and w #xFF) 16bval))
   1101                      (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
   1102                      (set (reg h-spr (sub (ifield f-reg) 1))
   1103                           (and (srl 16bval 8) #xFF))
   1104                      (set result (reg h-spr (ifield f-reg)))
   1105                   )
   1106 	       (set result (addc w fr 0)) ;; else part
   1107                )
   1108 	       (set zbit (zflag result))
   1109 	       (set fr result))
   1110      ()
   1111 )
   1112 
   1113 (dni addw_fr "Add W,fr"
   1114      ()
   1115      "add W,$fr"
   1116      (+ OP6_ADD DIR_TO_W fr)
   1117      (sequence ((QI result))
   1118 	       (set cbit (add-cflag w fr 0))
   1119 	       (set dcbit (add-dcflag w fr 0))
   1120 	       (set result (addc w fr 0))
   1121 	       (set zbit (zflag result))
   1122 	       (set w result))
   1123      ()
   1124 )
   1125 
   1126 (dni xorfr_w "XOR fr,W"
   1127      ()
   1128      "xor $fr,W"
   1129      (+ OP6_XOR DIR_NOTTO_W fr)
   1130      (sequence ()
   1131 	       (set fr (xor w fr))
   1132 	       (set zbit (zflag fr)))
   1133      ()
   1134 )
   1135 
   1136 (dni xorw_fr "XOR W,fr"
   1137      ()
   1138      "xor W,$fr"
   1139      (+ OP6_XOR DIR_TO_W fr)
   1140      (sequence ()
   1141 	       (set w (xor fr w))
   1142 	       (set zbit (zflag w)))
   1143      ()
   1144 )
   1145 
   1146 (dni andfr_w "AND fr,W"
   1147      ()
   1148      "and $fr,W"
   1149      (+ OP6_AND DIR_NOTTO_W fr)
   1150      (sequence ()
   1151 	       (set fr (and w fr))
   1152 	       (set zbit (zflag fr)))
   1153      ()
   1154 )
   1155 
   1156 (dni andw_fr "AND W,fr"
   1157      ()
   1158      "and W,$fr"
   1159      (+ OP6_AND DIR_TO_W fr)
   1160      (sequence ()
   1161 	       (set w (and fr w))
   1162 	       (set zbit (zflag w)))
   1163      ()
   1164 )
   1165 
   1166 (dni orfr_w "OR fr,W"
   1167      ()
   1168      "or $fr,W"
   1169      (+ OP6_OR DIR_NOTTO_W fr)
   1170      (sequence ()
   1171 	       (set fr (or w fr))
   1172 	       (set zbit (zflag fr)))
   1173      ()
   1174 )
   1175 
   1176 (dni orw_fr "OR W,fr"
   1177      ()
   1178      "or W,$fr"
   1179      (+ OP6_OR DIR_TO_W fr)
   1180      (sequence ()
   1181 	       (set w (or fr w))
   1182 	       (set zbit (zflag w)))
   1183      ()
   1184 )
   1185 
   1186 (dni dec_fr "Decrement fr"
   1187      ()
   1188      "dec $fr"
   1189      (+ OP6_DEC DIR_NOTTO_W fr)
   1190      (sequence ((QI isLreg) (HI 16bval))
   1191           (LregCheck isLreg (ifield f-reg))
   1192           ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
   1193           ;; We can take advantage of the fact that by a lucky
   1194           ;; coincidence, the address of register xxxH is always
   1195           ;; one lower than the address of register xxxL.
   1196           (if (eq isLreg #x1)
   1197              (sequence()
   1198                 ; Create the 16 bit value
   1199                 (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
   1200                 (set 16bval (sll 16bval 8))
   1201                 (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
   1202                 ; New 16 bit instruction
   1203 		(set 16bval (sub HI 16bval 1))
   1204                 ; Separate the 16 bit values into the H and L regs
   1205                 (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
   1206                 (set (reg h-spr (sub (ifield f-reg) 1))
   1207                      (and (srl 16bval 8) #xFF))
   1208                 (set fr (reg h-spr (ifield f-reg)))
   1209              )
   1210              ; Original instruction
   1211 	     (set fr (sub fr 1))
   1212 	  )
   1213 	     (set zbit (zflag fr)))
   1214      ()
   1215 )
   1216 
   1217 (dni decw_fr "Decrement fr into w"
   1218      ()
   1219      "dec W,$fr"
   1220      (+ OP6_DEC DIR_TO_W fr)
   1221      (sequence ()
   1222 	       (set w (sub fr 1))
   1223 	       (set zbit (zflag w)))
   1224      ()
   1225 )
   1226 
   1227 (dni subfr_w "Sub fr,W"
   1228      ()
   1229      "sub $fr,W"
   1230      (+ OP6_SUB DIR_NOTTO_W fr)
   1231      (sequence ((QI result) (QI isLreg) (HI 16bval))
   1232 	       (set cbit (not (sub-cflag fr w 0)))
   1233 	       (set dcbit (not (sub-dcflag fr w 0)))
   1234                (LregCheck isLreg (ifield f-reg))
   1235                ;; If fr is an Lreg, then we have to do 16-bit arithmetic.
   1236                ;; We can take advantage of the fact that by a lucky
   1237                ;; coincidence, the address of register xxxH is always
   1238                ;; one lower than the address of register xxxL.
   1239                (if (eq isLreg #x1)
   1240                   (sequence()
   1241                      ; Create the 16 bit value
   1242                      (set 16bval (reg h-spr (sub (ifield f-reg) 1)))
   1243                      (set 16bval (sll 16bval 8))
   1244                      (set 16bval (or 16bval (and (reg h-spr (ifield f-reg)) #xFF)))
   1245                      ; New 16 bit instruction
   1246                      (set 16bval (sub HI 16bval (and w #xFF)))
   1247                      ; Separate the 16 bit values into the H and L regs
   1248                      (set (reg h-spr (ifield f-reg)) (and 16bval #xFF))
   1249                      (set (reg h-spr (sub (ifield f-reg) 1))
   1250                           (and (srl 16bval 8) #xFF))
   1251                      (set result (reg h-spr (ifield f-reg)))
   1252                   )
   1253                ; Original instruction
   1254 	       (set result (subc fr w 0))
   1255                )
   1256 	       (set zbit (zflag result))
   1257 	       (set fr result))
   1258      ()
   1259 )
   1260 
   1261 (dni subw_fr "Sub W,fr"
   1262      ()
   1263      "sub W,$fr"
   1264      (+ OP6_SUB DIR_TO_W fr)
   1265      (sequence ((QI result))
   1266 	       (set cbit (not (sub-cflag fr w 0)))
   1267 	       (set dcbit (not (sub-dcflag fr w 0)))
   1268 	       (set result (subc fr w 0))
   1269 	       (set zbit (zflag result))
   1270 	       (set w result))
   1271      ()
   1272 )
   1273 
   1274 (dni clr_fr "Clear fr"
   1275      ()
   1276      "clr $fr"
   1277      (+ OP6_OTHER2 (f-dir 1) fr)
   1278      (sequence ()
   1279 	       (set fr 0)
   1280 	       (set zbit (zflag fr)))
   1281      ()
   1282 )
   1283 
   1284 (dni cmpw_fr "CMP W,fr"
   1285      ()
   1286      "cmp W,$fr"
   1287      (+ OP6_OTHER2 (f-dir 0) fr)
   1288      (sequence ()
   1289 	       (set cbit (not (sub-cflag fr w 0)))
   1290 	       (set dcbit (not (sub-dcflag fr w 0)))
   1291 	       (set zbit (zflag (sub w fr))))
   1292      ()
   1293 )
   1294 
   1295 (dni speed "Set speed"
   1296      ()
   1297      "speed #$lit8"
   1298      (+ (f-op8 1) lit8)
   1299      (set (reg h-registers #x0E) lit8)
   1300      ()
   1301 )
   1302 
   1303 (dni ireadi "Insn memory read with increment"
   1304      ()
   1305      "ireadi"
   1306      (+ OP6_OTHER1 (f-op6-10low #x1D))
   1307      (c-call "do_insn_read")
   1308      ()
   1309 )
   1310 
   1311 (dni iwritei "Insn memory write with increment"
   1312      ()
   1313      "iwritei"
   1314      (+ OP6_OTHER1 (f-op6-10low #x1C))
   1315      (c-call "do_insn_write")
   1316      ()
   1317 )
   1318 
   1319 (dni fread "Flash read"
   1320      ()
   1321      "fread"
   1322      (+ OP6_OTHER1 (f-op6-10low #x1B))
   1323      (c-call "do_flash_read")
   1324      ()
   1325 )
   1326 
   1327 (dni fwrite "Flash write"
   1328      ()
   1329      "fwrite"
   1330      (+ OP6_OTHER1 (f-op6-10low #x1A))
   1331      (c-call "do_flash_write")
   1332      ()
   1333 )
   1334 
   1335 (dni iread "Insn memory read"
   1336      ()
   1337      "iread"
   1338      (+ OP6_OTHER1 (f-op6-10low #x19))
   1339      (c-call "do_insn_read")
   1340      ()
   1341 )
   1342 
   1343 (dni iwrite "Insn memory write"
   1344      ()
   1345      "iwrite"
   1346      (+ OP6_OTHER1 (f-op6-10low #x18))
   1347      (c-call "do_insn_write")
   1348      ()
   1349 )
   1350 
   1351 (dni page "Set insn page"
   1352      (EXT-SKIP-INSN)
   1353      ;"page $page3"
   1354      "page $addr16p"
   1355      ;(+ OP6_OTHER1 (f-op6-7low #x2) page3)
   1356      ;(set pabits (srl page3 13))
   1357      (+ OP6_OTHER1 (f-op6-7low #x2) addr16p)
   1358      (set pabits addr16p)
   1359      ()
   1360 )
   1361 
   1362 (dni system "System call"
   1363      ()
   1364      "system"
   1365      (+ OP6_OTHER1 (f-op6-10low #xff))
   1366      (c-call "do_system")
   1367      ()
   1368 )
   1369 
   1370 (dni reti "Return from interrupt"
   1371      ()
   1372      "reti #$reti3"
   1373      (+ OP6_OTHER1 (f-op6-7low #x1) reti3)
   1374      (c-call "do_reti" reti3)
   1375      ()
   1376 )
   1377 
   1378 (dni ret "Return"
   1379      ()
   1380      "ret"
   1381      (+ OP6_OTHER1 (f-op6-10low #x07))
   1382      (sequence ((USI new_pc))
   1383 	       (set new_pc (c-call UHI "pop_pc_stack"))
   1384 	       (set pabits (srl new_pc 13))
   1385 	       (set pc new_pc))
   1386      ()
   1387 )
   1388 
   1389 (dni int "Software interrupt"
   1390      ()
   1391      "int"
   1392      (+ OP6_OTHER1 (f-op6-10low #x6))
   1393      (nop)
   1394      ()
   1395 )
   1396 
   1397 (dni breakx "Breakpoint with extended skip"
   1398      (EXT-SKIP-INSN)
   1399      "breakx"
   1400      (+ OP6_OTHER1 (f-op6-10low #x5))
   1401      (c-call "do_break" pc)
   1402      ()
   1403 )
   1404 
   1405 (dni cwdt "Clear watchdog timer"
   1406      ()
   1407      "cwdt"
   1408      (+ OP6_OTHER1 (f-op6-10low #x4))
   1409      (c-call "do_clear_wdt")
   1410      ()
   1411 )
   1412 
   1413 (dni ferase "Flash erase"
   1414      ()
   1415      "ferase"
   1416      (+ OP6_OTHER1 (f-op6-10low #x3))
   1417      (c-call "do_flash_erase")
   1418      ()
   1419 )
   1420 
   1421 (dni retnp "Return, no page"
   1422      ()
   1423      "retnp"
   1424      (+ OP6_OTHER1 (f-op6-10low #x2))
   1425      (sequence ((USI new_pc))
   1426 	       (set new_pc (c-call UHI "pop_pc_stack"))
   1427 	       (set pc new_pc))
   1428      ()
   1429 )
   1430 
   1431 (dni break "Breakpoint"
   1432      ()
   1433      "break"
   1434      (+ OP6_OTHER1 (f-op6-10low #x1))
   1435      (c-call "do_break" pc)
   1436      ()
   1437 )
   1438 
   1439 (dni nop "No operation"
   1440      ()
   1441      "nop"
   1442      (+ OP6_OTHER1 (f-op6-10low #x0))
   1443      (nop)
   1444      ()
   1445 )
   1446 			   
   1447 
   1448 ; Macro instructions
   1449 (dnmi sc "Skip on carry"
   1450       ()
   1451       "sc"
   1452       (emit sb (bitno 0) (fr #xB)) ; sb status.0
   1453 )
   1454 
   1455 (dnmi snc "Skip on no carry"
   1456       ()
   1457       "snc"
   1458       (emit snb (bitno 0) (fr #xB)) ; snb status.0
   1459 )
   1460       
   1461 (dnmi sz "Skip on zero"
   1462       ()
   1463       "sz"
   1464       (emit sb (bitno 2) (fr #xB)) ; sb status.2
   1465 )
   1466 
   1467 (dnmi snz "Skip on no zero"
   1468       ()
   1469       "snz"
   1470       (emit snb (bitno 2) (fr #xB)) ; snb status.2
   1471 )
   1472 
   1473 (dnmi skip "Skip always"
   1474       (SKIPA)
   1475       "skip"
   1476       (emit snb (bitno 0) (fr 9)) ; snb pcl.0 | (pcl&1)<<12
   1477 )
   1478 
   1479 (dnmi skipb "Skip always"
   1480       (SKIPA)
   1481       "skip"
   1482       (emit sb (bitno 0) (fr 9)) ; sb pcl.0 | (pcl&1)<<12
   1483 )
   1484 
   1485