preproc_init: Just clean include path
[nasm.git] / asm / preproc.c
blobb6afee39c2864916dcff4dc5d17a99c1393bd2e3
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2018 The NASM Authors - All Rights Reserved
4 * See the file AUTHORS included with the NASM distribution for
5 * the specific copyright holders.
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following
9 * conditions are met:
11 * * Redistributions of source code must retain the above copyright
12 * notice, this list of conditions and the following disclaimer.
13 * * Redistributions in binary form must reproduce the above
14 * copyright notice, this list of conditions and the following
15 * disclaimer in the documentation and/or other materials provided
16 * with the distribution.
18 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND
19 * CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
20 * INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
21 * MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
22 * DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR
23 * CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
24 * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
25 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
26 * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
27 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
28 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
29 * OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
30 * EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32 * ----------------------------------------------------------------------- */
35 * preproc.c macro preprocessor for the Netwide Assembler
38 /* Typical flow of text through preproc
40 * pp_getline gets tokenized lines, either
42 * from a macro expansion
44 * or
45 * {
46 * read_line gets raw text from stdmacpos, or predef, or current input file
47 * tokenize converts to tokens
48 * }
50 * expand_mmac_params is used to expand %1 etc., unless a macro is being
51 * defined or a false conditional is being processed
52 * (%0, %1, %+1, %-1, %%foo
54 * do_directive checks for directives
56 * expand_smacro is used to expand single line macros
58 * expand_mmacro is used to expand multi-line macros
60 * detoken is used to convert the line back to text
63 #include "compiler.h"
65 #include <stdio.h>
66 #include <stdarg.h>
67 #include <stdlib.h>
68 #include <stddef.h>
69 #include <string.h>
70 #include <ctype.h>
71 #include <limits.h>
73 #include "nasm.h"
74 #include "nasmlib.h"
75 #include "error.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
83 #include "listing.h"
85 typedef struct SMacro SMacro;
86 typedef struct MMacro MMacro;
87 typedef struct MMacroInvocation MMacroInvocation;
88 typedef struct Context Context;
89 typedef struct Token Token;
90 typedef struct Blocks Blocks;
91 typedef struct Line Line;
92 typedef struct Include Include;
93 typedef struct Cond Cond;
96 * Note on the storage of both SMacro and MMacros: the hash table
97 * indexes them case-insensitively, and we then have to go through a
98 * linked list of potential case aliases (and, for MMacros, parameter
99 * ranges); this is to preserve the matching semantics of the earlier
100 * code. If the number of case aliases for a specific macro is a
101 * performance issue, you may want to reconsider your coding style.
105 * Store the definition of a single-line macro.
107 struct SMacro {
108 SMacro *next;
109 char *name;
110 bool casesense;
111 bool in_progress;
112 unsigned int nparam;
113 Token *expansion;
117 * Store the definition of a multi-line macro. This is also used to
118 * store the interiors of `%rep...%endrep' blocks, which are
119 * effectively self-re-invoking multi-line macros which simply
120 * don't have a name or bother to appear in the hash tables. %rep
121 * blocks are signified by having a NULL `name' field.
123 * In a MMacro describing a `%rep' block, the `in_progress' field
124 * isn't merely boolean, but gives the number of repeats left to
125 * run.
127 * The `next' field is used for storing MMacros in hash tables; the
128 * `next_active' field is for stacking them on istk entries.
130 * When a MMacro is being expanded, `params', `iline', `nparam',
131 * `paramlen', `rotate' and `unique' are local to the invocation.
133 struct MMacro {
134 MMacro *next;
135 MMacroInvocation *prev; /* previous invocation */
136 char *name;
137 int nparam_min, nparam_max;
138 bool casesense;
139 bool plus; /* is the last parameter greedy? */
140 bool nolist; /* is this macro listing-inhibited? */
141 int64_t in_progress; /* is this macro currently being expanded? */
142 int32_t max_depth; /* maximum number of recursive expansions allowed */
143 Token *dlist; /* All defaults as one list */
144 Token **defaults; /* Parameter default pointers */
145 int ndefs; /* number of default parameters */
146 Line *expansion;
148 MMacro *next_active;
149 MMacro *rep_nest; /* used for nesting %rep */
150 Token **params; /* actual parameters */
151 Token *iline; /* invocation line */
152 unsigned int nparam, rotate;
153 int *paramlen;
154 uint64_t unique;
155 int lineno; /* Current line number on expansion */
156 uint64_t condcnt; /* number of if blocks... */
158 const char *fname; /* File where defined */
159 int32_t xline; /* First line in macro */
163 /* Store the definition of a multi-line macro, as defined in a
164 * previous recursive macro expansion.
166 struct MMacroInvocation {
167 MMacroInvocation *prev; /* previous invocation */
168 Token **params; /* actual parameters */
169 Token *iline; /* invocation line */
170 unsigned int nparam, rotate;
171 int *paramlen;
172 uint64_t unique;
173 uint64_t condcnt;
178 * The context stack is composed of a linked list of these.
180 struct Context {
181 Context *next;
182 char *name;
183 struct hash_table localmac;
184 uint32_t number;
188 * This is the internal form which we break input lines up into.
189 * Typically stored in linked lists.
191 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
192 * necessarily used as-is, but is intended to denote the number of
193 * the substituted parameter. So in the definition
195 * %define a(x,y) ( (x) & ~(y) )
197 * the token representing `x' will have its type changed to
198 * TOK_SMAC_PARAM, but the one representing `y' will be
199 * TOK_SMAC_PARAM+1.
201 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
202 * which doesn't need quotes around it. Used in the pre-include
203 * mechanism as an alternative to trying to find a sensible type of
204 * quote to use on the filename we were passed.
206 enum pp_token_type {
207 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
208 TOK_PREPROC_ID, TOK_STRING,
209 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
210 TOK_INTERNAL_STRING,
211 TOK_PREPROC_Q, TOK_PREPROC_QQ,
212 TOK_PASTE, /* %+ */
213 TOK_INDIRECT, /* %[...] */
214 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
215 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
218 #define PP_CONCAT_MASK(x) (1 << (x))
219 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
221 struct tokseq_match {
222 int mask_head;
223 int mask_tail;
226 struct Token {
227 Token *next;
228 char *text;
229 union {
230 SMacro *mac; /* associated macro for TOK_SMAC_END */
231 size_t len; /* scratch length field */
232 } a; /* Auxiliary data */
233 enum pp_token_type type;
237 * Multi-line macro definitions are stored as a linked list of
238 * these, which is essentially a container to allow several linked
239 * lists of Tokens.
241 * Note that in this module, linked lists are treated as stacks
242 * wherever possible. For this reason, Lines are _pushed_ on to the
243 * `expansion' field in MMacro structures, so that the linked list,
244 * if walked, would give the macro lines in reverse order; this
245 * means that we can walk the list when expanding a macro, and thus
246 * push the lines on to the `expansion' field in _istk_ in reverse
247 * order (so that when popped back off they are in the right
248 * order). It may seem cockeyed, and it relies on my design having
249 * an even number of steps in, but it works...
251 * Some of these structures, rather than being actual lines, are
252 * markers delimiting the end of the expansion of a given macro.
253 * This is for use in the cycle-tracking and %rep-handling code.
254 * Such structures have `finishes' non-NULL, and `first' NULL. All
255 * others have `finishes' NULL, but `first' may still be NULL if
256 * the line is blank.
258 struct Line {
259 Line *next;
260 MMacro *finishes;
261 Token *first;
265 * To handle an arbitrary level of file inclusion, we maintain a
266 * stack (ie linked list) of these things.
268 struct Include {
269 Include *next;
270 FILE *fp;
271 Cond *conds;
272 Line *expansion;
273 const char *fname;
274 int lineno, lineinc;
275 MMacro *mstk; /* stack of active macros/reps */
279 * File real name hash, so we don't have to re-search the include
280 * path for every pass (and potentially more than that if a file
281 * is used more than once.)
283 struct hash_table FileHash;
286 * Conditional assembly: we maintain a separate stack of these for
287 * each level of file inclusion. (The only reason we keep the
288 * stacks separate is to ensure that a stray `%endif' in a file
289 * included from within the true branch of a `%if' won't terminate
290 * it and cause confusion: instead, rightly, it'll cause an error.)
292 struct Cond {
293 Cond *next;
294 int state;
296 enum {
298 * These states are for use just after %if or %elif: IF_TRUE
299 * means the condition has evaluated to truth so we are
300 * currently emitting, whereas IF_FALSE means we are not
301 * currently emitting but will start doing so if a %else comes
302 * up. In these states, all directives are admissible: %elif,
303 * %else and %endif. (And of course %if.)
305 COND_IF_TRUE, COND_IF_FALSE,
307 * These states come up after a %else: ELSE_TRUE means we're
308 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
309 * any %elif or %else will cause an error.
311 COND_ELSE_TRUE, COND_ELSE_FALSE,
313 * These states mean that we're not emitting now, and also that
314 * nothing until %endif will be emitted at all. COND_DONE is
315 * used when we've had our moment of emission
316 * and have now started seeing %elifs. COND_NEVER is used when
317 * the condition construct in question is contained within a
318 * non-emitting branch of a larger condition construct,
319 * or if there is an error.
321 COND_DONE, COND_NEVER
323 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
326 * These defines are used as the possible return values for do_directive
328 #define NO_DIRECTIVE_FOUND 0
329 #define DIRECTIVE_FOUND 1
331 /* max reps */
332 #define REP_LIMIT ((INT64_C(1) << 62))
335 * Condition codes. Note that we use c_ prefix not C_ because C_ is
336 * used in nasm.h for the "real" condition codes. At _this_ level,
337 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
338 * ones, so we need a different enum...
340 static const char * const conditions[] = {
341 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
342 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
343 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
345 enum pp_conds {
346 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
347 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
348 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
349 c_none = -1
351 static const enum pp_conds inverse_ccs[] = {
352 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
353 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,
354 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
358 * Directive names.
360 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
361 static int is_condition(enum preproc_token arg)
363 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
366 /* For TASM compatibility we need to be able to recognise TASM compatible
367 * conditional compilation directives. Using the NASM pre-processor does
368 * not work, so we look for them specifically from the following list and
369 * then jam in the equivalent NASM directive into the input stream.
372 enum {
373 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
374 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
377 static const char * const tasm_directives[] = {
378 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
379 "ifndef", "include", "local"
382 static int StackSize = 4;
383 static const char *StackPointer = "ebp";
384 static int ArgOffset = 8;
385 static int LocalOffset = 0;
387 static Context *cstk;
388 static Include *istk;
389 static StrList *ipath;
391 static int pass; /* HACK: pass 0 = generate dependencies only */
392 static StrList *deplist;
394 static uint64_t unique; /* unique identifier numbers */
396 static Line *predef = NULL;
397 static bool do_predef;
400 * The current set of multi-line macros we have defined.
402 static struct hash_table mmacros;
405 * The current set of single-line macros we have defined.
407 static struct hash_table smacros;
410 * The multi-line macro we are currently defining, or the %rep
411 * block we are currently reading, if any.
413 static MMacro *defining;
415 static uint64_t nested_mac_count;
416 static uint64_t nested_rep_count;
419 * The number of macro parameters to allocate space for at a time.
421 #define PARAM_DELTA 16
424 * The standard macro set: defined in macros.c in a set of arrays.
425 * This gives our position in any macro set, while we are processing it.
426 * The stdmacset is an array of such macro sets.
428 static macros_t *stdmacpos;
429 static macros_t **stdmacnext;
430 static macros_t *stdmacros[8];
431 static macros_t *extrastdmac;
434 * Tokens are allocated in blocks to improve speed
436 #define TOKEN_BLOCKSIZE 4096
437 static Token *freeTokens = NULL;
438 struct Blocks {
439 Blocks *next;
440 void *chunk;
443 static Blocks blocks = { NULL, NULL };
446 * Forward declarations.
448 static void pp_add_stdmac(macros_t *macros);
449 static Token *expand_mmac_params(Token * tline);
450 static Token *expand_smacro(Token * tline);
451 static Token *expand_id(Token * tline);
452 static Context *get_ctx(const char *name, const char **namep);
453 static void make_tok_num(Token * tok, int64_t val);
454 static void pp_verror(int severity, const char *fmt, va_list ap);
455 static vefunc real_verror;
456 static void *new_Block(size_t size);
457 static void delete_Blocks(void);
458 static Token *new_Token(Token * next, enum pp_token_type type,
459 const char *text, int txtlen);
460 static Token *delete_Token(Token * t);
463 * Macros for safe checking of token pointers, avoid *(NULL)
465 #define tok_type_(x,t) ((x) && (x)->type == (t))
466 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
467 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
468 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
471 * nasm_unquote with error if the string contains NUL characters.
472 * If the string contains NUL characters, issue an error and return
473 * the C len, i.e. truncate at the NUL.
475 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
477 size_t len = nasm_unquote(qstr, NULL);
478 size_t clen = strlen(qstr);
480 if (len != clen)
481 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
482 pp_directives[directive]);
484 return clen;
488 * In-place reverse a list of tokens.
490 static Token *reverse_tokens(Token *t)
492 Token *prev = NULL;
493 Token *next;
495 while (t) {
496 next = t->next;
497 t->next = prev;
498 prev = t;
499 t = next;
502 return prev;
506 * Handle TASM specific directives, which do not contain a % in
507 * front of them. We do it here because I could not find any other
508 * place to do it for the moment, and it is a hack (ideally it would
509 * be nice to be able to use the NASM pre-processor to do it).
511 static char *check_tasm_directive(char *line)
513 int32_t i, j, k, m, len;
514 char *p, *q, *oldline, oldchar;
516 p = nasm_skip_spaces(line);
518 /* Binary search for the directive name */
519 i = -1;
520 j = ARRAY_SIZE(tasm_directives);
521 q = nasm_skip_word(p);
522 len = q - p;
523 if (len) {
524 oldchar = p[len];
525 p[len] = 0;
526 while (j - i > 1) {
527 k = (j + i) / 2;
528 m = nasm_stricmp(p, tasm_directives[k]);
529 if (m == 0) {
530 /* We have found a directive, so jam a % in front of it
531 * so that NASM will then recognise it as one if it's own.
533 p[len] = oldchar;
534 len = strlen(p);
535 oldline = line;
536 line = nasm_malloc(len + 2);
537 line[0] = '%';
538 if (k == TM_IFDIFI) {
540 * NASM does not recognise IFDIFI, so we convert
541 * it to %if 0. This is not used in NASM
542 * compatible code, but does need to parse for the
543 * TASM macro package.
545 strcpy(line + 1, "if 0");
546 } else {
547 memcpy(line + 1, p, len + 1);
549 nasm_free(oldline);
550 return line;
551 } else if (m < 0) {
552 j = k;
553 } else
554 i = k;
556 p[len] = oldchar;
558 return line;
562 * The pre-preprocessing stage... This function translates line
563 * number indications as they emerge from GNU cpp (`# lineno "file"
564 * flags') into NASM preprocessor line number indications (`%line
565 * lineno file').
567 static char *prepreproc(char *line)
569 int lineno, fnlen;
570 char *fname, *oldline;
572 if (line[0] == '#' && line[1] == ' ') {
573 oldline = line;
574 fname = oldline + 2;
575 lineno = atoi(fname);
576 fname += strspn(fname, "0123456789 ");
577 if (*fname == '"')
578 fname++;
579 fnlen = strcspn(fname, "\"");
580 line = nasm_malloc(20 + fnlen);
581 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
582 nasm_free(oldline);
584 if (tasm_compatible_mode)
585 return check_tasm_directive(line);
586 return line;
590 * Free a linked list of tokens.
592 static void free_tlist(Token * list)
594 while (list)
595 list = delete_Token(list);
599 * Free a linked list of lines.
601 static void free_llist(Line * list)
603 Line *l, *tmp;
604 list_for_each_safe(l, tmp, list) {
605 free_tlist(l->first);
606 nasm_free(l);
611 * Free an MMacro
613 static void free_mmacro(MMacro * m)
615 nasm_free(m->name);
616 free_tlist(m->dlist);
617 nasm_free(m->defaults);
618 free_llist(m->expansion);
619 nasm_free(m);
623 * Free all currently defined macros, and free the hash tables
625 static void free_smacro_table(struct hash_table *smt)
627 SMacro *s, *tmp;
628 const char *key;
629 struct hash_tbl_node *it = NULL;
631 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
632 nasm_free((void *)key);
633 list_for_each_safe(s, tmp, s) {
634 nasm_free(s->name);
635 free_tlist(s->expansion);
636 nasm_free(s);
639 hash_free(smt);
642 static void free_mmacro_table(struct hash_table *mmt)
644 MMacro *m, *tmp;
645 const char *key;
646 struct hash_tbl_node *it = NULL;
648 it = NULL;
649 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
650 nasm_free((void *)key);
651 list_for_each_safe(m ,tmp, m)
652 free_mmacro(m);
654 hash_free(mmt);
657 static void free_macros(void)
659 free_smacro_table(&smacros);
660 free_mmacro_table(&mmacros);
664 * Initialize the hash tables
666 static void init_macros(void)
668 hash_init(&smacros, HASH_LARGE);
669 hash_init(&mmacros, HASH_LARGE);
673 * Pop the context stack.
675 static void ctx_pop(void)
677 Context *c = cstk;
679 cstk = cstk->next;
680 free_smacro_table(&c->localmac);
681 nasm_free(c->name);
682 nasm_free(c);
686 * Search for a key in the hash index; adding it if necessary
687 * (in which case we initialize the data pointer to NULL.)
689 static void **
690 hash_findi_add(struct hash_table *hash, const char *str)
692 struct hash_insert hi;
693 void **r;
694 char *strx;
696 r = hash_findi(hash, str, &hi);
697 if (r)
698 return r;
700 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
701 return hash_add(&hi, strx, NULL);
705 * Like hash_findi, but returns the data element rather than a pointer
706 * to it. Used only when not adding a new element, hence no third
707 * argument.
709 static void *
710 hash_findix(struct hash_table *hash, const char *str)
712 void **p;
714 p = hash_findi(hash, str, NULL);
715 return p ? *p : NULL;
719 * read line from standart macros set,
720 * if there no more left -- return NULL
722 static char *line_from_stdmac(void)
724 unsigned char c;
725 const unsigned char *p = stdmacpos;
726 char *line, *q;
727 size_t len = 0;
729 if (!stdmacpos)
730 return NULL;
732 while ((c = *p++)) {
733 if (c >= 0x80)
734 len += pp_directives_len[c - 0x80] + 1;
735 else
736 len++;
739 line = nasm_malloc(len + 1);
740 q = line;
741 while ((c = *stdmacpos++)) {
742 if (c >= 0x80) {
743 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
744 q += pp_directives_len[c - 0x80];
745 *q++ = ' ';
746 } else {
747 *q++ = c;
750 stdmacpos = p;
751 *q = '\0';
753 if (!*stdmacpos) {
754 /* This was the last of this particular macro set */
755 stdmacpos = NULL;
756 if (*stdmacnext) {
757 stdmacpos = *stdmacnext++;
758 } else if (do_predef) {
759 Line *pd, *l;
760 Token *head, **tail, *t;
763 * Nasty hack: here we push the contents of
764 * `predef' on to the top-level expansion stack,
765 * since this is the most convenient way to
766 * implement the pre-include and pre-define
767 * features.
769 list_for_each(pd, predef) {
770 head = NULL;
771 tail = &head;
772 list_for_each(t, pd->first) {
773 *tail = new_Token(NULL, t->type, t->text, 0);
774 tail = &(*tail)->next;
777 l = nasm_malloc(sizeof(Line));
778 l->next = istk->expansion;
779 l->first = head;
780 l->finishes = NULL;
782 istk->expansion = l;
784 do_predef = false;
788 return line;
791 static char *read_line(void)
793 unsigned int size, c, next;
794 const unsigned int delta = 512;
795 const unsigned int pad = 8;
796 unsigned int nr_cont = 0;
797 bool cont = false;
798 char *buffer, *p;
800 /* Standart macros set (predefined) goes first */
801 p = line_from_stdmac();
802 if (p)
803 return p;
805 size = delta;
806 p = buffer = nasm_malloc(size);
808 for (;;) {
809 c = fgetc(istk->fp);
810 if ((int)(c) == EOF) {
811 p[0] = 0;
812 break;
815 switch (c) {
816 case '\r':
817 next = fgetc(istk->fp);
818 if (next != '\n')
819 ungetc(next, istk->fp);
820 if (cont) {
821 cont = false;
822 continue;
824 break;
826 case '\n':
827 if (cont) {
828 cont = false;
829 continue;
831 break;
833 case '\\':
834 next = fgetc(istk->fp);
835 ungetc(next, istk->fp);
836 if (next == '\r' || next == '\n') {
837 cont = true;
838 nr_cont++;
839 continue;
841 break;
844 if (c == '\r' || c == '\n') {
845 *p++ = 0;
846 break;
849 if (p >= (buffer + size - pad)) {
850 buffer = nasm_realloc(buffer, size + delta);
851 p = buffer + size - pad;
852 size += delta;
855 *p++ = (unsigned char)c;
858 if (p == buffer) {
859 nasm_free(buffer);
860 return NULL;
863 src_set_linnum(src_get_linnum() + istk->lineinc +
864 (nr_cont * istk->lineinc));
867 * Handle spurious ^Z, which may be inserted into source files
868 * by some file transfer utilities.
870 buffer[strcspn(buffer, "\032")] = '\0';
872 lfmt->line(LIST_READ, buffer);
874 return buffer;
878 * Tokenize a line of text. This is a very simple process since we
879 * don't need to parse the value out of e.g. numeric tokens: we
880 * simply split one string into many.
882 static Token *tokenize(char *line)
884 char c, *p = line;
885 enum pp_token_type type;
886 Token *list = NULL;
887 Token *t, **tail = &list;
889 while (*line) {
890 p = line;
891 if (*p == '%') {
892 p++;
893 if (*p == '+' && !nasm_isdigit(p[1])) {
894 p++;
895 type = TOK_PASTE;
896 } else if (nasm_isdigit(*p) ||
897 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
898 do {
899 p++;
901 while (nasm_isdigit(*p));
902 type = TOK_PREPROC_ID;
903 } else if (*p == '{') {
904 p++;
905 while (*p) {
906 if (*p == '}')
907 break;
908 p[-1] = *p;
909 p++;
911 if (*p != '}')
912 nasm_error(ERR_WARNING | ERR_PASS1,
913 "unterminated %%{ construct");
914 p[-1] = '\0';
915 if (*p)
916 p++;
917 type = TOK_PREPROC_ID;
918 } else if (*p == '[') {
919 int lvl = 1;
920 line += 2; /* Skip the leading %[ */
921 p++;
922 while (lvl && (c = *p++)) {
923 switch (c) {
924 case ']':
925 lvl--;
926 break;
927 case '%':
928 if (*p == '[')
929 lvl++;
930 break;
931 case '\'':
932 case '\"':
933 case '`':
934 p = nasm_skip_string(p - 1);
935 if (*p)
936 p++;
937 break;
938 default:
939 break;
942 p--;
943 if (*p)
944 *p++ = '\0';
945 if (lvl)
946 nasm_error(ERR_NONFATAL|ERR_PASS1,
947 "unterminated %%[ construct");
948 type = TOK_INDIRECT;
949 } else if (*p == '?') {
950 type = TOK_PREPROC_Q; /* %? */
951 p++;
952 if (*p == '?') {
953 type = TOK_PREPROC_QQ; /* %?? */
954 p++;
956 } else if (*p == '!') {
957 type = TOK_PREPROC_ID;
958 p++;
959 if (isidchar(*p)) {
960 do {
961 p++;
963 while (isidchar(*p));
964 } else if (*p == '\'' || *p == '\"' || *p == '`') {
965 p = nasm_skip_string(p);
966 if (*p)
967 p++;
968 else
969 nasm_error(ERR_NONFATAL|ERR_PASS1,
970 "unterminated %%! string");
971 } else {
972 /* %! without string or identifier */
973 type = TOK_OTHER; /* Legacy behavior... */
975 } else if (isidchar(*p) ||
976 ((*p == '!' || *p == '%' || *p == '$') &&
977 isidchar(p[1]))) {
978 do {
979 p++;
981 while (isidchar(*p));
982 type = TOK_PREPROC_ID;
983 } else {
984 type = TOK_OTHER;
985 if (*p == '%')
986 p++;
988 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
989 type = TOK_ID;
990 p++;
991 while (*p && isidchar(*p))
992 p++;
993 } else if (*p == '\'' || *p == '"' || *p == '`') {
995 * A string token.
997 type = TOK_STRING;
998 p = nasm_skip_string(p);
1000 if (*p) {
1001 p++;
1002 } else {
1003 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1004 /* Handling unterminated strings by UNV */
1005 /* type = -1; */
1007 } else if (p[0] == '$' && p[1] == '$') {
1008 type = TOK_OTHER; /* TOKEN_BASE */
1009 p += 2;
1010 } else if (isnumstart(*p)) {
1011 bool is_hex = false;
1012 bool is_float = false;
1013 bool has_e = false;
1014 char c, *r;
1017 * A numeric token.
1020 if (*p == '$') {
1021 p++;
1022 is_hex = true;
1025 for (;;) {
1026 c = *p++;
1028 if (!is_hex && (c == 'e' || c == 'E')) {
1029 has_e = true;
1030 if (*p == '+' || *p == '-') {
1032 * e can only be followed by +/- if it is either a
1033 * prefixed hex number or a floating-point number
1035 p++;
1036 is_float = true;
1038 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1039 is_hex = true;
1040 } else if (c == 'P' || c == 'p') {
1041 is_float = true;
1042 if (*p == '+' || *p == '-')
1043 p++;
1044 } else if (isnumchar(c))
1045 ; /* just advance */
1046 else if (c == '.') {
1048 * we need to deal with consequences of the legacy
1049 * parser, like "1.nolist" being two tokens
1050 * (TOK_NUMBER, TOK_ID) here; at least give it
1051 * a shot for now. In the future, we probably need
1052 * a flex-based scanner with proper pattern matching
1053 * to do it as well as it can be done. Nothing in
1054 * the world is going to help the person who wants
1055 * 0x123.p16 interpreted as two tokens, though.
1057 r = p;
1058 while (*r == '_')
1059 r++;
1061 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1062 (!is_hex && (*r == 'e' || *r == 'E')) ||
1063 (*r == 'p' || *r == 'P')) {
1064 p = r;
1065 is_float = true;
1066 } else
1067 break; /* Terminate the token */
1068 } else
1069 break;
1071 p--; /* Point to first character beyond number */
1073 if (p == line+1 && *line == '$') {
1074 type = TOK_OTHER; /* TOKEN_HERE */
1075 } else {
1076 if (has_e && !is_hex) {
1077 /* 1e13 is floating-point, but 1e13h is not */
1078 is_float = true;
1081 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1083 } else if (nasm_isspace(*p)) {
1084 type = TOK_WHITESPACE;
1085 p = nasm_skip_spaces(p);
1087 * Whitespace just before end-of-line is discarded by
1088 * pretending it's a comment; whitespace just before a
1089 * comment gets lumped into the comment.
1091 if (!*p || *p == ';') {
1092 type = TOK_COMMENT;
1093 while (*p)
1094 p++;
1096 } else if (*p == ';') {
1097 type = TOK_COMMENT;
1098 while (*p)
1099 p++;
1100 } else {
1102 * Anything else is an operator of some kind. We check
1103 * for all the double-character operators (>>, <<, //,
1104 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1105 * else is a single-character operator.
1107 type = TOK_OTHER;
1108 if ((p[0] == '>' && p[1] == '>') ||
1109 (p[0] == '<' && p[1] == '<') ||
1110 (p[0] == '/' && p[1] == '/') ||
1111 (p[0] == '<' && p[1] == '=') ||
1112 (p[0] == '>' && p[1] == '=') ||
1113 (p[0] == '=' && p[1] == '=') ||
1114 (p[0] == '!' && p[1] == '=') ||
1115 (p[0] == '<' && p[1] == '>') ||
1116 (p[0] == '&' && p[1] == '&') ||
1117 (p[0] == '|' && p[1] == '|') ||
1118 (p[0] == '^' && p[1] == '^')) {
1119 p++;
1121 p++;
1124 /* Handling unterminated string by UNV */
1125 /*if (type == -1)
1127 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1128 t->text[p-line] = *line;
1129 tail = &t->next;
1131 else */
1132 if (type != TOK_COMMENT) {
1133 *tail = t = new_Token(NULL, type, line, p - line);
1134 tail = &t->next;
1136 line = p;
1138 return list;
1142 * this function allocates a new managed block of memory and
1143 * returns a pointer to the block. The managed blocks are
1144 * deleted only all at once by the delete_Blocks function.
1146 static void *new_Block(size_t size)
1148 Blocks *b = &blocks;
1150 /* first, get to the end of the linked list */
1151 while (b->next)
1152 b = b->next;
1153 /* now allocate the requested chunk */
1154 b->chunk = nasm_malloc(size);
1156 /* now allocate a new block for the next request */
1157 b->next = nasm_zalloc(sizeof(Blocks));
1158 return b->chunk;
1162 * this function deletes all managed blocks of memory
1164 static void delete_Blocks(void)
1166 Blocks *a, *b = &blocks;
1169 * keep in mind that the first block, pointed to by blocks
1170 * is a static and not dynamically allocated, so we don't
1171 * free it.
1173 while (b) {
1174 if (b->chunk)
1175 nasm_free(b->chunk);
1176 a = b;
1177 b = b->next;
1178 if (a != &blocks)
1179 nasm_free(a);
1181 memset(&blocks, 0, sizeof(blocks));
1185 * this function creates a new Token and passes a pointer to it
1186 * back to the caller. It sets the type and text elements, and
1187 * also the a.mac and next elements to NULL.
1189 static Token *new_Token(Token * next, enum pp_token_type type,
1190 const char *text, int txtlen)
1192 Token *t;
1193 int i;
1195 if (!freeTokens) {
1196 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1197 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1198 freeTokens[i].next = &freeTokens[i + 1];
1199 freeTokens[i].next = NULL;
1201 t = freeTokens;
1202 freeTokens = t->next;
1203 t->next = next;
1204 t->a.mac = NULL;
1205 t->type = type;
1206 if (type == TOK_WHITESPACE || !text) {
1207 t->text = NULL;
1208 } else {
1209 if (txtlen == 0)
1210 txtlen = strlen(text);
1211 t->text = nasm_malloc(txtlen+1);
1212 memcpy(t->text, text, txtlen);
1213 t->text[txtlen] = '\0';
1215 return t;
1218 static Token *delete_Token(Token * t)
1220 Token *next = t->next;
1221 nasm_free(t->text);
1222 t->next = freeTokens;
1223 freeTokens = t;
1224 return next;
1228 * Convert a line of tokens back into text.
1229 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1230 * will be transformed into ..@ctxnum.xxx
1232 static char *detoken(Token * tlist, bool expand_locals)
1234 Token *t;
1235 char *line, *p;
1236 const char *q;
1237 int len = 0;
1239 list_for_each(t, tlist) {
1240 if (t->type == TOK_PREPROC_ID && t->text &&
1241 t->text[0] && t->text[1] == '!') {
1242 char *v;
1243 char *q = t->text;
1245 v = t->text + 2;
1246 if (*v == '\'' || *v == '\"' || *v == '`') {
1247 size_t len = nasm_unquote(v, NULL);
1248 size_t clen = strlen(v);
1250 if (len != clen) {
1251 nasm_error(ERR_NONFATAL | ERR_PASS1,
1252 "NUL character in %%! string");
1253 v = NULL;
1257 if (v) {
1258 char *p = getenv(v);
1259 if (!p) {
1260 nasm_error(ERR_NONFATAL | ERR_PASS1,
1261 "nonexistent environment variable `%s'", v);
1263 * FIXME We better should investigate if accessing
1264 * ->text[1] without ->text[0] is safe enough.
1266 t->text = nasm_zalloc(2);
1267 } else
1268 t->text = nasm_strdup(p);
1269 nasm_free(q);
1273 /* Expand local macros here and not during preprocessing */
1274 if (expand_locals &&
1275 t->type == TOK_PREPROC_ID && t->text &&
1276 t->text[0] == '%' && t->text[1] == '$') {
1277 const char *q;
1278 char *p;
1279 Context *ctx = get_ctx(t->text, &q);
1280 if (ctx) {
1281 char buffer[40];
1282 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1283 p = nasm_strcat(buffer, q);
1284 nasm_free(t->text);
1285 t->text = p;
1288 if (t->type == TOK_WHITESPACE)
1289 len++;
1290 else if (t->text)
1291 len += strlen(t->text);
1294 p = line = nasm_malloc(len + 1);
1296 list_for_each(t, tlist) {
1297 if (t->type == TOK_WHITESPACE) {
1298 *p++ = ' ';
1299 } else if (t->text) {
1300 q = t->text;
1301 while (*q)
1302 *p++ = *q++;
1305 *p = '\0';
1307 return line;
1311 * A scanner, suitable for use by the expression evaluator, which
1312 * operates on a line of Tokens. Expects a pointer to a pointer to
1313 * the first token in the line to be passed in as its private_data
1314 * field.
1316 * FIX: This really needs to be unified with stdscan.
1318 static int ppscan(void *private_data, struct tokenval *tokval)
1320 Token **tlineptr = private_data;
1321 Token *tline;
1322 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1324 do {
1325 tline = *tlineptr;
1326 *tlineptr = tline ? tline->next : NULL;
1327 } while (tline && (tline->type == TOK_WHITESPACE ||
1328 tline->type == TOK_COMMENT));
1330 if (!tline)
1331 return tokval->t_type = TOKEN_EOS;
1333 tokval->t_charptr = tline->text;
1335 if (tline->text[0] == '$' && !tline->text[1])
1336 return tokval->t_type = TOKEN_HERE;
1337 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1338 return tokval->t_type = TOKEN_BASE;
1340 if (tline->type == TOK_ID) {
1341 p = tokval->t_charptr = tline->text;
1342 if (p[0] == '$') {
1343 tokval->t_charptr++;
1344 return tokval->t_type = TOKEN_ID;
1347 for (r = p, s = ourcopy; *r; r++) {
1348 if (r >= p+MAX_KEYWORD)
1349 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1350 *s++ = nasm_tolower(*r);
1352 *s = '\0';
1353 /* right, so we have an identifier sitting in temp storage. now,
1354 * is it actually a register or instruction name, or what? */
1355 return nasm_token_hash(ourcopy, tokval);
1358 if (tline->type == TOK_NUMBER) {
1359 bool rn_error;
1360 tokval->t_integer = readnum(tline->text, &rn_error);
1361 tokval->t_charptr = tline->text;
1362 if (rn_error)
1363 return tokval->t_type = TOKEN_ERRNUM;
1364 else
1365 return tokval->t_type = TOKEN_NUM;
1368 if (tline->type == TOK_FLOAT) {
1369 return tokval->t_type = TOKEN_FLOAT;
1372 if (tline->type == TOK_STRING) {
1373 char bq, *ep;
1375 bq = tline->text[0];
1376 tokval->t_charptr = tline->text;
1377 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1379 if (ep[0] != bq || ep[1] != '\0')
1380 return tokval->t_type = TOKEN_ERRSTR;
1381 else
1382 return tokval->t_type = TOKEN_STR;
1385 if (tline->type == TOK_OTHER) {
1386 if (!strcmp(tline->text, "<<"))
1387 return tokval->t_type = TOKEN_SHL;
1388 if (!strcmp(tline->text, ">>"))
1389 return tokval->t_type = TOKEN_SHR;
1390 if (!strcmp(tline->text, "//"))
1391 return tokval->t_type = TOKEN_SDIV;
1392 if (!strcmp(tline->text, "%%"))
1393 return tokval->t_type = TOKEN_SMOD;
1394 if (!strcmp(tline->text, "=="))
1395 return tokval->t_type = TOKEN_EQ;
1396 if (!strcmp(tline->text, "<>"))
1397 return tokval->t_type = TOKEN_NE;
1398 if (!strcmp(tline->text, "!="))
1399 return tokval->t_type = TOKEN_NE;
1400 if (!strcmp(tline->text, "<="))
1401 return tokval->t_type = TOKEN_LE;
1402 if (!strcmp(tline->text, ">="))
1403 return tokval->t_type = TOKEN_GE;
1404 if (!strcmp(tline->text, "&&"))
1405 return tokval->t_type = TOKEN_DBL_AND;
1406 if (!strcmp(tline->text, "^^"))
1407 return tokval->t_type = TOKEN_DBL_XOR;
1408 if (!strcmp(tline->text, "||"))
1409 return tokval->t_type = TOKEN_DBL_OR;
1413 * We have no other options: just return the first character of
1414 * the token text.
1416 return tokval->t_type = tline->text[0];
1420 * Compare a string to the name of an existing macro; this is a
1421 * simple wrapper which calls either strcmp or nasm_stricmp
1422 * depending on the value of the `casesense' parameter.
1424 static int mstrcmp(const char *p, const char *q, bool casesense)
1426 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1430 * Compare a string to the name of an existing macro; this is a
1431 * simple wrapper which calls either strcmp or nasm_stricmp
1432 * depending on the value of the `casesense' parameter.
1434 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1436 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1440 * Return the Context structure associated with a %$ token. Return
1441 * NULL, having _already_ reported an error condition, if the
1442 * context stack isn't deep enough for the supplied number of $
1443 * signs.
1445 * If "namep" is non-NULL, set it to the pointer to the macro name
1446 * tail, i.e. the part beyond %$...
1448 static Context *get_ctx(const char *name, const char **namep)
1450 Context *ctx;
1451 int i;
1453 if (namep)
1454 *namep = name;
1456 if (!name || name[0] != '%' || name[1] != '$')
1457 return NULL;
1459 if (!cstk) {
1460 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1461 return NULL;
1464 name += 2;
1465 ctx = cstk;
1466 i = 0;
1467 while (ctx && *name == '$') {
1468 name++;
1469 i++;
1470 ctx = ctx->next;
1472 if (!ctx) {
1473 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1474 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1475 return NULL;
1478 if (namep)
1479 *namep = name;
1481 return ctx;
1485 * Open an include file. This routine must always return a valid
1486 * file pointer if it returns - it's responsible for throwing an
1487 * ERR_FATAL and bombing out completely if not. It should also try
1488 * the include path one by one until it finds the file or reaches
1489 * the end of the path.
1491 * Note: for INC_PROBE the function returns NULL at all times;
1492 * instead look for the
1494 enum incopen_mode {
1495 INC_NEEDED, /* File must exist */
1496 INC_OPTIONAL, /* Missing is OK */
1497 INC_PROBE /* Only an existence probe */
1500 /* This is conducts a full pathname search */
1501 static FILE *inc_fopen_search(const char *file, char **slpath,
1502 enum incopen_mode omode, enum file_flags fmode)
1504 FILE *fp;
1505 const char *prefix = "";
1506 const struct strlist_entry *ip = ipath->head;
1507 char *sp;
1508 bool found;
1510 while (1) {
1511 sp = nasm_catfile(prefix, file);
1512 if (omode == INC_PROBE) {
1513 fp = NULL;
1514 found = nasm_file_exists(sp);
1515 } else {
1516 fp = nasm_open_read(sp, fmode);
1517 found = (fp != NULL);
1519 if (found) {
1520 *slpath = sp;
1521 return fp;
1524 nasm_free(sp);
1526 if (!ip) {
1527 *slpath = NULL;
1528 return NULL;
1531 prefix = ip->str;
1532 ip = ip->next;
1537 * Open a file, or test for the presence of one (depending on omode),
1538 * considering the include path.
1540 static FILE *inc_fopen(const char *file,
1541 StrList *dhead,
1542 const char **found_path,
1543 enum incopen_mode omode,
1544 enum file_flags fmode)
1546 struct hash_insert hi;
1547 void **hp;
1548 char *path;
1549 FILE *fp = NULL;
1551 hp = hash_find(&FileHash, file, &hi);
1552 if (hp) {
1553 path = *hp;
1554 if (path || omode != INC_NEEDED) {
1555 strlist_add_string(dhead, path ? path : file);
1557 } else {
1558 /* Need to do the actual path search */
1559 fp = inc_fopen_search(file, &path, omode, fmode);
1561 /* Positive or negative result */
1562 hash_add(&hi, nasm_strdup(file), path);
1565 * Add file to dependency path.
1567 if (path || omode != INC_NEEDED)
1568 strlist_add_string(dhead, file);
1571 if (!path) {
1572 if (omode == INC_NEEDED)
1573 nasm_fatal("unable to open include file `%s'", file);
1574 } else {
1575 if (!fp && omode != INC_PROBE)
1576 fp = nasm_open_read(path, fmode);
1579 if (found_path)
1580 *found_path = path;
1582 return fp;
1586 * Opens an include or input file. Public version, for use by modules
1587 * that get a file:lineno pair and need to look at the file again
1588 * (e.g. the CodeView debug backend). Returns NULL on failure.
1590 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1592 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1596 * Determine if we should warn on defining a single-line macro of
1597 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1598 * return true if _any_ single-line macro of that name is defined.
1599 * Otherwise, will return true if a single-line macro with either
1600 * `nparam' or no parameters is defined.
1602 * If a macro with precisely the right number of parameters is
1603 * defined, or nparam is -1, the address of the definition structure
1604 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1605 * is NULL, no action will be taken regarding its contents, and no
1606 * error will occur.
1608 * Note that this is also called with nparam zero to resolve
1609 * `ifdef'.
1611 * If you already know which context macro belongs to, you can pass
1612 * the context pointer as first parameter; if you won't but name begins
1613 * with %$ the context will be automatically computed. If all_contexts
1614 * is true, macro will be searched in outer contexts as well.
1616 static bool
1617 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1618 bool nocase)
1620 struct hash_table *smtbl;
1621 SMacro *m;
1623 if (ctx) {
1624 smtbl = &ctx->localmac;
1625 } else if (name[0] == '%' && name[1] == '$') {
1626 if (cstk)
1627 ctx = get_ctx(name, &name);
1628 if (!ctx)
1629 return false; /* got to return _something_ */
1630 smtbl = &ctx->localmac;
1631 } else {
1632 smtbl = &smacros;
1634 m = (SMacro *) hash_findix(smtbl, name);
1636 while (m) {
1637 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1638 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1639 if (defn) {
1640 if (nparam == (int) m->nparam || nparam == -1)
1641 *defn = m;
1642 else
1643 *defn = NULL;
1645 return true;
1647 m = m->next;
1650 return false;
1654 * Count and mark off the parameters in a multi-line macro call.
1655 * This is called both from within the multi-line macro expansion
1656 * code, and also to mark off the default parameters when provided
1657 * in a %macro definition line.
1659 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1661 int paramsize, brace;
1663 *nparam = paramsize = 0;
1664 *params = NULL;
1665 while (t) {
1666 /* +1: we need space for the final NULL */
1667 if (*nparam+1 >= paramsize) {
1668 paramsize += PARAM_DELTA;
1669 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1671 skip_white_(t);
1672 brace = 0;
1673 if (tok_is_(t, "{"))
1674 brace++;
1675 (*params)[(*nparam)++] = t;
1676 if (brace) {
1677 while (brace && (t = t->next) != NULL) {
1678 if (tok_is_(t, "{"))
1679 brace++;
1680 else if (tok_is_(t, "}"))
1681 brace--;
1684 if (t) {
1686 * Now we've found the closing brace, look further
1687 * for the comma.
1689 t = t->next;
1690 skip_white_(t);
1691 if (tok_isnt_(t, ",")) {
1692 nasm_error(ERR_NONFATAL,
1693 "braces do not enclose all of macro parameter");
1694 while (tok_isnt_(t, ","))
1695 t = t->next;
1698 } else {
1699 while (tok_isnt_(t, ","))
1700 t = t->next;
1702 if (t) { /* got a comma/brace */
1703 t = t->next; /* eat the comma */
1709 * Determine whether one of the various `if' conditions is true or
1710 * not.
1712 * We must free the tline we get passed.
1714 static bool if_condition(Token * tline, enum preproc_token ct)
1716 enum pp_conditional i = PP_COND(ct);
1717 bool j;
1718 Token *t, *tt, **tptr, *origline;
1719 struct tokenval tokval;
1720 expr *evalresult;
1721 enum pp_token_type needtype;
1722 char *p;
1724 origline = tline;
1726 switch (i) {
1727 case PPC_IFCTX:
1728 j = false; /* have we matched yet? */
1729 while (true) {
1730 skip_white_(tline);
1731 if (!tline)
1732 break;
1733 if (tline->type != TOK_ID) {
1734 nasm_error(ERR_NONFATAL,
1735 "`%s' expects context identifiers", pp_directives[ct]);
1736 free_tlist(origline);
1737 return -1;
1739 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1740 j = true;
1741 tline = tline->next;
1743 break;
1745 case PPC_IFDEF:
1746 j = false; /* have we matched yet? */
1747 while (tline) {
1748 skip_white_(tline);
1749 if (!tline || (tline->type != TOK_ID &&
1750 (tline->type != TOK_PREPROC_ID ||
1751 tline->text[1] != '$'))) {
1752 nasm_error(ERR_NONFATAL,
1753 "`%s' expects macro identifiers", pp_directives[ct]);
1754 goto fail;
1756 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1757 j = true;
1758 tline = tline->next;
1760 break;
1762 case PPC_IFENV:
1763 tline = expand_smacro(tline);
1764 j = false; /* have we matched yet? */
1765 while (tline) {
1766 skip_white_(tline);
1767 if (!tline || (tline->type != TOK_ID &&
1768 tline->type != TOK_STRING &&
1769 (tline->type != TOK_PREPROC_ID ||
1770 tline->text[1] != '!'))) {
1771 nasm_error(ERR_NONFATAL,
1772 "`%s' expects environment variable names",
1773 pp_directives[ct]);
1774 goto fail;
1776 p = tline->text;
1777 if (tline->type == TOK_PREPROC_ID)
1778 p += 2; /* Skip leading %! */
1779 if (*p == '\'' || *p == '\"' || *p == '`')
1780 nasm_unquote_cstr(p, ct);
1781 if (getenv(p))
1782 j = true;
1783 tline = tline->next;
1785 break;
1787 case PPC_IFIDN:
1788 case PPC_IFIDNI:
1789 tline = expand_smacro(tline);
1790 t = tt = tline;
1791 while (tok_isnt_(tt, ","))
1792 tt = tt->next;
1793 if (!tt) {
1794 nasm_error(ERR_NONFATAL,
1795 "`%s' expects two comma-separated arguments",
1796 pp_directives[ct]);
1797 goto fail;
1799 tt = tt->next;
1800 j = true; /* assume equality unless proved not */
1801 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1802 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1803 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1804 pp_directives[ct]);
1805 goto fail;
1807 if (t->type == TOK_WHITESPACE) {
1808 t = t->next;
1809 continue;
1811 if (tt->type == TOK_WHITESPACE) {
1812 tt = tt->next;
1813 continue;
1815 if (tt->type != t->type) {
1816 j = false; /* found mismatching tokens */
1817 break;
1819 /* When comparing strings, need to unquote them first */
1820 if (t->type == TOK_STRING) {
1821 size_t l1 = nasm_unquote(t->text, NULL);
1822 size_t l2 = nasm_unquote(tt->text, NULL);
1824 if (l1 != l2) {
1825 j = false;
1826 break;
1828 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1829 j = false;
1830 break;
1832 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1833 j = false; /* found mismatching tokens */
1834 break;
1837 t = t->next;
1838 tt = tt->next;
1840 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1841 j = false; /* trailing gunk on one end or other */
1842 break;
1844 case PPC_IFMACRO:
1846 bool found = false;
1847 MMacro searching, *mmac;
1849 skip_white_(tline);
1850 tline = expand_id(tline);
1851 if (!tok_type_(tline, TOK_ID)) {
1852 nasm_error(ERR_NONFATAL,
1853 "`%s' expects a macro name", pp_directives[ct]);
1854 goto fail;
1856 searching.name = nasm_strdup(tline->text);
1857 searching.casesense = true;
1858 searching.plus = false;
1859 searching.nolist = false;
1860 searching.in_progress = 0;
1861 searching.max_depth = 0;
1862 searching.rep_nest = NULL;
1863 searching.nparam_min = 0;
1864 searching.nparam_max = INT_MAX;
1865 tline = expand_smacro(tline->next);
1866 skip_white_(tline);
1867 if (!tline) {
1868 } else if (!tok_type_(tline, TOK_NUMBER)) {
1869 nasm_error(ERR_NONFATAL,
1870 "`%s' expects a parameter count or nothing",
1871 pp_directives[ct]);
1872 } else {
1873 searching.nparam_min = searching.nparam_max =
1874 readnum(tline->text, &j);
1875 if (j)
1876 nasm_error(ERR_NONFATAL,
1877 "unable to parse parameter count `%s'",
1878 tline->text);
1880 if (tline && tok_is_(tline->next, "-")) {
1881 tline = tline->next->next;
1882 if (tok_is_(tline, "*"))
1883 searching.nparam_max = INT_MAX;
1884 else if (!tok_type_(tline, TOK_NUMBER))
1885 nasm_error(ERR_NONFATAL,
1886 "`%s' expects a parameter count after `-'",
1887 pp_directives[ct]);
1888 else {
1889 searching.nparam_max = readnum(tline->text, &j);
1890 if (j)
1891 nasm_error(ERR_NONFATAL,
1892 "unable to parse parameter count `%s'",
1893 tline->text);
1894 if (searching.nparam_min > searching.nparam_max) {
1895 nasm_error(ERR_NONFATAL,
1896 "minimum parameter count exceeds maximum");
1897 searching.nparam_max = searching.nparam_min;
1901 if (tline && tok_is_(tline->next, "+")) {
1902 tline = tline->next;
1903 searching.plus = true;
1905 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1906 while (mmac) {
1907 if (!strcmp(mmac->name, searching.name) &&
1908 (mmac->nparam_min <= searching.nparam_max
1909 || searching.plus)
1910 && (searching.nparam_min <= mmac->nparam_max
1911 || mmac->plus)) {
1912 found = true;
1913 break;
1915 mmac = mmac->next;
1917 if (tline && tline->next)
1918 nasm_error(ERR_WARNING|ERR_PASS1,
1919 "trailing garbage after %%ifmacro ignored");
1920 nasm_free(searching.name);
1921 j = found;
1922 break;
1925 case PPC_IFID:
1926 needtype = TOK_ID;
1927 goto iftype;
1928 case PPC_IFNUM:
1929 needtype = TOK_NUMBER;
1930 goto iftype;
1931 case PPC_IFSTR:
1932 needtype = TOK_STRING;
1933 goto iftype;
1935 iftype:
1936 t = tline = expand_smacro(tline);
1938 while (tok_type_(t, TOK_WHITESPACE) ||
1939 (needtype == TOK_NUMBER &&
1940 tok_type_(t, TOK_OTHER) &&
1941 (t->text[0] == '-' || t->text[0] == '+') &&
1942 !t->text[1]))
1943 t = t->next;
1945 j = tok_type_(t, needtype);
1946 break;
1948 case PPC_IFTOKEN:
1949 t = tline = expand_smacro(tline);
1950 while (tok_type_(t, TOK_WHITESPACE))
1951 t = t->next;
1953 j = false;
1954 if (t) {
1955 t = t->next; /* Skip the actual token */
1956 while (tok_type_(t, TOK_WHITESPACE))
1957 t = t->next;
1958 j = !t; /* Should be nothing left */
1960 break;
1962 case PPC_IFEMPTY:
1963 t = tline = expand_smacro(tline);
1964 while (tok_type_(t, TOK_WHITESPACE))
1965 t = t->next;
1967 j = !t; /* Should be empty */
1968 break;
1970 case PPC_IF:
1971 t = tline = expand_smacro(tline);
1972 tptr = &t;
1973 tokval.t_type = TOKEN_INVALID;
1974 evalresult = evaluate(ppscan, tptr, &tokval,
1975 NULL, pass | CRITICAL, NULL);
1976 if (!evalresult)
1977 return -1;
1978 if (tokval.t_type)
1979 nasm_error(ERR_WARNING|ERR_PASS1,
1980 "trailing garbage after expression ignored");
1981 if (!is_simple(evalresult)) {
1982 nasm_error(ERR_NONFATAL,
1983 "non-constant value given to `%s'", pp_directives[ct]);
1984 goto fail;
1986 j = reloc_value(evalresult) != 0;
1987 break;
1989 default:
1990 nasm_error(ERR_FATAL,
1991 "preprocessor directive `%s' not yet implemented",
1992 pp_directives[ct]);
1993 goto fail;
1996 free_tlist(origline);
1997 return j ^ PP_NEGATIVE(ct);
1999 fail:
2000 free_tlist(origline);
2001 return -1;
2005 * Common code for defining an smacro
2007 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2008 int nparam, Token *expansion)
2010 SMacro *smac, **smhead;
2011 struct hash_table *smtbl;
2013 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2014 if (!smac) {
2015 nasm_error(ERR_WARNING|ERR_PASS1,
2016 "single-line macro `%s' defined both with and"
2017 " without parameters", mname);
2019 * Some instances of the old code considered this a failure,
2020 * some others didn't. What is the right thing to do here?
2022 free_tlist(expansion);
2023 return false; /* Failure */
2024 } else {
2026 * We're redefining, so we have to take over an
2027 * existing SMacro structure. This means freeing
2028 * what was already in it.
2030 nasm_free(smac->name);
2031 free_tlist(smac->expansion);
2033 } else {
2034 smtbl = ctx ? &ctx->localmac : &smacros;
2035 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2036 smac = nasm_malloc(sizeof(SMacro));
2037 smac->next = *smhead;
2038 *smhead = smac;
2040 smac->name = nasm_strdup(mname);
2041 smac->casesense = casesense;
2042 smac->nparam = nparam;
2043 smac->expansion = expansion;
2044 smac->in_progress = false;
2045 return true; /* Success */
2049 * Undefine an smacro
2051 static void undef_smacro(Context *ctx, const char *mname)
2053 SMacro **smhead, *s, **sp;
2054 struct hash_table *smtbl;
2056 smtbl = ctx ? &ctx->localmac : &smacros;
2057 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2059 if (smhead) {
2061 * We now have a macro name... go hunt for it.
2063 sp = smhead;
2064 while ((s = *sp) != NULL) {
2065 if (!mstrcmp(s->name, mname, s->casesense)) {
2066 *sp = s->next;
2067 nasm_free(s->name);
2068 free_tlist(s->expansion);
2069 nasm_free(s);
2070 } else {
2071 sp = &s->next;
2078 * Parse a mmacro specification.
2080 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2082 bool err;
2084 tline = tline->next;
2085 skip_white_(tline);
2086 tline = expand_id(tline);
2087 if (!tok_type_(tline, TOK_ID)) {
2088 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2089 return false;
2092 def->prev = NULL;
2093 def->name = nasm_strdup(tline->text);
2094 def->plus = false;
2095 def->nolist = false;
2096 def->in_progress = 0;
2097 def->rep_nest = NULL;
2098 def->nparam_min = 0;
2099 def->nparam_max = 0;
2101 tline = expand_smacro(tline->next);
2102 skip_white_(tline);
2103 if (!tok_type_(tline, TOK_NUMBER)) {
2104 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2105 } else {
2106 def->nparam_min = def->nparam_max =
2107 readnum(tline->text, &err);
2108 if (err)
2109 nasm_error(ERR_NONFATAL,
2110 "unable to parse parameter count `%s'", tline->text);
2112 if (tline && tok_is_(tline->next, "-")) {
2113 tline = tline->next->next;
2114 if (tok_is_(tline, "*")) {
2115 def->nparam_max = INT_MAX;
2116 } else if (!tok_type_(tline, TOK_NUMBER)) {
2117 nasm_error(ERR_NONFATAL,
2118 "`%s' expects a parameter count after `-'", directive);
2119 } else {
2120 def->nparam_max = readnum(tline->text, &err);
2121 if (err) {
2122 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2123 tline->text);
2125 if (def->nparam_min > def->nparam_max) {
2126 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2127 def->nparam_max = def->nparam_min;
2131 if (tline && tok_is_(tline->next, "+")) {
2132 tline = tline->next;
2133 def->plus = true;
2135 if (tline && tok_type_(tline->next, TOK_ID) &&
2136 !nasm_stricmp(tline->next->text, ".nolist")) {
2137 tline = tline->next;
2138 def->nolist = true;
2142 * Handle default parameters.
2144 if (tline && tline->next) {
2145 def->dlist = tline->next;
2146 tline->next = NULL;
2147 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2148 } else {
2149 def->dlist = NULL;
2150 def->defaults = NULL;
2152 def->expansion = NULL;
2154 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2155 !def->plus)
2156 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2157 "too many default macro parameters");
2159 return true;
2164 * Decode a size directive
2166 static int parse_size(const char *str) {
2167 static const char *size_names[] =
2168 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2169 static const int sizes[] =
2170 { 0, 1, 4, 16, 8, 10, 2, 32 };
2171 return str ? sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1] : 0;
2175 * Process a preprocessor %pragma directive. Currently there are none.
2176 * Gets passed the token list starting with the "preproc" token from
2177 * "%pragma preproc".
2179 static void do_pragma_preproc(Token *tline)
2181 /* Skip to the real stuff */
2182 tline = tline->next;
2183 skip_white_(tline);
2184 if (!tline)
2185 return;
2187 (void)tline; /* Nothing else to do at present */
2191 * find and process preprocessor directive in passed line
2192 * Find out if a line contains a preprocessor directive, and deal
2193 * with it if so.
2195 * If a directive _is_ found, it is the responsibility of this routine
2196 * (and not the caller) to free_tlist() the line.
2198 * @param tline a pointer to the current tokeninzed line linked list
2199 * @param output if this directive generated output
2200 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2203 static int do_directive(Token *tline, char **output)
2205 enum preproc_token i;
2206 int j;
2207 bool err;
2208 int nparam;
2209 bool nolist;
2210 bool casesense;
2211 int k, m;
2212 int offset;
2213 char *p, *pp;
2214 const char *found_path;
2215 const char *mname;
2216 Include *inc;
2217 Context *ctx;
2218 Cond *cond;
2219 MMacro *mmac, **mmhead;
2220 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2221 Line *l;
2222 struct tokenval tokval;
2223 expr *evalresult;
2224 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2225 int64_t count;
2226 size_t len;
2227 int severity;
2229 *output = NULL; /* No output generated */
2230 origline = tline;
2232 skip_white_(tline);
2233 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2234 (tline->text[0] && (tline->text[1] == '%' ||
2235 tline->text[1] == '$' ||
2236 tline->text[1] == '!')))
2237 return NO_DIRECTIVE_FOUND;
2239 i = pp_token_hash(tline->text);
2242 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2243 * since they are known to be buggy at moment, we need to fix them
2244 * in future release (2.09-2.10)
2246 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2247 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2248 tline->text);
2249 return NO_DIRECTIVE_FOUND;
2253 * If we're in a non-emitting branch of a condition construct,
2254 * or walking to the end of an already terminated %rep block,
2255 * we should ignore all directives except for condition
2256 * directives.
2258 if (((istk->conds && !emitting(istk->conds->state)) ||
2259 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2260 return NO_DIRECTIVE_FOUND;
2264 * If we're defining a macro or reading a %rep block, we should
2265 * ignore all directives except for %macro/%imacro (which nest),
2266 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2267 * If we're in a %rep block, another %rep nests, so should be let through.
2269 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2270 i != PP_RMACRO && i != PP_IRMACRO &&
2271 i != PP_ENDMACRO && i != PP_ENDM &&
2272 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2273 return NO_DIRECTIVE_FOUND;
2276 if (defining) {
2277 if (i == PP_MACRO || i == PP_IMACRO ||
2278 i == PP_RMACRO || i == PP_IRMACRO) {
2279 nested_mac_count++;
2280 return NO_DIRECTIVE_FOUND;
2281 } else if (nested_mac_count > 0) {
2282 if (i == PP_ENDMACRO) {
2283 nested_mac_count--;
2284 return NO_DIRECTIVE_FOUND;
2287 if (!defining->name) {
2288 if (i == PP_REP) {
2289 nested_rep_count++;
2290 return NO_DIRECTIVE_FOUND;
2291 } else if (nested_rep_count > 0) {
2292 if (i == PP_ENDREP) {
2293 nested_rep_count--;
2294 return NO_DIRECTIVE_FOUND;
2300 switch (i) {
2301 case PP_INVALID:
2302 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2303 tline->text);
2304 return NO_DIRECTIVE_FOUND; /* didn't get it */
2306 case PP_PRAGMA:
2308 * %pragma namespace options...
2310 * The namespace "preproc" is reserved for the preprocessor;
2311 * all other namespaces generate a [pragma] assembly directive.
2313 * Invalid %pragmas are ignored and may have different
2314 * meaning in future versions of NASM.
2316 tline = tline->next;
2317 skip_white_(tline);
2318 tline = expand_smacro(tline);
2319 if (tok_type_(tline, TOK_ID)) {
2320 if (!nasm_stricmp(tline->text, "preproc")) {
2321 /* Preprocessor pragma */
2322 do_pragma_preproc(tline);
2323 } else {
2324 /* Build the assembler directive */
2325 t = new_Token(NULL, TOK_OTHER, "[", 1);
2326 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2327 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2328 tline = t;
2329 for (t = tline; t->next; t = t->next)
2331 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2332 /* true here can be revisited in the future */
2333 *output = detoken(tline, true);
2336 free_tlist(origline);
2337 return DIRECTIVE_FOUND;
2339 case PP_STACKSIZE:
2340 /* Directive to tell NASM what the default stack size is. The
2341 * default is for a 16-bit stack, and this can be overriden with
2342 * %stacksize large.
2344 tline = tline->next;
2345 if (tline && tline->type == TOK_WHITESPACE)
2346 tline = tline->next;
2347 if (!tline || tline->type != TOK_ID) {
2348 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2349 free_tlist(origline);
2350 return DIRECTIVE_FOUND;
2352 if (nasm_stricmp(tline->text, "flat") == 0) {
2353 /* All subsequent ARG directives are for a 32-bit stack */
2354 StackSize = 4;
2355 StackPointer = "ebp";
2356 ArgOffset = 8;
2357 LocalOffset = 0;
2358 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2359 /* All subsequent ARG directives are for a 64-bit stack */
2360 StackSize = 8;
2361 StackPointer = "rbp";
2362 ArgOffset = 16;
2363 LocalOffset = 0;
2364 } else if (nasm_stricmp(tline->text, "large") == 0) {
2365 /* All subsequent ARG directives are for a 16-bit stack,
2366 * far function call.
2368 StackSize = 2;
2369 StackPointer = "bp";
2370 ArgOffset = 4;
2371 LocalOffset = 0;
2372 } else if (nasm_stricmp(tline->text, "small") == 0) {
2373 /* All subsequent ARG directives are for a 16-bit stack,
2374 * far function call. We don't support near functions.
2376 StackSize = 2;
2377 StackPointer = "bp";
2378 ArgOffset = 6;
2379 LocalOffset = 0;
2380 } else {
2381 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2382 free_tlist(origline);
2383 return DIRECTIVE_FOUND;
2385 free_tlist(origline);
2386 return DIRECTIVE_FOUND;
2388 case PP_ARG:
2389 /* TASM like ARG directive to define arguments to functions, in
2390 * the following form:
2392 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2394 offset = ArgOffset;
2395 do {
2396 char *arg, directive[256];
2397 int size = StackSize;
2399 /* Find the argument name */
2400 tline = tline->next;
2401 if (tline && tline->type == TOK_WHITESPACE)
2402 tline = tline->next;
2403 if (!tline || tline->type != TOK_ID) {
2404 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2405 free_tlist(origline);
2406 return DIRECTIVE_FOUND;
2408 arg = tline->text;
2410 /* Find the argument size type */
2411 tline = tline->next;
2412 if (!tline || tline->type != TOK_OTHER
2413 || tline->text[0] != ':') {
2414 nasm_error(ERR_NONFATAL,
2415 "Syntax error processing `%%arg' directive");
2416 free_tlist(origline);
2417 return DIRECTIVE_FOUND;
2419 tline = tline->next;
2420 if (!tline || tline->type != TOK_ID) {
2421 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2422 free_tlist(origline);
2423 return DIRECTIVE_FOUND;
2426 /* Allow macro expansion of type parameter */
2427 tt = tokenize(tline->text);
2428 tt = expand_smacro(tt);
2429 size = parse_size(tt->text);
2430 if (!size) {
2431 nasm_error(ERR_NONFATAL,
2432 "Invalid size type for `%%arg' missing directive");
2433 free_tlist(tt);
2434 free_tlist(origline);
2435 return DIRECTIVE_FOUND;
2437 free_tlist(tt);
2439 /* Round up to even stack slots */
2440 size = ALIGN(size, StackSize);
2442 /* Now define the macro for the argument */
2443 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2444 arg, StackPointer, offset);
2445 do_directive(tokenize(directive), output);
2446 offset += size;
2448 /* Move to the next argument in the list */
2449 tline = tline->next;
2450 if (tline && tline->type == TOK_WHITESPACE)
2451 tline = tline->next;
2452 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2453 ArgOffset = offset;
2454 free_tlist(origline);
2455 return DIRECTIVE_FOUND;
2457 case PP_LOCAL:
2458 /* TASM like LOCAL directive to define local variables for a
2459 * function, in the following form:
2461 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2463 * The '= LocalSize' at the end is ignored by NASM, but is
2464 * required by TASM to define the local parameter size (and used
2465 * by the TASM macro package).
2467 offset = LocalOffset;
2468 do {
2469 char *local, directive[256];
2470 int size = StackSize;
2472 /* Find the argument name */
2473 tline = tline->next;
2474 if (tline && tline->type == TOK_WHITESPACE)
2475 tline = tline->next;
2476 if (!tline || tline->type != TOK_ID) {
2477 nasm_error(ERR_NONFATAL,
2478 "`%%local' missing argument parameter");
2479 free_tlist(origline);
2480 return DIRECTIVE_FOUND;
2482 local = tline->text;
2484 /* Find the argument size type */
2485 tline = tline->next;
2486 if (!tline || tline->type != TOK_OTHER
2487 || tline->text[0] != ':') {
2488 nasm_error(ERR_NONFATAL,
2489 "Syntax error processing `%%local' directive");
2490 free_tlist(origline);
2491 return DIRECTIVE_FOUND;
2493 tline = tline->next;
2494 if (!tline || tline->type != TOK_ID) {
2495 nasm_error(ERR_NONFATAL,
2496 "`%%local' missing size type parameter");
2497 free_tlist(origline);
2498 return DIRECTIVE_FOUND;
2501 /* Allow macro expansion of type parameter */
2502 tt = tokenize(tline->text);
2503 tt = expand_smacro(tt);
2504 size = parse_size(tt->text);
2505 if (!size) {
2506 nasm_error(ERR_NONFATAL,
2507 "Invalid size type for `%%local' missing directive");
2508 free_tlist(tt);
2509 free_tlist(origline);
2510 return DIRECTIVE_FOUND;
2512 free_tlist(tt);
2514 /* Round up to even stack slots */
2515 size = ALIGN(size, StackSize);
2517 offset += size; /* Negative offset, increment before */
2519 /* Now define the macro for the argument */
2520 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2521 local, StackPointer, offset);
2522 do_directive(tokenize(directive), output);
2524 /* Now define the assign to setup the enter_c macro correctly */
2525 snprintf(directive, sizeof(directive),
2526 "%%assign %%$localsize %%$localsize+%d", size);
2527 do_directive(tokenize(directive), output);
2529 /* Move to the next argument in the list */
2530 tline = tline->next;
2531 if (tline && tline->type == TOK_WHITESPACE)
2532 tline = tline->next;
2533 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2534 LocalOffset = offset;
2535 free_tlist(origline);
2536 return DIRECTIVE_FOUND;
2538 case PP_CLEAR:
2539 if (tline->next)
2540 nasm_error(ERR_WARNING|ERR_PASS1,
2541 "trailing garbage after `%%clear' ignored");
2542 free_macros();
2543 init_macros();
2544 free_tlist(origline);
2545 return DIRECTIVE_FOUND;
2547 case PP_DEPEND:
2548 t = tline->next = expand_smacro(tline->next);
2549 skip_white_(t);
2550 if (!t || (t->type != TOK_STRING &&
2551 t->type != TOK_INTERNAL_STRING)) {
2552 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2553 free_tlist(origline);
2554 return DIRECTIVE_FOUND; /* but we did _something_ */
2556 if (t->next)
2557 nasm_error(ERR_WARNING|ERR_PASS1,
2558 "trailing garbage after `%%depend' ignored");
2559 p = t->text;
2560 if (t->type != TOK_INTERNAL_STRING)
2561 nasm_unquote_cstr(p, i);
2562 strlist_add_string(deplist, p);
2563 free_tlist(origline);
2564 return DIRECTIVE_FOUND;
2566 case PP_INCLUDE:
2567 t = tline->next = expand_smacro(tline->next);
2568 skip_white_(t);
2570 if (!t || (t->type != TOK_STRING &&
2571 t->type != TOK_INTERNAL_STRING)) {
2572 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2573 free_tlist(origline);
2574 return DIRECTIVE_FOUND; /* but we did _something_ */
2576 if (t->next)
2577 nasm_error(ERR_WARNING|ERR_PASS1,
2578 "trailing garbage after `%%include' ignored");
2579 p = t->text;
2580 if (t->type != TOK_INTERNAL_STRING)
2581 nasm_unquote_cstr(p, i);
2582 inc = nasm_malloc(sizeof(Include));
2583 inc->next = istk;
2584 inc->conds = NULL;
2585 found_path = NULL;
2586 inc->fp = inc_fopen(p, deplist, &found_path,
2587 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2588 if (!inc->fp) {
2589 /* -MG given but file not found */
2590 nasm_free(inc);
2591 } else {
2592 inc->fname = src_set_fname(found_path ? found_path : p);
2593 inc->lineno = src_set_linnum(0);
2594 inc->lineinc = 1;
2595 inc->expansion = NULL;
2596 inc->mstk = NULL;
2597 istk = inc;
2598 lfmt->uplevel(LIST_INCLUDE);
2600 free_tlist(origline);
2601 return DIRECTIVE_FOUND;
2603 case PP_USE:
2605 static macros_t *use_pkg;
2606 const char *pkg_macro = NULL;
2608 tline = tline->next;
2609 skip_white_(tline);
2610 tline = expand_id(tline);
2612 if (!tline || (tline->type != TOK_STRING &&
2613 tline->type != TOK_INTERNAL_STRING &&
2614 tline->type != TOK_ID)) {
2615 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2616 free_tlist(origline);
2617 return DIRECTIVE_FOUND; /* but we did _something_ */
2619 if (tline->next)
2620 nasm_error(ERR_WARNING|ERR_PASS1,
2621 "trailing garbage after `%%use' ignored");
2622 if (tline->type == TOK_STRING)
2623 nasm_unquote_cstr(tline->text, i);
2624 use_pkg = nasm_stdmac_find_package(tline->text);
2625 if (!use_pkg)
2626 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2627 else
2628 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2629 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2630 /* Not already included, go ahead and include it */
2631 stdmacpos = use_pkg;
2633 free_tlist(origline);
2634 return DIRECTIVE_FOUND;
2636 case PP_PUSH:
2637 case PP_REPL:
2638 case PP_POP:
2639 tline = tline->next;
2640 skip_white_(tline);
2641 tline = expand_id(tline);
2642 if (tline) {
2643 if (!tok_type_(tline, TOK_ID)) {
2644 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2645 pp_directives[i]);
2646 free_tlist(origline);
2647 return DIRECTIVE_FOUND; /* but we did _something_ */
2649 if (tline->next)
2650 nasm_error(ERR_WARNING|ERR_PASS1,
2651 "trailing garbage after `%s' ignored",
2652 pp_directives[i]);
2653 p = nasm_strdup(tline->text);
2654 } else {
2655 p = NULL; /* Anonymous */
2658 if (i == PP_PUSH) {
2659 ctx = nasm_malloc(sizeof(Context));
2660 ctx->next = cstk;
2661 hash_init(&ctx->localmac, HASH_SMALL);
2662 ctx->name = p;
2663 ctx->number = unique++;
2664 cstk = ctx;
2665 } else {
2666 /* %pop or %repl */
2667 if (!cstk) {
2668 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2669 pp_directives[i]);
2670 } else if (i == PP_POP) {
2671 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2672 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2673 "expected %s",
2674 cstk->name ? cstk->name : "anonymous", p);
2675 else
2676 ctx_pop();
2677 } else {
2678 /* i == PP_REPL */
2679 nasm_free(cstk->name);
2680 cstk->name = p;
2681 p = NULL;
2683 nasm_free(p);
2685 free_tlist(origline);
2686 return DIRECTIVE_FOUND;
2687 case PP_FATAL:
2688 severity = ERR_FATAL;
2689 goto issue_error;
2690 case PP_ERROR:
2691 severity = ERR_NONFATAL;
2692 goto issue_error;
2693 case PP_WARNING:
2694 severity = ERR_WARNING|ERR_WARN_USER;
2695 goto issue_error;
2697 issue_error:
2699 /* Only error out if this is the final pass */
2700 if (pass != 2 && i != PP_FATAL)
2701 return DIRECTIVE_FOUND;
2703 tline->next = expand_smacro(tline->next);
2704 tline = tline->next;
2705 skip_white_(tline);
2706 t = tline ? tline->next : NULL;
2707 skip_white_(t);
2708 if (tok_type_(tline, TOK_STRING) && !t) {
2709 /* The line contains only a quoted string */
2710 p = tline->text;
2711 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2712 nasm_error(severity, "%s", p);
2713 } else {
2714 /* Not a quoted string, or more than a quoted string */
2715 p = detoken(tline, false);
2716 nasm_error(severity, "%s", p);
2717 nasm_free(p);
2719 free_tlist(origline);
2720 return DIRECTIVE_FOUND;
2723 CASE_PP_IF:
2724 if (istk->conds && !emitting(istk->conds->state))
2725 j = COND_NEVER;
2726 else {
2727 j = if_condition(tline->next, i);
2728 tline->next = NULL; /* it got freed */
2729 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2731 cond = nasm_malloc(sizeof(Cond));
2732 cond->next = istk->conds;
2733 cond->state = j;
2734 istk->conds = cond;
2735 if(istk->mstk)
2736 istk->mstk->condcnt ++;
2737 free_tlist(origline);
2738 return DIRECTIVE_FOUND;
2740 CASE_PP_ELIF:
2741 if (!istk->conds)
2742 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2743 switch(istk->conds->state) {
2744 case COND_IF_TRUE:
2745 istk->conds->state = COND_DONE;
2746 break;
2748 case COND_DONE:
2749 case COND_NEVER:
2750 break;
2752 case COND_ELSE_TRUE:
2753 case COND_ELSE_FALSE:
2754 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2755 "`%%elif' after `%%else' ignored");
2756 istk->conds->state = COND_NEVER;
2757 break;
2759 case COND_IF_FALSE:
2761 * IMPORTANT: In the case of %if, we will already have
2762 * called expand_mmac_params(); however, if we're
2763 * processing an %elif we must have been in a
2764 * non-emitting mode, which would have inhibited
2765 * the normal invocation of expand_mmac_params().
2766 * Therefore, we have to do it explicitly here.
2768 j = if_condition(expand_mmac_params(tline->next), i);
2769 tline->next = NULL; /* it got freed */
2770 istk->conds->state =
2771 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2772 break;
2774 free_tlist(origline);
2775 return DIRECTIVE_FOUND;
2777 case PP_ELSE:
2778 if (tline->next)
2779 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2780 "trailing garbage after `%%else' ignored");
2781 if (!istk->conds)
2782 nasm_fatal("`%%else: no matching `%%if'");
2783 switch(istk->conds->state) {
2784 case COND_IF_TRUE:
2785 case COND_DONE:
2786 istk->conds->state = COND_ELSE_FALSE;
2787 break;
2789 case COND_NEVER:
2790 break;
2792 case COND_IF_FALSE:
2793 istk->conds->state = COND_ELSE_TRUE;
2794 break;
2796 case COND_ELSE_TRUE:
2797 case COND_ELSE_FALSE:
2798 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2799 "`%%else' after `%%else' ignored.");
2800 istk->conds->state = COND_NEVER;
2801 break;
2803 free_tlist(origline);
2804 return DIRECTIVE_FOUND;
2806 case PP_ENDIF:
2807 if (tline->next)
2808 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2809 "trailing garbage after `%%endif' ignored");
2810 if (!istk->conds)
2811 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2812 cond = istk->conds;
2813 istk->conds = cond->next;
2814 nasm_free(cond);
2815 if(istk->mstk)
2816 istk->mstk->condcnt --;
2817 free_tlist(origline);
2818 return DIRECTIVE_FOUND;
2820 case PP_RMACRO:
2821 case PP_IRMACRO:
2822 case PP_MACRO:
2823 case PP_IMACRO:
2824 if (defining) {
2825 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2826 pp_directives[i]);
2827 return DIRECTIVE_FOUND;
2829 defining = nasm_zalloc(sizeof(MMacro));
2830 defining->max_depth = ((i == PP_RMACRO) || (i == PP_IRMACRO))
2831 ? nasm_limit[LIMIT_MACROS] : 0;
2832 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2833 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2834 nasm_free(defining);
2835 defining = NULL;
2836 return DIRECTIVE_FOUND;
2839 src_get(&defining->xline, &defining->fname);
2841 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2842 while (mmac) {
2843 if (!strcmp(mmac->name, defining->name) &&
2844 (mmac->nparam_min <= defining->nparam_max
2845 || defining->plus)
2846 && (defining->nparam_min <= mmac->nparam_max
2847 || mmac->plus)) {
2848 nasm_error(ERR_WARNING|ERR_PASS1,
2849 "redefining multi-line macro `%s'", defining->name);
2850 return DIRECTIVE_FOUND;
2852 mmac = mmac->next;
2854 free_tlist(origline);
2855 return DIRECTIVE_FOUND;
2857 case PP_ENDM:
2858 case PP_ENDMACRO:
2859 if (! (defining && defining->name)) {
2860 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2861 return DIRECTIVE_FOUND;
2863 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2864 defining->next = *mmhead;
2865 *mmhead = defining;
2866 defining = NULL;
2867 free_tlist(origline);
2868 return DIRECTIVE_FOUND;
2870 case PP_EXITMACRO:
2872 * We must search along istk->expansion until we hit a
2873 * macro-end marker for a macro with a name. Then we
2874 * bypass all lines between exitmacro and endmacro.
2876 list_for_each(l, istk->expansion)
2877 if (l->finishes && l->finishes->name)
2878 break;
2880 if (l) {
2882 * Remove all conditional entries relative to this
2883 * macro invocation. (safe to do in this context)
2885 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2886 cond = istk->conds;
2887 istk->conds = cond->next;
2888 nasm_free(cond);
2890 istk->expansion = l;
2891 } else {
2892 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2894 free_tlist(origline);
2895 return DIRECTIVE_FOUND;
2897 case PP_UNMACRO:
2898 case PP_UNIMACRO:
2900 MMacro **mmac_p;
2901 MMacro spec;
2903 spec.casesense = (i == PP_UNMACRO);
2904 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2905 return DIRECTIVE_FOUND;
2907 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2908 while (mmac_p && *mmac_p) {
2909 mmac = *mmac_p;
2910 if (mmac->casesense == spec.casesense &&
2911 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2912 mmac->nparam_min == spec.nparam_min &&
2913 mmac->nparam_max == spec.nparam_max &&
2914 mmac->plus == spec.plus) {
2915 *mmac_p = mmac->next;
2916 free_mmacro(mmac);
2917 } else {
2918 mmac_p = &mmac->next;
2921 free_tlist(origline);
2922 free_tlist(spec.dlist);
2923 return DIRECTIVE_FOUND;
2926 case PP_ROTATE:
2927 if (tline->next && tline->next->type == TOK_WHITESPACE)
2928 tline = tline->next;
2929 if (!tline->next) {
2930 free_tlist(origline);
2931 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2932 return DIRECTIVE_FOUND;
2934 t = expand_smacro(tline->next);
2935 tline->next = NULL;
2936 free_tlist(origline);
2937 tline = t;
2938 tptr = &t;
2939 tokval.t_type = TOKEN_INVALID;
2940 evalresult =
2941 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2942 free_tlist(tline);
2943 if (!evalresult)
2944 return DIRECTIVE_FOUND;
2945 if (tokval.t_type)
2946 nasm_error(ERR_WARNING|ERR_PASS1,
2947 "trailing garbage after expression ignored");
2948 if (!is_simple(evalresult)) {
2949 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2950 return DIRECTIVE_FOUND;
2952 mmac = istk->mstk;
2953 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2954 mmac = mmac->next_active;
2955 if (!mmac) {
2956 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2957 } else if (mmac->nparam == 0) {
2958 nasm_error(ERR_NONFATAL,
2959 "`%%rotate' invoked within macro without parameters");
2960 } else {
2961 int rotate = mmac->rotate + reloc_value(evalresult);
2963 rotate %= (int)mmac->nparam;
2964 if (rotate < 0)
2965 rotate += mmac->nparam;
2967 mmac->rotate = rotate;
2969 return DIRECTIVE_FOUND;
2971 case PP_REP:
2972 nolist = false;
2973 do {
2974 tline = tline->next;
2975 } while (tok_type_(tline, TOK_WHITESPACE));
2977 if (tok_type_(tline, TOK_ID) &&
2978 nasm_stricmp(tline->text, ".nolist") == 0) {
2979 nolist = true;
2980 do {
2981 tline = tline->next;
2982 } while (tok_type_(tline, TOK_WHITESPACE));
2985 if (tline) {
2986 t = expand_smacro(tline);
2987 tptr = &t;
2988 tokval.t_type = TOKEN_INVALID;
2989 evalresult =
2990 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2991 if (!evalresult) {
2992 free_tlist(origline);
2993 return DIRECTIVE_FOUND;
2995 if (tokval.t_type)
2996 nasm_error(ERR_WARNING|ERR_PASS1,
2997 "trailing garbage after expression ignored");
2998 if (!is_simple(evalresult)) {
2999 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3000 return DIRECTIVE_FOUND;
3002 count = reloc_value(evalresult);
3003 if (count > nasm_limit[LIMIT_REP]) {
3004 nasm_error(ERR_NONFATAL,
3005 "`%%rep' count %"PRId64" exceeds limit (currently %"PRId64")",
3006 count, nasm_limit[LIMIT_REP]);
3007 count = 0;
3008 } else if (count < 0) {
3009 nasm_error(ERR_WARNING|ERR_PASS2|ERR_WARN_NEG_REP,
3010 "negative `%%rep' count: %"PRId64, count);
3011 count = 0;
3012 } else {
3013 count++;
3015 } else {
3016 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3017 count = 0;
3019 free_tlist(origline);
3021 tmp_defining = defining;
3022 defining = nasm_malloc(sizeof(MMacro));
3023 defining->prev = NULL;
3024 defining->name = NULL; /* flags this macro as a %rep block */
3025 defining->casesense = false;
3026 defining->plus = false;
3027 defining->nolist = nolist;
3028 defining->in_progress = count;
3029 defining->max_depth = 0;
3030 defining->nparam_min = defining->nparam_max = 0;
3031 defining->defaults = NULL;
3032 defining->dlist = NULL;
3033 defining->expansion = NULL;
3034 defining->next_active = istk->mstk;
3035 defining->rep_nest = tmp_defining;
3036 return DIRECTIVE_FOUND;
3038 case PP_ENDREP:
3039 if (!defining || defining->name) {
3040 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3041 return DIRECTIVE_FOUND;
3045 * Now we have a "macro" defined - although it has no name
3046 * and we won't be entering it in the hash tables - we must
3047 * push a macro-end marker for it on to istk->expansion.
3048 * After that, it will take care of propagating itself (a
3049 * macro-end marker line for a macro which is really a %rep
3050 * block will cause the macro to be re-expanded, complete
3051 * with another macro-end marker to ensure the process
3052 * continues) until the whole expansion is forcibly removed
3053 * from istk->expansion by a %exitrep.
3055 l = nasm_malloc(sizeof(Line));
3056 l->next = istk->expansion;
3057 l->finishes = defining;
3058 l->first = NULL;
3059 istk->expansion = l;
3061 istk->mstk = defining;
3063 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3064 tmp_defining = defining;
3065 defining = defining->rep_nest;
3066 free_tlist(origline);
3067 return DIRECTIVE_FOUND;
3069 case PP_EXITREP:
3071 * We must search along istk->expansion until we hit a
3072 * macro-end marker for a macro with no name. Then we set
3073 * its `in_progress' flag to 0.
3075 list_for_each(l, istk->expansion)
3076 if (l->finishes && !l->finishes->name)
3077 break;
3079 if (l)
3080 l->finishes->in_progress = 1;
3081 else
3082 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3083 free_tlist(origline);
3084 return DIRECTIVE_FOUND;
3086 case PP_XDEFINE:
3087 case PP_IXDEFINE:
3088 case PP_DEFINE:
3089 case PP_IDEFINE:
3090 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3092 tline = tline->next;
3093 skip_white_(tline);
3094 tline = expand_id(tline);
3095 if (!tline || (tline->type != TOK_ID &&
3096 (tline->type != TOK_PREPROC_ID ||
3097 tline->text[1] != '$'))) {
3098 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3099 pp_directives[i]);
3100 free_tlist(origline);
3101 return DIRECTIVE_FOUND;
3104 ctx = get_ctx(tline->text, &mname);
3105 last = tline;
3106 param_start = tline = tline->next;
3107 nparam = 0;
3109 /* Expand the macro definition now for %xdefine and %ixdefine */
3110 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3111 tline = expand_smacro(tline);
3113 if (tok_is_(tline, "(")) {
3115 * This macro has parameters.
3118 tline = tline->next;
3119 while (1) {
3120 skip_white_(tline);
3121 if (!tline) {
3122 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3123 free_tlist(origline);
3124 return DIRECTIVE_FOUND;
3126 if (tline->type != TOK_ID) {
3127 nasm_error(ERR_NONFATAL,
3128 "`%s': parameter identifier expected",
3129 tline->text);
3130 free_tlist(origline);
3131 return DIRECTIVE_FOUND;
3133 tline->type = TOK_SMAC_PARAM + nparam++;
3134 tline = tline->next;
3135 skip_white_(tline);
3136 if (tok_is_(tline, ",")) {
3137 tline = tline->next;
3138 } else {
3139 if (!tok_is_(tline, ")")) {
3140 nasm_error(ERR_NONFATAL,
3141 "`)' expected to terminate macro template");
3142 free_tlist(origline);
3143 return DIRECTIVE_FOUND;
3145 break;
3148 last = tline;
3149 tline = tline->next;
3151 if (tok_type_(tline, TOK_WHITESPACE))
3152 last = tline, tline = tline->next;
3153 macro_start = NULL;
3154 last->next = NULL;
3155 t = tline;
3156 while (t) {
3157 if (t->type == TOK_ID) {
3158 list_for_each(tt, param_start)
3159 if (tt->type >= TOK_SMAC_PARAM &&
3160 !strcmp(tt->text, t->text))
3161 t->type = tt->type;
3163 tt = t->next;
3164 t->next = macro_start;
3165 macro_start = t;
3166 t = tt;
3169 * Good. We now have a macro name, a parameter count, and a
3170 * token list (in reverse order) for an expansion. We ought
3171 * to be OK just to create an SMacro, store it, and let
3172 * free_tlist have the rest of the line (which we have
3173 * carefully re-terminated after chopping off the expansion
3174 * from the end).
3176 define_smacro(ctx, mname, casesense, nparam, macro_start);
3177 free_tlist(origline);
3178 return DIRECTIVE_FOUND;
3180 case PP_UNDEF:
3181 tline = tline->next;
3182 skip_white_(tline);
3183 tline = expand_id(tline);
3184 if (!tline || (tline->type != TOK_ID &&
3185 (tline->type != TOK_PREPROC_ID ||
3186 tline->text[1] != '$'))) {
3187 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3188 free_tlist(origline);
3189 return DIRECTIVE_FOUND;
3191 if (tline->next) {
3192 nasm_error(ERR_WARNING|ERR_PASS1,
3193 "trailing garbage after macro name ignored");
3196 /* Find the context that symbol belongs to */
3197 ctx = get_ctx(tline->text, &mname);
3198 undef_smacro(ctx, mname);
3199 free_tlist(origline);
3200 return DIRECTIVE_FOUND;
3202 case PP_DEFSTR:
3203 case PP_IDEFSTR:
3204 casesense = (i == PP_DEFSTR);
3206 tline = tline->next;
3207 skip_white_(tline);
3208 tline = expand_id(tline);
3209 if (!tline || (tline->type != TOK_ID &&
3210 (tline->type != TOK_PREPROC_ID ||
3211 tline->text[1] != '$'))) {
3212 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3213 pp_directives[i]);
3214 free_tlist(origline);
3215 return DIRECTIVE_FOUND;
3218 ctx = get_ctx(tline->text, &mname);
3219 last = tline;
3220 tline = expand_smacro(tline->next);
3221 last->next = NULL;
3223 while (tok_type_(tline, TOK_WHITESPACE))
3224 tline = delete_Token(tline);
3226 p = detoken(tline, false);
3227 macro_start = nasm_malloc(sizeof(*macro_start));
3228 macro_start->next = NULL;
3229 macro_start->text = nasm_quote(p, strlen(p));
3230 macro_start->type = TOK_STRING;
3231 macro_start->a.mac = NULL;
3232 nasm_free(p);
3235 * We now have a macro name, an implicit parameter count of
3236 * zero, and a string token to use as an expansion. Create
3237 * and store an SMacro.
3239 define_smacro(ctx, mname, casesense, 0, macro_start);
3240 free_tlist(origline);
3241 return DIRECTIVE_FOUND;
3243 case PP_DEFTOK:
3244 case PP_IDEFTOK:
3245 casesense = (i == PP_DEFTOK);
3247 tline = tline->next;
3248 skip_white_(tline);
3249 tline = expand_id(tline);
3250 if (!tline || (tline->type != TOK_ID &&
3251 (tline->type != TOK_PREPROC_ID ||
3252 tline->text[1] != '$'))) {
3253 nasm_error(ERR_NONFATAL,
3254 "`%s' expects a macro identifier as first parameter",
3255 pp_directives[i]);
3256 free_tlist(origline);
3257 return DIRECTIVE_FOUND;
3259 ctx = get_ctx(tline->text, &mname);
3260 last = tline;
3261 tline = expand_smacro(tline->next);
3262 last->next = NULL;
3264 t = tline;
3265 while (tok_type_(t, TOK_WHITESPACE))
3266 t = t->next;
3267 /* t should now point to the string */
3268 if (!tok_type_(t, TOK_STRING)) {
3269 nasm_error(ERR_NONFATAL,
3270 "`%s` requires string as second parameter",
3271 pp_directives[i]);
3272 free_tlist(tline);
3273 free_tlist(origline);
3274 return DIRECTIVE_FOUND;
3278 * Convert the string to a token stream. Note that smacros
3279 * are stored with the token stream reversed, so we have to
3280 * reverse the output of tokenize().
3282 nasm_unquote_cstr(t->text, i);
3283 macro_start = reverse_tokens(tokenize(t->text));
3286 * We now have a macro name, an implicit parameter count of
3287 * zero, and a numeric token to use as an expansion. Create
3288 * and store an SMacro.
3290 define_smacro(ctx, mname, casesense, 0, macro_start);
3291 free_tlist(tline);
3292 free_tlist(origline);
3293 return DIRECTIVE_FOUND;
3295 case PP_PATHSEARCH:
3297 const char *found_path;
3299 casesense = true;
3301 tline = tline->next;
3302 skip_white_(tline);
3303 tline = expand_id(tline);
3304 if (!tline || (tline->type != TOK_ID &&
3305 (tline->type != TOK_PREPROC_ID ||
3306 tline->text[1] != '$'))) {
3307 nasm_error(ERR_NONFATAL,
3308 "`%%pathsearch' expects a macro identifier as first parameter");
3309 free_tlist(origline);
3310 return DIRECTIVE_FOUND;
3312 ctx = get_ctx(tline->text, &mname);
3313 last = tline;
3314 tline = expand_smacro(tline->next);
3315 last->next = NULL;
3317 t = tline;
3318 while (tok_type_(t, TOK_WHITESPACE))
3319 t = t->next;
3321 if (!t || (t->type != TOK_STRING &&
3322 t->type != TOK_INTERNAL_STRING)) {
3323 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3324 free_tlist(tline);
3325 free_tlist(origline);
3326 return DIRECTIVE_FOUND; /* but we did _something_ */
3328 if (t->next)
3329 nasm_error(ERR_WARNING|ERR_PASS1,
3330 "trailing garbage after `%%pathsearch' ignored");
3331 p = t->text;
3332 if (t->type != TOK_INTERNAL_STRING)
3333 nasm_unquote(p, NULL);
3335 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3336 if (!found_path)
3337 found_path = p;
3338 macro_start = nasm_malloc(sizeof(*macro_start));
3339 macro_start->next = NULL;
3340 macro_start->text = nasm_quote(found_path, strlen(found_path));
3341 macro_start->type = TOK_STRING;
3342 macro_start->a.mac = NULL;
3345 * We now have a macro name, an implicit parameter count of
3346 * zero, and a string token to use as an expansion. Create
3347 * and store an SMacro.
3349 define_smacro(ctx, mname, casesense, 0, macro_start);
3350 free_tlist(tline);
3351 free_tlist(origline);
3352 return DIRECTIVE_FOUND;
3355 case PP_STRLEN:
3356 casesense = true;
3358 tline = tline->next;
3359 skip_white_(tline);
3360 tline = expand_id(tline);
3361 if (!tline || (tline->type != TOK_ID &&
3362 (tline->type != TOK_PREPROC_ID ||
3363 tline->text[1] != '$'))) {
3364 nasm_error(ERR_NONFATAL,
3365 "`%%strlen' expects a macro identifier as first parameter");
3366 free_tlist(origline);
3367 return DIRECTIVE_FOUND;
3369 ctx = get_ctx(tline->text, &mname);
3370 last = tline;
3371 tline = expand_smacro(tline->next);
3372 last->next = NULL;
3374 t = tline;
3375 while (tok_type_(t, TOK_WHITESPACE))
3376 t = t->next;
3377 /* t should now point to the string */
3378 if (!tok_type_(t, TOK_STRING)) {
3379 nasm_error(ERR_NONFATAL,
3380 "`%%strlen` requires string as second parameter");
3381 free_tlist(tline);
3382 free_tlist(origline);
3383 return DIRECTIVE_FOUND;
3386 macro_start = nasm_malloc(sizeof(*macro_start));
3387 macro_start->next = NULL;
3388 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3389 macro_start->a.mac = NULL;
3392 * We now have a macro name, an implicit parameter count of
3393 * zero, and a numeric token to use as an expansion. Create
3394 * and store an SMacro.
3396 define_smacro(ctx, mname, casesense, 0, macro_start);
3397 free_tlist(tline);
3398 free_tlist(origline);
3399 return DIRECTIVE_FOUND;
3401 case PP_STRCAT:
3402 casesense = true;
3404 tline = tline->next;
3405 skip_white_(tline);
3406 tline = expand_id(tline);
3407 if (!tline || (tline->type != TOK_ID &&
3408 (tline->type != TOK_PREPROC_ID ||
3409 tline->text[1] != '$'))) {
3410 nasm_error(ERR_NONFATAL,
3411 "`%%strcat' expects a macro identifier as first parameter");
3412 free_tlist(origline);
3413 return DIRECTIVE_FOUND;
3415 ctx = get_ctx(tline->text, &mname);
3416 last = tline;
3417 tline = expand_smacro(tline->next);
3418 last->next = NULL;
3420 len = 0;
3421 list_for_each(t, tline) {
3422 switch (t->type) {
3423 case TOK_WHITESPACE:
3424 break;
3425 case TOK_STRING:
3426 len += t->a.len = nasm_unquote(t->text, NULL);
3427 break;
3428 case TOK_OTHER:
3429 if (!strcmp(t->text, ",")) /* permit comma separators */
3430 break;
3431 /* else fall through */
3432 default:
3433 nasm_error(ERR_NONFATAL,
3434 "non-string passed to `%%strcat' (%d)", t->type);
3435 free_tlist(tline);
3436 free_tlist(origline);
3437 return DIRECTIVE_FOUND;
3441 p = pp = nasm_malloc(len);
3442 list_for_each(t, tline) {
3443 if (t->type == TOK_STRING) {
3444 memcpy(p, t->text, t->a.len);
3445 p += t->a.len;
3450 * We now have a macro name, an implicit parameter count of
3451 * zero, and a numeric token to use as an expansion. Create
3452 * and store an SMacro.
3454 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3455 macro_start->text = nasm_quote(pp, len);
3456 nasm_free(pp);
3457 define_smacro(ctx, mname, casesense, 0, macro_start);
3458 free_tlist(tline);
3459 free_tlist(origline);
3460 return DIRECTIVE_FOUND;
3462 case PP_SUBSTR:
3464 int64_t start, count;
3465 size_t len;
3467 casesense = true;
3469 tline = tline->next;
3470 skip_white_(tline);
3471 tline = expand_id(tline);
3472 if (!tline || (tline->type != TOK_ID &&
3473 (tline->type != TOK_PREPROC_ID ||
3474 tline->text[1] != '$'))) {
3475 nasm_error(ERR_NONFATAL,
3476 "`%%substr' expects a macro identifier as first parameter");
3477 free_tlist(origline);
3478 return DIRECTIVE_FOUND;
3480 ctx = get_ctx(tline->text, &mname);
3481 last = tline;
3482 tline = expand_smacro(tline->next);
3483 last->next = NULL;
3485 if (tline) /* skip expanded id */
3486 t = tline->next;
3487 while (tok_type_(t, TOK_WHITESPACE))
3488 t = t->next;
3490 /* t should now point to the string */
3491 if (!tok_type_(t, TOK_STRING)) {
3492 nasm_error(ERR_NONFATAL,
3493 "`%%substr` requires string as second parameter");
3494 free_tlist(tline);
3495 free_tlist(origline);
3496 return DIRECTIVE_FOUND;
3499 tt = t->next;
3500 tptr = &tt;
3501 tokval.t_type = TOKEN_INVALID;
3502 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3503 if (!evalresult) {
3504 free_tlist(tline);
3505 free_tlist(origline);
3506 return DIRECTIVE_FOUND;
3507 } else if (!is_simple(evalresult)) {
3508 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3509 free_tlist(tline);
3510 free_tlist(origline);
3511 return DIRECTIVE_FOUND;
3513 start = evalresult->value - 1;
3515 while (tok_type_(tt, TOK_WHITESPACE))
3516 tt = tt->next;
3517 if (!tt) {
3518 count = 1; /* Backwards compatibility: one character */
3519 } else {
3520 tokval.t_type = TOKEN_INVALID;
3521 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3522 if (!evalresult) {
3523 free_tlist(tline);
3524 free_tlist(origline);
3525 return DIRECTIVE_FOUND;
3526 } else if (!is_simple(evalresult)) {
3527 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3528 free_tlist(tline);
3529 free_tlist(origline);
3530 return DIRECTIVE_FOUND;
3532 count = evalresult->value;
3535 len = nasm_unquote(t->text, NULL);
3537 /* make start and count being in range */
3538 if (start < 0)
3539 start = 0;
3540 if (count < 0)
3541 count = len + count + 1 - start;
3542 if (start + count > (int64_t)len)
3543 count = len - start;
3544 if (!len || count < 0 || start >=(int64_t)len)
3545 start = -1, count = 0; /* empty string */
3547 macro_start = nasm_malloc(sizeof(*macro_start));
3548 macro_start->next = NULL;
3549 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3550 macro_start->type = TOK_STRING;
3551 macro_start->a.mac = NULL;
3554 * We now have a macro name, an implicit parameter count of
3555 * zero, and a numeric token to use as an expansion. Create
3556 * and store an SMacro.
3558 define_smacro(ctx, mname, casesense, 0, macro_start);
3559 free_tlist(tline);
3560 free_tlist(origline);
3561 return DIRECTIVE_FOUND;
3564 case PP_ASSIGN:
3565 case PP_IASSIGN:
3566 casesense = (i == PP_ASSIGN);
3568 tline = tline->next;
3569 skip_white_(tline);
3570 tline = expand_id(tline);
3571 if (!tline || (tline->type != TOK_ID &&
3572 (tline->type != TOK_PREPROC_ID ||
3573 tline->text[1] != '$'))) {
3574 nasm_error(ERR_NONFATAL,
3575 "`%%%sassign' expects a macro identifier",
3576 (i == PP_IASSIGN ? "i" : ""));
3577 free_tlist(origline);
3578 return DIRECTIVE_FOUND;
3580 ctx = get_ctx(tline->text, &mname);
3581 last = tline;
3582 tline = expand_smacro(tline->next);
3583 last->next = NULL;
3585 t = tline;
3586 tptr = &t;
3587 tokval.t_type = TOKEN_INVALID;
3588 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3589 free_tlist(tline);
3590 if (!evalresult) {
3591 free_tlist(origline);
3592 return DIRECTIVE_FOUND;
3595 if (tokval.t_type)
3596 nasm_error(ERR_WARNING|ERR_PASS1,
3597 "trailing garbage after expression ignored");
3599 if (!is_simple(evalresult)) {
3600 nasm_error(ERR_NONFATAL,
3601 "non-constant value given to `%%%sassign'",
3602 (i == PP_IASSIGN ? "i" : ""));
3603 free_tlist(origline);
3604 return DIRECTIVE_FOUND;
3607 macro_start = nasm_malloc(sizeof(*macro_start));
3608 macro_start->next = NULL;
3609 make_tok_num(macro_start, reloc_value(evalresult));
3610 macro_start->a.mac = NULL;
3613 * We now have a macro name, an implicit parameter count of
3614 * zero, and a numeric token to use as an expansion. Create
3615 * and store an SMacro.
3617 define_smacro(ctx, mname, casesense, 0, macro_start);
3618 free_tlist(origline);
3619 return DIRECTIVE_FOUND;
3621 case PP_LINE:
3623 * Syntax is `%line nnn[+mmm] [filename]'
3625 tline = tline->next;
3626 skip_white_(tline);
3627 if (!tok_type_(tline, TOK_NUMBER)) {
3628 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3629 free_tlist(origline);
3630 return DIRECTIVE_FOUND;
3632 k = readnum(tline->text, &err);
3633 m = 1;
3634 tline = tline->next;
3635 if (tok_is_(tline, "+")) {
3636 tline = tline->next;
3637 if (!tok_type_(tline, TOK_NUMBER)) {
3638 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3639 free_tlist(origline);
3640 return DIRECTIVE_FOUND;
3642 m = readnum(tline->text, &err);
3643 tline = tline->next;
3645 skip_white_(tline);
3646 src_set_linnum(k);
3647 istk->lineinc = m;
3648 if (tline) {
3649 char *fname = detoken(tline, false);
3650 src_set_fname(fname);
3651 nasm_free(fname);
3653 free_tlist(origline);
3654 return DIRECTIVE_FOUND;
3656 default:
3657 nasm_error(ERR_FATAL,
3658 "preprocessor directive `%s' not yet implemented",
3659 pp_directives[i]);
3660 return DIRECTIVE_FOUND;
3665 * Ensure that a macro parameter contains a condition code and
3666 * nothing else. Return the condition code index if so, or -1
3667 * otherwise.
3669 static int find_cc(Token * t)
3671 Token *tt;
3673 if (!t)
3674 return -1; /* Probably a %+ without a space */
3676 skip_white_(t);
3677 if (!t)
3678 return -1;
3679 if (t->type != TOK_ID)
3680 return -1;
3681 tt = t->next;
3682 skip_white_(tt);
3683 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3684 return -1;
3686 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3690 * This routines walks over tokens strem and hadnles tokens
3691 * pasting, if @handle_explicit passed then explicit pasting
3692 * term is handled, otherwise -- implicit pastings only.
3694 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3695 size_t mnum, bool handle_explicit)
3697 Token *tok, *next, **prev_next, **prev_nonspace;
3698 bool pasted = false;
3699 char *buf, *p;
3700 size_t len, i;
3703 * The last token before pasting. We need it
3704 * to be able to connect new handled tokens.
3705 * In other words if there were a tokens stream
3707 * A -> B -> C -> D
3709 * and we've joined tokens B and C, the resulting
3710 * stream should be
3712 * A -> BC -> D
3714 tok = *head;
3715 prev_next = NULL;
3717 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3718 prev_nonspace = head;
3719 else
3720 prev_nonspace = NULL;
3722 while (tok && (next = tok->next)) {
3724 switch (tok->type) {
3725 case TOK_WHITESPACE:
3726 /* Zap redundant whitespaces */
3727 while (tok_type_(next, TOK_WHITESPACE))
3728 next = delete_Token(next);
3729 tok->next = next;
3730 break;
3732 case TOK_PASTE:
3733 /* Explicit pasting */
3734 if (!handle_explicit)
3735 break;
3736 next = delete_Token(tok);
3738 while (tok_type_(next, TOK_WHITESPACE))
3739 next = delete_Token(next);
3741 if (!pasted)
3742 pasted = true;
3744 /* Left pasting token is start of line */
3745 if (!prev_nonspace)
3746 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3749 * No ending token, this might happen in two
3750 * cases
3752 * 1) There indeed no right token at all
3753 * 2) There is a bare "%define ID" statement,
3754 * and @ID does expand to whitespace.
3756 * So technically we need to do a grammar analysis
3757 * in another stage of parsing, but for now lets don't
3758 * change the behaviour people used to. Simply allow
3759 * whitespace after paste token.
3761 if (!next) {
3763 * Zap ending space tokens and that's all.
3765 tok = (*prev_nonspace)->next;
3766 while (tok_type_(tok, TOK_WHITESPACE))
3767 tok = delete_Token(tok);
3768 tok = *prev_nonspace;
3769 tok->next = NULL;
3770 break;
3773 tok = *prev_nonspace;
3774 while (tok_type_(tok, TOK_WHITESPACE))
3775 tok = delete_Token(tok);
3776 len = strlen(tok->text);
3777 len += strlen(next->text);
3779 p = buf = nasm_malloc(len + 1);
3780 strcpy(p, tok->text);
3781 p = strchr(p, '\0');
3782 strcpy(p, next->text);
3784 delete_Token(tok);
3786 tok = tokenize(buf);
3787 nasm_free(buf);
3789 *prev_nonspace = tok;
3790 while (tok && tok->next)
3791 tok = tok->next;
3793 tok->next = delete_Token(next);
3795 /* Restart from pasted tokens head */
3796 tok = *prev_nonspace;
3797 break;
3799 default:
3800 /* implicit pasting */
3801 for (i = 0; i < mnum; i++) {
3802 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3803 continue;
3805 len = 0;
3806 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3807 len += strlen(next->text);
3808 next = next->next;
3811 /* No match or no text to process */
3812 if (tok == next || len == 0)
3813 break;
3815 len += strlen(tok->text);
3816 p = buf = nasm_malloc(len + 1);
3818 strcpy(p, tok->text);
3819 p = strchr(p, '\0');
3820 tok = delete_Token(tok);
3822 while (tok != next) {
3823 if (PP_CONCAT_MATCH(tok, m[i].mask_tail)) {
3824 strcpy(p, tok->text);
3825 p = strchr(p, '\0');
3827 tok = delete_Token(tok);
3830 tok = tokenize(buf);
3831 nasm_free(buf);
3833 if (prev_next)
3834 *prev_next = tok;
3835 else
3836 *head = tok;
3839 * Connect pasted into original stream,
3840 * ie A -> new-tokens -> B
3842 while (tok && tok->next)
3843 tok = tok->next;
3844 tok->next = next;
3846 if (!pasted)
3847 pasted = true;
3849 /* Restart from pasted tokens head */
3850 tok = prev_next ? *prev_next : *head;
3853 break;
3856 prev_next = &tok->next;
3858 if (tok->next &&
3859 !tok_type_(tok->next, TOK_WHITESPACE) &&
3860 !tok_type_(tok->next, TOK_PASTE))
3861 prev_nonspace = prev_next;
3863 tok = tok->next;
3866 return pasted;
3870 * expands to a list of tokens from %{x:y}
3872 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3874 Token *t = tline, **tt, *tm, *head;
3875 char *pos;
3876 int fst, lst, j, i;
3878 pos = strchr(tline->text, ':');
3879 nasm_assert(pos);
3881 lst = atoi(pos + 1);
3882 fst = atoi(tline->text + 1);
3885 * only macros params are accounted so
3886 * if someone passes %0 -- we reject such
3887 * value(s)
3889 if (lst == 0 || fst == 0)
3890 goto err;
3892 /* the values should be sane */
3893 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3894 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3895 goto err;
3897 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3898 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3900 /* counted from zero */
3901 fst--, lst--;
3904 * It will be at least one token. Note we
3905 * need to scan params until separator, otherwise
3906 * only first token will be passed.
3908 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3909 if (!tm)
3910 goto err;
3911 head = new_Token(NULL, tm->type, tm->text, 0);
3912 tt = &head->next, tm = tm->next;
3913 while (tok_isnt_(tm, ",")) {
3914 t = new_Token(NULL, tm->type, tm->text, 0);
3915 *tt = t, tt = &t->next, tm = tm->next;
3918 if (fst < lst) {
3919 for (i = fst + 1; i <= lst; i++) {
3920 t = new_Token(NULL, TOK_OTHER, ",", 0);
3921 *tt = t, tt = &t->next;
3922 j = (i + mac->rotate) % mac->nparam;
3923 tm = mac->params[j];
3924 while (tok_isnt_(tm, ",")) {
3925 t = new_Token(NULL, tm->type, tm->text, 0);
3926 *tt = t, tt = &t->next, tm = tm->next;
3929 } else {
3930 for (i = fst - 1; i >= lst; i--) {
3931 t = new_Token(NULL, TOK_OTHER, ",", 0);
3932 *tt = t, tt = &t->next;
3933 j = (i + mac->rotate) % mac->nparam;
3934 tm = mac->params[j];
3935 while (tok_isnt_(tm, ",")) {
3936 t = new_Token(NULL, tm->type, tm->text, 0);
3937 *tt = t, tt = &t->next, tm = tm->next;
3942 *last = tt;
3943 return head;
3945 err:
3946 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3947 &tline->text[1]);
3948 return tline;
3952 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3953 * %-n) and MMacro-local identifiers (%%foo) as well as
3954 * macro indirection (%[...]) and range (%{..:..}).
3956 static Token *expand_mmac_params(Token * tline)
3958 Token *t, *tt, **tail, *thead;
3959 bool changed = false;
3960 char *pos;
3962 tail = &thead;
3963 thead = NULL;
3965 while (tline) {
3966 if (tline->type == TOK_PREPROC_ID && tline->text && tline->text[0] &&
3967 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3968 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3969 tline->text[1] == '%')) {
3970 char *text = NULL;
3971 int type = 0, cc; /* type = 0 to placate optimisers */
3972 char tmpbuf[30];
3973 unsigned int n;
3974 int i;
3975 MMacro *mac;
3977 t = tline;
3978 tline = tline->next;
3980 mac = istk->mstk;
3981 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3982 mac = mac->next_active;
3983 if (!mac) {
3984 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3985 } else {
3986 pos = strchr(t->text, ':');
3987 if (!pos) {
3988 switch (t->text[1]) {
3990 * We have to make a substitution of one of the
3991 * forms %1, %-1, %+1, %%foo, %0.
3993 case '0':
3994 type = TOK_NUMBER;
3995 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3996 text = nasm_strdup(tmpbuf);
3997 break;
3998 case '%':
3999 type = TOK_ID;
4000 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4001 mac->unique);
4002 text = nasm_strcat(tmpbuf, t->text + 2);
4003 break;
4004 case '-':
4005 n = atoi(t->text + 2) - 1;
4006 if (n >= mac->nparam)
4007 tt = NULL;
4008 else {
4009 if (mac->nparam > 1)
4010 n = (n + mac->rotate) % mac->nparam;
4011 tt = mac->params[n];
4013 cc = find_cc(tt);
4014 if (cc == -1) {
4015 nasm_error(ERR_NONFATAL,
4016 "macro parameter %d is not a condition code",
4017 n + 1);
4018 text = NULL;
4019 } else {
4020 type = TOK_ID;
4021 if (inverse_ccs[cc] == -1) {
4022 nasm_error(ERR_NONFATAL,
4023 "condition code `%s' is not invertible",
4024 conditions[cc]);
4025 text = NULL;
4026 } else
4027 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4029 break;
4030 case '+':
4031 n = atoi(t->text + 2) - 1;
4032 if (n >= mac->nparam)
4033 tt = NULL;
4034 else {
4035 if (mac->nparam > 1)
4036 n = (n + mac->rotate) % mac->nparam;
4037 tt = mac->params[n];
4039 cc = find_cc(tt);
4040 if (cc == -1) {
4041 nasm_error(ERR_NONFATAL,
4042 "macro parameter %d is not a condition code",
4043 n + 1);
4044 text = NULL;
4045 } else {
4046 type = TOK_ID;
4047 text = nasm_strdup(conditions[cc]);
4049 break;
4050 default:
4051 n = atoi(t->text + 1) - 1;
4052 if (n >= mac->nparam)
4053 tt = NULL;
4054 else {
4055 if (mac->nparam > 1)
4056 n = (n + mac->rotate) % mac->nparam;
4057 tt = mac->params[n];
4059 if (tt) {
4060 for (i = 0; i < mac->paramlen[n]; i++) {
4061 *tail = new_Token(NULL, tt->type, tt->text, 0);
4062 tail = &(*tail)->next;
4063 tt = tt->next;
4066 text = NULL; /* we've done it here */
4067 break;
4069 } else {
4071 * seems we have a parameters range here
4073 Token *head, **last;
4074 head = expand_mmac_params_range(mac, t, &last);
4075 if (head != t) {
4076 *tail = head;
4077 *last = tline;
4078 tline = head;
4079 text = NULL;
4083 if (!text) {
4084 delete_Token(t);
4085 } else {
4086 *tail = t;
4087 tail = &t->next;
4088 t->type = type;
4089 nasm_free(t->text);
4090 t->text = text;
4091 t->a.mac = NULL;
4093 changed = true;
4094 continue;
4095 } else if (tline->type == TOK_INDIRECT) {
4096 t = tline;
4097 tline = tline->next;
4098 tt = tokenize(t->text);
4099 tt = expand_mmac_params(tt);
4100 tt = expand_smacro(tt);
4101 *tail = tt;
4102 while (tt) {
4103 tt->a.mac = NULL; /* Necessary? */
4104 tail = &tt->next;
4105 tt = tt->next;
4107 delete_Token(t);
4108 changed = true;
4109 } else {
4110 t = *tail = tline;
4111 tline = tline->next;
4112 t->a.mac = NULL;
4113 tail = &t->next;
4116 *tail = NULL;
4118 if (changed) {
4119 const struct tokseq_match t[] = {
4121 PP_CONCAT_MASK(TOK_ID) |
4122 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4123 PP_CONCAT_MASK(TOK_ID) |
4124 PP_CONCAT_MASK(TOK_NUMBER) |
4125 PP_CONCAT_MASK(TOK_FLOAT) |
4126 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4129 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4130 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4133 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4136 return thead;
4140 * Expand all single-line macro calls made in the given line.
4141 * Return the expanded version of the line. The original is deemed
4142 * to be destroyed in the process. (In reality we'll just move
4143 * Tokens from input to output a lot of the time, rather than
4144 * actually bothering to destroy and replicate.)
4147 static Token *expand_smacro(Token * tline)
4149 Token *t, *tt, *mstart, **tail, *thead;
4150 SMacro *head = NULL, *m;
4151 Token **params;
4152 int *paramsize;
4153 unsigned int nparam, sparam;
4154 int brackets;
4155 Token *org_tline = tline;
4156 Context *ctx;
4157 const char *mname;
4158 int64_t deadman = nasm_limit[LIMIT_MACROS];
4159 bool expanded;
4162 * Trick: we should avoid changing the start token pointer since it can
4163 * be contained in "next" field of other token. Because of this
4164 * we allocate a copy of first token and work with it; at the end of
4165 * routine we copy it back
4167 if (org_tline) {
4168 tline = new_Token(org_tline->next, org_tline->type,
4169 org_tline->text, 0);
4170 tline->a.mac = org_tline->a.mac;
4171 nasm_free(org_tline->text);
4172 org_tline->text = NULL;
4175 expanded = true; /* Always expand %+ at least once */
4177 again:
4178 thead = NULL;
4179 tail = &thead;
4181 while (tline) { /* main token loop */
4182 if (!--deadman) {
4183 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4184 goto err;
4187 if ((mname = tline->text)) {
4188 /* if this token is a local macro, look in local context */
4189 if (tline->type == TOK_ID) {
4190 head = (SMacro *)hash_findix(&smacros, mname);
4191 } else if (tline->type == TOK_PREPROC_ID) {
4192 ctx = get_ctx(mname, &mname);
4193 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4194 } else
4195 head = NULL;
4198 * We've hit an identifier. As in is_mmacro below, we first
4199 * check whether the identifier is a single-line macro at
4200 * all, then think about checking for parameters if
4201 * necessary.
4203 list_for_each(m, head)
4204 if (!mstrcmp(m->name, mname, m->casesense))
4205 break;
4206 if (m) {
4207 mstart = tline;
4208 params = NULL;
4209 paramsize = NULL;
4210 if (m->nparam == 0) {
4212 * Simple case: the macro is parameterless. Discard the
4213 * one token that the macro call took, and push the
4214 * expansion back on the to-do stack.
4216 if (!m->expansion) {
4217 if (!strcmp("__FILE__", m->name)) {
4218 const char *file = src_get_fname();
4219 /* nasm_free(tline->text); here? */
4220 tline->text = nasm_quote(file, strlen(file));
4221 tline->type = TOK_STRING;
4222 continue;
4224 if (!strcmp("__LINE__", m->name)) {
4225 nasm_free(tline->text);
4226 make_tok_num(tline, src_get_linnum());
4227 continue;
4229 if (!strcmp("__BITS__", m->name)) {
4230 nasm_free(tline->text);
4231 make_tok_num(tline, globalbits);
4232 continue;
4234 tline = delete_Token(tline);
4235 continue;
4237 } else {
4239 * Complicated case: at least one macro with this name
4240 * exists and takes parameters. We must find the
4241 * parameters in the call, count them, find the SMacro
4242 * that corresponds to that form of the macro call, and
4243 * substitute for the parameters when we expand. What a
4244 * pain.
4246 /*tline = tline->next;
4247 skip_white_(tline); */
4248 do {
4249 t = tline->next;
4250 while (tok_type_(t, TOK_SMAC_END)) {
4251 t->a.mac->in_progress = false;
4252 t->text = NULL;
4253 t = tline->next = delete_Token(t);
4255 tline = t;
4256 } while (tok_type_(tline, TOK_WHITESPACE));
4257 if (!tok_is_(tline, "(")) {
4259 * This macro wasn't called with parameters: ignore
4260 * the call. (Behaviour borrowed from gnu cpp.)
4262 tline = mstart;
4263 m = NULL;
4264 } else {
4265 int paren = 0;
4266 int white = 0;
4267 brackets = 0;
4268 nparam = 0;
4269 sparam = PARAM_DELTA;
4270 params = nasm_malloc(sparam * sizeof(Token *));
4271 params[0] = tline->next;
4272 paramsize = nasm_malloc(sparam * sizeof(int));
4273 paramsize[0] = 0;
4274 while (true) { /* parameter loop */
4276 * For some unusual expansions
4277 * which concatenates function call
4279 t = tline->next;
4280 while (tok_type_(t, TOK_SMAC_END)) {
4281 t->a.mac->in_progress = false;
4282 t->text = NULL;
4283 t = tline->next = delete_Token(t);
4285 tline = t;
4287 if (!tline) {
4288 nasm_error(ERR_NONFATAL,
4289 "macro call expects terminating `)'");
4290 break;
4292 if (tline->type == TOK_WHITESPACE
4293 && brackets <= 0) {
4294 if (paramsize[nparam])
4295 white++;
4296 else
4297 params[nparam] = tline->next;
4298 continue; /* parameter loop */
4300 if (tline->type == TOK_OTHER
4301 && tline->text[1] == 0) {
4302 char ch = tline->text[0];
4303 if (ch == ',' && !paren && brackets <= 0) {
4304 if (++nparam >= sparam) {
4305 sparam += PARAM_DELTA;
4306 params = nasm_realloc(params,
4307 sparam * sizeof(Token *));
4308 paramsize = nasm_realloc(paramsize,
4309 sparam * sizeof(int));
4311 params[nparam] = tline->next;
4312 paramsize[nparam] = 0;
4313 white = 0;
4314 continue; /* parameter loop */
4316 if (ch == '{' &&
4317 (brackets > 0 || (brackets == 0 &&
4318 !paramsize[nparam])))
4320 if (!(brackets++)) {
4321 params[nparam] = tline->next;
4322 continue; /* parameter loop */
4325 if (ch == '}' && brackets > 0)
4326 if (--brackets == 0) {
4327 brackets = -1;
4328 continue; /* parameter loop */
4330 if (ch == '(' && !brackets)
4331 paren++;
4332 if (ch == ')' && brackets <= 0)
4333 if (--paren < 0)
4334 break;
4336 if (brackets < 0) {
4337 brackets = 0;
4338 nasm_error(ERR_NONFATAL, "braces do not "
4339 "enclose all of macro parameter");
4341 paramsize[nparam] += white + 1;
4342 white = 0;
4343 } /* parameter loop */
4344 nparam++;
4345 while (m && (m->nparam != nparam ||
4346 mstrcmp(m->name, mname,
4347 m->casesense)))
4348 m = m->next;
4349 if (!m)
4350 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4351 "macro `%s' exists, "
4352 "but not taking %d parameters",
4353 mstart->text, nparam);
4356 if (m && m->in_progress)
4357 m = NULL;
4358 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4360 * Design question: should we handle !tline, which
4361 * indicates missing ')' here, or expand those
4362 * macros anyway, which requires the (t) test a few
4363 * lines down?
4365 nasm_free(params);
4366 nasm_free(paramsize);
4367 tline = mstart;
4368 } else {
4370 * Expand the macro: we are placed on the last token of the
4371 * call, so that we can easily split the call from the
4372 * following tokens. We also start by pushing an SMAC_END
4373 * token for the cycle removal.
4375 t = tline;
4376 if (t) {
4377 tline = t->next;
4378 t->next = NULL;
4380 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4381 tt->a.mac = m;
4382 m->in_progress = true;
4383 tline = tt;
4384 list_for_each(t, m->expansion) {
4385 if (t->type >= TOK_SMAC_PARAM) {
4386 Token *pcopy = tline, **ptail = &pcopy;
4387 Token *ttt, *pt;
4388 int i;
4390 ttt = params[t->type - TOK_SMAC_PARAM];
4391 i = paramsize[t->type - TOK_SMAC_PARAM];
4392 while (--i >= 0) {
4393 pt = *ptail = new_Token(tline, ttt->type,
4394 ttt->text, 0);
4395 ptail = &pt->next;
4396 ttt = ttt->next;
4397 if (!ttt && i > 0) {
4399 * FIXME: Need to handle more gracefully,
4400 * exiting early on agruments analysis.
4402 nasm_error(ERR_FATAL,
4403 "macro `%s' expects %d args",
4404 mstart->text,
4405 (int)paramsize[t->type - TOK_SMAC_PARAM]);
4408 tline = pcopy;
4409 } else if (t->type == TOK_PREPROC_Q) {
4410 tt = new_Token(tline, TOK_ID, mname, 0);
4411 tline = tt;
4412 } else if (t->type == TOK_PREPROC_QQ) {
4413 tt = new_Token(tline, TOK_ID, m->name, 0);
4414 tline = tt;
4415 } else {
4416 tt = new_Token(tline, t->type, t->text, 0);
4417 tline = tt;
4422 * Having done that, get rid of the macro call, and clean
4423 * up the parameters.
4425 nasm_free(params);
4426 nasm_free(paramsize);
4427 free_tlist(mstart);
4428 expanded = true;
4429 continue; /* main token loop */
4434 if (tline->type == TOK_SMAC_END) {
4435 /* On error path it might already be dropped */
4436 if (tline->a.mac)
4437 tline->a.mac->in_progress = false;
4438 tline = delete_Token(tline);
4439 } else {
4440 t = *tail = tline;
4441 tline = tline->next;
4442 t->a.mac = NULL;
4443 t->next = NULL;
4444 tail = &t->next;
4449 * Now scan the entire line and look for successive TOK_IDs that resulted
4450 * after expansion (they can't be produced by tokenize()). The successive
4451 * TOK_IDs should be concatenated.
4452 * Also we look for %+ tokens and concatenate the tokens before and after
4453 * them (without white spaces in between).
4455 if (expanded) {
4456 const struct tokseq_match t[] = {
4458 PP_CONCAT_MASK(TOK_ID) |
4459 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4460 PP_CONCAT_MASK(TOK_ID) |
4461 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4462 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4465 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4467 * If we concatenated something, *and* we had previously expanded
4468 * an actual macro, scan the lines again for macros...
4470 tline = thead;
4471 expanded = false;
4472 goto again;
4476 err:
4477 if (org_tline) {
4478 if (thead) {
4479 *org_tline = *thead;
4480 /* since we just gave text to org_line, don't free it */
4481 thead->text = NULL;
4482 delete_Token(thead);
4483 } else {
4484 /* the expression expanded to empty line;
4485 we can't return NULL for some reasons
4486 we just set the line to a single WHITESPACE token. */
4487 memset(org_tline, 0, sizeof(*org_tline));
4488 org_tline->text = NULL;
4489 org_tline->type = TOK_WHITESPACE;
4491 thead = org_tline;
4494 return thead;
4498 * Similar to expand_smacro but used exclusively with macro identifiers
4499 * right before they are fetched in. The reason is that there can be
4500 * identifiers consisting of several subparts. We consider that if there
4501 * are more than one element forming the name, user wants a expansion,
4502 * otherwise it will be left as-is. Example:
4504 * %define %$abc cde
4506 * the identifier %$abc will be left as-is so that the handler for %define
4507 * will suck it and define the corresponding value. Other case:
4509 * %define _%$abc cde
4511 * In this case user wants name to be expanded *before* %define starts
4512 * working, so we'll expand %$abc into something (if it has a value;
4513 * otherwise it will be left as-is) then concatenate all successive
4514 * PP_IDs into one.
4516 static Token *expand_id(Token * tline)
4518 Token *cur, *oldnext = NULL;
4520 if (!tline || !tline->next)
4521 return tline;
4523 cur = tline;
4524 while (cur->next &&
4525 (cur->next->type == TOK_ID ||
4526 cur->next->type == TOK_PREPROC_ID
4527 || cur->next->type == TOK_NUMBER))
4528 cur = cur->next;
4530 /* If identifier consists of just one token, don't expand */
4531 if (cur == tline)
4532 return tline;
4534 if (cur) {
4535 oldnext = cur->next; /* Detach the tail past identifier */
4536 cur->next = NULL; /* so that expand_smacro stops here */
4539 tline = expand_smacro(tline);
4541 if (cur) {
4542 /* expand_smacro possibly changhed tline; re-scan for EOL */
4543 cur = tline;
4544 while (cur && cur->next)
4545 cur = cur->next;
4546 if (cur)
4547 cur->next = oldnext;
4550 return tline;
4554 * Determine whether the given line constitutes a multi-line macro
4555 * call, and return the MMacro structure called if so. Doesn't have
4556 * to check for an initial label - that's taken care of in
4557 * expand_mmacro - but must check numbers of parameters. Guaranteed
4558 * to be called with tline->type == TOK_ID, so the putative macro
4559 * name is easy to find.
4561 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4563 MMacro *head, *m;
4564 Token **params;
4565 int nparam;
4567 head = (MMacro *) hash_findix(&mmacros, tline->text);
4570 * Efficiency: first we see if any macro exists with the given
4571 * name. If not, we can return NULL immediately. _Then_ we
4572 * count the parameters, and then we look further along the
4573 * list if necessary to find the proper MMacro.
4575 list_for_each(m, head)
4576 if (!mstrcmp(m->name, tline->text, m->casesense))
4577 break;
4578 if (!m)
4579 return NULL;
4582 * OK, we have a potential macro. Count and demarcate the
4583 * parameters.
4585 count_mmac_params(tline->next, &nparam, &params);
4588 * So we know how many parameters we've got. Find the MMacro
4589 * structure that handles this number.
4591 while (m) {
4592 if (m->nparam_min <= nparam
4593 && (m->plus || nparam <= m->nparam_max)) {
4595 * This one is right. Just check if cycle removal
4596 * prohibits us using it before we actually celebrate...
4598 if (m->in_progress > m->max_depth) {
4599 if (m->max_depth > 0) {
4600 nasm_error(ERR_WARNING,
4601 "reached maximum recursion depth of %i",
4602 m->max_depth);
4604 nasm_free(params);
4605 return NULL;
4608 * It's right, and we can use it. Add its default
4609 * parameters to the end of our list if necessary.
4611 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4612 params =
4613 nasm_realloc(params,
4614 ((m->nparam_min + m->ndefs +
4615 1) * sizeof(*params)));
4616 while (nparam < m->nparam_min + m->ndefs) {
4617 params[nparam] = m->defaults[nparam - m->nparam_min];
4618 nparam++;
4622 * If we've gone over the maximum parameter count (and
4623 * we're in Plus mode), ignore parameters beyond
4624 * nparam_max.
4626 if (m->plus && nparam > m->nparam_max)
4627 nparam = m->nparam_max;
4629 * Then terminate the parameter list, and leave.
4631 if (!params) { /* need this special case */
4632 params = nasm_malloc(sizeof(*params));
4633 nparam = 0;
4635 params[nparam] = NULL;
4636 *params_array = params;
4637 return m;
4640 * This one wasn't right: look for the next one with the
4641 * same name.
4643 list_for_each(m, m->next)
4644 if (!mstrcmp(m->name, tline->text, m->casesense))
4645 break;
4649 * After all that, we didn't find one with the right number of
4650 * parameters. Issue a warning, and fail to expand the macro.
4652 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4653 "macro `%s' exists, but not taking %d parameters",
4654 tline->text, nparam);
4655 nasm_free(params);
4656 return NULL;
4661 * Save MMacro invocation specific fields in
4662 * preparation for a recursive macro expansion
4664 static void push_mmacro(MMacro *m)
4666 MMacroInvocation *i;
4668 i = nasm_malloc(sizeof(MMacroInvocation));
4669 i->prev = m->prev;
4670 i->params = m->params;
4671 i->iline = m->iline;
4672 i->nparam = m->nparam;
4673 i->rotate = m->rotate;
4674 i->paramlen = m->paramlen;
4675 i->unique = m->unique;
4676 i->condcnt = m->condcnt;
4677 m->prev = i;
4682 * Restore MMacro invocation specific fields that were
4683 * saved during a previous recursive macro expansion
4685 static void pop_mmacro(MMacro *m)
4687 MMacroInvocation *i;
4689 if (m->prev) {
4690 i = m->prev;
4691 m->prev = i->prev;
4692 m->params = i->params;
4693 m->iline = i->iline;
4694 m->nparam = i->nparam;
4695 m->rotate = i->rotate;
4696 m->paramlen = i->paramlen;
4697 m->unique = i->unique;
4698 m->condcnt = i->condcnt;
4699 nasm_free(i);
4705 * Expand the multi-line macro call made by the given line, if
4706 * there is one to be expanded. If there is, push the expansion on
4707 * istk->expansion and return 1. Otherwise return 0.
4709 static int expand_mmacro(Token * tline)
4711 Token *startline = tline;
4712 Token *label = NULL;
4713 int dont_prepend = 0;
4714 Token **params, *t, *tt;
4715 MMacro *m;
4716 Line *l, *ll;
4717 int i, nparam, *paramlen;
4718 const char *mname;
4720 t = tline;
4721 skip_white_(t);
4722 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4723 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4724 return 0;
4725 m = is_mmacro(t, &params);
4726 if (m) {
4727 mname = t->text;
4728 } else {
4729 Token *last;
4731 * We have an id which isn't a macro call. We'll assume
4732 * it might be a label; we'll also check to see if a
4733 * colon follows it. Then, if there's another id after
4734 * that lot, we'll check it again for macro-hood.
4736 label = last = t;
4737 t = t->next;
4738 if (tok_type_(t, TOK_WHITESPACE))
4739 last = t, t = t->next;
4740 if (tok_is_(t, ":")) {
4741 dont_prepend = 1;
4742 last = t, t = t->next;
4743 if (tok_type_(t, TOK_WHITESPACE))
4744 last = t, t = t->next;
4746 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4747 return 0;
4748 last->next = NULL;
4749 mname = t->text;
4750 tline = t;
4754 * Fix up the parameters: this involves stripping leading and
4755 * trailing whitespace, then stripping braces if they are
4756 * present.
4758 for (nparam = 0; params[nparam]; nparam++) ;
4759 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4761 for (i = 0; params[i]; i++) {
4762 int brace = 0;
4763 int comma = (!m->plus || i < nparam - 1);
4765 t = params[i];
4766 skip_white_(t);
4767 if (tok_is_(t, "{"))
4768 t = t->next, brace++, comma = false;
4769 params[i] = t;
4770 paramlen[i] = 0;
4771 while (t) {
4772 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4773 break; /* ... because we have hit a comma */
4774 if (comma && t->type == TOK_WHITESPACE
4775 && tok_is_(t->next, ","))
4776 break; /* ... or a space then a comma */
4777 if (brace && t->type == TOK_OTHER) {
4778 if (t->text[0] == '{')
4779 brace++; /* ... or a nested opening brace */
4780 else if (t->text[0] == '}')
4781 if (!--brace)
4782 break; /* ... or a brace */
4784 t = t->next;
4785 paramlen[i]++;
4787 if (brace)
4788 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4792 * OK, we have a MMacro structure together with a set of
4793 * parameters. We must now go through the expansion and push
4794 * copies of each Line on to istk->expansion. Substitution of
4795 * parameter tokens and macro-local tokens doesn't get done
4796 * until the single-line macro substitution process; this is
4797 * because delaying them allows us to change the semantics
4798 * later through %rotate.
4800 * First, push an end marker on to istk->expansion, mark this
4801 * macro as in progress, and set up its invocation-specific
4802 * variables.
4804 ll = nasm_malloc(sizeof(Line));
4805 ll->next = istk->expansion;
4806 ll->finishes = m;
4807 ll->first = NULL;
4808 istk->expansion = ll;
4811 * Save the previous MMacro expansion in the case of
4812 * macro recursion
4814 if (m->max_depth && m->in_progress)
4815 push_mmacro(m);
4817 m->in_progress ++;
4818 m->params = params;
4819 m->iline = tline;
4820 m->nparam = nparam;
4821 m->rotate = 0;
4822 m->paramlen = paramlen;
4823 m->unique = unique++;
4824 m->lineno = 0;
4825 m->condcnt = 0;
4827 m->next_active = istk->mstk;
4828 istk->mstk = m;
4830 list_for_each(l, m->expansion) {
4831 Token **tail;
4833 ll = nasm_malloc(sizeof(Line));
4834 ll->finishes = NULL;
4835 ll->next = istk->expansion;
4836 istk->expansion = ll;
4837 tail = &ll->first;
4839 list_for_each(t, l->first) {
4840 Token *x = t;
4841 switch (t->type) {
4842 case TOK_PREPROC_Q:
4843 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4844 break;
4845 case TOK_PREPROC_QQ:
4846 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4847 break;
4848 case TOK_PREPROC_ID:
4849 if (t->text[1] == '0' && t->text[2] == '0') {
4850 dont_prepend = -1;
4851 x = label;
4852 if (!x)
4853 continue;
4855 /* fall through */
4856 default:
4857 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4858 break;
4860 tail = &tt->next;
4862 *tail = NULL;
4866 * If we had a label, push it on as the first line of
4867 * the macro expansion.
4869 if (label) {
4870 if (dont_prepend < 0)
4871 free_tlist(startline);
4872 else {
4873 ll = nasm_malloc(sizeof(Line));
4874 ll->finishes = NULL;
4875 ll->next = istk->expansion;
4876 istk->expansion = ll;
4877 ll->first = startline;
4878 if (!dont_prepend) {
4879 while (label->next)
4880 label = label->next;
4881 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4886 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4888 return 1;
4892 * This function adds macro names to error messages, and suppresses
4893 * them if necessary.
4895 static void pp_verror(int severity, const char *fmt, va_list arg)
4897 char buff[BUFSIZ];
4898 MMacro *mmac = NULL;
4899 int delta = 0;
4902 * If we're in a dead branch of IF or something like it, ignore the error.
4903 * However, because %else etc are evaluated in the state context
4904 * of the previous branch, errors might get lost:
4905 * %if 0 ... %else trailing garbage ... %endif
4906 * So %else etc should set the ERR_PP_PRECOND flag.
4908 if ((severity & ERR_MASK) < ERR_FATAL &&
4909 istk && istk->conds &&
4910 ((severity & ERR_PP_PRECOND) ?
4911 istk->conds->state == COND_NEVER :
4912 !emitting(istk->conds->state)))
4913 return;
4915 /* get %macro name */
4916 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4917 mmac = istk->mstk;
4918 /* but %rep blocks should be skipped */
4919 while (mmac && !mmac->name)
4920 mmac = mmac->next_active, delta++;
4923 if (mmac) {
4924 vsnprintf(buff, sizeof(buff), fmt, arg);
4926 nasm_set_verror(real_verror);
4927 nasm_error(severity, "(%s:%d) %s",
4928 mmac->name, mmac->lineno - delta, buff);
4929 nasm_set_verror(pp_verror);
4930 } else {
4931 real_verror(severity, fmt, arg);
4935 static void
4936 pp_reset(const char *file, int apass, StrList *dep_list)
4938 Token *t;
4940 cstk = NULL;
4941 istk = nasm_malloc(sizeof(Include));
4942 istk->next = NULL;
4943 istk->conds = NULL;
4944 istk->expansion = NULL;
4945 istk->mstk = NULL;
4946 istk->fp = nasm_open_read(file, NF_TEXT);
4947 istk->fname = NULL;
4948 src_set(0, file);
4949 istk->lineinc = 1;
4950 if (!istk->fp)
4951 nasm_fatal_fl(ERR_NOFILE, "unable to open input file `%s'", file);
4952 defining = NULL;
4953 nested_mac_count = 0;
4954 nested_rep_count = 0;
4955 init_macros();
4956 unique = 0;
4957 deplist = dep_list;
4959 if (tasm_compatible_mode)
4960 pp_add_stdmac(nasm_stdmac_tasm);
4962 pp_add_stdmac(nasm_stdmac_nasm);
4963 pp_add_stdmac(nasm_stdmac_version);
4965 if (extrastdmac)
4966 pp_add_stdmac(extrastdmac);
4968 stdmacpos = stdmacros[0];
4969 stdmacnext = &stdmacros[1];
4971 do_predef = true;
4974 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4975 * The caller, however, will also pass in 3 for preprocess-only so
4976 * we can set __PASS__ accordingly.
4978 pass = apass > 2 ? 2 : apass;
4980 strlist_add_string(deplist, file);
4983 * Define the __PASS__ macro. This is defined here unlike
4984 * all the other builtins, because it is special -- it varies between
4985 * passes.
4987 t = nasm_malloc(sizeof(*t));
4988 t->next = NULL;
4989 make_tok_num(t, apass);
4990 t->a.mac = NULL;
4991 define_smacro(NULL, "__PASS__", true, 0, t);
4994 static void pp_init(void)
4996 hash_init(&FileHash, HASH_MEDIUM);
4997 ipath = strlist_allocate();
5000 static char *pp_getline(void)
5002 char *line;
5003 Token *tline;
5005 real_verror = nasm_set_verror(pp_verror);
5007 while (1) {
5009 * Fetch a tokenized line, either from the macro-expansion
5010 * buffer or from the input file.
5012 tline = NULL;
5013 while (istk->expansion && istk->expansion->finishes) {
5014 Line *l = istk->expansion;
5015 if (!l->finishes->name && l->finishes->in_progress > 1) {
5016 Line *ll;
5019 * This is a macro-end marker for a macro with no
5020 * name, which means it's not really a macro at all
5021 * but a %rep block, and the `in_progress' field is
5022 * more than 1, meaning that we still need to
5023 * repeat. (1 means the natural last repetition; 0
5024 * means termination by %exitrep.) We have
5025 * therefore expanded up to the %endrep, and must
5026 * push the whole block on to the expansion buffer
5027 * again. We don't bother to remove the macro-end
5028 * marker: we'd only have to generate another one
5029 * if we did.
5031 l->finishes->in_progress--;
5032 list_for_each(l, l->finishes->expansion) {
5033 Token *t, *tt, **tail;
5035 ll = nasm_malloc(sizeof(Line));
5036 ll->next = istk->expansion;
5037 ll->finishes = NULL;
5038 ll->first = NULL;
5039 tail = &ll->first;
5041 list_for_each(t, l->first) {
5042 if (t->text || t->type == TOK_WHITESPACE) {
5043 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5044 tail = &tt->next;
5048 istk->expansion = ll;
5050 } else {
5052 * Check whether a `%rep' was started and not ended
5053 * within this macro expansion. This can happen and
5054 * should be detected. It's a fatal error because
5055 * I'm too confused to work out how to recover
5056 * sensibly from it.
5058 if (defining) {
5059 if (defining->name)
5060 nasm_panic("defining with name in expansion");
5061 else if (istk->mstk->name)
5062 nasm_fatal("`%%rep' without `%%endrep' within"
5063 " expansion of macro `%s'",
5064 istk->mstk->name);
5068 * FIXME: investigate the relationship at this point between
5069 * istk->mstk and l->finishes
5072 MMacro *m = istk->mstk;
5073 istk->mstk = m->next_active;
5074 if (m->name) {
5076 * This was a real macro call, not a %rep, and
5077 * therefore the parameter information needs to
5078 * be freed.
5080 if (m->prev) {
5081 pop_mmacro(m);
5082 l->finishes->in_progress --;
5083 } else {
5084 nasm_free(m->params);
5085 free_tlist(m->iline);
5086 nasm_free(m->paramlen);
5087 l->finishes->in_progress = 0;
5092 * FIXME It is incorrect to always free_mmacro here.
5093 * It leads to usage-after-free.
5095 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
5097 #if 0
5098 else
5099 free_mmacro(m);
5100 #endif
5102 istk->expansion = l->next;
5103 nasm_free(l);
5104 lfmt->downlevel(LIST_MACRO);
5107 while (1) { /* until we get a line we can use */
5109 if (istk->expansion) { /* from a macro expansion */
5110 char *p;
5111 Line *l = istk->expansion;
5112 if (istk->mstk)
5113 istk->mstk->lineno++;
5114 tline = l->first;
5115 istk->expansion = l->next;
5116 nasm_free(l);
5117 p = detoken(tline, false);
5118 lfmt->line(LIST_MACRO, p);
5119 nasm_free(p);
5120 break;
5122 line = read_line();
5123 if (line) { /* from the current input file */
5124 line = prepreproc(line);
5125 tline = tokenize(line);
5126 nasm_free(line);
5127 break;
5130 * The current file has ended; work down the istk
5133 Include *i = istk;
5134 fclose(i->fp);
5135 if (i->conds) {
5136 /* nasm_error can't be conditionally suppressed */
5137 nasm_fatal("expected `%%endif' before end of file");
5139 /* only set line and file name if there's a next node */
5140 if (i->next)
5141 src_set(i->lineno, i->fname);
5142 istk = i->next;
5143 lfmt->downlevel(LIST_INCLUDE);
5144 nasm_free(i);
5145 if (!istk) {
5146 line = NULL;
5147 goto done;
5149 if (istk->expansion && istk->expansion->finishes)
5150 break;
5155 * We must expand MMacro parameters and MMacro-local labels
5156 * _before_ we plunge into directive processing, to cope
5157 * with things like `%define something %1' such as STRUC
5158 * uses. Unless we're _defining_ a MMacro, in which case
5159 * those tokens should be left alone to go into the
5160 * definition; and unless we're in a non-emitting
5161 * condition, in which case we don't want to meddle with
5162 * anything.
5164 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5165 && !(istk->mstk && !istk->mstk->in_progress)) {
5166 tline = expand_mmac_params(tline);
5170 * Check the line to see if it's a preprocessor directive.
5172 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5173 if (line)
5174 break; /* Directive generated output */
5175 else
5176 continue;
5177 } else if (defining) {
5179 * We're defining a multi-line macro. We emit nothing
5180 * at all, and just
5181 * shove the tokenized line on to the macro definition.
5183 Line *l = nasm_malloc(sizeof(Line));
5184 l->next = defining->expansion;
5185 l->first = tline;
5186 l->finishes = NULL;
5187 defining->expansion = l;
5188 continue;
5189 } else if (istk->conds && !emitting(istk->conds->state)) {
5191 * We're in a non-emitting branch of a condition block.
5192 * Emit nothing at all, not even a blank line: when we
5193 * emerge from the condition we'll give a line-number
5194 * directive so we keep our place correctly.
5196 free_tlist(tline);
5197 continue;
5198 } else if (istk->mstk && !istk->mstk->in_progress) {
5200 * We're in a %rep block which has been terminated, so
5201 * we're walking through to the %endrep without
5202 * emitting anything. Emit nothing at all, not even a
5203 * blank line: when we emerge from the %rep block we'll
5204 * give a line-number directive so we keep our place
5205 * correctly.
5207 free_tlist(tline);
5208 continue;
5209 } else {
5210 tline = expand_smacro(tline);
5211 if (!expand_mmacro(tline)) {
5213 * De-tokenize the line again, and emit it.
5215 line = detoken(tline, true);
5216 free_tlist(tline);
5217 break;
5218 } else {
5219 continue; /* expand_mmacro calls free_tlist */
5224 done:
5225 nasm_set_verror(real_verror);
5226 return line;
5229 static void pp_cleanup(int pass)
5231 real_verror = nasm_set_verror(pp_verror);
5233 if (defining) {
5234 if (defining->name) {
5235 nasm_error(ERR_NONFATAL,
5236 "end of file while still defining macro `%s'",
5237 defining->name);
5238 } else {
5239 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5242 free_mmacro(defining);
5243 defining = NULL;
5246 nasm_set_verror(real_verror);
5248 while (cstk)
5249 ctx_pop();
5250 free_macros();
5251 while (istk) {
5252 Include *i = istk;
5253 istk = istk->next;
5254 fclose(i->fp);
5255 nasm_free(i);
5257 while (cstk)
5258 ctx_pop();
5259 src_set_fname(NULL);
5260 if (pass == 0) {
5261 free_llist(predef);
5262 predef = NULL;
5263 delete_Blocks();
5264 freeTokens = NULL;
5265 strlist_free(ipath);
5269 static void pp_include_path(const char *path)
5271 if (!path)
5272 path = "";
5274 strlist_add_string(ipath, path);
5277 static void pp_pre_include(char *fname)
5279 Token *inc, *space, *name;
5280 Line *l;
5282 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5283 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5284 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5286 l = nasm_malloc(sizeof(Line));
5287 l->next = predef;
5288 l->first = inc;
5289 l->finishes = NULL;
5290 predef = l;
5293 static void pp_pre_define(char *definition)
5295 Token *def, *space;
5296 Line *l;
5297 char *equals;
5299 real_verror = nasm_set_verror(pp_verror);
5301 equals = strchr(definition, '=');
5302 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5303 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5304 if (equals)
5305 *equals = ' ';
5306 space->next = tokenize(definition);
5307 if (equals)
5308 *equals = '=';
5310 if (space->next->type != TOK_PREPROC_ID &&
5311 space->next->type != TOK_ID)
5312 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5314 l = nasm_malloc(sizeof(Line));
5315 l->next = predef;
5316 l->first = def;
5317 l->finishes = NULL;
5318 predef = l;
5320 nasm_set_verror(real_verror);
5323 static void pp_pre_undefine(char *definition)
5325 Token *def, *space;
5326 Line *l;
5328 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5329 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5330 space->next = tokenize(definition);
5332 l = nasm_malloc(sizeof(Line));
5333 l->next = predef;
5334 l->first = def;
5335 l->finishes = NULL;
5336 predef = l;
5339 /* Insert an early preprocessor command that doesn't need special handling */
5340 static void pp_pre_command(const char *what, char *string)
5342 char *cmd;
5343 Token *def, *space;
5344 Line *l;
5346 def = tokenize(string);
5347 if (what) {
5348 cmd = nasm_strcat(what[0] == '%' ? "" : "%", what);
5349 space = new_Token(def, TOK_WHITESPACE, NULL, 0);
5350 def = new_Token(space, TOK_PREPROC_ID, cmd, 0);
5353 l = nasm_malloc(sizeof(Line));
5354 l->next = predef;
5355 l->first = def;
5356 l->finishes = NULL;
5357 predef = l;
5360 static void pp_add_stdmac(macros_t *macros)
5362 macros_t **mp;
5364 /* Find the end of the list and avoid duplicates */
5365 for (mp = stdmacros; *mp; mp++) {
5366 if (*mp == macros)
5367 return; /* Nothing to do */
5370 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5372 *mp = macros;
5375 static void pp_extra_stdmac(macros_t *macros)
5377 extrastdmac = macros;
5380 static void make_tok_num(Token * tok, int64_t val)
5382 char numbuf[32];
5383 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5384 tok->text = nasm_strdup(numbuf);
5385 tok->type = TOK_NUMBER;
5388 static void pp_list_one_macro(MMacro *m, int severity)
5390 if (!m)
5391 return;
5393 /* We need to print the next_active list in reverse order */
5394 pp_list_one_macro(m->next_active, severity);
5396 if (m->name && !m->nolist) {
5397 src_set(m->xline + m->lineno, m->fname);
5398 nasm_error(severity, "... from macro `%s' defined here", m->name);
5402 static void pp_error_list_macros(int severity)
5404 int32_t saved_line;
5405 const char *saved_fname = NULL;
5407 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5408 src_get(&saved_line, &saved_fname);
5410 if (istk)
5411 pp_list_one_macro(istk->mstk, severity);
5413 src_set(saved_line, saved_fname);
5416 const struct preproc_ops nasmpp = {
5417 pp_init,
5418 pp_reset,
5419 pp_getline,
5420 pp_cleanup,
5421 pp_extra_stdmac,
5422 pp_pre_define,
5423 pp_pre_undefine,
5424 pp_pre_include,
5425 pp_pre_command,
5426 pp_include_path,
5427 pp_error_list_macros,