* elf32-ppc.c (LWZU_0_X_11): Delete.
[binutils.git] / gas / config / tc-maxq.c
blobd6019e6763400e404d4d11befae6a23b6bd4a989
1 /* tc-maxq.c -- assembler code for a MAXQ chip.
3 Copyright 2004, 2005 Free Software Foundation, Inc.
5 Contributed by HCL Technologies Pvt. Ltd.
7 Author: Vineet Sharma(vineets@noida.hcltech.com) Inderpreet
8 S.(inderpreetb@noida.hcltech.com)
10 This file is part of GAS.
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 2, or (at your option) any later version.
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.
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. */
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"
33 #ifndef MAXQ10S
34 #define MAXQ10S 1
35 #endif
37 #ifndef _STRING_H
38 #include "string.h"
39 #endif
41 #ifndef DEFAULT_ARCH
42 #define DEFAULT_ARCH "MAXQ20"
43 #endif
45 #ifndef MAX_OPERANDS
46 #define MAX_OPERANDS 2
47 #endif
49 #ifndef MAX_MNEM_SIZE
50 #define MAX_MNEM_SIZE 8
51 #endif
53 #ifndef END_OF_INSN
54 #define END_OF_INSN '\0'
55 #endif
57 #ifndef IMMEDIATE_PREFIX
58 #define IMMEDIATE_PREFIX '#'
59 #endif
61 #ifndef MAX_REG_NAME_SIZE
62 #define MAX_REG_NAME_SIZE 4
63 #endif
65 #ifndef MAX_MEM_NAME_SIZE
66 #define MAX_MEM_NAME_SIZE 9
67 #endif
69 /* opcode for PFX[0]. */
70 #define PFX0 0x0b
72 /* Set default to MAXQ20. */
73 unsigned int max_version = bfd_mach_maxq20;
75 const char *default_arch = DEFAULT_ARCH;
77 /* Type of the operand: Register,Immediate,Memory access,flag or bit. */
79 union _maxq20_op
81 const reg_entry * reg;
82 char imms; /* This is to store the immediate value operand. */
83 expressionS * disps;
84 symbolS * data;
85 const mem_access * mem;
86 int flag;
87 const reg_bit * r_bit;
90 typedef union _maxq20_op maxq20_opcode;
92 /* For handling optional L/S in Maxq20. */
93 #ifdef BFD_ASSEMBLER
95 /* Exposed For Linker - maps indirectly to the liker relocations. */
96 #define LONG_PREFIX MAXQ_LONGJUMP /* BFD_RELOC_16 */
97 #define SHORT_PREFIX MAXQ_SHORTJUMP /* BFD_RELOC_16_PCREL_S2 */
98 #define ABSOLUTE_ADDR_FOR_DATA MAXQ_INTERSEGMENT
100 #define NO_PREFIX 0
101 #define EXPLICT_LONG_PREFIX 14
103 #else
105 #define EXPLICT_LONG_PREFIX 14
106 #define LONG_PREFIX 5
107 #define SHORT_PREFIX 1
108 #define ABSOLUTE_ADDR_FOR_DATA 0
109 #define NO_PREFIX 0
111 #endif
113 /* The main instruction structure containing fields to describe instrn */
114 typedef struct _maxq20_insn
116 /* The opcode information for the MAXQ20 */
117 MAXQ20_OPCODE_INFO op;
119 /* The number of operands */
120 unsigned int operands;
122 /* Number of different types of operands - Comments can be removed if reqd.
124 unsigned int reg_operands, mem_operands, disp_operands, data_operands;
125 unsigned int imm_operands, imm_bit_operands, bit_operands, flag_operands;
127 /* Types of the individual operands */
128 UNKNOWN_OP types[MAX_OPERANDS];
130 /* Relocation type for operand : to be investigated into */
131 int reloc[MAX_OPERANDS];
133 /* Complete information of the Operands */
134 maxq20_opcode maxq20_op[MAX_OPERANDS];
136 /* Choice of prefix register whenever needed */
137 int prefix;
139 /* Optional Prefix for Instructions like LJUMP, SJUMP etc */
140 unsigned char Instr_Prefix;
142 /* 16 bit Instruction word */
143 unsigned char instr[2];
145 maxq20_insn;
147 /* Definitions of all possible characters that can start an operand. */
148 const char *extra_symbol_chars = "@(#";
150 /* Special Character that would start a comment. */
151 const char comment_chars[] = ";";
153 /* Starts a comment when it appears at the start of a line. */
154 const char line_comment_chars[] = ";#";
156 const char line_separator_chars[] = ""; /* originally may b by sudeep "\n". */
158 /* The following are used for option processing. */
160 /* This is added to the mach independent string passed to getopt. */
161 const char *md_shortopts = "q";
163 /* Characters for exponent and floating point. */
164 const char EXP_CHARS[] = "eE";
165 const char FLT_CHARS[] = "";
167 /* This is for the machine dependent option handling. */
168 #define OPTION_EB (OPTION_MD_BASE + 0)
169 #define OPTION_EL (OPTION_MD_BASE + 1)
170 #define MAXQ_10 (OPTION_MD_BASE + 2)
171 #define MAXQ_20 (OPTION_MD_BASE + 3)
173 struct option md_longopts[] =
175 {"MAXQ10", no_argument, NULL, MAXQ_10},
176 {"MAXQ20", no_argument, NULL, MAXQ_20},
177 {NULL, no_argument, NULL, 0}
179 size_t md_longopts_size = sizeof (md_longopts);
181 /* md_undefined_symbol We have no need for this function. */
183 symbolS *
184 md_undefined_symbol (char * name ATTRIBUTE_UNUSED)
186 return NULL;
189 static void
190 maxq_target (int target)
192 max_version = target;
193 bfd_set_arch_mach (stdoutput, bfd_arch_maxq, max_version);
197 md_parse_option (int c, char *arg ATTRIBUTE_UNUSED)
199 /* Any options support will be added onto this switch case. */
200 switch (c)
202 case MAXQ_10:
203 max_version = bfd_mach_maxq10;
204 break;
205 case MAXQ_20:
206 max_version = bfd_mach_maxq20;
207 break;
209 default:
210 return 0;
213 return 1;
216 /* When a usage message is printed, this function is called and
217 it prints a description of the machine specific options. */
219 void
220 md_show_usage (FILE * stream)
222 /* Over here we will fill the description of the machine specific options. */
224 fprintf (stream, _(" MAXQ-specific assembler options:\n"));
226 fprintf (stream, _("\
227 -MAXQ20 generate obj for MAXQ20(default)\n\
228 -MAXQ10 generate obj for MAXQ10\n\
229 "));
232 #ifdef BFD_ASSEMBLER
233 unsigned long
234 maxq20_mach (void)
236 if (!(strcmp (default_arch, "MAXQ20")))
237 return 0;
239 as_fatal (_("Unknown architecture"));
240 return 1;
243 arelent *
244 tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
246 arelent *rel;
247 bfd_reloc_code_real_type code;
249 switch (fixp->fx_r_type)
251 case MAXQ_INTERSEGMENT:
252 case MAXQ_LONGJUMP:
253 case BFD_RELOC_16_PCREL_S2:
254 code = fixp->fx_r_type;
255 break;
257 case 0:
258 default:
259 switch (fixp->fx_size)
261 default:
262 as_bad_where (fixp->fx_file, fixp->fx_line,
263 _("can not do %d byte relocation"), fixp->fx_size);
264 code = BFD_RELOC_32;
265 break;
267 case 1:
268 code = BFD_RELOC_8;
269 break;
270 case 2:
271 code = BFD_RELOC_16;
272 break;
273 case 4:
274 code = BFD_RELOC_32;
275 break;
279 rel = xmalloc (sizeof (arelent));
280 rel->sym_ptr_ptr = xmalloc (sizeof (asymbol *));
281 *rel->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
283 rel->address = fixp->fx_frag->fr_address + fixp->fx_where;
284 rel->addend = fixp->fx_addnumber;
285 rel->howto = bfd_reloc_type_lookup (stdoutput, code);
287 if (rel->howto == NULL)
289 as_bad_where (fixp->fx_file, fixp->fx_line,
290 _("cannot represent relocation type %s"),
291 bfd_get_reloc_code_name (code));
293 /* Set howto to a garbage value so that we can keep going. */
294 rel->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_32);
295 assert (rel->howto != NULL);
298 return rel;
301 #endif
303 /* md_estimate_size_before_relax()
305 Called just before relax() for rs_machine_dependent frags. The MAXQ
306 assembler uses these frags to handle 16 bit absolute jumps which require a
307 prefix instruction to be inserted. Any symbol that is now undefined will
308 not become defined. Return the correct fr_subtype in the frag. Return the
309 initial "guess for variable size of frag"(This will be eiter 2 or 0) to
310 caller. The guess is actually the growth beyond the fixed part. Whatever
311 we do to grow the fixed or variable part contributes to our returned
312 value. */
315 md_estimate_size_before_relax (fragS *fragP, segT segment)
317 /* Check whether the symbol has been resolved or not.
318 Otherwise we will have to generate a fixup. */
319 if ((S_GET_SEGMENT (fragP->fr_symbol) != segment)
320 || fragP->fr_subtype == EXPLICT_LONG_PREFIX)
322 RELOC_ENUM reloc_type;
323 unsigned char *opcode;
324 int old_fr_fix;
326 /* Now this symbol has not been defined in this file.
327 Hence we will have to create a fixup. */
328 int size = 2;
330 /* This is for the prefix instruction. */
332 if (fragP->fr_subtype == EXPLICT_LONG_PREFIX)
333 fragP->fr_subtype = LONG_PREFIX;
335 if (S_GET_SEGMENT (fragP->fr_symbol) != segment
336 && ((!(fragP->fr_subtype) == EXPLICT_LONG_PREFIX)))
337 fragP->fr_subtype = ABSOLUTE_ADDR_FOR_DATA;
339 reloc_type =
340 (fragP->fr_subtype ? fragP->fr_subtype : ABSOLUTE_ADDR_FOR_DATA);
342 fragP->fr_subtype = reloc_type;
344 if (reloc_type == SHORT_PREFIX)
345 size = 0;
346 old_fr_fix = fragP->fr_fix;
347 opcode = (unsigned char *) fragP->fr_opcode;
349 fragP->fr_fix += (size);
351 fix_new (fragP, old_fr_fix - 2, size + 2,
352 fragP->fr_symbol, fragP->fr_offset, 0, reloc_type);
353 frag_wane (fragP);
354 return fragP->fr_fix - old_fr_fix;
357 if (fragP->fr_subtype == SHORT_PREFIX)
359 fragP->fr_subtype = SHORT_PREFIX;
360 return 0;
363 if (fragP->fr_subtype == NO_PREFIX || fragP->fr_subtype == LONG_PREFIX)
365 unsigned long instr;
366 unsigned long call_addr;
367 long diff;
368 fragS *f;
369 diff = diff ^ diff;;
370 call_addr = call_addr ^ call_addr;
371 instr = 0;
372 f = NULL;
374 /* segment_info_type *seginfo = seg_info (segment); */
375 instr = fragP->fr_address + fragP->fr_fix - 2;
377 /* This is the offset if it is a PC relative jump. */
378 call_addr = S_GET_VALUE (fragP->fr_symbol) + fragP->fr_offset;
380 /* PC stores the value of the next instruction. */
381 diff = (call_addr - instr) - 1;
383 if (diff >= (-128 * 2) && diff <= (2 * 127))
385 /* Now as offset is an 8 bit value, we will pass
386 that to the jump instruction directly. */
387 fragP->fr_subtype = NO_PREFIX;
388 return 0;
391 fragP->fr_subtype = LONG_PREFIX;
392 return 2;
395 as_fatal (_("Illegal Reloc type in md_estimate_size_before_relax for line : %d"),
396 frag_now->fr_line);
397 return 0;
400 /* Equal to MAX_PRECISION in atof-ieee.c */
401 #define MAX_LITTLENUMS 6
403 /* Turn a string in input_line_pointer into a floating point constant of type
404 TYPE, and store the appropriate bytes in *LITP. The number of LITTLENUMS
405 emitted is stored in *SIZEP. An error message is returned, or NULL on OK. */
407 char *
408 md_atof (int type, char * litP, int * sizeP)
410 int prec;
411 LITTLENUM_TYPE words[4];
412 char *t;
413 int i;
415 switch (type)
417 case 'f':
418 prec = 2;
419 break;
421 case 'd':
422 prec = 2;
423 /* The size of Double has been changed to 2 words ie 32 bits. */
424 /* prec = 4; */
425 break;
427 default:
428 *sizeP = 0;
429 return _("bad call to md_atof");
432 t = atof_ieee (input_line_pointer, type, words);
433 if (t)
434 input_line_pointer = t;
436 *sizeP = prec * 2;
438 for (i = prec - 1; i >= 0; i--)
440 md_number_to_chars (litP, (valueT) words[i], 2);
441 litP += 2;
444 return NULL;
447 void
448 maxq20_cons_fix_new (fragS * frag, unsigned int off, unsigned int len,
449 expressionS * exp)
451 int r = 0;
453 switch (len)
455 case 2:
456 r = MAXQ_WORDDATA; /* Word+n */
457 break;
458 case 4:
459 r = MAXQ_LONGDATA; /* Long+n */
460 break;
463 fix_new_exp (frag, off, len, exp, 0, r);
464 return;
467 short
468 tc_coff_fix2rtype (fixS * fixP)
470 return fixP->fx_r_type;
474 tc_coff_sizemachdep (fragS *fragP)
476 if (fragP->fr_next)
477 return (fragP->fr_next->fr_address - fragP->fr_address);
479 return 0;
482 /* GAS will call this for every rs_machine_dependent fragment. The
483 instruction is compleated using the data from the relaxation pass. It may
484 also create any necessary relocations. */
485 #ifdef BFD_ASSEMBLER
486 void
487 md_convert_frag (bfd * headers ATTRIBUTE_UNUSED,
488 segT seg ATTRIBUTE_UNUSED,
489 fragS * fragP)
490 #else
491 void
492 md_convert_frag (object_headers * headers ATTRIBUTE_UNUSED,
493 segT sec ATTRIBUTE_UNUSED,
494 fragS * fragP)
495 #endif
497 char *opcode;
498 offsetT target_address;
499 offsetT opcode_address;
500 offsetT displacement_from_opcode_start;
501 int address;
503 opcode = fragP->fr_opcode;
504 address = 0;
505 target_address = opcode_address = displacement_from_opcode_start = 0;
507 target_address =
508 (S_GET_VALUE (fragP->fr_symbol) / MAXQ_OCTETS_PER_BYTE) +
509 (fragP->fr_offset / MAXQ_OCTETS_PER_BYTE);
511 opcode_address =
512 (fragP->fr_address / MAXQ_OCTETS_PER_BYTE) +
513 ((fragP->fr_fix - 2) / MAXQ_OCTETS_PER_BYTE);
515 /* PC points to the next Instruction. */
516 displacement_from_opcode_start = ((target_address - opcode_address) - 1);
518 if ((displacement_from_opcode_start >= -128
519 && displacement_from_opcode_start <= 127)
520 && (fragP->fr_subtype == SHORT_PREFIX
521 || fragP->fr_subtype == NO_PREFIX))
523 /* Its a displacement. */
524 *opcode = (char) displacement_from_opcode_start;
526 else
528 /* Its an absolute 16 bit jump. Now we have to
529 load the prefix operator with the upper 8 bits. */
530 if (fragP->fr_subtype == SHORT_PREFIX)
532 as_bad (_("Cant make long jump/call into short jump/call : %d"),
533 fragP->fr_line);
534 return;
537 /* Check whether the symbol has been resolved or not.
538 Otherwise we will have to generate a fixup. */
540 if (fragP->fr_subtype != SHORT_PREFIX)
542 RELOC_ENUM reloc_type;
543 int old_fr_fix;
544 int size = 2;
546 /* Now this is a basolute jump/call.
547 Hence we will have to create a fixup. */
548 if (fragP->fr_subtype == NO_PREFIX)
549 fragP->fr_subtype = LONG_PREFIX;
551 reloc_type =
552 (fragP->fr_subtype ? fragP->fr_subtype : LONG_PREFIX);
554 if (reloc_type == 1)
555 size = 0;
556 old_fr_fix = fragP->fr_fix;
558 fragP->fr_fix += (size);
560 fix_new (fragP, old_fr_fix - 2, size + 2,
561 fragP->fr_symbol, fragP->fr_offset, 0, reloc_type);
562 frag_wane (fragP);
567 long
568 md_pcrel_from (fixS *fixP)
570 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
573 /* Writes the val to the buf, where n is the nuumber of bytes to write. */
575 void
576 maxq_number_to_chars (char *buf, valueT val, int n)
578 if (target_big_endian)
579 number_to_chars_bigendian (buf, val, n);
580 else
581 number_to_chars_littleendian (buf, val, n);
584 /* GAS will call this for each fixup. It's main objective is to store the
585 correct value in the object file. 'fixup_segment' performs the generic
586 overflow check on the 'valueT *val' argument after md_apply_fix3 returns.
587 If the overflow check is relevant for the target machine, then
588 'md_apply_fix3' should modify 'valueT *val', typically to the value stored
589 in the object file (not to be done in MAXQ). */
591 void
592 md_apply_fix3 (fixS *fixP, valueT *valT, segT seg ATTRIBUTE_UNUSED)
594 char *p = fixP->fx_frag->fr_literal + fixP->fx_where;
595 char *frag_to_fix_at =
596 fixP->fx_frag->fr_literal + fixP->fx_frag->fr_fix - 2;
598 if (fixP)
600 if (fixP->fx_frag && valT)
602 /* If the relaxation substate is not defined we make it equal
603 to the kind of relocation the fixup is generated for. */
604 if (!fixP->fx_frag->fr_subtype)
605 fixP->fx_frag->fr_subtype = fixP->fx_r_type;
607 /* For any instruction in which either we have specified an
608 absolute address or it is a long jump we need to add a PFX0
609 instruction to it. In this case as the instruction has already
610 being written at 'fx_where' in the frag we copy it at the end of
611 the frag(which is where the relocation was generated) as when
612 the relocation is generated the frag is grown by 2 type, this is
613 where we copy the contents of fx_where and add a pfx0 at
614 fx_where. */
615 if ((fixP->fx_frag->fr_subtype == ABSOLUTE_ADDR_FOR_DATA)
616 || (fixP->fx_frag->fr_subtype == LONG_PREFIX))
618 *(frag_to_fix_at + 1) = *(p + 1);
619 maxq_number_to_chars (p + 1, PFX0, 1);
622 #ifdef BFD_ASSEMBLER
623 /* Remember value for tc_gen_reloc. */
624 fixP->fx_addnumber = *valT;
625 #endif
628 /* This prob can be fixed by defining tc_fix_adjustable. */
629 #ifndef BFD_ASSEMBLER
630 if (fixP->fx_addsy && S_GET_SEGMENT (fixP->fx_addsy))
631 segment_info[S_GET_SEGMENT (fixP->fx_addsy)].dot = NULL;
632 #endif
634 /* Some fixups generated by GAS which gets resovled before this this
635 func. is called need to be wriiten to the frag as here we are going
636 to go away with the relocations fx_done=1. */
637 if (fixP->fx_addsy == NULL)
639 maxq_number_to_chars (p, *valT, fixP->fx_size);
640 fixP->fx_addnumber = *valT;
641 fixP->fx_done = 1;
646 /* Tables for lexical analysis. */
647 static char mnemonic_chars[256];
648 static char register_chars[256];
649 static char operand_chars[256];
650 static char identifier_chars[256];
651 static char digit_chars[256];
653 /* Lexical Macros. */
654 #define is_mnemonic_char(x) (mnemonic_chars[(unsigned char)(x)])
655 #define is_register_char(x) (register_chars[(unsigned char)(x)])
656 #define is_operand_char(x) (operand_chars[(unsigned char)(x)])
657 #define is_space_char(x) (x==' ')
658 #define is_identifier_char(x) (identifier_chars[(unsigned char)(x)])
659 #define is_digit_char(x) (identifier_chars[(unsigned char)(x)])
661 /* Special characters for operands. */
662 static char operand_special_chars[] = "[]@.-+";
664 /* md_assemble() will always leave the instruction passed to it unaltered.
665 To do this we store the instruction in a special stack. */
666 static char save_stack[32];
667 static char *save_stack_p;
669 #define END_STRING_AND_SAVE(s) \
670 do \
672 *save_stack_p++ = *(s); \
673 *s = '\0'; \
675 while (0)
677 #define RESTORE_END_STRING(s) \
678 do \
680 *(s) = *(--save_stack_p); \
682 while (0)
684 /* The instruction we are assembling. */
685 static maxq20_insn i;
687 /* The current template. */
688 static MAXQ20_OPCODES *current_templates;
690 /* The displacement operand if any. */
691 static expressionS disp_expressions;
693 /* Current Operand we are working on (0:1st operand,1:2nd operand). */
694 static int this_operand;
696 /* The prefix instruction if used. */
697 static char PFX_INSN[2];
698 static char INSERT_BUFFER[2];
700 /* For interface with expression() ????? */
701 extern char *input_line_pointer;
703 /* The HASH Tables: */
705 /* Operand Hash Table. */
706 static struct hash_control *op_hash;
708 /* Register Hash Table. */
709 static struct hash_control *reg_hash;
711 /* Memory reference Hash Table. */
712 static struct hash_control *mem_hash;
714 /* Bit hash table. */
715 static struct hash_control *bit_hash;
717 /* Memory Access syntax table. */
718 static struct hash_control *mem_syntax_hash;
720 /* This is a mapping from pseudo-op names to functions. */
722 const pseudo_typeS md_pseudo_table[] =
724 {"int", cons, 2}, /* size of 'int' has been changed to 1 word
725 (i.e) 16 bits. */
726 {"maxq10", maxq_target, bfd_mach_maxq10},
727 {"maxq20", maxq_target, bfd_mach_maxq20},
728 {NULL, 0, 0},
731 #if defined(BFD_HEADERS)
732 #ifdef RELSZ
733 const int md_reloc_size = RELSZ; /* Coff headers. */
734 #else
735 const int md_reloc_size = 12; /* Something else headers. */
736 #endif
737 #else
738 const int md_reloc_size = 12; /* Not bfdized. */
739 #endif
741 #define SET_PFX_ARG(x) (PFX_INSN[1] = x)
744 /* This function sets the PFX value coresponding to the specs. Source
745 Destination Index Selection ---------------------------------- Write To|
746 SourceRegRange | Dest Addr Range
747 ------------------------------------------------------ PFX[0] | 0h-Fh |
748 0h-7h PFX[1] | 10h-1Fh | 0h-7h PFX[2] | 0h-Fh | 8h-Fh PFX[3] | 10h-1Fh |
749 8h-Fh PFX[4] | 0h-Fh | 10h-17h PFX[5] | 10h-1Fh | 10h-17h PFX[6] | 0h-Fh |
750 18h-1Fh PFX[7] | 0h-Fh | 18h-1Fh */
752 static void
753 set_prefix (void)
755 short int src_index = 0, dst_index = 0;
757 if (i.operands == 0)
758 return;
759 if (i.operands == 1) /* Only SRC is Present */
761 if (i.types[0] == REG)
763 if (!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
765 dst_index = i.maxq20_op[0].reg[0].Mod_index;
766 src_index = 0x00;
768 else
770 src_index = i.maxq20_op[0].reg[0].Mod_index;
771 dst_index = 0x00;
776 if (i.operands == 2)
778 if (i.types[0] == REG && i.types[1] == REG)
780 dst_index = i.maxq20_op[0].reg[0].Mod_index;
781 src_index = i.maxq20_op[1].reg[0].Mod_index;
783 else if (i.types[0] != REG && i.types[1] == REG) /* DST is Absent */
785 src_index = i.maxq20_op[1].reg[0].Mod_index;
786 dst_index = 0x00;
788 else if (i.types[0] == REG && i.types[1] != REG) /* Id SRC is Absent */
790 dst_index = i.maxq20_op[0].reg[0].Mod_index;
791 src_index = 0x00;
793 else if (i.types[0] == BIT && i.maxq20_op[0].r_bit)
795 dst_index = i.maxq20_op[0].r_bit->reg->Mod_index;
796 src_index = 0x00;
799 else if (i.types[1] == BIT && i.maxq20_op[1].r_bit)
801 dst_index = 0x00;
802 src_index = i.maxq20_op[1].r_bit->reg->Mod_index;
806 if (src_index >= 0x00 && src_index <= 0xF)
808 if (dst_index >= 0x00 && dst_index <= 0x07)
809 /* Set PFX[0] */
810 i.prefix = 0;
812 else if (dst_index >= 0x08 && dst_index <= 0x0F)
813 /* Set PFX[2] */
814 i.prefix = 2;
816 else if (dst_index >= 0x10 && dst_index <= 0x17)
817 /* Set PFX[4] */
818 i.prefix = 4;
820 else if (dst_index >= 0x18 && dst_index <= 0x1F)
821 /* Set PFX[6] */
822 i.prefix = 6;
824 else if (src_index >= 0x10 && src_index <= 0x1F)
826 if (dst_index >= 0x00 && dst_index <= 0x07)
827 /* Set PFX[1] */
828 i.prefix = 1;
830 else if (dst_index >= 0x08 && dst_index <= 0x0F)
831 /* Set PFX[3] */
832 i.prefix = 3;
834 else if (dst_index >= 0x10 && dst_index <= 0x17)
835 /* Set PFX[5] */
836 i.prefix = 5;
838 else if (dst_index >= 0x18 && dst_index <= 0x1F)
839 /* Set PFX[7] */
840 i.prefix = 7;
844 static unsigned char
845 is_a_LSinstr (const char *ln_pointer)
847 int i = 0;
849 for (i = 0; LSInstr[i] != NULL; i++)
850 if (!strcmp (LSInstr[i], ln_pointer))
851 return 1;
853 return 0;
856 static void
857 LS_processing (const char *line)
859 if (is_a_LSinstr (line))
861 if ((line[0] == 'L') || (line[0] == 'l'))
863 i.prefix = 0;
864 INSERT_BUFFER[0] = PFX0;
865 i.Instr_Prefix = LONG_PREFIX;
867 else if ((line[0] == 'S') || (line[0] == 's'))
868 i.Instr_Prefix = SHORT_PREFIX;
869 else
870 i.Instr_Prefix = NO_PREFIX;
872 else
873 i.Instr_Prefix = LONG_PREFIX;
876 /* Separate mnemonics and the operands. */
878 static char *
879 parse_insn (char *line, char *mnemonic)
881 char *l = line;
882 char *token_start = l;
883 char *mnem_p;
884 char temp[MAX_MNEM_SIZE];
885 int ii = 0;
887 memset (temp, END_OF_INSN, MAX_MNEM_SIZE);
888 mnem_p = mnemonic;
890 while ((*mnem_p = mnemonic_chars[(unsigned char) *l]) != 0)
892 ii++;
893 mnem_p++;
894 if (mnem_p >= mnemonic + MAX_MNEM_SIZE)
896 as_bad (_("no such instruction: `%s'"), token_start);
897 return NULL;
899 l++;
902 if (!is_space_char (*l) && *l != END_OF_INSN)
904 as_bad (_("invalid character %s in mnemonic"), l);
905 return NULL;
908 while (ii)
910 temp[ii - 1] = toupper ((char) mnemonic[ii - 1]);
911 ii--;
914 LS_processing (temp);
916 if (i.Instr_Prefix != 0 && is_a_LSinstr (temp))
917 /* Skip the optional L-S. */
918 memcpy (temp, temp + 1, MAX_MNEM_SIZE);
920 /* Look up instruction (or prefix) via hash table. */
921 current_templates = (MAXQ20_OPCODES *) hash_find (op_hash, temp);
923 if (current_templates != NULL)
924 return l;
926 as_bad (_("no such instruction: `%s'"), token_start);
927 return NULL;
930 /* Function to calculate x to the power of y.
931 Just to avoid including the math libraries. */
933 static int
934 pwr (int x, int y)
936 int k, ans = 1;
938 for (k = 0; k < y; k++)
939 ans *= x;
941 return ans;
944 static reg_entry *
945 parse_reg_by_index (char *imm_start)
947 int k = 0, mid = 0, rid = 0, val = 0, j = 0;
948 char temp[4] = { 0 };
949 reg_entry *reg = NULL;
953 if (isdigit (imm_start[k]))
954 temp[k] = imm_start[k] - '0';
956 else if (isalpha (imm_start[k])
957 && (imm_start[k] = tolower (imm_start[k])) < 'g')
958 temp[k] = 10 + (int) (imm_start[k] - 'a');
960 else if (imm_start[k] == 'h')
961 break;
963 else if (imm_start[k] == END_OF_INSN)
965 imm_start[k] = 'd';
966 break;
969 else
970 return NULL; /* not a hex digit */
972 k++;
974 while (imm_start[k] != '\n');
976 switch (imm_start[k])
978 case 'h':
979 for (j = 0; j < k; j++)
980 val += temp[j] * pwr (16, k - j - 1);
981 break;
983 case 'd':
984 for (j = 0; j < k; j++)
986 if (temp[j] > 9)
987 return NULL; /* not a number */
989 val += temp[j] * pwr (10, k - j - 1);
990 break;
994 /* Get the module and register id's. */
995 mid = val & 0x0f;
996 rid = (val >> 4) & 0x0f;
998 if (mid < 6)
1000 /* Search the pheripheral reg table. */
1001 for (j = 0; j < num_of_reg; j++)
1003 if (new_reg_table[j].opcode == val)
1005 reg = (reg_entry *) & new_reg_table[j];
1006 break;
1011 else
1013 /* Search the system register table. */
1014 j = 0;
1016 while (system_reg_table[j].reg_name != NULL)
1018 if (system_reg_table[j].opcode == val)
1020 reg = (reg_entry *) & system_reg_table[j];
1021 break;
1023 j++;
1027 if (reg == NULL)
1029 as_bad (_("Invalid register value %s"), imm_start);
1030 return reg;
1033 #if CHANGE_PFX
1034 if (this_operand == 0 && reg != NULL)
1036 if (reg->Mod_index > 7)
1037 i.prefix = 2;
1038 else
1039 i.prefix = 0;
1041 #endif
1042 return (reg_entry *) reg;
1045 /* REG_STRING starts *before* REGISTER_PREFIX. */
1047 static reg_entry *
1048 parse_register (char *reg_string, char **end_op)
1050 char *s = reg_string;
1051 char *p = NULL;
1052 char reg_name_given[MAX_REG_NAME_SIZE + 1];
1053 reg_entry *r = NULL;
1055 r = NULL;
1056 p = NULL;
1058 /* Skip possible REGISTER_PREFIX and possible whitespace. */
1059 if (is_space_char (*s))
1060 ++s;
1062 p = reg_name_given;
1063 while ((*p++ = register_chars[(unsigned char) *s]) != '\0')
1065 if (p >= reg_name_given + MAX_REG_NAME_SIZE)
1066 return (reg_entry *) NULL;
1067 s++;
1070 *end_op = s;
1072 r = (reg_entry *) hash_find (reg_hash, reg_name_given);
1074 #if CHANGE_PFX
1075 if (this_operand == 0 && r != NULL)
1077 if (r->Mod_index > 7)
1078 i.prefix = 2;
1079 else
1080 i.prefix = 0;
1082 #endif
1083 return r;
1086 static reg_bit *
1087 parse_register_bit (char *reg_string, char **end_op)
1089 const char *s = reg_string;
1090 short k = 0;
1091 char diff = 0;
1092 reg_bit *rb = NULL;
1093 reg_entry *r = NULL;
1094 bit_name *b = NULL;
1095 char temp_bitname[MAX_REG_NAME_SIZE + 2];
1096 char temp[MAX_REG_NAME_SIZE + 1];
1098 memset (&temp, '\0', (MAX_REG_NAME_SIZE + 1));
1099 memset (&temp_bitname, '\0', (MAX_REG_NAME_SIZE + 2));
1101 diff = 0;
1102 r = NULL;
1103 rb = NULL;
1104 rb = xmalloc (sizeof (reg_bit));
1105 rb->reg = xmalloc (sizeof (reg_entry));
1106 k = 0;
1108 /* For supporting bit names. */
1109 b = (bit_name *) hash_find (bit_hash, reg_string);
1111 if (b != NULL)
1113 *end_op = reg_string + strlen (reg_string);
1114 strcpy (temp_bitname, b->reg_bit);
1115 s = temp_bitname;
1118 if (strchr (s, '.'))
1120 while (*s != '.')
1122 if (*s == '\0')
1123 return NULL;
1124 temp[k] = *s++;
1126 k++;
1128 temp[k] = '\0';
1131 if ((r = parse_register (temp, end_op)) == NULL)
1132 return NULL;
1134 rb->reg = r;
1136 /* Skip the "." */
1137 s++;
1139 if (isdigit ((char) *s))
1140 rb->bit = atoi (s);
1141 else if (isalpha ((char) *s))
1143 rb->bit = (char) *s - 'a';
1144 rb->bit += 10;
1145 if (rb->bit > 15)
1147 as_bad (_("Invalid bit number : '%c'"), (char) *s);
1148 return NULL;
1152 if (b != NULL)
1153 diff = strlen (temp_bitname) - strlen (temp) - 1;
1154 else
1155 diff = strlen (reg_string) - strlen (temp) - 1;
1157 if (*(s + diff) != '\0')
1159 as_bad (_("Illegal character after operand '%s'"), reg_string);
1160 return NULL;
1163 return rb;
1166 static void
1167 pfx_for_imm_val (int arg)
1169 if (i.prefix == -1)
1170 return;
1172 if (i.prefix == 0 && arg == 0 && PFX_INSN[1] == 0 && !(i.data_operands))
1173 return;
1175 if (!(i.prefix < 0) && !(i.prefix > 7))
1176 PFX_INSN[0] = (i.prefix << 4) | PFX0;
1178 if (!PFX_INSN[1])
1179 PFX_INSN[1] = arg;
1183 static int
1184 maxq20_immediate (char *imm_start)
1186 int val = 0, val_pfx = 0;
1187 char sign_val = 0;
1188 int k = 0, j;
1189 int temp[4] = { 0 };
1191 imm_start++;
1193 if (imm_start[1] == '\0' && (imm_start[0] == '0' || imm_start[0] == '1')
1194 && (this_operand == 1 && ((i.types[0] == BIT || i.types[0] == FLAG))))
1196 val = imm_start[0] - '0';
1197 i.imm_bit_operands++;
1198 i.types[this_operand] = IMMBIT;
1199 i.maxq20_op[this_operand].imms = (char) val;
1200 #if CHANGE_PFX
1201 if (i.prefix == 2)
1202 pfx_for_imm_val (0);
1203 #endif
1204 return 1;
1207 /* Check For Sign Charcater. */
1208 sign_val = 0;
1212 if (imm_start[k] == '-' && k == 0)
1213 sign_val = -1;
1215 else if (imm_start[k] == '+' && k == 0)
1216 sign_val = 1;
1218 else if (isdigit (imm_start[k]))
1219 temp[k] = imm_start[k] - '0';
1221 else if (isalpha (imm_start[k])
1222 && (imm_start[k] = tolower (imm_start[k])) < 'g')
1223 temp[k] = 10 + (int) (imm_start[k] - 'a');
1225 else if (imm_start[k] == 'h')
1226 break;
1228 else if (imm_start[k] == '\0')
1230 imm_start[k] = 'd';
1231 break;
1233 else
1235 as_bad (_("Invalid Character in immediate Value : %c"),
1236 imm_start[k]);
1237 return 0;
1239 k++;
1241 while (imm_start[k] != '\n');
1243 switch (imm_start[k])
1245 case 'h':
1246 for (j = (sign_val ? 1 : 0); j < k; j++)
1247 val += temp[j] * pwr (16, k - j - 1);
1248 break;
1250 case 'd':
1251 for (j = (sign_val ? 1 : 0); j < k; j++)
1253 if (temp[j] > 9)
1255 as_bad (_("Invalid Character in immediate value : %c"),
1256 imm_start[j]);
1257 return 0;
1259 val += temp[j] * pwr (10, k - j - 1);
1263 if (!sign_val)
1264 sign_val = 1;
1266 /* Now over here the value val stores the 8 bit/16 bit value. We will put a
1267 check if we are moving a 16 bit immediate value into an 8 bit register.
1268 In that case we will generate a warning and move only the lower 8 bits */
1269 if (val > 65535)
1271 as_bad (_("Immediate value greater than 16 bits"));
1272 return 0;
1275 val = val * sign_val;
1277 /* If it is a stack pointer and the value is greater than the maximum
1278 permissible size */
1279 if (this_operand == 1)
1281 if ((val * sign_val) > MAX_STACK && i.types[0] == REG
1282 && !strcmp (i.maxq20_op[0].reg->reg_name, "SP"))
1284 as_warn (_
1285 ("Attempt to move a value in the stack pointer greater than the size of the stack"));
1286 val = val & MAX_STACK;
1289 /* Check the range for 8 bit registers. */
1290 else if (((val * sign_val) > 0xFF) && (i.types[0] == REG)
1291 && (i.maxq20_op[0].reg->rtype == Reg_8W))
1293 as_warn (_
1294 ("Attempt to move 16 bit value into an 8 bit register.Truncating..\n"));
1295 val = val & 0xfe;
1298 else if (((sign_val == -1) || (val > 0xFF)) && (i.types[0] == REG)
1299 && (i.maxq20_op[0].reg->rtype == Reg_8W))
1301 val_pfx = val >> 8;
1302 val = ((val) & 0x00ff);
1303 SET_PFX_ARG (val_pfx);
1304 i.maxq20_op[this_operand].imms = (char) val;
1307 else if ((val <= 0xff) && (i.types[0] == REG)
1308 && (i.maxq20_op[0].reg->rtype == Reg_8W))
1309 i.maxq20_op[this_operand].imms = (char) val;
1312 /* Check for 16 bit registers. */
1313 else if (((sign_val == -1) || val > 0xFE) && i.types[0] == REG
1314 && i.maxq20_op[0].reg->rtype == Reg_16W)
1316 /* Add PFX for any negative value -> 16bit register. */
1317 val_pfx = val >> 8;
1318 val = ((val) & 0x00ff);
1319 SET_PFX_ARG (val_pfx);
1320 i.maxq20_op[this_operand].imms = (char) val;
1323 else if (val < 0xFF && i.types[0] == REG
1324 && i.maxq20_op[0].reg->rtype == Reg_16W)
1326 i.maxq20_op[this_operand].imms = (char) val;
1329 /* All the immediate memory access - no PFX. */
1330 else if (i.types[0] == MEM)
1332 if ((sign_val == -1) || val > 0xFE)
1334 val_pfx = val >> 8;
1335 val = ((val) & 0x00ff);
1336 SET_PFX_ARG (val_pfx);
1337 i.maxq20_op[this_operand].imms = (char) val;
1339 else
1340 i.maxq20_op[this_operand].imms = (char) val;
1343 /* Special handling for immediate jumps like jump nz, #03h etc. */
1344 else if (val < 0xFF && i.types[0] == FLAG)
1345 i.maxq20_op[this_operand].imms = (char) val;
1347 else if ((((sign_val == -1) || val > 0xFE)) && i.types[0] == FLAG)
1349 val_pfx = val >> 8;
1350 val = ((val) & 0x00ff);
1351 SET_PFX_ARG (val_pfx);
1352 i.maxq20_op[this_operand].imms = (char) val;
1354 else
1356 as_bad (_("Invalid immediate move operation"));
1357 return 0;
1360 else
1362 /* All the instruction with operation on ACC: like ADD src, etc. */
1363 if ((sign_val == -1) || val > 0xFE)
1365 val_pfx = val >> 8;
1366 val = ((val) & 0x00ff);
1367 SET_PFX_ARG (val_pfx);
1368 i.maxq20_op[this_operand].imms = (char) val;
1370 else
1371 i.maxq20_op[this_operand].imms = (char) val;
1374 i.imm_operands++;
1375 return 1;
1378 static int
1379 extract_int_val (const char *imm_start)
1381 int k, j, val;
1382 char sign_val;
1383 int temp[4];
1385 k = 0;
1386 j = 0;
1387 val = 0;
1388 sign_val = 0;
1391 if (imm_start[k] == '-' && k == 0)
1392 sign_val = -1;
1394 else if (imm_start[k] == '+' && k == 0)
1395 sign_val = 1;
1397 else if (isdigit (imm_start[k]))
1398 temp[k] = imm_start[k] - '0';
1400 else if (isalpha (imm_start[k]) && (tolower (imm_start[k])) < 'g')
1401 temp[k] = 10 + (int) (tolower (imm_start[k]) - 'a');
1403 else if (tolower (imm_start[k]) == 'h')
1404 break;
1406 else if ((imm_start[k] == '\0') || (imm_start[k] == ']'))
1407 /* imm_start[k]='d'; */
1408 break;
1410 else
1412 as_bad (_("Invalid Character in immediate Value : %c"),
1413 imm_start[k]);
1414 return 0;
1416 k++;
1418 while (imm_start[k] != '\n');
1420 switch (imm_start[k])
1422 case 'h':
1423 for (j = (sign_val ? 1 : 0); j < k; j++)
1424 val += temp[j] * pwr (16, k - j - 1);
1425 break;
1427 default:
1428 for (j = (sign_val ? 1 : 0); j < k; j++)
1430 if (temp[j] > 9)
1432 as_bad (_("Invalid Character in immediate value : %c"),
1433 imm_start[j]);
1434 return 0;
1436 val += temp[j] * pwr (10, k - j - 1);
1440 if (!sign_val)
1441 sign_val = 1;
1443 return val * sign_val;
1446 static char
1447 check_for_parse (const char *line)
1449 int val;
1451 if (*(line + 1) == '[')
1455 line++;
1456 if ((*line == '-') || (*line == '+'))
1457 break;
1459 while (!is_space_char (*line));
1461 if ((*line == '-') || (*line == '+'))
1462 val = extract_int_val (line);
1463 else
1464 val = extract_int_val (line + 1);
1466 INSERT_BUFFER[0] = 0x3E;
1467 INSERT_BUFFER[1] = val;
1469 return 1;
1472 return 0;
1475 static mem_access *
1476 maxq20_mem_access (char *mem_string, char **end_op)
1478 char *s = mem_string;
1479 char *p;
1480 char mem_name_given[MAX_MEM_NAME_SIZE + 1];
1481 mem_access *m;
1483 m = NULL;
1485 /* Skip possible whitespace. */
1486 if (is_space_char (*s))
1487 ++s;
1489 p = mem_name_given;
1490 while ((*p++ = register_chars[(unsigned char) *s]) != '\0')
1492 if (p >= mem_name_given + MAX_MEM_NAME_SIZE)
1493 return (mem_access *) NULL;
1494 s++;
1497 *end_op = s;
1499 m = (mem_access *) hash_find (mem_hash, mem_name_given);
1501 return m;
1504 /* This function checks whether the operand is a variable in the data segment
1505 and if so, it returns its symbol entry from the symbol table. */
1507 static symbolS *
1508 maxq20_data (char *op_string)
1510 symbolS *symbolP;
1511 symbolP = symbol_find (op_string);
1513 if (symbolP != NULL
1514 && S_GET_SEGMENT (symbolP) != now_seg
1515 && S_GET_SEGMENT (symbolP) !=
1516 #ifdef BFD_ASSEMBLER
1517 bfd_und_section_ptr
1518 #else
1519 SEG_UNKNOWN
1520 #endif
1523 int val_pfx;
1525 #ifdef BFD_ASSEMBLER
1526 val_pfx = 0;
1527 #else
1528 val_pfx = (symbolP->sy_value.X_add_number) >> 8;
1529 #endif
1531 /* In case we do not want to always include the prefix instruction and
1532 let the loader handle the job or in case of a 8 bit addressing mode,
1533 we will just check for val_pfx to be equal to zero and then load the
1534 prefix instruction. Otherwise no prefix instruction needs to be
1535 loaded. */
1536 /* The prefix register will have to be loaded automatically as we have
1537 a 16 bit addressing field. */
1538 pfx_for_imm_val (val_pfx);
1539 return symbolP;
1542 return NULL;
1545 static int
1546 maxq20_displacement (char *disp_start, char *disp_end)
1548 expressionS *exp;
1549 segT exp_seg = 0;
1550 char *save_input_line_pointer;
1551 #ifndef LEX_AT
1552 char *gotfree_input_line;
1553 #endif
1555 gotfree_input_line = NULL;
1556 exp = &disp_expressions;
1557 i.maxq20_op[this_operand].disps = exp;
1558 i.disp_operands++;
1559 save_input_line_pointer = input_line_pointer;
1560 input_line_pointer = disp_start;
1562 END_STRING_AND_SAVE (disp_end);
1564 #ifndef LEX_AT
1565 /* gotfree_input_line = lex_got (&i.reloc[this_operand], NULL); if
1566 (gotfree_input_line) input_line_pointer = gotfree_input_line; */
1567 #endif
1568 exp_seg = expression (exp);
1570 SKIP_WHITESPACE ();
1571 if (*input_line_pointer)
1572 as_bad (_("junk `%s' after expression"), input_line_pointer);
1573 #if GCC_ASM_O_HACK
1574 RESTORE_END_STRING (disp_end + 1);
1575 #endif
1576 RESTORE_END_STRING (disp_end);
1577 input_line_pointer = save_input_line_pointer;
1578 #ifndef LEX_AT
1579 if (gotfree_input_line)
1580 free (gotfree_input_line);
1581 #endif
1582 if (exp->X_op == O_absent || exp->X_op == O_big)
1584 /* Missing or bad expr becomes absolute 0. */
1585 as_bad (_("missing or invalid displacement expression `%s' taken as 0"),
1586 disp_start);
1587 exp->X_op = O_constant;
1588 exp->X_add_number = 0;
1589 exp->X_add_symbol = (symbolS *) 0;
1590 exp->X_op_symbol = (symbolS *) 0;
1592 #if (defined (OBJ_AOUT) || defined (OBJ_MAYBE_AOUT))
1594 if (exp->X_op != O_constant
1595 #ifdef BFD_ASSEMBLER
1596 && OUTPUT_FLAVOR == bfd_target_aout_flavour
1597 #endif
1598 && exp_seg != absolute_section
1599 && exp_seg != text_section
1600 && exp_seg != data_section
1601 && exp_seg != bss_section && exp_seg != undefined_section
1602 #ifdef BFD_ASSEMBLER
1603 && !bfd_is_com_section (exp_seg)
1604 #endif
1607 #ifdef BFD_ASSEMBLER
1608 as_bad (_("unimplemented segment %s in operand"), exp_seg->name);
1609 #else
1610 as_bad (_("unimplemented segment type %d in operand"), exp_seg);
1611 #endif
1612 return 0;
1614 #endif
1615 i.maxq20_op[this_operand].disps = exp;
1616 return 1;
1619 /* Parse OPERAND_STRING into the maxq20_insn structure I.
1620 Returns non-zero on error. */
1622 static int
1623 maxq20_operand (char *operand_string)
1625 reg_entry *r = NULL;
1626 reg_bit *rb = NULL;
1627 mem_access *m = NULL;
1628 char *end_op = NULL;
1629 symbolS *sym = NULL;
1630 char *base_string = NULL;
1631 int ii = 0;
1632 /* Start and end of displacement string expression (if found). */
1633 char *displacement_string_start = NULL;
1634 char *displacement_string_end = NULL;
1635 /* This maintains the case sentivness. */
1636 char case_str_op_string[MAX_OPERAND_SIZE + 1];
1637 char str_op_string[MAX_OPERAND_SIZE + 1];
1638 char *org_case_op_string = case_str_op_string;
1639 char *op_string = str_op_string;
1642 memset (op_string, END_OF_INSN, (MAX_OPERAND_SIZE + 1));
1643 memset (org_case_op_string, END_OF_INSN, (MAX_OPERAND_SIZE + 1));
1645 memcpy (op_string, operand_string, strlen (operand_string) + 1);
1646 memcpy (org_case_op_string, operand_string, strlen (operand_string) + 1);
1648 ii = strlen (operand_string) + 1;
1650 if (ii > MAX_OPERAND_SIZE)
1652 as_bad (_("Size of Operand '%s' greater than %d"), op_string,
1653 MAX_OPERAND_SIZE);
1654 return 0;
1657 while (ii)
1659 op_string[ii - 1] = toupper ((char) op_string[ii - 1]);
1660 ii--;
1663 if (is_space_char (*op_string))
1664 ++op_string;
1666 if (isxdigit (operand_string[0]))
1668 /* Now the operands can start with an Integer. */
1669 r = parse_reg_by_index (op_string);
1670 if (r != NULL)
1672 if (is_space_char (*op_string))
1673 ++op_string;
1674 i.types[this_operand] = REG; /* Set the type. */
1675 i.maxq20_op[this_operand].reg = r; /* Set the Register value. */
1676 i.reg_operands++;
1677 return 1;
1680 /* Get the origanal string. */
1681 memcpy (op_string, operand_string, strlen (operand_string) + 1);
1682 ii = strlen (operand_string) + 1;
1684 while (ii)
1686 op_string[ii - 1] = toupper ((char) op_string[ii - 1]);
1687 ii--;
1691 /* Check for flags. */
1692 if (!strcmp (op_string, "Z"))
1694 if (is_space_char (*op_string))
1695 ++op_string;
1697 i.types[this_operand] = FLAG; /* Set the type. */
1698 i.maxq20_op[this_operand].flag = FLAG_Z; /* Set the Register value. */
1700 i.flag_operands++;
1702 return 1;
1705 else if (!strcmp (op_string, "NZ"))
1707 if (is_space_char (*op_string))
1708 ++op_string;
1710 i.types[this_operand] = FLAG; /* Set the type. */
1711 i.maxq20_op[this_operand].flag = FLAG_NZ; /* Set the Register value. */
1712 i.flag_operands++;
1713 return 1;
1716 else if (!strcmp (op_string, "NC"))
1718 if (is_space_char (*op_string))
1719 ++op_string;
1721 i.types[this_operand] = FLAG; /* Set the type. */
1722 i.maxq20_op[this_operand].flag = FLAG_NC; /* Set the Register value. */
1723 i.flag_operands++;
1724 return 1;
1727 else if (!strcmp (op_string, "E"))
1729 if (is_space_char (*op_string))
1730 ++op_string;
1732 i.types[this_operand] = FLAG; /* Set the type. */
1733 i.maxq20_op[this_operand].flag = FLAG_E; /* Set the Register value. */
1735 i.flag_operands++;
1737 return 1;
1740 else if (!strcmp (op_string, "S"))
1742 if (is_space_char (*op_string))
1743 ++op_string;
1745 i.types[this_operand] = FLAG; /* Set the type. */
1746 i.maxq20_op[this_operand].flag = FLAG_S; /* Set the Register value. */
1748 i.flag_operands++;
1750 return 1;
1753 else if (!strcmp (op_string, "C"))
1755 if (is_space_char (*op_string))
1756 ++op_string;
1758 i.types[this_operand] = FLAG; /* Set the type. */
1759 i.maxq20_op[this_operand].flag = FLAG_C; /* Set the Register value. */
1761 i.flag_operands++;
1763 return 1;
1766 else if (!strcmp (op_string, "NE"))
1769 if (is_space_char (*op_string))
1770 ++op_string;
1772 i.types[this_operand] = FLAG; /* Set the type. */
1774 i.maxq20_op[this_operand].flag = FLAG_NE; /* Set the Register value. */
1776 i.flag_operands++;
1778 return 1;
1781 /* CHECK FOR REGISTER BIT */
1782 else if ((rb = parse_register_bit (op_string, &end_op)) != NULL)
1784 op_string = end_op;
1786 if (is_space_char (*op_string))
1787 ++op_string;
1789 i.types[this_operand] = BIT;
1791 i.maxq20_op[this_operand].r_bit = rb;
1793 i.bit_operands++;
1795 return 1;
1798 else if (*op_string == IMMEDIATE_PREFIX) /* FOR IMMEDITE. */
1800 if (is_space_char (*op_string))
1801 ++op_string;
1803 i.types[this_operand] = IMM;
1805 if (!maxq20_immediate (op_string))
1807 as_bad (_("illegal immediate operand '%s'"), op_string);
1808 return 0;
1810 return 1;
1813 else if (*op_string == ABSOLUTE_PREFIX || !strcmp (op_string, "NUL"))
1815 if (is_space_char (*op_string))
1816 ++op_string;
1818 /* For new requiremnt of copiler of for, @(BP,cons). */
1819 if (check_for_parse (op_string))
1821 memset (op_string, '\0', strlen (op_string) + 1);
1822 memcpy (op_string, "@BP[OFFS]\0", 11);
1825 i.types[this_operand] = MEM;
1827 if ((m = maxq20_mem_access (op_string, &end_op)) == NULL)
1829 as_bad (_("Invalid operand for memory access '%s'"), op_string);
1830 return 0;
1832 i.maxq20_op[this_operand].mem = m;
1834 i.mem_operands++;
1836 return 1;
1839 else if ((r = parse_register (op_string, &end_op)) != NULL) /* Check for register. */
1841 op_string = end_op;
1843 if (is_space_char (*op_string))
1844 ++op_string;
1846 i.types[this_operand] = REG; /* Set the type. */
1847 i.maxq20_op[this_operand].reg = r; /* Set the Register value. */
1848 i.reg_operands++;
1849 return 1;
1852 if (this_operand == 1)
1854 /* Changed for orginal case of data refrence on 30 Nov 2003. */
1855 /* The operand can either be a data reference or a symbol reference. */
1856 if ((sym = maxq20_data (org_case_op_string)) != NULL) /* Check for data memory. */
1858 while (is_space_char (*op_string))
1859 ++op_string;
1861 /* Set the type of the operand. */
1862 i.types[this_operand] = DATA;
1864 /* Set the value of the data. */
1865 i.maxq20_op[this_operand].data = sym;
1866 i.data_operands++;
1868 return 1;
1871 else if (is_digit_char (*op_string) || is_identifier_char (*op_string))
1873 /* This is a memory reference of some sort. char *base_string;
1874 Start and end of displacement string expression (if found). char
1875 *displacement_string_start; char *displacement_string_end. */
1876 base_string = org_case_op_string + strlen (org_case_op_string);
1878 --base_string;
1879 if (is_space_char (*base_string))
1880 --base_string;
1882 /* If we only have a displacement, set-up for it to be parsed
1883 later. */
1884 displacement_string_start = org_case_op_string;
1885 displacement_string_end = base_string + 1;
1886 if (displacement_string_start != displacement_string_end)
1888 if (!maxq20_displacement (displacement_string_start,
1889 displacement_string_end))
1891 as_bad (_("illegal displacement operand "));
1892 return 0;
1894 /* A displacement operand found. */
1895 i.types[this_operand] = DISP; /* Set the type. */
1896 return 1;
1901 /* Check for displacement. */
1902 else if (is_digit_char (*op_string) || is_identifier_char (*op_string))
1904 /* This is a memory reference of some sort. char *base_string;
1905 Start and end of displacement string expression (if found). char
1906 *displacement_string_start; char *displacement_string_end; */
1907 base_string = org_case_op_string + strlen (org_case_op_string);
1909 --base_string;
1910 if (is_space_char (*base_string))
1911 --base_string;
1913 /* If we only have a displacement, set-up for it to be parsed later. */
1914 displacement_string_start = org_case_op_string;
1915 displacement_string_end = base_string + 1;
1916 if (displacement_string_start != displacement_string_end)
1918 if (!maxq20_displacement (displacement_string_start,
1919 displacement_string_end))
1920 return 0;
1921 /* A displacement operand found. */
1922 i.types[this_operand] = DISP; /* Set the type. */
1925 return 1;
1928 /* Parse_operand takes as input instruction and operands and Parse operands
1929 and makes entry in the template. */
1931 static char *
1932 parse_operands (char *l, const char *mnemonic)
1934 char *token_start;
1936 /* 1 if operand is pending after ','. */
1937 short int expecting_operand = 0;
1939 /* Non-zero if operand parens not balanced. */
1940 short int paren_not_balanced;
1942 int operand_ok;
1944 /* For Overcoming Warning of unused variable. */
1945 if (mnemonic)
1946 operand_ok = 0;
1948 while (*l != END_OF_INSN)
1950 /* Skip optional white space before operand. */
1951 if (is_space_char (*l))
1952 ++l;
1954 if (!is_operand_char (*l) && *l != END_OF_INSN)
1956 as_bad (_("invalid character %c before operand %d"),
1957 (char) (*l), i.operands + 1);
1958 return NULL;
1960 token_start = l;
1962 paren_not_balanced = 0;
1963 while (paren_not_balanced || *l != ',')
1965 if (*l == END_OF_INSN)
1967 if (paren_not_balanced)
1969 as_bad (_("unbalanced brackets in operand %d."),
1970 i.operands + 1);
1971 return NULL;
1974 break;
1976 else if (!is_operand_char (*l) && !is_space_char (*l))
1978 as_bad (_("invalid character %c in operand %d"),
1979 (char) (*l), i.operands + 1);
1980 return NULL;
1982 if (*l == '[')
1983 ++paren_not_balanced;
1984 if (*l == ']')
1985 --paren_not_balanced;
1986 l++;
1989 if (l != token_start)
1991 /* Yes, we've read in another operand. */
1992 this_operand = i.operands++;
1993 if (i.operands > MAX_OPERANDS)
1995 as_bad (_("spurious operands; (%d operands/instruction max)"),
1996 MAX_OPERANDS);
1997 return NULL;
2000 /* Now parse operand adding info to 'i' as we go along. */
2001 END_STRING_AND_SAVE (l);
2003 operand_ok = maxq20_operand (token_start);
2005 RESTORE_END_STRING (l);
2007 if (!operand_ok)
2008 return NULL;
2010 else
2012 if (expecting_operand)
2014 expecting_operand_after_comma:
2015 as_bad (_("expecting operand after ','; got nothing"));
2016 return NULL;
2020 if (*l == ',')
2022 if (*(++l) == END_OF_INSN)
2023 /* Just skip it, if it's \n complain. */
2024 goto expecting_operand_after_comma;
2026 expecting_operand = 1;
2030 return l;
2033 static int
2034 match_operands (int type, MAX_ARG_TYPE flag_type, MAX_ARG_TYPE arg_type,
2035 int op_num)
2037 switch (type)
2039 case REG:
2040 if ((arg_type & A_REG) == A_REG)
2041 return 1;
2042 break;
2043 case IMM:
2044 if ((arg_type & A_IMM) == A_IMM)
2045 return 1;
2046 break;
2047 case IMMBIT:
2048 if ((arg_type & A_BIT_0) == A_BIT_0 && (i.maxq20_op[op_num].imms == 0))
2049 return 1;
2050 else if ((arg_type & A_BIT_1) == A_BIT_1
2051 && (i.maxq20_op[op_num].imms == 1))
2052 return 1;
2053 break;
2054 case MEM:
2055 if ((arg_type & A_MEM) == A_MEM)
2056 return 1;
2057 break;
2059 case FLAG:
2060 if ((arg_type & flag_type) == flag_type)
2061 return 1;
2063 break;
2065 case BIT:
2066 if ((arg_type & ACC_BIT) == ACC_BIT && !strcmp (i.maxq20_op[op_num].r_bit->reg->reg_name, "ACC"))
2067 return 1;
2068 else if ((arg_type & SRC_BIT) == SRC_BIT && (op_num == 1))
2069 return 1;
2070 else if ((op_num == 0) && (arg_type & DST_BIT) == DST_BIT)
2071 return 1;
2072 break;
2073 case DISP:
2074 if ((arg_type & A_DISP) == A_DISP)
2075 return 1;
2076 case DATA:
2077 if ((arg_type & A_DATA) == A_DATA)
2078 return 1;
2079 case BIT_BUCKET:
2080 if ((arg_type & A_BIT_BUCKET) == A_BIT_BUCKET)
2081 return 1;
2083 return 0;
2086 static int
2087 match_template (void)
2089 /* Points to template once we've found it. */
2090 const MAXQ20_OPCODE_INFO *t;
2091 char inv_oper;
2092 inv_oper = 0;
2094 for (t = current_templates->start; t < current_templates->end; t++)
2096 /* Must have right number of operands. */
2097 if (i.operands != t->op_number)
2098 continue;
2099 else if (!t->op_number)
2100 break;
2102 switch (i.operands)
2104 case 2:
2105 if (!match_operands (i.types[1], i.maxq20_op[1].flag, t->arg[1], 1))
2107 inv_oper = 1;
2108 continue;
2110 case 1:
2111 if (!match_operands (i.types[0], i.maxq20_op[0].flag, t->arg[0], 0))
2113 inv_oper = 2;
2114 continue;
2117 break;
2120 if (t == current_templates->end)
2122 /* We found no match. */
2123 as_bad (_("operand %d is invalid for `%s'"),
2124 inv_oper, current_templates->start->name);
2125 return 0;
2128 /* Copy the template we have found. */
2129 i.op = *t;
2130 return 1;
2133 /* This function filters out the various combinations of operands which are
2134 not allowed for a particular instruction. */
2136 static int
2137 match_filters (void)
2139 /* Now we have at our disposal the instruction i. We will be using the
2140 following fields i.op.name : This is the mnemonic name. i.types[2] :
2141 These are the types of the operands (REG/IMM/DISP/MEM/BIT/FLAG/IMMBIT)
2142 i.maxq20_op[2] : This contains the specific info of the operands. */
2144 /* Our first filter : NO ALU OPERATIONS CAN HAVE THE ACTIVE ACCUMULATOR AS
2145 SOURCE. */
2146 if (!strcmp (i.op.name, "AND") || !strcmp (i.op.name, "OR")
2147 || !strcmp (i.op.name, "XOR") || !strcmp (i.op.name, "ADD")
2148 || !strcmp (i.op.name, "ADDC") || !strcmp (i.op.name, "SUB")
2149 || !strcmp (i.op.name, "SUBB"))
2151 if (i.types[0] == REG)
2153 if (i.maxq20_op[0].reg->Mod_name == 0xa)
2155 as_bad (_
2156 ("The Accumulator cannot be used as a source in ALU instructions\n"));
2157 return 0;
2162 if (!strcmp (i.op.name, "MOVE") && (i.types[0] == MEM || i.types[1] == MEM)
2163 && i.operands == 2)
2165 mem_access_syntax *mem_op = NULL;
2167 if (i.types[0] == MEM)
2169 mem_op =
2170 (mem_access_syntax *) hash_find (mem_syntax_hash,
2171 i.maxq20_op[0].mem->name);
2172 if ((mem_op->type == SRC) && mem_op)
2174 as_bad (_("'%s' operand cant be used as destination in %s"),
2175 mem_op->name, i.op.name);
2176 return 0;
2178 else if ((mem_op->invalid_op != NULL) && (i.types[1] == MEM)
2179 && mem_op)
2181 int k = 0;
2183 for (k = 0; k < 5 || !mem_op->invalid_op[k]; k++)
2185 if (mem_op->invalid_op[k] != NULL)
2186 if (!strcmp
2187 (mem_op->invalid_op[k], i.maxq20_op[1].mem->name))
2189 as_bad (_
2190 ("Invalid Instruction '%s' operand cant be used with %s"),
2191 mem_op->name, i.maxq20_op[1].mem->name);
2192 return 0;
2198 if (i.types[1] == MEM)
2200 mem_op = NULL;
2201 mem_op =
2202 (mem_access_syntax *) hash_find (mem_syntax_hash,
2203 i.maxq20_op[1].mem->name);
2204 if (mem_op->type == DST && mem_op)
2206 as_bad (_("'%s' operand cant be used as source in %s"),
2207 mem_op->name, i.op.name);
2208 return 0;
2210 else if (mem_op->invalid_op != NULL && i.types[0] == MEM && mem_op)
2212 int k = 0;
2214 for (k = 0; k < 5 || !mem_op->invalid_op[k]; k++)
2216 if (mem_op->invalid_op[k] != NULL)
2217 if (!strcmp
2218 (mem_op->invalid_op[k], i.maxq20_op[0].mem->name))
2220 as_bad (_
2221 ("Invalid Instruction '%s' operand cant be used with %s"),
2222 mem_op->name, i.maxq20_op[0].mem->name);
2223 return 0;
2227 else if (i.types[0] == REG
2228 && !strcmp (i.maxq20_op[0].reg->reg_name, "OFFS")
2229 && mem_op)
2231 if (!strcmp (mem_op->name, "@BP[OFFS--]")
2232 || !strcmp (mem_op->name, "@BP[OFFS++]"))
2234 as_bad (_
2235 ("Invalid Instruction '%s' operand cant be used with %s"),
2236 mem_op->name, i.maxq20_op[0].mem->name);
2237 return 0;
2243 /* Added for SRC and DST in one operand instructioni i.e OR @--DP[1] added
2244 on 10-March-2004. */
2245 if ((i.types[0] == MEM) && (i.operands == 1)
2246 && !(!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI")))
2248 mem_access_syntax *mem_op = NULL;
2250 if (i.types[0] == MEM)
2252 mem_op =
2253 (mem_access_syntax *) hash_find (mem_syntax_hash,
2254 i.maxq20_op[0].mem->name);
2255 if (mem_op->type == DST && mem_op)
2257 as_bad (_("'%s' operand cant be used as source in %s"),
2258 mem_op->name, i.op.name);
2259 return 0;
2264 if (i.operands == 2 && i.types[0] == IMM)
2266 as_bad (_("'%s' instruction cant have first operand as Immediate vale"),
2267 i.op.name);
2268 return 0;
2271 /* Our second filter : SP or @SP-- cannot be used with PUSH or POP */
2272 if (!strcmp (i.op.name, "PUSH") || !strcmp (i.op.name, "POP")
2273 || !strcmp (i.op.name, "POPI"))
2275 if (i.types[0] == REG)
2277 if (!strcmp (i.maxq20_op[0].reg->reg_name, "SP"))
2279 as_bad (_("SP cannot be used with %s\n"), i.op.name);
2280 return 0;
2283 else if (i.types[0] == MEM
2284 && !strcmp (i.maxq20_op[0].mem->name, "@SP--"))
2286 as_bad (_("@SP-- cannot be used with PUSH\n"));
2287 return 0;
2291 /* This filter checks that two memory references using DP's cannot be used
2292 together in an instruction */
2293 if (!strcmp (i.op.name, "MOVE") && i.mem_operands == 2)
2295 if (strlen (i.maxq20_op[0].mem->name) != 6 ||
2296 strcmp (i.maxq20_op[0].mem->name, i.maxq20_op[1].mem->name))
2298 if (!strncmp (i.maxq20_op[0].mem->name, "@DP", 3)
2299 && !strncmp (i.maxq20_op[1].mem->name, "@DP", 3))
2301 as_bad (_
2302 ("Operands either contradictory or use the data bus in read/write state together"));
2303 return 0;
2306 if (!strncmp (i.maxq20_op[0].mem->name, "@SP", 3)
2307 && !strncmp (i.maxq20_op[1].mem->name, "@SP", 3))
2309 as_bad (_
2310 ("Operands either contradictory or use the data bus in read/write state together"));
2311 return 0;
2314 if ((i.maxq20_op[1].mem != NULL)
2315 && !strncmp (i.maxq20_op[1].mem->name, "NUL", 3))
2317 as_bad (_("MOVE Cant Use NUL as SRC"));
2318 return 0;
2322 /* This filter checks that contradictory movement between DP register and
2323 Memory access using DP followed by increment or decrement. */
2325 if (!strcmp (i.op.name, "MOVE") && i.mem_operands == 1
2326 && i.reg_operands == 1)
2328 int memnum, regnum;
2330 memnum = (i.types[0] == MEM) ? 0 : 1;
2331 regnum = (memnum == 0) ? 1 : 0;
2332 if (!strncmp (i.maxq20_op[regnum].reg->reg_name, "DP", 2) &&
2333 !strncmp ((i.maxq20_op[memnum].mem->name) + 1,
2334 i.maxq20_op[regnum].reg->reg_name, 5)
2335 && strcmp ((i.maxq20_op[memnum].mem->name) + 1,
2336 i.maxq20_op[regnum].reg->reg_name))
2338 as_bad (_
2339 ("Contradictory movement between DP register and memory access using DP"));
2340 return 0;
2342 else if (!strcmp (i.maxq20_op[regnum].reg->reg_name, "SP") &&
2343 !strncmp ((i.maxq20_op[memnum].mem->name) + 1,
2344 i.maxq20_op[regnum].reg->reg_name, 2))
2346 as_bad (_
2347 ("SP and @SP-- cannot be used together in a move instruction"));
2348 return 0;
2352 /* This filter restricts the instructions containing source and destination
2353 bits to only CTRL module of the serial registers. Peripheral registers
2354 yet to be defined. */
2356 if (i.bit_operands == 1 && i.operands == 2)
2358 int bitnum = (i.types[0] == BIT) ? 0 : 1;
2360 if (strcmp (i.maxq20_op[bitnum].r_bit->reg->reg_name, "ACC"))
2362 if (i.maxq20_op[bitnum].r_bit->reg->Mod_name >= 0x7 &&
2363 i.maxq20_op[bitnum].r_bit->reg->Mod_name != CTRL)
2365 as_bad (_
2366 ("Only Module 8 system registers allowed in this operation"));
2367 return 0;
2372 /* This filter is for checking the register bits. */
2373 if (i.bit_operands == 1 || i.operands == 2)
2375 int bitnum = 0, size = 0;
2377 bitnum = (i.types[0] == BIT) ? 0 : 1;
2378 if (i.bit_operands == 1)
2380 switch (i.maxq20_op[bitnum].r_bit->reg->rtype)
2382 case Reg_8W:
2383 size = 7; /* 8 bit register, both read and write. */
2384 break;
2385 case Reg_16W:
2386 size = 15;
2387 break;
2388 case Reg_8R:
2389 size = 7;
2390 if (bitnum == 0)
2392 as_fatal (_("Read only Register used as destination"));
2393 return 0;
2395 break;
2397 case Reg_16R:
2398 size = 15;
2399 if (bitnum == 0)
2401 as_fatal (_("Read only Register used as destination"));
2402 return 0;
2404 break;
2407 if (size < (i.maxq20_op[bitnum].r_bit)->bit)
2409 as_bad (_("Bit No '%d'exceeds register size in this operation"),
2410 (i.maxq20_op[bitnum].r_bit)->bit);
2411 return 0;
2415 if (i.bit_operands == 2)
2417 switch ((i.maxq20_op[0].r_bit)->reg->rtype)
2419 case Reg_8W:
2420 size = 7; /* 8 bit register, both read and write. */
2421 break;
2422 case Reg_16W:
2423 size = 15;
2424 break;
2425 case Reg_8R:
2426 case Reg_16R:
2427 as_fatal (_("Read only Register used as destination"));
2428 return 0;
2431 if (size < (i.maxq20_op[0].r_bit)->bit)
2433 as_bad (_
2434 ("Bit No '%d' exceeds register size in this operation"),
2435 (i.maxq20_op[0].r_bit)->bit);
2436 return 0;
2439 size = 0;
2440 switch ((i.maxq20_op[1].r_bit)->reg->rtype)
2442 case Reg_8R:
2443 case Reg_8W:
2444 size = 7; /* 8 bit register, both read and write. */
2445 break;
2446 case Reg_16R:
2447 case Reg_16W:
2448 size = 15;
2449 break;
2452 if (size < (i.maxq20_op[1].r_bit)->bit)
2454 as_bad (_
2455 ("Bit No '%d' exceeds register size in this operation"),
2456 (i.maxq20_op[1].r_bit)->bit);
2457 return 0;
2462 /* No branch operations should occur into the data memory. Hence any memory
2463 references have to be filtered out when used with instructions like
2464 jump, djnz[] and call. */
2466 if (!strcmp (i.op.name, "JUMP") || !strcmp (i.op.name, "CALL")
2467 || !strncmp (i.op.name, "DJNZ", 4))
2469 if (i.mem_operands)
2470 as_warn (_
2471 ("Memory References cannot be used with branching operations\n"));
2474 if (!strcmp (i.op.name, "DJNZ"))
2476 if (!
2477 (strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]")
2478 || strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]")))
2480 as_bad (_("DJNZ uses only LC[n] register \n"));
2481 return 0;
2485 /* No destination register used should be read only! */
2486 if ((i.operands == 2 && i.types[0] == REG) || !strcmp (i.op.name, "POP")
2487 || !strcmp (i.op.name, "POPI"))
2488 { /* The destination is a register */
2489 int regnum = 0;
2491 if (!strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
2493 regnum = 0;
2495 if (i.types[regnum] == MEM)
2497 mem_access_syntax *mem_op = NULL;
2499 mem_op =
2500 (mem_access_syntax *) hash_find (mem_syntax_hash,
2501 i.maxq20_op[regnum].mem->
2502 name);
2503 if (mem_op->type == SRC && mem_op)
2505 as_bad (_
2506 ("'%s' operand cant be used as destination in %s"),
2507 mem_op->name, i.op.name);
2508 return 0;
2513 if (i.maxq20_op[regnum].reg->rtype == Reg_8R
2514 || i.maxq20_op[regnum].reg->rtype == Reg_16R)
2516 as_bad (_("Read only register used for writing purposes '%s'"),
2517 i.maxq20_op[regnum].reg->reg_name);
2518 return 0;
2522 /* While moving the address of a data in the data section, the destination
2523 should be either data pointers only. */
2524 if ((i.data_operands) && (i.operands == 2))
2526 if ((i.types[0] != REG) && (i.types[0] != MEM))
2528 as_bad (_("Invalid destination for this kind of source."));
2529 return 0;
2532 if (i.types[0] == REG && i.maxq20_op[0].reg->rtype == Reg_8W)
2534 as_bad (_
2535 ("Invalid register as destination for this kind of source.Only data pointers can be used."));
2536 return 0;
2539 return 1;
2542 static int
2543 decode_insn (void)
2545 /* Check for the format Bit if defined. */
2546 if (i.op.format == 0 || i.op.format == 1)
2547 i.instr[0] = i.op.format << 7;
2548 else
2550 /* Format bit not defined. We will have to be find it out ourselves. */
2551 if (i.imm_operands == 1 || i.data_operands == 1 || i.disp_operands == 1)
2552 i.op.format = 0;
2553 else
2554 i.op.format = 1;
2555 i.instr[0] = i.op.format << 7;
2558 /* Now for the destination register. */
2560 /* If destination register is already defined . The conditions are the
2561 following: (1) The second entry in the destination array should be 0 (2)
2562 If there are two operands then the first entry should not be a register,
2563 memory or a register bit (3) If there are less than two operands and the
2564 it is not a pop operation (4) The second argument is the carry
2565 flag(applicable to move Acc.<b>,C. */
2566 if (i.op.dst[1] == 0
2568 ((i.types[0] != REG && i.types[0] != MEM && i.types[0] != BIT
2569 && i.operands == 2) || (i.operands < 2 && strcmp (i.op.name, "POP")
2570 && strcmp (i.op.name, "POPI"))
2571 || (i.op.arg[1] == FLAG_C)))
2573 i.op.dst[0] &= 0x7f;
2574 i.instr[0] |= i.op.dst[0];
2576 else if (i.op.dst[1] == 0 && !strcmp (i.op.name, "DJNZ")
2578 (((i.types[0] == REG)
2579 && (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]")
2580 || !strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]")))))
2582 i.op.dst[0] &= 0x7f;
2583 if (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[0]"))
2584 i.instr[0] |= 0x4D;
2586 if (!strcmp (i.maxq20_op[0].reg->reg_name, "LC[1]"))
2587 i.instr[0] |= 0x5D;
2589 else
2591 unsigned char temp;
2593 /* Target register will have to be specified. */
2594 if (i.types[0] == REG
2595 && (i.op.dst[0] == REG || i.op.dst[0] == (REG | MEM)))
2597 temp = (i.maxq20_op[0].reg)->opcode;
2598 temp &= 0x7f;
2599 i.instr[0] |= temp;
2601 else if (i.types[0] == MEM && (i.op.dst[0] == (REG | MEM)))
2603 temp = (i.maxq20_op[0].mem)->opcode;
2604 temp &= 0x7f;
2605 i.instr[0] |= temp;
2607 else if (i.types[0] == BIT && (i.op.dst[0] == REG))
2609 temp = (i.maxq20_op[0].r_bit)->reg->opcode;
2610 temp &= 0x7f;
2611 i.instr[0] |= temp;
2613 else if (i.types[1] == BIT && (i.op.dst[0] == BIT))
2615 temp = (i.maxq20_op[1].r_bit)->bit;
2616 temp = temp << 4;
2617 temp |= i.op.dst[1];
2618 temp &= 0x7f;
2619 i.instr[0] |= temp;
2621 else
2623 as_bad (_("Invalid Instruction"));
2624 return 0;
2628 /* Now for the source register. */
2630 /* If Source register is already known. The following conditions are
2631 checked: (1) There are no operands (2) If there is only one operand and
2632 it is a flag (3) If the operation is MOVE C,#0/#1 (4) If it is a POP
2633 operation. */
2635 if (i.operands == 0 || (i.operands == 1 && i.types[0] == FLAG)
2636 || (i.types[0] == FLAG && i.types[1] == IMMBIT)
2637 || !strcmp (i.op.name, "POP") || !strcmp (i.op.name, "POPI"))
2638 i.instr[1] = i.op.src[0];
2640 else if (i.imm_operands == 1 && ((i.op.src[0] & IMM) == IMM))
2641 i.instr[1] = i.maxq20_op[this_operand].imms;
2643 else if (i.types[this_operand] == REG && ((i.op.src[0] & REG) == REG))
2644 i.instr[1] = (char) ((i.maxq20_op[this_operand].reg)->opcode);
2646 else if (i.types[this_operand] == BIT && ((i.op.src[0] & REG) == REG))
2647 i.instr[1] = (char) (i.maxq20_op[this_operand].r_bit->reg->opcode);
2649 else if (i.types[this_operand] == MEM && ((i.op.src[0] & MEM) == MEM))
2650 i.instr[1] = (char) ((i.maxq20_op[this_operand].mem)->opcode);
2652 else if (i.types[this_operand] == DATA && ((i.op.src[0] & DATA) == DATA))
2653 /* This will copy only the lower order bytes into the instruction. The
2654 higher order bytes have already been copied into the prefix register. */
2655 i.instr[1] = 0;
2657 /* Decoding the source in the case when the second array entry is not 0.
2658 This means that the source register has been divided into two nibbles. */
2660 else if (i.op.src[1] != 0)
2662 /* If the first operand is a accumulator bit then
2663 the first 4 bits will be filled with the bit number. */
2664 if (i.types[0] == BIT && ((i.op.src[0] & BIT) == BIT))
2666 unsigned char temp = (i.maxq20_op[0].r_bit)->bit;
2668 temp = temp << 4;
2669 temp |= i.op.src[1];
2670 i.instr[1] = temp;
2672 /* In case of MOVE dst.<b>,#1 The first nibble in the source register
2673 has to start with a zero. This is called a ZEROBIT */
2674 else if (i.types[0] == BIT && ((i.op.src[0] & ZEROBIT) == ZEROBIT))
2676 char temp = (i.maxq20_op[0].r_bit)->bit;
2678 temp = temp << 4;
2679 temp |= i.op.src[1];
2680 temp &= 0x7f;
2681 i.instr[1] = temp;
2683 /* Similarly for a ONEBIT */
2684 else if (i.types[0] == BIT && ((i.op.src[0] & ONEBIT) == ONEBIT))
2686 char temp = (i.maxq20_op[0].r_bit)->bit;
2688 temp = temp << 4;
2689 temp |= i.op.src[1];
2690 temp |= 0x80;
2691 i.instr[1] = temp;
2693 /* In case the second operand is a register bit (MOVE C,Acc.<b> or MOVE
2694 C,src.<b> */
2695 else if (i.types[1] == BIT)
2697 if (i.op.src[1] == 0 && i.op.src[1] == REG)
2698 i.instr[1] = (i.maxq20_op[1].r_bit)->reg->opcode;
2700 else if (i.op.src[0] == BIT && i.op.src)
2702 char temp = (i.maxq20_op[1].r_bit)->bit;
2704 temp = temp << 4;
2705 temp |= i.op.src[1];
2706 i.instr[1] = temp;
2709 else
2711 as_bad (_("Invalid Instruction"));
2712 return 0;
2715 return 1;
2718 /* This is a function for outputting displacement operands. */
2720 static void
2721 output_disp (fragS *insn_start_frag, offsetT insn_start_off)
2723 char *p;
2724 relax_substateT subtype;
2725 symbolS *sym;
2726 offsetT off;
2727 int diff;
2729 diff = 0;
2730 insn_start_frag = frag_now;
2731 insn_start_off = frag_now_fix ();
2733 switch (i.Instr_Prefix)
2735 case LONG_PREFIX:
2736 subtype = EXPLICT_LONG_PREFIX;
2737 break;
2738 case SHORT_PREFIX:
2739 subtype = SHORT_PREFIX;
2740 break;
2741 default:
2742 subtype = NO_PREFIX;
2743 break;
2746 /* Its a symbol. Here we end the frag and start the relaxation. Now in our
2747 case there is no need for relaxation. But we do need support for a
2748 prefix operator. Hence we will check whethere is room for 4 bytes ( 2
2749 for prefix + 2 for the current instruction ) Hence if at a particular
2750 time we find out whether the prefix operator is reqd , we shift the
2751 current instruction two places ahead and insert the prefix instruction. */
2752 frag_grow (2 + 2);
2753 p = frag_more (2);
2755 sym = i.maxq20_op[this_operand].disps->X_add_symbol;
2756 off = i.maxq20_op[this_operand].disps->X_add_number;
2758 if (i.maxq20_op[this_operand].disps->X_add_symbol != NULL && sym && frag_now
2759 && (subtype != EXPLICT_LONG_PREFIX))
2761 /* If in the same frag. */
2762 if (frag_now == symbol_get_frag (sym))
2764 diff =
2765 ((((expressionS *) symbol_get_value_expression (sym))->
2766 X_add_number) - insn_start_off);
2768 /* PC points to the next instruction. */
2769 diff = (diff / MAXQ_OCTETS_PER_BYTE) - 1;
2771 if (diff >= -128 && diff <= 127)
2773 i.instr[1] = (char) diff;
2775 /* This will be overwritten later when the symbol is resolved. */
2776 *p = i.instr[1];
2777 *(p + 1) = i.instr[0];
2779 /* No Need to create a FIXUP. */
2780 return;
2785 /* This will be overwritten later when the symbol is resolved. */
2786 *p = i.instr[1];
2787 *(p + 1) = i.instr[0];
2789 if (i.maxq20_op[this_operand].disps->X_op != O_constant
2790 && i.maxq20_op[this_operand].disps->X_op != O_symbol)
2792 /* Handle complex expressions. */
2793 sym = make_expr_symbol (i.maxq20_op[this_operand].disps);
2794 off = 0;
2797 /* Vineet : This has been added for md_estimate_size_before_relax to
2798 estimate the correct size. */
2799 if (subtype != SHORT_PREFIX)
2800 i.reloc[this_operand] = LONG_PREFIX;
2802 frag_var (rs_machine_dependent, 2, i.reloc[this_operand], subtype, sym, off, p);
2805 /* This is a function for outputting displacement operands. */
2807 static void
2808 output_data (fragS *insn_start_frag, offsetT insn_start_off)
2810 char *p;
2811 relax_substateT subtype;
2812 symbolS *sym;
2813 offsetT off;
2814 int diff;
2816 diff = 0;
2817 off = 0;
2818 insn_start_frag = frag_now;
2819 insn_start_off = frag_now_fix ();
2821 subtype = EXPLICT_LONG_PREFIX;
2823 frag_grow (2 + 2);
2824 p = frag_more (2);
2826 sym = i.maxq20_op[this_operand].data;
2827 off = 0;
2829 /* This will be overwritten later when the symbol is resolved. */
2830 *p = i.instr[1];
2831 *(p + 1) = i.instr[0];
2833 if (i.maxq20_op[this_operand].disps->X_op != O_constant
2834 && i.maxq20_op[this_operand].disps->X_op != O_symbol)
2835 /* Handle complex expressions. */
2836 /* Because data is already in terms of symbol so no
2837 need to convert it from expression to symbol. */
2838 off = 0;
2840 frag_var (rs_machine_dependent, 2, i.reloc[this_operand], subtype, sym, off, p);
2843 static void
2844 output_insn (void)
2846 fragS *insn_start_frag;
2847 offsetT insn_start_off;
2848 char *p;
2850 /* Tie dwarf2 debug info to the address at the start of the insn. We can't
2851 do this after the insn has been output as the current frag may have been
2852 closed off. eg. by frag_var. */
2853 dwarf2_emit_insn (0);
2855 /* To ALign the text section on word. */
2857 frag_align (1, 0, 1);
2859 /* We initialise the frags for this particular instruction. */
2860 insn_start_frag = frag_now;
2861 insn_start_off = frag_now_fix ();
2863 /* If there are displacement operators(unresolved) present, then handle
2864 them separately. */
2865 if (i.disp_operands)
2867 output_disp (insn_start_frag, insn_start_off);
2868 return;
2871 if (i.data_operands)
2873 output_data (insn_start_frag, insn_start_off);
2874 return;
2877 /* Check whether the INSERT_BUFFER has to be written. */
2878 if (strcmp (INSERT_BUFFER, ""))
2880 p = frag_more (2);
2882 *p++ = INSERT_BUFFER[1];
2883 *p = INSERT_BUFFER[0];
2886 /* Check whether the prefix instruction has to be written. */
2887 if (strcmp (PFX_INSN, ""))
2889 p = frag_more (2);
2891 *p++ = PFX_INSN[1];
2892 *p = PFX_INSN[0];
2895 p = frag_more (2);
2896 /* For Little endian. */
2897 *p++ = i.instr[1];
2898 *p = i.instr[0];
2901 static void
2902 make_new_reg_table (void)
2904 unsigned long size_pm = sizeof (peripheral_reg_table);
2905 num_of_reg = ARRAY_SIZE (peripheral_reg_table);
2907 new_reg_table = xmalloc (size_pm);
2908 if (new_reg_table == NULL)
2909 as_bad (_("Cannot allocate memory"));
2911 memcpy (new_reg_table, peripheral_reg_table, size_pm);
2914 /* pmmain performs the initilizations for the pheripheral modules. */
2916 static void
2917 pmmain (void)
2919 make_new_reg_table ();
2920 return;
2923 void
2924 md_begin (void)
2926 const char *hash_err = NULL;
2927 int c = 0;
2928 char *p;
2929 const MAXQ20_OPCODE_INFO *optab;
2930 MAXQ20_OPCODES *core_optab; /* For opcodes of the same name. This will
2931 be inserted into the hash table. */
2932 struct reg *reg_tab;
2933 struct mem_access_syntax const *memsyntab;
2934 struct mem_access *memtab;
2935 struct bit_name *bittab;
2937 /* Initilize pherioipheral modules. */
2938 pmmain ();
2940 /* Initialise the opcode hash table. */
2941 op_hash = hash_new ();
2943 optab = op_table; /* Initialise it to the first entry of the
2944 maxq20 operand table. */
2946 /* Setup for loop. */
2947 core_optab = xmalloc (sizeof (MAXQ20_OPCODES));
2948 core_optab->start = optab;
2950 while (1)
2952 ++optab;
2953 if (optab->name == NULL || strcmp (optab->name, (optab - 1)->name) != 0)
2955 /* different name --> ship out current template list; add to hash
2956 table; & begin anew. */
2958 core_optab->end = optab;
2959 #ifdef MAXQ10S
2960 if (max_version == bfd_mach_maxq10)
2962 if (((optab - 1)->arch == MAXQ10) || ((optab - 1)->arch == MAX))
2964 hash_err = hash_insert (op_hash,
2965 (optab - 1)->name,
2966 (PTR) core_optab);
2969 else if (max_version == bfd_mach_maxq20)
2971 if (((optab - 1)->arch == MAXQ20) || ((optab - 1)->arch == MAX))
2973 #endif
2974 hash_err = hash_insert (op_hash,
2975 (optab - 1)->name,
2976 (PTR) core_optab);
2977 #if MAXQ10S
2980 else
2981 as_fatal (_("Internal Error: Illegal Architecure specified"));
2982 #endif
2983 if (hash_err)
2984 as_fatal (_("Internal Error: Can't hash %s: %s"),
2985 (optab - 1)->name, hash_err);
2987 if (optab->name == NULL)
2988 break;
2989 core_optab = xmalloc (sizeof (MAXQ20_OPCODES));
2990 core_optab->start = optab;
2994 /* Initialise a new register table. */
2995 reg_hash = hash_new ();
2997 for (reg_tab = system_reg_table;
2998 reg_tab < (system_reg_table + ARRAY_SIZE (system_reg_table));
2999 reg_tab++)
3001 #if MAXQ10S
3002 switch (max_version)
3004 case bfd_mach_maxq10:
3005 if ((reg_tab->arch == MAXQ10) || (reg_tab->arch == MAX))
3006 hash_err = hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
3007 break;
3009 case bfd_mach_maxq20:
3010 if ((reg_tab->arch == MAXQ20) || (reg_tab->arch == MAX))
3012 #endif
3013 hash_err =
3014 hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
3015 #if MAXQ10S
3017 break;
3018 default:
3019 as_fatal (_("Invalid architecture type"));
3021 #endif
3023 if (hash_err)
3024 as_fatal (_("Internal Error : Can't Hash %s : %s"),
3025 reg_tab->reg_name, hash_err);
3028 /* Pheripheral Registers Entry. */
3029 for (reg_tab = new_reg_table;
3030 reg_tab < (new_reg_table + num_of_reg - 1); reg_tab++)
3032 hash_err = hash_insert (reg_hash, reg_tab->reg_name, (PTR) reg_tab);
3034 if (hash_err)
3035 as_fatal (_("Internal Error : Can't Hash %s : %s"),
3036 reg_tab->reg_name, hash_err);
3039 /* Initialise a new memory operand table. */
3040 mem_hash = hash_new ();
3042 for (memtab = mem_table;
3043 memtab < mem_table + ARRAY_SIZE (mem_table);
3044 memtab++)
3046 hash_err = hash_insert (mem_hash, memtab->name, (PTR) memtab);
3047 if (hash_err)
3048 as_fatal (_("Internal Error : Can't Hash %s : %s"),
3049 memtab->name, hash_err);
3052 bit_hash = hash_new ();
3054 for (bittab = bit_table;
3055 bittab < bit_table + ARRAY_SIZE (bit_table);
3056 bittab++)
3058 hash_err = hash_insert (bit_hash, bittab->name, (PTR) bittab);
3059 if (hash_err)
3060 as_fatal (_("Internal Error : Can't Hash %s : %s"),
3061 bittab->name, hash_err);
3064 mem_syntax_hash = hash_new ();
3066 for (memsyntab = mem_access_syntax_table;
3067 memsyntab < mem_access_syntax_table + ARRAY_SIZE (mem_access_syntax_table);
3068 memsyntab++)
3070 hash_err =
3071 hash_insert (mem_syntax_hash, memsyntab->name, (PTR) memsyntab);
3072 if (hash_err)
3073 as_fatal (_("Internal Error : Can't Hash %s : %s"),
3074 memsyntab->name, hash_err);
3077 /* Initialise the lexical tables,mnemonic chars,operand chars. */
3078 for (c = 0; c < 256; c++)
3080 if (ISDIGIT (c))
3082 digit_chars[c] = c;
3083 mnemonic_chars[c] = c;
3084 operand_chars[c] = c;
3085 register_chars[c] = c;
3087 else if (ISLOWER (c))
3089 mnemonic_chars[c] = c;
3090 operand_chars[c] = c;
3091 register_chars[c] = c;
3093 else if (ISUPPER (c))
3095 mnemonic_chars[c] = TOLOWER (c);
3096 register_chars[c] = c;
3097 operand_chars[c] = c;
3100 if (ISALPHA (c) || ISDIGIT (c))
3102 identifier_chars[c] = c;
3104 else if (c > 128)
3106 identifier_chars[c] = c;
3107 operand_chars[c] = c;
3111 /* All the special characters. */
3112 register_chars['@'] = '@';
3113 register_chars['+'] = '+';
3114 register_chars['-'] = '-';
3115 digit_chars['-'] = '-';
3116 identifier_chars['_'] = '_';
3117 identifier_chars['.'] = '.';
3118 register_chars['['] = '[';
3119 register_chars[']'] = ']';
3120 operand_chars['_'] = '_';
3121 operand_chars['#'] = '#';
3122 mnemonic_chars['['] = '[';
3123 mnemonic_chars[']'] = ']';
3125 for (p = operand_special_chars; *p != '\0'; p++)
3126 operand_chars[(unsigned char) *p] = (unsigned char) *p;
3128 /* Set the maxq arch type. */
3129 maxq_target (max_version);
3132 /* md_assemble - Parse Instr - Seprate menmonics and operands - lookup the
3133 menmunonic in the operand table - Parse operands and populate the
3134 structure/template - Match the operand with opcode and its validity -
3135 Output Instr. */
3137 void
3138 md_assemble (char *line)
3140 int j;
3142 char mnemonic[MAX_MNEM_SIZE];
3143 char temp4prev[256];
3144 static char prev_insn[256];
3146 /* Initialize globals. */
3147 memset (&i, '\0', sizeof (i));
3148 for (j = 0; j < MAX_OPERANDS; j++)
3149 i.reloc[j] = NO_RELOC;
3151 i.prefix = -1;
3152 PFX_INSN[0] = 0;
3153 PFX_INSN[1] = 0;
3154 INSERT_BUFFER[0] = 0;
3155 INSERT_BUFFER[1] = 0;
3157 memcpy (temp4prev, line, strlen (line) + 1);
3159 save_stack_p = save_stack;
3161 line = (char *) parse_insn (line, mnemonic);
3162 if (line == NULL)
3163 return;
3165 line = (char *) parse_operands (line, mnemonic);
3166 if (line == NULL)
3167 return;
3169 /* Next, we find a template that matches the given insn, making sure the
3170 overlap of the given operands types is consistent with the template
3171 operand types. */
3172 if (!match_template ())
3173 return;
3175 /* In the MAXQ20, there are certain register combinations, and other
3176 restrictions which are not allowed. We will try to resolve these right
3177 now. */
3178 if (!match_filters ())
3179 return;
3181 /* Check for the approprate PFX register. */
3182 set_prefix ();
3183 pfx_for_imm_val (0);
3185 if (!decode_insn ()) /* decode insn. */
3186 need_pass_2 = 1;
3188 /* Check for Exlipct PFX instruction. */
3189 if (PFX_INSN[0] && (strstr (prev_insn, "PFX") || strstr (prev_insn, "pfx")))
3190 as_warn (_("Ineffective insntruction %s \n"), prev_insn);
3192 memcpy (prev_insn, temp4prev, strlen (temp4prev) + 1);
3194 /* We are ready to output the insn. */
3195 output_insn ();