Fix comment.
[platform/upstream/binutils.git] / gas / config / tc-maxq.c
1 /* tc-maxq.c -- assembler code for a MAXQ chip.
2
3    Copyright 2004, 2005, 2006, 2007 Free Software Foundation, Inc.
4
5    Contributed by HCL Technologies Pvt. Ltd.
6
7    Author: Vineet Sharma(vineets@noida.hcltech.com) Inderpreet
8    S.(inderpreetb@noida.hcltech.com)
9
10    This file is part of GAS.
11
12    GAS is free software; you can redistribute it and/or modify it under the
13    terms of the GNU General Public License as published by the Free Software
14    Foundation; either version 3, or (at your option) any later version.
15
16    GAS is distributed in the hope that it will be useful, but WITHOUT ANY
17    WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
18    FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
19    details.
20
21    You should have received a copy of the GNU General Public License along
22    with GAS; see the file COPYING.  If not, write to the Free Software
23    Foundation, 51 Franklin Street - Fifth Floor, Boston, MA 02110-1301, USA.  */
24
25 #include "as.h"
26 #include "safe-ctype.h"
27 #include "subsegs.h"
28 #include "dwarf2dbg.h"
29 #include "tc-maxq.h"
30 #include "opcode/maxq.h"
31 #include "ctype.h"
32
33 #ifndef MAXQ10S
34 #define MAXQ10S 1
35 #endif
36
37 #ifndef DEFAULT_ARCH
38 #define DEFAULT_ARCH "MAXQ20"
39 #endif
40
41 #ifndef MAX_OPERANDS
42 #define MAX_OPERANDS 2
43 #endif
44
45 #ifndef MAX_MNEM_SIZE
46 #define MAX_MNEM_SIZE 8
47 #endif
48
49 #ifndef END_OF_INSN
50 #define END_OF_INSN '\0'
51 #endif
52
53 #ifndef IMMEDIATE_PREFIX
54 #define IMMEDIATE_PREFIX '#'
55 #endif
56
57 #ifndef MAX_REG_NAME_SIZE
58 #define MAX_REG_NAME_SIZE 4
59 #endif
60
61 #ifndef MAX_MEM_NAME_SIZE
62 #define MAX_MEM_NAME_SIZE 9
63 #endif
64
65 /* opcode for PFX[0].  */
66 #define PFX0 0x0b
67
68 /* Set default to MAXQ20.  */
69 unsigned int max_version = bfd_mach_maxq20;
70
71 const char *default_arch = DEFAULT_ARCH;
72
73 /* Type of the operand: Register,Immediate,Memory access,flag or bit.  */
74
75 union _maxq20_op
76 {
77   const reg_entry *  reg;
78   char               imms; /* This is to store the immediate value operand.  */
79   expressionS *      disps;
80   symbolS *          data;
81   const mem_access * mem;
82   int                flag;
83   const reg_bit *    r_bit;
84 };
85
86 typedef union _maxq20_op maxq20_opcode;
87
88 /* For handling optional L/S in Maxq20.  */
89
90 /* Exposed For Linker - maps indirectly to the liker relocations.  */
91 #define LONG_PREFIX             MAXQ_LONGJUMP   /* BFD_RELOC_16 */
92 #define SHORT_PREFIX            MAXQ_SHORTJUMP  /* BFD_RELOC_16_PCREL_S2 */
93 #define ABSOLUTE_ADDR_FOR_DATA  MAXQ_INTERSEGMENT
94
95 #define NO_PREFIX               0
96 #define EXPLICT_LONG_PREFIX     14
97
98 /* The main instruction structure containing fields to describe instrn */
99 typedef struct _maxq20_insn
100 {
101   /* The opcode information for the MAXQ20 */
102   MAXQ20_OPCODE_INFO op;
103
104   /* The number of operands */
105   unsigned int operands;
106
107   /* Number of different types of operands - Comments can be removed if reqd. 
108    */
109   unsigned int reg_operands, mem_operands, disp_operands, data_operands;
110   unsigned int imm_operands, imm_bit_operands, bit_operands, flag_operands;
111
112   /* Types of the individual operands */
113   UNKNOWN_OP types[MAX_OPERANDS];
114
115   /* Relocation type for operand : to be investigated into */
116   int reloc[MAX_OPERANDS];
117
118   /* Complete information of the Operands */
119   maxq20_opcode maxq20_op[MAX_OPERANDS];
120
121   /* Choice of prefix register whenever needed */
122   int prefix;
123
124   /* Optional Prefix for Instructions like LJUMP, SJUMP etc */
125   unsigned char Instr_Prefix;
126
127   /* 16 bit Instruction word */
128   unsigned char instr[2];
129 }
130 maxq20_insn;
131
132 /* Definitions of all possible characters that can start an operand.  */
133 const char *extra_symbol_chars = "@(#";
134
135 /* Special Character that would start a comment.  */
136 const char comment_chars[] = ";";
137
138 /* Starts a comment when it appears at the start of a line.  */
139 const char line_comment_chars[] = ";#";
140
141 const char line_separator_chars[] = ""; /* originally may b by sudeep "\n".  */
142
143 /*  The following are used for option processing.  */
144
145 /* This is added to the mach independent string passed to getopt.  */
146 const char *md_shortopts = "q";
147
148 /* Characters for exponent and floating point.  */
149 const char EXP_CHARS[] = "eE";
150 const char FLT_CHARS[] = "";
151
152 /* This is for the machine dependent option handling.  */
153 #define OPTION_EB               (OPTION_MD_BASE + 0)
154 #define OPTION_EL               (OPTION_MD_BASE + 1)
155 #define MAXQ_10                 (OPTION_MD_BASE + 2)
156 #define MAXQ_20                 (OPTION_MD_BASE + 3)
157
158 struct option md_longopts[] =
159 {
160   {"MAXQ10", no_argument, NULL, MAXQ_10},
161   {"MAXQ20", no_argument, NULL, MAXQ_20},
162   {NULL, no_argument, NULL, 0}
163 };
164 size_t md_longopts_size = sizeof (md_longopts);
165
166 /* md_undefined_symbol We have no need for this function.  */
167
168 symbolS *
169 md_undefined_symbol (char * name ATTRIBUTE_UNUSED)
170 {
171   return NULL;
172 }
173
174 static void
175 maxq_target (int target)
176 {
177   max_version = target;
178   bfd_set_arch_mach (stdoutput, bfd_arch_maxq, max_version);
179 }
180
181 int
182 md_parse_option (int c, char *arg ATTRIBUTE_UNUSED)
183 {
184   /* Any options support will be added onto this switch case.  */
185   switch (c)
186     {
187     case MAXQ_10:
188       max_version = bfd_mach_maxq10;
189       break;
190     case MAXQ_20:
191       max_version = bfd_mach_maxq20;
192       break;
193
194     default:
195       return 0;
196     }
197
198   return 1;
199 }
200
201 /* When a usage message is printed, this function is called and
202    it prints a description of the machine specific options.  */
203
204 void
205 md_show_usage (FILE * stream)
206 {
207   /* Over here we will fill the description of the machine specific options.  */
208
209   fprintf (stream, _(" MAXQ-specific assembler options:\n"));
210
211   fprintf (stream, _("\
212         -MAXQ20                generate obj for MAXQ20(default)\n\
213         -MAXQ10                generate obj for MAXQ10\n\
214         "));
215 }
216
217 unsigned long
218 maxq20_mach (void)
219 {
220   if (!(strcmp (default_arch, "MAXQ20")))
221     return 0;
222
223   as_fatal (_("Unknown architecture"));
224   return 1;
225 }
226
227 arelent *
228 tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
229 {
230   arelent *rel;
231   bfd_reloc_code_real_type code;
232
233   switch (fixp->fx_r_type)
234     {
235     case MAXQ_INTERSEGMENT:
236     case MAXQ_LONGJUMP:
237     case BFD_RELOC_16_PCREL_S2:
238       code = fixp->fx_r_type;
239       break;
240
241     case 0:
242     default:
243       switch (fixp->fx_size)
244         {
245         default:
246           as_bad_where (fixp->fx_file, fixp->fx_line,
247                         _("can not do %d byte relocation"), fixp->fx_size);
248           code = BFD_RELOC_32;
249           break;
250
251         case 1:
252           code = BFD_RELOC_8;
253           break;
254         case 2:
255           code = BFD_RELOC_16;
256           break;
257         case 4:
258           code = BFD_RELOC_32;
259           break;
260         }
261     }
262
263   rel = xmalloc (sizeof (arelent));
264   rel->sym_ptr_ptr  = xmalloc (sizeof (asymbol *));
265   *rel->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
266
267   rel->address = fixp->fx_frag->fr_address + fixp->fx_where;
268   rel->addend  = fixp->fx_addnumber;
269   rel->howto   = bfd_reloc_type_lookup (stdoutput, code);
270
271   if (rel->howto == NULL)
272     {
273       as_bad_where (fixp->fx_file, fixp->fx_line,
274                     _("cannot represent relocation type %s"),
275                     bfd_get_reloc_code_name (code));
276
277       /* Set howto to a garbage value so that we can keep going.  */
278       rel->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_32);
279       assert (rel->howto != NULL);
280     }
281
282   return rel;
283 }
284
285 /* md_estimate_size_before_relax()
286
287    Called just before relax() for rs_machine_dependent frags.  The MAXQ
288    assembler uses these frags to handle 16 bit absolute jumps which require a 
289    prefix instruction to be inserted. Any symbol that is now undefined will
290    not become defined. Return the correct fr_subtype in the frag. Return the
291    initial "guess for variable size of frag"(This will be eiter 2 or 0) to
292    caller. The guess is actually the growth beyond the fixed part.  Whatever
293    we do to grow the fixed or variable part contributes to our returned
294    value.  */
295
296 int
297 md_estimate_size_before_relax (fragS *fragP, segT segment)
298 {
299   /* Check whether the symbol has been resolved or not.
300      Otherwise we will have to generate a fixup.  */
301   if ((S_GET_SEGMENT (fragP->fr_symbol) != segment)
302       || fragP->fr_subtype == EXPLICT_LONG_PREFIX)
303     {
304       RELOC_ENUM reloc_type;
305       unsigned char *opcode;
306       int old_fr_fix;
307
308       /* Now this symbol has not been defined in this file.
309          Hence we will have to create a fixup.  */
310       int size = 2;
311
312       /* This is for the prefix instruction.  */
313
314       if (fragP->fr_subtype == EXPLICT_LONG_PREFIX)
315         fragP->fr_subtype = LONG_PREFIX;
316
317       if (S_GET_SEGMENT (fragP->fr_symbol) != segment
318           && ((!(fragP->fr_subtype) == EXPLICT_LONG_PREFIX)))
319         fragP->fr_subtype = ABSOLUTE_ADDR_FOR_DATA;
320
321       reloc_type =
322         (fragP->fr_subtype ? fragP->fr_subtype : ABSOLUTE_ADDR_FOR_DATA);
323
324       fragP->fr_subtype = reloc_type;
325
326       if (reloc_type == SHORT_PREFIX)
327         size = 0;
328       old_fr_fix = fragP->fr_fix;
329       opcode = (unsigned char *) fragP->fr_opcode;
330
331       fragP->fr_fix += (size);
332
333       fix_new (fragP, old_fr_fix - 2, size + 2,
334                fragP->fr_symbol, fragP->fr_offset, 0, reloc_type);
335       frag_wane (fragP);
336       return fragP->fr_fix - old_fr_fix;
337     }
338
339   if (fragP->fr_subtype == SHORT_PREFIX)
340     {
341       fragP->fr_subtype = SHORT_PREFIX;
342       return 0;
343     }
344
345   if (fragP->fr_subtype == NO_PREFIX || fragP->fr_subtype == LONG_PREFIX)
346     {
347       unsigned long instr;
348       unsigned long call_addr;
349       long diff;
350       fragS *f;
351       diff = diff ^ diff;;
352       call_addr = call_addr ^ call_addr;
353       instr = 0;
354       f = NULL;
355
356       /* segment_info_type *seginfo = seg_info (segment);  */
357       instr = fragP->fr_address + fragP->fr_fix - 2;
358
359       /* This is the offset if it is a PC relative jump.  */
360       call_addr = S_GET_VALUE (fragP->fr_symbol) + fragP->fr_offset;
361
362       /* PC stores the value of the next instruction.  */
363       diff = (call_addr - instr) - 1;
364
365       if (diff >= (-128 * 2) && diff <= (2 * 127))
366         {
367           /* Now as offset is an 8 bit value, we will pass
368              that to the jump instruction directly.  */
369           fragP->fr_subtype = NO_PREFIX;
370           return 0;
371         }
372
373       fragP->fr_subtype = LONG_PREFIX;
374       return 2;
375     }
376
377   as_fatal (_("Illegal Reloc type in md_estimate_size_before_relax for line : %d"),
378             frag_now->fr_line);
379   return 0;
380 }
381
382 /* Equal to MAX_PRECISION in atof-ieee.c */
383 #define MAX_LITTLENUMS 6
384
385 /* Turn a string in input_line_pointer into a floating point constant of type 
386    TYPE, and store the appropriate bytes in *LITP.  The number of LITTLENUMS
387    emitted is stored in *SIZEP.  An error message is returned, or NULL on OK.  */
388
389 char *
390 md_atof (int type, char * litP, int * sizeP)
391 {
392   int prec;
393   LITTLENUM_TYPE words[4];
394   char *t;
395   int i;
396
397   switch (type)
398     {
399     case 'f':
400       prec = 2;
401       break;
402
403     case 'd':
404       prec = 2;
405       /* The size of Double has been changed to 2 words ie 32 bits.  */
406       /* prec = 4; */
407       break;
408
409     default:
410       *sizeP = 0;
411       return _("bad call to md_atof");
412     }
413
414   t = atof_ieee (input_line_pointer, type, words);
415   if (t)
416     input_line_pointer = t;
417
418   *sizeP = prec * 2;
419
420   for (i = prec - 1; i >= 0; i--)
421     {
422       md_number_to_chars (litP, (valueT) words[i], 2);
423       litP += 2;
424     }
425
426   return NULL;
427 }
428
429 void
430 maxq20_cons_fix_new (fragS * frag, unsigned int off, unsigned int len,
431                      expressionS * exp)
432 {
433   int r = 0;
434
435   switch (len)
436     {
437     case 2:
438       r = MAXQ_WORDDATA;        /* Word+n */
439       break;
440     case 4:
441       r = MAXQ_LONGDATA;        /* Long+n */
442       break;
443     }
444
445   fix_new_exp (frag, off, len, exp, 0, r);
446   return;
447 }
448
449 /* GAS will call this for every rs_machine_dependent fragment. The
450    instruction is completed using the data from the relaxation pass. It may
451    also create any necessary relocations.  */
452 void
453 md_convert_frag (bfd *   headers ATTRIBUTE_UNUSED,
454                  segT    seg ATTRIBUTE_UNUSED,
455                  fragS * fragP)
456 {
457   char *opcode;
458   offsetT target_address;
459   offsetT opcode_address;
460   offsetT displacement_from_opcode_start;
461   int address;
462
463   opcode = fragP->fr_opcode;
464   address = 0;
465   target_address = opcode_address = displacement_from_opcode_start = 0;
466
467   target_address =
468     (S_GET_VALUE (fragP->fr_symbol) / MAXQ_OCTETS_PER_BYTE) +
469     (fragP->fr_offset / MAXQ_OCTETS_PER_BYTE);
470
471   opcode_address =
472     (fragP->fr_address / MAXQ_OCTETS_PER_BYTE) +
473     ((fragP->fr_fix - 2) / MAXQ_OCTETS_PER_BYTE);
474
475   /* PC points to the next Instruction.  */
476   displacement_from_opcode_start = ((target_address - opcode_address)  - 1);
477
478   if ((displacement_from_opcode_start >= -128
479        && displacement_from_opcode_start <= 127)
480       && (fragP->fr_subtype == SHORT_PREFIX
481           || fragP->fr_subtype == NO_PREFIX))
482     {
483       /* Its a displacement.  */
484       *opcode = (char) displacement_from_opcode_start;
485     }
486   else
487     {
488       /* Its an absolute 16 bit jump. Now we have to
489          load the prefix operator with the upper 8 bits.  */
490       if (fragP->fr_subtype == SHORT_PREFIX)
491         {
492           as_bad (_("Cant make long jump/call into short jump/call : %d"),
493                   fragP->fr_line);
494           return;
495         }
496
497       /* Check whether the symbol has been resolved or not.
498          Otherwise we will have to generate a fixup.  */
499
500       if (fragP->fr_subtype != SHORT_PREFIX)
501         {
502           RELOC_ENUM reloc_type;
503           int old_fr_fix;
504           int size = 2;
505
506           /* Now this is a basolute jump/call.
507              Hence we will have to create a fixup.  */
508           if (fragP->fr_subtype == NO_PREFIX)
509             fragP->fr_subtype = LONG_PREFIX;
510
511           reloc_type =
512             (fragP->fr_subtype ? fragP->fr_subtype : LONG_PREFIX);
513
514           if (reloc_type == 1)
515             size = 0;
516           old_fr_fix = fragP->fr_fix;
517
518           fragP->fr_fix += (size);
519
520           fix_new (fragP, old_fr_fix - 2, size + 2,
521                    fragP->fr_symbol, fragP->fr_offset, 0, reloc_type);
522           frag_wane (fragP);
523         }
524     }
525 }
526
527 long
528 md_pcrel_from (fixS *fixP)
529 {
530   return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
531 }
532
533 /* Writes the val to the buf, where n is the nuumber of bytes to write.  */
534
535 void
536 maxq_number_to_chars (char *buf, valueT val, int n)
537 {
538   if (target_big_endian)
539     number_to_chars_bigendian (buf, val, n);
540   else
541     number_to_chars_littleendian (buf, val, n);
542 }
543
544 /* GAS will call this for each fixup. It's main objective is to store the
545    correct value in the object file. 'fixup_segment' performs the generic
546    overflow check on the 'valueT *val' argument after md_apply_fix returns.
547    If the overflow check is relevant for the target machine, then
548    'md_apply_fix' should modify 'valueT *val', typically to the value stored 
549    in the object file (not to be done in MAXQ).  */
550
551 void
552 md_apply_fix (fixS *fixP, valueT *valT, segT seg ATTRIBUTE_UNUSED)
553 {
554   char *p = fixP->fx_frag->fr_literal + fixP->fx_where;
555   char *frag_to_fix_at =
556     fixP->fx_frag->fr_literal + fixP->fx_frag->fr_fix - 2;
557
558   if (fixP)
559     {
560       if (fixP->fx_frag && valT)
561         {
562           /* If the relaxation substate is not defined we make it equal
563              to the kind of relocation the fixup is generated for.  */
564           if (!fixP->fx_frag->fr_subtype)
565             fixP->fx_frag->fr_subtype = fixP->fx_r_type;
566
567           /* For any instruction in which either we have specified an
568              absolute address or it is a long jump we need to add a PFX0
569              instruction to it. In this case as the instruction has already
570              being written at 'fx_where' in the frag we copy it at the end of 
571              the frag(which is where the relocation was generated) as when
572              the relocation is generated the frag is grown by 2 type, this is 
573              where we copy the contents of fx_where and add a pfx0 at
574              fx_where.  */
575           if ((fixP->fx_frag->fr_subtype == ABSOLUTE_ADDR_FOR_DATA)
576               || (fixP->fx_frag->fr_subtype == LONG_PREFIX))
577             {
578               *(frag_to_fix_at + 1) = *(p + 1);
579               maxq_number_to_chars (p + 1, PFX0, 1);
580             }
581
582           /* Remember value for tc_gen_reloc.  */
583           fixP->fx_addnumber = *valT;
584         }
585
586       /* Some fixups generated by GAS which gets resovled before this this
587          func. is called need to be wriiten to the frag as here we are going
588          to go away with the relocations fx_done=1.  */
589       if (fixP->fx_addsy == NULL)
590         {
591           maxq_number_to_chars (p, *valT, fixP->fx_size);
592           fixP->fx_addnumber = *valT;
593           fixP->fx_done = 1;
594         }
595     }
596 }
597
598 /* Tables for lexical analysis.  */
599 static char mnemonic_chars[256];
600 static char register_chars[256];
601 static char operand_chars[256];
602 static char identifier_chars[256];
603 static char digit_chars[256];
604
605 /* Lexical Macros.  */
606 #define is_mnemonic_char(x)   (mnemonic_chars[(unsigned char)(x)])
607 #define is_register_char(x)   (register_chars[(unsigned char)(x)])
608 #define is_operand_char(x)    (operand_chars[(unsigned char)(x)])
609 #define is_space_char(x)      (x==' ')
610 #define is_identifier_char(x) (identifier_chars[(unsigned char)(x)])
611 #define is_digit_char(x)      (identifier_chars[(unsigned char)(x)])
612
613 /* Special characters for operands.  */
614 static char operand_special_chars[] = "[]@.-+";
615
616 /* md_assemble() will always leave the instruction passed to it unaltered.
617    To do this we store the instruction in a special stack.  */
618 static char save_stack[32];
619 static char *save_stack_p;
620
621 #define END_STRING_AND_SAVE(s)  \
622   do                            \
623     {                           \
624       *save_stack_p++ = *(s);   \
625       *s = '\0';                \
626     }                           \
627   while (0)
628
629 #define RESTORE_END_STRING(s)   \
630   do                            \
631     {                           \
632       *(s) = *(--save_stack_p); \
633     }                           \
634   while (0)
635
636 /* The instruction we are assembling.  */
637 static maxq20_insn i;
638
639 /* The current template.  */
640 static MAXQ20_OPCODES *current_templates;
641
642 /* The displacement operand if any.  */
643 static expressionS disp_expressions;
644
645 /* Current Operand we are working on (0:1st operand,1:2nd operand).  */
646 static int this_operand;
647
648 /* The prefix instruction if used.  */
649 static char PFX_INSN[2];
650 static char INSERT_BUFFER[2];
651
652 /* For interface with expression() ????? */
653 extern char *input_line_pointer;
654
655 /* The HASH Tables:  */
656
657 /* Operand Hash Table.  */
658 static struct hash_control *op_hash;
659
660 /* Register Hash Table.  */
661 static struct hash_control *reg_hash;
662
663 /* Memory reference Hash Table.  */
664 static struct hash_control *mem_hash;
665
666 /* Bit hash table.  */
667 static struct hash_control *bit_hash;
668
669 /* Memory Access syntax table.  */
670 static struct hash_control *mem_syntax_hash;
671
672 /* This is a mapping from pseudo-op names to functions.  */
673
674 const pseudo_typeS md_pseudo_table[] =
675 {
676   {"int", cons, 2},             /* size of 'int' has been changed to 1 word
677                                    (i.e) 16 bits.  */
678   {"maxq10", maxq_target, bfd_mach_maxq10},
679   {"maxq20", maxq_target, bfd_mach_maxq20},
680   {NULL, 0, 0},
681 };
682
683 #define SET_PFX_ARG(x) (PFX_INSN[1] = x)
684
685
686 /* This function sets the PFX value corresponding to the specs. Source
687    Destination Index Selection ---------------------------------- Write To|
688    SourceRegRange | Dest Addr Range
689    ------------------------------------------------------ PFX[0] | 0h-Fh |
690    0h-7h PFX[1] | 10h-1Fh | 0h-7h PFX[2] | 0h-Fh | 8h-Fh PFX[3] | 10h-1Fh |
691    8h-Fh PFX[4] | 0h-Fh | 10h-17h PFX[5] | 10h-1Fh | 10h-17h PFX[6] | 0h-Fh | 
692    18h-1Fh PFX[7] | 0h-Fh | 18h-1Fh */
693
694 static void
695 set_prefix (void)
696 {
697   short int src_index = 0, dst_index = 0;
698
699   if (i.operands == 0)
700     return;
701   if (i.operands == 1)          /* Only SRC is Present */
702     {
703       if (i.types[0] == REG)
704         {
705           if (!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
706             {
707               dst_index = i.maxq20_op[0].reg[0].Mod_index;
708               src_index = 0x00;
709             }
710           else
711             {
712               src_index = i.maxq20_op[0].reg[0].Mod_index;
713               dst_index = 0x00;
714             }
715         }
716     }
717
718   if (i.operands == 2)
719     {
720       if (i.types[0] == REG && i.types[1] == REG)
721         {
722           dst_index = i.maxq20_op[0].reg[0].Mod_index;
723           src_index = i.maxq20_op[1].reg[0].Mod_index;
724         }
725       else if (i.types[0] != REG && i.types[1] == REG)  /* DST is Absent */
726         {
727           src_index = i.maxq20_op[1].reg[0].Mod_index;
728           dst_index = 0x00;
729         }
730       else if (i.types[0] == REG && i.types[1] != REG)  /* Id SRC is Absent */
731         {
732           dst_index = i.maxq20_op[0].reg[0].Mod_index;
733           src_index = 0x00;
734         }
735       else if (i.types[0] == BIT && i.maxq20_op[0].r_bit)
736         {
737           dst_index = i.maxq20_op[0].r_bit->reg->Mod_index;
738           src_index = 0x00;
739         }
740
741       else if (i.types[1] == BIT && i.maxq20_op[1].r_bit)
742         {
743           dst_index = 0x00;
744           src_index = i.maxq20_op[1].r_bit->reg->Mod_index;
745         }
746     }
747
748   if (src_index >= 0x00 && src_index <= 0xF)
749     {
750       if (dst_index >= 0x00 && dst_index <= 0x07)
751         /* Set PFX[0] */
752         i.prefix = 0;
753
754       else if (dst_index >= 0x08 && dst_index <= 0x0F)
755         /* Set PFX[2] */
756         i.prefix = 2;
757
758       else if (dst_index >= 0x10 && dst_index <= 0x17)
759         /* Set PFX[4] */
760         i.prefix = 4;
761
762       else if (dst_index >= 0x18 && dst_index <= 0x1F)
763         /* Set PFX[6] */
764         i.prefix = 6;
765     }
766   else if (src_index >= 0x10 && src_index <= 0x1F)
767     {
768       if (dst_index >= 0x00 && dst_index <= 0x07)
769         /* Set PFX[1] */
770         i.prefix = 1;
771
772       else if (dst_index >= 0x08 && dst_index <= 0x0F)
773         /* Set PFX[3] */
774         i.prefix = 3;
775
776       else if (dst_index >= 0x10 && dst_index <= 0x17)
777         /* Set PFX[5] */
778         i.prefix = 5;
779
780       else if (dst_index >= 0x18 && dst_index <= 0x1F)
781         /* Set PFX[7] */
782         i.prefix = 7;
783     }
784 }
785
786 static unsigned char
787 is_a_LSinstr (const char *ln_pointer)
788 {
789   int i = 0;
790
791   for (i = 0; LSInstr[i] != NULL; i++)
792     if (!strcmp (LSInstr[i], ln_pointer))
793       return 1;
794
795   return 0;
796 }
797
798 static void
799 LS_processing (const char *line)
800 {
801   if (is_a_LSinstr (line))
802     {
803       if ((line[0] == 'L') || (line[0] == 'l'))
804         {
805           i.prefix = 0;
806           INSERT_BUFFER[0] = PFX0;
807           i.Instr_Prefix = LONG_PREFIX;
808         }
809       else if ((line[0] == 'S') || (line[0] == 's'))
810         i.Instr_Prefix = SHORT_PREFIX;
811       else
812         i.Instr_Prefix = NO_PREFIX;
813     }
814   else
815     i.Instr_Prefix = LONG_PREFIX;
816 }
817
818 /* Separate mnemonics and the operands.  */
819
820 static char *
821 parse_insn (char *line, char *mnemonic)
822 {
823   char *l = line;
824   char *token_start = l;
825   char *mnem_p;
826   char temp[MAX_MNEM_SIZE];
827   int ii = 0;
828
829   memset (temp, END_OF_INSN, MAX_MNEM_SIZE);
830   mnem_p = mnemonic;
831
832   while ((*mnem_p = mnemonic_chars[(unsigned char) *l]) != 0)
833     {
834       ii++;
835       mnem_p++;
836       if (mnem_p >= mnemonic + MAX_MNEM_SIZE)
837         {
838           as_bad (_("no such instruction: `%s'"), token_start);
839           return NULL;
840         }
841       l++;
842     }
843
844   if (!is_space_char (*l) && *l != END_OF_INSN)
845     {
846       as_bad (_("invalid character %s in mnemonic"), l);
847       return NULL;
848     }
849
850   while (ii)
851     {
852       temp[ii - 1] = toupper ((char) mnemonic[ii - 1]);
853       ii--;
854     }
855
856   LS_processing (temp);
857
858   if (i.Instr_Prefix != 0 && is_a_LSinstr (temp))
859     /* Skip the optional L-S.  */
860     memcpy (temp, temp + 1, MAX_MNEM_SIZE);
861
862   /* Look up instruction (or prefix) via hash table.  */
863   current_templates = (MAXQ20_OPCODES *) hash_find (op_hash, temp);
864
865   if (current_templates != NULL)
866     return l;
867
868   as_bad (_("no such instruction: `%s'"), token_start);
869   return NULL;
870 }
871
872 /* Function to calculate x to the power of y.
873    Just to avoid including the math libraries.  */
874
875 static int
876 pwr (int x, int y)
877 {
878   int k, ans = 1;
879
880   for (k = 0; k < y; k++)
881     ans *= x;
882
883   return ans;
884 }
885
886 static reg_entry *
887 parse_reg_by_index (char *imm_start)
888 {
889   int k = 0, mid = 0, rid = 0, val = 0, j = 0;
890   char temp[4] = { 0 };
891   reg_entry *reg = NULL;
892
893   do
894     {
895       if (isdigit (imm_start[k]))
896         temp[k] = imm_start[k] - '0';
897
898       else if (isalpha (imm_start[k])
899                && (imm_start[k] = tolower (imm_start[k])) < 'g')
900         temp[k] = 10 + (int) (imm_start[k] - 'a');
901
902       else if (imm_start[k] == 'h')
903         break;
904
905       else if (imm_start[k] == END_OF_INSN)
906         {
907           imm_start[k] = 'd';
908           break;
909         }
910
911       else
912         return NULL;            /* not a hex digit */
913
914       k++;
915     }
916   while (imm_start[k] != '\n');
917
918   switch (imm_start[k])
919     {
920     case 'h':
921       for (j = 0; j < k; j++)
922         val += temp[j] * pwr (16, k - j - 1);
923       break;
924
925     case 'd':
926       for (j = 0; j < k; j++)
927         {
928           if (temp[j] > 9)
929             return NULL;        /* not a number */
930
931           val += temp[j] * pwr (10, k - j - 1);
932           break;
933         }
934     }
935
936   /* Get the module and register id's.  */
937   mid = val & 0x0f;
938   rid = (val >> 4) & 0x0f;
939
940   if (mid < 6)
941     {
942       /* Search the pheripheral reg table.  */
943       for (j = 0; j < num_of_reg; j++)
944         {
945           if (new_reg_table[j].opcode == val)
946             {
947               reg = (reg_entry *) & new_reg_table[j];
948               break;
949             }
950         }
951     }
952
953   else
954     {
955       /* Search the system register table.  */
956       j = 0;
957
958       while (system_reg_table[j].reg_name != NULL)
959         {
960           if (system_reg_table[j].opcode == val)
961             {
962               reg = (reg_entry *) & system_reg_table[j];
963               break;
964             }
965           j++;
966         }
967     }
968
969   if (reg == NULL)
970     {
971       as_bad (_("Invalid register value %s"), imm_start);
972       return reg;
973     }
974
975 #if CHANGE_PFX
976   if (this_operand == 0 && reg != NULL)
977     {
978       if (reg->Mod_index > 7)
979         i.prefix = 2;
980       else
981         i.prefix = 0;
982     }
983 #endif
984   return (reg_entry *) reg;
985 }
986
987 /* REG_STRING starts *before* REGISTER_PREFIX.  */
988
989 static reg_entry *
990 parse_register (char *reg_string, char **end_op)
991 {
992   char *s = reg_string;
993   char *p = NULL;
994   char reg_name_given[MAX_REG_NAME_SIZE + 1];
995   reg_entry *r = NULL;
996
997   r = NULL;
998   p = NULL;
999
1000   /* Skip possible REGISTER_PREFIX and possible whitespace.  */
1001   if (is_space_char (*s))
1002     ++s;
1003
1004   p = reg_name_given;
1005   while ((*p++ = register_chars[(unsigned char) *s]) != '\0')
1006     {
1007       if (p >= reg_name_given + MAX_REG_NAME_SIZE)
1008         return (reg_entry *) NULL;
1009       s++;
1010     }
1011
1012   *end_op = s;
1013
1014   r = (reg_entry *) hash_find (reg_hash, reg_name_given);
1015
1016 #if CHANGE_PFX
1017   if (this_operand == 0 && r != NULL)
1018     {
1019       if (r->Mod_index > 7)
1020         i.prefix = 2;
1021       else
1022         i.prefix = 0;
1023     }
1024 #endif
1025   return r;
1026 }
1027
1028 static reg_bit *
1029 parse_register_bit (char *reg_string, char **end_op)
1030 {
1031   const char *s = reg_string;
1032   short k = 0;
1033   char diff = 0;
1034   reg_bit *rb = NULL;
1035   reg_entry *r = NULL;
1036   bit_name *b = NULL;
1037   char temp_bitname[MAX_REG_NAME_SIZE + 2];
1038   char temp[MAX_REG_NAME_SIZE + 1];
1039
1040   memset (&temp, '\0', (MAX_REG_NAME_SIZE + 1));
1041   memset (&temp_bitname, '\0', (MAX_REG_NAME_SIZE + 2));
1042
1043   diff = 0;
1044   r = NULL;
1045   rb = NULL;
1046   rb = xmalloc (sizeof (reg_bit));
1047   rb->reg = xmalloc (sizeof (reg_entry));
1048   k = 0;
1049
1050   /* For supporting bit names.  */
1051   b = (bit_name *) hash_find (bit_hash, reg_string);
1052
1053   if (b != NULL)
1054     {
1055       *end_op = reg_string + strlen (reg_string);
1056       strcpy (temp_bitname, b->reg_bit);
1057       s = temp_bitname;
1058     }
1059
1060   if (strchr (s, '.'))
1061     {
1062       while (*s != '.')
1063         {
1064           if (*s == '\0')
1065             return NULL;
1066           temp[k] = *s++;
1067
1068           k++;
1069         }
1070       temp[k] = '\0';
1071     }
1072
1073   if ((r = parse_register (temp, end_op)) == NULL)
1074     return NULL;
1075
1076   rb->reg = r;
1077
1078   /* Skip the "."  */
1079   s++;
1080
1081   if (isdigit ((char) *s))
1082     rb->bit = atoi (s);
1083   else if (isalpha ((char) *s))
1084     {
1085       rb->bit = (char) *s - 'a';
1086       rb->bit += 10;
1087       if (rb->bit > 15)
1088         {
1089           as_bad (_("Invalid bit number : '%c'"), (char) *s);
1090           return NULL;
1091         }
1092     }
1093
1094   if (b != NULL)
1095     diff = strlen (temp_bitname) - strlen (temp) - 1;
1096   else
1097     diff = strlen (reg_string) - strlen (temp) - 1;
1098
1099   if (*(s + diff) != '\0')
1100     {
1101       as_bad (_("Illegal character after operand '%s'"), reg_string);
1102       return NULL;
1103     }
1104
1105   return rb;
1106 }
1107
1108 static void
1109 pfx_for_imm_val (int arg)
1110 {
1111   if (i.prefix == -1)
1112     return;
1113
1114   if (i.prefix == 0 && arg == 0 && PFX_INSN[1] == 0 && !(i.data_operands))
1115     return;
1116
1117   if (!(i.prefix < 0) && !(i.prefix > 7))
1118     PFX_INSN[0] = (i.prefix << 4) | PFX0;
1119
1120   if (!PFX_INSN[1])
1121     PFX_INSN[1] = arg;
1122
1123 }
1124
1125 static int
1126 maxq20_immediate (char *imm_start)
1127 {
1128   int val = 0, val_pfx = 0;
1129   char sign_val = 0;
1130   int k = 0, j;
1131   int temp[4] = { 0 };
1132
1133   imm_start++;
1134
1135   if (imm_start[1] == '\0' && (imm_start[0] == '0' || imm_start[0] == '1')
1136       && (this_operand == 1 && ((i.types[0] == BIT || i.types[0] == FLAG))))
1137     {
1138       val = imm_start[0] - '0';
1139       i.imm_bit_operands++;
1140       i.types[this_operand] = IMMBIT;
1141       i.maxq20_op[this_operand].imms = (char) val;
1142 #if CHANGE_PFX
1143       if (i.prefix == 2)
1144         pfx_for_imm_val (0);
1145 #endif
1146       return 1;
1147     }
1148
1149   /* Check For Sign Character.  */
1150   sign_val = 0;
1151
1152   do
1153     {
1154       if (imm_start[k] == '-' && k == 0)
1155         sign_val = -1;
1156
1157       else if (imm_start[k] == '+' && k == 0)
1158         sign_val = 1;
1159
1160       else if (isdigit (imm_start[k]))
1161         temp[k] = imm_start[k] - '0';
1162
1163       else if (isalpha (imm_start[k])
1164                && (imm_start[k] = tolower (imm_start[k])) < 'g')
1165         temp[k] = 10 + (int) (imm_start[k] - 'a');
1166
1167       else if (imm_start[k] == 'h')
1168         break;
1169
1170       else if (imm_start[k] == '\0')
1171         {
1172           imm_start[k] = 'd';
1173           break;
1174         }
1175       else
1176         {
1177           as_bad (_("Invalid Character in immediate Value : %c"),
1178                   imm_start[k]);
1179           return 0;
1180         }
1181       k++;
1182     }
1183   while (imm_start[k] != '\n');
1184
1185   switch (imm_start[k])
1186     {
1187     case 'h':
1188       for (j = (sign_val ? 1 : 0); j < k; j++)
1189         val += temp[j] * pwr (16, k - j - 1);
1190       break;
1191
1192     case 'd':
1193       for (j = (sign_val ? 1 : 0); j < k; j++)
1194         {
1195           if (temp[j] > 9)
1196             {
1197               as_bad (_("Invalid Character in immediate value : %c"),
1198                       imm_start[j]);
1199               return 0;
1200             }
1201           val += temp[j] * pwr (10, k - j - 1);
1202         }
1203     }
1204
1205   if (!sign_val)
1206     sign_val = 1;
1207
1208   /* Now over here the value val stores the 8 bit/16 bit value. We will put a 
1209      check if we are moving a 16 bit immediate value into an 8 bit register. 
1210      In that case we will generate a warning and move only the lower 8 bits */
1211   if (val > 65535)
1212     {
1213       as_bad (_("Immediate value greater than 16 bits"));
1214       return 0;
1215     }
1216
1217   val = val * sign_val;
1218
1219   /* If it is a stack pointer and the value is greater than the maximum
1220      permissible size */
1221   if (this_operand == 1)
1222     {
1223       if ((val * sign_val) > MAX_STACK && i.types[0] == REG
1224           && !strcmp (i.maxq20_op[0].reg->reg_name, "SP"))
1225         {
1226           as_warn (_
1227                    ("Attempt to move a value in the stack pointer greater than the size of the stack"));
1228           val = val & MAX_STACK;
1229         }
1230
1231       /* Check the range for 8 bit registers.  */
1232       else if (((val * sign_val) > 0xFF) && (i.types[0] == REG)
1233                && (i.maxq20_op[0].reg->rtype == Reg_8W))
1234         {
1235           as_warn (_
1236                    ("Attempt to move 16 bit value into an 8 bit register.Truncating..\n"));
1237           val = val & 0xfe;
1238         }
1239
1240       else if (((sign_val == -1) || (val > 0xFF)) && (i.types[0] == REG)
1241                && (i.maxq20_op[0].reg->rtype == Reg_8W))
1242         {
1243           val_pfx = val >> 8;
1244           val = ((val) & 0x00ff);
1245           SET_PFX_ARG (val_pfx);
1246           i.maxq20_op[this_operand].imms = (char) val;
1247         }
1248
1249       else if ((val <= 0xff) && (i.types[0] == REG)
1250                && (i.maxq20_op[0].reg->rtype == Reg_8W))
1251         i.maxq20_op[this_operand].imms = (char) val;
1252
1253
1254       /* Check for 16 bit registers.  */
1255       else if (((sign_val == -1) || val > 0xFE) && i.types[0] == REG
1256                && i.maxq20_op[0].reg->rtype == Reg_16W)
1257         {
1258           /* Add PFX for any negative value -> 16bit register.  */
1259           val_pfx = val >> 8;
1260           val = ((val) & 0x00ff);
1261           SET_PFX_ARG (val_pfx);
1262           i.maxq20_op[this_operand].imms = (char) val;
1263         }
1264
1265       else if (val < 0xFF && i.types[0] == REG
1266                && i.maxq20_op[0].reg->rtype == Reg_16W)
1267         {
1268           i.maxq20_op[this_operand].imms = (char) val;
1269         }
1270
1271       /* All the immediate memory access - no PFX.  */
1272       else if (i.types[0] == MEM)
1273         {
1274           if ((sign_val == -1) || val > 0xFE)
1275             {
1276               val_pfx = val >> 8;
1277               val = ((val) & 0x00ff);
1278               SET_PFX_ARG (val_pfx);
1279               i.maxq20_op[this_operand].imms = (char) val;
1280             }
1281           else
1282             i.maxq20_op[this_operand].imms = (char) val;
1283         }
1284
1285       /* Special handling for immediate jumps like jump nz, #03h etc.  */
1286       else if (val < 0xFF && i.types[0] == FLAG)
1287         i.maxq20_op[this_operand].imms = (char) val;
1288
1289       else if ((((sign_val == -1) || val > 0xFE)) && i.types[0] == FLAG)
1290         {
1291           val_pfx = val >> 8;
1292           val = ((val) & 0x00ff);
1293           SET_PFX_ARG (val_pfx);
1294           i.maxq20_op[this_operand].imms = (char) val;
1295         }
1296       else
1297         {
1298           as_bad (_("Invalid immediate move operation"));
1299           return 0;
1300         }
1301     }
1302   else
1303     {
1304       /* All the instruction with operation on ACC: like ADD src, etc.  */
1305       if ((sign_val == -1) || val > 0xFE)
1306         {
1307           val_pfx = val >> 8;
1308           val = ((val) & 0x00ff);
1309           SET_PFX_ARG (val_pfx);
1310           i.maxq20_op[this_operand].imms = (char) val;
1311         }
1312       else
1313         i.maxq20_op[this_operand].imms = (char) val;
1314     }
1315
1316   i.imm_operands++;
1317   return 1;
1318 }
1319
1320 static int
1321 extract_int_val (const char *imm_start)
1322 {
1323   int k, j, val;
1324   char sign_val;
1325   int temp[4];
1326
1327   k = 0;
1328   j = 0;
1329   val = 0;
1330   sign_val = 0;
1331   do
1332     {
1333       if (imm_start[k] == '-' && k == 0)
1334         sign_val = -1;
1335
1336       else if (imm_start[k] == '+' && k == 0)
1337         sign_val = 1;
1338
1339       else if (isdigit (imm_start[k]))
1340         temp[k] = imm_start[k] - '0';
1341
1342       else if (isalpha (imm_start[k]) && (tolower (imm_start[k])) < 'g')
1343         temp[k] = 10 + (int) (tolower (imm_start[k]) - 'a');
1344
1345       else if (tolower (imm_start[k]) == 'h')
1346         break;
1347
1348       else if ((imm_start[k] == '\0') || (imm_start[k] == ']'))
1349         /* imm_start[k]='d'; */
1350         break;
1351
1352       else
1353         {
1354           as_bad (_("Invalid Character in immediate Value : %c"),
1355                   imm_start[k]);
1356           return 0;
1357         }
1358       k++;
1359     }
1360   while (imm_start[k] != '\n');
1361
1362   switch (imm_start[k])
1363     {
1364     case 'h':
1365       for (j = (sign_val ? 1 : 0); j < k; j++)
1366         val += temp[j] * pwr (16, k - j - 1);
1367       break;
1368
1369     default:
1370       for (j = (sign_val ? 1 : 0); j < k; j++)
1371         {
1372           if (temp[j] > 9)
1373             {
1374               as_bad (_("Invalid Character in immediate value : %c"),
1375                       imm_start[j]);
1376               return 0;
1377             }
1378           val += temp[j] * pwr (10, k - j - 1);
1379         }
1380     }
1381
1382   if (!sign_val)
1383     sign_val = 1;
1384
1385   return val * sign_val;
1386 }
1387
1388 static char
1389 check_for_parse (const char *line)
1390 {
1391   int val;
1392
1393   if (*(line + 1) == '[')
1394     {
1395       do
1396         {
1397           line++;
1398           if ((*line == '-') || (*line == '+'))
1399             break;
1400         }
1401       while (!is_space_char (*line));
1402
1403       if ((*line == '-') || (*line == '+'))
1404         val = extract_int_val (line);
1405       else
1406         val = extract_int_val (line + 1);
1407
1408       INSERT_BUFFER[0] = 0x3E;
1409       INSERT_BUFFER[1] = val;
1410
1411       return 1;
1412     }
1413
1414   return 0;
1415 }
1416
1417 static mem_access *
1418 maxq20_mem_access (char *mem_string, char **end_op)
1419 {
1420   char *s = mem_string;
1421   char *p;
1422   char mem_name_given[MAX_MEM_NAME_SIZE + 1];
1423   mem_access *m;
1424
1425   m = NULL;
1426
1427   /* Skip possible whitespace.  */
1428   if (is_space_char (*s))
1429     ++s;
1430
1431   p = mem_name_given;
1432   while ((*p++ = register_chars[(unsigned char) *s]) != '\0')
1433     {
1434       if (p >= mem_name_given + MAX_MEM_NAME_SIZE)
1435         return (mem_access *) NULL;
1436       s++;
1437     }
1438
1439   *end_op = s;
1440
1441   m = (mem_access *) hash_find (mem_hash, mem_name_given);
1442
1443   return m;
1444 }
1445
1446 /* This function checks whether the operand is a variable in the data segment 
1447    and if so, it returns its symbol entry from the symbol table.  */
1448
1449 static symbolS *
1450 maxq20_data (char *op_string)
1451 {
1452   symbolS *symbolP;
1453   symbolP = symbol_find (op_string);
1454
1455   if (symbolP != NULL
1456       && S_GET_SEGMENT (symbolP) != now_seg
1457       && S_GET_SEGMENT (symbolP) != bfd_und_section_ptr)
1458     {
1459       /* In case we do not want to always include the prefix instruction and
1460          let the loader handle the job or in case of a 8 bit addressing mode, 
1461          we will just check for val_pfx to be equal to zero and then load the 
1462          prefix instruction. Otherwise no prefix instruction needs to be
1463          loaded.  */
1464       /* The prefix register will have to be loaded automatically as we have 
1465          a 16 bit addressing field.  */
1466       pfx_for_imm_val (0);
1467       return symbolP;
1468     }
1469
1470   return NULL;
1471 }
1472
1473 static int
1474 maxq20_displacement (char *disp_start, char *disp_end)
1475 {
1476   expressionS *exp;
1477   segT exp_seg = 0;
1478   char *save_input_line_pointer;
1479 #ifndef LEX_AT
1480   char *gotfree_input_line;
1481 #endif
1482
1483   gotfree_input_line = NULL;
1484   exp = &disp_expressions;
1485   i.maxq20_op[this_operand].disps = exp;
1486   i.disp_operands++;
1487   save_input_line_pointer = input_line_pointer;
1488   input_line_pointer = disp_start;
1489
1490   END_STRING_AND_SAVE (disp_end);
1491
1492 #ifndef LEX_AT
1493   /* gotfree_input_line = lex_got (&i.reloc[this_operand], NULL); if
1494      (gotfree_input_line) input_line_pointer = gotfree_input_line; */
1495 #endif
1496   exp_seg = expression (exp);
1497
1498   SKIP_WHITESPACE ();
1499   if (*input_line_pointer)
1500     as_bad (_("junk `%s' after expression"), input_line_pointer);
1501 #if GCC_ASM_O_HACK
1502   RESTORE_END_STRING (disp_end + 1);
1503 #endif
1504   RESTORE_END_STRING (disp_end);
1505   input_line_pointer = save_input_line_pointer;
1506 #ifndef LEX_AT
1507   if (gotfree_input_line)
1508     free (gotfree_input_line);
1509 #endif
1510   if (exp->X_op == O_absent || exp->X_op == O_big)
1511     {
1512       /* Missing or bad expr becomes absolute 0.  */
1513       as_bad (_("missing or invalid displacement expression `%s' taken as 0"),
1514               disp_start);
1515       exp->X_op = O_constant;
1516       exp->X_add_number = 0;
1517       exp->X_add_symbol = (symbolS *) 0;
1518       exp->X_op_symbol = (symbolS *) 0;
1519     }
1520 #if (defined (OBJ_AOUT) || defined (OBJ_MAYBE_AOUT))
1521
1522   if (exp->X_op != O_constant
1523       && OUTPUT_FLAVOR == bfd_target_aout_flavour
1524       && exp_seg != absolute_section
1525       && exp_seg != text_section
1526       && exp_seg != data_section
1527       && exp_seg != bss_section && exp_seg != undefined_section
1528       && !bfd_is_com_section (exp_seg))
1529     {
1530       as_bad (_("unimplemented segment %s in operand"), exp_seg->name);
1531       return 0;
1532     }
1533 #endif
1534   i.maxq20_op[this_operand].disps = exp;
1535   return 1;
1536 }
1537
1538 /* Parse OPERAND_STRING into the maxq20_insn structure I.
1539    Returns non-zero on error.  */
1540
1541 static int
1542 maxq20_operand (char *operand_string)
1543 {
1544   reg_entry *r = NULL;
1545   reg_bit *rb = NULL;
1546   mem_access *m = NULL;
1547   char *end_op = NULL;
1548   symbolS *sym = NULL;
1549   char *base_string = NULL;
1550   int ii = 0;
1551   /* Start and end of displacement string expression (if found).  */
1552   char *displacement_string_start = NULL;
1553   char *displacement_string_end = NULL;
1554   /* This maintains the  case sentivness.  */
1555   char case_str_op_string[MAX_OPERAND_SIZE + 1];
1556   char str_op_string[MAX_OPERAND_SIZE + 1];
1557   char *org_case_op_string = case_str_op_string;
1558   char *op_string = str_op_string;
1559
1560   
1561   memset (op_string, END_OF_INSN, (MAX_OPERAND_SIZE + 1));
1562   memset (org_case_op_string, END_OF_INSN, (MAX_OPERAND_SIZE + 1));
1563
1564   memcpy (op_string, operand_string, strlen (operand_string) + 1);
1565   memcpy (org_case_op_string, operand_string, strlen (operand_string) + 1);
1566
1567   ii = strlen (operand_string) + 1;
1568
1569   if (ii > MAX_OPERAND_SIZE)
1570     {
1571       as_bad (_("Size of Operand '%s' greater than %d"), op_string,
1572               MAX_OPERAND_SIZE);
1573       return 0;
1574     }
1575
1576   while (ii)
1577     {
1578       op_string[ii - 1] = toupper ((char) op_string[ii - 1]);
1579       ii--;
1580     }
1581
1582   if (is_space_char (*op_string))
1583     ++op_string;
1584
1585   if (isxdigit (operand_string[0]))
1586     {
1587       /* Now the operands can start with an Integer.  */
1588       r = parse_reg_by_index (op_string);
1589       if (r != NULL)
1590         {
1591           if (is_space_char (*op_string))
1592             ++op_string;
1593           i.types[this_operand] = REG;  /* Set the type.  */
1594           i.maxq20_op[this_operand].reg = r;    /* Set the Register value.  */
1595           i.reg_operands++;
1596           return 1;
1597         }
1598
1599       /* Get the original string.  */
1600       memcpy (op_string, operand_string, strlen (operand_string) + 1);
1601       ii = strlen (operand_string) + 1;
1602
1603       while (ii)
1604         {
1605           op_string[ii - 1] = toupper ((char) op_string[ii - 1]);
1606           ii--;
1607         }
1608     }
1609
1610   /* Check for flags.  */
1611   if (!strcmp (op_string, "Z"))
1612     {
1613       if (is_space_char (*op_string))
1614         ++op_string;
1615
1616       i.types[this_operand] = FLAG;             /* Set the type.  */
1617       i.maxq20_op[this_operand].flag = FLAG_Z;  /* Set the Register value.  */
1618
1619       i.flag_operands++;
1620
1621       return 1;
1622     }
1623
1624   else if (!strcmp (op_string, "NZ"))
1625     {
1626       if (is_space_char (*op_string))
1627         ++op_string;
1628
1629       i.types[this_operand] = FLAG;             /* Set the type.  */
1630       i.maxq20_op[this_operand].flag = FLAG_NZ; /* Set the Register value.  */
1631       i.flag_operands++;
1632       return 1;
1633     }
1634
1635   else if (!strcmp (op_string, "NC"))
1636     {
1637       if (is_space_char (*op_string))
1638         ++op_string;
1639
1640       i.types[this_operand] = FLAG;             /* Set the type.  */
1641       i.maxq20_op[this_operand].flag = FLAG_NC; /* Set the Register value.  */
1642       i.flag_operands++;
1643       return 1;
1644     }
1645
1646   else if (!strcmp (op_string, "E"))
1647     {
1648       if (is_space_char (*op_string))
1649         ++op_string;
1650
1651       i.types[this_operand] = FLAG;             /* Set the type.  */
1652       i.maxq20_op[this_operand].flag = FLAG_E;  /* Set the Register value.  */
1653
1654       i.flag_operands++;
1655
1656       return 1;
1657     }
1658
1659   else if (!strcmp (op_string, "S"))
1660     {
1661       if (is_space_char (*op_string))
1662         ++op_string;
1663
1664       i.types[this_operand] = FLAG;     /* Set the type.  */
1665       i.maxq20_op[this_operand].flag = FLAG_S;  /* Set the Register value.  */
1666
1667       i.flag_operands++;
1668
1669       return 1;
1670     }
1671
1672   else if (!strcmp (op_string, "C"))
1673     {
1674       if (is_space_char (*op_string))
1675         ++op_string;
1676
1677       i.types[this_operand] = FLAG;     /* Set the type.  */
1678       i.maxq20_op[this_operand].flag = FLAG_C;  /* Set the Register value.  */
1679
1680       i.flag_operands++;
1681
1682       return 1;
1683     }
1684
1685   else if (!strcmp (op_string, "NE"))
1686     {
1687
1688       if (is_space_char (*op_string))
1689         ++op_string;
1690
1691       i.types[this_operand] = FLAG;     /* Set the type.  */
1692
1693       i.maxq20_op[this_operand].flag = FLAG_NE; /* Set the Register value.  */
1694
1695       i.flag_operands++;
1696
1697       return 1;
1698     }
1699
1700   /* CHECK FOR REGISTER BIT */
1701   else if ((rb = parse_register_bit (op_string, &end_op)) != NULL)
1702     {
1703       op_string = end_op;
1704
1705       if (is_space_char (*op_string))
1706         ++op_string;
1707
1708       i.types[this_operand] = BIT;
1709
1710       i.maxq20_op[this_operand].r_bit = rb;
1711
1712       i.bit_operands++;
1713
1714       return 1;
1715     }
1716
1717   else if (*op_string == IMMEDIATE_PREFIX)      /* FOR IMMEDITE.  */
1718     {
1719       if (is_space_char (*op_string))
1720         ++op_string;
1721
1722       i.types[this_operand] = IMM;
1723
1724       if (!maxq20_immediate (op_string))
1725         {
1726           as_bad (_("illegal immediate operand '%s'"), op_string);
1727           return 0;
1728         }
1729       return 1;
1730     }
1731
1732   else if (*op_string == ABSOLUTE_PREFIX || !strcmp (op_string, "NUL"))
1733     {
1734      if (is_space_char (*op_string))
1735         ++op_string;
1736
1737       /* For new requiremnt of copiler of for, @(BP,cons).  */
1738       if (check_for_parse (op_string))
1739         {
1740           memset (op_string, '\0', strlen (op_string) + 1);
1741           memcpy (op_string, "@BP[OFFS]\0", 11);
1742         }
1743
1744       i.types[this_operand] = MEM;
1745
1746       if ((m = maxq20_mem_access (op_string, &end_op)) == NULL)
1747         {
1748           as_bad (_("Invalid operand for memory access '%s'"), op_string);
1749           return 0;
1750         }
1751       i.maxq20_op[this_operand].mem = m;
1752
1753       i.mem_operands++;
1754
1755       return 1;
1756     }
1757
1758   else if ((r = parse_register (op_string, &end_op)) != NULL)   /* Check for register.  */
1759     {
1760       op_string = end_op;
1761
1762       if (is_space_char (*op_string))
1763         ++op_string;
1764
1765       i.types[this_operand] = REG;      /* Set the type.  */
1766       i.maxq20_op[this_operand].reg = r;        /* Set the Register value.  */
1767       i.reg_operands++;
1768       return 1;
1769     }
1770
1771   if (this_operand == 1)
1772     {
1773       /* Changed for orginal case of data refrence on 30 Nov 2003.  */
1774       /* The operand can either be a data reference or a symbol reference.  */
1775       if ((sym = maxq20_data (org_case_op_string)) != NULL)     /* Check for data memory.  */
1776         {
1777           while (is_space_char (*op_string))
1778             ++op_string;
1779
1780           /* Set the type of the operand.  */
1781           i.types[this_operand] = DATA;
1782
1783           /* Set the value of the data.  */
1784           i.maxq20_op[this_operand].data = sym;
1785           i.data_operands++;
1786
1787           return 1;
1788         }
1789
1790       else if (is_digit_char (*op_string) || is_identifier_char (*op_string))
1791         {
1792           /* This is a memory reference of some sort. char *base_string;
1793              Start and end of displacement string expression (if found). char 
1794              *displacement_string_start; char *displacement_string_end.  */
1795           base_string = org_case_op_string + strlen (org_case_op_string);
1796
1797           --base_string;
1798           if (is_space_char (*base_string))
1799             --base_string;
1800
1801           /* If we only have a displacement, set-up for it to be parsed
1802              later.  */
1803           displacement_string_start = org_case_op_string;
1804           displacement_string_end = base_string + 1;
1805           if (displacement_string_start != displacement_string_end)
1806             {
1807               if (!maxq20_displacement (displacement_string_start,
1808                                         displacement_string_end))
1809                 {
1810                   as_bad (_("illegal displacement operand "));
1811                   return 0;
1812                 }
1813               /* A displacement operand found.  */
1814               i.types[this_operand] = DISP;     /* Set the type.  */
1815               return 1;
1816             }
1817         }
1818     }
1819   
1820   /* Check for displacement.  */
1821   else if (is_digit_char (*op_string) || is_identifier_char (*op_string))
1822     {
1823       /* This is a memory reference of some sort. char *base_string;
1824          Start and end of displacement string expression (if found). char
1825          *displacement_string_start; char *displacement_string_end;  */
1826       base_string = org_case_op_string + strlen (org_case_op_string);
1827
1828       --base_string;
1829       if (is_space_char (*base_string))
1830         --base_string;
1831
1832       /* If we only have a displacement, set-up for it to be parsed later.  */
1833       displacement_string_start = org_case_op_string;
1834       displacement_string_end = base_string + 1;
1835       if (displacement_string_start != displacement_string_end)
1836         {
1837           if (!maxq20_displacement (displacement_string_start,
1838                                     displacement_string_end))
1839             return 0;
1840           /* A displacement operand found.  */
1841           i.types[this_operand] = DISP; /* Set the type.  */
1842         }
1843     }
1844   return 1;
1845 }
1846
1847 /* Parse_operand takes as input instruction and operands and Parse operands
1848    and makes entry in the template.  */
1849
1850 static char *
1851 parse_operands (char *l, const char *mnemonic)
1852 {
1853   char *token_start;
1854
1855   /* 1 if operand is pending after ','.  */
1856   short int expecting_operand = 0;
1857
1858   /* Non-zero if operand parens not balanced.  */
1859   short int paren_not_balanced;
1860
1861   int operand_ok;
1862
1863   /* For Overcoming Warning of unused variable.  */
1864   if (mnemonic)
1865     operand_ok = 0;
1866
1867   while (*l != END_OF_INSN)
1868     {
1869       /* Skip optional white space before operand.  */
1870       if (is_space_char (*l))
1871         ++l;
1872
1873       if (!is_operand_char (*l) && *l != END_OF_INSN)
1874         {
1875           as_bad (_("invalid character %c before operand %d"),
1876                   (char) (*l), i.operands + 1);
1877           return NULL;
1878         }
1879       token_start = l;
1880
1881       paren_not_balanced = 0;
1882       while (paren_not_balanced || *l != ',')
1883         {
1884           if (*l == END_OF_INSN)
1885             {
1886               if (paren_not_balanced)
1887                 {
1888                   as_bad (_("unbalanced brackets in operand %d."),
1889                           i.operands + 1);
1890                   return NULL;
1891                 }
1892
1893               break;
1894             }
1895           else if (!is_operand_char (*l) && !is_space_char (*l))
1896             {
1897               as_bad (_("invalid character %c in operand %d"),
1898                       (char) (*l), i.operands + 1);
1899               return NULL;
1900             }
1901           if (*l == '[')
1902             ++paren_not_balanced;
1903           if (*l == ']')
1904             --paren_not_balanced;
1905           l++;
1906         }
1907
1908       if (l != token_start)
1909         {
1910           /* Yes, we've read in another operand.  */
1911           this_operand = i.operands++;
1912           if (i.operands > MAX_OPERANDS)
1913             {
1914               as_bad (_("spurious operands; (%d operands/instruction max)"),
1915                       MAX_OPERANDS);
1916               return NULL;
1917             }
1918
1919           /* Now parse operand adding info to 'i' as we go along.  */
1920           END_STRING_AND_SAVE (l);
1921
1922           operand_ok = maxq20_operand (token_start);
1923
1924           RESTORE_END_STRING (l);
1925
1926           if (!operand_ok)
1927             return NULL;
1928         }
1929       else
1930         {
1931           if (expecting_operand)
1932             {
1933             expecting_operand_after_comma:
1934               as_bad (_("expecting operand after ','; got nothing"));
1935               return NULL;
1936             }
1937         }
1938
1939       if (*l == ',')
1940         {
1941           if (*(++l) == END_OF_INSN)
1942             /* Just skip it, if it's \n complain.  */
1943             goto expecting_operand_after_comma;
1944
1945           expecting_operand = 1;
1946         }
1947     }
1948
1949   return l;
1950 }
1951
1952 static int
1953 match_operands (int type, MAX_ARG_TYPE flag_type, MAX_ARG_TYPE arg_type,
1954                 int op_num)
1955 {
1956   switch (type)
1957     {
1958     case REG:
1959       if ((arg_type & A_REG) == A_REG)
1960         return 1;
1961       break;
1962     case IMM:
1963       if ((arg_type & A_IMM) == A_IMM)
1964         return 1;
1965       break;
1966     case IMMBIT:
1967       if ((arg_type & A_BIT_0) == A_BIT_0 && (i.maxq20_op[op_num].imms == 0))
1968         return 1;
1969       else if ((arg_type & A_BIT_1) == A_BIT_1
1970                && (i.maxq20_op[op_num].imms == 1))
1971         return 1;
1972       break;
1973     case MEM:
1974       if ((arg_type & A_MEM) == A_MEM)
1975         return 1;
1976       break;
1977
1978     case FLAG:
1979       if ((arg_type & flag_type) == flag_type)
1980         return 1;
1981
1982       break;
1983
1984     case BIT:
1985       if ((arg_type & ACC_BIT) == ACC_BIT && !strcmp (i.maxq20_op[op_num].r_bit->reg->reg_name, "ACC"))
1986         return 1;
1987       else if ((arg_type & SRC_BIT) == SRC_BIT && (op_num == 1))
1988         return 1;
1989       else if ((op_num == 0) && (arg_type & DST_BIT) == DST_BIT)
1990         return 1;
1991       break;
1992     case DISP:
1993       if ((arg_type & A_DISP) == A_DISP)
1994         return 1;
1995     case DATA:
1996       if ((arg_type & A_DATA) == A_DATA)
1997         return 1;
1998     case BIT_BUCKET:
1999       if ((arg_type & A_BIT_BUCKET) == A_BIT_BUCKET)
2000         return 1;
2001     }
2002   return 0;
2003 }
2004
2005 static int
2006 match_template (void)
2007 {
2008   /* Points to template once we've found it.  */
2009   const MAXQ20_OPCODE_INFO *t;
2010   char inv_oper;
2011   inv_oper = 0;
2012
2013   for (t = current_templates->start; t < current_templates->end; t++)
2014     {
2015       /* Must have right number of operands.  */
2016       if (i.operands != t->op_number)
2017         continue;
2018       else if (!t->op_number)
2019         break;
2020
2021       switch (i.operands)
2022         {
2023         case 2:
2024           if (!match_operands (i.types[1], i.maxq20_op[1].flag, t->arg[1], 1))
2025             {
2026               inv_oper = 1;
2027               continue;
2028             }
2029         case 1:
2030           if (!match_operands (i.types[0], i.maxq20_op[0].flag, t->arg[0], 0))
2031             {
2032               inv_oper = 2;
2033               continue;
2034             }
2035         }
2036       break;
2037     }
2038
2039   if (t == current_templates->end)
2040     {
2041       /* We found no match.  */
2042       as_bad (_("operand %d is invalid for `%s'"),
2043               inv_oper, current_templates->start->name);
2044       return 0;
2045     }
2046
2047   /* Copy the template we have found.  */
2048   i.op = *t;
2049   return 1;
2050 }
2051
2052 /* This function filters out the various combinations of operands which are
2053    not allowed for a particular instruction.  */
2054
2055 static int
2056 match_filters (void)
2057 {
2058   /* Now we have at our disposal the instruction i. We will be using the
2059      following fields i.op.name : This is the mnemonic name. i.types[2] :
2060      These are the types of the operands (REG/IMM/DISP/MEM/BIT/FLAG/IMMBIT)
2061      i.maxq20_op[2] : This contains the specific info of the operands.  */
2062
2063   /* Our first filter : NO ALU OPERATIONS CAN HAVE THE ACTIVE ACCUMULATOR AS
2064      SOURCE.  */
2065   if (!strcmp (i.op.name, "AND") || !strcmp (i.op.name, "OR")
2066       || !strcmp (i.op.name, "XOR") || !strcmp (i.op.name, "ADD")
2067       || !strcmp (i.op.name, "ADDC") || !strcmp (i.op.name, "SUB")
2068       || !strcmp (i.op.name, "SUBB"))
2069     {
2070       if (i.types[0] == REG)
2071         {
2072           if (i.maxq20_op[0].reg->Mod_name == 0xa)
2073             {
2074               as_bad (_
2075                       ("The Accumulator cannot be used as a source in ALU instructions\n"));
2076               return 0;
2077             }
2078         }
2079     }
2080
2081   if (!strcmp (i.op.name, "MOVE") && (i.types[0] == MEM || i.types[1] == MEM)
2082       && i.operands == 2)
2083     {
2084       mem_access_syntax *mem_op = NULL;
2085
2086       if (i.types[0] == MEM)
2087         {
2088           mem_op =
2089             (mem_access_syntax *) hash_find (mem_syntax_hash,
2090                                              i.maxq20_op[0].mem->name);
2091           if ((mem_op->type == SRC) && mem_op)
2092             {
2093               as_bad (_("'%s' operand cant be used as destination in %s"),
2094                       mem_op->name, i.op.name);
2095               return 0;
2096             }
2097           else if ((mem_op->invalid_op != NULL) && (i.types[1] == MEM)
2098                    && mem_op)
2099             {
2100               int k = 0;
2101
2102               for (k = 0; k < 5 || !mem_op->invalid_op[k]; k++)
2103                 {
2104                   if (mem_op->invalid_op[k] != NULL)
2105                     if (!strcmp
2106                         (mem_op->invalid_op[k], i.maxq20_op[1].mem->name))
2107                       {
2108                         as_bad (_
2109                                 ("Invalid Instruction '%s' operand cant be used with %s"),
2110                                 mem_op->name, i.maxq20_op[1].mem->name);
2111                         return 0;
2112                       }
2113                 }
2114             }
2115         }
2116
2117       if (i.types[1] == MEM)
2118         {
2119           mem_op = NULL;
2120           mem_op =
2121             (mem_access_syntax *) hash_find (mem_syntax_hash,
2122                                              i.maxq20_op[1].mem->name);
2123           if (mem_op->type == DST && mem_op)
2124             {
2125               as_bad (_("'%s' operand cant be used as source in %s"),
2126                       mem_op->name, i.op.name);
2127               return 0;
2128             }
2129           else if (mem_op->invalid_op != NULL && i.types[0] == MEM && mem_op)
2130             {
2131               int k = 0;
2132
2133               for (k = 0; k < 5 || !mem_op->invalid_op[k]; k++)
2134                 {
2135                   if (mem_op->invalid_op[k] != NULL)
2136                     if (!strcmp
2137                         (mem_op->invalid_op[k], i.maxq20_op[0].mem->name))
2138                       {
2139                         as_bad (_
2140                                 ("Invalid Instruction '%s' operand cant be used with %s"),
2141                                 mem_op->name, i.maxq20_op[0].mem->name);
2142                         return 0;
2143                       }
2144                 }
2145             }
2146           else if (i.types[0] == REG
2147                    && !strcmp (i.maxq20_op[0].reg->reg_name, "OFFS")
2148                    && mem_op)
2149             {
2150               if (!strcmp (mem_op->name, "@BP[OFFS--]")
2151                   || !strcmp (mem_op->name, "@BP[OFFS++]"))
2152                 {
2153                   as_bad (_
2154                           ("Invalid Instruction '%s' operand cant be used with %s"),
2155                           mem_op->name, i.maxq20_op[0].mem->name);
2156                   return 0;
2157                 }
2158             }
2159         }
2160     }
2161
2162   /* Added for SRC and DST in one operand instructioni i.e OR @--DP[1] added
2163      on 10-March-2004.  */
2164   if ((i.types[0] == MEM) && (i.operands == 1)
2165       && !(!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI")))
2166     {
2167       mem_access_syntax *mem_op = NULL;
2168
2169       if (i.types[0] == MEM)
2170         {
2171           mem_op =
2172             (mem_access_syntax *) hash_find (mem_syntax_hash,
2173                                              i.maxq20_op[0].mem->name);
2174           if (mem_op->type == DST && mem_op)
2175             {
2176               as_bad (_("'%s' operand cant be used as source in %s"),
2177                       mem_op->name, i.op.name);
2178               return 0;
2179             }
2180         }
2181     }
2182
2183   if (i.operands == 2 && i.types[0] == IMM)
2184     {
2185       as_bad (_("'%s' instruction cant have first operand as Immediate vale"),
2186               i.op.name);
2187       return 0;
2188     }
2189
2190   /* Our second filter : SP or @SP-- cannot be used with PUSH or POP */
2191   if (!strcmp (i.op.name, "PUSH") || !strcmp (i.op.name, "POP")
2192       || !strcmp (i.op.name, "POPI"))
2193     {
2194       if (i.types[0] == REG)
2195         {
2196           if (!strcmp (i.maxq20_op[0].reg->reg_name, "SP"))
2197             {
2198               as_bad (_("SP cannot be used with %s\n"), i.op.name);
2199               return 0;
2200             }
2201         }
2202       else if (i.types[0] == MEM
2203                && !strcmp (i.maxq20_op[0].mem->name, "@SP--"))
2204         {
2205           as_bad (_("@SP-- cannot be used with PUSH\n"));
2206           return 0;
2207         }
2208     }
2209
2210   /* This filter checks that two memory references using DP's cannot be used
2211      together in an instruction */
2212   if (!strcmp (i.op.name, "MOVE") && i.mem_operands == 2)
2213     {
2214       if (strlen (i.maxq20_op[0].mem->name) != 6 ||
2215           strcmp (i.maxq20_op[0].mem->name, i.maxq20_op[1].mem->name))
2216         {
2217           if (!strncmp (i.maxq20_op[0].mem->name, "@DP", 3)
2218               && !strncmp (i.maxq20_op[1].mem->name, "@DP", 3))
2219             {
2220               as_bad (_
2221                       ("Operands either contradictory or use the data bus in read/write state together"));
2222               return 0;
2223             }
2224
2225           if (!strncmp (i.maxq20_op[0].mem->name, "@SP", 3)
2226               && !strncmp (i.maxq20_op[1].mem->name, "@SP", 3))
2227             {
2228               as_bad (_
2229                       ("Operands either contradictory or use the data bus in read/write state together"));
2230               return 0;
2231             }
2232         }
2233       if ((i.maxq20_op[1].mem != NULL)
2234           && !strncmp (i.maxq20_op[1].mem->name, "NUL", 3))
2235         {
2236           as_bad (_("MOVE Cant Use NUL as SRC"));
2237           return 0;
2238         }
2239     }
2240
2241   /* This filter checks that contradictory movement between DP register and
2242      Memory access using DP followed by increment or decrement.  */
2243
2244   if (!strcmp (i.op.name, "MOVE") && i.mem_operands == 1
2245       && i.reg_operands == 1)
2246     {
2247       int memnum, regnum;
2248
2249       memnum = (i.types[0] == MEM) ? 0 : 1;
2250       regnum = (memnum == 0) ? 1 : 0;
2251       if (!strncmp (i.maxq20_op[regnum].reg->reg_name, "DP", 2) &&
2252           !strncmp ((i.maxq20_op[memnum].mem->name) + 1,
2253                     i.maxq20_op[regnum].reg->reg_name, 5)
2254           && strcmp ((i.maxq20_op[memnum].mem->name) + 1,
2255                      i.maxq20_op[regnum].reg->reg_name))
2256         {
2257           as_bad (_
2258                   ("Contradictory movement between DP register and memory access using DP"));
2259           return 0;
2260         }
2261       else if (!strcmp (i.maxq20_op[regnum].reg->reg_name, "SP") &&
2262                !strncmp ((i.maxq20_op[memnum].mem->name) + 1,
2263                          i.maxq20_op[regnum].reg->reg_name, 2))
2264         {
2265           as_bad (_
2266                   ("SP and @SP-- cannot be used together in a move instruction"));
2267           return 0;
2268         }
2269     }
2270
2271   /* This filter restricts the instructions containing source and destination 
2272      bits to only CTRL module of the serial registers. Peripheral registers
2273      yet to be defined.  */
2274
2275   if (i.bit_operands == 1 && i.operands == 2)
2276     {
2277       int bitnum = (i.types[0] == BIT) ? 0 : 1;
2278
2279       if (strcmp (i.maxq20_op[bitnum].r_bit->reg->reg_name, "ACC"))
2280         {
2281           if (i.maxq20_op[bitnum].r_bit->reg->Mod_name >= 0x7 &&
2282               i.maxq20_op[bitnum].r_bit->reg->Mod_name != CTRL)
2283             {
2284               as_bad (_
2285                       ("Only Module 8 system registers allowed in this operation"));
2286               return 0;
2287             }
2288         }
2289     }
2290
2291   /* This filter is for checking the register bits.  */
2292   if (i.bit_operands == 1 || i.operands == 2)
2293     {
2294       int bitnum = 0, size = 0;
2295
2296       bitnum = (i.types[0] == BIT) ? 0 : 1;
2297       if (i.bit_operands == 1)
2298         {
2299           switch (i.maxq20_op[bitnum].r_bit->reg->rtype)
2300             {
2301             case Reg_8W:
2302               size = 7;         /* 8 bit register, both read and write.  */
2303               break;
2304             case Reg_16W:
2305               size = 15;
2306               break;
2307             case Reg_8R:
2308               size = 7;
2309               if (bitnum == 0)
2310                 {
2311                   as_fatal (_("Read only Register used as destination"));
2312                   return 0;
2313                 }
2314               break;
2315
2316             case Reg_16R:
2317               size = 15;
2318               if (bitnum == 0)
2319                 {
2320                   as_fatal (_("Read only Register used as destination"));
2321                   return 0;
2322                 }
2323               break;
2324             }
2325
2326           if (size < (i.maxq20_op[bitnum].r_bit)->bit)
2327             {
2328               as_bad (_("Bit No '%d'exceeds register size in this operation"),
2329                       (i.maxq20_op[bitnum].r_bit)->bit);
2330               return 0;
2331             }
2332         }
2333
2334       if (i.bit_operands == 2)
2335         {
2336           switch ((i.maxq20_op[0].r_bit)->reg->rtype)
2337             {
2338             case Reg_8W:
2339               size = 7;         /* 8 bit register, both read and write.  */
2340               break;
2341             case Reg_16W:
2342               size = 15;
2343               break;
2344             case Reg_8R:
2345             case Reg_16R:
2346               as_fatal (_("Read only Register used as destination"));
2347               return 0;
2348             }
2349
2350           if (size < (i.maxq20_op[0].r_bit)->bit)
2351             {
2352               as_bad (_
2353                       ("Bit No '%d' exceeds register size in this operation"),
2354                       (i.maxq20_op[0].r_bit)->bit);
2355               return 0;
2356             }
2357
2358           size = 0;
2359           switch ((i.maxq20_op[1].r_bit)->reg->rtype)
2360             {
2361             case Reg_8R:
2362             case Reg_8W:
2363               size = 7;         /* 8 bit register, both read and write.  */
2364               break;
2365             case Reg_16R:
2366             case Reg_16W:
2367               size = 15;
2368               break;
2369             }
2370
2371           if (size < (i.maxq20_op[1].r_bit)->bit)
2372             {
2373               as_bad (_
2374                       ("Bit No '%d' exceeds register size in this operation"),
2375                       (i.maxq20_op[1].r_bit)->bit);
2376               return 0;
2377             }
2378         }
2379     }
2380
2381   /* No branch operations should occur into the data memory. Hence any memory 
2382      references have to be filtered out when used with instructions like
2383      jump, djnz[] and call.  */
2384
2385   if (!strcmp (i.op.name, "JUMP") || !strcmp (i.op.name, "CALL")
2386       || !strncmp (i.op.name, "DJNZ", 4))
2387     {
2388       if (i.mem_operands)
2389         as_warn (_
2390                  ("Memory References cannot be used with branching operations\n"));
2391     }
2392
2393   if (!strcmp (i.op.name, "DJNZ"))
2394     {
2395       if (!
2396           (strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]")
2397            || strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]")))
2398         {
2399           as_bad (_("DJNZ uses only LC[n] register \n"));
2400           return 0;
2401         }
2402     }
2403
2404   /* No destination register used should be read only!  */
2405   if ((i.operands == 2 && i.types[0] == REG) || !strcmp (i.op.name, "POP")
2406       || !strcmp (i.op.name, "POPI"))
2407     {                           /* The destination is a register */
2408       int regnum = 0;
2409
2410       if (!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
2411         {
2412           regnum = 0;
2413
2414           if (i.types[regnum] == MEM)
2415             {
2416               mem_access_syntax *mem_op = NULL;
2417
2418               mem_op =
2419                 (mem_access_syntax *) hash_find (mem_syntax_hash,
2420                                                  i.maxq20_op[regnum].mem->
2421                                                  name);
2422               if (mem_op->type == SRC && mem_op)
2423                 {
2424                   as_bad (_
2425                           ("'%s' operand cant be used as destination  in %s"),
2426                           mem_op->name, i.op.name);
2427                   return 0;
2428                 }
2429             }
2430         }
2431
2432       if (i.maxq20_op[regnum].reg->rtype == Reg_8R
2433           || i.maxq20_op[regnum].reg->rtype == Reg_16R)
2434         {
2435           as_bad (_("Read only register used for writing purposes '%s'"),
2436                   i.maxq20_op[regnum].reg->reg_name);
2437           return 0;
2438         }
2439     }
2440
2441   /* While moving the address of a data in the data section, the destination
2442      should be either data pointers only.  */
2443   if ((i.data_operands) && (i.operands == 2))
2444     {
2445       if ((i.types[0] != REG) && (i.types[0] != MEM))
2446         {
2447           as_bad (_("Invalid destination for this kind of source."));
2448           return 0;
2449         }
2450
2451         if (i.types[0] == REG && i.maxq20_op[0].reg->rtype == Reg_8W)
2452           {
2453             as_bad (_
2454                     ("Invalid register as destination for this kind of source.Only data pointers can be used."));
2455             return 0;
2456           }
2457     }
2458   return 1;
2459 }
2460
2461 static int
2462 decode_insn (void)
2463 {
2464   /* Check for the format Bit if defined.  */
2465   if (i.op.format == 0 || i.op.format == 1)
2466     i.instr[0] = i.op.format << 7;
2467   else
2468     {
2469       /* Format bit not defined. We will have to be find it out ourselves.  */
2470       if (i.imm_operands == 1 || i.data_operands == 1 || i.disp_operands == 1)
2471         i.op.format = 0;
2472       else
2473         i.op.format = 1;
2474       i.instr[0] = i.op.format << 7;
2475     }
2476
2477   /* Now for the destination register.  */
2478
2479   /* If destination register is already defined . The conditions are the
2480      following: (1) The second entry in the destination array should be 0 (2) 
2481      If there are two operands then the first entry should not be a register,
2482      memory or a register bit (3) If there are less than two operands and the
2483      it is not a pop operation (4) The second argument is the carry
2484      flag(applicable to move Acc.<b>,C.  */
2485   if (i.op.dst[1] == 0
2486       &&
2487       ((i.types[0] != REG && i.types[0] != MEM && i.types[0] != BIT
2488         && i.operands == 2) || (i.operands < 2 && strcmp (i.op.name, "POP")
2489                                 && strcmp (i.op.name, "POPI"))
2490        || (i.op.arg[1] == FLAG_C)))
2491     {
2492       i.op.dst[0] &= 0x7f;
2493       i.instr[0] |= i.op.dst[0];
2494     }
2495   else if (i.op.dst[1] == 0 && !strcmp (i.op.name, "DJNZ")
2496            &&
2497            (((i.types[0] == REG)
2498              && (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]")
2499                  || !strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]")))))
2500     {
2501       i.op.dst[0] &= 0x7f;
2502       if (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]"))
2503         i.instr[0] |= 0x4D;
2504
2505       if (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]"))
2506         i.instr[0] |= 0x5D;
2507     }
2508   else
2509     {
2510       unsigned char temp;
2511
2512       /* Target register will have to be specified.  */
2513       if (i.types[0] == REG
2514           && (i.op.dst[0] == REG || i.op.dst[0] == (REG | MEM)))
2515         {
2516           temp = (i.maxq20_op[0].reg)->opcode;
2517           temp &= 0x7f;
2518           i.instr[0] |= temp;
2519         }
2520       else if (i.types[0] == MEM && (i.op.dst[0] == (REG | MEM)))
2521         {
2522           temp = (i.maxq20_op[0].mem)->opcode;
2523           temp &= 0x7f;
2524           i.instr[0] |= temp;
2525         }
2526       else if (i.types[0] == BIT && (i.op.dst[0] == REG))
2527         {
2528           temp = (i.maxq20_op[0].r_bit)->reg->opcode;
2529           temp &= 0x7f;
2530           i.instr[0] |= temp;
2531         }
2532       else if (i.types[1] == BIT && (i.op.dst[0] == BIT))
2533         {
2534           temp = (i.maxq20_op[1].r_bit)->bit;
2535           temp = temp << 4;
2536           temp |= i.op.dst[1];
2537           temp &= 0x7f;
2538           i.instr[0] |= temp;
2539         }
2540       else
2541         {
2542           as_bad (_("Invalid Instruction"));
2543           return 0;
2544         }
2545     }
2546
2547   /* Now for the source register.  */
2548
2549   /* If Source register is already known. The following conditions are
2550      checked: (1) There are no operands (2) If there is only one operand and
2551      it is a flag (3) If the operation is MOVE C,#0/#1 (4) If it is a POP
2552      operation.  */
2553
2554   if (i.operands == 0 || (i.operands == 1 && i.types[0] == FLAG)
2555       || (i.types[0] == FLAG && i.types[1] == IMMBIT)
2556       || !strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
2557     i.instr[1] = i.op.src[0];
2558
2559   else if (i.imm_operands == 1 && ((i.op.src[0] & IMM) == IMM))
2560     i.instr[1] = i.maxq20_op[this_operand].imms;
2561   
2562   else if (i.types[this_operand] == REG && ((i.op.src[0] & REG) == REG))
2563     i.instr[1] = (char) ((i.maxq20_op[this_operand].reg)->opcode);
2564
2565   else if (i.types[this_operand] == BIT && ((i.op.src[0] & REG) == REG))
2566     i.instr[1] = (char) (i.maxq20_op[this_operand].r_bit->reg->opcode);
2567
2568   else if (i.types[this_operand] == MEM && ((i.op.src[0] & MEM) == MEM))
2569     i.instr[1] = (char) ((i.maxq20_op[this_operand].mem)->opcode);
2570
2571   else if (i.types[this_operand] == DATA && ((i.op.src[0] & DATA) == DATA))
2572     /* This will copy only the lower order bytes into the instruction. The
2573        higher order bytes have already been copied into the prefix register.  */
2574     i.instr[1] = 0;
2575
2576   /* Decoding the source in the case when the second array entry is not 0.
2577      This means that the source register has been divided into two nibbles.  */
2578
2579   else if (i.op.src[1] != 0)
2580     {
2581       /* If the first operand is a accumulator bit then
2582          the first 4 bits will be filled with the bit number.  */
2583       if (i.types[0] == BIT && ((i.op.src[0] & BIT) == BIT))
2584         {
2585           unsigned char temp = (i.maxq20_op[0].r_bit)->bit;
2586
2587           temp = temp << 4;
2588           temp |= i.op.src[1];
2589           i.instr[1] = temp;
2590         }
2591       /* In case of MOVE dst.<b>,#1 The first nibble in the source register
2592          has to start with a zero. This is called a ZEROBIT */
2593       else if (i.types[0] == BIT && ((i.op.src[0] & ZEROBIT) == ZEROBIT))
2594         {
2595           char temp = (i.maxq20_op[0].r_bit)->bit;
2596
2597           temp = temp << 4;
2598           temp |= i.op.src[1];
2599           temp &= 0x7f;
2600           i.instr[1] = temp;
2601         }
2602       /* Similarly for a ONEBIT */
2603       else if (i.types[0] == BIT && ((i.op.src[0] & ONEBIT) == ONEBIT))
2604         {
2605           char temp = (i.maxq20_op[0].r_bit)->bit;
2606
2607           temp = temp << 4;
2608           temp |= i.op.src[1];
2609           temp |= 0x80;
2610           i.instr[1] = temp;
2611         }
2612       /* In case the second operand is a register bit (MOVE C,Acc.<b> or MOVE 
2613          C,src.<b> */
2614       else if (i.types[1] == BIT)
2615         {
2616           if (i.op.src[1] == 0 && i.op.src[1] == REG)
2617             i.instr[1] = (i.maxq20_op[1].r_bit)->reg->opcode;
2618
2619           else if (i.op.src[0] == BIT && i.op.src)
2620             {
2621               char temp = (i.maxq20_op[1].r_bit)->bit;
2622
2623               temp = temp << 4;
2624               temp |= i.op.src[1];
2625               i.instr[1] = temp;
2626             }
2627         }
2628       else
2629         {
2630           as_bad (_("Invalid Instruction"));
2631           return 0;
2632         }
2633     }
2634   return 1;
2635 }
2636
2637 /* This is a function for outputting displacement operands.  */
2638
2639 static void
2640 output_disp (fragS *insn_start_frag, offsetT insn_start_off)
2641 {
2642   char *p;
2643   relax_substateT subtype;
2644   symbolS *sym;
2645   offsetT off;
2646   int diff;
2647
2648   diff = 0;
2649   insn_start_frag = frag_now;
2650   insn_start_off = frag_now_fix ();
2651
2652   switch (i.Instr_Prefix)
2653     {
2654     case LONG_PREFIX:
2655       subtype = EXPLICT_LONG_PREFIX;
2656       break;
2657     case SHORT_PREFIX:
2658       subtype = SHORT_PREFIX;
2659       break;
2660     default:
2661       subtype = NO_PREFIX;
2662       break;
2663     }
2664
2665   /* Its a symbol. Here we end the frag and start the relaxation. Now in our
2666      case there is no need for relaxation. But we do need support for a
2667      prefix operator. Hence we will check whethere is room for 4 bytes ( 2
2668      for prefix + 2 for the current instruction ) Hence if at a particular
2669      time we find out whether the prefix operator is reqd , we shift the
2670      current instruction two places ahead and insert the prefix instruction.  */
2671   frag_grow (2 + 2);
2672   p = frag_more (2);
2673
2674   sym = i.maxq20_op[this_operand].disps->X_add_symbol;
2675   off = i.maxq20_op[this_operand].disps->X_add_number;
2676
2677   if (i.maxq20_op[this_operand].disps->X_add_symbol != NULL && sym && frag_now
2678       && (subtype != EXPLICT_LONG_PREFIX))
2679     {
2680       /* If in the same frag.  */
2681       if (frag_now == symbol_get_frag (sym))
2682         {
2683           diff =
2684             ((((expressionS *) symbol_get_value_expression (sym))->
2685               X_add_number) - insn_start_off);
2686
2687           /* PC points to the next instruction.  */
2688           diff = (diff / MAXQ_OCTETS_PER_BYTE) - 1;
2689
2690           if (diff >= -128 && diff <= 127)
2691             {
2692               i.instr[1] = (char) diff;
2693
2694               /* This will be overwritten later when the symbol is resolved.  */
2695               *p = i.instr[1];
2696               *(p + 1) = i.instr[0];
2697
2698               /* No Need to create a FIXUP.  */
2699               return;
2700             }
2701         }
2702     }
2703
2704   /* This will be overwritten later when the symbol is resolved.  */
2705   *p = i.instr[1];
2706   *(p + 1) = i.instr[0];
2707
2708   if (i.maxq20_op[this_operand].disps->X_op != O_constant
2709       && i.maxq20_op[this_operand].disps->X_op != O_symbol)
2710     {
2711       /* Handle complex expressions.  */
2712       sym = make_expr_symbol (i.maxq20_op[this_operand].disps);
2713       off = 0;
2714     }
2715
2716   /* Vineet : This has been added for md_estimate_size_before_relax to
2717      estimate the correct size.  */
2718   if (subtype != SHORT_PREFIX)
2719     i.reloc[this_operand] = LONG_PREFIX;
2720
2721   frag_var (rs_machine_dependent, 2, i.reloc[this_operand], subtype, sym, off,  p);
2722 }
2723
2724 /* This is a function for outputting displacement operands.  */
2725
2726 static void
2727 output_data (fragS *insn_start_frag, offsetT insn_start_off)
2728 {
2729   char *p;
2730   relax_substateT subtype;
2731   symbolS *sym;
2732   offsetT off;
2733   int diff;
2734
2735   diff = 0;
2736   off = 0;
2737   insn_start_frag = frag_now;
2738   insn_start_off = frag_now_fix ();
2739
2740   subtype = EXPLICT_LONG_PREFIX;
2741
2742   frag_grow (2 + 2);
2743   p = frag_more (2);
2744
2745   sym = i.maxq20_op[this_operand].data;
2746   off = 0;
2747
2748   /* This will be overwritten later when the symbol is resolved.  */
2749   *p = i.instr[1];
2750   *(p + 1) = i.instr[0];
2751
2752   if (i.maxq20_op[this_operand].disps->X_op != O_constant
2753       && i.maxq20_op[this_operand].disps->X_op != O_symbol)
2754     /* Handle complex expressions.  */
2755     /* Because data is already in terms of symbol so no
2756        need to convert it from expression to symbol.  */
2757     off = 0;
2758
2759   frag_var (rs_machine_dependent, 2, i.reloc[this_operand], subtype, sym, off,  p);
2760 }
2761
2762 static void
2763 output_insn (void)
2764 {
2765   fragS *insn_start_frag;
2766   offsetT insn_start_off;
2767   char *p;
2768
2769   /* Tie dwarf2 debug info to the address at the start of the insn. We can't
2770      do this after the insn has been output as the current frag may have been 
2771      closed off.  eg. by frag_var.  */
2772   dwarf2_emit_insn (0);
2773
2774   /* To ALign the text section on word.  */
2775
2776   frag_align (1, 0, 1);
2777
2778   /* We initialise the frags for this particular instruction.  */
2779   insn_start_frag = frag_now;
2780   insn_start_off = frag_now_fix ();
2781
2782   /* If there are displacement operators(unresolved) present, then handle
2783      them separately.  */
2784   if (i.disp_operands)
2785     {
2786       output_disp (insn_start_frag, insn_start_off);
2787       return;
2788     }
2789
2790   if (i.data_operands)
2791     {
2792       output_data (insn_start_frag, insn_start_off);
2793       return;
2794     }
2795
2796   /* Check whether the INSERT_BUFFER has to be written.  */
2797   if (strcmp (INSERT_BUFFER, ""))
2798     {
2799       p = frag_more (2);
2800
2801       *p++ = INSERT_BUFFER[1];
2802       *p = INSERT_BUFFER[0];
2803     }
2804
2805   /* Check whether the prefix instruction has to be written.  */
2806   if (strcmp (PFX_INSN, ""))
2807     {
2808       p = frag_more (2);
2809
2810       *p++ = PFX_INSN[1];
2811       *p = PFX_INSN[0];
2812     }
2813
2814   p = frag_more (2);
2815   /* For Little endian.  */
2816   *p++ = i.instr[1];
2817   *p = i.instr[0];
2818 }
2819
2820 static void
2821 make_new_reg_table (void)
2822 {
2823   unsigned long size_pm = sizeof (peripheral_reg_table);
2824   num_of_reg = ARRAY_SIZE (peripheral_reg_table);
2825
2826   new_reg_table = xmalloc (size_pm);
2827   if (new_reg_table == NULL)
2828     as_bad (_("Cannot allocate memory"));
2829
2830   memcpy (new_reg_table, peripheral_reg_table, size_pm);
2831 }
2832
2833 /* pmmain performs the initilizations for the pheripheral modules. */
2834
2835 static void
2836 pmmain (void)
2837 {
2838   make_new_reg_table ();
2839   return;
2840 }
2841
2842 void
2843 md_begin (void)
2844 {
2845   const char *hash_err = NULL;
2846   int c = 0;
2847   char *p;
2848   const MAXQ20_OPCODE_INFO *optab;
2849   MAXQ20_OPCODES *core_optab;   /* For opcodes of the same name. This will
2850                                    be inserted into the hash table.  */
2851   struct reg *reg_tab;
2852   struct mem_access_syntax const *memsyntab;
2853   struct mem_access *memtab;
2854   struct bit_name *bittab;
2855
2856   /* Initilize pherioipheral modules.  */
2857   pmmain ();
2858
2859   /* Initialise the opcode hash table.  */
2860   op_hash = hash_new ();
2861
2862   optab = op_table;             /* Initialise it to the first entry of the
2863                                    maxq20 operand table.  */
2864
2865   /* Setup for loop.  */
2866   core_optab = xmalloc (sizeof (MAXQ20_OPCODES));
2867   core_optab->start = optab;
2868
2869   while (1)
2870     {
2871       ++optab;
2872       if (optab->name == NULL || strcmp (optab->name, (optab - 1)->name) != 0)
2873         {
2874           /* different name --> ship out current template list; add to hash
2875              table; & begin anew.  */
2876
2877           core_optab->end = optab;
2878 #ifdef MAXQ10S
2879           if (max_version == bfd_mach_maxq10)
2880             {
2881               if (((optab - 1)->arch == MAXQ10) || ((optab - 1)->arch == MAX))
2882                 {
2883                   hash_err = hash_insert (op_hash,
2884                                           (optab - 1)->name,
2885                                           (PTR) core_optab);
2886                 }
2887             }
2888           else if (max_version == bfd_mach_maxq20)
2889             {
2890               if (((optab - 1)->arch == MAXQ20) || ((optab - 1)->arch == MAX))
2891                 {
2892 #endif
2893                   hash_err = hash_insert (op_hash,
2894                                           (optab - 1)->name,
2895                                           (PTR) core_optab);
2896 #if MAXQ10S
2897                 }
2898             }
2899           else
2900             as_fatal (_("Internal Error: Illegal Architecure specified"));
2901 #endif
2902           if (hash_err)
2903             as_fatal (_("Internal Error:  Can't hash %s: %s"),
2904                       (optab - 1)->name, hash_err);
2905
2906           if (optab->name == NULL)
2907             break;
2908           core_optab = xmalloc (sizeof (MAXQ20_OPCODES));
2909           core_optab->start = optab;
2910         }
2911     }
2912
2913   /* Initialise a new register table.  */
2914   reg_hash = hash_new ();
2915
2916   for (reg_tab = system_reg_table;
2917        reg_tab < (system_reg_table + ARRAY_SIZE (system_reg_table));
2918        reg_tab++)
2919     {
2920 #if MAXQ10S
2921       switch (max_version)
2922         {
2923         case bfd_mach_maxq10:
2924           if ((reg_tab->arch == MAXQ10) || (reg_tab->arch == MAX))
2925             hash_err = hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
2926           break;
2927
2928         case bfd_mach_maxq20:
2929           if ((reg_tab->arch == MAXQ20) || (reg_tab->arch == MAX))
2930             {
2931 #endif
2932               hash_err =
2933                 hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
2934 #if MAXQ10S
2935             }
2936           break;
2937         default:
2938           as_fatal (_("Invalid architecture type"));
2939         }
2940 #endif
2941
2942       if (hash_err)
2943         as_fatal (_("Internal Error : Can't Hash %s : %s"),
2944                   reg_tab->reg_name, hash_err);
2945     }
2946
2947   /* Pheripheral Registers Entry.  */
2948   for (reg_tab = new_reg_table;
2949        reg_tab < (new_reg_table + num_of_reg - 1); reg_tab++)
2950     {
2951       hash_err = hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
2952
2953       if (hash_err)
2954         as_fatal (_("Internal Error : Can't Hash %s : %s"),
2955                   reg_tab->reg_name, hash_err);
2956     }
2957
2958   /* Initialise a new memory operand table.  */
2959   mem_hash = hash_new ();
2960
2961   for (memtab = mem_table;
2962        memtab < mem_table + ARRAY_SIZE (mem_table);
2963        memtab++)
2964     {
2965       hash_err = hash_insert (mem_hash, memtab->name, (PTR) memtab);
2966       if (hash_err)
2967         as_fatal (_("Internal Error : Can't Hash %s : %s"),
2968                   memtab->name, hash_err);
2969     }
2970
2971   bit_hash = hash_new ();
2972
2973   for (bittab = bit_table;
2974        bittab < bit_table + ARRAY_SIZE (bit_table);
2975        bittab++)
2976     {
2977       hash_err = hash_insert (bit_hash, bittab->name, (PTR) bittab);
2978       if (hash_err)
2979         as_fatal (_("Internal Error : Can't Hash %s : %s"),
2980                   bittab->name, hash_err);
2981     }
2982
2983   mem_syntax_hash = hash_new ();
2984
2985   for (memsyntab = mem_access_syntax_table;
2986        memsyntab < mem_access_syntax_table + ARRAY_SIZE (mem_access_syntax_table);
2987        memsyntab++)
2988     {
2989       hash_err =
2990         hash_insert (mem_syntax_hash, memsyntab->name, (PTR) memsyntab);
2991       if (hash_err)
2992         as_fatal (_("Internal Error : Can't Hash %s : %s"),
2993                   memsyntab->name, hash_err);
2994     }
2995
2996   /* Initialise the lexical tables,mnemonic chars,operand chars.  */
2997   for (c = 0; c < 256; c++)
2998     {
2999       if (ISDIGIT (c))
3000         {
3001           digit_chars[c] = c;
3002           mnemonic_chars[c] = c;
3003           operand_chars[c] = c;
3004           register_chars[c] = c;
3005         }
3006       else if (ISLOWER (c))
3007         {
3008           mnemonic_chars[c] = c;
3009           operand_chars[c] = c;
3010           register_chars[c] = c;
3011         }
3012       else if (ISUPPER (c))
3013         {
3014           mnemonic_chars[c] = TOLOWER (c);
3015           register_chars[c] = c;
3016           operand_chars[c] = c;
3017         }
3018
3019       if (ISALPHA (c) || ISDIGIT (c))
3020         {
3021           identifier_chars[c] = c;
3022         }
3023       else if (c > 128)
3024         {
3025           identifier_chars[c] = c;
3026           operand_chars[c] = c;
3027         }
3028     }
3029
3030   /* All the special characters.  */
3031   register_chars['@'] = '@';
3032   register_chars['+'] = '+';
3033   register_chars['-'] = '-';
3034   digit_chars['-'] = '-';
3035   identifier_chars['_'] = '_';
3036   identifier_chars['.'] = '.';
3037   register_chars['['] = '[';
3038   register_chars[']'] = ']';
3039   operand_chars['_'] = '_';
3040   operand_chars['#'] = '#';
3041   mnemonic_chars['['] = '[';
3042   mnemonic_chars[']'] = ']';
3043
3044   for (p = operand_special_chars; *p != '\0'; p++)
3045     operand_chars[(unsigned char) *p] = (unsigned char) *p;
3046
3047   /* Set the maxq arch type.  */
3048   maxq_target (max_version);
3049 }
3050
3051 /* md_assemble - Parse Instr - Seprate menmonics and operands - lookup the
3052    menmunonic in the operand table - Parse operands and populate the
3053    structure/template - Match the operand with opcode and its validity -
3054    Output Instr.  */
3055
3056 void
3057 md_assemble (char *line)
3058 {
3059   int j;
3060
3061   char mnemonic[MAX_MNEM_SIZE];
3062   char temp4prev[256];
3063   static char prev_insn[256];
3064
3065   /* Initialize globals.  */
3066   memset (&i, '\0', sizeof (i));
3067   for (j = 0; j < MAX_OPERANDS; j++)
3068     i.reloc[j] = NO_RELOC;
3069
3070   i.prefix = -1;
3071   PFX_INSN[0] = 0;
3072   PFX_INSN[1] = 0;
3073   INSERT_BUFFER[0] = 0;
3074   INSERT_BUFFER[1] = 0;
3075
3076   memcpy (temp4prev, line, strlen (line) + 1);
3077
3078   save_stack_p = save_stack;
3079
3080   line = (char *) parse_insn (line, mnemonic);
3081   if (line == NULL)
3082     return;
3083
3084   line = (char *) parse_operands (line, mnemonic);
3085   if (line == NULL)
3086     return;
3087
3088   /* Next, we find a template that matches the given insn, making sure the
3089      overlap of the given operands types is consistent with the template
3090      operand types.  */
3091   if (!match_template ())
3092     return;
3093
3094   /* In the MAXQ20, there are certain register combinations, and other
3095      restrictions which are not allowed. We will try to resolve these right
3096      now.  */
3097   if (!match_filters ())
3098     return;
3099
3100   /* Check for the appropriate PFX register.  */
3101   set_prefix ();
3102   pfx_for_imm_val (0);
3103
3104   if (!decode_insn ())          /* decode insn. */
3105     need_pass_2 = 1;
3106
3107   /* Check for Exlipct PFX instruction.  */
3108   if (PFX_INSN[0] && (strstr (prev_insn, "PFX") || strstr (prev_insn, "pfx")))
3109     as_warn (_("Ineffective insntruction %s \n"), prev_insn);
3110
3111   memcpy (prev_insn, temp4prev, strlen (temp4prev) + 1);
3112
3113   /* We are ready to output the insn.  */
3114   output_insn ();
3115 }