OSDN Git Service

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