This is the mail archive of the binutils@sources.redhat.com mailing list for the binutils project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

GAS test generator and Maverick assembler tests


Hi Guys,

  As part of the contribution of the Cirrus Maverick co-processor
  support for GCC, I am also updating the Maverick assembler test
  files (maverick.[sd] in gas/testsuite/gas/arm) and the file that
  generates them (gas/testsuite/gas/arm/maverick.s).

  Since the generator program needs a support file (test-gen.c) I am
  also contributing it, and an example file (test-example.c) that
  also shows how it can be used.  These should have been contributed
  when maverick.c was first donated, but better late than never.

Cheers
        Nick


gas/ChangeLog
2003-02-21  Nick Clifton  <nickc at redhat dot com>

	* NEWS: Mention availability of test generator program.

gas/testsuite/ChangeLog
2003-02-21  Nick Clifton  <nickc at redhat dot com>

	* gas/all/test-gen.c: New file: Framework for automatically
	generating assembler test files.
        * gas/all/test-examples.c: New file: Example of a file using
	test-gen.c.

        * gas/arm/maverick.c: Rework to produce correct test files and
	fix formatting.
        * gas/arm/maverick.s: Regenerate.
        * gas/arm/maverick.d: Regenerate.
        * gas/arm/arm.exp: Always run Maverick tests.


