preproc.c: modified deprecation warning for context-local label fallthrough
[nasm.git] / preproc.c
blob186e7244dbcca5191bc149b7aa8550520bb8cff7
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2010 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>
72 #include <inttypes.h>
74 #include "nasm.h"
75 #include "nasmlib.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
84 typedef struct SMacro SMacro;
85 typedef struct MMacro MMacro;
86 typedef struct MMacroInvocation MMacroInvocation;
87 typedef struct Context Context;
88 typedef struct Token Token;
89 typedef struct Blocks Blocks;
90 typedef struct Line Line;
91 typedef struct Include Include;
92 typedef struct Cond Cond;
93 typedef struct IncPath IncPath;
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... */
160 /* Store the definition of a multi-line macro, as defined in a
161 * previous recursive macro expansion.
163 struct MMacroInvocation {
164 MMacroInvocation *prev; /* previous invocation */
165 Token **params; /* actual parameters */
166 Token *iline; /* invocation line */
167 unsigned int nparam, rotate;
168 int *paramlen;
169 uint64_t unique;
170 uint64_t condcnt;
175 * The context stack is composed of a linked list of these.
177 struct Context {
178 Context *next;
179 char *name;
180 struct hash_table localmac;
181 uint32_t number;
185 * This is the internal form which we break input lines up into.
186 * Typically stored in linked lists.
188 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
189 * necessarily used as-is, but is intended to denote the number of
190 * the substituted parameter. So in the definition
192 * %define a(x,y) ( (x) & ~(y) )
194 * the token representing `x' will have its type changed to
195 * TOK_SMAC_PARAM, but the one representing `y' will be
196 * TOK_SMAC_PARAM+1.
198 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
199 * which doesn't need quotes around it. Used in the pre-include
200 * mechanism as an alternative to trying to find a sensible type of
201 * quote to use on the filename we were passed.
203 enum pp_token_type {
204 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
205 TOK_PREPROC_ID, TOK_STRING,
206 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
207 TOK_INTERNAL_STRING,
208 TOK_PREPROC_Q, TOK_PREPROC_QQ,
209 TOK_PASTE, /* %+ */
210 TOK_INDIRECT, /* %[...] */
211 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
212 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
215 struct Token {
216 Token *next;
217 char *text;
218 union {
219 SMacro *mac; /* associated macro for TOK_SMAC_END */
220 size_t len; /* scratch length field */
221 } a; /* Auxiliary data */
222 enum pp_token_type type;
226 * Multi-line macro definitions are stored as a linked list of
227 * these, which is essentially a container to allow several linked
228 * lists of Tokens.
230 * Note that in this module, linked lists are treated as stacks
231 * wherever possible. For this reason, Lines are _pushed_ on to the
232 * `expansion' field in MMacro structures, so that the linked list,
233 * if walked, would give the macro lines in reverse order; this
234 * means that we can walk the list when expanding a macro, and thus
235 * push the lines on to the `expansion' field in _istk_ in reverse
236 * order (so that when popped back off they are in the right
237 * order). It may seem cockeyed, and it relies on my design having
238 * an even number of steps in, but it works...
240 * Some of these structures, rather than being actual lines, are
241 * markers delimiting the end of the expansion of a given macro.
242 * This is for use in the cycle-tracking and %rep-handling code.
243 * Such structures have `finishes' non-NULL, and `first' NULL. All
244 * others have `finishes' NULL, but `first' may still be NULL if
245 * the line is blank.
247 struct Line {
248 Line *next;
249 MMacro *finishes;
250 Token *first;
254 * To handle an arbitrary level of file inclusion, we maintain a
255 * stack (ie linked list) of these things.
257 struct Include {
258 Include *next;
259 FILE *fp;
260 Cond *conds;
261 Line *expansion;
262 char *fname;
263 int lineno, lineinc;
264 MMacro *mstk; /* stack of active macros/reps */
268 * Include search path. This is simply a list of strings which get
269 * prepended, in turn, to the name of an include file, in an
270 * attempt to find the file if it's not in the current directory.
272 struct IncPath {
273 IncPath *next;
274 char *path;
278 * Conditional assembly: we maintain a separate stack of these for
279 * each level of file inclusion. (The only reason we keep the
280 * stacks separate is to ensure that a stray `%endif' in a file
281 * included from within the true branch of a `%if' won't terminate
282 * it and cause confusion: instead, rightly, it'll cause an error.)
284 struct Cond {
285 Cond *next;
286 int state;
288 enum {
290 * These states are for use just after %if or %elif: IF_TRUE
291 * means the condition has evaluated to truth so we are
292 * currently emitting, whereas IF_FALSE means we are not
293 * currently emitting but will start doing so if a %else comes
294 * up. In these states, all directives are admissible: %elif,
295 * %else and %endif. (And of course %if.)
297 COND_IF_TRUE, COND_IF_FALSE,
299 * These states come up after a %else: ELSE_TRUE means we're
300 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
301 * any %elif or %else will cause an error.
303 COND_ELSE_TRUE, COND_ELSE_FALSE,
305 * These states mean that we're not emitting now, and also that
306 * nothing until %endif will be emitted at all. COND_DONE is
307 * used when we've had our moment of emission
308 * and have now started seeing %elifs. COND_NEVER is used when
309 * the condition construct in question is contained within a
310 * non-emitting branch of a larger condition construct,
311 * or if there is an error.
313 COND_DONE, COND_NEVER
315 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
318 * These defines are used as the possible return values for do_directive
320 #define NO_DIRECTIVE_FOUND 0
321 #define DIRECTIVE_FOUND 1
324 * This define sets the upper limit for smacro and recursive mmacro
325 * expansions
327 #define DEADMAN_LIMIT (1 << 20)
329 /* max reps */
330 #define REP_LIMIT ((INT64_C(1) << 62))
333 * Condition codes. Note that we use c_ prefix not C_ because C_ is
334 * used in nasm.h for the "real" condition codes. At _this_ level,
335 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
336 * ones, so we need a different enum...
338 static const char * const conditions[] = {
339 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
340 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
341 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
343 enum pp_conds {
344 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
345 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
346 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
347 c_none = -1
349 static const enum pp_conds inverse_ccs[] = {
350 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
351 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,
352 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
356 * Directive names.
358 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
359 static int is_condition(enum preproc_token arg)
361 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
364 /* For TASM compatibility we need to be able to recognise TASM compatible
365 * conditional compilation directives. Using the NASM pre-processor does
366 * not work, so we look for them specifically from the following list and
367 * then jam in the equivalent NASM directive into the input stream.
370 enum {
371 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
372 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
375 static const char * const tasm_directives[] = {
376 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
377 "ifndef", "include", "local"
380 static int StackSize = 4;
381 static char *StackPointer = "ebp";
382 static int ArgOffset = 8;
383 static int LocalOffset = 0;
385 static Context *cstk;
386 static Include *istk;
387 static IncPath *ipath = NULL;
389 static int pass; /* HACK: pass 0 = generate dependencies only */
390 static StrList **dephead, **deptail; /* Dependency list */
392 static uint64_t unique; /* unique identifier numbers */
394 static Line *predef = NULL;
395 static bool do_predef;
397 static ListGen *list;
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 the array nasm_stdmac.
425 * This gives our position in the macro set, when we're processing it.
427 static macros_t *stdmacpos;
430 * The extra standard macros that come from the object format, if
431 * any.
433 static macros_t *extrastdmac = NULL;
434 static bool any_extrastdmac;
437 * Tokens are allocated in blocks to improve speed
439 #define TOKEN_BLOCKSIZE 4096
440 static Token *freeTokens = NULL;
441 struct Blocks {
442 Blocks *next;
443 void *chunk;
446 static Blocks blocks = { NULL, NULL };
449 * Forward declarations.
451 static Token *expand_mmac_params(Token * tline);
452 static Token *expand_smacro(Token * tline);
453 static Token *expand_id(Token * tline);
454 static Context *get_ctx(const char *name, const char **namep,
455 bool all_contexts);
456 static void make_tok_num(Token * tok, int64_t val);
457 static void error(int severity, const char *fmt, ...);
458 static void error_precond(int severity, const char *fmt, ...);
459 static void *new_Block(size_t size);
460 static void delete_Blocks(void);
461 static Token *new_Token(Token * next, enum pp_token_type type,
462 const char *text, int txtlen);
463 static Token *delete_Token(Token * t);
466 * Macros for safe checking of token pointers, avoid *(NULL)
468 #define tok_type_(x,t) ((x) && (x)->type == (t))
469 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
470 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
471 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
474 * nasm_unquote with error if the string contains NUL characters.
475 * If the string contains NUL characters, issue an error and return
476 * the C len, i.e. truncate at the NUL.
478 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
480 size_t len = nasm_unquote(qstr, NULL);
481 size_t clen = strlen(qstr);
483 if (len != clen)
484 error(ERR_NONFATAL, "NUL character in `%s' directive",
485 pp_directives[directive]);
487 return clen;
491 * Handle TASM specific directives, which do not contain a % in
492 * front of them. We do it here because I could not find any other
493 * place to do it for the moment, and it is a hack (ideally it would
494 * be nice to be able to use the NASM pre-processor to do it).
496 static char *check_tasm_directive(char *line)
498 int32_t i, j, k, m, len;
499 char *p, *q, *oldline, oldchar;
501 p = nasm_skip_spaces(line);
503 /* Binary search for the directive name */
504 i = -1;
505 j = ARRAY_SIZE(tasm_directives);
506 q = nasm_skip_word(p);
507 len = q - p;
508 if (len) {
509 oldchar = p[len];
510 p[len] = 0;
511 while (j - i > 1) {
512 k = (j + i) / 2;
513 m = nasm_stricmp(p, tasm_directives[k]);
514 if (m == 0) {
515 /* We have found a directive, so jam a % in front of it
516 * so that NASM will then recognise it as one if it's own.
518 p[len] = oldchar;
519 len = strlen(p);
520 oldline = line;
521 line = nasm_malloc(len + 2);
522 line[0] = '%';
523 if (k == TM_IFDIFI) {
525 * NASM does not recognise IFDIFI, so we convert
526 * it to %if 0. This is not used in NASM
527 * compatible code, but does need to parse for the
528 * TASM macro package.
530 strcpy(line + 1, "if 0");
531 } else {
532 memcpy(line + 1, p, len + 1);
534 nasm_free(oldline);
535 return line;
536 } else if (m < 0) {
537 j = k;
538 } else
539 i = k;
541 p[len] = oldchar;
543 return line;
547 * The pre-preprocessing stage... This function translates line
548 * number indications as they emerge from GNU cpp (`# lineno "file"
549 * flags') into NASM preprocessor line number indications (`%line
550 * lineno file').
552 static char *prepreproc(char *line)
554 int lineno, fnlen;
555 char *fname, *oldline;
557 if (line[0] == '#' && line[1] == ' ') {
558 oldline = line;
559 fname = oldline + 2;
560 lineno = atoi(fname);
561 fname += strspn(fname, "0123456789 ");
562 if (*fname == '"')
563 fname++;
564 fnlen = strcspn(fname, "\"");
565 line = nasm_malloc(20 + fnlen);
566 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
567 nasm_free(oldline);
569 if (tasm_compatible_mode)
570 return check_tasm_directive(line);
571 return line;
575 * Free a linked list of tokens.
577 static void free_tlist(Token * list)
579 while (list)
580 list = delete_Token(list);
584 * Free a linked list of lines.
586 static void free_llist(Line * list)
588 Line *l, *tmp;
589 list_for_each_safe(l, tmp, list) {
590 free_tlist(l->first);
591 nasm_free(l);
596 * Free an MMacro
598 static void free_mmacro(MMacro * m)
600 nasm_free(m->name);
601 free_tlist(m->dlist);
602 nasm_free(m->defaults);
603 free_llist(m->expansion);
604 nasm_free(m);
608 * Free all currently defined macros, and free the hash tables
610 static void free_smacro_table(struct hash_table *smt)
612 SMacro *s, *tmp;
613 const char *key;
614 struct hash_tbl_node *it = NULL;
616 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
617 nasm_free((void *)key);
618 list_for_each_safe(s, tmp, s) {
619 nasm_free(s->name);
620 free_tlist(s->expansion);
621 nasm_free(s);
624 hash_free(smt);
627 static void free_mmacro_table(struct hash_table *mmt)
629 MMacro *m, *tmp;
630 const char *key;
631 struct hash_tbl_node *it = NULL;
633 it = NULL;
634 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
635 nasm_free((void *)key);
636 list_for_each_safe(m ,tmp, m)
637 free_mmacro(m);
639 hash_free(mmt);
642 static void free_macros(void)
644 free_smacro_table(&smacros);
645 free_mmacro_table(&mmacros);
649 * Initialize the hash tables
651 static void init_macros(void)
653 hash_init(&smacros, HASH_LARGE);
654 hash_init(&mmacros, HASH_LARGE);
658 * Pop the context stack.
660 static void ctx_pop(void)
662 Context *c = cstk;
664 cstk = cstk->next;
665 free_smacro_table(&c->localmac);
666 nasm_free(c->name);
667 nasm_free(c);
671 * Search for a key in the hash index; adding it if necessary
672 * (in which case we initialize the data pointer to NULL.)
674 static void **
675 hash_findi_add(struct hash_table *hash, const char *str)
677 struct hash_insert hi;
678 void **r;
679 char *strx;
681 r = hash_findi(hash, str, &hi);
682 if (r)
683 return r;
685 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
686 return hash_add(&hi, strx, NULL);
690 * Like hash_findi, but returns the data element rather than a pointer
691 * to it. Used only when not adding a new element, hence no third
692 * argument.
694 static void *
695 hash_findix(struct hash_table *hash, const char *str)
697 void **p;
699 p = hash_findi(hash, str, NULL);
700 return p ? *p : NULL;
704 * read line from standart macros set,
705 * if there no more left -- return NULL
707 static char *line_from_stdmac(void)
709 unsigned char c;
710 const unsigned char *p = stdmacpos;
711 char *line, *q;
712 size_t len = 0;
714 if (!stdmacpos)
715 return NULL;
717 while ((c = *p++)) {
718 if (c >= 0x80)
719 len += pp_directives_len[c - 0x80] + 1;
720 else
721 len++;
724 line = nasm_malloc(len + 1);
725 q = line;
726 while ((c = *stdmacpos++)) {
727 if (c >= 0x80) {
728 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
729 q += pp_directives_len[c - 0x80];
730 *q++ = ' ';
731 } else {
732 *q++ = c;
735 stdmacpos = p;
736 *q = '\0';
738 if (!*stdmacpos) {
739 /* This was the last of the standard macro chain... */
740 stdmacpos = NULL;
741 if (any_extrastdmac) {
742 stdmacpos = extrastdmac;
743 any_extrastdmac = false;
744 } else if (do_predef) {
745 Line *pd, *l;
746 Token *head, **tail, *t;
749 * Nasty hack: here we push the contents of
750 * `predef' on to the top-level expansion stack,
751 * since this is the most convenient way to
752 * implement the pre-include and pre-define
753 * features.
755 list_for_each(pd, predef) {
756 head = NULL;
757 tail = &head;
758 list_for_each(t, pd->first) {
759 *tail = new_Token(NULL, t->type, t->text, 0);
760 tail = &(*tail)->next;
763 l = nasm_malloc(sizeof(Line));
764 l->next = istk->expansion;
765 l->first = head;
766 l->finishes = NULL;
768 istk->expansion = l;
770 do_predef = false;
774 return line;
777 #define BUF_DELTA 512
779 * Read a line from the top file in istk, handling multiple CR/LFs
780 * at the end of the line read, and handling spurious ^Zs. Will
781 * return lines from the standard macro set if this has not already
782 * been done.
784 static char *read_line(void)
786 char *buffer, *p, *q;
787 int bufsize, continued_count;
790 * standart macros set (predefined) goes first
792 p = line_from_stdmac();
793 if (p)
794 return p;
797 * regular read from a file
799 bufsize = BUF_DELTA;
800 buffer = nasm_malloc(BUF_DELTA);
801 p = buffer;
802 continued_count = 0;
803 while (1) {
804 q = fgets(p, bufsize - (p - buffer), istk->fp);
805 if (!q)
806 break;
807 p += strlen(p);
808 if (p > buffer && p[-1] == '\n') {
810 * Convert backslash-CRLF line continuation sequences into
811 * nothing at all (for DOS and Windows)
813 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
814 p -= 3;
815 *p = 0;
816 continued_count++;
819 * Also convert backslash-LF line continuation sequences into
820 * nothing at all (for Unix)
822 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
823 p -= 2;
824 *p = 0;
825 continued_count++;
826 } else {
827 break;
830 if (p - buffer > bufsize - 10) {
831 int32_t offset = p - buffer;
832 bufsize += BUF_DELTA;
833 buffer = nasm_realloc(buffer, bufsize);
834 p = buffer + offset; /* prevent stale-pointer problems */
838 if (!q && p == buffer) {
839 nasm_free(buffer);
840 return NULL;
843 src_set_linnum(src_get_linnum() + istk->lineinc +
844 (continued_count * istk->lineinc));
847 * Play safe: remove CRs as well as LFs, if any of either are
848 * present at the end of the line.
850 while (--p >= buffer && (*p == '\n' || *p == '\r'))
851 *p = '\0';
854 * Handle spurious ^Z, which may be inserted into source files
855 * by some file transfer utilities.
857 buffer[strcspn(buffer, "\032")] = '\0';
859 list->line(LIST_READ, buffer);
861 return buffer;
865 * Tokenize a line of text. This is a very simple process since we
866 * don't need to parse the value out of e.g. numeric tokens: we
867 * simply split one string into many.
869 static Token *tokenize(char *line)
871 char c, *p = line;
872 enum pp_token_type type;
873 Token *list = NULL;
874 Token *t, **tail = &list;
876 while (*line) {
877 p = line;
878 if (*p == '%') {
879 p++;
880 if (*p == '+' && !nasm_isdigit(p[1])) {
881 p++;
882 type = TOK_PASTE;
883 } else if (nasm_isdigit(*p) ||
884 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
885 do {
886 p++;
888 while (nasm_isdigit(*p));
889 type = TOK_PREPROC_ID;
890 } else if (*p == '{') {
891 p++;
892 while (*p && *p != '}') {
893 p[-1] = *p;
894 p++;
896 p[-1] = '\0';
897 if (*p)
898 p++;
899 type = TOK_PREPROC_ID;
900 } else if (*p == '[') {
901 int lvl = 1;
902 line += 2; /* Skip the leading %[ */
903 p++;
904 while (lvl && (c = *p++)) {
905 switch (c) {
906 case ']':
907 lvl--;
908 break;
909 case '%':
910 if (*p == '[')
911 lvl++;
912 break;
913 case '\'':
914 case '\"':
915 case '`':
916 p = nasm_skip_string(p - 1) + 1;
917 break;
918 default:
919 break;
922 p--;
923 if (*p)
924 *p++ = '\0';
925 if (lvl)
926 error(ERR_NONFATAL, "unterminated %[ construct");
927 type = TOK_INDIRECT;
928 } else if (*p == '?') {
929 type = TOK_PREPROC_Q; /* %? */
930 p++;
931 if (*p == '?') {
932 type = TOK_PREPROC_QQ; /* %?? */
933 p++;
935 } else if (*p == '!') {
936 type = TOK_PREPROC_ID;
937 p++;
938 if (isidchar(*p)) {
939 do {
940 p++;
942 while (isidchar(*p));
943 } else if (*p == '\'' || *p == '\"' || *p == '`') {
944 p = nasm_skip_string(p);
945 if (*p)
946 p++;
947 else
948 error(ERR_NONFATAL|ERR_PASS1, "unterminated %! string");
949 } else {
950 /* %! without string or identifier */
951 type = TOK_OTHER; /* Legacy behavior... */
953 } else if (isidchar(*p) ||
954 ((*p == '!' || *p == '%' || *p == '$') &&
955 isidchar(p[1]))) {
956 do {
957 p++;
959 while (isidchar(*p));
960 type = TOK_PREPROC_ID;
961 } else {
962 type = TOK_OTHER;
963 if (*p == '%')
964 p++;
966 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
967 type = TOK_ID;
968 p++;
969 while (*p && isidchar(*p))
970 p++;
971 } else if (*p == '\'' || *p == '"' || *p == '`') {
973 * A string token.
975 type = TOK_STRING;
976 p = nasm_skip_string(p);
978 if (*p) {
979 p++;
980 } else {
981 error(ERR_WARNING|ERR_PASS1, "unterminated string");
982 /* Handling unterminated strings by UNV */
983 /* type = -1; */
985 } else if (p[0] == '$' && p[1] == '$') {
986 type = TOK_OTHER; /* TOKEN_BASE */
987 p += 2;
988 } else if (isnumstart(*p)) {
989 bool is_hex = false;
990 bool is_float = false;
991 bool has_e = false;
992 char c, *r;
995 * A numeric token.
998 if (*p == '$') {
999 p++;
1000 is_hex = true;
1003 for (;;) {
1004 c = *p++;
1006 if (!is_hex && (c == 'e' || c == 'E')) {
1007 has_e = true;
1008 if (*p == '+' || *p == '-') {
1010 * e can only be followed by +/- if it is either a
1011 * prefixed hex number or a floating-point number
1013 p++;
1014 is_float = true;
1016 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1017 is_hex = true;
1018 } else if (c == 'P' || c == 'p') {
1019 is_float = true;
1020 if (*p == '+' || *p == '-')
1021 p++;
1022 } else if (isnumchar(c) || c == '_')
1023 ; /* just advance */
1024 else if (c == '.') {
1026 * we need to deal with consequences of the legacy
1027 * parser, like "1.nolist" being two tokens
1028 * (TOK_NUMBER, TOK_ID) here; at least give it
1029 * a shot for now. In the future, we probably need
1030 * a flex-based scanner with proper pattern matching
1031 * to do it as well as it can be done. Nothing in
1032 * the world is going to help the person who wants
1033 * 0x123.p16 interpreted as two tokens, though.
1035 r = p;
1036 while (*r == '_')
1037 r++;
1039 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1040 (!is_hex && (*r == 'e' || *r == 'E')) ||
1041 (*r == 'p' || *r == 'P')) {
1042 p = r;
1043 is_float = true;
1044 } else
1045 break; /* Terminate the token */
1046 } else
1047 break;
1049 p--; /* Point to first character beyond number */
1051 if (p == line+1 && *line == '$') {
1052 type = TOK_OTHER; /* TOKEN_HERE */
1053 } else {
1054 if (has_e && !is_hex) {
1055 /* 1e13 is floating-point, but 1e13h is not */
1056 is_float = true;
1059 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1061 } else if (nasm_isspace(*p)) {
1062 type = TOK_WHITESPACE;
1063 p = nasm_skip_spaces(p);
1065 * Whitespace just before end-of-line is discarded by
1066 * pretending it's a comment; whitespace just before a
1067 * comment gets lumped into the comment.
1069 if (!*p || *p == ';') {
1070 type = TOK_COMMENT;
1071 while (*p)
1072 p++;
1074 } else if (*p == ';') {
1075 type = TOK_COMMENT;
1076 while (*p)
1077 p++;
1078 } else {
1080 * Anything else is an operator of some kind. We check
1081 * for all the double-character operators (>>, <<, //,
1082 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1083 * else is a single-character operator.
1085 type = TOK_OTHER;
1086 if ((p[0] == '>' && p[1] == '>') ||
1087 (p[0] == '<' && p[1] == '<') ||
1088 (p[0] == '/' && p[1] == '/') ||
1089 (p[0] == '<' && p[1] == '=') ||
1090 (p[0] == '>' && p[1] == '=') ||
1091 (p[0] == '=' && p[1] == '=') ||
1092 (p[0] == '!' && p[1] == '=') ||
1093 (p[0] == '<' && p[1] == '>') ||
1094 (p[0] == '&' && p[1] == '&') ||
1095 (p[0] == '|' && p[1] == '|') ||
1096 (p[0] == '^' && p[1] == '^')) {
1097 p++;
1099 p++;
1102 /* Handling unterminated string by UNV */
1103 /*if (type == -1)
1105 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1106 t->text[p-line] = *line;
1107 tail = &t->next;
1109 else */
1110 if (type != TOK_COMMENT) {
1111 *tail = t = new_Token(NULL, type, line, p - line);
1112 tail = &t->next;
1114 line = p;
1116 return list;
1120 * this function allocates a new managed block of memory and
1121 * returns a pointer to the block. The managed blocks are
1122 * deleted only all at once by the delete_Blocks function.
1124 static void *new_Block(size_t size)
1126 Blocks *b = &blocks;
1128 /* first, get to the end of the linked list */
1129 while (b->next)
1130 b = b->next;
1131 /* now allocate the requested chunk */
1132 b->chunk = nasm_malloc(size);
1134 /* now allocate a new block for the next request */
1135 b->next = nasm_malloc(sizeof(Blocks));
1136 /* and initialize the contents of the new block */
1137 b->next->next = NULL;
1138 b->next->chunk = NULL;
1139 return b->chunk;
1143 * this function deletes all managed blocks of memory
1145 static void delete_Blocks(void)
1147 Blocks *a, *b = &blocks;
1150 * keep in mind that the first block, pointed to by blocks
1151 * is a static and not dynamically allocated, so we don't
1152 * free it.
1154 while (b) {
1155 if (b->chunk)
1156 nasm_free(b->chunk);
1157 a = b;
1158 b = b->next;
1159 if (a != &blocks)
1160 nasm_free(a);
1165 * this function creates a new Token and passes a pointer to it
1166 * back to the caller. It sets the type and text elements, and
1167 * also the a.mac and next elements to NULL.
1169 static Token *new_Token(Token * next, enum pp_token_type type,
1170 const char *text, int txtlen)
1172 Token *t;
1173 int i;
1175 if (!freeTokens) {
1176 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1177 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1178 freeTokens[i].next = &freeTokens[i + 1];
1179 freeTokens[i].next = NULL;
1181 t = freeTokens;
1182 freeTokens = t->next;
1183 t->next = next;
1184 t->a.mac = NULL;
1185 t->type = type;
1186 if (type == TOK_WHITESPACE || !text) {
1187 t->text = NULL;
1188 } else {
1189 if (txtlen == 0)
1190 txtlen = strlen(text);
1191 t->text = nasm_malloc(txtlen+1);
1192 memcpy(t->text, text, txtlen);
1193 t->text[txtlen] = '\0';
1195 return t;
1198 static Token *delete_Token(Token * t)
1200 Token *next = t->next;
1201 nasm_free(t->text);
1202 t->next = freeTokens;
1203 freeTokens = t;
1204 return next;
1208 * Convert a line of tokens back into text.
1209 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1210 * will be transformed into ..@ctxnum.xxx
1212 static char *detoken(Token * tlist, bool expand_locals)
1214 Token *t;
1215 char *line, *p;
1216 const char *q;
1217 int len = 0;
1219 list_for_each(t, tlist) {
1220 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1221 char *v;
1222 char *q = t->text;
1224 v = t->text + 2;
1225 if (*v == '\'' || *v == '\"' || *v == '`') {
1226 size_t len = nasm_unquote(v, NULL);
1227 size_t clen = strlen(v);
1229 if (len != clen) {
1230 error(ERR_NONFATAL | ERR_PASS1,
1231 "NUL character in %! string");
1232 v = NULL;
1236 if (v) {
1237 char *p = getenv(v);
1238 if (!p) {
1239 error(ERR_NONFATAL | ERR_PASS1,
1240 "nonexistent environment variable `%s'", v);
1241 p = "";
1243 t->text = nasm_strdup(p);
1245 nasm_free(q);
1248 /* Expand local macros here and not during preprocessing */
1249 if (expand_locals &&
1250 t->type == TOK_PREPROC_ID && t->text &&
1251 t->text[0] == '%' && t->text[1] == '$') {
1252 const char *q;
1253 char *p;
1254 Context *ctx = get_ctx(t->text, &q, false);
1255 if (ctx) {
1256 char buffer[40];
1257 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1258 p = nasm_strcat(buffer, q);
1259 nasm_free(t->text);
1260 t->text = p;
1263 if (t->type == TOK_WHITESPACE)
1264 len++;
1265 else if (t->text)
1266 len += strlen(t->text);
1269 p = line = nasm_malloc(len + 1);
1271 list_for_each(t, tlist) {
1272 if (t->type == TOK_WHITESPACE) {
1273 *p++ = ' ';
1274 } else if (t->text) {
1275 q = t->text;
1276 while (*q)
1277 *p++ = *q++;
1280 *p = '\0';
1282 return line;
1286 * A scanner, suitable for use by the expression evaluator, which
1287 * operates on a line of Tokens. Expects a pointer to a pointer to
1288 * the first token in the line to be passed in as its private_data
1289 * field.
1291 * FIX: This really needs to be unified with stdscan.
1293 static int ppscan(void *private_data, struct tokenval *tokval)
1295 Token **tlineptr = private_data;
1296 Token *tline;
1297 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1299 do {
1300 tline = *tlineptr;
1301 *tlineptr = tline ? tline->next : NULL;
1302 } while (tline && (tline->type == TOK_WHITESPACE ||
1303 tline->type == TOK_COMMENT));
1305 if (!tline)
1306 return tokval->t_type = TOKEN_EOS;
1308 tokval->t_charptr = tline->text;
1310 if (tline->text[0] == '$' && !tline->text[1])
1311 return tokval->t_type = TOKEN_HERE;
1312 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1313 return tokval->t_type = TOKEN_BASE;
1315 if (tline->type == TOK_ID) {
1316 p = tokval->t_charptr = tline->text;
1317 if (p[0] == '$') {
1318 tokval->t_charptr++;
1319 return tokval->t_type = TOKEN_ID;
1322 for (r = p, s = ourcopy; *r; r++) {
1323 if (r >= p+MAX_KEYWORD)
1324 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1325 *s++ = nasm_tolower(*r);
1327 *s = '\0';
1328 /* right, so we have an identifier sitting in temp storage. now,
1329 * is it actually a register or instruction name, or what? */
1330 return nasm_token_hash(ourcopy, tokval);
1333 if (tline->type == TOK_NUMBER) {
1334 bool rn_error;
1335 tokval->t_integer = readnum(tline->text, &rn_error);
1336 tokval->t_charptr = tline->text;
1337 if (rn_error)
1338 return tokval->t_type = TOKEN_ERRNUM;
1339 else
1340 return tokval->t_type = TOKEN_NUM;
1343 if (tline->type == TOK_FLOAT) {
1344 return tokval->t_type = TOKEN_FLOAT;
1347 if (tline->type == TOK_STRING) {
1348 char bq, *ep;
1350 bq = tline->text[0];
1351 tokval->t_charptr = tline->text;
1352 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1354 if (ep[0] != bq || ep[1] != '\0')
1355 return tokval->t_type = TOKEN_ERRSTR;
1356 else
1357 return tokval->t_type = TOKEN_STR;
1360 if (tline->type == TOK_OTHER) {
1361 if (!strcmp(tline->text, "<<"))
1362 return tokval->t_type = TOKEN_SHL;
1363 if (!strcmp(tline->text, ">>"))
1364 return tokval->t_type = TOKEN_SHR;
1365 if (!strcmp(tline->text, "//"))
1366 return tokval->t_type = TOKEN_SDIV;
1367 if (!strcmp(tline->text, "%%"))
1368 return tokval->t_type = TOKEN_SMOD;
1369 if (!strcmp(tline->text, "=="))
1370 return tokval->t_type = TOKEN_EQ;
1371 if (!strcmp(tline->text, "<>"))
1372 return tokval->t_type = TOKEN_NE;
1373 if (!strcmp(tline->text, "!="))
1374 return tokval->t_type = TOKEN_NE;
1375 if (!strcmp(tline->text, "<="))
1376 return tokval->t_type = TOKEN_LE;
1377 if (!strcmp(tline->text, ">="))
1378 return tokval->t_type = TOKEN_GE;
1379 if (!strcmp(tline->text, "&&"))
1380 return tokval->t_type = TOKEN_DBL_AND;
1381 if (!strcmp(tline->text, "^^"))
1382 return tokval->t_type = TOKEN_DBL_XOR;
1383 if (!strcmp(tline->text, "||"))
1384 return tokval->t_type = TOKEN_DBL_OR;
1388 * We have no other options: just return the first character of
1389 * the token text.
1391 return tokval->t_type = tline->text[0];
1395 * Compare a string to the name of an existing macro; this is a
1396 * simple wrapper which calls either strcmp or nasm_stricmp
1397 * depending on the value of the `casesense' parameter.
1399 static int mstrcmp(const char *p, const char *q, bool casesense)
1401 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1405 * Compare a string to the name of an existing macro; this is a
1406 * simple wrapper which calls either strcmp or nasm_stricmp
1407 * depending on the value of the `casesense' parameter.
1409 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1411 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1415 * Return the Context structure associated with a %$ token. Return
1416 * NULL, having _already_ reported an error condition, if the
1417 * context stack isn't deep enough for the supplied number of $
1418 * signs.
1419 * If all_contexts == true, contexts that enclose current are
1420 * also scanned for such smacro, until it is found; if not -
1421 * only the context that directly results from the number of $'s
1422 * in variable's name.
1424 * If "namep" is non-NULL, set it to the pointer to the macro name
1425 * tail, i.e. the part beyond %$...
1427 static Context *get_ctx(const char *name, const char **namep,
1428 bool all_contexts)
1430 Context *ctx;
1431 SMacro *m;
1432 int i;
1434 if (namep)
1435 *namep = name;
1437 if (!name || name[0] != '%' || name[1] != '$')
1438 return NULL;
1440 if (!cstk) {
1441 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1442 return NULL;
1445 name += 2;
1446 ctx = cstk;
1447 i = 0;
1448 while (ctx && *name == '$') {
1449 name++;
1450 i++;
1451 ctx = ctx->next;
1453 if (!ctx) {
1454 error(ERR_NONFATAL, "`%s': context stack is only"
1455 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1456 return NULL;
1459 if (namep)
1460 *namep = name;
1462 if (!all_contexts)
1463 return ctx;
1465 do {
1466 /* Search for this smacro in found context */
1467 m = hash_findix(&ctx->localmac, name);
1468 while (m) {
1469 if (!mstrcmp(m->name, name, m->casesense)) {
1470 if ((i > 0) && (all_contexts == true)) {
1471 error(ERR_WARNING, "context-local label expansion"
1472 " to outer contexts will be deprecated"
1473 " starting in NASM 2.10, please update your"
1474 " code accordingly");
1476 return ctx;
1478 m = m->next;
1480 ctx = ctx->next;
1482 while (ctx);
1483 return NULL;
1487 * Check to see if a file is already in a string list
1489 static bool in_list(const StrList *list, const char *str)
1491 while (list) {
1492 if (!strcmp(list->str, str))
1493 return true;
1494 list = list->next;
1496 return false;
1500 * Open an include file. This routine must always return a valid
1501 * file pointer if it returns - it's responsible for throwing an
1502 * ERR_FATAL and bombing out completely if not. It should also try
1503 * the include path one by one until it finds the file or reaches
1504 * the end of the path.
1506 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1507 bool missing_ok)
1509 FILE *fp;
1510 char *prefix = "";
1511 IncPath *ip = ipath;
1512 int len = strlen(file);
1513 size_t prefix_len = 0;
1514 StrList *sl;
1516 while (1) {
1517 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1518 memcpy(sl->str, prefix, prefix_len);
1519 memcpy(sl->str+prefix_len, file, len+1);
1520 fp = fopen(sl->str, "r");
1521 if (fp && dhead && !in_list(*dhead, sl->str)) {
1522 sl->next = NULL;
1523 **dtail = sl;
1524 *dtail = &sl->next;
1525 } else {
1526 nasm_free(sl);
1528 if (fp)
1529 return fp;
1530 if (!ip) {
1531 if (!missing_ok)
1532 break;
1533 prefix = NULL;
1534 } else {
1535 prefix = ip->path;
1536 ip = ip->next;
1538 if (prefix) {
1539 prefix_len = strlen(prefix);
1540 } else {
1541 /* -MG given and file not found */
1542 if (dhead && !in_list(*dhead, file)) {
1543 sl = nasm_malloc(len+1+sizeof sl->next);
1544 sl->next = NULL;
1545 strcpy(sl->str, file);
1546 **dtail = sl;
1547 *dtail = &sl->next;
1549 return NULL;
1553 error(ERR_FATAL, "unable to open include file `%s'", file);
1554 return NULL;
1558 * Determine if we should warn on defining a single-line macro of
1559 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1560 * return true if _any_ single-line macro of that name is defined.
1561 * Otherwise, will return true if a single-line macro with either
1562 * `nparam' or no parameters is defined.
1564 * If a macro with precisely the right number of parameters is
1565 * defined, or nparam is -1, the address of the definition structure
1566 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1567 * is NULL, no action will be taken regarding its contents, and no
1568 * error will occur.
1570 * Note that this is also called with nparam zero to resolve
1571 * `ifdef'.
1573 * If you already know which context macro belongs to, you can pass
1574 * the context pointer as first parameter; if you won't but name begins
1575 * with %$ the context will be automatically computed. If all_contexts
1576 * is true, macro will be searched in outer contexts as well.
1578 static bool
1579 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1580 bool nocase)
1582 struct hash_table *smtbl;
1583 SMacro *m;
1585 if (ctx) {
1586 smtbl = &ctx->localmac;
1587 } else if (name[0] == '%' && name[1] == '$') {
1588 if (cstk)
1589 ctx = get_ctx(name, &name, false);
1590 if (!ctx)
1591 return false; /* got to return _something_ */
1592 smtbl = &ctx->localmac;
1593 } else {
1594 smtbl = &smacros;
1596 m = (SMacro *) hash_findix(smtbl, name);
1598 while (m) {
1599 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1600 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1601 if (defn) {
1602 if (nparam == (int) m->nparam || nparam == -1)
1603 *defn = m;
1604 else
1605 *defn = NULL;
1607 return true;
1609 m = m->next;
1612 return false;
1616 * Count and mark off the parameters in a multi-line macro call.
1617 * This is called both from within the multi-line macro expansion
1618 * code, and also to mark off the default parameters when provided
1619 * in a %macro definition line.
1621 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1623 int paramsize, brace;
1625 *nparam = paramsize = 0;
1626 *params = NULL;
1627 while (t) {
1628 /* +1: we need space for the final NULL */
1629 if (*nparam+1 >= paramsize) {
1630 paramsize += PARAM_DELTA;
1631 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1633 skip_white_(t);
1634 brace = false;
1635 if (tok_is_(t, "{"))
1636 brace = true;
1637 (*params)[(*nparam)++] = t;
1638 while (tok_isnt_(t, brace ? "}" : ","))
1639 t = t->next;
1640 if (t) { /* got a comma/brace */
1641 t = t->next;
1642 if (brace) {
1644 * Now we've found the closing brace, look further
1645 * for the comma.
1647 skip_white_(t);
1648 if (tok_isnt_(t, ",")) {
1649 error(ERR_NONFATAL,
1650 "braces do not enclose all of macro parameter");
1651 while (tok_isnt_(t, ","))
1652 t = t->next;
1654 if (t)
1655 t = t->next; /* eat the comma */
1662 * Determine whether one of the various `if' conditions is true or
1663 * not.
1665 * We must free the tline we get passed.
1667 static bool if_condition(Token * tline, enum preproc_token ct)
1669 enum pp_conditional i = PP_COND(ct);
1670 bool j;
1671 Token *t, *tt, **tptr, *origline;
1672 struct tokenval tokval;
1673 expr *evalresult;
1674 enum pp_token_type needtype;
1675 char *p;
1677 origline = tline;
1679 switch (i) {
1680 case PPC_IFCTX:
1681 j = false; /* have we matched yet? */
1682 while (true) {
1683 skip_white_(tline);
1684 if (!tline)
1685 break;
1686 if (tline->type != TOK_ID) {
1687 error(ERR_NONFATAL,
1688 "`%s' expects context identifiers", pp_directives[ct]);
1689 free_tlist(origline);
1690 return -1;
1692 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1693 j = true;
1694 tline = tline->next;
1696 break;
1698 case PPC_IFDEF:
1699 j = false; /* have we matched yet? */
1700 while (tline) {
1701 skip_white_(tline);
1702 if (!tline || (tline->type != TOK_ID &&
1703 (tline->type != TOK_PREPROC_ID ||
1704 tline->text[1] != '$'))) {
1705 error(ERR_NONFATAL,
1706 "`%s' expects macro identifiers", pp_directives[ct]);
1707 goto fail;
1709 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1710 j = true;
1711 tline = tline->next;
1713 break;
1715 case PPC_IFENV:
1716 tline = expand_smacro(tline);
1717 j = false; /* have we matched yet? */
1718 while (tline) {
1719 skip_white_(tline);
1720 if (!tline || (tline->type != TOK_ID &&
1721 tline->type != TOK_STRING &&
1722 (tline->type != TOK_PREPROC_ID ||
1723 tline->text[1] != '!'))) {
1724 error(ERR_NONFATAL,
1725 "`%s' expects environment variable names",
1726 pp_directives[ct]);
1727 goto fail;
1729 p = tline->text;
1730 if (tline->type == TOK_PREPROC_ID)
1731 p += 2; /* Skip leading %! */
1732 if (*p == '\'' || *p == '\"' || *p == '`')
1733 nasm_unquote_cstr(p, ct);
1734 if (getenv(p))
1735 j = true;
1736 tline = tline->next;
1738 break;
1740 case PPC_IFIDN:
1741 case PPC_IFIDNI:
1742 tline = expand_smacro(tline);
1743 t = tt = tline;
1744 while (tok_isnt_(tt, ","))
1745 tt = tt->next;
1746 if (!tt) {
1747 error(ERR_NONFATAL,
1748 "`%s' expects two comma-separated arguments",
1749 pp_directives[ct]);
1750 goto fail;
1752 tt = tt->next;
1753 j = true; /* assume equality unless proved not */
1754 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1755 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1756 error(ERR_NONFATAL, "`%s': more than one comma on line",
1757 pp_directives[ct]);
1758 goto fail;
1760 if (t->type == TOK_WHITESPACE) {
1761 t = t->next;
1762 continue;
1764 if (tt->type == TOK_WHITESPACE) {
1765 tt = tt->next;
1766 continue;
1768 if (tt->type != t->type) {
1769 j = false; /* found mismatching tokens */
1770 break;
1772 /* When comparing strings, need to unquote them first */
1773 if (t->type == TOK_STRING) {
1774 size_t l1 = nasm_unquote(t->text, NULL);
1775 size_t l2 = nasm_unquote(tt->text, NULL);
1777 if (l1 != l2) {
1778 j = false;
1779 break;
1781 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1782 j = false;
1783 break;
1785 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1786 j = false; /* found mismatching tokens */
1787 break;
1790 t = t->next;
1791 tt = tt->next;
1793 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1794 j = false; /* trailing gunk on one end or other */
1795 break;
1797 case PPC_IFMACRO:
1799 bool found = false;
1800 MMacro searching, *mmac;
1802 skip_white_(tline);
1803 tline = expand_id(tline);
1804 if (!tok_type_(tline, TOK_ID)) {
1805 error(ERR_NONFATAL,
1806 "`%s' expects a macro name", pp_directives[ct]);
1807 goto fail;
1809 searching.name = nasm_strdup(tline->text);
1810 searching.casesense = true;
1811 searching.plus = false;
1812 searching.nolist = false;
1813 searching.in_progress = 0;
1814 searching.max_depth = 0;
1815 searching.rep_nest = NULL;
1816 searching.nparam_min = 0;
1817 searching.nparam_max = INT_MAX;
1818 tline = expand_smacro(tline->next);
1819 skip_white_(tline);
1820 if (!tline) {
1821 } else if (!tok_type_(tline, TOK_NUMBER)) {
1822 error(ERR_NONFATAL,
1823 "`%s' expects a parameter count or nothing",
1824 pp_directives[ct]);
1825 } else {
1826 searching.nparam_min = searching.nparam_max =
1827 readnum(tline->text, &j);
1828 if (j)
1829 error(ERR_NONFATAL,
1830 "unable to parse parameter count `%s'",
1831 tline->text);
1833 if (tline && tok_is_(tline->next, "-")) {
1834 tline = tline->next->next;
1835 if (tok_is_(tline, "*"))
1836 searching.nparam_max = INT_MAX;
1837 else if (!tok_type_(tline, TOK_NUMBER))
1838 error(ERR_NONFATAL,
1839 "`%s' expects a parameter count after `-'",
1840 pp_directives[ct]);
1841 else {
1842 searching.nparam_max = readnum(tline->text, &j);
1843 if (j)
1844 error(ERR_NONFATAL,
1845 "unable to parse parameter count `%s'",
1846 tline->text);
1847 if (searching.nparam_min > searching.nparam_max)
1848 error(ERR_NONFATAL,
1849 "minimum parameter count exceeds maximum");
1852 if (tline && tok_is_(tline->next, "+")) {
1853 tline = tline->next;
1854 searching.plus = true;
1856 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1857 while (mmac) {
1858 if (!strcmp(mmac->name, searching.name) &&
1859 (mmac->nparam_min <= searching.nparam_max
1860 || searching.plus)
1861 && (searching.nparam_min <= mmac->nparam_max
1862 || mmac->plus)) {
1863 found = true;
1864 break;
1866 mmac = mmac->next;
1868 if (tline && tline->next)
1869 error(ERR_WARNING|ERR_PASS1,
1870 "trailing garbage after %%ifmacro ignored");
1871 nasm_free(searching.name);
1872 j = found;
1873 break;
1876 case PPC_IFID:
1877 needtype = TOK_ID;
1878 goto iftype;
1879 case PPC_IFNUM:
1880 needtype = TOK_NUMBER;
1881 goto iftype;
1882 case PPC_IFSTR:
1883 needtype = TOK_STRING;
1884 goto iftype;
1886 iftype:
1887 t = tline = expand_smacro(tline);
1889 while (tok_type_(t, TOK_WHITESPACE) ||
1890 (needtype == TOK_NUMBER &&
1891 tok_type_(t, TOK_OTHER) &&
1892 (t->text[0] == '-' || t->text[0] == '+') &&
1893 !t->text[1]))
1894 t = t->next;
1896 j = tok_type_(t, needtype);
1897 break;
1899 case PPC_IFTOKEN:
1900 t = tline = expand_smacro(tline);
1901 while (tok_type_(t, TOK_WHITESPACE))
1902 t = t->next;
1904 j = false;
1905 if (t) {
1906 t = t->next; /* Skip the actual token */
1907 while (tok_type_(t, TOK_WHITESPACE))
1908 t = t->next;
1909 j = !t; /* Should be nothing left */
1911 break;
1913 case PPC_IFEMPTY:
1914 t = tline = expand_smacro(tline);
1915 while (tok_type_(t, TOK_WHITESPACE))
1916 t = t->next;
1918 j = !t; /* Should be empty */
1919 break;
1921 case PPC_IF:
1922 t = tline = expand_smacro(tline);
1923 tptr = &t;
1924 tokval.t_type = TOKEN_INVALID;
1925 evalresult = evaluate(ppscan, tptr, &tokval,
1926 NULL, pass | CRITICAL, error, NULL);
1927 if (!evalresult)
1928 return -1;
1929 if (tokval.t_type)
1930 error(ERR_WARNING|ERR_PASS1,
1931 "trailing garbage after expression ignored");
1932 if (!is_simple(evalresult)) {
1933 error(ERR_NONFATAL,
1934 "non-constant value given to `%s'", pp_directives[ct]);
1935 goto fail;
1937 j = reloc_value(evalresult) != 0;
1938 break;
1940 default:
1941 error(ERR_FATAL,
1942 "preprocessor directive `%s' not yet implemented",
1943 pp_directives[ct]);
1944 goto fail;
1947 free_tlist(origline);
1948 return j ^ PP_NEGATIVE(ct);
1950 fail:
1951 free_tlist(origline);
1952 return -1;
1956 * Common code for defining an smacro
1958 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1959 int nparam, Token *expansion)
1961 SMacro *smac, **smhead;
1962 struct hash_table *smtbl;
1964 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1965 if (!smac) {
1966 error(ERR_WARNING|ERR_PASS1,
1967 "single-line macro `%s' defined both with and"
1968 " without parameters", mname);
1970 * Some instances of the old code considered this a failure,
1971 * some others didn't. What is the right thing to do here?
1973 free_tlist(expansion);
1974 return false; /* Failure */
1975 } else {
1977 * We're redefining, so we have to take over an
1978 * existing SMacro structure. This means freeing
1979 * what was already in it.
1981 nasm_free(smac->name);
1982 free_tlist(smac->expansion);
1984 } else {
1985 smtbl = ctx ? &ctx->localmac : &smacros;
1986 smhead = (SMacro **) hash_findi_add(smtbl, mname);
1987 smac = nasm_malloc(sizeof(SMacro));
1988 smac->next = *smhead;
1989 *smhead = smac;
1991 smac->name = nasm_strdup(mname);
1992 smac->casesense = casesense;
1993 smac->nparam = nparam;
1994 smac->expansion = expansion;
1995 smac->in_progress = false;
1996 return true; /* Success */
2000 * Undefine an smacro
2002 static void undef_smacro(Context *ctx, const char *mname)
2004 SMacro **smhead, *s, **sp;
2005 struct hash_table *smtbl;
2007 smtbl = ctx ? &ctx->localmac : &smacros;
2008 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2010 if (smhead) {
2012 * We now have a macro name... go hunt for it.
2014 sp = smhead;
2015 while ((s = *sp) != NULL) {
2016 if (!mstrcmp(s->name, mname, s->casesense)) {
2017 *sp = s->next;
2018 nasm_free(s->name);
2019 free_tlist(s->expansion);
2020 nasm_free(s);
2021 } else {
2022 sp = &s->next;
2029 * Parse a mmacro specification.
2031 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2033 bool err;
2035 tline = tline->next;
2036 skip_white_(tline);
2037 tline = expand_id(tline);
2038 if (!tok_type_(tline, TOK_ID)) {
2039 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2040 return false;
2043 def->prev = NULL;
2044 def->name = nasm_strdup(tline->text);
2045 def->plus = false;
2046 def->nolist = false;
2047 def->in_progress = 0;
2048 def->rep_nest = NULL;
2049 def->nparam_min = 0;
2050 def->nparam_max = 0;
2052 tline = expand_smacro(tline->next);
2053 skip_white_(tline);
2054 if (!tok_type_(tline, TOK_NUMBER)) {
2055 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2056 } else {
2057 def->nparam_min = def->nparam_max =
2058 readnum(tline->text, &err);
2059 if (err)
2060 error(ERR_NONFATAL,
2061 "unable to parse parameter count `%s'", tline->text);
2063 if (tline && tok_is_(tline->next, "-")) {
2064 tline = tline->next->next;
2065 if (tok_is_(tline, "*")) {
2066 def->nparam_max = INT_MAX;
2067 } else if (!tok_type_(tline, TOK_NUMBER)) {
2068 error(ERR_NONFATAL,
2069 "`%s' expects a parameter count after `-'", directive);
2070 } else {
2071 def->nparam_max = readnum(tline->text, &err);
2072 if (err) {
2073 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2074 tline->text);
2076 if (def->nparam_min > def->nparam_max) {
2077 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2081 if (tline && tok_is_(tline->next, "+")) {
2082 tline = tline->next;
2083 def->plus = true;
2085 if (tline && tok_type_(tline->next, TOK_ID) &&
2086 !nasm_stricmp(tline->next->text, ".nolist")) {
2087 tline = tline->next;
2088 def->nolist = true;
2092 * Handle default parameters.
2094 if (tline && tline->next) {
2095 def->dlist = tline->next;
2096 tline->next = NULL;
2097 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2098 } else {
2099 def->dlist = NULL;
2100 def->defaults = NULL;
2102 def->expansion = NULL;
2104 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2105 !def->plus)
2106 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2107 "too many default macro parameters");
2109 return true;
2114 * Decode a size directive
2116 static int parse_size(const char *str) {
2117 static const char *size_names[] =
2118 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2119 static const int sizes[] =
2120 { 0, 1, 4, 16, 8, 10, 2, 32 };
2122 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2126 * find and process preprocessor directive in passed line
2127 * Find out if a line contains a preprocessor directive, and deal
2128 * with it if so.
2130 * If a directive _is_ found, it is the responsibility of this routine
2131 * (and not the caller) to free_tlist() the line.
2133 * @param tline a pointer to the current tokeninzed line linked list
2134 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2137 static int do_directive(Token * tline)
2139 enum preproc_token i;
2140 int j;
2141 bool err;
2142 int nparam;
2143 bool nolist;
2144 bool casesense;
2145 int k, m;
2146 int offset;
2147 char *p, *pp;
2148 const char *mname;
2149 Include *inc;
2150 Context *ctx;
2151 Cond *cond;
2152 MMacro *mmac, **mmhead;
2153 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2154 Line *l;
2155 struct tokenval tokval;
2156 expr *evalresult;
2157 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2158 int64_t count;
2159 size_t len;
2160 int severity;
2162 origline = tline;
2164 skip_white_(tline);
2165 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2166 (tline->text[1] == '%' || tline->text[1] == '$'
2167 || tline->text[1] == '!'))
2168 return NO_DIRECTIVE_FOUND;
2170 i = pp_token_hash(tline->text);
2173 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2174 * since they are known to be buggy at moment, we need to fix them
2175 * in future release (2.09-2.10)
2177 if (i == PP_RMACRO || i == PP_RMACRO || i == PP_EXITMACRO) {
2178 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2179 tline->text);
2180 return NO_DIRECTIVE_FOUND;
2184 * If we're in a non-emitting branch of a condition construct,
2185 * or walking to the end of an already terminated %rep block,
2186 * we should ignore all directives except for condition
2187 * directives.
2189 if (((istk->conds && !emitting(istk->conds->state)) ||
2190 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2191 return NO_DIRECTIVE_FOUND;
2195 * If we're defining a macro or reading a %rep block, we should
2196 * ignore all directives except for %macro/%imacro (which nest),
2197 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2198 * If we're in a %rep block, another %rep nests, so should be let through.
2200 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2201 i != PP_RMACRO && i != PP_IRMACRO &&
2202 i != PP_ENDMACRO && i != PP_ENDM &&
2203 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2204 return NO_DIRECTIVE_FOUND;
2207 if (defining) {
2208 if (i == PP_MACRO || i == PP_IMACRO ||
2209 i == PP_RMACRO || i == PP_IRMACRO) {
2210 nested_mac_count++;
2211 return NO_DIRECTIVE_FOUND;
2212 } else if (nested_mac_count > 0) {
2213 if (i == PP_ENDMACRO) {
2214 nested_mac_count--;
2215 return NO_DIRECTIVE_FOUND;
2218 if (!defining->name) {
2219 if (i == PP_REP) {
2220 nested_rep_count++;
2221 return NO_DIRECTIVE_FOUND;
2222 } else if (nested_rep_count > 0) {
2223 if (i == PP_ENDREP) {
2224 nested_rep_count--;
2225 return NO_DIRECTIVE_FOUND;
2231 switch (i) {
2232 case PP_INVALID:
2233 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2234 tline->text);
2235 return NO_DIRECTIVE_FOUND; /* didn't get it */
2237 case PP_STACKSIZE:
2238 /* Directive to tell NASM what the default stack size is. The
2239 * default is for a 16-bit stack, and this can be overriden with
2240 * %stacksize large.
2242 tline = tline->next;
2243 if (tline && tline->type == TOK_WHITESPACE)
2244 tline = tline->next;
2245 if (!tline || tline->type != TOK_ID) {
2246 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2247 free_tlist(origline);
2248 return DIRECTIVE_FOUND;
2250 if (nasm_stricmp(tline->text, "flat") == 0) {
2251 /* All subsequent ARG directives are for a 32-bit stack */
2252 StackSize = 4;
2253 StackPointer = "ebp";
2254 ArgOffset = 8;
2255 LocalOffset = 0;
2256 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2257 /* All subsequent ARG directives are for a 64-bit stack */
2258 StackSize = 8;
2259 StackPointer = "rbp";
2260 ArgOffset = 16;
2261 LocalOffset = 0;
2262 } else if (nasm_stricmp(tline->text, "large") == 0) {
2263 /* All subsequent ARG directives are for a 16-bit stack,
2264 * far function call.
2266 StackSize = 2;
2267 StackPointer = "bp";
2268 ArgOffset = 4;
2269 LocalOffset = 0;
2270 } else if (nasm_stricmp(tline->text, "small") == 0) {
2271 /* All subsequent ARG directives are for a 16-bit stack,
2272 * far function call. We don't support near functions.
2274 StackSize = 2;
2275 StackPointer = "bp";
2276 ArgOffset = 6;
2277 LocalOffset = 0;
2278 } else {
2279 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2280 free_tlist(origline);
2281 return DIRECTIVE_FOUND;
2283 free_tlist(origline);
2284 return DIRECTIVE_FOUND;
2286 case PP_ARG:
2287 /* TASM like ARG directive to define arguments to functions, in
2288 * the following form:
2290 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2292 offset = ArgOffset;
2293 do {
2294 char *arg, directive[256];
2295 int size = StackSize;
2297 /* Find the argument name */
2298 tline = tline->next;
2299 if (tline && tline->type == TOK_WHITESPACE)
2300 tline = tline->next;
2301 if (!tline || tline->type != TOK_ID) {
2302 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2303 free_tlist(origline);
2304 return DIRECTIVE_FOUND;
2306 arg = tline->text;
2308 /* Find the argument size type */
2309 tline = tline->next;
2310 if (!tline || tline->type != TOK_OTHER
2311 || tline->text[0] != ':') {
2312 error(ERR_NONFATAL,
2313 "Syntax error processing `%%arg' directive");
2314 free_tlist(origline);
2315 return DIRECTIVE_FOUND;
2317 tline = tline->next;
2318 if (!tline || tline->type != TOK_ID) {
2319 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2320 free_tlist(origline);
2321 return DIRECTIVE_FOUND;
2324 /* Allow macro expansion of type parameter */
2325 tt = tokenize(tline->text);
2326 tt = expand_smacro(tt);
2327 size = parse_size(tt->text);
2328 if (!size) {
2329 error(ERR_NONFATAL,
2330 "Invalid size type for `%%arg' missing directive");
2331 free_tlist(tt);
2332 free_tlist(origline);
2333 return DIRECTIVE_FOUND;
2335 free_tlist(tt);
2337 /* Round up to even stack slots */
2338 size = ALIGN(size, StackSize);
2340 /* Now define the macro for the argument */
2341 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2342 arg, StackPointer, offset);
2343 do_directive(tokenize(directive));
2344 offset += size;
2346 /* Move to the next argument in the list */
2347 tline = tline->next;
2348 if (tline && tline->type == TOK_WHITESPACE)
2349 tline = tline->next;
2350 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2351 ArgOffset = offset;
2352 free_tlist(origline);
2353 return DIRECTIVE_FOUND;
2355 case PP_LOCAL:
2356 /* TASM like LOCAL directive to define local variables for a
2357 * function, in the following form:
2359 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2361 * The '= LocalSize' at the end is ignored by NASM, but is
2362 * required by TASM to define the local parameter size (and used
2363 * by the TASM macro package).
2365 offset = LocalOffset;
2366 do {
2367 char *local, directive[256];
2368 int size = StackSize;
2370 /* Find the argument name */
2371 tline = tline->next;
2372 if (tline && tline->type == TOK_WHITESPACE)
2373 tline = tline->next;
2374 if (!tline || tline->type != TOK_ID) {
2375 error(ERR_NONFATAL,
2376 "`%%local' missing argument parameter");
2377 free_tlist(origline);
2378 return DIRECTIVE_FOUND;
2380 local = tline->text;
2382 /* Find the argument size type */
2383 tline = tline->next;
2384 if (!tline || tline->type != TOK_OTHER
2385 || tline->text[0] != ':') {
2386 error(ERR_NONFATAL,
2387 "Syntax error processing `%%local' directive");
2388 free_tlist(origline);
2389 return DIRECTIVE_FOUND;
2391 tline = tline->next;
2392 if (!tline || tline->type != TOK_ID) {
2393 error(ERR_NONFATAL,
2394 "`%%local' missing size type parameter");
2395 free_tlist(origline);
2396 return DIRECTIVE_FOUND;
2399 /* Allow macro expansion of type parameter */
2400 tt = tokenize(tline->text);
2401 tt = expand_smacro(tt);
2402 size = parse_size(tt->text);
2403 if (!size) {
2404 error(ERR_NONFATAL,
2405 "Invalid size type for `%%local' missing directive");
2406 free_tlist(tt);
2407 free_tlist(origline);
2408 return DIRECTIVE_FOUND;
2410 free_tlist(tt);
2412 /* Round up to even stack slots */
2413 size = ALIGN(size, StackSize);
2415 offset += size; /* Negative offset, increment before */
2417 /* Now define the macro for the argument */
2418 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2419 local, StackPointer, offset);
2420 do_directive(tokenize(directive));
2422 /* Now define the assign to setup the enter_c macro correctly */
2423 snprintf(directive, sizeof(directive),
2424 "%%assign %%$localsize %%$localsize+%d", size);
2425 do_directive(tokenize(directive));
2427 /* Move to the next argument in the list */
2428 tline = tline->next;
2429 if (tline && tline->type == TOK_WHITESPACE)
2430 tline = tline->next;
2431 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2432 LocalOffset = offset;
2433 free_tlist(origline);
2434 return DIRECTIVE_FOUND;
2436 case PP_CLEAR:
2437 if (tline->next)
2438 error(ERR_WARNING|ERR_PASS1,
2439 "trailing garbage after `%%clear' ignored");
2440 free_macros();
2441 init_macros();
2442 free_tlist(origline);
2443 return DIRECTIVE_FOUND;
2445 case PP_DEPEND:
2446 t = tline->next = expand_smacro(tline->next);
2447 skip_white_(t);
2448 if (!t || (t->type != TOK_STRING &&
2449 t->type != TOK_INTERNAL_STRING)) {
2450 error(ERR_NONFATAL, "`%%depend' expects a file name");
2451 free_tlist(origline);
2452 return DIRECTIVE_FOUND; /* but we did _something_ */
2454 if (t->next)
2455 error(ERR_WARNING|ERR_PASS1,
2456 "trailing garbage after `%%depend' ignored");
2457 p = t->text;
2458 if (t->type != TOK_INTERNAL_STRING)
2459 nasm_unquote_cstr(p, i);
2460 if (dephead && !in_list(*dephead, p)) {
2461 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2462 sl->next = NULL;
2463 strcpy(sl->str, p);
2464 *deptail = sl;
2465 deptail = &sl->next;
2467 free_tlist(origline);
2468 return DIRECTIVE_FOUND;
2470 case PP_INCLUDE:
2471 t = tline->next = expand_smacro(tline->next);
2472 skip_white_(t);
2474 if (!t || (t->type != TOK_STRING &&
2475 t->type != TOK_INTERNAL_STRING)) {
2476 error(ERR_NONFATAL, "`%%include' expects a file name");
2477 free_tlist(origline);
2478 return DIRECTIVE_FOUND; /* but we did _something_ */
2480 if (t->next)
2481 error(ERR_WARNING|ERR_PASS1,
2482 "trailing garbage after `%%include' ignored");
2483 p = t->text;
2484 if (t->type != TOK_INTERNAL_STRING)
2485 nasm_unquote_cstr(p, i);
2486 inc = nasm_malloc(sizeof(Include));
2487 inc->next = istk;
2488 inc->conds = NULL;
2489 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2490 if (!inc->fp) {
2491 /* -MG given but file not found */
2492 nasm_free(inc);
2493 } else {
2494 inc->fname = src_set_fname(nasm_strdup(p));
2495 inc->lineno = src_set_linnum(0);
2496 inc->lineinc = 1;
2497 inc->expansion = NULL;
2498 inc->mstk = NULL;
2499 istk = inc;
2500 list->uplevel(LIST_INCLUDE);
2502 free_tlist(origline);
2503 return DIRECTIVE_FOUND;
2505 case PP_USE:
2507 static macros_t *use_pkg;
2508 const char *pkg_macro = NULL;
2510 tline = tline->next;
2511 skip_white_(tline);
2512 tline = expand_id(tline);
2514 if (!tline || (tline->type != TOK_STRING &&
2515 tline->type != TOK_INTERNAL_STRING &&
2516 tline->type != TOK_ID)) {
2517 error(ERR_NONFATAL, "`%%use' expects a package name");
2518 free_tlist(origline);
2519 return DIRECTIVE_FOUND; /* but we did _something_ */
2521 if (tline->next)
2522 error(ERR_WARNING|ERR_PASS1,
2523 "trailing garbage after `%%use' ignored");
2524 if (tline->type == TOK_STRING)
2525 nasm_unquote_cstr(tline->text, i);
2526 use_pkg = nasm_stdmac_find_package(tline->text);
2527 if (!use_pkg)
2528 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2529 else
2530 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2531 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2532 /* Not already included, go ahead and include it */
2533 stdmacpos = use_pkg;
2535 free_tlist(origline);
2536 return DIRECTIVE_FOUND;
2538 case PP_PUSH:
2539 case PP_REPL:
2540 case PP_POP:
2541 tline = tline->next;
2542 skip_white_(tline);
2543 tline = expand_id(tline);
2544 if (tline) {
2545 if (!tok_type_(tline, TOK_ID)) {
2546 error(ERR_NONFATAL, "`%s' expects a context identifier",
2547 pp_directives[i]);
2548 free_tlist(origline);
2549 return DIRECTIVE_FOUND; /* but we did _something_ */
2551 if (tline->next)
2552 error(ERR_WARNING|ERR_PASS1,
2553 "trailing garbage after `%s' ignored",
2554 pp_directives[i]);
2555 p = nasm_strdup(tline->text);
2556 } else {
2557 p = NULL; /* Anonymous */
2560 if (i == PP_PUSH) {
2561 ctx = nasm_malloc(sizeof(Context));
2562 ctx->next = cstk;
2563 hash_init(&ctx->localmac, HASH_SMALL);
2564 ctx->name = p;
2565 ctx->number = unique++;
2566 cstk = ctx;
2567 } else {
2568 /* %pop or %repl */
2569 if (!cstk) {
2570 error(ERR_NONFATAL, "`%s': context stack is empty",
2571 pp_directives[i]);
2572 } else if (i == PP_POP) {
2573 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2574 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2575 "expected %s",
2576 cstk->name ? cstk->name : "anonymous", p);
2577 else
2578 ctx_pop();
2579 } else {
2580 /* i == PP_REPL */
2581 nasm_free(cstk->name);
2582 cstk->name = p;
2583 p = NULL;
2585 nasm_free(p);
2587 free_tlist(origline);
2588 return DIRECTIVE_FOUND;
2589 case PP_FATAL:
2590 severity = ERR_FATAL;
2591 goto issue_error;
2592 case PP_ERROR:
2593 severity = ERR_NONFATAL;
2594 goto issue_error;
2595 case PP_WARNING:
2596 severity = ERR_WARNING|ERR_WARN_USER;
2597 goto issue_error;
2599 issue_error:
2601 /* Only error out if this is the final pass */
2602 if (pass != 2 && i != PP_FATAL)
2603 return DIRECTIVE_FOUND;
2605 tline->next = expand_smacro(tline->next);
2606 tline = tline->next;
2607 skip_white_(tline);
2608 t = tline ? tline->next : NULL;
2609 skip_white_(t);
2610 if (tok_type_(tline, TOK_STRING) && !t) {
2611 /* The line contains only a quoted string */
2612 p = tline->text;
2613 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2614 error(severity, "%s", p);
2615 } else {
2616 /* Not a quoted string, or more than a quoted string */
2617 p = detoken(tline, false);
2618 error(severity, "%s", p);
2619 nasm_free(p);
2621 free_tlist(origline);
2622 return DIRECTIVE_FOUND;
2625 CASE_PP_IF:
2626 if (istk->conds && !emitting(istk->conds->state))
2627 j = COND_NEVER;
2628 else {
2629 j = if_condition(tline->next, i);
2630 tline->next = NULL; /* it got freed */
2631 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2633 cond = nasm_malloc(sizeof(Cond));
2634 cond->next = istk->conds;
2635 cond->state = j;
2636 istk->conds = cond;
2637 if(istk->mstk)
2638 istk->mstk->condcnt ++;
2639 free_tlist(origline);
2640 return DIRECTIVE_FOUND;
2642 CASE_PP_ELIF:
2643 if (!istk->conds)
2644 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2645 switch(istk->conds->state) {
2646 case COND_IF_TRUE:
2647 istk->conds->state = COND_DONE;
2648 break;
2650 case COND_DONE:
2651 case COND_NEVER:
2652 break;
2654 case COND_ELSE_TRUE:
2655 case COND_ELSE_FALSE:
2656 error_precond(ERR_WARNING|ERR_PASS1,
2657 "`%%elif' after `%%else' ignored");
2658 istk->conds->state = COND_NEVER;
2659 break;
2661 case COND_IF_FALSE:
2663 * IMPORTANT: In the case of %if, we will already have
2664 * called expand_mmac_params(); however, if we're
2665 * processing an %elif we must have been in a
2666 * non-emitting mode, which would have inhibited
2667 * the normal invocation of expand_mmac_params().
2668 * Therefore, we have to do it explicitly here.
2670 j = if_condition(expand_mmac_params(tline->next), i);
2671 tline->next = NULL; /* it got freed */
2672 istk->conds->state =
2673 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2674 break;
2676 free_tlist(origline);
2677 return DIRECTIVE_FOUND;
2679 case PP_ELSE:
2680 if (tline->next)
2681 error_precond(ERR_WARNING|ERR_PASS1,
2682 "trailing garbage after `%%else' ignored");
2683 if (!istk->conds)
2684 error(ERR_FATAL, "`%%else': no matching `%%if'");
2685 switch(istk->conds->state) {
2686 case COND_IF_TRUE:
2687 case COND_DONE:
2688 istk->conds->state = COND_ELSE_FALSE;
2689 break;
2691 case COND_NEVER:
2692 break;
2694 case COND_IF_FALSE:
2695 istk->conds->state = COND_ELSE_TRUE;
2696 break;
2698 case COND_ELSE_TRUE:
2699 case COND_ELSE_FALSE:
2700 error_precond(ERR_WARNING|ERR_PASS1,
2701 "`%%else' after `%%else' ignored.");
2702 istk->conds->state = COND_NEVER;
2703 break;
2705 free_tlist(origline);
2706 return DIRECTIVE_FOUND;
2708 case PP_ENDIF:
2709 if (tline->next)
2710 error_precond(ERR_WARNING|ERR_PASS1,
2711 "trailing garbage after `%%endif' ignored");
2712 if (!istk->conds)
2713 error(ERR_FATAL, "`%%endif': no matching `%%if'");
2714 cond = istk->conds;
2715 istk->conds = cond->next;
2716 nasm_free(cond);
2717 if(istk->mstk)
2718 istk->mstk->condcnt --;
2719 free_tlist(origline);
2720 return DIRECTIVE_FOUND;
2722 case PP_RMACRO:
2723 case PP_IRMACRO:
2724 case PP_MACRO:
2725 case PP_IMACRO:
2726 if (defining) {
2727 error(ERR_FATAL, "`%s': already defining a macro",
2728 pp_directives[i]);
2729 return DIRECTIVE_FOUND;
2731 defining = nasm_malloc(sizeof(MMacro));
2732 defining->max_depth =
2733 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2734 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2735 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2736 nasm_free(defining);
2737 defining = NULL;
2738 return DIRECTIVE_FOUND;
2741 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2742 while (mmac) {
2743 if (!strcmp(mmac->name, defining->name) &&
2744 (mmac->nparam_min <= defining->nparam_max
2745 || defining->plus)
2746 && (defining->nparam_min <= mmac->nparam_max
2747 || mmac->plus)) {
2748 error(ERR_WARNING|ERR_PASS1,
2749 "redefining multi-line macro `%s'", defining->name);
2750 return DIRECTIVE_FOUND;
2752 mmac = mmac->next;
2754 free_tlist(origline);
2755 return DIRECTIVE_FOUND;
2757 case PP_ENDM:
2758 case PP_ENDMACRO:
2759 if (! (defining && defining->name)) {
2760 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2761 return DIRECTIVE_FOUND;
2763 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2764 defining->next = *mmhead;
2765 *mmhead = defining;
2766 defining = NULL;
2767 free_tlist(origline);
2768 return DIRECTIVE_FOUND;
2770 case PP_EXITMACRO:
2772 * We must search along istk->expansion until we hit a
2773 * macro-end marker for a macro with a name. Then we
2774 * bypass all lines between exitmacro and endmacro.
2776 list_for_each(l, istk->expansion)
2777 if (l->finishes && l->finishes->name)
2778 break;
2780 if (l) {
2782 * Remove all conditional entries relative to this
2783 * macro invocation. (safe to do in this context)
2785 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2786 cond = istk->conds;
2787 istk->conds = cond->next;
2788 nasm_free(cond);
2790 istk->expansion = l;
2791 } else {
2792 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2794 free_tlist(origline);
2795 return DIRECTIVE_FOUND;
2797 case PP_UNMACRO:
2798 case PP_UNIMACRO:
2800 MMacro **mmac_p;
2801 MMacro spec;
2803 spec.casesense = (i == PP_UNMACRO);
2804 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2805 return DIRECTIVE_FOUND;
2807 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2808 while (mmac_p && *mmac_p) {
2809 mmac = *mmac_p;
2810 if (mmac->casesense == spec.casesense &&
2811 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2812 mmac->nparam_min == spec.nparam_min &&
2813 mmac->nparam_max == spec.nparam_max &&
2814 mmac->plus == spec.plus) {
2815 *mmac_p = mmac->next;
2816 free_mmacro(mmac);
2817 } else {
2818 mmac_p = &mmac->next;
2821 free_tlist(origline);
2822 free_tlist(spec.dlist);
2823 return DIRECTIVE_FOUND;
2826 case PP_ROTATE:
2827 if (tline->next && tline->next->type == TOK_WHITESPACE)
2828 tline = tline->next;
2829 if (!tline->next) {
2830 free_tlist(origline);
2831 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2832 return DIRECTIVE_FOUND;
2834 t = expand_smacro(tline->next);
2835 tline->next = NULL;
2836 free_tlist(origline);
2837 tline = t;
2838 tptr = &t;
2839 tokval.t_type = TOKEN_INVALID;
2840 evalresult =
2841 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2842 free_tlist(tline);
2843 if (!evalresult)
2844 return DIRECTIVE_FOUND;
2845 if (tokval.t_type)
2846 error(ERR_WARNING|ERR_PASS1,
2847 "trailing garbage after expression ignored");
2848 if (!is_simple(evalresult)) {
2849 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2850 return DIRECTIVE_FOUND;
2852 mmac = istk->mstk;
2853 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2854 mmac = mmac->next_active;
2855 if (!mmac) {
2856 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2857 } else if (mmac->nparam == 0) {
2858 error(ERR_NONFATAL,
2859 "`%%rotate' invoked within macro without parameters");
2860 } else {
2861 int rotate = mmac->rotate + reloc_value(evalresult);
2863 rotate %= (int)mmac->nparam;
2864 if (rotate < 0)
2865 rotate += mmac->nparam;
2867 mmac->rotate = rotate;
2869 return DIRECTIVE_FOUND;
2871 case PP_REP:
2872 nolist = false;
2873 do {
2874 tline = tline->next;
2875 } while (tok_type_(tline, TOK_WHITESPACE));
2877 if (tok_type_(tline, TOK_ID) &&
2878 nasm_stricmp(tline->text, ".nolist") == 0) {
2879 nolist = true;
2880 do {
2881 tline = tline->next;
2882 } while (tok_type_(tline, TOK_WHITESPACE));
2885 if (tline) {
2886 t = expand_smacro(tline);
2887 tptr = &t;
2888 tokval.t_type = TOKEN_INVALID;
2889 evalresult =
2890 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2891 if (!evalresult) {
2892 free_tlist(origline);
2893 return DIRECTIVE_FOUND;
2895 if (tokval.t_type)
2896 error(ERR_WARNING|ERR_PASS1,
2897 "trailing garbage after expression ignored");
2898 if (!is_simple(evalresult)) {
2899 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2900 return DIRECTIVE_FOUND;
2902 count = reloc_value(evalresult);
2903 if (count >= REP_LIMIT) {
2904 error(ERR_NONFATAL, "`%%rep' value exceeds limit");
2905 count = 0;
2906 } else
2907 count++;
2908 } else {
2909 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2910 count = 0;
2912 free_tlist(origline);
2914 tmp_defining = defining;
2915 defining = nasm_malloc(sizeof(MMacro));
2916 defining->prev = NULL;
2917 defining->name = NULL; /* flags this macro as a %rep block */
2918 defining->casesense = false;
2919 defining->plus = false;
2920 defining->nolist = nolist;
2921 defining->in_progress = count;
2922 defining->max_depth = 0;
2923 defining->nparam_min = defining->nparam_max = 0;
2924 defining->defaults = NULL;
2925 defining->dlist = NULL;
2926 defining->expansion = NULL;
2927 defining->next_active = istk->mstk;
2928 defining->rep_nest = tmp_defining;
2929 return DIRECTIVE_FOUND;
2931 case PP_ENDREP:
2932 if (!defining || defining->name) {
2933 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2934 return DIRECTIVE_FOUND;
2938 * Now we have a "macro" defined - although it has no name
2939 * and we won't be entering it in the hash tables - we must
2940 * push a macro-end marker for it on to istk->expansion.
2941 * After that, it will take care of propagating itself (a
2942 * macro-end marker line for a macro which is really a %rep
2943 * block will cause the macro to be re-expanded, complete
2944 * with another macro-end marker to ensure the process
2945 * continues) until the whole expansion is forcibly removed
2946 * from istk->expansion by a %exitrep.
2948 l = nasm_malloc(sizeof(Line));
2949 l->next = istk->expansion;
2950 l->finishes = defining;
2951 l->first = NULL;
2952 istk->expansion = l;
2954 istk->mstk = defining;
2956 list->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2957 tmp_defining = defining;
2958 defining = defining->rep_nest;
2959 free_tlist(origline);
2960 return DIRECTIVE_FOUND;
2962 case PP_EXITREP:
2964 * We must search along istk->expansion until we hit a
2965 * macro-end marker for a macro with no name. Then we set
2966 * its `in_progress' flag to 0.
2968 list_for_each(l, istk->expansion)
2969 if (l->finishes && !l->finishes->name)
2970 break;
2972 if (l)
2973 l->finishes->in_progress = 1;
2974 else
2975 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
2976 free_tlist(origline);
2977 return DIRECTIVE_FOUND;
2979 case PP_XDEFINE:
2980 case PP_IXDEFINE:
2981 case PP_DEFINE:
2982 case PP_IDEFINE:
2983 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
2985 tline = tline->next;
2986 skip_white_(tline);
2987 tline = expand_id(tline);
2988 if (!tline || (tline->type != TOK_ID &&
2989 (tline->type != TOK_PREPROC_ID ||
2990 tline->text[1] != '$'))) {
2991 error(ERR_NONFATAL, "`%s' expects a macro identifier",
2992 pp_directives[i]);
2993 free_tlist(origline);
2994 return DIRECTIVE_FOUND;
2997 ctx = get_ctx(tline->text, &mname, false);
2998 last = tline;
2999 param_start = tline = tline->next;
3000 nparam = 0;
3002 /* Expand the macro definition now for %xdefine and %ixdefine */
3003 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3004 tline = expand_smacro(tline);
3006 if (tok_is_(tline, "(")) {
3008 * This macro has parameters.
3011 tline = tline->next;
3012 while (1) {
3013 skip_white_(tline);
3014 if (!tline) {
3015 error(ERR_NONFATAL, "parameter identifier expected");
3016 free_tlist(origline);
3017 return DIRECTIVE_FOUND;
3019 if (tline->type != TOK_ID) {
3020 error(ERR_NONFATAL,
3021 "`%s': parameter identifier expected",
3022 tline->text);
3023 free_tlist(origline);
3024 return DIRECTIVE_FOUND;
3026 tline->type = TOK_SMAC_PARAM + nparam++;
3027 tline = tline->next;
3028 skip_white_(tline);
3029 if (tok_is_(tline, ",")) {
3030 tline = tline->next;
3031 } else {
3032 if (!tok_is_(tline, ")")) {
3033 error(ERR_NONFATAL,
3034 "`)' expected to terminate macro template");
3035 free_tlist(origline);
3036 return DIRECTIVE_FOUND;
3038 break;
3041 last = tline;
3042 tline = tline->next;
3044 if (tok_type_(tline, TOK_WHITESPACE))
3045 last = tline, tline = tline->next;
3046 macro_start = NULL;
3047 last->next = NULL;
3048 t = tline;
3049 while (t) {
3050 if (t->type == TOK_ID) {
3051 list_for_each(tt, param_start)
3052 if (tt->type >= TOK_SMAC_PARAM &&
3053 !strcmp(tt->text, t->text))
3054 t->type = tt->type;
3056 tt = t->next;
3057 t->next = macro_start;
3058 macro_start = t;
3059 t = tt;
3062 * Good. We now have a macro name, a parameter count, and a
3063 * token list (in reverse order) for an expansion. We ought
3064 * to be OK just to create an SMacro, store it, and let
3065 * free_tlist have the rest of the line (which we have
3066 * carefully re-terminated after chopping off the expansion
3067 * from the end).
3069 define_smacro(ctx, mname, casesense, nparam, macro_start);
3070 free_tlist(origline);
3071 return DIRECTIVE_FOUND;
3073 case PP_UNDEF:
3074 tline = tline->next;
3075 skip_white_(tline);
3076 tline = expand_id(tline);
3077 if (!tline || (tline->type != TOK_ID &&
3078 (tline->type != TOK_PREPROC_ID ||
3079 tline->text[1] != '$'))) {
3080 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3081 free_tlist(origline);
3082 return DIRECTIVE_FOUND;
3084 if (tline->next) {
3085 error(ERR_WARNING|ERR_PASS1,
3086 "trailing garbage after macro name ignored");
3089 /* Find the context that symbol belongs to */
3090 ctx = get_ctx(tline->text, &mname, false);
3091 undef_smacro(ctx, mname);
3092 free_tlist(origline);
3093 return DIRECTIVE_FOUND;
3095 case PP_DEFSTR:
3096 case PP_IDEFSTR:
3097 casesense = (i == PP_DEFSTR);
3099 tline = tline->next;
3100 skip_white_(tline);
3101 tline = expand_id(tline);
3102 if (!tline || (tline->type != TOK_ID &&
3103 (tline->type != TOK_PREPROC_ID ||
3104 tline->text[1] != '$'))) {
3105 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3106 pp_directives[i]);
3107 free_tlist(origline);
3108 return DIRECTIVE_FOUND;
3111 ctx = get_ctx(tline->text, &mname, false);
3112 last = tline;
3113 tline = expand_smacro(tline->next);
3114 last->next = NULL;
3116 while (tok_type_(tline, TOK_WHITESPACE))
3117 tline = delete_Token(tline);
3119 p = detoken(tline, false);
3120 macro_start = nasm_malloc(sizeof(*macro_start));
3121 macro_start->next = NULL;
3122 macro_start->text = nasm_quote(p, strlen(p));
3123 macro_start->type = TOK_STRING;
3124 macro_start->a.mac = NULL;
3125 nasm_free(p);
3128 * We now have a macro name, an implicit parameter count of
3129 * zero, and a string token to use as an expansion. Create
3130 * and store an SMacro.
3132 define_smacro(ctx, mname, casesense, 0, macro_start);
3133 free_tlist(origline);
3134 return DIRECTIVE_FOUND;
3136 case PP_DEFTOK:
3137 case PP_IDEFTOK:
3138 casesense = (i == PP_DEFTOK);
3140 tline = tline->next;
3141 skip_white_(tline);
3142 tline = expand_id(tline);
3143 if (!tline || (tline->type != TOK_ID &&
3144 (tline->type != TOK_PREPROC_ID ||
3145 tline->text[1] != '$'))) {
3146 error(ERR_NONFATAL,
3147 "`%s' expects a macro identifier as first parameter",
3148 pp_directives[i]);
3149 free_tlist(origline);
3150 return DIRECTIVE_FOUND;
3152 ctx = get_ctx(tline->text, &mname, false);
3153 last = tline;
3154 tline = expand_smacro(tline->next);
3155 last->next = NULL;
3157 t = tline;
3158 while (tok_type_(t, TOK_WHITESPACE))
3159 t = t->next;
3160 /* t should now point to the string */
3161 if (t->type != TOK_STRING) {
3162 error(ERR_NONFATAL,
3163 "`%s` requires string as second parameter",
3164 pp_directives[i]);
3165 free_tlist(tline);
3166 free_tlist(origline);
3167 return DIRECTIVE_FOUND;
3170 nasm_unquote_cstr(t->text, i);
3171 macro_start = tokenize(t->text);
3174 * We now have a macro name, an implicit parameter count of
3175 * zero, and a numeric token to use as an expansion. Create
3176 * and store an SMacro.
3178 define_smacro(ctx, mname, casesense, 0, macro_start);
3179 free_tlist(tline);
3180 free_tlist(origline);
3181 return DIRECTIVE_FOUND;
3183 case PP_PATHSEARCH:
3185 FILE *fp;
3186 StrList *xsl = NULL;
3187 StrList **xst = &xsl;
3189 casesense = true;
3191 tline = tline->next;
3192 skip_white_(tline);
3193 tline = expand_id(tline);
3194 if (!tline || (tline->type != TOK_ID &&
3195 (tline->type != TOK_PREPROC_ID ||
3196 tline->text[1] != '$'))) {
3197 error(ERR_NONFATAL,
3198 "`%%pathsearch' expects a macro identifier as first parameter");
3199 free_tlist(origline);
3200 return DIRECTIVE_FOUND;
3202 ctx = get_ctx(tline->text, &mname, false);
3203 last = tline;
3204 tline = expand_smacro(tline->next);
3205 last->next = NULL;
3207 t = tline;
3208 while (tok_type_(t, TOK_WHITESPACE))
3209 t = t->next;
3211 if (!t || (t->type != TOK_STRING &&
3212 t->type != TOK_INTERNAL_STRING)) {
3213 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3214 free_tlist(tline);
3215 free_tlist(origline);
3216 return DIRECTIVE_FOUND; /* but we did _something_ */
3218 if (t->next)
3219 error(ERR_WARNING|ERR_PASS1,
3220 "trailing garbage after `%%pathsearch' ignored");
3221 p = t->text;
3222 if (t->type != TOK_INTERNAL_STRING)
3223 nasm_unquote(p, NULL);
3225 fp = inc_fopen(p, &xsl, &xst, true);
3226 if (fp) {
3227 p = xsl->str;
3228 fclose(fp); /* Don't actually care about the file */
3230 macro_start = nasm_malloc(sizeof(*macro_start));
3231 macro_start->next = NULL;
3232 macro_start->text = nasm_quote(p, strlen(p));
3233 macro_start->type = TOK_STRING;
3234 macro_start->a.mac = NULL;
3235 if (xsl)
3236 nasm_free(xsl);
3239 * We now have a macro name, an implicit parameter count of
3240 * zero, and a string token to use as an expansion. Create
3241 * and store an SMacro.
3243 define_smacro(ctx, mname, casesense, 0, macro_start);
3244 free_tlist(tline);
3245 free_tlist(origline);
3246 return DIRECTIVE_FOUND;
3249 case PP_STRLEN:
3250 casesense = true;
3252 tline = tline->next;
3253 skip_white_(tline);
3254 tline = expand_id(tline);
3255 if (!tline || (tline->type != TOK_ID &&
3256 (tline->type != TOK_PREPROC_ID ||
3257 tline->text[1] != '$'))) {
3258 error(ERR_NONFATAL,
3259 "`%%strlen' expects a macro identifier as first parameter");
3260 free_tlist(origline);
3261 return DIRECTIVE_FOUND;
3263 ctx = get_ctx(tline->text, &mname, false);
3264 last = tline;
3265 tline = expand_smacro(tline->next);
3266 last->next = NULL;
3268 t = tline;
3269 while (tok_type_(t, TOK_WHITESPACE))
3270 t = t->next;
3271 /* t should now point to the string */
3272 if (!tok_type_(t, TOK_STRING)) {
3273 error(ERR_NONFATAL,
3274 "`%%strlen` requires string as second parameter");
3275 free_tlist(tline);
3276 free_tlist(origline);
3277 return DIRECTIVE_FOUND;
3280 macro_start = nasm_malloc(sizeof(*macro_start));
3281 macro_start->next = NULL;
3282 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3283 macro_start->a.mac = NULL;
3286 * We now have a macro name, an implicit parameter count of
3287 * zero, and a numeric token to use as an expansion. Create
3288 * and store an SMacro.
3290 define_smacro(ctx, mname, casesense, 0, macro_start);
3291 free_tlist(tline);
3292 free_tlist(origline);
3293 return DIRECTIVE_FOUND;
3295 case PP_STRCAT:
3296 casesense = true;
3298 tline = tline->next;
3299 skip_white_(tline);
3300 tline = expand_id(tline);
3301 if (!tline || (tline->type != TOK_ID &&
3302 (tline->type != TOK_PREPROC_ID ||
3303 tline->text[1] != '$'))) {
3304 error(ERR_NONFATAL,
3305 "`%%strcat' expects a macro identifier as first parameter");
3306 free_tlist(origline);
3307 return DIRECTIVE_FOUND;
3309 ctx = get_ctx(tline->text, &mname, false);
3310 last = tline;
3311 tline = expand_smacro(tline->next);
3312 last->next = NULL;
3314 len = 0;
3315 list_for_each(t, tline) {
3316 switch (t->type) {
3317 case TOK_WHITESPACE:
3318 break;
3319 case TOK_STRING:
3320 len += t->a.len = nasm_unquote(t->text, NULL);
3321 break;
3322 case TOK_OTHER:
3323 if (!strcmp(t->text, ",")) /* permit comma separators */
3324 break;
3325 /* else fall through */
3326 default:
3327 error(ERR_NONFATAL,
3328 "non-string passed to `%%strcat' (%d)", t->type);
3329 free_tlist(tline);
3330 free_tlist(origline);
3331 return DIRECTIVE_FOUND;
3335 p = pp = nasm_malloc(len);
3336 list_for_each(t, tline) {
3337 if (t->type == TOK_STRING) {
3338 memcpy(p, t->text, t->a.len);
3339 p += t->a.len;
3344 * We now have a macro name, an implicit parameter count of
3345 * zero, and a numeric token to use as an expansion. Create
3346 * and store an SMacro.
3348 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3349 macro_start->text = nasm_quote(pp, len);
3350 nasm_free(pp);
3351 define_smacro(ctx, mname, casesense, 0, macro_start);
3352 free_tlist(tline);
3353 free_tlist(origline);
3354 return DIRECTIVE_FOUND;
3356 case PP_SUBSTR:
3358 int64_t a1, a2;
3359 size_t len;
3361 casesense = true;
3363 tline = tline->next;
3364 skip_white_(tline);
3365 tline = expand_id(tline);
3366 if (!tline || (tline->type != TOK_ID &&
3367 (tline->type != TOK_PREPROC_ID ||
3368 tline->text[1] != '$'))) {
3369 error(ERR_NONFATAL,
3370 "`%%substr' expects a macro identifier as first parameter");
3371 free_tlist(origline);
3372 return DIRECTIVE_FOUND;
3374 ctx = get_ctx(tline->text, &mname, false);
3375 last = tline;
3376 tline = expand_smacro(tline->next);
3377 last->next = NULL;
3379 t = tline->next;
3380 while (tok_type_(t, TOK_WHITESPACE))
3381 t = t->next;
3383 /* t should now point to the string */
3384 if (t->type != TOK_STRING) {
3385 error(ERR_NONFATAL,
3386 "`%%substr` requires string as second parameter");
3387 free_tlist(tline);
3388 free_tlist(origline);
3389 return DIRECTIVE_FOUND;
3392 tt = t->next;
3393 tptr = &tt;
3394 tokval.t_type = TOKEN_INVALID;
3395 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3396 pass, error, NULL);
3397 if (!evalresult) {
3398 free_tlist(tline);
3399 free_tlist(origline);
3400 return DIRECTIVE_FOUND;
3401 } else if (!is_simple(evalresult)) {
3402 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3403 free_tlist(tline);
3404 free_tlist(origline);
3405 return DIRECTIVE_FOUND;
3407 a1 = evalresult->value-1;
3409 while (tok_type_(tt, TOK_WHITESPACE))
3410 tt = tt->next;
3411 if (!tt) {
3412 a2 = 1; /* Backwards compatibility: one character */
3413 } else {
3414 tokval.t_type = TOKEN_INVALID;
3415 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3416 pass, error, NULL);
3417 if (!evalresult) {
3418 free_tlist(tline);
3419 free_tlist(origline);
3420 return DIRECTIVE_FOUND;
3421 } else if (!is_simple(evalresult)) {
3422 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3423 free_tlist(tline);
3424 free_tlist(origline);
3425 return DIRECTIVE_FOUND;
3427 a2 = evalresult->value;
3430 len = nasm_unquote(t->text, NULL);
3431 if (a2 < 0)
3432 a2 = a2+1+len-a1;
3433 if (a1+a2 > (int64_t)len)
3434 a2 = len-a1;
3436 macro_start = nasm_malloc(sizeof(*macro_start));
3437 macro_start->next = NULL;
3438 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3439 macro_start->type = TOK_STRING;
3440 macro_start->a.mac = NULL;
3443 * We now have a macro name, an implicit parameter count of
3444 * zero, and a numeric token to use as an expansion. Create
3445 * and store an SMacro.
3447 define_smacro(ctx, mname, casesense, 0, macro_start);
3448 free_tlist(tline);
3449 free_tlist(origline);
3450 return DIRECTIVE_FOUND;
3453 case PP_ASSIGN:
3454 case PP_IASSIGN:
3455 casesense = (i == PP_ASSIGN);
3457 tline = tline->next;
3458 skip_white_(tline);
3459 tline = expand_id(tline);
3460 if (!tline || (tline->type != TOK_ID &&
3461 (tline->type != TOK_PREPROC_ID ||
3462 tline->text[1] != '$'))) {
3463 error(ERR_NONFATAL,
3464 "`%%%sassign' expects a macro identifier",
3465 (i == PP_IASSIGN ? "i" : ""));
3466 free_tlist(origline);
3467 return DIRECTIVE_FOUND;
3469 ctx = get_ctx(tline->text, &mname, false);
3470 last = tline;
3471 tline = expand_smacro(tline->next);
3472 last->next = NULL;
3474 t = tline;
3475 tptr = &t;
3476 tokval.t_type = TOKEN_INVALID;
3477 evalresult =
3478 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3479 free_tlist(tline);
3480 if (!evalresult) {
3481 free_tlist(origline);
3482 return DIRECTIVE_FOUND;
3485 if (tokval.t_type)
3486 error(ERR_WARNING|ERR_PASS1,
3487 "trailing garbage after expression ignored");
3489 if (!is_simple(evalresult)) {
3490 error(ERR_NONFATAL,
3491 "non-constant value given to `%%%sassign'",
3492 (i == PP_IASSIGN ? "i" : ""));
3493 free_tlist(origline);
3494 return DIRECTIVE_FOUND;
3497 macro_start = nasm_malloc(sizeof(*macro_start));
3498 macro_start->next = NULL;
3499 make_tok_num(macro_start, reloc_value(evalresult));
3500 macro_start->a.mac = NULL;
3503 * We now have a macro name, an implicit parameter count of
3504 * zero, and a numeric token to use as an expansion. Create
3505 * and store an SMacro.
3507 define_smacro(ctx, mname, casesense, 0, macro_start);
3508 free_tlist(origline);
3509 return DIRECTIVE_FOUND;
3511 case PP_LINE:
3513 * Syntax is `%line nnn[+mmm] [filename]'
3515 tline = tline->next;
3516 skip_white_(tline);
3517 if (!tok_type_(tline, TOK_NUMBER)) {
3518 error(ERR_NONFATAL, "`%%line' expects line number");
3519 free_tlist(origline);
3520 return DIRECTIVE_FOUND;
3522 k = readnum(tline->text, &err);
3523 m = 1;
3524 tline = tline->next;
3525 if (tok_is_(tline, "+")) {
3526 tline = tline->next;
3527 if (!tok_type_(tline, TOK_NUMBER)) {
3528 error(ERR_NONFATAL, "`%%line' expects line increment");
3529 free_tlist(origline);
3530 return DIRECTIVE_FOUND;
3532 m = readnum(tline->text, &err);
3533 tline = tline->next;
3535 skip_white_(tline);
3536 src_set_linnum(k);
3537 istk->lineinc = m;
3538 if (tline) {
3539 nasm_free(src_set_fname(detoken(tline, false)));
3541 free_tlist(origline);
3542 return DIRECTIVE_FOUND;
3544 default:
3545 error(ERR_FATAL,
3546 "preprocessor directive `%s' not yet implemented",
3547 pp_directives[i]);
3548 return DIRECTIVE_FOUND;
3553 * Ensure that a macro parameter contains a condition code and
3554 * nothing else. Return the condition code index if so, or -1
3555 * otherwise.
3557 static int find_cc(Token * t)
3559 Token *tt;
3560 int i, j, k, m;
3562 if (!t)
3563 return -1; /* Probably a %+ without a space */
3565 skip_white_(t);
3566 if (t->type != TOK_ID)
3567 return -1;
3568 tt = t->next;
3569 skip_white_(tt);
3570 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3571 return -1;
3573 i = -1;
3574 j = ARRAY_SIZE(conditions);
3575 while (j - i > 1) {
3576 k = (j + i) / 2;
3577 m = nasm_stricmp(t->text, conditions[k]);
3578 if (m == 0) {
3579 i = k;
3580 j = -2;
3581 break;
3582 } else if (m < 0) {
3583 j = k;
3584 } else
3585 i = k;
3587 if (j != -2)
3588 return -1;
3589 return i;
3592 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3594 Token **tail, *t, *tt;
3595 Token **paste_head;
3596 bool did_paste = false;
3597 char *tmp;
3599 /* Now handle token pasting... */
3600 paste_head = NULL;
3601 tail = head;
3602 while ((t = *tail) && (tt = t->next)) {
3603 switch (t->type) {
3604 case TOK_WHITESPACE:
3605 if (tt->type == TOK_WHITESPACE) {
3606 /* Zap adjacent whitespace tokens */
3607 t->next = delete_Token(tt);
3608 } else {
3609 /* Do not advance paste_head here */
3610 tail = &t->next;
3612 break;
3613 case TOK_ID:
3614 case TOK_NUMBER:
3615 case TOK_FLOAT:
3617 size_t len = 0;
3618 char *tmp, *p;
3620 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3621 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3622 tt->type == TOK_OTHER)) {
3623 len += strlen(tt->text);
3624 tt = tt->next;
3628 * Now tt points to the first token after
3629 * the potential paste area...
3631 if (tt != t->next) {
3632 /* We have at least two tokens... */
3633 len += strlen(t->text);
3634 p = tmp = nasm_malloc(len+1);
3636 while (t != tt) {
3637 strcpy(p, t->text);
3638 p = strchr(p, '\0');
3639 t = delete_Token(t);
3642 t = *tail = tokenize(tmp);
3643 nasm_free(tmp);
3645 while (t->next) {
3646 tail = &t->next;
3647 t = t->next;
3649 t->next = tt; /* Attach the remaining token chain */
3651 did_paste = true;
3653 paste_head = tail;
3654 tail = &t->next;
3655 break;
3657 case TOK_PASTE: /* %+ */
3658 if (handle_paste_tokens) {
3659 /* Zap %+ and whitespace tokens to the right */
3660 while (t && (t->type == TOK_WHITESPACE ||
3661 t->type == TOK_PASTE))
3662 t = *tail = delete_Token(t);
3663 if (!paste_head || !t)
3664 break; /* Nothing to paste with */
3665 tail = paste_head;
3666 t = *tail;
3667 tt = t->next;
3668 while (tok_type_(tt, TOK_WHITESPACE))
3669 tt = t->next = delete_Token(tt);
3671 if (tt) {
3672 tmp = nasm_strcat(t->text, tt->text);
3673 delete_Token(t);
3674 tt = delete_Token(tt);
3675 t = *tail = tokenize(tmp);
3676 nasm_free(tmp);
3677 while (t->next) {
3678 tail = &t->next;
3679 t = t->next;
3681 t->next = tt; /* Attach the remaining token chain */
3682 did_paste = true;
3684 paste_head = tail;
3685 tail = &t->next;
3686 break;
3688 /* else fall through */
3689 default:
3690 tail = &t->next;
3691 if (!tok_type_(t->next, TOK_WHITESPACE))
3692 paste_head = tail;
3693 break;
3696 return did_paste;
3700 * expands to a list of tokens from %{x:y}
3702 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3704 Token *t = tline, **tt, *tm, *head;
3705 char *pos;
3706 int fst, lst, j, i;
3708 pos = strchr(tline->text, ':');
3709 nasm_assert(pos);
3711 lst = atoi(pos + 1);
3712 fst = atoi(tline->text + 1);
3715 * only macros params are accounted so
3716 * if someone passes %0 -- we reject such
3717 * value(s)
3719 if (lst == 0 || fst == 0)
3720 goto err;
3722 /* the values should be sane */
3723 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3724 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3725 goto err;
3727 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3728 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3730 /* counted from zero */
3731 fst--, lst--;
3734 * it will be at least one token
3736 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3737 t = new_Token(NULL, tm->type, tm->text, 0);
3738 head = t, tt = &t->next;
3739 if (fst < lst) {
3740 for (i = fst + 1; i <= lst; i++) {
3741 t = new_Token(NULL, TOK_OTHER, ",", 0);
3742 *tt = t, tt = &t->next;
3743 j = (i + mac->rotate) % mac->nparam;
3744 tm = mac->params[j];
3745 t = new_Token(NULL, tm->type, tm->text, 0);
3746 *tt = t, tt = &t->next;
3748 } else {
3749 for (i = fst - 1; i >= lst; i--) {
3750 t = new_Token(NULL, TOK_OTHER, ",", 0);
3751 *tt = t, tt = &t->next;
3752 j = (i + mac->rotate) % mac->nparam;
3753 tm = mac->params[j];
3754 t = new_Token(NULL, tm->type, tm->text, 0);
3755 *tt = t, tt = &t->next;
3759 *last = tt;
3760 return head;
3762 err:
3763 error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3764 &tline->text[1]);
3765 return tline;
3769 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3770 * %-n) and MMacro-local identifiers (%%foo) as well as
3771 * macro indirection (%[...]) and range (%{..:..}).
3773 static Token *expand_mmac_params(Token * tline)
3775 Token *t, *tt, **tail, *thead;
3776 bool changed = false;
3777 char *pos;
3779 tail = &thead;
3780 thead = NULL;
3782 while (tline) {
3783 if (tline->type == TOK_PREPROC_ID &&
3784 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3785 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3786 tline->text[1] == '%')) {
3787 char *text = NULL;
3788 int type = 0, cc; /* type = 0 to placate optimisers */
3789 char tmpbuf[30];
3790 unsigned int n;
3791 int i;
3792 MMacro *mac;
3794 t = tline;
3795 tline = tline->next;
3797 mac = istk->mstk;
3798 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3799 mac = mac->next_active;
3800 if (!mac) {
3801 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3802 } else {
3803 pos = strchr(t->text, ':');
3804 if (!pos) {
3805 switch (t->text[1]) {
3807 * We have to make a substitution of one of the
3808 * forms %1, %-1, %+1, %%foo, %0.
3810 case '0':
3811 type = TOK_NUMBER;
3812 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3813 text = nasm_strdup(tmpbuf);
3814 break;
3815 case '%':
3816 type = TOK_ID;
3817 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3818 mac->unique);
3819 text = nasm_strcat(tmpbuf, t->text + 2);
3820 break;
3821 case '-':
3822 n = atoi(t->text + 2) - 1;
3823 if (n >= mac->nparam)
3824 tt = NULL;
3825 else {
3826 if (mac->nparam > 1)
3827 n = (n + mac->rotate) % mac->nparam;
3828 tt = mac->params[n];
3830 cc = find_cc(tt);
3831 if (cc == -1) {
3832 error(ERR_NONFATAL,
3833 "macro parameter %d is not a condition code",
3834 n + 1);
3835 text = NULL;
3836 } else {
3837 type = TOK_ID;
3838 if (inverse_ccs[cc] == -1) {
3839 error(ERR_NONFATAL,
3840 "condition code `%s' is not invertible",
3841 conditions[cc]);
3842 text = NULL;
3843 } else
3844 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3846 break;
3847 case '+':
3848 n = atoi(t->text + 2) - 1;
3849 if (n >= mac->nparam)
3850 tt = NULL;
3851 else {
3852 if (mac->nparam > 1)
3853 n = (n + mac->rotate) % mac->nparam;
3854 tt = mac->params[n];
3856 cc = find_cc(tt);
3857 if (cc == -1) {
3858 error(ERR_NONFATAL,
3859 "macro parameter %d is not a condition code",
3860 n + 1);
3861 text = NULL;
3862 } else {
3863 type = TOK_ID;
3864 text = nasm_strdup(conditions[cc]);
3866 break;
3867 default:
3868 n = atoi(t->text + 1) - 1;
3869 if (n >= mac->nparam)
3870 tt = NULL;
3871 else {
3872 if (mac->nparam > 1)
3873 n = (n + mac->rotate) % mac->nparam;
3874 tt = mac->params[n];
3876 if (tt) {
3877 for (i = 0; i < mac->paramlen[n]; i++) {
3878 *tail = new_Token(NULL, tt->type, tt->text, 0);
3879 tail = &(*tail)->next;
3880 tt = tt->next;
3883 text = NULL; /* we've done it here */
3884 break;
3886 } else {
3888 * seems we have a parameters range here
3890 Token *head, **last;
3891 head = expand_mmac_params_range(mac, t, &last);
3892 if (head != t) {
3893 *tail = head;
3894 *last = tline;
3895 tline = head;
3896 text = NULL;
3900 if (!text) {
3901 delete_Token(t);
3902 } else {
3903 *tail = t;
3904 tail = &t->next;
3905 t->type = type;
3906 nasm_free(t->text);
3907 t->text = text;
3908 t->a.mac = NULL;
3910 changed = true;
3911 continue;
3912 } else if (tline->type == TOK_INDIRECT) {
3913 t = tline;
3914 tline = tline->next;
3915 tt = tokenize(t->text);
3916 tt = expand_mmac_params(tt);
3917 tt = expand_smacro(tt);
3918 *tail = tt;
3919 while (tt) {
3920 tt->a.mac = NULL; /* Necessary? */
3921 tail = &tt->next;
3922 tt = tt->next;
3924 delete_Token(t);
3925 changed = true;
3926 } else {
3927 t = *tail = tline;
3928 tline = tline->next;
3929 t->a.mac = NULL;
3930 tail = &t->next;
3933 *tail = NULL;
3935 if (changed)
3936 paste_tokens(&thead, false);
3938 return thead;
3942 * Expand all single-line macro calls made in the given line.
3943 * Return the expanded version of the line. The original is deemed
3944 * to be destroyed in the process. (In reality we'll just move
3945 * Tokens from input to output a lot of the time, rather than
3946 * actually bothering to destroy and replicate.)
3949 static Token *expand_smacro(Token * tline)
3951 Token *t, *tt, *mstart, **tail, *thead;
3952 SMacro *head = NULL, *m;
3953 Token **params;
3954 int *paramsize;
3955 unsigned int nparam, sparam;
3956 int brackets;
3957 Token *org_tline = tline;
3958 Context *ctx;
3959 const char *mname;
3960 int deadman = DEADMAN_LIMIT;
3961 bool expanded;
3964 * Trick: we should avoid changing the start token pointer since it can
3965 * be contained in "next" field of other token. Because of this
3966 * we allocate a copy of first token and work with it; at the end of
3967 * routine we copy it back
3969 if (org_tline) {
3970 tline = new_Token(org_tline->next, org_tline->type,
3971 org_tline->text, 0);
3972 tline->a.mac = org_tline->a.mac;
3973 nasm_free(org_tline->text);
3974 org_tline->text = NULL;
3977 expanded = true; /* Always expand %+ at least once */
3979 again:
3980 thead = NULL;
3981 tail = &thead;
3983 while (tline) { /* main token loop */
3984 if (!--deadman) {
3985 error(ERR_NONFATAL, "interminable macro recursion");
3986 goto err;
3989 if ((mname = tline->text)) {
3990 /* if this token is a local macro, look in local context */
3991 if (tline->type == TOK_ID) {
3992 head = (SMacro *)hash_findix(&smacros, mname);
3993 } else if (tline->type == TOK_PREPROC_ID) {
3994 ctx = get_ctx(mname, &mname, true);
3995 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
3996 } else
3997 head = NULL;
4000 * We've hit an identifier. As in is_mmacro below, we first
4001 * check whether the identifier is a single-line macro at
4002 * all, then think about checking for parameters if
4003 * necessary.
4005 list_for_each(m, head)
4006 if (!mstrcmp(m->name, mname, m->casesense))
4007 break;
4008 if (m) {
4009 mstart = tline;
4010 params = NULL;
4011 paramsize = NULL;
4012 if (m->nparam == 0) {
4014 * Simple case: the macro is parameterless. Discard the
4015 * one token that the macro call took, and push the
4016 * expansion back on the to-do stack.
4018 if (!m->expansion) {
4019 if (!strcmp("__FILE__", m->name)) {
4020 int32_t num = 0;
4021 char *file = NULL;
4022 src_get(&num, &file);
4023 tline->text = nasm_quote(file, strlen(file));
4024 tline->type = TOK_STRING;
4025 nasm_free(file);
4026 continue;
4028 if (!strcmp("__LINE__", m->name)) {
4029 nasm_free(tline->text);
4030 make_tok_num(tline, src_get_linnum());
4031 continue;
4033 if (!strcmp("__BITS__", m->name)) {
4034 nasm_free(tline->text);
4035 make_tok_num(tline, globalbits);
4036 continue;
4038 tline = delete_Token(tline);
4039 continue;
4041 } else {
4043 * Complicated case: at least one macro with this name
4044 * exists and takes parameters. We must find the
4045 * parameters in the call, count them, find the SMacro
4046 * that corresponds to that form of the macro call, and
4047 * substitute for the parameters when we expand. What a
4048 * pain.
4050 /*tline = tline->next;
4051 skip_white_(tline); */
4052 do {
4053 t = tline->next;
4054 while (tok_type_(t, TOK_SMAC_END)) {
4055 t->a.mac->in_progress = false;
4056 t->text = NULL;
4057 t = tline->next = delete_Token(t);
4059 tline = t;
4060 } while (tok_type_(tline, TOK_WHITESPACE));
4061 if (!tok_is_(tline, "(")) {
4063 * This macro wasn't called with parameters: ignore
4064 * the call. (Behaviour borrowed from gnu cpp.)
4066 tline = mstart;
4067 m = NULL;
4068 } else {
4069 int paren = 0;
4070 int white = 0;
4071 brackets = 0;
4072 nparam = 0;
4073 sparam = PARAM_DELTA;
4074 params = nasm_malloc(sparam * sizeof(Token *));
4075 params[0] = tline->next;
4076 paramsize = nasm_malloc(sparam * sizeof(int));
4077 paramsize[0] = 0;
4078 while (true) { /* parameter loop */
4080 * For some unusual expansions
4081 * which concatenates function call
4083 t = tline->next;
4084 while (tok_type_(t, TOK_SMAC_END)) {
4085 t->a.mac->in_progress = false;
4086 t->text = NULL;
4087 t = tline->next = delete_Token(t);
4089 tline = t;
4091 if (!tline) {
4092 error(ERR_NONFATAL,
4093 "macro call expects terminating `)'");
4094 break;
4096 if (tline->type == TOK_WHITESPACE
4097 && brackets <= 0) {
4098 if (paramsize[nparam])
4099 white++;
4100 else
4101 params[nparam] = tline->next;
4102 continue; /* parameter loop */
4104 if (tline->type == TOK_OTHER
4105 && tline->text[1] == 0) {
4106 char ch = tline->text[0];
4107 if (ch == ',' && !paren && brackets <= 0) {
4108 if (++nparam >= sparam) {
4109 sparam += PARAM_DELTA;
4110 params = nasm_realloc(params,
4111 sparam * sizeof(Token *));
4112 paramsize = nasm_realloc(paramsize,
4113 sparam * sizeof(int));
4115 params[nparam] = tline->next;
4116 paramsize[nparam] = 0;
4117 white = 0;
4118 continue; /* parameter loop */
4120 if (ch == '{' &&
4121 (brackets > 0 || (brackets == 0 &&
4122 !paramsize[nparam])))
4124 if (!(brackets++)) {
4125 params[nparam] = tline->next;
4126 continue; /* parameter loop */
4129 if (ch == '}' && brackets > 0)
4130 if (--brackets == 0) {
4131 brackets = -1;
4132 continue; /* parameter loop */
4134 if (ch == '(' && !brackets)
4135 paren++;
4136 if (ch == ')' && brackets <= 0)
4137 if (--paren < 0)
4138 break;
4140 if (brackets < 0) {
4141 brackets = 0;
4142 error(ERR_NONFATAL, "braces do not "
4143 "enclose all of macro parameter");
4145 paramsize[nparam] += white + 1;
4146 white = 0;
4147 } /* parameter loop */
4148 nparam++;
4149 while (m && (m->nparam != nparam ||
4150 mstrcmp(m->name, mname,
4151 m->casesense)))
4152 m = m->next;
4153 if (!m)
4154 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4155 "macro `%s' exists, "
4156 "but not taking %d parameters",
4157 mstart->text, nparam);
4160 if (m && m->in_progress)
4161 m = NULL;
4162 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4164 * Design question: should we handle !tline, which
4165 * indicates missing ')' here, or expand those
4166 * macros anyway, which requires the (t) test a few
4167 * lines down?
4169 nasm_free(params);
4170 nasm_free(paramsize);
4171 tline = mstart;
4172 } else {
4174 * Expand the macro: we are placed on the last token of the
4175 * call, so that we can easily split the call from the
4176 * following tokens. We also start by pushing an SMAC_END
4177 * token for the cycle removal.
4179 t = tline;
4180 if (t) {
4181 tline = t->next;
4182 t->next = NULL;
4184 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4185 tt->a.mac = m;
4186 m->in_progress = true;
4187 tline = tt;
4188 list_for_each(t, m->expansion) {
4189 if (t->type >= TOK_SMAC_PARAM) {
4190 Token *pcopy = tline, **ptail = &pcopy;
4191 Token *ttt, *pt;
4192 int i;
4194 ttt = params[t->type - TOK_SMAC_PARAM];
4195 i = paramsize[t->type - TOK_SMAC_PARAM];
4196 while (--i >= 0) {
4197 pt = *ptail = new_Token(tline, ttt->type,
4198 ttt->text, 0);
4199 ptail = &pt->next;
4200 ttt = ttt->next;
4202 tline = pcopy;
4203 } else if (t->type == TOK_PREPROC_Q) {
4204 tt = new_Token(tline, TOK_ID, mname, 0);
4205 tline = tt;
4206 } else if (t->type == TOK_PREPROC_QQ) {
4207 tt = new_Token(tline, TOK_ID, m->name, 0);
4208 tline = tt;
4209 } else {
4210 tt = new_Token(tline, t->type, t->text, 0);
4211 tline = tt;
4216 * Having done that, get rid of the macro call, and clean
4217 * up the parameters.
4219 nasm_free(params);
4220 nasm_free(paramsize);
4221 free_tlist(mstart);
4222 expanded = true;
4223 continue; /* main token loop */
4228 if (tline->type == TOK_SMAC_END) {
4229 tline->a.mac->in_progress = false;
4230 tline = delete_Token(tline);
4231 } else {
4232 t = *tail = tline;
4233 tline = tline->next;
4234 t->a.mac = NULL;
4235 t->next = NULL;
4236 tail = &t->next;
4241 * Now scan the entire line and look for successive TOK_IDs that resulted
4242 * after expansion (they can't be produced by tokenize()). The successive
4243 * TOK_IDs should be concatenated.
4244 * Also we look for %+ tokens and concatenate the tokens before and after
4245 * them (without white spaces in between).
4247 if (expanded && paste_tokens(&thead, true)) {
4249 * If we concatenated something, *and* we had previously expanded
4250 * an actual macro, scan the lines again for macros...
4252 tline = thead;
4253 expanded = false;
4254 goto again;
4257 err:
4258 if (org_tline) {
4259 if (thead) {
4260 *org_tline = *thead;
4261 /* since we just gave text to org_line, don't free it */
4262 thead->text = NULL;
4263 delete_Token(thead);
4264 } else {
4265 /* the expression expanded to empty line;
4266 we can't return NULL for some reasons
4267 we just set the line to a single WHITESPACE token. */
4268 memset(org_tline, 0, sizeof(*org_tline));
4269 org_tline->text = NULL;
4270 org_tline->type = TOK_WHITESPACE;
4272 thead = org_tline;
4275 return thead;
4279 * Similar to expand_smacro but used exclusively with macro identifiers
4280 * right before they are fetched in. The reason is that there can be
4281 * identifiers consisting of several subparts. We consider that if there
4282 * are more than one element forming the name, user wants a expansion,
4283 * otherwise it will be left as-is. Example:
4285 * %define %$abc cde
4287 * the identifier %$abc will be left as-is so that the handler for %define
4288 * will suck it and define the corresponding value. Other case:
4290 * %define _%$abc cde
4292 * In this case user wants name to be expanded *before* %define starts
4293 * working, so we'll expand %$abc into something (if it has a value;
4294 * otherwise it will be left as-is) then concatenate all successive
4295 * PP_IDs into one.
4297 static Token *expand_id(Token * tline)
4299 Token *cur, *oldnext = NULL;
4301 if (!tline || !tline->next)
4302 return tline;
4304 cur = tline;
4305 while (cur->next &&
4306 (cur->next->type == TOK_ID ||
4307 cur->next->type == TOK_PREPROC_ID
4308 || cur->next->type == TOK_NUMBER))
4309 cur = cur->next;
4311 /* If identifier consists of just one token, don't expand */
4312 if (cur == tline)
4313 return tline;
4315 if (cur) {
4316 oldnext = cur->next; /* Detach the tail past identifier */
4317 cur->next = NULL; /* so that expand_smacro stops here */
4320 tline = expand_smacro(tline);
4322 if (cur) {
4323 /* expand_smacro possibly changhed tline; re-scan for EOL */
4324 cur = tline;
4325 while (cur && cur->next)
4326 cur = cur->next;
4327 if (cur)
4328 cur->next = oldnext;
4331 return tline;
4335 * Determine whether the given line constitutes a multi-line macro
4336 * call, and return the MMacro structure called if so. Doesn't have
4337 * to check for an initial label - that's taken care of in
4338 * expand_mmacro - but must check numbers of parameters. Guaranteed
4339 * to be called with tline->type == TOK_ID, so the putative macro
4340 * name is easy to find.
4342 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4344 MMacro *head, *m;
4345 Token **params;
4346 int nparam;
4348 head = (MMacro *) hash_findix(&mmacros, tline->text);
4351 * Efficiency: first we see if any macro exists with the given
4352 * name. If not, we can return NULL immediately. _Then_ we
4353 * count the parameters, and then we look further along the
4354 * list if necessary to find the proper MMacro.
4356 list_for_each(m, head)
4357 if (!mstrcmp(m->name, tline->text, m->casesense))
4358 break;
4359 if (!m)
4360 return NULL;
4363 * OK, we have a potential macro. Count and demarcate the
4364 * parameters.
4366 count_mmac_params(tline->next, &nparam, &params);
4369 * So we know how many parameters we've got. Find the MMacro
4370 * structure that handles this number.
4372 while (m) {
4373 if (m->nparam_min <= nparam
4374 && (m->plus || nparam <= m->nparam_max)) {
4376 * This one is right. Just check if cycle removal
4377 * prohibits us using it before we actually celebrate...
4379 if (m->in_progress > m->max_depth) {
4380 if (m->max_depth > 0) {
4381 error(ERR_WARNING,
4382 "reached maximum recursion depth of %i",
4383 m->max_depth);
4385 nasm_free(params);
4386 return NULL;
4389 * It's right, and we can use it. Add its default
4390 * parameters to the end of our list if necessary.
4392 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4393 params =
4394 nasm_realloc(params,
4395 ((m->nparam_min + m->ndefs +
4396 1) * sizeof(*params)));
4397 while (nparam < m->nparam_min + m->ndefs) {
4398 params[nparam] = m->defaults[nparam - m->nparam_min];
4399 nparam++;
4403 * If we've gone over the maximum parameter count (and
4404 * we're in Plus mode), ignore parameters beyond
4405 * nparam_max.
4407 if (m->plus && nparam > m->nparam_max)
4408 nparam = m->nparam_max;
4410 * Then terminate the parameter list, and leave.
4412 if (!params) { /* need this special case */
4413 params = nasm_malloc(sizeof(*params));
4414 nparam = 0;
4416 params[nparam] = NULL;
4417 *params_array = params;
4418 return m;
4421 * This one wasn't right: look for the next one with the
4422 * same name.
4424 list_for_each(m, m->next)
4425 if (!mstrcmp(m->name, tline->text, m->casesense))
4426 break;
4430 * After all that, we didn't find one with the right number of
4431 * parameters. Issue a warning, and fail to expand the macro.
4433 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4434 "macro `%s' exists, but not taking %d parameters",
4435 tline->text, nparam);
4436 nasm_free(params);
4437 return NULL;
4442 * Save MMacro invocation specific fields in
4443 * preparation for a recursive macro expansion
4445 static void push_mmacro(MMacro *m)
4447 MMacroInvocation *i;
4449 i = nasm_malloc(sizeof(MMacroInvocation));
4450 i->prev = m->prev;
4451 i->params = m->params;
4452 i->iline = m->iline;
4453 i->nparam = m->nparam;
4454 i->rotate = m->rotate;
4455 i->paramlen = m->paramlen;
4456 i->unique = m->unique;
4457 i->condcnt = m->condcnt;
4458 m->prev = i;
4463 * Restore MMacro invocation specific fields that were
4464 * saved during a previous recursive macro expansion
4466 static void pop_mmacro(MMacro *m)
4468 MMacroInvocation *i;
4470 if (m->prev) {
4471 i = m->prev;
4472 m->prev = i->prev;
4473 m->params = i->params;
4474 m->iline = i->iline;
4475 m->nparam = i->nparam;
4476 m->rotate = i->rotate;
4477 m->paramlen = i->paramlen;
4478 m->unique = i->unique;
4479 m->condcnt = i->condcnt;
4480 nasm_free(i);
4486 * Expand the multi-line macro call made by the given line, if
4487 * there is one to be expanded. If there is, push the expansion on
4488 * istk->expansion and return 1. Otherwise return 0.
4490 static int expand_mmacro(Token * tline)
4492 Token *startline = tline;
4493 Token *label = NULL;
4494 int dont_prepend = 0;
4495 Token **params, *t, *mtok, *tt;
4496 MMacro *m;
4497 Line *l, *ll;
4498 int i, nparam, *paramlen;
4499 const char *mname;
4501 t = tline;
4502 skip_white_(t);
4503 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4504 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4505 return 0;
4506 mtok = t;
4507 m = is_mmacro(t, &params);
4508 if (m) {
4509 mname = t->text;
4510 } else {
4511 Token *last;
4513 * We have an id which isn't a macro call. We'll assume
4514 * it might be a label; we'll also check to see if a
4515 * colon follows it. Then, if there's another id after
4516 * that lot, we'll check it again for macro-hood.
4518 label = last = t;
4519 t = t->next;
4520 if (tok_type_(t, TOK_WHITESPACE))
4521 last = t, t = t->next;
4522 if (tok_is_(t, ":")) {
4523 dont_prepend = 1;
4524 last = t, t = t->next;
4525 if (tok_type_(t, TOK_WHITESPACE))
4526 last = t, t = t->next;
4528 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4529 return 0;
4530 last->next = NULL;
4531 mname = t->text;
4532 tline = t;
4536 * Fix up the parameters: this involves stripping leading and
4537 * trailing whitespace, then stripping braces if they are
4538 * present.
4540 for (nparam = 0; params[nparam]; nparam++) ;
4541 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4543 for (i = 0; params[i]; i++) {
4544 int brace = false;
4545 int comma = (!m->plus || i < nparam - 1);
4547 t = params[i];
4548 skip_white_(t);
4549 if (tok_is_(t, "{"))
4550 t = t->next, brace = true, comma = false;
4551 params[i] = t;
4552 paramlen[i] = 0;
4553 while (t) {
4554 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4555 break; /* ... because we have hit a comma */
4556 if (comma && t->type == TOK_WHITESPACE
4557 && tok_is_(t->next, ","))
4558 break; /* ... or a space then a comma */
4559 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4560 break; /* ... or a brace */
4561 t = t->next;
4562 paramlen[i]++;
4567 * OK, we have a MMacro structure together with a set of
4568 * parameters. We must now go through the expansion and push
4569 * copies of each Line on to istk->expansion. Substitution of
4570 * parameter tokens and macro-local tokens doesn't get done
4571 * until the single-line macro substitution process; this is
4572 * because delaying them allows us to change the semantics
4573 * later through %rotate.
4575 * First, push an end marker on to istk->expansion, mark this
4576 * macro as in progress, and set up its invocation-specific
4577 * variables.
4579 ll = nasm_malloc(sizeof(Line));
4580 ll->next = istk->expansion;
4581 ll->finishes = m;
4582 ll->first = NULL;
4583 istk->expansion = ll;
4586 * Save the previous MMacro expansion in the case of
4587 * macro recursion
4589 if (m->max_depth && m->in_progress)
4590 push_mmacro(m);
4592 m->in_progress ++;
4593 m->params = params;
4594 m->iline = tline;
4595 m->nparam = nparam;
4596 m->rotate = 0;
4597 m->paramlen = paramlen;
4598 m->unique = unique++;
4599 m->lineno = 0;
4600 m->condcnt = 0;
4602 m->next_active = istk->mstk;
4603 istk->mstk = m;
4605 list_for_each(l, m->expansion) {
4606 Token **tail;
4608 ll = nasm_malloc(sizeof(Line));
4609 ll->finishes = NULL;
4610 ll->next = istk->expansion;
4611 istk->expansion = ll;
4612 tail = &ll->first;
4614 list_for_each(t, l->first) {
4615 Token *x = t;
4616 switch (t->type) {
4617 case TOK_PREPROC_Q:
4618 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4619 break;
4620 case TOK_PREPROC_QQ:
4621 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4622 break;
4623 case TOK_PREPROC_ID:
4624 if (t->text[1] == '0' && t->text[2] == '0') {
4625 dont_prepend = -1;
4626 x = label;
4627 if (!x)
4628 continue;
4630 /* fall through */
4631 default:
4632 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4633 break;
4635 tail = &tt->next;
4637 *tail = NULL;
4641 * If we had a label, push it on as the first line of
4642 * the macro expansion.
4644 if (label) {
4645 if (dont_prepend < 0)
4646 free_tlist(startline);
4647 else {
4648 ll = nasm_malloc(sizeof(Line));
4649 ll->finishes = NULL;
4650 ll->next = istk->expansion;
4651 istk->expansion = ll;
4652 ll->first = startline;
4653 if (!dont_prepend) {
4654 while (label->next)
4655 label = label->next;
4656 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4661 list->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4663 return 1;
4666 /* The function that actually does the error reporting */
4667 static void verror(int severity, const char *fmt, va_list arg)
4669 char buff[1024];
4671 vsnprintf(buff, sizeof(buff), fmt, arg);
4673 if (istk && istk->mstk && istk->mstk->name)
4674 nasm_error(severity, "(%s:%d) %s", istk->mstk->name,
4675 istk->mstk->lineno, buff);
4676 else
4677 nasm_error(severity, "%s", buff);
4681 * Since preprocessor always operate only on the line that didn't
4682 * arrived yet, we should always use ERR_OFFBY1.
4684 static void error(int severity, const char *fmt, ...)
4686 va_list arg;
4688 /* If we're in a dead branch of IF or something like it, ignore the error */
4689 if (istk && istk->conds && !emitting(istk->conds->state))
4690 return;
4692 va_start(arg, fmt);
4693 verror(severity, fmt, arg);
4694 va_end(arg);
4698 * Because %else etc are evaluated in the state context
4699 * of the previous branch, errors might get lost with error():
4700 * %if 0 ... %else trailing garbage ... %endif
4701 * So %else etc should report errors with this function.
4703 static void error_precond(int severity, const char *fmt, ...)
4705 va_list arg;
4707 /* Only ignore the error if it's really in a dead branch */
4708 if (istk && istk->conds && istk->conds->state == COND_NEVER)
4709 return;
4711 va_start(arg, fmt);
4712 verror(severity, fmt, arg);
4713 va_end(arg);
4716 static void
4717 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4719 Token *t;
4721 cstk = NULL;
4722 istk = nasm_malloc(sizeof(Include));
4723 istk->next = NULL;
4724 istk->conds = NULL;
4725 istk->expansion = NULL;
4726 istk->mstk = NULL;
4727 istk->fp = fopen(file, "r");
4728 istk->fname = NULL;
4729 src_set_fname(nasm_strdup(file));
4730 src_set_linnum(0);
4731 istk->lineinc = 1;
4732 if (!istk->fp)
4733 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4734 file);
4735 defining = NULL;
4736 nested_mac_count = 0;
4737 nested_rep_count = 0;
4738 init_macros();
4739 unique = 0;
4740 if (tasm_compatible_mode) {
4741 stdmacpos = nasm_stdmac;
4742 } else {
4743 stdmacpos = nasm_stdmac_after_tasm;
4745 any_extrastdmac = extrastdmac && *extrastdmac;
4746 do_predef = true;
4747 list = listgen;
4750 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4751 * The caller, however, will also pass in 3 for preprocess-only so
4752 * we can set __PASS__ accordingly.
4754 pass = apass > 2 ? 2 : apass;
4756 dephead = deptail = deplist;
4757 if (deplist) {
4758 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4759 sl->next = NULL;
4760 strcpy(sl->str, file);
4761 *deptail = sl;
4762 deptail = &sl->next;
4766 * Define the __PASS__ macro. This is defined here unlike
4767 * all the other builtins, because it is special -- it varies between
4768 * passes.
4770 t = nasm_malloc(sizeof(*t));
4771 t->next = NULL;
4772 make_tok_num(t, apass);
4773 t->a.mac = NULL;
4774 define_smacro(NULL, "__PASS__", true, 0, t);
4777 static char *pp_getline(void)
4779 char *line;
4780 Token *tline;
4782 while (1) {
4784 * Fetch a tokenized line, either from the macro-expansion
4785 * buffer or from the input file.
4787 tline = NULL;
4788 while (istk->expansion && istk->expansion->finishes) {
4789 Line *l = istk->expansion;
4790 if (!l->finishes->name && l->finishes->in_progress > 1) {
4791 Line *ll;
4794 * This is a macro-end marker for a macro with no
4795 * name, which means it's not really a macro at all
4796 * but a %rep block, and the `in_progress' field is
4797 * more than 1, meaning that we still need to
4798 * repeat. (1 means the natural last repetition; 0
4799 * means termination by %exitrep.) We have
4800 * therefore expanded up to the %endrep, and must
4801 * push the whole block on to the expansion buffer
4802 * again. We don't bother to remove the macro-end
4803 * marker: we'd only have to generate another one
4804 * if we did.
4806 l->finishes->in_progress--;
4807 list_for_each(l, l->finishes->expansion) {
4808 Token *t, *tt, **tail;
4810 ll = nasm_malloc(sizeof(Line));
4811 ll->next = istk->expansion;
4812 ll->finishes = NULL;
4813 ll->first = NULL;
4814 tail = &ll->first;
4816 list_for_each(t, l->first) {
4817 if (t->text || t->type == TOK_WHITESPACE) {
4818 tt = *tail = new_Token(NULL, t->type, t->text, 0);
4819 tail = &tt->next;
4823 istk->expansion = ll;
4825 } else {
4827 * Check whether a `%rep' was started and not ended
4828 * within this macro expansion. This can happen and
4829 * should be detected. It's a fatal error because
4830 * I'm too confused to work out how to recover
4831 * sensibly from it.
4833 if (defining) {
4834 if (defining->name)
4835 error(ERR_PANIC,
4836 "defining with name in expansion");
4837 else if (istk->mstk->name)
4838 error(ERR_FATAL,
4839 "`%%rep' without `%%endrep' within"
4840 " expansion of macro `%s'",
4841 istk->mstk->name);
4845 * FIXME: investigate the relationship at this point between
4846 * istk->mstk and l->finishes
4849 MMacro *m = istk->mstk;
4850 istk->mstk = m->next_active;
4851 if (m->name) {
4853 * This was a real macro call, not a %rep, and
4854 * therefore the parameter information needs to
4855 * be freed.
4857 if (m->prev) {
4858 pop_mmacro(m);
4859 l->finishes->in_progress --;
4860 } else {
4861 nasm_free(m->params);
4862 free_tlist(m->iline);
4863 nasm_free(m->paramlen);
4864 l->finishes->in_progress = 0;
4866 } else
4867 free_mmacro(m);
4869 istk->expansion = l->next;
4870 nasm_free(l);
4871 list->downlevel(LIST_MACRO);
4874 while (1) { /* until we get a line we can use */
4876 if (istk->expansion) { /* from a macro expansion */
4877 char *p;
4878 Line *l = istk->expansion;
4879 if (istk->mstk)
4880 istk->mstk->lineno++;
4881 tline = l->first;
4882 istk->expansion = l->next;
4883 nasm_free(l);
4884 p = detoken(tline, false);
4885 list->line(LIST_MACRO, p);
4886 nasm_free(p);
4887 break;
4889 line = read_line();
4890 if (line) { /* from the current input file */
4891 line = prepreproc(line);
4892 tline = tokenize(line);
4893 nasm_free(line);
4894 break;
4897 * The current file has ended; work down the istk
4900 Include *i = istk;
4901 fclose(i->fp);
4902 if (i->conds)
4903 error(ERR_FATAL,
4904 "expected `%%endif' before end of file");
4905 /* only set line and file name if there's a next node */
4906 if (i->next) {
4907 src_set_linnum(i->lineno);
4908 nasm_free(src_set_fname(i->fname));
4910 istk = i->next;
4911 list->downlevel(LIST_INCLUDE);
4912 nasm_free(i);
4913 if (!istk)
4914 return NULL;
4915 if (istk->expansion && istk->expansion->finishes)
4916 break;
4921 * We must expand MMacro parameters and MMacro-local labels
4922 * _before_ we plunge into directive processing, to cope
4923 * with things like `%define something %1' such as STRUC
4924 * uses. Unless we're _defining_ a MMacro, in which case
4925 * those tokens should be left alone to go into the
4926 * definition; and unless we're in a non-emitting
4927 * condition, in which case we don't want to meddle with
4928 * anything.
4930 if (!defining && !(istk->conds && !emitting(istk->conds->state))
4931 && !(istk->mstk && !istk->mstk->in_progress)) {
4932 tline = expand_mmac_params(tline);
4936 * Check the line to see if it's a preprocessor directive.
4938 if (do_directive(tline) == DIRECTIVE_FOUND) {
4939 continue;
4940 } else if (defining) {
4942 * We're defining a multi-line macro. We emit nothing
4943 * at all, and just
4944 * shove the tokenized line on to the macro definition.
4946 Line *l = nasm_malloc(sizeof(Line));
4947 l->next = defining->expansion;
4948 l->first = tline;
4949 l->finishes = NULL;
4950 defining->expansion = l;
4951 continue;
4952 } else if (istk->conds && !emitting(istk->conds->state)) {
4954 * We're in a non-emitting branch of a condition block.
4955 * Emit nothing at all, not even a blank line: when we
4956 * emerge from the condition we'll give a line-number
4957 * directive so we keep our place correctly.
4959 free_tlist(tline);
4960 continue;
4961 } else if (istk->mstk && !istk->mstk->in_progress) {
4963 * We're in a %rep block which has been terminated, so
4964 * we're walking through to the %endrep without
4965 * emitting anything. Emit nothing at all, not even a
4966 * blank line: when we emerge from the %rep block we'll
4967 * give a line-number directive so we keep our place
4968 * correctly.
4970 free_tlist(tline);
4971 continue;
4972 } else {
4973 tline = expand_smacro(tline);
4974 if (!expand_mmacro(tline)) {
4976 * De-tokenize the line again, and emit it.
4978 line = detoken(tline, true);
4979 free_tlist(tline);
4980 break;
4981 } else {
4982 continue; /* expand_mmacro calls free_tlist */
4987 return line;
4990 static void pp_cleanup(int pass)
4992 if (defining) {
4993 if (defining->name) {
4994 error(ERR_NONFATAL,
4995 "end of file while still defining macro `%s'",
4996 defining->name);
4997 } else {
4998 error(ERR_NONFATAL, "end of file while still in %%rep");
5001 free_mmacro(defining);
5002 defining = NULL;
5004 while (cstk)
5005 ctx_pop();
5006 free_macros();
5007 while (istk) {
5008 Include *i = istk;
5009 istk = istk->next;
5010 fclose(i->fp);
5011 nasm_free(i->fname);
5012 nasm_free(i);
5014 while (cstk)
5015 ctx_pop();
5016 nasm_free(src_set_fname(NULL));
5017 if (pass == 0) {
5018 IncPath *i;
5019 free_llist(predef);
5020 delete_Blocks();
5021 while ((i = ipath)) {
5022 ipath = i->next;
5023 if (i->path)
5024 nasm_free(i->path);
5025 nasm_free(i);
5030 void pp_include_path(char *path)
5032 IncPath *i;
5034 i = nasm_malloc(sizeof(IncPath));
5035 i->path = path ? nasm_strdup(path) : NULL;
5036 i->next = NULL;
5038 if (ipath) {
5039 IncPath *j = ipath;
5040 while (j->next)
5041 j = j->next;
5042 j->next = i;
5043 } else {
5044 ipath = i;
5048 void pp_pre_include(char *fname)
5050 Token *inc, *space, *name;
5051 Line *l;
5053 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5054 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5055 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5057 l = nasm_malloc(sizeof(Line));
5058 l->next = predef;
5059 l->first = inc;
5060 l->finishes = NULL;
5061 predef = l;
5064 void pp_pre_define(char *definition)
5066 Token *def, *space;
5067 Line *l;
5068 char *equals;
5070 equals = strchr(definition, '=');
5071 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5072 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5073 if (equals)
5074 *equals = ' ';
5075 space->next = tokenize(definition);
5076 if (equals)
5077 *equals = '=';
5079 l = nasm_malloc(sizeof(Line));
5080 l->next = predef;
5081 l->first = def;
5082 l->finishes = NULL;
5083 predef = l;
5086 void pp_pre_undefine(char *definition)
5088 Token *def, *space;
5089 Line *l;
5091 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5092 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5093 space->next = tokenize(definition);
5095 l = nasm_malloc(sizeof(Line));
5096 l->next = predef;
5097 l->first = def;
5098 l->finishes = NULL;
5099 predef = l;
5103 * Added by Keith Kanios:
5105 * This function is used to assist with "runtime" preprocessor
5106 * directives. (e.g. pp_runtime("%define __BITS__ 64");)
5108 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
5109 * PASS A VALID STRING TO THIS FUNCTION!!!!!
5112 void pp_runtime(char *definition)
5114 Token *def;
5116 def = tokenize(definition);
5117 if (do_directive(def) == NO_DIRECTIVE_FOUND)
5118 free_tlist(def);
5122 void pp_extra_stdmac(macros_t *macros)
5124 extrastdmac = macros;
5127 static void make_tok_num(Token * tok, int64_t val)
5129 char numbuf[20];
5130 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5131 tok->text = nasm_strdup(numbuf);
5132 tok->type = TOK_NUMBER;
5135 Preproc nasmpp = {
5136 pp_reset,
5137 pp_getline,
5138 pp_cleanup