Add copyright headers to the *.c/*.h files in the main directory
[platform/upstream/nasm.git] / parser.c
1 /* ----------------------------------------------------------------------- *
2  *   
3  *   Copyright 1996-2009 The NASM Authors - All Rights Reserved
4  *   See the file AUTHORS included with the NASM distribution for
5  *   the specific copyright holders.
6  *
7  *   This program is free software; you can redistribute it and/or modify
8  *   it under the terms of the GNU Lesser General Public License as
9  *   published by the Free Software Foundation, Inc.,
10  *   51 Franklin St, Fifth Floor, Boston MA 02110-1301, USA; version 2.1,
11  *   or, at your option, any later version, incorporated herein by
12  *   reference.
13  *
14  *   Patches submitted to this file are required to be dual licensed
15  *   under the LGPL 2.1+ and the 2-clause BSD license:
16  *
17  *   Copyright 1996-2009 the NASM Authors - All rights reserved.
18  *
19  *   Redistribution and use in source and binary forms, with or without
20  *   modification, are permitted provided that the following
21  *   conditions are met:
22  *
23  *   * Redistributions of source code must retain the above copyright
24  *     notice, this list of conditions and the following disclaimer.
25  *   * Redistributions in binary form must reproduce the above
26  *     copyright notice, this list of conditions and the following
27  *     disclaimer in the documentation and/or other materials provided
28  *     with the distribution.
29  *     
30  *     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND
31  *     CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
32  *     INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
33  *     MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
34  *     DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR
35  *     CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
36  *     SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
37  *     NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
38  *     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
39  *     HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
40  *     CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
41  *     OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
42  *     EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
43  *
44  * ----------------------------------------------------------------------- */
45
46 /*
47  * parser.c   source line parser for the Netwide Assembler
48  */
49
50 #include "compiler.h"
51
52 #include <stdio.h>
53 #include <stdlib.h>
54 #include <stddef.h>
55 #include <string.h>
56 #include <ctype.h>
57 #include <inttypes.h>
58
59 #include "nasm.h"
60 #include "insns.h"
61 #include "nasmlib.h"
62 #include "stdscan.h"
63 #include "parser.h"
64 #include "float.h"
65 #include "tables.h"
66
67 extern int in_abs_seg;          /* ABSOLUTE segment flag */
68 extern int32_t abs_seg;            /* ABSOLUTE segment */
69 extern int32_t abs_offset;         /* ABSOLUTE segment offset */
70
71 static int is_comma_next(void);
72
73 static int i;
74 static struct tokenval tokval;
75 static efunc error;
76 static struct ofmt *outfmt;     /* Structure of addresses of output routines */
77 static struct location *location;         /* Pointer to current line's segment,offset */
78
79 void parser_global_info(struct ofmt *output, struct location * locp)
80 {
81     outfmt = output;
82     location = locp;
83 }
84
85 static int prefix_slot(enum prefixes prefix)
86 {
87     switch (prefix) {
88     case P_WAIT:
89         return PPS_WAIT;
90     case R_CS:
91     case R_DS:
92     case R_SS:
93     case R_ES:
94     case R_FS:
95     case R_GS:
96         return PPS_SEG;
97     case P_LOCK:
98     case P_REP:
99     case P_REPE:
100     case P_REPZ:
101     case P_REPNE:
102     case P_REPNZ:
103         return PPS_LREP;
104     case P_O16:
105     case P_O32:
106     case P_O64:
107     case P_OSP:
108         return PPS_OSIZE;
109     case P_A16:
110     case P_A32:
111     case P_A64:
112     case P_ASP:
113         return PPS_ASIZE;
114     default:
115         error(ERR_PANIC, "Invalid value %d passed to prefix_slot()", prefix);
116         return -1;
117     }
118 }
119
120 static void process_size_override(insn * result, int operand)
121 {
122     if (tasm_compatible_mode) {
123         switch ((int)tokval.t_integer) {
124             /* For TASM compatibility a size override inside the
125              * brackets changes the size of the operand, not the
126              * address type of the operand as it does in standard
127              * NASM syntax. Hence:
128              *
129              *  mov     eax,[DWORD val]
130              *
131              * is valid syntax in TASM compatibility mode. Note that
132              * you lose the ability to override the default address
133              * type for the instruction, but we never use anything
134              * but 32-bit flat model addressing in our code.
135              */
136         case S_BYTE:
137             result->oprs[operand].type |= BITS8;
138             break;
139         case S_WORD:
140             result->oprs[operand].type |= BITS16;
141             break;
142         case S_DWORD:
143         case S_LONG:
144             result->oprs[operand].type |= BITS32;
145             break;
146         case S_QWORD:
147             result->oprs[operand].type |= BITS64;
148             break;
149         case S_TWORD:
150             result->oprs[operand].type |= BITS80;
151             break;
152         case S_OWORD:
153             result->oprs[operand].type |= BITS128;
154             break;
155         default:
156             error(ERR_NONFATAL,
157                   "invalid operand size specification");
158             break;
159         }
160     } else {
161         /* Standard NASM compatible syntax */
162         switch ((int)tokval.t_integer) {
163         case S_NOSPLIT:
164             result->oprs[operand].eaflags |= EAF_TIMESTWO;
165             break;
166         case S_REL:
167             result->oprs[operand].eaflags |= EAF_REL;
168             break;
169         case S_ABS:
170             result->oprs[operand].eaflags |= EAF_ABS;
171             break;
172         case S_BYTE:
173             result->oprs[operand].disp_size = 8;
174             result->oprs[operand].eaflags |= EAF_BYTEOFFS;
175             break;
176         case P_A16:
177         case P_A32:
178         case P_A64:
179             if (result->prefixes[PPS_ASIZE] &&
180                 result->prefixes[PPS_ASIZE] != tokval.t_integer)
181                 error(ERR_NONFATAL,
182                       "conflicting address size specifications");
183             else
184                 result->prefixes[PPS_ASIZE] = tokval.t_integer;
185             break;
186         case S_WORD:
187             result->oprs[operand].disp_size = 16;
188             result->oprs[operand].eaflags |= EAF_WORDOFFS;
189             break;
190         case S_DWORD:
191         case S_LONG:
192             result->oprs[operand].disp_size = 32;
193             result->oprs[operand].eaflags |= EAF_WORDOFFS;
194             break;
195         case S_QWORD:
196             result->oprs[operand].disp_size = 64;
197             result->oprs[operand].eaflags |= EAF_WORDOFFS;
198             break;
199         default:
200             error(ERR_NONFATAL, "invalid size specification in"
201                   " effective address");
202             break;
203         }
204     }
205 }
206
207 insn *parse_line(int pass, char *buffer, insn * result,
208                  efunc errfunc, evalfunc evaluate, ldfunc ldef)
209 {
210     int operand;
211     int critical;
212     struct eval_hints hints;
213     int j;
214     bool first;
215     bool insn_is_label = false;
216     bool recover;
217
218 restart_parse:
219     first = true;
220     result->forw_ref = false;
221     error = errfunc;
222
223     stdscan_reset();
224     stdscan_bufptr = buffer;
225     i = stdscan(NULL, &tokval);
226
227     result->label = NULL;       /* Assume no label */
228     result->eops = NULL;        /* must do this, whatever happens */
229     result->operands = 0;       /* must initialize this */
230
231     if (i == 0) {               /* blank line - ignore */
232         result->opcode = -1;    /* and no instruction either */
233         return result;
234     }
235     if (i != TOKEN_ID && i != TOKEN_INSN && i != TOKEN_PREFIX &&
236         (i != TOKEN_REG || (REG_SREG & ~nasm_reg_flags[tokval.t_integer]))) {
237         error(ERR_NONFATAL, "label or instruction expected"
238               " at start of line");
239         result->opcode = -1;
240         return result;
241     }
242
243     if (i == TOKEN_ID || (insn_is_label && i == TOKEN_INSN)) {
244         /* there's a label here */
245         first = false;
246         result->label = tokval.t_charptr;
247         i = stdscan(NULL, &tokval);
248         if (i == ':') {         /* skip over the optional colon */
249             i = stdscan(NULL, &tokval);
250         } else if (i == 0) {
251             error(ERR_WARNING | ERR_WARN_OL | ERR_PASS1,
252                   "label alone on a line without a colon might be in error");
253         }
254         if (i != TOKEN_INSN || tokval.t_integer != I_EQU) {
255             /*
256              * FIXME: location->segment could be NO_SEG, in which case
257              * it is possible we should be passing 'abs_seg'. Look into this.
258              * Work out whether that is *really* what we should be doing.
259              * Generally fix things. I think this is right as it is, but
260              * am still not certain.
261              */
262             ldef(result->label, in_abs_seg ? abs_seg : location->segment,
263                  location->offset, NULL, true, false, outfmt, errfunc);
264         }
265     }
266
267     if (i == 0) {
268         result->opcode = -1;    /* this line contains just a label */
269         return result;
270     }
271
272     for (j = 0; j < MAXPREFIX; j++)
273         result->prefixes[j] = P_none;
274     result->times = 1L;
275
276     while (i == TOKEN_PREFIX ||
277            (i == TOKEN_REG && !(REG_SREG & ~nasm_reg_flags[tokval.t_integer])))
278     {
279         first = false;
280
281         /*
282          * Handle special case: the TIMES prefix.
283          */
284         if (i == TOKEN_PREFIX && tokval.t_integer == P_TIMES) {
285             expr *value;
286
287             i = stdscan(NULL, &tokval);
288             value =
289                 evaluate(stdscan, NULL, &tokval, NULL, pass0, error, NULL);
290             i = tokval.t_type;
291             if (!value) {       /* but, error in evaluator */
292                 result->opcode = -1;    /* unrecoverable parse error: */
293                 return result;  /* ignore this instruction */
294             }
295             if (!is_simple(value)) {
296                 error(ERR_NONFATAL,
297                       "non-constant argument supplied to TIMES");
298                 result->times = 1L;
299             } else {
300                 result->times = value->value;
301                 if (value->value < 0 && pass0 == 2) {
302                     error(ERR_NONFATAL, "TIMES value %d is negative",
303                           value->value);
304                     result->times = 0;
305                 }
306             }
307         } else {
308             int slot = prefix_slot(tokval.t_integer);
309             if (result->prefixes[slot]) {
310                if (result->prefixes[slot] == tokval.t_integer)
311                     error(ERR_WARNING,
312                       "instruction has redundant prefixes");
313                else
314                     error(ERR_NONFATAL,
315                       "instruction has conflicting prefixes");
316             }
317             result->prefixes[slot] = tokval.t_integer;
318             i = stdscan(NULL, &tokval);
319         }
320     }
321
322     if (i != TOKEN_INSN) {
323         int j;
324         enum prefixes pfx;
325
326         for (j = 0; j < MAXPREFIX; j++)
327             if ((pfx = result->prefixes[j]) != P_none)
328                 break;
329
330         if (i == 0 && pfx != P_none) {
331             /*
332              * Instruction prefixes are present, but no actual
333              * instruction. This is allowed: at this point we
334              * invent a notional instruction of RESB 0.
335              */
336             result->opcode = I_RESB;
337             result->operands = 1;
338             result->oprs[0].type = IMMEDIATE;
339             result->oprs[0].offset = 0L;
340             result->oprs[0].segment = result->oprs[0].wrt = NO_SEG;
341             return result;
342         } else {
343             error(ERR_NONFATAL, "parser: instruction expected");
344             result->opcode = -1;
345             return result;
346         }
347     }
348
349     result->opcode = tokval.t_integer;
350     result->condition = tokval.t_inttwo;
351
352     /*
353      * INCBIN cannot be satisfied with incorrectly
354      * evaluated operands, since the correct values _must_ be known
355      * on the first pass. Hence, even in pass one, we set the
356      * `critical' flag on calling evaluate(), so that it will bomb
357      * out on undefined symbols.
358      */
359     if (result->opcode == I_INCBIN) {
360         critical = (pass0 < 2 ? 1 : 2);
361
362     } else
363         critical = (pass == 2 ? 2 : 0);
364
365     if (result->opcode == I_DB || result->opcode == I_DW ||
366         result->opcode == I_DD || result->opcode == I_DQ ||
367         result->opcode == I_DT || result->opcode == I_DO ||
368         result->opcode == I_DY || result->opcode == I_INCBIN) {
369         extop *eop, **tail = &result->eops, **fixptr;
370         int oper_num = 0;
371         int32_t sign;
372
373         result->eops_float = false;
374
375         /*
376          * Begin to read the DB/DW/DD/DQ/DT/DO/INCBIN operands.
377          */
378         while (1) {
379             i = stdscan(NULL, &tokval);
380             if (i == 0)
381                 break;
382             else if (first && i == ':') {
383                 insn_is_label = true;
384                 goto restart_parse;
385             }
386             first = false;
387             fixptr = tail;
388             eop = *tail = nasm_malloc(sizeof(extop));
389             tail = &eop->next;
390             eop->next = NULL;
391             eop->type = EOT_NOTHING;
392             oper_num++;
393             sign = +1;
394
395             /* is_comma_next() here is to distinguish this from
396                a string used as part of an expression... */
397             if (i == TOKEN_STR && is_comma_next()) {
398                 eop->type = EOT_DB_STRING;
399                 eop->stringval = tokval.t_charptr;
400                 eop->stringlen = tokval.t_inttwo;
401                 i = stdscan(NULL, &tokval);     /* eat the comma */
402             } else if (i == TOKEN_STRFUNC) {
403                 bool parens = false;
404                 const char *funcname = tokval.t_charptr;
405                 enum strfunc func = tokval.t_integer;
406                 i = stdscan(NULL, &tokval);
407                 if (i == '(') {
408                     parens = true;
409                     i = stdscan(NULL, &tokval);
410                 }
411                 if (i != TOKEN_STR) {
412                     error(ERR_NONFATAL,
413                           "%s must be followed by a string constant",
414                           funcname);
415                         eop->type = EOT_NOTHING;
416                 } else {
417                     eop->type = EOT_DB_STRING_FREE;
418                     eop->stringlen =
419                         string_transform(tokval.t_charptr, tokval.t_inttwo,
420                                          &eop->stringval, func);
421                     if (eop->stringlen == (size_t)-1) {
422                         error(ERR_NONFATAL, "invalid string for transform");
423                         eop->type = EOT_NOTHING;
424                     }
425                 }
426                 if (parens && i && i != ')') {
427                     i = stdscan(NULL, &tokval);
428                     if (i != ')') {
429                         error(ERR_NONFATAL, "unterminated %s function",
430                               funcname);
431                     }
432                 }
433                 if (i && i != ',')
434                     i = stdscan(NULL, &tokval);
435             } else if (i == '-' || i == '+') {
436                 char *save = stdscan_bufptr;
437                 int token = i;
438                 sign = (i == '-') ? -1 : 1;
439                 i = stdscan(NULL, &tokval);
440                 if (i != TOKEN_FLOAT) {
441                     stdscan_bufptr = save;
442                     i = tokval.t_type = token;
443                     goto is_expression;
444                 } else {
445                     goto is_float;
446                 }
447             } else if (i == TOKEN_FLOAT) {
448             is_float:
449                 eop->type = EOT_DB_STRING;
450                 result->eops_float = true;
451                 switch (result->opcode) {
452                 case I_DB:
453                     eop->stringlen = 1;
454                     break;
455                 case I_DW:
456                     eop->stringlen = 2;
457                     break;
458                 case I_DD:
459                     eop->stringlen = 4;
460                     break;
461                 case I_DQ:
462                     eop->stringlen = 8;
463                     break;
464                 case I_DT:
465                     eop->stringlen = 10;
466                     break;
467                 case I_DO:
468                     eop->stringlen = 16;
469                     break;
470                 case I_DY:
471                     error(ERR_NONFATAL, "floating-point constant"
472                           " encountered in DY instruction");
473                     eop->stringlen = 0;
474                     break;
475                 default:
476                     error(ERR_NONFATAL, "floating-point constant"
477                           " encountered in unknown instruction");
478                     /*
479                      * fix suggested by Pedro Gimeno... original line
480                      * was:
481                      * eop->type = EOT_NOTHING;
482                      */
483                     eop->stringlen = 0;
484                     break;
485                 }
486                 eop = nasm_realloc(eop, sizeof(extop) + eop->stringlen);
487                 tail = &eop->next;
488                 *fixptr = eop;
489                 eop->stringval = (char *)eop + sizeof(extop);
490                 if (!eop->stringlen ||
491                     !float_const(tokval.t_charptr, sign,
492                                  (uint8_t *)eop->stringval,
493                                  eop->stringlen, error))
494                     eop->type = EOT_NOTHING;
495                 i = stdscan(NULL, &tokval); /* eat the comma */
496             } else {
497                 /* anything else, assume it is an expression */
498                 expr *value;
499
500             is_expression:
501                 value = evaluate(stdscan, NULL, &tokval, NULL,
502                                  critical, error, NULL);
503                 i = tokval.t_type;
504                 if (!value) {   /* error in evaluator */
505                     result->opcode = -1;        /* unrecoverable parse error: */
506                     return result;      /* ignore this instruction */
507                 }
508                 if (is_unknown(value)) {
509                     eop->type = EOT_DB_NUMBER;
510                     eop->offset = 0;    /* doesn't matter what we put */
511                     eop->segment = eop->wrt = NO_SEG;   /* likewise */
512                 } else if (is_reloc(value)) {
513                     eop->type = EOT_DB_NUMBER;
514                     eop->offset = reloc_value(value);
515                     eop->segment = reloc_seg(value);
516                     eop->wrt = reloc_wrt(value);
517                 } else {
518                     error(ERR_NONFATAL,
519                           "operand %d: expression is not simple"
520                           " or relocatable", oper_num);
521                 }
522             }
523
524             /*
525              * We're about to call stdscan(), which will eat the
526              * comma that we're currently sitting on between
527              * arguments. However, we'd better check first that it
528              * _is_ a comma.
529              */
530             if (i == 0)         /* also could be EOL */
531                 break;
532             if (i != ',') {
533                 error(ERR_NONFATAL, "comma expected after operand %d",
534                       oper_num);
535                 result->opcode = -1;    /* unrecoverable parse error: */
536                 return result;  /* ignore this instruction */
537             }
538         }
539
540         if (result->opcode == I_INCBIN) {
541             /*
542              * Correct syntax for INCBIN is that there should be
543              * one string operand, followed by one or two numeric
544              * operands.
545              */
546             if (!result->eops || result->eops->type != EOT_DB_STRING)
547                 error(ERR_NONFATAL, "`incbin' expects a file name");
548             else if (result->eops->next &&
549                      result->eops->next->type != EOT_DB_NUMBER)
550                 error(ERR_NONFATAL, "`incbin': second parameter is",
551                       " non-numeric");
552             else if (result->eops->next && result->eops->next->next &&
553                      result->eops->next->next->type != EOT_DB_NUMBER)
554                 error(ERR_NONFATAL, "`incbin': third parameter is",
555                       " non-numeric");
556             else if (result->eops->next && result->eops->next->next &&
557                      result->eops->next->next->next)
558                 error(ERR_NONFATAL,
559                       "`incbin': more than three parameters");
560             else
561                 return result;
562             /*
563              * If we reach here, one of the above errors happened.
564              * Throw the instruction away.
565              */
566             result->opcode = -1;
567             return result;
568         } else /* DB ... */ if (oper_num == 0)
569             error(ERR_WARNING | ERR_PASS1,
570                   "no operand for data declaration");
571         else
572             result->operands = oper_num;
573
574         return result;
575     }
576
577     /* right. Now we begin to parse the operands. There may be up to four
578      * of these, separated by commas, and terminated by a zero token. */
579
580     for (operand = 0; operand < MAX_OPERANDS; operand++) {
581         expr *value;            /* used most of the time */
582         int mref;               /* is this going to be a memory ref? */
583         int bracket;            /* is it a [] mref, or a & mref? */
584         int setsize = 0;
585
586         result->oprs[operand].disp_size = 0;    /* have to zero this whatever */
587         result->oprs[operand].eaflags = 0;      /* and this */
588         result->oprs[operand].opflags = 0;
589
590         i = stdscan(NULL, &tokval);
591         if (i == 0)
592             break;              /* end of operands: get out of here */
593         else if (first && i == ':') {
594             insn_is_label = true;
595             goto restart_parse;
596         }
597         first = false;
598         result->oprs[operand].type = 0; /* so far, no override */
599         while (i == TOKEN_SPECIAL) {    /* size specifiers */
600             switch ((int)tokval.t_integer) {
601             case S_BYTE:
602                 if (!setsize)   /* we want to use only the first */
603                     result->oprs[operand].type |= BITS8;
604                 setsize = 1;
605                 break;
606             case S_WORD:
607                 if (!setsize)
608                     result->oprs[operand].type |= BITS16;
609                 setsize = 1;
610                 break;
611             case S_DWORD:
612             case S_LONG:
613                 if (!setsize)
614                     result->oprs[operand].type |= BITS32;
615                 setsize = 1;
616                 break;
617             case S_QWORD:
618                 if (!setsize)
619                     result->oprs[operand].type |= BITS64;
620                 setsize = 1;
621                 break;
622             case S_TWORD:
623                 if (!setsize)
624                     result->oprs[operand].type |= BITS80;
625                 setsize = 1;
626                 break;
627             case S_OWORD:
628                 if (!setsize)
629                     result->oprs[operand].type |= BITS128;
630                 setsize = 1;
631                 break;
632             case S_YWORD:
633                 if (!setsize)
634                     result->oprs[operand].type |= BITS256;
635                 setsize = 1;
636                 break;
637             case S_TO:
638                 result->oprs[operand].type |= TO;
639                 break;
640             case S_STRICT:
641                 result->oprs[operand].type |= STRICT;
642                 break;
643             case S_FAR:
644                 result->oprs[operand].type |= FAR;
645                 break;
646             case S_NEAR:
647                 result->oprs[operand].type |= NEAR;
648                 break;
649             case S_SHORT:
650                 result->oprs[operand].type |= SHORT;
651                 break;
652             default:
653                 error(ERR_NONFATAL, "invalid operand size specification");
654             }
655             i = stdscan(NULL, &tokval);
656         }
657
658         if (i == '[' || i == '&') {     /* memory reference */
659             mref = true;
660             bracket = (i == '[');
661             i = stdscan(NULL, &tokval); /* then skip the colon */
662             while (i == TOKEN_SPECIAL || i == TOKEN_PREFIX) {
663                 process_size_override(result, operand);
664                 i = stdscan(NULL, &tokval);
665             }
666         } else {                /* immediate operand, or register */
667             mref = false;
668             bracket = false;    /* placate optimisers */
669         }
670
671         if ((result->oprs[operand].type & FAR) && !mref &&
672             result->opcode != I_JMP && result->opcode != I_CALL) {
673             error(ERR_NONFATAL, "invalid use of FAR operand specifier");
674         }
675
676         value = evaluate(stdscan, NULL, &tokval,
677                          &result->oprs[operand].opflags,
678                          critical, error, &hints);
679         i = tokval.t_type;
680         if (result->oprs[operand].opflags & OPFLAG_FORWARD) {
681             result->forw_ref = true;
682         }
683         if (!value) {           /* error in evaluator */
684             result->opcode = -1;        /* unrecoverable parse error: */
685             return result;      /* ignore this instruction */
686         }
687         if (i == ':' && mref) { /* it was seg:offset */
688             /*
689              * Process the segment override.
690              */
691             if (value[1].type != 0 || value->value != 1 ||
692                 REG_SREG & ~nasm_reg_flags[value->type])
693                 error(ERR_NONFATAL, "invalid segment override");
694             else if (result->prefixes[PPS_SEG])
695                 error(ERR_NONFATAL,
696                       "instruction has conflicting segment overrides");
697             else {
698                 result->prefixes[PPS_SEG] = value->type;
699                 if (!(REG_FSGS & ~nasm_reg_flags[value->type]))
700                     result->oprs[operand].eaflags |= EAF_FSGS;
701             }
702
703             i = stdscan(NULL, &tokval); /* then skip the colon */
704             while (i == TOKEN_SPECIAL || i == TOKEN_PREFIX) {
705                 process_size_override(result, operand);
706                 i = stdscan(NULL, &tokval);
707             }
708             value = evaluate(stdscan, NULL, &tokval,
709                              &result->oprs[operand].opflags,
710                              critical, error, &hints);
711             i = tokval.t_type;
712             if (result->oprs[operand].opflags & OPFLAG_FORWARD) {
713                 result->forw_ref = true;
714             }
715             /* and get the offset */
716             if (!value) {       /* but, error in evaluator */
717                 result->opcode = -1;    /* unrecoverable parse error: */
718                 return result;  /* ignore this instruction */
719             }
720         }
721
722         recover = false;
723         if (mref && bracket) {  /* find ] at the end */
724             if (i != ']') {
725                 error(ERR_NONFATAL, "parser: expecting ]");
726                 recover = true;
727             } else {            /* we got the required ] */
728                 i = stdscan(NULL, &tokval);
729                 if (i != 0 && i != ',') {
730                     error(ERR_NONFATAL, "comma or end of line expected");
731                     recover = true;
732                 }
733             }
734         } else {                /* immediate operand */
735             if (i != 0 && i != ',' && i != ':') {
736                 error(ERR_NONFATAL, "comma, colon or end of line expected");
737                 recover = true;
738             } else if (i == ':') {
739                 result->oprs[operand].type |= COLON;
740             }
741         }
742         if (recover) {
743             do {                /* error recovery */
744                 i = stdscan(NULL, &tokval);
745             } while (i != 0 && i != ',');
746         }
747
748         /* now convert the exprs returned from evaluate() into operand
749          * descriptions... */
750
751         if (mref) {             /* it's a memory reference */
752             expr *e = value;
753             int b, i, s;        /* basereg, indexreg, scale */
754             int64_t o;             /* offset */
755
756             b = i = -1, o = s = 0;
757             result->oprs[operand].hintbase = hints.base;
758             result->oprs[operand].hinttype = hints.type;
759
760             if (e->type && e->type <= EXPR_REG_END) {   /* this bit's a register */
761                 if (e->value == 1)      /* in fact it can be basereg */
762                     b = e->type;
763                 else            /* no, it has to be indexreg */
764                     i = e->type, s = e->value;
765                 e++;
766             }
767             if (e->type && e->type <= EXPR_REG_END) {   /* it's a 2nd register */
768                 if (b != -1)    /* If the first was the base, ... */
769                     i = e->type, s = e->value;  /* second has to be indexreg */
770
771                 else if (e->value != 1) {       /* If both want to be index */
772                     error(ERR_NONFATAL,
773                           "beroset-p-592-invalid effective address");
774                     result->opcode = -1;
775                     return result;
776                 } else
777                     b = e->type;
778                 e++;
779             }
780             if (e->type != 0) { /* is there an offset? */
781                 if (e->type <= EXPR_REG_END) {  /* in fact, is there an error? */
782                     error(ERR_NONFATAL,
783                           "beroset-p-603-invalid effective address");
784                     result->opcode = -1;
785                     return result;
786                 } else {
787                     if (e->type == EXPR_UNKNOWN) {
788                         result->oprs[operand].opflags |= OPFLAG_UNKNOWN;
789                         o = 0;  /* doesn't matter what */
790                         result->oprs[operand].wrt = NO_SEG;     /* nor this */
791                         result->oprs[operand].segment = NO_SEG; /* or this */
792                         while (e->type)
793                             e++;        /* go to the end of the line */
794                     } else {
795                         if (e->type == EXPR_SIMPLE) {
796                             o = e->value;
797                             e++;
798                         }
799                         if (e->type == EXPR_WRT) {
800                             result->oprs[operand].wrt = e->value;
801                             e++;
802                         } else
803                             result->oprs[operand].wrt = NO_SEG;
804                         /*
805                          * Look for a segment base type.
806                          */
807                         if (e->type && e->type < EXPR_SEGBASE) {
808                             error(ERR_NONFATAL,
809                                   "beroset-p-630-invalid effective address");
810                             result->opcode = -1;
811                             return result;
812                         }
813                         while (e->type && e->value == 0)
814                             e++;
815                         if (e->type && e->value != 1) {
816                             error(ERR_NONFATAL,
817                                   "beroset-p-637-invalid effective address");
818                             result->opcode = -1;
819                             return result;
820                         }
821                         if (e->type) {
822                             result->oprs[operand].segment =
823                                 e->type - EXPR_SEGBASE;
824                             e++;
825                         } else
826                             result->oprs[operand].segment = NO_SEG;
827                         while (e->type && e->value == 0)
828                             e++;
829                         if (e->type) {
830                             error(ERR_NONFATAL,
831                                   "beroset-p-650-invalid effective address");
832                             result->opcode = -1;
833                             return result;
834                         }
835                     }
836                 }
837             } else {
838                 o = 0;
839                 result->oprs[operand].wrt = NO_SEG;
840                 result->oprs[operand].segment = NO_SEG;
841             }
842
843             if (e->type != 0) { /* there'd better be nothing left! */
844                 error(ERR_NONFATAL,
845                       "beroset-p-663-invalid effective address");
846                 result->opcode = -1;
847                 return result;
848             }
849
850             /* It is memory, but it can match any r/m operand */
851             result->oprs[operand].type |= MEMORY_ANY;
852
853             if (b == -1 && (i == -1 || s == 0)) {
854                 int is_rel = globalbits == 64 &&
855                     !(result->oprs[operand].eaflags & EAF_ABS) &&
856                     ((globalrel &&
857                       !(result->oprs[operand].eaflags & EAF_FSGS)) ||
858                      (result->oprs[operand].eaflags & EAF_REL));
859
860                 result->oprs[operand].type |= is_rel ? IP_REL : MEM_OFFS;
861             }
862             result->oprs[operand].basereg = b;
863             result->oprs[operand].indexreg = i;
864             result->oprs[operand].scale = s;
865             result->oprs[operand].offset = o;
866         } else {                /* it's not a memory reference */
867             if (is_just_unknown(value)) {       /* it's immediate but unknown */
868                 result->oprs[operand].type |= IMMEDIATE;
869                 result->oprs[operand].opflags |= OPFLAG_UNKNOWN;
870                 result->oprs[operand].offset = 0;       /* don't care */
871                 result->oprs[operand].segment = NO_SEG; /* don't care again */
872                 result->oprs[operand].wrt = NO_SEG;     /* still don't care */
873
874                 if(optimizing >= 0 && !(result->oprs[operand].type & STRICT))
875                 {
876                     /* Be optimistic */
877                     result->oprs[operand].type |= SBYTE16 | SBYTE32 | SBYTE64;
878                 }
879             } else if (is_reloc(value)) {       /* it's immediate */
880                 result->oprs[operand].type |= IMMEDIATE;
881                 result->oprs[operand].offset = reloc_value(value);
882                 result->oprs[operand].segment = reloc_seg(value);
883                 result->oprs[operand].wrt = reloc_wrt(value);
884                 if (is_simple(value)) {
885                     if (reloc_value(value) == 1)
886                         result->oprs[operand].type |= UNITY;
887                     if (optimizing >= 0 &&
888                         !(result->oprs[operand].type & STRICT)) {
889                         int64_t v64 = reloc_value(value);
890                         int32_t v32 = (int32_t)v64;
891                         int16_t v16 = (int16_t)v32;
892
893                         if (v64 >= -128 && v64 <= 127)
894                             result->oprs[operand].type |= SBYTE64;
895                         if (v32 >= -128 && v32 <= 127)
896                             result->oprs[operand].type |= SBYTE32;
897                         if (v16 >= -128 && v16 <= 127)
898                             result->oprs[operand].type |= SBYTE16;
899                     }
900                 }
901             } else {            /* it's a register */
902                 unsigned int rs;
903
904                 if (value->type >= EXPR_SIMPLE || value->value != 1) {
905                     error(ERR_NONFATAL, "invalid operand type");
906                     result->opcode = -1;
907                     return result;
908                 }
909
910                 /*
911                  * check that its only 1 register, not an expression...
912                  */
913                 for (i = 1; value[i].type; i++)
914                     if (value[i].value) {
915                         error(ERR_NONFATAL, "invalid operand type");
916                         result->opcode = -1;
917                         return result;
918                     }
919
920                 /* clear overrides, except TO which applies to FPU regs */
921                 if (result->oprs[operand].type & ~TO) {
922                     /*
923                      * we want to produce a warning iff the specified size
924                      * is different from the register size
925                      */
926                     rs = result->oprs[operand].type & SIZE_MASK;
927                 } else
928                     rs = 0;
929
930                 result->oprs[operand].type &= TO;
931                 result->oprs[operand].type |= REGISTER;
932                 result->oprs[operand].type |= nasm_reg_flags[value->type];
933                 result->oprs[operand].basereg = value->type;
934
935                 if (rs && (result->oprs[operand].type & SIZE_MASK) != rs)
936                     error(ERR_WARNING | ERR_PASS1,
937                           "register size specification ignored");
938             }
939         }
940     }
941
942     result->operands = operand; /* set operand count */
943
944 /* clear remaining operands */
945 while (operand < MAX_OPERANDS)
946     result->oprs[operand++].type = 0;
947
948     /*
949      * Transform RESW, RESD, RESQ, REST, RESO, RESY into RESB.
950      */
951     switch (result->opcode) {
952     case I_RESW:
953         result->opcode = I_RESB;
954         result->oprs[0].offset *= 2;
955         break;
956     case I_RESD:
957         result->opcode = I_RESB;
958         result->oprs[0].offset *= 4;
959         break;
960     case I_RESQ:
961         result->opcode = I_RESB;
962         result->oprs[0].offset *= 8;
963         break;
964     case I_REST:
965         result->opcode = I_RESB;
966         result->oprs[0].offset *= 10;
967         break;
968     case I_RESO:
969         result->opcode = I_RESB;
970         result->oprs[0].offset *= 16;
971         break;
972     case I_RESY:
973         result->opcode = I_RESB;
974         result->oprs[0].offset *= 32;
975         break;
976     default:
977         break;
978     }
979
980     return result;
981 }
982
983 static int is_comma_next(void)
984 {
985     char *p;
986     int i;
987     struct tokenval tv;
988
989     p = stdscan_bufptr;
990     i = stdscan(NULL, &tv);
991     stdscan_bufptr = p;
992     return (i == ',' || i == ';' || !i);
993 }
994
995 void cleanup_insn(insn * i)
996 {
997     extop *e;
998
999     while ((e = i->eops)) {
1000         i->eops = e->next;
1001         if (e->type == EOT_DB_STRING_FREE)
1002             nasm_free(e->stringval);
1003         nasm_free(e);
1004     }
1005 }