Home | History | Annotate | Download | only in config
      1 /* tc-mmix.h -- Header file for tc-mmix.c.
      2    Copyright (C) 2001-2014 Free Software Foundation, Inc.
      3    Written by Hans-Peter Nilsson (hp (at) bitrange.com).
      4 
      5    This file is part of GAS, the GNU Assembler.
      6 
      7    GAS is free software; you can redistribute it and/or modify
      8    it under the terms of the GNU General Public License as published by
      9    the Free Software Foundation; either version 3, or (at your option)
     10    any later version.
     11 
     12    GAS is distributed in the hope that it will be useful,
     13    but WITHOUT ANY WARRANTY; without even the implied warranty of
     14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
     15    GNU General Public License for more details.
     16 
     17    You should have received a copy of the GNU General Public License
     18    along with GAS; see the file COPYING.  If not, write to the Free
     19    Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
     20    02110-1301, USA.  */
     21 
     22 #define TC_MMIX
     23 
     24 /* See gas/doc/internals.texi for explanation of these macros.  */
     25 #define TARGET_FORMAT "elf64-mmix"
     26 #define TARGET_ARCH bfd_arch_mmix
     27 #define TARGET_BYTES_BIG_ENDIAN 1
     28 
     29 extern const char mmix_comment_chars[];
     30 #define tc_comment_chars mmix_comment_chars
     31 
     32 extern const char mmix_symbol_chars[];
     33 #define tc_symbol_chars mmix_symbol_chars
     34 
     35 extern const char mmix_exp_chars[];
     36 #define EXP_CHARS mmix_exp_chars
     37 
     38 extern const char mmix_flt_chars[];
     39 #define FLT_CHARS mmix_flt_chars
     40 
     41 /* "@" is a synonym for ".".  */
     42 #define LEX_AT (LEX_BEGIN_NAME)
     43 
     44 extern int mmix_label_without_colon_this_line (void);
     45 #define LABELS_WITHOUT_COLONS mmix_label_without_colon_this_line ()
     46 
     47 extern int mmix_next_semicolon_is_eoln;
     48 #define TC_EOL_IN_INSN(p) (*(p) == ';' && ! mmix_next_semicolon_is_eoln)
     49 
     50 /* This is one direction we can get mmixal compatibility.  */
     51 extern void mmix_handle_mmixal (void);
     52 #define md_start_line_hook mmix_handle_mmixal
     53 
     54 extern void mmix_md_begin (void);
     55 #define md_begin mmix_md_begin
     56 
     57 extern void mmix_md_end (void);
     58 #define md_end mmix_md_end
     59 
     60 extern int mmix_current_location \
     61   (void (*fn) (expressionS *), expressionS *);
     62 extern int mmix_parse_predefined_name (char *, expressionS *);
     63 
     64 extern char *mmix_current_prefix;
     65 
     66 /* A bit ugly, since we "know" that there's a static function
     67    current_location that does what we want.  We also strip off a leading
     68    ':' in another ugly way.
     69 
     70    The [DVWIOUZX]_Handler symbols are provided when-used.  */
     71 
     72 extern int mmix_gnu_syntax;
     73 #define md_parse_name(name, exp, mode, cpos)			\
     74  (! mmix_gnu_syntax						\
     75   && (name[0] == '@'						\
     76       ? (! is_part_of_name (name[1])				\
     77 	 && mmix_current_location (current_location, exp))	\
     78       : ((name[0] == ':' || ISUPPER (name[0]))			\
     79 	 && mmix_parse_predefined_name (name, exp))))
     80 
     81 extern char *mmix_prefix_name (char *);
     82 
     83 /* We implement when *creating* a symbol, we also need to strip a ':' or
     84    prepend a prefix.  */
     85 #define tc_canonicalize_symbol_name(x) \
     86  (mmix_current_prefix == NULL && (x)[0] != ':' ? (x) : mmix_prefix_name (x))
     87 
     88 #define md_undefined_symbol(x) NULL
     89 
     90 extern void mmix_fb_label (expressionS *);
     91 
     92 /* Since integer_constant is local to expr.c, we have to make this a
     93    macro.  FIXME: Do it cleaner.  */
     94 #define md_operand(exp)							\
     95   do									\
     96     {									\
     97       if (input_line_pointer[0] == '#')					\
     98 	{								\
     99 	  input_line_pointer++;						\
    100 	  integer_constant (16, (exp));					\
    101 	}								\
    102       else if (input_line_pointer[0] == '&'				\
    103 	       && input_line_pointer[1] != '&')				\
    104 	as_bad (_("`&' serial number operator is not supported"));	\
    105       else								\
    106 	mmix_fb_label (exp);						\
    107     }									\
    108   while (0)
    109 
    110 /* Gas dislikes the 2ADD, 8ADD etc. insns, so we have to assemble them in
    111    the error-recovery loop.  Hopefully there are no significant
    112    differences.  Also, space on a line isn't gracefully handled.  */
    113 extern int mmix_assemble_return_nonzero (char *);
    114 #define tc_unrecognized_line(c)						\
    115  ((c) == ' '								\
    116   || (((c) == '1' || (c) == '2' || (c) == '4' || (c) == '8')		\
    117       && mmix_assemble_return_nonzero (input_line_pointer - 1)))
    118 
    119 #define md_number_to_chars number_to_chars_bigendian
    120 
    121 #define WORKING_DOT_WORD
    122 
    123 extern const struct relax_type mmix_relax_table[];
    124 #define TC_GENERIC_RELAX_TABLE mmix_relax_table
    125 
    126 /* We use the relax table for everything except the GREG frags and PUSHJ.  */
    127 extern long mmix_md_relax_frag (segT, fragS *, long);
    128 #define md_relax_frag mmix_md_relax_frag
    129 
    130 #define tc_fix_adjustable(FIX)					\
    131  (((FIX)->fx_addsy == NULL					\
    132    || S_GET_SEGMENT ((FIX)->fx_addsy) != reg_section)		\
    133   && (FIX)->fx_r_type != BFD_RELOC_VTABLE_INHERIT		\
    134   && (FIX)->fx_r_type != BFD_RELOC_VTABLE_ENTRY			\
    135   && (FIX)->fx_r_type != BFD_RELOC_MMIX_LOCAL)
    136 
    137 /* Adjust symbols which are registers.  */
    138 #define tc_adjust_symtab() mmix_adjust_symtab ()
    139 extern void mmix_adjust_symtab (void);
    140 
    141 /* Here's where we make all symbols global, when so requested.
    142    We must avoid doing that for expression symbols or section symbols,
    143    though.  */
    144 extern int mmix_globalize_symbols;
    145 #define tc_frob_symbol(sym, punt)				\
    146   do								\
    147     {								\
    148       if (S_GET_SEGMENT (sym) == reg_section)			\
    149 	{							\
    150 	  if (S_GET_NAME (sym)[0] != '$'			\
    151 	      && S_GET_VALUE (sym) < 256)			\
    152 	    {							\
    153 	      if (mmix_globalize_symbols)			\
    154 		S_SET_EXTERNAL (sym);				\
    155 	      else						\
    156 		symbol_mark_used_in_reloc (sym);		\
    157 	    }							\
    158 	}							\
    159       else if (mmix_globalize_symbols				\
    160 	       && ! symbol_section_p (sym)			\
    161 	       && sym != section_symbol (absolute_section)	\
    162 	       && ! S_IS_LOCAL (sym))				\
    163 	S_SET_EXTERNAL (sym);					\
    164     }								\
    165   while (0)
    166 
    167 /* No shared lib support, so we don't need to ensure externally
    168    visible symbols can be overridden.  */
    169 #define EXTERN_FORCE_RELOC 0
    170 
    171 /* When relaxing, we need to emit various relocs we otherwise wouldn't.  */
    172 #define TC_FORCE_RELOCATION(fix) mmix_force_relocation (fix)
    173 extern int mmix_force_relocation (struct fix *);
    174 
    175 /* Call md_pcrel_from_section(), not md_pcrel_from().  */
    176 #define MD_PCREL_FROM_SECTION(FIX, SEC) md_pcrel_from_section (FIX, SEC)
    177 extern long md_pcrel_from_section (struct fix *, segT);
    178 
    179 #define md_section_align(seg, size) (size)
    180 
    181 #define LISTING_HEADER "GAS for MMIX"
    182 
    183 /* The default of 4 means Bcc expansion looks like it's missing a line.  */
    184 #define LISTING_LHS_CONT_LINES 5
    185 
    186 extern fragS *mmix_opcode_frag;
    187 #define TC_FRAG_TYPE fragS *
    188 #define TC_FRAG_INIT(frag) (frag)->tc_frag_data = mmix_opcode_frag
    189 
    190 /* We need to associate each section symbol with a list of GREGs defined
    191    for that section/segment and sorted on offset, between the point where
    192    all symbols have been evaluated and all frags mapped, and when the
    193    fixups are done and relocs are output.  Similarly for each unknown
    194    symbol.  */
    195 extern void mmix_frob_file (void);
    196 #define tc_frob_file_before_fix()					\
    197   do									\
    198     {									\
    199       int i = 0;							\
    200 									\
    201       /* It's likely mmix_frob_file changed (removed) sections, so make	\
    202 	 sure sections are correctly numbered as per renumber_sections,	\
    203 	 (static to write.c where this macro is called).  */		\
    204       mmix_frob_file ();						\
    205       bfd_map_over_sections (stdoutput, renumber_sections, &i);		\
    206     }									\
    207   while (0)
    208 
    209 /* Used by mmix_frob_file.  Hangs on section symbols and unknown symbols.  */
    210 struct mmix_symbol_gregs;
    211 #define TC_SYMFIELD_TYPE struct mmix_symbol_gregs *
    212 
    213 /* Used by relaxation, counting maximum needed PUSHJ stubs for a section.  */
    214 struct mmix_segment_info_type
    215  {
    216    /* We only need to keep track of the last stubbable frag because
    217       there's no less hackish way to keep track of different relaxation
    218       rounds.  */
    219    fragS *last_stubfrag;
    220    bfd_size_type nstubs;
    221  };
    222 #define TC_SEGMENT_INFO_TYPE struct mmix_segment_info_type
    223 
    224 extern void mmix_md_elf_section_change_hook (void);
    225 #define md_elf_section_change_hook mmix_md_elf_section_change_hook
    226 
    227 extern void mmix_md_do_align (int, char *, int, int);
    228 #define md_do_align(n, fill, len, max, label) \
    229  mmix_md_do_align (n, fill, len, max)
    230 
    231 /* Each insn is a tetrabyte (4 bytes) long, but if there are BYTE
    232    sequences sprinkled in, we can get unaligned DWARF2 offsets, so let's
    233    explicitly say one byte.  */
    234 #define DWARF2_LINE_MIN_INSN_LENGTH 1
    235 
    236 /* This target is buggy, and sets fix size too large.  */
    237 #define TC_FX_SIZE_SLACK(FIX) 6
    238 
    239 /* MMIX has global register symbols.  */
    240 #define TC_GLOBAL_REGISTER_SYMBOL_OK
    241