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