Switch to GPLv3
[deliverable/binutils-gdb.git] / gas / config / tc-arm.c
index e1cd5fcaa509bc3f08877c74a7f8476814c83adb..fbb7ae2cb4ee7296c8c91c40c123c62db4ebc57b 100644 (file)
@@ -1,6 +1,6 @@
 /* tc-arm.c -- Assemble for the ARM
    Copyright 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003,
-   2004, 2005, 2006
+   2004, 2005, 2006, 2007
    Free Software Foundation, Inc.
    Contributed by Richard Earnshaw (rwe@pegasus.esprit.ec.org)
        Modified by David Taylor (dtaylor@armltd.co.uk)
@@ -12,7 +12,7 @@
 
    GAS 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, or (at your option)
+   the Free Software Foundation; either version 3, or (at your option)
    any later version.
 
    GAS is distributed in the hope that it will be useful,
@@ -555,6 +555,8 @@ struct asm_opcode
 #define OPCODE_MASK    0xfe1fffff
 #define V4_STR_BIT     0x00000020
 
+#define T2_SUBS_PC_LR  0xf3de8f00
+
 #define DATA_OP_SHIFT  21
 
 #define T2_OPCODE_MASK 0xfe1fffff
@@ -2611,6 +2613,7 @@ static void
 s_align (int unused ATTRIBUTE_UNUSED)
 {
   int temp;
+  bfd_boolean fill_p;
   long temp_fill;
   long max_alignment = 15;
 
@@ -2627,16 +2630,25 @@ s_align (int unused ATTRIBUTE_UNUSED)
     {
       input_line_pointer++;
       temp_fill = get_absolute_expression ();
+      fill_p = TRUE;
     }
   else
-    temp_fill = 0;
+    {
+      fill_p = FALSE;
+      temp_fill = 0;
+    }
 
   if (!temp)
     temp = 2;
 
   /* Only make a frag if we HAVE to.  */
   if (temp && !need_pass_2)
-    frag_align (temp, (int) temp_fill, 0);
+    {
+      if (!fill_p && subseg_text_p (now_seg))
+       frag_align_code (temp, 0);
+      else
+       frag_align (temp, (int) temp_fill, 0);
+    }
   demand_empty_rest_of_line ();
 
   record_alignment (now_seg, temp);
@@ -3817,84 +3829,7 @@ s_arm_unwind_raw (int ignored ATTRIBUTE_UNUSED)
 static void
 s_arm_eabi_attribute (int ignored ATTRIBUTE_UNUSED)
 {
-  expressionS exp;
-  bfd_boolean is_string;
-  int tag;
-  unsigned int i = 0;
-  char *s = NULL;
-  char saved_char;
-
-  expression (& exp);
-  if (exp.X_op != O_constant)
-    goto bad;
-
-  tag = exp.X_add_number;
-  if (tag == 4 || tag == 5 || tag == 32 || (tag > 32 && (tag & 1) != 0))
-    is_string = 1;
-  else
-    is_string = 0;
-
-  if (skip_past_comma (&input_line_pointer) == FAIL)
-    goto bad;
-  if (tag == 32 || !is_string)
-    {
-      expression (& exp);
-      if (exp.X_op != O_constant)
-       {
-         as_bad (_("expected numeric constant"));
-         ignore_rest_of_line ();
-         return;
-       }
-      i = exp.X_add_number;
-    }
-  if (tag == Tag_compatibility
-      && skip_past_comma (&input_line_pointer) == FAIL)
-    {
-      as_bad (_("expected comma"));
-      ignore_rest_of_line ();
-      return;
-    }
-  if (is_string)
-    {
-      skip_whitespace(input_line_pointer);
-      if (*input_line_pointer != '"')
-       goto bad_string;
-      input_line_pointer++;
-      s = input_line_pointer;
-      while (*input_line_pointer && *input_line_pointer != '"')
-       input_line_pointer++;
-      if (*input_line_pointer != '"')
-       goto bad_string;
-      saved_char = *input_line_pointer;
-      *input_line_pointer = 0;
-    }
-  else
-    {
-      s = NULL;
-      saved_char = 0;
-    }
-  
-  if (tag == Tag_compatibility)
-    elf32_arm_add_eabi_attr_compat (stdoutput, i, s);
-  else if (is_string)
-    elf32_arm_add_eabi_attr_string (stdoutput, tag, s);
-  else
-    elf32_arm_add_eabi_attr_int (stdoutput, tag, i);
-
-  if (s)
-    {
-      *input_line_pointer = saved_char;
-      input_line_pointer++;
-    }
-  demand_empty_rest_of_line ();
-  return;
-bad_string:
-  as_bad (_("bad string constant"));
-  ignore_rest_of_line ();
-  return;
-bad:
-  as_bad (_("expected <tag> , <value>"));
-  ignore_rest_of_line ();
+  s_vendor_attribute (OBJ_ATTR_PROC);
 }
 #endif /* OBJ_ELF */
 
