preproc: Fix malformed parameter count
[nasm.git] / asm / preproc.c
blobe5ad05aaf406f3d7f9913c42dc4a9c172fe736a5
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;
1653 /* param should be a natural number [0; INT_MAX] */
1654 static int read_param_count(const char *str)
1656 int result;
1657 bool err;
1659 result = readnum(str, &err);
1660 if (result < 0 || result > INT_MAX) {
1661 result = 0;
1662 nasm_error(ERR_NONFATAL, "parameter count `%s' is out of bounds [%d; %d]",
1663 str, 0, INT_MAX);
1664 } else if (err) {
1665 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'", str);
1667 return result;
1671 * Count and mark off the parameters in a multi-line macro call.
1672 * This is called both from within the multi-line macro expansion
1673 * code, and also to mark off the default parameters when provided
1674 * in a %macro definition line.
1676 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1678 int paramsize, brace;
1680 *nparam = paramsize = 0;
1681 *params = NULL;
1682 while (t) {
1683 /* +1: we need space for the final NULL */
1684 if (*nparam+1 >= paramsize) {
1685 paramsize += PARAM_DELTA;
1686 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1688 skip_white_(t);
1689 brace = 0;
1690 if (tok_is_(t, "{"))
1691 brace++;
1692 (*params)[(*nparam)++] = t;
1693 if (brace) {
1694 while (brace && (t = t->next) != NULL) {
1695 if (tok_is_(t, "{"))
1696 brace++;
1697 else if (tok_is_(t, "}"))
1698 brace--;
1701 if (t) {
1703 * Now we've found the closing brace, look further
1704 * for the comma.
1706 t = t->next;
1707 skip_white_(t);
1708 if (tok_isnt_(t, ",")) {
1709 nasm_error(ERR_NONFATAL,
1710 "braces do not enclose all of macro parameter");
1711 while (tok_isnt_(t, ","))
1712 t = t->next;
1715 } else {
1716 while (tok_isnt_(t, ","))
1717 t = t->next;
1719 if (t) { /* got a comma/brace */
1720 t = t->next; /* eat the comma */
1726 * Determine whether one of the various `if' conditions is true or
1727 * not.
1729 * We must free the tline we get passed.
1731 static bool if_condition(Token * tline, enum preproc_token ct)
1733 enum pp_conditional i = PP_COND(ct);
1734 bool j;
1735 Token *t, *tt, **tptr, *origline;
1736 struct tokenval tokval;
1737 expr *evalresult;
1738 enum pp_token_type needtype;
1739 char *p;
1741 origline = tline;
1743 switch (i) {
1744 case PPC_IFCTX:
1745 j = false; /* have we matched yet? */
1746 while (true) {
1747 skip_white_(tline);
1748 if (!tline)
1749 break;
1750 if (tline->type != TOK_ID) {
1751 nasm_error(ERR_NONFATAL,
1752 "`%s' expects context identifiers", pp_directives[ct]);
1753 free_tlist(origline);
1754 return -1;
1756 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1757 j = true;
1758 tline = tline->next;
1760 break;
1762 case PPC_IFDEF:
1763 j = false; /* have we matched yet? */
1764 while (tline) {
1765 skip_white_(tline);
1766 if (!tline || (tline->type != TOK_ID &&
1767 (tline->type != TOK_PREPROC_ID ||
1768 tline->text[1] != '$'))) {
1769 nasm_error(ERR_NONFATAL,
1770 "`%s' expects macro identifiers", pp_directives[ct]);
1771 goto fail;
1773 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1774 j = true;
1775 tline = tline->next;
1777 break;
1779 case PPC_IFENV:
1780 tline = expand_smacro(tline);
1781 j = false; /* have we matched yet? */
1782 while (tline) {
1783 skip_white_(tline);
1784 if (!tline || (tline->type != TOK_ID &&
1785 tline->type != TOK_STRING &&
1786 (tline->type != TOK_PREPROC_ID ||
1787 tline->text[1] != '!'))) {
1788 nasm_error(ERR_NONFATAL,
1789 "`%s' expects environment variable names",
1790 pp_directives[ct]);
1791 goto fail;
1793 p = tline->text;
1794 if (tline->type == TOK_PREPROC_ID)
1795 p += 2; /* Skip leading %! */
1796 if (*p == '\'' || *p == '\"' || *p == '`')
1797 nasm_unquote_cstr(p, ct);
1798 if (getenv(p))
1799 j = true;
1800 tline = tline->next;
1802 break;
1804 case PPC_IFIDN:
1805 case PPC_IFIDNI:
1806 tline = expand_smacro(tline);
1807 t = tt = tline;
1808 while (tok_isnt_(tt, ","))
1809 tt = tt->next;
1810 if (!tt) {
1811 nasm_error(ERR_NONFATAL,
1812 "`%s' expects two comma-separated arguments",
1813 pp_directives[ct]);
1814 goto fail;
1816 tt = tt->next;
1817 j = true; /* assume equality unless proved not */
1818 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1819 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1820 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1821 pp_directives[ct]);
1822 goto fail;
1824 if (t->type == TOK_WHITESPACE) {
1825 t = t->next;
1826 continue;
1828 if (tt->type == TOK_WHITESPACE) {
1829 tt = tt->next;
1830 continue;
1832 if (tt->type != t->type) {
1833 j = false; /* found mismatching tokens */
1834 break;
1836 /* When comparing strings, need to unquote them first */
1837 if (t->type == TOK_STRING) {
1838 size_t l1 = nasm_unquote(t->text, NULL);
1839 size_t l2 = nasm_unquote(tt->text, NULL);
1841 if (l1 != l2) {
1842 j = false;
1843 break;
1845 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1846 j = false;
1847 break;
1849 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1850 j = false; /* found mismatching tokens */
1851 break;
1854 t = t->next;
1855 tt = tt->next;
1857 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1858 j = false; /* trailing gunk on one end or other */
1859 break;
1861 case PPC_IFMACRO:
1863 bool found = false;
1864 MMacro searching, *mmac;
1866 skip_white_(tline);
1867 tline = expand_id(tline);
1868 if (!tok_type_(tline, TOK_ID)) {
1869 nasm_error(ERR_NONFATAL,
1870 "`%s' expects a macro name", pp_directives[ct]);
1871 goto fail;
1873 searching.name = nasm_strdup(tline->text);
1874 searching.casesense = true;
1875 searching.plus = false;
1876 searching.nolist = false;
1877 searching.in_progress = 0;
1878 searching.max_depth = 0;
1879 searching.rep_nest = NULL;
1880 searching.nparam_min = 0;
1881 searching.nparam_max = INT_MAX;
1882 tline = expand_smacro(tline->next);
1883 skip_white_(tline);
1884 if (!tline) {
1885 } else if (!tok_type_(tline, TOK_NUMBER)) {
1886 nasm_error(ERR_NONFATAL,
1887 "`%s' expects a parameter count or nothing",
1888 pp_directives[ct]);
1889 } else {
1890 searching.nparam_min = searching.nparam_max =
1891 read_param_count(tline->text);
1893 if (tline && tok_is_(tline->next, "-")) {
1894 tline = tline->next->next;
1895 if (tok_is_(tline, "*"))
1896 searching.nparam_max = INT_MAX;
1897 else if (!tok_type_(tline, TOK_NUMBER))
1898 nasm_error(ERR_NONFATAL,
1899 "`%s' expects a parameter count after `-'",
1900 pp_directives[ct]);
1901 else {
1902 searching.nparam_max = read_param_count(tline->text);
1903 if (searching.nparam_min > searching.nparam_max) {
1904 nasm_error(ERR_NONFATAL,
1905 "minimum parameter count exceeds maximum");
1906 searching.nparam_max = searching.nparam_min;
1910 if (tline && tok_is_(tline->next, "+")) {
1911 tline = tline->next;
1912 searching.plus = true;
1914 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1915 while (mmac) {
1916 if (!strcmp(mmac->name, searching.name) &&
1917 (mmac->nparam_min <= searching.nparam_max
1918 || searching.plus)
1919 && (searching.nparam_min <= mmac->nparam_max
1920 || mmac->plus)) {
1921 found = true;
1922 break;
1924 mmac = mmac->next;
1926 if (tline && tline->next)
1927 nasm_error(ERR_WARNING|ERR_PASS1,
1928 "trailing garbage after %%ifmacro ignored");
1929 nasm_free(searching.name);
1930 j = found;
1931 break;
1934 case PPC_IFID:
1935 needtype = TOK_ID;
1936 goto iftype;
1937 case PPC_IFNUM:
1938 needtype = TOK_NUMBER;
1939 goto iftype;
1940 case PPC_IFSTR:
1941 needtype = TOK_STRING;
1942 goto iftype;
1944 iftype:
1945 t = tline = expand_smacro(tline);
1947 while (tok_type_(t, TOK_WHITESPACE) ||
1948 (needtype == TOK_NUMBER &&
1949 tok_type_(t, TOK_OTHER) &&
1950 (t->text[0] == '-' || t->text[0] == '+') &&
1951 !t->text[1]))
1952 t = t->next;
1954 j = tok_type_(t, needtype);
1955 break;
1957 case PPC_IFTOKEN:
1958 t = tline = expand_smacro(tline);
1959 while (tok_type_(t, TOK_WHITESPACE))
1960 t = t->next;
1962 j = false;
1963 if (t) {
1964 t = t->next; /* Skip the actual token */
1965 while (tok_type_(t, TOK_WHITESPACE))
1966 t = t->next;
1967 j = !t; /* Should be nothing left */
1969 break;
1971 case PPC_IFEMPTY:
1972 t = tline = expand_smacro(tline);
1973 while (tok_type_(t, TOK_WHITESPACE))
1974 t = t->next;
1976 j = !t; /* Should be empty */
1977 break;
1979 case PPC_IF:
1980 t = tline = expand_smacro(tline);
1981 tptr = &t;
1982 tokval.t_type = TOKEN_INVALID;
1983 evalresult = evaluate(ppscan, tptr, &tokval,
1984 NULL, pass | CRITICAL, NULL);
1985 if (!evalresult)
1986 return -1;
1987 if (tokval.t_type)
1988 nasm_error(ERR_WARNING|ERR_PASS1,
1989 "trailing garbage after expression ignored");
1990 if (!is_simple(evalresult)) {
1991 nasm_error(ERR_NONFATAL,
1992 "non-constant value given to `%s'", pp_directives[ct]);
1993 goto fail;
1995 j = reloc_value(evalresult) != 0;
1996 break;
1998 default:
1999 nasm_error(ERR_FATAL,
2000 "preprocessor directive `%s' not yet implemented",
2001 pp_directives[ct]);
2002 goto fail;
2005 free_tlist(origline);
2006 return j ^ PP_NEGATIVE(ct);
2008 fail:
2009 free_tlist(origline);
2010 return -1;
2014 * Common code for defining an smacro
2016 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2017 int nparam, Token *expansion)
2019 SMacro *smac, **smhead;
2020 struct hash_table *smtbl;
2022 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2023 if (!smac) {
2024 nasm_error(ERR_WARNING|ERR_PASS1,
2025 "single-line macro `%s' defined both with and"
2026 " without parameters", mname);
2028 * Some instances of the old code considered this a failure,
2029 * some others didn't. What is the right thing to do here?
2031 free_tlist(expansion);
2032 return false; /* Failure */
2033 } else {
2035 * We're redefining, so we have to take over an
2036 * existing SMacro structure. This means freeing
2037 * what was already in it.
2039 nasm_free(smac->name);
2040 free_tlist(smac->expansion);
2042 } else {
2043 smtbl = ctx ? &ctx->localmac : &smacros;
2044 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2045 smac = nasm_malloc(sizeof(SMacro));
2046 smac->next = *smhead;
2047 *smhead = smac;
2049 smac->name = nasm_strdup(mname);
2050 smac->casesense = casesense;
2051 smac->nparam = nparam;
2052 smac->expansion = expansion;
2053 smac->in_progress = false;
2054 return true; /* Success */
2058 * Undefine an smacro
2060 static void undef_smacro(Context *ctx, const char *mname)
2062 SMacro **smhead, *s, **sp;
2063 struct hash_table *smtbl;
2065 smtbl = ctx ? &ctx->localmac : &smacros;
2066 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2068 if (smhead) {
2070 * We now have a macro name... go hunt for it.
2072 sp = smhead;
2073 while ((s = *sp) != NULL) {
2074 if (!mstrcmp(s->name, mname, s->casesense)) {
2075 *sp = s->next;
2076 nasm_free(s->name);
2077 free_tlist(s->expansion);
2078 nasm_free(s);
2079 } else {
2080 sp = &s->next;
2087 * Parse a mmacro specification.
2089 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2091 tline = tline->next;
2092 skip_white_(tline);
2093 tline = expand_id(tline);
2094 if (!tok_type_(tline, TOK_ID)) {
2095 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2096 return false;
2099 def->prev = NULL;
2100 def->name = nasm_strdup(tline->text);
2101 def->plus = false;
2102 def->nolist = false;
2103 def->in_progress = 0;
2104 def->rep_nest = NULL;
2105 def->nparam_min = 0;
2106 def->nparam_max = 0;
2108 tline = expand_smacro(tline->next);
2109 skip_white_(tline);
2110 if (!tok_type_(tline, TOK_NUMBER)) {
2111 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2112 } else {
2113 def->nparam_min = def->nparam_max = read_param_count(tline->text);
2115 if (tline && tok_is_(tline->next, "-")) {
2116 tline = tline->next->next;
2117 if (tok_is_(tline, "*")) {
2118 def->nparam_max = INT_MAX;
2119 } else if (!tok_type_(tline, TOK_NUMBER)) {
2120 nasm_error(ERR_NONFATAL,
2121 "`%s' expects a parameter count after `-'", directive);
2122 } else {
2123 def->nparam_max = read_param_count(tline->text);
2124 if (def->nparam_min > def->nparam_max) {
2125 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2126 def->nparam_max = def->nparam_min;
2130 if (tline && tok_is_(tline->next, "+")) {
2131 tline = tline->next;
2132 def->plus = true;
2134 if (tline && tok_type_(tline->next, TOK_ID) &&
2135 !nasm_stricmp(tline->next->text, ".nolist")) {
2136 tline = tline->next;
2137 def->nolist = true;
2141 * Handle default parameters.
2143 if (tline && tline->next) {
2144 def->dlist = tline->next;
2145 tline->next = NULL;
2146 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2147 } else {
2148 def->dlist = NULL;
2149 def->defaults = NULL;
2151 def->expansion = NULL;
2153 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2154 !def->plus)
2155 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2156 "too many default macro parameters");
2158 return true;
2163 * Decode a size directive
2165 static int parse_size(const char *str) {
2166 static const char *size_names[] =
2167 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2168 static const int sizes[] =
2169 { 0, 1, 4, 16, 8, 10, 2, 32 };
2170 return str ? sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1] : 0;
2174 * Process a preprocessor %pragma directive. Currently there are none.
2175 * Gets passed the token list starting with the "preproc" token from
2176 * "%pragma preproc".
2178 static void do_pragma_preproc(Token *tline)
2180 /* Skip to the real stuff */
2181 tline = tline->next;
2182 skip_white_(tline);
2183 if (!tline)
2184 return;
2186 (void)tline; /* Nothing else to do at present */
2190 * find and process preprocessor directive in passed line
2191 * Find out if a line contains a preprocessor directive, and deal
2192 * with it if so.
2194 * If a directive _is_ found, it is the responsibility of this routine
2195 * (and not the caller) to free_tlist() the line.
2197 * @param tline a pointer to the current tokeninzed line linked list
2198 * @param output if this directive generated output
2199 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2202 static int do_directive(Token *tline, char **output)
2204 enum preproc_token i;
2205 int j;
2206 bool err;
2207 int nparam;
2208 bool nolist;
2209 bool casesense;
2210 int k, m;
2211 int offset;
2212 char *p, *pp;
2213 const char *found_path;
2214 const char *mname;
2215 Include *inc;
2216 Context *ctx;
2217 Cond *cond;
2218 MMacro *mmac, **mmhead;
2219 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2220 Line *l;
2221 struct tokenval tokval;
2222 expr *evalresult;
2223 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2224 int64_t count;
2225 size_t len;
2226 int severity;
2228 *output = NULL; /* No output generated */
2229 origline = tline;
2231 skip_white_(tline);
2232 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2233 (tline->text[0] && (tline->text[1] == '%' ||
2234 tline->text[1] == '$' ||
2235 tline->text[1] == '!')))
2236 return NO_DIRECTIVE_FOUND;
2238 i = pp_token_hash(tline->text);
2241 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2242 * since they are known to be buggy at moment, we need to fix them
2243 * in future release (2.09-2.10)
2245 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2246 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2247 tline->text);
2248 return NO_DIRECTIVE_FOUND;
2252 * If we're in a non-emitting branch of a condition construct,
2253 * or walking to the end of an already terminated %rep block,
2254 * we should ignore all directives except for condition
2255 * directives.
2257 if (((istk->conds && !emitting(istk->conds->state)) ||
2258 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2259 return NO_DIRECTIVE_FOUND;
2263 * If we're defining a macro or reading a %rep block, we should
2264 * ignore all directives except for %macro/%imacro (which nest),
2265 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2266 * If we're in a %rep block, another %rep nests, so should be let through.
2268 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2269 i != PP_RMACRO && i != PP_IRMACRO &&
2270 i != PP_ENDMACRO && i != PP_ENDM &&
2271 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2272 return NO_DIRECTIVE_FOUND;
2275 if (defining) {
2276 if (i == PP_MACRO || i == PP_IMACRO ||
2277 i == PP_RMACRO || i == PP_IRMACRO) {
2278 nested_mac_count++;
2279 return NO_DIRECTIVE_FOUND;
2280 } else if (nested_mac_count > 0) {
2281 if (i == PP_ENDMACRO) {
2282 nested_mac_count--;
2283 return NO_DIRECTIVE_FOUND;
2286 if (!defining->name) {
2287 if (i == PP_REP) {
2288 nested_rep_count++;
2289 return NO_DIRECTIVE_FOUND;
2290 } else if (nested_rep_count > 0) {
2291 if (i == PP_ENDREP) {
2292 nested_rep_count--;
2293 return NO_DIRECTIVE_FOUND;
2299 switch (i) {
2300 case PP_INVALID:
2301 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2302 tline->text);
2303 return NO_DIRECTIVE_FOUND; /* didn't get it */
2305 case PP_PRAGMA:
2307 * %pragma namespace options...
2309 * The namespace "preproc" is reserved for the preprocessor;
2310 * all other namespaces generate a [pragma] assembly directive.
2312 * Invalid %pragmas are ignored and may have different
2313 * meaning in future versions of NASM.
2315 tline = tline->next;
2316 skip_white_(tline);
2317 tline = expand_smacro(tline);
2318 if (tok_type_(tline, TOK_ID)) {
2319 if (!nasm_stricmp(tline->text, "preproc")) {
2320 /* Preprocessor pragma */
2321 do_pragma_preproc(tline);
2322 } else {
2323 /* Build the assembler directive */
2324 t = new_Token(NULL, TOK_OTHER, "[", 1);
2325 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2326 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2327 tline = t;
2328 for (t = tline; t->next; t = t->next)
2330 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2331 /* true here can be revisited in the future */
2332 *output = detoken(tline, true);
2335 free_tlist(origline);
2336 return DIRECTIVE_FOUND;
2338 case PP_STACKSIZE:
2339 /* Directive to tell NASM what the default stack size is. The
2340 * default is for a 16-bit stack, and this can be overriden with
2341 * %stacksize large.
2343 tline = tline->next;
2344 if (tline && tline->type == TOK_WHITESPACE)
2345 tline = tline->next;
2346 if (!tline || tline->type != TOK_ID) {
2347 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2348 free_tlist(origline);
2349 return DIRECTIVE_FOUND;
2351 if (nasm_stricmp(tline->text, "flat") == 0) {
2352 /* All subsequent ARG directives are for a 32-bit stack */
2353 StackSize = 4;
2354 StackPointer = "ebp";
2355 ArgOffset = 8;
2356 LocalOffset = 0;
2357 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2358 /* All subsequent ARG directives are for a 64-bit stack */
2359 StackSize = 8;
2360 StackPointer = "rbp";
2361 ArgOffset = 16;
2362 LocalOffset = 0;
2363 } else if (nasm_stricmp(tline->text, "large") == 0) {
2364 /* All subsequent ARG directives are for a 16-bit stack,
2365 * far function call.
2367 StackSize = 2;
2368 StackPointer = "bp";
2369 ArgOffset = 4;
2370 LocalOffset = 0;
2371 } else if (nasm_stricmp(tline->text, "small") == 0) {
2372 /* All subsequent ARG directives are for a 16-bit stack,
2373 * far function call. We don't support near functions.
2375 StackSize = 2;
2376 StackPointer = "bp";
2377 ArgOffset = 6;
2378 LocalOffset = 0;
2379 } else {
2380 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2381 free_tlist(origline);
2382 return DIRECTIVE_FOUND;
2384 free_tlist(origline);
2385 return DIRECTIVE_FOUND;
2387 case PP_ARG:
2388 /* TASM like ARG directive to define arguments to functions, in
2389 * the following form:
2391 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2393 offset = ArgOffset;
2394 do {
2395 char *arg, directive[256];
2396 int size = StackSize;
2398 /* Find the argument name */
2399 tline = tline->next;
2400 if (tline && tline->type == TOK_WHITESPACE)
2401 tline = tline->next;
2402 if (!tline || tline->type != TOK_ID) {
2403 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2404 free_tlist(origline);
2405 return DIRECTIVE_FOUND;
2407 arg = tline->text;
2409 /* Find the argument size type */
2410 tline = tline->next;
2411 if (!tline || tline->type != TOK_OTHER
2412 || tline->text[0] != ':') {
2413 nasm_error(ERR_NONFATAL,
2414 "Syntax error processing `%%arg' directive");
2415 free_tlist(origline);
2416 return DIRECTIVE_FOUND;
2418 tline = tline->next;
2419 if (!tline || tline->type != TOK_ID) {
2420 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2421 free_tlist(origline);
2422 return DIRECTIVE_FOUND;
2425 /* Allow macro expansion of type parameter */
2426 tt = tokenize(tline->text);
2427 tt = expand_smacro(tt);
2428 size = parse_size(tt->text);
2429 if (!size) {
2430 nasm_error(ERR_NONFATAL,
2431 "Invalid size type for `%%arg' missing directive");
2432 free_tlist(tt);
2433 free_tlist(origline);
2434 return DIRECTIVE_FOUND;
2436 free_tlist(tt);
2438 /* Round up to even stack slots */
2439 size = ALIGN(size, StackSize);
2441 /* Now define the macro for the argument */
2442 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2443 arg, StackPointer, offset);
2444 do_directive(tokenize(directive), output);
2445 offset += size;
2447 /* Move to the next argument in the list */
2448 tline = tline->next;
2449 if (tline && tline->type == TOK_WHITESPACE)
2450 tline = tline->next;
2451 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2452 ArgOffset = offset;
2453 free_tlist(origline);
2454 return DIRECTIVE_FOUND;
2456 case PP_LOCAL:
2457 /* TASM like LOCAL directive to define local variables for a
2458 * function, in the following form:
2460 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2462 * The '= LocalSize' at the end is ignored by NASM, but is
2463 * required by TASM to define the local parameter size (and used
2464 * by the TASM macro package).
2466 offset = LocalOffset;
2467 do {
2468 char *local, directive[256];
2469 int size = StackSize;
2471 /* Find the argument name */
2472 tline = tline->next;
2473 if (tline && tline->type == TOK_WHITESPACE)
2474 tline = tline->next;
2475 if (!tline || tline->type != TOK_ID) {
2476 nasm_error(ERR_NONFATAL,
2477 "`%%local' missing argument parameter");
2478 free_tlist(origline);
2479 return DIRECTIVE_FOUND;
2481 local = tline->text;
2483 /* Find the argument size type */
2484 tline = tline->next;
2485 if (!tline || tline->type != TOK_OTHER
2486 || tline->text[0] != ':') {
2487 nasm_error(ERR_NONFATAL,
2488 "Syntax error processing `%%local' directive");
2489 free_tlist(origline);
2490 return DIRECTIVE_FOUND;
2492 tline = tline->next;
2493 if (!tline || tline->type != TOK_ID) {
2494 nasm_error(ERR_NONFATAL,
2495 "`%%local' missing size type parameter");
2496 free_tlist(origline);
2497 return DIRECTIVE_FOUND;
2500 /* Allow macro expansion of type parameter */
2501 tt = tokenize(tline->text);
2502 tt = expand_smacro(tt);
2503 size = parse_size(tt->text);
2504 if (!size) {
2505 nasm_error(ERR_NONFATAL,
2506 "Invalid size type for `%%local' missing directive");
2507 free_tlist(tt);
2508 free_tlist(origline);
2509 return DIRECTIVE_FOUND;
2511 free_tlist(tt);
2513 /* Round up to even stack slots */
2514 size = ALIGN(size, StackSize);
2516 offset += size; /* Negative offset, increment before */
2518 /* Now define the macro for the argument */
2519 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2520 local, StackPointer, offset);
2521 do_directive(tokenize(directive), output);
2523 /* Now define the assign to setup the enter_c macro correctly */
2524 snprintf(directive, sizeof(directive),
2525 "%%assign %%$localsize %%$localsize+%d", size);
2526 do_directive(tokenize(directive), output);
2528 /* Move to the next argument in the list */
2529 tline = tline->next;
2530 if (tline && tline->type == TOK_WHITESPACE)
2531 tline = tline->next;
2532 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2533 LocalOffset = offset;
2534 free_tlist(origline);
2535 return DIRECTIVE_FOUND;
2537 case PP_CLEAR:
2538 if (tline->next)
2539 nasm_error(ERR_WARNING|ERR_PASS1,
2540 "trailing garbage after `%%clear' ignored");
2541 free_macros();
2542 init_macros();
2543 free_tlist(origline);
2544 return DIRECTIVE_FOUND;
2546 case PP_DEPEND:
2547 t = tline->next = expand_smacro(tline->next);
2548 skip_white_(t);
2549 if (!t || (t->type != TOK_STRING &&
2550 t->type != TOK_INTERNAL_STRING)) {
2551 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2552 free_tlist(origline);
2553 return DIRECTIVE_FOUND; /* but we did _something_ */
2555 if (t->next)
2556 nasm_error(ERR_WARNING|ERR_PASS1,
2557 "trailing garbage after `%%depend' ignored");
2558 p = t->text;
2559 if (t->type != TOK_INTERNAL_STRING)
2560 nasm_unquote_cstr(p, i);
2561 strlist_add_string(deplist, p);
2562 free_tlist(origline);
2563 return DIRECTIVE_FOUND;
2565 case PP_INCLUDE:
2566 t = tline->next = expand_smacro(tline->next);
2567 skip_white_(t);
2569 if (!t || (t->type != TOK_STRING &&
2570 t->type != TOK_INTERNAL_STRING)) {
2571 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2572 free_tlist(origline);
2573 return DIRECTIVE_FOUND; /* but we did _something_ */
2575 if (t->next)
2576 nasm_error(ERR_WARNING|ERR_PASS1,
2577 "trailing garbage after `%%include' ignored");
2578 p = t->text;
2579 if (t->type != TOK_INTERNAL_STRING)
2580 nasm_unquote_cstr(p, i);
2581 inc = nasm_malloc(sizeof(Include));
2582 inc->next = istk;
2583 inc->conds = NULL;
2584 found_path = NULL;
2585 inc->fp = inc_fopen(p, deplist, &found_path,
2586 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2587 if (!inc->fp) {
2588 /* -MG given but file not found */
2589 nasm_free(inc);
2590 } else {
2591 inc->fname = src_set_fname(found_path ? found_path : p);
2592 inc->lineno = src_set_linnum(0);
2593 inc->lineinc = 1;
2594 inc->expansion = NULL;
2595 inc->mstk = NULL;
2596 istk = inc;
2597 lfmt->uplevel(LIST_INCLUDE);
2599 free_tlist(origline);
2600 return DIRECTIVE_FOUND;
2602 case PP_USE:
2604 static macros_t *use_pkg;
2605 const char *pkg_macro = NULL;
2607 tline = tline->next;
2608 skip_white_(tline);
2609 tline = expand_id(tline);
2611 if (!tline || (tline->type != TOK_STRING &&
2612 tline->type != TOK_INTERNAL_STRING &&
2613 tline->type != TOK_ID)) {
2614 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2615 free_tlist(origline);
2616 return DIRECTIVE_FOUND; /* but we did _something_ */
2618 if (tline->next)
2619 nasm_error(ERR_WARNING|ERR_PASS1,
2620 "trailing garbage after `%%use' ignored");
2621 if (tline->type == TOK_STRING)
2622 nasm_unquote_cstr(tline->text, i);
2623 use_pkg = nasm_stdmac_find_package(tline->text);
2624 if (!use_pkg)
2625 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2626 else
2627 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2628 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2629 /* Not already included, go ahead and include it */
2630 stdmacpos = use_pkg;
2632 free_tlist(origline);
2633 return DIRECTIVE_FOUND;
2635 case PP_PUSH:
2636 case PP_REPL:
2637 case PP_POP:
2638 tline = tline->next;
2639 skip_white_(tline);
2640 tline = expand_id(tline);
2641 if (tline) {
2642 if (!tok_type_(tline, TOK_ID)) {
2643 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2644 pp_directives[i]);
2645 free_tlist(origline);
2646 return DIRECTIVE_FOUND; /* but we did _something_ */
2648 if (tline->next)
2649 nasm_error(ERR_WARNING|ERR_PASS1,
2650 "trailing garbage after `%s' ignored",
2651 pp_directives[i]);
2652 p = nasm_strdup(tline->text);
2653 } else {
2654 p = NULL; /* Anonymous */
2657 if (i == PP_PUSH) {
2658 ctx = nasm_malloc(sizeof(Context));
2659 ctx->next = cstk;
2660 hash_init(&ctx->localmac, HASH_SMALL);
2661 ctx->name = p;
2662 ctx->number = unique++;
2663 cstk = ctx;
2664 } else {
2665 /* %pop or %repl */
2666 if (!cstk) {
2667 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2668 pp_directives[i]);
2669 } else if (i == PP_POP) {
2670 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2671 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2672 "expected %s",
2673 cstk->name ? cstk->name : "anonymous", p);
2674 else
2675 ctx_pop();
2676 } else {
2677 /* i == PP_REPL */
2678 nasm_free(cstk->name);
2679 cstk->name = p;
2680 p = NULL;
2682 nasm_free(p);
2684 free_tlist(origline);
2685 return DIRECTIVE_FOUND;
2686 case PP_FATAL:
2687 severity = ERR_FATAL;
2688 goto issue_error;
2689 case PP_ERROR:
2690 severity = ERR_NONFATAL;
2691 goto issue_error;
2692 case PP_WARNING:
2693 severity = ERR_WARNING|ERR_WARN_USER;
2694 goto issue_error;
2696 issue_error:
2698 /* Only error out if this is the final pass */
2699 if (pass != 2 && i != PP_FATAL)
2700 return DIRECTIVE_FOUND;
2702 tline->next = expand_smacro(tline->next);
2703 tline = tline->next;
2704 skip_white_(tline);
2705 t = tline ? tline->next : NULL;
2706 skip_white_(t);
2707 if (tok_type_(tline, TOK_STRING) && !t) {
2708 /* The line contains only a quoted string */
2709 p = tline->text;
2710 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2711 nasm_error(severity, "%s", p);
2712 } else {
2713 /* Not a quoted string, or more than a quoted string */
2714 p = detoken(tline, false);
2715 nasm_error(severity, "%s", p);
2716 nasm_free(p);
2718 free_tlist(origline);
2719 return DIRECTIVE_FOUND;
2722 CASE_PP_IF:
2723 if (istk->conds && !emitting(istk->conds->state))
2724 j = COND_NEVER;
2725 else {
2726 j = if_condition(tline->next, i);
2727 tline->next = NULL; /* it got freed */
2728 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2730 cond = nasm_malloc(sizeof(Cond));
2731 cond->next = istk->conds;
2732 cond->state = j;
2733 istk->conds = cond;
2734 if(istk->mstk)
2735 istk->mstk->condcnt ++;
2736 free_tlist(origline);
2737 return DIRECTIVE_FOUND;
2739 CASE_PP_ELIF:
2740 if (!istk->conds)
2741 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2742 switch(istk->conds->state) {
2743 case COND_IF_TRUE:
2744 istk->conds->state = COND_DONE;
2745 break;
2747 case COND_DONE:
2748 case COND_NEVER:
2749 break;
2751 case COND_ELSE_TRUE:
2752 case COND_ELSE_FALSE:
2753 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2754 "`%%elif' after `%%else' ignored");
2755 istk->conds->state = COND_NEVER;
2756 break;
2758 case COND_IF_FALSE:
2760 * IMPORTANT: In the case of %if, we will already have
2761 * called expand_mmac_params(); however, if we're
2762 * processing an %elif we must have been in a
2763 * non-emitting mode, which would have inhibited
2764 * the normal invocation of expand_mmac_params().
2765 * Therefore, we have to do it explicitly here.
2767 j = if_condition(expand_mmac_params(tline->next), i);
2768 tline->next = NULL; /* it got freed */
2769 istk->conds->state =
2770 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2771 break;
2773 free_tlist(origline);
2774 return DIRECTIVE_FOUND;
2776 case PP_ELSE:
2777 if (tline->next)
2778 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2779 "trailing garbage after `%%else' ignored");
2780 if (!istk->conds)
2781 nasm_fatal("`%%else: no matching `%%if'");
2782 switch(istk->conds->state) {
2783 case COND_IF_TRUE:
2784 case COND_DONE:
2785 istk->conds->state = COND_ELSE_FALSE;
2786 break;
2788 case COND_NEVER:
2789 break;
2791 case COND_IF_FALSE:
2792 istk->conds->state = COND_ELSE_TRUE;
2793 break;
2795 case COND_ELSE_TRUE:
2796 case COND_ELSE_FALSE:
2797 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2798 "`%%else' after `%%else' ignored.");
2799 istk->conds->state = COND_NEVER;
2800 break;
2802 free_tlist(origline);
2803 return DIRECTIVE_FOUND;
2805 case PP_ENDIF:
2806 if (tline->next)
2807 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2808 "trailing garbage after `%%endif' ignored");
2809 if (!istk->conds)
2810 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2811 cond = istk->conds;
2812 istk->conds = cond->next;
2813 nasm_free(cond);
2814 if(istk->mstk)
2815 istk->mstk->condcnt --;
2816 free_tlist(origline);
2817 return DIRECTIVE_FOUND;
2819 case PP_RMACRO:
2820 case PP_IRMACRO:
2821 case PP_MACRO:
2822 case PP_IMACRO:
2823 if (defining) {
2824 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2825 pp_directives[i]);
2826 return DIRECTIVE_FOUND;
2828 defining = nasm_zalloc(sizeof(MMacro));
2829 defining->max_depth = ((i == PP_RMACRO) || (i == PP_IRMACRO))
2830 ? nasm_limit[LIMIT_MACROS] : 0;
2831 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2832 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2833 nasm_free(defining);
2834 defining = NULL;
2835 return DIRECTIVE_FOUND;
2838 src_get(&defining->xline, &defining->fname);
2840 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2841 while (mmac) {
2842 if (!strcmp(mmac->name, defining->name) &&
2843 (mmac->nparam_min <= defining->nparam_max
2844 || defining->plus)
2845 && (defining->nparam_min <= mmac->nparam_max
2846 || mmac->plus)) {
2847 nasm_error(ERR_WARNING|ERR_PASS1,
2848 "redefining multi-line macro `%s'", defining->name);
2849 return DIRECTIVE_FOUND;
2851 mmac = mmac->next;
2853 free_tlist(origline);
2854 return DIRECTIVE_FOUND;
2856 case PP_ENDM:
2857 case PP_ENDMACRO:
2858 if (! (defining && defining->name)) {
2859 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2860 return DIRECTIVE_FOUND;
2862 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2863 defining->next = *mmhead;
2864 *mmhead = defining;
2865 defining = NULL;
2866 free_tlist(origline);
2867 return DIRECTIVE_FOUND;
2869 case PP_EXITMACRO:
2871 * We must search along istk->expansion until we hit a
2872 * macro-end marker for a macro with a name. Then we
2873 * bypass all lines between exitmacro and endmacro.
2875 list_for_each(l, istk->expansion)
2876 if (l->finishes && l->finishes->name)
2877 break;
2879 if (l) {
2881 * Remove all conditional entries relative to this
2882 * macro invocation. (safe to do in this context)
2884 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2885 cond = istk->conds;
2886 istk->conds = cond->next;
2887 nasm_free(cond);
2889 istk->expansion = l;
2890 } else {
2891 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2893 free_tlist(origline);
2894 return DIRECTIVE_FOUND;
2896 case PP_UNMACRO:
2897 case PP_UNIMACRO:
2899 MMacro **mmac_p;
2900 MMacro spec;
2902 spec.casesense = (i == PP_UNMACRO);
2903 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2904 return DIRECTIVE_FOUND;
2906 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2907 while (mmac_p && *mmac_p) {
2908 mmac = *mmac_p;
2909 if (mmac->casesense == spec.casesense &&
2910 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2911 mmac->nparam_min == spec.nparam_min &&
2912 mmac->nparam_max == spec.nparam_max &&
2913 mmac->plus == spec.plus) {
2914 *mmac_p = mmac->next;
2915 free_mmacro(mmac);
2916 } else {
2917 mmac_p = &mmac->next;
2920 free_tlist(origline);
2921 free_tlist(spec.dlist);
2922 return DIRECTIVE_FOUND;
2925 case PP_ROTATE:
2926 if (tline->next && tline->next->type == TOK_WHITESPACE)
2927 tline = tline->next;
2928 if (!tline->next) {
2929 free_tlist(origline);
2930 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2931 return DIRECTIVE_FOUND;
2933 t = expand_smacro(tline->next);
2934 tline->next = NULL;
2935 free_tlist(origline);
2936 tline = t;
2937 tptr = &t;
2938 tokval.t_type = TOKEN_INVALID;
2939 evalresult =
2940 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2941 free_tlist(tline);
2942 if (!evalresult)
2943 return DIRECTIVE_FOUND;
2944 if (tokval.t_type)
2945 nasm_error(ERR_WARNING|ERR_PASS1,
2946 "trailing garbage after expression ignored");
2947 if (!is_simple(evalresult)) {
2948 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2949 return DIRECTIVE_FOUND;
2951 mmac = istk->mstk;
2952 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2953 mmac = mmac->next_active;
2954 if (!mmac) {
2955 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2956 } else if (mmac->nparam == 0) {
2957 nasm_error(ERR_NONFATAL,
2958 "`%%rotate' invoked within macro without parameters");
2959 } else {
2960 int rotate = mmac->rotate + reloc_value(evalresult);
2962 rotate %= (int)mmac->nparam;
2963 if (rotate < 0)
2964 rotate += mmac->nparam;
2966 mmac->rotate = rotate;
2968 return DIRECTIVE_FOUND;
2970 case PP_REP:
2971 nolist = false;
2972 do {
2973 tline = tline->next;
2974 } while (tok_type_(tline, TOK_WHITESPACE));
2976 if (tok_type_(tline, TOK_ID) &&
2977 nasm_stricmp(tline->text, ".nolist") == 0) {
2978 nolist = true;
2979 do {
2980 tline = tline->next;
2981 } while (tok_type_(tline, TOK_WHITESPACE));
2984 if (tline) {
2985 t = expand_smacro(tline);
2986 tptr = &t;
2987 tokval.t_type = TOKEN_INVALID;
2988 evalresult =
2989 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2990 if (!evalresult) {
2991 free_tlist(origline);
2992 return DIRECTIVE_FOUND;
2994 if (tokval.t_type)
2995 nasm_error(ERR_WARNING|ERR_PASS1,
2996 "trailing garbage after expression ignored");
2997 if (!is_simple(evalresult)) {
2998 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2999 return DIRECTIVE_FOUND;
3001 count = reloc_value(evalresult);
3002 if (count > nasm_limit[LIMIT_REP]) {
3003 nasm_error(ERR_NONFATAL,
3004 "`%%rep' count %"PRId64" exceeds limit (currently %"PRId64")",
3005 count, nasm_limit[LIMIT_REP]);
3006 count = 0;
3007 } else if (count < 0) {
3008 nasm_error(ERR_WARNING|ERR_PASS2|ERR_WARN_NEG_REP,
3009 "negative `%%rep' count: %"PRId64, count);
3010 count = 0;
3011 } else {
3012 count++;
3014 } else {
3015 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3016 count = 0;
3018 free_tlist(origline);
3020 tmp_defining = defining;
3021 defining = nasm_malloc(sizeof(MMacro));
3022 defining->prev = NULL;
3023 defining->name = NULL; /* flags this macro as a %rep block */
3024 defining->casesense = false;
3025 defining->plus = false;
3026 defining->nolist = nolist;
3027 defining->in_progress = count;
3028 defining->max_depth = 0;
3029 defining->nparam_min = defining->nparam_max = 0;
3030 defining->defaults = NULL;
3031 defining->dlist = NULL;
3032 defining->expansion = NULL;
3033 defining->next_active = istk->mstk;
3034 defining->rep_nest = tmp_defining;
3035 return DIRECTIVE_FOUND;
3037 case PP_ENDREP:
3038 if (!defining || defining->name) {
3039 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3040 return DIRECTIVE_FOUND;
3044 * Now we have a "macro" defined - although it has no name
3045 * and we won't be entering it in the hash tables - we must
3046 * push a macro-end marker for it on to istk->expansion.
3047 * After that, it will take care of propagating itself (a
3048 * macro-end marker line for a macro which is really a %rep
3049 * block will cause the macro to be re-expanded, complete
3050 * with another macro-end marker to ensure the process
3051 * continues) until the whole expansion is forcibly removed
3052 * from istk->expansion by a %exitrep.
3054 l = nasm_malloc(sizeof(Line));
3055 l->next = istk->expansion;
3056 l->finishes = defining;
3057 l->first = NULL;
3058 istk->expansion = l;
3060 istk->mstk = defining;
3062 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3063 tmp_defining = defining;
3064 defining = defining->rep_nest;
3065 free_tlist(origline);
3066 return DIRECTIVE_FOUND;
3068 case PP_EXITREP:
3070 * We must search along istk->expansion until we hit a
3071 * macro-end marker for a macro with no name. Then we set
3072 * its `in_progress' flag to 0.
3074 list_for_each(l, istk->expansion)
3075 if (l->finishes && !l->finishes->name)
3076 break;
3078 if (l)
3079 l->finishes->in_progress = 1;
3080 else
3081 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3082 free_tlist(origline);
3083 return DIRECTIVE_FOUND;
3085 case PP_XDEFINE:
3086 case PP_IXDEFINE:
3087 case PP_DEFINE:
3088 case PP_IDEFINE:
3089 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3091 tline = tline->next;
3092 skip_white_(tline);
3093 tline = expand_id(tline);
3094 if (!tline || (tline->type != TOK_ID &&
3095 (tline->type != TOK_PREPROC_ID ||
3096 tline->text[1] != '$'))) {
3097 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3098 pp_directives[i]);
3099 free_tlist(origline);
3100 return DIRECTIVE_FOUND;
3103 ctx = get_ctx(tline->text, &mname);
3104 last = tline;
3105 param_start = tline = tline->next;
3106 nparam = 0;
3108 /* Expand the macro definition now for %xdefine and %ixdefine */
3109 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3110 tline = expand_smacro(tline);
3112 if (tok_is_(tline, "(")) {
3114 * This macro has parameters.
3117 tline = tline->next;
3118 while (1) {
3119 skip_white_(tline);
3120 if (!tline) {
3121 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3122 free_tlist(origline);
3123 return DIRECTIVE_FOUND;
3125 if (tline->type != TOK_ID) {
3126 nasm_error(ERR_NONFATAL,
3127 "`%s': parameter identifier expected",
3128 tline->text);
3129 free_tlist(origline);
3130 return DIRECTIVE_FOUND;
3132 tline->type = TOK_SMAC_PARAM + nparam++;
3133 tline = tline->next;
3134 skip_white_(tline);
3135 if (tok_is_(tline, ",")) {
3136 tline = tline->next;
3137 } else {
3138 if (!tok_is_(tline, ")")) {
3139 nasm_error(ERR_NONFATAL,
3140 "`)' expected to terminate macro template");
3141 free_tlist(origline);
3142 return DIRECTIVE_FOUND;
3144 break;
3147 last = tline;
3148 tline = tline->next;
3150 if (tok_type_(tline, TOK_WHITESPACE))
3151 last = tline, tline = tline->next;
3152 macro_start = NULL;
3153 last->next = NULL;
3154 t = tline;
3155 while (t) {
3156 if (t->type == TOK_ID) {
3157 list_for_each(tt, param_start)
3158 if (tt->type >= TOK_SMAC_PARAM &&
3159 !strcmp(tt->text, t->text))
3160 t->type = tt->type;
3162 tt = t->next;
3163 t->next = macro_start;
3164 macro_start = t;
3165 t = tt;
3168 * Good. We now have a macro name, a parameter count, and a
3169 * token list (in reverse order) for an expansion. We ought
3170 * to be OK just to create an SMacro, store it, and let
3171 * free_tlist have the rest of the line (which we have
3172 * carefully re-terminated after chopping off the expansion
3173 * from the end).
3175 define_smacro(ctx, mname, casesense, nparam, macro_start);
3176 free_tlist(origline);
3177 return DIRECTIVE_FOUND;
3179 case PP_UNDEF:
3180 tline = tline->next;
3181 skip_white_(tline);
3182 tline = expand_id(tline);
3183 if (!tline || (tline->type != TOK_ID &&
3184 (tline->type != TOK_PREPROC_ID ||
3185 tline->text[1] != '$'))) {
3186 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3187 free_tlist(origline);
3188 return DIRECTIVE_FOUND;
3190 if (tline->next) {
3191 nasm_error(ERR_WARNING|ERR_PASS1,
3192 "trailing garbage after macro name ignored");
3195 /* Find the context that symbol belongs to */
3196 ctx = get_ctx(tline->text, &mname);
3197 undef_smacro(ctx, mname);
3198 free_tlist(origline);
3199 return DIRECTIVE_FOUND;
3201 case PP_DEFSTR:
3202 case PP_IDEFSTR:
3203 casesense = (i == PP_DEFSTR);
3205 tline = tline->next;
3206 skip_white_(tline);
3207 tline = expand_id(tline);
3208 if (!tline || (tline->type != TOK_ID &&
3209 (tline->type != TOK_PREPROC_ID ||
3210 tline->text[1] != '$'))) {
3211 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3212 pp_directives[i]);
3213 free_tlist(origline);
3214 return DIRECTIVE_FOUND;
3217 ctx = get_ctx(tline->text, &mname);
3218 last = tline;
3219 tline = expand_smacro(tline->next);
3220 last->next = NULL;
3222 while (tok_type_(tline, TOK_WHITESPACE))
3223 tline = delete_Token(tline);
3225 p = detoken(tline, false);
3226 macro_start = nasm_malloc(sizeof(*macro_start));
3227 macro_start->next = NULL;
3228 macro_start->text = nasm_quote(p, strlen(p));
3229 macro_start->type = TOK_STRING;
3230 macro_start->a.mac = NULL;
3231 nasm_free(p);
3234 * We now have a macro name, an implicit parameter count of
3235 * zero, and a string token to use as an expansion. Create
3236 * and store an SMacro.
3238 define_smacro(ctx, mname, casesense, 0, macro_start);
3239 free_tlist(origline);
3240 return DIRECTIVE_FOUND;
3242 case PP_DEFTOK:
3243 case PP_IDEFTOK:
3244 casesense = (i == PP_DEFTOK);
3246 tline = tline->next;
3247 skip_white_(tline);
3248 tline = expand_id(tline);
3249 if (!tline || (tline->type != TOK_ID &&
3250 (tline->type != TOK_PREPROC_ID ||
3251 tline->text[1] != '$'))) {
3252 nasm_error(ERR_NONFATAL,
3253 "`%s' expects a macro identifier as first parameter",
3254 pp_directives[i]);
3255 free_tlist(origline);
3256 return DIRECTIVE_FOUND;
3258 ctx = get_ctx(tline->text, &mname);
3259 last = tline;
3260 tline = expand_smacro(tline->next);
3261 last->next = NULL;
3263 t = tline;
3264 while (tok_type_(t, TOK_WHITESPACE))
3265 t = t->next;
3266 /* t should now point to the string */
3267 if (!tok_type_(t, TOK_STRING)) {
3268 nasm_error(ERR_NONFATAL,
3269 "`%s` requires string as second parameter",
3270 pp_directives[i]);
3271 free_tlist(tline);
3272 free_tlist(origline);
3273 return DIRECTIVE_FOUND;
3277 * Convert the string to a token stream. Note that smacros
3278 * are stored with the token stream reversed, so we have to
3279 * reverse the output of tokenize().
3281 nasm_unquote_cstr(t->text, i);
3282 macro_start = reverse_tokens(tokenize(t->text));
3285 * We now have a macro name, an implicit parameter count of
3286 * zero, and a numeric token to use as an expansion. Create
3287 * and store an SMacro.
3289 define_smacro(ctx, mname, casesense, 0, macro_start);
3290 free_tlist(tline);
3291 free_tlist(origline);
3292 return DIRECTIVE_FOUND;
3294 case PP_PATHSEARCH:
3296 const char *found_path;
3298 casesense = true;
3300 tline = tline->next;
3301 skip_white_(tline);
3302 tline = expand_id(tline);
3303 if (!tline || (tline->type != TOK_ID &&
3304 (tline->type != TOK_PREPROC_ID ||
3305 tline->text[1] != '$'))) {
3306 nasm_error(ERR_NONFATAL,
3307 "`%%pathsearch' expects a macro identifier as first parameter");
3308 free_tlist(origline);
3309 return DIRECTIVE_FOUND;
3311 ctx = get_ctx(tline->text, &mname);
3312 last = tline;
3313 tline = expand_smacro(tline->next);
3314 last->next = NULL;
3316 t = tline;
3317 while (tok_type_(t, TOK_WHITESPACE))
3318 t = t->next;
3320 if (!t || (t->type != TOK_STRING &&
3321 t->type != TOK_INTERNAL_STRING)) {
3322 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3323 free_tlist(tline);
3324 free_tlist(origline);
3325 return DIRECTIVE_FOUND; /* but we did _something_ */
3327 if (t->next)
3328 nasm_error(ERR_WARNING|ERR_PASS1,
3329 "trailing garbage after `%%pathsearch' ignored");
3330 p = t->text;
3331 if (t->type != TOK_INTERNAL_STRING)
3332 nasm_unquote(p, NULL);
3334 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3335 if (!found_path)
3336 found_path = p;
3337 macro_start = nasm_malloc(sizeof(*macro_start));
3338 macro_start->next = NULL;
3339 macro_start->text = nasm_quote(found_path, strlen(found_path));
3340 macro_start->type = TOK_STRING;
3341 macro_start->a.mac = NULL;
3344 * We now have a macro name, an implicit parameter count of
3345 * zero, and a string token to use as an expansion. Create
3346 * and store an SMacro.
3348 define_smacro(ctx, mname, casesense, 0, macro_start);
3349 free_tlist(tline);
3350 free_tlist(origline);
3351 return DIRECTIVE_FOUND;
3354 case PP_STRLEN:
3355 casesense = true;
3357 tline = tline->next;
3358 skip_white_(tline);
3359 tline = expand_id(tline);
3360 if (!tline || (tline->type != TOK_ID &&
3361 (tline->type != TOK_PREPROC_ID ||
3362 tline->text[1] != '$'))) {
3363 nasm_error(ERR_NONFATAL,
3364 "`%%strlen' expects a macro identifier as first parameter");
3365 free_tlist(origline);
3366 return DIRECTIVE_FOUND;
3368 ctx = get_ctx(tline->text, &mname);
3369 last = tline;
3370 tline = expand_smacro(tline->next);
3371 last->next = NULL;
3373 t = tline;
3374 while (tok_type_(t, TOK_WHITESPACE))
3375 t = t->next;
3376 /* t should now point to the string */
3377 if (!tok_type_(t, TOK_STRING)) {
3378 nasm_error(ERR_NONFATAL,
3379 "`%%strlen` requires string as second parameter");
3380 free_tlist(tline);
3381 free_tlist(origline);
3382 return DIRECTIVE_FOUND;
3385 macro_start = nasm_malloc(sizeof(*macro_start));
3386 macro_start->next = NULL;
3387 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3388 macro_start->a.mac = NULL;
3391 * We now have a macro name, an implicit parameter count of
3392 * zero, and a numeric token to use as an expansion. Create
3393 * and store an SMacro.
3395 define_smacro(ctx, mname, casesense, 0, macro_start);
3396 free_tlist(tline);
3397 free_tlist(origline);
3398 return DIRECTIVE_FOUND;
3400 case PP_STRCAT:
3401 casesense = true;
3403 tline = tline->next;
3404 skip_white_(tline);
3405 tline = expand_id(tline);
3406 if (!tline || (tline->type != TOK_ID &&
3407 (tline->type != TOK_PREPROC_ID ||
3408 tline->text[1] != '$'))) {
3409 nasm_error(ERR_NONFATAL,
3410 "`%%strcat' expects a macro identifier as first parameter");
3411 free_tlist(origline);
3412 return DIRECTIVE_FOUND;
3414 ctx = get_ctx(tline->text, &mname);
3415 last = tline;
3416 tline = expand_smacro(tline->next);
3417 last->next = NULL;
3419 len = 0;
3420 list_for_each(t, tline) {
3421 switch (t->type) {
3422 case TOK_WHITESPACE:
3423 break;
3424 case TOK_STRING:
3425 len += t->a.len = nasm_unquote(t->text, NULL);
3426 break;
3427 case TOK_OTHER:
3428 if (!strcmp(t->text, ",")) /* permit comma separators */
3429 break;
3430 /* else fall through */
3431 default:
3432 nasm_error(ERR_NONFATAL,
3433 "non-string passed to `%%strcat' (%d)", t->type);
3434 free_tlist(tline);
3435 free_tlist(origline);
3436 return DIRECTIVE_FOUND;
3440 p = pp = nasm_malloc(len);
3441 list_for_each(t, tline) {
3442 if (t->type == TOK_STRING) {
3443 memcpy(p, t->text, t->a.len);
3444 p += t->a.len;
3449 * We now have a macro name, an implicit parameter count of
3450 * zero, and a numeric token to use as an expansion. Create
3451 * and store an SMacro.
3453 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3454 macro_start->text = nasm_quote(pp, len);
3455 nasm_free(pp);
3456 define_smacro(ctx, mname, casesense, 0, macro_start);
3457 free_tlist(tline);
3458 free_tlist(origline);
3459 return DIRECTIVE_FOUND;
3461 case PP_SUBSTR:
3463 int64_t start, count;
3464 size_t len;
3466 casesense = true;
3468 tline = tline->next;
3469 skip_white_(tline);
3470 tline = expand_id(tline);
3471 if (!tline || (tline->type != TOK_ID &&
3472 (tline->type != TOK_PREPROC_ID ||
3473 tline->text[1] != '$'))) {
3474 nasm_error(ERR_NONFATAL,
3475 "`%%substr' expects a macro identifier as first parameter");
3476 free_tlist(origline);
3477 return DIRECTIVE_FOUND;
3479 ctx = get_ctx(tline->text, &mname);
3480 last = tline;
3481 tline = expand_smacro(tline->next);
3482 last->next = NULL;
3484 if (tline) /* skip expanded id */
3485 t = tline->next;
3486 while (tok_type_(t, TOK_WHITESPACE))
3487 t = t->next;
3489 /* t should now point to the string */
3490 if (!tok_type_(t, TOK_STRING)) {
3491 nasm_error(ERR_NONFATAL,
3492 "`%%substr` requires string as second parameter");
3493 free_tlist(tline);
3494 free_tlist(origline);
3495 return DIRECTIVE_FOUND;
3498 tt = t->next;
3499 tptr = &tt;
3500 tokval.t_type = TOKEN_INVALID;
3501 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3502 if (!evalresult) {
3503 free_tlist(tline);
3504 free_tlist(origline);
3505 return DIRECTIVE_FOUND;
3506 } else if (!is_simple(evalresult)) {
3507 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3508 free_tlist(tline);
3509 free_tlist(origline);
3510 return DIRECTIVE_FOUND;
3512 start = evalresult->value - 1;
3514 while (tok_type_(tt, TOK_WHITESPACE))
3515 tt = tt->next;
3516 if (!tt) {
3517 count = 1; /* Backwards compatibility: one character */
3518 } else {
3519 tokval.t_type = TOKEN_INVALID;
3520 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3521 if (!evalresult) {
3522 free_tlist(tline);
3523 free_tlist(origline);
3524 return DIRECTIVE_FOUND;
3525 } else if (!is_simple(evalresult)) {
3526 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3527 free_tlist(tline);
3528 free_tlist(origline);
3529 return DIRECTIVE_FOUND;
3531 count = evalresult->value;
3534 len = nasm_unquote(t->text, NULL);
3536 /* make start and count being in range */
3537 if (start < 0)
3538 start = 0;
3539 if (count < 0)
3540 count = len + count + 1 - start;
3541 if (start + count > (int64_t)len)
3542 count = len - start;
3543 if (!len || count < 0 || start >=(int64_t)len)
3544 start = -1, count = 0; /* empty string */
3546 macro_start = nasm_malloc(sizeof(*macro_start));
3547 macro_start->next = NULL;
3548 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3549 macro_start->type = TOK_STRING;
3550 macro_start->a.mac = NULL;
3553 * We now have a macro name, an implicit parameter count of
3554 * zero, and a numeric token to use as an expansion. Create
3555 * and store an SMacro.
3557 define_smacro(ctx, mname, casesense, 0, macro_start);
3558 free_tlist(tline);
3559 free_tlist(origline);
3560 return DIRECTIVE_FOUND;
3563 case PP_ASSIGN:
3564 case PP_IASSIGN:
3565 casesense = (i == PP_ASSIGN);
3567 tline = tline->next;
3568 skip_white_(tline);
3569 tline = expand_id(tline);
3570 if (!tline || (tline->type != TOK_ID &&
3571 (tline->type != TOK_PREPROC_ID ||
3572 tline->text[1] != '$'))) {
3573 nasm_error(ERR_NONFATAL,
3574 "`%%%sassign' expects a macro identifier",
3575 (i == PP_IASSIGN ? "i" : ""));
3576 free_tlist(origline);
3577 return DIRECTIVE_FOUND;
3579 ctx = get_ctx(tline->text, &mname);
3580 last = tline;
3581 tline = expand_smacro(tline->next);
3582 last->next = NULL;
3584 t = tline;
3585 tptr = &t;
3586 tokval.t_type = TOKEN_INVALID;
3587 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3588 free_tlist(tline);
3589 if (!evalresult) {
3590 free_tlist(origline);
3591 return DIRECTIVE_FOUND;
3594 if (tokval.t_type)
3595 nasm_error(ERR_WARNING|ERR_PASS1,
3596 "trailing garbage after expression ignored");
3598 if (!is_simple(evalresult)) {
3599 nasm_error(ERR_NONFATAL,
3600 "non-constant value given to `%%%sassign'",
3601 (i == PP_IASSIGN ? "i" : ""));
3602 free_tlist(origline);
3603 return DIRECTIVE_FOUND;
3606 macro_start = nasm_malloc(sizeof(*macro_start));
3607 macro_start->next = NULL;
3608 make_tok_num(macro_start, reloc_value(evalresult));
3609 macro_start->a.mac = NULL;
3612 * We now have a macro name, an implicit parameter count of
3613 * zero, and a numeric token to use as an expansion. Create
3614 * and store an SMacro.
3616 define_smacro(ctx, mname, casesense, 0, macro_start);
3617 free_tlist(origline);
3618 return DIRECTIVE_FOUND;
3620 case PP_LINE:
3622 * Syntax is `%line nnn[+mmm] [filename]'
3624 tline = tline->next;
3625 skip_white_(tline);
3626 if (!tok_type_(tline, TOK_NUMBER)) {
3627 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3628 free_tlist(origline);
3629 return DIRECTIVE_FOUND;
3631 k = readnum(tline->text, &err);
3632 m = 1;
3633 tline = tline->next;
3634 if (tok_is_(tline, "+")) {
3635 tline = tline->next;
3636 if (!tok_type_(tline, TOK_NUMBER)) {
3637 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3638 free_tlist(origline);
3639 return DIRECTIVE_FOUND;
3641 m = readnum(tline->text, &err);
3642 tline = tline->next;
3644 skip_white_(tline);
3645 src_set_linnum(k);
3646 istk->lineinc = m;
3647 if (tline) {
3648 char *fname = detoken(tline, false);
3649 src_set_fname(fname);
3650 nasm_free(fname);
3652 free_tlist(origline);
3653 return DIRECTIVE_FOUND;
3655 default:
3656 nasm_error(ERR_FATAL,
3657 "preprocessor directive `%s' not yet implemented",
3658 pp_directives[i]);
3659 return DIRECTIVE_FOUND;
3664 * Ensure that a macro parameter contains a condition code and
3665 * nothing else. Return the condition code index if so, or -1
3666 * otherwise.
3668 static int find_cc(Token * t)
3670 Token *tt;
3672 if (!t)
3673 return -1; /* Probably a %+ without a space */
3675 skip_white_(t);
3676 if (!t)
3677 return -1;
3678 if (t->type != TOK_ID)
3679 return -1;
3680 tt = t->next;
3681 skip_white_(tt);
3682 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3683 return -1;
3685 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3689 * This routines walks over tokens strem and hadnles tokens
3690 * pasting, if @handle_explicit passed then explicit pasting
3691 * term is handled, otherwise -- implicit pastings only.
3693 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3694 size_t mnum, bool handle_explicit)
3696 Token *tok, *next, **prev_next, **prev_nonspace;
3697 bool pasted = false;
3698 char *buf, *p;
3699 size_t len, i;
3702 * The last token before pasting. We need it
3703 * to be able to connect new handled tokens.
3704 * In other words if there were a tokens stream
3706 * A -> B -> C -> D
3708 * and we've joined tokens B and C, the resulting
3709 * stream should be
3711 * A -> BC -> D
3713 tok = *head;
3714 prev_next = NULL;
3716 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3717 prev_nonspace = head;
3718 else
3719 prev_nonspace = NULL;
3721 while (tok && (next = tok->next)) {
3723 switch (tok->type) {
3724 case TOK_WHITESPACE:
3725 /* Zap redundant whitespaces */
3726 while (tok_type_(next, TOK_WHITESPACE))
3727 next = delete_Token(next);
3728 tok->next = next;
3729 break;
3731 case TOK_PASTE:
3732 /* Explicit pasting */
3733 if (!handle_explicit)
3734 break;
3735 next = delete_Token(tok);
3737 while (tok_type_(next, TOK_WHITESPACE))
3738 next = delete_Token(next);
3740 if (!pasted)
3741 pasted = true;
3743 /* Left pasting token is start of line */
3744 if (!prev_nonspace)
3745 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3748 * No ending token, this might happen in two
3749 * cases
3751 * 1) There indeed no right token at all
3752 * 2) There is a bare "%define ID" statement,
3753 * and @ID does expand to whitespace.
3755 * So technically we need to do a grammar analysis
3756 * in another stage of parsing, but for now lets don't
3757 * change the behaviour people used to. Simply allow
3758 * whitespace after paste token.
3760 if (!next) {
3762 * Zap ending space tokens and that's all.
3764 tok = (*prev_nonspace)->next;
3765 while (tok_type_(tok, TOK_WHITESPACE))
3766 tok = delete_Token(tok);
3767 tok = *prev_nonspace;
3768 tok->next = NULL;
3769 break;
3772 tok = *prev_nonspace;
3773 while (tok_type_(tok, TOK_WHITESPACE))
3774 tok = delete_Token(tok);
3775 len = strlen(tok->text);
3776 len += strlen(next->text);
3778 p = buf = nasm_malloc(len + 1);
3779 strcpy(p, tok->text);
3780 p = strchr(p, '\0');
3781 strcpy(p, next->text);
3783 delete_Token(tok);
3785 tok = tokenize(buf);
3786 nasm_free(buf);
3788 *prev_nonspace = tok;
3789 while (tok && tok->next)
3790 tok = tok->next;
3792 tok->next = delete_Token(next);
3794 /* Restart from pasted tokens head */
3795 tok = *prev_nonspace;
3796 break;
3798 default:
3799 /* implicit pasting */
3800 for (i = 0; i < mnum; i++) {
3801 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3802 continue;
3804 len = 0;
3805 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3806 len += strlen(next->text);
3807 next = next->next;
3810 /* No match or no text to process */
3811 if (tok == next || len == 0)
3812 break;
3814 len += strlen(tok->text);
3815 p = buf = nasm_malloc(len + 1);
3817 strcpy(p, tok->text);
3818 p = strchr(p, '\0');
3819 tok = delete_Token(tok);
3821 while (tok != next) {
3822 if (PP_CONCAT_MATCH(tok, m[i].mask_tail)) {
3823 strcpy(p, tok->text);
3824 p = strchr(p, '\0');
3826 tok = delete_Token(tok);
3829 tok = tokenize(buf);
3830 nasm_free(buf);
3832 if (prev_next)
3833 *prev_next = tok;
3834 else
3835 *head = tok;
3838 * Connect pasted into original stream,
3839 * ie A -> new-tokens -> B
3841 while (tok && tok->next)
3842 tok = tok->next;
3843 tok->next = next;
3845 if (!pasted)
3846 pasted = true;
3848 /* Restart from pasted tokens head */
3849 tok = prev_next ? *prev_next : *head;
3852 break;
3855 prev_next = &tok->next;
3857 if (tok->next &&
3858 !tok_type_(tok->next, TOK_WHITESPACE) &&
3859 !tok_type_(tok->next, TOK_PASTE))
3860 prev_nonspace = prev_next;
3862 tok = tok->next;
3865 return pasted;
3869 * expands to a list of tokens from %{x:y}
3871 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3873 Token *t = tline, **tt, *tm, *head;
3874 char *pos;
3875 int fst, lst, j, i;
3877 pos = strchr(tline->text, ':');
3878 nasm_assert(pos);
3880 lst = atoi(pos + 1);
3881 fst = atoi(tline->text + 1);
3884 * only macros params are accounted so
3885 * if someone passes %0 -- we reject such
3886 * value(s)
3888 if (lst == 0 || fst == 0)
3889 goto err;
3891 /* the values should be sane */
3892 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3893 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3894 goto err;
3896 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3897 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3899 /* counted from zero */
3900 fst--, lst--;
3903 * It will be at least one token. Note we
3904 * need to scan params until separator, otherwise
3905 * only first token will be passed.
3907 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3908 if (!tm)
3909 goto err;
3910 head = new_Token(NULL, tm->type, tm->text, 0);
3911 tt = &head->next, tm = tm->next;
3912 while (tok_isnt_(tm, ",")) {
3913 t = new_Token(NULL, tm->type, tm->text, 0);
3914 *tt = t, tt = &t->next, tm = tm->next;
3917 if (fst < lst) {
3918 for (i = fst + 1; i <= lst; i++) {
3919 t = new_Token(NULL, TOK_OTHER, ",", 0);
3920 *tt = t, tt = &t->next;
3921 j = (i + mac->rotate) % mac->nparam;
3922 tm = mac->params[j];
3923 while (tok_isnt_(tm, ",")) {
3924 t = new_Token(NULL, tm->type, tm->text, 0);
3925 *tt = t, tt = &t->next, tm = tm->next;
3928 } else {
3929 for (i = fst - 1; i >= lst; i--) {
3930 t = new_Token(NULL, TOK_OTHER, ",", 0);
3931 *tt = t, tt = &t->next;
3932 j = (i + mac->rotate) % mac->nparam;
3933 tm = mac->params[j];
3934 while (tok_isnt_(tm, ",")) {
3935 t = new_Token(NULL, tm->type, tm->text, 0);
3936 *tt = t, tt = &t->next, tm = tm->next;
3941 *last = tt;
3942 return head;
3944 err:
3945 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3946 &tline->text[1]);
3947 return tline;
3951 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3952 * %-n) and MMacro-local identifiers (%%foo) as well as
3953 * macro indirection (%[...]) and range (%{..:..}).
3955 static Token *expand_mmac_params(Token * tline)
3957 Token *t, *tt, **tail, *thead;
3958 bool changed = false;
3959 char *pos;
3961 tail = &thead;
3962 thead = NULL;
3964 while (tline) {
3965 if (tline->type == TOK_PREPROC_ID && tline->text && tline->text[0] &&
3966 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3967 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3968 tline->text[1] == '%')) {
3969 char *text = NULL;
3970 int type = 0, cc; /* type = 0 to placate optimisers */
3971 char tmpbuf[30];
3972 unsigned int n;
3973 int i;
3974 MMacro *mac;
3976 t = tline;
3977 tline = tline->next;
3979 mac = istk->mstk;
3980 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3981 mac = mac->next_active;
3982 if (!mac) {
3983 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3984 } else {
3985 pos = strchr(t->text, ':');
3986 if (!pos) {
3987 switch (t->text[1]) {
3989 * We have to make a substitution of one of the
3990 * forms %1, %-1, %+1, %%foo, %0.
3992 case '0':
3993 type = TOK_NUMBER;
3994 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3995 text = nasm_strdup(tmpbuf);
3996 break;
3997 case '%':
3998 type = TOK_ID;
3999 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4000 mac->unique);
4001 text = nasm_strcat(tmpbuf, t->text + 2);
4002 break;
4003 case '-':
4004 n = atoi(t->text + 2) - 1;
4005 if (n >= mac->nparam)
4006 tt = NULL;
4007 else {
4008 if (mac->nparam > 1)
4009 n = (n + mac->rotate) % mac->nparam;
4010 tt = mac->params[n];
4012 cc = find_cc(tt);
4013 if (cc == -1) {
4014 nasm_error(ERR_NONFATAL,
4015 "macro parameter %d is not a condition code",
4016 n + 1);
4017 text = NULL;
4018 } else {
4019 type = TOK_ID;
4020 if (inverse_ccs[cc] == -1) {
4021 nasm_error(ERR_NONFATAL,
4022 "condition code `%s' is not invertible",
4023 conditions[cc]);
4024 text = NULL;
4025 } else
4026 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4028 break;
4029 case '+':
4030 n = atoi(t->text + 2) - 1;
4031 if (n >= mac->nparam)
4032 tt = NULL;
4033 else {
4034 if (mac->nparam > 1)
4035 n = (n + mac->rotate) % mac->nparam;
4036 tt = mac->params[n];
4038 cc = find_cc(tt);
4039 if (cc == -1) {
4040 nasm_error(ERR_NONFATAL,
4041 "macro parameter %d is not a condition code",
4042 n + 1);
4043 text = NULL;
4044 } else {
4045 type = TOK_ID;
4046 text = nasm_strdup(conditions[cc]);
4048 break;
4049 default:
4050 n = atoi(t->text + 1) - 1;
4051 if (n >= mac->nparam)
4052 tt = NULL;
4053 else {
4054 if (mac->nparam > 1)
4055 n = (n + mac->rotate) % mac->nparam;
4056 tt = mac->params[n];
4058 if (tt) {
4059 for (i = 0; i < mac->paramlen[n]; i++) {
4060 *tail = new_Token(NULL, tt->type, tt->text, 0);
4061 tail = &(*tail)->next;
4062 tt = tt->next;
4065 text = NULL; /* we've done it here */
4066 break;
4068 } else {
4070 * seems we have a parameters range here
4072 Token *head, **last;
4073 head = expand_mmac_params_range(mac, t, &last);
4074 if (head != t) {
4075 *tail = head;
4076 *last = tline;
4077 tline = head;
4078 text = NULL;
4082 if (!text) {
4083 delete_Token(t);
4084 } else {
4085 *tail = t;
4086 tail = &t->next;
4087 t->type = type;
4088 nasm_free(t->text);
4089 t->text = text;
4090 t->a.mac = NULL;
4092 changed = true;
4093 continue;
4094 } else if (tline->type == TOK_INDIRECT) {
4095 t = tline;
4096 tline = tline->next;
4097 tt = tokenize(t->text);
4098 tt = expand_mmac_params(tt);
4099 tt = expand_smacro(tt);
4100 *tail = tt;
4101 while (tt) {
4102 tt->a.mac = NULL; /* Necessary? */
4103 tail = &tt->next;
4104 tt = tt->next;
4106 delete_Token(t);
4107 changed = true;
4108 } else {
4109 t = *tail = tline;
4110 tline = tline->next;
4111 t->a.mac = NULL;
4112 tail = &t->next;
4115 *tail = NULL;
4117 if (changed) {
4118 const struct tokseq_match t[] = {
4120 PP_CONCAT_MASK(TOK_ID) |
4121 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4122 PP_CONCAT_MASK(TOK_ID) |
4123 PP_CONCAT_MASK(TOK_NUMBER) |
4124 PP_CONCAT_MASK(TOK_FLOAT) |
4125 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4128 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4129 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4132 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4135 return thead;
4139 * Expand all single-line macro calls made in the given line.
4140 * Return the expanded version of the line. The original is deemed
4141 * to be destroyed in the process. (In reality we'll just move
4142 * Tokens from input to output a lot of the time, rather than
4143 * actually bothering to destroy and replicate.)
4146 static Token *expand_smacro(Token * tline)
4148 Token *t, *tt, *mstart, **tail, *thead;
4149 SMacro *head = NULL, *m;
4150 Token **params;
4151 int *paramsize;
4152 unsigned int nparam, sparam;
4153 int brackets;
4154 Token *org_tline = tline;
4155 Context *ctx;
4156 const char *mname;
4157 int64_t deadman = nasm_limit[LIMIT_MACROS];
4158 bool expanded;
4161 * Trick: we should avoid changing the start token pointer since it can
4162 * be contained in "next" field of other token. Because of this
4163 * we allocate a copy of first token and work with it; at the end of
4164 * routine we copy it back
4166 if (org_tline) {
4167 tline = new_Token(org_tline->next, org_tline->type,
4168 org_tline->text, 0);
4169 tline->a.mac = org_tline->a.mac;
4170 nasm_free(org_tline->text);
4171 org_tline->text = NULL;
4174 expanded = true; /* Always expand %+ at least once */
4176 again:
4177 thead = NULL;
4178 tail = &thead;
4180 while (tline) { /* main token loop */
4181 if (!--deadman) {
4182 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4183 goto err;
4186 if ((mname = tline->text)) {
4187 /* if this token is a local macro, look in local context */
4188 if (tline->type == TOK_ID) {
4189 head = (SMacro *)hash_findix(&smacros, mname);
4190 } else if (tline->type == TOK_PREPROC_ID) {
4191 ctx = get_ctx(mname, &mname);
4192 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4193 } else
4194 head = NULL;
4197 * We've hit an identifier. As in is_mmacro below, we first
4198 * check whether the identifier is a single-line macro at
4199 * all, then think about checking for parameters if
4200 * necessary.
4202 list_for_each(m, head)
4203 if (!mstrcmp(m->name, mname, m->casesense))
4204 break;
4205 if (m) {
4206 mstart = tline;
4207 params = NULL;
4208 paramsize = NULL;
4209 if (m->nparam == 0) {
4211 * Simple case: the macro is parameterless. Discard the
4212 * one token that the macro call took, and push the
4213 * expansion back on the to-do stack.
4215 if (!m->expansion) {
4216 if (!strcmp("__FILE__", m->name)) {
4217 const char *file = src_get_fname();
4218 /* nasm_free(tline->text); here? */
4219 tline->text = nasm_quote(file, strlen(file));
4220 tline->type = TOK_STRING;
4221 continue;
4223 if (!strcmp("__LINE__", m->name)) {
4224 nasm_free(tline->text);
4225 make_tok_num(tline, src_get_linnum());
4226 continue;
4228 if (!strcmp("__BITS__", m->name)) {
4229 nasm_free(tline->text);
4230 make_tok_num(tline, globalbits);
4231 continue;
4233 tline = delete_Token(tline);
4234 continue;
4236 } else {
4238 * Complicated case: at least one macro with this name
4239 * exists and takes parameters. We must find the
4240 * parameters in the call, count them, find the SMacro
4241 * that corresponds to that form of the macro call, and
4242 * substitute for the parameters when we expand. What a
4243 * pain.
4245 /*tline = tline->next;
4246 skip_white_(tline); */
4247 do {
4248 t = tline->next;
4249 while (tok_type_(t, TOK_SMAC_END)) {
4250 t->a.mac->in_progress = false;
4251 t->text = NULL;
4252 t = tline->next = delete_Token(t);
4254 tline = t;
4255 } while (tok_type_(tline, TOK_WHITESPACE));
4256 if (!tok_is_(tline, "(")) {
4258 * This macro wasn't called with parameters: ignore
4259 * the call. (Behaviour borrowed from gnu cpp.)
4261 tline = mstart;
4262 m = NULL;
4263 } else {
4264 int paren = 0;
4265 int white = 0;
4266 brackets = 0;
4267 nparam = 0;
4268 sparam = PARAM_DELTA;
4269 params = nasm_malloc(sparam * sizeof(Token *));
4270 params[0] = tline->next;
4271 paramsize = nasm_malloc(sparam * sizeof(int));
4272 paramsize[0] = 0;
4273 while (true) { /* parameter loop */
4275 * For some unusual expansions
4276 * which concatenates function call
4278 t = tline->next;
4279 while (tok_type_(t, TOK_SMAC_END)) {
4280 t->a.mac->in_progress = false;
4281 t->text = NULL;
4282 t = tline->next = delete_Token(t);
4284 tline = t;
4286 if (!tline) {
4287 nasm_error(ERR_NONFATAL,
4288 "macro call expects terminating `)'");
4289 break;
4291 if (tline->type == TOK_WHITESPACE
4292 && brackets <= 0) {
4293 if (paramsize[nparam])
4294 white++;
4295 else
4296 params[nparam] = tline->next;
4297 continue; /* parameter loop */
4299 if (tline->type == TOK_OTHER
4300 && tline->text[1] == 0) {
4301 char ch = tline->text[0];
4302 if (ch == ',' && !paren && brackets <= 0) {
4303 if (++nparam >= sparam) {
4304 sparam += PARAM_DELTA;
4305 params = nasm_realloc(params,
4306 sparam * sizeof(Token *));
4307 paramsize = nasm_realloc(paramsize,
4308 sparam * sizeof(int));
4310 params[nparam] = tline->next;
4311 paramsize[nparam] = 0;
4312 white = 0;
4313 continue; /* parameter loop */
4315 if (ch == '{' &&
4316 (brackets > 0 || (brackets == 0 &&
4317 !paramsize[nparam])))
4319 if (!(brackets++)) {
4320 params[nparam] = tline->next;
4321 continue; /* parameter loop */
4324 if (ch == '}' && brackets > 0)
4325 if (--brackets == 0) {
4326 brackets = -1;
4327 continue; /* parameter loop */
4329 if (ch == '(' && !brackets)
4330 paren++;
4331 if (ch == ')' && brackets <= 0)
4332 if (--paren < 0)
4333 break;
4335 if (brackets < 0) {
4336 brackets = 0;
4337 nasm_error(ERR_NONFATAL, "braces do not "
4338 "enclose all of macro parameter");
4340 paramsize[nparam] += white + 1;
4341 white = 0;
4342 } /* parameter loop */
4343 nparam++;
4344 while (m && (m->nparam != nparam ||
4345 mstrcmp(m->name, mname,
4346 m->casesense)))
4347 m = m->next;
4348 if (!m)
4349 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4350 "macro `%s' exists, "
4351 "but not taking %d parameters",
4352 mstart->text, nparam);
4355 if (m && m->in_progress)
4356 m = NULL;
4357 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4359 * Design question: should we handle !tline, which
4360 * indicates missing ')' here, or expand those
4361 * macros anyway, which requires the (t) test a few
4362 * lines down?
4364 nasm_free(params);
4365 nasm_free(paramsize);
4366 tline = mstart;
4367 } else {
4369 * Expand the macro: we are placed on the last token of the
4370 * call, so that we can easily split the call from the
4371 * following tokens. We also start by pushing an SMAC_END
4372 * token for the cycle removal.
4374 t = tline;
4375 if (t) {
4376 tline = t->next;
4377 t->next = NULL;
4379 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4380 tt->a.mac = m;
4381 m->in_progress = true;
4382 tline = tt;
4383 list_for_each(t, m->expansion) {
4384 if (t->type >= TOK_SMAC_PARAM) {
4385 Token *pcopy = tline, **ptail = &pcopy;
4386 Token *ttt, *pt;
4387 int i;
4389 ttt = params[t->type - TOK_SMAC_PARAM];
4390 i = paramsize[t->type - TOK_SMAC_PARAM];
4391 while (--i >= 0) {
4392 pt = *ptail = new_Token(tline, ttt->type,
4393 ttt->text, 0);
4394 ptail = &pt->next;
4395 ttt = ttt->next;
4396 if (!ttt && i > 0) {
4398 * FIXME: Need to handle more gracefully,
4399 * exiting early on agruments analysis.
4401 nasm_error(ERR_FATAL,
4402 "macro `%s' expects %d args",
4403 mstart->text,
4404 (int)paramsize[t->type - TOK_SMAC_PARAM]);
4407 tline = pcopy;
4408 } else if (t->type == TOK_PREPROC_Q) {
4409 tt = new_Token(tline, TOK_ID, mname, 0);
4410 tline = tt;
4411 } else if (t->type == TOK_PREPROC_QQ) {
4412 tt = new_Token(tline, TOK_ID, m->name, 0);
4413 tline = tt;
4414 } else {
4415 tt = new_Token(tline, t->type, t->text, 0);
4416 tline = tt;
4421 * Having done that, get rid of the macro call, and clean
4422 * up the parameters.
4424 nasm_free(params);
4425 nasm_free(paramsize);
4426 free_tlist(mstart);
4427 expanded = true;
4428 continue; /* main token loop */
4433 if (tline->type == TOK_SMAC_END) {
4434 /* On error path it might already be dropped */
4435 if (tline->a.mac)
4436 tline->a.mac->in_progress = false;
4437 tline = delete_Token(tline);
4438 } else {
4439 t = *tail = tline;
4440 tline = tline->next;
4441 t->a.mac = NULL;
4442 t->next = NULL;
4443 tail = &t->next;
4448 * Now scan the entire line and look for successive TOK_IDs that resulted
4449 * after expansion (they can't be produced by tokenize()). The successive
4450 * TOK_IDs should be concatenated.
4451 * Also we look for %+ tokens and concatenate the tokens before and after
4452 * them (without white spaces in between).
4454 if (expanded) {
4455 const struct tokseq_match t[] = {
4457 PP_CONCAT_MASK(TOK_ID) |
4458 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4459 PP_CONCAT_MASK(TOK_ID) |
4460 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4461 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4464 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4466 * If we concatenated something, *and* we had previously expanded
4467 * an actual macro, scan the lines again for macros...
4469 tline = thead;
4470 expanded = false;
4471 goto again;
4475 err:
4476 if (org_tline) {
4477 if (thead) {
4478 *org_tline = *thead;
4479 /* since we just gave text to org_line, don't free it */
4480 thead->text = NULL;
4481 delete_Token(thead);
4482 } else {
4483 /* the expression expanded to empty line;
4484 we can't return NULL for some reasons
4485 we just set the line to a single WHITESPACE token. */
4486 memset(org_tline, 0, sizeof(*org_tline));
4487 org_tline->text = NULL;
4488 org_tline->type = TOK_WHITESPACE;
4490 thead = org_tline;
4493 return thead;
4497 * Similar to expand_smacro but used exclusively with macro identifiers
4498 * right before they are fetched in. The reason is that there can be
4499 * identifiers consisting of several subparts. We consider that if there
4500 * are more than one element forming the name, user wants a expansion,
4501 * otherwise it will be left as-is. Example:
4503 * %define %$abc cde
4505 * the identifier %$abc will be left as-is so that the handler for %define
4506 * will suck it and define the corresponding value. Other case:
4508 * %define _%$abc cde
4510 * In this case user wants name to be expanded *before* %define starts
4511 * working, so we'll expand %$abc into something (if it has a value;
4512 * otherwise it will be left as-is) then concatenate all successive
4513 * PP_IDs into one.
4515 static Token *expand_id(Token * tline)
4517 Token *cur, *oldnext = NULL;
4519 if (!tline || !tline->next)
4520 return tline;
4522 cur = tline;
4523 while (cur->next &&
4524 (cur->next->type == TOK_ID ||
4525 cur->next->type == TOK_PREPROC_ID
4526 || cur->next->type == TOK_NUMBER))
4527 cur = cur->next;
4529 /* If identifier consists of just one token, don't expand */
4530 if (cur == tline)
4531 return tline;
4533 if (cur) {
4534 oldnext = cur->next; /* Detach the tail past identifier */
4535 cur->next = NULL; /* so that expand_smacro stops here */
4538 tline = expand_smacro(tline);
4540 if (cur) {
4541 /* expand_smacro possibly changhed tline; re-scan for EOL */
4542 cur = tline;
4543 while (cur && cur->next)
4544 cur = cur->next;
4545 if (cur)
4546 cur->next = oldnext;
4549 return tline;
4553 * Determine whether the given line constitutes a multi-line macro
4554 * call, and return the MMacro structure called if so. Doesn't have
4555 * to check for an initial label - that's taken care of in
4556 * expand_mmacro - but must check numbers of parameters. Guaranteed
4557 * to be called with tline->type == TOK_ID, so the putative macro
4558 * name is easy to find.
4560 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4562 MMacro *head, *m;
4563 Token **params;
4564 int nparam;
4566 head = (MMacro *) hash_findix(&mmacros, tline->text);
4569 * Efficiency: first we see if any macro exists with the given
4570 * name. If not, we can return NULL immediately. _Then_ we
4571 * count the parameters, and then we look further along the
4572 * list if necessary to find the proper MMacro.
4574 list_for_each(m, head)
4575 if (!mstrcmp(m->name, tline->text, m->casesense))
4576 break;
4577 if (!m)
4578 return NULL;
4581 * OK, we have a potential macro. Count and demarcate the
4582 * parameters.
4584 count_mmac_params(tline->next, &nparam, &params);
4587 * So we know how many parameters we've got. Find the MMacro
4588 * structure that handles this number.
4590 while (m) {
4591 if (m->nparam_min <= nparam
4592 && (m->plus || nparam <= m->nparam_max)) {
4594 * This one is right. Just check if cycle removal
4595 * prohibits us using it before we actually celebrate...
4597 if (m->in_progress > m->max_depth) {
4598 if (m->max_depth > 0) {
4599 nasm_error(ERR_WARNING,
4600 "reached maximum recursion depth of %i",
4601 m->max_depth);
4603 nasm_free(params);
4604 return NULL;
4607 * It's right, and we can use it. Add its default
4608 * parameters to the end of our list if necessary.
4610 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4611 params =
4612 nasm_realloc(params,
4613 ((m->nparam_min + m->ndefs +
4614 1) * sizeof(*params)));
4615 while (nparam < m->nparam_min + m->ndefs) {
4616 params[nparam] = m->defaults[nparam - m->nparam_min];
4617 nparam++;
4621 * If we've gone over the maximum parameter count (and
4622 * we're in Plus mode), ignore parameters beyond
4623 * nparam_max.
4625 if (m->plus && nparam > m->nparam_max)
4626 nparam = m->nparam_max;
4628 * Then terminate the parameter list, and leave.
4630 if (!params) { /* need this special case */
4631 params = nasm_malloc(sizeof(*params));
4632 nparam = 0;
4634 params[nparam] = NULL;
4635 *params_array = params;
4636 return m;
4639 * This one wasn't right: look for the next one with the
4640 * same name.
4642 list_for_each(m, m->next)
4643 if (!mstrcmp(m->name, tline->text, m->casesense))
4644 break;
4648 * After all that, we didn't find one with the right number of
4649 * parameters. Issue a warning, and fail to expand the macro.
4651 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4652 "macro `%s' exists, but not taking %d parameters",
4653 tline->text, nparam);
4654 nasm_free(params);
4655 return NULL;
4660 * Save MMacro invocation specific fields in
4661 * preparation for a recursive macro expansion
4663 static void push_mmacro(MMacro *m)
4665 MMacroInvocation *i;
4667 i = nasm_malloc(sizeof(MMacroInvocation));
4668 i->prev = m->prev;
4669 i->params = m->params;
4670 i->iline = m->iline;
4671 i->nparam = m->nparam;
4672 i->rotate = m->rotate;
4673 i->paramlen = m->paramlen;
4674 i->unique = m->unique;
4675 i->condcnt = m->condcnt;
4676 m->prev = i;
4681 * Restore MMacro invocation specific fields that were
4682 * saved during a previous recursive macro expansion
4684 static void pop_mmacro(MMacro *m)
4686 MMacroInvocation *i;
4688 if (m->prev) {
4689 i = m->prev;
4690 m->prev = i->prev;
4691 m->params = i->params;
4692 m->iline = i->iline;
4693 m->nparam = i->nparam;
4694 m->rotate = i->rotate;
4695 m->paramlen = i->paramlen;
4696 m->unique = i->unique;
4697 m->condcnt = i->condcnt;
4698 nasm_free(i);
4704 * Expand the multi-line macro call made by the given line, if
4705 * there is one to be expanded. If there is, push the expansion on
4706 * istk->expansion and return 1. Otherwise return 0.
4708 static int expand_mmacro(Token * tline)
4710 Token *startline = tline;
4711 Token *label = NULL;
4712 int dont_prepend = 0;
4713 Token **params, *t, *tt;
4714 MMacro *m;
4715 Line *l, *ll;
4716 int i, nparam, *paramlen;
4717 const char *mname;
4719 t = tline;
4720 skip_white_(t);
4721 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4722 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4723 return 0;
4724 m = is_mmacro(t, &params);
4725 if (m) {
4726 mname = t->text;
4727 } else {
4728 Token *last;
4730 * We have an id which isn't a macro call. We'll assume
4731 * it might be a label; we'll also check to see if a
4732 * colon follows it. Then, if there's another id after
4733 * that lot, we'll check it again for macro-hood.
4735 label = last = t;
4736 t = t->next;
4737 if (tok_type_(t, TOK_WHITESPACE))
4738 last = t, t = t->next;
4739 if (tok_is_(t, ":")) {
4740 dont_prepend = 1;
4741 last = t, t = t->next;
4742 if (tok_type_(t, TOK_WHITESPACE))
4743 last = t, t = t->next;
4745 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4746 return 0;
4747 last->next = NULL;
4748 mname = t->text;
4749 tline = t;
4753 * Fix up the parameters: this involves stripping leading and
4754 * trailing whitespace, then stripping braces if they are
4755 * present.
4757 for (nparam = 0; params[nparam]; nparam++) ;
4758 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4760 for (i = 0; params[i]; i++) {
4761 int brace = 0;
4762 int comma = (!m->plus || i < nparam - 1);
4764 t = params[i];
4765 skip_white_(t);
4766 if (tok_is_(t, "{"))
4767 t = t->next, brace++, comma = false;
4768 params[i] = t;
4769 paramlen[i] = 0;
4770 while (t) {
4771 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4772 break; /* ... because we have hit a comma */
4773 if (comma && t->type == TOK_WHITESPACE
4774 && tok_is_(t->next, ","))
4775 break; /* ... or a space then a comma */
4776 if (brace && t->type == TOK_OTHER) {
4777 if (t->text[0] == '{')
4778 brace++; /* ... or a nested opening brace */
4779 else if (t->text[0] == '}')
4780 if (!--brace)
4781 break; /* ... or a brace */
4783 t = t->next;
4784 paramlen[i]++;
4786 if (brace)
4787 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4791 * OK, we have a MMacro structure together with a set of
4792 * parameters. We must now go through the expansion and push
4793 * copies of each Line on to istk->expansion. Substitution of
4794 * parameter tokens and macro-local tokens doesn't get done
4795 * until the single-line macro substitution process; this is
4796 * because delaying them allows us to change the semantics
4797 * later through %rotate.
4799 * First, push an end marker on to istk->expansion, mark this
4800 * macro as in progress, and set up its invocation-specific
4801 * variables.
4803 ll = nasm_malloc(sizeof(Line));
4804 ll->next = istk->expansion;
4805 ll->finishes = m;
4806 ll->first = NULL;
4807 istk->expansion = ll;
4810 * Save the previous MMacro expansion in the case of
4811 * macro recursion
4813 if (m->max_depth && m->in_progress)
4814 push_mmacro(m);
4816 m->in_progress ++;
4817 m->params = params;
4818 m->iline = tline;
4819 m->nparam = nparam;
4820 m->rotate = 0;
4821 m->paramlen = paramlen;
4822 m->unique = unique++;
4823 m->lineno = 0;
4824 m->condcnt = 0;
4826 m->next_active = istk->mstk;
4827 istk->mstk = m;
4829 list_for_each(l, m->expansion) {
4830 Token **tail;
4832 ll = nasm_malloc(sizeof(Line));
4833 ll->finishes = NULL;
4834 ll->next = istk->expansion;
4835 istk->expansion = ll;
4836 tail = &ll->first;
4838 list_for_each(t, l->first) {
4839 Token *x = t;
4840 switch (t->type) {
4841 case TOK_PREPROC_Q:
4842 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4843 break;
4844 case TOK_PREPROC_QQ:
4845 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4846 break;
4847 case TOK_PREPROC_ID:
4848 if (t->text[1] == '0' && t->text[2] == '0') {
4849 dont_prepend = -1;
4850 x = label;
4851 if (!x)
4852 continue;
4854 /* fall through */
4855 default:
4856 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4857 break;
4859 tail = &tt->next;
4861 *tail = NULL;
4865 * If we had a label, push it on as the first line of
4866 * the macro expansion.
4868 if (label) {
4869 if (dont_prepend < 0)
4870 free_tlist(startline);
4871 else {
4872 ll = nasm_malloc(sizeof(Line));
4873 ll->finishes = NULL;
4874 ll->next = istk->expansion;
4875 istk->expansion = ll;
4876 ll->first = startline;
4877 if (!dont_prepend) {
4878 while (label->next)
4879 label = label->next;
4880 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4885 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4887 return 1;
4891 * This function adds macro names to error messages, and suppresses
4892 * them if necessary.
4894 static void pp_verror(int severity, const char *fmt, va_list arg)
4896 char buff[BUFSIZ];
4897 MMacro *mmac = NULL;
4898 int delta = 0;
4901 * If we're in a dead branch of IF or something like it, ignore the error.
4902 * However, because %else etc are evaluated in the state context
4903 * of the previous branch, errors might get lost:
4904 * %if 0 ... %else trailing garbage ... %endif
4905 * So %else etc should set the ERR_PP_PRECOND flag.
4907 if ((severity & ERR_MASK) < ERR_FATAL &&
4908 istk && istk->conds &&
4909 ((severity & ERR_PP_PRECOND) ?
4910 istk->conds->state == COND_NEVER :
4911 !emitting(istk->conds->state)))
4912 return;
4914 /* get %macro name */
4915 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4916 mmac = istk->mstk;
4917 /* but %rep blocks should be skipped */
4918 while (mmac && !mmac->name)
4919 mmac = mmac->next_active, delta++;
4922 if (mmac) {
4923 vsnprintf(buff, sizeof(buff), fmt, arg);
4925 nasm_set_verror(real_verror);
4926 nasm_error(severity, "(%s:%d) %s",
4927 mmac->name, mmac->lineno - delta, buff);
4928 nasm_set_verror(pp_verror);
4929 } else {
4930 real_verror(severity, fmt, arg);
4934 static void
4935 pp_reset(const char *file, int apass, StrList *dep_list)
4937 Token *t;
4939 cstk = NULL;
4940 istk = nasm_malloc(sizeof(Include));
4941 istk->next = NULL;
4942 istk->conds = NULL;
4943 istk->expansion = NULL;
4944 istk->mstk = NULL;
4945 istk->fp = nasm_open_read(file, NF_TEXT);
4946 istk->fname = NULL;
4947 src_set(0, file);
4948 istk->lineinc = 1;
4949 if (!istk->fp)
4950 nasm_fatal_fl(ERR_NOFILE, "unable to open input file `%s'", file);
4951 defining = NULL;
4952 nested_mac_count = 0;
4953 nested_rep_count = 0;
4954 init_macros();
4955 unique = 0;
4956 deplist = dep_list;
4958 if (tasm_compatible_mode)
4959 pp_add_stdmac(nasm_stdmac_tasm);
4961 pp_add_stdmac(nasm_stdmac_nasm);
4962 pp_add_stdmac(nasm_stdmac_version);
4964 if (extrastdmac)
4965 pp_add_stdmac(extrastdmac);
4967 stdmacpos = stdmacros[0];
4968 stdmacnext = &stdmacros[1];
4970 do_predef = true;
4973 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4974 * The caller, however, will also pass in 3 for preprocess-only so
4975 * we can set __PASS__ accordingly.
4977 pass = apass > 2 ? 2 : apass;
4979 strlist_add_string(deplist, file);
4982 * Define the __PASS__ macro. This is defined here unlike
4983 * all the other builtins, because it is special -- it varies between
4984 * passes.
4986 t = nasm_malloc(sizeof(*t));
4987 t->next = NULL;
4988 make_tok_num(t, apass);
4989 t->a.mac = NULL;
4990 define_smacro(NULL, "__PASS__", true, 0, t);
4993 static void pp_init(void)
4995 hash_init(&FileHash, HASH_MEDIUM);
4996 ipath = strlist_allocate();
4999 static char *pp_getline(void)
5001 char *line;
5002 Token *tline;
5004 real_verror = nasm_set_verror(pp_verror);
5006 while (1) {
5008 * Fetch a tokenized line, either from the macro-expansion
5009 * buffer or from the input file.
5011 tline = NULL;
5012 while (istk->expansion && istk->expansion->finishes) {
5013 Line *l = istk->expansion;
5014 if (!l->finishes->name && l->finishes->in_progress > 1) {
5015 Line *ll;
5018 * This is a macro-end marker for a macro with no
5019 * name, which means it's not really a macro at all
5020 * but a %rep block, and the `in_progress' field is
5021 * more than 1, meaning that we still need to
5022 * repeat. (1 means the natural last repetition; 0
5023 * means termination by %exitrep.) We have
5024 * therefore expanded up to the %endrep, and must
5025 * push the whole block on to the expansion buffer
5026 * again. We don't bother to remove the macro-end
5027 * marker: we'd only have to generate another one
5028 * if we did.
5030 l->finishes->in_progress--;
5031 list_for_each(l, l->finishes->expansion) {
5032 Token *t, *tt, **tail;
5034 ll = nasm_malloc(sizeof(Line));
5035 ll->next = istk->expansion;
5036 ll->finishes = NULL;
5037 ll->first = NULL;
5038 tail = &ll->first;
5040 list_for_each(t, l->first) {
5041 if (t->text || t->type == TOK_WHITESPACE) {
5042 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5043 tail = &tt->next;
5047 istk->expansion = ll;
5049 } else {
5051 * Check whether a `%rep' was started and not ended
5052 * within this macro expansion. This can happen and
5053 * should be detected. It's a fatal error because
5054 * I'm too confused to work out how to recover
5055 * sensibly from it.
5057 if (defining) {
5058 if (defining->name)
5059 nasm_panic("defining with name in expansion");
5060 else if (istk->mstk->name)
5061 nasm_fatal("`%%rep' without `%%endrep' within"
5062 " expansion of macro `%s'",
5063 istk->mstk->name);
5067 * FIXME: investigate the relationship at this point between
5068 * istk->mstk and l->finishes
5071 MMacro *m = istk->mstk;
5072 istk->mstk = m->next_active;
5073 if (m->name) {
5075 * This was a real macro call, not a %rep, and
5076 * therefore the parameter information needs to
5077 * be freed.
5079 if (m->prev) {
5080 pop_mmacro(m);
5081 l->finishes->in_progress --;
5082 } else {
5083 nasm_free(m->params);
5084 free_tlist(m->iline);
5085 nasm_free(m->paramlen);
5086 l->finishes->in_progress = 0;
5091 * FIXME It is incorrect to always free_mmacro here.
5092 * It leads to usage-after-free.
5094 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
5096 #if 0
5097 else
5098 free_mmacro(m);
5099 #endif
5101 istk->expansion = l->next;
5102 nasm_free(l);
5103 lfmt->downlevel(LIST_MACRO);
5106 while (1) { /* until we get a line we can use */
5108 if (istk->expansion) { /* from a macro expansion */
5109 char *p;
5110 Line *l = istk->expansion;
5111 if (istk->mstk)
5112 istk->mstk->lineno++;
5113 tline = l->first;
5114 istk->expansion = l->next;
5115 nasm_free(l);
5116 p = detoken(tline, false);
5117 lfmt->line(LIST_MACRO, p);
5118 nasm_free(p);
5119 break;
5121 line = read_line();
5122 if (line) { /* from the current input file */
5123 line = prepreproc(line);
5124 tline = tokenize(line);
5125 nasm_free(line);
5126 break;
5129 * The current file has ended; work down the istk
5132 Include *i = istk;
5133 fclose(i->fp);
5134 if (i->conds) {
5135 /* nasm_error can't be conditionally suppressed */
5136 nasm_fatal("expected `%%endif' before end of file");
5138 /* only set line and file name if there's a next node */
5139 if (i->next)
5140 src_set(i->lineno, i->fname);
5141 istk = i->next;
5142 lfmt->downlevel(LIST_INCLUDE);
5143 nasm_free(i);
5144 if (!istk) {
5145 line = NULL;
5146 goto done;
5148 if (istk->expansion && istk->expansion->finishes)
5149 break;
5154 * We must expand MMacro parameters and MMacro-local labels
5155 * _before_ we plunge into directive processing, to cope
5156 * with things like `%define something %1' such as STRUC
5157 * uses. Unless we're _defining_ a MMacro, in which case
5158 * those tokens should be left alone to go into the
5159 * definition; and unless we're in a non-emitting
5160 * condition, in which case we don't want to meddle with
5161 * anything.
5163 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5164 && !(istk->mstk && !istk->mstk->in_progress)) {
5165 tline = expand_mmac_params(tline);
5169 * Check the line to see if it's a preprocessor directive.
5171 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5172 if (line)
5173 break; /* Directive generated output */
5174 else
5175 continue;
5176 } else if (defining) {
5178 * We're defining a multi-line macro. We emit nothing
5179 * at all, and just
5180 * shove the tokenized line on to the macro definition.
5182 Line *l = nasm_malloc(sizeof(Line));
5183 l->next = defining->expansion;
5184 l->first = tline;
5185 l->finishes = NULL;
5186 defining->expansion = l;
5187 continue;
5188 } else if (istk->conds && !emitting(istk->conds->state)) {
5190 * We're in a non-emitting branch of a condition block.
5191 * Emit nothing at all, not even a blank line: when we
5192 * emerge from the condition we'll give a line-number
5193 * directive so we keep our place correctly.
5195 free_tlist(tline);
5196 continue;
5197 } else if (istk->mstk && !istk->mstk->in_progress) {
5199 * We're in a %rep block which has been terminated, so
5200 * we're walking through to the %endrep without
5201 * emitting anything. Emit nothing at all, not even a
5202 * blank line: when we emerge from the %rep block we'll
5203 * give a line-number directive so we keep our place
5204 * correctly.
5206 free_tlist(tline);
5207 continue;
5208 } else {
5209 tline = expand_smacro(tline);
5210 if (!expand_mmacro(tline)) {
5212 * De-tokenize the line again, and emit it.
5214 line = detoken(tline, true);
5215 free_tlist(tline);
5216 break;
5217 } else {
5218 continue; /* expand_mmacro calls free_tlist */
5223 done:
5224 nasm_set_verror(real_verror);
5225 return line;
5228 static void pp_cleanup(int pass)
5230 real_verror = nasm_set_verror(pp_verror);
5232 if (defining) {
5233 if (defining->name) {
5234 nasm_error(ERR_NONFATAL,
5235 "end of file while still defining macro `%s'",
5236 defining->name);
5237 } else {
5238 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5241 free_mmacro(defining);
5242 defining = NULL;
5245 nasm_set_verror(real_verror);
5247 while (cstk)
5248 ctx_pop();
5249 free_macros();
5250 while (istk) {
5251 Include *i = istk;
5252 istk = istk->next;
5253 fclose(i->fp);
5254 nasm_free(i);
5256 while (cstk)
5257 ctx_pop();
5258 src_set_fname(NULL);
5259 if (pass == 0) {
5260 free_llist(predef);
5261 predef = NULL;
5262 delete_Blocks();
5263 freeTokens = NULL;
5264 strlist_free(ipath);
5268 static void pp_include_path(const char *path)
5270 if (!path)
5271 path = "";
5273 strlist_add_string(ipath, path);
5276 static void pp_pre_include(char *fname)
5278 Token *inc, *space, *name;
5279 Line *l;
5281 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5282 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5283 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5285 l = nasm_malloc(sizeof(Line));
5286 l->next = predef;
5287 l->first = inc;
5288 l->finishes = NULL;
5289 predef = l;
5292 static void pp_pre_define(char *definition)
5294 Token *def, *space;
5295 Line *l;
5296 char *equals;
5298 real_verror = nasm_set_verror(pp_verror);
5300 equals = strchr(definition, '=');
5301 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5302 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5303 if (equals)
5304 *equals = ' ';
5305 space->next = tokenize(definition);
5306 if (equals)
5307 *equals = '=';
5309 if (space->next->type != TOK_PREPROC_ID &&
5310 space->next->type != TOK_ID)
5311 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5313 l = nasm_malloc(sizeof(Line));
5314 l->next = predef;
5315 l->first = def;
5316 l->finishes = NULL;
5317 predef = l;
5319 nasm_set_verror(real_verror);
5322 static void pp_pre_undefine(char *definition)
5324 Token *def, *space;
5325 Line *l;
5327 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5328 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5329 space->next = tokenize(definition);
5331 l = nasm_malloc(sizeof(Line));
5332 l->next = predef;
5333 l->first = def;
5334 l->finishes = NULL;
5335 predef = l;
5338 /* Insert an early preprocessor command that doesn't need special handling */
5339 static void pp_pre_command(const char *what, char *string)
5341 char *cmd;
5342 Token *def, *space;
5343 Line *l;
5345 def = tokenize(string);
5346 if (what) {
5347 cmd = nasm_strcat(what[0] == '%' ? "" : "%", what);
5348 space = new_Token(def, TOK_WHITESPACE, NULL, 0);
5349 def = new_Token(space, TOK_PREPROC_ID, cmd, 0);
5352 l = nasm_malloc(sizeof(Line));
5353 l->next = predef;
5354 l->first = def;
5355 l->finishes = NULL;
5356 predef = l;
5359 static void pp_add_stdmac(macros_t *macros)
5361 macros_t **mp;
5363 /* Find the end of the list and avoid duplicates */
5364 for (mp = stdmacros; *mp; mp++) {
5365 if (*mp == macros)
5366 return; /* Nothing to do */
5369 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5371 *mp = macros;
5374 static void pp_extra_stdmac(macros_t *macros)
5376 extrastdmac = macros;
5379 static void make_tok_num(Token * tok, int64_t val)
5381 char numbuf[32];
5382 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5383 tok->text = nasm_strdup(numbuf);
5384 tok->type = TOK_NUMBER;
5387 static void pp_list_one_macro(MMacro *m, int severity)
5389 if (!m)
5390 return;
5392 /* We need to print the next_active list in reverse order */
5393 pp_list_one_macro(m->next_active, severity);
5395 if (m->name && !m->nolist) {
5396 src_set(m->xline + m->lineno, m->fname);
5397 nasm_error(severity, "... from macro `%s' defined here", m->name);
5401 static void pp_error_list_macros(int severity)
5403 int32_t saved_line;
5404 const char *saved_fname = NULL;
5406 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5407 src_get(&saved_line, &saved_fname);
5409 if (istk)
5410 pp_list_one_macro(istk->mstk, severity);
5412 src_set(saved_line, saved_fname);
5415 const struct preproc_ops nasmpp = {
5416 pp_init,
5417 pp_reset,
5418 pp_getline,
5419 pp_cleanup,
5420 pp_extra_stdmac,
5421 pp_pre_define,
5422 pp_pre_undefine,
5423 pp_pre_include,
5424 pp_pre_command,
5425 pp_include_path,
5426 pp_error_list_macros,