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