@@ -5600,7 +5535,13 @@ parse_operands (char *str, const unsigned char *pattern)
        case OP_RVD:   po_reg_or_fail (REG_TYPE_VFD);     break;
         case OP_oRND:
        case OP_RND:   po_reg_or_fail (REG_TYPE_VFD);     break;
-       case OP_RVC:   po_reg_or_fail (REG_TYPE_VFC);     break;
+       case OP_RVC:
+         po_reg_or_goto (REG_TYPE_VFC, coproc_reg);
+         break;
+         /* Also accept generic coprocessor regs for unknown registers.  */
+         coproc_reg:
+         po_reg_or_fail (REG_TYPE_CN);
+         break;
        case OP_RMF:   po_reg_or_fail (REG_TYPE_MVF);     break;
        case OP_RMD:   po_reg_or_fail (REG_TYPE_MVD);     break;
        case OP_RMFX:  po_reg_or_fail (REG_TYPE_MVFX);    break;
@@ -8439,7 +8380,21 @@ do_t_add_sub (void)
          if (inst.size_req == 4
              || (inst.size_req != 2 && !opcode))
            {
-             if (Rs == REG_PC)
+             if (Rd == REG_PC)
+               {
+                 constraint (Rs != REG_LR || inst.instruction != T_MNEM_subs,
+                            _("only SUBS PC, LR, #const allowed"));
+                 constraint (inst.reloc.exp.X_op != O_constant,
+                             _("expression too complex"));
+                 constraint (inst.reloc.exp.X_add_number < 0
+                             || inst.reloc.exp.X_add_number > 0xff,
+                            _("immediate value out of range"));
+                 inst.instruction = T2_SUBS_PC_LR
+                                    | inst.reloc.exp.X_add_number;
+                 inst.reloc.type = BFD_RELOC_UNUSED;
+                 return;
+               }
+             else if (Rs == REG_PC)
                {
                  /* Always use addw/subw.  */
                  inst.instruction = add ? 0xf20f0000 : 0xf2af0000;
@@ -9086,6 +9041,68 @@ do_t_it (void)
   inst.instruction |= cond << 4;
 }
 
+/* Helper function used for both push/pop and ldm/stm.  */
+static void
+encode_thumb2_ldmstm (int base, unsigned mask, bfd_boolean writeback)
+{
+  bfd_boolean load;
+
+  load = (inst.instruction & (1 << 20)) != 0;
+
+  if (mask & (1 << 13))
+    inst.error =  _("SP not allowed in register list");
+  if (load)
+    {
+      if (mask & (1 << 14)
+         && mask & (1 << 15))
+       inst.error = _("LR and PC should not both be in register list");
+
+      if ((mask & (1 << base)) != 0
+         && writeback)
+       as_warn (_("base register should not be in register list "
+                  "when written back"));
+    }
+  else
+    {
+      if (mask & (1 << 15))
+       inst.error = _("PC not allowed in register list");
+
+      if (mask & (1 << base))
+       as_warn (_("value stored for r%d is UNPREDICTABLE"), base);
+    }
+
+  if ((mask & (mask - 1)) == 0)
+    {
+      /* Single register transfers implemented as str/ldr.  */
+      if (writeback)
+       {
+         if (inst.instruction & (1 << 23))
+           inst.instruction = 0x00000b04; /* ia! -> [base], #4 */
+         else
+           inst.instruction = 0x00000d04; /* db! -> [base, #-4]! */
+       }
+      else
+       {
+         if (inst.instruction & (1 << 23))
+           inst.instruction = 0x00800000; /* ia -> [base] */
+         else
+           inst.instruction = 0x00000c04; /* db -> [base, #-4] */
+       }
+
+      inst.instruction |= 0xf8400000;
+      if (load)
+       inst.instruction |= 0x00100000;
+
+      mask = ffs(mask) - 1;
+      mask <<= 12;
+    }
+  else if (writeback)
+    inst.instruction |= WRITE_BACK;
+
+  inst.instruction |= mask;
+  inst.instruction |= base << 16;
+}
+
 static void
 do_t_ldmstm (void)
 {
@@ -9097,54 +9114,51 @@ do_t_ldmstm (void)
 
   if (unified_syntax)
     {
+      bfd_boolean narrow;
+      unsigned mask;
+
+      narrow = FALSE;
       /* See if we can use a 16-bit instruction.  */
       if (inst.instruction < 0xffff /* not ldmdb/stmdb */
          && inst.size_req != 4
-         && inst.operands[0].reg <= 7
-         && !(inst.operands[1].imm & ~0xff)
-         && (inst.instruction == T_MNEM_stmia
-             ? inst.operands[0].writeback
-             : (inst.operands[0].writeback
-                == !(inst.operands[1].imm & (1 << inst.operands[0].reg)))))
+         && !(inst.operands[1].imm & ~0xff))
        {
-         if (inst.instruction == T_MNEM_stmia
-             && (inst.operands[1].imm & (1 << inst.operands[0].reg))
-             && (inst.operands[1].imm & ((1 << inst.operands[0].reg) - 1)))
-           as_warn (_("value stored for r%d is UNPREDICTABLE"),
-                    inst.operands[0].reg);
+         mask = 1 << inst.operands[0].reg;
 
-         inst.instruction = THUMB_OP16 (inst.instruction);
-         inst.instruction |= inst.operands[0].reg << 8;
-         inst.instruction |= inst.operands[1].imm;
-       }
-      else
-       {
-         if (inst.operands[1].imm & (1 << 13))
-           as_warn (_("SP should not be in register list"));
-         if (inst.instruction == T_MNEM_stmia)
+         if (inst.operands[0].reg <= 7
+             && (inst.instruction == T_MNEM_stmia
+                 ? inst.operands[0].writeback
+                 : (inst.operands[0].writeback
+                    == !(inst.operands[1].imm & mask))))
            {
-             if (inst.operands[1].imm & (1 << 15))
-               as_warn (_("PC should not be in register list"));
-             if (inst.operands[1].imm & (1 << inst.operands[0].reg))
+             if (inst.instruction == T_MNEM_stmia
+                 && (inst.operands[1].imm & mask)
+                 && (inst.operands[1].imm & (mask - 1)))
                as_warn (_("value stored for r%d is UNPREDICTABLE"),
                         inst.operands[0].reg);
+
+             inst.instruction = THUMB_OP16 (inst.instruction);
+             inst.instruction |= inst.operands[0].reg << 8;
+             inst.instruction |= inst.operands[1].imm;
+             narrow = TRUE;
            }
-         else
+         else if (inst.operands[0] .reg == REG_SP
+                  && inst.operands[0].writeback)
            {
-             if (inst.operands[1].imm & (1 << 14)
-                 && inst.operands[1].imm & (1 << 15))
-               as_warn (_("LR and PC should not both be in register list"));
-             if ((inst.operands[1].imm & (1 << inst.operands[0].reg))
-                 && inst.operands[0].writeback)
-               as_warn (_("base register should not be in register list "
-                          "when written back"));
+             inst.instruction = THUMB_OP16 (inst.instruction == T_MNEM_stmia
+                                            ? T_MNEM_push : T_MNEM_pop);
+             inst.instruction |= inst.operands[1].imm;
+             narrow = TRUE;
            }
+       }
+
+      if (!narrow)
+       {
          if (inst.instruction < 0xffff)
            inst.instruction = THUMB_OP32 (inst.instruction);
-         inst.instruction |= inst.operands[0].reg << 16;
-         inst.instruction |= inst.operands[1].imm;
-         if (inst.operands[0].writeback)
-           inst.instruction |= WRITE_BACK;
+
+         encode_thumb2_ldmstm(inst.operands[0].reg, inst.operands[1].imm,
+                              inst.operands[0].writeback);
        }
     }
   else
@@ -9427,6 +9441,16 @@ do_t_mov_cmp (void)
          || inst.operands[1].shifted)
        narrow = FALSE;
 
