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