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