+      /* MOVS PC, LR is encoded as SUBS PC, LR, #0.  */
+      if (opcode == T_MNEM_movs && inst.operands[1].isreg
+         && !inst.operands[1].shifted
+         && inst.operands[0].reg == REG_PC
+         && inst.operands[1].reg == REG_LR)
+       {
+         inst.instruction = T2_SUBS_PC_LR;
+         return;
+       }
+
       if (!inst.operands[1].isreg)
        {
          /* Immediate operand.  */
@@ -9449,11 +9473,98 @@ do_t_mov_cmp (void)
              inst.reloc.type = BFD_RELOC_ARM_T32_IMMEDIATE;
            }
        }
+      else if (inst.operands[1].shifted && inst.operands[1].immisreg
+              && (inst.instruction == T_MNEM_mov
+                  || inst.instruction == T_MNEM_movs))
+       {
+         /* Register shifts are encoded as separate shift instructions.  */
+         bfd_boolean flags = (inst.instruction == T_MNEM_movs);
+
+         if (current_it_mask)
+           narrow = !flags;
+         else
+           narrow = flags;
+
+         if (inst.size_req == 4)
+           narrow = FALSE;
+
+         if (!low_regs || inst.operands[1].imm > 7)
+           narrow = FALSE;
+
+         if (inst.operands[0].reg != inst.operands[1].reg)
+           narrow = FALSE;
+
+         switch (inst.operands[1].shift_kind)
+           {
+           case SHIFT_LSL:
+             opcode = narrow ? T_OPCODE_LSL_R : THUMB_OP32 (T_MNEM_lsl);
+             break;
+           case SHIFT_ASR:
+             opcode = narrow ? T_OPCODE_ASR_R : THUMB_OP32 (T_MNEM_asr);
+             break;
+           case SHIFT_LSR:
+             opcode = narrow ? T_OPCODE_LSR_R : THUMB_OP32 (T_MNEM_lsr);
+             break;
+           case SHIFT_ROR:
+             opcode = narrow ? T_OPCODE_ROR_R : THUMB_OP32 (T_MNEM_ror);
+             break;
+           default:
+             abort();
+           }
+
+         inst.instruction = opcode;
+         if (narrow)
+           {
+             inst.instruction |= inst.operands[0].reg;
+             inst.instruction |= inst.operands[1].imm << 3;
+           }
+         else
+           {
+             if (flags)
+               inst.instruction |= CONDS_BIT;
+
+             inst.instruction |= inst.operands[0].reg << 8;
+             inst.instruction |= inst.operands[1].reg << 16;
+             inst.instruction |= inst.operands[1].imm;
+           }
+       }
       else if (!narrow)
        {
-         inst.instruction = THUMB_OP32 (inst.instruction);
-         inst.instruction |= inst.operands[0].reg << r0off;
-         encode_thumb32_shifted_operand (1);
+         /* Some mov with immediate shift have narrow variants.
+            Register shifts are handled above.  */
+         if (low_regs && inst.operands[1].shifted
+             && (inst.instruction == T_MNEM_mov
+                 || inst.instruction == T_MNEM_movs))
+           {
+             if (current_it_mask)
+               narrow = (inst.instruction == T_MNEM_mov);
+             else
+               narrow = (inst.instruction == T_MNEM_movs);
+           }
+
+         if (narrow)
+           {
+             switch (inst.operands[1].shift_kind)
+               {
+               case SHIFT_LSL: inst.instruction = T_OPCODE_LSL_I; break;
+               case SHIFT_LSR: inst.instruction = T_OPCODE_LSR_I; break;
+               case SHIFT_ASR: inst.instruction = T_OPCODE_ASR_I; break;
+               default: narrow = FALSE; break;
+               }
+           }
+
+         if (narrow)
+           {
+             inst.instruction |= inst.operands[0].reg;
+             inst.instruction |= inst.operands[1].reg << 3;
+             inst.reloc.type = BFD_RELOC_ARM_THUMB_SHIFT;
+           }
+         else
+           {
+             inst.instruction = THUMB_OP32 (inst.instruction);
+             inst.instruction |= inst.operands[0].reg << r0off;
+             encode_thumb32_shifted_operand (1);
+           }
        }
       else
        switch (inst.instruction)
