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