* subsegs.h (struct frchain): Delete frch_seg.
[external/binutils.git] / gas / ChangeLog
1 2006-05-04  Alan Modra  <amodra@bigpond.net.au>
2
3         * subsegs.h (struct frchain): Delete frch_seg.
4         (frchain_root): Delete.
5         (seg_info): Define as macro.
6         * subsegs.c (frchain_root): Delete.
7         (abs_seg_info, und_seg_info, absolute_frchain): Delete.
8         (subsegs_begin, subseg_change): Adjust for above.
9         (subseg_set_rest): Likewise.  Add new frchain structs to seginfo
10         rather than to one big list.
11         (subseg_get): Don't special case abs, und sections.
12         (subseg_new, subseg_force_new): Don't set frchainP here.
13         (seg_info): Delete.
14         (subsegs_print_statistics): Adjust frag chain control list traversal.
15         * debug.c (dmp_frags):  Likewise.
16         * dwarf2dbg.c (first_frag_for_seg): Don't start looking for frag
17         at frchain_root.  Make use of known frchain ordering.
18         (last_frag_for_seg): Likewise.
19         (get_frag_fix): Likewise.  Add seg param.
20         (process_entries, out_debug_aranges): Adjust get_frag_fix calls.
21         * write.c (chain_frchains_together_1): Adjust for struct frchain.
22         (SUB_SEGMENT_ALIGN): Likewise.
23         (subsegs_finish): Adjust frchain list traversal.
24         * config/tc-xtensa.c (xtensa_cleanup_align_frags): Likewise.
25         (xtensa_fix_target_frags, xtensa_mark_narrow_branches): Likewise.
26         (xtensa_mark_zcl_first_insns, xtensa_fix_a0_b_retw_frags): Likewise.
27         (xtensa_fix_b_j_loop_end_frags): Likewise.
28         (xtensa_fix_close_loop_end_frags): Likewise.
29         (xtensa_fix_short_loop_frags, xtensa_sanity_check): Likewise.
30         (retrieve_segment_info): Delete frch_seg initialisation.
31
32 2006-05-03  Alan Modra  <amodra@bigpond.net.au>
33
34         * subsegs.c (subseg_get): Don't call obj_sec_set_private_data.
35         * config/obj-elf.h (obj_sec_set_private_data): Delete.
36         * config/tc-hppa.c (tc_gen_reloc): Don't use bfd_abs_symbol.
37         * config/tc-mn10300.c (tc_gen_reloc): Likewise.
38
39 2006-05-02  Joseph Myers  <joseph@codesourcery.com>
40
41         * config/tc-arm.c (do_iwmmxt_wldstbh): Don't multiply offset by 4
42         here.
43         (md_apply_fix3): Multiply offset by 4 here for
44         BFD_RELOC_ARM_CP_OFF_IMM_S2 and BFD_RELOC_ARM_T32_CP_OFF_IMM_S2.
45
46 2006-05-02  H.J. Lu  <hongjiu.lu@intel.com>
47             Jan Beulich  <jbeulich@novell.com>
48
49         * config/tc-i386.c (output_invalid_buf): Change size for
50         unsigned char.
51         * config/tc-tic30.c (output_invalid_buf): Likewise.
52
53         * config/tc-i386.c (output_invalid): Cast none-ascii char to
54         unsigned char.
55         * config/tc-tic30.c (output_invalid): Likewise.
56
57 2006-05-02  Daniel Jacobowitz  <dan@codesourcery.com>
58
59         * doc/Makefile.am (AM_MAKEINFOFLAGS): New.
60         (TEXI2POD): Use AM_MAKEINFOFLAGS.
61         (asconfig.texi): Don't set top_srcdir.
62         * doc/as.texinfo: Don't use top_srcdir.
63         * aclocal.m4, Makefile.in, doc/Makefile.in: Regenerated.
64
65 2006-05-02  H.J. Lu  <hongjiu.lu@intel.com>
66
67         * config/tc-i386.c (output_invalid_buf): Change size to 16.
68         * config/tc-tic30.c (output_invalid_buf): Likewise.
69
70         * config/tc-i386.c (output_invalid): Use snprintf instead of
71         sprintf.
72         * config/tc-ia64.c (declare_register_set): Likewise.
73         (emit_one_bundle): Likewise.
74         (check_dependencies): Likewise.
75         * config/tc-tic30.c (output_invalid): Likewise.
76
77 2006-05-02  Paul Brook  <paul@codesourcery.com>
78
79         * config/tc-arm.c (arm_optimize_expr): New function.
80         * config/tc-arm.h (md_optimize_expr): Define
81         (arm_optimize_expr): Add prototype.
82         (TC_FORCE_RELOCATION_SUB_SAME): Define.
83
84 2006-05-02  Ben Elliston  <bje@au.ibm.com>
85
86         * config/obj-elf.h (ELF_TARGET_SYMBOL_FIELDS): Make single bit
87         field unsigned.
88
89         * sb.h (sb_list_vector): Move to sb.c.
90         * sb.c (free_list): Use type of sb_list_vector directly.
91         (sb_build): Fix off-by-one error in assertion about `size'.
92
93 2006-05-01  Ben Elliston  <bje@au.ibm.com>
94
95         * listing.c (listing_listing): Remove useless loop.
96         * macro.c (macro_expand): Remove is_positional local variable.
97         * read.c (s_comm_internal): Simplify `if' condition 1 || x -> 1
98         and simplify surrounding expressions, where possible.
99         (assign_symbol): Likewise.
100         (s_weakref): Likewise.
101         * symbols.c (colon): Likewise.
102
103 2006-05-01  James Lemke  <jwlemke@wasabisystems.com>
104
105         * subsegs.c (subseg_set_rest): Always set seginfp->frchainP if NULL.
106
107 2006-04-30  Thiemo Seufer  <ths@mips.com>
108             David Ung  <davidu@mips.com>
109
110         * config/tc-mips.c (validate_mips_insn): Handling of udi cases.
111         (mips_immed): New table that records various handling of udi
112         instruction patterns.
113         (mips_ip): Adds udi handling.
114
115 2006-04-28  Alan Modra  <amodra@bigpond.net.au>
116
117         * dwarf2dbg.c (get_line_subseg): Attach new struct line_seg to end
118         of list rather than beginning.
119
120 2006-04-26  Julian Brown  <julian@codesourcery.com>
121
122         * gas/config/tc-arm.c (neon_is_quarter_float): Move, and rename to...
123         (is_quarter_float): Rename from above. Simplify slightly.
124         (parse_qfloat_immediate): Parse a "quarter precision" floating-point
125         number.
126         (parse_neon_mov): Parse floating-point constants.
127         (neon_qfloat_bits): Fix encoding.
128         (neon_cmode_for_move_imm): Tweak to use floating-point encoding in
129         preference to integer encoding when using the F32 type.
130
131 2006-04-26  Julian Brown  <julian@codesourcery.com>
132
133         * config/tc-arm.c (neon_el_type): Make NT_invtype be the zero (so
134         zero-initialising structures containing it will lead to invalid types).
135         (arm_it): Add vectype to each operand.
136         (NTA_HASTYPE, NTA_HASINDEX): Constants used in neon_typed_alias
137         defined field.
138         (neon_typed_alias): New structure. Extra information for typed
139         register aliases.
140         (reg_entry): Add neon type info field.
141         (arm_reg_parse): Remove RTYPE argument (revert to previous arguments).
142         Break out alternative syntax for coprocessor registers, etc. into...
143         (arm_reg_alt_syntax): New function. Alternate syntax handling broken
144         out from arm_reg_parse.
145         (parse_neon_type): Move. Return SUCCESS/FAIL.
146         (first_error): New function. Call to ensure first error which occurs is
147         reported.
148         (parse_neon_operand_type): Parse exactly one type.
149         (NEON_ALL_LANES, NEON_INTERLEAVE_LANES): Move.
150         (parse_typed_reg_or_scalar): New function. Handle core of both
151         arm_typed_reg_parse and parse_scalar.
152         (arm_typed_reg_parse): Parse a register with an optional type.
153         (NEON_SCALAR_REG, NEON_SCALAR_INDEX): Extract parts of parse_scalar
154         result.
155         (parse_scalar): Parse a Neon scalar with optional type.
156         (parse_reg_list): Use first_error.
157         (parse_vfp_reg_list): Use arm_typed_reg_parse instead of arm_reg_parse.
158         (neon_alias_types_same): New function. Return true if two (alias) types
159         are the same.
160         (parse_neon_el_struct_list): Use parse_typed_reg_or_scalar. Return type
161         of elements.
162         (insert_reg_alias): Return new reg_entry not void.
163         (insert_neon_reg_alias): New function. Insert type/index information as
164         well as register for alias.
165         (create_neon_reg_alias): New function. Parse .dn/.qn directives and
166         make typed register aliases accordingly.
167         (s_dn, s_qn): New functions. Handle incorrectly used .dn/.qn at start
168         of line.
169         (s_unreq): Delete type information if present.
170         (s_arm_unwind_save_mmxwr): Remove arg 3 from arm_reg_parse calls.
171         (s_arm_unwind_save_mmxwcg): Likewise.
172         (s_arm_unwind_movsp): Likewise.
173         (s_arm_unwind_setfp): Likewise.
174         (parse_shift): Likewise.
175         (parse_shifter_operand): Likewise.
176         (parse_address): Likewise.
177         (parse_tb): Likewise.
178         (tc_arm_regname_to_dw2regnum): Likewise.
179         (md_pseudo_table): Add dn, qn.
180         (parse_neon_mov): Handle typed operands.
181         (parse_operands): Likewise.
182         (neon_type_mask): Add N_SIZ.
183         (N_ALLMODS): New macro.
184         (neon_check_shape): Fix typo in NS_DDD_QQQ case. Use first_error.
185         (el_type_of_type_chk): Add some safeguards.
186         (modify_types_allowed): Fix logic bug.
187         (neon_check_type): Handle operands with types.
188         (neon_three_same): Remove redundant optional arg handling.
189         (do_neon_dyadic_i64_su, do_neon_shl_imm, do_neon_qshl_imm)
190         (do_neon_logic, do_neon_qdmulh, do_neon_fcmp_absolute)
191         (do_neon_step): Adjust accordingly.
192         (neon_cmode_for_logic_imm): Use first_error.
193         (do_neon_bitfield): Call neon_check_type.
194         (neon_dyadic): Rename to...
195         (neon_dyadic_misc): ...this. New name for neon_dyadic. Add bitfield
196         to allow modification of type of the destination.
197         (do_neon_dyadic_if_su, do_neon_dyadic_if_i, do_neon_dyadic_if_i_d)
198         (do_neon_addsub_if_i, do_neon_mul): Adjust accordingly.
199         (do_neon_compare): Make destination be an untyped bitfield.
200         (neon_scalar_for_mul): Use NEON_SCALAR_REG, NEON_SCALAR_INDEX.
201         (neon_mul_mac): Return early in case of errors.
202         (neon_move_immediate): Use first_error.
203         (neon_mac_reg_scalar_long): Fix type to include scalar.
204         (do_neon_dup): Likewise.
205         (do_neon_mov): Likewise (in several places).
206         (do_neon_tbl_tbx): Fix type.
207         (do_neon_ld_st_interleave, neon_alignment_bit, do_neon_ld_st_lane)
208         (do_neon_ld_dup): Exit early in case of errors and/or use
209         first_error.
210         (opcode_lookup): Update for parse_neon_type returning SUCCESS/FAIL.
211         Handle .dn/.qn directives.
212         (REGDEF): Add zero for reg_entry neon field.
213
214 2006-04-26  Julian Brown  <julian@codesourcery.com>
215
216         * config/tc-arm.c (limits.h): Include.
217         (fpu_arch_vfp_v3, fpu_vfp_ext_v3, fpu_neon_ext_v1)
218         (fpu_vfp_v3_or_neon_ext): Declare constants.
219         (neon_el_type): New enumeration of types for Neon vector elements.
220         (neon_type_el): New struct. Define type and size of a vector element.
221         (NEON_MAX_TYPE_ELS): Define constant. The maximum number of types per
222         instruction.
223         (neon_type): Define struct. The type of an instruction.
224         (arm_it): Add 'vectype' for the current instruction.
225         (isscalar, immisalign, regisimm, isquad): New predicates for operands.
226         (vfp_sp_reg_pos): Rename to...
227         (vfp_reg_pos): ...this, and add VFP_REG_Dd, VFP_REG_Dm, VFP_REG_Dn
228         tags.
229         (arm_reg_type): Add REG_TYPE_NQ (Neon Q register) and REG_TYPE_NDQ
230         (Neon D or Q register).
231         (reg_expected_msgs): Sync with above. Allow VFD to mean VFP or Neon D
232         register.
233         (GE_OPT_PREFIX_BIG): Define constant, for use in...
234         (my_get_expression): Allow above constant as argument to accept
235         64-bit constants with optional prefix.
236         (arm_reg_parse): Add extra argument to return the specific type of
237         register in when either a D or Q register (REG_TYPE_NDQ) is
238         requested. Can be NULL.
239         (parse_scalar): New function. Parse Neon scalar (vector reg and index).
240         (parse_reg_list): Update for new arm_reg_parse args.
241         (parse_vfp_reg_list): Allow parsing of Neon D/Q register lists.
242         (parse_neon_el_struct_list): New function. Parse element/structure
243         register lists for VLD<n>/VST<n> instructions.
244         (s_arm_unwind_save_vfp): Update for new parse_vfp_reg_list args.
245         (s_arm_unwind_save_mmxwr): Likewise.
246         (s_arm_unwind_save_mmxwcg): Likewise.
247         (s_arm_unwind_movsp): Likewise.
248         (s_arm_unwind_setfp): Likewise.
249         (parse_big_immediate): New function. Parse an immediate, which may be
250         64 bits wide. Put results in inst.operands[i].
251         (parse_shift): Update for new arm_reg_parse args.
252         (parse_address): Likewise. Add parsing of alignment specifiers.
253         (parse_neon_mov): Parse the operands of a VMOV instruction.
254         (operand_parse_code): Add OP_RND, OP_RNQ, OP_RNDQ, OP_RNSC, OP_NRDLST,
255         OP_NSTRLST, OP_NILO, OP_RNDQ_I0, OP_RR_RNSC, OP_RNDQ_RNSC, OP_RND_RNSC,
256         OP_VMOV, OP_RNDQ_IMVNb, OP_RNDQ_I63b, OP_I0, OP_I16z, OP_I32z, OP_I64,
257         OP_I64z, OP_oI32b, OP_oRND, OP_oRNQ, OP_oRNDQ.
258         (parse_operands): Handle new codes above.
259         (encode_arm_vfp_sp_reg): Rename to...
260         (encode_arm_vfp_reg): ...this. Handle D regs (0-31) too. Complain if
261         selected VFP version only supports D0-D15.
262         (do_vfp_sp_monadic, do_vfp_sp_dyadic, do_vfp_sp_compare_z)
263         (do_vfp_dp_sp_cvt, do_vfp_reg_from_sp, do_vfp_reg2_from_sp2)
264         (do_vfp_sp_from_reg, do_vfp_sp2_from_reg2, do_vfp_sp_ldst)
265         (do_vfp_dp_ldst, vfp_sp_ldstm, vfp_dp_ldstm): Update for new
266         encode_arm_vfp_reg name, and allow 32 D regs.
267         (do_vfp_dp_rd_rm, do_vfp_dp_rn_rd, do_vfp_dp_rd_rn, do_vfp_dp_rd_rn_rm)
268         (do_vfp_rm_rd_rn): New functions to encode VFP insns allowing 32 D
269         regs.
270         (do_vfp_sp_const, do_vfp_dp_const, vfp_conv, do_vfp_sp_conv_16)
271         (do_vfp_dp_conv_16, do_vfp_sp_conv_32, do_vfp_dp_conv_32): Handle
272         constant-load and conversion insns introduced with VFPv3.
273         (neon_tab_entry): New struct.
274         (NEON_ENC_TAB): Bit patterns for overloaded Neon instructions, and
275         those which are the targets of pseudo-instructions.
276         (neon_opc): Enumerate opcodes, use as indices into...
277         (neon_enc_tab): ...this. Hold data from NEON_ENC_TAB.
278         (NEON_ENC_INTEGER, NEON_ENC_ARMREG, NEON_ENC_POLY, NEON_ENC_FLOAT)
279         (NEON_ENC_SCALAR, NEON_ENC_IMMED, NEON_ENC_INTERLV, NEON_ENC_LANE)
280         (NEON_ENC_DUP): Define meaningful helper macros to look up values in
281         neon_enc_tab.
282         (neon_shape): Enumerate shapes (permitted register widths, etc.) for
283         Neon instructions.
284         (neon_type_mask): New. Compact type representation for type checking.
285         (N_SU_ALL, N_SU_32, N_SU_16_64, N_SUF_32, N_I_ALL, N_IF_32): Common
286         permitted type combinations.
287         (N_IGNORE_TYPE): New macro.
288         (neon_check_shape): New function. Check an instruction shape for
289         multiple alternatives. Return the specific shape for the current
290         instruction.
291         (neon_modify_type_size): New function. Modify a vector type and size,
292         depending on the bit mask in argument 1.
293         (neon_type_promote): New function. Convert a given "key" type (of an
294         operand) into the correct type for a different operand, based on a bit
295         mask.
296         (type_chk_of_el_type): New function. Convert a type and size into the
297         compact representation used for type checking.
298         (el_type_of_type_ckh): New function. Reverse of above (only when a
299         single bit is set in the bit mask).
300         (modify_types_allowed): New function. Alter a mask of allowed types
301         based on a bit mask of modifications.
302         (neon_check_type): New function. Check the type of the current
303         instruction against the variable argument list. The "key" type of the
304         instruction is returned.
305         (neon_dp_fixup): New function. Fill in and modify instruction bits for
306         a Neon data-processing instruction depending on whether we're in ARM
307         mode or Thumb-2 mode.
308         (neon_logbits): New function.
309         (neon_three_same, neon_two_same, do_neon_dyadic_i_su)
310         (do_neon_dyadic_i64_su, neon_imm_shift, do_neon_shl_imm)
311         (do_neon_qshl_imm, neon_cmode_for_logic_imm, neon_bits_same_in_bytes)
312         (neon_squash_bits, neon_is_quarter_float, neon_qfloat_bits)
313         (neon_cmode_for_move_imm, neon_write_immbits, neon_invert_size)
314         (do_neon_logic, do_neon_bitfield, neon_dyadic, do_neon_dyadic_if_su)
315         (do_neon_dyadic_if_su_d, do_neon_dyadic_if_i, do_neon_dyadic_if_i_d)
316         (do_neon_addsub_if_i, neon_exchange_operands, neon_compare)
317         (do_neon_cmp, do_neon_cmp_inv, do_neon_ceq, neon_scalar_for_mul)
318         (neon_mul_mac, do_neon_mac_maybe_scalar, do_neon_tst, do_neon_mul)
319         (do_neon_qdmulh, do_neon_fcmp_absolute, do_neon_fcmp_absolute_inv)
320         (do_neon_step, do_neon_abs_neg, do_neon_sli, do_neon_sri)
321         (do_neon_qshlu_imm, do_neon_qmovn, do_neon_qmovun)
322         (do_neon_rshift_sat_narrow, do_neon_rshift_sat_narrow_u, do_neon_movn)
323         (do_neon_rshift_narrow, do_neon_shll, neon_cvt_flavour, do_neon_cvt)
324         (neon_move_immediate, do_neon_mvn, neon_mixed_length)
325         (do_neon_dyadic_long, do_neon_abal, neon_mac_reg_scalar_long)
326         (do_neon_mac_maybe_scalar_long, do_neon_dyadic_wide, do_neon_vmull)
327         (do_neon_ext, do_neon_rev, do_neon_dup, do_neon_mov)
328         (do_neon_rshift_round_imm, do_neon_movl, do_neon_trn, do_neon_zip_uzp)
329         (do_neon_sat_abs_neg, do_neon_pair_long, do_neon_recip_est)
330         (do_neon_cls, do_neon_clz, do_neon_cnt, do_neon_swp, do_neon_tbl_tbx)
331         (do_neon_ldm_stm, do_neon_ldr_str, do_neon_ld_st_interleave)
332         (neon_alignment_bit, do_neon_ld_st_lane, do_neon_ld_dup)
333         (do_neon_ldx_stx): New functions. Neon bit encoding and encoding
334         helpers.
335         (parse_neon_type): New function. Parse Neon type specifier.
336         (opcode_lookup): Allow parsing of Neon type specifiers.
337         (REGNUM2, REGSETH, REGSET2): New macros.
338         (reg_names): Add new VFPv3 and Neon registers.
339         (NUF, nUF, NCE, nCE): New macros for opcode table.
340         (insns): More VFP registers allowed in fcpyd, fmdhr, fmdlr, fmrdh,
341         fmrdl, fabsd, fnegd, fsqrtd, faddd, fsubd, fmuld, fdivd, fmacd, fmscd,
342         fnmuld, fnmacd, fnmscd, fcmpd, fcmpzd, fcmped, fcmpezd, fmdrr, fmrrd.
343         Add Neon instructions vaba, vhadd, vrhadd, vhsub, vqadd, vqsub, vrshl,
344         vqrshl, vshl, vqshl{u}, vand, vbic, vorr, vorn, veor, vbsl, vbit, vbif,
345         vabd, vmax, vmin, vcge, vcgt, vclt, vcle, vceq, vpmax, vpmin, vmla,
346         vmls, vpadd, vadd, vsub, vtst, vmul, vqdmulh, vqrdmulh, vacge, vacgt,
347         vaclt, vacle, vrecps, vrsqrts, vabs, vneg, v{r}shr,  v{r}sra, vsli,
348         vsri, vqshrn, vq{r}shr{u}n, v{r}shrn, vshll, vcvt, vmov, vmvn, vabal,
349         vabdl, vaddl, vsubl, vmlal, vmlsl, vaddw, vsubw, v{r}addhn, v{r}subhn,
350         vqdmlal, vqdmlsl, vqdmull, vmull, vext, vrev64, vrev32, vrev16, vdup,
351         vmovl, v{q}movn, vzip, vuzp, vqabs, vqneg, vpadal, vpaddl, vrecpe,
352         vrsqrte, vcls, vclz, vcnt, vswp, vtrn, vtbl, vtbx, vldm, vstm, vldr,
353         vstr, vld[1234], vst[1234], fconst[sd], f[us][lh]to[sd],
354         fto[us][lh][sd].
355         (tc_arm_regname_to_dw2regnum): Update for arm_reg_parse args.
356         (arm_cpu_option_table): Add Neon and VFPv3 to Cortex-A8.
357         (arm_option_cpu_value): Add vfp3 and neon.
358         (aeabi_set_public_attributes): Support VFPv3 and NEON attributes. Fix
359         VFPv1 attribute.
360
361 2006-04-25  Bob Wilson  <bob.wilson@acm.org>
362
363         * config/xtensa-relax.c (widen_spec_list): Use new "WIDE.<opcode>"
364         syntax instead of hardcoded opcodes with ".w18" suffixes.
365         (wide_branch_opcode): New.
366         (build_transition): Use it to check for wide branch opcodes with
367         either ".w18" or ".w15" suffixes.
368
369 2006-04-25  Bob Wilson  <bob.wilson@acm.org>
370
371         * config/tc-xtensa.c (xtensa_create_literal_symbol,
372         xg_assemble_literal, xg_assemble_literal_space): Do not set the
373         frag's is_literal flag.
374
375 2006-04-25  Bob Wilson  <bob.wilson@acm.org>
376
377         * config/xtensa-relax.c (XCHAL_HAVE_WIDE_BRANCHES): Provide default.
378
379 2006-04-23  Kazu Hirata  <kazu@codesourcery.com>
380
381         * config/obj-coff.c, config/tc-arm.c, config/tc-bfin.c,
382         config/tc-cris.c, config/tc-crx.c, config/tc-i386.c,
383         config/tc-ia64.c, config/tc-maxq.c, config/tc-maxq.h,
384         config/tc-mips.c, config/tc-msp430.c, config/tc-sh.c,
385         config/tc-tic4x.c, config/tc-xtensa.c: Fix comment typos.
386
387 2005-04-20  Paul Brook  <paul@codesourcery.com>
388
389         * config/tc-arm.c (s_arm_arch, s_arm_cpu, s_arm_fpu): Enable for
390         all targets.
391         (md_pseudo_table): Enable .arch, .cpu and .fpu for all targets.
392
393 2006-04-19  Alan Modra  <amodra@bigpond.net.au>
394
395         * Makefile.am (CPU_TYPES): Add maxq and mt.  Sort.
396         (CPU_OBJ_VALID): Change sense of COFF test to default to invalid.
397         Make some cpus unsupported on ELF.  Run "make dep-am".
398         * Makefile.in: Regenerate.
399
400 2006-04-19  Alan Modra  <amodra@bigpond.net.au>
401
402         * configure.in (--enable-targets): Indent help message.
403         * configure: Regenerate.
404
405 2006-04-18  H.J. Lu  <hongjiu.lu@intel.com>
406
407         PR gas/2533
408         * config/tc-i386.c (i386_immediate): Check illegal immediate
409         register operand.
410
411 2006-04-18  Alan Modra  <amodra@bigpond.net.au>
412
413         * config/tc-i386.c: Formatting.
414         (output_disp, output_imm): ISO C90 params.
415
416         * frags.c (frag_offset_fixed_p): Constify args.
417         * frags.h (frag_offset_fixed_p): Ditto.
418
419         * config/tc-dlx.h (tc_coff_symbol_emit_hook): Delete.
420         (COFF_MAGIC): Delete.
421
422         * config/tc-xc16x.h (TC_LINKRELAX_FIXUP): Delete.
423
424 2006-04-16  Daniel Jacobowitz  <dan@codesourcery.com>
425
426         * po/POTFILES.in: Regenerated.
427
428 2006-04-16  Mark Mitchell  <mark@codesourcery.com>
429
430         * doc/as.texinfo: Mention that some .type syntaxes are not
431         supported on all architectures.
432
433 2006-04-14  Sterling Augustine  <sterling@tensilica.com>
434
435         * config/tc-xtensa.c (emit_single_op): Do not relax MOVI
436         instructions when such transformations have been disabled.
437
438 2006-04-10  Sterling Augustine  <sterling@tensilica.com>
439
440         * config/tc-xtensa.c (xg_assemble_vliw_tokens): Record loop target
441         symbols in RELAX[_CHECK]_ALIGN_NEXT_OPCODE frags.
442         (xtensa_fix_close_loop_end_frags): Use the recorded values instead of
443         decoding the loop instructions.  Remove current_offset variable.
444         (xtensa_fix_short_loop_frags): Likewise.
445         (min_bytes_to_other_loop_end): Remove current_offset argument.
446
447 2006-04-09  Arnold Metselaar  <arnold.metselaar@planet.nl>
448
449         * config/tc-z80.c (z80_optimize_expr): Removed.
450         * config/tc-z80.h (z80_optimize_expr, md_optimize_expr): Removed.
451
452 2006-04-07  Joerg Wunsch <j.gnu@uriah.heep.sax.de>
453
454         * gas/config/tc-avr.c (mcu_types): Add support for attiny261,
455         attiny461, attiny861, attiny25, attiny45, attiny85,attiny24,
456         attiny44, attiny84, at90pwm2, at90pwm3, atmega164, atmega324,
457         atmega644, atmega329, atmega3290, atmega649, atmega6490,
458         atmega406, atmega640, atmega1280, atmega1281, at90can32,
459         at90can64, at90usb646, at90usb647, at90usb1286 and
460         at90usb1287.
461         Move atmega48 and atmega88 from AVR_ISA_M8 to AVR_ISA_PWMx.
462
463 2006-04-07  Paul Brook  <paul@codesourcery.com>
464
465         * config/tc-arm.c (parse_operands): Set default error message.
466
467 2006-04-07  Paul Brook  <paul@codesourcery.com>
468
469         * config/tc-arm.c (parse_tb): Set inst.error before returning FAIL.
470
471 2006-04-07  Paul Brook  <paul@codesourcery.com>
472
473         * config/tc-arm.c (md_apply_fix): Set H bit on blx instruction.
474
475 2006-04-07  Paul Brook  <paul@codesourcery.com>
476
477         * config/tc-arm.c (THUMB2_LOAD_BIT): Define.
478         (move_or_literal_pool): Handle Thumb-2 instructions.
479         (do_t_ldst): Call move_or_literal_pool for =N addressing modes.
480
481 2006-04-07  Alan Modra  <amodra@bigpond.net.au>
482
483         PR 2512.
484         * config/tc-i386.c (match_template): Move 64-bit operand tests
485         inside loop.
486
487 2006-04-06  Carlos O'Donell  <carlos@codesourcery.com>
488
489         * po/Make-in: Add install-html target.
490         * Makefile.am: Add install-html and install-html-recursive targets.
491         * Makefile.in: Regenerate.
492         * configure.in: AC_SUBST datarootdir, docdir, htmldir.
493         * configure: Regenerate.
494         * doc/Makefile.am: Add install-html and install-html-am targets.
495         * doc/Makefile.in: Regenerate.
496
497 2006-04-06  Alan Modra  <amodra@bigpond.net.au>
498
499         * frags.c (frag_offset_fixed_p): Reinitialise offset before
500         second scan.
501
502 2006-04-05  Richard Sandiford  <richard@codesourcery.com>
503             Daniel Jacobowitz  <dan@codesourcery.com>
504
505         * config/tc-sparc.c (sparc_target_format): Handle TE_VXWORKS.
506         (GOTT_BASE, GOTT_INDEX): New.
507         (tc_gen_reloc): Don't alter relocations against GOTT_BASE and
508         GOTT_INDEX when generating VxWorks PIC.
509         * configure.tgt (sparc*-*-vxworks*): Remove this special case;
510         use the generic *-*-vxworks* stanza instead.
511
512 2006-04-04  Alan Modra  <amodra@bigpond.net.au>
513
514         PR 997
515         * frags.c (frag_offset_fixed_p): New function.
516         * frags.h (frag_offset_fixed_p): Declare.
517         * expr.c (expr): Use frag_offset_fixed_p when simplifying subtraction.
518         (resolve_expression): Likewise.
519
520 2006-04-03  Sterling Augustine  <sterling@tensilica.com>
521
522         * config/tc-xtensa.c (init_op_placement_info_table): Check for formats
523         of the same length but different numbers of slots.
524
525 2006-03-30  Andreas Schwab  <schwab@suse.de>
526
527         * configure.in: Fix help string for --enable-targets option.
528         * configure: Regenerate.
529
530 2006-03-28  Nathan Sidwell  <nathan@codesourcery.com>
531
532         * gas/config/tc-m68k.c (find_cf_chip): Merge into ...
533         (m68k_ip): ... here.  Use for all chips.  Protect against buffer
534         overrun and avoid excessive copying.
535
536         * config/tc-m68k.c (m68000_control_regs, m68010_control_regs,
537         m68020_control_regs, m68040_control_regs, m68060_control_regs,
538         mcf_control_regs, mcf5208_control_regs, mcf5213_control_regs,
539         mcf5329_control_regs, mcf5249_control_regs, mcf528x_control_regs,
540         mcfv4e_control_regs, m68010_control_regs): Rename and reorder to ...
541         (m68000_ctrl, m68010_ctrl, m68020_ctrl, m68040_ctrl, m68060_ctrl,
542         mcf_ctrl, mcf5208_ctrl, mcf5213_ctrl, mcf5235_ctrl, mcf5249_ctrl, 
543         mcf5216_ctrl, mcf5250_ctrl, mcf5271_ctrl, mcf5272_ctrl,
544         mcf5282_ctrl, mcfv4e_ctrl): ... these.
545         (mcf5275_ctrl, mcf5329_ctrl, mcf5373_ctrl): New.
546         (struct m68k_cpu): Change chip field to control_regs.
547         (current_chip): Remove.
548         (control_regs): New.
549         (m68k_archs, m68k_extensions): Adjust.
550         (m68k_cpus): Reorder to be in cpu number order.  Adjust.
551         (CPU_ALLOW_MC, CPU_ALLOW_NEGATION): Remove.
552         (find_cf_chip): Reimplement for new organization of cpu table.
553         (select_control_regs): Remove.
554         (mri_chip): Adjust.
555         (struct save_opts): Save control regs, not chip.
556         (s_save, s_restore): Adjust.
557         (m68k_lookup_cpu): Give deprecated warning when necessary.
558         (m68k_init_arch): Adjust.
559         (md_show_usage): Adjust for new cpu table organization.
560
561 2006-03-25  Bernd Schmidt  <bernd.schmidt@analog.com>
562
563         * config/bfin-defs.h (Expr_Node_Type enum): Add Expr_Node_GOT_Reloc.
564         * config/bfin-lex.l: Recognize GOT17M4 and FUNCDESC_GOT17M4.
565         * config/bfin-parse.y: Include "libbfd.h", "elf/common.h" and
566         "elf/bfin.h".
567         (GOT17M4, FUNCDESC_GOT17M4): New tokens of type <value>.
568         (any_gotrel): New rule.
569         (got): Use it, and create Expr_Node_GOT_Reloc nodes.
570         * config/tc-bfin.c: Include "libbfd.h", "elf/common.h" and
571         "elf/bfin.h".
572         (DEFAULT_FLAGS, bfin_flags, bfin_pic_flag): New.
573         (bfin_pic_ptr): New function.
574         (md_pseudo_table): Add it for ".picptr".
575         (OPTION_FDPIC): New macro.
576         (md_longopts): Add -mfdpic.
577         (md_parse_option): Handle it.
578         (md_begin): Set BFD flags.
579         (md_apply_fix3, bfin_fix_adjustable): Handle new relocs.
580         (bfin_gen_ldstidxi): Adjust to match the trees that the parser gives
581         us for GOT relocs.
582         * Makefile.am (bfin-parse.o): Update dependencies.
583         (DEPTC_bfin_elf): Likewise.
584         * Makefile.in: Regenerate.
585
586 2006-03-25  Richard Sandiford  <richard@codesourcery.com>
587
588         * config/tc-m68k.c (m68k_cpus): Change cpu_cf5208 entries to use
589         mcfemac instead of mcfmac.
590
591 2006-03-23  Michael Matz  <matz@suse.de>
592
593         * config/tc-i386.c (type_names): Correct placement of 'static'.
594         (reloc): Map some more relocs to their 64 bit counterpart when
595         size is 8.
596         (output_insn): Work around breakage if DEBUG386 is defined.
597         (output_disp): A BFD_RELOC_64 with GOT_symbol as operand also
598         needs to be mapped to BFD_RELOC_X86_64_GOTPC64 or
599         BFD_RELOC_X86_64_GOTPC32.  Also x86-64 handles pcrel addressing
600         different from i386.
601         (output_imm): Ditto.
602         (lex_got): Recognize @PLTOFF and @GOTPLT.  Make @GOT accept also
603         Imm64.
604         (md_convert_frag): Jumps can now be larger than 2GB away, error
605         out in that case.
606         (tc_gen_reloc): New relocs are passed through.  BFD_RELOC_64
607         and BFD_RELOC_64_PCREL are mapped to BFD_RELOC_X86_64_GOTPC64.
608
609 2006-03-22  Richard Sandiford  <richard@codesourcery.com>
610             Daniel Jacobowitz  <dan@codesourcery.com>
611             Phil Edwards  <phil@codesourcery.com>
612             Zack Weinberg  <zack@codesourcery.com>
613             Mark Mitchell  <mark@codesourcery.com>
614             Nathan Sidwell  <nathan@codesourcery.com>
615
616         * config/tc-mips.c (mips_target_format): Handle vxworks targets.
617         (md_begin): Complain about -G being used for PIC.  Don't change
618         the text, data and bss alignments on VxWorks.
619         (reloc_needs_lo_p): Don't return true for R_MIPS_GOT16 when
620         generating VxWorks PIC.
621         (load_address): Extend SVR4_PIC handling to VXWORKS_PIC.
622         (macro): Likewise, but do not treat la $25 specially for
623         VxWorks PIC, and do not handle jal.
624         (OPTION_MVXWORKS_PIC): New macro.
625         (md_longopts): Add -mvxworks-pic.
626         (md_parse_option): Don't complain about using PIC and -G together here.
627         Handle OPTION_MVXWORKS_PIC.
628         (md_estimate_size_before_relax): Always use the first relaxation
629         sequence on VxWorks.
630         * config/tc-mips.h (VXWORKS_PIC): New.
631
632 2006-03-21  Paul Brook  <paul@codesourcery.com>
633
634         * config/tc-arm.c (md_apply_fix): Fix typo in offset mask.
635
636 2006-03-21  Sterling Augustine  <sterling@tensilica.com>
637
638         * config/tc-xtensa.c (enforce_three_byte_loop_align): New flag.
639         (xtensa_setup_hw_workarounds): Set this new flag for older hardware.
640         (get_loop_align_size): New.
641         (xtensa_end): Skip xtensa_mark_narrow_branches when not aligning.
642         (xtensa_mark_zcl_first_insns): Prevent widening of first loop frag.
643         (get_text_align_power): Rewrite to handle inputs in the range 2-8.
644         (get_noop_aligned_address): Use get_loop_align_size.
645         (get_aligned_diff): Likewise.
646
647 2006-03-21  Paul Brook  <paul@codesourcery.com>
648
649         * config/tc-arm.c (insns): Correct opcodes for ldrbt and strbt.
650
651 2006-03-20  Paul Brook  <paul@codesourcery.com>
652
653         * config/tc-arm.c (BAD_BRANCH, BAD_NOT_IT): Define.
654         (do_t_branch): Encode branches inside IT blocks as unconditional.
655         (do_t_cps): New function.
656         (do_t_blx, do_t_bkpt, do_t_branch23, do_t_bx, do_t_bxj, do_t_cpsi,
657         do_t_czb, do_t_it, do_t_setend, do_t_tb): Add IT constaints.
658         (opcode_lookup): Allow conditional suffixes on all instructions in
659         Thumb mode.
660         (md_assemble): Advance condexec state before checking for errors.
661         (insns): Use do_t_cps.
662
663 2006-03-20  Paul Brook  <paul@codesourcery.com>
664
665         * config/tc-arm.c (output_relax_insn): Call dwarf2_emit_insn before
666         outputting the insn.
667
668 2006-03-18  Jan-Benedict Glaw  <jbglaw@lug-owl.de>
669
670         * config/tc-vax.c: Update copyright year.
671         * config/tc-vax.h: Likewise.
672
673 2006-03-18  Jan-Benedict Glaw  <jbglaw@lug-owl.de>
674
675         * config/tc-vax.c (md_chars_to_number): Used only locally, so
676         make it static.
677         * config/tc-vax.h (md_chars_to_number): Remove obsolete declaration.
678
679 2006-03-17  Paul Brook  <paul@codesourcery.com>
680
681         * config/tc-arm.c (insns): Add ldm and stm.
682
683 2006-03-17  Ben Elliston  <bje@au.ibm.com>
684
685         PR gas/2446
686         * doc/as.texinfo (Ident): Document this directive more thoroughly.
687
688 2006-03-16  Paul Brook  <paul@codesourcery.com>
689
690         * config/tc-arm.c (insns): Add "svc".
691
692 2006-03-13  Bob Wilson  <bob.wilson@acm.org>
693
694         * config/tc-xtensa.c (xg_translate_sysreg_op): Remove has_underbar
695         flag and avoid double underscore prefixes.
696
697 2006-03-10  Paul Brook  <paul@codesourcery.com>
698
699         * config/tc-arm.c (md_begin): Handle EABIv5.
700         (arm_eabis): Add EF_ARM_EABI_VER5.
701         * doc/c-arm.texi: Document -meabi=5.
702
703 2006-03-10  Ben Elliston  <bje@au.ibm.com>
704
705         * app.c (do_scrub_chars): Simplify string handling.
706
707 2006-03-07  Richard Sandiford  <richard@codesourcery.com>
708             Daniel Jacobowitz  <dan@codesourcery.com>
709             Zack Weinberg  <zack@codesourcery.com>
710             Nathan Sidwell  <nathan@codesourcery.com>
711             Paul Brook  <paul@codesourcery.com>
712             Ricardo Anguiano  <anguiano@codesourcery.com>
713             Phil Edwards  <phil@codesourcery.com>
714
715         * config/tc-arm.c (md_apply_fix): Install a value of zero into a
716         BFD_RELOC_ARM_OFFSET_IMM field if we're going to generate a RELA
717         R_ARM_ABS12 reloc.
718         (tc_gen_reloc): Keep the original fx_offset for RELA pc-relative
719         relocs, but adjust by md_pcrel_from_section.  Create R_ARM_ABS12
720         relocations for BFD_RELOC_ARM_OFFSET_IMM on RELA targets.
721
722 2006-03-06  Bob Wilson  <bob.wilson@acm.org>
723
724         * config/tc-xtensa.c (xtensa_post_relax_hook): Generate literal tables
725         even when using the text-section-literals option.
726
727 2006-03-06  Nathan Sidwell  <nathan@codesourcery.com>
728
729         * config/tc-m68k.c (m68k_extensions): Allow 'float' on both m68k
730         and cf.
731         (m68k_ip): <case 'J'> Check we have some control regs.
732         (md_parse_option): Allow raw arch switch.
733         (m68k_init_arch): Better detection of arch/cpu mismatch.  Detect
734         whether 68881 or cfloat was meant by -mfloat.
735         (md_show_usage): Adjust extension display.
736         (m68k_elf_final_processing): Adjust.
737
738 2006-03-03  Bjoern Haase  <bjoern.m.haase@web.de>
739
740         * config/tc-avr.c (avr_mod_hash_value): New function.
741         (md_apply_fix, exp_mod): Use BFD_RELOC_HH8_LDI and
742         BFD_RELOC_MS8_LDI for hlo8() and hhi8() 
743         (md_begin): Set linkrelax variable to 1, use avr_mod_hash_value
744         instead of int avr_ldi_expression: use avr_mod_hash_value instead
745         of (int).
746         (tc_gen_reloc): Handle substractions of symbols, if possible do
747         fixups, abort otherwise.        
748         * config/tc-avr.h (TC_LINKRELAX_FIXUP, TC_VALIDATE_FIX,
749         tc_fix_adjustable): Define.
750         
751 2006-03-02  James E Wilson  <wilson@specifix.com>
752
753         * config/tc-ia64.c (emit_one_bundle): For IA64_OPCODE_LAST, if we
754         change the template, then clear md.slot[curr].end_of_insn_group.
755
756 2006-02-28  Jan Beulich  <jbeulich@novell.com>
757
758         * macro.c (get_any_string): Don't insert quotes for <>-quoted input.
759
760 2006-02-28  Jan Beulich  <jbeulich@novell.com>
761
762         PR/1070
763         * macro.c (getstring): Don't treat parentheses special anymore.
764         (get_any_string): Don't consider '(' and ')' as quoting anymore.
765         Special-case '(', ')', '[', and ']' when dealing with non-quoting
766         characters.
767
768 2006-02-28  Mat <mat@csail.mit.edu>
769
770         * dwarf2dbg.c (get_filenum): Don't inadvertently decrease files_in_use.
771
772 2006-02-27  Jakub Jelinek  <jakub@redhat.com>
773
774         * dw2gencfi.c (struct fde_entry, struct cie_entry): Add signal_frame
775         field.
776         (CFI_signal_frame): Define.
777         (cfi_pseudo_table): Add .cfi_signal_frame.
778         (dot_cfi): Handle CFI_signal_frame.
779         (output_cie): Handle cie->signal_frame.
780         (select_cie_for_fde): Don't share CIE if signal_frame flag is
781         different.  Copy signal_frame from FDE to newly created CIE.
782         * doc/as.texinfo: Document .cfi_signal_frame.
783
784 2006-02-27  Carlos O'Donell  <carlos@codesourcery.com>
785
786         * doc/Makefile.am: Add html target.
787         * doc/Makefile.in: Regenerate.
788         * po/Make-in: Add html target.
789
790 2006-02-27  H.J. Lu <hongjiu.lu@intel.com>
791
792         * config/tc-i386.c (output_insn): Support Intel Merom New
793         Instructions.
794
795         * config/tc-i386.h (CpuMNI): New.
796         (CpuUnknownFlags): Add CpuMNI.
797
798 2006-02-24  David S. Miller  <davem@sunset.davemloft.net>
799
800         * config/tc-sparc.c (priv_reg_table): Add entry for "gl".
801         (hpriv_reg_table): New table for hyperprivileged registers.
802         (sparc_ip): New cases '$' and '%' for wrhpr/rdhpr hyperprivileged
803         register encoding.
804
805 2006-02-24  DJ Delorie  <dj@redhat.com>
806
807         * config/tc-m32c.h (md_apply_fix): Define to m32c_apply_fix.
808         (tc_gen_reloc): Don't define.
809         * config/tc-m32c.c (rl_for, relaxable): New convenience macros.
810         (OPTION_LINKRELAX): New.
811         (md_longopts): Add it.
812         (m32c_relax): New.
813         (md_parse_options): Set it.
814         (md_assemble): Emit relaxation relocs as needed.
815         (md_convert_frag): Emit relaxation relocs as needed.
816         (md_cgen_lookup_reloc): Add LAB_8_8 and LAB_8_16.
817         (m32c_apply_fix): New.
818         (tc_gen_reloc): New.
819         (m32c_force_relocation): Force out jump relocs when relaxing.
820         (m32c_fix_adjustable): Return false if relaxing.
821
822 2006-02-24  Paul Brook  <paul@codesourcery.com>
823
824         * config/arm/tc-arm.c (arm_ext_v6_notm, arm_ext_div, arm_ext_v7,
825         arm_ext_v7a, arm_ext_v7r, arm_ext_v7m): New variables.
826         (struct asm_barrier_opt): Define.
827         (arm_v7m_psr_hsh, arm_barrier_opt_hsh): New variables.
828         (parse_psr): Accept V7M psr names.
829         (parse_barrier): New function.
830         (enum operand_parse_code): Add OP_oBARRIER.
831         (parse_operands): Implement OP_oBARRIER.
832         (do_barrier): New function.
833         (do_dbg, do_pli, do_t_barrier, do_t_dbg, do_t_div): New functions.
834         (do_t_cpsi): Add V7M restrictions.
835         (do_t_mrs, do_t_msr): Validate V7M variants.
836         (md_assemble): Check for NULL variants.
837         (v7m_psrs, barrier_opt_names): New tables.
838         (insns): Add V7 instructions.  Mark V6 instructions absent from V7M.
839         (md_begin): Initialize arm_v7m_psr_hsh and arm_barrier_opt_hsh.
840         (arm_cpu_option_table): Add Cortex-M3, R4 and A8.
841         (arm_arch_option_table): Add armv7, armv7a, armv7r and armv7m.
842         (struct cpu_arch_ver_table): Define.
843         (cpu_arch_ver): New.
844         (aeabi_set_public_attributes): Use cpu_arch_ver.  Set
845         Tag_CPU_arch_profile.
846         * doc/c-arm.texi: Document new cpu and arch options.
847
848 2006-02-23  H.J. Lu  <hongjiu.lu@intel.com>
849
850         * config/tc-ia64.c (operand_match): Handle IA64_OPND_IMMU5b.
851
852 2006-02-23  H.J. Lu  <hongjiu.lu@intel.com>
853
854         * config/tc-ia64.c: Update copyright years.
855
856 2006-02-22  H.J. Lu  <hongjiu.lu@intel.com>
857
858         * config/tc-ia64.c (specify_resource): Add the rule 17 from
859         SDM 2.2.
860
861 2005-02-22  Paul Brook  <paul@codesourcery.com>
862
863         * config/tc-arm.c (do_pld): Remove incorrect write to
864         inst.instruction.
865         (encode_thumb32_addr_mode): Use correct operand.
866
867 2006-02-21  Paul Brook  <paul@codesourcery.com>
868
869         * config/tc-arm.c (md_apply_fix): Fix off-by-one errors.
870
871 2006-02-17  Shrirang Khisti  <shrirangk@kpitcummins.com>
872             Anil Paranjape   <anilp1@kpitcummins.com>
873             Shilin Shakti    <shilins@kpitcummins.com>
874
875         * Makefile.am: Add xc16x related entry.
876         * Makefile.in: Regenerate.
877         * configure.in: Added xc16x related entry.
878         * configure: Regenerate.
879         * config/tc-xc16x.h: New file
880         * config/tc-xc16x.c: New file
881         * doc/c-xc16x.texi: New file for xc16x
882         * doc/all.texi: Entry for xc16x
883         * doc/Makefile.texi: Added c-xc16x.texi 
884         * NEWS: Announce the support for the new target.
885
886 2006-02-16  Nick Hudson  <nick.hudson@dsl.pipex.com>
887
888         * configure.tgt: set emulation for mips-*-netbsd*
889
890 2006-02-14  Jakub Jelinek  <jakub@redhat.com>
891
892         * config.in: Rebuilt.
893
894 2006-02-13  Bob Wilson  <bob.wilson@acm.org>
895
896         * config/tc-xtensa.c (xg_add_opcode_fix): Number operands starting
897         from 1, not 0, in error messages.
898         (md_assemble): Simplify special-case check for ENTRY instructions.
899         (tinsn_has_invalid_symbolic_operands): Do not include opcode and
900         operand in error message.
901
902 2006-02-13  Joseph S. Myers  <joseph@codesourcery.com>
903
904         * configure.tgt (arm-*-linux-gnueabi*): Change to
905         arm-*-linux-*eabi*.
906
907 2006-02-10  Nick Clifton  <nickc@redhat.com>
908
909         * config/tc-crx.c (check_range): Ensure that the sign bit of a
910         32-bit value is propagated into the upper bits of a 64-bit long.
911
912         * config/tc-arc.c (init_opcode_tables): Fix cast.
913         (arc_extoper, md_operand): Likewise.
914
915 2006-02-09  David Heine  <dlheine@tensilica.com>
916
917         * config/tc-xtensa.c (xg_assembly_relax): Increment steps_taken for
918         each relaxation step.
919
920 2006-02-09  Eric Botcazou  <ebotcazou@libertysurf.fr>
921         
922         * configure.in (CHECK_DECLS): Add vsnprintf.
923         * configure: Regenerate.
924         * messages.c (errno.h, stdarg.h, varargs.h, va_list): Do not
925         include/declare here, but...
926         * as.h: Move code detecting VARARGS idiom to the top.
927         (errno.h, stdarg.h, varargs.h, va_list): ...here.
928         (vsnprintf): Declare if not already declared.
929
930 2006-02-08  H.J. Lu  <hongjiu.lu@intel.com>
931
932         * as.c (close_output_file): New.
933         (main): Register close_output_file with xatexit before
934         dump_statistics. Don't call output_file_close.
935
936 2006-02-07  Nathan Sidwell  <nathan@codesourcery.com>
937
938         * config/tc-m68k.c (mcf5208_control_regs, mcf5213_control_regs,
939         mcf5329_control_regs): New.
940         (not_current_architecture, selected_arch, selected_cpu): New.
941         (m68k_archs, m68k_extensions): New.
942         (archs): Renamed to ...
943         (m68k_cpus): ... here.  Adjust.
944         (n_arches): Remove.
945         (md_pseudo_table): Add arch and cpu directives.
946         (find_cf_chip, m68k_ip): Adjust table scanning.
947         (no_68851, no_68881): Remove.
948         (md_assemble): Lazily initialize.
949         (select_control_regs): Adjust cpu names. Add 5208, 5213, 5329.
950         (md_init_after_args): Move functionality to m68k_init_arch.
951         (mri_chip): Adjust table scanning.
952         (md_parse_option): Reimplement 'm' processing to add -march & -mcpu
953         options with saner parsing.
954         (m68k_lookup_cpu, m68k_set_arch, m68k_set_cpu, m68k_set_extension,
955         m68k_init_arch): New.
956         (s_m68k_cpu, s_m68k_arch): New.
957         (md_show_usage): Adjust.
958         (m68k_elf_final_processing): Set CF EF flags.
959         * config/tc-m68k.h (m68k_init_after_args): Remove.
960         (tc_init_after_args): Remove.
961         * doc/c-m68k.texi (M68K-Opts): Document -march, -mcpu options.
962         (M68k-Directives): Document .arch and .cpu directives.
963
964 2006-02-05  Arnold Metselaar  <arnold.metselaar@planet.nl>
965
966         * config/tc-z80.c (z80_start_line_hook): allow .equ and .defl as 
967         synonyms for equ and defl. 
968         (z80_cons_fix_new): New function.
969         (emit_byte): Disallow relative jumps to absolute locations.
970         (emit_data): Only handle defb, prototype changed, because defb is 
971         now handled as pseudo-op rather than an instruction.
972         (instab): Entries for defb,defw,db,dw moved from here...
973         (md_pseudo_table): ... to here, use generic cons() for defw,dw. 
974         Add entries for def24,def32,d24,d32.
975         (md_assemble): Improved error handling.
976         (md_apply_fix): New case BFD_RELOC_24, set fixP->fx_no_overflow to one.
977         * config/tc-z80.h (TC_CONS_FIX_NEW): Define.
978         (z80_cons_fix_new): Declare.
979         * doc/c-z80.texi (defb, db): Mention warning on overflow. 
980         (def24,d24,def32,d32): New pseudo-ops.
981         
982 2006-02-02  Paul Brook  <paul@codesourcery.com>
983
984         * config/tc-arm.c (do_shift): Remove Thumb-1 constraint.
985
986 2005-02-02  Paul Brook  <paul@codesourcery.com>
987
988         * config/tc-arm.c (T2_OPCODE_MASK, T2_DATA_OP_SHIFT, T2_OPCODE_AND,
989         T2_OPCODE_BIC, T2_OPCODE_ORR, T2_OPCODE_ORN, T2_OPCODE_EOR,
990         T2_OPCODE_ADD, T2_OPCODE_ADC, T2_OPCODE_SBC, T2_OPCODE_SUB,
991         T2_OPCODE_RSB): Define.
992         (thumb32_negate_data_op): New function.
993         (md_apply_fix): Use it.
994
995 2006-01-31  Bob Wilson  <bob.wilson@acm.org>
996
997         * config/xtensa-istack.h (TInsn): Remove record_fix and sub_symbol
998         fields.
999         * config/tc-xtensa.h (xtensa_frag_type): Remove slot_sub_symbols field.
1000         * config/tc-xtensa.c (md_apply_fix): Check for unexpected uses of
1001         subtracted symbols.
1002         (relaxation_requirements): Add pfinish_frag argument and use it to
1003         replace setting tinsn->record_fix fields.
1004         (xg_assemble_vliw_tokens): Adjust calls to relaxation_requirements
1005         and vinsn_to_insnbuf.  Remove references to record_fix and
1006         slot_sub_symbols fields.
1007         (xtensa_mark_narrow_branches): Delete unused code.
1008         (is_narrow_branch_guaranteed_in_range): Handle expr that is not just
1009         a symbol.
1010         (convert_frag_immed): Adjust vinsn_to_insnbuf call and do not set
1011         record_fix fields.
1012         (tinsn_immed_from_frag): Remove code for handling slot_sub_symbols.
1013         (vinsn_to_insnbuf): Change use of record_fixup argument, replacing use
1014         of the record_fix field.  Simplify error messages for unexpected
1015         symbolic operands.
1016         (set_expr_symbol_offset_diff): Delete.
1017
1018 2006-01-31  Paul Brook  <paul@codesourcery.com>
1019
1020         * config/tc-arm.c (arm_reg_parse): Check if reg is non-NULL.
1021
1022 2006-01-31  Paul Brook  <paul@codesourcery.com>
1023         Richard Earnshaw <rearnsha@arm.com>
1024
1025         * config/tc-arm.c: Use arm_feature_set.
1026         (arm_ext_*, arm_arch_full, arm_arch_t2, arm_arch_none,
1027         arm_cext_iwmmxt, arm_cext_xscale, arm_cext_maverick, fpu_fpa_ext_v1,
1028         fpu_fpa_ext_v2, fpu_vfp_ext_v1xd, fpu_vfp_ext_v1, fpu_vfp_ext_v2):
1029         New variables.
1030         (insns): Use them.
1031         (md_atof, opcode_select, opcode_select, md_assemble, md_assemble,
1032         md_begin, arm_parse_extension, arm_parse_cpu, arm_parse_arch,
1033         arm_parse_fpu, arm_parse_float_abi, aeabi_set_public_attributes,
1034         s_arm_cpu, s_arm_arch, s_arm_fpu): Use macros for accessing CPU
1035         feature flags.
1036         (arm_legacy_option_table, arm_option_cpu_value_table): New types.
1037         (arm_opts): Move old cpu/arch options from here...
1038         (arm_legacy_opts): ... to here.
1039         (md_parse_option): Search arm_legacy_opts.
1040         (arm_cpus, arm_archs, arm_extensions, arm_fpus)
1041         (arm_float_abis, arm_eabis): Make const.
1042
1043 2006-01-25  Bob Wilson  <bob.wilson@acm.org>
1044
1045         * config/tc-xtensa.c (md_apply_fix): Set value to zero for PLT relocs.
1046
1047 2006-01-21  Jie Zhang  <jie.zhang@analog.com>
1048
1049         * config/bfin-parse.y (asm_1): Check value range for 16 bit immediate
1050         in load immediate intruction.
1051
1052 2006-01-21  Jie Zhang  <jie.zhang@analog.com>
1053
1054         * config/bfin-parse.y (value_match): Use correct conversion
1055         specifications in template string for __FILE__ and __LINE__.
1056         (binary): Ditto.
1057         (unary): Ditto.
1058
1059 2006-01-18  Alexandre Oliva  <aoliva@redhat.com>
1060
1061         Introduce TLS descriptors for i386 and x86_64.
1062         * config/tc-i386.c (tc_i386_fix_adjustable): Handle
1063         BFD_RELOC_386_TLS_GOTDESC, BFD_RELOC_386_TLS_DESC_CALL,
1064         BFD_RELOC_X86_64_GOTPC32_TLSDESC, BFD_RELOC_X86_64_TLSDESC_CALL.
1065         (optimize_disp): Emit fix up for BFD_RELOC_386_TLS_DESC_CALL and
1066         BFD_RELOC_X86_64_TLSDESC_CALL immediately, and clear the
1067         displacement bits.
1068         (build_modrm_byte): Set up zero modrm for TLS desc calls.
1069         (lex_got): Handle @tlsdesc and @tlscall.
1070         (md_apply_fix, tc_gen_reloc): Handle the new relocations.
1071
1072 2006-01-11  Nick Clifton  <nickc@redhat.com>
1073
1074         Fixes for building on 64-bit hosts:
1075         * config/tc-avr.c (mod_index): New union to allow conversion
1076         between pointers and integers.
1077         (md_begin, avr_ldi_expression): Use it.
1078         * config/tc-i370.c (md_assemble): Add cast for argument to print
1079         statement.
1080         * config/tc-tic54x.c (subsym_substitute): Likewise.
1081         * config/tc-mn10200.c (md_assemble): Use a union to convert the
1082         opindex field of fr_cgen structure into a pointer so that it can
1083         be stored in a frag.
1084         * config/tc-mn10300.c (md_assemble): Likewise.
1085         * config/tc-frv.c (frv_debug_tomcat): Use %p to print pointer
1086         types.
1087         * config/tc-v850.c: Replace uses of (int) casts with correct
1088         types.
1089
1090 2006-01-09  H.J. Lu  <hongjiu.lu@intel.com>
1091
1092         PR gas/2117
1093         * symbols.c (snapshot_symbol): Don't change a defined symbol.
1094
1095 2006-01-03  Hans-Peter Nilsson  <hp@bitrange.com>
1096
1097         PR gas/2101
1098         * config/tc-mmix.c (mmix_handle_mmixal): Don't treat #[0-9][FB] as
1099         a local-label reference.
1100
1101 For older changes see ChangeLog-2005
1102 \f
1103 Local Variables:
1104 mode: change-log
1105 left-margin: 8
1106 fill-column: 74
1107 version-control: never
1108 End: