peproc: Fix sigsevg in smacro expansion
[nasm.git] / asm / preproc.c
blobcd4a94949b189fff2934d725b6e5f70b52169c3c
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[1] == '!') {
1258 char *v;
1259 char *q = t->text;
1261 v = t->text + 2;
1262 if (*v == '\'' || *v == '\"' || *v == '`') {
1263 size_t len = nasm_unquote(v, NULL);
1264 size_t clen = strlen(v);
1266 if (len != clen) {
1267 nasm_error(ERR_NONFATAL | ERR_PASS1,
1268 "NUL character in %%! string");
1269 v = NULL;
1273 if (v) {
1274 char *p = getenv(v);
1275 if (!p) {
1276 nasm_error(ERR_NONFATAL | ERR_PASS1,
1277 "nonexistent environment variable `%s'", v);
1279 * FIXME We better should investigate if accessing
1280 * ->text[1] without ->text[0] is safe enough.
1282 t->text = nasm_zalloc(2);
1283 } else
1284 t->text = nasm_strdup(p);
1285 nasm_free(q);
1289 /* Expand local macros here and not during preprocessing */
1290 if (expand_locals &&
1291 t->type == TOK_PREPROC_ID && t->text &&
1292 t->text[0] == '%' && t->text[1] == '$') {
1293 const char *q;
1294 char *p;
1295 Context *ctx = get_ctx(t->text, &q);
1296 if (ctx) {
1297 char buffer[40];
1298 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1299 p = nasm_strcat(buffer, q);
1300 nasm_free(t->text);
1301 t->text = p;
1304 if (t->type == TOK_WHITESPACE)
1305 len++;
1306 else if (t->text)
1307 len += strlen(t->text);
1310 p = line = nasm_malloc(len + 1);
1312 list_for_each(t, tlist) {
1313 if (t->type == TOK_WHITESPACE) {
1314 *p++ = ' ';
1315 } else if (t->text) {
1316 q = t->text;
1317 while (*q)
1318 *p++ = *q++;
1321 *p = '\0';
1323 return line;
1327 * A scanner, suitable for use by the expression evaluator, which
1328 * operates on a line of Tokens. Expects a pointer to a pointer to
1329 * the first token in the line to be passed in as its private_data
1330 * field.
1332 * FIX: This really needs to be unified with stdscan.
1334 static int ppscan(void *private_data, struct tokenval *tokval)
1336 Token **tlineptr = private_data;
1337 Token *tline;
1338 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1340 do {
1341 tline = *tlineptr;
1342 *tlineptr = tline ? tline->next : NULL;
1343 } while (tline && (tline->type == TOK_WHITESPACE ||
1344 tline->type == TOK_COMMENT));
1346 if (!tline)
1347 return tokval->t_type = TOKEN_EOS;
1349 tokval->t_charptr = tline->text;
1351 if (tline->text[0] == '$' && !tline->text[1])
1352 return tokval->t_type = TOKEN_HERE;
1353 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1354 return tokval->t_type = TOKEN_BASE;
1356 if (tline->type == TOK_ID) {
1357 p = tokval->t_charptr = tline->text;
1358 if (p[0] == '$') {
1359 tokval->t_charptr++;
1360 return tokval->t_type = TOKEN_ID;
1363 for (r = p, s = ourcopy; *r; r++) {
1364 if (r >= p+MAX_KEYWORD)
1365 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1366 *s++ = nasm_tolower(*r);
1368 *s = '\0';
1369 /* right, so we have an identifier sitting in temp storage. now,
1370 * is it actually a register or instruction name, or what? */
1371 return nasm_token_hash(ourcopy, tokval);
1374 if (tline->type == TOK_NUMBER) {
1375 bool rn_error;
1376 tokval->t_integer = readnum(tline->text, &rn_error);
1377 tokval->t_charptr = tline->text;
1378 if (rn_error)
1379 return tokval->t_type = TOKEN_ERRNUM;
1380 else
1381 return tokval->t_type = TOKEN_NUM;
1384 if (tline->type == TOK_FLOAT) {
1385 return tokval->t_type = TOKEN_FLOAT;
1388 if (tline->type == TOK_STRING) {
1389 char bq, *ep;
1391 bq = tline->text[0];
1392 tokval->t_charptr = tline->text;
1393 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1395 if (ep[0] != bq || ep[1] != '\0')
1396 return tokval->t_type = TOKEN_ERRSTR;
1397 else
1398 return tokval->t_type = TOKEN_STR;
1401 if (tline->type == TOK_OTHER) {
1402 if (!strcmp(tline->text, "<<"))
1403 return tokval->t_type = TOKEN_SHL;
1404 if (!strcmp(tline->text, ">>"))
1405 return tokval->t_type = TOKEN_SHR;
1406 if (!strcmp(tline->text, "//"))
1407 return tokval->t_type = TOKEN_SDIV;
1408 if (!strcmp(tline->text, "%%"))
1409 return tokval->t_type = TOKEN_SMOD;
1410 if (!strcmp(tline->text, "=="))
1411 return tokval->t_type = TOKEN_EQ;
1412 if (!strcmp(tline->text, "<>"))
1413 return tokval->t_type = TOKEN_NE;
1414 if (!strcmp(tline->text, "!="))
1415 return tokval->t_type = TOKEN_NE;
1416 if (!strcmp(tline->text, "<="))
1417 return tokval->t_type = TOKEN_LE;
1418 if (!strcmp(tline->text, ">="))
1419 return tokval->t_type = TOKEN_GE;
1420 if (!strcmp(tline->text, "&&"))
1421 return tokval->t_type = TOKEN_DBL_AND;
1422 if (!strcmp(tline->text, "^^"))
1423 return tokval->t_type = TOKEN_DBL_XOR;
1424 if (!strcmp(tline->text, "||"))
1425 return tokval->t_type = TOKEN_DBL_OR;
1429 * We have no other options: just return the first character of
1430 * the token text.
1432 return tokval->t_type = tline->text[0];
1436 * Compare a string to the name of an existing macro; this is a
1437 * simple wrapper which calls either strcmp or nasm_stricmp
1438 * depending on the value of the `casesense' parameter.
1440 static int mstrcmp(const char *p, const char *q, bool casesense)
1442 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1446 * Compare a string to the name of an existing macro; this is a
1447 * simple wrapper which calls either strcmp or nasm_stricmp
1448 * depending on the value of the `casesense' parameter.
1450 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1452 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1456 * Return the Context structure associated with a %$ token. Return
1457 * NULL, having _already_ reported an error condition, if the
1458 * context stack isn't deep enough for the supplied number of $
1459 * signs.
1461 * If "namep" is non-NULL, set it to the pointer to the macro name
1462 * tail, i.e. the part beyond %$...
1464 static Context *get_ctx(const char *name, const char **namep)
1466 Context *ctx;
1467 int i;
1469 if (namep)
1470 *namep = name;
1472 if (!name || name[0] != '%' || name[1] != '$')
1473 return NULL;
1475 if (!cstk) {
1476 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1477 return NULL;
1480 name += 2;
1481 ctx = cstk;
1482 i = 0;
1483 while (ctx && *name == '$') {
1484 name++;
1485 i++;
1486 ctx = ctx->next;
1488 if (!ctx) {
1489 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1490 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1491 return NULL;
1494 if (namep)
1495 *namep = name;
1497 return ctx;
1501 * Open an include file. This routine must always return a valid
1502 * file pointer if it returns - it's responsible for throwing an
1503 * ERR_FATAL and bombing out completely if not. It should also try
1504 * the include path one by one until it finds the file or reaches
1505 * the end of the path.
1507 * Note: for INC_PROBE the function returns NULL at all times;
1508 * instead look for the
1510 enum incopen_mode {
1511 INC_NEEDED, /* File must exist */
1512 INC_OPTIONAL, /* Missing is OK */
1513 INC_PROBE /* Only an existence probe */
1516 /* This is conducts a full pathname search */
1517 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1518 enum incopen_mode omode, enum file_flags fmode)
1520 FILE *fp;
1521 char *prefix = "";
1522 const IncPath *ip = ipath;
1523 int len = strlen(file);
1524 size_t prefix_len = 0;
1525 StrList *sl;
1526 size_t path_len;
1527 bool found;
1529 while (1) {
1530 path_len = prefix_len + len + 1;
1532 sl = nasm_malloc(path_len + sizeof sl->next);
1533 memcpy(sl->str, prefix, prefix_len);
1534 memcpy(sl->str+prefix_len, file, len+1);
1535 sl->next = NULL;
1537 if (omode == INC_PROBE) {
1538 fp = NULL;
1539 found = nasm_file_exists(sl->str);
1540 } else {
1541 fp = nasm_open_read(sl->str, fmode);
1542 found = (fp != NULL);
1544 if (found) {
1545 *slpath = sl;
1546 return fp;
1549 nasm_free(sl);
1551 if (!ip)
1552 return NULL;
1554 prefix = ip->path;
1555 prefix_len = strlen(prefix);
1556 ip = ip->next;
1561 * Open a file, or test for the presence of one (depending on omode),
1562 * considering the include path.
1564 static FILE *inc_fopen(const char *file,
1565 StrList **dhead,
1566 const char **found_path,
1567 enum incopen_mode omode,
1568 enum file_flags fmode)
1570 StrList *sl;
1571 struct hash_insert hi;
1572 void **hp;
1573 char *path;
1574 FILE *fp = NULL;
1576 hp = hash_find(&FileHash, file, &hi);
1577 if (hp) {
1578 path = *hp;
1579 if (path || omode != INC_NEEDED) {
1580 nasm_add_string_to_strlist(dhead, path ? path : file);
1582 } else {
1583 /* Need to do the actual path search */
1584 size_t file_len;
1586 sl = NULL;
1587 fp = inc_fopen_search(file, &sl, omode, fmode);
1589 file_len = strlen(file);
1591 if (!sl) {
1592 /* Store negative result for this file */
1593 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1594 memcpy(sl->str, file, file_len+1);
1595 sl->next = NULL;
1596 file = sl->str;
1597 path = NULL;
1598 } else {
1599 path = sl->str;
1600 file = strchr(path, '\0') - file_len;
1603 hash_add(&hi, file, path); /* Positive or negative result */
1606 * Add file to dependency path. The in_list() is needed
1607 * in case the file was already added with %depend.
1609 if (path || omode != INC_NEEDED)
1610 nasm_add_to_strlist(dhead, sl);
1613 if (!path) {
1614 if (omode == INC_NEEDED)
1615 nasm_fatal(0, "unable to open include file `%s'", file);
1617 if (found_path)
1618 *found_path = NULL;
1620 return NULL;
1623 if (!fp && omode != INC_PROBE)
1624 fp = nasm_open_read(path, fmode);
1626 if (found_path)
1627 *found_path = path;
1629 return fp;
1633 * Opens an include or input file. Public version, for use by modules
1634 * that get a file:lineno pair and need to look at the file again
1635 * (e.g. the CodeView debug backend). Returns NULL on failure.
1637 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1639 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1643 * Determine if we should warn on defining a single-line macro of
1644 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1645 * return true if _any_ single-line macro of that name is defined.
1646 * Otherwise, will return true if a single-line macro with either
1647 * `nparam' or no parameters is defined.
1649 * If a macro with precisely the right number of parameters is
1650 * defined, or nparam is -1, the address of the definition structure
1651 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1652 * is NULL, no action will be taken regarding its contents, and no
1653 * error will occur.
1655 * Note that this is also called with nparam zero to resolve
1656 * `ifdef'.
1658 * If you already know which context macro belongs to, you can pass
1659 * the context pointer as first parameter; if you won't but name begins
1660 * with %$ the context will be automatically computed. If all_contexts
1661 * is true, macro will be searched in outer contexts as well.
1663 static bool
1664 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1665 bool nocase)
1667 struct hash_table *smtbl;
1668 SMacro *m;
1670 if (ctx) {
1671 smtbl = &ctx->localmac;
1672 } else if (name[0] == '%' && name[1] == '$') {
1673 if (cstk)
1674 ctx = get_ctx(name, &name);
1675 if (!ctx)
1676 return false; /* got to return _something_ */
1677 smtbl = &ctx->localmac;
1678 } else {
1679 smtbl = &smacros;
1681 m = (SMacro *) hash_findix(smtbl, name);
1683 while (m) {
1684 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1685 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1686 if (defn) {
1687 if (nparam == (int) m->nparam || nparam == -1)
1688 *defn = m;
1689 else
1690 *defn = NULL;
1692 return true;
1694 m = m->next;
1697 return false;
1701 * Count and mark off the parameters in a multi-line macro call.
1702 * This is called both from within the multi-line macro expansion
1703 * code, and also to mark off the default parameters when provided
1704 * in a %macro definition line.
1706 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1708 int paramsize, brace;
1710 *nparam = paramsize = 0;
1711 *params = NULL;
1712 while (t) {
1713 /* +1: we need space for the final NULL */
1714 if (*nparam+1 >= paramsize) {
1715 paramsize += PARAM_DELTA;
1716 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1718 skip_white_(t);
1719 brace = 0;
1720 if (tok_is_(t, "{"))
1721 brace++;
1722 (*params)[(*nparam)++] = t;
1723 if (brace) {
1724 while (brace && (t = t->next) != NULL) {
1725 if (tok_is_(t, "{"))
1726 brace++;
1727 else if (tok_is_(t, "}"))
1728 brace--;
1731 if (t) {
1733 * Now we've found the closing brace, look further
1734 * for the comma.
1736 t = t->next;
1737 skip_white_(t);
1738 if (tok_isnt_(t, ",")) {
1739 nasm_error(ERR_NONFATAL,
1740 "braces do not enclose all of macro parameter");
1741 while (tok_isnt_(t, ","))
1742 t = t->next;
1745 } else {
1746 while (tok_isnt_(t, ","))
1747 t = t->next;
1749 if (t) { /* got a comma/brace */
1750 t = t->next; /* eat the comma */
1756 * Determine whether one of the various `if' conditions is true or
1757 * not.
1759 * We must free the tline we get passed.
1761 static bool if_condition(Token * tline, enum preproc_token ct)
1763 enum pp_conditional i = PP_COND(ct);
1764 bool j;
1765 Token *t, *tt, **tptr, *origline;
1766 struct tokenval tokval;
1767 expr *evalresult;
1768 enum pp_token_type needtype;
1769 char *p;
1771 origline = tline;
1773 switch (i) {
1774 case PPC_IFCTX:
1775 j = false; /* have we matched yet? */
1776 while (true) {
1777 skip_white_(tline);
1778 if (!tline)
1779 break;
1780 if (tline->type != TOK_ID) {
1781 nasm_error(ERR_NONFATAL,
1782 "`%s' expects context identifiers", pp_directives[ct]);
1783 free_tlist(origline);
1784 return -1;
1786 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1787 j = true;
1788 tline = tline->next;
1790 break;
1792 case PPC_IFDEF:
1793 j = false; /* have we matched yet? */
1794 while (tline) {
1795 skip_white_(tline);
1796 if (!tline || (tline->type != TOK_ID &&
1797 (tline->type != TOK_PREPROC_ID ||
1798 tline->text[1] != '$'))) {
1799 nasm_error(ERR_NONFATAL,
1800 "`%s' expects macro identifiers", pp_directives[ct]);
1801 goto fail;
1803 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1804 j = true;
1805 tline = tline->next;
1807 break;
1809 case PPC_IFENV:
1810 tline = expand_smacro(tline);
1811 j = false; /* have we matched yet? */
1812 while (tline) {
1813 skip_white_(tline);
1814 if (!tline || (tline->type != TOK_ID &&
1815 tline->type != TOK_STRING &&
1816 (tline->type != TOK_PREPROC_ID ||
1817 tline->text[1] != '!'))) {
1818 nasm_error(ERR_NONFATAL,
1819 "`%s' expects environment variable names",
1820 pp_directives[ct]);
1821 goto fail;
1823 p = tline->text;
1824 if (tline->type == TOK_PREPROC_ID)
1825 p += 2; /* Skip leading %! */
1826 if (*p == '\'' || *p == '\"' || *p == '`')
1827 nasm_unquote_cstr(p, ct);
1828 if (getenv(p))
1829 j = true;
1830 tline = tline->next;
1832 break;
1834 case PPC_IFIDN:
1835 case PPC_IFIDNI:
1836 tline = expand_smacro(tline);
1837 t = tt = tline;
1838 while (tok_isnt_(tt, ","))
1839 tt = tt->next;
1840 if (!tt) {
1841 nasm_error(ERR_NONFATAL,
1842 "`%s' expects two comma-separated arguments",
1843 pp_directives[ct]);
1844 goto fail;
1846 tt = tt->next;
1847 j = true; /* assume equality unless proved not */
1848 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1849 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1850 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1851 pp_directives[ct]);
1852 goto fail;
1854 if (t->type == TOK_WHITESPACE) {
1855 t = t->next;
1856 continue;
1858 if (tt->type == TOK_WHITESPACE) {
1859 tt = tt->next;
1860 continue;
1862 if (tt->type != t->type) {
1863 j = false; /* found mismatching tokens */
1864 break;
1866 /* When comparing strings, need to unquote them first */
1867 if (t->type == TOK_STRING) {
1868 size_t l1 = nasm_unquote(t->text, NULL);
1869 size_t l2 = nasm_unquote(tt->text, NULL);
1871 if (l1 != l2) {
1872 j = false;
1873 break;
1875 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1876 j = false;
1877 break;
1879 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1880 j = false; /* found mismatching tokens */
1881 break;
1884 t = t->next;
1885 tt = tt->next;
1887 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1888 j = false; /* trailing gunk on one end or other */
1889 break;
1891 case PPC_IFMACRO:
1893 bool found = false;
1894 MMacro searching, *mmac;
1896 skip_white_(tline);
1897 tline = expand_id(tline);
1898 if (!tok_type_(tline, TOK_ID)) {
1899 nasm_error(ERR_NONFATAL,
1900 "`%s' expects a macro name", pp_directives[ct]);
1901 goto fail;
1903 searching.name = nasm_strdup(tline->text);
1904 searching.casesense = true;
1905 searching.plus = false;
1906 searching.nolist = false;
1907 searching.in_progress = 0;
1908 searching.max_depth = 0;
1909 searching.rep_nest = NULL;
1910 searching.nparam_min = 0;
1911 searching.nparam_max = INT_MAX;
1912 tline = expand_smacro(tline->next);
1913 skip_white_(tline);
1914 if (!tline) {
1915 } else if (!tok_type_(tline, TOK_NUMBER)) {
1916 nasm_error(ERR_NONFATAL,
1917 "`%s' expects a parameter count or nothing",
1918 pp_directives[ct]);
1919 } else {
1920 searching.nparam_min = searching.nparam_max =
1921 readnum(tline->text, &j);
1922 if (j)
1923 nasm_error(ERR_NONFATAL,
1924 "unable to parse parameter count `%s'",
1925 tline->text);
1927 if (tline && tok_is_(tline->next, "-")) {
1928 tline = tline->next->next;
1929 if (tok_is_(tline, "*"))
1930 searching.nparam_max = INT_MAX;
1931 else if (!tok_type_(tline, TOK_NUMBER))
1932 nasm_error(ERR_NONFATAL,
1933 "`%s' expects a parameter count after `-'",
1934 pp_directives[ct]);
1935 else {
1936 searching.nparam_max = readnum(tline->text, &j);
1937 if (j)
1938 nasm_error(ERR_NONFATAL,
1939 "unable to parse parameter count `%s'",
1940 tline->text);
1941 if (searching.nparam_min > searching.nparam_max) {
1942 nasm_error(ERR_NONFATAL,
1943 "minimum parameter count exceeds maximum");
1944 searching.nparam_max = searching.nparam_min;
1948 if (tline && tok_is_(tline->next, "+")) {
1949 tline = tline->next;
1950 searching.plus = true;
1952 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1953 while (mmac) {
1954 if (!strcmp(mmac->name, searching.name) &&
1955 (mmac->nparam_min <= searching.nparam_max
1956 || searching.plus)
1957 && (searching.nparam_min <= mmac->nparam_max
1958 || mmac->plus)) {
1959 found = true;
1960 break;
1962 mmac = mmac->next;
1964 if (tline && tline->next)
1965 nasm_error(ERR_WARNING|ERR_PASS1,
1966 "trailing garbage after %%ifmacro ignored");
1967 nasm_free(searching.name);
1968 j = found;
1969 break;
1972 case PPC_IFID:
1973 needtype = TOK_ID;
1974 goto iftype;
1975 case PPC_IFNUM:
1976 needtype = TOK_NUMBER;
1977 goto iftype;
1978 case PPC_IFSTR:
1979 needtype = TOK_STRING;
1980 goto iftype;
1982 iftype:
1983 t = tline = expand_smacro(tline);
1985 while (tok_type_(t, TOK_WHITESPACE) ||
1986 (needtype == TOK_NUMBER &&
1987 tok_type_(t, TOK_OTHER) &&
1988 (t->text[0] == '-' || t->text[0] == '+') &&
1989 !t->text[1]))
1990 t = t->next;
1992 j = tok_type_(t, needtype);
1993 break;
1995 case PPC_IFTOKEN:
1996 t = tline = expand_smacro(tline);
1997 while (tok_type_(t, TOK_WHITESPACE))
1998 t = t->next;
2000 j = false;
2001 if (t) {
2002 t = t->next; /* Skip the actual token */
2003 while (tok_type_(t, TOK_WHITESPACE))
2004 t = t->next;
2005 j = !t; /* Should be nothing left */
2007 break;
2009 case PPC_IFEMPTY:
2010 t = tline = expand_smacro(tline);
2011 while (tok_type_(t, TOK_WHITESPACE))
2012 t = t->next;
2014 j = !t; /* Should be empty */
2015 break;
2017 case PPC_IF:
2018 t = tline = expand_smacro(tline);
2019 tptr = &t;
2020 tokval.t_type = TOKEN_INVALID;
2021 evalresult = evaluate(ppscan, tptr, &tokval,
2022 NULL, pass | CRITICAL, NULL);
2023 if (!evalresult)
2024 return -1;
2025 if (tokval.t_type)
2026 nasm_error(ERR_WARNING|ERR_PASS1,
2027 "trailing garbage after expression ignored");
2028 if (!is_simple(evalresult)) {
2029 nasm_error(ERR_NONFATAL,
2030 "non-constant value given to `%s'", pp_directives[ct]);
2031 goto fail;
2033 j = reloc_value(evalresult) != 0;
2034 break;
2036 default:
2037 nasm_error(ERR_FATAL,
2038 "preprocessor directive `%s' not yet implemented",
2039 pp_directives[ct]);
2040 goto fail;
2043 free_tlist(origline);
2044 return j ^ PP_NEGATIVE(ct);
2046 fail:
2047 free_tlist(origline);
2048 return -1;
2052 * Common code for defining an smacro
2054 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2055 int nparam, Token *expansion)
2057 SMacro *smac, **smhead;
2058 struct hash_table *smtbl;
2060 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2061 if (!smac) {
2062 nasm_error(ERR_WARNING|ERR_PASS1,
2063 "single-line macro `%s' defined both with and"
2064 " without parameters", mname);
2066 * Some instances of the old code considered this a failure,
2067 * some others didn't. What is the right thing to do here?
2069 free_tlist(expansion);
2070 return false; /* Failure */
2071 } else {
2073 * We're redefining, so we have to take over an
2074 * existing SMacro structure. This means freeing
2075 * what was already in it.
2077 nasm_free(smac->name);
2078 free_tlist(smac->expansion);
2080 } else {
2081 smtbl = ctx ? &ctx->localmac : &smacros;
2082 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2083 smac = nasm_malloc(sizeof(SMacro));
2084 smac->next = *smhead;
2085 *smhead = smac;
2087 smac->name = nasm_strdup(mname);
2088 smac->casesense = casesense;
2089 smac->nparam = nparam;
2090 smac->expansion = expansion;
2091 smac->in_progress = false;
2092 return true; /* Success */
2096 * Undefine an smacro
2098 static void undef_smacro(Context *ctx, const char *mname)
2100 SMacro **smhead, *s, **sp;
2101 struct hash_table *smtbl;
2103 smtbl = ctx ? &ctx->localmac : &smacros;
2104 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2106 if (smhead) {
2108 * We now have a macro name... go hunt for it.
2110 sp = smhead;
2111 while ((s = *sp) != NULL) {
2112 if (!mstrcmp(s->name, mname, s->casesense)) {
2113 *sp = s->next;
2114 nasm_free(s->name);
2115 free_tlist(s->expansion);
2116 nasm_free(s);
2117 } else {
2118 sp = &s->next;
2125 * Parse a mmacro specification.
2127 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2129 bool err;
2131 tline = tline->next;
2132 skip_white_(tline);
2133 tline = expand_id(tline);
2134 if (!tok_type_(tline, TOK_ID)) {
2135 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2136 return false;
2139 def->prev = NULL;
2140 def->name = nasm_strdup(tline->text);
2141 def->plus = false;
2142 def->nolist = false;
2143 def->in_progress = 0;
2144 def->rep_nest = NULL;
2145 def->nparam_min = 0;
2146 def->nparam_max = 0;
2148 tline = expand_smacro(tline->next);
2149 skip_white_(tline);
2150 if (!tok_type_(tline, TOK_NUMBER)) {
2151 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2152 } else {
2153 def->nparam_min = def->nparam_max =
2154 readnum(tline->text, &err);
2155 if (err)
2156 nasm_error(ERR_NONFATAL,
2157 "unable to parse parameter count `%s'", tline->text);
2159 if (tline && tok_is_(tline->next, "-")) {
2160 tline = tline->next->next;
2161 if (tok_is_(tline, "*")) {
2162 def->nparam_max = INT_MAX;
2163 } else if (!tok_type_(tline, TOK_NUMBER)) {
2164 nasm_error(ERR_NONFATAL,
2165 "`%s' expects a parameter count after `-'", directive);
2166 } else {
2167 def->nparam_max = readnum(tline->text, &err);
2168 if (err) {
2169 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2170 tline->text);
2172 if (def->nparam_min > def->nparam_max) {
2173 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2174 def->nparam_max = def->nparam_min;
2178 if (tline && tok_is_(tline->next, "+")) {
2179 tline = tline->next;
2180 def->plus = true;
2182 if (tline && tok_type_(tline->next, TOK_ID) &&
2183 !nasm_stricmp(tline->next->text, ".nolist")) {
2184 tline = tline->next;
2185 def->nolist = true;
2189 * Handle default parameters.
2191 if (tline && tline->next) {
2192 def->dlist = tline->next;
2193 tline->next = NULL;
2194 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2195 } else {
2196 def->dlist = NULL;
2197 def->defaults = NULL;
2199 def->expansion = NULL;
2201 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2202 !def->plus)
2203 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2204 "too many default macro parameters");
2206 return true;
2211 * Decode a size directive
2213 static int parse_size(const char *str) {
2214 static const char *size_names[] =
2215 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2216 static const int sizes[] =
2217 { 0, 1, 4, 16, 8, 10, 2, 32 };
2219 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2223 * Process a preprocessor %pragma directive. Currently there are none.
2224 * Gets passed the token list starting with the "preproc" token from
2225 * "%pragma preproc".
2227 static void do_pragma_preproc(Token *tline)
2229 /* Skip to the real stuff */
2230 tline = tline->next;
2231 skip_white_(tline);
2232 if (!tline)
2233 return;
2235 (void)tline; /* Nothing else to do at present */
2239 * find and process preprocessor directive in passed line
2240 * Find out if a line contains a preprocessor directive, and deal
2241 * with it if so.
2243 * If a directive _is_ found, it is the responsibility of this routine
2244 * (and not the caller) to free_tlist() the line.
2246 * @param tline a pointer to the current tokeninzed line linked list
2247 * @param output if this directive generated output
2248 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2251 static int do_directive(Token *tline, char **output)
2253 enum preproc_token i;
2254 int j;
2255 bool err;
2256 int nparam;
2257 bool nolist;
2258 bool casesense;
2259 int k, m;
2260 int offset;
2261 char *p, *pp;
2262 const char *found_path;
2263 const char *mname;
2264 Include *inc;
2265 Context *ctx;
2266 Cond *cond;
2267 MMacro *mmac, **mmhead;
2268 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2269 Line *l;
2270 struct tokenval tokval;
2271 expr *evalresult;
2272 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2273 int64_t count;
2274 size_t len;
2275 int severity;
2277 *output = NULL; /* No output generated */
2278 origline = tline;
2280 skip_white_(tline);
2281 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2282 (tline->text[1] == '%' || tline->text[1] == '$'
2283 || tline->text[1] == '!'))
2284 return NO_DIRECTIVE_FOUND;
2286 i = pp_token_hash(tline->text);
2289 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2290 * since they are known to be buggy at moment, we need to fix them
2291 * in future release (2.09-2.10)
2293 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2294 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2295 tline->text);
2296 return NO_DIRECTIVE_FOUND;
2300 * If we're in a non-emitting branch of a condition construct,
2301 * or walking to the end of an already terminated %rep block,
2302 * we should ignore all directives except for condition
2303 * directives.
2305 if (((istk->conds && !emitting(istk->conds->state)) ||
2306 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2307 return NO_DIRECTIVE_FOUND;
2311 * If we're defining a macro or reading a %rep block, we should
2312 * ignore all directives except for %macro/%imacro (which nest),
2313 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2314 * If we're in a %rep block, another %rep nests, so should be let through.
2316 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2317 i != PP_RMACRO && i != PP_IRMACRO &&
2318 i != PP_ENDMACRO && i != PP_ENDM &&
2319 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2320 return NO_DIRECTIVE_FOUND;
2323 if (defining) {
2324 if (i == PP_MACRO || i == PP_IMACRO ||
2325 i == PP_RMACRO || i == PP_IRMACRO) {
2326 nested_mac_count++;
2327 return NO_DIRECTIVE_FOUND;
2328 } else if (nested_mac_count > 0) {
2329 if (i == PP_ENDMACRO) {
2330 nested_mac_count--;
2331 return NO_DIRECTIVE_FOUND;
2334 if (!defining->name) {
2335 if (i == PP_REP) {
2336 nested_rep_count++;
2337 return NO_DIRECTIVE_FOUND;
2338 } else if (nested_rep_count > 0) {
2339 if (i == PP_ENDREP) {
2340 nested_rep_count--;
2341 return NO_DIRECTIVE_FOUND;
2347 switch (i) {
2348 case PP_INVALID:
2349 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2350 tline->text);
2351 return NO_DIRECTIVE_FOUND; /* didn't get it */
2353 case PP_PRAGMA:
2355 * %pragma namespace options...
2357 * The namespace "preproc" is reserved for the preprocessor;
2358 * all other namespaces generate a [pragma] assembly directive.
2360 * Invalid %pragmas are ignored and may have different
2361 * meaning in future versions of NASM.
2363 tline = tline->next;
2364 skip_white_(tline);
2365 tline = expand_smacro(tline);
2366 if (tok_type_(tline, TOK_ID)) {
2367 if (!nasm_stricmp(tline->text, "preproc")) {
2368 /* Preprocessor pragma */
2369 do_pragma_preproc(tline);
2370 } else {
2371 /* Build the assembler directive */
2372 t = new_Token(NULL, TOK_OTHER, "[", 1);
2373 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2374 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2375 tline = t;
2376 for (t = tline; t->next; t = t->next)
2378 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2379 /* true here can be revisited in the future */
2380 *output = detoken(tline, true);
2383 free_tlist(origline);
2384 return DIRECTIVE_FOUND;
2386 case PP_STACKSIZE:
2387 /* Directive to tell NASM what the default stack size is. The
2388 * default is for a 16-bit stack, and this can be overriden with
2389 * %stacksize large.
2391 tline = tline->next;
2392 if (tline && tline->type == TOK_WHITESPACE)
2393 tline = tline->next;
2394 if (!tline || tline->type != TOK_ID) {
2395 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2396 free_tlist(origline);
2397 return DIRECTIVE_FOUND;
2399 if (nasm_stricmp(tline->text, "flat") == 0) {
2400 /* All subsequent ARG directives are for a 32-bit stack */
2401 StackSize = 4;
2402 StackPointer = "ebp";
2403 ArgOffset = 8;
2404 LocalOffset = 0;
2405 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2406 /* All subsequent ARG directives are for a 64-bit stack */
2407 StackSize = 8;
2408 StackPointer = "rbp";
2409 ArgOffset = 16;
2410 LocalOffset = 0;
2411 } else if (nasm_stricmp(tline->text, "large") == 0) {
2412 /* All subsequent ARG directives are for a 16-bit stack,
2413 * far function call.
2415 StackSize = 2;
2416 StackPointer = "bp";
2417 ArgOffset = 4;
2418 LocalOffset = 0;
2419 } else if (nasm_stricmp(tline->text, "small") == 0) {
2420 /* All subsequent ARG directives are for a 16-bit stack,
2421 * far function call. We don't support near functions.
2423 StackSize = 2;
2424 StackPointer = "bp";
2425 ArgOffset = 6;
2426 LocalOffset = 0;
2427 } else {
2428 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2429 free_tlist(origline);
2430 return DIRECTIVE_FOUND;
2432 free_tlist(origline);
2433 return DIRECTIVE_FOUND;
2435 case PP_ARG:
2436 /* TASM like ARG directive to define arguments to functions, in
2437 * the following form:
2439 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2441 offset = ArgOffset;
2442 do {
2443 char *arg, directive[256];
2444 int size = StackSize;
2446 /* Find the argument name */
2447 tline = tline->next;
2448 if (tline && tline->type == TOK_WHITESPACE)
2449 tline = tline->next;
2450 if (!tline || tline->type != TOK_ID) {
2451 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2452 free_tlist(origline);
2453 return DIRECTIVE_FOUND;
2455 arg = tline->text;
2457 /* Find the argument size type */
2458 tline = tline->next;
2459 if (!tline || tline->type != TOK_OTHER
2460 || tline->text[0] != ':') {
2461 nasm_error(ERR_NONFATAL,
2462 "Syntax error processing `%%arg' directive");
2463 free_tlist(origline);
2464 return DIRECTIVE_FOUND;
2466 tline = tline->next;
2467 if (!tline || tline->type != TOK_ID) {
2468 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2469 free_tlist(origline);
2470 return DIRECTIVE_FOUND;
2473 /* Allow macro expansion of type parameter */
2474 tt = tokenize(tline->text);
2475 tt = expand_smacro(tt);
2476 size = parse_size(tt->text);
2477 if (!size) {
2478 nasm_error(ERR_NONFATAL,
2479 "Invalid size type for `%%arg' missing directive");
2480 free_tlist(tt);
2481 free_tlist(origline);
2482 return DIRECTIVE_FOUND;
2484 free_tlist(tt);
2486 /* Round up to even stack slots */
2487 size = ALIGN(size, StackSize);
2489 /* Now define the macro for the argument */
2490 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2491 arg, StackPointer, offset);
2492 do_directive(tokenize(directive), output);
2493 offset += size;
2495 /* Move to the next argument in the list */
2496 tline = tline->next;
2497 if (tline && tline->type == TOK_WHITESPACE)
2498 tline = tline->next;
2499 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2500 ArgOffset = offset;
2501 free_tlist(origline);
2502 return DIRECTIVE_FOUND;
2504 case PP_LOCAL:
2505 /* TASM like LOCAL directive to define local variables for a
2506 * function, in the following form:
2508 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2510 * The '= LocalSize' at the end is ignored by NASM, but is
2511 * required by TASM to define the local parameter size (and used
2512 * by the TASM macro package).
2514 offset = LocalOffset;
2515 do {
2516 char *local, directive[256];
2517 int size = StackSize;
2519 /* Find the argument name */
2520 tline = tline->next;
2521 if (tline && tline->type == TOK_WHITESPACE)
2522 tline = tline->next;
2523 if (!tline || tline->type != TOK_ID) {
2524 nasm_error(ERR_NONFATAL,
2525 "`%%local' missing argument parameter");
2526 free_tlist(origline);
2527 return DIRECTIVE_FOUND;
2529 local = tline->text;
2531 /* Find the argument size type */
2532 tline = tline->next;
2533 if (!tline || tline->type != TOK_OTHER
2534 || tline->text[0] != ':') {
2535 nasm_error(ERR_NONFATAL,
2536 "Syntax error processing `%%local' directive");
2537 free_tlist(origline);
2538 return DIRECTIVE_FOUND;
2540 tline = tline->next;
2541 if (!tline || tline->type != TOK_ID) {
2542 nasm_error(ERR_NONFATAL,
2543 "`%%local' missing size type parameter");
2544 free_tlist(origline);
2545 return DIRECTIVE_FOUND;
2548 /* Allow macro expansion of type parameter */
2549 tt = tokenize(tline->text);
2550 tt = expand_smacro(tt);
2551 size = parse_size(tt->text);
2552 if (!size) {
2553 nasm_error(ERR_NONFATAL,
2554 "Invalid size type for `%%local' missing directive");
2555 free_tlist(tt);
2556 free_tlist(origline);
2557 return DIRECTIVE_FOUND;
2559 free_tlist(tt);
2561 /* Round up to even stack slots */
2562 size = ALIGN(size, StackSize);
2564 offset += size; /* Negative offset, increment before */
2566 /* Now define the macro for the argument */
2567 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2568 local, StackPointer, offset);
2569 do_directive(tokenize(directive), output);
2571 /* Now define the assign to setup the enter_c macro correctly */
2572 snprintf(directive, sizeof(directive),
2573 "%%assign %%$localsize %%$localsize+%d", size);
2574 do_directive(tokenize(directive), output);
2576 /* Move to the next argument in the list */
2577 tline = tline->next;
2578 if (tline && tline->type == TOK_WHITESPACE)
2579 tline = tline->next;
2580 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2581 LocalOffset = offset;
2582 free_tlist(origline);
2583 return DIRECTIVE_FOUND;
2585 case PP_CLEAR:
2586 if (tline->next)
2587 nasm_error(ERR_WARNING|ERR_PASS1,
2588 "trailing garbage after `%%clear' ignored");
2589 free_macros();
2590 init_macros();
2591 free_tlist(origline);
2592 return DIRECTIVE_FOUND;
2594 case PP_DEPEND:
2595 t = tline->next = expand_smacro(tline->next);
2596 skip_white_(t);
2597 if (!t || (t->type != TOK_STRING &&
2598 t->type != TOK_INTERNAL_STRING)) {
2599 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2600 free_tlist(origline);
2601 return DIRECTIVE_FOUND; /* but we did _something_ */
2603 if (t->next)
2604 nasm_error(ERR_WARNING|ERR_PASS1,
2605 "trailing garbage after `%%depend' ignored");
2606 p = t->text;
2607 if (t->type != TOK_INTERNAL_STRING)
2608 nasm_unquote_cstr(p, i);
2609 nasm_add_string_to_strlist(dephead, p);
2610 free_tlist(origline);
2611 return DIRECTIVE_FOUND;
2613 case PP_INCLUDE:
2614 t = tline->next = expand_smacro(tline->next);
2615 skip_white_(t);
2617 if (!t || (t->type != TOK_STRING &&
2618 t->type != TOK_INTERNAL_STRING)) {
2619 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2620 free_tlist(origline);
2621 return DIRECTIVE_FOUND; /* but we did _something_ */
2623 if (t->next)
2624 nasm_error(ERR_WARNING|ERR_PASS1,
2625 "trailing garbage after `%%include' ignored");
2626 p = t->text;
2627 if (t->type != TOK_INTERNAL_STRING)
2628 nasm_unquote_cstr(p, i);
2629 inc = nasm_malloc(sizeof(Include));
2630 inc->next = istk;
2631 inc->conds = NULL;
2632 found_path = NULL;
2633 inc->fp = inc_fopen(p, dephead, &found_path,
2634 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2635 if (!inc->fp) {
2636 /* -MG given but file not found */
2637 nasm_free(inc);
2638 } else {
2639 inc->fname = src_set_fname(found_path ? found_path : p);
2640 inc->lineno = src_set_linnum(0);
2641 inc->lineinc = 1;
2642 inc->expansion = NULL;
2643 inc->mstk = NULL;
2644 istk = inc;
2645 lfmt->uplevel(LIST_INCLUDE);
2647 free_tlist(origline);
2648 return DIRECTIVE_FOUND;
2650 case PP_USE:
2652 static macros_t *use_pkg;
2653 const char *pkg_macro = NULL;
2655 tline = tline->next;
2656 skip_white_(tline);
2657 tline = expand_id(tline);
2659 if (!tline || (tline->type != TOK_STRING &&
2660 tline->type != TOK_INTERNAL_STRING &&
2661 tline->type != TOK_ID)) {
2662 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2663 free_tlist(origline);
2664 return DIRECTIVE_FOUND; /* but we did _something_ */
2666 if (tline->next)
2667 nasm_error(ERR_WARNING|ERR_PASS1,
2668 "trailing garbage after `%%use' ignored");
2669 if (tline->type == TOK_STRING)
2670 nasm_unquote_cstr(tline->text, i);
2671 use_pkg = nasm_stdmac_find_package(tline->text);
2672 if (!use_pkg)
2673 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2674 else
2675 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2676 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2677 /* Not already included, go ahead and include it */
2678 stdmacpos = use_pkg;
2680 free_tlist(origline);
2681 return DIRECTIVE_FOUND;
2683 case PP_PUSH:
2684 case PP_REPL:
2685 case PP_POP:
2686 tline = tline->next;
2687 skip_white_(tline);
2688 tline = expand_id(tline);
2689 if (tline) {
2690 if (!tok_type_(tline, TOK_ID)) {
2691 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2692 pp_directives[i]);
2693 free_tlist(origline);
2694 return DIRECTIVE_FOUND; /* but we did _something_ */
2696 if (tline->next)
2697 nasm_error(ERR_WARNING|ERR_PASS1,
2698 "trailing garbage after `%s' ignored",
2699 pp_directives[i]);
2700 p = nasm_strdup(tline->text);
2701 } else {
2702 p = NULL; /* Anonymous */
2705 if (i == PP_PUSH) {
2706 ctx = nasm_malloc(sizeof(Context));
2707 ctx->next = cstk;
2708 hash_init(&ctx->localmac, HASH_SMALL);
2709 ctx->name = p;
2710 ctx->number = unique++;
2711 cstk = ctx;
2712 } else {
2713 /* %pop or %repl */
2714 if (!cstk) {
2715 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2716 pp_directives[i]);
2717 } else if (i == PP_POP) {
2718 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2719 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2720 "expected %s",
2721 cstk->name ? cstk->name : "anonymous", p);
2722 else
2723 ctx_pop();
2724 } else {
2725 /* i == PP_REPL */
2726 nasm_free(cstk->name);
2727 cstk->name = p;
2728 p = NULL;
2730 nasm_free(p);
2732 free_tlist(origline);
2733 return DIRECTIVE_FOUND;
2734 case PP_FATAL:
2735 severity = ERR_FATAL;
2736 goto issue_error;
2737 case PP_ERROR:
2738 severity = ERR_NONFATAL;
2739 goto issue_error;
2740 case PP_WARNING:
2741 severity = ERR_WARNING|ERR_WARN_USER;
2742 goto issue_error;
2744 issue_error:
2746 /* Only error out if this is the final pass */
2747 if (pass != 2 && i != PP_FATAL)
2748 return DIRECTIVE_FOUND;
2750 tline->next = expand_smacro(tline->next);
2751 tline = tline->next;
2752 skip_white_(tline);
2753 t = tline ? tline->next : NULL;
2754 skip_white_(t);
2755 if (tok_type_(tline, TOK_STRING) && !t) {
2756 /* The line contains only a quoted string */
2757 p = tline->text;
2758 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2759 nasm_error(severity, "%s", p);
2760 } else {
2761 /* Not a quoted string, or more than a quoted string */
2762 p = detoken(tline, false);
2763 nasm_error(severity, "%s", p);
2764 nasm_free(p);
2766 free_tlist(origline);
2767 return DIRECTIVE_FOUND;
2770 CASE_PP_IF:
2771 if (istk->conds && !emitting(istk->conds->state))
2772 j = COND_NEVER;
2773 else {
2774 j = if_condition(tline->next, i);
2775 tline->next = NULL; /* it got freed */
2776 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2778 cond = nasm_malloc(sizeof(Cond));
2779 cond->next = istk->conds;
2780 cond->state = j;
2781 istk->conds = cond;
2782 if(istk->mstk)
2783 istk->mstk->condcnt ++;
2784 free_tlist(origline);
2785 return DIRECTIVE_FOUND;
2787 CASE_PP_ELIF:
2788 if (!istk->conds)
2789 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2790 switch(istk->conds->state) {
2791 case COND_IF_TRUE:
2792 istk->conds->state = COND_DONE;
2793 break;
2795 case COND_DONE:
2796 case COND_NEVER:
2797 break;
2799 case COND_ELSE_TRUE:
2800 case COND_ELSE_FALSE:
2801 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2802 "`%%elif' after `%%else' ignored");
2803 istk->conds->state = COND_NEVER;
2804 break;
2806 case COND_IF_FALSE:
2808 * IMPORTANT: In the case of %if, we will already have
2809 * called expand_mmac_params(); however, if we're
2810 * processing an %elif we must have been in a
2811 * non-emitting mode, which would have inhibited
2812 * the normal invocation of expand_mmac_params().
2813 * Therefore, we have to do it explicitly here.
2815 j = if_condition(expand_mmac_params(tline->next), i);
2816 tline->next = NULL; /* it got freed */
2817 istk->conds->state =
2818 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2819 break;
2821 free_tlist(origline);
2822 return DIRECTIVE_FOUND;
2824 case PP_ELSE:
2825 if (tline->next)
2826 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2827 "trailing garbage after `%%else' ignored");
2828 if (!istk->conds)
2829 nasm_fatal(0, "`%%else: no matching `%%if'");
2830 switch(istk->conds->state) {
2831 case COND_IF_TRUE:
2832 case COND_DONE:
2833 istk->conds->state = COND_ELSE_FALSE;
2834 break;
2836 case COND_NEVER:
2837 break;
2839 case COND_IF_FALSE:
2840 istk->conds->state = COND_ELSE_TRUE;
2841 break;
2843 case COND_ELSE_TRUE:
2844 case COND_ELSE_FALSE:
2845 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2846 "`%%else' after `%%else' ignored.");
2847 istk->conds->state = COND_NEVER;
2848 break;
2850 free_tlist(origline);
2851 return DIRECTIVE_FOUND;
2853 case PP_ENDIF:
2854 if (tline->next)
2855 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2856 "trailing garbage after `%%endif' ignored");
2857 if (!istk->conds)
2858 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2859 cond = istk->conds;
2860 istk->conds = cond->next;
2861 nasm_free(cond);
2862 if(istk->mstk)
2863 istk->mstk->condcnt --;
2864 free_tlist(origline);
2865 return DIRECTIVE_FOUND;
2867 case PP_RMACRO:
2868 case PP_IRMACRO:
2869 case PP_MACRO:
2870 case PP_IMACRO:
2871 if (defining) {
2872 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2873 pp_directives[i]);
2874 return DIRECTIVE_FOUND;
2876 defining = nasm_zalloc(sizeof(MMacro));
2877 defining->max_depth =
2878 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2879 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2880 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2881 nasm_free(defining);
2882 defining = NULL;
2883 return DIRECTIVE_FOUND;
2886 src_get(&defining->xline, &defining->fname);
2888 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2889 while (mmac) {
2890 if (!strcmp(mmac->name, defining->name) &&
2891 (mmac->nparam_min <= defining->nparam_max
2892 || defining->plus)
2893 && (defining->nparam_min <= mmac->nparam_max
2894 || mmac->plus)) {
2895 nasm_error(ERR_WARNING|ERR_PASS1,
2896 "redefining multi-line macro `%s'", defining->name);
2897 return DIRECTIVE_FOUND;
2899 mmac = mmac->next;
2901 free_tlist(origline);
2902 return DIRECTIVE_FOUND;
2904 case PP_ENDM:
2905 case PP_ENDMACRO:
2906 if (! (defining && defining->name)) {
2907 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2908 return DIRECTIVE_FOUND;
2910 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2911 defining->next = *mmhead;
2912 *mmhead = defining;
2913 defining = NULL;
2914 free_tlist(origline);
2915 return DIRECTIVE_FOUND;
2917 case PP_EXITMACRO:
2919 * We must search along istk->expansion until we hit a
2920 * macro-end marker for a macro with a name. Then we
2921 * bypass all lines between exitmacro and endmacro.
2923 list_for_each(l, istk->expansion)
2924 if (l->finishes && l->finishes->name)
2925 break;
2927 if (l) {
2929 * Remove all conditional entries relative to this
2930 * macro invocation. (safe to do in this context)
2932 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2933 cond = istk->conds;
2934 istk->conds = cond->next;
2935 nasm_free(cond);
2937 istk->expansion = l;
2938 } else {
2939 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2941 free_tlist(origline);
2942 return DIRECTIVE_FOUND;
2944 case PP_UNMACRO:
2945 case PP_UNIMACRO:
2947 MMacro **mmac_p;
2948 MMacro spec;
2950 spec.casesense = (i == PP_UNMACRO);
2951 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2952 return DIRECTIVE_FOUND;
2954 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2955 while (mmac_p && *mmac_p) {
2956 mmac = *mmac_p;
2957 if (mmac->casesense == spec.casesense &&
2958 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2959 mmac->nparam_min == spec.nparam_min &&
2960 mmac->nparam_max == spec.nparam_max &&
2961 mmac->plus == spec.plus) {
2962 *mmac_p = mmac->next;
2963 free_mmacro(mmac);
2964 } else {
2965 mmac_p = &mmac->next;
2968 free_tlist(origline);
2969 free_tlist(spec.dlist);
2970 return DIRECTIVE_FOUND;
2973 case PP_ROTATE:
2974 if (tline->next && tline->next->type == TOK_WHITESPACE)
2975 tline = tline->next;
2976 if (!tline->next) {
2977 free_tlist(origline);
2978 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2979 return DIRECTIVE_FOUND;
2981 t = expand_smacro(tline->next);
2982 tline->next = NULL;
2983 free_tlist(origline);
2984 tline = t;
2985 tptr = &t;
2986 tokval.t_type = TOKEN_INVALID;
2987 evalresult =
2988 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2989 free_tlist(tline);
2990 if (!evalresult)
2991 return DIRECTIVE_FOUND;
2992 if (tokval.t_type)
2993 nasm_error(ERR_WARNING|ERR_PASS1,
2994 "trailing garbage after expression ignored");
2995 if (!is_simple(evalresult)) {
2996 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2997 return DIRECTIVE_FOUND;
2999 mmac = istk->mstk;
3000 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
3001 mmac = mmac->next_active;
3002 if (!mmac) {
3003 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
3004 } else if (mmac->nparam == 0) {
3005 nasm_error(ERR_NONFATAL,
3006 "`%%rotate' invoked within macro without parameters");
3007 } else {
3008 int rotate = mmac->rotate + reloc_value(evalresult);
3010 rotate %= (int)mmac->nparam;
3011 if (rotate < 0)
3012 rotate += mmac->nparam;
3014 mmac->rotate = rotate;
3016 return DIRECTIVE_FOUND;
3018 case PP_REP:
3019 nolist = false;
3020 do {
3021 tline = tline->next;
3022 } while (tok_type_(tline, TOK_WHITESPACE));
3024 if (tok_type_(tline, TOK_ID) &&
3025 nasm_stricmp(tline->text, ".nolist") == 0) {
3026 nolist = true;
3027 do {
3028 tline = tline->next;
3029 } while (tok_type_(tline, TOK_WHITESPACE));
3032 if (tline) {
3033 t = expand_smacro(tline);
3034 tptr = &t;
3035 tokval.t_type = TOKEN_INVALID;
3036 evalresult =
3037 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3038 if (!evalresult) {
3039 free_tlist(origline);
3040 return DIRECTIVE_FOUND;
3042 if (tokval.t_type)
3043 nasm_error(ERR_WARNING|ERR_PASS1,
3044 "trailing garbage after expression ignored");
3045 if (!is_simple(evalresult)) {
3046 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3047 return DIRECTIVE_FOUND;
3049 count = reloc_value(evalresult);
3050 if (count >= REP_LIMIT) {
3051 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3052 count = 0;
3053 } else
3054 count++;
3055 } else {
3056 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3057 count = 0;
3059 free_tlist(origline);
3061 tmp_defining = defining;
3062 defining = nasm_malloc(sizeof(MMacro));
3063 defining->prev = NULL;
3064 defining->name = NULL; /* flags this macro as a %rep block */
3065 defining->casesense = false;
3066 defining->plus = false;
3067 defining->nolist = nolist;
3068 defining->in_progress = count;
3069 defining->max_depth = 0;
3070 defining->nparam_min = defining->nparam_max = 0;
3071 defining->defaults = NULL;
3072 defining->dlist = NULL;
3073 defining->expansion = NULL;
3074 defining->next_active = istk->mstk;
3075 defining->rep_nest = tmp_defining;
3076 return DIRECTIVE_FOUND;
3078 case PP_ENDREP:
3079 if (!defining || defining->name) {
3080 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3081 return DIRECTIVE_FOUND;
3085 * Now we have a "macro" defined - although it has no name
3086 * and we won't be entering it in the hash tables - we must
3087 * push a macro-end marker for it on to istk->expansion.
3088 * After that, it will take care of propagating itself (a
3089 * macro-end marker line for a macro which is really a %rep
3090 * block will cause the macro to be re-expanded, complete
3091 * with another macro-end marker to ensure the process
3092 * continues) until the whole expansion is forcibly removed
3093 * from istk->expansion by a %exitrep.
3095 l = nasm_malloc(sizeof(Line));
3096 l->next = istk->expansion;
3097 l->finishes = defining;
3098 l->first = NULL;
3099 istk->expansion = l;
3101 istk->mstk = defining;
3103 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3104 tmp_defining = defining;
3105 defining = defining->rep_nest;
3106 free_tlist(origline);
3107 return DIRECTIVE_FOUND;
3109 case PP_EXITREP:
3111 * We must search along istk->expansion until we hit a
3112 * macro-end marker for a macro with no name. Then we set
3113 * its `in_progress' flag to 0.
3115 list_for_each(l, istk->expansion)
3116 if (l->finishes && !l->finishes->name)
3117 break;
3119 if (l)
3120 l->finishes->in_progress = 1;
3121 else
3122 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3123 free_tlist(origline);
3124 return DIRECTIVE_FOUND;
3126 case PP_XDEFINE:
3127 case PP_IXDEFINE:
3128 case PP_DEFINE:
3129 case PP_IDEFINE:
3130 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3132 tline = tline->next;
3133 skip_white_(tline);
3134 tline = expand_id(tline);
3135 if (!tline || (tline->type != TOK_ID &&
3136 (tline->type != TOK_PREPROC_ID ||
3137 tline->text[1] != '$'))) {
3138 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3139 pp_directives[i]);
3140 free_tlist(origline);
3141 return DIRECTIVE_FOUND;
3144 ctx = get_ctx(tline->text, &mname);
3145 last = tline;
3146 param_start = tline = tline->next;
3147 nparam = 0;
3149 /* Expand the macro definition now for %xdefine and %ixdefine */
3150 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3151 tline = expand_smacro(tline);
3153 if (tok_is_(tline, "(")) {
3155 * This macro has parameters.
3158 tline = tline->next;
3159 while (1) {
3160 skip_white_(tline);
3161 if (!tline) {
3162 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3163 free_tlist(origline);
3164 return DIRECTIVE_FOUND;
3166 if (tline->type != TOK_ID) {
3167 nasm_error(ERR_NONFATAL,
3168 "`%s': parameter identifier expected",
3169 tline->text);
3170 free_tlist(origline);
3171 return DIRECTIVE_FOUND;
3173 tline->type = TOK_SMAC_PARAM + nparam++;
3174 tline = tline->next;
3175 skip_white_(tline);
3176 if (tok_is_(tline, ",")) {
3177 tline = tline->next;
3178 } else {
3179 if (!tok_is_(tline, ")")) {
3180 nasm_error(ERR_NONFATAL,
3181 "`)' expected to terminate macro template");
3182 free_tlist(origline);
3183 return DIRECTIVE_FOUND;
3185 break;
3188 last = tline;
3189 tline = tline->next;
3191 if (tok_type_(tline, TOK_WHITESPACE))
3192 last = tline, tline = tline->next;
3193 macro_start = NULL;
3194 last->next = NULL;
3195 t = tline;
3196 while (t) {
3197 if (t->type == TOK_ID) {
3198 list_for_each(tt, param_start)
3199 if (tt->type >= TOK_SMAC_PARAM &&
3200 !strcmp(tt->text, t->text))
3201 t->type = tt->type;
3203 tt = t->next;
3204 t->next = macro_start;
3205 macro_start = t;
3206 t = tt;
3209 * Good. We now have a macro name, a parameter count, and a
3210 * token list (in reverse order) for an expansion. We ought
3211 * to be OK just to create an SMacro, store it, and let
3212 * free_tlist have the rest of the line (which we have
3213 * carefully re-terminated after chopping off the expansion
3214 * from the end).
3216 define_smacro(ctx, mname, casesense, nparam, macro_start);
3217 free_tlist(origline);
3218 return DIRECTIVE_FOUND;
3220 case PP_UNDEF:
3221 tline = tline->next;
3222 skip_white_(tline);
3223 tline = expand_id(tline);
3224 if (!tline || (tline->type != TOK_ID &&
3225 (tline->type != TOK_PREPROC_ID ||
3226 tline->text[1] != '$'))) {
3227 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3228 free_tlist(origline);
3229 return DIRECTIVE_FOUND;
3231 if (tline->next) {
3232 nasm_error(ERR_WARNING|ERR_PASS1,
3233 "trailing garbage after macro name ignored");
3236 /* Find the context that symbol belongs to */
3237 ctx = get_ctx(tline->text, &mname);
3238 undef_smacro(ctx, mname);
3239 free_tlist(origline);
3240 return DIRECTIVE_FOUND;
3242 case PP_DEFSTR:
3243 case PP_IDEFSTR:
3244 casesense = (i == PP_DEFSTR);
3246 tline = tline->next;
3247 skip_white_(tline);
3248 tline = expand_id(tline);
3249 if (!tline || (tline->type != TOK_ID &&
3250 (tline->type != TOK_PREPROC_ID ||
3251 tline->text[1] != '$'))) {
3252 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3253 pp_directives[i]);
3254 free_tlist(origline);
3255 return DIRECTIVE_FOUND;
3258 ctx = get_ctx(tline->text, &mname);
3259 last = tline;
3260 tline = expand_smacro(tline->next);
3261 last->next = NULL;
3263 while (tok_type_(tline, TOK_WHITESPACE))
3264 tline = delete_Token(tline);
3266 p = detoken(tline, false);
3267 macro_start = nasm_malloc(sizeof(*macro_start));
3268 macro_start->next = NULL;
3269 macro_start->text = nasm_quote(p, strlen(p));
3270 macro_start->type = TOK_STRING;
3271 macro_start->a.mac = NULL;
3272 nasm_free(p);
3275 * We now have a macro name, an implicit parameter count of
3276 * zero, and a string token to use as an expansion. Create
3277 * and store an SMacro.
3279 define_smacro(ctx, mname, casesense, 0, macro_start);
3280 free_tlist(origline);
3281 return DIRECTIVE_FOUND;
3283 case PP_DEFTOK:
3284 case PP_IDEFTOK:
3285 casesense = (i == PP_DEFTOK);
3287 tline = tline->next;
3288 skip_white_(tline);
3289 tline = expand_id(tline);
3290 if (!tline || (tline->type != TOK_ID &&
3291 (tline->type != TOK_PREPROC_ID ||
3292 tline->text[1] != '$'))) {
3293 nasm_error(ERR_NONFATAL,
3294 "`%s' expects a macro identifier as first parameter",
3295 pp_directives[i]);
3296 free_tlist(origline);
3297 return DIRECTIVE_FOUND;
3299 ctx = get_ctx(tline->text, &mname);
3300 last = tline;
3301 tline = expand_smacro(tline->next);
3302 last->next = NULL;
3304 t = tline;
3305 while (tok_type_(t, TOK_WHITESPACE))
3306 t = t->next;
3307 /* t should now point to the string */
3308 if (!tok_type_(t, TOK_STRING)) {
3309 nasm_error(ERR_NONFATAL,
3310 "`%s` requires string as second parameter",
3311 pp_directives[i]);
3312 free_tlist(tline);
3313 free_tlist(origline);
3314 return DIRECTIVE_FOUND;
3318 * Convert the string to a token stream. Note that smacros
3319 * are stored with the token stream reversed, so we have to
3320 * reverse the output of tokenize().
3322 nasm_unquote_cstr(t->text, i);
3323 macro_start = reverse_tokens(tokenize(t->text));
3326 * We now have a macro name, an implicit parameter count of
3327 * zero, and a numeric token to use as an expansion. Create
3328 * and store an SMacro.
3330 define_smacro(ctx, mname, casesense, 0, macro_start);
3331 free_tlist(tline);
3332 free_tlist(origline);
3333 return DIRECTIVE_FOUND;
3335 case PP_PATHSEARCH:
3337 const char *found_path;
3339 casesense = true;
3341 tline = tline->next;
3342 skip_white_(tline);
3343 tline = expand_id(tline);
3344 if (!tline || (tline->type != TOK_ID &&
3345 (tline->type != TOK_PREPROC_ID ||
3346 tline->text[1] != '$'))) {
3347 nasm_error(ERR_NONFATAL,
3348 "`%%pathsearch' expects a macro identifier as first parameter");
3349 free_tlist(origline);
3350 return DIRECTIVE_FOUND;
3352 ctx = get_ctx(tline->text, &mname);
3353 last = tline;
3354 tline = expand_smacro(tline->next);
3355 last->next = NULL;
3357 t = tline;
3358 while (tok_type_(t, TOK_WHITESPACE))
3359 t = t->next;
3361 if (!t || (t->type != TOK_STRING &&
3362 t->type != TOK_INTERNAL_STRING)) {
3363 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3364 free_tlist(tline);
3365 free_tlist(origline);
3366 return DIRECTIVE_FOUND; /* but we did _something_ */
3368 if (t->next)
3369 nasm_error(ERR_WARNING|ERR_PASS1,
3370 "trailing garbage after `%%pathsearch' ignored");
3371 p = t->text;
3372 if (t->type != TOK_INTERNAL_STRING)
3373 nasm_unquote(p, NULL);
3375 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3376 if (!found_path)
3377 found_path = p;
3378 macro_start = nasm_malloc(sizeof(*macro_start));
3379 macro_start->next = NULL;
3380 macro_start->text = nasm_quote(found_path, strlen(found_path));
3381 macro_start->type = TOK_STRING;
3382 macro_start->a.mac = NULL;
3385 * We now have a macro name, an implicit parameter count of
3386 * zero, and a string token to use as an expansion. Create
3387 * and store an SMacro.
3389 define_smacro(ctx, mname, casesense, 0, macro_start);
3390 free_tlist(tline);
3391 free_tlist(origline);
3392 return DIRECTIVE_FOUND;
3395 case PP_STRLEN:
3396 casesense = true;
3398 tline = tline->next;
3399 skip_white_(tline);
3400 tline = expand_id(tline);
3401 if (!tline || (tline->type != TOK_ID &&
3402 (tline->type != TOK_PREPROC_ID ||
3403 tline->text[1] != '$'))) {
3404 nasm_error(ERR_NONFATAL,
3405 "`%%strlen' expects a macro identifier as first parameter");
3406 free_tlist(origline);
3407 return DIRECTIVE_FOUND;
3409 ctx = get_ctx(tline->text, &mname);
3410 last = tline;
3411 tline = expand_smacro(tline->next);
3412 last->next = NULL;
3414 t = tline;
3415 while (tok_type_(t, TOK_WHITESPACE))
3416 t = t->next;
3417 /* t should now point to the string */
3418 if (!tok_type_(t, TOK_STRING)) {
3419 nasm_error(ERR_NONFATAL,
3420 "`%%strlen` requires string as second parameter");
3421 free_tlist(tline);
3422 free_tlist(origline);
3423 return DIRECTIVE_FOUND;
3426 macro_start = nasm_malloc(sizeof(*macro_start));
3427 macro_start->next = NULL;
3428 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3429 macro_start->a.mac = NULL;
3432 * We now have a macro name, an implicit parameter count of
3433 * zero, and a numeric token to use as an expansion. Create
3434 * and store an SMacro.
3436 define_smacro(ctx, mname, casesense, 0, macro_start);
3437 free_tlist(tline);
3438 free_tlist(origline);
3439 return DIRECTIVE_FOUND;
3441 case PP_STRCAT:
3442 casesense = true;
3444 tline = tline->next;
3445 skip_white_(tline);
3446 tline = expand_id(tline);
3447 if (!tline || (tline->type != TOK_ID &&
3448 (tline->type != TOK_PREPROC_ID ||
3449 tline->text[1] != '$'))) {
3450 nasm_error(ERR_NONFATAL,
3451 "`%%strcat' expects a macro identifier as first parameter");
3452 free_tlist(origline);
3453 return DIRECTIVE_FOUND;
3455 ctx = get_ctx(tline->text, &mname);
3456 last = tline;
3457 tline = expand_smacro(tline->next);
3458 last->next = NULL;
3460 len = 0;
3461 list_for_each(t, tline) {
3462 switch (t->type) {
3463 case TOK_WHITESPACE:
3464 break;
3465 case TOK_STRING:
3466 len += t->a.len = nasm_unquote(t->text, NULL);
3467 break;
3468 case TOK_OTHER:
3469 if (!strcmp(t->text, ",")) /* permit comma separators */
3470 break;
3471 /* else fall through */
3472 default:
3473 nasm_error(ERR_NONFATAL,
3474 "non-string passed to `%%strcat' (%d)", t->type);
3475 free_tlist(tline);
3476 free_tlist(origline);
3477 return DIRECTIVE_FOUND;
3481 p = pp = nasm_malloc(len);
3482 list_for_each(t, tline) {
3483 if (t->type == TOK_STRING) {
3484 memcpy(p, t->text, t->a.len);
3485 p += t->a.len;
3490 * We now have a macro name, an implicit parameter count of
3491 * zero, and a numeric token to use as an expansion. Create
3492 * and store an SMacro.
3494 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3495 macro_start->text = nasm_quote(pp, len);
3496 nasm_free(pp);
3497 define_smacro(ctx, mname, casesense, 0, macro_start);
3498 free_tlist(tline);
3499 free_tlist(origline);
3500 return DIRECTIVE_FOUND;
3502 case PP_SUBSTR:
3504 int64_t start, count;
3505 size_t len;
3507 casesense = true;
3509 tline = tline->next;
3510 skip_white_(tline);
3511 tline = expand_id(tline);
3512 if (!tline || (tline->type != TOK_ID &&
3513 (tline->type != TOK_PREPROC_ID ||
3514 tline->text[1] != '$'))) {
3515 nasm_error(ERR_NONFATAL,
3516 "`%%substr' expects a macro identifier as first parameter");
3517 free_tlist(origline);
3518 return DIRECTIVE_FOUND;
3520 ctx = get_ctx(tline->text, &mname);
3521 last = tline;
3522 tline = expand_smacro(tline->next);
3523 last->next = NULL;
3525 if (tline) /* skip expanded id */
3526 t = tline->next;
3527 while (tok_type_(t, TOK_WHITESPACE))
3528 t = t->next;
3530 /* t should now point to the string */
3531 if (!tok_type_(t, TOK_STRING)) {
3532 nasm_error(ERR_NONFATAL,
3533 "`%%substr` requires string as second parameter");
3534 free_tlist(tline);
3535 free_tlist(origline);
3536 return DIRECTIVE_FOUND;
3539 tt = t->next;
3540 tptr = &tt;
3541 tokval.t_type = TOKEN_INVALID;
3542 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3543 if (!evalresult) {
3544 free_tlist(tline);
3545 free_tlist(origline);
3546 return DIRECTIVE_FOUND;
3547 } else if (!is_simple(evalresult)) {
3548 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3549 free_tlist(tline);
3550 free_tlist(origline);
3551 return DIRECTIVE_FOUND;
3553 start = evalresult->value - 1;
3555 while (tok_type_(tt, TOK_WHITESPACE))
3556 tt = tt->next;
3557 if (!tt) {
3558 count = 1; /* Backwards compatibility: one character */
3559 } else {
3560 tokval.t_type = TOKEN_INVALID;
3561 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3562 if (!evalresult) {
3563 free_tlist(tline);
3564 free_tlist(origline);
3565 return DIRECTIVE_FOUND;
3566 } else if (!is_simple(evalresult)) {
3567 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3568 free_tlist(tline);
3569 free_tlist(origline);
3570 return DIRECTIVE_FOUND;
3572 count = evalresult->value;
3575 len = nasm_unquote(t->text, NULL);
3577 /* make start and count being in range */
3578 if (start < 0)
3579 start = 0;
3580 if (count < 0)
3581 count = len + count + 1 - start;
3582 if (start + count > (int64_t)len)
3583 count = len - start;
3584 if (!len || count < 0 || start >=(int64_t)len)
3585 start = -1, count = 0; /* empty string */
3587 macro_start = nasm_malloc(sizeof(*macro_start));
3588 macro_start->next = NULL;
3589 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3590 macro_start->type = TOK_STRING;
3591 macro_start->a.mac = NULL;
3594 * We now have a macro name, an implicit parameter count of
3595 * zero, and a numeric token to use as an expansion. Create
3596 * and store an SMacro.
3598 define_smacro(ctx, mname, casesense, 0, macro_start);
3599 free_tlist(tline);
3600 free_tlist(origline);
3601 return DIRECTIVE_FOUND;
3604 case PP_ASSIGN:
3605 case PP_IASSIGN:
3606 casesense = (i == PP_ASSIGN);
3608 tline = tline->next;
3609 skip_white_(tline);
3610 tline = expand_id(tline);
3611 if (!tline || (tline->type != TOK_ID &&
3612 (tline->type != TOK_PREPROC_ID ||
3613 tline->text[1] != '$'))) {
3614 nasm_error(ERR_NONFATAL,
3615 "`%%%sassign' expects a macro identifier",
3616 (i == PP_IASSIGN ? "i" : ""));
3617 free_tlist(origline);
3618 return DIRECTIVE_FOUND;
3620 ctx = get_ctx(tline->text, &mname);
3621 last = tline;
3622 tline = expand_smacro(tline->next);
3623 last->next = NULL;
3625 t = tline;
3626 tptr = &t;
3627 tokval.t_type = TOKEN_INVALID;
3628 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3629 free_tlist(tline);
3630 if (!evalresult) {
3631 free_tlist(origline);
3632 return DIRECTIVE_FOUND;
3635 if (tokval.t_type)
3636 nasm_error(ERR_WARNING|ERR_PASS1,
3637 "trailing garbage after expression ignored");
3639 if (!is_simple(evalresult)) {
3640 nasm_error(ERR_NONFATAL,
3641 "non-constant value given to `%%%sassign'",
3642 (i == PP_IASSIGN ? "i" : ""));
3643 free_tlist(origline);
3644 return DIRECTIVE_FOUND;
3647 macro_start = nasm_malloc(sizeof(*macro_start));
3648 macro_start->next = NULL;
3649 make_tok_num(macro_start, reloc_value(evalresult));
3650 macro_start->a.mac = NULL;
3653 * We now have a macro name, an implicit parameter count of
3654 * zero, and a numeric token to use as an expansion. Create
3655 * and store an SMacro.
3657 define_smacro(ctx, mname, casesense, 0, macro_start);
3658 free_tlist(origline);
3659 return DIRECTIVE_FOUND;
3661 case PP_LINE:
3663 * Syntax is `%line nnn[+mmm] [filename]'
3665 tline = tline->next;
3666 skip_white_(tline);
3667 if (!tok_type_(tline, TOK_NUMBER)) {
3668 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3669 free_tlist(origline);
3670 return DIRECTIVE_FOUND;
3672 k = readnum(tline->text, &err);
3673 m = 1;
3674 tline = tline->next;
3675 if (tok_is_(tline, "+")) {
3676 tline = tline->next;
3677 if (!tok_type_(tline, TOK_NUMBER)) {
3678 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3679 free_tlist(origline);
3680 return DIRECTIVE_FOUND;
3682 m = readnum(tline->text, &err);
3683 tline = tline->next;
3685 skip_white_(tline);
3686 src_set_linnum(k);
3687 istk->lineinc = m;
3688 if (tline) {
3689 char *fname = detoken(tline, false);
3690 src_set_fname(fname);
3691 nasm_free(fname);
3693 free_tlist(origline);
3694 return DIRECTIVE_FOUND;
3696 default:
3697 nasm_error(ERR_FATAL,
3698 "preprocessor directive `%s' not yet implemented",
3699 pp_directives[i]);
3700 return DIRECTIVE_FOUND;
3705 * Ensure that a macro parameter contains a condition code and
3706 * nothing else. Return the condition code index if so, or -1
3707 * otherwise.
3709 static int find_cc(Token * t)
3711 Token *tt;
3713 if (!t)
3714 return -1; /* Probably a %+ without a space */
3716 skip_white_(t);
3717 if (t->type != TOK_ID)
3718 return -1;
3719 tt = t->next;
3720 skip_white_(tt);
3721 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3722 return -1;
3724 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3728 * This routines walks over tokens strem and hadnles tokens
3729 * pasting, if @handle_explicit passed then explicit pasting
3730 * term is handled, otherwise -- implicit pastings only.
3732 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3733 size_t mnum, bool handle_explicit)
3735 Token *tok, *next, **prev_next, **prev_nonspace;
3736 bool pasted = false;
3737 char *buf, *p;
3738 size_t len, i;
3741 * The last token before pasting. We need it
3742 * to be able to connect new handled tokens.
3743 * In other words if there were a tokens stream
3745 * A -> B -> C -> D
3747 * and we've joined tokens B and C, the resulting
3748 * stream should be
3750 * A -> BC -> D
3752 tok = *head;
3753 prev_next = NULL;
3755 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3756 prev_nonspace = head;
3757 else
3758 prev_nonspace = NULL;
3760 while (tok && (next = tok->next)) {
3762 switch (tok->type) {
3763 case TOK_WHITESPACE:
3764 /* Zap redundant whitespaces */
3765 while (tok_type_(next, TOK_WHITESPACE))
3766 next = delete_Token(next);
3767 tok->next = next;
3768 break;
3770 case TOK_PASTE:
3771 /* Explicit pasting */
3772 if (!handle_explicit)
3773 break;
3774 next = delete_Token(tok);
3776 while (tok_type_(next, TOK_WHITESPACE))
3777 next = delete_Token(next);
3779 if (!pasted)
3780 pasted = true;
3782 /* Left pasting token is start of line */
3783 if (!prev_nonspace)
3784 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3787 * No ending token, this might happen in two
3788 * cases
3790 * 1) There indeed no right token at all
3791 * 2) There is a bare "%define ID" statement,
3792 * and @ID does expand to whitespace.
3794 * So technically we need to do a grammar analysis
3795 * in another stage of parsing, but for now lets don't
3796 * change the behaviour people used to. Simply allow
3797 * whitespace after paste token.
3799 if (!next) {
3801 * Zap ending space tokens and that's all.
3803 tok = (*prev_nonspace)->next;
3804 while (tok_type_(tok, TOK_WHITESPACE))
3805 tok = delete_Token(tok);
3806 tok = *prev_nonspace;
3807 tok->next = NULL;
3808 break;
3811 tok = *prev_nonspace;
3812 while (tok_type_(tok, TOK_WHITESPACE))
3813 tok = delete_Token(tok);
3814 len = strlen(tok->text);
3815 len += strlen(next->text);
3817 p = buf = nasm_malloc(len + 1);
3818 strcpy(p, tok->text);
3819 p = strchr(p, '\0');
3820 strcpy(p, next->text);
3822 delete_Token(tok);
3824 tok = tokenize(buf);
3825 nasm_free(buf);
3827 *prev_nonspace = tok;
3828 while (tok && tok->next)
3829 tok = tok->next;
3831 tok->next = delete_Token(next);
3833 /* Restart from pasted tokens head */
3834 tok = *prev_nonspace;
3835 break;
3837 default:
3838 /* implicit pasting */
3839 for (i = 0; i < mnum; i++) {
3840 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3841 continue;
3843 len = 0;
3844 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3845 len += strlen(next->text);
3846 next = next->next;
3849 /* No match */
3850 if (tok == next)
3851 break;
3853 len += strlen(tok->text);
3854 p = buf = nasm_malloc(len + 1);
3856 strcpy(p, tok->text);
3857 p = strchr(p, '\0');
3858 tok = delete_Token(tok);
3860 while (tok != next) {
3861 if (PP_CONCAT_MATCH(tok, m[i].mask_tail)) {
3862 strcpy(p, tok->text);
3863 p = strchr(p, '\0');
3865 tok = delete_Token(tok);
3868 tok = tokenize(buf);
3869 nasm_free(buf);
3871 if (prev_next)
3872 *prev_next = tok;
3873 else
3874 *head = tok;
3877 * Connect pasted into original stream,
3878 * ie A -> new-tokens -> B
3880 while (tok && tok->next)
3881 tok = tok->next;
3882 tok->next = next;
3884 if (!pasted)
3885 pasted = true;
3887 /* Restart from pasted tokens head */
3888 tok = prev_next ? *prev_next : *head;
3891 break;
3894 prev_next = &tok->next;
3896 if (tok->next &&
3897 !tok_type_(tok->next, TOK_WHITESPACE) &&
3898 !tok_type_(tok->next, TOK_PASTE))
3899 prev_nonspace = prev_next;
3901 tok = tok->next;
3904 return pasted;
3908 * expands to a list of tokens from %{x:y}
3910 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3912 Token *t = tline, **tt, *tm, *head;
3913 char *pos;
3914 int fst, lst, j, i;
3916 pos = strchr(tline->text, ':');
3917 nasm_assert(pos);
3919 lst = atoi(pos + 1);
3920 fst = atoi(tline->text + 1);
3923 * only macros params are accounted so
3924 * if someone passes %0 -- we reject such
3925 * value(s)
3927 if (lst == 0 || fst == 0)
3928 goto err;
3930 /* the values should be sane */
3931 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3932 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3933 goto err;
3935 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3936 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3938 /* counted from zero */
3939 fst--, lst--;
3942 * It will be at least one token. Note we
3943 * need to scan params until separator, otherwise
3944 * only first token will be passed.
3946 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3947 head = new_Token(NULL, tm->type, tm->text, 0);
3948 tt = &head->next, tm = tm->next;
3949 while (tok_isnt_(tm, ",")) {
3950 t = new_Token(NULL, tm->type, tm->text, 0);
3951 *tt = t, tt = &t->next, tm = tm->next;
3954 if (fst < lst) {
3955 for (i = fst + 1; i <= lst; i++) {
3956 t = new_Token(NULL, TOK_OTHER, ",", 0);
3957 *tt = t, tt = &t->next;
3958 j = (i + mac->rotate) % mac->nparam;
3959 tm = mac->params[j];
3960 while (tok_isnt_(tm, ",")) {
3961 t = new_Token(NULL, tm->type, tm->text, 0);
3962 *tt = t, tt = &t->next, tm = tm->next;
3965 } else {
3966 for (i = fst - 1; i >= lst; i--) {
3967 t = new_Token(NULL, TOK_OTHER, ",", 0);
3968 *tt = t, tt = &t->next;
3969 j = (i + mac->rotate) % mac->nparam;
3970 tm = mac->params[j];
3971 while (tok_isnt_(tm, ",")) {
3972 t = new_Token(NULL, tm->type, tm->text, 0);
3973 *tt = t, tt = &t->next, tm = tm->next;
3978 *last = tt;
3979 return head;
3981 err:
3982 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3983 &tline->text[1]);
3984 return tline;
3988 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3989 * %-n) and MMacro-local identifiers (%%foo) as well as
3990 * macro indirection (%[...]) and range (%{..:..}).
3992 static Token *expand_mmac_params(Token * tline)
3994 Token *t, *tt, **tail, *thead;
3995 bool changed = false;
3996 char *pos;
3998 tail = &thead;
3999 thead = NULL;
4001 while (tline) {
4002 if (tline->type == TOK_PREPROC_ID &&
4003 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
4004 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
4005 tline->text[1] == '%')) {
4006 char *text = NULL;
4007 int type = 0, cc; /* type = 0 to placate optimisers */
4008 char tmpbuf[30];
4009 unsigned int n;
4010 int i;
4011 MMacro *mac;
4013 t = tline;
4014 tline = tline->next;
4016 mac = istk->mstk;
4017 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4018 mac = mac->next_active;
4019 if (!mac) {
4020 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4021 } else {
4022 pos = strchr(t->text, ':');
4023 if (!pos) {
4024 switch (t->text[1]) {
4026 * We have to make a substitution of one of the
4027 * forms %1, %-1, %+1, %%foo, %0.
4029 case '0':
4030 type = TOK_NUMBER;
4031 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4032 text = nasm_strdup(tmpbuf);
4033 break;
4034 case '%':
4035 type = TOK_ID;
4036 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4037 mac->unique);
4038 text = nasm_strcat(tmpbuf, t->text + 2);
4039 break;
4040 case '-':
4041 n = atoi(t->text + 2) - 1;
4042 if (n >= mac->nparam)
4043 tt = NULL;
4044 else {
4045 if (mac->nparam > 1)
4046 n = (n + mac->rotate) % mac->nparam;
4047 tt = mac->params[n];
4049 cc = find_cc(tt);
4050 if (cc == -1) {
4051 nasm_error(ERR_NONFATAL,
4052 "macro parameter %d is not a condition code",
4053 n + 1);
4054 text = NULL;
4055 } else {
4056 type = TOK_ID;
4057 if (inverse_ccs[cc] == -1) {
4058 nasm_error(ERR_NONFATAL,
4059 "condition code `%s' is not invertible",
4060 conditions[cc]);
4061 text = NULL;
4062 } else
4063 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4065 break;
4066 case '+':
4067 n = atoi(t->text + 2) - 1;
4068 if (n >= mac->nparam)
4069 tt = NULL;
4070 else {
4071 if (mac->nparam > 1)
4072 n = (n + mac->rotate) % mac->nparam;
4073 tt = mac->params[n];
4075 cc = find_cc(tt);
4076 if (cc == -1) {
4077 nasm_error(ERR_NONFATAL,
4078 "macro parameter %d is not a condition code",
4079 n + 1);
4080 text = NULL;
4081 } else {
4082 type = TOK_ID;
4083 text = nasm_strdup(conditions[cc]);
4085 break;
4086 default:
4087 n = atoi(t->text + 1) - 1;
4088 if (n >= mac->nparam)
4089 tt = NULL;
4090 else {
4091 if (mac->nparam > 1)
4092 n = (n + mac->rotate) % mac->nparam;
4093 tt = mac->params[n];
4095 if (tt) {
4096 for (i = 0; i < mac->paramlen[n]; i++) {
4097 *tail = new_Token(NULL, tt->type, tt->text, 0);
4098 tail = &(*tail)->next;
4099 tt = tt->next;
4102 text = NULL; /* we've done it here */
4103 break;
4105 } else {
4107 * seems we have a parameters range here
4109 Token *head, **last;
4110 head = expand_mmac_params_range(mac, t, &last);
4111 if (head != t) {
4112 *tail = head;
4113 *last = tline;
4114 tline = head;
4115 text = NULL;
4119 if (!text) {
4120 delete_Token(t);
4121 } else {
4122 *tail = t;
4123 tail = &t->next;
4124 t->type = type;
4125 nasm_free(t->text);
4126 t->text = text;
4127 t->a.mac = NULL;
4129 changed = true;
4130 continue;
4131 } else if (tline->type == TOK_INDIRECT) {
4132 t = tline;
4133 tline = tline->next;
4134 tt = tokenize(t->text);
4135 tt = expand_mmac_params(tt);
4136 tt = expand_smacro(tt);
4137 *tail = tt;
4138 while (tt) {
4139 tt->a.mac = NULL; /* Necessary? */
4140 tail = &tt->next;
4141 tt = tt->next;
4143 delete_Token(t);
4144 changed = true;
4145 } else {
4146 t = *tail = tline;
4147 tline = tline->next;
4148 t->a.mac = NULL;
4149 tail = &t->next;
4152 *tail = NULL;
4154 if (changed) {
4155 const struct tokseq_match t[] = {
4157 PP_CONCAT_MASK(TOK_ID) |
4158 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4159 PP_CONCAT_MASK(TOK_ID) |
4160 PP_CONCAT_MASK(TOK_NUMBER) |
4161 PP_CONCAT_MASK(TOK_FLOAT) |
4162 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4165 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4166 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4169 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4172 return thead;
4176 * Expand all single-line macro calls made in the given line.
4177 * Return the expanded version of the line. The original is deemed
4178 * to be destroyed in the process. (In reality we'll just move
4179 * Tokens from input to output a lot of the time, rather than
4180 * actually bothering to destroy and replicate.)
4183 static Token *expand_smacro(Token * tline)
4185 Token *t, *tt, *mstart, **tail, *thead;
4186 SMacro *head = NULL, *m;
4187 Token **params;
4188 int *paramsize;
4189 unsigned int nparam, sparam;
4190 int brackets;
4191 Token *org_tline = tline;
4192 Context *ctx;
4193 const char *mname;
4194 int deadman = DEADMAN_LIMIT;
4195 bool expanded;
4198 * Trick: we should avoid changing the start token pointer since it can
4199 * be contained in "next" field of other token. Because of this
4200 * we allocate a copy of first token and work with it; at the end of
4201 * routine we copy it back
4203 if (org_tline) {
4204 tline = new_Token(org_tline->next, org_tline->type,
4205 org_tline->text, 0);
4206 tline->a.mac = org_tline->a.mac;
4207 nasm_free(org_tline->text);
4208 org_tline->text = NULL;
4211 expanded = true; /* Always expand %+ at least once */
4213 again:
4214 thead = NULL;
4215 tail = &thead;
4217 while (tline) { /* main token loop */
4218 if (!--deadman) {
4219 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4220 goto err;
4223 if ((mname = tline->text)) {
4224 /* if this token is a local macro, look in local context */
4225 if (tline->type == TOK_ID) {
4226 head = (SMacro *)hash_findix(&smacros, mname);
4227 } else if (tline->type == TOK_PREPROC_ID) {
4228 ctx = get_ctx(mname, &mname);
4229 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4230 } else
4231 head = NULL;
4234 * We've hit an identifier. As in is_mmacro below, we first
4235 * check whether the identifier is a single-line macro at
4236 * all, then think about checking for parameters if
4237 * necessary.
4239 list_for_each(m, head)
4240 if (!mstrcmp(m->name, mname, m->casesense))
4241 break;
4242 if (m) {
4243 mstart = tline;
4244 params = NULL;
4245 paramsize = NULL;
4246 if (m->nparam == 0) {
4248 * Simple case: the macro is parameterless. Discard the
4249 * one token that the macro call took, and push the
4250 * expansion back on the to-do stack.
4252 if (!m->expansion) {
4253 if (!strcmp("__FILE__", m->name)) {
4254 const char *file = src_get_fname();
4255 /* nasm_free(tline->text); here? */
4256 tline->text = nasm_quote(file, strlen(file));
4257 tline->type = TOK_STRING;
4258 continue;
4260 if (!strcmp("__LINE__", m->name)) {
4261 nasm_free(tline->text);
4262 make_tok_num(tline, src_get_linnum());
4263 continue;
4265 if (!strcmp("__BITS__", m->name)) {
4266 nasm_free(tline->text);
4267 make_tok_num(tline, globalbits);
4268 continue;
4270 tline = delete_Token(tline);
4271 continue;
4273 } else {
4275 * Complicated case: at least one macro with this name
4276 * exists and takes parameters. We must find the
4277 * parameters in the call, count them, find the SMacro
4278 * that corresponds to that form of the macro call, and
4279 * substitute for the parameters when we expand. What a
4280 * pain.
4282 /*tline = tline->next;
4283 skip_white_(tline); */
4284 do {
4285 t = tline->next;
4286 while (tok_type_(t, TOK_SMAC_END)) {
4287 t->a.mac->in_progress = false;
4288 t->text = NULL;
4289 t = tline->next = delete_Token(t);
4291 tline = t;
4292 } while (tok_type_(tline, TOK_WHITESPACE));
4293 if (!tok_is_(tline, "(")) {
4295 * This macro wasn't called with parameters: ignore
4296 * the call. (Behaviour borrowed from gnu cpp.)
4298 tline = mstart;
4299 m = NULL;
4300 } else {
4301 int paren = 0;
4302 int white = 0;
4303 brackets = 0;
4304 nparam = 0;
4305 sparam = PARAM_DELTA;
4306 params = nasm_malloc(sparam * sizeof(Token *));
4307 params[0] = tline->next;
4308 paramsize = nasm_malloc(sparam * sizeof(int));
4309 paramsize[0] = 0;
4310 while (true) { /* parameter loop */
4312 * For some unusual expansions
4313 * which concatenates function call
4315 t = tline->next;
4316 while (tok_type_(t, TOK_SMAC_END)) {
4317 t->a.mac->in_progress = false;
4318 t->text = NULL;
4319 t = tline->next = delete_Token(t);
4321 tline = t;
4323 if (!tline) {
4324 nasm_error(ERR_NONFATAL,
4325 "macro call expects terminating `)'");
4326 break;
4328 if (tline->type == TOK_WHITESPACE
4329 && brackets <= 0) {
4330 if (paramsize[nparam])
4331 white++;
4332 else
4333 params[nparam] = tline->next;
4334 continue; /* parameter loop */
4336 if (tline->type == TOK_OTHER
4337 && tline->text[1] == 0) {
4338 char ch = tline->text[0];
4339 if (ch == ',' && !paren && brackets <= 0) {
4340 if (++nparam >= sparam) {
4341 sparam += PARAM_DELTA;
4342 params = nasm_realloc(params,
4343 sparam * sizeof(Token *));
4344 paramsize = nasm_realloc(paramsize,
4345 sparam * sizeof(int));
4347 params[nparam] = tline->next;
4348 paramsize[nparam] = 0;
4349 white = 0;
4350 continue; /* parameter loop */
4352 if (ch == '{' &&
4353 (brackets > 0 || (brackets == 0 &&
4354 !paramsize[nparam])))
4356 if (!(brackets++)) {
4357 params[nparam] = tline->next;
4358 continue; /* parameter loop */
4361 if (ch == '}' && brackets > 0)
4362 if (--brackets == 0) {
4363 brackets = -1;
4364 continue; /* parameter loop */
4366 if (ch == '(' && !brackets)
4367 paren++;
4368 if (ch == ')' && brackets <= 0)
4369 if (--paren < 0)
4370 break;
4372 if (brackets < 0) {
4373 brackets = 0;
4374 nasm_error(ERR_NONFATAL, "braces do not "
4375 "enclose all of macro parameter");
4377 paramsize[nparam] += white + 1;
4378 white = 0;
4379 } /* parameter loop */
4380 nparam++;
4381 while (m && (m->nparam != nparam ||
4382 mstrcmp(m->name, mname,
4383 m->casesense)))
4384 m = m->next;
4385 if (!m)
4386 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4387 "macro `%s' exists, "
4388 "but not taking %d parameters",
4389 mstart->text, nparam);
4392 if (m && m->in_progress)
4393 m = NULL;
4394 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4396 * Design question: should we handle !tline, which
4397 * indicates missing ')' here, or expand those
4398 * macros anyway, which requires the (t) test a few
4399 * lines down?
4401 nasm_free(params);
4402 nasm_free(paramsize);
4403 tline = mstart;
4404 } else {
4406 * Expand the macro: we are placed on the last token of the
4407 * call, so that we can easily split the call from the
4408 * following tokens. We also start by pushing an SMAC_END
4409 * token for the cycle removal.
4411 t = tline;
4412 if (t) {
4413 tline = t->next;
4414 t->next = NULL;
4416 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4417 tt->a.mac = m;
4418 m->in_progress = true;
4419 tline = tt;
4420 list_for_each(t, m->expansion) {
4421 if (t->type >= TOK_SMAC_PARAM) {
4422 Token *pcopy = tline, **ptail = &pcopy;
4423 Token *ttt, *pt;
4424 int i;
4426 ttt = params[t->type - TOK_SMAC_PARAM];
4427 i = paramsize[t->type - TOK_SMAC_PARAM];
4428 while (--i >= 0) {
4429 pt = *ptail = new_Token(tline, ttt->type,
4430 ttt->text, 0);
4431 ptail = &pt->next;
4432 ttt = ttt->next;
4433 if (!ttt && i > 0) {
4435 * FIXME: Need to handle more gracefully,
4436 * exiting early on agruments analysis.
4438 nasm_error(ERR_FATAL,
4439 "macro `%s' expects %d args",
4440 mstart->text,
4441 (int)paramsize[t->type - TOK_SMAC_PARAM]);
4444 tline = pcopy;
4445 } else if (t->type == TOK_PREPROC_Q) {
4446 tt = new_Token(tline, TOK_ID, mname, 0);
4447 tline = tt;
4448 } else if (t->type == TOK_PREPROC_QQ) {
4449 tt = new_Token(tline, TOK_ID, m->name, 0);
4450 tline = tt;
4451 } else {
4452 tt = new_Token(tline, t->type, t->text, 0);
4453 tline = tt;
4458 * Having done that, get rid of the macro call, and clean
4459 * up the parameters.
4461 nasm_free(params);
4462 nasm_free(paramsize);
4463 free_tlist(mstart);
4464 expanded = true;
4465 continue; /* main token loop */
4470 if (tline->type == TOK_SMAC_END) {
4471 tline->a.mac->in_progress = false;
4472 tline = delete_Token(tline);
4473 } else {
4474 t = *tail = tline;
4475 tline = tline->next;
4476 t->a.mac = NULL;
4477 t->next = NULL;
4478 tail = &t->next;
4483 * Now scan the entire line and look for successive TOK_IDs that resulted
4484 * after expansion (they can't be produced by tokenize()). The successive
4485 * TOK_IDs should be concatenated.
4486 * Also we look for %+ tokens and concatenate the tokens before and after
4487 * them (without white spaces in between).
4489 if (expanded) {
4490 const struct tokseq_match t[] = {
4492 PP_CONCAT_MASK(TOK_ID) |
4493 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4494 PP_CONCAT_MASK(TOK_ID) |
4495 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4496 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4499 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4501 * If we concatenated something, *and* we had previously expanded
4502 * an actual macro, scan the lines again for macros...
4504 tline = thead;
4505 expanded = false;
4506 goto again;
4510 err:
4511 if (org_tline) {
4512 if (thead) {
4513 *org_tline = *thead;
4514 /* since we just gave text to org_line, don't free it */
4515 thead->text = NULL;
4516 delete_Token(thead);
4517 } else {
4518 /* the expression expanded to empty line;
4519 we can't return NULL for some reasons
4520 we just set the line to a single WHITESPACE token. */
4521 memset(org_tline, 0, sizeof(*org_tline));
4522 org_tline->text = NULL;
4523 org_tline->type = TOK_WHITESPACE;
4525 thead = org_tline;
4528 return thead;
4532 * Similar to expand_smacro but used exclusively with macro identifiers
4533 * right before they are fetched in. The reason is that there can be
4534 * identifiers consisting of several subparts. We consider that if there
4535 * are more than one element forming the name, user wants a expansion,
4536 * otherwise it will be left as-is. Example:
4538 * %define %$abc cde
4540 * the identifier %$abc will be left as-is so that the handler for %define
4541 * will suck it and define the corresponding value. Other case:
4543 * %define _%$abc cde
4545 * In this case user wants name to be expanded *before* %define starts
4546 * working, so we'll expand %$abc into something (if it has a value;
4547 * otherwise it will be left as-is) then concatenate all successive
4548 * PP_IDs into one.
4550 static Token *expand_id(Token * tline)
4552 Token *cur, *oldnext = NULL;
4554 if (!tline || !tline->next)
4555 return tline;
4557 cur = tline;
4558 while (cur->next &&
4559 (cur->next->type == TOK_ID ||
4560 cur->next->type == TOK_PREPROC_ID
4561 || cur->next->type == TOK_NUMBER))
4562 cur = cur->next;
4564 /* If identifier consists of just one token, don't expand */
4565 if (cur == tline)
4566 return tline;
4568 if (cur) {
4569 oldnext = cur->next; /* Detach the tail past identifier */
4570 cur->next = NULL; /* so that expand_smacro stops here */
4573 tline = expand_smacro(tline);
4575 if (cur) {
4576 /* expand_smacro possibly changhed tline; re-scan for EOL */
4577 cur = tline;
4578 while (cur && cur->next)
4579 cur = cur->next;
4580 if (cur)
4581 cur->next = oldnext;
4584 return tline;
4588 * Determine whether the given line constitutes a multi-line macro
4589 * call, and return the MMacro structure called if so. Doesn't have
4590 * to check for an initial label - that's taken care of in
4591 * expand_mmacro - but must check numbers of parameters. Guaranteed
4592 * to be called with tline->type == TOK_ID, so the putative macro
4593 * name is easy to find.
4595 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4597 MMacro *head, *m;
4598 Token **params;
4599 int nparam;
4601 head = (MMacro *) hash_findix(&mmacros, tline->text);
4604 * Efficiency: first we see if any macro exists with the given
4605 * name. If not, we can return NULL immediately. _Then_ we
4606 * count the parameters, and then we look further along the
4607 * list if necessary to find the proper MMacro.
4609 list_for_each(m, head)
4610 if (!mstrcmp(m->name, tline->text, m->casesense))
4611 break;
4612 if (!m)
4613 return NULL;
4616 * OK, we have a potential macro. Count and demarcate the
4617 * parameters.
4619 count_mmac_params(tline->next, &nparam, &params);
4622 * So we know how many parameters we've got. Find the MMacro
4623 * structure that handles this number.
4625 while (m) {
4626 if (m->nparam_min <= nparam
4627 && (m->plus || nparam <= m->nparam_max)) {
4629 * This one is right. Just check if cycle removal
4630 * prohibits us using it before we actually celebrate...
4632 if (m->in_progress > m->max_depth) {
4633 if (m->max_depth > 0) {
4634 nasm_error(ERR_WARNING,
4635 "reached maximum recursion depth of %i",
4636 m->max_depth);
4638 nasm_free(params);
4639 return NULL;
4642 * It's right, and we can use it. Add its default
4643 * parameters to the end of our list if necessary.
4645 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4646 params =
4647 nasm_realloc(params,
4648 ((m->nparam_min + m->ndefs +
4649 1) * sizeof(*params)));
4650 while (nparam < m->nparam_min + m->ndefs) {
4651 params[nparam] = m->defaults[nparam - m->nparam_min];
4652 nparam++;
4656 * If we've gone over the maximum parameter count (and
4657 * we're in Plus mode), ignore parameters beyond
4658 * nparam_max.
4660 if (m->plus && nparam > m->nparam_max)
4661 nparam = m->nparam_max;
4663 * Then terminate the parameter list, and leave.
4665 if (!params) { /* need this special case */
4666 params = nasm_malloc(sizeof(*params));
4667 nparam = 0;
4669 params[nparam] = NULL;
4670 *params_array = params;
4671 return m;
4674 * This one wasn't right: look for the next one with the
4675 * same name.
4677 list_for_each(m, m->next)
4678 if (!mstrcmp(m->name, tline->text, m->casesense))
4679 break;
4683 * After all that, we didn't find one with the right number of
4684 * parameters. Issue a warning, and fail to expand the macro.
4686 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4687 "macro `%s' exists, but not taking %d parameters",
4688 tline->text, nparam);
4689 nasm_free(params);
4690 return NULL;
4695 * Save MMacro invocation specific fields in
4696 * preparation for a recursive macro expansion
4698 static void push_mmacro(MMacro *m)
4700 MMacroInvocation *i;
4702 i = nasm_malloc(sizeof(MMacroInvocation));
4703 i->prev = m->prev;
4704 i->params = m->params;
4705 i->iline = m->iline;
4706 i->nparam = m->nparam;
4707 i->rotate = m->rotate;
4708 i->paramlen = m->paramlen;
4709 i->unique = m->unique;
4710 i->condcnt = m->condcnt;
4711 m->prev = i;
4716 * Restore MMacro invocation specific fields that were
4717 * saved during a previous recursive macro expansion
4719 static void pop_mmacro(MMacro *m)
4721 MMacroInvocation *i;
4723 if (m->prev) {
4724 i = m->prev;
4725 m->prev = i->prev;
4726 m->params = i->params;
4727 m->iline = i->iline;
4728 m->nparam = i->nparam;
4729 m->rotate = i->rotate;
4730 m->paramlen = i->paramlen;
4731 m->unique = i->unique;
4732 m->condcnt = i->condcnt;
4733 nasm_free(i);
4739 * Expand the multi-line macro call made by the given line, if
4740 * there is one to be expanded. If there is, push the expansion on
4741 * istk->expansion and return 1. Otherwise return 0.
4743 static int expand_mmacro(Token * tline)
4745 Token *startline = tline;
4746 Token *label = NULL;
4747 int dont_prepend = 0;
4748 Token **params, *t, *tt;
4749 MMacro *m;
4750 Line *l, *ll;
4751 int i, nparam, *paramlen;
4752 const char *mname;
4754 t = tline;
4755 skip_white_(t);
4756 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4757 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4758 return 0;
4759 m = is_mmacro(t, &params);
4760 if (m) {
4761 mname = t->text;
4762 } else {
4763 Token *last;
4765 * We have an id which isn't a macro call. We'll assume
4766 * it might be a label; we'll also check to see if a
4767 * colon follows it. Then, if there's another id after
4768 * that lot, we'll check it again for macro-hood.
4770 label = last = t;
4771 t = t->next;
4772 if (tok_type_(t, TOK_WHITESPACE))
4773 last = t, t = t->next;
4774 if (tok_is_(t, ":")) {
4775 dont_prepend = 1;
4776 last = t, t = t->next;
4777 if (tok_type_(t, TOK_WHITESPACE))
4778 last = t, t = t->next;
4780 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4781 return 0;
4782 last->next = NULL;
4783 mname = t->text;
4784 tline = t;
4788 * Fix up the parameters: this involves stripping leading and
4789 * trailing whitespace, then stripping braces if they are
4790 * present.
4792 for (nparam = 0; params[nparam]; nparam++) ;
4793 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4795 for (i = 0; params[i]; i++) {
4796 int brace = 0;
4797 int comma = (!m->plus || i < nparam - 1);
4799 t = params[i];
4800 skip_white_(t);
4801 if (tok_is_(t, "{"))
4802 t = t->next, brace++, comma = false;
4803 params[i] = t;
4804 paramlen[i] = 0;
4805 while (t) {
4806 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4807 break; /* ... because we have hit a comma */
4808 if (comma && t->type == TOK_WHITESPACE
4809 && tok_is_(t->next, ","))
4810 break; /* ... or a space then a comma */
4811 if (brace && t->type == TOK_OTHER) {
4812 if (t->text[0] == '{')
4813 brace++; /* ... or a nested opening brace */
4814 else if (t->text[0] == '}')
4815 if (!--brace)
4816 break; /* ... or a brace */
4818 t = t->next;
4819 paramlen[i]++;
4821 if (brace)
4822 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4826 * OK, we have a MMacro structure together with a set of
4827 * parameters. We must now go through the expansion and push
4828 * copies of each Line on to istk->expansion. Substitution of
4829 * parameter tokens and macro-local tokens doesn't get done
4830 * until the single-line macro substitution process; this is
4831 * because delaying them allows us to change the semantics
4832 * later through %rotate.
4834 * First, push an end marker on to istk->expansion, mark this
4835 * macro as in progress, and set up its invocation-specific
4836 * variables.
4838 ll = nasm_malloc(sizeof(Line));
4839 ll->next = istk->expansion;
4840 ll->finishes = m;
4841 ll->first = NULL;
4842 istk->expansion = ll;
4845 * Save the previous MMacro expansion in the case of
4846 * macro recursion
4848 if (m->max_depth && m->in_progress)
4849 push_mmacro(m);
4851 m->in_progress ++;
4852 m->params = params;
4853 m->iline = tline;
4854 m->nparam = nparam;
4855 m->rotate = 0;
4856 m->paramlen = paramlen;
4857 m->unique = unique++;
4858 m->lineno = 0;
4859 m->condcnt = 0;
4861 m->next_active = istk->mstk;
4862 istk->mstk = m;
4864 list_for_each(l, m->expansion) {
4865 Token **tail;
4867 ll = nasm_malloc(sizeof(Line));
4868 ll->finishes = NULL;
4869 ll->next = istk->expansion;
4870 istk->expansion = ll;
4871 tail = &ll->first;
4873 list_for_each(t, l->first) {
4874 Token *x = t;
4875 switch (t->type) {
4876 case TOK_PREPROC_Q:
4877 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4878 break;
4879 case TOK_PREPROC_QQ:
4880 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4881 break;
4882 case TOK_PREPROC_ID:
4883 if (t->text[1] == '0' && t->text[2] == '0') {
4884 dont_prepend = -1;
4885 x = label;
4886 if (!x)
4887 continue;
4889 /* fall through */
4890 default:
4891 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4892 break;
4894 tail = &tt->next;
4896 *tail = NULL;
4900 * If we had a label, push it on as the first line of
4901 * the macro expansion.
4903 if (label) {
4904 if (dont_prepend < 0)
4905 free_tlist(startline);
4906 else {
4907 ll = nasm_malloc(sizeof(Line));
4908 ll->finishes = NULL;
4909 ll->next = istk->expansion;
4910 istk->expansion = ll;
4911 ll->first = startline;
4912 if (!dont_prepend) {
4913 while (label->next)
4914 label = label->next;
4915 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4920 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4922 return 1;
4926 * This function adds macro names to error messages, and suppresses
4927 * them if necessary.
4929 static void pp_verror(int severity, const char *fmt, va_list arg)
4931 char buff[BUFSIZ];
4932 MMacro *mmac = NULL;
4933 int delta = 0;
4936 * If we're in a dead branch of IF or something like it, ignore the error.
4937 * However, because %else etc are evaluated in the state context
4938 * of the previous branch, errors might get lost:
4939 * %if 0 ... %else trailing garbage ... %endif
4940 * So %else etc should set the ERR_PP_PRECOND flag.
4942 if ((severity & ERR_MASK) < ERR_FATAL &&
4943 istk && istk->conds &&
4944 ((severity & ERR_PP_PRECOND) ?
4945 istk->conds->state == COND_NEVER :
4946 !emitting(istk->conds->state)))
4947 return;
4949 /* get %macro name */
4950 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4951 mmac = istk->mstk;
4952 /* but %rep blocks should be skipped */
4953 while (mmac && !mmac->name)
4954 mmac = mmac->next_active, delta++;
4957 if (mmac) {
4958 vsnprintf(buff, sizeof(buff), fmt, arg);
4960 nasm_set_verror(real_verror);
4961 nasm_error(severity, "(%s:%d) %s",
4962 mmac->name, mmac->lineno - delta, buff);
4963 nasm_set_verror(pp_verror);
4964 } else {
4965 real_verror(severity, fmt, arg);
4969 static void
4970 pp_reset(char *file, int apass, StrList **deplist)
4972 Token *t;
4974 cstk = NULL;
4975 istk = nasm_malloc(sizeof(Include));
4976 istk->next = NULL;
4977 istk->conds = NULL;
4978 istk->expansion = NULL;
4979 istk->mstk = NULL;
4980 istk->fp = nasm_open_read(file, NF_TEXT);
4981 istk->fname = NULL;
4982 src_set(0, file);
4983 istk->lineinc = 1;
4984 if (!istk->fp)
4985 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4986 defining = NULL;
4987 nested_mac_count = 0;
4988 nested_rep_count = 0;
4989 init_macros();
4990 unique = 0;
4992 if (tasm_compatible_mode)
4993 pp_add_stdmac(nasm_stdmac_tasm);
4995 pp_add_stdmac(nasm_stdmac_nasm);
4996 pp_add_stdmac(nasm_stdmac_version);
4998 if (extrastdmac)
4999 pp_add_stdmac(extrastdmac);
5001 stdmacpos = stdmacros[0];
5002 stdmacnext = &stdmacros[1];
5004 do_predef = true;
5007 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
5008 * The caller, however, will also pass in 3 for preprocess-only so
5009 * we can set __PASS__ accordingly.
5011 pass = apass > 2 ? 2 : apass;
5013 dephead = deplist;
5014 nasm_add_string_to_strlist(dephead, file);
5017 * Define the __PASS__ macro. This is defined here unlike
5018 * all the other builtins, because it is special -- it varies between
5019 * passes.
5021 t = nasm_malloc(sizeof(*t));
5022 t->next = NULL;
5023 make_tok_num(t, apass);
5024 t->a.mac = NULL;
5025 define_smacro(NULL, "__PASS__", true, 0, t);
5028 static void pp_init(void)
5030 hash_init(&FileHash, HASH_MEDIUM);
5033 static char *pp_getline(void)
5035 char *line;
5036 Token *tline;
5038 real_verror = nasm_set_verror(pp_verror);
5040 while (1) {
5042 * Fetch a tokenized line, either from the macro-expansion
5043 * buffer or from the input file.
5045 tline = NULL;
5046 while (istk->expansion && istk->expansion->finishes) {
5047 Line *l = istk->expansion;
5048 if (!l->finishes->name && l->finishes->in_progress > 1) {
5049 Line *ll;
5052 * This is a macro-end marker for a macro with no
5053 * name, which means it's not really a macro at all
5054 * but a %rep block, and the `in_progress' field is
5055 * more than 1, meaning that we still need to
5056 * repeat. (1 means the natural last repetition; 0
5057 * means termination by %exitrep.) We have
5058 * therefore expanded up to the %endrep, and must
5059 * push the whole block on to the expansion buffer
5060 * again. We don't bother to remove the macro-end
5061 * marker: we'd only have to generate another one
5062 * if we did.
5064 l->finishes->in_progress--;
5065 list_for_each(l, l->finishes->expansion) {
5066 Token *t, *tt, **tail;
5068 ll = nasm_malloc(sizeof(Line));
5069 ll->next = istk->expansion;
5070 ll->finishes = NULL;
5071 ll->first = NULL;
5072 tail = &ll->first;
5074 list_for_each(t, l->first) {
5075 if (t->text || t->type == TOK_WHITESPACE) {
5076 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5077 tail = &tt->next;
5081 istk->expansion = ll;
5083 } else {
5085 * Check whether a `%rep' was started and not ended
5086 * within this macro expansion. This can happen and
5087 * should be detected. It's a fatal error because
5088 * I'm too confused to work out how to recover
5089 * sensibly from it.
5091 if (defining) {
5092 if (defining->name)
5093 nasm_panic(0, "defining with name in expansion");
5094 else if (istk->mstk->name)
5095 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5096 " expansion of macro `%s'",
5097 istk->mstk->name);
5101 * FIXME: investigate the relationship at this point between
5102 * istk->mstk and l->finishes
5105 MMacro *m = istk->mstk;
5106 istk->mstk = m->next_active;
5107 if (m->name) {
5109 * This was a real macro call, not a %rep, and
5110 * therefore the parameter information needs to
5111 * be freed.
5113 if (m->prev) {
5114 pop_mmacro(m);
5115 l->finishes->in_progress --;
5116 } else {
5117 nasm_free(m->params);
5118 free_tlist(m->iline);
5119 nasm_free(m->paramlen);
5120 l->finishes->in_progress = 0;
5125 * FIXME It is incorrect to always free_mmacro here.
5126 * It leads to usage-after-free.
5128 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
5130 #if 0
5131 else
5132 free_mmacro(m);
5133 #endif
5135 istk->expansion = l->next;
5136 nasm_free(l);
5137 lfmt->downlevel(LIST_MACRO);
5140 while (1) { /* until we get a line we can use */
5142 if (istk->expansion) { /* from a macro expansion */
5143 char *p;
5144 Line *l = istk->expansion;
5145 if (istk->mstk)
5146 istk->mstk->lineno++;
5147 tline = l->first;
5148 istk->expansion = l->next;
5149 nasm_free(l);
5150 p = detoken(tline, false);
5151 lfmt->line(LIST_MACRO, p);
5152 nasm_free(p);
5153 break;
5155 line = read_line();
5156 if (line) { /* from the current input file */
5157 line = prepreproc(line);
5158 tline = tokenize(line);
5159 nasm_free(line);
5160 break;
5163 * The current file has ended; work down the istk
5166 Include *i = istk;
5167 fclose(i->fp);
5168 if (i->conds) {
5169 /* nasm_error can't be conditionally suppressed */
5170 nasm_fatal(0,
5171 "expected `%%endif' before end of file");
5173 /* only set line and file name if there's a next node */
5174 if (i->next)
5175 src_set(i->lineno, i->fname);
5176 istk = i->next;
5177 lfmt->downlevel(LIST_INCLUDE);
5178 nasm_free(i);
5179 if (!istk) {
5180 line = NULL;
5181 goto done;
5183 if (istk->expansion && istk->expansion->finishes)
5184 break;
5189 * We must expand MMacro parameters and MMacro-local labels
5190 * _before_ we plunge into directive processing, to cope
5191 * with things like `%define something %1' such as STRUC
5192 * uses. Unless we're _defining_ a MMacro, in which case
5193 * those tokens should be left alone to go into the
5194 * definition; and unless we're in a non-emitting
5195 * condition, in which case we don't want to meddle with
5196 * anything.
5198 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5199 && !(istk->mstk && !istk->mstk->in_progress)) {
5200 tline = expand_mmac_params(tline);
5204 * Check the line to see if it's a preprocessor directive.
5206 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5207 if (line)
5208 break; /* Directive generated output */
5209 else
5210 continue;
5211 } else if (defining) {
5213 * We're defining a multi-line macro. We emit nothing
5214 * at all, and just
5215 * shove the tokenized line on to the macro definition.
5217 Line *l = nasm_malloc(sizeof(Line));
5218 l->next = defining->expansion;
5219 l->first = tline;
5220 l->finishes = NULL;
5221 defining->expansion = l;
5222 continue;
5223 } else if (istk->conds && !emitting(istk->conds->state)) {
5225 * We're in a non-emitting branch of a condition block.
5226 * Emit nothing at all, not even a blank line: when we
5227 * emerge from the condition we'll give a line-number
5228 * directive so we keep our place correctly.
5230 free_tlist(tline);
5231 continue;
5232 } else if (istk->mstk && !istk->mstk->in_progress) {
5234 * We're in a %rep block which has been terminated, so
5235 * we're walking through to the %endrep without
5236 * emitting anything. Emit nothing at all, not even a
5237 * blank line: when we emerge from the %rep block we'll
5238 * give a line-number directive so we keep our place
5239 * correctly.
5241 free_tlist(tline);
5242 continue;
5243 } else {
5244 tline = expand_smacro(tline);
5245 if (!expand_mmacro(tline)) {
5247 * De-tokenize the line again, and emit it.
5249 line = detoken(tline, true);
5250 free_tlist(tline);
5251 break;
5252 } else {
5253 continue; /* expand_mmacro calls free_tlist */
5258 done:
5259 nasm_set_verror(real_verror);
5260 return line;
5263 static void pp_cleanup(int pass)
5265 real_verror = nasm_set_verror(pp_verror);
5267 if (defining) {
5268 if (defining->name) {
5269 nasm_error(ERR_NONFATAL,
5270 "end of file while still defining macro `%s'",
5271 defining->name);
5272 } else {
5273 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5276 free_mmacro(defining);
5277 defining = NULL;
5280 nasm_set_verror(real_verror);
5282 while (cstk)
5283 ctx_pop();
5284 free_macros();
5285 while (istk) {
5286 Include *i = istk;
5287 istk = istk->next;
5288 fclose(i->fp);
5289 nasm_free(i);
5291 while (cstk)
5292 ctx_pop();
5293 src_set_fname(NULL);
5294 if (pass == 0) {
5295 IncPath *i;
5296 free_llist(predef);
5297 predef = NULL;
5298 delete_Blocks();
5299 freeTokens = NULL;
5300 while ((i = ipath)) {
5301 ipath = i->next;
5302 if (i->path)
5303 nasm_free(i->path);
5304 nasm_free(i);
5309 static void pp_include_path(char *path)
5311 IncPath *i;
5313 i = nasm_malloc(sizeof(IncPath));
5314 i->path = path ? nasm_strdup(path) : NULL;
5315 i->next = NULL;
5317 if (ipath) {
5318 IncPath *j = ipath;
5319 while (j->next)
5320 j = j->next;
5321 j->next = i;
5322 } else {
5323 ipath = i;
5327 static void pp_pre_include(char *fname)
5329 Token *inc, *space, *name;
5330 Line *l;
5332 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5333 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5334 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5336 l = nasm_malloc(sizeof(Line));
5337 l->next = predef;
5338 l->first = inc;
5339 l->finishes = NULL;
5340 predef = l;
5343 static void pp_pre_define(char *definition)
5345 Token *def, *space;
5346 Line *l;
5347 char *equals;
5349 real_verror = nasm_set_verror(pp_verror);
5351 equals = strchr(definition, '=');
5352 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5353 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5354 if (equals)
5355 *equals = ' ';
5356 space->next = tokenize(definition);
5357 if (equals)
5358 *equals = '=';
5360 if (space->next->type != TOK_PREPROC_ID &&
5361 space->next->type != TOK_ID)
5362 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5364 l = nasm_malloc(sizeof(Line));
5365 l->next = predef;
5366 l->first = def;
5367 l->finishes = NULL;
5368 predef = l;
5370 nasm_set_verror(real_verror);
5373 static void pp_pre_undefine(char *definition)
5375 Token *def, *space;
5376 Line *l;
5378 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5379 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5380 space->next = tokenize(definition);
5382 l = nasm_malloc(sizeof(Line));
5383 l->next = predef;
5384 l->first = def;
5385 l->finishes = NULL;
5386 predef = l;
5389 static void pp_add_stdmac(macros_t *macros)
5391 macros_t **mp;
5393 /* Find the end of the list and avoid duplicates */
5394 for (mp = stdmacros; *mp; mp++) {
5395 if (*mp == macros)
5396 return; /* Nothing to do */
5399 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5401 *mp = macros;
5404 static void pp_extra_stdmac(macros_t *macros)
5406 extrastdmac = macros;
5409 static void make_tok_num(Token * tok, int64_t val)
5411 char numbuf[32];
5412 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5413 tok->text = nasm_strdup(numbuf);
5414 tok->type = TOK_NUMBER;
5417 static void pp_list_one_macro(MMacro *m, int severity)
5419 if (!m)
5420 return;
5422 /* We need to print the next_active list in reverse order */
5423 pp_list_one_macro(m->next_active, severity);
5425 if (m->name && !m->nolist) {
5426 src_set(m->xline + m->lineno, m->fname);
5427 nasm_error(severity, "... from macro `%s' defined here", m->name);
5431 static void pp_error_list_macros(int severity)
5433 int32_t saved_line;
5434 const char *saved_fname = NULL;
5436 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5437 src_get(&saved_line, &saved_fname);
5439 if (istk)
5440 pp_list_one_macro(istk->mstk, severity);
5442 src_set(saved_line, saved_fname);
5445 const struct preproc_ops nasmpp = {
5446 pp_init,
5447 pp_reset,
5448 pp_getline,
5449 pp_cleanup,
5450 pp_extra_stdmac,
5451 pp_pre_define,
5452 pp_pre_undefine,
5453 pp_pre_include,
5454 pp_include_path,
5455 pp_error_list_macros,