prepoc: Fix heap-buffer-overflow in detoken
[nasm.git] / asm / preproc.c
blob475926d886ec9c2085c1217eb9e4d2307cbceb53
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2017 The NASM Authors - All Rights Reserved
4 * See the file AUTHORS included with the NASM distribution for
5 * the specific copyright holders.
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following
9 * conditions are met:
11 * * Redistributions of source code must retain the above copyright
12 * notice, this list of conditions and the following disclaimer.
13 * * Redistributions in binary form must reproduce the above
14 * copyright notice, this list of conditions and the following
15 * disclaimer in the documentation and/or other materials provided
16 * with the distribution.
18 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND
19 * CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
20 * INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
21 * MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
22 * DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR
23 * CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
24 * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
25 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
26 * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
27 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
28 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
29 * OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
30 * EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32 * ----------------------------------------------------------------------- */
35 * preproc.c macro preprocessor for the Netwide Assembler
38 /* Typical flow of text through preproc
40 * pp_getline gets tokenized lines, either
42 * from a macro expansion
44 * or
45 * {
46 * read_line gets raw text from stdmacpos, or predef, or current input file
47 * tokenize converts to tokens
48 * }
50 * expand_mmac_params is used to expand %1 etc., unless a macro is being
51 * defined or a false conditional is being processed
52 * (%0, %1, %+1, %-1, %%foo
54 * do_directive checks for directives
56 * expand_smacro is used to expand single line macros
58 * expand_mmacro is used to expand multi-line macros
60 * detoken is used to convert the line back to text
63 #include "compiler.h"
65 #include <stdio.h>
66 #include <stdarg.h>
67 #include <stdlib.h>
68 #include <stddef.h>
69 #include <string.h>
70 #include <ctype.h>
71 #include <limits.h>
73 #include "nasm.h"
74 #include "nasmlib.h"
75 #include "error.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
83 #include "listing.h"
85 typedef struct SMacro SMacro;
86 typedef struct MMacro MMacro;
87 typedef struct MMacroInvocation MMacroInvocation;
88 typedef struct Context Context;
89 typedef struct Token Token;
90 typedef struct Blocks Blocks;
91 typedef struct Line Line;
92 typedef struct Include Include;
93 typedef struct Cond Cond;
94 typedef struct IncPath IncPath;
97 * Note on the storage of both SMacro and MMacros: the hash table
98 * indexes them case-insensitively, and we then have to go through a
99 * linked list of potential case aliases (and, for MMacros, parameter
100 * ranges); this is to preserve the matching semantics of the earlier
101 * code. If the number of case aliases for a specific macro is a
102 * performance issue, you may want to reconsider your coding style.
106 * Store the definition of a single-line macro.
108 struct SMacro {
109 SMacro *next;
110 char *name;
111 bool casesense;
112 bool in_progress;
113 unsigned int nparam;
114 Token *expansion;
118 * Store the definition of a multi-line macro. This is also used to
119 * store the interiors of `%rep...%endrep' blocks, which are
120 * effectively self-re-invoking multi-line macros which simply
121 * don't have a name or bother to appear in the hash tables. %rep
122 * blocks are signified by having a NULL `name' field.
124 * In a MMacro describing a `%rep' block, the `in_progress' field
125 * isn't merely boolean, but gives the number of repeats left to
126 * run.
128 * The `next' field is used for storing MMacros in hash tables; the
129 * `next_active' field is for stacking them on istk entries.
131 * When a MMacro is being expanded, `params', `iline', `nparam',
132 * `paramlen', `rotate' and `unique' are local to the invocation.
134 struct MMacro {
135 MMacro *next;
136 MMacroInvocation *prev; /* previous invocation */
137 char *name;
138 int nparam_min, nparam_max;
139 bool casesense;
140 bool plus; /* is the last parameter greedy? */
141 bool nolist; /* is this macro listing-inhibited? */
142 int64_t in_progress; /* is this macro currently being expanded? */
143 int32_t max_depth; /* maximum number of recursive expansions allowed */
144 Token *dlist; /* All defaults as one list */
145 Token **defaults; /* Parameter default pointers */
146 int ndefs; /* number of default parameters */
147 Line *expansion;
149 MMacro *next_active;
150 MMacro *rep_nest; /* used for nesting %rep */
151 Token **params; /* actual parameters */
152 Token *iline; /* invocation line */
153 unsigned int nparam, rotate;
154 int *paramlen;
155 uint64_t unique;
156 int lineno; /* Current line number on expansion */
157 uint64_t condcnt; /* number of if blocks... */
159 const char *fname; /* File where defined */
160 int32_t xline; /* First line in macro */
164 /* Store the definition of a multi-line macro, as defined in a
165 * previous recursive macro expansion.
167 struct MMacroInvocation {
168 MMacroInvocation *prev; /* previous invocation */
169 Token **params; /* actual parameters */
170 Token *iline; /* invocation line */
171 unsigned int nparam, rotate;
172 int *paramlen;
173 uint64_t unique;
174 uint64_t condcnt;
179 * The context stack is composed of a linked list of these.
181 struct Context {
182 Context *next;
183 char *name;
184 struct hash_table localmac;
185 uint32_t number;
189 * This is the internal form which we break input lines up into.
190 * Typically stored in linked lists.
192 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
193 * necessarily used as-is, but is intended to denote the number of
194 * the substituted parameter. So in the definition
196 * %define a(x,y) ( (x) & ~(y) )
198 * the token representing `x' will have its type changed to
199 * TOK_SMAC_PARAM, but the one representing `y' will be
200 * TOK_SMAC_PARAM+1.
202 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
203 * which doesn't need quotes around it. Used in the pre-include
204 * mechanism as an alternative to trying to find a sensible type of
205 * quote to use on the filename we were passed.
207 enum pp_token_type {
208 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
209 TOK_PREPROC_ID, TOK_STRING,
210 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
211 TOK_INTERNAL_STRING,
212 TOK_PREPROC_Q, TOK_PREPROC_QQ,
213 TOK_PASTE, /* %+ */
214 TOK_INDIRECT, /* %[...] */
215 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
216 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
219 #define PP_CONCAT_MASK(x) (1 << (x))
220 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
222 struct tokseq_match {
223 int mask_head;
224 int mask_tail;
227 struct Token {
228 Token *next;
229 char *text;
230 union {
231 SMacro *mac; /* associated macro for TOK_SMAC_END */
232 size_t len; /* scratch length field */
233 } a; /* Auxiliary data */
234 enum pp_token_type type;
238 * Multi-line macro definitions are stored as a linked list of
239 * these, which is essentially a container to allow several linked
240 * lists of Tokens.
242 * Note that in this module, linked lists are treated as stacks
243 * wherever possible. For this reason, Lines are _pushed_ on to the
244 * `expansion' field in MMacro structures, so that the linked list,
245 * if walked, would give the macro lines in reverse order; this
246 * means that we can walk the list when expanding a macro, and thus
247 * push the lines on to the `expansion' field in _istk_ in reverse
248 * order (so that when popped back off they are in the right
249 * order). It may seem cockeyed, and it relies on my design having
250 * an even number of steps in, but it works...
252 * Some of these structures, rather than being actual lines, are
253 * markers delimiting the end of the expansion of a given macro.
254 * This is for use in the cycle-tracking and %rep-handling code.
255 * Such structures have `finishes' non-NULL, and `first' NULL. All
256 * others have `finishes' NULL, but `first' may still be NULL if
257 * the line is blank.
259 struct Line {
260 Line *next;
261 MMacro *finishes;
262 Token *first;
266 * To handle an arbitrary level of file inclusion, we maintain a
267 * stack (ie linked list) of these things.
269 struct Include {
270 Include *next;
271 FILE *fp;
272 Cond *conds;
273 Line *expansion;
274 const char *fname;
275 int lineno, lineinc;
276 MMacro *mstk; /* stack of active macros/reps */
280 * Include search path. This is simply a list of strings which get
281 * prepended, in turn, to the name of an include file, in an
282 * attempt to find the file if it's not in the current directory.
284 struct IncPath {
285 IncPath *next;
286 char *path;
290 * File real name hash, so we don't have to re-search the include
291 * path for every pass (and potentially more than that if a file
292 * is used more than once.)
294 struct hash_table FileHash;
297 * Conditional assembly: we maintain a separate stack of these for
298 * each level of file inclusion. (The only reason we keep the
299 * stacks separate is to ensure that a stray `%endif' in a file
300 * included from within the true branch of a `%if' won't terminate
301 * it and cause confusion: instead, rightly, it'll cause an error.)
303 struct Cond {
304 Cond *next;
305 int state;
307 enum {
309 * These states are for use just after %if or %elif: IF_TRUE
310 * means the condition has evaluated to truth so we are
311 * currently emitting, whereas IF_FALSE means we are not
312 * currently emitting but will start doing so if a %else comes
313 * up. In these states, all directives are admissible: %elif,
314 * %else and %endif. (And of course %if.)
316 COND_IF_TRUE, COND_IF_FALSE,
318 * These states come up after a %else: ELSE_TRUE means we're
319 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
320 * any %elif or %else will cause an error.
322 COND_ELSE_TRUE, COND_ELSE_FALSE,
324 * These states mean that we're not emitting now, and also that
325 * nothing until %endif will be emitted at all. COND_DONE is
326 * used when we've had our moment of emission
327 * and have now started seeing %elifs. COND_NEVER is used when
328 * the condition construct in question is contained within a
329 * non-emitting branch of a larger condition construct,
330 * or if there is an error.
332 COND_DONE, COND_NEVER
334 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
337 * These defines are used as the possible return values for do_directive
339 #define NO_DIRECTIVE_FOUND 0
340 #define DIRECTIVE_FOUND 1
343 * This define sets the upper limit for smacro and recursive mmacro
344 * expansions
346 #define DEADMAN_LIMIT (1 << 20)
348 /* max reps */
349 #define REP_LIMIT ((INT64_C(1) << 62))
352 * Condition codes. Note that we use c_ prefix not C_ because C_ is
353 * used in nasm.h for the "real" condition codes. At _this_ level,
354 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
355 * ones, so we need a different enum...
357 static const char * const conditions[] = {
358 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
359 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
360 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
362 enum pp_conds {
363 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
364 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
365 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
366 c_none = -1
368 static const enum pp_conds inverse_ccs[] = {
369 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
370 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,
371 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
375 * Directive names.
377 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
378 static int is_condition(enum preproc_token arg)
380 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
383 /* For TASM compatibility we need to be able to recognise TASM compatible
384 * conditional compilation directives. Using the NASM pre-processor does
385 * not work, so we look for them specifically from the following list and
386 * then jam in the equivalent NASM directive into the input stream.
389 enum {
390 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
391 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
394 static const char * const tasm_directives[] = {
395 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
396 "ifndef", "include", "local"
399 static int StackSize = 4;
400 static const char *StackPointer = "ebp";
401 static int ArgOffset = 8;
402 static int LocalOffset = 0;
404 static Context *cstk;
405 static Include *istk;
406 static IncPath *ipath = NULL;
408 static int pass; /* HACK: pass 0 = generate dependencies only */
409 static StrList **dephead;
411 static uint64_t unique; /* unique identifier numbers */
413 static Line *predef = NULL;
414 static bool do_predef;
417 * The current set of multi-line macros we have defined.
419 static struct hash_table mmacros;
422 * The current set of single-line macros we have defined.
424 static struct hash_table smacros;
427 * The multi-line macro we are currently defining, or the %rep
428 * block we are currently reading, if any.
430 static MMacro *defining;
432 static uint64_t nested_mac_count;
433 static uint64_t nested_rep_count;
436 * The number of macro parameters to allocate space for at a time.
438 #define PARAM_DELTA 16
441 * The standard macro set: defined in macros.c in a set of arrays.
442 * This gives our position in any macro set, while we are processing it.
443 * The stdmacset is an array of such macro sets.
445 static macros_t *stdmacpos;
446 static macros_t **stdmacnext;
447 static macros_t *stdmacros[8];
448 static macros_t *extrastdmac;
451 * Tokens are allocated in blocks to improve speed
453 #define TOKEN_BLOCKSIZE 4096
454 static Token *freeTokens = NULL;
455 struct Blocks {
456 Blocks *next;
457 void *chunk;
460 static Blocks blocks = { NULL, NULL };
463 * Forward declarations.
465 static void pp_add_stdmac(macros_t *macros);
466 static Token *expand_mmac_params(Token * tline);
467 static Token *expand_smacro(Token * tline);
468 static Token *expand_id(Token * tline);
469 static Context *get_ctx(const char *name, const char **namep);
470 static void make_tok_num(Token * tok, int64_t val);
471 static void pp_verror(int severity, const char *fmt, va_list ap);
472 static vefunc real_verror;
473 static void *new_Block(size_t size);
474 static void delete_Blocks(void);
475 static Token *new_Token(Token * next, enum pp_token_type type,
476 const char *text, int txtlen);
477 static Token *delete_Token(Token * t);
480 * Macros for safe checking of token pointers, avoid *(NULL)
482 #define tok_type_(x,t) ((x) && (x)->type == (t))
483 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
484 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
485 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
488 * nasm_unquote with error if the string contains NUL characters.
489 * If the string contains NUL characters, issue an error and return
490 * the C len, i.e. truncate at the NUL.
492 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
494 size_t len = nasm_unquote(qstr, NULL);
495 size_t clen = strlen(qstr);
497 if (len != clen)
498 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
499 pp_directives[directive]);
501 return clen;
505 * In-place reverse a list of tokens.
507 static Token *reverse_tokens(Token *t)
509 Token *prev = NULL;
510 Token *next;
512 while (t) {
513 next = t->next;
514 t->next = prev;
515 prev = t;
516 t = next;
519 return prev;
523 * Handle TASM specific directives, which do not contain a % in
524 * front of them. We do it here because I could not find any other
525 * place to do it for the moment, and it is a hack (ideally it would
526 * be nice to be able to use the NASM pre-processor to do it).
528 static char *check_tasm_directive(char *line)
530 int32_t i, j, k, m, len;
531 char *p, *q, *oldline, oldchar;
533 p = nasm_skip_spaces(line);
535 /* Binary search for the directive name */
536 i = -1;
537 j = ARRAY_SIZE(tasm_directives);
538 q = nasm_skip_word(p);
539 len = q - p;
540 if (len) {
541 oldchar = p[len];
542 p[len] = 0;
543 while (j - i > 1) {
544 k = (j + i) / 2;
545 m = nasm_stricmp(p, tasm_directives[k]);
546 if (m == 0) {
547 /* We have found a directive, so jam a % in front of it
548 * so that NASM will then recognise it as one if it's own.
550 p[len] = oldchar;
551 len = strlen(p);
552 oldline = line;
553 line = nasm_malloc(len + 2);
554 line[0] = '%';
555 if (k == TM_IFDIFI) {
557 * NASM does not recognise IFDIFI, so we convert
558 * it to %if 0. This is not used in NASM
559 * compatible code, but does need to parse for the
560 * TASM macro package.
562 strcpy(line + 1, "if 0");
563 } else {
564 memcpy(line + 1, p, len + 1);
566 nasm_free(oldline);
567 return line;
568 } else if (m < 0) {
569 j = k;
570 } else
571 i = k;
573 p[len] = oldchar;
575 return line;
579 * The pre-preprocessing stage... This function translates line
580 * number indications as they emerge from GNU cpp (`# lineno "file"
581 * flags') into NASM preprocessor line number indications (`%line
582 * lineno file').
584 static char *prepreproc(char *line)
586 int lineno, fnlen;
587 char *fname, *oldline;
589 if (line[0] == '#' && line[1] == ' ') {
590 oldline = line;
591 fname = oldline + 2;
592 lineno = atoi(fname);
593 fname += strspn(fname, "0123456789 ");
594 if (*fname == '"')
595 fname++;
596 fnlen = strcspn(fname, "\"");
597 line = nasm_malloc(20 + fnlen);
598 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
599 nasm_free(oldline);
601 if (tasm_compatible_mode)
602 return check_tasm_directive(line);
603 return line;
607 * Free a linked list of tokens.
609 static void free_tlist(Token * list)
611 while (list)
612 list = delete_Token(list);
616 * Free a linked list of lines.
618 static void free_llist(Line * list)
620 Line *l, *tmp;
621 list_for_each_safe(l, tmp, list) {
622 free_tlist(l->first);
623 nasm_free(l);
628 * Free an MMacro
630 static void free_mmacro(MMacro * m)
632 nasm_free(m->name);
633 free_tlist(m->dlist);
634 nasm_free(m->defaults);
635 free_llist(m->expansion);
636 nasm_free(m);
640 * Free all currently defined macros, and free the hash tables
642 static void free_smacro_table(struct hash_table *smt)
644 SMacro *s, *tmp;
645 const char *key;
646 struct hash_tbl_node *it = NULL;
648 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
649 nasm_free((void *)key);
650 list_for_each_safe(s, tmp, s) {
651 nasm_free(s->name);
652 free_tlist(s->expansion);
653 nasm_free(s);
656 hash_free(smt);
659 static void free_mmacro_table(struct hash_table *mmt)
661 MMacro *m, *tmp;
662 const char *key;
663 struct hash_tbl_node *it = NULL;
665 it = NULL;
666 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
667 nasm_free((void *)key);
668 list_for_each_safe(m ,tmp, m)
669 free_mmacro(m);
671 hash_free(mmt);
674 static void free_macros(void)
676 free_smacro_table(&smacros);
677 free_mmacro_table(&mmacros);
681 * Initialize the hash tables
683 static void init_macros(void)
685 hash_init(&smacros, HASH_LARGE);
686 hash_init(&mmacros, HASH_LARGE);
690 * Pop the context stack.
692 static void ctx_pop(void)
694 Context *c = cstk;
696 cstk = cstk->next;
697 free_smacro_table(&c->localmac);
698 nasm_free(c->name);
699 nasm_free(c);
703 * Search for a key in the hash index; adding it if necessary
704 * (in which case we initialize the data pointer to NULL.)
706 static void **
707 hash_findi_add(struct hash_table *hash, const char *str)
709 struct hash_insert hi;
710 void **r;
711 char *strx;
713 r = hash_findi(hash, str, &hi);
714 if (r)
715 return r;
717 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
718 return hash_add(&hi, strx, NULL);
722 * Like hash_findi, but returns the data element rather than a pointer
723 * to it. Used only when not adding a new element, hence no third
724 * argument.
726 static void *
727 hash_findix(struct hash_table *hash, const char *str)
729 void **p;
731 p = hash_findi(hash, str, NULL);
732 return p ? *p : NULL;
736 * read line from standart macros set,
737 * if there no more left -- return NULL
739 static char *line_from_stdmac(void)
741 unsigned char c;
742 const unsigned char *p = stdmacpos;
743 char *line, *q;
744 size_t len = 0;
746 if (!stdmacpos)
747 return NULL;
749 while ((c = *p++)) {
750 if (c >= 0x80)
751 len += pp_directives_len[c - 0x80] + 1;
752 else
753 len++;
756 line = nasm_malloc(len + 1);
757 q = line;
758 while ((c = *stdmacpos++)) {
759 if (c >= 0x80) {
760 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
761 q += pp_directives_len[c - 0x80];
762 *q++ = ' ';
763 } else {
764 *q++ = c;
767 stdmacpos = p;
768 *q = '\0';
770 if (!*stdmacpos) {
771 /* This was the last of this particular macro set */
772 stdmacpos = NULL;
773 if (*stdmacnext) {
774 stdmacpos = *stdmacnext++;
775 } else if (do_predef) {
776 Line *pd, *l;
777 Token *head, **tail, *t;
780 * Nasty hack: here we push the contents of
781 * `predef' on to the top-level expansion stack,
782 * since this is the most convenient way to
783 * implement the pre-include and pre-define
784 * features.
786 list_for_each(pd, predef) {
787 head = NULL;
788 tail = &head;
789 list_for_each(t, pd->first) {
790 *tail = new_Token(NULL, t->type, t->text, 0);
791 tail = &(*tail)->next;
794 l = nasm_malloc(sizeof(Line));
795 l->next = istk->expansion;
796 l->first = head;
797 l->finishes = NULL;
799 istk->expansion = l;
801 do_predef = false;
805 return line;
808 static char *read_line(void)
810 unsigned int size, c, next;
811 const unsigned int delta = 512;
812 const unsigned int pad = 8;
813 unsigned int nr_cont = 0;
814 bool cont = false;
815 char *buffer, *p;
817 /* Standart macros set (predefined) goes first */
818 p = line_from_stdmac();
819 if (p)
820 return p;
822 size = delta;
823 p = buffer = nasm_malloc(size);
825 for (;;) {
826 c = fgetc(istk->fp);
827 if ((int)(c) == EOF) {
828 p[0] = 0;
829 break;
832 switch (c) {
833 case '\r':
834 next = fgetc(istk->fp);
835 if (next != '\n')
836 ungetc(next, istk->fp);
837 if (cont) {
838 cont = false;
839 continue;
841 break;
843 case '\n':
844 if (cont) {
845 cont = false;
846 continue;
848 break;
850 case '\\':
851 next = fgetc(istk->fp);
852 ungetc(next, istk->fp);
853 if (next == '\r' || next == '\n') {
854 cont = true;
855 nr_cont++;
856 continue;
858 break;
861 if (c == '\r' || c == '\n') {
862 *p++ = 0;
863 break;
866 if (p >= (buffer + size - pad)) {
867 buffer = nasm_realloc(buffer, size + delta);
868 p = buffer + size - pad;
869 size += delta;
872 *p++ = (unsigned char)c;
875 if (p == buffer) {
876 nasm_free(buffer);
877 return NULL;
880 src_set_linnum(src_get_linnum() + istk->lineinc +
881 (nr_cont * istk->lineinc));
884 * Handle spurious ^Z, which may be inserted into source files
885 * by some file transfer utilities.
887 buffer[strcspn(buffer, "\032")] = '\0';
889 lfmt->line(LIST_READ, buffer);
891 return buffer;
895 * Tokenize a line of text. This is a very simple process since we
896 * don't need to parse the value out of e.g. numeric tokens: we
897 * simply split one string into many.
899 static Token *tokenize(char *line)
901 char c, *p = line;
902 enum pp_token_type type;
903 Token *list = NULL;
904 Token *t, **tail = &list;
906 while (*line) {
907 p = line;
908 if (*p == '%') {
909 p++;
910 if (*p == '+' && !nasm_isdigit(p[1])) {
911 p++;
912 type = TOK_PASTE;
913 } else if (nasm_isdigit(*p) ||
914 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
915 do {
916 p++;
918 while (nasm_isdigit(*p));
919 type = TOK_PREPROC_ID;
920 } else if (*p == '{') {
921 p++;
922 while (*p) {
923 if (*p == '}')
924 break;
925 p[-1] = *p;
926 p++;
928 if (*p != '}')
929 nasm_error(ERR_WARNING | ERR_PASS1,
930 "unterminated %%{ construct");
931 p[-1] = '\0';
932 if (*p)
933 p++;
934 type = TOK_PREPROC_ID;
935 } else if (*p == '[') {
936 int lvl = 1;
937 line += 2; /* Skip the leading %[ */
938 p++;
939 while (lvl && (c = *p++)) {
940 switch (c) {
941 case ']':
942 lvl--;
943 break;
944 case '%':
945 if (*p == '[')
946 lvl++;
947 break;
948 case '\'':
949 case '\"':
950 case '`':
951 p = nasm_skip_string(p - 1);
952 if (*p)
953 p++;
954 break;
955 default:
956 break;
959 p--;
960 if (*p)
961 *p++ = '\0';
962 if (lvl)
963 nasm_error(ERR_NONFATAL|ERR_PASS1,
964 "unterminated %%[ construct");
965 type = TOK_INDIRECT;
966 } else if (*p == '?') {
967 type = TOK_PREPROC_Q; /* %? */
968 p++;
969 if (*p == '?') {
970 type = TOK_PREPROC_QQ; /* %?? */
971 p++;
973 } else if (*p == '!') {
974 type = TOK_PREPROC_ID;
975 p++;
976 if (isidchar(*p)) {
977 do {
978 p++;
980 while (isidchar(*p));
981 } else if (*p == '\'' || *p == '\"' || *p == '`') {
982 p = nasm_skip_string(p);
983 if (*p)
984 p++;
985 else
986 nasm_error(ERR_NONFATAL|ERR_PASS1,
987 "unterminated %%! string");
988 } else {
989 /* %! without string or identifier */
990 type = TOK_OTHER; /* Legacy behavior... */
992 } else if (isidchar(*p) ||
993 ((*p == '!' || *p == '%' || *p == '$') &&
994 isidchar(p[1]))) {
995 do {
996 p++;
998 while (isidchar(*p));
999 type = TOK_PREPROC_ID;
1000 } else {
1001 type = TOK_OTHER;
1002 if (*p == '%')
1003 p++;
1005 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1006 type = TOK_ID;
1007 p++;
1008 while (*p && isidchar(*p))
1009 p++;
1010 } else if (*p == '\'' || *p == '"' || *p == '`') {
1012 * A string token.
1014 type = TOK_STRING;
1015 p = nasm_skip_string(p);
1017 if (*p) {
1018 p++;
1019 } else {
1020 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1021 /* Handling unterminated strings by UNV */
1022 /* type = -1; */
1024 } else if (p[0] == '$' && p[1] == '$') {
1025 type = TOK_OTHER; /* TOKEN_BASE */
1026 p += 2;
1027 } else if (isnumstart(*p)) {
1028 bool is_hex = false;
1029 bool is_float = false;
1030 bool has_e = false;
1031 char c, *r;
1034 * A numeric token.
1037 if (*p == '$') {
1038 p++;
1039 is_hex = true;
1042 for (;;) {
1043 c = *p++;
1045 if (!is_hex && (c == 'e' || c == 'E')) {
1046 has_e = true;
1047 if (*p == '+' || *p == '-') {
1049 * e can only be followed by +/- if it is either a
1050 * prefixed hex number or a floating-point number
1052 p++;
1053 is_float = true;
1055 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1056 is_hex = true;
1057 } else if (c == 'P' || c == 'p') {
1058 is_float = true;
1059 if (*p == '+' || *p == '-')
1060 p++;
1061 } else if (isnumchar(c))
1062 ; /* just advance */
1063 else if (c == '.') {
1065 * we need to deal with consequences of the legacy
1066 * parser, like "1.nolist" being two tokens
1067 * (TOK_NUMBER, TOK_ID) here; at least give it
1068 * a shot for now. In the future, we probably need
1069 * a flex-based scanner with proper pattern matching
1070 * to do it as well as it can be done. Nothing in
1071 * the world is going to help the person who wants
1072 * 0x123.p16 interpreted as two tokens, though.
1074 r = p;
1075 while (*r == '_')
1076 r++;
1078 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1079 (!is_hex && (*r == 'e' || *r == 'E')) ||
1080 (*r == 'p' || *r == 'P')) {
1081 p = r;
1082 is_float = true;
1083 } else
1084 break; /* Terminate the token */
1085 } else
1086 break;
1088 p--; /* Point to first character beyond number */
1090 if (p == line+1 && *line == '$') {
1091 type = TOK_OTHER; /* TOKEN_HERE */
1092 } else {
1093 if (has_e && !is_hex) {
1094 /* 1e13 is floating-point, but 1e13h is not */
1095 is_float = true;
1098 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1100 } else if (nasm_isspace(*p)) {
1101 type = TOK_WHITESPACE;
1102 p = nasm_skip_spaces(p);
1104 * Whitespace just before end-of-line is discarded by
1105 * pretending it's a comment; whitespace just before a
1106 * comment gets lumped into the comment.
1108 if (!*p || *p == ';') {
1109 type = TOK_COMMENT;
1110 while (*p)
1111 p++;
1113 } else if (*p == ';') {
1114 type = TOK_COMMENT;
1115 while (*p)
1116 p++;
1117 } else {
1119 * Anything else is an operator of some kind. We check
1120 * for all the double-character operators (>>, <<, //,
1121 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1122 * else is a single-character operator.
1124 type = TOK_OTHER;
1125 if ((p[0] == '>' && p[1] == '>') ||
1126 (p[0] == '<' && p[1] == '<') ||
1127 (p[0] == '/' && p[1] == '/') ||
1128 (p[0] == '<' && p[1] == '=') ||
1129 (p[0] == '>' && p[1] == '=') ||
1130 (p[0] == '=' && p[1] == '=') ||
1131 (p[0] == '!' && p[1] == '=') ||
1132 (p[0] == '<' && p[1] == '>') ||
1133 (p[0] == '&' && p[1] == '&') ||
1134 (p[0] == '|' && p[1] == '|') ||
1135 (p[0] == '^' && p[1] == '^')) {
1136 p++;
1138 p++;
1141 /* Handling unterminated string by UNV */
1142 /*if (type == -1)
1144 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1145 t->text[p-line] = *line;
1146 tail = &t->next;
1148 else */
1149 if (type != TOK_COMMENT) {
1150 *tail = t = new_Token(NULL, type, line, p - line);
1151 tail = &t->next;
1153 line = p;
1155 return list;
1159 * this function allocates a new managed block of memory and
1160 * returns a pointer to the block. The managed blocks are
1161 * deleted only all at once by the delete_Blocks function.
1163 static void *new_Block(size_t size)
1165 Blocks *b = &blocks;
1167 /* first, get to the end of the linked list */
1168 while (b->next)
1169 b = b->next;
1170 /* now allocate the requested chunk */
1171 b->chunk = nasm_malloc(size);
1173 /* now allocate a new block for the next request */
1174 b->next = nasm_zalloc(sizeof(Blocks));
1175 return b->chunk;
1179 * this function deletes all managed blocks of memory
1181 static void delete_Blocks(void)
1183 Blocks *a, *b = &blocks;
1186 * keep in mind that the first block, pointed to by blocks
1187 * is a static and not dynamically allocated, so we don't
1188 * free it.
1190 while (b) {
1191 if (b->chunk)
1192 nasm_free(b->chunk);
1193 a = b;
1194 b = b->next;
1195 if (a != &blocks)
1196 nasm_free(a);
1198 memset(&blocks, 0, sizeof(blocks));
1202 * this function creates a new Token and passes a pointer to it
1203 * back to the caller. It sets the type and text elements, and
1204 * also the a.mac and next elements to NULL.
1206 static Token *new_Token(Token * next, enum pp_token_type type,
1207 const char *text, int txtlen)
1209 Token *t;
1210 int i;
1212 if (!freeTokens) {
1213 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1214 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1215 freeTokens[i].next = &freeTokens[i + 1];
1216 freeTokens[i].next = NULL;
1218 t = freeTokens;
1219 freeTokens = t->next;
1220 t->next = next;
1221 t->a.mac = NULL;
1222 t->type = type;
1223 if (type == TOK_WHITESPACE || !text) {
1224 t->text = NULL;
1225 } else {
1226 if (txtlen == 0)
1227 txtlen = strlen(text);
1228 t->text = nasm_malloc(txtlen+1);
1229 memcpy(t->text, text, txtlen);
1230 t->text[txtlen] = '\0';
1232 return t;
1235 static Token *delete_Token(Token * t)
1237 Token *next = t->next;
1238 nasm_free(t->text);
1239 t->next = freeTokens;
1240 freeTokens = t;
1241 return next;
1245 * Convert a line of tokens back into text.
1246 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1247 * will be transformed into ..@ctxnum.xxx
1249 static char *detoken(Token * tlist, bool expand_locals)
1251 Token *t;
1252 char *line, *p;
1253 const char *q;
1254 int len = 0;
1256 list_for_each(t, tlist) {
1257 if (t->type == TOK_PREPROC_ID && t->text &&
1258 t->text[0] && t->text[1] == '!') {
1259 char *v;
1260 char *q = t->text;
1262 v = t->text + 2;
1263 if (*v == '\'' || *v == '\"' || *v == '`') {
1264 size_t len = nasm_unquote(v, NULL);
1265 size_t clen = strlen(v);
1267 if (len != clen) {
1268 nasm_error(ERR_NONFATAL | ERR_PASS1,
1269 "NUL character in %%! string");
1270 v = NULL;
1274 if (v) {
1275 char *p = getenv(v);
1276 if (!p) {
1277 nasm_error(ERR_NONFATAL | ERR_PASS1,
1278 "nonexistent environment variable `%s'", v);
1280 * FIXME We better should investigate if accessing
1281 * ->text[1] without ->text[0] is safe enough.
1283 t->text = nasm_zalloc(2);
1284 } else
1285 t->text = nasm_strdup(p);
1286 nasm_free(q);
1290 /* Expand local macros here and not during preprocessing */
1291 if (expand_locals &&
1292 t->type == TOK_PREPROC_ID && t->text &&
1293 t->text[0] == '%' && t->text[1] == '$') {
1294 const char *q;
1295 char *p;
1296 Context *ctx = get_ctx(t->text, &q);
1297 if (ctx) {
1298 char buffer[40];
1299 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1300 p = nasm_strcat(buffer, q);
1301 nasm_free(t->text);
1302 t->text = p;
1305 if (t->type == TOK_WHITESPACE)
1306 len++;
1307 else if (t->text)
1308 len += strlen(t->text);
1311 p = line = nasm_malloc(len + 1);
1313 list_for_each(t, tlist) {
1314 if (t->type == TOK_WHITESPACE) {
1315 *p++ = ' ';
1316 } else if (t->text) {
1317 q = t->text;
1318 while (*q)
1319 *p++ = *q++;
1322 *p = '\0';
1324 return line;
1328 * A scanner, suitable for use by the expression evaluator, which
1329 * operates on a line of Tokens. Expects a pointer to a pointer to
1330 * the first token in the line to be passed in as its private_data
1331 * field.
1333 * FIX: This really needs to be unified with stdscan.
1335 static int ppscan(void *private_data, struct tokenval *tokval)
1337 Token **tlineptr = private_data;
1338 Token *tline;
1339 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1341 do {
1342 tline = *tlineptr;
1343 *tlineptr = tline ? tline->next : NULL;
1344 } while (tline && (tline->type == TOK_WHITESPACE ||
1345 tline->type == TOK_COMMENT));
1347 if (!tline)
1348 return tokval->t_type = TOKEN_EOS;
1350 tokval->t_charptr = tline->text;
1352 if (tline->text[0] == '$' && !tline->text[1])
1353 return tokval->t_type = TOKEN_HERE;
1354 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1355 return tokval->t_type = TOKEN_BASE;
1357 if (tline->type == TOK_ID) {
1358 p = tokval->t_charptr = tline->text;
1359 if (p[0] == '$') {
1360 tokval->t_charptr++;
1361 return tokval->t_type = TOKEN_ID;
1364 for (r = p, s = ourcopy; *r; r++) {
1365 if (r >= p+MAX_KEYWORD)
1366 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1367 *s++ = nasm_tolower(*r);
1369 *s = '\0';
1370 /* right, so we have an identifier sitting in temp storage. now,
1371 * is it actually a register or instruction name, or what? */
1372 return nasm_token_hash(ourcopy, tokval);
1375 if (tline->type == TOK_NUMBER) {
1376 bool rn_error;
1377 tokval->t_integer = readnum(tline->text, &rn_error);
1378 tokval->t_charptr = tline->text;
1379 if (rn_error)
1380 return tokval->t_type = TOKEN_ERRNUM;
1381 else
1382 return tokval->t_type = TOKEN_NUM;
1385 if (tline->type == TOK_FLOAT) {
1386 return tokval->t_type = TOKEN_FLOAT;
1389 if (tline->type == TOK_STRING) {
1390 char bq, *ep;
1392 bq = tline->text[0];
1393 tokval->t_charptr = tline->text;
1394 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1396 if (ep[0] != bq || ep[1] != '\0')
1397 return tokval->t_type = TOKEN_ERRSTR;
1398 else
1399 return tokval->t_type = TOKEN_STR;
1402 if (tline->type == TOK_OTHER) {
1403 if (!strcmp(tline->text, "<<"))
1404 return tokval->t_type = TOKEN_SHL;
1405 if (!strcmp(tline->text, ">>"))
1406 return tokval->t_type = TOKEN_SHR;
1407 if (!strcmp(tline->text, "//"))
1408 return tokval->t_type = TOKEN_SDIV;
1409 if (!strcmp(tline->text, "%%"))
1410 return tokval->t_type = TOKEN_SMOD;
1411 if (!strcmp(tline->text, "=="))
1412 return tokval->t_type = TOKEN_EQ;
1413 if (!strcmp(tline->text, "<>"))
1414 return tokval->t_type = TOKEN_NE;
1415 if (!strcmp(tline->text, "!="))
1416 return tokval->t_type = TOKEN_NE;
1417 if (!strcmp(tline->text, "<="))
1418 return tokval->t_type = TOKEN_LE;
1419 if (!strcmp(tline->text, ">="))
1420 return tokval->t_type = TOKEN_GE;
1421 if (!strcmp(tline->text, "&&"))
1422 return tokval->t_type = TOKEN_DBL_AND;
1423 if (!strcmp(tline->text, "^^"))
1424 return tokval->t_type = TOKEN_DBL_XOR;
1425 if (!strcmp(tline->text, "||"))
1426 return tokval->t_type = TOKEN_DBL_OR;
1430 * We have no other options: just return the first character of
1431 * the token text.
1433 return tokval->t_type = tline->text[0];
1437 * Compare a string to the name of an existing macro; this is a
1438 * simple wrapper which calls either strcmp or nasm_stricmp
1439 * depending on the value of the `casesense' parameter.
1441 static int mstrcmp(const char *p, const char *q, bool casesense)
1443 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1447 * Compare a string to the name of an existing macro; this is a
1448 * simple wrapper which calls either strcmp or nasm_stricmp
1449 * depending on the value of the `casesense' parameter.
1451 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1453 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1457 * Return the Context structure associated with a %$ token. Return
1458 * NULL, having _already_ reported an error condition, if the
1459 * context stack isn't deep enough for the supplied number of $
1460 * signs.
1462 * If "namep" is non-NULL, set it to the pointer to the macro name
1463 * tail, i.e. the part beyond %$...
1465 static Context *get_ctx(const char *name, const char **namep)
1467 Context *ctx;
1468 int i;
1470 if (namep)
1471 *namep = name;
1473 if (!name || name[0] != '%' || name[1] != '$')
1474 return NULL;
1476 if (!cstk) {
1477 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1478 return NULL;
1481 name += 2;
1482 ctx = cstk;
1483 i = 0;
1484 while (ctx && *name == '$') {
1485 name++;
1486 i++;
1487 ctx = ctx->next;
1489 if (!ctx) {
1490 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1491 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1492 return NULL;
1495 if (namep)
1496 *namep = name;
1498 return ctx;
1502 * Open an include file. This routine must always return a valid
1503 * file pointer if it returns - it's responsible for throwing an
1504 * ERR_FATAL and bombing out completely if not. It should also try
1505 * the include path one by one until it finds the file or reaches
1506 * the end of the path.
1508 * Note: for INC_PROBE the function returns NULL at all times;
1509 * instead look for the
1511 enum incopen_mode {
1512 INC_NEEDED, /* File must exist */
1513 INC_OPTIONAL, /* Missing is OK */
1514 INC_PROBE /* Only an existence probe */
1517 /* This is conducts a full pathname search */
1518 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1519 enum incopen_mode omode, enum file_flags fmode)
1521 FILE *fp;
1522 char *prefix = "";
1523 const IncPath *ip = ipath;
1524 int len = strlen(file);
1525 size_t prefix_len = 0;
1526 StrList *sl;
1527 size_t path_len;
1528 bool found;
1530 while (1) {
1531 path_len = prefix_len + len + 1;
1533 sl = nasm_malloc(path_len + sizeof sl->next);
1534 memcpy(sl->str, prefix, prefix_len);
1535 memcpy(sl->str+prefix_len, file, len+1);
1536 sl->next = NULL;
1538 if (omode == INC_PROBE) {
1539 fp = NULL;
1540 found = nasm_file_exists(sl->str);
1541 } else {
1542 fp = nasm_open_read(sl->str, fmode);
1543 found = (fp != NULL);
1545 if (found) {
1546 *slpath = sl;
1547 return fp;
1550 nasm_free(sl);
1552 if (!ip)
1553 return NULL;
1555 prefix = ip->path;
1556 prefix_len = strlen(prefix);
1557 ip = ip->next;
1562 * Open a file, or test for the presence of one (depending on omode),
1563 * considering the include path.
1565 static FILE *inc_fopen(const char *file,
1566 StrList **dhead,
1567 const char **found_path,
1568 enum incopen_mode omode,
1569 enum file_flags fmode)
1571 StrList *sl;
1572 struct hash_insert hi;
1573 void **hp;
1574 char *path;
1575 FILE *fp = NULL;
1577 hp = hash_find(&FileHash, file, &hi);
1578 if (hp) {
1579 path = *hp;
1580 if (path || omode != INC_NEEDED) {
1581 nasm_add_string_to_strlist(dhead, path ? path : file);
1583 } else {
1584 /* Need to do the actual path search */
1585 size_t file_len;
1587 sl = NULL;
1588 fp = inc_fopen_search(file, &sl, omode, fmode);
1590 file_len = strlen(file);
1592 if (!sl) {
1593 /* Store negative result for this file */
1594 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1595 memcpy(sl->str, file, file_len+1);
1596 sl->next = NULL;
1597 file = sl->str;
1598 path = NULL;
1599 } else {
1600 path = sl->str;
1601 file = strchr(path, '\0') - file_len;
1604 hash_add(&hi, file, path); /* Positive or negative result */
1607 * Add file to dependency path. The in_list() is needed
1608 * in case the file was already added with %depend.
1610 if (path || omode != INC_NEEDED)
1611 nasm_add_to_strlist(dhead, sl);
1614 if (!path) {
1615 if (omode == INC_NEEDED)
1616 nasm_fatal(0, "unable to open include file `%s'", file);
1618 if (found_path)
1619 *found_path = NULL;
1621 return NULL;
1624 if (!fp && omode != INC_PROBE)
1625 fp = nasm_open_read(path, fmode);
1627 if (found_path)
1628 *found_path = path;
1630 return fp;
1634 * Opens an include or input file. Public version, for use by modules
1635 * that get a file:lineno pair and need to look at the file again
1636 * (e.g. the CodeView debug backend). Returns NULL on failure.
1638 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1640 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1644 * Determine if we should warn on defining a single-line macro of
1645 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1646 * return true if _any_ single-line macro of that name is defined.
1647 * Otherwise, will return true if a single-line macro with either
1648 * `nparam' or no parameters is defined.
1650 * If a macro with precisely the right number of parameters is
1651 * defined, or nparam is -1, the address of the definition structure
1652 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1653 * is NULL, no action will be taken regarding its contents, and no
1654 * error will occur.
1656 * Note that this is also called with nparam zero to resolve
1657 * `ifdef'.
1659 * If you already know which context macro belongs to, you can pass
1660 * the context pointer as first parameter; if you won't but name begins
1661 * with %$ the context will be automatically computed. If all_contexts
1662 * is true, macro will be searched in outer contexts as well.
1664 static bool
1665 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1666 bool nocase)
1668 struct hash_table *smtbl;
1669 SMacro *m;
1671 if (ctx) {
1672 smtbl = &ctx->localmac;
1673 } else if (name[0] == '%' && name[1] == '$') {
1674 if (cstk)
1675 ctx = get_ctx(name, &name);
1676 if (!ctx)
1677 return false; /* got to return _something_ */
1678 smtbl = &ctx->localmac;
1679 } else {
1680 smtbl = &smacros;
1682 m = (SMacro *) hash_findix(smtbl, name);
1684 while (m) {
1685 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1686 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1687 if (defn) {
1688 if (nparam == (int) m->nparam || nparam == -1)
1689 *defn = m;
1690 else
1691 *defn = NULL;
1693 return true;
1695 m = m->next;
1698 return false;
1702 * Count and mark off the parameters in a multi-line macro call.
1703 * This is called both from within the multi-line macro expansion
1704 * code, and also to mark off the default parameters when provided
1705 * in a %macro definition line.
1707 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1709 int paramsize, brace;
1711 *nparam = paramsize = 0;
1712 *params = NULL;
1713 while (t) {
1714 /* +1: we need space for the final NULL */
1715 if (*nparam+1 >= paramsize) {
1716 paramsize += PARAM_DELTA;
1717 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1719 skip_white_(t);
1720 brace = 0;
1721 if (tok_is_(t, "{"))
1722 brace++;
1723 (*params)[(*nparam)++] = t;
1724 if (brace) {
1725 while (brace && (t = t->next) != NULL) {
1726 if (tok_is_(t, "{"))
1727 brace++;
1728 else if (tok_is_(t, "}"))
1729 brace--;
1732 if (t) {
1734 * Now we've found the closing brace, look further
1735 * for the comma.
1737 t = t->next;
1738 skip_white_(t);
1739 if (tok_isnt_(t, ",")) {
1740 nasm_error(ERR_NONFATAL,
1741 "braces do not enclose all of macro parameter");
1742 while (tok_isnt_(t, ","))
1743 t = t->next;
1746 } else {
1747 while (tok_isnt_(t, ","))
1748 t = t->next;
1750 if (t) { /* got a comma/brace */
1751 t = t->next; /* eat the comma */
1757 * Determine whether one of the various `if' conditions is true or
1758 * not.
1760 * We must free the tline we get passed.
1762 static bool if_condition(Token * tline, enum preproc_token ct)
1764 enum pp_conditional i = PP_COND(ct);
1765 bool j;
1766 Token *t, *tt, **tptr, *origline;
1767 struct tokenval tokval;
1768 expr *evalresult;
1769 enum pp_token_type needtype;
1770 char *p;
1772 origline = tline;
1774 switch (i) {
1775 case PPC_IFCTX:
1776 j = false; /* have we matched yet? */
1777 while (true) {
1778 skip_white_(tline);
1779 if (!tline)
1780 break;
1781 if (tline->type != TOK_ID) {
1782 nasm_error(ERR_NONFATAL,
1783 "`%s' expects context identifiers", pp_directives[ct]);
1784 free_tlist(origline);
1785 return -1;
1787 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1788 j = true;
1789 tline = tline->next;
1791 break;
1793 case PPC_IFDEF:
1794 j = false; /* have we matched yet? */
1795 while (tline) {
1796 skip_white_(tline);
1797 if (!tline || (tline->type != TOK_ID &&
1798 (tline->type != TOK_PREPROC_ID ||
1799 tline->text[1] != '$'))) {
1800 nasm_error(ERR_NONFATAL,
1801 "`%s' expects macro identifiers", pp_directives[ct]);
1802 goto fail;
1804 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1805 j = true;
1806 tline = tline->next;
1808 break;
1810 case PPC_IFENV:
1811 tline = expand_smacro(tline);
1812 j = false; /* have we matched yet? */
1813 while (tline) {
1814 skip_white_(tline);
1815 if (!tline || (tline->type != TOK_ID &&
1816 tline->type != TOK_STRING &&
1817 (tline->type != TOK_PREPROC_ID ||
1818 tline->text[1] != '!'))) {
1819 nasm_error(ERR_NONFATAL,
1820 "`%s' expects environment variable names",
1821 pp_directives[ct]);
1822 goto fail;
1824 p = tline->text;
1825 if (tline->type == TOK_PREPROC_ID)
1826 p += 2; /* Skip leading %! */
1827 if (*p == '\'' || *p == '\"' || *p == '`')
1828 nasm_unquote_cstr(p, ct);
1829 if (getenv(p))
1830 j = true;
1831 tline = tline->next;
1833 break;
1835 case PPC_IFIDN:
1836 case PPC_IFIDNI:
1837 tline = expand_smacro(tline);
1838 t = tt = tline;
1839 while (tok_isnt_(tt, ","))
1840 tt = tt->next;
1841 if (!tt) {
1842 nasm_error(ERR_NONFATAL,
1843 "`%s' expects two comma-separated arguments",
1844 pp_directives[ct]);
1845 goto fail;
1847 tt = tt->next;
1848 j = true; /* assume equality unless proved not */
1849 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1850 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1851 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1852 pp_directives[ct]);
1853 goto fail;
1855 if (t->type == TOK_WHITESPACE) {
1856 t = t->next;
1857 continue;
1859 if (tt->type == TOK_WHITESPACE) {
1860 tt = tt->next;
1861 continue;
1863 if (tt->type != t->type) {
1864 j = false; /* found mismatching tokens */
1865 break;
1867 /* When comparing strings, need to unquote them first */
1868 if (t->type == TOK_STRING) {
1869 size_t l1 = nasm_unquote(t->text, NULL);
1870 size_t l2 = nasm_unquote(tt->text, NULL);
1872 if (l1 != l2) {
1873 j = false;
1874 break;
1876 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1877 j = false;
1878 break;
1880 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1881 j = false; /* found mismatching tokens */
1882 break;
1885 t = t->next;
1886 tt = tt->next;
1888 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1889 j = false; /* trailing gunk on one end or other */
1890 break;
1892 case PPC_IFMACRO:
1894 bool found = false;
1895 MMacro searching, *mmac;
1897 skip_white_(tline);
1898 tline = expand_id(tline);
1899 if (!tok_type_(tline, TOK_ID)) {
1900 nasm_error(ERR_NONFATAL,
1901 "`%s' expects a macro name", pp_directives[ct]);
1902 goto fail;
1904 searching.name = nasm_strdup(tline->text);
1905 searching.casesense = true;
1906 searching.plus = false;
1907 searching.nolist = false;
1908 searching.in_progress = 0;
1909 searching.max_depth = 0;
1910 searching.rep_nest = NULL;
1911 searching.nparam_min = 0;
1912 searching.nparam_max = INT_MAX;
1913 tline = expand_smacro(tline->next);
1914 skip_white_(tline);
1915 if (!tline) {
1916 } else if (!tok_type_(tline, TOK_NUMBER)) {
1917 nasm_error(ERR_NONFATAL,
1918 "`%s' expects a parameter count or nothing",
1919 pp_directives[ct]);
1920 } else {
1921 searching.nparam_min = searching.nparam_max =
1922 readnum(tline->text, &j);
1923 if (j)
1924 nasm_error(ERR_NONFATAL,
1925 "unable to parse parameter count `%s'",
1926 tline->text);
1928 if (tline && tok_is_(tline->next, "-")) {
1929 tline = tline->next->next;
1930 if (tok_is_(tline, "*"))
1931 searching.nparam_max = INT_MAX;
1932 else if (!tok_type_(tline, TOK_NUMBER))
1933 nasm_error(ERR_NONFATAL,
1934 "`%s' expects a parameter count after `-'",
1935 pp_directives[ct]);
1936 else {
1937 searching.nparam_max = readnum(tline->text, &j);
1938 if (j)
1939 nasm_error(ERR_NONFATAL,
1940 "unable to parse parameter count `%s'",
1941 tline->text);
1942 if (searching.nparam_min > searching.nparam_max) {
1943 nasm_error(ERR_NONFATAL,
1944 "minimum parameter count exceeds maximum");
1945 searching.nparam_max = searching.nparam_min;
1949 if (tline && tok_is_(tline->next, "+")) {
1950 tline = tline->next;
1951 searching.plus = true;
1953 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1954 while (mmac) {
1955 if (!strcmp(mmac->name, searching.name) &&
1956 (mmac->nparam_min <= searching.nparam_max
1957 || searching.plus)
1958 && (searching.nparam_min <= mmac->nparam_max
1959 || mmac->plus)) {
1960 found = true;
1961 break;
1963 mmac = mmac->next;
1965 if (tline && tline->next)
1966 nasm_error(ERR_WARNING|ERR_PASS1,
1967 "trailing garbage after %%ifmacro ignored");
1968 nasm_free(searching.name);
1969 j = found;
1970 break;
1973 case PPC_IFID:
1974 needtype = TOK_ID;
1975 goto iftype;
1976 case PPC_IFNUM:
1977 needtype = TOK_NUMBER;
1978 goto iftype;
1979 case PPC_IFSTR:
1980 needtype = TOK_STRING;
1981 goto iftype;
1983 iftype:
1984 t = tline = expand_smacro(tline);
1986 while (tok_type_(t, TOK_WHITESPACE) ||
1987 (needtype == TOK_NUMBER &&
1988 tok_type_(t, TOK_OTHER) &&
1989 (t->text[0] == '-' || t->text[0] == '+') &&
1990 !t->text[1]))
1991 t = t->next;
1993 j = tok_type_(t, needtype);
1994 break;
1996 case PPC_IFTOKEN:
1997 t = tline = expand_smacro(tline);
1998 while (tok_type_(t, TOK_WHITESPACE))
1999 t = t->next;
2001 j = false;
2002 if (t) {
2003 t = t->next; /* Skip the actual token */
2004 while (tok_type_(t, TOK_WHITESPACE))
2005 t = t->next;
2006 j = !t; /* Should be nothing left */
2008 break;
2010 case PPC_IFEMPTY:
2011 t = tline = expand_smacro(tline);
2012 while (tok_type_(t, TOK_WHITESPACE))
2013 t = t->next;
2015 j = !t; /* Should be empty */
2016 break;
2018 case PPC_IF:
2019 t = tline = expand_smacro(tline);
2020 tptr = &t;
2021 tokval.t_type = TOKEN_INVALID;
2022 evalresult = evaluate(ppscan, tptr, &tokval,
2023 NULL, pass | CRITICAL, NULL);
2024 if (!evalresult)
2025 return -1;
2026 if (tokval.t_type)
2027 nasm_error(ERR_WARNING|ERR_PASS1,
2028 "trailing garbage after expression ignored");
2029 if (!is_simple(evalresult)) {
2030 nasm_error(ERR_NONFATAL,
2031 "non-constant value given to `%s'", pp_directives[ct]);
2032 goto fail;
2034 j = reloc_value(evalresult) != 0;
2035 break;
2037 default:
2038 nasm_error(ERR_FATAL,
2039 "preprocessor directive `%s' not yet implemented",
2040 pp_directives[ct]);
2041 goto fail;
2044 free_tlist(origline);
2045 return j ^ PP_NEGATIVE(ct);
2047 fail:
2048 free_tlist(origline);
2049 return -1;
2053 * Common code for defining an smacro
2055 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2056 int nparam, Token *expansion)
2058 SMacro *smac, **smhead;
2059 struct hash_table *smtbl;
2061 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2062 if (!smac) {
2063 nasm_error(ERR_WARNING|ERR_PASS1,
2064 "single-line macro `%s' defined both with and"
2065 " without parameters", mname);
2067 * Some instances of the old code considered this a failure,
2068 * some others didn't. What is the right thing to do here?
2070 free_tlist(expansion);
2071 return false; /* Failure */
2072 } else {
2074 * We're redefining, so we have to take over an
2075 * existing SMacro structure. This means freeing
2076 * what was already in it.
2078 nasm_free(smac->name);
2079 free_tlist(smac->expansion);
2081 } else {
2082 smtbl = ctx ? &ctx->localmac : &smacros;
2083 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2084 smac = nasm_malloc(sizeof(SMacro));
2085 smac->next = *smhead;
2086 *smhead = smac;
2088 smac->name = nasm_strdup(mname);
2089 smac->casesense = casesense;
2090 smac->nparam = nparam;
2091 smac->expansion = expansion;
2092 smac->in_progress = false;
2093 return true; /* Success */
2097 * Undefine an smacro
2099 static void undef_smacro(Context *ctx, const char *mname)
2101 SMacro **smhead, *s, **sp;
2102 struct hash_table *smtbl;
2104 smtbl = ctx ? &ctx->localmac : &smacros;
2105 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2107 if (smhead) {
2109 * We now have a macro name... go hunt for it.
2111 sp = smhead;
2112 while ((s = *sp) != NULL) {
2113 if (!mstrcmp(s->name, mname, s->casesense)) {
2114 *sp = s->next;
2115 nasm_free(s->name);
2116 free_tlist(s->expansion);
2117 nasm_free(s);
2118 } else {
2119 sp = &s->next;
2126 * Parse a mmacro specification.
2128 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2130 bool err;
2132 tline = tline->next;
2133 skip_white_(tline);
2134 tline = expand_id(tline);
2135 if (!tok_type_(tline, TOK_ID)) {
2136 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2137 return false;
2140 def->prev = NULL;
2141 def->name = nasm_strdup(tline->text);
2142 def->plus = false;
2143 def->nolist = false;
2144 def->in_progress = 0;
2145 def->rep_nest = NULL;
2146 def->nparam_min = 0;
2147 def->nparam_max = 0;
2149 tline = expand_smacro(tline->next);
2150 skip_white_(tline);
2151 if (!tok_type_(tline, TOK_NUMBER)) {
2152 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2153 } else {
2154 def->nparam_min = def->nparam_max =
2155 readnum(tline->text, &err);
2156 if (err)
2157 nasm_error(ERR_NONFATAL,
2158 "unable to parse parameter count `%s'", tline->text);
2160 if (tline && tok_is_(tline->next, "-")) {
2161 tline = tline->next->next;
2162 if (tok_is_(tline, "*")) {
2163 def->nparam_max = INT_MAX;
2164 } else if (!tok_type_(tline, TOK_NUMBER)) {
2165 nasm_error(ERR_NONFATAL,
2166 "`%s' expects a parameter count after `-'", directive);
2167 } else {
2168 def->nparam_max = readnum(tline->text, &err);
2169 if (err) {
2170 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2171 tline->text);
2173 if (def->nparam_min > def->nparam_max) {
2174 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2175 def->nparam_max = def->nparam_min;
2179 if (tline && tok_is_(tline->next, "+")) {
2180 tline = tline->next;
2181 def->plus = true;
2183 if (tline && tok_type_(tline->next, TOK_ID) &&
2184 !nasm_stricmp(tline->next->text, ".nolist")) {
2185 tline = tline->next;
2186 def->nolist = true;
2190 * Handle default parameters.
2192 if (tline && tline->next) {
2193 def->dlist = tline->next;
2194 tline->next = NULL;
2195 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2196 } else {
2197 def->dlist = NULL;
2198 def->defaults = NULL;
2200 def->expansion = NULL;
2202 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2203 !def->plus)
2204 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2205 "too many default macro parameters");
2207 return true;
2212 * Decode a size directive
2214 static int parse_size(const char *str) {
2215 static const char *size_names[] =
2216 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2217 static const int sizes[] =
2218 { 0, 1, 4, 16, 8, 10, 2, 32 };
2220 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2224 * Process a preprocessor %pragma directive. Currently there are none.
2225 * Gets passed the token list starting with the "preproc" token from
2226 * "%pragma preproc".
2228 static void do_pragma_preproc(Token *tline)
2230 /* Skip to the real stuff */
2231 tline = tline->next;
2232 skip_white_(tline);
2233 if (!tline)
2234 return;
2236 (void)tline; /* Nothing else to do at present */
2240 * find and process preprocessor directive in passed line
2241 * Find out if a line contains a preprocessor directive, and deal
2242 * with it if so.
2244 * If a directive _is_ found, it is the responsibility of this routine
2245 * (and not the caller) to free_tlist() the line.
2247 * @param tline a pointer to the current tokeninzed line linked list
2248 * @param output if this directive generated output
2249 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2252 static int do_directive(Token *tline, char **output)
2254 enum preproc_token i;
2255 int j;
2256 bool err;
2257 int nparam;
2258 bool nolist;
2259 bool casesense;
2260 int k, m;
2261 int offset;
2262 char *p, *pp;
2263 const char *found_path;
2264 const char *mname;
2265 Include *inc;
2266 Context *ctx;
2267 Cond *cond;
2268 MMacro *mmac, **mmhead;
2269 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2270 Line *l;
2271 struct tokenval tokval;
2272 expr *evalresult;
2273 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2274 int64_t count;
2275 size_t len;
2276 int severity;
2278 *output = NULL; /* No output generated */
2279 origline = tline;
2281 skip_white_(tline);
2282 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2283 (tline->text[1] == '%' || tline->text[1] == '$'
2284 || tline->text[1] == '!'))
2285 return NO_DIRECTIVE_FOUND;
2287 i = pp_token_hash(tline->text);
2290 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2291 * since they are known to be buggy at moment, we need to fix them
2292 * in future release (2.09-2.10)
2294 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2295 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2296 tline->text);
2297 return NO_DIRECTIVE_FOUND;
2301 * If we're in a non-emitting branch of a condition construct,
2302 * or walking to the end of an already terminated %rep block,
2303 * we should ignore all directives except for condition
2304 * directives.
2306 if (((istk->conds && !emitting(istk->conds->state)) ||
2307 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2308 return NO_DIRECTIVE_FOUND;
2312 * If we're defining a macro or reading a %rep block, we should
2313 * ignore all directives except for %macro/%imacro (which nest),
2314 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2315 * If we're in a %rep block, another %rep nests, so should be let through.
2317 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2318 i != PP_RMACRO && i != PP_IRMACRO &&
2319 i != PP_ENDMACRO && i != PP_ENDM &&
2320 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2321 return NO_DIRECTIVE_FOUND;
2324 if (defining) {
2325 if (i == PP_MACRO || i == PP_IMACRO ||
2326 i == PP_RMACRO || i == PP_IRMACRO) {
2327 nested_mac_count++;
2328 return NO_DIRECTIVE_FOUND;
2329 } else if (nested_mac_count > 0) {
2330 if (i == PP_ENDMACRO) {
2331 nested_mac_count--;
2332 return NO_DIRECTIVE_FOUND;
2335 if (!defining->name) {
2336 if (i == PP_REP) {
2337 nested_rep_count++;
2338 return NO_DIRECTIVE_FOUND;
2339 } else if (nested_rep_count > 0) {
2340 if (i == PP_ENDREP) {
2341 nested_rep_count--;
2342 return NO_DIRECTIVE_FOUND;
2348 switch (i) {
2349 case PP_INVALID:
2350 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2351 tline->text);
2352 return NO_DIRECTIVE_FOUND; /* didn't get it */
2354 case PP_PRAGMA:
2356 * %pragma namespace options...
2358 * The namespace "preproc" is reserved for the preprocessor;
2359 * all other namespaces generate a [pragma] assembly directive.
2361 * Invalid %pragmas are ignored and may have different
2362 * meaning in future versions of NASM.
2364 tline = tline->next;
2365 skip_white_(tline);
2366 tline = expand_smacro(tline);
2367 if (tok_type_(tline, TOK_ID)) {
2368 if (!nasm_stricmp(tline->text, "preproc")) {
2369 /* Preprocessor pragma */
2370 do_pragma_preproc(tline);
2371 } else {
2372 /* Build the assembler directive */
2373 t = new_Token(NULL, TOK_OTHER, "[", 1);
2374 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2375 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2376 tline = t;
2377 for (t = tline; t->next; t = t->next)
2379 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2380 /* true here can be revisited in the future */
2381 *output = detoken(tline, true);
2384 free_tlist(origline);
2385 return DIRECTIVE_FOUND;
2387 case PP_STACKSIZE:
2388 /* Directive to tell NASM what the default stack size is. The
2389 * default is for a 16-bit stack, and this can be overriden with
2390 * %stacksize large.
2392 tline = tline->next;
2393 if (tline && tline->type == TOK_WHITESPACE)
2394 tline = tline->next;
2395 if (!tline || tline->type != TOK_ID) {
2396 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2397 free_tlist(origline);
2398 return DIRECTIVE_FOUND;
2400 if (nasm_stricmp(tline->text, "flat") == 0) {
2401 /* All subsequent ARG directives are for a 32-bit stack */
2402 StackSize = 4;
2403 StackPointer = "ebp";
2404 ArgOffset = 8;
2405 LocalOffset = 0;
2406 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2407 /* All subsequent ARG directives are for a 64-bit stack */
2408 StackSize = 8;
2409 StackPointer = "rbp";
2410 ArgOffset = 16;
2411 LocalOffset = 0;
2412 } else if (nasm_stricmp(tline->text, "large") == 0) {
2413 /* All subsequent ARG directives are for a 16-bit stack,
2414 * far function call.
2416 StackSize = 2;
2417 StackPointer = "bp";
2418 ArgOffset = 4;
2419 LocalOffset = 0;
2420 } else if (nasm_stricmp(tline->text, "small") == 0) {
2421 /* All subsequent ARG directives are for a 16-bit stack,
2422 * far function call. We don't support near functions.
2424 StackSize = 2;
2425 StackPointer = "bp";
2426 ArgOffset = 6;
2427 LocalOffset = 0;
2428 } else {
2429 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2430 free_tlist(origline);
2431 return DIRECTIVE_FOUND;
2433 free_tlist(origline);
2434 return DIRECTIVE_FOUND;
2436 case PP_ARG:
2437 /* TASM like ARG directive to define arguments to functions, in
2438 * the following form:
2440 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2442 offset = ArgOffset;
2443 do {
2444 char *arg, directive[256];
2445 int size = StackSize;
2447 /* Find the argument name */
2448 tline = tline->next;
2449 if (tline && tline->type == TOK_WHITESPACE)
2450 tline = tline->next;
2451 if (!tline || tline->type != TOK_ID) {
2452 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2453 free_tlist(origline);
2454 return DIRECTIVE_FOUND;
2456 arg = tline->text;
2458 /* Find the argument size type */
2459 tline = tline->next;
2460 if (!tline || tline->type != TOK_OTHER
2461 || tline->text[0] != ':') {
2462 nasm_error(ERR_NONFATAL,
2463 "Syntax error processing `%%arg' directive");
2464 free_tlist(origline);
2465 return DIRECTIVE_FOUND;
2467 tline = tline->next;
2468 if (!tline || tline->type != TOK_ID) {
2469 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2470 free_tlist(origline);
2471 return DIRECTIVE_FOUND;
2474 /* Allow macro expansion of type parameter */
2475 tt = tokenize(tline->text);
2476 tt = expand_smacro(tt);
2477 size = parse_size(tt->text);
2478 if (!size) {
2479 nasm_error(ERR_NONFATAL,
2480 "Invalid size type for `%%arg' missing directive");
2481 free_tlist(tt);
2482 free_tlist(origline);
2483 return DIRECTIVE_FOUND;
2485 free_tlist(tt);
2487 /* Round up to even stack slots */
2488 size = ALIGN(size, StackSize);
2490 /* Now define the macro for the argument */
2491 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2492 arg, StackPointer, offset);
2493 do_directive(tokenize(directive), output);
2494 offset += size;
2496 /* Move to the next argument in the list */
2497 tline = tline->next;
2498 if (tline && tline->type == TOK_WHITESPACE)
2499 tline = tline->next;
2500 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2501 ArgOffset = offset;
2502 free_tlist(origline);
2503 return DIRECTIVE_FOUND;
2505 case PP_LOCAL:
2506 /* TASM like LOCAL directive to define local variables for a
2507 * function, in the following form:
2509 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2511 * The '= LocalSize' at the end is ignored by NASM, but is
2512 * required by TASM to define the local parameter size (and used
2513 * by the TASM macro package).
2515 offset = LocalOffset;
2516 do {
2517 char *local, directive[256];
2518 int size = StackSize;
2520 /* Find the argument name */
2521 tline = tline->next;
2522 if (tline && tline->type == TOK_WHITESPACE)
2523 tline = tline->next;
2524 if (!tline || tline->type != TOK_ID) {
2525 nasm_error(ERR_NONFATAL,
2526 "`%%local' missing argument parameter");
2527 free_tlist(origline);
2528 return DIRECTIVE_FOUND;
2530 local = tline->text;
2532 /* Find the argument size type */
2533 tline = tline->next;
2534 if (!tline || tline->type != TOK_OTHER
2535 || tline->text[0] != ':') {
2536 nasm_error(ERR_NONFATAL,
2537 "Syntax error processing `%%local' directive");
2538 free_tlist(origline);
2539 return DIRECTIVE_FOUND;
2541 tline = tline->next;
2542 if (!tline || tline->type != TOK_ID) {
2543 nasm_error(ERR_NONFATAL,
2544 "`%%local' missing size type parameter");
2545 free_tlist(origline);
2546 return DIRECTIVE_FOUND;
2549 /* Allow macro expansion of type parameter */
2550 tt = tokenize(tline->text);
2551 tt = expand_smacro(tt);
2552 size = parse_size(tt->text);
2553 if (!size) {
2554 nasm_error(ERR_NONFATAL,
2555 "Invalid size type for `%%local' missing directive");
2556 free_tlist(tt);
2557 free_tlist(origline);
2558 return DIRECTIVE_FOUND;
2560 free_tlist(tt);
2562 /* Round up to even stack slots */
2563 size = ALIGN(size, StackSize);
2565 offset += size; /* Negative offset, increment before */
2567 /* Now define the macro for the argument */
2568 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2569 local, StackPointer, offset);
2570 do_directive(tokenize(directive), output);
2572 /* Now define the assign to setup the enter_c macro correctly */
2573 snprintf(directive, sizeof(directive),
2574 "%%assign %%$localsize %%$localsize+%d", size);
2575 do_directive(tokenize(directive), output);
2577 /* Move to the next argument in the list */
2578 tline = tline->next;
2579 if (tline && tline->type == TOK_WHITESPACE)
2580 tline = tline->next;
2581 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2582 LocalOffset = offset;
2583 free_tlist(origline);
2584 return DIRECTIVE_FOUND;
2586 case PP_CLEAR:
2587 if (tline->next)
2588 nasm_error(ERR_WARNING|ERR_PASS1,
2589 "trailing garbage after `%%clear' ignored");
2590 free_macros();
2591 init_macros();
2592 free_tlist(origline);
2593 return DIRECTIVE_FOUND;
2595 case PP_DEPEND:
2596 t = tline->next = expand_smacro(tline->next);
2597 skip_white_(t);
2598 if (!t || (t->type != TOK_STRING &&
2599 t->type != TOK_INTERNAL_STRING)) {
2600 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2601 free_tlist(origline);
2602 return DIRECTIVE_FOUND; /* but we did _something_ */
2604 if (t->next)
2605 nasm_error(ERR_WARNING|ERR_PASS1,
2606 "trailing garbage after `%%depend' ignored");
2607 p = t->text;
2608 if (t->type != TOK_INTERNAL_STRING)
2609 nasm_unquote_cstr(p, i);
2610 nasm_add_string_to_strlist(dephead, p);
2611 free_tlist(origline);
2612 return DIRECTIVE_FOUND;
2614 case PP_INCLUDE:
2615 t = tline->next = expand_smacro(tline->next);
2616 skip_white_(t);
2618 if (!t || (t->type != TOK_STRING &&
2619 t->type != TOK_INTERNAL_STRING)) {
2620 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2621 free_tlist(origline);
2622 return DIRECTIVE_FOUND; /* but we did _something_ */
2624 if (t->next)
2625 nasm_error(ERR_WARNING|ERR_PASS1,
2626 "trailing garbage after `%%include' ignored");
2627 p = t->text;
2628 if (t->type != TOK_INTERNAL_STRING)
2629 nasm_unquote_cstr(p, i);
2630 inc = nasm_malloc(sizeof(Include));
2631 inc->next = istk;
2632 inc->conds = NULL;
2633 found_path = NULL;
2634 inc->fp = inc_fopen(p, dephead, &found_path,
2635 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2636 if (!inc->fp) {
2637 /* -MG given but file not found */
2638 nasm_free(inc);
2639 } else {
2640 inc->fname = src_set_fname(found_path ? found_path : p);
2641 inc->lineno = src_set_linnum(0);
2642 inc->lineinc = 1;
2643 inc->expansion = NULL;
2644 inc->mstk = NULL;
2645 istk = inc;
2646 lfmt->uplevel(LIST_INCLUDE);
2648 free_tlist(origline);
2649 return DIRECTIVE_FOUND;
2651 case PP_USE:
2653 static macros_t *use_pkg;
2654 const char *pkg_macro = NULL;
2656 tline = tline->next;
2657 skip_white_(tline);
2658 tline = expand_id(tline);
2660 if (!tline || (tline->type != TOK_STRING &&
2661 tline->type != TOK_INTERNAL_STRING &&
2662 tline->type != TOK_ID)) {
2663 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2664 free_tlist(origline);
2665 return DIRECTIVE_FOUND; /* but we did _something_ */
2667 if (tline->next)
2668 nasm_error(ERR_WARNING|ERR_PASS1,
2669 "trailing garbage after `%%use' ignored");
2670 if (tline->type == TOK_STRING)
2671 nasm_unquote_cstr(tline->text, i);
2672 use_pkg = nasm_stdmac_find_package(tline->text);
2673 if (!use_pkg)
2674 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2675 else
2676 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2677 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2678 /* Not already included, go ahead and include it */
2679 stdmacpos = use_pkg;
2681 free_tlist(origline);
2682 return DIRECTIVE_FOUND;
2684 case PP_PUSH:
2685 case PP_REPL:
2686 case PP_POP:
2687 tline = tline->next;
2688 skip_white_(tline);
2689 tline = expand_id(tline);
2690 if (tline) {
2691 if (!tok_type_(tline, TOK_ID)) {
2692 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2693 pp_directives[i]);
2694 free_tlist(origline);
2695 return DIRECTIVE_FOUND; /* but we did _something_ */
2697 if (tline->next)
2698 nasm_error(ERR_WARNING|ERR_PASS1,
2699 "trailing garbage after `%s' ignored",
2700 pp_directives[i]);
2701 p = nasm_strdup(tline->text);
2702 } else {
2703 p = NULL; /* Anonymous */
2706 if (i == PP_PUSH) {
2707 ctx = nasm_malloc(sizeof(Context));
2708 ctx->next = cstk;
2709 hash_init(&ctx->localmac, HASH_SMALL);
2710 ctx->name = p;
2711 ctx->number = unique++;
2712 cstk = ctx;
2713 } else {
2714 /* %pop or %repl */
2715 if (!cstk) {
2716 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2717 pp_directives[i]);
2718 } else if (i == PP_POP) {
2719 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2720 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2721 "expected %s",
2722 cstk->name ? cstk->name : "anonymous", p);
2723 else
2724 ctx_pop();
2725 } else {
2726 /* i == PP_REPL */
2727 nasm_free(cstk->name);
2728 cstk->name = p;
2729 p = NULL;
2731 nasm_free(p);
2733 free_tlist(origline);
2734 return DIRECTIVE_FOUND;
2735 case PP_FATAL:
2736 severity = ERR_FATAL;
2737 goto issue_error;
2738 case PP_ERROR:
2739 severity = ERR_NONFATAL;
2740 goto issue_error;
2741 case PP_WARNING:
2742 severity = ERR_WARNING|ERR_WARN_USER;
2743 goto issue_error;
2745 issue_error:
2747 /* Only error out if this is the final pass */
2748 if (pass != 2 && i != PP_FATAL)
2749 return DIRECTIVE_FOUND;
2751 tline->next = expand_smacro(tline->next);
2752 tline = tline->next;
2753 skip_white_(tline);
2754 t = tline ? tline->next : NULL;
2755 skip_white_(t);
2756 if (tok_type_(tline, TOK_STRING) && !t) {
2757 /* The line contains only a quoted string */
2758 p = tline->text;
2759 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2760 nasm_error(severity, "%s", p);
2761 } else {
2762 /* Not a quoted string, or more than a quoted string */
2763 p = detoken(tline, false);
2764 nasm_error(severity, "%s", p);
2765 nasm_free(p);
2767 free_tlist(origline);
2768 return DIRECTIVE_FOUND;
2771 CASE_PP_IF:
2772 if (istk->conds && !emitting(istk->conds->state))
2773 j = COND_NEVER;
2774 else {
2775 j = if_condition(tline->next, i);
2776 tline->next = NULL; /* it got freed */
2777 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2779 cond = nasm_malloc(sizeof(Cond));
2780 cond->next = istk->conds;
2781 cond->state = j;
2782 istk->conds = cond;
2783 if(istk->mstk)
2784 istk->mstk->condcnt ++;
2785 free_tlist(origline);
2786 return DIRECTIVE_FOUND;
2788 CASE_PP_ELIF:
2789 if (!istk->conds)
2790 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2791 switch(istk->conds->state) {
2792 case COND_IF_TRUE:
2793 istk->conds->state = COND_DONE;
2794 break;
2796 case COND_DONE:
2797 case COND_NEVER:
2798 break;
2800 case COND_ELSE_TRUE:
2801 case COND_ELSE_FALSE:
2802 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2803 "`%%elif' after `%%else' ignored");
2804 istk->conds->state = COND_NEVER;
2805 break;
2807 case COND_IF_FALSE:
2809 * IMPORTANT: In the case of %if, we will already have
2810 * called expand_mmac_params(); however, if we're
2811 * processing an %elif we must have been in a
2812 * non-emitting mode, which would have inhibited
2813 * the normal invocation of expand_mmac_params().
2814 * Therefore, we have to do it explicitly here.
2816 j = if_condition(expand_mmac_params(tline->next), i);
2817 tline->next = NULL; /* it got freed */
2818 istk->conds->state =
2819 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2820 break;
2822 free_tlist(origline);
2823 return DIRECTIVE_FOUND;
2825 case PP_ELSE:
2826 if (tline->next)
2827 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2828 "trailing garbage after `%%else' ignored");
2829 if (!istk->conds)
2830 nasm_fatal(0, "`%%else: no matching `%%if'");
2831 switch(istk->conds->state) {
2832 case COND_IF_TRUE:
2833 case COND_DONE:
2834 istk->conds->state = COND_ELSE_FALSE;
2835 break;
2837 case COND_NEVER:
2838 break;
2840 case COND_IF_FALSE:
2841 istk->conds->state = COND_ELSE_TRUE;
2842 break;
2844 case COND_ELSE_TRUE:
2845 case COND_ELSE_FALSE:
2846 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2847 "`%%else' after `%%else' ignored.");
2848 istk->conds->state = COND_NEVER;
2849 break;
2851 free_tlist(origline);
2852 return DIRECTIVE_FOUND;
2854 case PP_ENDIF:
2855 if (tline->next)
2856 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2857 "trailing garbage after `%%endif' ignored");
2858 if (!istk->conds)
2859 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2860 cond = istk->conds;
2861 istk->conds = cond->next;
2862 nasm_free(cond);
2863 if(istk->mstk)
2864 istk->mstk->condcnt --;
2865 free_tlist(origline);
2866 return DIRECTIVE_FOUND;
2868 case PP_RMACRO:
2869 case PP_IRMACRO:
2870 case PP_MACRO:
2871 case PP_IMACRO:
2872 if (defining) {
2873 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2874 pp_directives[i]);
2875 return DIRECTIVE_FOUND;
2877 defining = nasm_zalloc(sizeof(MMacro));
2878 defining->max_depth =
2879 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2880 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2881 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2882 nasm_free(defining);
2883 defining = NULL;
2884 return DIRECTIVE_FOUND;
2887 src_get(&defining->xline, &defining->fname);
2889 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2890 while (mmac) {
2891 if (!strcmp(mmac->name, defining->name) &&
2892 (mmac->nparam_min <= defining->nparam_max
2893 || defining->plus)
2894 && (defining->nparam_min <= mmac->nparam_max
2895 || mmac->plus)) {
2896 nasm_error(ERR_WARNING|ERR_PASS1,
2897 "redefining multi-line macro `%s'", defining->name);
2898 return DIRECTIVE_FOUND;
2900 mmac = mmac->next;
2902 free_tlist(origline);
2903 return DIRECTIVE_FOUND;
2905 case PP_ENDM:
2906 case PP_ENDMACRO:
2907 if (! (defining && defining->name)) {
2908 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2909 return DIRECTIVE_FOUND;
2911 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2912 defining->next = *mmhead;
2913 *mmhead = defining;
2914 defining = NULL;
2915 free_tlist(origline);
2916 return DIRECTIVE_FOUND;
2918 case PP_EXITMACRO:
2920 * We must search along istk->expansion until we hit a
2921 * macro-end marker for a macro with a name. Then we
2922 * bypass all lines between exitmacro and endmacro.
2924 list_for_each(l, istk->expansion)
2925 if (l->finishes && l->finishes->name)
2926 break;
2928 if (l) {
2930 * Remove all conditional entries relative to this
2931 * macro invocation. (safe to do in this context)
2933 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2934 cond = istk->conds;
2935 istk->conds = cond->next;
2936 nasm_free(cond);
2938 istk->expansion = l;
2939 } else {
2940 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2942 free_tlist(origline);
2943 return DIRECTIVE_FOUND;
2945 case PP_UNMACRO:
2946 case PP_UNIMACRO:
2948 MMacro **mmac_p;
2949 MMacro spec;
2951 spec.casesense = (i == PP_UNMACRO);
2952 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2953 return DIRECTIVE_FOUND;
2955 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2956 while (mmac_p && *mmac_p) {
2957 mmac = *mmac_p;
2958 if (mmac->casesense == spec.casesense &&
2959 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2960 mmac->nparam_min == spec.nparam_min &&
2961 mmac->nparam_max == spec.nparam_max &&
2962 mmac->plus == spec.plus) {
2963 *mmac_p = mmac->next;
2964 free_mmacro(mmac);
2965 } else {
2966 mmac_p = &mmac->next;
2969 free_tlist(origline);
2970 free_tlist(spec.dlist);
2971 return DIRECTIVE_FOUND;
2974 case PP_ROTATE:
2975 if (tline->next && tline->next->type == TOK_WHITESPACE)
2976 tline = tline->next;
2977 if (!tline->next) {
2978 free_tlist(origline);
2979 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2980 return DIRECTIVE_FOUND;
2982 t = expand_smacro(tline->next);
2983 tline->next = NULL;
2984 free_tlist(origline);
2985 tline = t;
2986 tptr = &t;
2987 tokval.t_type = TOKEN_INVALID;
2988 evalresult =
2989 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2990 free_tlist(tline);
2991 if (!evalresult)
2992 return DIRECTIVE_FOUND;
2993 if (tokval.t_type)
2994 nasm_error(ERR_WARNING|ERR_PASS1,
2995 "trailing garbage after expression ignored");
2996 if (!is_simple(evalresult)) {
2997 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2998 return DIRECTIVE_FOUND;
3000 mmac = istk->mstk;
3001 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
3002 mmac = mmac->next_active;
3003 if (!mmac) {
3004 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
3005 } else if (mmac->nparam == 0) {
3006 nasm_error(ERR_NONFATAL,
3007 "`%%rotate' invoked within macro without parameters");
3008 } else {
3009 int rotate = mmac->rotate + reloc_value(evalresult);
3011 rotate %= (int)mmac->nparam;
3012 if (rotate < 0)
3013 rotate += mmac->nparam;
3015 mmac->rotate = rotate;
3017 return DIRECTIVE_FOUND;
3019 case PP_REP:
3020 nolist = false;
3021 do {
3022 tline = tline->next;
3023 } while (tok_type_(tline, TOK_WHITESPACE));
3025 if (tok_type_(tline, TOK_ID) &&
3026 nasm_stricmp(tline->text, ".nolist") == 0) {
3027 nolist = true;
3028 do {
3029 tline = tline->next;
3030 } while (tok_type_(tline, TOK_WHITESPACE));
3033 if (tline) {
3034 t = expand_smacro(tline);
3035 tptr = &t;
3036 tokval.t_type = TOKEN_INVALID;
3037 evalresult =
3038 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3039 if (!evalresult) {
3040 free_tlist(origline);
3041 return DIRECTIVE_FOUND;
3043 if (tokval.t_type)
3044 nasm_error(ERR_WARNING|ERR_PASS1,
3045 "trailing garbage after expression ignored");
3046 if (!is_simple(evalresult)) {
3047 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3048 return DIRECTIVE_FOUND;
3050 count = reloc_value(evalresult);
3051 if (count >= REP_LIMIT) {
3052 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3053 count = 0;
3054 } else
3055 count++;
3056 } else {
3057 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3058 count = 0;
3060 free_tlist(origline);
3062 tmp_defining = defining;
3063 defining = nasm_malloc(sizeof(MMacro));
3064 defining->prev = NULL;
3065 defining->name = NULL; /* flags this macro as a %rep block */
3066 defining->casesense = false;
3067 defining->plus = false;
3068 defining->nolist = nolist;
3069 defining->in_progress = count;
3070 defining->max_depth = 0;
3071 defining->nparam_min = defining->nparam_max = 0;
3072 defining->defaults = NULL;
3073 defining->dlist = NULL;
3074 defining->expansion = NULL;
3075 defining->next_active = istk->mstk;
3076 defining->rep_nest = tmp_defining;
3077 return DIRECTIVE_FOUND;
3079 case PP_ENDREP:
3080 if (!defining || defining->name) {
3081 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3082 return DIRECTIVE_FOUND;
3086 * Now we have a "macro" defined - although it has no name
3087 * and we won't be entering it in the hash tables - we must
3088 * push a macro-end marker for it on to istk->expansion.
3089 * After that, it will take care of propagating itself (a
3090 * macro-end marker line for a macro which is really a %rep
3091 * block will cause the macro to be re-expanded, complete
3092 * with another macro-end marker to ensure the process
3093 * continues) until the whole expansion is forcibly removed
3094 * from istk->expansion by a %exitrep.
3096 l = nasm_malloc(sizeof(Line));
3097 l->next = istk->expansion;
3098 l->finishes = defining;
3099 l->first = NULL;
3100 istk->expansion = l;
3102 istk->mstk = defining;
3104 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3105 tmp_defining = defining;
3106 defining = defining->rep_nest;
3107 free_tlist(origline);
3108 return DIRECTIVE_FOUND;
3110 case PP_EXITREP:
3112 * We must search along istk->expansion until we hit a
3113 * macro-end marker for a macro with no name. Then we set
3114 * its `in_progress' flag to 0.
3116 list_for_each(l, istk->expansion)
3117 if (l->finishes && !l->finishes->name)
3118 break;
3120 if (l)
3121 l->finishes->in_progress = 1;
3122 else
3123 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3124 free_tlist(origline);
3125 return DIRECTIVE_FOUND;
3127 case PP_XDEFINE:
3128 case PP_IXDEFINE:
3129 case PP_DEFINE:
3130 case PP_IDEFINE:
3131 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3133 tline = tline->next;
3134 skip_white_(tline);
3135 tline = expand_id(tline);
3136 if (!tline || (tline->type != TOK_ID &&
3137 (tline->type != TOK_PREPROC_ID ||
3138 tline->text[1] != '$'))) {
3139 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3140 pp_directives[i]);
3141 free_tlist(origline);
3142 return DIRECTIVE_FOUND;
3145 ctx = get_ctx(tline->text, &mname);
3146 last = tline;
3147 param_start = tline = tline->next;
3148 nparam = 0;
3150 /* Expand the macro definition now for %xdefine and %ixdefine */
3151 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3152 tline = expand_smacro(tline);
3154 if (tok_is_(tline, "(")) {
3156 * This macro has parameters.
3159 tline = tline->next;
3160 while (1) {
3161 skip_white_(tline);
3162 if (!tline) {
3163 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3164 free_tlist(origline);
3165 return DIRECTIVE_FOUND;
3167 if (tline->type != TOK_ID) {
3168 nasm_error(ERR_NONFATAL,
3169 "`%s': parameter identifier expected",
3170 tline->text);
3171 free_tlist(origline);
3172 return DIRECTIVE_FOUND;
3174 tline->type = TOK_SMAC_PARAM + nparam++;
3175 tline = tline->next;
3176 skip_white_(tline);
3177 if (tok_is_(tline, ",")) {
3178 tline = tline->next;
3179 } else {
3180 if (!tok_is_(tline, ")")) {
3181 nasm_error(ERR_NONFATAL,
3182 "`)' expected to terminate macro template");
3183 free_tlist(origline);
3184 return DIRECTIVE_FOUND;
3186 break;
3189 last = tline;
3190 tline = tline->next;
3192 if (tok_type_(tline, TOK_WHITESPACE))
3193 last = tline, tline = tline->next;
3194 macro_start = NULL;
3195 last->next = NULL;
3196 t = tline;
3197 while (t) {
3198 if (t->type == TOK_ID) {
3199 list_for_each(tt, param_start)
3200 if (tt->type >= TOK_SMAC_PARAM &&
3201 !strcmp(tt->text, t->text))
3202 t->type = tt->type;
3204 tt = t->next;
3205 t->next = macro_start;
3206 macro_start = t;
3207 t = tt;
3210 * Good. We now have a macro name, a parameter count, and a
3211 * token list (in reverse order) for an expansion. We ought
3212 * to be OK just to create an SMacro, store it, and let
3213 * free_tlist have the rest of the line (which we have
3214 * carefully re-terminated after chopping off the expansion
3215 * from the end).
3217 define_smacro(ctx, mname, casesense, nparam, macro_start);
3218 free_tlist(origline);
3219 return DIRECTIVE_FOUND;
3221 case PP_UNDEF:
3222 tline = tline->next;
3223 skip_white_(tline);
3224 tline = expand_id(tline);
3225 if (!tline || (tline->type != TOK_ID &&
3226 (tline->type != TOK_PREPROC_ID ||
3227 tline->text[1] != '$'))) {
3228 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3229 free_tlist(origline);
3230 return DIRECTIVE_FOUND;
3232 if (tline->next) {
3233 nasm_error(ERR_WARNING|ERR_PASS1,
3234 "trailing garbage after macro name ignored");
3237 /* Find the context that symbol belongs to */
3238 ctx = get_ctx(tline->text, &mname);
3239 undef_smacro(ctx, mname);
3240 free_tlist(origline);
3241 return DIRECTIVE_FOUND;
3243 case PP_DEFSTR:
3244 case PP_IDEFSTR:
3245 casesense = (i == PP_DEFSTR);
3247 tline = tline->next;
3248 skip_white_(tline);
3249 tline = expand_id(tline);
3250 if (!tline || (tline->type != TOK_ID &&
3251 (tline->type != TOK_PREPROC_ID ||
3252 tline->text[1] != '$'))) {
3253 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3254 pp_directives[i]);
3255 free_tlist(origline);
3256 return DIRECTIVE_FOUND;
3259 ctx = get_ctx(tline->text, &mname);
3260 last = tline;
3261 tline = expand_smacro(tline->next);
3262 last->next = NULL;
3264 while (tok_type_(tline, TOK_WHITESPACE))
3265 tline = delete_Token(tline);
3267 p = detoken(tline, false);
3268 macro_start = nasm_malloc(sizeof(*macro_start));
3269 macro_start->next = NULL;
3270 macro_start->text = nasm_quote(p, strlen(p));
3271 macro_start->type = TOK_STRING;
3272 macro_start->a.mac = NULL;
3273 nasm_free(p);
3276 * We now have a macro name, an implicit parameter count of
3277 * zero, and a string token to use as an expansion. Create
3278 * and store an SMacro.
3280 define_smacro(ctx, mname, casesense, 0, macro_start);
3281 free_tlist(origline);
3282 return DIRECTIVE_FOUND;
3284 case PP_DEFTOK:
3285 case PP_IDEFTOK:
3286 casesense = (i == PP_DEFTOK);
3288 tline = tline->next;
3289 skip_white_(tline);
3290 tline = expand_id(tline);
3291 if (!tline || (tline->type != TOK_ID &&
3292 (tline->type != TOK_PREPROC_ID ||
3293 tline->text[1] != '$'))) {
3294 nasm_error(ERR_NONFATAL,
3295 "`%s' expects a macro identifier as first parameter",
3296 pp_directives[i]);
3297 free_tlist(origline);
3298 return DIRECTIVE_FOUND;
3300 ctx = get_ctx(tline->text, &mname);
3301 last = tline;
3302 tline = expand_smacro(tline->next);
3303 last->next = NULL;
3305 t = tline;
3306 while (tok_type_(t, TOK_WHITESPACE))
3307 t = t->next;
3308 /* t should now point to the string */
3309 if (!tok_type_(t, TOK_STRING)) {
3310 nasm_error(ERR_NONFATAL,
3311 "`%s` requires string as second parameter",
3312 pp_directives[i]);
3313 free_tlist(tline);
3314 free_tlist(origline);
3315 return DIRECTIVE_FOUND;
3319 * Convert the string to a token stream. Note that smacros
3320 * are stored with the token stream reversed, so we have to
3321 * reverse the output of tokenize().
3323 nasm_unquote_cstr(t->text, i);
3324 macro_start = reverse_tokens(tokenize(t->text));
3327 * We now have a macro name, an implicit parameter count of
3328 * zero, and a numeric token to use as an expansion. Create
3329 * and store an SMacro.
3331 define_smacro(ctx, mname, casesense, 0, macro_start);
3332 free_tlist(tline);
3333 free_tlist(origline);
3334 return DIRECTIVE_FOUND;
3336 case PP_PATHSEARCH:
3338 const char *found_path;
3340 casesense = true;
3342 tline = tline->next;
3343 skip_white_(tline);
3344 tline = expand_id(tline);
3345 if (!tline || (tline->type != TOK_ID &&
3346 (tline->type != TOK_PREPROC_ID ||
3347 tline->text[1] != '$'))) {
3348 nasm_error(ERR_NONFATAL,
3349 "`%%pathsearch' expects a macro identifier as first parameter");
3350 free_tlist(origline);
3351 return DIRECTIVE_FOUND;
3353 ctx = get_ctx(tline->text, &mname);
3354 last = tline;
3355 tline = expand_smacro(tline->next);
3356 last->next = NULL;
3358 t = tline;
3359 while (tok_type_(t, TOK_WHITESPACE))
3360 t = t->next;
3362 if (!t || (t->type != TOK_STRING &&
3363 t->type != TOK_INTERNAL_STRING)) {
3364 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3365 free_tlist(tline);
3366 free_tlist(origline);
3367 return DIRECTIVE_FOUND; /* but we did _something_ */
3369 if (t->next)
3370 nasm_error(ERR_WARNING|ERR_PASS1,
3371 "trailing garbage after `%%pathsearch' ignored");
3372 p = t->text;
3373 if (t->type != TOK_INTERNAL_STRING)
3374 nasm_unquote(p, NULL);
3376 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3377 if (!found_path)
3378 found_path = p;
3379 macro_start = nasm_malloc(sizeof(*macro_start));
3380 macro_start->next = NULL;
3381 macro_start->text = nasm_quote(found_path, strlen(found_path));
3382 macro_start->type = TOK_STRING;
3383 macro_start->a.mac = NULL;
3386 * We now have a macro name, an implicit parameter count of
3387 * zero, and a string token to use as an expansion. Create
3388 * and store an SMacro.
3390 define_smacro(ctx, mname, casesense, 0, macro_start);
3391 free_tlist(tline);
3392 free_tlist(origline);
3393 return DIRECTIVE_FOUND;
3396 case PP_STRLEN:
3397 casesense = true;
3399 tline = tline->next;
3400 skip_white_(tline);
3401 tline = expand_id(tline);
3402 if (!tline || (tline->type != TOK_ID &&
3403 (tline->type != TOK_PREPROC_ID ||
3404 tline->text[1] != '$'))) {
3405 nasm_error(ERR_NONFATAL,
3406 "`%%strlen' expects a macro identifier as first parameter");
3407 free_tlist(origline);
3408 return DIRECTIVE_FOUND;
3410 ctx = get_ctx(tline->text, &mname);
3411 last = tline;
3412 tline = expand_smacro(tline->next);
3413 last->next = NULL;
3415 t = tline;
3416 while (tok_type_(t, TOK_WHITESPACE))
3417 t = t->next;
3418 /* t should now point to the string */
3419 if (!tok_type_(t, TOK_STRING)) {
3420 nasm_error(ERR_NONFATAL,
3421 "`%%strlen` requires string as second parameter");
3422 free_tlist(tline);
3423 free_tlist(origline);
3424 return DIRECTIVE_FOUND;
3427 macro_start = nasm_malloc(sizeof(*macro_start));
3428 macro_start->next = NULL;
3429 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3430 macro_start->a.mac = NULL;
3433 * We now have a macro name, an implicit parameter count of
3434 * zero, and a numeric token to use as an expansion. Create
3435 * and store an SMacro.
3437 define_smacro(ctx, mname, casesense, 0, macro_start);
3438 free_tlist(tline);
3439 free_tlist(origline);
3440 return DIRECTIVE_FOUND;
3442 case PP_STRCAT:
3443 casesense = true;
3445 tline = tline->next;
3446 skip_white_(tline);
3447 tline = expand_id(tline);
3448 if (!tline || (tline->type != TOK_ID &&
3449 (tline->type != TOK_PREPROC_ID ||
3450 tline->text[1] != '$'))) {
3451 nasm_error(ERR_NONFATAL,
3452 "`%%strcat' expects a macro identifier as first parameter");
3453 free_tlist(origline);
3454 return DIRECTIVE_FOUND;
3456 ctx = get_ctx(tline->text, &mname);
3457 last = tline;
3458 tline = expand_smacro(tline->next);
3459 last->next = NULL;
3461 len = 0;
3462 list_for_each(t, tline) {
3463 switch (t->type) {
3464 case TOK_WHITESPACE:
3465 break;
3466 case TOK_STRING:
3467 len += t->a.len = nasm_unquote(t->text, NULL);
3468 break;
3469 case TOK_OTHER:
3470 if (!strcmp(t->text, ",")) /* permit comma separators */
3471 break;
3472 /* else fall through */
3473 default:
3474 nasm_error(ERR_NONFATAL,
3475 "non-string passed to `%%strcat' (%d)", t->type);
3476 free_tlist(tline);
3477 free_tlist(origline);
3478 return DIRECTIVE_FOUND;
3482 p = pp = nasm_malloc(len);
3483 list_for_each(t, tline) {
3484 if (t->type == TOK_STRING) {
3485 memcpy(p, t->text, t->a.len);
3486 p += t->a.len;
3491 * We now have a macro name, an implicit parameter count of
3492 * zero, and a numeric token to use as an expansion. Create
3493 * and store an SMacro.
3495 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3496 macro_start->text = nasm_quote(pp, len);
3497 nasm_free(pp);
3498 define_smacro(ctx, mname, casesense, 0, macro_start);
3499 free_tlist(tline);
3500 free_tlist(origline);
3501 return DIRECTIVE_FOUND;
3503 case PP_SUBSTR:
3505 int64_t start, count;
3506 size_t len;
3508 casesense = true;
3510 tline = tline->next;
3511 skip_white_(tline);
3512 tline = expand_id(tline);
3513 if (!tline || (tline->type != TOK_ID &&
3514 (tline->type != TOK_PREPROC_ID ||
3515 tline->text[1] != '$'))) {
3516 nasm_error(ERR_NONFATAL,
3517 "`%%substr' expects a macro identifier as first parameter");
3518 free_tlist(origline);
3519 return DIRECTIVE_FOUND;
3521 ctx = get_ctx(tline->text, &mname);
3522 last = tline;
3523 tline = expand_smacro(tline->next);
3524 last->next = NULL;
3526 if (tline) /* skip expanded id */
3527 t = tline->next;
3528 while (tok_type_(t, TOK_WHITESPACE))
3529 t = t->next;
3531 /* t should now point to the string */
3532 if (!tok_type_(t, TOK_STRING)) {
3533 nasm_error(ERR_NONFATAL,
3534 "`%%substr` requires string as second parameter");
3535 free_tlist(tline);
3536 free_tlist(origline);
3537 return DIRECTIVE_FOUND;
3540 tt = t->next;
3541 tptr = &tt;
3542 tokval.t_type = TOKEN_INVALID;
3543 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3544 if (!evalresult) {
3545 free_tlist(tline);
3546 free_tlist(origline);
3547 return DIRECTIVE_FOUND;
3548 } else if (!is_simple(evalresult)) {
3549 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3550 free_tlist(tline);
3551 free_tlist(origline);
3552 return DIRECTIVE_FOUND;
3554 start = evalresult->value - 1;
3556 while (tok_type_(tt, TOK_WHITESPACE))
3557 tt = tt->next;
3558 if (!tt) {
3559 count = 1; /* Backwards compatibility: one character */
3560 } else {
3561 tokval.t_type = TOKEN_INVALID;
3562 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3563 if (!evalresult) {
3564 free_tlist(tline);
3565 free_tlist(origline);
3566 return DIRECTIVE_FOUND;
3567 } else if (!is_simple(evalresult)) {
3568 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3569 free_tlist(tline);
3570 free_tlist(origline);
3571 return DIRECTIVE_FOUND;
3573 count = evalresult->value;
3576 len = nasm_unquote(t->text, NULL);
3578 /* make start and count being in range */
3579 if (start < 0)
3580 start = 0;
3581 if (count < 0)
3582 count = len + count + 1 - start;
3583 if (start + count > (int64_t)len)
3584 count = len - start;
3585 if (!len || count < 0 || start >=(int64_t)len)
3586 start = -1, count = 0; /* empty string */
3588 macro_start = nasm_malloc(sizeof(*macro_start));
3589 macro_start->next = NULL;
3590 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3591 macro_start->type = TOK_STRING;
3592 macro_start->a.mac = NULL;
3595 * We now have a macro name, an implicit parameter count of
3596 * zero, and a numeric token to use as an expansion. Create
3597 * and store an SMacro.
3599 define_smacro(ctx, mname, casesense, 0, macro_start);
3600 free_tlist(tline);
3601 free_tlist(origline);
3602 return DIRECTIVE_FOUND;
3605 case PP_ASSIGN:
3606 case PP_IASSIGN:
3607 casesense = (i == PP_ASSIGN);
3609 tline = tline->next;
3610 skip_white_(tline);
3611 tline = expand_id(tline);
3612 if (!tline || (tline->type != TOK_ID &&
3613 (tline->type != TOK_PREPROC_ID ||
3614 tline->text[1] != '$'))) {
3615 nasm_error(ERR_NONFATAL,
3616 "`%%%sassign' expects a macro identifier",
3617 (i == PP_IASSIGN ? "i" : ""));
3618 free_tlist(origline);
3619 return DIRECTIVE_FOUND;
3621 ctx = get_ctx(tline->text, &mname);
3622 last = tline;
3623 tline = expand_smacro(tline->next);
3624 last->next = NULL;
3626 t = tline;
3627 tptr = &t;
3628 tokval.t_type = TOKEN_INVALID;
3629 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3630 free_tlist(tline);
3631 if (!evalresult) {
3632 free_tlist(origline);
3633 return DIRECTIVE_FOUND;
3636 if (tokval.t_type)
3637 nasm_error(ERR_WARNING|ERR_PASS1,
3638 "trailing garbage after expression ignored");
3640 if (!is_simple(evalresult)) {
3641 nasm_error(ERR_NONFATAL,
3642 "non-constant value given to `%%%sassign'",
3643 (i == PP_IASSIGN ? "i" : ""));
3644 free_tlist(origline);
3645 return DIRECTIVE_FOUND;
3648 macro_start = nasm_malloc(sizeof(*macro_start));
3649 macro_start->next = NULL;
3650 make_tok_num(macro_start, reloc_value(evalresult));
3651 macro_start->a.mac = NULL;
3654 * We now have a macro name, an implicit parameter count of
3655 * zero, and a numeric token to use as an expansion. Create
3656 * and store an SMacro.
3658 define_smacro(ctx, mname, casesense, 0, macro_start);
3659 free_tlist(origline);
3660 return DIRECTIVE_FOUND;
3662 case PP_LINE:
3664 * Syntax is `%line nnn[+mmm] [filename]'
3666 tline = tline->next;
3667 skip_white_(tline);
3668 if (!tok_type_(tline, TOK_NUMBER)) {
3669 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3670 free_tlist(origline);
3671 return DIRECTIVE_FOUND;
3673 k = readnum(tline->text, &err);
3674 m = 1;
3675 tline = tline->next;
3676 if (tok_is_(tline, "+")) {
3677 tline = tline->next;
3678 if (!tok_type_(tline, TOK_NUMBER)) {
3679 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3680 free_tlist(origline);
3681 return DIRECTIVE_FOUND;
3683 m = readnum(tline->text, &err);
3684 tline = tline->next;
3686 skip_white_(tline);
3687 src_set_linnum(k);
3688 istk->lineinc = m;
3689 if (tline) {
3690 char *fname = detoken(tline, false);
3691 src_set_fname(fname);
3692 nasm_free(fname);
3694 free_tlist(origline);
3695 return DIRECTIVE_FOUND;
3697 default:
3698 nasm_error(ERR_FATAL,
3699 "preprocessor directive `%s' not yet implemented",
3700 pp_directives[i]);
3701 return DIRECTIVE_FOUND;
3706 * Ensure that a macro parameter contains a condition code and
3707 * nothing else. Return the condition code index if so, or -1
3708 * otherwise.
3710 static int find_cc(Token * t)
3712 Token *tt;
3714 if (!t)
3715 return -1; /* Probably a %+ without a space */
3717 skip_white_(t);
3718 if (!t)
3719 return -1;
3720 if (t->type != TOK_ID)
3721 return -1;
3722 tt = t->next;
3723 skip_white_(tt);
3724 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3725 return -1;
3727 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3731 * This routines walks over tokens strem and hadnles tokens
3732 * pasting, if @handle_explicit passed then explicit pasting
3733 * term is handled, otherwise -- implicit pastings only.
3735 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3736 size_t mnum, bool handle_explicit)
3738 Token *tok, *next, **prev_next, **prev_nonspace;
3739 bool pasted = false;
3740 char *buf, *p;
3741 size_t len, i;
3744 * The last token before pasting. We need it
3745 * to be able to connect new handled tokens.
3746 * In other words if there were a tokens stream
3748 * A -> B -> C -> D
3750 * and we've joined tokens B and C, the resulting
3751 * stream should be
3753 * A -> BC -> D
3755 tok = *head;
3756 prev_next = NULL;
3758 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3759 prev_nonspace = head;
3760 else
3761 prev_nonspace = NULL;
3763 while (tok && (next = tok->next)) {
3765 switch (tok->type) {
3766 case TOK_WHITESPACE:
3767 /* Zap redundant whitespaces */
3768 while (tok_type_(next, TOK_WHITESPACE))
3769 next = delete_Token(next);
3770 tok->next = next;
3771 break;
3773 case TOK_PASTE:
3774 /* Explicit pasting */
3775 if (!handle_explicit)
3776 break;
3777 next = delete_Token(tok);
3779 while (tok_type_(next, TOK_WHITESPACE))
3780 next = delete_Token(next);
3782 if (!pasted)
3783 pasted = true;
3785 /* Left pasting token is start of line */
3786 if (!prev_nonspace)
3787 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3790 * No ending token, this might happen in two
3791 * cases
3793 * 1) There indeed no right token at all
3794 * 2) There is a bare "%define ID" statement,
3795 * and @ID does expand to whitespace.
3797 * So technically we need to do a grammar analysis
3798 * in another stage of parsing, but for now lets don't
3799 * change the behaviour people used to. Simply allow
3800 * whitespace after paste token.
3802 if (!next) {
3804 * Zap ending space tokens and that's all.
3806 tok = (*prev_nonspace)->next;
3807 while (tok_type_(tok, TOK_WHITESPACE))
3808 tok = delete_Token(tok);
3809 tok = *prev_nonspace;
3810 tok->next = NULL;
3811 break;
3814 tok = *prev_nonspace;
3815 while (tok_type_(tok, TOK_WHITESPACE))
3816 tok = delete_Token(tok);
3817 len = strlen(tok->text);
3818 len += strlen(next->text);
3820 p = buf = nasm_malloc(len + 1);
3821 strcpy(p, tok->text);
3822 p = strchr(p, '\0');
3823 strcpy(p, next->text);
3825 delete_Token(tok);
3827 tok = tokenize(buf);
3828 nasm_free(buf);
3830 *prev_nonspace = tok;
3831 while (tok && tok->next)
3832 tok = tok->next;
3834 tok->next = delete_Token(next);
3836 /* Restart from pasted tokens head */
3837 tok = *prev_nonspace;
3838 break;
3840 default:
3841 /* implicit pasting */
3842 for (i = 0; i < mnum; i++) {
3843 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3844 continue;
3846 len = 0;
3847 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3848 len += strlen(next->text);
3849 next = next->next;
3852 /* No match or no text to process */
3853 if (tok == next || len == 0)
3854 break;
3856 len += strlen(tok->text);
3857 p = buf = nasm_malloc(len + 1);
3859 strcpy(p, tok->text);
3860 p = strchr(p, '\0');
3861 tok = delete_Token(tok);
3863 while (tok != next) {
3864 if (PP_CONCAT_MATCH(tok, m[i].mask_tail)) {
3865 strcpy(p, tok->text);
3866 p = strchr(p, '\0');
3868 tok = delete_Token(tok);
3871 tok = tokenize(buf);
3872 nasm_free(buf);
3874 if (prev_next)
3875 *prev_next = tok;
3876 else
3877 *head = tok;
3880 * Connect pasted into original stream,
3881 * ie A -> new-tokens -> B
3883 while (tok && tok->next)
3884 tok = tok->next;
3885 tok->next = next;
3887 if (!pasted)
3888 pasted = true;
3890 /* Restart from pasted tokens head */
3891 tok = prev_next ? *prev_next : *head;
3894 break;
3897 prev_next = &tok->next;
3899 if (tok->next &&
3900 !tok_type_(tok->next, TOK_WHITESPACE) &&
3901 !tok_type_(tok->next, TOK_PASTE))
3902 prev_nonspace = prev_next;
3904 tok = tok->next;
3907 return pasted;
3911 * expands to a list of tokens from %{x:y}
3913 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3915 Token *t = tline, **tt, *tm, *head;
3916 char *pos;
3917 int fst, lst, j, i;
3919 pos = strchr(tline->text, ':');
3920 nasm_assert(pos);
3922 lst = atoi(pos + 1);
3923 fst = atoi(tline->text + 1);
3926 * only macros params are accounted so
3927 * if someone passes %0 -- we reject such
3928 * value(s)
3930 if (lst == 0 || fst == 0)
3931 goto err;
3933 /* the values should be sane */
3934 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3935 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3936 goto err;
3938 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3939 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3941 /* counted from zero */
3942 fst--, lst--;
3945 * It will be at least one token. Note we
3946 * need to scan params until separator, otherwise
3947 * only first token will be passed.
3949 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3950 head = new_Token(NULL, tm->type, tm->text, 0);
3951 tt = &head->next, tm = tm->next;
3952 while (tok_isnt_(tm, ",")) {
3953 t = new_Token(NULL, tm->type, tm->text, 0);
3954 *tt = t, tt = &t->next, tm = tm->next;
3957 if (fst < lst) {
3958 for (i = fst + 1; i <= lst; i++) {
3959 t = new_Token(NULL, TOK_OTHER, ",", 0);
3960 *tt = t, tt = &t->next;
3961 j = (i + mac->rotate) % mac->nparam;
3962 tm = mac->params[j];
3963 while (tok_isnt_(tm, ",")) {
3964 t = new_Token(NULL, tm->type, tm->text, 0);
3965 *tt = t, tt = &t->next, tm = tm->next;
3968 } else {
3969 for (i = fst - 1; i >= lst; i--) {
3970 t = new_Token(NULL, TOK_OTHER, ",", 0);
3971 *tt = t, tt = &t->next;
3972 j = (i + mac->rotate) % mac->nparam;
3973 tm = mac->params[j];
3974 while (tok_isnt_(tm, ",")) {
3975 t = new_Token(NULL, tm->type, tm->text, 0);
3976 *tt = t, tt = &t->next, tm = tm->next;
3981 *last = tt;
3982 return head;
3984 err:
3985 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3986 &tline->text[1]);
3987 return tline;
3991 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3992 * %-n) and MMacro-local identifiers (%%foo) as well as
3993 * macro indirection (%[...]) and range (%{..:..}).
3995 static Token *expand_mmac_params(Token * tline)
3997 Token *t, *tt, **tail, *thead;
3998 bool changed = false;
3999 char *pos;
4001 tail = &thead;
4002 thead = NULL;
4004 while (tline) {
4005 if (tline->type == TOK_PREPROC_ID &&
4006 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
4007 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
4008 tline->text[1] == '%')) {
4009 char *text = NULL;
4010 int type = 0, cc; /* type = 0 to placate optimisers */
4011 char tmpbuf[30];
4012 unsigned int n;
4013 int i;
4014 MMacro *mac;
4016 t = tline;
4017 tline = tline->next;
4019 mac = istk->mstk;
4020 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4021 mac = mac->next_active;
4022 if (!mac) {
4023 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4024 } else {
4025 pos = strchr(t->text, ':');
4026 if (!pos) {
4027 switch (t->text[1]) {
4029 * We have to make a substitution of one of the
4030 * forms %1, %-1, %+1, %%foo, %0.
4032 case '0':
4033 type = TOK_NUMBER;
4034 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4035 text = nasm_strdup(tmpbuf);
4036 break;
4037 case '%':
4038 type = TOK_ID;
4039 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4040 mac->unique);
4041 text = nasm_strcat(tmpbuf, t->text + 2);
4042 break;
4043 case '-':
4044 n = atoi(t->text + 2) - 1;
4045 if (n >= mac->nparam)
4046 tt = NULL;
4047 else {
4048 if (mac->nparam > 1)
4049 n = (n + mac->rotate) % mac->nparam;
4050 tt = mac->params[n];
4052 cc = find_cc(tt);
4053 if (cc == -1) {
4054 nasm_error(ERR_NONFATAL,
4055 "macro parameter %d is not a condition code",
4056 n + 1);
4057 text = NULL;
4058 } else {
4059 type = TOK_ID;
4060 if (inverse_ccs[cc] == -1) {
4061 nasm_error(ERR_NONFATAL,
4062 "condition code `%s' is not invertible",
4063 conditions[cc]);
4064 text = NULL;
4065 } else
4066 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4068 break;
4069 case '+':
4070 n = atoi(t->text + 2) - 1;
4071 if (n >= mac->nparam)
4072 tt = NULL;
4073 else {
4074 if (mac->nparam > 1)
4075 n = (n + mac->rotate) % mac->nparam;
4076 tt = mac->params[n];
4078 cc = find_cc(tt);
4079 if (cc == -1) {
4080 nasm_error(ERR_NONFATAL,
4081 "macro parameter %d is not a condition code",
4082 n + 1);
4083 text = NULL;
4084 } else {
4085 type = TOK_ID;
4086 text = nasm_strdup(conditions[cc]);
4088 break;
4089 default:
4090 n = atoi(t->text + 1) - 1;
4091 if (n >= mac->nparam)
4092 tt = NULL;
4093 else {
4094 if (mac->nparam > 1)
4095 n = (n + mac->rotate) % mac->nparam;
4096 tt = mac->params[n];
4098 if (tt) {
4099 for (i = 0; i < mac->paramlen[n]; i++) {
4100 *tail = new_Token(NULL, tt->type, tt->text, 0);
4101 tail = &(*tail)->next;
4102 tt = tt->next;
4105 text = NULL; /* we've done it here */
4106 break;
4108 } else {
4110 * seems we have a parameters range here
4112 Token *head, **last;
4113 head = expand_mmac_params_range(mac, t, &last);
4114 if (head != t) {
4115 *tail = head;
4116 *last = tline;
4117 tline = head;
4118 text = NULL;
4122 if (!text) {
4123 delete_Token(t);
4124 } else {
4125 *tail = t;
4126 tail = &t->next;
4127 t->type = type;
4128 nasm_free(t->text);
4129 t->text = text;
4130 t->a.mac = NULL;
4132 changed = true;
4133 continue;
4134 } else if (tline->type == TOK_INDIRECT) {
4135 t = tline;
4136 tline = tline->next;
4137 tt = tokenize(t->text);
4138 tt = expand_mmac_params(tt);
4139 tt = expand_smacro(tt);
4140 *tail = tt;
4141 while (tt) {
4142 tt->a.mac = NULL; /* Necessary? */
4143 tail = &tt->next;
4144 tt = tt->next;
4146 delete_Token(t);
4147 changed = true;
4148 } else {
4149 t = *tail = tline;
4150 tline = tline->next;
4151 t->a.mac = NULL;
4152 tail = &t->next;
4155 *tail = NULL;
4157 if (changed) {
4158 const struct tokseq_match t[] = {
4160 PP_CONCAT_MASK(TOK_ID) |
4161 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4162 PP_CONCAT_MASK(TOK_ID) |
4163 PP_CONCAT_MASK(TOK_NUMBER) |
4164 PP_CONCAT_MASK(TOK_FLOAT) |
4165 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4168 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4169 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4172 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4175 return thead;
4179 * Expand all single-line macro calls made in the given line.
4180 * Return the expanded version of the line. The original is deemed
4181 * to be destroyed in the process. (In reality we'll just move
4182 * Tokens from input to output a lot of the time, rather than
4183 * actually bothering to destroy and replicate.)
4186 static Token *expand_smacro(Token * tline)
4188 Token *t, *tt, *mstart, **tail, *thead;
4189 SMacro *head = NULL, *m;
4190 Token **params;
4191 int *paramsize;
4192 unsigned int nparam, sparam;
4193 int brackets;
4194 Token *org_tline = tline;
4195 Context *ctx;
4196 const char *mname;
4197 int deadman = DEADMAN_LIMIT;
4198 bool expanded;
4201 * Trick: we should avoid changing the start token pointer since it can
4202 * be contained in "next" field of other token. Because of this
4203 * we allocate a copy of first token and work with it; at the end of
4204 * routine we copy it back
4206 if (org_tline) {
4207 tline = new_Token(org_tline->next, org_tline->type,
4208 org_tline->text, 0);
4209 tline->a.mac = org_tline->a.mac;
4210 nasm_free(org_tline->text);
4211 org_tline->text = NULL;
4214 expanded = true; /* Always expand %+ at least once */
4216 again:
4217 thead = NULL;
4218 tail = &thead;
4220 while (tline) { /* main token loop */
4221 if (!--deadman) {
4222 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4223 goto err;
4226 if ((mname = tline->text)) {
4227 /* if this token is a local macro, look in local context */
4228 if (tline->type == TOK_ID) {
4229 head = (SMacro *)hash_findix(&smacros, mname);
4230 } else if (tline->type == TOK_PREPROC_ID) {
4231 ctx = get_ctx(mname, &mname);
4232 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4233 } else
4234 head = NULL;
4237 * We've hit an identifier. As in is_mmacro below, we first
4238 * check whether the identifier is a single-line macro at
4239 * all, then think about checking for parameters if
4240 * necessary.
4242 list_for_each(m, head)
4243 if (!mstrcmp(m->name, mname, m->casesense))
4244 break;
4245 if (m) {
4246 mstart = tline;
4247 params = NULL;
4248 paramsize = NULL;
4249 if (m->nparam == 0) {
4251 * Simple case: the macro is parameterless. Discard the
4252 * one token that the macro call took, and push the
4253 * expansion back on the to-do stack.
4255 if (!m->expansion) {
4256 if (!strcmp("__FILE__", m->name)) {
4257 const char *file = src_get_fname();
4258 /* nasm_free(tline->text); here? */
4259 tline->text = nasm_quote(file, strlen(file));
4260 tline->type = TOK_STRING;
4261 continue;
4263 if (!strcmp("__LINE__", m->name)) {
4264 nasm_free(tline->text);
4265 make_tok_num(tline, src_get_linnum());
4266 continue;
4268 if (!strcmp("__BITS__", m->name)) {
4269 nasm_free(tline->text);
4270 make_tok_num(tline, globalbits);
4271 continue;
4273 tline = delete_Token(tline);
4274 continue;
4276 } else {
4278 * Complicated case: at least one macro with this name
4279 * exists and takes parameters. We must find the
4280 * parameters in the call, count them, find the SMacro
4281 * that corresponds to that form of the macro call, and
4282 * substitute for the parameters when we expand. What a
4283 * pain.
4285 /*tline = tline->next;
4286 skip_white_(tline); */
4287 do {
4288 t = tline->next;
4289 while (tok_type_(t, TOK_SMAC_END)) {
4290 t->a.mac->in_progress = false;
4291 t->text = NULL;
4292 t = tline->next = delete_Token(t);
4294 tline = t;
4295 } while (tok_type_(tline, TOK_WHITESPACE));
4296 if (!tok_is_(tline, "(")) {
4298 * This macro wasn't called with parameters: ignore
4299 * the call. (Behaviour borrowed from gnu cpp.)
4301 tline = mstart;
4302 m = NULL;
4303 } else {
4304 int paren = 0;
4305 int white = 0;
4306 brackets = 0;
4307 nparam = 0;
4308 sparam = PARAM_DELTA;
4309 params = nasm_malloc(sparam * sizeof(Token *));
4310 params[0] = tline->next;
4311 paramsize = nasm_malloc(sparam * sizeof(int));
4312 paramsize[0] = 0;
4313 while (true) { /* parameter loop */
4315 * For some unusual expansions
4316 * which concatenates function call
4318 t = tline->next;
4319 while (tok_type_(t, TOK_SMAC_END)) {
4320 t->a.mac->in_progress = false;
4321 t->text = NULL;
4322 t = tline->next = delete_Token(t);
4324 tline = t;
4326 if (!tline) {
4327 nasm_error(ERR_NONFATAL,
4328 "macro call expects terminating `)'");
4329 break;
4331 if (tline->type == TOK_WHITESPACE
4332 && brackets <= 0) {
4333 if (paramsize[nparam])
4334 white++;
4335 else
4336 params[nparam] = tline->next;
4337 continue; /* parameter loop */
4339 if (tline->type == TOK_OTHER
4340 && tline->text[1] == 0) {
4341 char ch = tline->text[0];
4342 if (ch == ',' && !paren && brackets <= 0) {
4343 if (++nparam >= sparam) {
4344 sparam += PARAM_DELTA;
4345 params = nasm_realloc(params,
4346 sparam * sizeof(Token *));
4347 paramsize = nasm_realloc(paramsize,
4348 sparam * sizeof(int));
4350 params[nparam] = tline->next;
4351 paramsize[nparam] = 0;
4352 white = 0;
4353 continue; /* parameter loop */
4355 if (ch == '{' &&
4356 (brackets > 0 || (brackets == 0 &&
4357 !paramsize[nparam])))
4359 if (!(brackets++)) {
4360 params[nparam] = tline->next;
4361 continue; /* parameter loop */
4364 if (ch == '}' && brackets > 0)
4365 if (--brackets == 0) {
4366 brackets = -1;
4367 continue; /* parameter loop */
4369 if (ch == '(' && !brackets)
4370 paren++;
4371 if (ch == ')' && brackets <= 0)
4372 if (--paren < 0)
4373 break;
4375 if (brackets < 0) {
4376 brackets = 0;
4377 nasm_error(ERR_NONFATAL, "braces do not "
4378 "enclose all of macro parameter");
4380 paramsize[nparam] += white + 1;
4381 white = 0;
4382 } /* parameter loop */
4383 nparam++;
4384 while (m && (m->nparam != nparam ||
4385 mstrcmp(m->name, mname,
4386 m->casesense)))
4387 m = m->next;
4388 if (!m)
4389 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4390 "macro `%s' exists, "
4391 "but not taking %d parameters",
4392 mstart->text, nparam);
4395 if (m && m->in_progress)
4396 m = NULL;
4397 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4399 * Design question: should we handle !tline, which
4400 * indicates missing ')' here, or expand those
4401 * macros anyway, which requires the (t) test a few
4402 * lines down?
4404 nasm_free(params);
4405 nasm_free(paramsize);
4406 tline = mstart;
4407 } else {
4409 * Expand the macro: we are placed on the last token of the
4410 * call, so that we can easily split the call from the
4411 * following tokens. We also start by pushing an SMAC_END
4412 * token for the cycle removal.
4414 t = tline;
4415 if (t) {
4416 tline = t->next;
4417 t->next = NULL;
4419 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4420 tt->a.mac = m;
4421 m->in_progress = true;
4422 tline = tt;
4423 list_for_each(t, m->expansion) {
4424 if (t->type >= TOK_SMAC_PARAM) {
4425 Token *pcopy = tline, **ptail = &pcopy;
4426 Token *ttt, *pt;
4427 int i;
4429 ttt = params[t->type - TOK_SMAC_PARAM];
4430 i = paramsize[t->type - TOK_SMAC_PARAM];
4431 while (--i >= 0) {
4432 pt = *ptail = new_Token(tline, ttt->type,
4433 ttt->text, 0);
4434 ptail = &pt->next;
4435 ttt = ttt->next;
4436 if (!ttt && i > 0) {
4438 * FIXME: Need to handle more gracefully,
4439 * exiting early on agruments analysis.
4441 nasm_error(ERR_FATAL,
4442 "macro `%s' expects %d args",
4443 mstart->text,
4444 (int)paramsize[t->type - TOK_SMAC_PARAM]);
4447 tline = pcopy;
4448 } else if (t->type == TOK_PREPROC_Q) {
4449 tt = new_Token(tline, TOK_ID, mname, 0);
4450 tline = tt;
4451 } else if (t->type == TOK_PREPROC_QQ) {
4452 tt = new_Token(tline, TOK_ID, m->name, 0);
4453 tline = tt;
4454 } else {
4455 tt = new_Token(tline, t->type, t->text, 0);
4456 tline = tt;
4461 * Having done that, get rid of the macro call, and clean
4462 * up the parameters.
4464 nasm_free(params);
4465 nasm_free(paramsize);
4466 free_tlist(mstart);
4467 expanded = true;
4468 continue; /* main token loop */
4473 if (tline->type == TOK_SMAC_END) {
4474 tline->a.mac->in_progress = false;
4475 tline = delete_Token(tline);
4476 } else {
4477 t = *tail = tline;
4478 tline = tline->next;
4479 t->a.mac = NULL;
4480 t->next = NULL;
4481 tail = &t->next;
4486 * Now scan the entire line and look for successive TOK_IDs that resulted
4487 * after expansion (they can't be produced by tokenize()). The successive
4488 * TOK_IDs should be concatenated.
4489 * Also we look for %+ tokens and concatenate the tokens before and after
4490 * them (without white spaces in between).
4492 if (expanded) {
4493 const struct tokseq_match t[] = {
4495 PP_CONCAT_MASK(TOK_ID) |
4496 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4497 PP_CONCAT_MASK(TOK_ID) |
4498 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4499 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4502 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4504 * If we concatenated something, *and* we had previously expanded
4505 * an actual macro, scan the lines again for macros...
4507 tline = thead;
4508 expanded = false;
4509 goto again;
4513 err:
4514 if (org_tline) {
4515 if (thead) {
4516 *org_tline = *thead;
4517 /* since we just gave text to org_line, don't free it */
4518 thead->text = NULL;
4519 delete_Token(thead);
4520 } else {
4521 /* the expression expanded to empty line;
4522 we can't return NULL for some reasons
4523 we just set the line to a single WHITESPACE token. */
4524 memset(org_tline, 0, sizeof(*org_tline));
4525 org_tline->text = NULL;
4526 org_tline->type = TOK_WHITESPACE;
4528 thead = org_tline;
4531 return thead;
4535 * Similar to expand_smacro but used exclusively with macro identifiers
4536 * right before they are fetched in. The reason is that there can be
4537 * identifiers consisting of several subparts. We consider that if there
4538 * are more than one element forming the name, user wants a expansion,
4539 * otherwise it will be left as-is. Example:
4541 * %define %$abc cde
4543 * the identifier %$abc will be left as-is so that the handler for %define
4544 * will suck it and define the corresponding value. Other case:
4546 * %define _%$abc cde
4548 * In this case user wants name to be expanded *before* %define starts
4549 * working, so we'll expand %$abc into something (if it has a value;
4550 * otherwise it will be left as-is) then concatenate all successive
4551 * PP_IDs into one.
4553 static Token *expand_id(Token * tline)
4555 Token *cur, *oldnext = NULL;
4557 if (!tline || !tline->next)
4558 return tline;
4560 cur = tline;
4561 while (cur->next &&
4562 (cur->next->type == TOK_ID ||
4563 cur->next->type == TOK_PREPROC_ID
4564 || cur->next->type == TOK_NUMBER))
4565 cur = cur->next;
4567 /* If identifier consists of just one token, don't expand */
4568 if (cur == tline)
4569 return tline;
4571 if (cur) {
4572 oldnext = cur->next; /* Detach the tail past identifier */
4573 cur->next = NULL; /* so that expand_smacro stops here */
4576 tline = expand_smacro(tline);
4578 if (cur) {
4579 /* expand_smacro possibly changhed tline; re-scan for EOL */
4580 cur = tline;
4581 while (cur && cur->next)
4582 cur = cur->next;
4583 if (cur)
4584 cur->next = oldnext;
4587 return tline;
4591 * Determine whether the given line constitutes a multi-line macro
4592 * call, and return the MMacro structure called if so. Doesn't have
4593 * to check for an initial label - that's taken care of in
4594 * expand_mmacro - but must check numbers of parameters. Guaranteed
4595 * to be called with tline->type == TOK_ID, so the putative macro
4596 * name is easy to find.
4598 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4600 MMacro *head, *m;
4601 Token **params;
4602 int nparam;
4604 head = (MMacro *) hash_findix(&mmacros, tline->text);
4607 * Efficiency: first we see if any macro exists with the given
4608 * name. If not, we can return NULL immediately. _Then_ we
4609 * count the parameters, and then we look further along the
4610 * list if necessary to find the proper MMacro.
4612 list_for_each(m, head)
4613 if (!mstrcmp(m->name, tline->text, m->casesense))
4614 break;
4615 if (!m)
4616 return NULL;
4619 * OK, we have a potential macro. Count and demarcate the
4620 * parameters.
4622 count_mmac_params(tline->next, &nparam, &params);
4625 * So we know how many parameters we've got. Find the MMacro
4626 * structure that handles this number.
4628 while (m) {
4629 if (m->nparam_min <= nparam
4630 && (m->plus || nparam <= m->nparam_max)) {
4632 * This one is right. Just check if cycle removal
4633 * prohibits us using it before we actually celebrate...
4635 if (m->in_progress > m->max_depth) {
4636 if (m->max_depth > 0) {
4637 nasm_error(ERR_WARNING,
4638 "reached maximum recursion depth of %i",
4639 m->max_depth);
4641 nasm_free(params);
4642 return NULL;
4645 * It's right, and we can use it. Add its default
4646 * parameters to the end of our list if necessary.
4648 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4649 params =
4650 nasm_realloc(params,
4651 ((m->nparam_min + m->ndefs +
4652 1) * sizeof(*params)));
4653 while (nparam < m->nparam_min + m->ndefs) {
4654 params[nparam] = m->defaults[nparam - m->nparam_min];
4655 nparam++;
4659 * If we've gone over the maximum parameter count (and
4660 * we're in Plus mode), ignore parameters beyond
4661 * nparam_max.
4663 if (m->plus && nparam > m->nparam_max)
4664 nparam = m->nparam_max;
4666 * Then terminate the parameter list, and leave.
4668 if (!params) { /* need this special case */
4669 params = nasm_malloc(sizeof(*params));
4670 nparam = 0;
4672 params[nparam] = NULL;
4673 *params_array = params;
4674 return m;
4677 * This one wasn't right: look for the next one with the
4678 * same name.
4680 list_for_each(m, m->next)
4681 if (!mstrcmp(m->name, tline->text, m->casesense))
4682 break;
4686 * After all that, we didn't find one with the right number of
4687 * parameters. Issue a warning, and fail to expand the macro.
4689 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4690 "macro `%s' exists, but not taking %d parameters",
4691 tline->text, nparam);
4692 nasm_free(params);
4693 return NULL;
4698 * Save MMacro invocation specific fields in
4699 * preparation for a recursive macro expansion
4701 static void push_mmacro(MMacro *m)
4703 MMacroInvocation *i;
4705 i = nasm_malloc(sizeof(MMacroInvocation));
4706 i->prev = m->prev;
4707 i->params = m->params;
4708 i->iline = m->iline;
4709 i->nparam = m->nparam;
4710 i->rotate = m->rotate;
4711 i->paramlen = m->paramlen;
4712 i->unique = m->unique;
4713 i->condcnt = m->condcnt;
4714 m->prev = i;
4719 * Restore MMacro invocation specific fields that were
4720 * saved during a previous recursive macro expansion
4722 static void pop_mmacro(MMacro *m)
4724 MMacroInvocation *i;
4726 if (m->prev) {
4727 i = m->prev;
4728 m->prev = i->prev;
4729 m->params = i->params;
4730 m->iline = i->iline;
4731 m->nparam = i->nparam;
4732 m->rotate = i->rotate;
4733 m->paramlen = i->paramlen;
4734 m->unique = i->unique;
4735 m->condcnt = i->condcnt;
4736 nasm_free(i);
4742 * Expand the multi-line macro call made by the given line, if
4743 * there is one to be expanded. If there is, push the expansion on
4744 * istk->expansion and return 1. Otherwise return 0.
4746 static int expand_mmacro(Token * tline)
4748 Token *startline = tline;
4749 Token *label = NULL;
4750 int dont_prepend = 0;
4751 Token **params, *t, *tt;
4752 MMacro *m;
4753 Line *l, *ll;
4754 int i, nparam, *paramlen;
4755 const char *mname;
4757 t = tline;
4758 skip_white_(t);
4759 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4760 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4761 return 0;
4762 m = is_mmacro(t, &params);
4763 if (m) {
4764 mname = t->text;
4765 } else {
4766 Token *last;
4768 * We have an id which isn't a macro call. We'll assume
4769 * it might be a label; we'll also check to see if a
4770 * colon follows it. Then, if there's another id after
4771 * that lot, we'll check it again for macro-hood.
4773 label = last = t;
4774 t = t->next;
4775 if (tok_type_(t, TOK_WHITESPACE))
4776 last = t, t = t->next;
4777 if (tok_is_(t, ":")) {
4778 dont_prepend = 1;
4779 last = t, t = t->next;
4780 if (tok_type_(t, TOK_WHITESPACE))
4781 last = t, t = t->next;
4783 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4784 return 0;
4785 last->next = NULL;
4786 mname = t->text;
4787 tline = t;
4791 * Fix up the parameters: this involves stripping leading and
4792 * trailing whitespace, then stripping braces if they are
4793 * present.
4795 for (nparam = 0; params[nparam]; nparam++) ;
4796 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4798 for (i = 0; params[i]; i++) {
4799 int brace = 0;
4800 int comma = (!m->plus || i < nparam - 1);
4802 t = params[i];
4803 skip_white_(t);
4804 if (tok_is_(t, "{"))
4805 t = t->next, brace++, comma = false;
4806 params[i] = t;
4807 paramlen[i] = 0;
4808 while (t) {
4809 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4810 break; /* ... because we have hit a comma */
4811 if (comma && t->type == TOK_WHITESPACE
4812 && tok_is_(t->next, ","))
4813 break; /* ... or a space then a comma */
4814 if (brace && t->type == TOK_OTHER) {
4815 if (t->text[0] == '{')
4816 brace++; /* ... or a nested opening brace */
4817 else if (t->text[0] == '}')
4818 if (!--brace)
4819 break; /* ... or a brace */
4821 t = t->next;
4822 paramlen[i]++;
4824 if (brace)
4825 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4829 * OK, we have a MMacro structure together with a set of
4830 * parameters. We must now go through the expansion and push
4831 * copies of each Line on to istk->expansion. Substitution of
4832 * parameter tokens and macro-local tokens doesn't get done
4833 * until the single-line macro substitution process; this is
4834 * because delaying them allows us to change the semantics
4835 * later through %rotate.
4837 * First, push an end marker on to istk->expansion, mark this
4838 * macro as in progress, and set up its invocation-specific
4839 * variables.
4841 ll = nasm_malloc(sizeof(Line));
4842 ll->next = istk->expansion;
4843 ll->finishes = m;
4844 ll->first = NULL;
4845 istk->expansion = ll;
4848 * Save the previous MMacro expansion in the case of
4849 * macro recursion
4851 if (m->max_depth && m->in_progress)
4852 push_mmacro(m);
4854 m->in_progress ++;
4855 m->params = params;
4856 m->iline = tline;
4857 m->nparam = nparam;
4858 m->rotate = 0;
4859 m->paramlen = paramlen;
4860 m->unique = unique++;
4861 m->lineno = 0;
4862 m->condcnt = 0;
4864 m->next_active = istk->mstk;
4865 istk->mstk = m;
4867 list_for_each(l, m->expansion) {
4868 Token **tail;
4870 ll = nasm_malloc(sizeof(Line));
4871 ll->finishes = NULL;
4872 ll->next = istk->expansion;
4873 istk->expansion = ll;
4874 tail = &ll->first;
4876 list_for_each(t, l->first) {
4877 Token *x = t;
4878 switch (t->type) {
4879 case TOK_PREPROC_Q:
4880 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4881 break;
4882 case TOK_PREPROC_QQ:
4883 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4884 break;
4885 case TOK_PREPROC_ID:
4886 if (t->text[1] == '0' && t->text[2] == '0') {
4887 dont_prepend = -1;
4888 x = label;
4889 if (!x)
4890 continue;
4892 /* fall through */
4893 default:
4894 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4895 break;
4897 tail = &tt->next;
4899 *tail = NULL;
4903 * If we had a label, push it on as the first line of
4904 * the macro expansion.
4906 if (label) {
4907 if (dont_prepend < 0)
4908 free_tlist(startline);
4909 else {
4910 ll = nasm_malloc(sizeof(Line));
4911 ll->finishes = NULL;
4912 ll->next = istk->expansion;
4913 istk->expansion = ll;
4914 ll->first = startline;
4915 if (!dont_prepend) {
4916 while (label->next)
4917 label = label->next;
4918 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4923 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4925 return 1;
4929 * This function adds macro names to error messages, and suppresses
4930 * them if necessary.
4932 static void pp_verror(int severity, const char *fmt, va_list arg)
4934 char buff[BUFSIZ];
4935 MMacro *mmac = NULL;
4936 int delta = 0;
4939 * If we're in a dead branch of IF or something like it, ignore the error.
4940 * However, because %else etc are evaluated in the state context
4941 * of the previous branch, errors might get lost:
4942 * %if 0 ... %else trailing garbage ... %endif
4943 * So %else etc should set the ERR_PP_PRECOND flag.
4945 if ((severity & ERR_MASK) < ERR_FATAL &&
4946 istk && istk->conds &&
4947 ((severity & ERR_PP_PRECOND) ?
4948 istk->conds->state == COND_NEVER :
4949 !emitting(istk->conds->state)))
4950 return;
4952 /* get %macro name */
4953 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4954 mmac = istk->mstk;
4955 /* but %rep blocks should be skipped */
4956 while (mmac && !mmac->name)
4957 mmac = mmac->next_active, delta++;
4960 if (mmac) {
4961 vsnprintf(buff, sizeof(buff), fmt, arg);
4963 nasm_set_verror(real_verror);
4964 nasm_error(severity, "(%s:%d) %s",
4965 mmac->name, mmac->lineno - delta, buff);
4966 nasm_set_verror(pp_verror);
4967 } else {
4968 real_verror(severity, fmt, arg);
4972 static void
4973 pp_reset(char *file, int apass, StrList **deplist)
4975 Token *t;
4977 cstk = NULL;
4978 istk = nasm_malloc(sizeof(Include));
4979 istk->next = NULL;
4980 istk->conds = NULL;
4981 istk->expansion = NULL;
4982 istk->mstk = NULL;
4983 istk->fp = nasm_open_read(file, NF_TEXT);
4984 istk->fname = NULL;
4985 src_set(0, file);
4986 istk->lineinc = 1;
4987 if (!istk->fp)
4988 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4989 defining = NULL;
4990 nested_mac_count = 0;
4991 nested_rep_count = 0;
4992 init_macros();
4993 unique = 0;
4995 if (tasm_compatible_mode)
4996 pp_add_stdmac(nasm_stdmac_tasm);
4998 pp_add_stdmac(nasm_stdmac_nasm);
4999 pp_add_stdmac(nasm_stdmac_version);
5001 if (extrastdmac)
5002 pp_add_stdmac(extrastdmac);
5004 stdmacpos = stdmacros[0];
5005 stdmacnext = &stdmacros[1];
5007 do_predef = true;
5010 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
5011 * The caller, however, will also pass in 3 for preprocess-only so
5012 * we can set __PASS__ accordingly.
5014 pass = apass > 2 ? 2 : apass;
5016 dephead = deplist;
5017 nasm_add_string_to_strlist(dephead, file);
5020 * Define the __PASS__ macro. This is defined here unlike
5021 * all the other builtins, because it is special -- it varies between
5022 * passes.
5024 t = nasm_malloc(sizeof(*t));
5025 t->next = NULL;
5026 make_tok_num(t, apass);
5027 t->a.mac = NULL;
5028 define_smacro(NULL, "__PASS__", true, 0, t);
5031 static void pp_init(void)
5033 hash_init(&FileHash, HASH_MEDIUM);
5036 static char *pp_getline(void)
5038 char *line;
5039 Token *tline;
5041 real_verror = nasm_set_verror(pp_verror);
5043 while (1) {
5045 * Fetch a tokenized line, either from the macro-expansion
5046 * buffer or from the input file.
5048 tline = NULL;
5049 while (istk->expansion && istk->expansion->finishes) {
5050 Line *l = istk->expansion;
5051 if (!l->finishes->name && l->finishes->in_progress > 1) {
5052 Line *ll;
5055 * This is a macro-end marker for a macro with no
5056 * name, which means it's not really a macro at all
5057 * but a %rep block, and the `in_progress' field is
5058 * more than 1, meaning that we still need to
5059 * repeat. (1 means the natural last repetition; 0
5060 * means termination by %exitrep.) We have
5061 * therefore expanded up to the %endrep, and must
5062 * push the whole block on to the expansion buffer
5063 * again. We don't bother to remove the macro-end
5064 * marker: we'd only have to generate another one
5065 * if we did.
5067 l->finishes->in_progress--;
5068 list_for_each(l, l->finishes->expansion) {
5069 Token *t, *tt, **tail;
5071 ll = nasm_malloc(sizeof(Line));
5072 ll->next = istk->expansion;
5073 ll->finishes = NULL;
5074 ll->first = NULL;
5075 tail = &ll->first;
5077 list_for_each(t, l->first) {
5078 if (t->text || t->type == TOK_WHITESPACE) {
5079 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5080 tail = &tt->next;
5084 istk->expansion = ll;
5086 } else {
5088 * Check whether a `%rep' was started and not ended
5089 * within this macro expansion. This can happen and
5090 * should be detected. It's a fatal error because
5091 * I'm too confused to work out how to recover
5092 * sensibly from it.
5094 if (defining) {
5095 if (defining->name)
5096 nasm_panic(0, "defining with name in expansion");
5097 else if (istk->mstk->name)
5098 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5099 " expansion of macro `%s'",
5100 istk->mstk->name);
5104 * FIXME: investigate the relationship at this point between
5105 * istk->mstk and l->finishes
5108 MMacro *m = istk->mstk;
5109 istk->mstk = m->next_active;
5110 if (m->name) {
5112 * This was a real macro call, not a %rep, and
5113 * therefore the parameter information needs to
5114 * be freed.
5116 if (m->prev) {
5117 pop_mmacro(m);
5118 l->finishes->in_progress --;
5119 } else {
5120 nasm_free(m->params);
5121 free_tlist(m->iline);
5122 nasm_free(m->paramlen);
5123 l->finishes->in_progress = 0;
5128 * FIXME It is incorrect to always free_mmacro here.
5129 * It leads to usage-after-free.
5131 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
5133 #if 0
5134 else
5135 free_mmacro(m);
5136 #endif
5138 istk->expansion = l->next;
5139 nasm_free(l);
5140 lfmt->downlevel(LIST_MACRO);
5143 while (1) { /* until we get a line we can use */
5145 if (istk->expansion) { /* from a macro expansion */
5146 char *p;
5147 Line *l = istk->expansion;
5148 if (istk->mstk)
5149 istk->mstk->lineno++;
5150 tline = l->first;
5151 istk->expansion = l->next;
5152 nasm_free(l);
5153 p = detoken(tline, false);
5154 lfmt->line(LIST_MACRO, p);
5155 nasm_free(p);
5156 break;
5158 line = read_line();
5159 if (line) { /* from the current input file */
5160 line = prepreproc(line);
5161 tline = tokenize(line);
5162 nasm_free(line);
5163 break;
5166 * The current file has ended; work down the istk
5169 Include *i = istk;
5170 fclose(i->fp);
5171 if (i->conds) {
5172 /* nasm_error can't be conditionally suppressed */
5173 nasm_fatal(0,
5174 "expected `%%endif' before end of file");
5176 /* only set line and file name if there's a next node */
5177 if (i->next)
5178 src_set(i->lineno, i->fname);
5179 istk = i->next;
5180 lfmt->downlevel(LIST_INCLUDE);
5181 nasm_free(i);
5182 if (!istk) {
5183 line = NULL;
5184 goto done;
5186 if (istk->expansion && istk->expansion->finishes)
5187 break;
5192 * We must expand MMacro parameters and MMacro-local labels
5193 * _before_ we plunge into directive processing, to cope
5194 * with things like `%define something %1' such as STRUC
5195 * uses. Unless we're _defining_ a MMacro, in which case
5196 * those tokens should be left alone to go into the
5197 * definition; and unless we're in a non-emitting
5198 * condition, in which case we don't want to meddle with
5199 * anything.
5201 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5202 && !(istk->mstk && !istk->mstk->in_progress)) {
5203 tline = expand_mmac_params(tline);
5207 * Check the line to see if it's a preprocessor directive.
5209 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5210 if (line)
5211 break; /* Directive generated output */
5212 else
5213 continue;
5214 } else if (defining) {
5216 * We're defining a multi-line macro. We emit nothing
5217 * at all, and just
5218 * shove the tokenized line on to the macro definition.
5220 Line *l = nasm_malloc(sizeof(Line));
5221 l->next = defining->expansion;
5222 l->first = tline;
5223 l->finishes = NULL;
5224 defining->expansion = l;
5225 continue;
5226 } else if (istk->conds && !emitting(istk->conds->state)) {
5228 * We're in a non-emitting branch of a condition block.
5229 * Emit nothing at all, not even a blank line: when we
5230 * emerge from the condition we'll give a line-number
5231 * directive so we keep our place correctly.
5233 free_tlist(tline);
5234 continue;
5235 } else if (istk->mstk && !istk->mstk->in_progress) {
5237 * We're in a %rep block which has been terminated, so
5238 * we're walking through to the %endrep without
5239 * emitting anything. Emit nothing at all, not even a
5240 * blank line: when we emerge from the %rep block we'll
5241 * give a line-number directive so we keep our place
5242 * correctly.
5244 free_tlist(tline);
5245 continue;
5246 } else {
5247 tline = expand_smacro(tline);
5248 if (!expand_mmacro(tline)) {
5250 * De-tokenize the line again, and emit it.
5252 line = detoken(tline, true);
5253 free_tlist(tline);
5254 break;
5255 } else {
5256 continue; /* expand_mmacro calls free_tlist */
5261 done:
5262 nasm_set_verror(real_verror);
5263 return line;
5266 static void pp_cleanup(int pass)
5268 real_verror = nasm_set_verror(pp_verror);
5270 if (defining) {
5271 if (defining->name) {
5272 nasm_error(ERR_NONFATAL,
5273 "end of file while still defining macro `%s'",
5274 defining->name);
5275 } else {
5276 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5279 free_mmacro(defining);
5280 defining = NULL;
5283 nasm_set_verror(real_verror);
5285 while (cstk)
5286 ctx_pop();
5287 free_macros();
5288 while (istk) {
5289 Include *i = istk;
5290 istk = istk->next;
5291 fclose(i->fp);
5292 nasm_free(i);
5294 while (cstk)
5295 ctx_pop();
5296 src_set_fname(NULL);
5297 if (pass == 0) {
5298 IncPath *i;
5299 free_llist(predef);
5300 predef = NULL;
5301 delete_Blocks();
5302 freeTokens = NULL;
5303 while ((i = ipath)) {
5304 ipath = i->next;
5305 if (i->path)
5306 nasm_free(i->path);
5307 nasm_free(i);
5312 static void pp_include_path(char *path)
5314 IncPath *i;
5316 i = nasm_malloc(sizeof(IncPath));
5317 i->path = path ? nasm_strdup(path) : NULL;
5318 i->next = NULL;
5320 if (ipath) {
5321 IncPath *j = ipath;
5322 while (j->next)
5323 j = j->next;
5324 j->next = i;
5325 } else {
5326 ipath = i;
5330 static void pp_pre_include(char *fname)
5332 Token *inc, *space, *name;
5333 Line *l;
5335 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5336 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5337 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5339 l = nasm_malloc(sizeof(Line));
5340 l->next = predef;
5341 l->first = inc;
5342 l->finishes = NULL;
5343 predef = l;
5346 static void pp_pre_define(char *definition)
5348 Token *def, *space;
5349 Line *l;
5350 char *equals;
5352 real_verror = nasm_set_verror(pp_verror);
5354 equals = strchr(definition, '=');
5355 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5356 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5357 if (equals)
5358 *equals = ' ';
5359 space->next = tokenize(definition);
5360 if (equals)
5361 *equals = '=';
5363 if (space->next->type != TOK_PREPROC_ID &&
5364 space->next->type != TOK_ID)
5365 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5367 l = nasm_malloc(sizeof(Line));
5368 l->next = predef;
5369 l->first = def;
5370 l->finishes = NULL;
5371 predef = l;
5373 nasm_set_verror(real_verror);
5376 static void pp_pre_undefine(char *definition)
5378 Token *def, *space;
5379 Line *l;
5381 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5382 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5383 space->next = tokenize(definition);
5385 l = nasm_malloc(sizeof(Line));
5386 l->next = predef;
5387 l->first = def;
5388 l->finishes = NULL;
5389 predef = l;
5392 static void pp_add_stdmac(macros_t *macros)
5394 macros_t **mp;
5396 /* Find the end of the list and avoid duplicates */
5397 for (mp = stdmacros; *mp; mp++) {
5398 if (*mp == macros)
5399 return; /* Nothing to do */
5402 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5404 *mp = macros;
5407 static void pp_extra_stdmac(macros_t *macros)
5409 extrastdmac = macros;
5412 static void make_tok_num(Token * tok, int64_t val)
5414 char numbuf[32];
5415 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5416 tok->text = nasm_strdup(numbuf);
5417 tok->type = TOK_NUMBER;
5420 static void pp_list_one_macro(MMacro *m, int severity)
5422 if (!m)
5423 return;
5425 /* We need to print the next_active list in reverse order */
5426 pp_list_one_macro(m->next_active, severity);
5428 if (m->name && !m->nolist) {
5429 src_set(m->xline + m->lineno, m->fname);
5430 nasm_error(severity, "... from macro `%s' defined here", m->name);
5434 static void pp_error_list_macros(int severity)
5436 int32_t saved_line;
5437 const char *saved_fname = NULL;
5439 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5440 src_get(&saved_line, &saved_fname);
5442 if (istk)
5443 pp_list_one_macro(istk->mstk, severity);
5445 src_set(saved_line, saved_fname);
5448 const struct preproc_ops nasmpp = {
5449 pp_init,
5450 pp_reset,
5451 pp_getline,
5452 pp_cleanup,
5453 pp_extra_stdmac,
5454 pp_pre_define,
5455 pp_pre_undefine,
5456 pp_pre_include,
5457 pp_include_path,
5458 pp_error_list_macros,