Merge branch 'nasm-2.07.xx'
[platform/upstream/nasm.git] / preproc.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  *   Redistribution and use in source and binary forms, with or without
8  *   modification, are permitted provided that the following
9  *   conditions are met:
10  *
11  *   * Redistributions of source code must retain the above copyright
12  *     notice, this list of conditions and the following disclaimer.
13  *   * Redistributions in binary form must reproduce the above
14  *     copyright notice, this list of conditions and the following
15  *     disclaimer in the documentation and/or other materials provided
16  *     with the distribution.
17  *     
18  *     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND
19  *     CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
20  *     INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
21  *     MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
22  *     DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR
23  *     CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
24  *     SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
25  *     NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
26  *     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
27  *     HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
28  *     CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
29  *     OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
30  *     EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
31  *
32  * ----------------------------------------------------------------------- */
33
34 /*
35  * preproc.c   macro preprocessor for the Netwide Assembler
36  */
37
38 /* Typical flow of text through preproc
39  *
40  * pp_getline gets tokenized lines, either
41  *
42  *   from a macro expansion
43  *
44  * or
45  *   {
46  *   read_line  gets raw text from stdmacpos, or predef, or current input file
47  *   tokenize   converts to tokens
48  *   }
49  *
50  * expand_mmac_params is used to expand %1 etc., unless a macro is being
51  * defined or a false conditional is being processed
52  * (%0, %1, %+1, %-1, %%foo
53  *
54  * do_directive checks for directives
55  *
56  * expand_smacro is used to expand single line macros
57  *
58  * expand_mmacro is used to expand multi-line macros
59  *
60  * detoken is used to convert the line back to text
61  */
62
63 #include "compiler.h"
64
65 #include <stdio.h>
66 #include <stdarg.h>
67 #include <stdlib.h>
68 #include <stddef.h>
69 #include <string.h>
70 #include <ctype.h>
71 #include <limits.h>
72 #include <inttypes.h>
73
74 #include "nasm.h"
75 #include "nasmlib.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
83
84 typedef struct SMacro SMacro;
85 typedef struct MMacro MMacro;
86 typedef struct MMacroInvocation MMacroInvocation;
87 typedef struct Context Context;
88 typedef struct Token Token;
89 typedef struct Blocks Blocks;
90 typedef struct Line Line;
91 typedef struct Include Include;
92 typedef struct Cond Cond;
93 typedef struct IncPath IncPath;
94
95 /*
96  * Note on the storage of both SMacro and MMacros: the hash table
97  * indexes them case-insensitively, and we then have to go through a
98  * linked list of potential case aliases (and, for MMacros, parameter
99  * ranges); this is to preserve the matching semantics of the earlier
100  * code.  If the number of case aliases for a specific macro is a
101  * performance issue, you may want to reconsider your coding style.
102  */
103
104 /*
105  * Store the definition of a single-line macro.
106  */
107 struct SMacro {
108     SMacro *next;
109     char *name;
110     bool casesense;
111     bool in_progress;
112     unsigned int nparam;
113     Token *expansion;
114 };
115
116 /*
117  * Store the definition of a multi-line macro. This is also used to
118  * store the interiors of `%rep...%endrep' blocks, which are
119  * effectively self-re-invoking multi-line macros which simply
120  * don't have a name or bother to appear in the hash tables. %rep
121  * blocks are signified by having a NULL `name' field.
122  *
123  * In a MMacro describing a `%rep' block, the `in_progress' field
124  * isn't merely boolean, but gives the number of repeats left to
125  * run.
126  *
127  * The `next' field is used for storing MMacros in hash tables; the
128  * `next_active' field is for stacking them on istk entries.
129  *
130  * When a MMacro is being expanded, `params', `iline', `nparam',
131  * `paramlen', `rotate' and `unique' are local to the invocation.
132  */
133 struct MMacro {
134     MMacro *next;
135     MMacroInvocation *prev;      /* previous invocation */
136     char *name;
137     int nparam_min, nparam_max;
138     bool casesense;
139     bool plus;                   /* is the last parameter greedy? */
140     bool nolist;                 /* is this macro listing-inhibited? */
141     int64_t in_progress;         /* is this macro currently being expanded? */
142     int32_t max_depth;           /* maximum number of recursive expansions allowed */
143     Token *dlist;               /* All defaults as one list */
144     Token **defaults;           /* Parameter default pointers */
145     int ndefs;                  /* number of default parameters */
146     Line *expansion;
147
148     MMacro *next_active;
149     MMacro *rep_nest;           /* used for nesting %rep */
150     Token **params;             /* actual parameters */
151     Token *iline;               /* invocation line */
152     unsigned int nparam, rotate;
153     int *paramlen;
154     uint64_t unique;
155     int lineno;                 /* Current line number on expansion */
156 };
157
158
159 /* Store the definition of a multi-line macro, as defined in a
160  * previous recursive macro expansion.
161  */
162 struct MMacroInvocation {
163     MMacroInvocation *prev;     /* previous invocation */
164     Token **params;             /* actual parameters */
165     Token *iline;               /* invocation line */
166     unsigned int nparam, rotate;
167     int *paramlen;
168     uint64_t unique;
169 };
170
171
172 /*
173  * The context stack is composed of a linked list of these.
174  */
175 struct Context {
176     Context *next;
177     char *name;
178     struct hash_table localmac;
179     uint32_t number;
180 };
181
182 /*
183  * This is the internal form which we break input lines up into.
184  * Typically stored in linked lists.
185  *
186  * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
187  * necessarily used as-is, but is intended to denote the number of
188  * the substituted parameter. So in the definition
189  *
190  *     %define a(x,y) ( (x) & ~(y) )
191  *
192  * the token representing `x' will have its type changed to
193  * TOK_SMAC_PARAM, but the one representing `y' will be
194  * TOK_SMAC_PARAM+1.
195  *
196  * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
197  * which doesn't need quotes around it. Used in the pre-include
198  * mechanism as an alternative to trying to find a sensible type of
199  * quote to use on the filename we were passed.
200  */
201 enum pp_token_type {
202     TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
203     TOK_PREPROC_ID, TOK_STRING,
204     TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
205     TOK_INTERNAL_STRING,
206     TOK_PREPROC_Q, TOK_PREPROC_QQ,
207     TOK_PASTE,                  /* %+ */
208     TOK_INDIRECT,               /* %[...] */
209     TOK_SMAC_PARAM,             /* MUST BE LAST IN THE LIST!!! */
210     TOK_MAX = INT_MAX           /* Keep compiler from reducing the range */
211 };
212
213 struct Token {
214     Token *next;
215     char *text;
216     union {
217         SMacro *mac;            /* associated macro for TOK_SMAC_END */
218         size_t len;             /* scratch length field */
219     } a;                        /* Auxiliary data */
220     enum pp_token_type type;
221 };
222
223 /*
224  * Multi-line macro definitions are stored as a linked list of
225  * these, which is essentially a container to allow several linked
226  * lists of Tokens.
227  *
228  * Note that in this module, linked lists are treated as stacks
229  * wherever possible. For this reason, Lines are _pushed_ on to the
230  * `expansion' field in MMacro structures, so that the linked list,
231  * if walked, would give the macro lines in reverse order; this
232  * means that we can walk the list when expanding a macro, and thus
233  * push the lines on to the `expansion' field in _istk_ in reverse
234  * order (so that when popped back off they are in the right
235  * order). It may seem cockeyed, and it relies on my design having
236  * an even number of steps in, but it works...
237  *
238  * Some of these structures, rather than being actual lines, are
239  * markers delimiting the end of the expansion of a given macro.
240  * This is for use in the cycle-tracking and %rep-handling code.
241  * Such structures have `finishes' non-NULL, and `first' NULL. All
242  * others have `finishes' NULL, but `first' may still be NULL if
243  * the line is blank.
244  */
245 struct Line {
246     Line *next;
247     MMacro *finishes;
248     Token *first;
249 };
250
251 /*
252  * To handle an arbitrary level of file inclusion, we maintain a
253  * stack (ie linked list) of these things.
254  */
255 struct Include {
256     Include *next;
257     FILE *fp;
258     Cond *conds;
259     Line *expansion;
260     char *fname;
261     int lineno, lineinc;
262     MMacro *mstk;               /* stack of active macros/reps */
263 };
264
265 /*
266  * Include search path. This is simply a list of strings which get
267  * prepended, in turn, to the name of an include file, in an
268  * attempt to find the file if it's not in the current directory.
269  */
270 struct IncPath {
271     IncPath *next;
272     char *path;
273 };
274
275 /*
276  * Conditional assembly: we maintain a separate stack of these for
277  * each level of file inclusion. (The only reason we keep the
278  * stacks separate is to ensure that a stray `%endif' in a file
279  * included from within the true branch of a `%if' won't terminate
280  * it and cause confusion: instead, rightly, it'll cause an error.)
281  */
282 struct Cond {
283     Cond *next;
284     int state;
285 };
286 enum {
287     /*
288      * These states are for use just after %if or %elif: IF_TRUE
289      * means the condition has evaluated to truth so we are
290      * currently emitting, whereas IF_FALSE means we are not
291      * currently emitting but will start doing so if a %else comes
292      * up. In these states, all directives are admissible: %elif,
293      * %else and %endif. (And of course %if.)
294      */
295     COND_IF_TRUE, COND_IF_FALSE,
296     /*
297      * These states come up after a %else: ELSE_TRUE means we're
298      * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
299      * any %elif or %else will cause an error.
300      */
301     COND_ELSE_TRUE, COND_ELSE_FALSE,
302     /*
303      * These states mean that we're not emitting now, and also that
304      * nothing until %endif will be emitted at all. COND_DONE is
305      * used when we've had our moment of emission
306      * and have now started seeing %elifs. COND_NEVER is used when
307      * the condition construct in question is contained within a
308      * non-emitting branch of a larger condition construct,
309      * or if there is an error.
310      */
311     COND_DONE, COND_NEVER
312 };
313 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
314
315 /*
316  * These defines are used as the possible return values for do_directive
317  */
318 #define NO_DIRECTIVE_FOUND  0
319 #define DIRECTIVE_FOUND     1
320
321 /*
322  * This define sets the upper limit for smacro and recursive mmacro
323  * expansions
324  */
325 #define DEADMAN_LIMIT (1 << 20)
326
327 /*
328  * Condition codes. Note that we use c_ prefix not C_ because C_ is
329  * used in nasm.h for the "real" condition codes. At _this_ level,
330  * we treat CXZ and ECXZ as condition codes, albeit non-invertible
331  * ones, so we need a different enum...
332  */
333 static const char * const conditions[] = {
334     "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
335     "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
336     "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
337 };
338 enum pp_conds {
339     c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
340     c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
341     c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
342     c_none = -1
343 };
344 static const enum pp_conds inverse_ccs[] = {
345     c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
346     c_A, c_AE, c_B, c_BE, c_C, c_E, c_G, c_GE, c_L, c_LE, c_O, c_P, c_S,
347     c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
348 };
349
350 /*
351  * Directive names.
352  */
353 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
354 static int is_condition(enum preproc_token arg)
355 {
356     return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
357 }
358
359 /* For TASM compatibility we need to be able to recognise TASM compatible
360  * conditional compilation directives. Using the NASM pre-processor does
361  * not work, so we look for them specifically from the following list and
362  * then jam in the equivalent NASM directive into the input stream.
363  */
364
365 enum {
366     TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
367     TM_IFNDEF, TM_INCLUDE, TM_LOCAL
368 };
369
370 static const char * const tasm_directives[] = {
371     "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
372     "ifndef", "include", "local"
373 };
374
375 static int StackSize = 4;
376 static char *StackPointer = "ebp";
377 static int ArgOffset = 8;
378 static int LocalOffset = 0;
379
380 static Context *cstk;
381 static Include *istk;
382 static IncPath *ipath = NULL;
383
384 static int pass;                /* HACK: pass 0 = generate dependencies only */
385 static StrList **dephead, **deptail; /* Dependency list */
386
387 static uint64_t unique;    /* unique identifier numbers */
388
389 static Line *predef = NULL;
390 static bool do_predef;
391
392 static ListGen *list;
393
394 /*
395  * The current set of multi-line macros we have defined.
396  */
397 static struct hash_table mmacros;
398
399 /*
400  * The current set of single-line macros we have defined.
401  */
402 static struct hash_table smacros;
403
404 /*
405  * The multi-line macro we are currently defining, or the %rep
406  * block we are currently reading, if any.
407  */
408 static MMacro *defining;
409
410 static uint64_t nested_mac_count;
411 static uint64_t nested_rep_count;
412
413 /*
414  * The number of macro parameters to allocate space for at a time.
415  */
416 #define PARAM_DELTA 16
417
418 /*
419  * The standard macro set: defined in macros.c in the array nasm_stdmac.
420  * This gives our position in the macro set, when we're processing it.
421  */
422 static macros_t *stdmacpos;
423
424 /*
425  * The extra standard macros that come from the object format, if
426  * any.
427  */
428 static macros_t *extrastdmac = NULL;
429 static bool any_extrastdmac;
430
431 /*
432  * Tokens are allocated in blocks to improve speed
433  */
434 #define TOKEN_BLOCKSIZE 4096
435 static Token *freeTokens = NULL;
436 struct Blocks {
437     Blocks *next;
438     void *chunk;
439 };
440
441 static Blocks blocks = { NULL, NULL };
442
443 /*
444  * Forward declarations.
445  */
446 static Token *expand_mmac_params(Token * tline);
447 static Token *expand_smacro(Token * tline);
448 static Token *expand_id(Token * tline);
449 static Context *get_ctx(const char *name, const char **namep,
450                         bool all_contexts);
451 static void make_tok_num(Token * tok, int64_t val);
452 static void error(int severity, const char *fmt, ...);
453 static void error_precond(int severity, const char *fmt, ...);
454 static void *new_Block(size_t size);
455 static void delete_Blocks(void);
456 static Token *new_Token(Token * next, enum pp_token_type type,
457                         const char *text, int txtlen);
458 static Token *delete_Token(Token * t);
459
460 /*
461  * Macros for safe checking of token pointers, avoid *(NULL)
462  */
463 #define tok_type_(x,t) ((x) && (x)->type == (t))
464 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
465 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
466 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
467
468 /* Handle TASM specific directives, which do not contain a % in
469  * front of them. We do it here because I could not find any other
470  * place to do it for the moment, and it is a hack (ideally it would
471  * be nice to be able to use the NASM pre-processor to do it).
472  */
473 static char *check_tasm_directive(char *line)
474 {
475     int32_t i, j, k, m, len;
476     char *p = line, *oldline, oldchar;
477
478     /* Skip whitespace */
479     while (nasm_isspace(*p) && *p != 0)
480         p++;
481
482     /* Binary search for the directive name */
483     i = -1;
484     j = elements(tasm_directives);
485     len = 0;
486     while (!nasm_isspace(p[len]) && p[len] != 0)
487         len++;
488     if (len) {
489         oldchar = p[len];
490         p[len] = 0;
491         while (j - i > 1) {
492             k = (j + i) / 2;
493             m = nasm_stricmp(p, tasm_directives[k]);
494             if (m == 0) {
495                 /* We have found a directive, so jam a % in front of it
496                  * so that NASM will then recognise it as one if it's own.
497                  */
498                 p[len] = oldchar;
499                 len = strlen(p);
500                 oldline = line;
501                 line = nasm_malloc(len + 2);
502                 line[0] = '%';
503                 if (k == TM_IFDIFI) {
504                     /*
505                      * NASM does not recognise IFDIFI, so we convert
506                      * it to %if 0. This is not used in NASM
507                      * compatible code, but does need to parse for the
508                      * TASM macro package.
509                      */
510                     strcpy(line + 1, "if 0");
511                 } else {
512                     memcpy(line + 1, p, len + 1);
513                 }
514                 nasm_free(oldline);
515                 return line;
516             } else if (m < 0) {
517                 j = k;
518             } else
519                 i = k;
520         }
521         p[len] = oldchar;
522     }
523     return line;
524 }
525
526 /*
527  * The pre-preprocessing stage... This function translates line
528  * number indications as they emerge from GNU cpp (`# lineno "file"
529  * flags') into NASM preprocessor line number indications (`%line
530  * lineno file').
531  */
532 static char *prepreproc(char *line)
533 {
534     int lineno, fnlen;
535     char *fname, *oldline;
536
537     if (line[0] == '#' && line[1] == ' ') {
538         oldline = line;
539         fname = oldline + 2;
540         lineno = atoi(fname);
541         fname += strspn(fname, "0123456789 ");
542         if (*fname == '"')
543             fname++;
544         fnlen = strcspn(fname, "\"");
545         line = nasm_malloc(20 + fnlen);
546         snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
547         nasm_free(oldline);
548     }
549     if (tasm_compatible_mode)
550         return check_tasm_directive(line);
551     return line;
552 }
553
554 /*
555  * Free a linked list of tokens.
556  */
557 static void free_tlist(Token * list)
558 {
559     while (list) {
560         list = delete_Token(list);
561     }
562 }
563
564 /*
565  * Free a linked list of lines.
566  */
567 static void free_llist(Line * list)
568 {
569     Line *l;
570     while (list) {
571         l = list;
572         list = list->next;
573         free_tlist(l->first);
574         nasm_free(l);
575     }
576 }
577
578 /*
579  * Free an MMacro
580  */
581 static void free_mmacro(MMacro * m)
582 {
583     nasm_free(m->name);
584     free_tlist(m->dlist);
585     nasm_free(m->defaults);
586     free_llist(m->expansion);
587     nasm_free(m);
588 }
589
590 /*
591  * Free all currently defined macros, and free the hash tables
592  */
593 static void free_smacro_table(struct hash_table *smt)
594 {
595     SMacro *s;
596     const char *key;
597     struct hash_tbl_node *it = NULL;
598
599     while ((s = hash_iterate(smt, &it, &key)) != NULL) {
600         nasm_free((void *)key);
601         while (s) {
602             SMacro *ns = s->next;
603             nasm_free(s->name);
604             free_tlist(s->expansion);
605             nasm_free(s);
606             s = ns;
607         }
608     }
609     hash_free(smt);
610 }
611
612 static void free_mmacro_table(struct hash_table *mmt)
613 {
614     MMacro *m;
615     const char *key;
616     struct hash_tbl_node *it = NULL;
617
618     it = NULL;
619     while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
620         nasm_free((void *)key);
621         while (m) {
622             MMacro *nm = m->next;
623             free_mmacro(m);
624             m = nm;
625         }
626     }
627     hash_free(mmt);
628 }
629
630 static void free_macros(void)
631 {
632     free_smacro_table(&smacros);
633     free_mmacro_table(&mmacros);
634 }
635
636 /*
637  * Initialize the hash tables
638  */
639 static void init_macros(void)
640 {
641     hash_init(&smacros, HASH_LARGE);
642     hash_init(&mmacros, HASH_LARGE);
643 }
644
645 /*
646  * Pop the context stack.
647  */
648 static void ctx_pop(void)
649 {
650     Context *c = cstk;
651
652     cstk = cstk->next;
653     free_smacro_table(&c->localmac);
654     nasm_free(c->name);
655     nasm_free(c);
656 }
657
658 /*
659  * Search for a key in the hash index; adding it if necessary
660  * (in which case we initialize the data pointer to NULL.)
661  */
662 static void **
663 hash_findi_add(struct hash_table *hash, const char *str)
664 {
665     struct hash_insert hi;
666     void **r;
667     char *strx;
668
669     r = hash_findi(hash, str, &hi);
670     if (r)
671         return r;
672
673     strx = nasm_strdup(str);    /* Use a more efficient allocator here? */
674     return hash_add(&hi, strx, NULL);
675 }
676
677 /*
678  * Like hash_findi, but returns the data element rather than a pointer
679  * to it.  Used only when not adding a new element, hence no third
680  * argument.
681  */
682 static void *
683 hash_findix(struct hash_table *hash, const char *str)
684 {
685     void **p;
686
687     p = hash_findi(hash, str, NULL);
688     return p ? *p : NULL;
689 }
690
691 #define BUF_DELTA 512
692 /*
693  * Read a line from the top file in istk, handling multiple CR/LFs
694  * at the end of the line read, and handling spurious ^Zs. Will
695  * return lines from the standard macro set if this has not already
696  * been done.
697  */
698 static char *read_line(void)
699 {
700     char *buffer, *p, *q;
701     int bufsize, continued_count;
702
703     if (stdmacpos) {
704         unsigned char c;
705         const unsigned char *p = stdmacpos;
706         char *ret, *q;
707         size_t len = 0;
708         while ((c = *p++)) {
709             if (c >= 0x80)
710                 len += pp_directives_len[c-0x80]+1;
711             else
712                 len++;
713         }
714         ret = nasm_malloc(len+1);
715         q = ret;
716         while ((c = *stdmacpos++)) {
717             if (c >= 0x80) {
718                 memcpy(q, pp_directives[c-0x80], pp_directives_len[c-0x80]);
719                 q += pp_directives_len[c-0x80];
720                 *q++ = ' ';
721             } else {
722                 *q++ = c;
723             }
724         }
725         stdmacpos = p;
726         *q = '\0';
727
728         if (!*stdmacpos) {
729             /* This was the last of the standard macro chain... */
730             stdmacpos = NULL;
731             if (any_extrastdmac) {
732                 stdmacpos = extrastdmac;
733                 any_extrastdmac = false;
734             } else if (do_predef) {
735                 Line *pd, *l;
736                 Token *head, **tail, *t;
737
738                 /*
739                  * Nasty hack: here we push the contents of
740                  * `predef' on to the top-level expansion stack,
741                  * since this is the most convenient way to
742                  * implement the pre-include and pre-define
743                  * features.
744                  */
745                 for (pd = predef; pd; pd = pd->next) {
746                     head = NULL;
747                     tail = &head;
748                     for (t = pd->first; t; t = t->next) {
749                         *tail = new_Token(NULL, t->type, t->text, 0);
750                         tail = &(*tail)->next;
751                     }
752                     l = nasm_malloc(sizeof(Line));
753                     l->next = istk->expansion;
754                     l->first = head;
755                     l->finishes = NULL;
756                     istk->expansion = l;
757                 }
758                 do_predef = false;
759             }
760         }
761         return ret;
762     }
763
764     bufsize = BUF_DELTA;
765     buffer = nasm_malloc(BUF_DELTA);
766     p = buffer;
767     continued_count = 0;
768     while (1) {
769         q = fgets(p, bufsize - (p - buffer), istk->fp);
770         if (!q)
771             break;
772         p += strlen(p);
773         if (p > buffer && p[-1] == '\n') {
774             /* Convert backslash-CRLF line continuation sequences into
775                nothing at all (for DOS and Windows) */
776             if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
777                 p -= 3;
778                 *p = 0;
779                 continued_count++;
780             }
781             /* Also convert backslash-LF line continuation sequences into
782                nothing at all (for Unix) */
783             else if (((p - 1) > buffer) && (p[-2] == '\\')) {
784                 p -= 2;
785                 *p = 0;
786                 continued_count++;
787             } else {
788                 break;
789             }
790         }
791         if (p - buffer > bufsize - 10) {
792             int32_t offset = p - buffer;
793             bufsize += BUF_DELTA;
794             buffer = nasm_realloc(buffer, bufsize);
795             p = buffer + offset;        /* prevent stale-pointer problems */
796         }
797     }
798
799     if (!q && p == buffer) {
800         nasm_free(buffer);
801         return NULL;
802     }
803
804     src_set_linnum(src_get_linnum() + istk->lineinc +
805                    (continued_count * istk->lineinc));
806
807     /*
808      * Play safe: remove CRs as well as LFs, if any of either are
809      * present at the end of the line.
810      */
811     while (--p >= buffer && (*p == '\n' || *p == '\r'))
812         *p = '\0';
813
814     /*
815      * Handle spurious ^Z, which may be inserted into source files
816      * by some file transfer utilities.
817      */
818     buffer[strcspn(buffer, "\032")] = '\0';
819
820     list->line(LIST_READ, buffer);
821
822     return buffer;
823 }
824
825 /*
826  * Tokenize a line of text. This is a very simple process since we
827  * don't need to parse the value out of e.g. numeric tokens: we
828  * simply split one string into many.
829  */
830 static Token *tokenize(char *line)
831 {
832     char c, *p = line;
833     enum pp_token_type type;
834     Token *list = NULL;
835     Token *t, **tail = &list;
836
837     while (*line) {
838         p = line;
839         if (*p == '%') {
840             p++;
841             if (*p == '+' && !nasm_isdigit(p[1])) {
842                 p++;
843                 type = TOK_PASTE;
844             } else if (nasm_isdigit(*p) ||
845                        ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
846                 do {
847                     p++;
848                 }
849                 while (nasm_isdigit(*p));
850                 type = TOK_PREPROC_ID;
851             } else if (*p == '{') {
852                 p++;
853                 while (*p && *p != '}') {
854                     p[-1] = *p;
855                     p++;
856                 }
857                 p[-1] = '\0';
858                 if (*p)
859                     p++;
860                 type = TOK_PREPROC_ID;
861             } else if (*p == '[') {
862                 int lvl = 1;
863                 line += 2;      /* Skip the leading %[ */
864                 p++;
865                 while (lvl && (c = *p++)) {
866                     switch (c) {
867                     case ']':
868                         lvl--;
869                         break;
870                     case '%':
871                         if (*p == '[')
872                             lvl++;
873                         break;
874                     case '\'':
875                     case '\"':
876                     case '`':
877                         p = nasm_skip_string(p)+1;
878                         break;
879                     default:
880                         break;
881                     }
882                 }
883                 p--;
884                 if (*p)
885                     *p++ = '\0';
886                 if (lvl)
887                     error(ERR_NONFATAL, "unterminated %[ construct");
888                 type = TOK_INDIRECT;
889             } else if (*p == '?') {
890                 type = TOK_PREPROC_Q; /* %? */
891                 p++;
892                 if (*p == '?') {
893                     type = TOK_PREPROC_QQ; /* %?? */
894                     p++;
895                 }
896             } else if (isidchar(*p) ||
897                        ((*p == '!' || *p == '%' || *p == '$') &&
898                         isidchar(p[1]))) {
899                 do {
900                     p++;
901                 }
902                 while (isidchar(*p));
903                 type = TOK_PREPROC_ID;
904             } else {
905                 type = TOK_OTHER;
906                 if (*p == '%')
907                     p++;
908             }
909         } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
910             type = TOK_ID;
911             p++;
912             while (*p && isidchar(*p))
913                 p++;
914         } else if (*p == '\'' || *p == '"' || *p == '`') {
915             /*
916              * A string token.
917              */
918             type = TOK_STRING;
919             p = nasm_skip_string(p);
920
921             if (*p) {
922                 p++;
923             } else {
924                 error(ERR_WARNING|ERR_PASS1, "unterminated string");
925                 /* Handling unterminated strings by UNV */
926                 /* type = -1; */
927             }
928         } else if (p[0] == '$' && p[1] == '$') {
929             type = TOK_OTHER;   /* TOKEN_BASE */
930             p += 2;
931         } else if (isnumstart(*p)) {
932             bool is_hex = false;
933             bool is_float = false;
934             bool has_e = false;
935             char c, *r;
936
937             /*
938              * A numeric token.
939              */
940
941             if (*p == '$') {
942                 p++;
943                 is_hex = true;
944             }
945
946             for (;;) {
947                 c = *p++;
948
949                 if (!is_hex && (c == 'e' || c == 'E')) {
950                     has_e = true;
951                     if (*p == '+' || *p == '-') {
952                         /* e can only be followed by +/- if it is either a
953                            prefixed hex number or a floating-point number */
954                         p++;
955                         is_float = true;
956                     }
957                 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
958                     is_hex = true;
959                 } else if (c == 'P' || c == 'p') {
960                     is_float = true;
961                     if (*p == '+' || *p == '-')
962                         p++;
963                 } else if (isnumchar(c) || c == '_')
964                     ; /* just advance */
965                 else if (c == '.') {
966                     /* we need to deal with consequences of the legacy
967                        parser, like "1.nolist" being two tokens
968                        (TOK_NUMBER, TOK_ID) here; at least give it
969                        a shot for now.  In the future, we probably need
970                        a flex-based scanner with proper pattern matching
971                        to do it as well as it can be done.  Nothing in
972                        the world is going to help the person who wants
973                        0x123.p16 interpreted as two tokens, though. */
974                     r = p;
975                     while (*r == '_')
976                         r++;
977
978                     if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
979                         (!is_hex && (*r == 'e' || *r == 'E')) ||
980                         (*r == 'p' || *r == 'P')) {
981                         p = r;
982                         is_float = true;
983                     } else
984                         break;  /* Terminate the token */
985                 } else
986                     break;
987             }
988             p--;        /* Point to first character beyond number */
989
990             if (p == line+1 && *line == '$') {
991                 type = TOK_OTHER; /* TOKEN_HERE */
992             } else {
993                 if (has_e && !is_hex) {
994                     /* 1e13 is floating-point, but 1e13h is not */
995                     is_float = true;
996                 }
997
998                 type = is_float ? TOK_FLOAT : TOK_NUMBER;
999             }
1000         } else if (nasm_isspace(*p)) {
1001             type = TOK_WHITESPACE;
1002             p++;
1003             while (*p && nasm_isspace(*p))
1004                 p++;
1005             /*
1006              * Whitespace just before end-of-line is discarded by
1007              * pretending it's a comment; whitespace just before a
1008              * comment gets lumped into the comment.
1009              */
1010             if (!*p || *p == ';') {
1011                 type = TOK_COMMENT;
1012                 while (*p)
1013                     p++;
1014             }
1015         } else if (*p == ';') {
1016             type = TOK_COMMENT;
1017             while (*p)
1018                 p++;
1019         } else {
1020             /*
1021              * Anything else is an operator of some kind. We check
1022              * for all the double-character operators (>>, <<, //,
1023              * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1024              * else is a single-character operator.
1025              */
1026             type = TOK_OTHER;
1027             if ((p[0] == '>' && p[1] == '>') ||
1028                 (p[0] == '<' && p[1] == '<') ||
1029                 (p[0] == '/' && p[1] == '/') ||
1030                 (p[0] == '<' && p[1] == '=') ||
1031                 (p[0] == '>' && p[1] == '=') ||
1032                 (p[0] == '=' && p[1] == '=') ||
1033                 (p[0] == '!' && p[1] == '=') ||
1034                 (p[0] == '<' && p[1] == '>') ||
1035                 (p[0] == '&' && p[1] == '&') ||
1036                 (p[0] == '|' && p[1] == '|') ||
1037                 (p[0] == '^' && p[1] == '^')) {
1038                 p++;
1039             }
1040             p++;
1041         }
1042
1043         /* Handling unterminated string by UNV */
1044         /*if (type == -1)
1045           {
1046           *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1047           t->text[p-line] = *line;
1048           tail = &t->next;
1049           }
1050           else */
1051         if (type != TOK_COMMENT) {
1052             *tail = t = new_Token(NULL, type, line, p - line);
1053             tail = &t->next;
1054         }
1055         line = p;
1056     }
1057     return list;
1058 }
1059
1060 /*
1061  * this function allocates a new managed block of memory and
1062  * returns a pointer to the block.  The managed blocks are
1063  * deleted only all at once by the delete_Blocks function.
1064  */
1065 static void *new_Block(size_t size)
1066 {
1067     Blocks *b = &blocks;
1068
1069     /* first, get to the end of the linked list */
1070     while (b->next)
1071         b = b->next;
1072     /* now allocate the requested chunk */
1073     b->chunk = nasm_malloc(size);
1074
1075     /* now allocate a new block for the next request */
1076     b->next = nasm_malloc(sizeof(Blocks));
1077     /* and initialize the contents of the new block */
1078     b->next->next = NULL;
1079     b->next->chunk = NULL;
1080     return b->chunk;
1081 }
1082
1083 /*
1084  * this function deletes all managed blocks of memory
1085  */
1086 static void delete_Blocks(void)
1087 {
1088     Blocks *a, *b = &blocks;
1089
1090     /*
1091      * keep in mind that the first block, pointed to by blocks
1092      * is a static and not dynamically allocated, so we don't
1093      * free it.
1094      */
1095     while (b) {
1096         if (b->chunk)
1097             nasm_free(b->chunk);
1098         a = b;
1099         b = b->next;
1100         if (a != &blocks)
1101             nasm_free(a);
1102     }
1103 }
1104
1105 /*
1106  *  this function creates a new Token and passes a pointer to it
1107  *  back to the caller.  It sets the type and text elements, and
1108  *  also the a.mac and next elements to NULL.
1109  */
1110 static Token *new_Token(Token * next, enum pp_token_type type,
1111                         const char *text, int txtlen)
1112 {
1113     Token *t;
1114     int i;
1115
1116     if (!freeTokens) {
1117         freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1118         for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1119             freeTokens[i].next = &freeTokens[i + 1];
1120         freeTokens[i].next = NULL;
1121     }
1122     t = freeTokens;
1123     freeTokens = t->next;
1124     t->next = next;
1125     t->a.mac = NULL;
1126     t->type = type;
1127     if (type == TOK_WHITESPACE || !text) {
1128         t->text = NULL;
1129     } else {
1130         if (txtlen == 0)
1131             txtlen = strlen(text);
1132         t->text = nasm_malloc(txtlen+1);
1133         memcpy(t->text, text, txtlen);
1134         t->text[txtlen] = '\0';
1135     }
1136     return t;
1137 }
1138
1139 static Token *delete_Token(Token * t)
1140 {
1141     Token *next = t->next;
1142     nasm_free(t->text);
1143     t->next = freeTokens;
1144     freeTokens = t;
1145     return next;
1146 }
1147
1148 /*
1149  * Convert a line of tokens back into text.
1150  * If expand_locals is not zero, identifiers of the form "%$*xxx"
1151  * will be transformed into ..@ctxnum.xxx
1152  */
1153 static char *detoken(Token * tlist, bool expand_locals)
1154 {
1155     Token *t;
1156     int len;
1157     char *line, *p;
1158     const char *q;
1159
1160     len = 0;
1161     for (t = tlist; t; t = t->next) {
1162         if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1163             char *p = getenv(t->text + 2);
1164             nasm_free(t->text);
1165             if (p)
1166                 t->text = nasm_strdup(p);
1167             else
1168                 t->text = NULL;
1169         }
1170         /* Expand local macros here and not during preprocessing */
1171         if (expand_locals &&
1172             t->type == TOK_PREPROC_ID && t->text &&
1173             t->text[0] == '%' && t->text[1] == '$') {
1174             const char *q;
1175             char *p;
1176             Context *ctx = get_ctx(t->text, &q, false);
1177             if (ctx) {
1178                 char buffer[40];
1179                 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1180                 p = nasm_strcat(buffer, q);
1181                 nasm_free(t->text);
1182                 t->text = p;
1183             }
1184         }
1185         if (t->type == TOK_WHITESPACE) {
1186             len++;
1187         } else if (t->text) {
1188             len += strlen(t->text);
1189         }
1190     }
1191     p = line = nasm_malloc(len + 1);
1192     for (t = tlist; t; t = t->next) {
1193         if (t->type == TOK_WHITESPACE) {
1194             *p++ = ' ';
1195         } else if (t->text) {
1196             q = t->text;
1197             while (*q)
1198                 *p++ = *q++;
1199         }
1200     }
1201     *p = '\0';
1202     return line;
1203 }
1204
1205 /*
1206  * A scanner, suitable for use by the expression evaluator, which
1207  * operates on a line of Tokens. Expects a pointer to a pointer to
1208  * the first token in the line to be passed in as its private_data
1209  * field.
1210  *
1211  * FIX: This really needs to be unified with stdscan.
1212  */
1213 static int ppscan(void *private_data, struct tokenval *tokval)
1214 {
1215     Token **tlineptr = private_data;
1216     Token *tline;
1217     char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1218
1219     do {
1220         tline = *tlineptr;
1221         *tlineptr = tline ? tline->next : NULL;
1222     }
1223     while (tline && (tline->type == TOK_WHITESPACE ||
1224                      tline->type == TOK_COMMENT));
1225
1226     if (!tline)
1227         return tokval->t_type = TOKEN_EOS;
1228
1229     tokval->t_charptr = tline->text;
1230
1231     if (tline->text[0] == '$' && !tline->text[1])
1232         return tokval->t_type = TOKEN_HERE;
1233     if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1234         return tokval->t_type = TOKEN_BASE;
1235
1236     if (tline->type == TOK_ID) {
1237         p = tokval->t_charptr = tline->text;
1238         if (p[0] == '$') {
1239             tokval->t_charptr++;
1240             return tokval->t_type = TOKEN_ID;
1241         }
1242
1243         for (r = p, s = ourcopy; *r; r++) {
1244             if (r >= p+MAX_KEYWORD)
1245                 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1246             *s++ = nasm_tolower(*r);
1247         }
1248         *s = '\0';
1249         /* right, so we have an identifier sitting in temp storage. now,
1250          * is it actually a register or instruction name, or what? */
1251         return nasm_token_hash(ourcopy, tokval);
1252     }
1253
1254     if (tline->type == TOK_NUMBER) {
1255         bool rn_error;
1256         tokval->t_integer = readnum(tline->text, &rn_error);
1257         tokval->t_charptr = tline->text;
1258         if (rn_error)
1259             return tokval->t_type = TOKEN_ERRNUM;
1260         else
1261             return tokval->t_type = TOKEN_NUM;
1262     }
1263
1264     if (tline->type == TOK_FLOAT) {
1265         return tokval->t_type = TOKEN_FLOAT;
1266     }
1267
1268     if (tline->type == TOK_STRING) {
1269         char bq, *ep;
1270
1271         bq = tline->text[0];
1272         tokval->t_charptr = tline->text;
1273         tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1274
1275         if (ep[0] != bq || ep[1] != '\0')
1276             return tokval->t_type = TOKEN_ERRSTR;
1277         else
1278             return tokval->t_type = TOKEN_STR;
1279     }
1280
1281     if (tline->type == TOK_OTHER) {
1282         if (!strcmp(tline->text, "<<"))
1283             return tokval->t_type = TOKEN_SHL;
1284         if (!strcmp(tline->text, ">>"))
1285             return tokval->t_type = TOKEN_SHR;
1286         if (!strcmp(tline->text, "//"))
1287             return tokval->t_type = TOKEN_SDIV;
1288         if (!strcmp(tline->text, "%%"))
1289             return tokval->t_type = TOKEN_SMOD;
1290         if (!strcmp(tline->text, "=="))
1291             return tokval->t_type = TOKEN_EQ;
1292         if (!strcmp(tline->text, "<>"))
1293             return tokval->t_type = TOKEN_NE;
1294         if (!strcmp(tline->text, "!="))
1295             return tokval->t_type = TOKEN_NE;
1296         if (!strcmp(tline->text, "<="))
1297             return tokval->t_type = TOKEN_LE;
1298         if (!strcmp(tline->text, ">="))
1299             return tokval->t_type = TOKEN_GE;
1300         if (!strcmp(tline->text, "&&"))
1301             return tokval->t_type = TOKEN_DBL_AND;
1302         if (!strcmp(tline->text, "^^"))
1303             return tokval->t_type = TOKEN_DBL_XOR;
1304         if (!strcmp(tline->text, "||"))
1305             return tokval->t_type = TOKEN_DBL_OR;
1306     }
1307
1308     /*
1309      * We have no other options: just return the first character of
1310      * the token text.
1311      */
1312     return tokval->t_type = tline->text[0];
1313 }
1314
1315 /*
1316  * Compare a string to the name of an existing macro; this is a
1317  * simple wrapper which calls either strcmp or nasm_stricmp
1318  * depending on the value of the `casesense' parameter.
1319  */
1320 static int mstrcmp(const char *p, const char *q, bool casesense)
1321 {
1322     return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1323 }
1324
1325 /*
1326  * Compare a string to the name of an existing macro; this is a
1327  * simple wrapper which calls either strcmp or nasm_stricmp
1328  * depending on the value of the `casesense' parameter.
1329  */
1330 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1331 {
1332     return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1333 }
1334
1335 /*
1336  * Return the Context structure associated with a %$ token. Return
1337  * NULL, having _already_ reported an error condition, if the
1338  * context stack isn't deep enough for the supplied number of $
1339  * signs.
1340  * If all_contexts == true, contexts that enclose current are
1341  * also scanned for such smacro, until it is found; if not -
1342  * only the context that directly results from the number of $'s
1343  * in variable's name.
1344  *
1345  * If "namep" is non-NULL, set it to the pointer to the macro name
1346  * tail, i.e. the part beyond %$...
1347  */
1348 static Context *get_ctx(const char *name, const char **namep,
1349                         bool all_contexts)
1350 {
1351     Context *ctx;
1352     SMacro *m;
1353     int i;
1354
1355     if (namep)
1356         *namep = name;
1357
1358     if (!name || name[0] != '%' || name[1] != '$')
1359         return NULL;
1360
1361     if (!cstk) {
1362         error(ERR_NONFATAL, "`%s': context stack is empty", name);
1363         return NULL;
1364     }
1365
1366     name += 2;
1367     ctx = cstk;
1368     i = 0;
1369     while (ctx && *name == '$') {
1370         name++;
1371         i++;
1372         ctx = ctx->next;
1373     }
1374     if (!ctx) {
1375         error(ERR_NONFATAL, "`%s': context stack is only"
1376               " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1377         return NULL;
1378     }
1379
1380     if (namep)
1381         *namep = name;
1382
1383     if (!all_contexts)
1384         return ctx;
1385
1386     do {
1387         /* Search for this smacro in found context */
1388         m = hash_findix(&ctx->localmac, name);
1389         while (m) {
1390             if (!mstrcmp(m->name, name, m->casesense))
1391                 return ctx;
1392             m = m->next;
1393         }
1394         ctx = ctx->next;
1395     }
1396     while (ctx);
1397     return NULL;
1398 }
1399
1400 /*
1401  * Check to see if a file is already in a string list
1402  */
1403 static bool in_list(const StrList *list, const char *str)
1404 {
1405     while (list) {
1406         if (!strcmp(list->str, str))
1407             return true;
1408         list = list->next;
1409     }
1410     return false;
1411 }
1412
1413 /*
1414  * Open an include file. This routine must always return a valid
1415  * file pointer if it returns - it's responsible for throwing an
1416  * ERR_FATAL and bombing out completely if not. It should also try
1417  * the include path one by one until it finds the file or reaches
1418  * the end of the path.
1419  */
1420 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1421                        bool missing_ok)
1422 {
1423     FILE *fp;
1424     char *prefix = "";
1425     IncPath *ip = ipath;
1426     int len = strlen(file);
1427     size_t prefix_len = 0;
1428     StrList *sl;
1429
1430     while (1) {
1431         sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1432         memcpy(sl->str, prefix, prefix_len);
1433         memcpy(sl->str+prefix_len, file, len+1);
1434         fp = fopen(sl->str, "r");
1435         if (fp && dhead && !in_list(*dhead, sl->str)) {
1436             sl->next = NULL;
1437             **dtail = sl;
1438             *dtail = &sl->next;
1439         } else {
1440             nasm_free(sl);
1441         }
1442         if (fp)
1443             return fp;
1444         if (!ip) {
1445             if (!missing_ok)
1446                 break;
1447             prefix = NULL;
1448         } else {
1449             prefix = ip->path;
1450             ip = ip->next;
1451         }
1452         if (prefix) {
1453             prefix_len = strlen(prefix);
1454         } else {
1455             /* -MG given and file not found */
1456             if (dhead && !in_list(*dhead, file)) {
1457                 sl = nasm_malloc(len+1+sizeof sl->next);
1458                 sl->next = NULL;
1459                 strcpy(sl->str, file);
1460                 **dtail = sl;
1461                 *dtail = &sl->next;
1462             }
1463             return NULL;
1464         }
1465     }
1466
1467     error(ERR_FATAL, "unable to open include file `%s'", file);
1468     return NULL;                /* never reached - placate compilers */
1469 }
1470
1471 /*
1472  * Determine if we should warn on defining a single-line macro of
1473  * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1474  * return true if _any_ single-line macro of that name is defined.
1475  * Otherwise, will return true if a single-line macro with either
1476  * `nparam' or no parameters is defined.
1477  *
1478  * If a macro with precisely the right number of parameters is
1479  * defined, or nparam is -1, the address of the definition structure
1480  * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1481  * is NULL, no action will be taken regarding its contents, and no
1482  * error will occur.
1483  *
1484  * Note that this is also called with nparam zero to resolve
1485  * `ifdef'.
1486  *
1487  * If you already know which context macro belongs to, you can pass
1488  * the context pointer as first parameter; if you won't but name begins
1489  * with %$ the context will be automatically computed. If all_contexts
1490  * is true, macro will be searched in outer contexts as well.
1491  */
1492 static bool
1493 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1494                bool nocase)
1495 {
1496     struct hash_table *smtbl;
1497     SMacro *m;
1498
1499     if (ctx) {
1500         smtbl = &ctx->localmac;
1501     } else if (name[0] == '%' && name[1] == '$') {
1502         if (cstk)
1503             ctx = get_ctx(name, &name, false);
1504         if (!ctx)
1505             return false;       /* got to return _something_ */
1506         smtbl = &ctx->localmac;
1507     } else {
1508         smtbl = &smacros;
1509     }
1510     m = (SMacro *) hash_findix(smtbl, name);
1511
1512     while (m) {
1513         if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1514             (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1515             if (defn) {
1516                 if (nparam == (int) m->nparam || nparam == -1)
1517                     *defn = m;
1518                 else
1519                     *defn = NULL;
1520             }
1521             return true;
1522         }
1523         m = m->next;
1524     }
1525
1526     return false;
1527 }
1528
1529 /*
1530  * Count and mark off the parameters in a multi-line macro call.
1531  * This is called both from within the multi-line macro expansion
1532  * code, and also to mark off the default parameters when provided
1533  * in a %macro definition line.
1534  */
1535 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1536 {
1537     int paramsize, brace;
1538
1539     *nparam = paramsize = 0;
1540     *params = NULL;
1541     while (t) {
1542         /* +1: we need space for the final NULL */
1543         if (*nparam+1 >= paramsize) {
1544             paramsize += PARAM_DELTA;
1545             *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1546         }
1547         skip_white_(t);
1548         brace = false;
1549         if (tok_is_(t, "{"))
1550             brace = true;
1551         (*params)[(*nparam)++] = t;
1552         while (tok_isnt_(t, brace ? "}" : ","))
1553             t = t->next;
1554         if (t) {                /* got a comma/brace */
1555             t = t->next;
1556             if (brace) {
1557                 /*
1558                  * Now we've found the closing brace, look further
1559                  * for the comma.
1560                  */
1561                 skip_white_(t);
1562                 if (tok_isnt_(t, ",")) {
1563                     error(ERR_NONFATAL,
1564                           "braces do not enclose all of macro parameter");
1565                     while (tok_isnt_(t, ","))
1566                         t = t->next;
1567                 }
1568                 if (t)
1569                     t = t->next;        /* eat the comma */
1570             }
1571         }
1572     }
1573 }
1574
1575 /*
1576  * Determine whether one of the various `if' conditions is true or
1577  * not.
1578  *
1579  * We must free the tline we get passed.
1580  */
1581 static bool if_condition(Token * tline, enum preproc_token ct)
1582 {
1583     enum pp_conditional i = PP_COND(ct);
1584     bool j;
1585     Token *t, *tt, **tptr, *origline;
1586     struct tokenval tokval;
1587     expr *evalresult;
1588     enum pp_token_type needtype;
1589
1590     origline = tline;
1591
1592     switch (i) {
1593     case PPC_IFCTX:
1594         j = false;              /* have we matched yet? */
1595         while (true) {
1596             skip_white_(tline);
1597             if (!tline)
1598                 break;
1599             if (tline->type != TOK_ID) {
1600                 error(ERR_NONFATAL,
1601                       "`%s' expects context identifiers", pp_directives[ct]);
1602                 free_tlist(origline);
1603                 return -1;
1604             }
1605             if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1606                 j = true;
1607             tline = tline->next;
1608         }
1609         break;
1610
1611     case PPC_IFDEF:
1612         j = false;              /* have we matched yet? */
1613         while (tline) {
1614             skip_white_(tline);
1615             if (!tline || (tline->type != TOK_ID &&
1616                            (tline->type != TOK_PREPROC_ID ||
1617                             tline->text[1] != '$'))) {
1618                 error(ERR_NONFATAL,
1619                       "`%s' expects macro identifiers", pp_directives[ct]);
1620                 goto fail;
1621             }
1622             if (smacro_defined(NULL, tline->text, 0, NULL, true))
1623                 j = true;
1624             tline = tline->next;
1625         }
1626         break;
1627
1628     case PPC_IFIDN:
1629     case PPC_IFIDNI:
1630         tline = expand_smacro(tline);
1631         t = tt = tline;
1632         while (tok_isnt_(tt, ","))
1633             tt = tt->next;
1634         if (!tt) {
1635             error(ERR_NONFATAL,
1636                   "`%s' expects two comma-separated arguments",
1637                   pp_directives[ct]);
1638             goto fail;
1639         }
1640         tt = tt->next;
1641         j = true;               /* assume equality unless proved not */
1642         while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1643             if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1644                 error(ERR_NONFATAL, "`%s': more than one comma on line",
1645                       pp_directives[ct]);
1646                 goto fail;
1647             }
1648             if (t->type == TOK_WHITESPACE) {
1649                 t = t->next;
1650                 continue;
1651             }
1652             if (tt->type == TOK_WHITESPACE) {
1653                 tt = tt->next;
1654                 continue;
1655             }
1656             if (tt->type != t->type) {
1657                 j = false;      /* found mismatching tokens */
1658                 break;
1659             }
1660             /* When comparing strings, need to unquote them first */
1661             if (t->type == TOK_STRING) {
1662                 size_t l1 = nasm_unquote(t->text, NULL);
1663                 size_t l2 = nasm_unquote(tt->text, NULL);
1664
1665                 if (l1 != l2) {
1666                     j = false;
1667                     break;
1668                 }
1669                 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1670                     j = false;
1671                     break;
1672                 }
1673             } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1674                 j = false;      /* found mismatching tokens */
1675                 break;
1676             }
1677
1678             t = t->next;
1679             tt = tt->next;
1680         }
1681         if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1682             j = false;          /* trailing gunk on one end or other */
1683         break;
1684
1685     case PPC_IFMACRO:
1686     {
1687         bool found = false;
1688         MMacro searching, *mmac;
1689
1690         skip_white_(tline);
1691         tline = expand_id(tline);
1692         if (!tok_type_(tline, TOK_ID)) {
1693             error(ERR_NONFATAL,
1694                   "`%s' expects a macro name", pp_directives[ct]);
1695             goto fail;
1696         }
1697         searching.name = nasm_strdup(tline->text);
1698         searching.casesense = true;
1699         searching.plus = false;
1700         searching.nolist = false;
1701         searching.in_progress = 0;
1702         searching.max_depth = 0;
1703         searching.rep_nest = NULL;
1704         searching.nparam_min = 0;
1705         searching.nparam_max = INT_MAX;
1706         tline = expand_smacro(tline->next);
1707         skip_white_(tline);
1708         if (!tline) {
1709         } else if (!tok_type_(tline, TOK_NUMBER)) {
1710             error(ERR_NONFATAL,
1711                   "`%s' expects a parameter count or nothing",
1712                   pp_directives[ct]);
1713         } else {
1714             searching.nparam_min = searching.nparam_max =
1715                 readnum(tline->text, &j);
1716             if (j)
1717                 error(ERR_NONFATAL,
1718                       "unable to parse parameter count `%s'",
1719                       tline->text);
1720         }
1721         if (tline && tok_is_(tline->next, "-")) {
1722             tline = tline->next->next;
1723             if (tok_is_(tline, "*"))
1724                 searching.nparam_max = INT_MAX;
1725             else if (!tok_type_(tline, TOK_NUMBER))
1726                 error(ERR_NONFATAL,
1727                       "`%s' expects a parameter count after `-'",
1728                       pp_directives[ct]);
1729             else {
1730                 searching.nparam_max = readnum(tline->text, &j);
1731                 if (j)
1732                     error(ERR_NONFATAL,
1733                           "unable to parse parameter count `%s'",
1734                           tline->text);
1735                 if (searching.nparam_min > searching.nparam_max)
1736                     error(ERR_NONFATAL,
1737                           "minimum parameter count exceeds maximum");
1738             }
1739         }
1740         if (tline && tok_is_(tline->next, "+")) {
1741             tline = tline->next;
1742             searching.plus = true;
1743         }
1744         mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1745         while (mmac) {
1746             if (!strcmp(mmac->name, searching.name) &&
1747                 (mmac->nparam_min <= searching.nparam_max
1748                  || searching.plus)
1749                 && (searching.nparam_min <= mmac->nparam_max
1750                     || mmac->plus)) {
1751                 found = true;
1752                 break;
1753             }
1754             mmac = mmac->next;
1755         }
1756         if (tline && tline->next)
1757             error(ERR_WARNING|ERR_PASS1,
1758                   "trailing garbage after %%ifmacro ignored");
1759         nasm_free(searching.name);
1760         j = found;
1761         break;
1762     }
1763
1764     case PPC_IFID:
1765         needtype = TOK_ID;
1766         goto iftype;
1767     case PPC_IFNUM:
1768         needtype = TOK_NUMBER;
1769         goto iftype;
1770     case PPC_IFSTR:
1771         needtype = TOK_STRING;
1772         goto iftype;
1773
1774     iftype:
1775         t = tline = expand_smacro(tline);
1776
1777         while (tok_type_(t, TOK_WHITESPACE) ||
1778                (needtype == TOK_NUMBER &&
1779                 tok_type_(t, TOK_OTHER) &&
1780                 (t->text[0] == '-' || t->text[0] == '+') &&
1781                 !t->text[1]))
1782             t = t->next;
1783
1784         j = tok_type_(t, needtype);
1785         break;
1786
1787     case PPC_IFTOKEN:
1788         t = tline = expand_smacro(tline);
1789         while (tok_type_(t, TOK_WHITESPACE))
1790             t = t->next;
1791
1792         j = false;
1793         if (t) {
1794             t = t->next;        /* Skip the actual token */
1795             while (tok_type_(t, TOK_WHITESPACE))
1796                 t = t->next;
1797             j = !t;             /* Should be nothing left */
1798         }
1799         break;
1800
1801     case PPC_IFEMPTY:
1802         t = tline = expand_smacro(tline);
1803         while (tok_type_(t, TOK_WHITESPACE))
1804             t = t->next;
1805
1806         j = !t;                 /* Should be empty */
1807         break;
1808
1809     case PPC_IF:
1810         t = tline = expand_smacro(tline);
1811         tptr = &t;
1812         tokval.t_type = TOKEN_INVALID;
1813         evalresult = evaluate(ppscan, tptr, &tokval,
1814                               NULL, pass | CRITICAL, error, NULL);
1815         if (!evalresult)
1816             return -1;
1817         if (tokval.t_type)
1818             error(ERR_WARNING|ERR_PASS1,
1819                   "trailing garbage after expression ignored");
1820         if (!is_simple(evalresult)) {
1821             error(ERR_NONFATAL,
1822                   "non-constant value given to `%s'", pp_directives[ct]);
1823             goto fail;
1824         }
1825         j = reloc_value(evalresult) != 0;
1826         break;
1827
1828     default:
1829         error(ERR_FATAL,
1830               "preprocessor directive `%s' not yet implemented",
1831               pp_directives[ct]);
1832         goto fail;
1833     }
1834
1835     free_tlist(origline);
1836     return j ^ PP_NEGATIVE(ct);
1837
1838 fail:
1839     free_tlist(origline);
1840     return -1;
1841 }
1842
1843 /*
1844  * Common code for defining an smacro
1845  */
1846 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1847                           int nparam, Token *expansion)
1848 {
1849     SMacro *smac, **smhead;
1850     struct hash_table *smtbl;
1851
1852     if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1853         if (!smac) {
1854             error(ERR_WARNING|ERR_PASS1,
1855                   "single-line macro `%s' defined both with and"
1856                   " without parameters", mname);
1857
1858             /* Some instances of the old code considered this a failure,
1859                some others didn't.  What is the right thing to do here? */
1860             free_tlist(expansion);
1861             return false;       /* Failure */
1862         } else {
1863             /*
1864              * We're redefining, so we have to take over an
1865              * existing SMacro structure. This means freeing
1866              * what was already in it.
1867              */
1868             nasm_free(smac->name);
1869             free_tlist(smac->expansion);
1870         }
1871     } else {
1872         smtbl  = ctx ? &ctx->localmac : &smacros;
1873         smhead = (SMacro **) hash_findi_add(smtbl, mname);
1874         smac = nasm_malloc(sizeof(SMacro));
1875         smac->next = *smhead;
1876         *smhead = smac;
1877     }
1878     smac->name = nasm_strdup(mname);
1879     smac->casesense = casesense;
1880     smac->nparam = nparam;
1881     smac->expansion = expansion;
1882     smac->in_progress = false;
1883     return true;                /* Success */
1884 }
1885
1886 /*
1887  * Undefine an smacro
1888  */
1889 static void undef_smacro(Context *ctx, const char *mname)
1890 {
1891     SMacro **smhead, *s, **sp;
1892     struct hash_table *smtbl;
1893
1894     smtbl = ctx ? &ctx->localmac : &smacros;
1895     smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
1896
1897     if (smhead) {
1898         /*
1899          * We now have a macro name... go hunt for it.
1900          */
1901         sp = smhead;
1902         while ((s = *sp) != NULL) {
1903             if (!mstrcmp(s->name, mname, s->casesense)) {
1904                 *sp = s->next;
1905                 nasm_free(s->name);
1906                 free_tlist(s->expansion);
1907                 nasm_free(s);
1908             } else {
1909                 sp = &s->next;
1910             }
1911         }
1912     }
1913 }
1914
1915 /*
1916  * Parse a mmacro specification.
1917  */
1918 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
1919 {
1920     bool err;
1921
1922     tline = tline->next;
1923     skip_white_(tline);
1924     tline = expand_id(tline);
1925     if (!tok_type_(tline, TOK_ID)) {
1926         error(ERR_NONFATAL, "`%s' expects a macro name", directive);
1927         return false;
1928     }
1929
1930     def->prev = NULL;
1931     def->name = nasm_strdup(tline->text);
1932     def->plus = false;
1933     def->nolist = false;
1934     def->in_progress = 0;
1935     def->rep_nest = NULL;
1936     def->nparam_min = 0;
1937     def->nparam_max = 0;
1938
1939     tline = expand_smacro(tline->next);
1940     skip_white_(tline);
1941     if (!tok_type_(tline, TOK_NUMBER)) {
1942         error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
1943     } else {
1944         def->nparam_min = def->nparam_max =
1945             readnum(tline->text, &err);
1946         if (err)
1947             error(ERR_NONFATAL,
1948                   "unable to parse parameter count `%s'", tline->text);
1949     }
1950     if (tline && tok_is_(tline->next, "-")) {
1951         tline = tline->next->next;
1952         if (tok_is_(tline, "*")) {
1953             def->nparam_max = INT_MAX;
1954         } else if (!tok_type_(tline, TOK_NUMBER)) {
1955             error(ERR_NONFATAL,
1956                   "`%s' expects a parameter count after `-'", directive);
1957         } else {
1958             def->nparam_max = readnum(tline->text, &err);
1959             if (err) {
1960                 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
1961                       tline->text);
1962             }
1963             if (def->nparam_min > def->nparam_max) {
1964                 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
1965             }
1966         }
1967     }
1968     if (tline && tok_is_(tline->next, "+")) {
1969         tline = tline->next;
1970         def->plus = true;
1971     }
1972     if (tline && tok_type_(tline->next, TOK_ID) &&
1973         !nasm_stricmp(tline->next->text, ".nolist")) {
1974         tline = tline->next;
1975         def->nolist = true;
1976     }
1977         
1978     /*
1979      * Handle default parameters.
1980      */
1981     if (tline && tline->next) {
1982         def->dlist = tline->next;
1983         tline->next = NULL;
1984         count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
1985     } else {
1986         def->dlist = NULL;
1987         def->defaults = NULL;
1988     }
1989     def->expansion = NULL;
1990
1991     if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
1992         !def->plus)
1993         error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
1994               "too many default macro parameters");
1995
1996     return true;
1997 }
1998
1999
2000 /*
2001  * Decode a size directive
2002  */
2003 static int parse_size(const char *str) {
2004     static const char *size_names[] =
2005         { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2006     static const int sizes[] =
2007         { 0, 1, 4, 16, 8, 10, 2, 32 };
2008
2009     return sizes[bsii(str, size_names, elements(size_names))+1];
2010 }
2011
2012 /*
2013  * nasm_unquote with error if the string contains NUL characters.
2014  * If the string contains NUL characters, issue an error and return
2015  * the C len, i.e. truncate at the NUL.
2016  */
2017 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
2018 {
2019     size_t len = nasm_unquote(qstr, NULL);
2020     size_t clen = strlen(qstr);
2021
2022     if (len != clen)
2023         error(ERR_NONFATAL, "NUL character in `%s' directive",
2024               pp_directives[directive]);
2025
2026     return clen;
2027 }
2028
2029 /**
2030  * find and process preprocessor directive in passed line
2031  * Find out if a line contains a preprocessor directive, and deal
2032  * with it if so.
2033  *
2034  * If a directive _is_ found, it is the responsibility of this routine
2035  * (and not the caller) to free_tlist() the line.
2036  *
2037  * @param tline a pointer to the current tokeninzed line linked list
2038  * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2039  *
2040  */
2041 static int do_directive(Token * tline)
2042 {
2043     enum preproc_token i;
2044     int j;
2045     bool err;
2046     int nparam;
2047     bool nolist;
2048     bool casesense;
2049     int k, m;
2050     int offset;
2051     char *p, *pp;
2052     const char *mname;
2053     Include *inc;
2054     Context *ctx;
2055     Cond *cond;
2056     MMacro *mmac, **mmhead;
2057     Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2058     Line *l;
2059     struct tokenval tokval;
2060     expr *evalresult;
2061     MMacro *tmp_defining;       /* Used when manipulating rep_nest */
2062     int64_t count;
2063     size_t len;
2064     int severity;
2065
2066     origline = tline;
2067
2068     skip_white_(tline);
2069     if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2070         (tline->text[1] == '%' || tline->text[1] == '$'
2071          || tline->text[1] == '!'))
2072         return NO_DIRECTIVE_FOUND;
2073
2074     i = pp_token_hash(tline->text);
2075
2076     /*
2077      * If we're in a non-emitting branch of a condition construct,
2078      * or walking to the end of an already terminated %rep block,
2079      * we should ignore all directives except for condition
2080      * directives.
2081      */
2082     if (((istk->conds && !emitting(istk->conds->state)) ||
2083          (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2084         return NO_DIRECTIVE_FOUND;
2085     }
2086
2087     /*
2088      * If we're defining a macro or reading a %rep block, we should
2089      * ignore all directives except for %macro/%imacro (which nest),
2090      * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2091      * If we're in a %rep block, another %rep nests, so should be let through.
2092      */
2093     if (defining && i != PP_MACRO && i != PP_IMACRO &&
2094         i != PP_RMACRO &&  i != PP_IRMACRO &&
2095         i != PP_ENDMACRO && i != PP_ENDM &&
2096         (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2097         return NO_DIRECTIVE_FOUND;
2098     }
2099
2100     if (defining) {
2101         if (i == PP_MACRO || i == PP_IMACRO ||
2102             i == PP_RMACRO || i == PP_IRMACRO) {
2103             nested_mac_count++;
2104             return NO_DIRECTIVE_FOUND;
2105         } else if (nested_mac_count > 0) {
2106             if (i == PP_ENDMACRO) {
2107                 nested_mac_count--;
2108                 return NO_DIRECTIVE_FOUND;
2109             }
2110         }
2111         if (!defining->name) {
2112             if (i == PP_REP) {
2113                 nested_rep_count++;
2114                 return NO_DIRECTIVE_FOUND;
2115             } else if (nested_rep_count > 0) {
2116                 if (i == PP_ENDREP) {
2117                     nested_rep_count--;
2118                     return NO_DIRECTIVE_FOUND;
2119                 }
2120             }
2121         }
2122     }
2123
2124     switch (i) {
2125     case PP_INVALID:
2126         error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2127               tline->text);
2128         return NO_DIRECTIVE_FOUND;      /* didn't get it */
2129
2130     case PP_STACKSIZE:
2131         /* Directive to tell NASM what the default stack size is. The
2132          * default is for a 16-bit stack, and this can be overriden with
2133          * %stacksize large.
2134          * the following form:
2135          *
2136          *      ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2137          */
2138         tline = tline->next;
2139         if (tline && tline->type == TOK_WHITESPACE)
2140             tline = tline->next;
2141         if (!tline || tline->type != TOK_ID) {
2142             error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2143             free_tlist(origline);
2144             return DIRECTIVE_FOUND;
2145         }
2146         if (nasm_stricmp(tline->text, "flat") == 0) {
2147             /* All subsequent ARG directives are for a 32-bit stack */
2148             StackSize = 4;
2149             StackPointer = "ebp";
2150             ArgOffset = 8;
2151             LocalOffset = 0;
2152         } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2153             /* All subsequent ARG directives are for a 64-bit stack */
2154             StackSize = 8;
2155             StackPointer = "rbp";
2156             ArgOffset = 8;
2157             LocalOffset = 0;
2158         } else if (nasm_stricmp(tline->text, "large") == 0) {
2159             /* All subsequent ARG directives are for a 16-bit stack,
2160              * far function call.
2161              */
2162             StackSize = 2;
2163             StackPointer = "bp";
2164             ArgOffset = 4;
2165             LocalOffset = 0;
2166         } else if (nasm_stricmp(tline->text, "small") == 0) {
2167             /* All subsequent ARG directives are for a 16-bit stack,
2168              * far function call. We don't support near functions.
2169              */
2170             StackSize = 2;
2171             StackPointer = "bp";
2172             ArgOffset = 6;
2173             LocalOffset = 0;
2174         } else {
2175             error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2176             free_tlist(origline);
2177             return DIRECTIVE_FOUND;
2178         }
2179         free_tlist(origline);
2180         return DIRECTIVE_FOUND;
2181
2182     case PP_ARG:
2183         /* TASM like ARG directive to define arguments to functions, in
2184          * the following form:
2185          *
2186          *      ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2187          */
2188         offset = ArgOffset;
2189         do {
2190             char *arg, directive[256];
2191             int size = StackSize;
2192
2193             /* Find the argument name */
2194             tline = tline->next;
2195             if (tline && tline->type == TOK_WHITESPACE)
2196                 tline = tline->next;
2197             if (!tline || tline->type != TOK_ID) {
2198                 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2199                 free_tlist(origline);
2200                 return DIRECTIVE_FOUND;
2201             }
2202             arg = tline->text;
2203
2204             /* Find the argument size type */
2205             tline = tline->next;
2206             if (!tline || tline->type != TOK_OTHER
2207                 || tline->text[0] != ':') {
2208                 error(ERR_NONFATAL,
2209                       "Syntax error processing `%%arg' directive");
2210                 free_tlist(origline);
2211                 return DIRECTIVE_FOUND;
2212             }
2213             tline = tline->next;
2214             if (!tline || tline->type != TOK_ID) {
2215                 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2216                 free_tlist(origline);
2217                 return DIRECTIVE_FOUND;
2218             }
2219
2220             /* Allow macro expansion of type parameter */
2221             tt = tokenize(tline->text);
2222             tt = expand_smacro(tt);
2223             size = parse_size(tt->text);
2224             if (!size) {
2225                 error(ERR_NONFATAL,
2226                       "Invalid size type for `%%arg' missing directive");
2227                 free_tlist(tt);
2228                 free_tlist(origline);
2229                 return DIRECTIVE_FOUND;
2230             }
2231             free_tlist(tt);
2232
2233             /* Round up to even stack slots */
2234             size = (size+StackSize-1) & ~(StackSize-1);
2235
2236             /* Now define the macro for the argument */
2237             snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2238                      arg, StackPointer, offset);
2239             do_directive(tokenize(directive));
2240             offset += size;
2241
2242             /* Move to the next argument in the list */
2243             tline = tline->next;
2244             if (tline && tline->type == TOK_WHITESPACE)
2245                 tline = tline->next;
2246         } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2247         ArgOffset = offset;
2248         free_tlist(origline);
2249         return DIRECTIVE_FOUND;
2250
2251     case PP_LOCAL:
2252         /* TASM like LOCAL directive to define local variables for a
2253          * function, in the following form:
2254          *
2255          *      LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2256          *
2257          * The '= LocalSize' at the end is ignored by NASM, but is
2258          * required by TASM to define the local parameter size (and used
2259          * by the TASM macro package).
2260          */
2261         offset = LocalOffset;
2262         do {
2263             char *local, directive[256];
2264             int size = StackSize;
2265
2266             /* Find the argument name */
2267             tline = tline->next;
2268             if (tline && tline->type == TOK_WHITESPACE)
2269                 tline = tline->next;
2270             if (!tline || tline->type != TOK_ID) {
2271                 error(ERR_NONFATAL,
2272                       "`%%local' missing argument parameter");
2273                 free_tlist(origline);
2274                 return DIRECTIVE_FOUND;
2275             }
2276             local = tline->text;
2277
2278             /* Find the argument size type */
2279             tline = tline->next;
2280             if (!tline || tline->type != TOK_OTHER
2281                 || tline->text[0] != ':') {
2282                 error(ERR_NONFATAL,
2283                       "Syntax error processing `%%local' directive");
2284                 free_tlist(origline);
2285                 return DIRECTIVE_FOUND;
2286             }
2287             tline = tline->next;
2288             if (!tline || tline->type != TOK_ID) {
2289                 error(ERR_NONFATAL,
2290                       "`%%local' missing size type parameter");
2291                 free_tlist(origline);
2292                 return DIRECTIVE_FOUND;
2293             }
2294
2295             /* Allow macro expansion of type parameter */
2296             tt = tokenize(tline->text);
2297             tt = expand_smacro(tt);
2298             size = parse_size(tt->text);
2299             if (!size) {
2300                 error(ERR_NONFATAL,
2301                       "Invalid size type for `%%local' missing directive");
2302                 free_tlist(tt);
2303                 free_tlist(origline);
2304                 return DIRECTIVE_FOUND;
2305             }
2306             free_tlist(tt);
2307
2308             /* Round up to even stack slots */
2309             size = (size+StackSize-1) & ~(StackSize-1);
2310
2311             offset += size;     /* Negative offset, increment before */
2312
2313             /* Now define the macro for the argument */
2314             snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2315                      local, StackPointer, offset);
2316             do_directive(tokenize(directive));
2317
2318             /* Now define the assign to setup the enter_c macro correctly */
2319             snprintf(directive, sizeof(directive),
2320                      "%%assign %%$localsize %%$localsize+%d", size);
2321             do_directive(tokenize(directive));
2322
2323             /* Move to the next argument in the list */
2324             tline = tline->next;
2325             if (tline && tline->type == TOK_WHITESPACE)
2326                 tline = tline->next;
2327         } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2328         LocalOffset = offset;
2329         free_tlist(origline);
2330         return DIRECTIVE_FOUND;
2331
2332     case PP_CLEAR:
2333         if (tline->next)
2334             error(ERR_WARNING|ERR_PASS1,
2335                   "trailing garbage after `%%clear' ignored");
2336         free_macros();
2337         init_macros();
2338         free_tlist(origline);
2339         return DIRECTIVE_FOUND;
2340
2341     case PP_DEPEND:
2342         t = tline->next = expand_smacro(tline->next);
2343         skip_white_(t);
2344         if (!t || (t->type != TOK_STRING &&
2345                    t->type != TOK_INTERNAL_STRING)) {
2346             error(ERR_NONFATAL, "`%%depend' expects a file name");
2347             free_tlist(origline);
2348             return DIRECTIVE_FOUND;     /* but we did _something_ */
2349         }
2350         if (t->next)
2351             error(ERR_WARNING|ERR_PASS1,
2352                   "trailing garbage after `%%depend' ignored");
2353         p = t->text;
2354         if (t->type != TOK_INTERNAL_STRING)
2355             nasm_unquote_cstr(p, i);
2356         if (dephead && !in_list(*dephead, p)) {
2357             StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2358             sl->next = NULL;
2359             strcpy(sl->str, p);
2360             *deptail = sl;
2361             deptail = &sl->next;
2362         }
2363         free_tlist(origline);
2364         return DIRECTIVE_FOUND;
2365
2366     case PP_INCLUDE:
2367         t = tline->next = expand_smacro(tline->next);
2368         skip_white_(t);
2369
2370         if (!t || (t->type != TOK_STRING &&
2371                    t->type != TOK_INTERNAL_STRING)) {
2372             error(ERR_NONFATAL, "`%%include' expects a file name");
2373             free_tlist(origline);
2374             return DIRECTIVE_FOUND;     /* but we did _something_ */
2375         }
2376         if (t->next)
2377             error(ERR_WARNING|ERR_PASS1,
2378                   "trailing garbage after `%%include' ignored");
2379         p = t->text;
2380         if (t->type != TOK_INTERNAL_STRING)
2381             nasm_unquote_cstr(p, i);
2382         inc = nasm_malloc(sizeof(Include));
2383         inc->next = istk;
2384         inc->conds = NULL;
2385         inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2386         if (!inc->fp) {
2387             /* -MG given but file not found */
2388             nasm_free(inc);
2389         } else {
2390             inc->fname = src_set_fname(nasm_strdup(p));
2391             inc->lineno = src_set_linnum(0);
2392             inc->lineinc = 1;
2393             inc->expansion = NULL;
2394             inc->mstk = NULL;
2395             istk = inc;
2396             list->uplevel(LIST_INCLUDE);
2397         }
2398         free_tlist(origline);
2399         return DIRECTIVE_FOUND;
2400
2401     case PP_USE:
2402     {
2403         static macros_t *use_pkg;
2404         const char *pkg_macro;
2405
2406         tline = tline->next;
2407         skip_white_(tline);
2408         tline = expand_id(tline);
2409
2410         if (!tline || (tline->type != TOK_STRING &&
2411                        tline->type != TOK_INTERNAL_STRING &&
2412                        tline->type != TOK_ID)) {
2413             error(ERR_NONFATAL, "`%%use' expects a package name");
2414             free_tlist(origline);
2415             return DIRECTIVE_FOUND;     /* but we did _something_ */
2416         }
2417         if (tline->next)
2418             error(ERR_WARNING|ERR_PASS1,
2419                   "trailing garbage after `%%use' ignored");
2420         if (tline->type == TOK_STRING)
2421             nasm_unquote_cstr(tline->text, i);
2422         use_pkg = nasm_stdmac_find_package(tline->text);
2423         if (!use_pkg)
2424             error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2425         /* The first string will be <%define>__USE_*__ */
2426         pkg_macro = (char *)use_pkg + 1;
2427         if (!smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2428             /* Not already included, go ahead and include it */
2429             stdmacpos = use_pkg;
2430         }
2431         free_tlist(origline);
2432         return DIRECTIVE_FOUND;
2433     }
2434     case PP_PUSH:
2435     case PP_REPL:
2436     case PP_POP:
2437         tline = tline->next;
2438         skip_white_(tline);
2439         tline = expand_id(tline);
2440         if (tline) {
2441             if (!tok_type_(tline, TOK_ID)) {
2442                 error(ERR_NONFATAL, "`%s' expects a context identifier",
2443                       pp_directives[i]);
2444                 free_tlist(origline);
2445                 return DIRECTIVE_FOUND;     /* but we did _something_ */
2446             }
2447             if (tline->next)
2448                 error(ERR_WARNING|ERR_PASS1,
2449                       "trailing garbage after `%s' ignored",
2450                       pp_directives[i]);
2451             p = nasm_strdup(tline->text);
2452         } else {
2453             p = NULL;           /* Anonymous */
2454         }
2455
2456         if (i == PP_PUSH) {
2457             ctx = nasm_malloc(sizeof(Context));
2458             ctx->next = cstk;
2459             hash_init(&ctx->localmac, HASH_SMALL);
2460             ctx->name = p;
2461             ctx->number = unique++;
2462             cstk = ctx;
2463         } else {
2464             /* %pop or %repl */
2465             if (!cstk) {
2466                 error(ERR_NONFATAL, "`%s': context stack is empty",
2467                       pp_directives[i]);
2468             } else if (i == PP_POP) {
2469                 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2470                     error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2471                           "expected %s",
2472                           cstk->name ? cstk->name : "anonymous", p);
2473                 else
2474                     ctx_pop();
2475             } else {
2476                 /* i == PP_REPL */
2477                 nasm_free(cstk->name);
2478                 cstk->name = p;
2479                 p = NULL;
2480             }
2481             nasm_free(p);
2482         }
2483         free_tlist(origline);
2484         return DIRECTIVE_FOUND;
2485     case PP_FATAL:
2486         severity = ERR_FATAL;
2487         goto issue_error;
2488     case PP_ERROR:
2489         severity = ERR_NONFATAL;
2490         goto issue_error;
2491     case PP_WARNING:
2492         severity = ERR_WARNING|ERR_WARN_USER;
2493         goto issue_error;
2494
2495     issue_error:
2496     {
2497         /* Only error out if this is the final pass */
2498         if (pass != 2 && i != PP_FATAL)
2499             return DIRECTIVE_FOUND;
2500         
2501         tline->next = expand_smacro(tline->next);
2502         tline = tline->next;
2503         skip_white_(tline);
2504         t = tline ? tline->next : NULL;
2505         skip_white_(t);
2506         if (tok_type_(tline, TOK_STRING) && !t) {
2507             /* The line contains only a quoted string */
2508             p = tline->text;
2509             nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2510             error(severity, "%s",  p);
2511         } else {
2512             /* Not a quoted string, or more than a quoted string */
2513             p = detoken(tline, false);
2514             error(severity, "%s",  p);
2515             nasm_free(p);
2516         }
2517         free_tlist(origline);
2518         return DIRECTIVE_FOUND;
2519     }
2520
2521     CASE_PP_IF:
2522         if (istk->conds && !emitting(istk->conds->state))
2523             j = COND_NEVER;
2524         else {
2525             j = if_condition(tline->next, i);
2526             tline->next = NULL; /* it got freed */
2527             j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2528         }
2529         cond = nasm_malloc(sizeof(Cond));
2530         cond->next = istk->conds;
2531         cond->state = j;
2532         istk->conds = cond;
2533         free_tlist(origline);
2534         return DIRECTIVE_FOUND;
2535
2536     CASE_PP_ELIF:
2537         if (!istk->conds)
2538             error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2539         switch(istk->conds->state) {
2540         case COND_IF_TRUE:
2541             istk->conds->state = COND_DONE;
2542             break;
2543
2544         case COND_DONE:
2545         case COND_NEVER:
2546             break;
2547
2548         case COND_ELSE_TRUE:
2549         case COND_ELSE_FALSE:
2550             error_precond(ERR_WARNING|ERR_PASS1,
2551                           "`%%elif' after `%%else' ignored");
2552             istk->conds->state = COND_NEVER;
2553             break;
2554
2555         case COND_IF_FALSE:
2556             /*
2557              * IMPORTANT: In the case of %if, we will already have
2558              * called expand_mmac_params(); however, if we're
2559              * processing an %elif we must have been in a
2560              * non-emitting mode, which would have inhibited
2561              * the normal invocation of expand_mmac_params().
2562              * Therefore, we have to do it explicitly here.
2563              */
2564             j = if_condition(expand_mmac_params(tline->next), i);
2565             tline->next = NULL; /* it got freed */
2566             istk->conds->state =
2567                 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2568             break;
2569         }
2570         free_tlist(origline);
2571         return DIRECTIVE_FOUND;
2572
2573     case PP_ELSE:
2574         if (tline->next)
2575             error_precond(ERR_WARNING|ERR_PASS1,
2576                           "trailing garbage after `%%else' ignored");
2577         if (!istk->conds)
2578             error(ERR_FATAL, "`%%else': no matching `%%if'");
2579         switch(istk->conds->state) {
2580         case COND_IF_TRUE:
2581         case COND_DONE:
2582             istk->conds->state = COND_ELSE_FALSE;
2583             break;
2584
2585         case COND_NEVER:
2586             break;
2587
2588         case COND_IF_FALSE:
2589             istk->conds->state = COND_ELSE_TRUE;
2590             break;
2591
2592         case COND_ELSE_TRUE:
2593         case COND_ELSE_FALSE:
2594             error_precond(ERR_WARNING|ERR_PASS1,
2595                           "`%%else' after `%%else' ignored.");
2596             istk->conds->state = COND_NEVER;
2597             break;
2598         }
2599         free_tlist(origline);
2600         return DIRECTIVE_FOUND;
2601
2602     case PP_ENDIF:
2603         if (tline->next)
2604             error_precond(ERR_WARNING|ERR_PASS1,
2605                           "trailing garbage after `%%endif' ignored");
2606         if (!istk->conds)
2607             error(ERR_FATAL, "`%%endif': no matching `%%if'");
2608         cond = istk->conds;
2609         istk->conds = cond->next;
2610         nasm_free(cond);
2611         free_tlist(origline);
2612         return DIRECTIVE_FOUND;
2613                 
2614     case PP_RMACRO:
2615     case PP_IRMACRO:
2616     case PP_MACRO:
2617     case PP_IMACRO:
2618         if (defining) {
2619             error(ERR_FATAL, "`%s': already defining a macro",
2620                   pp_directives[i]);
2621             return DIRECTIVE_FOUND;
2622         }
2623         defining = nasm_malloc(sizeof(MMacro));
2624         defining->max_depth =
2625             (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2626         defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2627         if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2628             nasm_free(defining);
2629             defining = NULL;
2630             return DIRECTIVE_FOUND;
2631         }
2632
2633         mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2634         while (mmac) {
2635             if (!strcmp(mmac->name, defining->name) &&
2636                 (mmac->nparam_min <= defining->nparam_max
2637                  || defining->plus)
2638                 && (defining->nparam_min <= mmac->nparam_max
2639                     || mmac->plus)) {
2640                 error(ERR_WARNING|ERR_PASS1,
2641                       "redefining multi-line macro `%s'", defining->name);
2642                 return DIRECTIVE_FOUND;
2643             }
2644             mmac = mmac->next;
2645         }
2646         free_tlist(origline);
2647         return DIRECTIVE_FOUND;
2648
2649     case PP_ENDM:
2650     case PP_ENDMACRO:
2651         if (! (defining && defining->name)) {
2652             error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2653             return DIRECTIVE_FOUND;
2654         }
2655         mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2656         defining->next = *mmhead;
2657         *mmhead = defining;
2658         defining = NULL;
2659         free_tlist(origline);
2660         return DIRECTIVE_FOUND;
2661
2662     case PP_EXITMACRO:
2663         /*
2664          * We must search along istk->expansion until we hit a
2665          * macro-end marker for a macro with a name. Then we set
2666          * its `in_progress' flag to 0.
2667          */
2668         for (l = istk->expansion; l; l = l->next)
2669             if (l->finishes && l->finishes->name)
2670                 break;
2671
2672         if (l) {
2673             l->finishes->in_progress = 0;
2674         } else {
2675             error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2676         }
2677         free_tlist(origline);
2678         return DIRECTIVE_FOUND;
2679
2680     case PP_UNMACRO:
2681     case PP_UNIMACRO:
2682     {
2683         MMacro **mmac_p;
2684         MMacro spec;
2685
2686         spec.casesense = (i == PP_UNMACRO);
2687         if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2688             return DIRECTIVE_FOUND;
2689         }
2690         mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2691         while (mmac_p && *mmac_p) {
2692             mmac = *mmac_p;
2693             if (mmac->casesense == spec.casesense &&
2694                 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2695                 mmac->nparam_min == spec.nparam_min &&
2696                 mmac->nparam_max == spec.nparam_max &&
2697                 mmac->plus == spec.plus) {
2698                 *mmac_p = mmac->next;
2699                 free_mmacro(mmac);
2700             } else {
2701                 mmac_p = &mmac->next;
2702             }
2703         }
2704         free_tlist(origline);
2705         free_tlist(spec.dlist);
2706         return DIRECTIVE_FOUND;
2707     }
2708
2709     case PP_ROTATE:
2710         if (tline->next && tline->next->type == TOK_WHITESPACE)
2711             tline = tline->next;
2712         if (!tline->next) {
2713             free_tlist(origline);
2714             error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2715             return DIRECTIVE_FOUND;
2716         }
2717         t = expand_smacro(tline->next);
2718         tline->next = NULL;
2719         free_tlist(origline);
2720         tline = t;
2721         tptr = &t;
2722         tokval.t_type = TOKEN_INVALID;
2723         evalresult =
2724             evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2725         free_tlist(tline);
2726         if (!evalresult)
2727             return DIRECTIVE_FOUND;
2728         if (tokval.t_type)
2729             error(ERR_WARNING|ERR_PASS1,
2730                   "trailing garbage after expression ignored");
2731         if (!is_simple(evalresult)) {
2732             error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2733             return DIRECTIVE_FOUND;
2734         }
2735         mmac = istk->mstk;
2736         while (mmac && !mmac->name)     /* avoid mistaking %reps for macros */
2737             mmac = mmac->next_active;
2738         if (!mmac) {
2739             error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2740         } else if (mmac->nparam == 0) {
2741             error(ERR_NONFATAL,
2742                   "`%%rotate' invoked within macro without parameters");
2743         } else {
2744             int rotate = mmac->rotate + reloc_value(evalresult);
2745
2746             rotate %= (int)mmac->nparam;
2747             if (rotate < 0)
2748                 rotate += mmac->nparam;
2749
2750             mmac->rotate = rotate;
2751         }
2752         return DIRECTIVE_FOUND;
2753
2754     case PP_REP:
2755         nolist = false;
2756         do {
2757             tline = tline->next;
2758         } while (tok_type_(tline, TOK_WHITESPACE));
2759
2760         if (tok_type_(tline, TOK_ID) &&
2761             nasm_stricmp(tline->text, ".nolist") == 0) {
2762             nolist = true;
2763             do {
2764                 tline = tline->next;
2765             } while (tok_type_(tline, TOK_WHITESPACE));
2766         }
2767
2768         if (tline) {
2769             t = expand_smacro(tline);
2770             tptr = &t;
2771             tokval.t_type = TOKEN_INVALID;
2772             evalresult =
2773                 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2774             if (!evalresult) {
2775                 free_tlist(origline);
2776                 return DIRECTIVE_FOUND;
2777             }
2778             if (tokval.t_type)
2779                 error(ERR_WARNING|ERR_PASS1,
2780                       "trailing garbage after expression ignored");
2781             if (!is_simple(evalresult)) {
2782                 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2783                 return DIRECTIVE_FOUND;
2784             }
2785             count = reloc_value(evalresult) + 1;
2786         } else {
2787             error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2788             count = 0;
2789         }
2790         free_tlist(origline);
2791
2792         tmp_defining = defining;
2793         defining = nasm_malloc(sizeof(MMacro));
2794         defining->prev = NULL;
2795         defining->name = NULL;  /* flags this macro as a %rep block */
2796         defining->casesense = false;
2797         defining->plus = false;
2798         defining->nolist = nolist;
2799         defining->in_progress = count;
2800         defining->max_depth = 0;
2801         defining->nparam_min = defining->nparam_max = 0;
2802         defining->defaults = NULL;
2803         defining->dlist = NULL;
2804         defining->expansion = NULL;
2805         defining->next_active = istk->mstk;
2806         defining->rep_nest = tmp_defining;
2807         return DIRECTIVE_FOUND;
2808
2809     case PP_ENDREP:
2810         if (!defining || defining->name) {
2811             error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2812             return DIRECTIVE_FOUND;
2813         }
2814
2815         /*
2816          * Now we have a "macro" defined - although it has no name
2817          * and we won't be entering it in the hash tables - we must
2818          * push a macro-end marker for it on to istk->expansion.
2819          * After that, it will take care of propagating itself (a
2820          * macro-end marker line for a macro which is really a %rep
2821          * block will cause the macro to be re-expanded, complete
2822          * with another macro-end marker to ensure the process
2823          * continues) until the whole expansion is forcibly removed
2824          * from istk->expansion by a %exitrep.
2825          */
2826         l = nasm_malloc(sizeof(Line));
2827         l->next = istk->expansion;
2828         l->finishes = defining;
2829         l->first = NULL;
2830         istk->expansion = l;
2831
2832         istk->mstk = defining;
2833
2834         list->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2835         tmp_defining = defining;
2836         defining = defining->rep_nest;
2837         free_tlist(origline);
2838         return DIRECTIVE_FOUND;
2839
2840     case PP_EXITREP:
2841         /*
2842          * We must search along istk->expansion until we hit a
2843          * macro-end marker for a macro with no name. Then we set
2844          * its `in_progress' flag to 0.
2845          */
2846         for (l = istk->expansion; l; l = l->next)
2847             if (l->finishes && !l->finishes->name)
2848                 break;
2849
2850         if (l)
2851             l->finishes->in_progress = 1;
2852         else
2853             error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
2854         free_tlist(origline);
2855         return DIRECTIVE_FOUND;
2856
2857     case PP_XDEFINE:
2858     case PP_IXDEFINE:
2859     case PP_DEFINE:
2860     case PP_IDEFINE:
2861         casesense = (i == PP_DEFINE || i == PP_XDEFINE);
2862
2863         tline = tline->next;
2864         skip_white_(tline);
2865         tline = expand_id(tline);
2866         if (!tline || (tline->type != TOK_ID &&
2867                        (tline->type != TOK_PREPROC_ID ||
2868                         tline->text[1] != '$'))) {
2869             error(ERR_NONFATAL, "`%s' expects a macro identifier",
2870                   pp_directives[i]);
2871             free_tlist(origline);
2872             return DIRECTIVE_FOUND;
2873         }
2874
2875         ctx = get_ctx(tline->text, &mname, false);
2876         last = tline;
2877         param_start = tline = tline->next;
2878         nparam = 0;
2879
2880         /* Expand the macro definition now for %xdefine and %ixdefine */
2881         if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
2882             tline = expand_smacro(tline);
2883
2884         if (tok_is_(tline, "(")) {
2885             /*
2886              * This macro has parameters.
2887              */
2888
2889             tline = tline->next;
2890             while (1) {
2891                 skip_white_(tline);
2892                 if (!tline) {
2893                     error(ERR_NONFATAL, "parameter identifier expected");
2894                     free_tlist(origline);
2895                     return DIRECTIVE_FOUND;
2896                 }
2897                 if (tline->type != TOK_ID) {
2898                     error(ERR_NONFATAL,
2899                           "`%s': parameter identifier expected",
2900                           tline->text);
2901                     free_tlist(origline);
2902                     return DIRECTIVE_FOUND;
2903                 }
2904                 tline->type = TOK_SMAC_PARAM + nparam++;
2905                 tline = tline->next;
2906                 skip_white_(tline);
2907                 if (tok_is_(tline, ",")) {
2908                     tline = tline->next;
2909                 } else {
2910                     if (!tok_is_(tline, ")")) {
2911                         error(ERR_NONFATAL,
2912                               "`)' expected to terminate macro template");
2913                         free_tlist(origline);
2914                         return DIRECTIVE_FOUND;
2915                     }
2916                     break;
2917                 }
2918             }
2919             last = tline;
2920             tline = tline->next;
2921         }
2922         if (tok_type_(tline, TOK_WHITESPACE))
2923             last = tline, tline = tline->next;
2924         macro_start = NULL;
2925         last->next = NULL;
2926         t = tline;
2927         while (t) {
2928             if (t->type == TOK_ID) {
2929                 for (tt = param_start; tt; tt = tt->next)
2930                     if (tt->type >= TOK_SMAC_PARAM &&
2931                         !strcmp(tt->text, t->text))
2932                         t->type = tt->type;
2933             }
2934             tt = t->next;
2935             t->next = macro_start;
2936             macro_start = t;
2937             t = tt;
2938         }
2939         /*
2940          * Good. We now have a macro name, a parameter count, and a
2941          * token list (in reverse order) for an expansion. We ought
2942          * to be OK just to create an SMacro, store it, and let
2943          * free_tlist have the rest of the line (which we have
2944          * carefully re-terminated after chopping off the expansion
2945          * from the end).
2946          */
2947         define_smacro(ctx, mname, casesense, nparam, macro_start);
2948         free_tlist(origline);
2949         return DIRECTIVE_FOUND;
2950
2951     case PP_UNDEF:
2952         tline = tline->next;
2953         skip_white_(tline);
2954         tline = expand_id(tline);
2955         if (!tline || (tline->type != TOK_ID &&
2956                        (tline->type != TOK_PREPROC_ID ||
2957                         tline->text[1] != '$'))) {
2958             error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
2959             free_tlist(origline);
2960             return DIRECTIVE_FOUND;
2961         }
2962         if (tline->next) {
2963             error(ERR_WARNING|ERR_PASS1,
2964                   "trailing garbage after macro name ignored");
2965         }
2966
2967         /* Find the context that symbol belongs to */
2968         ctx = get_ctx(tline->text, &mname, false);
2969         undef_smacro(ctx, mname);
2970         free_tlist(origline);
2971         return DIRECTIVE_FOUND;
2972
2973     case PP_DEFSTR:
2974     case PP_IDEFSTR:
2975         casesense = (i == PP_DEFSTR);
2976
2977         tline = tline->next;
2978         skip_white_(tline);
2979         tline = expand_id(tline);
2980         if (!tline || (tline->type != TOK_ID &&
2981                        (tline->type != TOK_PREPROC_ID ||
2982                         tline->text[1] != '$'))) {
2983             error(ERR_NONFATAL, "`%s' expects a macro identifier",
2984                   pp_directives[i]);
2985             free_tlist(origline);
2986             return DIRECTIVE_FOUND;
2987         }
2988
2989         ctx = get_ctx(tline->text, &mname, false);
2990         last = tline;
2991         tline = expand_smacro(tline->next);
2992         last->next = NULL;
2993
2994         while (tok_type_(tline, TOK_WHITESPACE))
2995             tline = delete_Token(tline);
2996
2997         p = detoken(tline, false);
2998         macro_start = nasm_malloc(sizeof(*macro_start));
2999         macro_start->next = NULL;
3000         macro_start->text = nasm_quote(p, strlen(p));
3001         macro_start->type = TOK_STRING;
3002         macro_start->a.mac = NULL;
3003         nasm_free(p);
3004
3005         /*
3006          * We now have a macro name, an implicit parameter count of
3007          * zero, and a string token to use as an expansion. Create
3008          * and store an SMacro.
3009          */
3010         define_smacro(ctx, mname, casesense, 0, macro_start);
3011         free_tlist(origline);
3012         return DIRECTIVE_FOUND;
3013                 
3014     case PP_DEFTOK:
3015     case PP_IDEFTOK:
3016         casesense = (i == PP_DEFTOK);
3017         
3018         tline = tline->next;
3019         skip_white_(tline);
3020         tline = expand_id(tline);
3021         if (!tline || (tline->type != TOK_ID &&
3022                        (tline->type != TOK_PREPROC_ID ||
3023                         tline->text[1] != '$'))) {
3024             error(ERR_NONFATAL,
3025                   "`%s' expects a macro identifier as first parameter",
3026                   pp_directives[i]);
3027             free_tlist(origline);
3028             return DIRECTIVE_FOUND;
3029         }
3030         ctx = get_ctx(tline->text, &mname, false);
3031         last = tline;
3032         tline = expand_smacro(tline->next);
3033         last->next = NULL;
3034
3035         t = tline;
3036         while (tok_type_(t, TOK_WHITESPACE))
3037             t = t->next;
3038         /* t should now point to the string */
3039         if (t->type != TOK_STRING) {
3040             error(ERR_NONFATAL,
3041                   "`%s` requires string as second parameter",
3042                   pp_directives[i]);
3043             free_tlist(tline);
3044             free_tlist(origline);
3045             return DIRECTIVE_FOUND;
3046         }
3047
3048         nasm_unquote_cstr(t->text, i);
3049         macro_start = tokenize(t->text);
3050         
3051         /*
3052          * We now have a macro name, an implicit parameter count of
3053          * zero, and a numeric token to use as an expansion. Create
3054          * and store an SMacro.
3055          */
3056         define_smacro(ctx, mname, casesense, 0, macro_start);
3057         free_tlist(tline);
3058         free_tlist(origline);
3059         return DIRECTIVE_FOUND;
3060
3061     case PP_PATHSEARCH:
3062     {
3063         FILE *fp;
3064         StrList *xsl = NULL;
3065         StrList **xst = &xsl;
3066
3067         casesense = true;
3068
3069         tline = tline->next;
3070         skip_white_(tline);
3071         tline = expand_id(tline);
3072         if (!tline || (tline->type != TOK_ID &&
3073                        (tline->type != TOK_PREPROC_ID ||
3074                         tline->text[1] != '$'))) {
3075             error(ERR_NONFATAL,
3076                   "`%%pathsearch' expects a macro identifier as first parameter");
3077             free_tlist(origline);
3078             return DIRECTIVE_FOUND;
3079         }
3080         ctx = get_ctx(tline->text, &mname, false);
3081         last = tline;
3082         tline = expand_smacro(tline->next);
3083         last->next = NULL;
3084
3085         t = tline;
3086         while (tok_type_(t, TOK_WHITESPACE))
3087             t = t->next;
3088
3089         if (!t || (t->type != TOK_STRING &&
3090                    t->type != TOK_INTERNAL_STRING)) {
3091             error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3092             free_tlist(tline);
3093             free_tlist(origline);
3094             return DIRECTIVE_FOUND;     /* but we did _something_ */
3095         }
3096         if (t->next)
3097             error(ERR_WARNING|ERR_PASS1,
3098                   "trailing garbage after `%%pathsearch' ignored");
3099         p = t->text;
3100         if (t->type != TOK_INTERNAL_STRING)
3101             nasm_unquote(p, NULL);
3102
3103         fp = inc_fopen(p, &xsl, &xst, true);
3104         if (fp) {
3105             p = xsl->str;
3106             fclose(fp);         /* Don't actually care about the file */
3107         }
3108         macro_start = nasm_malloc(sizeof(*macro_start));
3109         macro_start->next = NULL;
3110         macro_start->text = nasm_quote(p, strlen(p));
3111         macro_start->type = TOK_STRING;
3112         macro_start->a.mac = NULL;
3113         if (xsl)
3114             nasm_free(xsl);
3115
3116         /*
3117          * We now have a macro name, an implicit parameter count of
3118          * zero, and a string token to use as an expansion. Create
3119          * and store an SMacro.
3120          */
3121         define_smacro(ctx, mname, casesense, 0, macro_start);
3122         free_tlist(tline);
3123         free_tlist(origline);
3124         return DIRECTIVE_FOUND;
3125     }
3126
3127     case PP_STRLEN:
3128         casesense = true;
3129
3130         tline = tline->next;
3131         skip_white_(tline);
3132         tline = expand_id(tline);
3133         if (!tline || (tline->type != TOK_ID &&
3134                        (tline->type != TOK_PREPROC_ID ||
3135                         tline->text[1] != '$'))) {
3136             error(ERR_NONFATAL,
3137                   "`%%strlen' expects a macro identifier as first parameter");
3138             free_tlist(origline);
3139             return DIRECTIVE_FOUND;
3140         }
3141         ctx = get_ctx(tline->text, &mname, false);
3142         last = tline;
3143         tline = expand_smacro(tline->next);
3144         last->next = NULL;
3145
3146         t = tline;
3147         while (tok_type_(t, TOK_WHITESPACE))
3148             t = t->next;
3149         /* t should now point to the string */
3150         if (t->type != TOK_STRING) {
3151             error(ERR_NONFATAL,
3152                   "`%%strlen` requires string as second parameter");
3153             free_tlist(tline);
3154             free_tlist(origline);
3155             return DIRECTIVE_FOUND;
3156         }
3157
3158         macro_start = nasm_malloc(sizeof(*macro_start));
3159         macro_start->next = NULL;
3160         make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3161         macro_start->a.mac = NULL;
3162
3163         /*
3164          * We now have a macro name, an implicit parameter count of
3165          * zero, and a numeric token to use as an expansion. Create
3166          * and store an SMacro.
3167          */
3168         define_smacro(ctx, mname, casesense, 0, macro_start);
3169         free_tlist(tline);
3170         free_tlist(origline);
3171         return DIRECTIVE_FOUND;
3172
3173     case PP_STRCAT:
3174         casesense = true;
3175
3176         tline = tline->next;
3177         skip_white_(tline);
3178         tline = expand_id(tline);
3179         if (!tline || (tline->type != TOK_ID &&
3180                        (tline->type != TOK_PREPROC_ID ||
3181                         tline->text[1] != '$'))) {
3182             error(ERR_NONFATAL,
3183                   "`%%strcat' expects a macro identifier as first parameter");
3184             free_tlist(origline);
3185             return DIRECTIVE_FOUND;
3186         }
3187         ctx = get_ctx(tline->text, &mname, false);
3188         last = tline;
3189         tline = expand_smacro(tline->next);
3190         last->next = NULL;
3191
3192         len = 0;
3193         for (t = tline; t; t = t->next) {
3194             switch (t->type) {
3195             case TOK_WHITESPACE:
3196                 break;
3197             case TOK_STRING:
3198                 len += t->a.len = nasm_unquote(t->text, NULL);
3199                 break;
3200             case TOK_OTHER:
3201                 if (!strcmp(t->text, ",")) /* permit comma separators */
3202                     break;
3203                 /* else fall through */
3204             default:
3205                 error(ERR_NONFATAL,
3206                       "non-string passed to `%%strcat' (%d)", t->type);
3207                 free_tlist(tline);
3208                 free_tlist(origline);
3209                 return DIRECTIVE_FOUND;
3210             }
3211         }
3212
3213         p = pp = nasm_malloc(len);
3214         for (t = tline; t; t = t->next) {
3215             if (t->type == TOK_STRING) {
3216                 memcpy(p, t->text, t->a.len);
3217                 p += t->a.len;
3218             }
3219         }
3220
3221         /*
3222          * We now have a macro name, an implicit parameter count of
3223          * zero, and a numeric token to use as an expansion. Create
3224          * and store an SMacro.
3225          */
3226         macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3227         macro_start->text = nasm_quote(pp, len);
3228         nasm_free(pp);
3229         define_smacro(ctx, mname, casesense, 0, macro_start);
3230         free_tlist(tline);
3231         free_tlist(origline);
3232         return DIRECTIVE_FOUND;
3233
3234     case PP_SUBSTR:
3235     {
3236         int64_t a1, a2;
3237         size_t len;
3238
3239         casesense = true;
3240
3241         tline = tline->next;
3242         skip_white_(tline);
3243         tline = expand_id(tline);
3244         if (!tline || (tline->type != TOK_ID &&
3245                        (tline->type != TOK_PREPROC_ID ||
3246                         tline->text[1] != '$'))) {
3247             error(ERR_NONFATAL,
3248                   "`%%substr' expects a macro identifier as first parameter");
3249             free_tlist(origline);
3250             return DIRECTIVE_FOUND;
3251         }
3252         ctx = get_ctx(tline->text, &mname, false);
3253         last = tline;
3254         tline = expand_smacro(tline->next);
3255         last->next = NULL;
3256
3257         t = tline->next;
3258         while (tok_type_(t, TOK_WHITESPACE))
3259             t = t->next;
3260
3261         /* t should now point to the string */
3262         if (t->type != TOK_STRING) {
3263             error(ERR_NONFATAL,
3264                   "`%%substr` requires string as second parameter");
3265             free_tlist(tline);
3266             free_tlist(origline);
3267             return DIRECTIVE_FOUND;
3268         }
3269
3270         tt = t->next;
3271         tptr = &tt;
3272         tokval.t_type = TOKEN_INVALID;
3273         evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3274                               pass, error, NULL);
3275         if (!evalresult) {
3276             free_tlist(tline);
3277             free_tlist(origline);
3278             return DIRECTIVE_FOUND;
3279         } else if (!is_simple(evalresult)) {
3280             error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3281             free_tlist(tline);
3282             free_tlist(origline);
3283             return DIRECTIVE_FOUND;
3284         }
3285         a1 = evalresult->value-1;
3286
3287         while (tok_type_(tt, TOK_WHITESPACE))
3288             tt = tt->next;
3289         if (!tt) {
3290             a2 = 1;             /* Backwards compatibility: one character */
3291         } else {
3292             tokval.t_type = TOKEN_INVALID;
3293             evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3294                                   pass, error, NULL);
3295             if (!evalresult) {
3296                 free_tlist(tline);
3297                 free_tlist(origline);
3298                 return DIRECTIVE_FOUND;
3299             } else if (!is_simple(evalresult)) {
3300                 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3301                 free_tlist(tline);
3302                 free_tlist(origline);
3303                 return DIRECTIVE_FOUND;
3304             }
3305             a2 = evalresult->value;
3306         }
3307
3308         len = nasm_unquote(t->text, NULL);
3309         if (a2 < 0)
3310             a2 = a2+1+len-a1;
3311         if (a1+a2 > (int64_t)len)
3312             a2 = len-a1;
3313
3314         macro_start = nasm_malloc(sizeof(*macro_start));
3315         macro_start->next = NULL;
3316         macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3317         macro_start->type = TOK_STRING;
3318         macro_start->a.mac = NULL;
3319
3320         /*
3321          * We now have a macro name, an implicit parameter count of
3322          * zero, and a numeric token to use as an expansion. Create
3323          * and store an SMacro.
3324          */
3325         define_smacro(ctx, mname, casesense, 0, macro_start);
3326         free_tlist(tline);
3327         free_tlist(origline);
3328         return DIRECTIVE_FOUND;
3329     }
3330
3331     case PP_ASSIGN:
3332     case PP_IASSIGN:
3333         casesense = (i == PP_ASSIGN);
3334
3335         tline = tline->next;
3336         skip_white_(tline);
3337         tline = expand_id(tline);
3338         if (!tline || (tline->type != TOK_ID &&
3339                        (tline->type != TOK_PREPROC_ID ||
3340                         tline->text[1] != '$'))) {
3341             error(ERR_NONFATAL,
3342                   "`%%%sassign' expects a macro identifier",
3343                   (i == PP_IASSIGN ? "i" : ""));
3344             free_tlist(origline);
3345             return DIRECTIVE_FOUND;
3346         }
3347         ctx = get_ctx(tline->text, &mname, false);
3348         last = tline;
3349         tline = expand_smacro(tline->next);
3350         last->next = NULL;
3351
3352         t = tline;
3353         tptr = &t;
3354         tokval.t_type = TOKEN_INVALID;
3355         evalresult =
3356             evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3357         free_tlist(tline);
3358         if (!evalresult) {
3359             free_tlist(origline);
3360             return DIRECTIVE_FOUND;
3361         }
3362
3363         if (tokval.t_type)
3364             error(ERR_WARNING|ERR_PASS1,
3365                   "trailing garbage after expression ignored");
3366
3367         if (!is_simple(evalresult)) {
3368             error(ERR_NONFATAL,
3369                   "non-constant value given to `%%%sassign'",
3370                   (i == PP_IASSIGN ? "i" : ""));
3371             free_tlist(origline);
3372             return DIRECTIVE_FOUND;
3373         }
3374
3375         macro_start = nasm_malloc(sizeof(*macro_start));
3376         macro_start->next = NULL;
3377         make_tok_num(macro_start, reloc_value(evalresult));
3378         macro_start->a.mac = NULL;
3379
3380         /*
3381          * We now have a macro name, an implicit parameter count of
3382          * zero, and a numeric token to use as an expansion. Create
3383          * and store an SMacro.
3384          */
3385         define_smacro(ctx, mname, casesense, 0, macro_start);
3386         free_tlist(origline);
3387         return DIRECTIVE_FOUND;
3388
3389     case PP_LINE:
3390         /*
3391          * Syntax is `%line nnn[+mmm] [filename]'
3392          */
3393         tline = tline->next;
3394         skip_white_(tline);
3395         if (!tok_type_(tline, TOK_NUMBER)) {
3396             error(ERR_NONFATAL, "`%%line' expects line number");
3397             free_tlist(origline);
3398             return DIRECTIVE_FOUND;
3399         }
3400         k = readnum(tline->text, &err);
3401         m = 1;
3402         tline = tline->next;
3403         if (tok_is_(tline, "+")) {
3404             tline = tline->next;
3405             if (!tok_type_(tline, TOK_NUMBER)) {
3406                 error(ERR_NONFATAL, "`%%line' expects line increment");
3407                 free_tlist(origline);
3408                 return DIRECTIVE_FOUND;
3409             }
3410             m = readnum(tline->text, &err);
3411             tline = tline->next;
3412         }
3413         skip_white_(tline);
3414         src_set_linnum(k);
3415         istk->lineinc = m;
3416         if (tline) {
3417             nasm_free(src_set_fname(detoken(tline, false)));
3418         }
3419         free_tlist(origline);
3420         return DIRECTIVE_FOUND;
3421
3422     default:
3423         error(ERR_FATAL,
3424               "preprocessor directive `%s' not yet implemented",
3425               pp_directives[i]);
3426         return DIRECTIVE_FOUND;
3427     }
3428 }
3429
3430 /*
3431  * Ensure that a macro parameter contains a condition code and
3432  * nothing else. Return the condition code index if so, or -1
3433  * otherwise.
3434  */
3435 static int find_cc(Token * t)
3436 {
3437     Token *tt;
3438     int i, j, k, m;
3439
3440     if (!t)
3441         return -1;              /* Probably a %+ without a space */
3442
3443     skip_white_(t);
3444     if (t->type != TOK_ID)
3445         return -1;
3446     tt = t->next;
3447     skip_white_(tt);
3448     if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3449         return -1;
3450
3451     i = -1;
3452     j = elements(conditions);
3453     while (j - i > 1) {
3454         k = (j + i) / 2;
3455         m = nasm_stricmp(t->text, conditions[k]);
3456         if (m == 0) {
3457             i = k;
3458             j = -2;
3459             break;
3460         } else if (m < 0) {
3461             j = k;
3462         } else
3463             i = k;
3464     }
3465     if (j != -2)
3466         return -1;
3467     return i;
3468 }
3469
3470 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3471 {
3472     Token **tail, *t, *tt;
3473     Token **paste_head;
3474     bool did_paste = false;
3475     char *tmp;
3476
3477     /* Now handle token pasting... */
3478     paste_head = NULL;
3479     tail = head;
3480     while ((t = *tail) && (tt = t->next)) {
3481         switch (t->type) {
3482         case TOK_WHITESPACE:
3483             if (tt->type == TOK_WHITESPACE) {
3484                 /* Zap adjacent whitespace tokens */
3485                 t->next = delete_Token(tt);
3486             } else {
3487                 /* Do not advance paste_head here */
3488                 tail = &t->next;
3489             }
3490             break;
3491         case TOK_ID:
3492         case TOK_PREPROC_ID:
3493         case TOK_NUMBER:
3494         case TOK_FLOAT:
3495         {
3496             size_t len = 0;
3497             char *tmp, *p;
3498
3499             while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3500                           tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3501                           tt->type == TOK_OTHER)) {
3502                 len += strlen(tt->text);
3503                 tt = tt->next;
3504             }
3505
3506             /* Now tt points to the first token after the potential
3507                paste area... */
3508             if (tt != t->next) {
3509                 /* We have at least two tokens... */
3510                 len += strlen(t->text);
3511                 p = tmp = nasm_malloc(len+1);
3512
3513                 while (t != tt) {
3514                     strcpy(p, t->text);
3515                     p = strchr(p, '\0');
3516                     t = delete_Token(t);
3517                 }
3518
3519                 t = *tail = tokenize(tmp);
3520                 nasm_free(tmp);
3521
3522                 while (t->next) {
3523                     tail = &t->next;
3524                     t = t->next;
3525                 }
3526                 t->next = tt;   /* Attach the remaining token chain */
3527
3528                 did_paste = true;
3529             }
3530             paste_head = tail;
3531             tail = &t->next;
3532             break;
3533         }
3534         case TOK_PASTE:         /* %+ */
3535             if (handle_paste_tokens) {
3536                 /* Zap %+ and whitespace tokens to the right */
3537                 while (t && (t->type == TOK_WHITESPACE ||
3538                              t->type == TOK_PASTE))
3539                     t = *tail = delete_Token(t);
3540                 if (!paste_head || !t)
3541                     break;      /* Nothing to paste with */
3542                 tail = paste_head;
3543                 t = *tail;
3544                 tt = t->next;
3545                 while (tok_type_(tt, TOK_WHITESPACE))
3546                     tt = t->next = delete_Token(tt);
3547
3548                 if (tt) {
3549                     tmp = nasm_strcat(t->text, tt->text);
3550                     delete_Token(t);
3551                     tt = delete_Token(tt);
3552                     t = *tail = tokenize(tmp);
3553                     nasm_free(tmp);
3554                     while (t->next) {
3555                         tail = &t->next;
3556                         t = t->next;
3557                     }
3558                     t->next = tt; /* Attach the remaining token chain */
3559                     did_paste = true;
3560                 }
3561                 paste_head = tail;
3562                 tail = &t->next;
3563                 break;
3564             }
3565             /* else fall through */
3566         default:
3567             tail = paste_head = &t->next;
3568             break;
3569         }
3570     }
3571     return did_paste;
3572 }
3573 /*
3574  * Expand MMacro-local things: parameter references (%0, %n, %+n,
3575  * %-n) and MMacro-local identifiers (%%foo) as well as
3576  * macro indirection (%[...]).
3577  */
3578 static Token *expand_mmac_params(Token * tline)
3579 {
3580     Token *t, *tt, **tail, *thead;
3581     bool changed = false;
3582
3583     tail = &thead;
3584     thead = NULL;
3585
3586     while (tline) {
3587         if (tline->type == TOK_PREPROC_ID &&
3588             (((tline->text[1] == '+' || tline->text[1] == '-')
3589               && tline->text[2]) || tline->text[1] == '%'
3590              || (tline->text[1] >= '0' && tline->text[1] <= '9'))) {
3591             char *text = NULL;
3592             int type = 0, cc;   /* type = 0 to placate optimisers */
3593             char tmpbuf[30];
3594             unsigned int n;
3595             int i;
3596             MMacro *mac;
3597
3598             t = tline;
3599             tline = tline->next;
3600
3601             mac = istk->mstk;
3602             while (mac && !mac->name)   /* avoid mistaking %reps for macros */
3603                 mac = mac->next_active;
3604             if (!mac)
3605                 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3606             else
3607                 switch (t->text[1]) {
3608                     /*
3609                      * We have to make a substitution of one of the
3610                      * forms %1, %-1, %+1, %%foo, %0.
3611                      */
3612                 case '0':
3613                     type = TOK_NUMBER;
3614                     snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3615                     text = nasm_strdup(tmpbuf);
3616                     break;
3617                 case '%':
3618                     type = TOK_ID;
3619                     snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3620                              mac->unique);
3621                     text = nasm_strcat(tmpbuf, t->text + 2);
3622                     break;
3623                 case '-':
3624                     n = atoi(t->text + 2) - 1;
3625                     if (n >= mac->nparam)
3626                         tt = NULL;
3627                     else {
3628                         if (mac->nparam > 1)
3629                             n = (n + mac->rotate) % mac->nparam;
3630                         tt = mac->params[n];
3631                     }
3632                     cc = find_cc(tt);
3633                     if (cc == -1) {
3634                         error(ERR_NONFATAL,
3635                               "macro parameter %d is not a condition code",
3636                               n + 1);
3637                         text = NULL;
3638                     } else {
3639                         type = TOK_ID;
3640                         if (inverse_ccs[cc] == -1) {
3641                             error(ERR_NONFATAL,
3642                                   "condition code `%s' is not invertible",
3643                                   conditions[cc]);
3644                             text = NULL;
3645                         } else
3646                             text = nasm_strdup(conditions[inverse_ccs[cc]]);
3647                     }
3648                     break;
3649                 case '+':
3650                     n = atoi(t->text + 2) - 1;
3651                     if (n >= mac->nparam)
3652                         tt = NULL;
3653                     else {
3654                         if (mac->nparam > 1)
3655                             n = (n + mac->rotate) % mac->nparam;
3656                         tt = mac->params[n];
3657                     }
3658                     cc = find_cc(tt);
3659                     if (cc == -1) {
3660                         error(ERR_NONFATAL,
3661                               "macro parameter %d is not a condition code",
3662                               n + 1);
3663                         text = NULL;
3664                     } else {
3665                         type = TOK_ID;
3666                         text = nasm_strdup(conditions[cc]);
3667                     }
3668                     break;
3669                 default:
3670                     n = atoi(t->text + 1) - 1;
3671                     if (n >= mac->nparam)
3672                         tt = NULL;
3673                     else {
3674                         if (mac->nparam > 1)
3675                             n = (n + mac->rotate) % mac->nparam;
3676                         tt = mac->params[n];
3677                     }
3678                     if (tt) {
3679                         for (i = 0; i < mac->paramlen[n]; i++) {
3680                             *tail = new_Token(NULL, tt->type, tt->text, 0);
3681                             tail = &(*tail)->next;
3682                             tt = tt->next;
3683                         }
3684                     }
3685                     text = NULL;        /* we've done it here */
3686                     break;
3687                 }
3688             if (!text) {
3689                 delete_Token(t);
3690             } else {
3691                 *tail = t;
3692                 tail = &t->next;
3693                 t->type = type;
3694                 nasm_free(t->text);
3695                 t->text = text;
3696                 t->a.mac = NULL;
3697             }
3698             changed = true;
3699             continue;
3700         } else if (tline->type == TOK_INDIRECT) {
3701             t = tline;
3702             tline = tline->next;
3703             tt = tokenize(t->text);
3704             tt = expand_mmac_params(tt);
3705             tt = expand_smacro(tt);
3706             *tail = tt;
3707             while (tt) {
3708                 tt->a.mac = NULL; /* Necessary? */
3709                 tail = &tt->next;
3710                 tt = tt->next;
3711             }
3712             delete_Token(t);
3713             changed = true;
3714         } else {
3715             t = *tail = tline;
3716             tline = tline->next;
3717             t->a.mac = NULL;
3718             tail = &t->next;
3719         }
3720     }
3721     *tail = NULL;
3722
3723     if (changed)
3724         paste_tokens(&thead, false);
3725
3726     return thead;
3727 }
3728
3729 /*
3730  * Expand all single-line macro calls made in the given line.
3731  * Return the expanded version of the line. The original is deemed
3732  * to be destroyed in the process. (In reality we'll just move
3733  * Tokens from input to output a lot of the time, rather than
3734  * actually bothering to destroy and replicate.)
3735  */
3736
3737 static Token *expand_smacro(Token * tline)
3738 {
3739     Token *t, *tt, *mstart, **tail, *thead;
3740     struct hash_table *smtbl;
3741     SMacro *head = NULL, *m;
3742     Token **params;
3743     int *paramsize;
3744     unsigned int nparam, sparam;
3745     int brackets;
3746     Token *org_tline = tline;
3747     Context *ctx;
3748     const char *mname;
3749     int deadman = DEADMAN_LIMIT;
3750     bool expanded;
3751
3752     /*
3753      * Trick: we should avoid changing the start token pointer since it can
3754      * be contained in "next" field of other token. Because of this
3755      * we allocate a copy of first token and work with it; at the end of
3756      * routine we copy it back
3757      */
3758     if (org_tline) {
3759         tline =
3760             new_Token(org_tline->next, org_tline->type, org_tline->text,
3761                       0);
3762         tline->a.mac = org_tline->a.mac;
3763         nasm_free(org_tline->text);
3764         org_tline->text = NULL;
3765     }
3766
3767     expanded = true;            /* Always expand %+ at least once */
3768
3769 again:
3770     tail = &thead;
3771     thead = NULL;
3772
3773     while (tline) {             /* main token loop */
3774         if (!--deadman) {
3775             error(ERR_NONFATAL, "interminable macro recursion");
3776             break;
3777         }
3778
3779         if ((mname = tline->text)) {
3780             /* if this token is a local macro, look in local context */
3781             if (tline->type == TOK_ID || tline->type == TOK_PREPROC_ID)
3782                 ctx = get_ctx(mname, &mname, true);
3783             else
3784                 ctx = NULL;
3785             smtbl = ctx ? &ctx->localmac : &smacros;
3786             head = (SMacro *) hash_findix(smtbl, mname);
3787
3788             /*
3789              * We've hit an identifier. As in is_mmacro below, we first
3790              * check whether the identifier is a single-line macro at
3791              * all, then think about checking for parameters if
3792              * necessary.
3793              */
3794             for (m = head; m; m = m->next)
3795                 if (!mstrcmp(m->name, mname, m->casesense))
3796                     break;
3797             if (m) {
3798                 mstart = tline;
3799                 params = NULL;
3800                 paramsize = NULL;
3801                 if (m->nparam == 0) {
3802                     /*
3803                      * Simple case: the macro is parameterless. Discard the
3804                      * one token that the macro call took, and push the
3805                      * expansion back on the to-do stack.
3806                      */
3807                     if (!m->expansion) {
3808                         if (!strcmp("__FILE__", m->name)) {
3809                             int32_t num = 0;
3810                             char *file = NULL;
3811                             src_get(&num, &file);
3812                             tline->text = nasm_quote(file, strlen(file));
3813                             tline->type = TOK_STRING;
3814                             nasm_free(file);
3815                             continue;
3816                         }
3817                         if (!strcmp("__LINE__", m->name)) {
3818                             nasm_free(tline->text);
3819                             make_tok_num(tline, src_get_linnum());
3820                             continue;
3821                         }
3822                         if (!strcmp("__BITS__", m->name)) {
3823                             nasm_free(tline->text);
3824                             make_tok_num(tline, globalbits);
3825                             continue;
3826                         }
3827                         tline = delete_Token(tline);
3828                         continue;
3829                     }
3830                 } else {
3831                     /*
3832                      * Complicated case: at least one macro with this name
3833                      * exists and takes parameters. We must find the
3834                      * parameters in the call, count them, find the SMacro
3835                      * that corresponds to that form of the macro call, and
3836                      * substitute for the parameters when we expand. What a
3837                      * pain.
3838                      */
3839                     /*tline = tline->next;
3840                       skip_white_(tline); */
3841                     do {
3842                         t = tline->next;
3843                         while (tok_type_(t, TOK_SMAC_END)) {
3844                             t->a.mac->in_progress = false;
3845                             t->text = NULL;
3846                             t = tline->next = delete_Token(t);
3847                         }
3848                         tline = t;
3849                     } while (tok_type_(tline, TOK_WHITESPACE));
3850                     if (!tok_is_(tline, "(")) {
3851                         /*
3852                          * This macro wasn't called with parameters: ignore
3853                          * the call. (Behaviour borrowed from gnu cpp.)
3854                          */
3855                         tline = mstart;
3856                         m = NULL;
3857                     } else {
3858                         int paren = 0;
3859                         int white = 0;
3860                         brackets = 0;
3861                         nparam = 0;
3862                         sparam = PARAM_DELTA;
3863                         params = nasm_malloc(sparam * sizeof(Token *));
3864                         params[0] = tline->next;
3865                         paramsize = nasm_malloc(sparam * sizeof(int));
3866                         paramsize[0] = 0;
3867                         while (true) {  /* parameter loop */
3868                             /*
3869                              * For some unusual expansions
3870                              * which concatenates function call
3871                              */
3872                             t = tline->next;
3873                             while (tok_type_(t, TOK_SMAC_END)) {
3874                                 t->a.mac->in_progress = false;
3875                                 t->text = NULL;
3876                                 t = tline->next = delete_Token(t);
3877                             }
3878                             tline = t;
3879
3880                             if (!tline) {
3881                                 error(ERR_NONFATAL,
3882                                       "macro call expects terminating `)'");
3883                                 break;
3884                             }
3885                             if (tline->type == TOK_WHITESPACE
3886                                 && brackets <= 0) {
3887                                 if (paramsize[nparam])
3888                                     white++;
3889                                 else
3890                                     params[nparam] = tline->next;
3891                                 continue;       /* parameter loop */
3892                             }
3893                             if (tline->type == TOK_OTHER
3894                                 && tline->text[1] == 0) {
3895                                 char ch = tline->text[0];
3896                                 if (ch == ',' && !paren && brackets <= 0) {
3897                                     if (++nparam >= sparam) {
3898                                         sparam += PARAM_DELTA;
3899                                         params = nasm_realloc(params,
3900                                                               sparam *
3901                                                               sizeof(Token
3902                                                                      *));
3903                                         paramsize =
3904                                             nasm_realloc(paramsize,
3905                                                          sparam *
3906                                                          sizeof(int));
3907                                     }
3908                                     params[nparam] = tline->next;
3909                                     paramsize[nparam] = 0;
3910                                     white = 0;
3911                                     continue;   /* parameter loop */
3912                                 }
3913                                 if (ch == '{' &&
3914                                     (brackets > 0 || (brackets == 0 &&
3915                                                       !paramsize[nparam])))
3916                                 {
3917                                     if (!(brackets++)) {
3918                                         params[nparam] = tline->next;
3919                                         continue;       /* parameter loop */
3920                                     }
3921                                 }
3922                                 if (ch == '}' && brackets > 0)
3923                                     if (--brackets == 0) {
3924                                         brackets = -1;
3925                                         continue;       /* parameter loop */
3926                                     }
3927                                 if (ch == '(' && !brackets)
3928                                     paren++;
3929                                 if (ch == ')' && brackets <= 0)
3930                                     if (--paren < 0)
3931                                         break;
3932                             }
3933                             if (brackets < 0) {
3934                                 brackets = 0;
3935                                 error(ERR_NONFATAL, "braces do not "
3936                                       "enclose all of macro parameter");
3937                             }
3938                             paramsize[nparam] += white + 1;
3939                             white = 0;
3940                         }       /* parameter loop */
3941                         nparam++;
3942                         while (m && (m->nparam != nparam ||
3943                                      mstrcmp(m->name, mname,
3944                                              m->casesense)))
3945                             m = m->next;
3946                         if (!m)
3947                             error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
3948                                   "macro `%s' exists, "
3949                                   "but not taking %d parameters",
3950                                   mstart->text, nparam);
3951                     }
3952                 }
3953                 if (m && m->in_progress)
3954                     m = NULL;
3955                 if (!m) {       /* in progess or didn't find '(' or wrong nparam */
3956                     /*
3957                      * Design question: should we handle !tline, which
3958                      * indicates missing ')' here, or expand those
3959                      * macros anyway, which requires the (t) test a few
3960                      * lines down?
3961                      */
3962                     nasm_free(params);
3963                     nasm_free(paramsize);
3964                     tline = mstart;
3965                 } else {
3966                     /*
3967                      * Expand the macro: we are placed on the last token of the
3968                      * call, so that we can easily split the call from the
3969                      * following tokens. We also start by pushing an SMAC_END
3970                      * token for the cycle removal.
3971                      */
3972                     t = tline;
3973                     if (t) {
3974                         tline = t->next;
3975                         t->next = NULL;
3976                     }
3977                     tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
3978                     tt->a.mac = m;
3979                     m->in_progress = true;
3980                     tline = tt;
3981                     for (t = m->expansion; t; t = t->next) {
3982                         if (t->type >= TOK_SMAC_PARAM) {
3983                             Token *pcopy = tline, **ptail = &pcopy;
3984                             Token *ttt, *pt;
3985                             int i;
3986
3987                             ttt = params[t->type - TOK_SMAC_PARAM];
3988                             for (i = paramsize[t->type - TOK_SMAC_PARAM];
3989                                  --i >= 0;) {
3990                                 pt = *ptail =
3991                                     new_Token(tline, ttt->type, ttt->text,
3992                                               0);
3993                                 ptail = &pt->next;
3994                                 ttt = ttt->next;
3995                             }
3996                             tline = pcopy;
3997                         } else if (t->type == TOK_PREPROC_Q) {
3998                             tt = new_Token(tline, TOK_ID, mname, 0);
3999                             tline = tt;
4000                         } else if (t->type == TOK_PREPROC_QQ) {
4001                             tt = new_Token(tline, TOK_ID, m->name, 0);
4002                             tline = tt;
4003                         } else {
4004                             tt = new_Token(tline, t->type, t->text, 0);
4005                             tline = tt;
4006                         }
4007                     }
4008
4009                     /*
4010                      * Having done that, get rid of the macro call, and clean
4011                      * up the parameters.
4012                      */
4013                     nasm_free(params);
4014                     nasm_free(paramsize);
4015                     free_tlist(mstart);
4016                     expanded = true;
4017                     continue;   /* main token loop */
4018                 }
4019             }
4020         }
4021
4022         if (tline->type == TOK_SMAC_END) {
4023             tline->a.mac->in_progress = false;
4024             tline = delete_Token(tline);
4025         } else {
4026             t = *tail = tline;
4027             tline = tline->next;
4028             t->a.mac = NULL;
4029             t->next = NULL;
4030             tail = &t->next;
4031         }
4032     }
4033
4034     /*
4035      * Now scan the entire line and look for successive TOK_IDs that resulted
4036      * after expansion (they can't be produced by tokenize()). The successive
4037      * TOK_IDs should be concatenated.
4038      * Also we look for %+ tokens and concatenate the tokens before and after
4039      * them (without white spaces in between).
4040      */
4041     if (expanded && paste_tokens(&thead, true)) {
4042         /*
4043          * If we concatenated something, *and* we had previously expanded
4044          * an actual macro, scan the lines again for macros...
4045          */
4046         tline = thead;
4047         expanded = false;
4048         goto again;
4049     }
4050
4051     if (org_tline) {
4052         if (thead) {
4053             *org_tline = *thead;
4054             /* since we just gave text to org_line, don't free it */
4055             thead->text = NULL;
4056             delete_Token(thead);
4057         } else {
4058             /* the expression expanded to empty line;
4059                we can't return NULL for some reasons
4060                we just set the line to a single WHITESPACE token. */
4061             memset(org_tline, 0, sizeof(*org_tline));
4062             org_tline->text = NULL;
4063             org_tline->type = TOK_WHITESPACE;
4064         }
4065         thead = org_tline;
4066     }
4067
4068     return thead;
4069 }
4070
4071 /*
4072  * Similar to expand_smacro but used exclusively with macro identifiers
4073  * right before they are fetched in. The reason is that there can be
4074  * identifiers consisting of several subparts. We consider that if there
4075  * are more than one element forming the name, user wants a expansion,
4076  * otherwise it will be left as-is. Example:
4077  *
4078  *      %define %$abc cde
4079  *
4080  * the identifier %$abc will be left as-is so that the handler for %define
4081  * will suck it and define the corresponding value. Other case:
4082  *
4083  *      %define _%$abc cde
4084  *
4085  * In this case user wants name to be expanded *before* %define starts
4086  * working, so we'll expand %$abc into something (if it has a value;
4087  * otherwise it will be left as-is) then concatenate all successive
4088  * PP_IDs into one.
4089  */
4090 static Token *expand_id(Token * tline)
4091 {
4092     Token *cur, *oldnext = NULL;
4093
4094     if (!tline || !tline->next)
4095         return tline;
4096
4097     cur = tline;
4098     while (cur->next &&
4099            (cur->next->type == TOK_ID ||
4100             cur->next->type == TOK_PREPROC_ID
4101             || cur->next->type == TOK_NUMBER))
4102         cur = cur->next;
4103
4104     /* If identifier consists of just one token, don't expand */
4105     if (cur == tline)
4106         return tline;
4107
4108     if (cur) {
4109         oldnext = cur->next;    /* Detach the tail past identifier */
4110         cur->next = NULL;       /* so that expand_smacro stops here */
4111     }
4112
4113     tline = expand_smacro(tline);
4114
4115     if (cur) {
4116         /* expand_smacro possibly changhed tline; re-scan for EOL */
4117         cur = tline;
4118         while (cur && cur->next)
4119             cur = cur->next;
4120         if (cur)
4121             cur->next = oldnext;
4122     }
4123
4124     return tline;
4125 }
4126
4127 /*
4128  * Determine whether the given line constitutes a multi-line macro
4129  * call, and return the MMacro structure called if so. Doesn't have
4130  * to check for an initial label - that's taken care of in
4131  * expand_mmacro - but must check numbers of parameters. Guaranteed
4132  * to be called with tline->type == TOK_ID, so the putative macro
4133  * name is easy to find.
4134  */
4135 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4136 {
4137     MMacro *head, *m;
4138     Token **params;
4139     int nparam;
4140
4141     head = (MMacro *) hash_findix(&mmacros, tline->text);
4142
4143     /*
4144      * Efficiency: first we see if any macro exists with the given
4145      * name. If not, we can return NULL immediately. _Then_ we
4146      * count the parameters, and then we look further along the
4147      * list if necessary to find the proper MMacro.
4148      */
4149     for (m = head; m; m = m->next)
4150         if (!mstrcmp(m->name, tline->text, m->casesense))
4151             break;
4152     if (!m)
4153         return NULL;
4154
4155     /*
4156      * OK, we have a potential macro. Count and demarcate the
4157      * parameters.
4158      */
4159     count_mmac_params(tline->next, &nparam, &params);
4160
4161     /*
4162      * So we know how many parameters we've got. Find the MMacro
4163      * structure that handles this number.
4164      */
4165     while (m) {
4166         if (m->nparam_min <= nparam
4167             && (m->plus || nparam <= m->nparam_max)) {
4168             /*
4169              * This one is right. Just check if cycle removal
4170              * prohibits us using it before we actually celebrate...
4171              */
4172             if (m->in_progress > m->max_depth) {
4173                 if (m->max_depth > 0) {
4174                     error(ERR_WARNING,
4175                           "reached maximum recursion depth of %i",
4176                           m->max_depth);
4177                 }
4178                 nasm_free(params);
4179                 return NULL;
4180             }
4181             /*
4182              * It's right, and we can use it. Add its default
4183              * parameters to the end of our list if necessary.
4184              */
4185             if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4186                 params =
4187                     nasm_realloc(params,
4188                                  ((m->nparam_min + m->ndefs +
4189                                    1) * sizeof(*params)));
4190                 while (nparam < m->nparam_min + m->ndefs) {
4191                     params[nparam] = m->defaults[nparam - m->nparam_min];
4192                     nparam++;
4193                 }
4194             }
4195             /*
4196              * If we've gone over the maximum parameter count (and
4197              * we're in Plus mode), ignore parameters beyond
4198              * nparam_max.
4199              */
4200             if (m->plus && nparam > m->nparam_max)
4201                 nparam = m->nparam_max;
4202             /*
4203              * Then terminate the parameter list, and leave.
4204              */
4205             if (!params) {      /* need this special case */
4206                 params = nasm_malloc(sizeof(*params));
4207                 nparam = 0;
4208             }
4209             params[nparam] = NULL;
4210             *params_array = params;
4211             return m;
4212         }
4213         /*
4214          * This one wasn't right: look for the next one with the
4215          * same name.
4216          */
4217         for (m = m->next; m; m = m->next)
4218             if (!mstrcmp(m->name, tline->text, m->casesense))
4219                 break;
4220     }
4221
4222     /*
4223      * After all that, we didn't find one with the right number of
4224      * parameters. Issue a warning, and fail to expand the macro.
4225      */
4226     error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4227           "macro `%s' exists, but not taking %d parameters",
4228           tline->text, nparam);
4229     nasm_free(params);
4230     return NULL;
4231 }
4232
4233
4234 /*
4235  * Save MMacro invocation specific fields in
4236  * preparation for a recursive macro expansion
4237  */
4238 static void push_mmacro(MMacro *m)
4239 {
4240     MMacroInvocation *i;
4241
4242     i = nasm_malloc(sizeof(MMacroInvocation));
4243     i->prev = m->prev;
4244     i->params = m->params;
4245     i->iline = m->iline;
4246     i->nparam = m->nparam;
4247     i->rotate = m->rotate;
4248     i->paramlen = m->paramlen;
4249     i->unique = m->unique;
4250     m->prev = i;
4251 }
4252
4253
4254 /*
4255  * Restore MMacro invocation specific fields that were
4256  * saved during a previous recursive macro expansion
4257  */
4258 static void pop_mmacro(MMacro *m)
4259 {
4260     MMacroInvocation *i;
4261
4262     if (m->prev) {
4263         i = m->prev;
4264         m->prev = i->prev;
4265         m->params = i->params;
4266         m->iline = i->iline;
4267         m->nparam = i->nparam;
4268         m->rotate = i->rotate;
4269         m->paramlen = i->paramlen;
4270         m->unique = i->unique;
4271         nasm_free(i);
4272     }
4273 }
4274
4275
4276 /*
4277  * Expand the multi-line macro call made by the given line, if
4278  * there is one to be expanded. If there is, push the expansion on
4279  * istk->expansion and return 1. Otherwise return 0.
4280  */
4281 static int expand_mmacro(Token * tline)
4282 {
4283     Token *startline = tline;
4284     Token *label = NULL;
4285     int dont_prepend = 0;
4286     Token **params, *t, *mtok, *tt;
4287     MMacro *m;
4288     Line *l, *ll;
4289     int i, nparam, *paramlen;
4290     const char *mname;
4291
4292     t = tline;
4293     skip_white_(t);
4294     /*    if (!tok_type_(t, TOK_ID))  Lino 02/25/02 */
4295     if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4296         return 0;
4297     mtok = t;
4298     m = is_mmacro(t, &params);
4299     if (m) {
4300         mname = t->text;
4301     } else {
4302         Token *last;
4303         /*
4304          * We have an id which isn't a macro call. We'll assume
4305          * it might be a label; we'll also check to see if a
4306          * colon follows it. Then, if there's another id after
4307          * that lot, we'll check it again for macro-hood.
4308          */
4309         label = last = t;
4310         t = t->next;
4311         if (tok_type_(t, TOK_WHITESPACE))
4312             last = t, t = t->next;
4313         if (tok_is_(t, ":")) {
4314             dont_prepend = 1;
4315             last = t, t = t->next;
4316             if (tok_type_(t, TOK_WHITESPACE))
4317                 last = t, t = t->next;
4318         }
4319         if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4320             return 0;
4321         last->next = NULL;
4322         mname = t->text;
4323         tline = t;
4324     }
4325
4326     /*
4327      * Fix up the parameters: this involves stripping leading and
4328      * trailing whitespace, then stripping braces if they are
4329      * present.
4330      */
4331     for (nparam = 0; params[nparam]; nparam++) ;
4332     paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4333
4334     for (i = 0; params[i]; i++) {
4335         int brace = false;
4336         int comma = (!m->plus || i < nparam - 1);
4337
4338         t = params[i];
4339         skip_white_(t);
4340         if (tok_is_(t, "{"))
4341             t = t->next, brace = true, comma = false;
4342         params[i] = t;
4343         paramlen[i] = 0;
4344         while (t) {
4345             if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4346                 break;          /* ... because we have hit a comma */
4347             if (comma && t->type == TOK_WHITESPACE
4348                 && tok_is_(t->next, ","))
4349                 break;          /* ... or a space then a comma */
4350             if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4351                 break;          /* ... or a brace */
4352             t = t->next;
4353             paramlen[i]++;
4354         }
4355     }
4356
4357     /*
4358      * OK, we have a MMacro structure together with a set of
4359      * parameters. We must now go through the expansion and push
4360      * copies of each Line on to istk->expansion. Substitution of
4361      * parameter tokens and macro-local tokens doesn't get done
4362      * until the single-line macro substitution process; this is
4363      * because delaying them allows us to change the semantics
4364      * later through %rotate.
4365      *
4366      * First, push an end marker on to istk->expansion, mark this
4367      * macro as in progress, and set up its invocation-specific
4368      * variables.
4369      */
4370     ll = nasm_malloc(sizeof(Line));
4371     ll->next = istk->expansion;
4372     ll->finishes = m;
4373     ll->first = NULL;
4374     istk->expansion = ll;
4375         
4376     /*
4377      * Save the previous MMacro expansion in the case of
4378      * macro recursion
4379      */
4380     if (m->max_depth && m->in_progress)
4381         push_mmacro(m);
4382
4383     m->in_progress ++;
4384     m->params = params;
4385     m->iline = tline;
4386     m->nparam = nparam;
4387     m->rotate = 0;
4388     m->paramlen = paramlen;
4389     m->unique = unique++;
4390     m->lineno = 0;
4391
4392     m->next_active = istk->mstk;
4393     istk->mstk = m;
4394
4395     for (l = m->expansion; l; l = l->next) {
4396         Token **tail;
4397
4398         ll = nasm_malloc(sizeof(Line));
4399         ll->finishes = NULL;
4400         ll->next = istk->expansion;
4401         istk->expansion = ll;
4402         tail = &ll->first;
4403
4404         for (t = l->first; t; t = t->next) {
4405             Token *x = t;
4406             switch (t->type) {
4407             case TOK_PREPROC_Q:
4408                 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4409                 break;
4410             case TOK_PREPROC_QQ:
4411                 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4412                 break;
4413             case TOK_PREPROC_ID:
4414                 if (t->text[1] == '0' && t->text[2] == '0') {
4415                     dont_prepend = -1;
4416                     x = label;
4417                     if (!x)
4418                         continue;
4419                 }
4420                 /* fall through */
4421             default:
4422                 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4423                 break;
4424             }
4425             tail = &tt->next;
4426         }
4427         *tail = NULL;
4428     }
4429
4430     /*
4431      * If we had a label, push it on as the first line of
4432      * the macro expansion.
4433      */
4434     if (label) {
4435         if (dont_prepend < 0)
4436             free_tlist(startline);
4437         else {
4438             ll = nasm_malloc(sizeof(Line));
4439             ll->finishes = NULL;
4440             ll->next = istk->expansion;
4441             istk->expansion = ll;
4442             ll->first = startline;
4443             if (!dont_prepend) {
4444                 while (label->next)
4445                     label = label->next;
4446                 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4447             }
4448         }
4449     }
4450
4451     list->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4452
4453     return 1;
4454 }
4455
4456 /* The function that actually does the error reporting */
4457 static void verror(int severity, const char *fmt, va_list arg)
4458 {
4459     char buff[1024];
4460
4461     vsnprintf(buff, sizeof(buff), fmt, arg);
4462
4463     if (istk && istk->mstk && istk->mstk->name)
4464         nasm_error(severity, "(%s:%d) %s", istk->mstk->name,
4465                istk->mstk->lineno, buff);
4466     else
4467         nasm_error(severity, "%s", buff);
4468 }
4469
4470 /*
4471  * Since preprocessor always operate only on the line that didn't
4472  * arrived yet, we should always use ERR_OFFBY1.
4473  */
4474 static void error(int severity, const char *fmt, ...)
4475 {
4476     va_list arg;
4477
4478     /* If we're in a dead branch of IF or something like it, ignore the error */
4479     if (istk && istk->conds && !emitting(istk->conds->state))
4480         return;
4481
4482     va_start(arg, fmt);
4483     verror(severity, fmt, arg);
4484     va_end(arg);
4485 }
4486
4487 /*
4488  * Because %else etc are evaluated in the state context
4489  * of the previous branch, errors might get lost with error():
4490  *   %if 0 ... %else trailing garbage ... %endif
4491  * So %else etc should report errors with this function.
4492  */
4493 static void error_precond(int severity, const char *fmt, ...)
4494 {
4495     va_list arg;
4496
4497     /* Only ignore the error if it's really in a dead branch */
4498     if (istk && istk->conds && istk->conds->state == COND_NEVER)
4499         return;
4500
4501     va_start(arg, fmt);
4502     verror(severity, fmt, arg);
4503     va_end(arg);
4504 }
4505
4506 static void
4507 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4508 {
4509     Token *t;
4510
4511     cstk = NULL;
4512     istk = nasm_malloc(sizeof(Include));
4513     istk->next = NULL;
4514     istk->conds = NULL;
4515     istk->expansion = NULL;
4516     istk->mstk = NULL;
4517     istk->fp = fopen(file, "r");
4518     istk->fname = NULL;
4519     src_set_fname(nasm_strdup(file));
4520     src_set_linnum(0);
4521     istk->lineinc = 1;
4522     if (!istk->fp)
4523         error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4524               file);
4525     defining = NULL;
4526     nested_mac_count = 0;
4527     nested_rep_count = 0;
4528     init_macros();
4529     unique = 0;
4530     if (tasm_compatible_mode) {
4531         stdmacpos = nasm_stdmac;
4532     } else {
4533         stdmacpos = nasm_stdmac_after_tasm;
4534     }
4535     any_extrastdmac = extrastdmac && *extrastdmac;
4536     do_predef = true;
4537     list = listgen;
4538
4539     /*
4540      * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4541      * The caller, however, will also pass in 3 for preprocess-only so
4542      * we can set __PASS__ accordingly.
4543      */
4544     pass = apass > 2 ? 2 : apass;
4545
4546     dephead = deptail = deplist;
4547     if (deplist) {
4548         StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4549         sl->next = NULL;
4550         strcpy(sl->str, file);
4551         *deptail = sl;
4552         deptail = &sl->next;
4553     }
4554
4555     /*
4556      * Define the __PASS__ macro.  This is defined here unlike
4557      * all the other builtins, because it is special -- it varies between
4558      * passes.
4559      */
4560     t = nasm_malloc(sizeof(*t));
4561     t->next = NULL;
4562     make_tok_num(t, apass);
4563     t->a.mac = NULL;
4564     define_smacro(NULL, "__PASS__", true, 0, t);
4565 }
4566
4567 static char *pp_getline(void)
4568 {
4569     char *line;
4570     Token *tline;
4571
4572     while (1) {
4573         /*
4574          * Fetch a tokenized line, either from the macro-expansion
4575          * buffer or from the input file.
4576          */
4577         tline = NULL;
4578         while (istk->expansion && istk->expansion->finishes) {
4579             Line *l = istk->expansion;
4580             if (!l->finishes->name && l->finishes->in_progress > 1) {
4581                 Line *ll;
4582
4583                 /*
4584                  * This is a macro-end marker for a macro with no
4585                  * name, which means it's not really a macro at all
4586                  * but a %rep block, and the `in_progress' field is
4587                  * more than 1, meaning that we still need to
4588                  * repeat. (1 means the natural last repetition; 0
4589                  * means termination by %exitrep.) We have
4590                  * therefore expanded up to the %endrep, and must
4591                  * push the whole block on to the expansion buffer
4592                  * again. We don't bother to remove the macro-end
4593                  * marker: we'd only have to generate another one
4594                  * if we did.
4595                  */
4596                 l->finishes->in_progress--;
4597                 for (l = l->finishes->expansion; l; l = l->next) {
4598                     Token *t, *tt, **tail;
4599
4600                     ll = nasm_malloc(sizeof(Line));
4601                     ll->next = istk->expansion;
4602                     ll->finishes = NULL;
4603                     ll->first = NULL;
4604                     tail = &ll->first;
4605
4606                     for (t = l->first; t; t = t->next) {
4607                         if (t->text || t->type == TOK_WHITESPACE) {
4608                             tt = *tail =
4609                                 new_Token(NULL, t->type, t->text, 0);
4610                             tail = &tt->next;
4611                         }
4612                     }
4613
4614                     istk->expansion = ll;
4615                 }
4616             } else {
4617                 /*
4618                  * Check whether a `%rep' was started and not ended
4619                  * within this macro expansion. This can happen and
4620                  * should be detected. It's a fatal error because
4621                  * I'm too confused to work out how to recover
4622                  * sensibly from it.
4623                  */
4624                 if (defining) {
4625                     if (defining->name)
4626                         error(ERR_PANIC,
4627                               "defining with name in expansion");
4628                     else if (istk->mstk->name)
4629                         error(ERR_FATAL,
4630                               "`%%rep' without `%%endrep' within"
4631                               " expansion of macro `%s'",
4632                               istk->mstk->name);
4633                 }
4634
4635                 /*
4636                  * FIXME:  investigate the relationship at this point between
4637                  * istk->mstk and l->finishes
4638                  */
4639                 {
4640                     MMacro *m = istk->mstk;
4641                     istk->mstk = m->next_active;
4642                     if (m->name) {
4643                         /*
4644                          * This was a real macro call, not a %rep, and
4645                          * therefore the parameter information needs to
4646                          * be freed.
4647                          */
4648                         if (m->prev) {
4649                             pop_mmacro(m);
4650                             l->finishes->in_progress --;
4651                         } else {
4652                             nasm_free(m->params);
4653                             free_tlist(m->iline);
4654                             nasm_free(m->paramlen);
4655                             l->finishes->in_progress = 0;
4656                         }
4657                     } else
4658                         free_mmacro(m);
4659                 }
4660                 istk->expansion = l->next;
4661                 nasm_free(l);
4662                 list->downlevel(LIST_MACRO);
4663             }
4664         }
4665         while (1) {             /* until we get a line we can use */
4666
4667             if (istk->expansion) {      /* from a macro expansion */
4668                 char *p;
4669                 Line *l = istk->expansion;
4670                 if (istk->mstk)
4671                     istk->mstk->lineno++;
4672                 tline = l->first;
4673                 istk->expansion = l->next;
4674                 nasm_free(l);
4675                 p = detoken(tline, false);
4676                 list->line(LIST_MACRO, p);
4677                 nasm_free(p);
4678                 break;
4679             }
4680             line = read_line();
4681             if (line) {         /* from the current input file */
4682                 line = prepreproc(line);
4683                 tline = tokenize(line);
4684                 nasm_free(line);
4685                 break;
4686             }
4687             /*
4688              * The current file has ended; work down the istk
4689              */
4690             {
4691                 Include *i = istk;
4692                 fclose(i->fp);
4693                 if (i->conds)
4694                     error(ERR_FATAL,
4695                           "expected `%%endif' before end of file");
4696                 /* only set line and file name if there's a next node */
4697                 if (i->next) {
4698                     src_set_linnum(i->lineno);
4699                     nasm_free(src_set_fname(i->fname));
4700                 }
4701                 istk = i->next;
4702                 list->downlevel(LIST_INCLUDE);
4703                 nasm_free(i);
4704                 if (!istk)
4705                     return NULL;
4706                 if (istk->expansion && istk->expansion->finishes)
4707                     break;
4708             }
4709         }
4710
4711         /*
4712          * We must expand MMacro parameters and MMacro-local labels
4713          * _before_ we plunge into directive processing, to cope
4714          * with things like `%define something %1' such as STRUC
4715          * uses. Unless we're _defining_ a MMacro, in which case
4716          * those tokens should be left alone to go into the
4717          * definition; and unless we're in a non-emitting
4718          * condition, in which case we don't want to meddle with
4719          * anything.
4720          */
4721         if (!defining && !(istk->conds && !emitting(istk->conds->state))
4722             && !(istk->mstk && !istk->mstk->in_progress)) {
4723             tline = expand_mmac_params(tline);
4724         }
4725
4726         /*
4727          * Check the line to see if it's a preprocessor directive.
4728          */
4729         if (do_directive(tline) == DIRECTIVE_FOUND) {
4730             continue;
4731         } else if (defining) {
4732             /*
4733              * We're defining a multi-line macro. We emit nothing
4734              * at all, and just
4735              * shove the tokenized line on to the macro definition.
4736              */
4737             Line *l = nasm_malloc(sizeof(Line));
4738             l->next = defining->expansion;
4739             l->first = tline;
4740             l->finishes = NULL;
4741             defining->expansion = l;
4742             continue;
4743         } else if (istk->conds && !emitting(istk->conds->state)) {
4744             /*
4745              * We're in a non-emitting branch of a condition block.
4746              * Emit nothing at all, not even a blank line: when we
4747              * emerge from the condition we'll give a line-number
4748              * directive so we keep our place correctly.
4749              */
4750             free_tlist(tline);
4751             continue;
4752         } else if (istk->mstk && !istk->mstk->in_progress) {
4753             /*
4754              * We're in a %rep block which has been terminated, so
4755              * we're walking through to the %endrep without
4756              * emitting anything. Emit nothing at all, not even a
4757              * blank line: when we emerge from the %rep block we'll
4758              * give a line-number directive so we keep our place
4759              * correctly.
4760              */
4761             free_tlist(tline);
4762             continue;
4763         } else {
4764             tline = expand_smacro(tline);
4765             if (!expand_mmacro(tline)) {
4766                 /*
4767                  * De-tokenize the line again, and emit it.
4768                  */
4769                 line = detoken(tline, true);
4770                 free_tlist(tline);
4771                 break;
4772             } else {
4773                 continue;       /* expand_mmacro calls free_tlist */
4774             }
4775         }
4776     }
4777
4778     return line;
4779 }
4780
4781 static void pp_cleanup(int pass)
4782 {
4783     if (defining) {
4784         if (defining->name) {
4785             error(ERR_NONFATAL,
4786                   "end of file while still defining macro `%s'",
4787                   defining->name);
4788         } else {
4789             error(ERR_NONFATAL, "end of file while still in %%rep");
4790         }
4791
4792         free_mmacro(defining);
4793     }
4794     while (cstk)
4795         ctx_pop();
4796     free_macros();
4797     while (istk) {
4798         Include *i = istk;
4799         istk = istk->next;
4800         fclose(i->fp);
4801         nasm_free(i->fname);
4802         nasm_free(i);
4803     }
4804     while (cstk)
4805         ctx_pop();
4806     nasm_free(src_set_fname(NULL));
4807     if (pass == 0) {
4808         IncPath *i;
4809         free_llist(predef);
4810         delete_Blocks();
4811         while ((i = ipath)) {
4812             ipath = i->next;
4813             if (i->path)
4814                 nasm_free(i->path);
4815             nasm_free(i);
4816         }
4817     }
4818 }
4819
4820 void pp_include_path(char *path)
4821 {
4822     IncPath *i;
4823
4824     i = nasm_malloc(sizeof(IncPath));
4825     i->path = path ? nasm_strdup(path) : NULL;
4826     i->next = NULL;
4827
4828     if (ipath) {
4829         IncPath *j = ipath;
4830         while (j->next)
4831             j = j->next;
4832         j->next = i;
4833     } else {
4834         ipath = i;
4835     }
4836 }
4837
4838 void pp_pre_include(char *fname)
4839 {
4840     Token *inc, *space, *name;
4841     Line *l;
4842
4843     name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
4844     space = new_Token(name, TOK_WHITESPACE, NULL, 0);
4845     inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
4846
4847     l = nasm_malloc(sizeof(Line));
4848     l->next = predef;
4849     l->first = inc;
4850     l->finishes = NULL;
4851     predef = l;
4852 }
4853
4854 void pp_pre_define(char *definition)
4855 {
4856     Token *def, *space;
4857     Line *l;
4858     char *equals;
4859
4860     equals = strchr(definition, '=');
4861     space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4862     def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
4863     if (equals)
4864         *equals = ' ';
4865     space->next = tokenize(definition);
4866     if (equals)
4867         *equals = '=';
4868
4869     l = nasm_malloc(sizeof(Line));
4870     l->next = predef;
4871     l->first = def;
4872     l->finishes = NULL;
4873     predef = l;
4874 }
4875
4876 void pp_pre_undefine(char *definition)
4877 {
4878     Token *def, *space;
4879     Line *l;
4880
4881     space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4882     def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
4883     space->next = tokenize(definition);
4884
4885     l = nasm_malloc(sizeof(Line));
4886     l->next = predef;
4887     l->first = def;
4888     l->finishes = NULL;
4889     predef = l;
4890 }
4891
4892 /*
4893  * Added by Keith Kanios:
4894  *
4895  * This function is used to assist with "runtime" preprocessor
4896  * directives. (e.g. pp_runtime("%define __BITS__ 64");)
4897  *
4898  * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
4899  * PASS A VALID STRING TO THIS FUNCTION!!!!!
4900  */
4901
4902 void pp_runtime(char *definition)
4903 {
4904     Token *def;
4905
4906     def = tokenize(definition);
4907     if (do_directive(def) == NO_DIRECTIVE_FOUND)
4908         free_tlist(def);
4909
4910 }
4911
4912 void pp_extra_stdmac(macros_t *macros)
4913 {
4914     extrastdmac = macros;
4915 }
4916
4917 static void make_tok_num(Token * tok, int64_t val)
4918 {
4919     char numbuf[20];
4920     snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
4921     tok->text = nasm_strdup(numbuf);
4922     tok->type = TOK_NUMBER;
4923 }
4924
4925 Preproc nasmpp = {
4926     pp_reset,
4927     pp_getline,
4928     pp_cleanup
4929 };