Extended test file.
[nasm/externdefs2.git] / asm / preproc.c
bloba8388bcbba46061216803f68bc36a15387c855e2
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) + 1;
952 break;
953 default:
954 break;
957 p--;
958 if (*p)
959 *p++ = '\0';
960 if (lvl)
961 nasm_error(ERR_NONFATAL|ERR_PASS1,
962 "unterminated %%[ construct");
963 type = TOK_INDIRECT;
964 } else if (*p == '?') {
965 type = TOK_PREPROC_Q; /* %? */
966 p++;
967 if (*p == '?') {
968 type = TOK_PREPROC_QQ; /* %?? */
969 p++;
971 } else if (*p == '!') {
972 type = TOK_PREPROC_ID;
973 p++;
974 if (isidchar(*p)) {
975 do {
976 p++;
978 while (isidchar(*p));
979 } else if (*p == '\'' || *p == '\"' || *p == '`') {
980 p = nasm_skip_string(p);
981 if (*p)
982 p++;
983 else
984 nasm_error(ERR_NONFATAL|ERR_PASS1,
985 "unterminated %%! string");
986 } else {
987 /* %! without string or identifier */
988 type = TOK_OTHER; /* Legacy behavior... */
990 } else if (isidchar(*p) ||
991 ((*p == '!' || *p == '%' || *p == '$') &&
992 isidchar(p[1]))) {
993 do {
994 p++;
996 while (isidchar(*p));
997 type = TOK_PREPROC_ID;
998 } else {
999 type = TOK_OTHER;
1000 if (*p == '%')
1001 p++;
1003 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1004 type = TOK_ID;
1005 p++;
1006 while (*p && isidchar(*p))
1007 p++;
1008 } else if (*p == '\'' || *p == '"' || *p == '`') {
1010 * A string token.
1012 type = TOK_STRING;
1013 p = nasm_skip_string(p);
1015 if (*p) {
1016 p++;
1017 } else {
1018 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1019 /* Handling unterminated strings by UNV */
1020 /* type = -1; */
1022 } else if (p[0] == '$' && p[1] == '$') {
1023 type = TOK_OTHER; /* TOKEN_BASE */
1024 p += 2;
1025 } else if (isnumstart(*p)) {
1026 bool is_hex = false;
1027 bool is_float = false;
1028 bool has_e = false;
1029 char c, *r;
1032 * A numeric token.
1035 if (*p == '$') {
1036 p++;
1037 is_hex = true;
1040 for (;;) {
1041 c = *p++;
1043 if (!is_hex && (c == 'e' || c == 'E')) {
1044 has_e = true;
1045 if (*p == '+' || *p == '-') {
1047 * e can only be followed by +/- if it is either a
1048 * prefixed hex number or a floating-point number
1050 p++;
1051 is_float = true;
1053 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1054 is_hex = true;
1055 } else if (c == 'P' || c == 'p') {
1056 is_float = true;
1057 if (*p == '+' || *p == '-')
1058 p++;
1059 } else if (isnumchar(c))
1060 ; /* just advance */
1061 else if (c == '.') {
1063 * we need to deal with consequences of the legacy
1064 * parser, like "1.nolist" being two tokens
1065 * (TOK_NUMBER, TOK_ID) here; at least give it
1066 * a shot for now. In the future, we probably need
1067 * a flex-based scanner with proper pattern matching
1068 * to do it as well as it can be done. Nothing in
1069 * the world is going to help the person who wants
1070 * 0x123.p16 interpreted as two tokens, though.
1072 r = p;
1073 while (*r == '_')
1074 r++;
1076 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1077 (!is_hex && (*r == 'e' || *r == 'E')) ||
1078 (*r == 'p' || *r == 'P')) {
1079 p = r;
1080 is_float = true;
1081 } else
1082 break; /* Terminate the token */
1083 } else
1084 break;
1086 p--; /* Point to first character beyond number */
1088 if (p == line+1 && *line == '$') {
1089 type = TOK_OTHER; /* TOKEN_HERE */
1090 } else {
1091 if (has_e && !is_hex) {
1092 /* 1e13 is floating-point, but 1e13h is not */
1093 is_float = true;
1096 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1098 } else if (nasm_isspace(*p)) {
1099 type = TOK_WHITESPACE;
1100 p = nasm_skip_spaces(p);
1102 * Whitespace just before end-of-line is discarded by
1103 * pretending it's a comment; whitespace just before a
1104 * comment gets lumped into the comment.
1106 if (!*p || *p == ';') {
1107 type = TOK_COMMENT;
1108 while (*p)
1109 p++;
1111 } else if (*p == ';') {
1112 type = TOK_COMMENT;
1113 while (*p)
1114 p++;
1115 } else {
1117 * Anything else is an operator of some kind. We check
1118 * for all the double-character operators (>>, <<, //,
1119 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1120 * else is a single-character operator.
1122 type = TOK_OTHER;
1123 if ((p[0] == '>' && p[1] == '>') ||
1124 (p[0] == '<' && p[1] == '<') ||
1125 (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++;
1136 p++;
1139 /* Handling unterminated string by UNV */
1140 /*if (type == -1)
1142 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1143 t->text[p-line] = *line;
1144 tail = &t->next;
1146 else */
1147 if (type != TOK_COMMENT) {
1148 *tail = t = new_Token(NULL, type, line, p - line);
1149 tail = &t->next;
1151 line = p;
1153 return list;
1157 * this function allocates a new managed block of memory and
1158 * returns a pointer to the block. The managed blocks are
1159 * deleted only all at once by the delete_Blocks function.
1161 static void *new_Block(size_t size)
1163 Blocks *b = &blocks;
1165 /* first, get to the end of the linked list */
1166 while (b->next)
1167 b = b->next;
1168 /* now allocate the requested chunk */
1169 b->chunk = nasm_malloc(size);
1171 /* now allocate a new block for the next request */
1172 b->next = nasm_zalloc(sizeof(Blocks));
1173 return b->chunk;
1177 * this function deletes all managed blocks of memory
1179 static void delete_Blocks(void)
1181 Blocks *a, *b = &blocks;
1184 * keep in mind that the first block, pointed to by blocks
1185 * is a static and not dynamically allocated, so we don't
1186 * free it.
1188 while (b) {
1189 if (b->chunk)
1190 nasm_free(b->chunk);
1191 a = b;
1192 b = b->next;
1193 if (a != &blocks)
1194 nasm_free(a);
1196 memset(&blocks, 0, sizeof(blocks));
1200 * this function creates a new Token and passes a pointer to it
1201 * back to the caller. It sets the type and text elements, and
1202 * also the a.mac and next elements to NULL.
1204 static Token *new_Token(Token * next, enum pp_token_type type,
1205 const char *text, int txtlen)
1207 Token *t;
1208 int i;
1210 if (!freeTokens) {
1211 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1212 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1213 freeTokens[i].next = &freeTokens[i + 1];
1214 freeTokens[i].next = NULL;
1216 t = freeTokens;
1217 freeTokens = t->next;
1218 t->next = next;
1219 t->a.mac = NULL;
1220 t->type = type;
1221 if (type == TOK_WHITESPACE || !text) {
1222 t->text = NULL;
1223 } else {
1224 if (txtlen == 0)
1225 txtlen = strlen(text);
1226 t->text = nasm_malloc(txtlen+1);
1227 memcpy(t->text, text, txtlen);
1228 t->text[txtlen] = '\0';
1230 return t;
1233 static Token *delete_Token(Token * t)
1235 Token *next = t->next;
1236 nasm_free(t->text);
1237 t->next = freeTokens;
1238 freeTokens = t;
1239 return next;
1243 * Convert a line of tokens back into text.
1244 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1245 * will be transformed into ..@ctxnum.xxx
1247 static char *detoken(Token * tlist, bool expand_locals)
1249 Token *t;
1250 char *line, *p;
1251 const char *q;
1252 int len = 0;
1254 list_for_each(t, tlist) {
1255 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1256 char *v;
1257 char *q = t->text;
1259 v = t->text + 2;
1260 if (*v == '\'' || *v == '\"' || *v == '`') {
1261 size_t len = nasm_unquote(v, NULL);
1262 size_t clen = strlen(v);
1264 if (len != clen) {
1265 nasm_error(ERR_NONFATAL | ERR_PASS1,
1266 "NUL character in %%! string");
1267 v = NULL;
1271 if (v) {
1272 char *p = getenv(v);
1273 if (!p) {
1274 nasm_error(ERR_NONFATAL | ERR_PASS1,
1275 "nonexistent environment variable `%s'", v);
1277 * FIXME We better should investigate if accessing
1278 * ->text[1] without ->text[0] is safe enough.
1280 t->text = nasm_zalloc(2);
1281 } else
1282 t->text = nasm_strdup(p);
1283 nasm_free(q);
1287 /* Expand local macros here and not during preprocessing */
1288 if (expand_locals &&
1289 t->type == TOK_PREPROC_ID && t->text &&
1290 t->text[0] == '%' && t->text[1] == '$') {
1291 const char *q;
1292 char *p;
1293 Context *ctx = get_ctx(t->text, &q);
1294 if (ctx) {
1295 char buffer[40];
1296 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1297 p = nasm_strcat(buffer, q);
1298 nasm_free(t->text);
1299 t->text = p;
1302 if (t->type == TOK_WHITESPACE)
1303 len++;
1304 else if (t->text)
1305 len += strlen(t->text);
1308 p = line = nasm_malloc(len + 1);
1310 list_for_each(t, tlist) {
1311 if (t->type == TOK_WHITESPACE) {
1312 *p++ = ' ';
1313 } else if (t->text) {
1314 q = t->text;
1315 while (*q)
1316 *p++ = *q++;
1319 *p = '\0';
1321 return line;
1325 * A scanner, suitable for use by the expression evaluator, which
1326 * operates on a line of Tokens. Expects a pointer to a pointer to
1327 * the first token in the line to be passed in as its private_data
1328 * field.
1330 * FIX: This really needs to be unified with stdscan.
1332 static int ppscan(void *private_data, struct tokenval *tokval)
1334 Token **tlineptr = private_data;
1335 Token *tline;
1336 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1338 do {
1339 tline = *tlineptr;
1340 *tlineptr = tline ? tline->next : NULL;
1341 } while (tline && (tline->type == TOK_WHITESPACE ||
1342 tline->type == TOK_COMMENT));
1344 if (!tline)
1345 return tokval->t_type = TOKEN_EOS;
1347 tokval->t_charptr = tline->text;
1349 if (tline->text[0] == '$' && !tline->text[1])
1350 return tokval->t_type = TOKEN_HERE;
1351 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1352 return tokval->t_type = TOKEN_BASE;
1354 if (tline->type == TOK_ID) {
1355 p = tokval->t_charptr = tline->text;
1356 if (p[0] == '$') {
1357 tokval->t_charptr++;
1358 return tokval->t_type = TOKEN_ID;
1361 for (r = p, s = ourcopy; *r; r++) {
1362 if (r >= p+MAX_KEYWORD)
1363 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1364 *s++ = nasm_tolower(*r);
1366 *s = '\0';
1367 /* right, so we have an identifier sitting in temp storage. now,
1368 * is it actually a register or instruction name, or what? */
1369 return nasm_token_hash(ourcopy, tokval);
1372 if (tline->type == TOK_NUMBER) {
1373 bool rn_error;
1374 tokval->t_integer = readnum(tline->text, &rn_error);
1375 tokval->t_charptr = tline->text;
1376 if (rn_error)
1377 return tokval->t_type = TOKEN_ERRNUM;
1378 else
1379 return tokval->t_type = TOKEN_NUM;
1382 if (tline->type == TOK_FLOAT) {
1383 return tokval->t_type = TOKEN_FLOAT;
1386 if (tline->type == TOK_STRING) {
1387 char bq, *ep;
1389 bq = tline->text[0];
1390 tokval->t_charptr = tline->text;
1391 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1393 if (ep[0] != bq || ep[1] != '\0')
1394 return tokval->t_type = TOKEN_ERRSTR;
1395 else
1396 return tokval->t_type = TOKEN_STR;
1399 if (tline->type == TOK_OTHER) {
1400 if (!strcmp(tline->text, "<<"))
1401 return tokval->t_type = TOKEN_SHL;
1402 if (!strcmp(tline->text, ">>"))
1403 return tokval->t_type = TOKEN_SHR;
1404 if (!strcmp(tline->text, "//"))
1405 return tokval->t_type = TOKEN_SDIV;
1406 if (!strcmp(tline->text, "%%"))
1407 return tokval->t_type = TOKEN_SMOD;
1408 if (!strcmp(tline->text, "=="))
1409 return tokval->t_type = TOKEN_EQ;
1410 if (!strcmp(tline->text, "<>"))
1411 return tokval->t_type = TOKEN_NE;
1412 if (!strcmp(tline->text, "!="))
1413 return tokval->t_type = TOKEN_NE;
1414 if (!strcmp(tline->text, "<="))
1415 return tokval->t_type = TOKEN_LE;
1416 if (!strcmp(tline->text, ">="))
1417 return tokval->t_type = TOKEN_GE;
1418 if (!strcmp(tline->text, "&&"))
1419 return tokval->t_type = TOKEN_DBL_AND;
1420 if (!strcmp(tline->text, "^^"))
1421 return tokval->t_type = TOKEN_DBL_XOR;
1422 if (!strcmp(tline->text, "||"))
1423 return tokval->t_type = TOKEN_DBL_OR;
1427 * We have no other options: just return the first character of
1428 * the token text.
1430 return tokval->t_type = tline->text[0];
1434 * Compare a string to the name of an existing macro; this is a
1435 * simple wrapper which calls either strcmp or nasm_stricmp
1436 * depending on the value of the `casesense' parameter.
1438 static int mstrcmp(const char *p, const char *q, bool casesense)
1440 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1444 * Compare a string to the name of an existing macro; this is a
1445 * simple wrapper which calls either strcmp or nasm_stricmp
1446 * depending on the value of the `casesense' parameter.
1448 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1450 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1454 * Return the Context structure associated with a %$ token. Return
1455 * NULL, having _already_ reported an error condition, if the
1456 * context stack isn't deep enough for the supplied number of $
1457 * signs.
1459 * If "namep" is non-NULL, set it to the pointer to the macro name
1460 * tail, i.e. the part beyond %$...
1462 static Context *get_ctx(const char *name, const char **namep)
1464 Context *ctx;
1465 int i;
1467 if (namep)
1468 *namep = name;
1470 if (!name || name[0] != '%' || name[1] != '$')
1471 return NULL;
1473 if (!cstk) {
1474 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1475 return NULL;
1478 name += 2;
1479 ctx = cstk;
1480 i = 0;
1481 while (ctx && *name == '$') {
1482 name++;
1483 i++;
1484 ctx = ctx->next;
1486 if (!ctx) {
1487 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1488 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1489 return NULL;
1492 if (namep)
1493 *namep = name;
1495 return ctx;
1499 * Open an include file. This routine must always return a valid
1500 * file pointer if it returns - it's responsible for throwing an
1501 * ERR_FATAL and bombing out completely if not. It should also try
1502 * the include path one by one until it finds the file or reaches
1503 * the end of the path.
1505 * Note: for INC_PROBE the function returns NULL at all times;
1506 * instead look for the
1508 enum incopen_mode {
1509 INC_NEEDED, /* File must exist */
1510 INC_OPTIONAL, /* Missing is OK */
1511 INC_PROBE /* Only an existence probe */
1514 /* This is conducts a full pathname search */
1515 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1516 enum incopen_mode omode, enum file_flags fmode)
1518 FILE *fp;
1519 char *prefix = "";
1520 const IncPath *ip = ipath;
1521 int len = strlen(file);
1522 size_t prefix_len = 0;
1523 StrList *sl;
1524 size_t path_len;
1525 bool found;
1527 while (1) {
1528 path_len = prefix_len + len + 1;
1530 sl = nasm_malloc(path_len + sizeof sl->next);
1531 memcpy(sl->str, prefix, prefix_len);
1532 memcpy(sl->str+prefix_len, file, len+1);
1533 sl->next = NULL;
1535 if (omode == INC_PROBE) {
1536 fp = NULL;
1537 found = nasm_file_exists(sl->str);
1538 } else {
1539 fp = nasm_open_read(sl->str, fmode);
1540 found = (fp != NULL);
1542 if (found) {
1543 *slpath = sl;
1544 return fp;
1547 nasm_free(sl);
1549 if (!ip)
1550 return NULL;
1552 prefix = ip->path;
1553 prefix_len = strlen(prefix);
1554 ip = ip->next;
1559 * Open a file, or test for the presence of one (depending on omode),
1560 * considering the include path.
1562 static FILE *inc_fopen(const char *file,
1563 StrList **dhead,
1564 const char **found_path,
1565 enum incopen_mode omode,
1566 enum file_flags fmode)
1568 StrList *sl;
1569 struct hash_insert hi;
1570 void **hp;
1571 char *path;
1572 FILE *fp = NULL;
1574 hp = hash_find(&FileHash, file, &hi);
1575 if (hp) {
1576 path = *hp;
1577 if (path || omode != INC_NEEDED) {
1578 nasm_add_string_to_strlist(dhead, path ? path : file);
1580 } else {
1581 /* Need to do the actual path search */
1582 size_t file_len;
1584 sl = NULL;
1585 fp = inc_fopen_search(file, &sl, omode, fmode);
1587 file_len = strlen(file);
1589 if (!sl) {
1590 /* Store negative result for this file */
1591 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1592 memcpy(sl->str, file, file_len+1);
1593 sl->next = NULL;
1594 file = sl->str;
1595 path = NULL;
1596 } else {
1597 path = sl->str;
1598 file = strchr(path, '\0') - file_len;
1601 hash_add(&hi, file, path); /* Positive or negative result */
1604 * Add file to dependency path. The in_list() is needed
1605 * in case the file was already added with %depend.
1607 if (path || omode != INC_NEEDED)
1608 nasm_add_to_strlist(dhead, sl);
1611 if (!path) {
1612 if (omode == INC_NEEDED)
1613 nasm_fatal(0, "unable to open include file `%s'", file);
1615 if (found_path)
1616 *found_path = NULL;
1618 return NULL;
1621 if (!fp && omode != INC_PROBE)
1622 fp = nasm_open_read(path, fmode);
1624 if (found_path)
1625 *found_path = path;
1627 return fp;
1631 * Opens an include or input file. Public version, for use by modules
1632 * that get a file:lineno pair and need to look at the file again
1633 * (e.g. the CodeView debug backend). Returns NULL on failure.
1635 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1637 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1641 * Determine if we should warn on defining a single-line macro of
1642 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1643 * return true if _any_ single-line macro of that name is defined.
1644 * Otherwise, will return true if a single-line macro with either
1645 * `nparam' or no parameters is defined.
1647 * If a macro with precisely the right number of parameters is
1648 * defined, or nparam is -1, the address of the definition structure
1649 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1650 * is NULL, no action will be taken regarding its contents, and no
1651 * error will occur.
1653 * Note that this is also called with nparam zero to resolve
1654 * `ifdef'.
1656 * If you already know which context macro belongs to, you can pass
1657 * the context pointer as first parameter; if you won't but name begins
1658 * with %$ the context will be automatically computed. If all_contexts
1659 * is true, macro will be searched in outer contexts as well.
1661 static bool
1662 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1663 bool nocase)
1665 struct hash_table *smtbl;
1666 SMacro *m;
1668 if (ctx) {
1669 smtbl = &ctx->localmac;
1670 } else if (name[0] == '%' && name[1] == '$') {
1671 if (cstk)
1672 ctx = get_ctx(name, &name);
1673 if (!ctx)
1674 return false; /* got to return _something_ */
1675 smtbl = &ctx->localmac;
1676 } else {
1677 smtbl = &smacros;
1679 m = (SMacro *) hash_findix(smtbl, name);
1681 while (m) {
1682 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1683 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1684 if (defn) {
1685 if (nparam == (int) m->nparam || nparam == -1)
1686 *defn = m;
1687 else
1688 *defn = NULL;
1690 return true;
1692 m = m->next;
1695 return false;
1699 * Count and mark off the parameters in a multi-line macro call.
1700 * This is called both from within the multi-line macro expansion
1701 * code, and also to mark off the default parameters when provided
1702 * in a %macro definition line.
1704 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1706 int paramsize, brace;
1708 *nparam = paramsize = 0;
1709 *params = NULL;
1710 while (t) {
1711 /* +1: we need space for the final NULL */
1712 if (*nparam+1 >= paramsize) {
1713 paramsize += PARAM_DELTA;
1714 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1716 skip_white_(t);
1717 brace = 0;
1718 if (tok_is_(t, "{"))
1719 brace++;
1720 (*params)[(*nparam)++] = t;
1721 if (brace) {
1722 while (brace && (t = t->next) != NULL) {
1723 if (tok_is_(t, "{"))
1724 brace++;
1725 else if (tok_is_(t, "}"))
1726 brace--;
1729 if (t) {
1731 * Now we've found the closing brace, look further
1732 * for the comma.
1734 t = t->next;
1735 skip_white_(t);
1736 if (tok_isnt_(t, ",")) {
1737 nasm_error(ERR_NONFATAL,
1738 "braces do not enclose all of macro parameter");
1739 while (tok_isnt_(t, ","))
1740 t = t->next;
1743 } else {
1744 while (tok_isnt_(t, ","))
1745 t = t->next;
1747 if (t) { /* got a comma/brace */
1748 t = t->next; /* eat the comma */
1754 * Determine whether one of the various `if' conditions is true or
1755 * not.
1757 * We must free the tline we get passed.
1759 static bool if_condition(Token * tline, enum preproc_token ct)
1761 enum pp_conditional i = PP_COND(ct);
1762 bool j;
1763 Token *t, *tt, **tptr, *origline;
1764 struct tokenval tokval;
1765 expr *evalresult;
1766 enum pp_token_type needtype;
1767 char *p;
1769 origline = tline;
1771 switch (i) {
1772 case PPC_IFCTX:
1773 j = false; /* have we matched yet? */
1774 while (true) {
1775 skip_white_(tline);
1776 if (!tline)
1777 break;
1778 if (tline->type != TOK_ID) {
1779 nasm_error(ERR_NONFATAL,
1780 "`%s' expects context identifiers", pp_directives[ct]);
1781 free_tlist(origline);
1782 return -1;
1784 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1785 j = true;
1786 tline = tline->next;
1788 break;
1790 case PPC_IFDEF:
1791 j = false; /* have we matched yet? */
1792 while (tline) {
1793 skip_white_(tline);
1794 if (!tline || (tline->type != TOK_ID &&
1795 (tline->type != TOK_PREPROC_ID ||
1796 tline->text[1] != '$'))) {
1797 nasm_error(ERR_NONFATAL,
1798 "`%s' expects macro identifiers", pp_directives[ct]);
1799 goto fail;
1801 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1802 j = true;
1803 tline = tline->next;
1805 break;
1807 case PPC_IFENV:
1808 tline = expand_smacro(tline);
1809 j = false; /* have we matched yet? */
1810 while (tline) {
1811 skip_white_(tline);
1812 if (!tline || (tline->type != TOK_ID &&
1813 tline->type != TOK_STRING &&
1814 (tline->type != TOK_PREPROC_ID ||
1815 tline->text[1] != '!'))) {
1816 nasm_error(ERR_NONFATAL,
1817 "`%s' expects environment variable names",
1818 pp_directives[ct]);
1819 goto fail;
1821 p = tline->text;
1822 if (tline->type == TOK_PREPROC_ID)
1823 p += 2; /* Skip leading %! */
1824 if (*p == '\'' || *p == '\"' || *p == '`')
1825 nasm_unquote_cstr(p, ct);
1826 if (getenv(p))
1827 j = true;
1828 tline = tline->next;
1830 break;
1832 case PPC_IFIDN:
1833 case PPC_IFIDNI:
1834 tline = expand_smacro(tline);
1835 t = tt = tline;
1836 while (tok_isnt_(tt, ","))
1837 tt = tt->next;
1838 if (!tt) {
1839 nasm_error(ERR_NONFATAL,
1840 "`%s' expects two comma-separated arguments",
1841 pp_directives[ct]);
1842 goto fail;
1844 tt = tt->next;
1845 j = true; /* assume equality unless proved not */
1846 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1847 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1848 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1849 pp_directives[ct]);
1850 goto fail;
1852 if (t->type == TOK_WHITESPACE) {
1853 t = t->next;
1854 continue;
1856 if (tt->type == TOK_WHITESPACE) {
1857 tt = tt->next;
1858 continue;
1860 if (tt->type != t->type) {
1861 j = false; /* found mismatching tokens */
1862 break;
1864 /* When comparing strings, need to unquote them first */
1865 if (t->type == TOK_STRING) {
1866 size_t l1 = nasm_unquote(t->text, NULL);
1867 size_t l2 = nasm_unquote(tt->text, NULL);
1869 if (l1 != l2) {
1870 j = false;
1871 break;
1873 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1874 j = false;
1875 break;
1877 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1878 j = false; /* found mismatching tokens */
1879 break;
1882 t = t->next;
1883 tt = tt->next;
1885 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1886 j = false; /* trailing gunk on one end or other */
1887 break;
1889 case PPC_IFMACRO:
1891 bool found = false;
1892 MMacro searching, *mmac;
1894 skip_white_(tline);
1895 tline = expand_id(tline);
1896 if (!tok_type_(tline, TOK_ID)) {
1897 nasm_error(ERR_NONFATAL,
1898 "`%s' expects a macro name", pp_directives[ct]);
1899 goto fail;
1901 searching.name = nasm_strdup(tline->text);
1902 searching.casesense = true;
1903 searching.plus = false;
1904 searching.nolist = false;
1905 searching.in_progress = 0;
1906 searching.max_depth = 0;
1907 searching.rep_nest = NULL;
1908 searching.nparam_min = 0;
1909 searching.nparam_max = INT_MAX;
1910 tline = expand_smacro(tline->next);
1911 skip_white_(tline);
1912 if (!tline) {
1913 } else if (!tok_type_(tline, TOK_NUMBER)) {
1914 nasm_error(ERR_NONFATAL,
1915 "`%s' expects a parameter count or nothing",
1916 pp_directives[ct]);
1917 } else {
1918 searching.nparam_min = searching.nparam_max =
1919 readnum(tline->text, &j);
1920 if (j)
1921 nasm_error(ERR_NONFATAL,
1922 "unable to parse parameter count `%s'",
1923 tline->text);
1925 if (tline && tok_is_(tline->next, "-")) {
1926 tline = tline->next->next;
1927 if (tok_is_(tline, "*"))
1928 searching.nparam_max = INT_MAX;
1929 else if (!tok_type_(tline, TOK_NUMBER))
1930 nasm_error(ERR_NONFATAL,
1931 "`%s' expects a parameter count after `-'",
1932 pp_directives[ct]);
1933 else {
1934 searching.nparam_max = readnum(tline->text, &j);
1935 if (j)
1936 nasm_error(ERR_NONFATAL,
1937 "unable to parse parameter count `%s'",
1938 tline->text);
1939 if (searching.nparam_min > searching.nparam_max)
1940 nasm_error(ERR_NONFATAL,
1941 "minimum parameter count exceeds maximum");
1944 if (tline && tok_is_(tline->next, "+")) {
1945 tline = tline->next;
1946 searching.plus = true;
1948 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1949 while (mmac) {
1950 if (!strcmp(mmac->name, searching.name) &&
1951 (mmac->nparam_min <= searching.nparam_max
1952 || searching.plus)
1953 && (searching.nparam_min <= mmac->nparam_max
1954 || mmac->plus)) {
1955 found = true;
1956 break;
1958 mmac = mmac->next;
1960 if (tline && tline->next)
1961 nasm_error(ERR_WARNING|ERR_PASS1,
1962 "trailing garbage after %%ifmacro ignored");
1963 nasm_free(searching.name);
1964 j = found;
1965 break;
1968 case PPC_IFID:
1969 needtype = TOK_ID;
1970 goto iftype;
1971 case PPC_IFNUM:
1972 needtype = TOK_NUMBER;
1973 goto iftype;
1974 case PPC_IFSTR:
1975 needtype = TOK_STRING;
1976 goto iftype;
1978 iftype:
1979 t = tline = expand_smacro(tline);
1981 while (tok_type_(t, TOK_WHITESPACE) ||
1982 (needtype == TOK_NUMBER &&
1983 tok_type_(t, TOK_OTHER) &&
1984 (t->text[0] == '-' || t->text[0] == '+') &&
1985 !t->text[1]))
1986 t = t->next;
1988 j = tok_type_(t, needtype);
1989 break;
1991 case PPC_IFTOKEN:
1992 t = tline = expand_smacro(tline);
1993 while (tok_type_(t, TOK_WHITESPACE))
1994 t = t->next;
1996 j = false;
1997 if (t) {
1998 t = t->next; /* Skip the actual token */
1999 while (tok_type_(t, TOK_WHITESPACE))
2000 t = t->next;
2001 j = !t; /* Should be nothing left */
2003 break;
2005 case PPC_IFEMPTY:
2006 t = tline = expand_smacro(tline);
2007 while (tok_type_(t, TOK_WHITESPACE))
2008 t = t->next;
2010 j = !t; /* Should be empty */
2011 break;
2013 case PPC_IF:
2014 t = tline = expand_smacro(tline);
2015 tptr = &t;
2016 tokval.t_type = TOKEN_INVALID;
2017 evalresult = evaluate(ppscan, tptr, &tokval,
2018 NULL, pass | CRITICAL, NULL);
2019 if (!evalresult)
2020 return -1;
2021 if (tokval.t_type)
2022 nasm_error(ERR_WARNING|ERR_PASS1,
2023 "trailing garbage after expression ignored");
2024 if (!is_simple(evalresult)) {
2025 nasm_error(ERR_NONFATAL,
2026 "non-constant value given to `%s'", pp_directives[ct]);
2027 goto fail;
2029 j = reloc_value(evalresult) != 0;
2030 break;
2032 default:
2033 nasm_error(ERR_FATAL,
2034 "preprocessor directive `%s' not yet implemented",
2035 pp_directives[ct]);
2036 goto fail;
2039 free_tlist(origline);
2040 return j ^ PP_NEGATIVE(ct);
2042 fail:
2043 free_tlist(origline);
2044 return -1;
2048 * Common code for defining an smacro
2050 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2051 int nparam, Token *expansion)
2053 SMacro *smac, **smhead;
2054 struct hash_table *smtbl;
2056 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2057 if (!smac) {
2058 nasm_error(ERR_WARNING|ERR_PASS1,
2059 "single-line macro `%s' defined both with and"
2060 " without parameters", mname);
2062 * Some instances of the old code considered this a failure,
2063 * some others didn't. What is the right thing to do here?
2065 free_tlist(expansion);
2066 return false; /* Failure */
2067 } else {
2069 * We're redefining, so we have to take over an
2070 * existing SMacro structure. This means freeing
2071 * what was already in it.
2073 nasm_free(smac->name);
2074 free_tlist(smac->expansion);
2076 } else {
2077 smtbl = ctx ? &ctx->localmac : &smacros;
2078 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2079 smac = nasm_malloc(sizeof(SMacro));
2080 smac->next = *smhead;
2081 *smhead = smac;
2083 smac->name = nasm_strdup(mname);
2084 smac->casesense = casesense;
2085 smac->nparam = nparam;
2086 smac->expansion = expansion;
2087 smac->in_progress = false;
2088 return true; /* Success */
2092 * Undefine an smacro
2094 static void undef_smacro(Context *ctx, const char *mname)
2096 SMacro **smhead, *s, **sp;
2097 struct hash_table *smtbl;
2099 smtbl = ctx ? &ctx->localmac : &smacros;
2100 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2102 if (smhead) {
2104 * We now have a macro name... go hunt for it.
2106 sp = smhead;
2107 while ((s = *sp) != NULL) {
2108 if (!mstrcmp(s->name, mname, s->casesense)) {
2109 *sp = s->next;
2110 nasm_free(s->name);
2111 free_tlist(s->expansion);
2112 nasm_free(s);
2113 } else {
2114 sp = &s->next;
2121 * Parse a mmacro specification.
2123 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2125 bool err;
2127 tline = tline->next;
2128 skip_white_(tline);
2129 tline = expand_id(tline);
2130 if (!tok_type_(tline, TOK_ID)) {
2131 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2132 return false;
2135 def->prev = NULL;
2136 def->name = nasm_strdup(tline->text);
2137 def->plus = false;
2138 def->nolist = false;
2139 def->in_progress = 0;
2140 def->rep_nest = NULL;
2141 def->nparam_min = 0;
2142 def->nparam_max = 0;
2144 tline = expand_smacro(tline->next);
2145 skip_white_(tline);
2146 if (!tok_type_(tline, TOK_NUMBER)) {
2147 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2148 } else {
2149 def->nparam_min = def->nparam_max =
2150 readnum(tline->text, &err);
2151 if (err)
2152 nasm_error(ERR_NONFATAL,
2153 "unable to parse parameter count `%s'", tline->text);
2155 if (tline && tok_is_(tline->next, "-")) {
2156 tline = tline->next->next;
2157 if (tok_is_(tline, "*")) {
2158 def->nparam_max = INT_MAX;
2159 } else if (!tok_type_(tline, TOK_NUMBER)) {
2160 nasm_error(ERR_NONFATAL,
2161 "`%s' expects a parameter count after `-'", directive);
2162 } else {
2163 def->nparam_max = readnum(tline->text, &err);
2164 if (err) {
2165 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2166 tline->text);
2168 if (def->nparam_min > def->nparam_max) {
2169 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2173 if (tline && tok_is_(tline->next, "+")) {
2174 tline = tline->next;
2175 def->plus = true;
2177 if (tline && tok_type_(tline->next, TOK_ID) &&
2178 !nasm_stricmp(tline->next->text, ".nolist")) {
2179 tline = tline->next;
2180 def->nolist = true;
2184 * Handle default parameters.
2186 if (tline && tline->next) {
2187 def->dlist = tline->next;
2188 tline->next = NULL;
2189 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2190 } else {
2191 def->dlist = NULL;
2192 def->defaults = NULL;
2194 def->expansion = NULL;
2196 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2197 !def->plus)
2198 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2199 "too many default macro parameters");
2201 return true;
2206 * Decode a size directive
2208 static int parse_size(const char *str) {
2209 static const char *size_names[] =
2210 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2211 static const int sizes[] =
2212 { 0, 1, 4, 16, 8, 10, 2, 32 };
2214 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2218 * Process a preprocessor %pragma directive. Currently there are none.
2219 * Gets passed the token list starting with the "preproc" token from
2220 * "%pragma preproc".
2222 static void do_pragma_preproc(Token *tline)
2224 /* Skip to the real stuff */
2225 tline = tline->next;
2226 skip_white_(tline);
2227 if (!tline)
2228 return;
2230 (void)tline; /* Nothing else to do at present */
2234 * find and process preprocessor directive in passed line
2235 * Find out if a line contains a preprocessor directive, and deal
2236 * with it if so.
2238 * If a directive _is_ found, it is the responsibility of this routine
2239 * (and not the caller) to free_tlist() the line.
2241 * @param tline a pointer to the current tokeninzed line linked list
2242 * @param output if this directive generated output
2243 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2246 static int do_directive(Token *tline, char **output)
2248 enum preproc_token i;
2249 int j;
2250 bool err;
2251 int nparam;
2252 bool nolist;
2253 bool casesense;
2254 int k, m;
2255 int offset;
2256 char *p, *pp;
2257 const char *found_path;
2258 const char *mname;
2259 Include *inc;
2260 Context *ctx;
2261 Cond *cond;
2262 MMacro *mmac, **mmhead;
2263 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2264 Line *l;
2265 struct tokenval tokval;
2266 expr *evalresult;
2267 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2268 int64_t count;
2269 size_t len;
2270 int severity;
2272 *output = NULL; /* No output generated */
2273 origline = tline;
2275 skip_white_(tline);
2276 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2277 (tline->text[1] == '%' || tline->text[1] == '$'
2278 || tline->text[1] == '!'))
2279 return NO_DIRECTIVE_FOUND;
2281 i = pp_token_hash(tline->text);
2284 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2285 * since they are known to be buggy at moment, we need to fix them
2286 * in future release (2.09-2.10)
2288 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2289 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2290 tline->text);
2291 return NO_DIRECTIVE_FOUND;
2295 * If we're in a non-emitting branch of a condition construct,
2296 * or walking to the end of an already terminated %rep block,
2297 * we should ignore all directives except for condition
2298 * directives.
2300 if (((istk->conds && !emitting(istk->conds->state)) ||
2301 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2302 return NO_DIRECTIVE_FOUND;
2306 * If we're defining a macro or reading a %rep block, we should
2307 * ignore all directives except for %macro/%imacro (which nest),
2308 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2309 * If we're in a %rep block, another %rep nests, so should be let through.
2311 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2312 i != PP_RMACRO && i != PP_IRMACRO &&
2313 i != PP_ENDMACRO && i != PP_ENDM &&
2314 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2315 return NO_DIRECTIVE_FOUND;
2318 if (defining) {
2319 if (i == PP_MACRO || i == PP_IMACRO ||
2320 i == PP_RMACRO || i == PP_IRMACRO) {
2321 nested_mac_count++;
2322 return NO_DIRECTIVE_FOUND;
2323 } else if (nested_mac_count > 0) {
2324 if (i == PP_ENDMACRO) {
2325 nested_mac_count--;
2326 return NO_DIRECTIVE_FOUND;
2329 if (!defining->name) {
2330 if (i == PP_REP) {
2331 nested_rep_count++;
2332 return NO_DIRECTIVE_FOUND;
2333 } else if (nested_rep_count > 0) {
2334 if (i == PP_ENDREP) {
2335 nested_rep_count--;
2336 return NO_DIRECTIVE_FOUND;
2342 switch (i) {
2343 case PP_INVALID:
2344 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2345 tline->text);
2346 return NO_DIRECTIVE_FOUND; /* didn't get it */
2348 case PP_PRAGMA:
2350 * %pragma namespace options...
2352 * The namespace "preproc" is reserved for the preprocessor;
2353 * all other namespaces generate a [pragma] assembly directive.
2355 * Invalid %pragmas are ignored and may have different
2356 * meaning in future versions of NASM.
2358 tline = tline->next;
2359 skip_white_(tline);
2360 tline = expand_smacro(tline);
2361 if (tok_type_(tline, TOK_ID)) {
2362 if (!nasm_stricmp(tline->text, "preproc")) {
2363 /* Preprocessor pragma */
2364 do_pragma_preproc(tline);
2365 } else {
2366 /* Build the assembler directive */
2367 t = new_Token(NULL, TOK_OTHER, "[", 1);
2368 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2369 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2370 tline = t;
2371 for (t = tline; t->next; t = t->next)
2373 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2374 /* true here can be revisited in the future */
2375 *output = detoken(tline, true);
2378 free_tlist(origline);
2379 return DIRECTIVE_FOUND;
2381 case PP_STACKSIZE:
2382 /* Directive to tell NASM what the default stack size is. The
2383 * default is for a 16-bit stack, and this can be overriden with
2384 * %stacksize large.
2386 tline = tline->next;
2387 if (tline && tline->type == TOK_WHITESPACE)
2388 tline = tline->next;
2389 if (!tline || tline->type != TOK_ID) {
2390 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2391 free_tlist(origline);
2392 return DIRECTIVE_FOUND;
2394 if (nasm_stricmp(tline->text, "flat") == 0) {
2395 /* All subsequent ARG directives are for a 32-bit stack */
2396 StackSize = 4;
2397 StackPointer = "ebp";
2398 ArgOffset = 8;
2399 LocalOffset = 0;
2400 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2401 /* All subsequent ARG directives are for a 64-bit stack */
2402 StackSize = 8;
2403 StackPointer = "rbp";
2404 ArgOffset = 16;
2405 LocalOffset = 0;
2406 } else if (nasm_stricmp(tline->text, "large") == 0) {
2407 /* All subsequent ARG directives are for a 16-bit stack,
2408 * far function call.
2410 StackSize = 2;
2411 StackPointer = "bp";
2412 ArgOffset = 4;
2413 LocalOffset = 0;
2414 } else if (nasm_stricmp(tline->text, "small") == 0) {
2415 /* All subsequent ARG directives are for a 16-bit stack,
2416 * far function call. We don't support near functions.
2418 StackSize = 2;
2419 StackPointer = "bp";
2420 ArgOffset = 6;
2421 LocalOffset = 0;
2422 } else {
2423 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2424 free_tlist(origline);
2425 return DIRECTIVE_FOUND;
2427 free_tlist(origline);
2428 return DIRECTIVE_FOUND;
2430 case PP_ARG:
2431 /* TASM like ARG directive to define arguments to functions, in
2432 * the following form:
2434 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2436 offset = ArgOffset;
2437 do {
2438 char *arg, directive[256];
2439 int size = StackSize;
2441 /* Find the argument name */
2442 tline = tline->next;
2443 if (tline && tline->type == TOK_WHITESPACE)
2444 tline = tline->next;
2445 if (!tline || tline->type != TOK_ID) {
2446 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2447 free_tlist(origline);
2448 return DIRECTIVE_FOUND;
2450 arg = tline->text;
2452 /* Find the argument size type */
2453 tline = tline->next;
2454 if (!tline || tline->type != TOK_OTHER
2455 || tline->text[0] != ':') {
2456 nasm_error(ERR_NONFATAL,
2457 "Syntax error processing `%%arg' directive");
2458 free_tlist(origline);
2459 return DIRECTIVE_FOUND;
2461 tline = tline->next;
2462 if (!tline || tline->type != TOK_ID) {
2463 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2464 free_tlist(origline);
2465 return DIRECTIVE_FOUND;
2468 /* Allow macro expansion of type parameter */
2469 tt = tokenize(tline->text);
2470 tt = expand_smacro(tt);
2471 size = parse_size(tt->text);
2472 if (!size) {
2473 nasm_error(ERR_NONFATAL,
2474 "Invalid size type for `%%arg' missing directive");
2475 free_tlist(tt);
2476 free_tlist(origline);
2477 return DIRECTIVE_FOUND;
2479 free_tlist(tt);
2481 /* Round up to even stack slots */
2482 size = ALIGN(size, StackSize);
2484 /* Now define the macro for the argument */
2485 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2486 arg, StackPointer, offset);
2487 do_directive(tokenize(directive), output);
2488 offset += size;
2490 /* Move to the next argument in the list */
2491 tline = tline->next;
2492 if (tline && tline->type == TOK_WHITESPACE)
2493 tline = tline->next;
2494 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2495 ArgOffset = offset;
2496 free_tlist(origline);
2497 return DIRECTIVE_FOUND;
2499 case PP_LOCAL:
2500 /* TASM like LOCAL directive to define local variables for a
2501 * function, in the following form:
2503 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2505 * The '= LocalSize' at the end is ignored by NASM, but is
2506 * required by TASM to define the local parameter size (and used
2507 * by the TASM macro package).
2509 offset = LocalOffset;
2510 do {
2511 char *local, directive[256];
2512 int size = StackSize;
2514 /* Find the argument name */
2515 tline = tline->next;
2516 if (tline && tline->type == TOK_WHITESPACE)
2517 tline = tline->next;
2518 if (!tline || tline->type != TOK_ID) {
2519 nasm_error(ERR_NONFATAL,
2520 "`%%local' missing argument parameter");
2521 free_tlist(origline);
2522 return DIRECTIVE_FOUND;
2524 local = tline->text;
2526 /* Find the argument size type */
2527 tline = tline->next;
2528 if (!tline || tline->type != TOK_OTHER
2529 || tline->text[0] != ':') {
2530 nasm_error(ERR_NONFATAL,
2531 "Syntax error processing `%%local' directive");
2532 free_tlist(origline);
2533 return DIRECTIVE_FOUND;
2535 tline = tline->next;
2536 if (!tline || tline->type != TOK_ID) {
2537 nasm_error(ERR_NONFATAL,
2538 "`%%local' missing size type parameter");
2539 free_tlist(origline);
2540 return DIRECTIVE_FOUND;
2543 /* Allow macro expansion of type parameter */
2544 tt = tokenize(tline->text);
2545 tt = expand_smacro(tt);
2546 size = parse_size(tt->text);
2547 if (!size) {
2548 nasm_error(ERR_NONFATAL,
2549 "Invalid size type for `%%local' missing directive");
2550 free_tlist(tt);
2551 free_tlist(origline);
2552 return DIRECTIVE_FOUND;
2554 free_tlist(tt);
2556 /* Round up to even stack slots */
2557 size = ALIGN(size, StackSize);
2559 offset += size; /* Negative offset, increment before */
2561 /* Now define the macro for the argument */
2562 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2563 local, StackPointer, offset);
2564 do_directive(tokenize(directive), output);
2566 /* Now define the assign to setup the enter_c macro correctly */
2567 snprintf(directive, sizeof(directive),
2568 "%%assign %%$localsize %%$localsize+%d", size);
2569 do_directive(tokenize(directive), output);
2571 /* Move to the next argument in the list */
2572 tline = tline->next;
2573 if (tline && tline->type == TOK_WHITESPACE)
2574 tline = tline->next;
2575 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2576 LocalOffset = offset;
2577 free_tlist(origline);
2578 return DIRECTIVE_FOUND;
2580 case PP_CLEAR:
2581 if (tline->next)
2582 nasm_error(ERR_WARNING|ERR_PASS1,
2583 "trailing garbage after `%%clear' ignored");
2584 free_macros();
2585 init_macros();
2586 free_tlist(origline);
2587 return DIRECTIVE_FOUND;
2589 case PP_DEPEND:
2590 t = tline->next = expand_smacro(tline->next);
2591 skip_white_(t);
2592 if (!t || (t->type != TOK_STRING &&
2593 t->type != TOK_INTERNAL_STRING)) {
2594 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2595 free_tlist(origline);
2596 return DIRECTIVE_FOUND; /* but we did _something_ */
2598 if (t->next)
2599 nasm_error(ERR_WARNING|ERR_PASS1,
2600 "trailing garbage after `%%depend' ignored");
2601 p = t->text;
2602 if (t->type != TOK_INTERNAL_STRING)
2603 nasm_unquote_cstr(p, i);
2604 nasm_add_string_to_strlist(dephead, p);
2605 free_tlist(origline);
2606 return DIRECTIVE_FOUND;
2608 case PP_INCLUDE:
2609 t = tline->next = expand_smacro(tline->next);
2610 skip_white_(t);
2612 if (!t || (t->type != TOK_STRING &&
2613 t->type != TOK_INTERNAL_STRING)) {
2614 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2615 free_tlist(origline);
2616 return DIRECTIVE_FOUND; /* but we did _something_ */
2618 if (t->next)
2619 nasm_error(ERR_WARNING|ERR_PASS1,
2620 "trailing garbage after `%%include' ignored");
2621 p = t->text;
2622 if (t->type != TOK_INTERNAL_STRING)
2623 nasm_unquote_cstr(p, i);
2624 inc = nasm_malloc(sizeof(Include));
2625 inc->next = istk;
2626 inc->conds = NULL;
2627 found_path = NULL;
2628 inc->fp = inc_fopen(p, dephead, &found_path,
2629 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2630 if (!inc->fp) {
2631 /* -MG given but file not found */
2632 nasm_free(inc);
2633 } else {
2634 inc->fname = src_set_fname(found_path ? found_path : p);
2635 inc->lineno = src_set_linnum(0);
2636 inc->lineinc = 1;
2637 inc->expansion = NULL;
2638 inc->mstk = NULL;
2639 istk = inc;
2640 lfmt->uplevel(LIST_INCLUDE);
2642 free_tlist(origline);
2643 return DIRECTIVE_FOUND;
2645 case PP_USE:
2647 static macros_t *use_pkg;
2648 const char *pkg_macro = NULL;
2650 tline = tline->next;
2651 skip_white_(tline);
2652 tline = expand_id(tline);
2654 if (!tline || (tline->type != TOK_STRING &&
2655 tline->type != TOK_INTERNAL_STRING &&
2656 tline->type != TOK_ID)) {
2657 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2658 free_tlist(origline);
2659 return DIRECTIVE_FOUND; /* but we did _something_ */
2661 if (tline->next)
2662 nasm_error(ERR_WARNING|ERR_PASS1,
2663 "trailing garbage after `%%use' ignored");
2664 if (tline->type == TOK_STRING)
2665 nasm_unquote_cstr(tline->text, i);
2666 use_pkg = nasm_stdmac_find_package(tline->text);
2667 if (!use_pkg)
2668 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2669 else
2670 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2671 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2672 /* Not already included, go ahead and include it */
2673 stdmacpos = use_pkg;
2675 free_tlist(origline);
2676 return DIRECTIVE_FOUND;
2678 case PP_PUSH:
2679 case PP_REPL:
2680 case PP_POP:
2681 tline = tline->next;
2682 skip_white_(tline);
2683 tline = expand_id(tline);
2684 if (tline) {
2685 if (!tok_type_(tline, TOK_ID)) {
2686 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2687 pp_directives[i]);
2688 free_tlist(origline);
2689 return DIRECTIVE_FOUND; /* but we did _something_ */
2691 if (tline->next)
2692 nasm_error(ERR_WARNING|ERR_PASS1,
2693 "trailing garbage after `%s' ignored",
2694 pp_directives[i]);
2695 p = nasm_strdup(tline->text);
2696 } else {
2697 p = NULL; /* Anonymous */
2700 if (i == PP_PUSH) {
2701 ctx = nasm_malloc(sizeof(Context));
2702 ctx->next = cstk;
2703 hash_init(&ctx->localmac, HASH_SMALL);
2704 ctx->name = p;
2705 ctx->number = unique++;
2706 cstk = ctx;
2707 } else {
2708 /* %pop or %repl */
2709 if (!cstk) {
2710 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2711 pp_directives[i]);
2712 } else if (i == PP_POP) {
2713 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2714 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2715 "expected %s",
2716 cstk->name ? cstk->name : "anonymous", p);
2717 else
2718 ctx_pop();
2719 } else {
2720 /* i == PP_REPL */
2721 nasm_free(cstk->name);
2722 cstk->name = p;
2723 p = NULL;
2725 nasm_free(p);
2727 free_tlist(origline);
2728 return DIRECTIVE_FOUND;
2729 case PP_FATAL:
2730 severity = ERR_FATAL;
2731 goto issue_error;
2732 case PP_ERROR:
2733 severity = ERR_NONFATAL;
2734 goto issue_error;
2735 case PP_WARNING:
2736 severity = ERR_WARNING|ERR_WARN_USER;
2737 goto issue_error;
2739 issue_error:
2741 /* Only error out if this is the final pass */
2742 if (pass != 2 && i != PP_FATAL)
2743 return DIRECTIVE_FOUND;
2745 tline->next = expand_smacro(tline->next);
2746 tline = tline->next;
2747 skip_white_(tline);
2748 t = tline ? tline->next : NULL;
2749 skip_white_(t);
2750 if (tok_type_(tline, TOK_STRING) && !t) {
2751 /* The line contains only a quoted string */
2752 p = tline->text;
2753 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2754 nasm_error(severity, "%s", p);
2755 } else {
2756 /* Not a quoted string, or more than a quoted string */
2757 p = detoken(tline, false);
2758 nasm_error(severity, "%s", p);
2759 nasm_free(p);
2761 free_tlist(origline);
2762 return DIRECTIVE_FOUND;
2765 CASE_PP_IF:
2766 if (istk->conds && !emitting(istk->conds->state))
2767 j = COND_NEVER;
2768 else {
2769 j = if_condition(tline->next, i);
2770 tline->next = NULL; /* it got freed */
2771 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2773 cond = nasm_malloc(sizeof(Cond));
2774 cond->next = istk->conds;
2775 cond->state = j;
2776 istk->conds = cond;
2777 if(istk->mstk)
2778 istk->mstk->condcnt ++;
2779 free_tlist(origline);
2780 return DIRECTIVE_FOUND;
2782 CASE_PP_ELIF:
2783 if (!istk->conds)
2784 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2785 switch(istk->conds->state) {
2786 case COND_IF_TRUE:
2787 istk->conds->state = COND_DONE;
2788 break;
2790 case COND_DONE:
2791 case COND_NEVER:
2792 break;
2794 case COND_ELSE_TRUE:
2795 case COND_ELSE_FALSE:
2796 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2797 "`%%elif' after `%%else' ignored");
2798 istk->conds->state = COND_NEVER;
2799 break;
2801 case COND_IF_FALSE:
2803 * IMPORTANT: In the case of %if, we will already have
2804 * called expand_mmac_params(); however, if we're
2805 * processing an %elif we must have been in a
2806 * non-emitting mode, which would have inhibited
2807 * the normal invocation of expand_mmac_params().
2808 * Therefore, we have to do it explicitly here.
2810 j = if_condition(expand_mmac_params(tline->next), i);
2811 tline->next = NULL; /* it got freed */
2812 istk->conds->state =
2813 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2814 break;
2816 free_tlist(origline);
2817 return DIRECTIVE_FOUND;
2819 case PP_ELSE:
2820 if (tline->next)
2821 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2822 "trailing garbage after `%%else' ignored");
2823 if (!istk->conds)
2824 nasm_fatal(0, "`%%else: no matching `%%if'");
2825 switch(istk->conds->state) {
2826 case COND_IF_TRUE:
2827 case COND_DONE:
2828 istk->conds->state = COND_ELSE_FALSE;
2829 break;
2831 case COND_NEVER:
2832 break;
2834 case COND_IF_FALSE:
2835 istk->conds->state = COND_ELSE_TRUE;
2836 break;
2838 case COND_ELSE_TRUE:
2839 case COND_ELSE_FALSE:
2840 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2841 "`%%else' after `%%else' ignored.");
2842 istk->conds->state = COND_NEVER;
2843 break;
2845 free_tlist(origline);
2846 return DIRECTIVE_FOUND;
2848 case PP_ENDIF:
2849 if (tline->next)
2850 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2851 "trailing garbage after `%%endif' ignored");
2852 if (!istk->conds)
2853 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2854 cond = istk->conds;
2855 istk->conds = cond->next;
2856 nasm_free(cond);
2857 if(istk->mstk)
2858 istk->mstk->condcnt --;
2859 free_tlist(origline);
2860 return DIRECTIVE_FOUND;
2862 case PP_RMACRO:
2863 case PP_IRMACRO:
2864 case PP_MACRO:
2865 case PP_IMACRO:
2866 if (defining) {
2867 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2868 pp_directives[i]);
2869 return DIRECTIVE_FOUND;
2871 defining = nasm_zalloc(sizeof(MMacro));
2872 defining->max_depth =
2873 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2874 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2875 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2876 nasm_free(defining);
2877 defining = NULL;
2878 return DIRECTIVE_FOUND;
2881 src_get(&defining->xline, &defining->fname);
2883 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2884 while (mmac) {
2885 if (!strcmp(mmac->name, defining->name) &&
2886 (mmac->nparam_min <= defining->nparam_max
2887 || defining->plus)
2888 && (defining->nparam_min <= mmac->nparam_max
2889 || mmac->plus)) {
2890 nasm_error(ERR_WARNING|ERR_PASS1,
2891 "redefining multi-line macro `%s'", defining->name);
2892 return DIRECTIVE_FOUND;
2894 mmac = mmac->next;
2896 free_tlist(origline);
2897 return DIRECTIVE_FOUND;
2899 case PP_ENDM:
2900 case PP_ENDMACRO:
2901 if (! (defining && defining->name)) {
2902 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2903 return DIRECTIVE_FOUND;
2905 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2906 defining->next = *mmhead;
2907 *mmhead = defining;
2908 defining = NULL;
2909 free_tlist(origline);
2910 return DIRECTIVE_FOUND;
2912 case PP_EXITMACRO:
2914 * We must search along istk->expansion until we hit a
2915 * macro-end marker for a macro with a name. Then we
2916 * bypass all lines between exitmacro and endmacro.
2918 list_for_each(l, istk->expansion)
2919 if (l->finishes && l->finishes->name)
2920 break;
2922 if (l) {
2924 * Remove all conditional entries relative to this
2925 * macro invocation. (safe to do in this context)
2927 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2928 cond = istk->conds;
2929 istk->conds = cond->next;
2930 nasm_free(cond);
2932 istk->expansion = l;
2933 } else {
2934 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2936 free_tlist(origline);
2937 return DIRECTIVE_FOUND;
2939 case PP_UNMACRO:
2940 case PP_UNIMACRO:
2942 MMacro **mmac_p;
2943 MMacro spec;
2945 spec.casesense = (i == PP_UNMACRO);
2946 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2947 return DIRECTIVE_FOUND;
2949 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2950 while (mmac_p && *mmac_p) {
2951 mmac = *mmac_p;
2952 if (mmac->casesense == spec.casesense &&
2953 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2954 mmac->nparam_min == spec.nparam_min &&
2955 mmac->nparam_max == spec.nparam_max &&
2956 mmac->plus == spec.plus) {
2957 *mmac_p = mmac->next;
2958 free_mmacro(mmac);
2959 } else {
2960 mmac_p = &mmac->next;
2963 free_tlist(origline);
2964 free_tlist(spec.dlist);
2965 return DIRECTIVE_FOUND;
2968 case PP_ROTATE:
2969 if (tline->next && tline->next->type == TOK_WHITESPACE)
2970 tline = tline->next;
2971 if (!tline->next) {
2972 free_tlist(origline);
2973 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2974 return DIRECTIVE_FOUND;
2976 t = expand_smacro(tline->next);
2977 tline->next = NULL;
2978 free_tlist(origline);
2979 tline = t;
2980 tptr = &t;
2981 tokval.t_type = TOKEN_INVALID;
2982 evalresult =
2983 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2984 free_tlist(tline);
2985 if (!evalresult)
2986 return DIRECTIVE_FOUND;
2987 if (tokval.t_type)
2988 nasm_error(ERR_WARNING|ERR_PASS1,
2989 "trailing garbage after expression ignored");
2990 if (!is_simple(evalresult)) {
2991 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2992 return DIRECTIVE_FOUND;
2994 mmac = istk->mstk;
2995 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2996 mmac = mmac->next_active;
2997 if (!mmac) {
2998 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2999 } else if (mmac->nparam == 0) {
3000 nasm_error(ERR_NONFATAL,
3001 "`%%rotate' invoked within macro without parameters");
3002 } else {
3003 int rotate = mmac->rotate + reloc_value(evalresult);
3005 rotate %= (int)mmac->nparam;
3006 if (rotate < 0)
3007 rotate += mmac->nparam;
3009 mmac->rotate = rotate;
3011 return DIRECTIVE_FOUND;
3013 case PP_REP:
3014 nolist = false;
3015 do {
3016 tline = tline->next;
3017 } while (tok_type_(tline, TOK_WHITESPACE));
3019 if (tok_type_(tline, TOK_ID) &&
3020 nasm_stricmp(tline->text, ".nolist") == 0) {
3021 nolist = true;
3022 do {
3023 tline = tline->next;
3024 } while (tok_type_(tline, TOK_WHITESPACE));
3027 if (tline) {
3028 t = expand_smacro(tline);
3029 tptr = &t;
3030 tokval.t_type = TOKEN_INVALID;
3031 evalresult =
3032 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3033 if (!evalresult) {
3034 free_tlist(origline);
3035 return DIRECTIVE_FOUND;
3037 if (tokval.t_type)
3038 nasm_error(ERR_WARNING|ERR_PASS1,
3039 "trailing garbage after expression ignored");
3040 if (!is_simple(evalresult)) {
3041 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3042 return DIRECTIVE_FOUND;
3044 count = reloc_value(evalresult);
3045 if (count >= REP_LIMIT) {
3046 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3047 count = 0;
3048 } else
3049 count++;
3050 } else {
3051 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3052 count = 0;
3054 free_tlist(origline);
3056 tmp_defining = defining;
3057 defining = nasm_malloc(sizeof(MMacro));
3058 defining->prev = NULL;
3059 defining->name = NULL; /* flags this macro as a %rep block */
3060 defining->casesense = false;
3061 defining->plus = false;
3062 defining->nolist = nolist;
3063 defining->in_progress = count;
3064 defining->max_depth = 0;
3065 defining->nparam_min = defining->nparam_max = 0;
3066 defining->defaults = NULL;
3067 defining->dlist = NULL;
3068 defining->expansion = NULL;
3069 defining->next_active = istk->mstk;
3070 defining->rep_nest = tmp_defining;
3071 return DIRECTIVE_FOUND;
3073 case PP_ENDREP:
3074 if (!defining || defining->name) {
3075 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3076 return DIRECTIVE_FOUND;
3080 * Now we have a "macro" defined - although it has no name
3081 * and we won't be entering it in the hash tables - we must
3082 * push a macro-end marker for it on to istk->expansion.
3083 * After that, it will take care of propagating itself (a
3084 * macro-end marker line for a macro which is really a %rep
3085 * block will cause the macro to be re-expanded, complete
3086 * with another macro-end marker to ensure the process
3087 * continues) until the whole expansion is forcibly removed
3088 * from istk->expansion by a %exitrep.
3090 l = nasm_malloc(sizeof(Line));
3091 l->next = istk->expansion;
3092 l->finishes = defining;
3093 l->first = NULL;
3094 istk->expansion = l;
3096 istk->mstk = defining;
3098 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3099 tmp_defining = defining;
3100 defining = defining->rep_nest;
3101 free_tlist(origline);
3102 return DIRECTIVE_FOUND;
3104 case PP_EXITREP:
3106 * We must search along istk->expansion until we hit a
3107 * macro-end marker for a macro with no name. Then we set
3108 * its `in_progress' flag to 0.
3110 list_for_each(l, istk->expansion)
3111 if (l->finishes && !l->finishes->name)
3112 break;
3114 if (l)
3115 l->finishes->in_progress = 1;
3116 else
3117 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3118 free_tlist(origline);
3119 return DIRECTIVE_FOUND;
3121 case PP_XDEFINE:
3122 case PP_IXDEFINE:
3123 case PP_DEFINE:
3124 case PP_IDEFINE:
3125 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3127 tline = tline->next;
3128 skip_white_(tline);
3129 tline = expand_id(tline);
3130 if (!tline || (tline->type != TOK_ID &&
3131 (tline->type != TOK_PREPROC_ID ||
3132 tline->text[1] != '$'))) {
3133 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3134 pp_directives[i]);
3135 free_tlist(origline);
3136 return DIRECTIVE_FOUND;
3139 ctx = get_ctx(tline->text, &mname);
3140 last = tline;
3141 param_start = tline = tline->next;
3142 nparam = 0;
3144 /* Expand the macro definition now for %xdefine and %ixdefine */
3145 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3146 tline = expand_smacro(tline);
3148 if (tok_is_(tline, "(")) {
3150 * This macro has parameters.
3153 tline = tline->next;
3154 while (1) {
3155 skip_white_(tline);
3156 if (!tline) {
3157 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3158 free_tlist(origline);
3159 return DIRECTIVE_FOUND;
3161 if (tline->type != TOK_ID) {
3162 nasm_error(ERR_NONFATAL,
3163 "`%s': parameter identifier expected",
3164 tline->text);
3165 free_tlist(origline);
3166 return DIRECTIVE_FOUND;
3168 tline->type = TOK_SMAC_PARAM + nparam++;
3169 tline = tline->next;
3170 skip_white_(tline);
3171 if (tok_is_(tline, ",")) {
3172 tline = tline->next;
3173 } else {
3174 if (!tok_is_(tline, ")")) {
3175 nasm_error(ERR_NONFATAL,
3176 "`)' expected to terminate macro template");
3177 free_tlist(origline);
3178 return DIRECTIVE_FOUND;
3180 break;
3183 last = tline;
3184 tline = tline->next;
3186 if (tok_type_(tline, TOK_WHITESPACE))
3187 last = tline, tline = tline->next;
3188 macro_start = NULL;
3189 last->next = NULL;
3190 t = tline;
3191 while (t) {
3192 if (t->type == TOK_ID) {
3193 list_for_each(tt, param_start)
3194 if (tt->type >= TOK_SMAC_PARAM &&
3195 !strcmp(tt->text, t->text))
3196 t->type = tt->type;
3198 tt = t->next;
3199 t->next = macro_start;
3200 macro_start = t;
3201 t = tt;
3204 * Good. We now have a macro name, a parameter count, and a
3205 * token list (in reverse order) for an expansion. We ought
3206 * to be OK just to create an SMacro, store it, and let
3207 * free_tlist have the rest of the line (which we have
3208 * carefully re-terminated after chopping off the expansion
3209 * from the end).
3211 define_smacro(ctx, mname, casesense, nparam, macro_start);
3212 free_tlist(origline);
3213 return DIRECTIVE_FOUND;
3215 case PP_UNDEF:
3216 tline = tline->next;
3217 skip_white_(tline);
3218 tline = expand_id(tline);
3219 if (!tline || (tline->type != TOK_ID &&
3220 (tline->type != TOK_PREPROC_ID ||
3221 tline->text[1] != '$'))) {
3222 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3223 free_tlist(origline);
3224 return DIRECTIVE_FOUND;
3226 if (tline->next) {
3227 nasm_error(ERR_WARNING|ERR_PASS1,
3228 "trailing garbage after macro name ignored");
3231 /* Find the context that symbol belongs to */
3232 ctx = get_ctx(tline->text, &mname);
3233 undef_smacro(ctx, mname);
3234 free_tlist(origline);
3235 return DIRECTIVE_FOUND;
3237 case PP_DEFSTR:
3238 case PP_IDEFSTR:
3239 casesense = (i == PP_DEFSTR);
3241 tline = tline->next;
3242 skip_white_(tline);
3243 tline = expand_id(tline);
3244 if (!tline || (tline->type != TOK_ID &&
3245 (tline->type != TOK_PREPROC_ID ||
3246 tline->text[1] != '$'))) {
3247 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3248 pp_directives[i]);
3249 free_tlist(origline);
3250 return DIRECTIVE_FOUND;
3253 ctx = get_ctx(tline->text, &mname);
3254 last = tline;
3255 tline = expand_smacro(tline->next);
3256 last->next = NULL;
3258 while (tok_type_(tline, TOK_WHITESPACE))
3259 tline = delete_Token(tline);
3261 p = detoken(tline, false);
3262 macro_start = nasm_malloc(sizeof(*macro_start));
3263 macro_start->next = NULL;
3264 macro_start->text = nasm_quote(p, strlen(p));
3265 macro_start->type = TOK_STRING;
3266 macro_start->a.mac = NULL;
3267 nasm_free(p);
3270 * We now have a macro name, an implicit parameter count of
3271 * zero, and a string token to use as an expansion. Create
3272 * and store an SMacro.
3274 define_smacro(ctx, mname, casesense, 0, macro_start);
3275 free_tlist(origline);
3276 return DIRECTIVE_FOUND;
3278 case PP_DEFTOK:
3279 case PP_IDEFTOK:
3280 casesense = (i == PP_DEFTOK);
3282 tline = tline->next;
3283 skip_white_(tline);
3284 tline = expand_id(tline);
3285 if (!tline || (tline->type != TOK_ID &&
3286 (tline->type != TOK_PREPROC_ID ||
3287 tline->text[1] != '$'))) {
3288 nasm_error(ERR_NONFATAL,
3289 "`%s' expects a macro identifier as first parameter",
3290 pp_directives[i]);
3291 free_tlist(origline);
3292 return DIRECTIVE_FOUND;
3294 ctx = get_ctx(tline->text, &mname);
3295 last = tline;
3296 tline = expand_smacro(tline->next);
3297 last->next = NULL;
3299 t = tline;
3300 while (tok_type_(t, TOK_WHITESPACE))
3301 t = t->next;
3302 /* t should now point to the string */
3303 if (!tok_type_(t, TOK_STRING)) {
3304 nasm_error(ERR_NONFATAL,
3305 "`%s` requires string as second parameter",
3306 pp_directives[i]);
3307 free_tlist(tline);
3308 free_tlist(origline);
3309 return DIRECTIVE_FOUND;
3313 * Convert the string to a token stream. Note that smacros
3314 * are stored with the token stream reversed, so we have to
3315 * reverse the output of tokenize().
3317 nasm_unquote_cstr(t->text, i);
3318 macro_start = reverse_tokens(tokenize(t->text));
3321 * We now have a macro name, an implicit parameter count of
3322 * zero, and a numeric token to use as an expansion. Create
3323 * and store an SMacro.
3325 define_smacro(ctx, mname, casesense, 0, macro_start);
3326 free_tlist(tline);
3327 free_tlist(origline);
3328 return DIRECTIVE_FOUND;
3330 case PP_PATHSEARCH:
3332 const char *found_path;
3334 casesense = true;
3336 tline = tline->next;
3337 skip_white_(tline);
3338 tline = expand_id(tline);
3339 if (!tline || (tline->type != TOK_ID &&
3340 (tline->type != TOK_PREPROC_ID ||
3341 tline->text[1] != '$'))) {
3342 nasm_error(ERR_NONFATAL,
3343 "`%%pathsearch' expects a macro identifier as first parameter");
3344 free_tlist(origline);
3345 return DIRECTIVE_FOUND;
3347 ctx = get_ctx(tline->text, &mname);
3348 last = tline;
3349 tline = expand_smacro(tline->next);
3350 last->next = NULL;
3352 t = tline;
3353 while (tok_type_(t, TOK_WHITESPACE))
3354 t = t->next;
3356 if (!t || (t->type != TOK_STRING &&
3357 t->type != TOK_INTERNAL_STRING)) {
3358 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3359 free_tlist(tline);
3360 free_tlist(origline);
3361 return DIRECTIVE_FOUND; /* but we did _something_ */
3363 if (t->next)
3364 nasm_error(ERR_WARNING|ERR_PASS1,
3365 "trailing garbage after `%%pathsearch' ignored");
3366 p = t->text;
3367 if (t->type != TOK_INTERNAL_STRING)
3368 nasm_unquote(p, NULL);
3370 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3371 if (!found_path)
3372 found_path = p;
3373 macro_start = nasm_malloc(sizeof(*macro_start));
3374 macro_start->next = NULL;
3375 macro_start->text = nasm_quote(found_path, strlen(found_path));
3376 macro_start->type = TOK_STRING;
3377 macro_start->a.mac = NULL;
3380 * We now have a macro name, an implicit parameter count of
3381 * zero, and a string token to use as an expansion. Create
3382 * and store an SMacro.
3384 define_smacro(ctx, mname, casesense, 0, macro_start);
3385 free_tlist(tline);
3386 free_tlist(origline);
3387 return DIRECTIVE_FOUND;
3390 case PP_STRLEN:
3391 casesense = true;
3393 tline = tline->next;
3394 skip_white_(tline);
3395 tline = expand_id(tline);
3396 if (!tline || (tline->type != TOK_ID &&
3397 (tline->type != TOK_PREPROC_ID ||
3398 tline->text[1] != '$'))) {
3399 nasm_error(ERR_NONFATAL,
3400 "`%%strlen' expects a macro identifier as first parameter");
3401 free_tlist(origline);
3402 return DIRECTIVE_FOUND;
3404 ctx = get_ctx(tline->text, &mname);
3405 last = tline;
3406 tline = expand_smacro(tline->next);
3407 last->next = NULL;
3409 t = tline;
3410 while (tok_type_(t, TOK_WHITESPACE))
3411 t = t->next;
3412 /* t should now point to the string */
3413 if (!tok_type_(t, TOK_STRING)) {
3414 nasm_error(ERR_NONFATAL,
3415 "`%%strlen` requires string as second parameter");
3416 free_tlist(tline);
3417 free_tlist(origline);
3418 return DIRECTIVE_FOUND;
3421 macro_start = nasm_malloc(sizeof(*macro_start));
3422 macro_start->next = NULL;
3423 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3424 macro_start->a.mac = NULL;
3427 * We now have a macro name, an implicit parameter count of
3428 * zero, and a numeric token to use as an expansion. Create
3429 * and store an SMacro.
3431 define_smacro(ctx, mname, casesense, 0, macro_start);
3432 free_tlist(tline);
3433 free_tlist(origline);
3434 return DIRECTIVE_FOUND;
3436 case PP_STRCAT:
3437 casesense = true;
3439 tline = tline->next;
3440 skip_white_(tline);
3441 tline = expand_id(tline);
3442 if (!tline || (tline->type != TOK_ID &&
3443 (tline->type != TOK_PREPROC_ID ||
3444 tline->text[1] != '$'))) {
3445 nasm_error(ERR_NONFATAL,
3446 "`%%strcat' expects a macro identifier as first parameter");
3447 free_tlist(origline);
3448 return DIRECTIVE_FOUND;
3450 ctx = get_ctx(tline->text, &mname);
3451 last = tline;
3452 tline = expand_smacro(tline->next);
3453 last->next = NULL;
3455 len = 0;
3456 list_for_each(t, tline) {
3457 switch (t->type) {
3458 case TOK_WHITESPACE:
3459 break;
3460 case TOK_STRING:
3461 len += t->a.len = nasm_unquote(t->text, NULL);
3462 break;
3463 case TOK_OTHER:
3464 if (!strcmp(t->text, ",")) /* permit comma separators */
3465 break;
3466 /* else fall through */
3467 default:
3468 nasm_error(ERR_NONFATAL,
3469 "non-string passed to `%%strcat' (%d)", t->type);
3470 free_tlist(tline);
3471 free_tlist(origline);
3472 return DIRECTIVE_FOUND;
3476 p = pp = nasm_malloc(len);
3477 list_for_each(t, tline) {
3478 if (t->type == TOK_STRING) {
3479 memcpy(p, t->text, t->a.len);
3480 p += t->a.len;
3485 * We now have a macro name, an implicit parameter count of
3486 * zero, and a numeric token to use as an expansion. Create
3487 * and store an SMacro.
3489 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3490 macro_start->text = nasm_quote(pp, len);
3491 nasm_free(pp);
3492 define_smacro(ctx, mname, casesense, 0, macro_start);
3493 free_tlist(tline);
3494 free_tlist(origline);
3495 return DIRECTIVE_FOUND;
3497 case PP_SUBSTR:
3499 int64_t start, count;
3500 size_t len;
3502 casesense = true;
3504 tline = tline->next;
3505 skip_white_(tline);
3506 tline = expand_id(tline);
3507 if (!tline || (tline->type != TOK_ID &&
3508 (tline->type != TOK_PREPROC_ID ||
3509 tline->text[1] != '$'))) {
3510 nasm_error(ERR_NONFATAL,
3511 "`%%substr' expects a macro identifier as first parameter");
3512 free_tlist(origline);
3513 return DIRECTIVE_FOUND;
3515 ctx = get_ctx(tline->text, &mname);
3516 last = tline;
3517 tline = expand_smacro(tline->next);
3518 last->next = NULL;
3520 if (tline) /* skip expanded id */
3521 t = tline->next;
3522 while (tok_type_(t, TOK_WHITESPACE))
3523 t = t->next;
3525 /* t should now point to the string */
3526 if (!tok_type_(t, TOK_STRING)) {
3527 nasm_error(ERR_NONFATAL,
3528 "`%%substr` requires string as second parameter");
3529 free_tlist(tline);
3530 free_tlist(origline);
3531 return DIRECTIVE_FOUND;
3534 tt = t->next;
3535 tptr = &tt;
3536 tokval.t_type = TOKEN_INVALID;
3537 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3538 if (!evalresult) {
3539 free_tlist(tline);
3540 free_tlist(origline);
3541 return DIRECTIVE_FOUND;
3542 } else if (!is_simple(evalresult)) {
3543 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3544 free_tlist(tline);
3545 free_tlist(origline);
3546 return DIRECTIVE_FOUND;
3548 start = evalresult->value - 1;
3550 while (tok_type_(tt, TOK_WHITESPACE))
3551 tt = tt->next;
3552 if (!tt) {
3553 count = 1; /* Backwards compatibility: one character */
3554 } else {
3555 tokval.t_type = TOKEN_INVALID;
3556 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3557 if (!evalresult) {
3558 free_tlist(tline);
3559 free_tlist(origline);
3560 return DIRECTIVE_FOUND;
3561 } else if (!is_simple(evalresult)) {
3562 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3563 free_tlist(tline);
3564 free_tlist(origline);
3565 return DIRECTIVE_FOUND;
3567 count = evalresult->value;
3570 len = nasm_unquote(t->text, NULL);
3572 /* make start and count being in range */
3573 if (start < 0)
3574 start = 0;
3575 if (count < 0)
3576 count = len + count + 1 - start;
3577 if (start + count > (int64_t)len)
3578 count = len - start;
3579 if (!len || count < 0 || start >=(int64_t)len)
3580 start = -1, count = 0; /* empty string */
3582 macro_start = nasm_malloc(sizeof(*macro_start));
3583 macro_start->next = NULL;
3584 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3585 macro_start->type = TOK_STRING;
3586 macro_start->a.mac = NULL;
3589 * We now have a macro name, an implicit parameter count of
3590 * zero, and a numeric token to use as an expansion. Create
3591 * and store an SMacro.
3593 define_smacro(ctx, mname, casesense, 0, macro_start);
3594 free_tlist(tline);
3595 free_tlist(origline);
3596 return DIRECTIVE_FOUND;
3599 case PP_ASSIGN:
3600 case PP_IASSIGN:
3601 casesense = (i == PP_ASSIGN);
3603 tline = tline->next;
3604 skip_white_(tline);
3605 tline = expand_id(tline);
3606 if (!tline || (tline->type != TOK_ID &&
3607 (tline->type != TOK_PREPROC_ID ||
3608 tline->text[1] != '$'))) {
3609 nasm_error(ERR_NONFATAL,
3610 "`%%%sassign' expects a macro identifier",
3611 (i == PP_IASSIGN ? "i" : ""));
3612 free_tlist(origline);
3613 return DIRECTIVE_FOUND;
3615 ctx = get_ctx(tline->text, &mname);
3616 last = tline;
3617 tline = expand_smacro(tline->next);
3618 last->next = NULL;
3620 t = tline;
3621 tptr = &t;
3622 tokval.t_type = TOKEN_INVALID;
3623 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3624 free_tlist(tline);
3625 if (!evalresult) {
3626 free_tlist(origline);
3627 return DIRECTIVE_FOUND;
3630 if (tokval.t_type)
3631 nasm_error(ERR_WARNING|ERR_PASS1,
3632 "trailing garbage after expression ignored");
3634 if (!is_simple(evalresult)) {
3635 nasm_error(ERR_NONFATAL,
3636 "non-constant value given to `%%%sassign'",
3637 (i == PP_IASSIGN ? "i" : ""));
3638 free_tlist(origline);
3639 return DIRECTIVE_FOUND;
3642 macro_start = nasm_malloc(sizeof(*macro_start));
3643 macro_start->next = NULL;
3644 make_tok_num(macro_start, reloc_value(evalresult));
3645 macro_start->a.mac = NULL;
3648 * We now have a macro name, an implicit parameter count of
3649 * zero, and a numeric token to use as an expansion. Create
3650 * and store an SMacro.
3652 define_smacro(ctx, mname, casesense, 0, macro_start);
3653 free_tlist(origline);
3654 return DIRECTIVE_FOUND;
3656 case PP_LINE:
3658 * Syntax is `%line nnn[+mmm] [filename]'
3660 tline = tline->next;
3661 skip_white_(tline);
3662 if (!tok_type_(tline, TOK_NUMBER)) {
3663 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3664 free_tlist(origline);
3665 return DIRECTIVE_FOUND;
3667 k = readnum(tline->text, &err);
3668 m = 1;
3669 tline = tline->next;
3670 if (tok_is_(tline, "+")) {
3671 tline = tline->next;
3672 if (!tok_type_(tline, TOK_NUMBER)) {
3673 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3674 free_tlist(origline);
3675 return DIRECTIVE_FOUND;
3677 m = readnum(tline->text, &err);
3678 tline = tline->next;
3680 skip_white_(tline);
3681 src_set_linnum(k);
3682 istk->lineinc = m;
3683 if (tline) {
3684 char *fname = detoken(tline, false);
3685 src_set_fname(fname);
3686 nasm_free(fname);
3688 free_tlist(origline);
3689 return DIRECTIVE_FOUND;
3691 default:
3692 nasm_error(ERR_FATAL,
3693 "preprocessor directive `%s' not yet implemented",
3694 pp_directives[i]);
3695 return DIRECTIVE_FOUND;
3700 * Ensure that a macro parameter contains a condition code and
3701 * nothing else. Return the condition code index if so, or -1
3702 * otherwise.
3704 static int find_cc(Token * t)
3706 Token *tt;
3708 if (!t)
3709 return -1; /* Probably a %+ without a space */
3711 skip_white_(t);
3712 if (t->type != TOK_ID)
3713 return -1;
3714 tt = t->next;
3715 skip_white_(tt);
3716 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3717 return -1;
3719 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3723 * This routines walks over tokens strem and hadnles tokens
3724 * pasting, if @handle_explicit passed then explicit pasting
3725 * term is handled, otherwise -- implicit pastings only.
3727 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3728 size_t mnum, bool handle_explicit)
3730 Token *tok, *next, **prev_next, **prev_nonspace;
3731 bool pasted = false;
3732 char *buf, *p;
3733 size_t len, i;
3736 * The last token before pasting. We need it
3737 * to be able to connect new handled tokens.
3738 * In other words if there were a tokens stream
3740 * A -> B -> C -> D
3742 * and we've joined tokens B and C, the resulting
3743 * stream should be
3745 * A -> BC -> D
3747 tok = *head;
3748 prev_next = NULL;
3750 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3751 prev_nonspace = head;
3752 else
3753 prev_nonspace = NULL;
3755 while (tok && (next = tok->next)) {
3757 switch (tok->type) {
3758 case TOK_WHITESPACE:
3759 /* Zap redundant whitespaces */
3760 while (tok_type_(next, TOK_WHITESPACE))
3761 next = delete_Token(next);
3762 tok->next = next;
3763 break;
3765 case TOK_PASTE:
3766 /* Explicit pasting */
3767 if (!handle_explicit)
3768 break;
3769 next = delete_Token(tok);
3771 while (tok_type_(next, TOK_WHITESPACE))
3772 next = delete_Token(next);
3774 if (!pasted)
3775 pasted = true;
3777 /* Left pasting token is start of line */
3778 if (!prev_nonspace)
3779 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3782 * No ending token, this might happen in two
3783 * cases
3785 * 1) There indeed no right token at all
3786 * 2) There is a bare "%define ID" statement,
3787 * and @ID does expand to whitespace.
3789 * So technically we need to do a grammar analysis
3790 * in another stage of parsing, but for now lets don't
3791 * change the behaviour people used to. Simply allow
3792 * whitespace after paste token.
3794 if (!next) {
3796 * Zap ending space tokens and that's all.
3798 tok = (*prev_nonspace)->next;
3799 while (tok_type_(tok, TOK_WHITESPACE))
3800 tok = delete_Token(tok);
3801 tok = *prev_nonspace;
3802 tok->next = NULL;
3803 break;
3806 tok = *prev_nonspace;
3807 while (tok_type_(tok, TOK_WHITESPACE))
3808 tok = delete_Token(tok);
3809 len = strlen(tok->text);
3810 len += strlen(next->text);
3812 p = buf = nasm_malloc(len + 1);
3813 strcpy(p, tok->text);
3814 p = strchr(p, '\0');
3815 strcpy(p, next->text);
3817 delete_Token(tok);
3819 tok = tokenize(buf);
3820 nasm_free(buf);
3822 *prev_nonspace = tok;
3823 while (tok && tok->next)
3824 tok = tok->next;
3826 tok->next = delete_Token(next);
3828 /* Restart from pasted tokens head */
3829 tok = *prev_nonspace;
3830 break;
3832 default:
3833 /* implicit pasting */
3834 for (i = 0; i < mnum; i++) {
3835 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3836 continue;
3838 len = 0;
3839 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3840 len += strlen(next->text);
3841 next = next->next;
3844 /* No match */
3845 if (tok == next)
3846 break;
3848 len += strlen(tok->text);
3849 p = buf = nasm_malloc(len + 1);
3851 strcpy(p, tok->text);
3852 p = strchr(p, '\0');
3853 tok = delete_Token(tok);
3855 while (tok != next) {
3856 if (PP_CONCAT_MATCH(tok, m[i].mask_tail)) {
3857 strcpy(p, tok->text);
3858 p = strchr(p, '\0');
3860 tok = delete_Token(tok);
3863 tok = tokenize(buf);
3864 nasm_free(buf);
3866 if (prev_next)
3867 *prev_next = tok;
3868 else
3869 *head = tok;
3872 * Connect pasted into original stream,
3873 * ie A -> new-tokens -> B
3875 while (tok && tok->next)
3876 tok = tok->next;
3877 tok->next = next;
3879 if (!pasted)
3880 pasted = true;
3882 /* Restart from pasted tokens head */
3883 tok = prev_next ? *prev_next : *head;
3886 break;
3889 prev_next = &tok->next;
3891 if (tok->next &&
3892 !tok_type_(tok->next, TOK_WHITESPACE) &&
3893 !tok_type_(tok->next, TOK_PASTE))
3894 prev_nonspace = prev_next;
3896 tok = tok->next;
3899 return pasted;
3903 * expands to a list of tokens from %{x:y}
3905 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3907 Token *t = tline, **tt, *tm, *head;
3908 char *pos;
3909 int fst, lst, j, i;
3911 pos = strchr(tline->text, ':');
3912 nasm_assert(pos);
3914 lst = atoi(pos + 1);
3915 fst = atoi(tline->text + 1);
3918 * only macros params are accounted so
3919 * if someone passes %0 -- we reject such
3920 * value(s)
3922 if (lst == 0 || fst == 0)
3923 goto err;
3925 /* the values should be sane */
3926 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3927 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3928 goto err;
3930 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3931 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3933 /* counted from zero */
3934 fst--, lst--;
3937 * It will be at least one token. Note we
3938 * need to scan params until separator, otherwise
3939 * only first token will be passed.
3941 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3942 head = new_Token(NULL, tm->type, tm->text, 0);
3943 tt = &head->next, tm = tm->next;
3944 while (tok_isnt_(tm, ",")) {
3945 t = new_Token(NULL, tm->type, tm->text, 0);
3946 *tt = t, tt = &t->next, tm = tm->next;
3949 if (fst < lst) {
3950 for (i = fst + 1; i <= lst; i++) {
3951 t = new_Token(NULL, TOK_OTHER, ",", 0);
3952 *tt = t, tt = &t->next;
3953 j = (i + mac->rotate) % mac->nparam;
3954 tm = mac->params[j];
3955 while (tok_isnt_(tm, ",")) {
3956 t = new_Token(NULL, tm->type, tm->text, 0);
3957 *tt = t, tt = &t->next, tm = tm->next;
3960 } else {
3961 for (i = fst - 1; i >= lst; i--) {
3962 t = new_Token(NULL, TOK_OTHER, ",", 0);
3963 *tt = t, tt = &t->next;
3964 j = (i + mac->rotate) % mac->nparam;
3965 tm = mac->params[j];
3966 while (tok_isnt_(tm, ",")) {
3967 t = new_Token(NULL, tm->type, tm->text, 0);
3968 *tt = t, tt = &t->next, tm = tm->next;
3973 *last = tt;
3974 return head;
3976 err:
3977 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3978 &tline->text[1]);
3979 return tline;
3983 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3984 * %-n) and MMacro-local identifiers (%%foo) as well as
3985 * macro indirection (%[...]) and range (%{..:..}).
3987 static Token *expand_mmac_params(Token * tline)
3989 Token *t, *tt, **tail, *thead;
3990 bool changed = false;
3991 char *pos;
3993 tail = &thead;
3994 thead = NULL;
3996 while (tline) {
3997 if (tline->type == TOK_PREPROC_ID &&
3998 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3999 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
4000 tline->text[1] == '%')) {
4001 char *text = NULL;
4002 int type = 0, cc; /* type = 0 to placate optimisers */
4003 char tmpbuf[30];
4004 unsigned int n;
4005 int i;
4006 MMacro *mac;
4008 t = tline;
4009 tline = tline->next;
4011 mac = istk->mstk;
4012 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4013 mac = mac->next_active;
4014 if (!mac) {
4015 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4016 } else {
4017 pos = strchr(t->text, ':');
4018 if (!pos) {
4019 switch (t->text[1]) {
4021 * We have to make a substitution of one of the
4022 * forms %1, %-1, %+1, %%foo, %0.
4024 case '0':
4025 type = TOK_NUMBER;
4026 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4027 text = nasm_strdup(tmpbuf);
4028 break;
4029 case '%':
4030 type = TOK_ID;
4031 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4032 mac->unique);
4033 text = nasm_strcat(tmpbuf, t->text + 2);
4034 break;
4035 case '-':
4036 n = atoi(t->text + 2) - 1;
4037 if (n >= mac->nparam)
4038 tt = NULL;
4039 else {
4040 if (mac->nparam > 1)
4041 n = (n + mac->rotate) % mac->nparam;
4042 tt = mac->params[n];
4044 cc = find_cc(tt);
4045 if (cc == -1) {
4046 nasm_error(ERR_NONFATAL,
4047 "macro parameter %d is not a condition code",
4048 n + 1);
4049 text = NULL;
4050 } else {
4051 type = TOK_ID;
4052 if (inverse_ccs[cc] == -1) {
4053 nasm_error(ERR_NONFATAL,
4054 "condition code `%s' is not invertible",
4055 conditions[cc]);
4056 text = NULL;
4057 } else
4058 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4060 break;
4061 case '+':
4062 n = atoi(t->text + 2) - 1;
4063 if (n >= mac->nparam)
4064 tt = NULL;
4065 else {
4066 if (mac->nparam > 1)
4067 n = (n + mac->rotate) % mac->nparam;
4068 tt = mac->params[n];
4070 cc = find_cc(tt);
4071 if (cc == -1) {
4072 nasm_error(ERR_NONFATAL,
4073 "macro parameter %d is not a condition code",
4074 n + 1);
4075 text = NULL;
4076 } else {
4077 type = TOK_ID;
4078 text = nasm_strdup(conditions[cc]);
4080 break;
4081 default:
4082 n = atoi(t->text + 1) - 1;
4083 if (n >= mac->nparam)
4084 tt = NULL;
4085 else {
4086 if (mac->nparam > 1)
4087 n = (n + mac->rotate) % mac->nparam;
4088 tt = mac->params[n];
4090 if (tt) {
4091 for (i = 0; i < mac->paramlen[n]; i++) {
4092 *tail = new_Token(NULL, tt->type, tt->text, 0);
4093 tail = &(*tail)->next;
4094 tt = tt->next;
4097 text = NULL; /* we've done it here */
4098 break;
4100 } else {
4102 * seems we have a parameters range here
4104 Token *head, **last;
4105 head = expand_mmac_params_range(mac, t, &last);
4106 if (head != t) {
4107 *tail = head;
4108 *last = tline;
4109 tline = head;
4110 text = NULL;
4114 if (!text) {
4115 delete_Token(t);
4116 } else {
4117 *tail = t;
4118 tail = &t->next;
4119 t->type = type;
4120 nasm_free(t->text);
4121 t->text = text;
4122 t->a.mac = NULL;
4124 changed = true;
4125 continue;
4126 } else if (tline->type == TOK_INDIRECT) {
4127 t = tline;
4128 tline = tline->next;
4129 tt = tokenize(t->text);
4130 tt = expand_mmac_params(tt);
4131 tt = expand_smacro(tt);
4132 *tail = tt;
4133 while (tt) {
4134 tt->a.mac = NULL; /* Necessary? */
4135 tail = &tt->next;
4136 tt = tt->next;
4138 delete_Token(t);
4139 changed = true;
4140 } else {
4141 t = *tail = tline;
4142 tline = tline->next;
4143 t->a.mac = NULL;
4144 tail = &t->next;
4147 *tail = NULL;
4149 if (changed) {
4150 const struct tokseq_match t[] = {
4152 PP_CONCAT_MASK(TOK_ID) |
4153 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4154 PP_CONCAT_MASK(TOK_ID) |
4155 PP_CONCAT_MASK(TOK_NUMBER) |
4156 PP_CONCAT_MASK(TOK_FLOAT) |
4157 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4160 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4161 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4164 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4167 return thead;
4171 * Expand all single-line macro calls made in the given line.
4172 * Return the expanded version of the line. The original is deemed
4173 * to be destroyed in the process. (In reality we'll just move
4174 * Tokens from input to output a lot of the time, rather than
4175 * actually bothering to destroy and replicate.)
4178 static Token *expand_smacro(Token * tline)
4180 Token *t, *tt, *mstart, **tail, *thead;
4181 SMacro *head = NULL, *m;
4182 Token **params;
4183 int *paramsize;
4184 unsigned int nparam, sparam;
4185 int brackets;
4186 Token *org_tline = tline;
4187 Context *ctx;
4188 const char *mname;
4189 int deadman = DEADMAN_LIMIT;
4190 bool expanded;
4193 * Trick: we should avoid changing the start token pointer since it can
4194 * be contained in "next" field of other token. Because of this
4195 * we allocate a copy of first token and work with it; at the end of
4196 * routine we copy it back
4198 if (org_tline) {
4199 tline = new_Token(org_tline->next, org_tline->type,
4200 org_tline->text, 0);
4201 tline->a.mac = org_tline->a.mac;
4202 nasm_free(org_tline->text);
4203 org_tline->text = NULL;
4206 expanded = true; /* Always expand %+ at least once */
4208 again:
4209 thead = NULL;
4210 tail = &thead;
4212 while (tline) { /* main token loop */
4213 if (!--deadman) {
4214 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4215 goto err;
4218 if ((mname = tline->text)) {
4219 /* if this token is a local macro, look in local context */
4220 if (tline->type == TOK_ID) {
4221 head = (SMacro *)hash_findix(&smacros, mname);
4222 } else if (tline->type == TOK_PREPROC_ID) {
4223 ctx = get_ctx(mname, &mname);
4224 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4225 } else
4226 head = NULL;
4229 * We've hit an identifier. As in is_mmacro below, we first
4230 * check whether the identifier is a single-line macro at
4231 * all, then think about checking for parameters if
4232 * necessary.
4234 list_for_each(m, head)
4235 if (!mstrcmp(m->name, mname, m->casesense))
4236 break;
4237 if (m) {
4238 mstart = tline;
4239 params = NULL;
4240 paramsize = NULL;
4241 if (m->nparam == 0) {
4243 * Simple case: the macro is parameterless. Discard the
4244 * one token that the macro call took, and push the
4245 * expansion back on the to-do stack.
4247 if (!m->expansion) {
4248 if (!strcmp("__FILE__", m->name)) {
4249 const char *file = src_get_fname();
4250 /* nasm_free(tline->text); here? */
4251 tline->text = nasm_quote(file, strlen(file));
4252 tline->type = TOK_STRING;
4253 continue;
4255 if (!strcmp("__LINE__", m->name)) {
4256 nasm_free(tline->text);
4257 make_tok_num(tline, src_get_linnum());
4258 continue;
4260 if (!strcmp("__BITS__", m->name)) {
4261 nasm_free(tline->text);
4262 make_tok_num(tline, globalbits);
4263 continue;
4265 tline = delete_Token(tline);
4266 continue;
4268 } else {
4270 * Complicated case: at least one macro with this name
4271 * exists and takes parameters. We must find the
4272 * parameters in the call, count them, find the SMacro
4273 * that corresponds to that form of the macro call, and
4274 * substitute for the parameters when we expand. What a
4275 * pain.
4277 /*tline = tline->next;
4278 skip_white_(tline); */
4279 do {
4280 t = tline->next;
4281 while (tok_type_(t, TOK_SMAC_END)) {
4282 t->a.mac->in_progress = false;
4283 t->text = NULL;
4284 t = tline->next = delete_Token(t);
4286 tline = t;
4287 } while (tok_type_(tline, TOK_WHITESPACE));
4288 if (!tok_is_(tline, "(")) {
4290 * This macro wasn't called with parameters: ignore
4291 * the call. (Behaviour borrowed from gnu cpp.)
4293 tline = mstart;
4294 m = NULL;
4295 } else {
4296 int paren = 0;
4297 int white = 0;
4298 brackets = 0;
4299 nparam = 0;
4300 sparam = PARAM_DELTA;
4301 params = nasm_malloc(sparam * sizeof(Token *));
4302 params[0] = tline->next;
4303 paramsize = nasm_malloc(sparam * sizeof(int));
4304 paramsize[0] = 0;
4305 while (true) { /* parameter loop */
4307 * For some unusual expansions
4308 * which concatenates function call
4310 t = tline->next;
4311 while (tok_type_(t, TOK_SMAC_END)) {
4312 t->a.mac->in_progress = false;
4313 t->text = NULL;
4314 t = tline->next = delete_Token(t);
4316 tline = t;
4318 if (!tline) {
4319 nasm_error(ERR_NONFATAL,
4320 "macro call expects terminating `)'");
4321 break;
4323 if (tline->type == TOK_WHITESPACE
4324 && brackets <= 0) {
4325 if (paramsize[nparam])
4326 white++;
4327 else
4328 params[nparam] = tline->next;
4329 continue; /* parameter loop */
4331 if (tline->type == TOK_OTHER
4332 && tline->text[1] == 0) {
4333 char ch = tline->text[0];
4334 if (ch == ',' && !paren && brackets <= 0) {
4335 if (++nparam >= sparam) {
4336 sparam += PARAM_DELTA;
4337 params = nasm_realloc(params,
4338 sparam * sizeof(Token *));
4339 paramsize = nasm_realloc(paramsize,
4340 sparam * sizeof(int));
4342 params[nparam] = tline->next;
4343 paramsize[nparam] = 0;
4344 white = 0;
4345 continue; /* parameter loop */
4347 if (ch == '{' &&
4348 (brackets > 0 || (brackets == 0 &&
4349 !paramsize[nparam])))
4351 if (!(brackets++)) {
4352 params[nparam] = tline->next;
4353 continue; /* parameter loop */
4356 if (ch == '}' && brackets > 0)
4357 if (--brackets == 0) {
4358 brackets = -1;
4359 continue; /* parameter loop */
4361 if (ch == '(' && !brackets)
4362 paren++;
4363 if (ch == ')' && brackets <= 0)
4364 if (--paren < 0)
4365 break;
4367 if (brackets < 0) {
4368 brackets = 0;
4369 nasm_error(ERR_NONFATAL, "braces do not "
4370 "enclose all of macro parameter");
4372 paramsize[nparam] += white + 1;
4373 white = 0;
4374 } /* parameter loop */
4375 nparam++;
4376 while (m && (m->nparam != nparam ||
4377 mstrcmp(m->name, mname,
4378 m->casesense)))
4379 m = m->next;
4380 if (!m)
4381 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4382 "macro `%s' exists, "
4383 "but not taking %d parameters",
4384 mstart->text, nparam);
4387 if (m && m->in_progress)
4388 m = NULL;
4389 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4391 * Design question: should we handle !tline, which
4392 * indicates missing ')' here, or expand those
4393 * macros anyway, which requires the (t) test a few
4394 * lines down?
4396 nasm_free(params);
4397 nasm_free(paramsize);
4398 tline = mstart;
4399 } else {
4401 * Expand the macro: we are placed on the last token of the
4402 * call, so that we can easily split the call from the
4403 * following tokens. We also start by pushing an SMAC_END
4404 * token for the cycle removal.
4406 t = tline;
4407 if (t) {
4408 tline = t->next;
4409 t->next = NULL;
4411 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4412 tt->a.mac = m;
4413 m->in_progress = true;
4414 tline = tt;
4415 list_for_each(t, m->expansion) {
4416 if (t->type >= TOK_SMAC_PARAM) {
4417 Token *pcopy = tline, **ptail = &pcopy;
4418 Token *ttt, *pt;
4419 int i;
4421 ttt = params[t->type - TOK_SMAC_PARAM];
4422 i = paramsize[t->type - TOK_SMAC_PARAM];
4423 while (--i >= 0) {
4424 pt = *ptail = new_Token(tline, ttt->type,
4425 ttt->text, 0);
4426 ptail = &pt->next;
4427 ttt = ttt->next;
4429 tline = pcopy;
4430 } else if (t->type == TOK_PREPROC_Q) {
4431 tt = new_Token(tline, TOK_ID, mname, 0);
4432 tline = tt;
4433 } else if (t->type == TOK_PREPROC_QQ) {
4434 tt = new_Token(tline, TOK_ID, m->name, 0);
4435 tline = tt;
4436 } else {
4437 tt = new_Token(tline, t->type, t->text, 0);
4438 tline = tt;
4443 * Having done that, get rid of the macro call, and clean
4444 * up the parameters.
4446 nasm_free(params);
4447 nasm_free(paramsize);
4448 free_tlist(mstart);
4449 expanded = true;
4450 continue; /* main token loop */
4455 if (tline->type == TOK_SMAC_END) {
4456 tline->a.mac->in_progress = false;
4457 tline = delete_Token(tline);
4458 } else {
4459 t = *tail = tline;
4460 tline = tline->next;
4461 t->a.mac = NULL;
4462 t->next = NULL;
4463 tail = &t->next;
4468 * Now scan the entire line and look for successive TOK_IDs that resulted
4469 * after expansion (they can't be produced by tokenize()). The successive
4470 * TOK_IDs should be concatenated.
4471 * Also we look for %+ tokens and concatenate the tokens before and after
4472 * them (without white spaces in between).
4474 if (expanded) {
4475 const struct tokseq_match t[] = {
4477 PP_CONCAT_MASK(TOK_ID) |
4478 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4479 PP_CONCAT_MASK(TOK_ID) |
4480 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4481 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4484 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4486 * If we concatenated something, *and* we had previously expanded
4487 * an actual macro, scan the lines again for macros...
4489 tline = thead;
4490 expanded = false;
4491 goto again;
4495 err:
4496 if (org_tline) {
4497 if (thead) {
4498 *org_tline = *thead;
4499 /* since we just gave text to org_line, don't free it */
4500 thead->text = NULL;
4501 delete_Token(thead);
4502 } else {
4503 /* the expression expanded to empty line;
4504 we can't return NULL for some reasons
4505 we just set the line to a single WHITESPACE token. */
4506 memset(org_tline, 0, sizeof(*org_tline));
4507 org_tline->text = NULL;
4508 org_tline->type = TOK_WHITESPACE;
4510 thead = org_tline;
4513 return thead;
4517 * Similar to expand_smacro but used exclusively with macro identifiers
4518 * right before they are fetched in. The reason is that there can be
4519 * identifiers consisting of several subparts. We consider that if there
4520 * are more than one element forming the name, user wants a expansion,
4521 * otherwise it will be left as-is. Example:
4523 * %define %$abc cde
4525 * the identifier %$abc will be left as-is so that the handler for %define
4526 * will suck it and define the corresponding value. Other case:
4528 * %define _%$abc cde
4530 * In this case user wants name to be expanded *before* %define starts
4531 * working, so we'll expand %$abc into something (if it has a value;
4532 * otherwise it will be left as-is) then concatenate all successive
4533 * PP_IDs into one.
4535 static Token *expand_id(Token * tline)
4537 Token *cur, *oldnext = NULL;
4539 if (!tline || !tline->next)
4540 return tline;
4542 cur = tline;
4543 while (cur->next &&
4544 (cur->next->type == TOK_ID ||
4545 cur->next->type == TOK_PREPROC_ID
4546 || cur->next->type == TOK_NUMBER))
4547 cur = cur->next;
4549 /* If identifier consists of just one token, don't expand */
4550 if (cur == tline)
4551 return tline;
4553 if (cur) {
4554 oldnext = cur->next; /* Detach the tail past identifier */
4555 cur->next = NULL; /* so that expand_smacro stops here */
4558 tline = expand_smacro(tline);
4560 if (cur) {
4561 /* expand_smacro possibly changhed tline; re-scan for EOL */
4562 cur = tline;
4563 while (cur && cur->next)
4564 cur = cur->next;
4565 if (cur)
4566 cur->next = oldnext;
4569 return tline;
4573 * Determine whether the given line constitutes a multi-line macro
4574 * call, and return the MMacro structure called if so. Doesn't have
4575 * to check for an initial label - that's taken care of in
4576 * expand_mmacro - but must check numbers of parameters. Guaranteed
4577 * to be called with tline->type == TOK_ID, so the putative macro
4578 * name is easy to find.
4580 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4582 MMacro *head, *m;
4583 Token **params;
4584 int nparam;
4586 head = (MMacro *) hash_findix(&mmacros, tline->text);
4589 * Efficiency: first we see if any macro exists with the given
4590 * name. If not, we can return NULL immediately. _Then_ we
4591 * count the parameters, and then we look further along the
4592 * list if necessary to find the proper MMacro.
4594 list_for_each(m, head)
4595 if (!mstrcmp(m->name, tline->text, m->casesense))
4596 break;
4597 if (!m)
4598 return NULL;
4601 * OK, we have a potential macro. Count and demarcate the
4602 * parameters.
4604 count_mmac_params(tline->next, &nparam, &params);
4607 * So we know how many parameters we've got. Find the MMacro
4608 * structure that handles this number.
4610 while (m) {
4611 if (m->nparam_min <= nparam
4612 && (m->plus || nparam <= m->nparam_max)) {
4614 * This one is right. Just check if cycle removal
4615 * prohibits us using it before we actually celebrate...
4617 if (m->in_progress > m->max_depth) {
4618 if (m->max_depth > 0) {
4619 nasm_error(ERR_WARNING,
4620 "reached maximum recursion depth of %i",
4621 m->max_depth);
4623 nasm_free(params);
4624 return NULL;
4627 * It's right, and we can use it. Add its default
4628 * parameters to the end of our list if necessary.
4630 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4631 params =
4632 nasm_realloc(params,
4633 ((m->nparam_min + m->ndefs +
4634 1) * sizeof(*params)));
4635 while (nparam < m->nparam_min + m->ndefs) {
4636 params[nparam] = m->defaults[nparam - m->nparam_min];
4637 nparam++;
4641 * If we've gone over the maximum parameter count (and
4642 * we're in Plus mode), ignore parameters beyond
4643 * nparam_max.
4645 if (m->plus && nparam > m->nparam_max)
4646 nparam = m->nparam_max;
4648 * Then terminate the parameter list, and leave.
4650 if (!params) { /* need this special case */
4651 params = nasm_malloc(sizeof(*params));
4652 nparam = 0;
4654 params[nparam] = NULL;
4655 *params_array = params;
4656 return m;
4659 * This one wasn't right: look for the next one with the
4660 * same name.
4662 list_for_each(m, m->next)
4663 if (!mstrcmp(m->name, tline->text, m->casesense))
4664 break;
4668 * After all that, we didn't find one with the right number of
4669 * parameters. Issue a warning, and fail to expand the macro.
4671 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4672 "macro `%s' exists, but not taking %d parameters",
4673 tline->text, nparam);
4674 nasm_free(params);
4675 return NULL;
4680 * Save MMacro invocation specific fields in
4681 * preparation for a recursive macro expansion
4683 static void push_mmacro(MMacro *m)
4685 MMacroInvocation *i;
4687 i = nasm_malloc(sizeof(MMacroInvocation));
4688 i->prev = m->prev;
4689 i->params = m->params;
4690 i->iline = m->iline;
4691 i->nparam = m->nparam;
4692 i->rotate = m->rotate;
4693 i->paramlen = m->paramlen;
4694 i->unique = m->unique;
4695 i->condcnt = m->condcnt;
4696 m->prev = i;
4701 * Restore MMacro invocation specific fields that were
4702 * saved during a previous recursive macro expansion
4704 static void pop_mmacro(MMacro *m)
4706 MMacroInvocation *i;
4708 if (m->prev) {
4709 i = m->prev;
4710 m->prev = i->prev;
4711 m->params = i->params;
4712 m->iline = i->iline;
4713 m->nparam = i->nparam;
4714 m->rotate = i->rotate;
4715 m->paramlen = i->paramlen;
4716 m->unique = i->unique;
4717 m->condcnt = i->condcnt;
4718 nasm_free(i);
4724 * Expand the multi-line macro call made by the given line, if
4725 * there is one to be expanded. If there is, push the expansion on
4726 * istk->expansion and return 1. Otherwise return 0.
4728 static int expand_mmacro(Token * tline)
4730 Token *startline = tline;
4731 Token *label = NULL;
4732 int dont_prepend = 0;
4733 Token **params, *t, *tt;
4734 MMacro *m;
4735 Line *l, *ll;
4736 int i, nparam, *paramlen;
4737 const char *mname;
4739 t = tline;
4740 skip_white_(t);
4741 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4742 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4743 return 0;
4744 m = is_mmacro(t, &params);
4745 if (m) {
4746 mname = t->text;
4747 } else {
4748 Token *last;
4750 * We have an id which isn't a macro call. We'll assume
4751 * it might be a label; we'll also check to see if a
4752 * colon follows it. Then, if there's another id after
4753 * that lot, we'll check it again for macro-hood.
4755 label = last = t;
4756 t = t->next;
4757 if (tok_type_(t, TOK_WHITESPACE))
4758 last = t, t = t->next;
4759 if (tok_is_(t, ":")) {
4760 dont_prepend = 1;
4761 last = t, t = t->next;
4762 if (tok_type_(t, TOK_WHITESPACE))
4763 last = t, t = t->next;
4765 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4766 return 0;
4767 last->next = NULL;
4768 mname = t->text;
4769 tline = t;
4773 * Fix up the parameters: this involves stripping leading and
4774 * trailing whitespace, then stripping braces if they are
4775 * present.
4777 for (nparam = 0; params[nparam]; nparam++) ;
4778 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4780 for (i = 0; params[i]; i++) {
4781 int brace = 0;
4782 int comma = (!m->plus || i < nparam - 1);
4784 t = params[i];
4785 skip_white_(t);
4786 if (tok_is_(t, "{"))
4787 t = t->next, brace++, comma = false;
4788 params[i] = t;
4789 paramlen[i] = 0;
4790 while (t) {
4791 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4792 break; /* ... because we have hit a comma */
4793 if (comma && t->type == TOK_WHITESPACE
4794 && tok_is_(t->next, ","))
4795 break; /* ... or a space then a comma */
4796 if (brace && t->type == TOK_OTHER) {
4797 if (t->text[0] == '{')
4798 brace++; /* ... or a nested opening brace */
4799 else if (t->text[0] == '}')
4800 if (!--brace)
4801 break; /* ... or a brace */
4803 t = t->next;
4804 paramlen[i]++;
4806 if (brace)
4807 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4811 * OK, we have a MMacro structure together with a set of
4812 * parameters. We must now go through the expansion and push
4813 * copies of each Line on to istk->expansion. Substitution of
4814 * parameter tokens and macro-local tokens doesn't get done
4815 * until the single-line macro substitution process; this is
4816 * because delaying them allows us to change the semantics
4817 * later through %rotate.
4819 * First, push an end marker on to istk->expansion, mark this
4820 * macro as in progress, and set up its invocation-specific
4821 * variables.
4823 ll = nasm_malloc(sizeof(Line));
4824 ll->next = istk->expansion;
4825 ll->finishes = m;
4826 ll->first = NULL;
4827 istk->expansion = ll;
4830 * Save the previous MMacro expansion in the case of
4831 * macro recursion
4833 if (m->max_depth && m->in_progress)
4834 push_mmacro(m);
4836 m->in_progress ++;
4837 m->params = params;
4838 m->iline = tline;
4839 m->nparam = nparam;
4840 m->rotate = 0;
4841 m->paramlen = paramlen;
4842 m->unique = unique++;
4843 m->lineno = 0;
4844 m->condcnt = 0;
4846 m->next_active = istk->mstk;
4847 istk->mstk = m;
4849 list_for_each(l, m->expansion) {
4850 Token **tail;
4852 ll = nasm_malloc(sizeof(Line));
4853 ll->finishes = NULL;
4854 ll->next = istk->expansion;
4855 istk->expansion = ll;
4856 tail = &ll->first;
4858 list_for_each(t, l->first) {
4859 Token *x = t;
4860 switch (t->type) {
4861 case TOK_PREPROC_Q:
4862 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4863 break;
4864 case TOK_PREPROC_QQ:
4865 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4866 break;
4867 case TOK_PREPROC_ID:
4868 if (t->text[1] == '0' && t->text[2] == '0') {
4869 dont_prepend = -1;
4870 x = label;
4871 if (!x)
4872 continue;
4874 /* fall through */
4875 default:
4876 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4877 break;
4879 tail = &tt->next;
4881 *tail = NULL;
4885 * If we had a label, push it on as the first line of
4886 * the macro expansion.
4888 if (label) {
4889 if (dont_prepend < 0)
4890 free_tlist(startline);
4891 else {
4892 ll = nasm_malloc(sizeof(Line));
4893 ll->finishes = NULL;
4894 ll->next = istk->expansion;
4895 istk->expansion = ll;
4896 ll->first = startline;
4897 if (!dont_prepend) {
4898 while (label->next)
4899 label = label->next;
4900 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4905 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4907 return 1;
4911 * This function adds macro names to error messages, and suppresses
4912 * them if necessary.
4914 static void pp_verror(int severity, const char *fmt, va_list arg)
4916 char buff[BUFSIZ];
4917 MMacro *mmac = NULL;
4918 int delta = 0;
4921 * If we're in a dead branch of IF or something like it, ignore the error.
4922 * However, because %else etc are evaluated in the state context
4923 * of the previous branch, errors might get lost:
4924 * %if 0 ... %else trailing garbage ... %endif
4925 * So %else etc should set the ERR_PP_PRECOND flag.
4927 if ((severity & ERR_MASK) < ERR_FATAL &&
4928 istk && istk->conds &&
4929 ((severity & ERR_PP_PRECOND) ?
4930 istk->conds->state == COND_NEVER :
4931 !emitting(istk->conds->state)))
4932 return;
4934 /* get %macro name */
4935 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4936 mmac = istk->mstk;
4937 /* but %rep blocks should be skipped */
4938 while (mmac && !mmac->name)
4939 mmac = mmac->next_active, delta++;
4942 if (mmac) {
4943 vsnprintf(buff, sizeof(buff), fmt, arg);
4945 nasm_set_verror(real_verror);
4946 nasm_error(severity, "(%s:%d) %s",
4947 mmac->name, mmac->lineno - delta, buff);
4948 nasm_set_verror(pp_verror);
4949 } else {
4950 real_verror(severity, fmt, arg);
4954 static void
4955 pp_reset(char *file, int apass, StrList **deplist)
4957 Token *t;
4959 cstk = NULL;
4960 istk = nasm_malloc(sizeof(Include));
4961 istk->next = NULL;
4962 istk->conds = NULL;
4963 istk->expansion = NULL;
4964 istk->mstk = NULL;
4965 istk->fp = nasm_open_read(file, NF_TEXT);
4966 istk->fname = NULL;
4967 src_set(0, file);
4968 istk->lineinc = 1;
4969 if (!istk->fp)
4970 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4971 defining = NULL;
4972 nested_mac_count = 0;
4973 nested_rep_count = 0;
4974 init_macros();
4975 unique = 0;
4977 if (tasm_compatible_mode)
4978 pp_add_stdmac(nasm_stdmac_tasm);
4980 pp_add_stdmac(nasm_stdmac_nasm);
4981 pp_add_stdmac(nasm_stdmac_version);
4983 if (extrastdmac)
4984 pp_add_stdmac(extrastdmac);
4986 stdmacpos = stdmacros[0];
4987 stdmacnext = &stdmacros[1];
4989 do_predef = true;
4992 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4993 * The caller, however, will also pass in 3 for preprocess-only so
4994 * we can set __PASS__ accordingly.
4996 pass = apass > 2 ? 2 : apass;
4998 dephead = deplist;
4999 nasm_add_string_to_strlist(dephead, file);
5002 * Define the __PASS__ macro. This is defined here unlike
5003 * all the other builtins, because it is special -- it varies between
5004 * passes.
5006 t = nasm_malloc(sizeof(*t));
5007 t->next = NULL;
5008 make_tok_num(t, apass);
5009 t->a.mac = NULL;
5010 define_smacro(NULL, "__PASS__", true, 0, t);
5013 static void pp_init(void)
5015 hash_init(&FileHash, HASH_MEDIUM);
5018 static char *pp_getline(void)
5020 char *line;
5021 Token *tline;
5023 real_verror = nasm_set_verror(pp_verror);
5025 while (1) {
5027 * Fetch a tokenized line, either from the macro-expansion
5028 * buffer or from the input file.
5030 tline = NULL;
5031 while (istk->expansion && istk->expansion->finishes) {
5032 Line *l = istk->expansion;
5033 if (!l->finishes->name && l->finishes->in_progress > 1) {
5034 Line *ll;
5037 * This is a macro-end marker for a macro with no
5038 * name, which means it's not really a macro at all
5039 * but a %rep block, and the `in_progress' field is
5040 * more than 1, meaning that we still need to
5041 * repeat. (1 means the natural last repetition; 0
5042 * means termination by %exitrep.) We have
5043 * therefore expanded up to the %endrep, and must
5044 * push the whole block on to the expansion buffer
5045 * again. We don't bother to remove the macro-end
5046 * marker: we'd only have to generate another one
5047 * if we did.
5049 l->finishes->in_progress--;
5050 list_for_each(l, l->finishes->expansion) {
5051 Token *t, *tt, **tail;
5053 ll = nasm_malloc(sizeof(Line));
5054 ll->next = istk->expansion;
5055 ll->finishes = NULL;
5056 ll->first = NULL;
5057 tail = &ll->first;
5059 list_for_each(t, l->first) {
5060 if (t->text || t->type == TOK_WHITESPACE) {
5061 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5062 tail = &tt->next;
5066 istk->expansion = ll;
5068 } else {
5070 * Check whether a `%rep' was started and not ended
5071 * within this macro expansion. This can happen and
5072 * should be detected. It's a fatal error because
5073 * I'm too confused to work out how to recover
5074 * sensibly from it.
5076 if (defining) {
5077 if (defining->name)
5078 nasm_panic(0, "defining with name in expansion");
5079 else if (istk->mstk->name)
5080 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5081 " expansion of macro `%s'",
5082 istk->mstk->name);
5086 * FIXME: investigate the relationship at this point between
5087 * istk->mstk and l->finishes
5090 MMacro *m = istk->mstk;
5091 istk->mstk = m->next_active;
5092 if (m->name) {
5094 * This was a real macro call, not a %rep, and
5095 * therefore the parameter information needs to
5096 * be freed.
5098 if (m->prev) {
5099 pop_mmacro(m);
5100 l->finishes->in_progress --;
5101 } else {
5102 nasm_free(m->params);
5103 free_tlist(m->iline);
5104 nasm_free(m->paramlen);
5105 l->finishes->in_progress = 0;
5110 * FIXME It is incorrect to always free_mmacro here.
5111 * It leads to usage-after-free.
5113 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
5115 #if 0
5116 else
5117 free_mmacro(m);
5118 #endif
5120 istk->expansion = l->next;
5121 nasm_free(l);
5122 lfmt->downlevel(LIST_MACRO);
5125 while (1) { /* until we get a line we can use */
5127 if (istk->expansion) { /* from a macro expansion */
5128 char *p;
5129 Line *l = istk->expansion;
5130 if (istk->mstk)
5131 istk->mstk->lineno++;
5132 tline = l->first;
5133 istk->expansion = l->next;
5134 nasm_free(l);
5135 p = detoken(tline, false);
5136 lfmt->line(LIST_MACRO, p);
5137 nasm_free(p);
5138 break;
5140 line = read_line();
5141 if (line) { /* from the current input file */
5142 line = prepreproc(line);
5143 tline = tokenize(line);
5144 nasm_free(line);
5145 break;
5148 * The current file has ended; work down the istk
5151 Include *i = istk;
5152 fclose(i->fp);
5153 if (i->conds) {
5154 /* nasm_error can't be conditionally suppressed */
5155 nasm_fatal(0,
5156 "expected `%%endif' before end of file");
5158 /* only set line and file name if there's a next node */
5159 if (i->next)
5160 src_set(i->lineno, i->fname);
5161 istk = i->next;
5162 lfmt->downlevel(LIST_INCLUDE);
5163 nasm_free(i);
5164 if (!istk) {
5165 line = NULL;
5166 goto done;
5168 if (istk->expansion && istk->expansion->finishes)
5169 break;
5174 * We must expand MMacro parameters and MMacro-local labels
5175 * _before_ we plunge into directive processing, to cope
5176 * with things like `%define something %1' such as STRUC
5177 * uses. Unless we're _defining_ a MMacro, in which case
5178 * those tokens should be left alone to go into the
5179 * definition; and unless we're in a non-emitting
5180 * condition, in which case we don't want to meddle with
5181 * anything.
5183 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5184 && !(istk->mstk && !istk->mstk->in_progress)) {
5185 tline = expand_mmac_params(tline);
5189 * Check the line to see if it's a preprocessor directive.
5191 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5192 if (line)
5193 break; /* Directive generated output */
5194 else
5195 continue;
5196 } else if (defining) {
5198 * We're defining a multi-line macro. We emit nothing
5199 * at all, and just
5200 * shove the tokenized line on to the macro definition.
5202 Line *l = nasm_malloc(sizeof(Line));
5203 l->next = defining->expansion;
5204 l->first = tline;
5205 l->finishes = NULL;
5206 defining->expansion = l;
5207 continue;
5208 } else if (istk->conds && !emitting(istk->conds->state)) {
5210 * We're in a non-emitting branch of a condition block.
5211 * Emit nothing at all, not even a blank line: when we
5212 * emerge from the condition we'll give a line-number
5213 * directive so we keep our place correctly.
5215 free_tlist(tline);
5216 continue;
5217 } else if (istk->mstk && !istk->mstk->in_progress) {
5219 * We're in a %rep block which has been terminated, so
5220 * we're walking through to the %endrep without
5221 * emitting anything. Emit nothing at all, not even a
5222 * blank line: when we emerge from the %rep block we'll
5223 * give a line-number directive so we keep our place
5224 * correctly.
5226 free_tlist(tline);
5227 continue;
5228 } else {
5229 tline = expand_smacro(tline);
5230 if (!expand_mmacro(tline)) {
5232 * De-tokenize the line again, and emit it.
5234 line = detoken(tline, true);
5235 free_tlist(tline);
5236 break;
5237 } else {
5238 continue; /* expand_mmacro calls free_tlist */
5243 done:
5244 nasm_set_verror(real_verror);
5245 return line;
5248 static void pp_cleanup(int pass)
5250 real_verror = nasm_set_verror(pp_verror);
5252 if (defining) {
5253 if (defining->name) {
5254 nasm_error(ERR_NONFATAL,
5255 "end of file while still defining macro `%s'",
5256 defining->name);
5257 } else {
5258 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5261 free_mmacro(defining);
5262 defining = NULL;
5265 nasm_set_verror(real_verror);
5267 while (cstk)
5268 ctx_pop();
5269 free_macros();
5270 while (istk) {
5271 Include *i = istk;
5272 istk = istk->next;
5273 fclose(i->fp);
5274 nasm_free(i);
5276 while (cstk)
5277 ctx_pop();
5278 src_set_fname(NULL);
5279 if (pass == 0) {
5280 IncPath *i;
5281 free_llist(predef);
5282 predef = NULL;
5283 delete_Blocks();
5284 freeTokens = NULL;
5285 while ((i = ipath)) {
5286 ipath = i->next;
5287 if (i->path)
5288 nasm_free(i->path);
5289 nasm_free(i);
5294 static void pp_include_path(char *path)
5296 IncPath *i;
5298 i = nasm_malloc(sizeof(IncPath));
5299 i->path = path ? nasm_strdup(path) : NULL;
5300 i->next = NULL;
5302 if (ipath) {
5303 IncPath *j = ipath;
5304 while (j->next)
5305 j = j->next;
5306 j->next = i;
5307 } else {
5308 ipath = i;
5312 static void pp_pre_include(char *fname)
5314 Token *inc, *space, *name;
5315 Line *l;
5317 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5318 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5319 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5321 l = nasm_malloc(sizeof(Line));
5322 l->next = predef;
5323 l->first = inc;
5324 l->finishes = NULL;
5325 predef = l;
5328 static void pp_pre_define(char *definition)
5330 Token *def, *space;
5331 Line *l;
5332 char *equals;
5334 real_verror = nasm_set_verror(pp_verror);
5336 equals = strchr(definition, '=');
5337 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5338 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5339 if (equals)
5340 *equals = ' ';
5341 space->next = tokenize(definition);
5342 if (equals)
5343 *equals = '=';
5345 if (space->next->type != TOK_PREPROC_ID &&
5346 space->next->type != TOK_ID)
5347 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5349 l = nasm_malloc(sizeof(Line));
5350 l->next = predef;
5351 l->first = def;
5352 l->finishes = NULL;
5353 predef = l;
5355 nasm_set_verror(real_verror);
5358 static void pp_pre_undefine(char *definition)
5360 Token *def, *space;
5361 Line *l;
5363 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5364 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5365 space->next = tokenize(definition);
5367 l = nasm_malloc(sizeof(Line));
5368 l->next = predef;
5369 l->first = def;
5370 l->finishes = NULL;
5371 predef = l;
5374 static void pp_add_stdmac(macros_t *macros)
5376 macros_t **mp;
5378 /* Find the end of the list and avoid duplicates */
5379 for (mp = stdmacros; *mp; mp++) {
5380 if (*mp == macros)
5381 return; /* Nothing to do */
5384 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5386 *mp = macros;
5389 static void pp_extra_stdmac(macros_t *macros)
5391 extrastdmac = macros;
5394 static void make_tok_num(Token * tok, int64_t val)
5396 char numbuf[32];
5397 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5398 tok->text = nasm_strdup(numbuf);
5399 tok->type = TOK_NUMBER;
5402 static void pp_list_one_macro(MMacro *m, int severity)
5404 if (!m)
5405 return;
5407 /* We need to print the next_active list in reverse order */
5408 pp_list_one_macro(m->next_active, severity);
5410 if (m->name && !m->nolist) {
5411 src_set(m->xline + m->lineno, m->fname);
5412 nasm_error(severity, "... from macro `%s' defined here", m->name);
5416 static void pp_error_list_macros(int severity)
5418 int32_t saved_line;
5419 const char *saved_fname = NULL;
5421 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5422 src_get(&saved_line, &saved_fname);
5424 if (istk)
5425 pp_list_one_macro(istk->mstk, severity);
5427 src_set(saved_line, saved_fname);
5430 const struct preproc_ops nasmpp = {
5431 pp_init,
5432 pp_reset,
5433 pp_getline,
5434 pp_cleanup,
5435 pp_extra_stdmac,
5436 pp_pre_define,
5437 pp_pre_undefine,
5438 pp_pre_include,
5439 pp_include_path,
5440 pp_error_list_macros,