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