@@ -9833,7 +9944,7 @@ do_t_push_pop (void)
 
   mask = inst.operands[0].imm;
   if ((mask & ~0xff) == 0)
-    inst.instruction = THUMB_OP16 (inst.instruction);
+    inst.instruction = THUMB_OP16 (inst.instruction) | mask;
   else if ((inst.instruction == T_MNEM_push
            && (mask & ~0xff) == 1 << REG_LR)
           || (inst.instruction == T_MNEM_pop
@@ -9841,43 +9952,18 @@ do_t_push_pop (void)
     {
       inst.instruction = THUMB_OP16 (inst.instruction);
       inst.instruction |= THUMB_PP_PC_LR;
-      mask &= 0xff;
+      inst.instruction |= mask & 0xff;
     }
   else if (unified_syntax)
     {
-      if (mask & (1 << 13))
-       inst.error =  _("SP not allowed in register list");
-      if (inst.instruction == T_MNEM_push)
-       {
-         if (mask & (1 << 15))
-           inst.error = _("PC not allowed in register list");
-       }
-      else
-       {
-         if (mask & (1 << 14)
-             && mask & (1 << 15))
-           inst.error = _("LR and PC should not both be in register list");
-       }
-      if ((mask & (mask - 1)) == 0)
-       {
-         /* Single register push/pop implemented as str/ldr.  */
-         if (inst.instruction == T_MNEM_push)
-           inst.instruction = 0xf84d0d04; /* str reg, [sp, #-4]! */
-         else
-           inst.instruction = 0xf85d0b04; /* ldr reg, [sp], #4 */
-         mask = ffs(mask) - 1;
-         mask <<= 12;
-       }
-      else
-       inst.instruction = THUMB_OP32 (inst.instruction);
+      inst.instruction = THUMB_OP32 (inst.instruction);
+      encode_thumb2_ldmstm(13, mask, TRUE);
     }
   else
     {
       inst.error = _("invalid register list to push/pop instruction");
       return;
     }
-
-  inst.instruction |= mask;
 }
 
 static void
@@ -9922,8 +10008,37 @@ do_t_rsb (void)
   inst.instruction |= Rs << 16;
   if (!inst.operands[2].isreg)
     {
-      inst.instruction = (inst.instruction & 0xe1ffffff) | 0x10000000;
-      inst.reloc.type = BFD_RELOC_ARM_T32_IMMEDIATE;
+      bfd_boolean narrow;
+
+      if ((inst.instruction & 0x00100000) != 0)
+       narrow = (current_it_mask == 0);
+      else
+       narrow = (current_it_mask != 0);
+
+      if (Rd > 7 || Rs > 7)
+       narrow = FALSE;
+
+      if (inst.size_req == 4 || !unified_syntax)
+       narrow = FALSE;
+
+      if (inst.reloc.exp.X_op != O_constant
+         || inst.reloc.exp.X_add_number != 0)
+       narrow = FALSE;
+
+      /* Turn rsb #0 into 16-bit neg.  We should probably do this via
+         relaxation, but it doesn't seem worth the hassle.  */
+      if (narrow)
+       {
+         inst.reloc.type = BFD_RELOC_UNUSED;
+         inst.instruction = THUMB_OP16 (T_MNEM_negs);
+         inst.instruction |= Rs << 3;
+         inst.instruction |= Rd;
+       }
+      else
+       {
+         inst.instruction = (inst.instruction & 0xe1ffffff) | 0x10000000;
+         inst.reloc.type = BFD_RELOC_ARM_T32_IMMEDIATE;
+       }
     }
   else
     encode_thumb32_shifted_operand (2);
@@ -12781,6 +12896,7 @@ do_neon_ext (void)
   struct neon_type_el et = neon_check_type (3, rs,
     N_EQK, N_EQK, N_8 | N_16 | N_32 | N_64 | N_KEY);
   unsigned imm = (inst.operands[3].imm * et.size) / 8;
+  constraint (imm >= (neon_quad (rs) ? 16 : 8), _("shift out of range"));
   inst.instruction |= LOW4 (inst.operands[0].reg) << 12;
   inst.instruction |= HI1 (inst.operands[0].reg) << 22;
   inst.instruction |= LOW4 (inst.operands[1].reg) << 16;
@@ -14046,6 +14162,14 @@ md_assemble (char *str)
          return;
        }
 