Index: gas/testsuite/gas/arm/arm.exp
===================================================================
RCS file: /cvs/src/src/gas/testsuite/gas/arm/arm.exp,v
retrieving revision 1.15
diff -c -3 -p -w -r1.15 arm.exp
*** gas/testsuite/gas/arm/arm.exp	22 Aug 2002 16:10:04 -0000	1.15
--- gas/testsuite/gas/arm/arm.exp	21 Feb 2003 18:50:09 -0000
*************** if {[istarget *arm*-*-*] || [istarget "x
*** 62,67 ****
--- 62,69 ----
  
      run_dump_test "adrl"
  
+     run_dump_test "maverick"
+     
      if {[istarget *-*-elf*] || [istarget *-*-linux*]} then {
  	run_dump_test "pic"
      }
*************** if [istarget arm-*-pe] {
*** 77,82 ****
      #run_dump_test "be-fpconst"
  }
  
- if [istarget arm9e-*] {
-     run_dump_test "maverick"
- }
--- 79,81 ----

Index: gas/testsuite/gas/arm/maverick.c
===================================================================
RCS file: /cvs/src/src/gas/testsuite/gas/arm/maverick.c,v
retrieving revision 1.1
diff -c -3 -p -w -r1.1 maverick.c
*** gas/testsuite/gas/arm/maverick.c	8 Oct 2001 18:59:16 -0000	1.1
--- gas/testsuite/gas/arm/maverick.c	21 Feb 2003 18:50:10 -0000
***************
*** 1,33 ****
! /* Copyright (C) 2000 Free Software Foundation
!  * Contributed by Alexandre Oliva <aoliva at cygnus dot com>
!  *
!  * This file 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 2 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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
!  */
  
  /* Generator of tests for Maverick.
!  *
!  * See the following file for usage and documentation.  */
  #include "../all/test-gen.c"
  
  /* These are the ARM registers.  Some of them have canonical names
!  * other than r##, so we'll use both in the asm input, but only the
!  * canonical names in the expected disassembler output.  */
! char *arm_regs[] = {
    /* Canonical names.  */
    "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
!   "r8", "r9", "r10", "r11", "r12", "sp", "lr", "pc",
    /* Alternate names, i.e., those that can be used in the assembler,
     * but that will never be emitted by the disassembler.  */
    "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
--- 1,33 ----
! /* Copyright (C) 2000, 2003 Free Software Foundation
!    Contributed by Alexandre Oliva <aoliva at cygnus dot com>
! 
!    This file 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 2 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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
  
  /* Generator of tests for Maverick.
! 
!    See the following file for usage and documentation.  */
  #include "../all/test-gen.c"
  
  /* These are the ARM registers.  Some of them have canonical names
!    other than r##, so we'll use both in the asm input, but only the
!    canonical names in the expected disassembler output.  */
! char *arm_regs[] =
!   {
      /* Canonical names.  */
      "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
!     "r8", "r9", "sl", "fp", "ip", "sp", "lr", "pc",
      /* Alternate names, i.e., those that can be used in the assembler,
       * but that will never be emitted by the disassembler.  */
      "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
*************** char *arm_regs[] = {
*** 35,42 ****
  };
  
  /* The various types of registers: ARM's registers, Maverick's
!  * f/d/fx/dx registers, Maverick's accumulators and Maverick's status
!  * register.  */
  #define armreg(shift) \
    reg_r (arm_regs, shift, 0xf, mk_get_bits (5u))
  #define mvreg(prefix, shift) \
--- 35,42 ----
    };
  
  /* The various types of registers: ARM's registers, Maverick's
!    f/d/fx/dx registers, Maverick's accumulators and Maverick's
!    status register.  */
  #define armreg(shift) \
    reg_r (arm_regs, shift, 0xf, mk_get_bits (5u))
  #define mvreg(prefix, shift) \
*************** char *arm_regs[] = {
*** 47,62 ****
    literal ("dspsc"), tick_random
  
  /* This outputs the condition flag that may follow each ARM insn.
!  * Since the condition 15 is invalid, we use it to check that the
!  * assembler recognizes the absence of a condition as `al'.  However,
!  * the disassembler won't ever output `al', so, if we emit it in the
!  * assembler, expect the condition to be omitted in the disassembler
!  * output.  */
  int
  arm_cond (func_arg *arg, insn_data *data)
  #define arm_cond { arm_cond }
  {
!   static const char conds[16][3] = {
      "eq", "ne", "cs", "cc",
      "mi", "pl", "vs", "vc",
      "hi", "ls", "ge", "lt",
--- 47,64 ----
    literal ("dspsc"), tick_random
  
  /* This outputs the condition flag that may follow each ARM insn.
!    Since the condition 15 is invalid, we use it to check that the
!    assembler recognizes the absence of a condition as `al'.  However,
!    the disassembler won't ever output `al', so, if we emit it in the
!    assembler, expect the condition to be omitted in the disassembler
!    output.  */
! 
  int
  arm_cond (func_arg * arg, insn_data * data)
  #define arm_cond { arm_cond }
  {
!   static const char conds[16][3] =
!     {
        "eq", "ne", "cs", "cc",
        "mi", "pl", "vs", "vc",
        "hi", "ls", "ge", "lt",
*************** arm_cond (func_arg *arg, insn_data *data
*** 72,105 ****
  }
  
  /* The sign of an offset is actually used to determined whether the
!  * absolute value of the offset should be added or subtracted, so we
!  * must adjust negative values so that they do not overflow: -256 is
!  * not valid, but -0 is distinct from +0. */
  int
  off8s (func_arg *arg, insn_data *data)
  #define off8s { off8s }
  {
!   int val = get_bits (9s);
!   char value[6], *strt = value;
!   *strt++ = '#';
    if (val < 0)
      {
-       *strt++ = '-';
-       ++val;
        val = -val;
        data->bits = val;
      }
    else
!     data->bits = val | (1 << 23);
!   sprintf (strt, "%i", val);
    data->as_in = data->dis_out = strdup (value);
    return 0;
  }
  
  /* This function generates a 7-bit signed constant, emitted as
!  * follows: the 4 least-significant bits are stored in the 4
!  * least-significant bits of the word; the 3 most-significant bits are
!  * stored in bits 7:5, i.e., bit 4 is skipped.  */
  int
  imm7 (func_arg *arg, insn_data *data)
  #define imm7 { imm7 }
--- 74,127 ----
  }
  
  /* The sign of an offset is actually used to determined whether the
!    absolute value of the offset should be added or subtracted, so we
!    must adjust negative values so that they do not overflow: -256 is
!    not valid, but -0 is distinct from +0.  */
  int
  off8s (func_arg * arg, insn_data * data)
  #define off8s { off8s }
  {
!   int val;
!   char value[6];
! 
!   /* Values less that -255 or between -3 and 0 are problematical.
!      The assembler performs translations on the addressing modes
!      for these values, meaning that we cannot just recreate the
!      disassembler string in the LDST macro without knowing what
!      value had been generated in off8s.  */
!   do
!     {
!       val  = get_bits (9s);
!     }
!   while (val < -255 || (val > -4 && val < 1));
!   
    if (val < 0)
      {
        val = - val;
+       val &= ~3;
+       sprintf (value, ", -#%i", val);
+       data->dis_out = strdup (value);
+       sprintf (value, ", #-%i", val);
+       data->as_in = strdup (value);
+       val >>= 2;
        data->bits = val;
      }
    else
!     {
!       val &= ~3;
!       sprintf (value, ", #%i", val);
        data->as_in = data->dis_out = strdup (value);
+       val >>= 2;
+       data->bits = val | (1 << 23);
+     }
+   
    return 0;
  }
  
  /* This function generates a 7-bit signed constant, emitted as
!    follows: the 4 least-significant bits are stored in the 4
!    least-significant bits of the word; the 3 most-significant bits are
!    stored in bits 7:5, i.e., bit 4 is skipped.  */
  int
  imm7 (func_arg *arg, insn_data *data)
  #define imm7 { imm7 }
*************** imm7 (func_arg *arg, insn_data *data)
*** 114,126 ****
  }
  
  /* Convenience wrapper to define_insn, that prefixes every insn with
!  * `cf' (so, if you specify command-line arguments, remember that `cf'
!  * must *not* be part of the string), and post-fixes a condition code.
!  * insname and insnvar specify the main insn name and a variant;
!  * they're just concatenated, and insnvar is often empty.  word is the
!  * bit pattern that defines the insn, properly shifted, and funcs is a
!  * sequence of funcs that define the operands and the syntax of the
!  * insn.  */
  #define mv_insn(insname, insnvar, word, funcs...) \
    define_insn(insname ## insnvar, \
  	      literal ("cf"), \
--- 136,148 ----
  }
  
  /* Convenience wrapper to define_insn, that prefixes every insn with
!    `cf' (so, if you specify command-line arguments, remember that `cf'
!    must *not* be part of the string), and post-fixes a condition code.
!    insname and insnvar specify the main insn name and a variant;
!    they're just concatenated, and insnvar is often empty.  word is the
!    bit pattern that defines the insn, properly shifted, and funcs is a
!    sequence of funcs that define the operands and the syntax of the
!    insn.  */
  #define mv_insn(insname, insnvar, word, funcs...) \
    define_insn (insname ## insnvar, \
  	      literal ("cf"), \
*************** imm7 (func_arg *arg, insn_data *data)
*** 130,165 ****
  	      ## funcs)
  
  /* Define a single LDC/STC variant.  op is the main insn opcode; ld
!  * stands for load (it should be 0 on stores), dword selects 64-bit
!  * operations, pre should be enabled for pre-increment, and wb, for
!  * write-back.  sep1, sep2 and sep3 are syntactical elements ([]!)
!  * that the assembler will use to enable pre and wb.  It would
!  * probably have been cleaner to couple the syntactical elements with
!  * the pre/wb bits directly, but it would have required the definition
!  * of more functions.  */
  #define LDST(insname, insnvar, op, ld, dword, regname, pre, wb, sep1, sep2, sep3) \
    mv_insn (insname, insnvar, \
  	   (12<<24)|(op<<8)|(ld<<20)|(pre<<24)|(dword<<22)|(wb<<21), \
  	    mvreg (regname, 12), comma, \
! 	    lsqbkt, armreg (16), sep1, comma, off8s, sep2, sep3, \
  	    tick_random)
  
  /* Define all variants of an LDR or STR instruction, namely,
!  * pre-indexed without write-back, pre-indexed with write-back and
!  * post-indexed.  */
  #define LDSTall(insname, op, ld, dword, regname) \
    LDST (insname, _p, op, ld, dword, regname, 1, 0, nothing, rsqbkt, nothing); \
    LDST (insname, _pw, op, ld, dword, regname, 1, 1, nothing, rsqbkt, literal("!")); \
!   LDST (insname, ,op, ld, dword, regname, 0, 0, rsqbkt, nothing, nothing)
  
  /* Produce the insn identifiers of all LDST variants of a given insn.
!  * To be used in the initialization of an insn group array.  */
  #define insns_LDSTall(insname) \
    insn (insname ## _p), insn (insname ## _pw), insn (insname)
  
  /* Define a CDP variant that uses two registers, at offsets 12 and 16.
!  * The two opcodes and the co-processor number identify the CDP
!  * insn.  */
  #define CDP2(insname, var, cpnum, opcode1, opcode2, reg1name, reg2name) \
    mv_insn (insname##var, , \
  	   (14<<24)|((opcode1)<<20)|((cpnum)<<8)|((opcode2)<<5), \
--- 152,187 ----
  	      ## funcs)
  
  /* Define a single LDC/STC variant.  op is the main insn opcode; ld
!    stands for load (it should be 0 on stores), dword selects 64-bit
!    operations, pre should be enabled for pre-increment, and wb, for
!    write-back.  sep1, sep2 and sep3 are syntactical elements ([]!)
!    that the assembler will use to enable pre and wb.  It would
!    probably have been cleaner to couple the syntactical elements with
!    the pre/wb bits directly, but it would have required the definition
!    of more functions.  */
  #define LDST(insname, insnvar, op, ld, dword, regname, pre, wb, sep1, sep2, sep3) \
    mv_insn (insname, insnvar, \
  	   (12 << 24) | (op << 8) | (ld << 20) | (pre << 24) | (dword << 22) | (wb << 21), \
  	    mvreg (regname, 12), comma, \
! 	    lsqbkt, armreg (16), sep1, off8s, sep2, sep3, \
  	    tick_random)
  
  /* Define all variants of an LDR or STR instruction, namely,
!    pre-indexed without write-back, pre-indexed with write-back and
!    post-indexed.  */
  #define LDSTall(insname, op, ld, dword, regname) \
    LDST (insname, _p, op, ld, dword, regname, 1, 0, nothing, rsqbkt, nothing); \
    LDST (insname, _pw, op, ld, dword, regname, 1, 1, nothing, rsqbkt, literal ("!")); \
!   LDST (insname, ,op, ld, dword, regname, 0, 1, rsqbkt, nothing, nothing)
  
  /* Produce the insn identifiers of all LDST variants of a given insn.
!    To be used in the initialization of an insn group array.  */
  #define insns_LDSTall(insname) \
    insn (insname ## _p), insn (insname ## _pw), insn (insname)
  
  /* Define a CDP variant that uses two registers, at offsets 12 and 16.
!    The two opcodes and the co-processor number identify the CDP
!    insn.  */
  #define CDP2(insname, var, cpnum, opcode1, opcode2, reg1name, reg2name) \
    mv_insn (insname##var, , \
  	   (14 << 24) | ((opcode1) << 20) | ((cpnum) << 8) | ((opcode2) << 5), \
*************** imm7 (func_arg *arg, insn_data *data)
*** 182,196 ****
    CDP2 (insname, d, 4, opcode1, opcode2, "d", "d")
  
  /* Define a CDP instruction with two register operands and one 7-bit
!  * signed immediate generated with imm7.  */
  #define CDP2_imm7(insname, cpnum, opcode1, reg1name, reg2name) \
    mv_insn (insname, , (14<<24)|((opcode1)<<20)|((cpnum)<<8), \
  	   mvreg (reg1name, 12), comma, mvreg (reg2name, 16), comma, imm7, \
  	   tick_random)
  
  /* Produce the insn identifiers of CDP floating-point or integer insn
!  * pairs (i.e., it appends the suffixes for 32-bit and 64-bit
!  * insns.  */
  #define CDPfp_insns(insname) \
    insn (insname ## s), insn (insname ## d)
  #define CDPx_insns(insname) \
--- 204,218 ----
    CDP2 (insname, d, 4, opcode1, opcode2, "d", "d")
  
  /* Define a CDP instruction with two register operands and one 7-bit
!    signed immediate generated with imm7.  */
  #define CDP2_imm7(insname, cpnum, opcode1, reg1name, reg2name) \
    mv_insn (insname, , (14 << 24) | ((opcode1) << 20) | ((cpnum) << 8), \
  	   mvreg (reg1name, 12), comma, mvreg (reg2name, 16), comma, imm7, \
  	   tick_random)
  
  /* Produce the insn identifiers of CDP floating-point or integer insn
!    pairs (i.e., it appends the suffixes for 32-bit and 64-bit
!    insns.  */
  #define CDPfp_insns(insname) \
    insn (insname ## s), insn (insname ## d)
  #define CDPx_insns(insname) \
*************** imm7 (func_arg *arg, insn_data *data)
*** 260,296 ****
    MCRC2 (mv ## insname, 6, 0, 0, opcode2, mvreg (regDSPname, 0), acreg (16))
  
  /* Define move insns between a float DSP register and an ARM
!  * register.  */
  #define MVf(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 4, opcode2, "f"); \
    MVARMDSP (nameDA, 4, opcode2, "f")
  
  /* Define move insns between a double DSP register and an ARM
!  * register.  */
  #define MVd(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 4, opcode2, "d"); \
    MVARMDSP (nameDA, 4, opcode2, "d")
  
  /* Define move insns between a 32-bit integer DSP register and an ARM
!  * register.  */
  #define MVfx(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 5, opcode2, "fx"); \
    MVARMDSP (nameDA, 5, opcode2, "fx")
  
  /* Define move insns between a 64-bit integer DSP register and an ARM
!  * register.  */
  #define MVdx(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 5, opcode2, "dx"); \
    MVARMDSP (nameDA, 5, opcode2, "dx")
  
  /* Define move insns between a 32-bit DSP register and a DSP
!  * accumulator.  */
  #define MVfxa(nameFA, nameAF, opcode2) \
    MVDSPACC (nameFA, opcode2, "fx"); \
    MVACCDSP (nameAF, opcode2, "fx")
  
  /* Define move insns between a 64-bit DSP register and a DSP
!  * accumulator.  */
  #define MVdxa(nameDA, nameAD, opcode2) \
    MVDSPACC (nameDA, opcode2, "dx"); \
    MVACCDSP (nameAD, opcode2, "dx")
--- 282,318 ----
    MCRC2 (mv ## insname, 6, 0, 0, opcode2, mvreg (regDSPname, 0), acreg (16))
  
  /* Define move insns between a float DSP register and an ARM
!    register.  */
  #define MVf(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 4, opcode2, "f"); \
    MVARMDSP (nameDA, 4, opcode2, "f")
  
  /* Define move insns between a double DSP register and an ARM
!    register.  */
  #define MVd(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 4, opcode2, "d"); \
    MVARMDSP (nameDA, 4, opcode2, "d")
  
  /* Define move insns between a 32-bit integer DSP register and an ARM
!    register.  */
  #define MVfx(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 5, opcode2, "fx"); \
    MVARMDSP (nameDA, 5, opcode2, "fx")
  
  /* Define move insns between a 64-bit integer DSP register and an ARM
!    register.  */
  #define MVdx(nameAD, nameDA, opcode2) \
    MVDSPARM (nameAD, 5, opcode2, "dx"); \
    MVARMDSP (nameDA, 5, opcode2, "dx")
  
  /* Define move insns between a 32-bit DSP register and a DSP
!    accumulator.  */
  #define MVfxa(nameFA, nameAF, opcode2) \
    MVDSPACC (nameFA, opcode2, "fx"); \
    MVACCDSP (nameAF, opcode2, "fx")
  
  /* Define move insns between a 64-bit DSP register and a DSP
!    accumulator.  */
  #define MVdxa(nameDA, nameAD, opcode2) \
    MVDSPACC (nameDA, opcode2, "dx"); \
    MVACCDSP (nameAD, opcode2, "dx")
*************** LDSTall (str32, 5, 0, 0, "fx");
*** 318,324 ****
  LDSTall (str64, 5, 0, 1, "dx");
  
  /* Create the load_store insn group.  */
! func *load_store_insns[] = {
    insns_LDSTall (ldrs),  insns_LDSTall (ldrd),
    insns_LDSTall (ldr32), insns_LDSTall (ldr64),
    insns_LDSTall (strs),  insns_LDSTall (strd),
--- 340,347 ----
  LDSTall (str64, 5, 0, 1, "dx");
  
  /* Create the load_store insn group.  */
! func *load_store_insns[] =
!   {
      insns_LDSTall (ldrs),  insns_LDSTall (ldrd),
      insns_LDSTall (ldr32), insns_LDSTall (ldr64),
      insns_LDSTall (strs),  insns_LDSTall (strd),
*************** CDP2 (cpys, , 4, 0, 0, "f", "f");
*** 343,349 ****
  CDP2 (cpyd, , 4, 0, 1, "d", "d");
  
  /* Create the move insns group.  */
! func *move_insns[] = {
    insns_MV (sr, rs), insns_MV (dlr, rdl), insns_MV (dhr, rdh),
    insns_MV (64lr, r64l), insns_MV (64hr, r64h),
    insns_MV (al32, 32al), insns_MV (am32, 32am), insns_MV (ah32, 32ah),
--- 366,373 ----
  CDP2 (cpyd, , 4, 0, 1, "d", "d");
  
  /* Create the move insns group.  */
! func * move_insns[] =
!   {
      insns_MV (sr, rs), insns_MV (dlr, rdl), insns_MV (dhr, rdh),
      insns_MV (64lr, r64l), insns_MV (64hr, r64h),
      insns_MV (al32, 32al), insns_MV (am32, 32am), insns_MV (ah32, 32ah),
*************** CDP2 (truncs32, , 5, 1, 6, "fx", "f");
*** 365,371 ****
  CDP2 (truncd32, , 5, 1, 7, "fx", "d");
  
  /* Create the conv insns group.  */
! func *conv_insns[] = {
    insn (cvtsd), insn (cvtds), insn (cvt32s), insn (cvt32d),
    insn (cvt64s), insn (cvt64d), insn (cvts32), insn (cvtd32),
    insn (truncs32), insn (truncd32),
--- 389,396 ----
  CDP2 (truncd32, , 5, 1, 7, "fx", "d");
  
  /* Create the conv insns group.  */
! func * conv_insns[] =
!   {
      insn (cvtsd), insn (cvtds), insn (cvt32s), insn (cvt32d),
      insn (cvt64s), insn (cvt64d), insn (cvts32), insn (cvtd32),
      insn (truncs32), insn (truncd32),
*************** CDP2_imm7 (sh32, 5, 0, "fx", "fx");
*** 379,385 ****
  CDP2_imm7 (sh64, 5, 2, "dx", "dx");
  
  /* Create the shift insns group.  */
! func *shift_insns[] = {
    insn (rshl32), insn (rshl64),
    insn (sh32), insn (sh64),
    0
--- 404,411 ----
  CDP2_imm7 (sh64, 5, 2, "dx", "dx");
  
  /* Create the shift insns group.  */
! func *shift_insns[] =
!   {
      insn (rshl32), insn (rshl64),
      insn (sh32), insn (sh64),
      0
*************** MCRC3 (cmp32, 5, 0, 1, 4, armreg (12), m
*** 392,398 ****
  MCRC3 (cmp64, 5, 0, 1, 5, armreg (12), mvreg ("dx", 16), mvreg ("dx", 0));
  
  /* Create the comp insns group.  */
! func *comp_insns[] = {
    insn (cmps), insn (cmpd),
    insn (cmp32), insn (cmp64),
    0
--- 418,425 ----
  MCRC3 (cmp64, 5, 0, 1, 5, armreg (12), mvreg ("dx", 16), mvreg ("dx", 0));
  
  /* Create the comp insns group.  */
! func *comp_insns[] =
!   {
      insn (cmps), insn (cmpd),
      insn (cmp32), insn (cmp64),
      0
*************** CDP3f (mul, 1, 0);
*** 411,417 ****
  CDP3d (mul, 1, 1);
  
  /* Create the fp-arith insns group.  */
! func *fp_arith_insns[] = {
    CDPfp_insns (abs), CDPfp_insns (neg),
    CDPfp_insns (add), CDPfp_insns (sub), CDPfp_insns (mul),
    0
--- 438,445 ----
  CDP3d (mul, 1, 1);
  
  /* Create the fp-arith insns group.  */
! func *fp_arith_insns[] =
!   {
      CDPfp_insns (abs), CDPfp_insns (neg),
      CDPfp_insns (add), CDPfp_insns (sub), CDPfp_insns (mul),
      0
*************** CDP3fx (mac, 1, 2);
*** 432,438 ****
  CDP3fx (msc, 1, 3);
  
  /* Create the int-arith insns group.  */
! func *int_arith_insns[] = {
    CDPx_insns (abs), CDPx_insns (neg),
    CDPx_insns (add), CDPx_insns (sub), CDPx_insns (mul),
    insn (mac32), insn (msc32),
--- 460,467 ----
  CDP3fx (msc, 1, 3);
  
  /* Create the int-arith insns group.  */
! func * int_arith_insns[] =
!   {
      CDPx_insns (abs), CDPx_insns (neg),
      CDPx_insns (add), CDPx_insns (sub), CDPx_insns (mul),
      insn (mac32), insn (msc32),
*************** CDP42A (madda32, 2);
*** 446,460 ****
  CDP42A (msuba32, 3);
  
  /* Create the acc-arith insns group.  */
! func *acc_arith_insns[] = {
    insn (madd32), insn (msub32),
    insn (madda32), insn (msuba32),
    0
  };
  
  /* Create the set of all groups.  */
! group_t
! groups[] = {
    { "load_store", load_store_insns },
    { "move", move_insns },
    { "conv", conv_insns },
--- 475,490 ----
  CDP42A (msuba32, 3);
  
  /* Create the acc-arith insns group.  */
! func * acc_arith_insns[] =
!   {
      insn (madd32), insn (msub32),
      insn (madda32), insn (msuba32),
      0
    };
  
  /* Create the set of all groups.  */
! group_t groups[] =
!   {
      { "load_store", load_store_insns },
      { "move", move_insns },
      { "conv", conv_insns },
*************** main(int argc, char *argv[])
*** 480,491 ****
  	 "\t.align\n",
  	 as_in);
    /* Output comments for the testsuite-driver and the initial
!    * disassembler output. */
    fputs ("#objdump: -dr --prefix-address --show-raw-insn\n"
  	 "#name: Maverick\n"
! 	 "#as: -marm9e\n"
  	 "\n"
! 	 "# Test the instructions of Maverick\n"
  	 "\n"
  	 ".*: +file format.*arm.*\n"
  	 "\n"
--- 510,521 ----
  	 "\t.align\n",
  	 as_in);
    /* Output comments for the testsuite-driver and the initial
!      disassembler output.  */
    fputs ("#objdump: -dr --prefix-address --show-raw-insn\n"
  	 "#name: Maverick\n"
! 	 "#as: -mcpu=ep9312\n"
  	 "\n"
! 	 "# Test the instructions of the Cirrus Maverick floating point co-processor\n"
  	 "\n"
  	 ".*: +file format.*arm.*\n"
  	 "\n"

Index: gas/testsuite/gas/arm/maverick.d
===================================================================
RCS file: /cvs/src/src/gas/testsuite/gas/arm/maverick.d,v
retrieving revision 1.2
diff -c -3 -p -w -r1.2 maverick.d
*** gas/testsuite/gas/arm/maverick.d	18 Jan 2002 17:01:55 -0000	1.2
--- gas/testsuite/gas/arm/maverick.d	21 Feb 2003 18:50:11 -0000
***************
*** 1,477 ****
  #objdump: -dr --prefix-address --show-raw-insn
  #name: Maverick
! #as: -mcpu=arm9+maverick
  
! # Test the instructions of Maverick
  
  .*: +file format.*arm.*
  
  Disassembly of section .text:
  # load_store:
! 00000000 <load_store> 0d ?9d ?54 ?ff ? *	cfldrseq	mvf5, ?\[sp, ?#255\]
! 00000004 <load_store\+0x4> 4d ?9b ?e4 ?49 ? *	cfldrsmi	mvf14, ?\[r11, ?#73\]
! 00000008 <load_store\+0x8> 7d ?1c ?24 ?ef ? *	cfldrsvc	mvf2, ?\[r12, ?#-239\]
! 0000000c <load_store\+0xc> bd ?1a ?04 ?ff ? *	cfldrslt	mvf0, ?\[r10, ?#-255\]
! 00000010 <load_store\+0x10> 3d ?11 ?c4 ?27 ? *	cfldrscc	mvf12, ?\[r1, ?#-39\]
! 00000014 <load_store\+0x14> ed ?bf ?d4 ?68 ? *	cfldrs	mvf13, ?\[pc, ?#104\]!
! 00000018 <load_store\+0x18> 2d ?30 ?94 ?00 ? *	cfldrscs	mvf9, ?\[r0, ?#-0\]!
! 0000001c <load_store\+0x1c> ad ?be ?94 ?48 ? *	cfldrsge	mvf9, ?\[lr, ?#72\]!
! 00000020 <load_store\+0x20> 8d ?b5 ?d4 ?25 ? *	cfldrshi	mvf13, ?\[r5, ?#37\]!
! 00000024 <load_store\+0x24> cd ?b3 ?64 ?00 ? *	cfldrsgt	mvf6, ?\[r3, ?#0\]!
! 00000028 <load_store\+0x28> 5c ?94 ?e4 ?40 ? *	cfldrspl	mvf14, ?\[r4\], ?#64
! 0000002c <load_store\+0x2c> 1c ?12 ?84 ?9d ? *	cfldrsne	mvf8, ?\[r2\], ?#-157
! 00000030 <load_store\+0x30> bc ?99 ?44 ?01 ? *	cfldrslt	mvf4, ?\[r9\], ?#1
! 00000034 <load_store\+0x34> 5c ?17 ?f4 ?3f ? *	cfldrspl	mvf15, ?\[r7\], ?#-63
! 00000038 <load_store\+0x38> ec ?18 ?34 ?88 ? *	cfldrs	mvf3, ?\[r8\], ?#-136
! 0000003c <load_store\+0x3c> 2d ?56 ?14 ?44 ? *	cfldrdcs	mvd1, ?\[r6, ?#-68\]
! 00000040 <load_store\+0x40> 0d ?dd ?74 ?ff ? *	cfldrdeq	mvd7, ?\[sp, ?#255\]
! 00000044 <load_store\+0x44> cd ?db ?a4 ?49 ? *	cfldrdgt	mvd10, ?\[r11, ?#73\]
! 00000048 <load_store\+0x48> dd ?5c ?64 ?ef ? *	cfldrdle	mvd6, ?\[r12, ?#-239\]
! 0000004c <load_store\+0x4c> 9d ?5a ?04 ?ff ? *	cfldrdls	mvd0, ?\[r10, ?#-255\]
! 00000050 <load_store\+0x50> 9d ?71 ?44 ?27 ? *	cfldrdls	mvd4, ?\[r1, ?#-39\]!
! 00000054 <load_store\+0x54> dd ?ff ?74 ?68 ? *	cfldrdle	mvd7, ?\[pc, ?#104\]!
! 00000058 <load_store\+0x58> 6d ?70 ?b4 ?00 ? *	cfldrdvs	mvd11, ?\[r0, ?#-0\]!
! 0000005c <load_store\+0x5c> ed ?fe ?34 ?48 ? *	cfldrd	mvd3, ?\[lr, ?#72\]!
! 00000060 <load_store\+0x60> 8d ?f5 ?f4 ?25 ? *	cfldrdhi	mvd15, ?\[r5, ?#37\]!
! 00000064 <load_store\+0x64> 4c ?d3 ?24 ?00 ? *	cfldrdmi	mvd2, ?\[r3\], ?#0
! 00000068 <load_store\+0x68> ec ?d4 ?a4 ?40 ? *	cfldrd	mvd10, ?\[r4\], ?#64
! 0000006c <load_store\+0x6c> 3c ?52 ?84 ?9d ? *	cfldrdcc	mvd8, ?\[r2\], ?#-157
! 00000070 <load_store\+0x70> 1c ?d9 ?c4 ?01 ? *	cfldrdne	mvd12, ?\[r9\], ?#1
! 00000074 <load_store\+0x74> 7c ?57 ?54 ?3f ? *	cfldrdvc	mvd5, ?\[r7\], ?#-63
! 00000078 <load_store\+0x78> ad ?18 ?15 ?88 ? *	cfldr32ge	mvfx1, ?\[r8, ?#-136\]
! 0000007c <load_store\+0x7c> 6d ?16 ?b5 ?44 ? *	cfldr32vs	mvfx11, ?\[r6, ?#-68\]
! 00000080 <load_store\+0x80> 0d ?9d ?55 ?ff ? *	cfldr32eq	mvfx5, ?\[sp, ?#255\]
! 00000084 <load_store\+0x84> 4d ?9b ?e5 ?49 ? *	cfldr32mi	mvfx14, ?\[r11, ?#73\]
! 00000088 <load_store\+0x88> 7d ?1c ?25 ?ef ? *	cfldr32vc	mvfx2, ?\[r12, ?#-239\]
! 0000008c <load_store\+0x8c> bd ?3a ?05 ?ff ? *	cfldr32lt	mvfx0, ?\[r10, ?#-255\]!
! 00000090 <load_store\+0x90> 3d ?31 ?c5 ?27 ? *	cfldr32cc	mvfx12, ?\[r1, ?#-39\]!
! 00000094 <load_store\+0x94> ed ?bf ?d5 ?68 ? *	cfldr32	mvfx13, ?\[pc, ?#104\]!
! 00000098 <load_store\+0x98> 2d ?30 ?95 ?00 ? *	cfldr32cs	mvfx9, ?\[r0, ?#-0\]!
! 0000009c <load_store\+0x9c> ad ?be ?95 ?48 ? *	cfldr32ge	mvfx9, ?\[lr, ?#72\]!
! 000000a0 <load_store\+0xa0> 8c ?95 ?d5 ?25 ? *	cfldr32hi	mvfx13, ?\[r5\], ?#37
! 000000a4 <load_store\+0xa4> cc ?93 ?65 ?00 ? *	cfldr32gt	mvfx6, ?\[r3\], ?#0
! 000000a8 <load_store\+0xa8> 5c ?94 ?e5 ?40 ? *	cfldr32pl	mvfx14, ?\[r4\], ?#64
! 000000ac <load_store\+0xac> 1c ?12 ?85 ?9d ? *	cfldr32ne	mvfx8, ?\[r2\], ?#-157
! 000000b0 <load_store\+0xb0> bc ?99 ?45 ?01 ? *	cfldr32lt	mvfx4, ?\[r9\], ?#1
! 000000b4 <load_store\+0xb4> 5d ?57 ?f5 ?3f ? *	cfldr64pl	mvdx15, ?\[r7, ?#-63\]
! 000000b8 <load_store\+0xb8> ed ?58 ?35 ?88 ? *	cfldr64	mvdx3, ?\[r8, ?#-136\]
! 000000bc <load_store\+0xbc> 2d ?56 ?15 ?44 ? *	cfldr64cs	mvdx1, ?\[r6, ?#-68\]
! 000000c0 <load_store\+0xc0> 0d ?dd ?75 ?ff ? *	cfldr64eq	mvdx7, ?\[sp, ?#255\]
! 000000c4 <load_store\+0xc4> cd ?db ?a5 ?49 ? *	cfldr64gt	mvdx10, ?\[r11, ?#73\]
! 000000c8 <load_store\+0xc8> dd ?7c ?65 ?ef ? *	cfldr64le	mvdx6, ?\[r12, ?#-239\]!
! 000000cc <load_store\+0xcc> 9d ?7a ?05 ?ff ? *	cfldr64ls	mvdx0, ?\[r10, ?#-255\]!
! 000000d0 <load_store\+0xd0> 9d ?71 ?45 ?27 ? *	cfldr64ls	mvdx4, ?\[r1, ?#-39\]!
! 000000d4 <load_store\+0xd4> dd ?ff ?75 ?68 ? *	cfldr64le	mvdx7, ?\[pc, ?#104\]!
! 000000d8 <load_store\+0xd8> 6d ?70 ?b5 ?00 ? *	cfldr64vs	mvdx11, ?\[r0, ?#-0\]!
! 000000dc <load_store\+0xdc> ec ?de ?35 ?48 ? *	cfldr64	mvdx3, ?\[lr\], ?#72
! 000000e0 <load_store\+0xe0> 8c ?d5 ?f5 ?25 ? *	cfldr64hi	mvdx15, ?\[r5\], ?#37
! 000000e4 <load_store\+0xe4> 4c ?d3 ?25 ?00 ? *	cfldr64mi	mvdx2, ?\[r3\], ?#0
! 000000e8 <load_store\+0xe8> ec ?d4 ?a5 ?40 ? *	cfldr64	mvdx10, ?\[r4\], ?#64
! 000000ec <load_store\+0xec> 3c ?52 ?85 ?9d ? *	cfldr64cc	mvdx8, ?\[r2\], ?#-157
! 000000f0 <load_store\+0xf0> 1d ?89 ?c4 ?01 ? *	cfstrsne	mvf12, ?\[r9, ?#1\]
! 000000f4 <load_store\+0xf4> 7d ?07 ?54 ?3f ? *	cfstrsvc	mvf5, ?\[r7, ?#-63\]
! 000000f8 <load_store\+0xf8> ad ?08 ?14 ?88 ? *	cfstrsge	mvf1, ?\[r8, ?#-136\]
! 000000fc <load_store\+0xfc> 6d ?06 ?b4 ?44 ? *	cfstrsvs	mvf11, ?\[r6, ?#-68\]
! 00000100 <load_store\+0x100> 0d ?8d ?54 ?ff ? *	cfstrseq	mvf5, ?\[sp, ?#255\]
! 00000104 <load_store\+0x104> 4d ?ab ?e4 ?49 ? *	cfstrsmi	mvf14, ?\[r11, ?#73\]!
! 00000108 <load_store\+0x108> 7d ?2c ?24 ?ef ? *	cfstrsvc	mvf2, ?\[r12, ?#-239\]!
! 0000010c <load_store\+0x10c> bd ?2a ?04 ?ff ? *	cfstrslt	mvf0, ?\[r10, ?#-255\]!
! 00000110 <load_store\+0x110> 3d ?21 ?c4 ?27 ? *	cfstrscc	mvf12, ?\[r1, ?#-39\]!
! 00000114 <load_store\+0x114> ed ?af ?d4 ?68 ? *	cfstrs	mvf13, ?\[pc, ?#104\]!
! 00000118 <load_store\+0x118> 2c ?00 ?94 ?00 ? *	cfstrscs	mvf9, ?\[r0\], ?#-0
! 0000011c <load_store\+0x11c> ac ?8e ?94 ?48 ? *	cfstrsge	mvf9, ?\[lr\], ?#72
! 00000120 <load_store\+0x120> 8c ?85 ?d4 ?25 ? *	cfstrshi	mvf13, ?\[r5\], ?#37
! 00000124 <load_store\+0x124> cc ?83 ?64 ?00 ? *	cfstrsgt	mvf6, ?\[r3\], ?#0
! 00000128 <load_store\+0x128> 5c ?84 ?e4 ?40 ? *	cfstrspl	mvf14, ?\[r4\], ?#64
! 0000012c <load_store\+0x12c> 1d ?42 ?84 ?9d ? *	cfstrdne	mvd8, ?\[r2, ?#-157\]
! 00000130 <load_store\+0x130> bd ?c9 ?44 ?01 ? *	cfstrdlt	mvd4, ?\[r9, ?#1\]
! 00000134 <load_store\+0x134> 5d ?47 ?f4 ?3f ? *	cfstrdpl	mvd15, ?\[r7, ?#-63\]
! 00000138 <load_store\+0x138> ed ?48 ?34 ?88 ? *	cfstrd	mvd3, ?\[r8, ?#-136\]
! 0000013c <load_store\+0x13c> 2d ?46 ?14 ?44 ? *	cfstrdcs	mvd1, ?\[r6, ?#-68\]
! 00000140 <load_store\+0x140> 0d ?ed ?74 ?ff ? *	cfstrdeq	mvd7, ?\[sp, ?#255\]!
! 00000144 <load_store\+0x144> cd ?eb ?a4 ?49 ? *	cfstrdgt	mvd10, ?\[r11, ?#73\]!
! 00000148 <load_store\+0x148> dd ?6c ?64 ?ef ? *	cfstrdle	mvd6, ?\[r12, ?#-239\]!
! 0000014c <load_store\+0x14c> 9d ?6a ?04 ?ff ? *	cfstrdls	mvd0, ?\[r10, ?#-255\]!
! 00000150 <load_store\+0x150> 9d ?61 ?44 ?27 ? *	cfstrdls	mvd4, ?\[r1, ?#-39\]!
! 00000154 <load_store\+0x154> dc ?cf ?74 ?68 ? *	cfstrdle	mvd7, ?\[pc\], ?#104
! 00000158 <load_store\+0x158> 6c ?40 ?b4 ?00 ? *	cfstrdvs	mvd11, ?\[r0\], ?#-0
! 0000015c <load_store\+0x15c> ec ?ce ?34 ?48 ? *	cfstrd	mvd3, ?\[lr\], ?#72
! 00000160 <load_store\+0x160> 8c ?c5 ?f4 ?25 ? *	cfstrdhi	mvd15, ?\[r5\], ?#37
! 00000164 <load_store\+0x164> 4c ?c3 ?24 ?00 ? *	cfstrdmi	mvd2, ?\[r3\], ?#0
! 00000168 <load_store\+0x168> ed ?84 ?a5 ?40 ? *	cfstr32	mvfx10, ?\[r4, ?#64\]
! 0000016c <load_store\+0x16c> 3d ?02 ?85 ?9d ? *	cfstr32cc	mvfx8, ?\[r2, ?#-157\]
! 00000170 <load_store\+0x170> 1d ?89 ?c5 ?01 ? *	cfstr32ne	mvfx12, ?\[r9, ?#1\]
! 00000174 <load_store\+0x174> 7d ?07 ?55 ?3f ? *	cfstr32vc	mvfx5, ?\[r7, ?#-63\]
! 00000178 <load_store\+0x178> ad ?08 ?15 ?88 ? *	cfstr32ge	mvfx1, ?\[r8, ?#-136\]
! 0000017c <load_store\+0x17c> 6d ?26 ?b5 ?44 ? *	cfstr32vs	mvfx11, ?\[r6, ?#-68\]!
! 00000180 <load_store\+0x180> 0d ?ad ?55 ?ff ? *	cfstr32eq	mvfx5, ?\[sp, ?#255\]!
! 00000184 <load_store\+0x184> 4d ?ab ?e5 ?49 ? *	cfstr32mi	mvfx14, ?\[r11, ?#73\]!
! 00000188 <load_store\+0x188> 7d ?2c ?25 ?ef ? *	cfstr32vc	mvfx2, ?\[r12, ?#-239\]!
! 0000018c <load_store\+0x18c> bd ?2a ?05 ?ff ? *	cfstr32lt	mvfx0, ?\[r10, ?#-255\]!
! 00000190 <load_store\+0x190> 3c ?01 ?c5 ?27 ? *	cfstr32cc	mvfx12, ?\[r1\], ?#-39
! 00000194 <load_store\+0x194> ec ?8f ?d5 ?68 ? *	cfstr32	mvfx13, ?\[pc\], ?#104
! 00000198 <load_store\+0x198> 2c ?00 ?95 ?00 ? *	cfstr32cs	mvfx9, ?\[r0\], ?#-0
! 0000019c <load_store\+0x19c> ac ?8e ?95 ?48 ? *	cfstr32ge	mvfx9, ?\[lr\], ?#72
! 000001a0 <load_store\+0x1a0> 8c ?85 ?d5 ?25 ? *	cfstr32hi	mvfx13, ?\[r5\], ?#37
! 000001a4 <load_store\+0x1a4> cd ?c3 ?65 ?00 ? *	cfstr64gt	mvdx6, ?\[r3, ?#0\]
! 000001a8 <load_store\+0x1a8> 5d ?c4 ?e5 ?40 ? *	cfstr64pl	mvdx14, ?\[r4, ?#64\]
! 000001ac <load_store\+0x1ac> 1d ?42 ?85 ?9d ? *	cfstr64ne	mvdx8, ?\[r2, ?#-157\]
! 000001b0 <load_store\+0x1b0> bd ?c9 ?45 ?01 ? *	cfstr64lt	mvdx4, ?\[r9, ?#1\]
! 000001b4 <load_store\+0x1b4> 5d ?47 ?f5 ?3f ? *	cfstr64pl	mvdx15, ?\[r7, ?#-63\]
! 000001b8 <load_store\+0x1b8> ed ?68 ?35 ?88 ? *	cfstr64	mvdx3, ?\[r8, ?#-136\]!
! 000001bc <load_store\+0x1bc> 2d ?66 ?15 ?44 ? *	cfstr64cs	mvdx1, ?\[r6, ?#-68\]!
! 000001c0 <load_store\+0x1c0> 0d ?ed ?75 ?ff ? *	cfstr64eq	mvdx7, ?\[sp, ?#255\]!
! 000001c4 <load_store\+0x1c4> cd ?eb ?a5 ?49 ? *	cfstr64gt	mvdx10, ?\[r11, ?#73\]!
! 000001c8 <load_store\+0x1c8> dd ?6c ?65 ?ef ? *	cfstr64le	mvdx6, ?\[r12, ?#-239\]!
! 000001cc <load_store\+0x1cc> 9c ?4a ?05 ?ff ? *	cfstr64ls	mvdx0, ?\[r10\], ?#-255
! 000001d0 <load_store\+0x1d0> 9c ?41 ?45 ?27 ? *	cfstr64ls	mvdx4, ?\[r1\], ?#-39
! 000001d4 <load_store\+0x1d4> dc ?cf ?75 ?68 ? *	cfstr64le	mvdx7, ?\[pc\], ?#104
! 000001d8 <load_store\+0x1d8> 6c ?40 ?b5 ?00 ? *	cfstr64vs	mvdx11, ?\[r0\], ?#-0
! 000001dc <load_store\+0x1dc> ec ?ce ?35 ?48 ? *	cfstr64	mvdx3, ?\[lr\], ?#72
  # move:
! 000001e0 <move> 8e ?0f ?54 ?50 ? *	cfmvsrhi	mvf15, ?r5
! 000001e4 <move\+0x4> 6e ?0b ?64 ?50 ? *	cfmvsrvs	mvf11, ?r6
! 000001e8 <move\+0x8> 2e ?09 ?04 ?50 ? *	cfmvsrcs	mvf9, ?r0
! 000001ec <move\+0xc> 5e ?0f ?74 ?50 ? *	cfmvsrpl	mvf15, ?r7
! 000001f0 <move\+0x10> 9e ?04 ?14 ?50 ? *	cfmvsrls	mvf4, ?r1
! 000001f4 <move\+0x14> 3e ?1d ?84 ?50 ? *	cfmvrscc	r8, ?mvf13
! 000001f8 <move\+0x18> 7e ?11 ?f4 ?50 ? *	cfmvrsvc	pc, ?mvf1
! 000001fc <move\+0x1c> ce ?1b ?94 ?50 ? *	cfmvrsgt	r9, ?mvf11
! 00000200 <move\+0x20> 0e ?15 ?a4 ?50 ? *	cfmvrseq	r10, ?mvf5
! 00000204 <move\+0x24> ee ?1c ?44 ?50 ? *	cfmvrs	r4, ?mvf12
! 00000208 <move\+0x28> ae ?01 ?84 ?10 ? *	cfmvdlrge	mvd1, ?r8
! 0000020c <move\+0x2c> ee ?0d ?f4 ?10 ? *	cfmvdlr	mvd13, ?pc
! 00000210 <move\+0x30> be ?04 ?94 ?10 ? *	cfmvdlrlt	mvd4, ?r9
! 00000214 <move\+0x34> 9e ?00 ?a4 ?10 ? *	cfmvdlrls	mvd0, ?r10
! 00000218 <move\+0x38> ee ?0a ?44 ?10 ? *	cfmvdlr	mvd10, ?r4
! 0000021c <move\+0x3c> 4e ?13 ?14 ?10 ? *	cfmvrdlmi	r1, ?mvd3
! 00000220 <move\+0x40> 8e ?17 ?24 ?10 ? *	cfmvrdlhi	r2, ?mvd7
! 00000224 <move\+0x44> 2e ?1c ?c4 ?10 ? *	cfmvrdlcs	r12, ?mvd12
! 00000228 <move\+0x48> 6e ?10 ?34 ?10 ? *	cfmvrdlvs	r3, ?mvd0
! 0000022c <move\+0x4c> 7e ?1e ?d4 ?10 ? *	cfmvrdlvc	sp, ?mvd14
! 00000230 <move\+0x50> 3e ?0c ?14 ?30 ? *	cfmvdhrcc	mvd12, ?r1
! 00000234 <move\+0x54> 1e ?08 ?24 ?30 ? *	cfmvdhrne	mvd8, ?r2
! 00000238 <move\+0x58> de ?06 ?c4 ?30 ? *	cfmvdhrle	mvd6, ?r12
! 0000023c <move\+0x5c> 4e ?02 ?34 ?30 ? *	cfmvdhrmi	mvd2, ?r3
! 00000240 <move\+0x60> 0e ?05 ?d4 ?30 ? *	cfmvdhreq	mvd5, ?sp
! 00000244 <move\+0x64> ae ?14 ?44 ?30 ? *	cfmvrdhge	r4, ?mvd4
! 00000248 <move\+0x68> ee ?18 ?b4 ?30 ? *	cfmvrdh	r11, ?mvd8
! 0000024c <move\+0x6c> de ?12 ?54 ?30 ? *	cfmvrdhle	r5, ?mvd2
! 00000250 <move\+0x70> 1e ?16 ?64 ?30 ? *	cfmvrdhne	r6, ?mvd6
! 00000254 <move\+0x74> be ?17 ?04 ?30 ? *	cfmvrdhlt	r0, ?mvd7
! 00000258 <move\+0x78> 5e ?0e ?45 ?10 ? *	cfmv64lrpl	mvdx14, ?r4
! 0000025c <move\+0x7c> ce ?0a ?b5 ?10 ? *	cfmv64lrgt	mvdx10, ?r11
! 00000260 <move\+0x80> 8e ?0f ?55 ?10 ? *	cfmv64lrhi	mvdx15, ?r5
! 00000264 <move\+0x84> 6e ?0b ?65 ?10 ? *	cfmv64lrvs	mvdx11, ?r6
! 00000268 <move\+0x88> 2e ?09 ?05 ?10 ? *	cfmv64lrcs	mvdx9, ?r0
! 0000026c <move\+0x8c> 5e ?1a ?d5 ?10 ? *	cfmvr64lpl	sp, ?mvdx10
! 00000270 <move\+0x90> 9e ?1e ?e5 ?10 ? *	cfmvr64lls	lr, ?mvdx14
! 00000274 <move\+0x94> 3e ?1d ?85 ?10 ? *	cfmvr64lcc	r8, ?mvdx13
! 00000278 <move\+0x98> 7e ?11 ?f5 ?10 ? *	cfmvr64lvc	pc, ?mvdx1
! 0000027c <move\+0x9c> ce ?1b ?95 ?10 ? *	cfmvr64lgt	r9, ?mvdx11
! 00000280 <move\+0xa0> 0e ?07 ?d5 ?30 ? *	cfmv64hreq	mvdx7, ?sp
! 00000284 <move\+0xa4> ee ?03 ?e5 ?30 ? *	cfmv64hr	mvdx3, ?lr
! 00000288 <move\+0xa8> ae ?01 ?85 ?30 ? *	cfmv64hrge	mvdx1, ?r8
! 0000028c <move\+0xac> ee ?0d ?f5 ?30 ? *	cfmv64hr	mvdx13, ?pc
! 00000290 <move\+0xb0> be ?04 ?95 ?30 ? *	cfmv64hrlt	mvdx4, ?r9
! 00000294 <move\+0xb4> 9e ?15 ?05 ?30 ? *	cfmvr64hls	r0, ?mvdx5
! 00000298 <move\+0xb8> ee ?19 ?75 ?30 ? *	cfmvr64h	r7, ?mvdx9
! 0000029c <move\+0xbc> 4e ?13 ?15 ?30 ? *	cfmvr64hmi	r1, ?mvdx3
! 000002a0 <move\+0xc0> 8e ?17 ?25 ?30 ? *	cfmvr64hhi	r2, ?mvdx7
! 000002a4 <move\+0xc4> 2e ?1c ?c5 ?30 ? *	cfmvr64hcs	r12, ?mvdx12
! 000002a8 <move\+0xc8> 6e ?10 ?06 ?11 ? *	cfmval32vs	mvax1, ?mvfx0
! 000002ac <move\+0xcc> 7e ?1e ?06 ?13 ? *	cfmval32vc	mvax3, ?mvfx14
! 000002b0 <move\+0xd0> 3e ?1a ?06 ?10 ? *	cfmval32cc	mvax0, ?mvfx10
! 000002b4 <move\+0xd4> 1e ?1f ?06 ?11 ? *	cfmval32ne	mvax1, ?mvfx15
! 000002b8 <move\+0xd8> de ?1b ?06 ?10 ? *	cfmval32le	mvax0, ?mvfx11
! 000002bc <move\+0xdc> 4e ?01 ?06 ?12 ? *	cfmv32almi	mvfx2, ?mvax1
! 000002c0 <move\+0xe0> 0e ?03 ?06 ?15 ? *	cfmv32aleq	mvfx5, ?mvax3
! 000002c4 <move\+0xe4> ae ?00 ?06 ?19 ? *	cfmv32alge	mvfx9, ?mvax0
! 000002c8 <move\+0xe8> ee ?01 ?06 ?13 ? *	cfmv32al	mvfx3, ?mvax1
! 000002cc <move\+0xec> de ?00 ?06 ?17 ? *	cfmv32alle	mvfx7, ?mvax0
! 000002d0 <move\+0xf0> 1e ?16 ?06 ?32 ? *	cfmvam32ne	mvax2, ?mvfx6
! 000002d4 <move\+0xf4> be ?17 ?06 ?30 ? *	cfmvam32lt	mvax0, ?mvfx7
! 000002d8 <move\+0xf8> 5e ?13 ?06 ?32 ? *	cfmvam32pl	mvax2, ?mvfx3
! 000002dc <move\+0xfc> ce ?11 ?06 ?31 ? *	cfmvam32gt	mvax1, ?mvfx1
! 000002e0 <move\+0x100> 8e ?1d ?06 ?33 ? *	cfmvam32hi	mvax3, ?mvfx13
! 000002e4 <move\+0x104> 6e ?02 ?06 ?3b ? *	cfmv32amvs	mvfx11, ?mvax2
! 000002e8 <move\+0x108> 2e ?00 ?06 ?39 ? *	cfmv32amcs	mvfx9, ?mvax0
! 000002ec <move\+0x10c> 5e ?02 ?06 ?3f ? *	cfmv32ampl	mvfx15, ?mvax2
! 000002f0 <move\+0x110> 9e ?01 ?06 ?34 ? *	cfmv32amls	mvfx4, ?mvax1
! 000002f4 <move\+0x114> 3e ?03 ?06 ?38 ? *	cfmv32amcc	mvfx8, ?mvax3
! 000002f8 <move\+0x118> 7e ?11 ?06 ?50 ? *	cfmvah32vc	mvax0, ?mvfx1
! 000002fc <move\+0x11c> ce ?1b ?06 ?50 ? *	cfmvah32gt	mvax0, ?mvfx11
! 00000300 <move\+0x120> 0e ?15 ?06 ?51 ? *	cfmvah32eq	mvax1, ?mvfx5
! 00000304 <move\+0x124> ee ?1c ?06 ?52 ? *	cfmvah32	mvax2, ?mvfx12
! 00000308 <move\+0x128> ae ?18 ?06 ?53 ? *	cfmvah32ge	mvax3, ?mvfx8
! 0000030c <move\+0x12c> ee ?00 ?06 ?5d ? *	cfmv32ah	mvfx13, ?mvax0
! 00000310 <move\+0x130> be ?00 ?06 ?54 ? *	cfmv32ahlt	mvfx4, ?mvax0
! 00000314 <move\+0x134> 9e ?01 ?06 ?50 ? *	cfmv32ahls	mvfx0, ?mvax1
! 00000318 <move\+0x138> ee ?02 ?06 ?5a ? *	cfmv32ah	mvfx10, ?mvax2
! 0000031c <move\+0x13c> 4e ?03 ?06 ?5e ? *	cfmv32ahmi	mvfx14, ?mvax3
! 00000320 <move\+0x140> 8e ?17 ?06 ?73 ? *	cfmva32hi	mvax3, ?mvfx7
! 00000324 <move\+0x144> 2e ?1c ?06 ?73 ? *	cfmva32cs	mvax3, ?mvfx12
! 00000328 <move\+0x148> 6e ?10 ?06 ?71 ? *	cfmva32vs	mvax1, ?mvfx0
! 0000032c <move\+0x14c> 7e ?1e ?06 ?73 ? *	cfmva32vc	mvax3, ?mvfx14
! 00000330 <move\+0x150> 3e ?1a ?06 ?70 ? *	cfmva32cc	mvax0, ?mvfx10
! 00000334 <move\+0x154> 1e ?03 ?06 ?78 ? *	cfmv32ane	mvfx8, ?mvax3
! 00000338 <move\+0x158> de ?03 ?06 ?76 ? *	cfmv32ale	mvfx6, ?mvax3
! 0000033c <move\+0x15c> 4e ?01 ?06 ?72 ? *	cfmv32ami	mvfx2, ?mvax1
! 00000340 <move\+0x160> 0e ?03 ?06 ?75 ? *	cfmv32aeq	mvfx5, ?mvax3
! 00000344 <move\+0x164> ae ?00 ?06 ?79 ? *	cfmv32age	mvfx9, ?mvax0
! 00000348 <move\+0x168> ee ?18 ?06 ?93 ? *	cfmva64	mvax3, ?mvdx8
! 0000034c <move\+0x16c> de ?12 ?06 ?92 ? *	cfmva64le	mvax2, ?mvdx2
! 00000350 <move\+0x170> 1e ?16 ?06 ?92 ? *	cfmva64ne	mvax2, ?mvdx6
! 00000354 <move\+0x174> be ?17 ?06 ?90 ? *	cfmva64lt	mvax0, ?mvdx7
! 00000358 <move\+0x178> 5e ?13 ?06 ?92 ? *	cfmva64pl	mvax2, ?mvdx3
! 0000035c <move\+0x17c> ce ?03 ?06 ?9a ? *	cfmv64agt	mvdx10, ?mvax3
! 00000360 <move\+0x180> 8e ?02 ?06 ?9f ? *	cfmv64ahi	mvdx15, ?mvax2
! 00000364 <move\+0x184> 6e ?02 ?06 ?9b ? *	cfmv64avs	mvdx11, ?mvax2
! 00000368 <move\+0x188> 2e ?00 ?06 ?99 ? *	cfmv64acs	mvdx9, ?mvax0
! 0000036c <move\+0x18c> 5e ?02 ?06 ?9f ? *	cfmv64apl	mvdx15, ?mvax2
! 00000370 <move\+0x190> 9e ?1e ?06 ?b0 ? *	cfmvsc32ls	dspsc, ?mvfx14
! 00000374 <move\+0x194> 3e ?1d ?06 ?b0 ? *	cfmvsc32cc	dspsc, ?mvfx13
! 00000378 <move\+0x198> 7e ?11 ?06 ?b0 ? *	cfmvsc32vc	dspsc, ?mvfx1
! 0000037c <move\+0x19c> ce ?1b ?06 ?b0 ? *	cfmvsc32gt	dspsc, ?mvfx11
! 00000380 <move\+0x1a0> 0e ?15 ?06 ?b0 ? *	cfmvsc32eq	dspsc, ?mvfx5
! 00000384 <move\+0x1a4> ee ?00 ?06 ?b3 ? *	cfmv32sc	mvfx3, ?dspsc
! 00000388 <move\+0x1a8> ae ?00 ?06 ?b1 ? *	cfmv32scge	mvfx1, ?dspsc
! 0000038c <move\+0x1ac> ee ?00 ?06 ?bd ? *	cfmv32sc	mvfx13, ?dspsc
! 00000390 <move\+0x1b0> be ?00 ?06 ?b4 ? *	cfmv32sclt	mvfx4, ?dspsc
! 00000394 <move\+0x1b4> 9e ?00 ?06 ?b0 ? *	cfmv32scls	mvfx0, ?dspsc
! 00000398 <move\+0x1b8> ee ?09 ?a4 ?00 ? *	cfcpys	mvf10, ?mvf9
! 0000039c <move\+0x1bc> 4e ?03 ?e4 ?00 ? *	cfcpysmi	mvf14, ?mvf3
! 000003a0 <move\+0x1c0> 8e ?07 ?d4 ?00 ? *	cfcpyshi	mvf13, ?mvf7
! 000003a4 <move\+0x1c4> 2e ?0c ?14 ?00 ? *	cfcpyscs	mvf1, ?mvf12
! 000003a8 <move\+0x1c8> 6e ?00 ?b4 ?00 ? *	cfcpysvs	mvf11, ?mvf0
! 000003ac <move\+0x1cc> 7e ?0e ?54 ?20 ? *	cfcpydvc	mvd5, ?mvd14
! 000003b0 <move\+0x1d0> 3e ?0a ?c4 ?20 ? *	cfcpydcc	mvd12, ?mvd10
! 000003b4 <move\+0x1d4> 1e ?0f ?84 ?20 ? *	cfcpydne	mvd8, ?mvd15
! 000003b8 <move\+0x1d8> de ?0b ?64 ?20 ? *	cfcpydle	mvd6, ?mvd11
! 000003bc <move\+0x1dc> 4e ?09 ?24 ?20 ? *	cfcpydmi	mvd2, ?mvd9
  # conv:
! 000003c0 <conv> 0e ?0f ?54 ?60 ? *	cfcvtsdeq	mvd5, ?mvf15
! 000003c4 <conv\+0x4> ae ?04 ?94 ?60 ? *	cfcvtsdge	mvd9, ?mvf4
! 000003c8 <conv\+0x8> ee ?08 ?34 ?60 ? *	cfcvtsd	mvd3, ?mvf8
! 000003cc <conv\+0xc> de ?02 ?74 ?60 ? *	cfcvtsdle	mvd7, ?mvf2
! 000003d0 <conv\+0x10> 1e ?06 ?c4 ?60 ? *	cfcvtsdne	mvd12, ?mvf6
! 000003d4 <conv\+0x14> be ?07 ?04 ?40 ? *	cfcvtdslt	mvf0, ?mvd7
! 000003d8 <conv\+0x18> 5e ?03 ?e4 ?40 ? *	cfcvtdspl	mvf14, ?mvd3
! 000003dc <conv\+0x1c> ce ?01 ?a4 ?40 ? *	cfcvtdsgt	mvf10, ?mvd1
! 000003e0 <conv\+0x20> 8e ?0d ?f4 ?40 ? *	cfcvtdshi	mvf15, ?mvd13
! 000003e4 <conv\+0x24> 6e ?04 ?b4 ?40 ? *	cfcvtdsvs	mvf11, ?mvd4
! 000003e8 <conv\+0x28> 2e ?00 ?94 ?80 ? *	cfcvt32scs	mvf9, ?mvfx0
! 000003ec <conv\+0x2c> 5e ?0a ?f4 ?80 ? *	cfcvt32spl	mvf15, ?mvfx10
! 000003f0 <conv\+0x30> 9e ?0e ?44 ?80 ? *	cfcvt32sls	mvf4, ?mvfx14
! 000003f4 <conv\+0x34> 3e ?0d ?84 ?80 ? *	cfcvt32scc	mvf8, ?mvfx13
! 000003f8 <conv\+0x38> 7e ?01 ?24 ?80 ? *	cfcvt32svc	mvf2, ?mvfx1
! 000003fc <conv\+0x3c> ce ?0b ?64 ?a0 ? *	cfcvt32dgt	mvd6, ?mvfx11
! 00000400 <conv\+0x40> 0e ?05 ?74 ?a0 ? *	cfcvt32deq	mvd7, ?mvfx5
! 00000404 <conv\+0x44> ee ?0c ?34 ?a0 ? *	cfcvt32d	mvd3, ?mvfx12
! 00000408 <conv\+0x48> ae ?08 ?14 ?a0 ? *	cfcvt32dge	mvd1, ?mvfx8
! 0000040c <conv\+0x4c> ee ?06 ?d4 ?a0 ? *	cfcvt32d	mvd13, ?mvfx6
! 00000410 <conv\+0x50> be ?02 ?44 ?c0 ? *	cfcvt64slt	mvf4, ?mvdx2
! 00000414 <conv\+0x54> 9e ?05 ?04 ?c0 ? *	cfcvt64sls	mvf0, ?mvdx5
! 00000418 <conv\+0x58> ee ?09 ?a4 ?c0 ? *	cfcvt64s	mvf10, ?mvdx9
! 0000041c <conv\+0x5c> 4e ?03 ?e4 ?c0 ? *	cfcvt64smi	mvf14, ?mvdx3
! 00000420 <conv\+0x60> 8e ?07 ?d4 ?c0 ? *	cfcvt64shi	mvf13, ?mvdx7
! 00000424 <conv\+0x64> 2e ?0c ?14 ?e0 ? *	cfcvt64dcs	mvd1, ?mvdx12
! 00000428 <conv\+0x68> 6e ?00 ?b4 ?e0 ? *	cfcvt64dvs	mvd11, ?mvdx0
! 0000042c <conv\+0x6c> 7e ?0e ?54 ?e0 ? *	cfcvt64dvc	mvd5, ?mvdx14
! 00000430 <conv\+0x70> 3e ?0a ?c4 ?e0 ? *	cfcvt64dcc	mvd12, ?mvdx10
! 00000434 <conv\+0x74> 1e ?0f ?84 ?e0 ? *	cfcvt64dne	mvd8, ?mvdx15
! 00000438 <conv\+0x78> de ?1b ?65 ?80 ? *	cfcvts32le	mvfx6, ?mvf11
! 0000043c <conv\+0x7c> 4e ?19 ?25 ?80 ? *	cfcvts32mi	mvfx2, ?mvf9
! 00000440 <conv\+0x80> 0e ?1f ?55 ?80 ? *	cfcvts32eq	mvfx5, ?mvf15
! 00000444 <conv\+0x84> ae ?14 ?95 ?80 ? *	cfcvts32ge	mvfx9, ?mvf4
! 00000448 <conv\+0x88> ee ?18 ?35 ?80 ? *	cfcvts32	mvfx3, ?mvf8
! 0000044c <conv\+0x8c> de ?12 ?75 ?a0 ? *	cfcvtd32le	mvfx7, ?mvd2
! 00000450 <conv\+0x90> 1e ?16 ?c5 ?a0 ? *	cfcvtd32ne	mvfx12, ?mvd6
! 00000454 <conv\+0x94> be ?17 ?05 ?a0 ? *	cfcvtd32lt	mvfx0, ?mvd7
! 00000458 <conv\+0x98> 5e ?13 ?e5 ?a0 ? *	cfcvtd32pl	mvfx14, ?mvd3
! 0000045c <conv\+0x9c> ce ?11 ?a5 ?a0 ? *	cfcvtd32gt	mvfx10, ?mvd1
! 00000460 <conv\+0xa0> 8e ?1d ?f5 ?c0 ? *	cftruncs32hi	mvfx15, ?mvf13
! 00000464 <conv\+0xa4> 6e ?14 ?b5 ?c0 ? *	cftruncs32vs	mvfx11, ?mvf4
! 00000468 <conv\+0xa8> 2e ?10 ?95 ?c0 ? *	cftruncs32cs	mvfx9, ?mvf0
! 0000046c <conv\+0xac> 5e ?1a ?f5 ?c0 ? *	cftruncs32pl	mvfx15, ?mvf10
! 00000470 <conv\+0xb0> 9e ?1e ?45 ?c0 ? *	cftruncs32ls	mvfx4, ?mvf14
! 00000474 <conv\+0xb4> 3e ?1d ?85 ?e0 ? *	cftruncd32cc	mvfx8, ?mvd13
! 00000478 <conv\+0xb8> 7e ?11 ?25 ?e0 ? *	cftruncd32vc	mvfx2, ?mvd1
! 0000047c <conv\+0xbc> ce ?1b ?65 ?e0 ? *	cftruncd32gt	mvfx6, ?mvd11
! 00000480 <conv\+0xc0> 0e ?15 ?75 ?e0 ? *	cftruncd32eq	mvfx7, ?mvd5
! 00000484 <conv\+0xc4> ee ?1c ?35 ?e0 ? *	cftruncd32	mvfx3, ?mvd12
  # shift:
! 00000488 <shift> ae ?01 ?25 ?58 ? *	cfrshl32ge	mvfx1, ?mvfx8, ?r2
! 0000048c <shift\+0x4> 6e ?0b ?95 ?54 ? *	cfrshl32vs	mvfx11, ?mvfx4, ?r9
! 00000490 <shift\+0x8> 0e ?05 ?75 ?5f ? *	cfrshl32eq	mvfx5, ?mvfx15, ?r7
! 00000494 <shift\+0xc> 4e ?0e ?85 ?53 ? *	cfrshl32mi	mvfx14, ?mvfx3, ?r8
! 00000498 <shift\+0x10> 7e ?02 ?65 ?51 ? *	cfrshl32vc	mvfx2, ?mvfx1, ?r6
! 0000049c <shift\+0x14> be ?00 ?d5 ?77 ? *	cfrshl64lt	mvdx0, ?mvdx7, ?sp
! 000004a0 <shift\+0x18> 3e ?0c ?b5 ?7a ? *	cfrshl64cc	mvdx12, ?mvdx10, ?r11
! 000004a4 <shift\+0x1c> ee ?0d ?c5 ?76 ? *	cfrshl64	mvdx13, ?mvdx6, ?r12
! 000004a8 <shift\+0x20> 2e ?09 ?a5 ?70 ? *	cfrshl64cs	mvdx9, ?mvdx0, ?r10
! 000004ac <shift\+0x24> ae ?09 ?15 ?74 ? *	cfrshl64ge	mvdx9, ?mvdx4, ?r1
! 000004b0 <shift\+0x28> 8e ?07 ?d5 ?41 ? *	cfsh32hi	mvfx13, ?mvfx7, ?#33
! 000004b4 <shift\+0x2c> ce ?0b ?65 ?00 ? *	cfsh32gt	mvfx6, ?mvfx11, ?#0
! 000004b8 <shift\+0x30> 5e ?03 ?e5 ?40 ? *	cfsh32pl	mvfx14, ?mvfx3, ?#32
! 000004bc <shift\+0x34> 1e ?0f ?85 ?c1 ? *	cfsh32ne	mvfx8, ?mvfx15, ?#-31
! 000004c0 <shift\+0x38> be ?02 ?45 ?01 ? *	cfsh32lt	mvfx4, ?mvfx2, ?#1
! 000004c4 <shift\+0x3c> 5e ?2a ?f5 ?c0 ? *	cfsh64pl	mvdx15, ?mvdx10, ?#-32
! 000004c8 <shift\+0x40> ee ?28 ?35 ?c5 ? *	cfsh64	mvdx3, ?mvdx8, ?#-27
! 000004cc <shift\+0x44> 2e ?2c ?15 ?eb ? *	cfsh64cs	mvdx1, ?mvdx12, ?#-5
! 000004d0 <shift\+0x48> 0e ?25 ?75 ?6f ? *	cfsh64eq	mvdx7, ?mvdx5, ?#63
! 000004d4 <shift\+0x4c> ce ?21 ?a5 ?09 ? *	cfsh64gt	mvdx10, ?mvdx1, ?#9
  # comp:
! 000004d8 <comp> de ?1b ?f4 ?94 ? *	cfcmpsle	pc, ?mvf11, ?mvf4
! 000004dc <comp\+0x4> 9e ?15 ?04 ?9f ? *	cfcmpsls	r0, ?mvf5, ?mvf15
! 000004e0 <comp\+0x8> 9e ?1e ?e4 ?93 ? *	cfcmpsls	lr, ?mvf14, ?mvf3
! 000004e4 <comp\+0xc> de ?12 ?54 ?91 ? *	cfcmpsle	r5, ?mvf2, ?mvf1
! 000004e8 <comp\+0x10> 6e ?10 ?34 ?97 ? *	cfcmpsvs	r3, ?mvf0, ?mvf7
! 000004ec <comp\+0x14> ee ?1c ?44 ?ba ? *	cfcmpd	r4, ?mvd12, ?mvd10
! 000004f0 <comp\+0x18> 8e ?1d ?24 ?b6 ? *	cfcmpdhi	r2, ?mvd13, ?mvd6
! 000004f4 <comp\+0x1c> 4e ?19 ?94 ?b0 ? *	cfcmpdmi	r9, ?mvd9, ?mvd0
! 000004f8 <comp\+0x20> ee ?19 ?74 ?b4 ? *	cfcmpd	r7, ?mvd9, ?mvd4
! 000004fc <comp\+0x24> 3e ?1d ?84 ?b7 ? *	cfcmpdcc	r8, ?mvd13, ?mvd7
! 00000500 <comp\+0x28> 1e ?16 ?65 ?9b ? *	cfcmp32ne	r6, ?mvfx6, ?mvfx11
! 00000504 <comp\+0x2c> 7e ?1e ?d5 ?93 ? *	cfcmp32vc	sp, ?mvfx14, ?mvfx3
! 00000508 <comp\+0x30> ae ?18 ?b5 ?9f ? *	cfcmp32ge	r11, ?mvfx8, ?mvfx15
! 0000050c <comp\+0x34> 6e ?14 ?c5 ?92 ? *	cfcmp32vs	r12, ?mvfx4, ?mvfx2
! 00000510 <comp\+0x38> 0e ?1f ?a5 ?9a ? *	cfcmp32eq	r10, ?mvfx15, ?mvfx10
! 00000514 <comp\+0x3c> 4e ?13 ?15 ?b8 ? *	cfcmp64mi	r1, ?mvdx3, ?mvdx8
! 00000518 <comp\+0x40> 7e ?11 ?f5 ?bc ? *	cfcmp64vc	pc, ?mvdx1, ?mvdx12
! 0000051c <comp\+0x44> be ?17 ?05 ?b5 ? *	cfcmp64lt	r0, ?mvdx7, ?mvdx5
! 00000520 <comp\+0x48> 3e ?1a ?e5 ?b1 ? *	cfcmp64cc	lr, ?mvdx10, ?mvdx1
! 00000524 <comp\+0x4c> ee ?16 ?55 ?bb ? *	cfcmp64	r5, ?mvdx6, ?mvdx11
  # fp_arith:
! 00000528 <fp_arith> 2e ?30 ?94 ?00 ? *	cfabsscs	mvf9, ?mvf0
! 0000052c <fp_arith\+0x4> 5e ?3a ?f4 ?00 ? *	cfabsspl	mvf15, ?mvf10
! 00000530 <fp_arith\+0x8> 9e ?3e ?44 ?00 ? *	cfabssls	mvf4, ?mvf14
! 00000534 <fp_arith\+0xc> 3e ?3d ?84 ?00 ? *	cfabsscc	mvf8, ?mvf13
! 00000538 <fp_arith\+0x10> 7e ?31 ?24 ?00 ? *	cfabssvc	mvf2, ?mvf1
! 0000053c <fp_arith\+0x14> ce ?3b ?64 ?20 ? *	cfabsdgt	mvd6, ?mvd11
! 00000540 <fp_arith\+0x18> 0e ?35 ?74 ?20 ? *	cfabsdeq	mvd7, ?mvd5
! 00000544 <fp_arith\+0x1c> ee ?3c ?34 ?20 ? *	cfabsd	mvd3, ?mvd12
! 00000548 <fp_arith\+0x20> ae ?38 ?14 ?20 ? *	cfabsdge	mvd1, ?mvd8
! 0000054c <fp_arith\+0x24> ee ?36 ?d4 ?20 ? *	cfabsd	mvd13, ?mvd6
! 00000550 <fp_arith\+0x28> be ?32 ?44 ?40 ? *	cfnegslt	mvf4, ?mvf2
! 00000554 <fp_arith\+0x2c> 9e ?35 ?04 ?40 ? *	cfnegsls	mvf0, ?mvf5
! 00000558 <fp_arith\+0x30> ee ?39 ?a4 ?40 ? *	cfnegs	mvf10, ?mvf9
! 0000055c <fp_arith\+0x34> 4e ?33 ?e4 ?40 ? *	cfnegsmi	mvf14, ?mvf3
! 00000560 <fp_arith\+0x38> 8e ?37 ?d4 ?40 ? *	cfnegshi	mvf13, ?mvf7
! 00000564 <fp_arith\+0x3c> 2e ?3c ?14 ?60 ? *	cfnegdcs	mvd1, ?mvd12
! 00000568 <fp_arith\+0x40> 6e ?30 ?b4 ?60 ? *	cfnegdvs	mvd11, ?mvd0
! 0000056c <fp_arith\+0x44> 7e ?3e ?54 ?60 ? *	cfnegdvc	mvd5, ?mvd14
! 00000570 <fp_arith\+0x48> 3e ?3a ?c4 ?60 ? *	cfnegdcc	mvd12, ?mvd10
! 00000574 <fp_arith\+0x4c> 1e ?3f ?84 ?60 ? *	cfnegdne	mvd8, ?mvd15
! 00000578 <fp_arith\+0x50> de ?3b ?64 ?84 ? *	cfaddsle	mvf6, ?mvf11, ?mvf4
! 0000057c <fp_arith\+0x54> 9e ?35 ?04 ?8f ? *	cfaddsls	mvf0, ?mvf5, ?mvf15
! 00000580 <fp_arith\+0x58> 9e ?3e ?44 ?83 ? *	cfaddsls	mvf4, ?mvf14, ?mvf3
! 00000584 <fp_arith\+0x5c> de ?32 ?74 ?81 ? *	cfaddsle	mvf7, ?mvf2, ?mvf1
! 00000588 <fp_arith\+0x60> 6e ?30 ?b4 ?87 ? *	cfaddsvs	mvf11, ?mvf0, ?mvf7
! 0000058c <fp_arith\+0x64> ee ?3c ?34 ?aa ? *	cfaddd	mvd3, ?mvd12, ?mvd10
! 00000590 <fp_arith\+0x68> 8e ?3d ?f4 ?a6 ? *	cfadddhi	mvd15, ?mvd13, ?mvd6
! 00000594 <fp_arith\+0x6c> 4e ?39 ?24 ?a0 ? *	cfadddmi	mvd2, ?mvd9, ?mvd0
! 00000598 <fp_arith\+0x70> ee ?39 ?a4 ?a4 ? *	cfaddd	mvd10, ?mvd9, ?mvd4
! 0000059c <fp_arith\+0x74> 3e ?3d ?84 ?a7 ? *	cfadddcc	mvd8, ?mvd13, ?mvd7
! 000005a0 <fp_arith\+0x78> 1e ?36 ?c4 ?cb ? *	cfsubsne	mvf12, ?mvf6, ?mvf11
! 000005a4 <fp_arith\+0x7c> 7e ?3e ?54 ?c3 ? *	cfsubsvc	mvf5, ?mvf14, ?mvf3
! 000005a8 <fp_arith\+0x80> ae ?38 ?14 ?cf ? *	cfsubsge	mvf1, ?mvf8, ?mvf15
! 000005ac <fp_arith\+0x84> 6e ?34 ?b4 ?c2 ? *	cfsubsvs	mvf11, ?mvf4, ?mvf2
! 000005b0 <fp_arith\+0x88> 0e ?3f ?54 ?ca ? *	cfsubseq	mvf5, ?mvf15, ?mvf10
! 000005b4 <fp_arith\+0x8c> 4e ?33 ?e4 ?e8 ? *	cfsubdmi	mvd14, ?mvd3, ?mvd8
! 000005b8 <fp_arith\+0x90> 7e ?31 ?24 ?ec ? *	cfsubdvc	mvd2, ?mvd1, ?mvd12
! 000005bc <fp_arith\+0x94> be ?37 ?04 ?e5 ? *	cfsubdlt	mvd0, ?mvd7, ?mvd5
! 000005c0 <fp_arith\+0x98> 3e ?3a ?c4 ?e1 ? *	cfsubdcc	mvd12, ?mvd10, ?mvd1
! 000005c4 <fp_arith\+0x9c> ee ?36 ?d4 ?eb ? *	cfsubd	mvd13, ?mvd6, ?mvd11
! 000005c8 <fp_arith\+0xa0> 2e ?10 ?94 ?05 ? *	cfmulscs	mvf9, ?mvf0, ?mvf5
! 000005cc <fp_arith\+0xa4> ae ?14 ?94 ?0e ? *	cfmulsge	mvf9, ?mvf4, ?mvf14
! 000005d0 <fp_arith\+0xa8> 8e ?17 ?d4 ?02 ? *	cfmulshi	mvf13, ?mvf7, ?mvf2
! 000005d4 <fp_arith\+0xac> ce ?1b ?64 ?00 ? *	cfmulsgt	mvf6, ?mvf11, ?mvf0
! 000005d8 <fp_arith\+0xb0> 5e ?13 ?e4 ?0c ? *	cfmulspl	mvf14, ?mvf3, ?mvf12
! 000005dc <fp_arith\+0xb4> 1e ?1f ?84 ?2d ? *	cfmuldne	mvd8, ?mvd15, ?mvd13
! 000005e0 <fp_arith\+0xb8> be ?12 ?44 ?29 ? *	cfmuldlt	mvd4, ?mvd2, ?mvd9
! 000005e4 <fp_arith\+0xbc> 5e ?1a ?f4 ?29 ? *	cfmuldpl	mvd15, ?mvd10, ?mvd9
! 000005e8 <fp_arith\+0xc0> ee ?18 ?34 ?2d ? *	cfmuld	mvd3, ?mvd8, ?mvd13
! 000005ec <fp_arith\+0xc4> 2e ?1c ?14 ?26 ? *	cfmuldcs	mvd1, ?mvd12, ?mvd6
  # int_arith:
! 000005f0 <int_arith> 0e ?35 ?75 ?00 ? *	cfabs32eq	mvfx7, ?mvfx5
! 000005f4 <int_arith\+0x4> ee ?3c ?35 ?00 ? *	cfabs32	mvfx3, ?mvfx12
! 000005f8 <int_arith\+0x8> ae ?38 ?15 ?00 ? *	cfabs32ge	mvfx1, ?mvfx8
! 000005fc <int_arith\+0xc> ee ?36 ?d5 ?00 ? *	cfabs32	mvfx13, ?mvfx6
! 00000600 <int_arith\+0x10> be ?32 ?45 ?00 ? *	cfabs32lt	mvfx4, ?mvfx2
! 00000604 <int_arith\+0x14> 9e ?35 ?05 ?20 ? *	cfabs64ls	mvdx0, ?mvdx5
! 00000608 <int_arith\+0x18> ee ?39 ?a5 ?20 ? *	cfabs64	mvdx10, ?mvdx9
! 0000060c <int_arith\+0x1c> 4e ?33 ?e5 ?20 ? *	cfabs64mi	mvdx14, ?mvdx3
! 00000610 <int_arith\+0x20> 8e ?37 ?d5 ?20 ? *	cfabs64hi	mvdx13, ?mvdx7
! 00000614 <int_arith\+0x24> 2e ?3c ?15 ?20 ? *	cfabs64cs	mvdx1, ?mvdx12
! 00000618 <int_arith\+0x28> 6e ?30 ?b5 ?40 ? *	cfneg32vs	mvfx11, ?mvfx0
! 0000061c <int_arith\+0x2c> 7e ?3e ?55 ?40 ? *	cfneg32vc	mvfx5, ?mvfx14
! 00000620 <int_arith\+0x30> 3e ?3a ?c5 ?40 ? *	cfneg32cc	mvfx12, ?mvfx10
! 00000624 <int_arith\+0x34> 1e ?3f ?85 ?40 ? *	cfneg32ne	mvfx8, ?mvfx15
! 00000628 <int_arith\+0x38> de ?3b ?65 ?40 ? *	cfneg32le	mvfx6, ?mvfx11
! 0000062c <int_arith\+0x3c> 4e ?39 ?25 ?60 ? *	cfneg64mi	mvdx2, ?mvdx9
! 00000630 <int_arith\+0x40> 0e ?3f ?55 ?60 ? *	cfneg64eq	mvdx5, ?mvdx15
! 00000634 <int_arith\+0x44> ae ?34 ?95 ?60 ? *	cfneg64ge	mvdx9, ?mvdx4
! 00000638 <int_arith\+0x48> ee ?38 ?35 ?60 ? *	cfneg64	mvdx3, ?mvdx8
! 0000063c <int_arith\+0x4c> de ?32 ?75 ?60 ? *	cfneg64le	mvdx7, ?mvdx2
! 00000640 <int_arith\+0x50> 1e ?36 ?c5 ?8b ? *	cfadd32ne	mvfx12, ?mvfx6, ?mvfx11
! 00000644 <int_arith\+0x54> 7e ?3e ?55 ?83 ? *	cfadd32vc	mvfx5, ?mvfx14, ?mvfx3
! 00000648 <int_arith\+0x58> ae ?38 ?15 ?8f ? *	cfadd32ge	mvfx1, ?mvfx8, ?mvfx15
! 0000064c <int_arith\+0x5c> 6e ?34 ?b5 ?82 ? *	cfadd32vs	mvfx11, ?mvfx4, ?mvfx2
! 00000650 <int_arith\+0x60> 0e ?3f ?55 ?8a ? *	cfadd32eq	mvfx5, ?mvfx15, ?mvfx10
! 00000654 <int_arith\+0x64> 4e ?33 ?e5 ?a8 ? *	cfadd64mi	mvdx14, ?mvdx3, ?mvdx8
! 00000658 <int_arith\+0x68> 7e ?31 ?25 ?ac ? *	cfadd64vc	mvdx2, ?mvdx1, ?mvdx12
! 0000065c <int_arith\+0x6c> be ?37 ?05 ?a5 ? *	cfadd64lt	mvdx0, ?mvdx7, ?mvdx5
! 00000660 <int_arith\+0x70> 3e ?3a ?c5 ?a1 ? *	cfadd64cc	mvdx12, ?mvdx10, ?mvdx1
! 00000664 <int_arith\+0x74> ee ?36 ?d5 ?ab ? *	cfadd64	mvdx13, ?mvdx6, ?mvdx11
! 00000668 <int_arith\+0x78> 2e ?30 ?95 ?c5 ? *	cfsub32cs	mvfx9, ?mvfx0, ?mvfx5
! 0000066c <int_arith\+0x7c> ae ?34 ?95 ?ce ? *	cfsub32ge	mvfx9, ?mvfx4, ?mvfx14
! 00000670 <int_arith\+0x80> 8e ?37 ?d5 ?c2 ? *	cfsub32hi	mvfx13, ?mvfx7, ?mvfx2
! 00000674 <int_arith\+0x84> ce ?3b ?65 ?c0 ? *	cfsub32gt	mvfx6, ?mvfx11, ?mvfx0
! 00000678 <int_arith\+0x88> 5e ?33 ?e5 ?cc ? *	cfsub32pl	mvfx14, ?mvfx3, ?mvfx12
! 0000067c <int_arith\+0x8c> 1e ?3f ?85 ?ed ? *	cfsub64ne	mvdx8, ?mvdx15, ?mvdx13
! 00000680 <int_arith\+0x90> be ?32 ?45 ?e9 ? *	cfsub64lt	mvdx4, ?mvdx2, ?mvdx9
! 00000684 <int_arith\+0x94> 5e ?3a ?f5 ?e9 ? *	cfsub64pl	mvdx15, ?mvdx10, ?mvdx9
! 00000688 <int_arith\+0x98> ee ?38 ?35 ?ed ? *	cfsub64	mvdx3, ?mvdx8, ?mvdx13
! 0000068c <int_arith\+0x9c> 2e ?3c ?15 ?e6 ? *	cfsub64cs	mvdx1, ?mvdx12, ?mvdx6
! 00000690 <int_arith\+0xa0> 0e ?15 ?75 ?0e ? *	cfmul32eq	mvfx7, ?mvfx5, ?mvfx14
! 00000694 <int_arith\+0xa4> ce ?11 ?a5 ?08 ? *	cfmul32gt	mvfx10, ?mvfx1, ?mvfx8
! 00000698 <int_arith\+0xa8> de ?1b ?65 ?04 ? *	cfmul32le	mvfx6, ?mvfx11, ?mvfx4
! 0000069c <int_arith\+0xac> 9e ?15 ?05 ?0f ? *	cfmul32ls	mvfx0, ?mvfx5, ?mvfx15
! 000006a0 <int_arith\+0xb0> 9e ?1e ?45 ?03 ? *	cfmul32ls	mvfx4, ?mvfx14, ?mvfx3
! 000006a4 <int_arith\+0xb4> de ?12 ?75 ?21 ? *	cfmul64le	mvdx7, ?mvdx2, ?mvdx1
! 000006a8 <int_arith\+0xb8> 6e ?10 ?b5 ?27 ? *	cfmul64vs	mvdx11, ?mvdx0, ?mvdx7
! 000006ac <int_arith\+0xbc> ee ?1c ?35 ?2a ? *	cfmul64	mvdx3, ?mvdx12, ?mvdx10
! 000006b0 <int_arith\+0xc0> 8e ?1d ?f5 ?26 ? *	cfmul64hi	mvdx15, ?mvdx13, ?mvdx6
! 000006b4 <int_arith\+0xc4> 4e ?19 ?25 ?20 ? *	cfmul64mi	mvdx2, ?mvdx9, ?mvdx0
! 000006b8 <int_arith\+0xc8> ee ?19 ?a5 ?44 ? *	cfmac32	mvfx10, ?mvfx9, ?mvfx4
! 000006bc <int_arith\+0xcc> 3e ?1d ?85 ?47 ? *	cfmac32cc	mvfx8, ?mvfx13, ?mvfx7
! 000006c0 <int_arith\+0xd0> 1e ?16 ?c5 ?4b ? *	cfmac32ne	mvfx12, ?mvfx6, ?mvfx11
! 000006c4 <int_arith\+0xd4> 7e ?1e ?55 ?43 ? *	cfmac32vc	mvfx5, ?mvfx14, ?mvfx3
! 000006c8 <int_arith\+0xd8> ae ?18 ?15 ?4f ? *	cfmac32ge	mvfx1, ?mvfx8, ?mvfx15
! 000006cc <int_arith\+0xdc> 6e ?14 ?b5 ?62 ? *	cfmsc32vs	mvfx11, ?mvfx4, ?mvfx2
! 000006d0 <int_arith\+0xe0> 0e ?1f ?55 ?6a ? *	cfmsc32eq	mvfx5, ?mvfx15, ?mvfx10
! 000006d4 <int_arith\+0xe4> 4e ?13 ?e5 ?68 ? *	cfmsc32mi	mvfx14, ?mvfx3, ?mvfx8
! 000006d8 <int_arith\+0xe8> 7e ?11 ?25 ?6c ? *	cfmsc32vc	mvfx2, ?mvfx1, ?mvfx12
! 000006dc <int_arith\+0xec> be ?17 ?05 ?65 ? *	cfmsc32lt	mvfx0, ?mvfx7, ?mvfx5
  # acc_arith:
! 000006e0 <acc_arith> 3e ?01 ?a6 ?08 ? *	cfmadd32cc	mvax0, ?mvfx10, ?mvfx1, ?mvfx8
! 000006e4 <acc_arith\+0x4> ee ?0b ?66 ?44 ? *	cfmadd32	mvax2, ?mvfx6, ?mvfx11, ?mvfx4
! 000006e8 <acc_arith\+0x8> 2e ?05 ?06 ?2f ? *	cfmadd32cs	mvax1, ?mvfx0, ?mvfx5, ?mvfx15
! 000006ec <acc_arith\+0xc> ae ?0e ?46 ?43 ? *	cfmadd32ge	mvax2, ?mvfx4, ?mvfx14, ?mvfx3
! 000006f0 <acc_arith\+0x10> 8e ?02 ?76 ?61 ? *	cfmadd32hi	mvax3, ?mvfx7, ?mvfx2, ?mvfx1
! 000006f4 <acc_arith\+0x14> ce ?10 ?b6 ?07 ? *	cfmsub32gt	mvax0, ?mvfx11, ?mvfx0, ?mvfx7
! 000006f8 <acc_arith\+0x18> 5e ?1c ?36 ?4a ? *	cfmsub32pl	mvax2, ?mvfx3, ?mvfx12, ?mvfx10
! 000006fc <acc_arith\+0x1c> 1e ?1d ?f6 ?26 ? *	cfmsub32ne	mvax1, ?mvfx15, ?mvfx13, ?mvfx6
! 00000700 <acc_arith\+0x20> be ?19 ?26 ?40 ? *	cfmsub32lt	mvax2, ?mvfx2, ?mvfx9, ?mvfx0
! 00000704 <acc_arith\+0x24> 5e ?19 ?a6 ?64 ? *	cfmsub32pl	mvax3, ?mvfx10, ?mvfx9, ?mvfx4
! 00000708 <acc_arith\+0x28> ee ?2d ?16 ?67 ? *	cfmadda32	mvax3, ?mvax1, ?mvfx13, ?mvfx7
! 0000070c <acc_arith\+0x2c> 2e ?26 ?26 ?6b ? *	cfmadda32cs	mvax3, ?mvax2, ?mvfx6, ?mvfx11
! 00000710 <acc_arith\+0x30> 0e ?2e ?36 ?23 ? *	cfmadda32eq	mvax1, ?mvax3, ?mvfx14, ?mvfx3
! 00000714 <acc_arith\+0x34> ce ?28 ?36 ?2f ? *	cfmadda32gt	mvax1, ?mvax3, ?mvfx8, ?mvfx15
! 00000718 <acc_arith\+0x38> de ?24 ?36 ?02 ? *	cfmadda32le	mvax0, ?mvax3, ?mvfx4, ?mvfx2
! 0000071c <acc_arith\+0x3c> 9e ?3f ?16 ?0a ? *	cfmsuba32ls	mvax0, ?mvax1, ?mvfx15, ?mvfx10
! 00000720 <acc_arith\+0x40> 9e ?33 ?16 ?08 ? *	cfmsuba32ls	mvax0, ?mvax1, ?mvfx3, ?mvfx8
! 00000724 <acc_arith\+0x44> de ?31 ?06 ?4c ? *	cfmsuba32le	mvax2, ?mvax0, ?mvfx1, ?mvfx12
! 00000728 <acc_arith\+0x48> 6e ?37 ?06 ?25 ? *	cfmsuba32vs	mvax1, ?mvax0, ?mvfx7, ?mvfx5
! 0000072c <acc_arith\+0x4c> ee ?3a ?06 ?41 ? *	cfmsuba32	mvax2, ?mvax0, ?mvfx10, ?mvfx1
--- 1,477 ----
  #objdump: -dr --prefix-address --show-raw-insn
  #name: Maverick
! #as: -mcpu=ep9312
  
! # Test the instructions of the Cirrus Maverick floating point co-processor
  
  .*: +file format.*arm.*
  
  Disassembly of section .text:
  # load_store:
! 0*0 <load_store> 0d ?9d ?54 ?3f ? *	cfldrseq	mvf5, ?\[sp, #252\]
! 0*4 <load_store\+0x4> 4d ?9b ?e4 ?12 ? *	cfldrsmi	mvf14, ?\[fp, #72\]
! 0*8 <load_store\+0x8> 7d ?1c ?24 ?3c ? *	cfldrsvc	mvf2, ?\[ip, -#240\]
! 0*c <load_store\+0xc> bd ?9a ?04 ?3f ? *	cfldrslt	mvf0, ?\[sl, #252\]
! 0*10 <load_store\+0x10> cd ?9b ?a4 ?12 ? *	cfldrsgt	mvf10, ?\[fp, #72\]
! 0*14 <load_store\+0x14> dd ?3c ?64 ?3c ? *	cfldrsle	mvf6, ?\[ip, -#240\]!
! 0*18 <load_store\+0x18> 9d ?ba ?04 ?3f ? *	cfldrsls	mvf0, ?\[sl, #252\]!
! 0*1c <load_store\+0x1c> 4d ?bb ?e4 ?12 ? *	cfldrsmi	mvf14, ?\[fp, #72\]!
! 0*20 <load_store\+0x20> 7d ?3c ?24 ?3c ? *	cfldrsvc	mvf2, ?\[ip, -#240\]!
! 0*24 <load_store\+0x24> bd ?ba ?04 ?3f ? *	cfldrslt	mvf0, ?\[sl, #252\]!
! 0*28 <load_store\+0x28> cc ?bb ?a4 ?12 ? *	cfldrsgt	mvf10, ?\[fp\], #72
! 0*2c <load_store\+0x2c> dc ?3c ?64 ?3c ? *	cfldrsle	mvf6, ?\[ip\], -#240
! 0*30 <load_store\+0x30> 9c ?ba ?04 ?3f ? *	cfldrsls	mvf0, ?\[sl\], #252
! 0*34 <load_store\+0x34> 4c ?bb ?e4 ?12 ? *	cfldrsmi	mvf14, ?\[fp\], #72
! 0*38 <load_store\+0x38> 7c ?3c ?24 ?3c ? *	cfldrsvc	mvf2, ?\[ip\], -#240
! 0*3c <load_store\+0x3c> bd ?da ?04 ?3f ? *	cfldrdlt	mvd0, ?\[sl, #252\]
! 0*40 <load_store\+0x40> cd ?db ?a4 ?12 ? *	cfldrdgt	mvd10, ?\[fp, #72\]
! 0*44 <load_store\+0x44> dd ?5c ?64 ?3c ? *	cfldrdle	mvd6, ?\[ip, -#240\]
! 0*48 <load_store\+0x48> 9d ?da ?04 ?3f ? *	cfldrdls	mvd0, ?\[sl, #252\]
! 0*4c <load_store\+0x4c> 4d ?db ?e4 ?12 ? *	cfldrdmi	mvd14, ?\[fp, #72\]
! 0*50 <load_store\+0x50> 7d ?7c ?24 ?3c ? *	cfldrdvc	mvd2, ?\[ip, -#240\]!
! 0*54 <load_store\+0x54> bd ?fa ?04 ?3f ? *	cfldrdlt	mvd0, ?\[sl, #252\]!
! 0*58 <load_store\+0x58> cd ?fb ?a4 ?12 ? *	cfldrdgt	mvd10, ?\[fp, #72\]!
! 0*5c <load_store\+0x5c> dd ?7c ?64 ?3c ? *	cfldrdle	mvd6, ?\[ip, -#240\]!
! 0*60 <load_store\+0x60> 9d ?fa ?04 ?3f ? *	cfldrdls	mvd0, ?\[sl, #252\]!
! 0*64 <load_store\+0x64> 4c ?fb ?e4 ?12 ? *	cfldrdmi	mvd14, ?\[fp\], #72
! 0*68 <load_store\+0x68> 7c ?7c ?24 ?3c ? *	cfldrdvc	mvd2, ?\[ip\], -#240
! 0*6c <load_store\+0x6c> bc ?fa ?04 ?3f ? *	cfldrdlt	mvd0, ?\[sl\], #252
! 0*70 <load_store\+0x70> cc ?fb ?a4 ?12 ? *	cfldrdgt	mvd10, ?\[fp\], #72
! 0*74 <load_store\+0x74> dc ?7c ?64 ?3c ? *	cfldrdle	mvd6, ?\[ip\], -#240
! 0*78 <load_store\+0x78> 9d ?9a ?05 ?3f ? *	cfldr32ls	mvfx0, ?\[sl, #252\]
! 0*7c <load_store\+0x7c> 4d ?9b ?e5 ?12 ? *	cfldr32mi	mvfx14, ?\[fp, #72\]
! 0*80 <load_store\+0x80> 7d ?1c ?25 ?3c ? *	cfldr32vc	mvfx2, ?\[ip, -#240\]
! 0*84 <load_store\+0x84> bd ?9a ?05 ?3f ? *	cfldr32lt	mvfx0, ?\[sl, #252\]
! 0*88 <load_store\+0x88> cd ?9b ?a5 ?12 ? *	cfldr32gt	mvfx10, ?\[fp, #72\]
! 0*8c <load_store\+0x8c> dd ?3c ?65 ?3c ? *	cfldr32le	mvfx6, ?\[ip, -#240\]!
! 0*90 <load_store\+0x90> 9d ?ba ?05 ?3f ? *	cfldr32ls	mvfx0, ?\[sl, #252\]!
! 0*94 <load_store\+0x94> 4d ?bb ?e5 ?12 ? *	cfldr32mi	mvfx14, ?\[fp, #72\]!
! 0*98 <load_store\+0x98> 7d ?3c ?25 ?3c ? *	cfldr32vc	mvfx2, ?\[ip, -#240\]!
! 0*9c <load_store\+0x9c> bd ?ba ?05 ?3f ? *	cfldr32lt	mvfx0, ?\[sl, #252\]!
! 0*a0 <load_store\+0xa0> cc ?bb ?a5 ?12 ? *	cfldr32gt	mvfx10, ?\[fp\], #72
! 0*a4 <load_store\+0xa4> dc ?3c ?65 ?3c ? *	cfldr32le	mvfx6, ?\[ip\], -#240
! 0*a8 <load_store\+0xa8> 9c ?ba ?05 ?3f ? *	cfldr32ls	mvfx0, ?\[sl\], #252
! 0*ac <load_store\+0xac> 4c ?bb ?e5 ?12 ? *	cfldr32mi	mvfx14, ?\[fp\], #72
! 0*b0 <load_store\+0xb0> 7c ?3c ?25 ?3c ? *	cfldr32vc	mvfx2, ?\[ip\], -#240
! 0*b4 <load_store\+0xb4> bd ?da ?05 ?3f ? *	cfldr64lt	mvdx0, ?\[sl, #252\]
! 0*b8 <load_store\+0xb8> cd ?db ?a5 ?12 ? *	cfldr64gt	mvdx10, ?\[fp, #72\]
! 0*bc <load_store\+0xbc> dd ?5c ?65 ?3c ? *	cfldr64le	mvdx6, ?\[ip, -#240\]
! 0*c0 <load_store\+0xc0> 9d ?da ?05 ?3f ? *	cfldr64ls	mvdx0, ?\[sl, #252\]
! 0*c4 <load_store\+0xc4> 4d ?db ?e5 ?12 ? *	cfldr64mi	mvdx14, ?\[fp, #72\]
! 0*c8 <load_store\+0xc8> 7d ?7c ?25 ?3c ? *	cfldr64vc	mvdx2, ?\[ip, -#240\]!
! 0*cc <load_store\+0xcc> bd ?fa ?05 ?3f ? *	cfldr64lt	mvdx0, ?\[sl, #252\]!
! 0*d0 <load_store\+0xd0> cd ?fb ?a5 ?12 ? *	cfldr64gt	mvdx10, ?\[fp, #72\]!
! 0*d4 <load_store\+0xd4> dd ?7c ?65 ?3c ? *	cfldr64le	mvdx6, ?\[ip, -#240\]!
! 0*d8 <load_store\+0xd8> 9d ?fa ?05 ?3f ? *	cfldr64ls	mvdx0, ?\[sl, #252\]!
! 0*dc <load_store\+0xdc> 4c ?fb ?e5 ?12 ? *	cfldr64mi	mvdx14, ?\[fp\], #72
! 0*e0 <load_store\+0xe0> 7c ?7c ?25 ?3c ? *	cfldr64vc	mvdx2, ?\[ip\], -#240
! 0*e4 <load_store\+0xe4> bc ?fa ?05 ?3f ? *	cfldr64lt	mvdx0, ?\[sl\], #252
! 0*e8 <load_store\+0xe8> cc ?fb ?a5 ?12 ? *	cfldr64gt	mvdx10, ?\[fp\], #72
! 0*ec <load_store\+0xec> dc ?7c ?65 ?3c ? *	cfldr64le	mvdx6, ?\[ip\], -#240
! 0*f0 <load_store\+0xf0> 9d ?8a ?04 ?3f ? *	cfstrsls	mvf0, ?\[sl, #252\]
! 0*f4 <load_store\+0xf4> 4d ?8b ?e4 ?12 ? *	cfstrsmi	mvf14, ?\[fp, #72\]
! 0*f8 <load_store\+0xf8> 7d ?0c ?24 ?3c ? *	cfstrsvc	mvf2, ?\[ip, -#240\]
! 0*fc <load_store\+0xfc> bd ?8a ?04 ?3f ? *	cfstrslt	mvf0, ?\[sl, #252\]
! 0*100 <load_store\+0x100> cd ?8b ?a4 ?12 ? *	cfstrsgt	mvf10, ?\[fp, #72\]
! 0*104 <load_store\+0x104> dd ?2c ?64 ?3c ? *	cfstrsle	mvf6, ?\[ip, -#240\]!
! 0*108 <load_store\+0x108> 9d ?aa ?04 ?3f ? *	cfstrsls	mvf0, ?\[sl, #252\]!
! 0*10c <load_store\+0x10c> 4d ?ab ?e4 ?12 ? *	cfstrsmi	mvf14, ?\[fp, #72\]!
! 0*110 <load_store\+0x110> 7d ?2c ?24 ?3c ? *	cfstrsvc	mvf2, ?\[ip, -#240\]!
! 0*114 <load_store\+0x114> bd ?aa ?04 ?3f ? *	cfstrslt	mvf0, ?\[sl, #252\]!
! 0*118 <load_store\+0x118> cc ?ab ?a4 ?12 ? *	cfstrsgt	mvf10, ?\[fp\], #72
! 0*11c <load_store\+0x11c> dc ?2c ?64 ?3c ? *	cfstrsle	mvf6, ?\[ip\], -#240
! 0*120 <load_store\+0x120> 9c ?aa ?04 ?3f ? *	cfstrsls	mvf0, ?\[sl\], #252
! 0*124 <load_store\+0x124> 4c ?ab ?e4 ?12 ? *	cfstrsmi	mvf14, ?\[fp\], #72
! 0*128 <load_store\+0x128> 7c ?2c ?24 ?3c ? *	cfstrsvc	mvf2, ?\[ip\], -#240
! 0*12c <load_store\+0x12c> bd ?ca ?04 ?3f ? *	cfstrdlt	mvd0, ?\[sl, #252\]
! 0*130 <load_store\+0x130> cd ?cb ?a4 ?12 ? *	cfstrdgt	mvd10, ?\[fp, #72\]
! 0*134 <load_store\+0x134> dd ?4c ?64 ?3c ? *	cfstrdle	mvd6, ?\[ip, -#240\]
! 0*138 <load_store\+0x138> 9d ?ca ?04 ?3f ? *	cfstrdls	mvd0, ?\[sl, #252\]
! 0*13c <load_store\+0x13c> 4d ?cb ?e4 ?12 ? *	cfstrdmi	mvd14, ?\[fp, #72\]
! 0*140 <load_store\+0x140> 7d ?6c ?24 ?3c ? *	cfstrdvc	mvd2, ?\[ip, -#240\]!
! 0*144 <load_store\+0x144> bd ?ea ?04 ?3f ? *	cfstrdlt	mvd0, ?\[sl, #252\]!
! 0*148 <load_store\+0x148> cd ?eb ?a4 ?12 ? *	cfstrdgt	mvd10, ?\[fp, #72\]!
! 0*14c <load_store\+0x14c> dd ?6c ?64 ?3c ? *	cfstrdle	mvd6, ?\[ip, -#240\]!
! 0*150 <load_store\+0x150> 9d ?ea ?04 ?3f ? *	cfstrdls	mvd0, ?\[sl, #252\]!
! 0*154 <load_store\+0x154> 4c ?eb ?e4 ?12 ? *	cfstrdmi	mvd14, ?\[fp\], #72
! 0*158 <load_store\+0x158> 7c ?6c ?24 ?3c ? *	cfstrdvc	mvd2, ?\[ip\], -#240
! 0*15c <load_store\+0x15c> bc ?ea ?04 ?3f ? *	cfstrdlt	mvd0, ?\[sl\], #252
! 0*160 <load_store\+0x160> cc ?eb ?a4 ?12 ? *	cfstrdgt	mvd10, ?\[fp\], #72
! 0*164 <load_store\+0x164> dc ?6c ?64 ?3c ? *	cfstrdle	mvd6, ?\[ip\], -#240
! 0*168 <load_store\+0x168> 9d ?8a ?05 ?3f ? *	cfstr32ls	mvfx0, ?\[sl, #252\]
! 0*16c <load_store\+0x16c> 4d ?8b ?e5 ?12 ? *	cfstr32mi	mvfx14, ?\[fp, #72\]
! 0*170 <load_store\+0x170> 7d ?0c ?25 ?3c ? *	cfstr32vc	mvfx2, ?\[ip, -#240\]
! 0*174 <load_store\+0x174> bd ?8a ?05 ?3f ? *	cfstr32lt	mvfx0, ?\[sl, #252\]
! 0*178 <load_store\+0x178> cd ?8b ?a5 ?12 ? *	cfstr32gt	mvfx10, ?\[fp, #72\]
! 0*17c <load_store\+0x17c> dd ?2c ?65 ?3c ? *	cfstr32le	mvfx6, ?\[ip, -#240\]!
! 0*180 <load_store\+0x180> 9d ?aa ?05 ?3f ? *	cfstr32ls	mvfx0, ?\[sl, #252\]!
! 0*184 <load_store\+0x184> 4d ?ab ?e5 ?12 ? *	cfstr32mi	mvfx14, ?\[fp, #72\]!
! 0*188 <load_store\+0x188> 7d ?2c ?25 ?3c ? *	cfstr32vc	mvfx2, ?\[ip, -#240\]!
! 0*18c <load_store\+0x18c> bd ?aa ?05 ?3f ? *	cfstr32lt	mvfx0, ?\[sl, #252\]!
! 0*190 <load_store\+0x190> cc ?ab ?a5 ?12 ? *	cfstr32gt	mvfx10, ?\[fp\], #72
! 0*194 <load_store\+0x194> dc ?2c ?65 ?3c ? *	cfstr32le	mvfx6, ?\[ip\], -#240
! 0*198 <load_store\+0x198> 9c ?aa ?05 ?3f ? *	cfstr32ls	mvfx0, ?\[sl\], #252
! 0*19c <load_store\+0x19c> 4c ?ab ?e5 ?12 ? *	cfstr32mi	mvfx14, ?\[fp\], #72
! 0*1a0 <load_store\+0x1a0> 7c ?2c ?25 ?3c ? *	cfstr32vc	mvfx2, ?\[ip\], -#240
! 0*1a4 <load_store\+0x1a4> bd ?ca ?05 ?3f ? *	cfstr64lt	mvdx0, ?\[sl, #252\]
! 0*1a8 <load_store\+0x1a8> cd ?cb ?a5 ?12 ? *	cfstr64gt	mvdx10, ?\[fp, #72\]
! 0*1ac <load_store\+0x1ac> dd ?4c ?65 ?3c ? *	cfstr64le	mvdx6, ?\[ip, -#240\]
! 0*1b0 <load_store\+0x1b0> 9d ?ca ?05 ?3f ? *	cfstr64ls	mvdx0, ?\[sl, #252\]
! 0*1b4 <load_store\+0x1b4> 4d ?cb ?e5 ?12 ? *	cfstr64mi	mvdx14, ?\[fp, #72\]
! 0*1b8 <load_store\+0x1b8> 7d ?6c ?25 ?3c ? *	cfstr64vc	mvdx2, ?\[ip, -#240\]!
! 0*1bc <load_store\+0x1bc> bd ?ea ?05 ?3f ? *	cfstr64lt	mvdx0, ?\[sl, #252\]!
! 0*1c0 <load_store\+0x1c0> cd ?eb ?a5 ?12 ? *	cfstr64gt	mvdx10, ?\[fp, #72\]!
! 0*1c4 <load_store\+0x1c4> dd ?6c ?65 ?3c ? *	cfstr64le	mvdx6, ?\[ip, -#240\]!
! 0*1c8 <load_store\+0x1c8> 9d ?ea ?05 ?3f ? *	cfstr64ls	mvdx0, ?\[sl, #252\]!
! 0*1cc <load_store\+0x1cc> 4c ?eb ?e5 ?12 ? *	cfstr64mi	mvdx14, ?\[fp\], #72
! 0*1d0 <load_store\+0x1d0> 7c ?6c ?25 ?3c ? *	cfstr64vc	mvdx2, ?\[ip\], -#240
! 0*1d4 <load_store\+0x1d4> bc ?ea ?05 ?3f ? *	cfstr64lt	mvdx0, ?\[sl\], #252
! 0*1d8 <load_store\+0x1d8> cc ?eb ?a5 ?12 ? *	cfstr64gt	mvdx10, ?\[fp\], #72
! 0*1dc <load_store\+0x1dc> dc ?6c ?65 ?3c ? *	cfstr64le	mvdx6, ?\[ip\], -#240
  # move:
! 0*1e0 <move> 9e ?00 ?a4 ?50 ? *	cfmvsrls	mvf0, ?sl
! 0*1e4 <move\+0x4> ee ?0a ?44 ?50 ? *	cfmvsr	mvf10, ?r4
! 0*1e8 <move\+0x8> 4e ?0e ?b4 ?50 ? *	cfmvsrmi	mvf14, ?fp
! 0*1ec <move\+0xc> 8e ?0d ?54 ?50 ? *	cfmvsrhi	mvf13, ?r5
! 0*1f0 <move\+0x10> 2e ?01 ?64 ?50 ? *	cfmvsrcs	mvf1, ?r6
! 0*1f4 <move\+0x14> 6e ?10 ?34 ?50 ? *	cfmvrsvs	r3, ?mvf0
! 0*1f8 <move\+0x18> 7e ?1e ?d4 ?50 ? *	cfmvrsvc	sp, ?mvf14
! 0*1fc <move\+0x1c> 3e ?1a ?e4 ?50 ? *	cfmvrscc	lr, ?mvf10
! 0*200 <move\+0x20> 1e ?1f ?84 ?50 ? *	cfmvrsne	r8, ?mvf15
! 0*204 <move\+0x24> de ?1b ?f4 ?50 ? *	cfmvrsle	pc, ?mvf11
! 0*208 <move\+0x28> 4e ?02 ?34 ?10 ? *	cfmvdlrmi	mvd2, ?r3
! 0*20c <move\+0x2c> 0e ?05 ?d4 ?10 ? *	cfmvdlreq	mvd5, ?sp
! 0*210 <move\+0x30> ae ?09 ?e4 ?10 ? *	cfmvdlrge	mvd9, ?lr
! 0*214 <move\+0x34> ee ?03 ?84 ?10 ? *	cfmvdlr	mvd3, ?r8
! 0*218 <move\+0x38> de ?07 ?f4 ?10 ? *	cfmvdlrle	mvd7, ?pc
! 0*21c <move\+0x3c> 1e ?16 ?64 ?10 ? *	cfmvrdlne	r6, ?mvd6
! 0*220 <move\+0x40> be ?17 ?04 ?10 ? *	cfmvrdllt	r0, ?mvd7
! 0*224 <move\+0x44> 5e ?13 ?74 ?10 ? *	cfmvrdlpl	r7, ?mvd3
! 0*228 <move\+0x48> ce ?11 ?14 ?10 ? *	cfmvrdlgt	r1, ?mvd1
! 0*22c <move\+0x4c> 8e ?1d ?24 ?10 ? *	cfmvrdlhi	r2, ?mvd13
! 0*230 <move\+0x50> 6e ?0b ?64 ?30 ? *	cfmvdhrvs	mvd11, ?r6
! 0*234 <move\+0x54> 2e ?09 ?04 ?30 ? *	cfmvdhrcs	mvd9, ?r0
! 0*238 <move\+0x58> 5e ?0f ?74 ?30 ? *	cfmvdhrpl	mvd15, ?r7
! 0*23c <move\+0x5c> 9e ?04 ?14 ?30 ? *	cfmvdhrls	mvd4, ?r1
! 0*240 <move\+0x60> 3e ?08 ?24 ?30 ? *	cfmvdhrcc	mvd8, ?r2
! 0*244 <move\+0x64> 7e ?11 ?f4 ?30 ? *	cfmvrdhvc	pc, ?mvd1
! 0*248 <move\+0x68> ce ?1b ?94 ?30 ? *	cfmvrdhgt	r9, ?mvd11
! 0*24c <move\+0x6c> 0e ?15 ?a4 ?30 ? *	cfmvrdheq	sl, ?mvd5
! 0*250 <move\+0x70> ee ?1c ?44 ?30 ? *	cfmvrdh	r4, ?mvd12
! 0*254 <move\+0x74> ae ?18 ?b4 ?30 ? *	cfmvrdhge	fp, ?mvd8
! 0*258 <move\+0x78> ee ?0d ?f5 ?10 ? *	cfmv64lr	mvdx13, ?pc
! 0*25c <move\+0x7c> be ?04 ?95 ?10 ? *	cfmv64lrlt	mvdx4, ?r9
! 0*260 <move\+0x80> 9e ?00 ?a5 ?10 ? *	cfmv64lrls	mvdx0, ?sl
! 0*264 <move\+0x84> ee ?0a ?45 ?10 ? *	cfmv64lr	mvdx10, ?r4
! 0*268 <move\+0x88> 4e ?0e ?b5 ?10 ? *	cfmv64lrmi	mvdx14, ?fp
! 0*26c <move\+0x8c> 8e ?17 ?25 ?10 ? *	cfmvr64lhi	r2, ?mvdx7
! 0*270 <move\+0x90> 2e ?1c ?c5 ?10 ? *	cfmvr64lcs	ip, ?mvdx12
! 0*274 <move\+0x94> 6e ?10 ?35 ?10 ? *	cfmvr64lvs	r3, ?mvdx0
! 0*278 <move\+0x98> 7e ?1e ?d5 ?10 ? *	cfmvr64lvc	sp, ?mvdx14
! 0*27c <move\+0x9c> 3e ?1a ?e5 ?10 ? *	cfmvr64lcc	lr, ?mvdx10
! 0*280 <move\+0xa0> 1e ?08 ?25 ?30 ? *	cfmv64hrne	mvdx8, ?r2
! 0*284 <move\+0xa4> de ?06 ?c5 ?30 ? *	cfmv64hrle	mvdx6, ?ip
! 0*288 <move\+0xa8> 4e ?02 ?35 ?30 ? *	cfmv64hrmi	mvdx2, ?r3
! 0*28c <move\+0xac> 0e ?05 ?d5 ?30 ? *	cfmv64hreq	mvdx5, ?sp
! 0*290 <move\+0xb0> ae ?09 ?e5 ?30 ? *	cfmv64hrge	mvdx9, ?lr
! 0*294 <move\+0xb4> ee ?18 ?b5 ?30 ? *	cfmvr64h	fp, ?mvdx8
! 0*298 <move\+0xb8> de ?12 ?55 ?30 ? *	cfmvr64hle	r5, ?mvdx2
! 0*29c <move\+0xbc> 1e ?16 ?65 ?30 ? *	cfmvr64hne	r6, ?mvdx6
! 0*2a0 <move\+0xc0> be ?17 ?05 ?30 ? *	cfmvr64hlt	r0, ?mvdx7
! 0*2a4 <move\+0xc4> 5e ?13 ?75 ?30 ? *	cfmvr64hpl	r7, ?mvdx3
! 0*2a8 <move\+0xc8> ce ?11 ?06 ?11 ? *	cfmval32gt	mvax1, ?mvfx1
! 0*2ac <move\+0xcc> 8e ?1d ?06 ?13 ? *	cfmval32hi	mvax3, ?mvfx13
! 0*2b0 <move\+0xd0> 6e ?14 ?06 ?13 ? *	cfmval32vs	mvax3, ?mvfx4
! 0*2b4 <move\+0xd4> 2e ?10 ?06 ?11 ? *	cfmval32cs	mvax1, ?mvfx0
! 0*2b8 <move\+0xd8> 5e ?1a ?06 ?13 ? *	cfmval32pl	mvax3, ?mvfx10
! 0*2bc <move\+0xdc> 9e ?01 ?06 ?14 ? *	cfmv32alls	mvfx4, ?mvax1
! 0*2c0 <move\+0xe0> 3e ?03 ?06 ?18 ? *	cfmv32alcc	mvfx8, ?mvax3
! 0*2c4 <move\+0xe4> 7e ?03 ?06 ?12 ? *	cfmv32alvc	mvfx2, ?mvax3
! 0*2c8 <move\+0xe8> ce ?01 ?06 ?16 ? *	cfmv32algt	mvfx6, ?mvax1
! 0*2cc <move\+0xec> 0e ?03 ?06 ?17 ? *	cfmv32aleq	mvfx7, ?mvax3
! 0*2d0 <move\+0xf0> ee ?1c ?06 ?32 ? *	cfmvam32	mvax2, ?mvfx12
! 0*2d4 <move\+0xf4> ae ?18 ?06 ?33 ? *	cfmvam32ge	mvax3, ?mvfx8
! 0*2d8 <move\+0xf8> ee ?16 ?06 ?32 ? *	cfmvam32	mvax2, ?mvfx6
! 0*2dc <move\+0xfc> be ?12 ?06 ?32 ? *	cfmvam32lt	mvax2, ?mvfx2
! 0*2e0 <move\+0x100> 9e ?15 ?06 ?30 ? *	cfmvam32ls	mvax0, ?mvfx5
! 0*2e4 <move\+0x104> ee ?02 ?06 ?3a ? *	cfmv32am	mvfx10, ?mvax2
! 0*2e8 <move\+0x108> 4e ?03 ?06 ?3e ? *	cfmv32ammi	mvfx14, ?mvax3
! 0*2ec <move\+0x10c> 8e ?02 ?06 ?3d ? *	cfmv32amhi	mvfx13, ?mvax2
! 0*2f0 <move\+0x110> 2e ?02 ?06 ?31 ? *	cfmv32amcs	mvfx1, ?mvax2
! 0*2f4 <move\+0x114> 6e ?00 ?06 ?3b ? *	cfmv32amvs	mvfx11, ?mvax0
! 0*2f8 <move\+0x118> 7e ?1e ?06 ?53 ? *	cfmvah32vc	mvax3, ?mvfx14
! 0*2fc <move\+0x11c> 3e ?1a ?06 ?50 ? *	cfmvah32cc	mvax0, ?mvfx10
! 0*300 <move\+0x120> 1e ?1f ?06 ?51 ? *	cfmvah32ne	mvax1, ?mvfx15
! 0*304 <move\+0x124> de ?1b ?06 ?50 ? *	cfmvah32le	mvax0, ?mvfx11
! 0*308 <move\+0x128> 4e ?19 ?06 ?50 ? *	cfmvah32mi	mvax0, ?mvfx9
! 0*30c <move\+0x12c> 0e ?03 ?06 ?55 ? *	cfmv32aheq	mvfx5, ?mvax3
! 0*310 <move\+0x130> ae ?00 ?06 ?59 ? *	cfmv32ahge	mvfx9, ?mvax0
! 0*314 <move\+0x134> ee ?01 ?06 ?53 ? *	cfmv32ah	mvfx3, ?mvax1
! 0*318 <move\+0x138> de ?00 ?06 ?57 ? *	cfmv32ahle	mvfx7, ?mvax0
! 0*31c <move\+0x13c> 1e ?00 ?06 ?5c ? *	cfmv32ahne	mvfx12, ?mvax0
! 0*320 <move\+0x140> be ?17 ?06 ?70 ? *	cfmva32lt	mvax0, ?mvfx7
! 0*324 <move\+0x144> 5e ?13 ?06 ?72 ? *	cfmva32pl	mvax2, ?mvfx3
! 0*328 <move\+0x148> ce ?11 ?06 ?71 ? *	cfmva32gt	mvax1, ?mvfx1
! 0*32c <move\+0x14c> 8e ?1d ?06 ?73 ? *	cfmva32hi	mvax3, ?mvfx13
! 0*330 <move\+0x150> 6e ?14 ?06 ?73 ? *	cfmva32vs	mvax3, ?mvfx4
! 0*334 <move\+0x154> 2e ?00 ?06 ?79 ? *	cfmv32acs	mvfx9, ?mvax0
! 0*338 <move\+0x158> 5e ?02 ?06 ?7f ? *	cfmv32apl	mvfx15, ?mvax2
! 0*33c <move\+0x15c> 9e ?01 ?06 ?74 ? *	cfmv32als	mvfx4, ?mvax1
! 0*340 <move\+0x160> 3e ?03 ?06 ?78 ? *	cfmv32acc	mvfx8, ?mvax3
! 0*344 <move\+0x164> 7e ?03 ?06 ?72 ? *	cfmv32avc	mvfx2, ?mvax3
! 0*348 <move\+0x168> ce ?1b ?06 ?90 ? *	cfmva64gt	mvax0, ?mvdx11
! 0*34c <move\+0x16c> 0e ?15 ?06 ?91 ? *	cfmva64eq	mvax1, ?mvdx5
! 0*350 <move\+0x170> ee ?1c ?06 ?92 ? *	cfmva64	mvax2, ?mvdx12
! 0*354 <move\+0x174> ae ?18 ?06 ?93 ? *	cfmva64ge	mvax3, ?mvdx8
! 0*358 <move\+0x178> ee ?16 ?06 ?92 ? *	cfmva64	mvax2, ?mvdx6
! 0*35c <move\+0x17c> be ?00 ?06 ?94 ? *	cfmv64alt	mvdx4, ?mvax0
! 0*360 <move\+0x180> 9e ?01 ?06 ?90 ? *	cfmv64als	mvdx0, ?mvax1
! 0*364 <move\+0x184> ee ?02 ?06 ?9a ? *	cfmv64a	mvdx10, ?mvax2
! 0*368 <move\+0x188> 4e ?03 ?06 ?9e ? *	cfmv64ami	mvdx14, ?mvax3
! 0*36c <move\+0x18c> 8e ?02 ?06 ?9d ? *	cfmv64ahi	mvdx13, ?mvax2
! 0*370 <move\+0x190> 2e ?1c ?06 ?b0 ? *	cfmvsc32cs	dspsc, ?mvfx12
! 0*374 <move\+0x194> 6e ?10 ?06 ?b0 ? *	cfmvsc32vs	dspsc, ?mvfx0
! 0*378 <move\+0x198> 7e ?1e ?06 ?b0 ? *	cfmvsc32vc	dspsc, ?mvfx14
! 0*37c <move\+0x19c> 3e ?1a ?06 ?b0 ? *	cfmvsc32cc	dspsc, ?mvfx10
! 0*380 <move\+0x1a0> 1e ?1f ?06 ?b0 ? *	cfmvsc32ne	dspsc, ?mvfx15
! 0*384 <move\+0x1a4> de ?00 ?06 ?b6 ? *	cfmv32scle	mvfx6, ?dspsc
! 0*388 <move\+0x1a8> 4e ?00 ?06 ?b2 ? *	cfmv32scmi	mvfx2, ?dspsc
! 0*38c <move\+0x1ac> 0e ?00 ?06 ?b5 ? *	cfmv32sceq	mvfx5, ?dspsc
! 0*390 <move\+0x1b0> ae ?00 ?06 ?b9 ? *	cfmv32scge	mvfx9, ?dspsc
! 0*394 <move\+0x1b4> ee ?00 ?06 ?b3 ? *	cfmv32sc	mvfx3, ?dspsc
! 0*398 <move\+0x1b8> de ?02 ?74 ?00 ? *	cfcpysle	mvf7, ?mvf2
! 0*39c <move\+0x1bc> 1e ?06 ?c4 ?00 ? *	cfcpysne	mvf12, ?mvf6
! 0*3a0 <move\+0x1c0> be ?07 ?04 ?00 ? *	cfcpyslt	mvf0, ?mvf7
! 0*3a4 <move\+0x1c4> 5e ?03 ?e4 ?00 ? *	cfcpyspl	mvf14, ?mvf3
! 0*3a8 <move\+0x1c8> ce ?01 ?a4 ?00 ? *	cfcpysgt	mvf10, ?mvf1
! 0*3ac <move\+0x1cc> 8e ?0d ?f4 ?20 ? *	cfcpydhi	mvd15, ?mvd13
! 0*3b0 <move\+0x1d0> 6e ?04 ?b4 ?20 ? *	cfcpydvs	mvd11, ?mvd4
! 0*3b4 <move\+0x1d4> 2e ?00 ?94 ?20 ? *	cfcpydcs	mvd9, ?mvd0
! 0*3b8 <move\+0x1d8> 5e ?0a ?f4 ?20 ? *	cfcpydpl	mvd15, ?mvd10
! 0*3bc <move\+0x1dc> 9e ?0e ?44 ?20 ? *	cfcpydls	mvd4, ?mvd14
  # conv:
! 0*3c0 <conv> 3e ?0d ?84 ?60 ? *	cfcvtsdcc	mvd8, ?mvf13
! 0*3c4 <conv\+0x4> 7e ?01 ?24 ?60 ? *	cfcvtsdvc	mvd2, ?mvf1
! 0*3c8 <conv\+0x8> ce ?0b ?64 ?60 ? *	cfcvtsdgt	mvd6, ?mvf11
! 0*3cc <conv\+0xc> 0e ?05 ?74 ?60 ? *	cfcvtsdeq	mvd7, ?mvf5
! 0*3d0 <conv\+0x10> ee ?0c ?34 ?60 ? *	cfcvtsd	mvd3, ?mvf12
! 0*3d4 <conv\+0x14> ae ?08 ?14 ?40 ? *	cfcvtdsge	mvf1, ?mvd8
! 0*3d8 <conv\+0x18> ee ?06 ?d4 ?40 ? *	cfcvtds	mvf13, ?mvd6
! 0*3dc <conv\+0x1c> be ?02 ?44 ?40 ? *	cfcvtdslt	mvf4, ?mvd2
! 0*3e0 <conv\+0x20> 9e ?05 ?04 ?40 ? *	cfcvtdsls	mvf0, ?mvd5
! 0*3e4 <conv\+0x24> ee ?09 ?a4 ?40 ? *	cfcvtds	mvf10, ?mvd9
! 0*3e8 <conv\+0x28> 4e ?03 ?e4 ?80 ? *	cfcvt32smi	mvf14, ?mvfx3
! 0*3ec <conv\+0x2c> 8e ?07 ?d4 ?80 ? *	cfcvt32shi	mvf13, ?mvfx7
! 0*3f0 <conv\+0x30> 2e ?0c ?14 ?80 ? *	cfcvt32scs	mvf1, ?mvfx12
! 0*3f4 <conv\+0x34> 6e ?00 ?b4 ?80 ? *	cfcvt32svs	mvf11, ?mvfx0
! 0*3f8 <conv\+0x38> 7e ?0e ?54 ?80 ? *	cfcvt32svc	mvf5, ?mvfx14
! 0*3fc <conv\+0x3c> 3e ?0a ?c4 ?a0 ? *	cfcvt32dcc	mvd12, ?mvfx10
! 0*400 <conv\+0x40> 1e ?0f ?84 ?a0 ? *	cfcvt32dne	mvd8, ?mvfx15
! 0*404 <conv\+0x44> de ?0b ?64 ?a0 ? *	cfcvt32dle	mvd6, ?mvfx11
! 0*408 <conv\+0x48> 4e ?09 ?24 ?a0 ? *	cfcvt32dmi	mvd2, ?mvfx9
! 0*40c <conv\+0x4c> 0e ?0f ?54 ?a0 ? *	cfcvt32deq	mvd5, ?mvfx15
! 0*410 <conv\+0x50> ae ?04 ?94 ?c0 ? *	cfcvt64sge	mvf9, ?mvdx4
! 0*414 <conv\+0x54> ee ?08 ?34 ?c0 ? *	cfcvt64s	mvf3, ?mvdx8
! 0*418 <conv\+0x58> de ?02 ?74 ?c0 ? *	cfcvt64sle	mvf7, ?mvdx2
! 0*41c <conv\+0x5c> 1e ?06 ?c4 ?c0 ? *	cfcvt64sne	mvf12, ?mvdx6
! 0*420 <conv\+0x60> be ?07 ?04 ?c0 ? *	cfcvt64slt	mvf0, ?mvdx7
! 0*424 <conv\+0x64> 5e ?03 ?e4 ?e0 ? *	cfcvt64dpl	mvd14, ?mvdx3
! 0*428 <conv\+0x68> ce ?01 ?a4 ?e0 ? *	cfcvt64dgt	mvd10, ?mvdx1
! 0*42c <conv\+0x6c> 8e ?0d ?f4 ?e0 ? *	cfcvt64dhi	mvd15, ?mvdx13
! 0*430 <conv\+0x70> 6e ?04 ?b4 ?e0 ? *	cfcvt64dvs	mvd11, ?mvdx4
! 0*434 <conv\+0x74> 2e ?00 ?94 ?e0 ? *	cfcvt64dcs	mvd9, ?mvdx0
! 0*438 <conv\+0x78> 5e ?1a ?f5 ?80 ? *	cfcvts32pl	mvfx15, ?mvf10
! 0*43c <conv\+0x7c> 9e ?1e ?45 ?80 ? *	cfcvts32ls	mvfx4, ?mvf14
! 0*440 <conv\+0x80> 3e ?1d ?85 ?80 ? *	cfcvts32cc	mvfx8, ?mvf13
! 0*444 <conv\+0x84> 7e ?11 ?25 ?80 ? *	cfcvts32vc	mvfx2, ?mvf1
! 0*448 <conv\+0x88> ce ?1b ?65 ?80 ? *	cfcvts32gt	mvfx6, ?mvf11
! 0*44c <conv\+0x8c> 0e ?15 ?75 ?a0 ? *	cfcvtd32eq	mvfx7, ?mvd5
! 0*450 <conv\+0x90> ee ?1c ?35 ?a0 ? *	cfcvtd32	mvfx3, ?mvd12
! 0*454 <conv\+0x94> ae ?18 ?15 ?a0 ? *	cfcvtd32ge	mvfx1, ?mvd8
! 0*458 <conv\+0x98> ee ?16 ?d5 ?a0 ? *	cfcvtd32	mvfx13, ?mvd6
! 0*45c <conv\+0x9c> be ?12 ?45 ?a0 ? *	cfcvtd32lt	mvfx4, ?mvd2
! 0*460 <conv\+0xa0> 9e ?15 ?05 ?c0 ? *	cftruncs32ls	mvfx0, ?mvf5
! 0*464 <conv\+0xa4> ee ?19 ?a5 ?c0 ? *	cftruncs32	mvfx10, ?mvf9
! 0*468 <conv\+0xa8> 4e ?13 ?e5 ?c0 ? *	cftruncs32mi	mvfx14, ?mvf3
! 0*46c <conv\+0xac> 8e ?17 ?d5 ?c0 ? *	cftruncs32hi	mvfx13, ?mvf7
! 0*470 <conv\+0xb0> 2e ?1c ?15 ?c0 ? *	cftruncs32cs	mvfx1, ?mvf12
! 0*474 <conv\+0xb4> 6e ?10 ?b5 ?e0 ? *	cftruncd32vs	mvfx11, ?mvd0
! 0*478 <conv\+0xb8> 7e ?1e ?55 ?e0 ? *	cftruncd32vc	mvfx5, ?mvd14
! 0*47c <conv\+0xbc> 3e ?1a ?c5 ?e0 ? *	cftruncd32cc	mvfx12, ?mvd10
! 0*480 <conv\+0xc0> 1e ?1f ?85 ?e0 ? *	cftruncd32ne	mvfx8, ?mvd15
! 0*484 <conv\+0xc4> de ?1b ?65 ?e0 ? *	cftruncd32le	mvfx6, ?mvd11
  # shift:
! 0*488 <shift> 4e ?02 ?05 ?59 ? *	cfrshl32mi	mvfx2, ?mvfx9, ?r0
! 0*48c <shift\+0x4> ee ?0a ?e5 ?59 ? *	cfrshl32	mvfx10, ?mvfx9, ?lr
! 0*490 <shift\+0x8> 3e ?08 ?55 ?5d ? *	cfrshl32cc	mvfx8, ?mvfx13, ?r5
! 0*494 <shift\+0xc> 1e ?0c ?35 ?56 ? *	cfrshl32ne	mvfx12, ?mvfx6, ?r3
! 0*498 <shift\+0x10> 7e ?05 ?45 ?5e ? *	cfrshl32vc	mvfx5, ?mvfx14, ?r4
! 0*49c <shift\+0x14> ae ?01 ?25 ?78 ? *	cfrshl64ge	mvdx1, ?mvdx8, ?r2
! 0*4a0 <shift\+0x18> 6e ?0b ?95 ?74 ? *	cfrshl64vs	mvdx11, ?mvdx4, ?r9
! 0*4a4 <shift\+0x1c> 0e ?05 ?75 ?7f ? *	cfrshl64eq	mvdx5, ?mvdx15, ?r7
! 0*4a8 <shift\+0x20> 4e ?0e ?85 ?73 ? *	cfrshl64mi	mvdx14, ?mvdx3, ?r8
! 0*4ac <shift\+0x24> 7e ?02 ?65 ?71 ? *	cfrshl64vc	mvdx2, ?mvdx1, ?r6
! 0*4b0 <shift\+0x28> be ?07 ?05 ?80 ? *	cfsh32lt	mvfx0, ?mvfx7, ?#-64
! 0*4b4 <shift\+0x2c> 3e ?0a ?c5 ?cc ? *	cfsh32cc	mvfx12, ?mvfx10, ?#-20
! 0*4b8 <shift\+0x30> ee ?06 ?d5 ?48 ? *	cfsh32	mvfx13, ?mvfx6, ?#40
! 0*4bc <shift\+0x34> 2e ?00 ?95 ?ef ? *	cfsh32cs	mvfx9, ?mvfx0, ?#-1
! 0*4c0 <shift\+0x38> ae ?04 ?95 ?28 ? *	cfsh32ge	mvfx9, ?mvfx4, ?#24
! 0*4c4 <shift\+0x3c> 8e ?27 ?d5 ?41 ? *	cfsh64hi	mvdx13, ?mvdx7, ?#33
! 0*4c8 <shift\+0x40> ce ?2b ?65 ?00 ? *	cfsh64gt	mvdx6, ?mvdx11, ?#0
! 0*4cc <shift\+0x44> 5e ?23 ?e5 ?40 ? *	cfsh64pl	mvdx14, ?mvdx3, ?#32
! 0*4d0 <shift\+0x48> 1e ?2f ?85 ?c1 ? *	cfsh64ne	mvdx8, ?mvdx15, ?#-31
! 0*4d4 <shift\+0x4c> be ?22 ?45 ?01 ? *	cfsh64lt	mvdx4, ?mvdx2, ?#1
  # comp:
! 0*4d8 <comp> 5e ?1a ?d4 ?99 ? *	cfcmpspl	sp, ?mvf10, ?mvf9
! 0*4dc <comp\+0x4> ee ?18 ?b4 ?9d ? *	cfcmps	fp, ?mvf8, ?mvf13
! 0*4e0 <comp\+0x8> 2e ?1c ?c4 ?96 ? *	cfcmpscs	ip, ?mvf12, ?mvf6
! 0*4e4 <comp\+0xc> 0e ?15 ?a4 ?9e ? *	cfcmpseq	sl, ?mvf5, ?mvf14
! 0*4e8 <comp\+0x10> ce ?11 ?14 ?98 ? *	cfcmpsgt	r1, ?mvf1, ?mvf8
! 0*4ec <comp\+0x14> de ?1b ?f4 ?b4 ? *	cfcmpdle	pc, ?mvd11, ?mvd4
! 0*4f0 <comp\+0x18> 9e ?15 ?04 ?bf ? *	cfcmpdls	r0, ?mvd5, ?mvd15
! 0*4f4 <comp\+0x1c> 9e ?1e ?e4 ?b3 ? *	cfcmpdls	lr, ?mvd14, ?mvd3
! 0*4f8 <comp\+0x20> de ?12 ?54 ?b1 ? *	cfcmpdle	r5, ?mvd2, ?mvd1
! 0*4fc <comp\+0x24> 6e ?10 ?34 ?b7 ? *	cfcmpdvs	r3, ?mvd0, ?mvd7
! 0*500 <comp\+0x28> ee ?1c ?45 ?9a ? *	cfcmp32	r4, ?mvfx12, ?mvfx10
! 0*504 <comp\+0x2c> 8e ?1d ?25 ?96 ? *	cfcmp32hi	r2, ?mvfx13, ?mvfx6
! 0*508 <comp\+0x30> 4e ?19 ?95 ?90 ? *	cfcmp32mi	r9, ?mvfx9, ?mvfx0
! 0*50c <comp\+0x34> ee ?19 ?75 ?94 ? *	cfcmp32	r7, ?mvfx9, ?mvfx4
! 0*510 <comp\+0x38> 3e ?1d ?85 ?97 ? *	cfcmp32cc	r8, ?mvfx13, ?mvfx7
! 0*514 <comp\+0x3c> 1e ?16 ?65 ?bb ? *	cfcmp64ne	r6, ?mvdx6, ?mvdx11
! 0*518 <comp\+0x40> 7e ?1e ?d5 ?b3 ? *	cfcmp64vc	sp, ?mvdx14, ?mvdx3
! 0*51c <comp\+0x44> ae ?18 ?b5 ?bf ? *	cfcmp64ge	fp, ?mvdx8, ?mvdx15
! 0*520 <comp\+0x48> 6e ?14 ?c5 ?b2 ? *	cfcmp64vs	ip, ?mvdx4, ?mvdx2
! 0*524 <comp\+0x4c> 0e ?1f ?a5 ?ba ? *	cfcmp64eq	sl, ?mvdx15, ?mvdx10
  # fp_arith:
! 0*528 <fp_arith> 4e ?33 ?e4 ?00 ? *	cfabssmi	mvf14, ?mvf3
! 0*52c <fp_arith\+0x4> 8e ?37 ?d4 ?00 ? *	cfabsshi	mvf13, ?mvf7
! 0*530 <fp_arith\+0x8> 2e ?3c ?14 ?00 ? *	cfabsscs	mvf1, ?mvf12
! 0*534 <fp_arith\+0xc> 6e ?30 ?b4 ?00 ? *	cfabssvs	mvf11, ?mvf0
! 0*538 <fp_arith\+0x10> 7e ?3e ?54 ?00 ? *	cfabssvc	mvf5, ?mvf14
! 0*53c <fp_arith\+0x14> 3e ?3a ?c4 ?20 ? *	cfabsdcc	mvd12, ?mvd10
! 0*540 <fp_arith\+0x18> 1e ?3f ?84 ?20 ? *	cfabsdne	mvd8, ?mvd15
! 0*544 <fp_arith\+0x1c> de ?3b ?64 ?20 ? *	cfabsdle	mvd6, ?mvd11
! 0*548 <fp_arith\+0x20> 4e ?39 ?24 ?20 ? *	cfabsdmi	mvd2, ?mvd9
! 0*54c <fp_arith\+0x24> 0e ?3f ?54 ?20 ? *	cfabsdeq	mvd5, ?mvd15
! 0*550 <fp_arith\+0x28> ae ?34 ?94 ?40 ? *	cfnegsge	mvf9, ?mvf4
! 0*554 <fp_arith\+0x2c> ee ?38 ?34 ?40 ? *	cfnegs	mvf3, ?mvf8
! 0*558 <fp_arith\+0x30> de ?32 ?74 ?40 ? *	cfnegsle	mvf7, ?mvf2
! 0*55c <fp_arith\+0x34> 1e ?36 ?c4 ?40 ? *	cfnegsne	mvf12, ?mvf6
! 0*560 <fp_arith\+0x38> be ?37 ?04 ?40 ? *	cfnegslt	mvf0, ?mvf7
! 0*564 <fp_arith\+0x3c> 5e ?33 ?e4 ?60 ? *	cfnegdpl	mvd14, ?mvd3
! 0*568 <fp_arith\+0x40> ce ?31 ?a4 ?60 ? *	cfnegdgt	mvd10, ?mvd1
! 0*56c <fp_arith\+0x44> 8e ?3d ?f4 ?60 ? *	cfnegdhi	mvd15, ?mvd13
! 0*570 <fp_arith\+0x48> 6e ?34 ?b4 ?60 ? *	cfnegdvs	mvd11, ?mvd4
! 0*574 <fp_arith\+0x4c> 2e ?30 ?94 ?60 ? *	cfnegdcs	mvd9, ?mvd0
! 0*578 <fp_arith\+0x50> 5e ?3a ?f4 ?89 ? *	cfaddspl	mvf15, ?mvf10, ?mvf9
! 0*57c <fp_arith\+0x54> ee ?38 ?34 ?8d ? *	cfadds	mvf3, ?mvf8, ?mvf13
! 0*580 <fp_arith\+0x58> 2e ?3c ?14 ?86 ? *	cfaddscs	mvf1, ?mvf12, ?mvf6
! 0*584 <fp_arith\+0x5c> 0e ?35 ?74 ?8e ? *	cfaddseq	mvf7, ?mvf5, ?mvf14
! 0*588 <fp_arith\+0x60> ce ?31 ?a4 ?88 ? *	cfaddsgt	mvf10, ?mvf1, ?mvf8
! 0*58c <fp_arith\+0x64> de ?3b ?64 ?a4 ? *	cfadddle	mvd6, ?mvd11, ?mvd4
! 0*590 <fp_arith\+0x68> 9e ?35 ?04 ?af ? *	cfadddls	mvd0, ?mvd5, ?mvd15
! 0*594 <fp_arith\+0x6c> 9e ?3e ?44 ?a3 ? *	cfadddls	mvd4, ?mvd14, ?mvd3
! 0*598 <fp_arith\+0x70> de ?32 ?74 ?a1 ? *	cfadddle	mvd7, ?mvd2, ?mvd1
! 0*59c <fp_arith\+0x74> 6e ?30 ?b4 ?a7 ? *	cfadddvs	mvd11, ?mvd0, ?mvd7
! 0*5a0 <fp_arith\+0x78> ee ?3c ?34 ?ca ? *	cfsubs	mvf3, ?mvf12, ?mvf10
! 0*5a4 <fp_arith\+0x7c> 8e ?3d ?f4 ?c6 ? *	cfsubshi	mvf15, ?mvf13, ?mvf6
! 0*5a8 <fp_arith\+0x80> 4e ?39 ?24 ?c0 ? *	cfsubsmi	mvf2, ?mvf9, ?mvf0
! 0*5ac <fp_arith\+0x84> ee ?39 ?a4 ?c4 ? *	cfsubs	mvf10, ?mvf9, ?mvf4
! 0*5b0 <fp_arith\+0x88> 3e ?3d ?84 ?c7 ? *	cfsubscc	mvf8, ?mvf13, ?mvf7
! 0*5b4 <fp_arith\+0x8c> 1e ?36 ?c4 ?eb ? *	cfsubdne	mvd12, ?mvd6, ?mvd11
! 0*5b8 <fp_arith\+0x90> 7e ?3e ?54 ?e3 ? *	cfsubdvc	mvd5, ?mvd14, ?mvd3
! 0*5bc <fp_arith\+0x94> ae ?38 ?14 ?ef ? *	cfsubdge	mvd1, ?mvd8, ?mvd15
! 0*5c0 <fp_arith\+0x98> 6e ?34 ?b4 ?e2 ? *	cfsubdvs	mvd11, ?mvd4, ?mvd2
! 0*5c4 <fp_arith\+0x9c> 0e ?3f ?54 ?ea ? *	cfsubdeq	mvd5, ?mvd15, ?mvd10
! 0*5c8 <fp_arith\+0xa0> 4e ?13 ?e4 ?08 ? *	cfmulsmi	mvf14, ?mvf3, ?mvf8
! 0*5cc <fp_arith\+0xa4> 7e ?11 ?24 ?0c ? *	cfmulsvc	mvf2, ?mvf1, ?mvf12
! 0*5d0 <fp_arith\+0xa8> be ?17 ?04 ?05 ? *	cfmulslt	mvf0, ?mvf7, ?mvf5
! 0*5d4 <fp_arith\+0xac> 3e ?1a ?c4 ?01 ? *	cfmulscc	mvf12, ?mvf10, ?mvf1
! 0*5d8 <fp_arith\+0xb0> ee ?16 ?d4 ?0b ? *	cfmuls	mvf13, ?mvf6, ?mvf11
! 0*5dc <fp_arith\+0xb4> 2e ?10 ?94 ?25 ? *	cfmuldcs	mvd9, ?mvd0, ?mvd5
! 0*5e0 <fp_arith\+0xb8> ae ?14 ?94 ?2e ? *	cfmuldge	mvd9, ?mvd4, ?mvd14
! 0*5e4 <fp_arith\+0xbc> 8e ?17 ?d4 ?22 ? *	cfmuldhi	mvd13, ?mvd7, ?mvd2
! 0*5e8 <fp_arith\+0xc0> ce ?1b ?64 ?20 ? *	cfmuldgt	mvd6, ?mvd11, ?mvd0
! 0*5ec <fp_arith\+0xc4> 5e ?13 ?e4 ?2c ? *	cfmuldpl	mvd14, ?mvd3, ?mvd12
  # int_arith:
! 0*5f0 <int_arith> 1e ?3f ?85 ?00 ? *	cfabs32ne	mvfx8, ?mvfx15
! 0*5f4 <int_arith\+0x4> de ?3b ?65 ?00 ? *	cfabs32le	mvfx6, ?mvfx11
! 0*5f8 <int_arith\+0x8> 4e ?39 ?25 ?00 ? *	cfabs32mi	mvfx2, ?mvfx9
! 0*5fc <int_arith\+0xc> 0e ?3f ?55 ?00 ? *	cfabs32eq	mvfx5, ?mvfx15
! 0*600 <int_arith\+0x10> ae ?34 ?95 ?00 ? *	cfabs32ge	mvfx9, ?mvfx4
! 0*604 <int_arith\+0x14> ee ?38 ?35 ?20 ? *	cfabs64	mvdx3, ?mvdx8
! 0*608 <int_arith\+0x18> de ?32 ?75 ?20 ? *	cfabs64le	mvdx7, ?mvdx2
! 0*60c <int_arith\+0x1c> 1e ?36 ?c5 ?20 ? *	cfabs64ne	mvdx12, ?mvdx6
! 0*610 <int_arith\+0x20> be ?37 ?05 ?20 ? *	cfabs64lt	mvdx0, ?mvdx7
! 0*614 <int_arith\+0x24> 5e ?33 ?e5 ?20 ? *	cfabs64pl	mvdx14, ?mvdx3
! 0*618 <int_arith\+0x28> ce ?31 ?a5 ?40 ? *	cfneg32gt	mvfx10, ?mvfx1
! 0*61c <int_arith\+0x2c> 8e ?3d ?f5 ?40 ? *	cfneg32hi	mvfx15, ?mvfx13
! 0*620 <int_arith\+0x30> 6e ?34 ?b5 ?40 ? *	cfneg32vs	mvfx11, ?mvfx4
! 0*624 <int_arith\+0x34> 2e ?30 ?95 ?40 ? *	cfneg32cs	mvfx9, ?mvfx0
! 0*628 <int_arith\+0x38> 5e ?3a ?f5 ?40 ? *	cfneg32pl	mvfx15, ?mvfx10
! 0*62c <int_arith\+0x3c> 9e ?3e ?45 ?60 ? *	cfneg64ls	mvdx4, ?mvdx14
! 0*630 <int_arith\+0x40> 3e ?3d ?85 ?60 ? *	cfneg64cc	mvdx8, ?mvdx13
! 0*634 <int_arith\+0x44> 7e ?31 ?25 ?60 ? *	cfneg64vc	mvdx2, ?mvdx1
! 0*638 <int_arith\+0x48> ce ?3b ?65 ?60 ? *	cfneg64gt	mvdx6, ?mvdx11
! 0*63c <int_arith\+0x4c> 0e ?35 ?75 ?60 ? *	cfneg64eq	mvdx7, ?mvdx5
! 0*640 <int_arith\+0x50> ee ?3c ?35 ?8a ? *	cfadd32	mvfx3, ?mvfx12, ?mvfx10
! 0*644 <int_arith\+0x54> 8e ?3d ?f5 ?86 ? *	cfadd32hi	mvfx15, ?mvfx13, ?mvfx6
! 0*648 <int_arith\+0x58> 4e ?39 ?25 ?80 ? *	cfadd32mi	mvfx2, ?mvfx9, ?mvfx0
! 0*64c <int_arith\+0x5c> ee ?39 ?a5 ?84 ? *	cfadd32	mvfx10, ?mvfx9, ?mvfx4
! 0*650 <int_arith\+0x60> 3e ?3d ?85 ?87 ? *	cfadd32cc	mvfx8, ?mvfx13, ?mvfx7
! 0*654 <int_arith\+0x64> 1e ?36 ?c5 ?ab ? *	cfadd64ne	mvdx12, ?mvdx6, ?mvdx11
! 0*658 <int_arith\+0x68> 7e ?3e ?55 ?a3 ? *	cfadd64vc	mvdx5, ?mvdx14, ?mvdx3
! 0*65c <int_arith\+0x6c> ae ?38 ?15 ?af ? *	cfadd64ge	mvdx1, ?mvdx8, ?mvdx15
! 0*660 <int_arith\+0x70> 6e ?34 ?b5 ?a2 ? *	cfadd64vs	mvdx11, ?mvdx4, ?mvdx2
! 0*664 <int_arith\+0x74> 0e ?3f ?55 ?aa ? *	cfadd64eq	mvdx5, ?mvdx15, ?mvdx10
! 0*668 <int_arith\+0x78> 4e ?33 ?e5 ?c8 ? *	cfsub32mi	mvfx14, ?mvfx3, ?mvfx8
! 0*66c <int_arith\+0x7c> 7e ?31 ?25 ?cc ? *	cfsub32vc	mvfx2, ?mvfx1, ?mvfx12
! 0*670 <int_arith\+0x80> be ?37 ?05 ?c5 ? *	cfsub32lt	mvfx0, ?mvfx7, ?mvfx5
! 0*674 <int_arith\+0x84> 3e ?3a ?c5 ?c1 ? *	cfsub32cc	mvfx12, ?mvfx10, ?mvfx1
! 0*678 <int_arith\+0x88> ee ?36 ?d5 ?cb ? *	cfsub32	mvfx13, ?mvfx6, ?mvfx11
! 0*67c <int_arith\+0x8c> 2e ?30 ?95 ?e5 ? *	cfsub64cs	mvdx9, ?mvdx0, ?mvdx5
! 0*680 <int_arith\+0x90> ae ?34 ?95 ?ee ? *	cfsub64ge	mvdx9, ?mvdx4, ?mvdx14
! 0*684 <int_arith\+0x94> 8e ?37 ?d5 ?e2 ? *	cfsub64hi	mvdx13, ?mvdx7, ?mvdx2
! 0*688 <int_arith\+0x98> ce ?3b ?65 ?e0 ? *	cfsub64gt	mvdx6, ?mvdx11, ?mvdx0
! 0*68c <int_arith\+0x9c> 5e ?33 ?e5 ?ec ? *	cfsub64pl	mvdx14, ?mvdx3, ?mvdx12
! 0*690 <int_arith\+0xa0> 1e ?1f ?85 ?0d ? *	cfmul32ne	mvfx8, ?mvfx15, ?mvfx13
! 0*694 <int_arith\+0xa4> be ?12 ?45 ?09 ? *	cfmul32lt	mvfx4, ?mvfx2, ?mvfx9
! 0*698 <int_arith\+0xa8> 5e ?1a ?f5 ?09 ? *	cfmul32pl	mvfx15, ?mvfx10, ?mvfx9
! 0*69c <int_arith\+0xac> ee ?18 ?35 ?0d ? *	cfmul32	mvfx3, ?mvfx8, ?mvfx13
! 0*6a0 <int_arith\+0xb0> 2e ?1c ?15 ?06 ? *	cfmul32cs	mvfx1, ?mvfx12, ?mvfx6
! 0*6a4 <int_arith\+0xb4> 0e ?15 ?75 ?2e ? *	cfmul64eq	mvdx7, ?mvdx5, ?mvdx14
! 0*6a8 <int_arith\+0xb8> ce ?11 ?a5 ?28 ? *	cfmul64gt	mvdx10, ?mvdx1, ?mvdx8
! 0*6ac <int_arith\+0xbc> de ?1b ?65 ?24 ? *	cfmul64le	mvdx6, ?mvdx11, ?mvdx4
! 0*6b0 <int_arith\+0xc0> 9e ?15 ?05 ?2f ? *	cfmul64ls	mvdx0, ?mvdx5, ?mvdx15
! 0*6b4 <int_arith\+0xc4> 9e ?1e ?45 ?23 ? *	cfmul64ls	mvdx4, ?mvdx14, ?mvdx3
! 0*6b8 <int_arith\+0xc8> de ?12 ?75 ?41 ? *	cfmac32le	mvfx7, ?mvfx2, ?mvfx1
! 0*6bc <int_arith\+0xcc> 6e ?10 ?b5 ?47 ? *	cfmac32vs	mvfx11, ?mvfx0, ?mvfx7
! 0*6c0 <int_arith\+0xd0> ee ?1c ?35 ?4a ? *	cfmac32	mvfx3, ?mvfx12, ?mvfx10
! 0*6c4 <int_arith\+0xd4> 8e ?1d ?f5 ?46 ? *	cfmac32hi	mvfx15, ?mvfx13, ?mvfx6
! 0*6c8 <int_arith\+0xd8> 4e ?19 ?25 ?40 ? *	cfmac32mi	mvfx2, ?mvfx9, ?mvfx0
! 0*6cc <int_arith\+0xdc> ee ?19 ?a5 ?64 ? *	cfmsc32	mvfx10, ?mvfx9, ?mvfx4
! 0*6d0 <int_arith\+0xe0> 3e ?1d ?85 ?67 ? *	cfmsc32cc	mvfx8, ?mvfx13, ?mvfx7
! 0*6d4 <int_arith\+0xe4> 1e ?16 ?c5 ?6b ? *	cfmsc32ne	mvfx12, ?mvfx6, ?mvfx11
! 0*6d8 <int_arith\+0xe8> 7e ?1e ?55 ?63 ? *	cfmsc32vc	mvfx5, ?mvfx14, ?mvfx3
! 0*6dc <int_arith\+0xec> ae ?18 ?15 ?6f ? *	cfmsc32ge	mvfx1, ?mvfx8, ?mvfx15
  # acc_arith:
! 0*6e0 <acc_arith> 6e ?02 ?46 ?69 ? *	cfmadd32vs	mvax3, ?mvfx4, ?mvfx2, ?mvfx9
! 0*6e4 <acc_arith\+0x4> 0e ?0a ?f6 ?29 ? *	cfmadd32eq	mvax1, ?mvfx15, ?mvfx10, ?mvfx9
! 0*6e8 <acc_arith\+0x8> 4e ?08 ?36 ?2d ? *	cfmadd32mi	mvax1, ?mvfx3, ?mvfx8, ?mvfx13
! 0*6ec <acc_arith\+0xc> 7e ?0c ?16 ?06 ? *	cfmadd32vc	mvax0, ?mvfx1, ?mvfx12, ?mvfx6
! 0*6f0 <acc_arith\+0x10> be ?05 ?76 ?0e ? *	cfmadd32lt	mvax0, ?mvfx7, ?mvfx5, ?mvfx14
! 0*6f4 <acc_arith\+0x14> 3e ?11 ?a6 ?08 ? *	cfmsub32cc	mvax0, ?mvfx10, ?mvfx1, ?mvfx8
! 0*6f8 <acc_arith\+0x18> ee ?1b ?66 ?44 ? *	cfmsub32	mvax2, ?mvfx6, ?mvfx11, ?mvfx4
! 0*6fc <acc_arith\+0x1c> 2e ?15 ?06 ?2f ? *	cfmsub32cs	mvax1, ?mvfx0, ?mvfx5, ?mvfx15
! 0*700 <acc_arith\+0x20> ae ?1e ?46 ?43 ? *	cfmsub32ge	mvax2, ?mvfx4, ?mvfx14, ?mvfx3
! 0*704 <acc_arith\+0x24> 8e ?12 ?76 ?61 ? *	cfmsub32hi	mvax3, ?mvfx7, ?mvfx2, ?mvfx1
! 0*708 <acc_arith\+0x28> ce ?20 ?16 ?07 ? *	cfmadda32gt	mvax0, ?mvax1, ?mvfx0, ?mvfx7
! 0*70c <acc_arith\+0x2c> 5e ?2c ?26 ?4a ? *	cfmadda32pl	mvax2, ?mvax2, ?mvfx12, ?mvfx10
! 0*710 <acc_arith\+0x30> 1e ?2d ?36 ?26 ? *	cfmadda32ne	mvax1, ?mvax3, ?mvfx13, ?mvfx6
! 0*714 <acc_arith\+0x34> be ?29 ?06 ?40 ? *	cfmadda32lt	mvax2, ?mvax0, ?mvfx9, ?mvfx0
! 0*718 <acc_arith\+0x38> 5e ?29 ?26 ?64 ? *	cfmadda32pl	mvax3, ?mvax2, ?mvfx9, ?mvfx4
! 0*71c <acc_arith\+0x3c> ee ?3d ?16 ?67 ? *	cfmsuba32	mvax3, ?mvax1, ?mvfx13, ?mvfx7
! 0*720 <acc_arith\+0x40> 2e ?36 ?26 ?6b ? *	cfmsuba32cs	mvax3, ?mvax2, ?mvfx6, ?mvfx11
! 0*724 <acc_arith\+0x44> 0e ?3e ?36 ?23 ? *	cfmsuba32eq	mvax1, ?mvax3, ?mvfx14, ?mvfx3
! 0*728 <acc_arith\+0x48> ce ?38 ?36 ?2f ? *	cfmsuba32gt	mvax1, ?mvax3, ?mvfx8, ?mvfx15
! 0*72c <acc_arith\+0x4c> de ?34 ?36 ?02 ? *	cfmsuba32le	mvax0, ?mvax3, ?mvfx4, ?mvfx2

*** /dev/null	Sat Aug 31 00:31:37 2002
--- test-gen.c	Fri Feb 21 18:52:00 2003
***************
*** 0 ****
--- 1,744 ----
+ #ifndef TEST_GEN_C
+ #define TEST_GEN_C 1
+ 
+ /* Copyright (C) 2000, 2003 Free Software Foundation
+    Contributed by Alexandre Oliva <aoliva at cygnus dot com>
+ 
+    This file 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 2 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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
+ 
+ /* This is a source file with infra-structure to test generators for
+    assemblers and disassemblers.
+ 
+    The strategy to generate testcases is as follows.  We'll output to
+    two streams: one will get the assembly source, and the other will
+    get regexps that match the expected binary patterns.
+ 
+    To generate each instruction, the functions of a func[] are called,
+    each with the corresponding func_arg.  Each function should set
+    members of insn_data, to decide what it's going to output to the
+    assembly source, the corresponding output for the disassembler
+    tester, and the bits to be set in the instruction word.  The
+    strings to be output must have been allocated with strdup() or
+    malloc(), so that they can be freed.  A function may also modify
+    insn_size.  More details in test-gen.c
+ 
+    Because this would have generated too many tests, we have chosen to
+    define ``random'' sequences of numbers/registers, and simply
+    generate each instruction a couple of times, which should get us
+    enough coverage.
+ 
+    In general, test generators should be compiled/run as follows:
+   
+    % gcc test.c -o test
+    % ./test > test.s 2 > test.d
+ 
+    Please note that this file contains a couple of GCC-isms, such as
+    macro varargs (also available in C99, but with a difference syntax)
+    and labeled elements in initializers (so that insn definitions are
+    simpler and safer).
+ 
+    It is assumed that the test generator #includes this file after
+    defining any of the preprocessor macros documented below.  The test
+    generator is supposed to define instructions, at least one group of
+    instructions, optionally, a sequence of groups.
+ 
+    It should also define a main() function that outputs the initial
+    lines of the assembler input and of the test control file, that
+    also contains the disassembler output.  The main() funcion may
+    optionally set skip_list too, before calling output_groups() or
+    output_insns().  */
+ 
+ /* Define to 1 to avoid repeating instructions and to use a simpler
+    register/constant generation mechanism.  This makes it much easier
+    to verify that the generated bit patterns are correct.  */
+ #ifndef SIMPLIFY_OUTPUT
+ #define SIMPLIFY_OUTPUT 0
+ #endif
+ 
+ /* Define to 0 to avoid generating disassembler tests.  */
+ #ifndef DISASSEMBLER_TEST
+ #define DISASSEMBLER_TEST 1
+ #endif
+ 
+ /* Define to the number of times to repeat the generation of each
+    insn.  It's best to use prime numbers, to improve randomization.  */
+ #ifndef INSN_REPEAT
+ #define INSN_REPEAT 5
+ #endif
+ 
+ /* Define in order to get randomization_counter printed, as a comment,
+    in the disassembler output, after each insn is emitted.  */
+ #ifndef OUTPUT_RANDOMIZATION_COUNTER
+ #define OUTPUT_RANDOMIZATION_COUNTER 0
+ #endif
+ 
+ /* Other configuration macros are DEFINED_WORD and DEFINED_FUNC_ARG,
+    see below.  */
+ 
+ #include <stdio.h>
+ #include <string.h>
+ #include <stdlib.h>
+ 
+ /* It is expected that the main program defines the type `word' before
+    includeing this.  */
+ #ifndef DEFINED_WORD
+ typedef unsigned long long word;
+ #endif
+ 
+ /* This struct is used as the output area for each function.  It
+    should store in as_in a pointer to the string to be output to the
+    assembler; in dis_out, the string to be expected in return from the
+    disassembler, and in bits the bits of the instruction word that are
+    enabled by the assembly fragment.  */
+ typedef struct
+ {
+   char * as_in;
+   char * dis_out;
+   word   bits;
+ } insn_data;
+ 
+ #ifndef DEFINED_FUNC_ARG
+ /* This is the struct that feeds information to each function.  You're
+    free to extend it, by `typedef'ing it before including this file,
+    and defining DEFINED_FUNC_ARG.  You may even reorder the fields,
+    but do not remove any of the existing fields.  */
+ typedef struct
+ {
+   int    i1;
+   int    i2;
+   int    i3;
+   void * p1;
+   void * p2;
+   word   w;
+ } func_arg;
+ #endif
+ 
+ /* This is the struct whose arrays define insns.  Each func in the
+    array will be called, in sequence, being given a pointer to the
+    associated arg and a pointer to a zero-initialized output area,
+    that it may fill in.  */
+ typedef struct
+ {
+   int (*    func) (func_arg *, insn_data *);
+   func_arg  arg;
+ } func;
+ 
+ /* Use this to group insns under a name.  */
+ typedef struct
+ {
+   const char * name;
+   func **      insns;
+ } group_t;
+ 
+ /* This is the size of each instruction.  Use `insn_size_bits' instead
+    of `insn_bits' in an insn defition to modify it.  */
+ int insn_size = 4;
+ 
+ /* The offset of the next insn, as expected in the disassembler
+    output.  */
+ int current_offset = 0;
+ 
+ /* The offset and name of the last label to be emitted.  */
+ int last_label_offset = 0;
+ const char * last_label_name = 0;
+ 
+ /* This variable may be initialized in main() to `argv+1', if
+    `argc>1', so that tests are emitted only for instructions that
+    match exactly one of the given command-line arguments.  If it is
+    NULL, tests for all instructions are emitted.  It must be a
+    NULL-terminated array of pointers to strings (just like
+    `argv+1').  */
+ char ** skip_list = 0;
+ 
+ /* This is a counter used to walk the various arrays of ``random''
+    operand generation.  In simplified output mode, it is zeroed after
+    each insn, otherwise it just keeps growing.  */
+ unsigned randomization_counter = 0;
+ 
+ /* Use `define_insn' to create an array of funcs to define an insn,
+    then `insn' to refer to that insn when defining an insn group.  */
+ #define define_insn(insname, funcs...) \
+   func i_ ## insname[] = { funcs, { 0 } }
+ #define insn(insname) (i_ ## insname)
+ 
+ /* Use these to output a comma followed by an optional space, a single
+    space, a plus sign, left and right square brackets and parentheses,
+    all of them properly quoted.  */
+ #define comma  literal_q (", ", ", ?")
+ #define space  literal (" ")
+ #define tab    literal ("\t")
+ #define plus   literal_q ("+", "\\+")
+ #define lsqbkt literal_q ("[", "\\[")
+ #define rsqbkt literal_q ("]", "\\]")
+ #define lparen literal_q ("(", "\\(")
+ #define rparen literal_q (")", "\\)")
+ 
+ /* Use this as a placeholder when you define a macro that expects an
+    argument, but you don't have anything to output there.  */
+ int
+ nothing (func_arg *arg, insn_data *data)
+ #define nothing { nothing }
+ {
+   return 0;
+ }
+ 
+ /* This is to be used in the argument list of define_insn, causing a
+    string to be copied into both the assembly and the expected
+    disassembler output.  It is assumed not to modify the binary
+    encoding of the insn.  */
+ int
+ literal (func_arg *arg, insn_data *data)
+ #define literal(s) { literal, { p1: (s) } }
+ {
+   data->as_in = data->dis_out = strdup ((char *) arg->p1);
+   return 0;
+ }
+ 
+ /* The characters `[', `]', `\\' and `^' must be quoted in the
+    disassembler-output matcher.  If a literal string contains any of
+    these characters, use literal_q instead of literal, and specify the
+    unquoted version (for as input) as the first argument, and the
+    quoted version (for expected disassembler output) as the second
+    one.  */
+ int
+ literal_q (func_arg *arg, insn_data *data)
+ #define literal_q(s,q) { literal_q, { p1: (s), p2: (q) } }
+ {
+   data->as_in = strdup ((char *) arg->p1);
+   data->dis_out = strdup ((char *) arg->p2);
+   return 0;
+ }
+ 
+ /* Given an insn name, check whether it should be skipped or not,
+    depending on skip_list.  Return non-zero if the insn is to be
+    skipped.  */
+ int
+ skip_insn (char *name)
+ {
+   char **test;
+ 
+   if (! skip_list)
+     return 0;
+ 
+   for (test = skip_list; * test; ++ test)
+     if (strcmp (name, * test) == 0)
+       return 0;
+ 
+   return 1;
+ }
+ 
+ /* Use this to emit the actual insn name, with its opcode, in
+    architectures with fixed-length instructions.  */
+ int
+ insn_bits (func_arg *arg, insn_data *data)
+ #define insn_bits(name,bits) \
+   { insn_bits, { p1: # name, w: bits } }
+ {
+   if (skip_insn ((char *) arg->p1))
+     return 1;
+   data->as_in = data->dis_out = strdup ((char *) arg->p1);
+   data->bits = arg->w;
+   return 0;
+ }
+ 
+ /* Use this to emit the insn name and its opcode in architectures
+    without a variable instruction length.  */ 
+ int
+ insn_size_bits (func_arg *arg, insn_data *data)
+ #define insn_size_bits(name,size,bits) \
+   { insn_size_bits, { p1: # name, i1: size, w: bits } }
+ {
+   if (skip_insn ((char *) arg->p1))
+     return 1;
+   data->as_in = data->dis_out = strdup ((char *) arg->p1);
+   data->bits = arg->w;
+   insn_size = arg->i1;
+   return 0;
+ }
+ 
+ /* Use this to advance the random generator by one, in case it is
+    generating repetitive patterns.  It is usually good to arrange that
+    each insn consumes a prime number of ``random'' numbers, or, at
+    least, that it does not consume an exact power of two ``random''
+    numbers.  */
+ int
+ tick_random (func_arg *arg, insn_data *data)
+ #define tick_random { tick_random }
+ {
+   ++ randomization_counter;
+   return 0;
+ }
+ 
+ /* Select the next ``random'' number from the array V of size S, and
+    advance the counter.  */
+ #define get_bits_from_size(V,S) \
+   ((V)[randomization_counter ++ % (S)])
+ 
+ /* Utility macros.  `_get_bits_var', used in some macros below, assume
+    the names of the arrays used to define the ``random'' orders start
+    with `random_order_'.  */
+ #define _get_bits_var(N) (random_order_ ## N)
+ #define _get_bits_size(V) (sizeof (V) / sizeof * (V))
+ 
+ /* Use this within a `func_arg' to select one of the arrays below (or
+    any other array that starts with random_order_N.  */
+ #define mk_get_bits(N) \
+   p2: _get_bits_var (N), i3: _get_bits_size (_get_bits_var (N))
+ 
+ /* Simplified versions of get_bits_from_size for when you have access
+    to the array, so that its size can be implicitly calculated.  */
+ #define get_bits_from(V) get_bits_from_size ((V),_get_bits_size ((V)))
+ #define get_bits(N)      get_bits_from (_get_bits_var (N))
+ 
+ 
+ /* Use `2u' to generate 2-bit unsigned values.  Good for selecting
+    registers randomly from a set of 4 registers.  */
+ unsigned random_order_2u[] =
+   {
+     /* This sequence was generated by hand so that no digit appers more
+        than once in any horizontal or vertical line.  */
+     0, 1, 3, 2,
+     2, 0, 1, 3,
+     1, 3, 2, 0,
+     3, 2, 0, 1
+   };
+ 
+ /* Use `3u' to generate 3-bit unsigned values.  Good for selecting
+    registers randomly from a set of 8 registers.  */
+ unsigned random_order_3u[] =
+   {
+     /* This sequence was generated by:
+        f(k) = 3k mod 8
+        except that the middle pairs were swapped.  */
+     0, 6, 3, 1, 4, 2, 7, 5,
+     /* This sequence was generated by:
+        f(k) = 5k mod 8
+        except that the middle pairs were swapped.  */
+     0, 2, 5, 7, 4, 6, 1, 3,
+   };
+ 
+ /* Use `4u' to generate 4-bit unsigned values.  Good for selecting
+    registers randomly from a set of 16 registers.  */
+ unsigned random_order_4u[] =
+   {
+     /* This sequence was generated by:
+        f(k) = 5k mod 16
+        except that the middle pairs were swapped.  */
+     0,  5, 15, 10, 9,  4, 14,  3,
+     8, 13,  7,  2, 1, 12,  6, 11,
+     /* This sequence was generated by:
+        f(k) = 7k mod 16
+        except that the middle pairs were swapped.  */
+     0,  7,  5, 14,  3, 12, 10, 1,
+     8, 15, 13,  6, 11,  4,  2, 9,
+   };
+ 
+ /* Use `5u' to generate 5-bit unsigned values.  Good for selecting
+    registers randomly from a set of 32 registers.  */
+ unsigned random_order_5u[] =
+   {
+     /* This sequence was generated by:
+        f(k) = (13k) mod 32
+        except that the middle pairs were swapped.  */
+     0, 26, 13,  7, 20, 14,  1, 27,
+     8, 2,  21, 15, 28, 22,  9,  3,
+     16, 10, 29, 23,  4, 30, 17, 11,
+     24,  18, 5, 31, 12, 6,  25, 19
+   };
+ 
+ /* Use `7s' to generate 7-bit signed values.  Good for selecting
+    ``interesting'' constants from -64 to +63.  */
+ int random_order_7s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     0, -1, -64, 63, -32, 32, 24, -20,
+     9, -27, -31, 33, 40, -2, -5, 1
+   };
+ 
+ /* Use `8s' to generate 8-bit signed values.  Good for selecting
+    ``interesting'' constants from -128 to +127.  */
+ int random_order_8s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     0, -1, -128, 127, -32, 32, 24, -20,
+     73, -27, -95, 33, 104, -2, -69, 1
+   };
+ 
+ /* Use `9s' to generate 9-bit signed values.  Good for selecting
+    ``interesting'' constants from -256 to +255.  */
+ int random_order_9s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     0, -1, -256, 255, -64, 64, 72, -40,
+     73, -137, -158, 37, 104, -240, -69, 1
+   };
+ 
+ /* Use `16s' to generate 16-bit signed values.  Good for selecting
+    ``interesting'' constants from -32768 to +32767.  */
+ int random_order_16s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     -32768,
+     32767,
+     (-1 << 15) | (64 << 8) | 32,
+     (64 << 8) | 32,
+     0x1234,
+     (-1 << 15) | 0x8765,
+     0x0180,
+     (-1 << 15) | 0x8001
+ };
+ 
+ /* Use `24s' to generate 24-bit signed values.  Good for selecting
+    ``interesting'' constants from -2^23 to 2^23-1.  */
+ int random_order_24s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     -1 << 23,
+     1 << 23 -1,
+     (-1 << 23) | (((64 << 8) | 32) << 8) | 16,
+     (((64 << 8) | 32) << 8) | 16,
+     0x123456,
+     (-1 << 23) | 0x876543,
+     0x01ff80,
+     (-1 << 23) | 0x80ff01
+ };
+ 
+ /* Use `32s' to generate 32-bit signed values.  Good for selecting
+    ``interesting'' constants from -2^31 to 2^31-1.  */
+ int random_order_32s[] =
+   {
+     /* Sequence generated by hand, to explore limit values and a few
+        intermediate values selected by chance.  Keep the number of
+        intermediate values low, to ensure that the limit values are
+        generated often enough.  */
+     -1 << 31,
+     1 << 31 - 1,
+     (-1 << 31) | (((((64 << 8) | 32) << 8) | 16) << 8) | 8,
+     (((((64 << 8) | 32) << 8) | 16) << 8) | 8,
+     0x12345678,
+     (-1 << 31) | 0x87654321,
+     0x01ffff80,
+     (-1 << 31) | 0x80ffff01
+   };
+ 
+ /* This function computes the number of digits needed to represent a
+    given number.  */
+ unsigned long
+ ulen (unsigned long i, unsigned base)
+ {
+   int count = 0;
+ 
+   if (i == 0)
+     return 1;
+   for (; i > 0; ++ count)
+     i /= base;
+   return count;
+ }
+ 
+ /* Use this to generate a signed constant of the given size, shifted
+    by the given amount, with the specified endianness.  */
+ int
+ signed_constant (func_arg * arg, insn_data * data)
+ #define signed_constant(bits, shift, revert) \
+   { signed_constant, { i1: shift, i2: bits * (revert ? -1 : 1), \
+ 		       mk_get_bits (bits ## s) } }
+ {
+   long val = get_bits_from_size ((unsigned *) arg->p2, arg->i3);
+   int len = (val >= 0 ? ulen (val, 10) : (1 + ulen (-val, 10)));
+   int nbits = (arg->i2 >= 0 ? arg->i2 : -arg->i2);
+   word bits = ((word) val) & (((((word) 1) << (nbits - 1)) << 1) - 1);
+ 
+   data->as_in = data->dis_out = malloc (len + 1);
+   sprintf (data->as_in, "%ld", val);
+   if (arg->i2 < 0)
+     {
+       word rbits = 0;
+ 
+       do
+ 	{
+ 	  rbits <<= 8;
+ 	  rbits |= bits & 0xff;
+ 	  bits >>= 8;
+ 	  nbits -= 8;
+ 	}
+       while (nbits > 0);
+ 
+       bits = rbits;
+     }
+   data->bits = bits << arg->i1;
+ 
+   return 0;
+ }
+ 
+ /* Use this to generate a unsigned constant of the given size, shifted
+    by the given amount, with the specified endianness.  */
+ int
+ unsigned_constant (func_arg * arg, insn_data * data)
+ #define unsigned_constant(bits, shift, revert) \
+   { unsigned_constant, { i1: shift, i2: bits * (revert ? -1 : 1), \
+ 			 mk_get_bits (bits ## s) } }
+ {
+   int nbits = (arg->i2 >= 0 ? arg->i2 : -arg->i2);
+   unsigned long val =
+     get_bits_from_size ((unsigned *) arg->p2, arg->i3)
+     & (((((word) 1) << (nbits - 1)) << 1) - 1);
+   int len = ulen (val, 10);
+   word bits = val;
+ 
+   data->as_in = data->dis_out = malloc (len + 1);
+   sprintf (data->as_in, "%lu", val);
+   if (arg->i2 < 0)
+     {
+       word rbits = 0;
+ 
+       do
+ 	{
+ 	  rbits <<= 8;
+ 	  rbits |= bits & 0xff;
+ 	  bits >>= 8;
+ 	  nbits -= 8;
+ 	}
+       while (nbits > 0);
+ 
+       bits = rbits;
+     }
+   data->bits = bits << arg->i1;
+ 
+   return 0;
+ }
+ 
+ /* Use this to generate an absolute address of the given size, shifted
+    by the given amount, with the specified endianness.  */
+ int
+ absolute_address (func_arg *arg, insn_data *data)
+ #define absolute_address (bits, shift, revert) \
+   { absolute_address, { i1: shift, i2: bits * (revert ? -1 : 1), \
+ 			mk_get_bits (bits ## s) } }
+ {
+   int nbits = (arg->i2 >= 0 ? arg->i2 : -arg->i2);
+   unsigned long val =
+     get_bits_from_size ((unsigned *) arg->p2, arg->i3)
+     & (((((word) 1) << (nbits - 1)) << 1) - 1);
+   word bits = val;
+ 
+   data->as_in = malloc (ulen (val, 10) + 1);
+   sprintf (data->as_in, "%lu", val);
+   data->dis_out = malloc (nbits / 4 + 11);
+   sprintf (data->dis_out, "0*%0*lx <[^>]*>", nbits / 4, val);
+   if (arg->i2 < 0)
+     {
+       word rbits = 0;
+ 
+       do
+ 	{
+ 	  rbits <<= 8;
+ 	  rbits |= bits & 0xff;
+ 	  bits >>= 8;
+ 	  nbits -= 8;
+ 	}
+       while (nbits > 0);
+ 
+       bits = rbits;
+     }
+   data->bits = bits << arg->i1;
+ 
+   return 0;
+ }
+ 
+ /* Use this to generate a register name that starts with a given
+    prefix, and is followed by a number generated by `gen' (see
+    mk_get_bits below).  The register number is shifted `shift' bits
+    left before being stored in the binary insn.  */
+ int
+ reg_p (func_arg *arg, insn_data *data)
+ #define reg_p(prefix,shift,gen) \
+   { reg_p, { i1: (shift), p1: (prefix), gen } }
+ {
+   unsigned reg = get_bits_from_size ((unsigned *) arg->p2, arg->i3);
+   char *regname = (char *) arg->p1;
+ 
+   data->as_in = data->dis_out = malloc (strlen (regname) + ulen (reg, 10) + 1);
+   sprintf (data->as_in, "%s%u", regname, reg);
+   data->bits = reg;
+   data->bits <<= arg->i1;
+   return 0;
+ }
+ 
+ /* Use this to generate a register name taken from an array.  The
+    index into the array `names' is to be produced by `gen', but `mask'
+    may be used to filter out some of the bits before choosing the
+    disassembler output and the bits for the binary insn, shifted left
+    by `shift'.  For example, if registers have canonical names, but
+    can also be referred to by aliases, the array can be n times larger
+    than the actual number of registers, and the mask is then used to
+    pick the canonical name for the disassembler output, and to
+    eliminate the extra bits from the binary output.  */
+ int
+ reg_r (func_arg *arg, insn_data *data)
+ #define reg_r(names,shift,mask,gen) \
+   { reg_r, { i1: (shift), i2: (mask), p1: (names), gen } }
+ {
+   unsigned reg = get_bits_from_size ((unsigned *) arg->p2, arg->i3);
+   
+   data->as_in = strdup (((const char **) arg->p1)[reg]);
+   reg &= arg->i2;
+   data->dis_out = strdup (((const char **) arg->p1)[reg]);
+   data->bits = reg;
+   data->bits <<= arg->i1;
+   return 0;
+ }
+ 
+ /* Given a NULL-terminated array of insns-definitions (pointers to
+    arrays of funcs), output test code for the insns to as_in (assembly
+    input) and dis_out (expected disassembler output).  */
+ void
+ output_insns (func **insn, FILE *as_in, FILE *dis_out)
+ {
+   for (; *insn; ++insn)
+     {
+       insn_data *data;
+       func *parts = *insn;
+       int part_count = 0, r;
+ 
+       /* Figure out how many funcs have to be called.  */
+       while (parts[part_count].func)
+ 	++part_count;
+ 
+       /* Allocate storage for the output area of each func.  */
+       data = (insn_data*) malloc (part_count * sizeof (insn_data));
+ 
+ #if SIMPLIFY_OUTPUT
+       randomization_counter = 0;
+ #else
+       /* Repeat each insn several times.  */
+       for (r = 0; r < INSN_REPEAT; ++r)
+ #endif
+ 	{
+ 	  unsigned saved_rc = randomization_counter;
+ 	  int part;
+ 	  word bits = 0;
+ 
+ 	  for (part = 0; part < part_count; ++part)
+ 	    {
+ 	      /* Zero-initialize the storage.  */
+ 	      data[part].as_in = data[part].dis_out = 0;
+ 	      data[part].bits = 0;
+ 	      /* If a func returns non-zero, skip this line.  */
+ 	      if (parts[part].func (&parts[part].arg, &data[part]))
+ 		goto skip;
+ 	      /* Otherwise, get its output bit pattern into the total
+ 	         bit pattern.  */
+ 	      bits |= data[part].bits;
+ 	    }
+ 	  
+ 	  if (as_in)
+ 	    {
+ 	      /* Output the whole assembly line.  */
+ 	      fputc ('\t', as_in);
+ 	      for (part = 0; part < part_count; ++part)
+ 		if (data[part].as_in)
+ 		  fputs (data[part].as_in, as_in);
+ 	      fputc ('\n', as_in);
+ 	    }
+ 
+ 	  if (dis_out)
+ 	    {
+ 	      /* Output the disassembler expected output line,
+ 	         starting with the offset and the insn binary pattern,
+ 	         just like objdump outputs.  Because objdump sometimes
+ 	         inserts spaces between each byte in the insn binary
+ 	         pattern, make the space optional.  */
+ 	      fprintf (dis_out, "0*%x <", current_offset);
+ 	      if (last_label_name)
+ 		if (current_offset == last_label_offset)
+ 		  fputs (last_label_name, dis_out);
+ 		else
+ 		  fprintf (dis_out, "%s\\+0x%x", last_label_name,
+ 			   current_offset - last_label_offset);
+ 	      else
+ 		fputs ("[^>]*", dis_out);
+ 	      fputs ("> ", dis_out);
+ 	      for (part = insn_size; part-- > 0; )
+ 		fprintf (dis_out, "%02x ?", (int)(bits >> (part * 8)) & 0xff);
+ 	      fputs (" *\t", dis_out);
+ 	      
+ #if DISASSEMBLER_TEST
+ 	      for (part = 0; part < part_count; ++part)
+ 		if (data[part].dis_out)
+ 		  fputs (data[part].dis_out, dis_out);
+ #else
+ 	      /* If we're not testing the DISASSEMBLER, just match
+ 	         anything.  */
+ 	      fputs (".*", dis_out);
+ #endif
+ 	      fputc ('\n', dis_out);
+ #if OUTPUT_RANDOMIZATION_COUNTER
+ 	      fprintf (dis_out, "# %i\n", randomization_counter);
+ #endif
+ 	    }
+ 
+ 	  /* Account for the insn_size bytes we've just output.  */
+ 	  current_offset += insn_size;
+ 
+ 	  /* Release the memory that each func may have allocated.  */
+ 	  for (; part-- > 0;)
+ 	    {
+ 	    skip:
+ 	      if (data[part].as_in)
+ 		free (data[part].as_in);
+ 	      if (data[part].dis_out
+ 		  && data[part].dis_out != data[part].as_in)
+ 		free (data[part].dis_out);
+ 	    }
+ 
+ 	  /* There's nothing random here, don't repeat this insn.  */
+ 	  if (randomization_counter == saved_rc)
+ 	    break;
+ 	}
+ 
+       free (data);
+     }
+ }
+ 
+ /* For each group, output an asm label and the insns of the group.  */
+ void
+ output_groups (group_t group[], FILE *as_in, FILE *dis_out)
+ {
+   for (; group->name; ++group)
+     {
+       fprintf (as_in, "%s:\n", group->name);
+       fprintf (dis_out, "# %s:\n", group->name);
+       last_label_offset = current_offset;
+       last_label_name = group->name;
+       output_insns (group->insns, as_in, dis_out);
+     }
+ }
+ 
+ #endif
*** /dev/null	Sat Aug 31 00:31:37 2002
--- test-example.c	Fri Feb 21 18:49:53 2003
***************
*** 0 ****
--- 1,103 ----
+ /* Copyright (C) 2000, 2003 Free Software Foundation
+    Contributed by Alexandre Oliva <aoliva at cygnus dot com>
+ 
+    This file 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 2 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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
+ 
+ /* Generator of tests for insns introduced in AM33 2.0.
+   
+    See the following file for usage and documentation.  */
+ #include "../all/test-gen.c"
+ 
+ /* Define any char*[]s you may need here.  */
+ char *named_regs[] = { "a", "b", "c", "d" };
+ 
+ /* Define helper macros to generate register accesses here.  */
+ #define namedregs(shift) \
+   reg_r (named_regs, shift, 0x3, mk_get_bits (2u))
+ #define numberedregs(shift) \
+   reg_p ("f", shift, mk_get_bits (2u))
+ 
+ /* Define helper functions here.  */
+ int
+ jmp_cond (func_arg * arg, insn_data * data)
+ #define jmp_cond(shift) { jmp_cond, { i1: shift } }
+ {
+   static const char conds[4][2] = { "z", "n", "g", "l" };
+   unsigned val = get_bits (2u);
+ 
+   data->as_in = data->dis_out = strdup (conds[val]);
+   data->bits = val << arg->i1;
+ 
+   /* Do not forget to return 0, otherwise the insn will be skipped.  */
+   return 0;
+ }
+ 
+ /* Define convenience wrappers to define_insn.  */
+ #define cond_jmp_insn(insname, word, funcs...) \
+   define_insn (insname, \
+ 	       insn_size_bits (insname, 1, word), \
+ 	       jmp_cond (4), \
+ 	       tab, \
+ 	       ## funcs)
+ 
+ /* Define insns.  */
+ cond_jmp_insn (j, 0x40, numberedregs(2), comma, namedregs (0));
+ 
+ /* Define an insn group.  */
+ func *jmp_insns[] =
+   {
+     insn (j),
+     0
+   };
+ 
+ /* Define the set of all groups.  */
+ group_t
+ groups[] =
+   {
+     { "jumps", jmp_insns },
+     { 0 }
+   };
+ 
+ int
+ main (int argc, char *argv[])
+ {
+   FILE *as_in = stdout, *dis_out = stderr;
+ 
+   /* Check whether we're filtering insns.  */
+   if (argc > 1)
+     skip_list = argv + 1;
+ 
+   /* Output assembler header.  */
+   fputs ("\t.text\n"
+ 	 "\t.align\n",
+ 	 as_in);
+   /* Output comments for the testsuite-driver and the initial
+      disassembler output.  */
+   fputs ("#objdump: -dr --prefix-address --show-raw-insn\n"
+ 	 "#name: Foo Digital Processor\n"
+ 	 "#as: -mfood\n"
+ 	 "\n"
+ 	 "# Test the instructions of FooD\n"
+ 	 "\n"
+ 	 ".*: +file format.*food.*\n"
+ 	 "\n"
+ 	 "Disassembly of section .text:\n",
+ 	 dis_out);
+ 
+   /* Now emit all (selected) insns.  */
+   output_groups (groups, as_in, dis_out);
+ 
+   exit (0);
+ }


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]