+      if (!ARM_CPU_HAS_FEATURE (variant, arm_ext_v6t2) && !inst.size_req)
+       {
+         /* Implicit require narrow instructions on Thumb-1.  This avoids
+            relaxation accidentally introducing Thumb-2 instructions.  */
+         if (opcode->tencode != do_t_blx && opcode->tencode != do_t_branch23)
+           inst.size_req = 2;
+       }
+
       /* Check conditional suffixes.  */
       if (current_it_mask)
        {
@@ -14087,6 +14211,11 @@ md_assemble (char *str)
              return;
            }
        }
+
+      /* Something has gone badly wrong if we try to relax a fixed size
+         instruction.  */
+      assert (inst.size_req == 0 || !inst.relax);
+
       ARM_MERGE_FEATURE_SETS (thumb_arch_used, thumb_arch_used,
                              *opcode->tvariant);
       /* Many Thumb-2 instructions also have Thumb-1 variants, so explicitly
@@ -14306,6 +14435,10 @@ static const struct reg_entry reg_names[] =
   /* VFP control registers.  */
   REGDEF(fpsid,0,VFC), REGDEF(fpscr,1,VFC), REGDEF(fpexc,8,VFC),
   REGDEF(FPSID,0,VFC), REGDEF(FPSCR,1,VFC), REGDEF(FPEXC,8,VFC),
+  REGDEF(fpinst,9,VFC), REGDEF(fpinst2,10,VFC),
+  REGDEF(FPINST,9,VFC), REGDEF(FPINST2,10,VFC),
+  REGDEF(mvfr0,7,VFC), REGDEF(mvfr1,6,VFC),
+  REGDEF(MVFR0,7,VFC), REGDEF(MVFR1,6,VFC),
 
   /* Maverick DSP coprocessor registers.  */
   REGSET(mvf,MVF),  REGSET(mvd,MVD),  REGSET(mvfx,MVFX),  REGSET(mvdx,MVDX),
@@ -14422,20 +14555,21 @@ static const struct asm_psr psrs[] =
 /* Table of V7M psr names.  */
 static const struct asm_psr v7m_psrs[] =
 {
-  {"apsr",     0 },
-  {"iapsr",    1 },
-  {"eapsr",    2 },
-  {"psr",      3 },
-  {"ipsr",     5 },
-  {"epsr",     6 },
-  {"iepsr",    7 },
-  {"msp",      8 },
-  {"psp",      9 },
-  {"primask",  16},
-  {"basepri",  17},
-  {"basepri_max", 18},
-  {"faultmask",        19},
-  {"control",  20}
+  {"apsr",       0 }, {"APSR",         0 },
+  {"iapsr",      1 }, {"IAPSR",        1 },
+  {"eapsr",      2 }, {"EAPSR",        2 },
+  {"psr",        3 }, {"PSR",          3 },
+  {"xpsr",       3 }, {"XPSR",         3 }, {"xPSR",     3 },
+  {"ipsr",       5 }, {"IPSR",         5 },
+  {"epsr",       6 }, {"EPSR",         6 },
+  {"iepsr",      7 }, {"IEPSR",        7 },
+  {"msp",        8 }, {"MSP",          8 },
+  {"psp",        9 }, {"PSP",          9 },
+  {"primask",    16}, {"PRIMASK",      16},
+  {"basepri",    17}, {"BASEPRI",      17},
+  {"basepri_max", 18}, {"BASEPRI_MAX", 18},
+  {"faultmask",          19}, {"FAULTMASK",    19},
+  {"control",    20}, {"CONTROL",      20}
 };
 
 /* Table of all shift-in-operand names.         */
@@ -14763,6 +14897,10 @@ static const struct asm_opcode insns[] =
  tCE(push,     92d0000, push,     1, (REGLST),      push_pop, t_push_pop),
  tCE(pop,      8bd0000, pop,      1, (REGLST),      push_pop, t_push_pop),
 
+ /* These may simplify to neg.  */
+ TCE(rsb,      0600000, ebc00000, 3, (RR, oRR, SH), arit, t_rsb),
+ TC3(rsbs,     0700000, ebd00000, 3, (RR, oRR, SH), arit, t_rsb),
+
 #undef THUMB_VARIANT
 #define THUMB_VARIANT &arm_ext_v6
  TCE(cpy,       1a00000, 4600,     2, (RR, RR),      rd_rm, t_cpy),
@@ -14770,8 +14908,6 @@ static const struct asm_opcode insns[] =
  /* V1 instructions with no Thumb analogue prior to V6T2.  */
 #undef THUMB_VARIANT
 #define THUMB_VARIANT &arm_ext_v6t2
- TCE(rsb,      0600000, ebc00000, 3, (RR, oRR, SH), arit, t_rsb),
- TC3(rsbs,     0700000, ebd00000, 3, (RR, oRR, SH), arit, t_rsb),
  TCE(teq,      1300000, ea900f00, 2, (RR, SH),      cmp,  t_mvn_tst),
  TC3w(teqs,    1300000, ea900f00, 2, (RR, SH),      cmp,  t_mvn_tst),
   CL(teqp,     130f000,           2, (RR, SH),      cmp),
@@ -14911,8 +15047,8 @@ static const struct asm_opcode insns[] =
 #undef ARM_VARIANT
 #define ARM_VARIANT &arm_ext_v5e /*  ARM Architecture 5TE.  */
  TUF(pld,      450f000, f810f000, 1, (ADDR),                pld,  t_pld),
- TC3(ldrd,     00000d0, e9500000, 3, (RRnpc, oRRnpc, ADDRGLDRS), ldrd, t_ldstd),
- TC3(strd,     00000f0, e9400000, 3, (RRnpc, oRRnpc, ADDRGLDRS), ldrd, t_ldstd),
+ TC3(ldrd,     00000d0, e8500000, 3, (RRnpc, oRRnpc, ADDRGLDRS), ldrd, t_ldstd),
+ TC3(strd,     00000f0, e8400000, 3, (RRnpc, oRRnpc, ADDRGLDRS), ldrd, t_ldstd),
 
  TCE(mcrr,     c400000, ec400000, 5, (RCP, I15b, RRnpc, RRnpc, RCN), co_reg2c, co_reg2c),
  TCE(mrrc,     c500000, ec500000, 5, (RCP, I15b, RRnpc, RRnpc, RCN), co_reg2c, co_reg2c),
@@ -14939,6 +15075,7 @@ static const struct asm_opcode insns[] =
 #undef THUMB_VARIANT
 #define THUMB_VARIANT &arm_ext_v6t2
  TCE(ldrex,    1900f9f, e8500f00, 2, (RRnpc, ADDR),              ldrex, t_ldrex),
+ TCE(strex,    1800f90, e8400000, 3, (RRnpc, RRnpc, ADDR),        strex,  t_strex),
  TUF(mcrr2,    c400000, fc400000, 5, (RCP, I15b, RRnpc, RRnpc, RCN), co_reg2c, co_reg2c),
  TUF(mrrc2,    c500000, fc500000, 5, (RCP, I15b, RRnpc, RRnpc, RCN), co_reg2c, co_reg2c),
 
@@ -15027,7 +15164,6 @@ static const struct asm_opcode insns[] =
   UF(srsda,    8400500,           2, (oRRw, I31w),                srs),
  TUF(srsdb,    9400500, e800c000, 2, (oRRw, I31w),                srs,  srs),
  TCE(ssat16,   6a00f30, f3200000, 3, (RRnpc, I16, RRnpc),         ssat16, t_ssat16),
- TCE(strex,    1800f90, e8400000, 3, (RRnpc, RRnpc, ADDR),        strex,  t_strex),
  TCE(umaal,    0400090, fbe00060, 4, (RRnpc, RRnpc, RRnpc, RRnpc),smlal,  t_mlal),
  TCE(usad8,    780f010, fb70f000, 3, (RRnpc, RRnpc, RRnpc),       smul,   t_simd),
  TCE(usada8,   7800010, fb700000, 4, (RRnpc, RRnpc, RRnpc, RRnpc),smla,   t_mla),
@@ -15893,8 +16029,8 @@ static const struct asm_opcode insns[] =
  nUF(vmull,     vmull,   3, (RNQ, RND, RND_RNSC), neon_vmull),
 
   /* Extract. Size 8.  */
- NUF(vext,      0b00000, 4, (RNDQ, oRNDQ, RNDQ, I7), neon_ext),
- NUF(vextq,     0b00000, 4, (RNQ,  oRNQ,  RNQ,  I7), neon_ext),
+ NUF(vext,      0b00000, 4, (RNDQ, oRNDQ, RNDQ, I15), neon_ext),
+ NUF(vextq,     0b00000, 4, (RNQ,  oRNQ,  RNQ,  I15), neon_ext),
 
   /* Two registers, miscellaneous.  */
   /* Reverse. Sizes 8 16 32 (must be < size in opcode).  */
@@ -17843,7 +17979,7 @@ md_apply_fix (fixS *    fixP,
            as_bad_where (fixP->fx_file, fixP->fx_line,
                          _("invalid literal constant: pool needs to be closer"));
          else
-           as_bad (_("bad immediate value for half-word offset (%ld)"),
+           as_bad (_("bad immediate value for 8-bit offset (%ld)"),
                    (long) value);
          break;
        }
@@ -20396,65 +20532,54 @@ aeabi_set_public_attributes (void)
          for (i = 0; p[i]; i++)
            p[i] = TOUPPER (p[i]);
        }
-      elf32_arm_add_eabi_attr_string (stdoutput, 5, p);
+      bfd_elf_add_proc_attr_string (stdoutput, 5, p);
     }
   /* Tag_CPU_arch.  */
-  elf32_arm_add_eabi_attr_int (stdoutput, 6, arch);
+  bfd_elf_add_proc_attr_int (stdoutput, 6, arch);
   /* Tag_CPU_arch_profile.  */
   if (ARM_CPU_HAS_FEATURE (flags, arm_ext_v7a))
-    elf32_arm_add_eabi_attr_int (stdoutput, 7, 'A');
+    bfd_elf_add_proc_attr_int (stdoutput, 7, 'A');
   else if (ARM_CPU_HAS_FEATURE (flags, arm_ext_v7r))
-    elf32_arm_add_eabi_attr_int (stdoutput, 7, 'R');
+    bfd_elf_add_proc_attr_int (stdoutput, 7, 'R');
   else if (ARM_CPU_HAS_FEATURE (flags, arm_ext_v7m))
-    elf32_arm_add_eabi_attr_int (stdoutput, 7, 'M');
+    bfd_elf_add_proc_attr_int (stdoutput, 7, 'M');
   /* Tag_ARM_ISA_use.  */
   if (ARM_CPU_HAS_FEATURE (arm_arch_used, arm_arch_full))
-    elf32_arm_add_eabi_attr_int (stdoutput, 8, 1);
+    bfd_elf_add_proc_attr_int (stdoutput, 8, 1);
   /* Tag_THUMB_ISA_use.  */
   if (ARM_CPU_HAS_FEATURE (thumb_arch_used, arm_arch_full))
-    elf32_arm_add_eabi_attr_int (stdoutput, 9,
+    bfd_elf_add_proc_attr_int (stdoutput, 9,
        ARM_CPU_HAS_FEATURE (thumb_arch_used, arm_arch_t2) ? 2 : 1);
   /* Tag_VFP_arch.  */
   if (ARM_CPU_HAS_FEATURE (thumb_arch_used, fpu_vfp_ext_v3)
       || ARM_CPU_HAS_FEATURE (arm_arch_used, fpu_vfp_ext_v3))
-    elf32_arm_add_eabi_attr_int (stdoutput, 10, 3);
+    bfd_elf_add_proc_attr_int (stdoutput, 10, 3);
   else if (ARM_CPU_HAS_FEATURE (thumb_arch_used, fpu_vfp_ext_v2)
            || ARM_CPU_HAS_FEATURE (arm_arch_used, fpu_vfp_ext_v2))
-    elf32_arm_add_eabi_attr_int (stdoutput, 10, 2);
+    bfd_elf_add_proc_attr_int (stdoutput, 10, 2);
   else if (ARM_CPU_HAS_FEATURE (thumb_arch_used, fpu_vfp_ext_v1)
            || ARM_CPU_HAS_FEATURE (arm_arch_used, fpu_vfp_ext_v1)
            || ARM_CPU_HAS_FEATURE (thumb_arch_used, fpu_vfp_ext_v1xd)
            || ARM_CPU_HAS_FEATURE (arm_arch_used, fpu_vfp_ext_v1xd))
-    elf32_arm_add_eabi_attr_int (stdoutput, 10, 1);
+    bfd_elf_add_proc_attr_int (stdoutput, 10, 1);
   /* Tag_WMMX_arch.  */
   if (ARM_CPU_HAS_FEATURE (thumb_arch_used, arm_cext_iwmmxt)
       || ARM_CPU_HAS_FEATURE (arm_arch_used, arm_cext_iwmmxt))
-    elf32_arm_add_eabi_attr_int (stdoutput, 11, 1);
+    bfd_elf_add_proc_attr_int (stdoutput, 11, 1);
   /* Tag_NEON_arch.  */
   if (ARM_CPU_HAS_FEATURE (thumb_arch_used, fpu_neon_ext_v1)
       || ARM_CPU_HAS_FEATURE (arm_arch_used, fpu_neon_ext_v1))
-    elf32_arm_add_eabi_attr_int (stdoutput, 12, 1);
+    bfd_elf_add_proc_attr_int (stdoutput, 12, 1);
 }
 
-/* Add the .ARM.attributes section.  */
+/* Add the default contents for the .ARM.attributes section.  */
 void
 arm_md_end (void)
 {
-  segT s;
-  char *p;
-  addressT addr;
-  offsetT size;
-  
   if (EF_ARM_EABI_VERSION (meabi_flags) < EF_ARM_EABI_VER4)
     return;
 
   aeabi_set_public_attributes ();
-  size = elf32_arm_eabi_attr_size (stdoutput);
-  s = subseg_new (".ARM.attributes", 0);
-  bfd_set_section_flags (stdoutput, s, SEC_READONLY | SEC_DATA);
-  addr = frag_now_fix ();
-  p = frag_more (size);
-  elf32_arm_set_eabi_attr_contents (stdoutput, (bfd_byte *)p, size);
 }
 #endif /* OBJ_ELF */
 
This page took 0.039077 seconds and 4 git commands to generate.