preproc: make "StackPointer" a const char *
[nasm.git] / preproc.c
blob845f8fc13174dfa97a90ded5d2db9ac950381195
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2016 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 "preproc.h"
76 #include "hashtbl.h"
77 #include "quote.h"
78 #include "stdscan.h"
79 #include "eval.h"
80 #include "tokens.h"
81 #include "tables.h"
82 #include "listing.h"
84 typedef struct SMacro SMacro;
85 typedef struct MMacro MMacro;
86 typedef struct MMacroInvocation MMacroInvocation;
87 typedef struct Context Context;
88 typedef struct Token Token;
89 typedef struct Blocks Blocks;
90 typedef struct Line Line;
91 typedef struct Include Include;
92 typedef struct Cond Cond;
93 typedef struct IncPath IncPath;
96 * Note on the storage of both SMacro and MMacros: the hash table
97 * indexes them case-insensitively, and we then have to go through a
98 * linked list of potential case aliases (and, for MMacros, parameter
99 * ranges); this is to preserve the matching semantics of the earlier
100 * code. If the number of case aliases for a specific macro is a
101 * performance issue, you may want to reconsider your coding style.
105 * Store the definition of a single-line macro.
107 struct SMacro {
108 SMacro *next;
109 char *name;
110 bool casesense;
111 bool in_progress;
112 unsigned int nparam;
113 Token *expansion;
117 * Store the definition of a multi-line macro. This is also used to
118 * store the interiors of `%rep...%endrep' blocks, which are
119 * effectively self-re-invoking multi-line macros which simply
120 * don't have a name or bother to appear in the hash tables. %rep
121 * blocks are signified by having a NULL `name' field.
123 * In a MMacro describing a `%rep' block, the `in_progress' field
124 * isn't merely boolean, but gives the number of repeats left to
125 * run.
127 * The `next' field is used for storing MMacros in hash tables; the
128 * `next_active' field is for stacking them on istk entries.
130 * When a MMacro is being expanded, `params', `iline', `nparam',
131 * `paramlen', `rotate' and `unique' are local to the invocation.
133 struct MMacro {
134 MMacro *next;
135 MMacroInvocation *prev; /* previous invocation */
136 char *name;
137 int nparam_min, nparam_max;
138 bool casesense;
139 bool plus; /* is the last parameter greedy? */
140 bool nolist; /* is this macro listing-inhibited? */
141 int64_t in_progress; /* is this macro currently being expanded? */
142 int32_t max_depth; /* maximum number of recursive expansions allowed */
143 Token *dlist; /* All defaults as one list */
144 Token **defaults; /* Parameter default pointers */
145 int ndefs; /* number of default parameters */
146 Line *expansion;
148 MMacro *next_active;
149 MMacro *rep_nest; /* used for nesting %rep */
150 Token **params; /* actual parameters */
151 Token *iline; /* invocation line */
152 unsigned int nparam, rotate;
153 int *paramlen;
154 uint64_t unique;
155 int lineno; /* Current line number on expansion */
156 uint64_t condcnt; /* number of if blocks... */
158 const char *fname; /* File where defined */
159 int32_t xline; /* First line in macro */
163 /* Store the definition of a multi-line macro, as defined in a
164 * previous recursive macro expansion.
166 struct MMacroInvocation {
167 MMacroInvocation *prev; /* previous invocation */
168 Token **params; /* actual parameters */
169 Token *iline; /* invocation line */
170 unsigned int nparam, rotate;
171 int *paramlen;
172 uint64_t unique;
173 uint64_t condcnt;
178 * The context stack is composed of a linked list of these.
180 struct Context {
181 Context *next;
182 char *name;
183 struct hash_table localmac;
184 uint32_t number;
188 * This is the internal form which we break input lines up into.
189 * Typically stored in linked lists.
191 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
192 * necessarily used as-is, but is intended to denote the number of
193 * the substituted parameter. So in the definition
195 * %define a(x,y) ( (x) & ~(y) )
197 * the token representing `x' will have its type changed to
198 * TOK_SMAC_PARAM, but the one representing `y' will be
199 * TOK_SMAC_PARAM+1.
201 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
202 * which doesn't need quotes around it. Used in the pre-include
203 * mechanism as an alternative to trying to find a sensible type of
204 * quote to use on the filename we were passed.
206 enum pp_token_type {
207 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
208 TOK_PREPROC_ID, TOK_STRING,
209 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
210 TOK_INTERNAL_STRING,
211 TOK_PREPROC_Q, TOK_PREPROC_QQ,
212 TOK_PASTE, /* %+ */
213 TOK_INDIRECT, /* %[...] */
214 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
215 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
218 #define PP_CONCAT_MASK(x) (1 << (x))
219 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
221 struct tokseq_match {
222 int mask_head;
223 int mask_tail;
226 struct Token {
227 Token *next;
228 char *text;
229 union {
230 SMacro *mac; /* associated macro for TOK_SMAC_END */
231 size_t len; /* scratch length field */
232 } a; /* Auxiliary data */
233 enum pp_token_type type;
237 * Multi-line macro definitions are stored as a linked list of
238 * these, which is essentially a container to allow several linked
239 * lists of Tokens.
241 * Note that in this module, linked lists are treated as stacks
242 * wherever possible. For this reason, Lines are _pushed_ on to the
243 * `expansion' field in MMacro structures, so that the linked list,
244 * if walked, would give the macro lines in reverse order; this
245 * means that we can walk the list when expanding a macro, and thus
246 * push the lines on to the `expansion' field in _istk_ in reverse
247 * order (so that when popped back off they are in the right
248 * order). It may seem cockeyed, and it relies on my design having
249 * an even number of steps in, but it works...
251 * Some of these structures, rather than being actual lines, are
252 * markers delimiting the end of the expansion of a given macro.
253 * This is for use in the cycle-tracking and %rep-handling code.
254 * Such structures have `finishes' non-NULL, and `first' NULL. All
255 * others have `finishes' NULL, but `first' may still be NULL if
256 * the line is blank.
258 struct Line {
259 Line *next;
260 MMacro *finishes;
261 Token *first;
265 * To handle an arbitrary level of file inclusion, we maintain a
266 * stack (ie linked list) of these things.
268 struct Include {
269 Include *next;
270 FILE *fp;
271 Cond *conds;
272 Line *expansion;
273 const char *fname;
274 int lineno, lineinc;
275 MMacro *mstk; /* stack of active macros/reps */
279 * Include search path. This is simply a list of strings which get
280 * prepended, in turn, to the name of an include file, in an
281 * attempt to find the file if it's not in the current directory.
283 struct IncPath {
284 IncPath *next;
285 char *path;
289 * Conditional assembly: we maintain a separate stack of these for
290 * each level of file inclusion. (The only reason we keep the
291 * stacks separate is to ensure that a stray `%endif' in a file
292 * included from within the true branch of a `%if' won't terminate
293 * it and cause confusion: instead, rightly, it'll cause an error.)
295 struct Cond {
296 Cond *next;
297 int state;
299 enum {
301 * These states are for use just after %if or %elif: IF_TRUE
302 * means the condition has evaluated to truth so we are
303 * currently emitting, whereas IF_FALSE means we are not
304 * currently emitting but will start doing so if a %else comes
305 * up. In these states, all directives are admissible: %elif,
306 * %else and %endif. (And of course %if.)
308 COND_IF_TRUE, COND_IF_FALSE,
310 * These states come up after a %else: ELSE_TRUE means we're
311 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
312 * any %elif or %else will cause an error.
314 COND_ELSE_TRUE, COND_ELSE_FALSE,
316 * These states mean that we're not emitting now, and also that
317 * nothing until %endif will be emitted at all. COND_DONE is
318 * used when we've had our moment of emission
319 * and have now started seeing %elifs. COND_NEVER is used when
320 * the condition construct in question is contained within a
321 * non-emitting branch of a larger condition construct,
322 * or if there is an error.
324 COND_DONE, COND_NEVER
326 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
329 * These defines are used as the possible return values for do_directive
331 #define NO_DIRECTIVE_FOUND 0
332 #define DIRECTIVE_FOUND 1
335 * This define sets the upper limit for smacro and recursive mmacro
336 * expansions
338 #define DEADMAN_LIMIT (1 << 20)
340 /* max reps */
341 #define REP_LIMIT ((INT64_C(1) << 62))
344 * Condition codes. Note that we use c_ prefix not C_ because C_ is
345 * used in nasm.h for the "real" condition codes. At _this_ level,
346 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
347 * ones, so we need a different enum...
349 static const char * const conditions[] = {
350 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
351 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
352 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
354 enum pp_conds {
355 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
356 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
357 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
358 c_none = -1
360 static const enum pp_conds inverse_ccs[] = {
361 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
362 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,
363 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
367 * Directive names.
369 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
370 static int is_condition(enum preproc_token arg)
372 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
375 /* For TASM compatibility we need to be able to recognise TASM compatible
376 * conditional compilation directives. Using the NASM pre-processor does
377 * not work, so we look for them specifically from the following list and
378 * then jam in the equivalent NASM directive into the input stream.
381 enum {
382 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
383 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
386 static const char * const tasm_directives[] = {
387 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
388 "ifndef", "include", "local"
391 static int StackSize = 4;
392 static const char *StackPointer = "ebp";
393 static int ArgOffset = 8;
394 static int LocalOffset = 0;
396 static Context *cstk;
397 static Include *istk;
398 static IncPath *ipath = NULL;
400 static int pass; /* HACK: pass 0 = generate dependencies only */
401 static StrList **dephead, **deptail; /* Dependency list */
403 static uint64_t unique; /* unique identifier numbers */
405 static Line *predef = NULL;
406 static bool do_predef;
409 * The current set of multi-line macros we have defined.
411 static struct hash_table mmacros;
414 * The current set of single-line macros we have defined.
416 static struct hash_table smacros;
419 * The multi-line macro we are currently defining, or the %rep
420 * block we are currently reading, if any.
422 static MMacro *defining;
424 static uint64_t nested_mac_count;
425 static uint64_t nested_rep_count;
428 * The number of macro parameters to allocate space for at a time.
430 #define PARAM_DELTA 16
433 * The standard macro set: defined in macros.c in the array nasm_stdmac.
434 * This gives our position in the macro set, when we're processing it.
436 static macros_t *stdmacpos;
439 * The extra standard macros that come from the object format, if
440 * any.
442 static macros_t *extrastdmac = NULL;
443 static bool any_extrastdmac;
446 * Tokens are allocated in blocks to improve speed
448 #define TOKEN_BLOCKSIZE 4096
449 static Token *freeTokens = NULL;
450 struct Blocks {
451 Blocks *next;
452 void *chunk;
455 static Blocks blocks = { NULL, NULL };
458 * Forward declarations.
460 static Token *expand_mmac_params(Token * tline);
461 static Token *expand_smacro(Token * tline);
462 static Token *expand_id(Token * tline);
463 static Context *get_ctx(const char *name, const char **namep);
464 static void make_tok_num(Token * tok, int64_t val);
465 static void pp_verror(int severity, const char *fmt, va_list ap);
466 static vefunc real_verror;
467 static void *new_Block(size_t size);
468 static void delete_Blocks(void);
469 static Token *new_Token(Token * next, enum pp_token_type type,
470 const char *text, int txtlen);
471 static Token *delete_Token(Token * t);
474 * Macros for safe checking of token pointers, avoid *(NULL)
476 #define tok_type_(x,t) ((x) && (x)->type == (t))
477 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
478 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
479 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
482 * nasm_unquote with error if the string contains NUL characters.
483 * If the string contains NUL characters, issue an error and return
484 * the C len, i.e. truncate at the NUL.
486 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
488 size_t len = nasm_unquote(qstr, NULL);
489 size_t clen = strlen(qstr);
491 if (len != clen)
492 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
493 pp_directives[directive]);
495 return clen;
499 * In-place reverse a list of tokens.
501 static Token *reverse_tokens(Token *t)
503 Token *prev = NULL;
504 Token *next;
506 while (t) {
507 next = t->next;
508 t->next = prev;
509 prev = t;
510 t = next;
513 return prev;
517 * Handle TASM specific directives, which do not contain a % in
518 * front of them. We do it here because I could not find any other
519 * place to do it for the moment, and it is a hack (ideally it would
520 * be nice to be able to use the NASM pre-processor to do it).
522 static char *check_tasm_directive(char *line)
524 int32_t i, j, k, m, len;
525 char *p, *q, *oldline, oldchar;
527 p = nasm_skip_spaces(line);
529 /* Binary search for the directive name */
530 i = -1;
531 j = ARRAY_SIZE(tasm_directives);
532 q = nasm_skip_word(p);
533 len = q - p;
534 if (len) {
535 oldchar = p[len];
536 p[len] = 0;
537 while (j - i > 1) {
538 k = (j + i) / 2;
539 m = nasm_stricmp(p, tasm_directives[k]);
540 if (m == 0) {
541 /* We have found a directive, so jam a % in front of it
542 * so that NASM will then recognise it as one if it's own.
544 p[len] = oldchar;
545 len = strlen(p);
546 oldline = line;
547 line = nasm_malloc(len + 2);
548 line[0] = '%';
549 if (k == TM_IFDIFI) {
551 * NASM does not recognise IFDIFI, so we convert
552 * it to %if 0. This is not used in NASM
553 * compatible code, but does need to parse for the
554 * TASM macro package.
556 strcpy(line + 1, "if 0");
557 } else {
558 memcpy(line + 1, p, len + 1);
560 nasm_free(oldline);
561 return line;
562 } else if (m < 0) {
563 j = k;
564 } else
565 i = k;
567 p[len] = oldchar;
569 return line;
573 * The pre-preprocessing stage... This function translates line
574 * number indications as they emerge from GNU cpp (`# lineno "file"
575 * flags') into NASM preprocessor line number indications (`%line
576 * lineno file').
578 static char *prepreproc(char *line)
580 int lineno, fnlen;
581 char *fname, *oldline;
583 if (line[0] == '#' && line[1] == ' ') {
584 oldline = line;
585 fname = oldline + 2;
586 lineno = atoi(fname);
587 fname += strspn(fname, "0123456789 ");
588 if (*fname == '"')
589 fname++;
590 fnlen = strcspn(fname, "\"");
591 line = nasm_malloc(20 + fnlen);
592 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
593 nasm_free(oldline);
595 if (tasm_compatible_mode)
596 return check_tasm_directive(line);
597 return line;
601 * Free a linked list of tokens.
603 static void free_tlist(Token * list)
605 while (list)
606 list = delete_Token(list);
610 * Free a linked list of lines.
612 static void free_llist(Line * list)
614 Line *l, *tmp;
615 list_for_each_safe(l, tmp, list) {
616 free_tlist(l->first);
617 nasm_free(l);
622 * Free an MMacro
624 static void free_mmacro(MMacro * m)
626 nasm_free(m->name);
627 free_tlist(m->dlist);
628 nasm_free(m->defaults);
629 free_llist(m->expansion);
630 nasm_free(m);
634 * Free all currently defined macros, and free the hash tables
636 static void free_smacro_table(struct hash_table *smt)
638 SMacro *s, *tmp;
639 const char *key;
640 struct hash_tbl_node *it = NULL;
642 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
643 nasm_free((void *)key);
644 list_for_each_safe(s, tmp, s) {
645 nasm_free(s->name);
646 free_tlist(s->expansion);
647 nasm_free(s);
650 hash_free(smt);
653 static void free_mmacro_table(struct hash_table *mmt)
655 MMacro *m, *tmp;
656 const char *key;
657 struct hash_tbl_node *it = NULL;
659 it = NULL;
660 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
661 nasm_free((void *)key);
662 list_for_each_safe(m ,tmp, m)
663 free_mmacro(m);
665 hash_free(mmt);
668 static void free_macros(void)
670 free_smacro_table(&smacros);
671 free_mmacro_table(&mmacros);
675 * Initialize the hash tables
677 static void init_macros(void)
679 hash_init(&smacros, HASH_LARGE);
680 hash_init(&mmacros, HASH_LARGE);
684 * Pop the context stack.
686 static void ctx_pop(void)
688 Context *c = cstk;
690 cstk = cstk->next;
691 free_smacro_table(&c->localmac);
692 nasm_free(c->name);
693 nasm_free(c);
697 * Search for a key in the hash index; adding it if necessary
698 * (in which case we initialize the data pointer to NULL.)
700 static void **
701 hash_findi_add(struct hash_table *hash, const char *str)
703 struct hash_insert hi;
704 void **r;
705 char *strx;
707 r = hash_findi(hash, str, &hi);
708 if (r)
709 return r;
711 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
712 return hash_add(&hi, strx, NULL);
716 * Like hash_findi, but returns the data element rather than a pointer
717 * to it. Used only when not adding a new element, hence no third
718 * argument.
720 static void *
721 hash_findix(struct hash_table *hash, const char *str)
723 void **p;
725 p = hash_findi(hash, str, NULL);
726 return p ? *p : NULL;
730 * read line from standart macros set,
731 * if there no more left -- return NULL
733 static char *line_from_stdmac(void)
735 unsigned char c;
736 const unsigned char *p = stdmacpos;
737 char *line, *q;
738 size_t len = 0;
740 if (!stdmacpos)
741 return NULL;
743 while ((c = *p++)) {
744 if (c >= 0x80)
745 len += pp_directives_len[c - 0x80] + 1;
746 else
747 len++;
750 line = nasm_malloc(len + 1);
751 q = line;
752 while ((c = *stdmacpos++)) {
753 if (c >= 0x80) {
754 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
755 q += pp_directives_len[c - 0x80];
756 *q++ = ' ';
757 } else {
758 *q++ = c;
761 stdmacpos = p;
762 *q = '\0';
764 if (!*stdmacpos) {
765 /* This was the last of the standard macro chain... */
766 stdmacpos = NULL;
767 if (any_extrastdmac) {
768 stdmacpos = extrastdmac;
769 any_extrastdmac = false;
770 } else if (do_predef) {
771 Line *pd, *l;
772 Token *head, **tail, *t;
775 * Nasty hack: here we push the contents of
776 * `predef' on to the top-level expansion stack,
777 * since this is the most convenient way to
778 * implement the pre-include and pre-define
779 * features.
781 list_for_each(pd, predef) {
782 head = NULL;
783 tail = &head;
784 list_for_each(t, pd->first) {
785 *tail = new_Token(NULL, t->type, t->text, 0);
786 tail = &(*tail)->next;
789 l = nasm_malloc(sizeof(Line));
790 l->next = istk->expansion;
791 l->first = head;
792 l->finishes = NULL;
794 istk->expansion = l;
796 do_predef = false;
800 return line;
803 static char *read_line(void)
805 unsigned int size, c, next;
806 const unsigned int delta = 512;
807 const unsigned int pad = 8;
808 unsigned int nr_cont = 0;
809 bool cont = false;
810 char *buffer, *p;
812 /* Standart macros set (predefined) goes first */
813 p = line_from_stdmac();
814 if (p)
815 return p;
817 size = delta;
818 p = buffer = nasm_malloc(size);
820 for (;;) {
821 c = fgetc(istk->fp);
822 if ((int)(c) == EOF) {
823 p[0] = 0;
824 break;
827 switch (c) {
828 case '\r':
829 next = fgetc(istk->fp);
830 if (next != '\n')
831 ungetc(next, istk->fp);
832 if (cont) {
833 cont = false;
834 continue;
836 break;
838 case '\n':
839 if (cont) {
840 cont = false;
841 continue;
843 break;
845 case '\\':
846 next = fgetc(istk->fp);
847 ungetc(next, istk->fp);
848 if (next == '\r' || next == '\n') {
849 cont = true;
850 nr_cont++;
851 continue;
853 break;
856 if (c == '\r' || c == '\n') {
857 *p++ = 0;
858 break;
861 if (p >= (buffer + size - pad)) {
862 buffer = nasm_realloc(buffer, size + delta);
863 p = buffer + size - pad;
864 size += delta;
867 *p++ = (unsigned char)c;
870 if (p == buffer) {
871 nasm_free(buffer);
872 return NULL;
875 src_set_linnum(src_get_linnum() + istk->lineinc +
876 (nr_cont * istk->lineinc));
879 * Handle spurious ^Z, which may be inserted into source files
880 * by some file transfer utilities.
882 buffer[strcspn(buffer, "\032")] = '\0';
884 lfmt->line(LIST_READ, buffer);
886 return buffer;
890 * Tokenize a line of text. This is a very simple process since we
891 * don't need to parse the value out of e.g. numeric tokens: we
892 * simply split one string into many.
894 static Token *tokenize(char *line)
896 char c, *p = line;
897 enum pp_token_type type;
898 Token *list = NULL;
899 Token *t, **tail = &list;
901 while (*line) {
902 p = line;
903 if (*p == '%') {
904 p++;
905 if (*p == '+' && !nasm_isdigit(p[1])) {
906 p++;
907 type = TOK_PASTE;
908 } else if (nasm_isdigit(*p) ||
909 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
910 do {
911 p++;
913 while (nasm_isdigit(*p));
914 type = TOK_PREPROC_ID;
915 } else if (*p == '{') {
916 p++;
917 while (*p) {
918 if (*p == '}')
919 break;
920 p[-1] = *p;
921 p++;
923 if (*p != '}')
924 nasm_error(ERR_WARNING | ERR_PASS1,
925 "unterminated %%{ construct");
926 p[-1] = '\0';
927 if (*p)
928 p++;
929 type = TOK_PREPROC_ID;
930 } else if (*p == '[') {
931 int lvl = 1;
932 line += 2; /* Skip the leading %[ */
933 p++;
934 while (lvl && (c = *p++)) {
935 switch (c) {
936 case ']':
937 lvl--;
938 break;
939 case '%':
940 if (*p == '[')
941 lvl++;
942 break;
943 case '\'':
944 case '\"':
945 case '`':
946 p = nasm_skip_string(p - 1) + 1;
947 break;
948 default:
949 break;
952 p--;
953 if (*p)
954 *p++ = '\0';
955 if (lvl)
956 nasm_error(ERR_NONFATAL|ERR_PASS1,
957 "unterminated %%[ construct");
958 type = TOK_INDIRECT;
959 } else if (*p == '?') {
960 type = TOK_PREPROC_Q; /* %? */
961 p++;
962 if (*p == '?') {
963 type = TOK_PREPROC_QQ; /* %?? */
964 p++;
966 } else if (*p == '!') {
967 type = TOK_PREPROC_ID;
968 p++;
969 if (isidchar(*p)) {
970 do {
971 p++;
973 while (isidchar(*p));
974 } else if (*p == '\'' || *p == '\"' || *p == '`') {
975 p = nasm_skip_string(p);
976 if (*p)
977 p++;
978 else
979 nasm_error(ERR_NONFATAL|ERR_PASS1,
980 "unterminated %%! string");
981 } else {
982 /* %! without string or identifier */
983 type = TOK_OTHER; /* Legacy behavior... */
985 } else if (isidchar(*p) ||
986 ((*p == '!' || *p == '%' || *p == '$') &&
987 isidchar(p[1]))) {
988 do {
989 p++;
991 while (isidchar(*p));
992 type = TOK_PREPROC_ID;
993 } else {
994 type = TOK_OTHER;
995 if (*p == '%')
996 p++;
998 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
999 type = TOK_ID;
1000 p++;
1001 while (*p && isidchar(*p))
1002 p++;
1003 } else if (*p == '\'' || *p == '"' || *p == '`') {
1005 * A string token.
1007 type = TOK_STRING;
1008 p = nasm_skip_string(p);
1010 if (*p) {
1011 p++;
1012 } else {
1013 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1014 /* Handling unterminated strings by UNV */
1015 /* type = -1; */
1017 } else if (p[0] == '$' && p[1] == '$') {
1018 type = TOK_OTHER; /* TOKEN_BASE */
1019 p += 2;
1020 } else if (isnumstart(*p)) {
1021 bool is_hex = false;
1022 bool is_float = false;
1023 bool has_e = false;
1024 char c, *r;
1027 * A numeric token.
1030 if (*p == '$') {
1031 p++;
1032 is_hex = true;
1035 for (;;) {
1036 c = *p++;
1038 if (!is_hex && (c == 'e' || c == 'E')) {
1039 has_e = true;
1040 if (*p == '+' || *p == '-') {
1042 * e can only be followed by +/- if it is either a
1043 * prefixed hex number or a floating-point number
1045 p++;
1046 is_float = true;
1048 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1049 is_hex = true;
1050 } else if (c == 'P' || c == 'p') {
1051 is_float = true;
1052 if (*p == '+' || *p == '-')
1053 p++;
1054 } else if (isnumchar(c) || c == '_')
1055 ; /* just advance */
1056 else if (c == '.') {
1058 * we need to deal with consequences of the legacy
1059 * parser, like "1.nolist" being two tokens
1060 * (TOK_NUMBER, TOK_ID) here; at least give it
1061 * a shot for now. In the future, we probably need
1062 * a flex-based scanner with proper pattern matching
1063 * to do it as well as it can be done. Nothing in
1064 * the world is going to help the person who wants
1065 * 0x123.p16 interpreted as two tokens, though.
1067 r = p;
1068 while (*r == '_')
1069 r++;
1071 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1072 (!is_hex && (*r == 'e' || *r == 'E')) ||
1073 (*r == 'p' || *r == 'P')) {
1074 p = r;
1075 is_float = true;
1076 } else
1077 break; /* Terminate the token */
1078 } else
1079 break;
1081 p--; /* Point to first character beyond number */
1083 if (p == line+1 && *line == '$') {
1084 type = TOK_OTHER; /* TOKEN_HERE */
1085 } else {
1086 if (has_e && !is_hex) {
1087 /* 1e13 is floating-point, but 1e13h is not */
1088 is_float = true;
1091 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1093 } else if (nasm_isspace(*p)) {
1094 type = TOK_WHITESPACE;
1095 p = nasm_skip_spaces(p);
1097 * Whitespace just before end-of-line is discarded by
1098 * pretending it's a comment; whitespace just before a
1099 * comment gets lumped into the comment.
1101 if (!*p || *p == ';') {
1102 type = TOK_COMMENT;
1103 while (*p)
1104 p++;
1106 } else if (*p == ';') {
1107 type = TOK_COMMENT;
1108 while (*p)
1109 p++;
1110 } else {
1112 * Anything else is an operator of some kind. We check
1113 * for all the double-character operators (>>, <<, //,
1114 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1115 * else is a single-character operator.
1117 type = TOK_OTHER;
1118 if ((p[0] == '>' && p[1] == '>') ||
1119 (p[0] == '<' && p[1] == '<') ||
1120 (p[0] == '/' && p[1] == '/') ||
1121 (p[0] == '<' && p[1] == '=') ||
1122 (p[0] == '>' && p[1] == '=') ||
1123 (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++;
1131 p++;
1134 /* Handling unterminated string by UNV */
1135 /*if (type == -1)
1137 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1138 t->text[p-line] = *line;
1139 tail = &t->next;
1141 else */
1142 if (type != TOK_COMMENT) {
1143 *tail = t = new_Token(NULL, type, line, p - line);
1144 tail = &t->next;
1146 line = p;
1148 return list;
1152 * this function allocates a new managed block of memory and
1153 * returns a pointer to the block. The managed blocks are
1154 * deleted only all at once by the delete_Blocks function.
1156 static void *new_Block(size_t size)
1158 Blocks *b = &blocks;
1160 /* first, get to the end of the linked list */
1161 while (b->next)
1162 b = b->next;
1163 /* now allocate the requested chunk */
1164 b->chunk = nasm_malloc(size);
1166 /* now allocate a new block for the next request */
1167 b->next = nasm_zalloc(sizeof(Blocks));
1168 return b->chunk;
1172 * this function deletes all managed blocks of memory
1174 static void delete_Blocks(void)
1176 Blocks *a, *b = &blocks;
1179 * keep in mind that the first block, pointed to by blocks
1180 * is a static and not dynamically allocated, so we don't
1181 * free it.
1183 while (b) {
1184 if (b->chunk)
1185 nasm_free(b->chunk);
1186 a = b;
1187 b = b->next;
1188 if (a != &blocks)
1189 nasm_free(a);
1191 memset(&blocks, 0, sizeof(blocks));
1195 * this function creates a new Token and passes a pointer to it
1196 * back to the caller. It sets the type and text elements, and
1197 * also the a.mac and next elements to NULL.
1199 static Token *new_Token(Token * next, enum pp_token_type type,
1200 const char *text, int txtlen)
1202 Token *t;
1203 int i;
1205 if (!freeTokens) {
1206 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1207 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1208 freeTokens[i].next = &freeTokens[i + 1];
1209 freeTokens[i].next = NULL;
1211 t = freeTokens;
1212 freeTokens = t->next;
1213 t->next = next;
1214 t->a.mac = NULL;
1215 t->type = type;
1216 if (type == TOK_WHITESPACE || !text) {
1217 t->text = NULL;
1218 } else {
1219 if (txtlen == 0)
1220 txtlen = strlen(text);
1221 t->text = nasm_malloc(txtlen+1);
1222 memcpy(t->text, text, txtlen);
1223 t->text[txtlen] = '\0';
1225 return t;
1228 static Token *delete_Token(Token * t)
1230 Token *next = t->next;
1231 nasm_free(t->text);
1232 t->next = freeTokens;
1233 freeTokens = t;
1234 return next;
1238 * Convert a line of tokens back into text.
1239 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1240 * will be transformed into ..@ctxnum.xxx
1242 static char *detoken(Token * tlist, bool expand_locals)
1244 Token *t;
1245 char *line, *p;
1246 const char *q;
1247 int len = 0;
1249 list_for_each(t, tlist) {
1250 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1251 char *v;
1252 char *q = t->text;
1254 v = t->text + 2;
1255 if (*v == '\'' || *v == '\"' || *v == '`') {
1256 size_t len = nasm_unquote(v, NULL);
1257 size_t clen = strlen(v);
1259 if (len != clen) {
1260 nasm_error(ERR_NONFATAL | ERR_PASS1,
1261 "NUL character in %%! string");
1262 v = NULL;
1266 if (v) {
1267 char *p = getenv(v);
1268 if (!p) {
1269 nasm_error(ERR_NONFATAL | ERR_PASS1,
1270 "nonexistent environment variable `%s'", v);
1271 p = "";
1273 t->text = nasm_strdup(p);
1275 nasm_free(q);
1278 /* Expand local macros here and not during preprocessing */
1279 if (expand_locals &&
1280 t->type == TOK_PREPROC_ID && t->text &&
1281 t->text[0] == '%' && t->text[1] == '$') {
1282 const char *q;
1283 char *p;
1284 Context *ctx = get_ctx(t->text, &q);
1285 if (ctx) {
1286 char buffer[40];
1287 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1288 p = nasm_strcat(buffer, q);
1289 nasm_free(t->text);
1290 t->text = p;
1293 if (t->type == TOK_WHITESPACE)
1294 len++;
1295 else if (t->text)
1296 len += strlen(t->text);
1299 p = line = nasm_malloc(len + 1);
1301 list_for_each(t, tlist) {
1302 if (t->type == TOK_WHITESPACE) {
1303 *p++ = ' ';
1304 } else if (t->text) {
1305 q = t->text;
1306 while (*q)
1307 *p++ = *q++;
1310 *p = '\0';
1312 return line;
1316 * A scanner, suitable for use by the expression evaluator, which
1317 * operates on a line of Tokens. Expects a pointer to a pointer to
1318 * the first token in the line to be passed in as its private_data
1319 * field.
1321 * FIX: This really needs to be unified with stdscan.
1323 static int ppscan(void *private_data, struct tokenval *tokval)
1325 Token **tlineptr = private_data;
1326 Token *tline;
1327 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1329 do {
1330 tline = *tlineptr;
1331 *tlineptr = tline ? tline->next : NULL;
1332 } while (tline && (tline->type == TOK_WHITESPACE ||
1333 tline->type == TOK_COMMENT));
1335 if (!tline)
1336 return tokval->t_type = TOKEN_EOS;
1338 tokval->t_charptr = tline->text;
1340 if (tline->text[0] == '$' && !tline->text[1])
1341 return tokval->t_type = TOKEN_HERE;
1342 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1343 return tokval->t_type = TOKEN_BASE;
1345 if (tline->type == TOK_ID) {
1346 p = tokval->t_charptr = tline->text;
1347 if (p[0] == '$') {
1348 tokval->t_charptr++;
1349 return tokval->t_type = TOKEN_ID;
1352 for (r = p, s = ourcopy; *r; r++) {
1353 if (r >= p+MAX_KEYWORD)
1354 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1355 *s++ = nasm_tolower(*r);
1357 *s = '\0';
1358 /* right, so we have an identifier sitting in temp storage. now,
1359 * is it actually a register or instruction name, or what? */
1360 return nasm_token_hash(ourcopy, tokval);
1363 if (tline->type == TOK_NUMBER) {
1364 bool rn_error;
1365 tokval->t_integer = readnum(tline->text, &rn_error);
1366 tokval->t_charptr = tline->text;
1367 if (rn_error)
1368 return tokval->t_type = TOKEN_ERRNUM;
1369 else
1370 return tokval->t_type = TOKEN_NUM;
1373 if (tline->type == TOK_FLOAT) {
1374 return tokval->t_type = TOKEN_FLOAT;
1377 if (tline->type == TOK_STRING) {
1378 char bq, *ep;
1380 bq = tline->text[0];
1381 tokval->t_charptr = tline->text;
1382 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1384 if (ep[0] != bq || ep[1] != '\0')
1385 return tokval->t_type = TOKEN_ERRSTR;
1386 else
1387 return tokval->t_type = TOKEN_STR;
1390 if (tline->type == TOK_OTHER) {
1391 if (!strcmp(tline->text, "<<"))
1392 return tokval->t_type = TOKEN_SHL;
1393 if (!strcmp(tline->text, ">>"))
1394 return tokval->t_type = TOKEN_SHR;
1395 if (!strcmp(tline->text, "//"))
1396 return tokval->t_type = TOKEN_SDIV;
1397 if (!strcmp(tline->text, "%%"))
1398 return tokval->t_type = TOKEN_SMOD;
1399 if (!strcmp(tline->text, "=="))
1400 return tokval->t_type = TOKEN_EQ;
1401 if (!strcmp(tline->text, "<>"))
1402 return tokval->t_type = TOKEN_NE;
1403 if (!strcmp(tline->text, "!="))
1404 return tokval->t_type = TOKEN_NE;
1405 if (!strcmp(tline->text, "<="))
1406 return tokval->t_type = TOKEN_LE;
1407 if (!strcmp(tline->text, ">="))
1408 return tokval->t_type = TOKEN_GE;
1409 if (!strcmp(tline->text, "&&"))
1410 return tokval->t_type = TOKEN_DBL_AND;
1411 if (!strcmp(tline->text, "^^"))
1412 return tokval->t_type = TOKEN_DBL_XOR;
1413 if (!strcmp(tline->text, "||"))
1414 return tokval->t_type = TOKEN_DBL_OR;
1418 * We have no other options: just return the first character of
1419 * the token text.
1421 return tokval->t_type = tline->text[0];
1425 * Compare a string to the name of an existing macro; this is a
1426 * simple wrapper which calls either strcmp or nasm_stricmp
1427 * depending on the value of the `casesense' parameter.
1429 static int mstrcmp(const char *p, const char *q, bool casesense)
1431 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1435 * Compare a string to the name of an existing macro; this is a
1436 * simple wrapper which calls either strcmp or nasm_stricmp
1437 * depending on the value of the `casesense' parameter.
1439 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1441 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1445 * Return the Context structure associated with a %$ token. Return
1446 * NULL, having _already_ reported an error condition, if the
1447 * context stack isn't deep enough for the supplied number of $
1448 * signs.
1450 * If "namep" is non-NULL, set it to the pointer to the macro name
1451 * tail, i.e. the part beyond %$...
1453 static Context *get_ctx(const char *name, const char **namep)
1455 Context *ctx;
1456 int i;
1458 if (namep)
1459 *namep = name;
1461 if (!name || name[0] != '%' || name[1] != '$')
1462 return NULL;
1464 if (!cstk) {
1465 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1466 return NULL;
1469 name += 2;
1470 ctx = cstk;
1471 i = 0;
1472 while (ctx && *name == '$') {
1473 name++;
1474 i++;
1475 ctx = ctx->next;
1477 if (!ctx) {
1478 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1479 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1480 return NULL;
1483 if (namep)
1484 *namep = name;
1486 return ctx;
1490 * Check to see if a file is already in a string list
1492 static bool in_list(const StrList *list, const char *str)
1494 while (list) {
1495 if (!strcmp(list->str, str))
1496 return true;
1497 list = list->next;
1499 return false;
1503 * Open an include file. This routine must always return a valid
1504 * file pointer if it returns - it's responsible for throwing an
1505 * ERR_FATAL and bombing out completely if not. It should also try
1506 * the include path one by one until it finds the file or reaches
1507 * the end of the path.
1509 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1510 bool missing_ok, const char *mode)
1512 FILE *fp;
1513 char *prefix = "";
1514 IncPath *ip = ipath;
1515 int len = strlen(file);
1516 size_t prefix_len = 0;
1517 StrList *sl;
1519 while (1) {
1520 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1521 memcpy(sl->str, prefix, prefix_len);
1522 memcpy(sl->str+prefix_len, file, len+1);
1523 fp = fopen(sl->str, mode);
1524 if (fp && dhead && !in_list(*dhead, sl->str)) {
1525 sl->next = NULL;
1526 **dtail = sl;
1527 *dtail = &sl->next;
1528 } else {
1529 nasm_free(sl);
1531 if (fp)
1532 return fp;
1533 if (!ip) {
1534 if (!missing_ok)
1535 break;
1536 prefix = NULL;
1537 } else {
1538 prefix = ip->path;
1539 ip = ip->next;
1541 if (prefix) {
1542 prefix_len = strlen(prefix);
1543 } else {
1544 /* -MG given and file not found */
1545 if (dhead && !in_list(*dhead, file)) {
1546 sl = nasm_malloc(len+1+sizeof sl->next);
1547 sl->next = NULL;
1548 strcpy(sl->str, file);
1549 **dtail = sl;
1550 *dtail = &sl->next;
1552 return NULL;
1556 nasm_error(ERR_FATAL, "unable to open include file `%s'", file);
1557 return NULL;
1561 * Opens an include or input file. Public version, for use by modules
1562 * that get a file:lineno pair and need to look at the file again
1563 * (e.g. the CodeView debug backend). Returns NULL on failure.
1565 FILE *pp_input_fopen(const char *filename, const char *mode)
1567 FILE *fp;
1568 StrList *xsl = NULL;
1569 StrList **xst = &xsl;
1571 fp = inc_fopen(filename, &xsl, &xst, true, mode);
1572 if (xsl)
1573 nasm_free(xsl);
1574 return fp;
1578 * Determine if we should warn on defining a single-line macro of
1579 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1580 * return true if _any_ single-line macro of that name is defined.
1581 * Otherwise, will return true if a single-line macro with either
1582 * `nparam' or no parameters is defined.
1584 * If a macro with precisely the right number of parameters is
1585 * defined, or nparam is -1, the address of the definition structure
1586 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1587 * is NULL, no action will be taken regarding its contents, and no
1588 * error will occur.
1590 * Note that this is also called with nparam zero to resolve
1591 * `ifdef'.
1593 * If you already know which context macro belongs to, you can pass
1594 * the context pointer as first parameter; if you won't but name begins
1595 * with %$ the context will be automatically computed. If all_contexts
1596 * is true, macro will be searched in outer contexts as well.
1598 static bool
1599 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1600 bool nocase)
1602 struct hash_table *smtbl;
1603 SMacro *m;
1605 if (ctx) {
1606 smtbl = &ctx->localmac;
1607 } else if (name[0] == '%' && name[1] == '$') {
1608 if (cstk)
1609 ctx = get_ctx(name, &name);
1610 if (!ctx)
1611 return false; /* got to return _something_ */
1612 smtbl = &ctx->localmac;
1613 } else {
1614 smtbl = &smacros;
1616 m = (SMacro *) hash_findix(smtbl, name);
1618 while (m) {
1619 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1620 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1621 if (defn) {
1622 if (nparam == (int) m->nparam || nparam == -1)
1623 *defn = m;
1624 else
1625 *defn = NULL;
1627 return true;
1629 m = m->next;
1632 return false;
1636 * Count and mark off the parameters in a multi-line macro call.
1637 * This is called both from within the multi-line macro expansion
1638 * code, and also to mark off the default parameters when provided
1639 * in a %macro definition line.
1641 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1643 int paramsize, brace;
1645 *nparam = paramsize = 0;
1646 *params = NULL;
1647 while (t) {
1648 /* +1: we need space for the final NULL */
1649 if (*nparam+1 >= paramsize) {
1650 paramsize += PARAM_DELTA;
1651 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1653 skip_white_(t);
1654 brace = 0;
1655 if (tok_is_(t, "{"))
1656 brace++;
1657 (*params)[(*nparam)++] = t;
1658 if (brace) {
1659 while (brace && (t = t->next) != NULL) {
1660 if (tok_is_(t, "{"))
1661 brace++;
1662 else if (tok_is_(t, "}"))
1663 brace--;
1666 if (t) {
1668 * Now we've found the closing brace, look further
1669 * for the comma.
1671 t = t->next;
1672 skip_white_(t);
1673 if (tok_isnt_(t, ",")) {
1674 nasm_error(ERR_NONFATAL,
1675 "braces do not enclose all of macro parameter");
1676 while (tok_isnt_(t, ","))
1677 t = t->next;
1680 } else {
1681 while (tok_isnt_(t, ","))
1682 t = t->next;
1684 if (t) { /* got a comma/brace */
1685 t = t->next; /* eat the comma */
1691 * Determine whether one of the various `if' conditions is true or
1692 * not.
1694 * We must free the tline we get passed.
1696 static bool if_condition(Token * tline, enum preproc_token ct)
1698 enum pp_conditional i = PP_COND(ct);
1699 bool j;
1700 Token *t, *tt, **tptr, *origline;
1701 struct tokenval tokval;
1702 expr *evalresult;
1703 enum pp_token_type needtype;
1704 char *p;
1706 origline = tline;
1708 switch (i) {
1709 case PPC_IFCTX:
1710 j = false; /* have we matched yet? */
1711 while (true) {
1712 skip_white_(tline);
1713 if (!tline)
1714 break;
1715 if (tline->type != TOK_ID) {
1716 nasm_error(ERR_NONFATAL,
1717 "`%s' expects context identifiers", pp_directives[ct]);
1718 free_tlist(origline);
1719 return -1;
1721 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1722 j = true;
1723 tline = tline->next;
1725 break;
1727 case PPC_IFDEF:
1728 j = false; /* have we matched yet? */
1729 while (tline) {
1730 skip_white_(tline);
1731 if (!tline || (tline->type != TOK_ID &&
1732 (tline->type != TOK_PREPROC_ID ||
1733 tline->text[1] != '$'))) {
1734 nasm_error(ERR_NONFATAL,
1735 "`%s' expects macro identifiers", pp_directives[ct]);
1736 goto fail;
1738 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1739 j = true;
1740 tline = tline->next;
1742 break;
1744 case PPC_IFENV:
1745 tline = expand_smacro(tline);
1746 j = false; /* have we matched yet? */
1747 while (tline) {
1748 skip_white_(tline);
1749 if (!tline || (tline->type != TOK_ID &&
1750 tline->type != TOK_STRING &&
1751 (tline->type != TOK_PREPROC_ID ||
1752 tline->text[1] != '!'))) {
1753 nasm_error(ERR_NONFATAL,
1754 "`%s' expects environment variable names",
1755 pp_directives[ct]);
1756 goto fail;
1758 p = tline->text;
1759 if (tline->type == TOK_PREPROC_ID)
1760 p += 2; /* Skip leading %! */
1761 if (*p == '\'' || *p == '\"' || *p == '`')
1762 nasm_unquote_cstr(p, ct);
1763 if (getenv(p))
1764 j = true;
1765 tline = tline->next;
1767 break;
1769 case PPC_IFIDN:
1770 case PPC_IFIDNI:
1771 tline = expand_smacro(tline);
1772 t = tt = tline;
1773 while (tok_isnt_(tt, ","))
1774 tt = tt->next;
1775 if (!tt) {
1776 nasm_error(ERR_NONFATAL,
1777 "`%s' expects two comma-separated arguments",
1778 pp_directives[ct]);
1779 goto fail;
1781 tt = tt->next;
1782 j = true; /* assume equality unless proved not */
1783 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1784 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1785 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1786 pp_directives[ct]);
1787 goto fail;
1789 if (t->type == TOK_WHITESPACE) {
1790 t = t->next;
1791 continue;
1793 if (tt->type == TOK_WHITESPACE) {
1794 tt = tt->next;
1795 continue;
1797 if (tt->type != t->type) {
1798 j = false; /* found mismatching tokens */
1799 break;
1801 /* When comparing strings, need to unquote them first */
1802 if (t->type == TOK_STRING) {
1803 size_t l1 = nasm_unquote(t->text, NULL);
1804 size_t l2 = nasm_unquote(tt->text, NULL);
1806 if (l1 != l2) {
1807 j = false;
1808 break;
1810 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1811 j = false;
1812 break;
1814 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1815 j = false; /* found mismatching tokens */
1816 break;
1819 t = t->next;
1820 tt = tt->next;
1822 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1823 j = false; /* trailing gunk on one end or other */
1824 break;
1826 case PPC_IFMACRO:
1828 bool found = false;
1829 MMacro searching, *mmac;
1831 skip_white_(tline);
1832 tline = expand_id(tline);
1833 if (!tok_type_(tline, TOK_ID)) {
1834 nasm_error(ERR_NONFATAL,
1835 "`%s' expects a macro name", pp_directives[ct]);
1836 goto fail;
1838 searching.name = nasm_strdup(tline->text);
1839 searching.casesense = true;
1840 searching.plus = false;
1841 searching.nolist = false;
1842 searching.in_progress = 0;
1843 searching.max_depth = 0;
1844 searching.rep_nest = NULL;
1845 searching.nparam_min = 0;
1846 searching.nparam_max = INT_MAX;
1847 tline = expand_smacro(tline->next);
1848 skip_white_(tline);
1849 if (!tline) {
1850 } else if (!tok_type_(tline, TOK_NUMBER)) {
1851 nasm_error(ERR_NONFATAL,
1852 "`%s' expects a parameter count or nothing",
1853 pp_directives[ct]);
1854 } else {
1855 searching.nparam_min = searching.nparam_max =
1856 readnum(tline->text, &j);
1857 if (j)
1858 nasm_error(ERR_NONFATAL,
1859 "unable to parse parameter count `%s'",
1860 tline->text);
1862 if (tline && tok_is_(tline->next, "-")) {
1863 tline = tline->next->next;
1864 if (tok_is_(tline, "*"))
1865 searching.nparam_max = INT_MAX;
1866 else if (!tok_type_(tline, TOK_NUMBER))
1867 nasm_error(ERR_NONFATAL,
1868 "`%s' expects a parameter count after `-'",
1869 pp_directives[ct]);
1870 else {
1871 searching.nparam_max = readnum(tline->text, &j);
1872 if (j)
1873 nasm_error(ERR_NONFATAL,
1874 "unable to parse parameter count `%s'",
1875 tline->text);
1876 if (searching.nparam_min > searching.nparam_max)
1877 nasm_error(ERR_NONFATAL,
1878 "minimum parameter count exceeds maximum");
1881 if (tline && tok_is_(tline->next, "+")) {
1882 tline = tline->next;
1883 searching.plus = true;
1885 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1886 while (mmac) {
1887 if (!strcmp(mmac->name, searching.name) &&
1888 (mmac->nparam_min <= searching.nparam_max
1889 || searching.plus)
1890 && (searching.nparam_min <= mmac->nparam_max
1891 || mmac->plus)) {
1892 found = true;
1893 break;
1895 mmac = mmac->next;
1897 if (tline && tline->next)
1898 nasm_error(ERR_WARNING|ERR_PASS1,
1899 "trailing garbage after %%ifmacro ignored");
1900 nasm_free(searching.name);
1901 j = found;
1902 break;
1905 case PPC_IFID:
1906 needtype = TOK_ID;
1907 goto iftype;
1908 case PPC_IFNUM:
1909 needtype = TOK_NUMBER;
1910 goto iftype;
1911 case PPC_IFSTR:
1912 needtype = TOK_STRING;
1913 goto iftype;
1915 iftype:
1916 t = tline = expand_smacro(tline);
1918 while (tok_type_(t, TOK_WHITESPACE) ||
1919 (needtype == TOK_NUMBER &&
1920 tok_type_(t, TOK_OTHER) &&
1921 (t->text[0] == '-' || t->text[0] == '+') &&
1922 !t->text[1]))
1923 t = t->next;
1925 j = tok_type_(t, needtype);
1926 break;
1928 case PPC_IFTOKEN:
1929 t = tline = expand_smacro(tline);
1930 while (tok_type_(t, TOK_WHITESPACE))
1931 t = t->next;
1933 j = false;
1934 if (t) {
1935 t = t->next; /* Skip the actual token */
1936 while (tok_type_(t, TOK_WHITESPACE))
1937 t = t->next;
1938 j = !t; /* Should be nothing left */
1940 break;
1942 case PPC_IFEMPTY:
1943 t = tline = expand_smacro(tline);
1944 while (tok_type_(t, TOK_WHITESPACE))
1945 t = t->next;
1947 j = !t; /* Should be empty */
1948 break;
1950 case PPC_IF:
1951 t = tline = expand_smacro(tline);
1952 tptr = &t;
1953 tokval.t_type = TOKEN_INVALID;
1954 evalresult = evaluate(ppscan, tptr, &tokval,
1955 NULL, pass | CRITICAL, NULL);
1956 if (!evalresult)
1957 return -1;
1958 if (tokval.t_type)
1959 nasm_error(ERR_WARNING|ERR_PASS1,
1960 "trailing garbage after expression ignored");
1961 if (!is_simple(evalresult)) {
1962 nasm_error(ERR_NONFATAL,
1963 "non-constant value given to `%s'", pp_directives[ct]);
1964 goto fail;
1966 j = reloc_value(evalresult) != 0;
1967 break;
1969 default:
1970 nasm_error(ERR_FATAL,
1971 "preprocessor directive `%s' not yet implemented",
1972 pp_directives[ct]);
1973 goto fail;
1976 free_tlist(origline);
1977 return j ^ PP_NEGATIVE(ct);
1979 fail:
1980 free_tlist(origline);
1981 return -1;
1985 * Common code for defining an smacro
1987 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1988 int nparam, Token *expansion)
1990 SMacro *smac, **smhead;
1991 struct hash_table *smtbl;
1993 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1994 if (!smac) {
1995 nasm_error(ERR_WARNING|ERR_PASS1,
1996 "single-line macro `%s' defined both with and"
1997 " without parameters", mname);
1999 * Some instances of the old code considered this a failure,
2000 * some others didn't. What is the right thing to do here?
2002 free_tlist(expansion);
2003 return false; /* Failure */
2004 } else {
2006 * We're redefining, so we have to take over an
2007 * existing SMacro structure. This means freeing
2008 * what was already in it.
2010 nasm_free(smac->name);
2011 free_tlist(smac->expansion);
2013 } else {
2014 smtbl = ctx ? &ctx->localmac : &smacros;
2015 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2016 smac = nasm_malloc(sizeof(SMacro));
2017 smac->next = *smhead;
2018 *smhead = smac;
2020 smac->name = nasm_strdup(mname);
2021 smac->casesense = casesense;
2022 smac->nparam = nparam;
2023 smac->expansion = expansion;
2024 smac->in_progress = false;
2025 return true; /* Success */
2029 * Undefine an smacro
2031 static void undef_smacro(Context *ctx, const char *mname)
2033 SMacro **smhead, *s, **sp;
2034 struct hash_table *smtbl;
2036 smtbl = ctx ? &ctx->localmac : &smacros;
2037 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2039 if (smhead) {
2041 * We now have a macro name... go hunt for it.
2043 sp = smhead;
2044 while ((s = *sp) != NULL) {
2045 if (!mstrcmp(s->name, mname, s->casesense)) {
2046 *sp = s->next;
2047 nasm_free(s->name);
2048 free_tlist(s->expansion);
2049 nasm_free(s);
2050 } else {
2051 sp = &s->next;
2058 * Parse a mmacro specification.
2060 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2062 bool err;
2064 tline = tline->next;
2065 skip_white_(tline);
2066 tline = expand_id(tline);
2067 if (!tok_type_(tline, TOK_ID)) {
2068 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2069 return false;
2072 def->prev = NULL;
2073 def->name = nasm_strdup(tline->text);
2074 def->plus = false;
2075 def->nolist = false;
2076 def->in_progress = 0;
2077 def->rep_nest = NULL;
2078 def->nparam_min = 0;
2079 def->nparam_max = 0;
2081 tline = expand_smacro(tline->next);
2082 skip_white_(tline);
2083 if (!tok_type_(tline, TOK_NUMBER)) {
2084 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2085 } else {
2086 def->nparam_min = def->nparam_max =
2087 readnum(tline->text, &err);
2088 if (err)
2089 nasm_error(ERR_NONFATAL,
2090 "unable to parse parameter count `%s'", tline->text);
2092 if (tline && tok_is_(tline->next, "-")) {
2093 tline = tline->next->next;
2094 if (tok_is_(tline, "*")) {
2095 def->nparam_max = INT_MAX;
2096 } else if (!tok_type_(tline, TOK_NUMBER)) {
2097 nasm_error(ERR_NONFATAL,
2098 "`%s' expects a parameter count after `-'", directive);
2099 } else {
2100 def->nparam_max = readnum(tline->text, &err);
2101 if (err) {
2102 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2103 tline->text);
2105 if (def->nparam_min > def->nparam_max) {
2106 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2110 if (tline && tok_is_(tline->next, "+")) {
2111 tline = tline->next;
2112 def->plus = true;
2114 if (tline && tok_type_(tline->next, TOK_ID) &&
2115 !nasm_stricmp(tline->next->text, ".nolist")) {
2116 tline = tline->next;
2117 def->nolist = true;
2121 * Handle default parameters.
2123 if (tline && tline->next) {
2124 def->dlist = tline->next;
2125 tline->next = NULL;
2126 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2127 } else {
2128 def->dlist = NULL;
2129 def->defaults = NULL;
2131 def->expansion = NULL;
2133 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2134 !def->plus)
2135 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2136 "too many default macro parameters");
2138 return true;
2143 * Decode a size directive
2145 static int parse_size(const char *str) {
2146 static const char *size_names[] =
2147 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2148 static const int sizes[] =
2149 { 0, 1, 4, 16, 8, 10, 2, 32 };
2151 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2155 * find and process preprocessor directive in passed line
2156 * Find out if a line contains a preprocessor directive, and deal
2157 * with it if so.
2159 * If a directive _is_ found, it is the responsibility of this routine
2160 * (and not the caller) to free_tlist() the line.
2162 * @param tline a pointer to the current tokeninzed line linked list
2163 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2166 static int do_directive(Token * tline)
2168 enum preproc_token i;
2169 int j;
2170 bool err;
2171 int nparam;
2172 bool nolist;
2173 bool casesense;
2174 int k, m;
2175 int offset;
2176 char *p, *pp;
2177 const char *mname;
2178 Include *inc;
2179 Context *ctx;
2180 Cond *cond;
2181 MMacro *mmac, **mmhead;
2182 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2183 Line *l;
2184 struct tokenval tokval;
2185 expr *evalresult;
2186 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2187 int64_t count;
2188 size_t len;
2189 int severity;
2191 origline = tline;
2193 skip_white_(tline);
2194 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2195 (tline->text[1] == '%' || tline->text[1] == '$'
2196 || tline->text[1] == '!'))
2197 return NO_DIRECTIVE_FOUND;
2199 i = pp_token_hash(tline->text);
2202 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2203 * since they are known to be buggy at moment, we need to fix them
2204 * in future release (2.09-2.10)
2206 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2207 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2208 tline->text);
2209 return NO_DIRECTIVE_FOUND;
2213 * If we're in a non-emitting branch of a condition construct,
2214 * or walking to the end of an already terminated %rep block,
2215 * we should ignore all directives except for condition
2216 * directives.
2218 if (((istk->conds && !emitting(istk->conds->state)) ||
2219 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2220 return NO_DIRECTIVE_FOUND;
2224 * If we're defining a macro or reading a %rep block, we should
2225 * ignore all directives except for %macro/%imacro (which nest),
2226 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2227 * If we're in a %rep block, another %rep nests, so should be let through.
2229 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2230 i != PP_RMACRO && i != PP_IRMACRO &&
2231 i != PP_ENDMACRO && i != PP_ENDM &&
2232 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2233 return NO_DIRECTIVE_FOUND;
2236 if (defining) {
2237 if (i == PP_MACRO || i == PP_IMACRO ||
2238 i == PP_RMACRO || i == PP_IRMACRO) {
2239 nested_mac_count++;
2240 return NO_DIRECTIVE_FOUND;
2241 } else if (nested_mac_count > 0) {
2242 if (i == PP_ENDMACRO) {
2243 nested_mac_count--;
2244 return NO_DIRECTIVE_FOUND;
2247 if (!defining->name) {
2248 if (i == PP_REP) {
2249 nested_rep_count++;
2250 return NO_DIRECTIVE_FOUND;
2251 } else if (nested_rep_count > 0) {
2252 if (i == PP_ENDREP) {
2253 nested_rep_count--;
2254 return NO_DIRECTIVE_FOUND;
2260 switch (i) {
2261 case PP_INVALID:
2262 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2263 tline->text);
2264 return NO_DIRECTIVE_FOUND; /* didn't get it */
2266 case PP_STACKSIZE:
2267 /* Directive to tell NASM what the default stack size is. The
2268 * default is for a 16-bit stack, and this can be overriden with
2269 * %stacksize large.
2271 tline = tline->next;
2272 if (tline && tline->type == TOK_WHITESPACE)
2273 tline = tline->next;
2274 if (!tline || tline->type != TOK_ID) {
2275 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2276 free_tlist(origline);
2277 return DIRECTIVE_FOUND;
2279 if (nasm_stricmp(tline->text, "flat") == 0) {
2280 /* All subsequent ARG directives are for a 32-bit stack */
2281 StackSize = 4;
2282 StackPointer = "ebp";
2283 ArgOffset = 8;
2284 LocalOffset = 0;
2285 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2286 /* All subsequent ARG directives are for a 64-bit stack */
2287 StackSize = 8;
2288 StackPointer = "rbp";
2289 ArgOffset = 16;
2290 LocalOffset = 0;
2291 } else if (nasm_stricmp(tline->text, "large") == 0) {
2292 /* All subsequent ARG directives are for a 16-bit stack,
2293 * far function call.
2295 StackSize = 2;
2296 StackPointer = "bp";
2297 ArgOffset = 4;
2298 LocalOffset = 0;
2299 } else if (nasm_stricmp(tline->text, "small") == 0) {
2300 /* All subsequent ARG directives are for a 16-bit stack,
2301 * far function call. We don't support near functions.
2303 StackSize = 2;
2304 StackPointer = "bp";
2305 ArgOffset = 6;
2306 LocalOffset = 0;
2307 } else {
2308 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2309 free_tlist(origline);
2310 return DIRECTIVE_FOUND;
2312 free_tlist(origline);
2313 return DIRECTIVE_FOUND;
2315 case PP_ARG:
2316 /* TASM like ARG directive to define arguments to functions, in
2317 * the following form:
2319 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2321 offset = ArgOffset;
2322 do {
2323 char *arg, directive[256];
2324 int size = StackSize;
2326 /* Find the argument name */
2327 tline = tline->next;
2328 if (tline && tline->type == TOK_WHITESPACE)
2329 tline = tline->next;
2330 if (!tline || tline->type != TOK_ID) {
2331 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2332 free_tlist(origline);
2333 return DIRECTIVE_FOUND;
2335 arg = tline->text;
2337 /* Find the argument size type */
2338 tline = tline->next;
2339 if (!tline || tline->type != TOK_OTHER
2340 || tline->text[0] != ':') {
2341 nasm_error(ERR_NONFATAL,
2342 "Syntax error processing `%%arg' directive");
2343 free_tlist(origline);
2344 return DIRECTIVE_FOUND;
2346 tline = tline->next;
2347 if (!tline || tline->type != TOK_ID) {
2348 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2349 free_tlist(origline);
2350 return DIRECTIVE_FOUND;
2353 /* Allow macro expansion of type parameter */
2354 tt = tokenize(tline->text);
2355 tt = expand_smacro(tt);
2356 size = parse_size(tt->text);
2357 if (!size) {
2358 nasm_error(ERR_NONFATAL,
2359 "Invalid size type for `%%arg' missing directive");
2360 free_tlist(tt);
2361 free_tlist(origline);
2362 return DIRECTIVE_FOUND;
2364 free_tlist(tt);
2366 /* Round up to even stack slots */
2367 size = ALIGN(size, StackSize);
2369 /* Now define the macro for the argument */
2370 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2371 arg, StackPointer, offset);
2372 do_directive(tokenize(directive));
2373 offset += size;
2375 /* Move to the next argument in the list */
2376 tline = tline->next;
2377 if (tline && tline->type == TOK_WHITESPACE)
2378 tline = tline->next;
2379 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2380 ArgOffset = offset;
2381 free_tlist(origline);
2382 return DIRECTIVE_FOUND;
2384 case PP_LOCAL:
2385 /* TASM like LOCAL directive to define local variables for a
2386 * function, in the following form:
2388 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2390 * The '= LocalSize' at the end is ignored by NASM, but is
2391 * required by TASM to define the local parameter size (and used
2392 * by the TASM macro package).
2394 offset = LocalOffset;
2395 do {
2396 char *local, directive[256];
2397 int size = StackSize;
2399 /* Find the argument name */
2400 tline = tline->next;
2401 if (tline && tline->type == TOK_WHITESPACE)
2402 tline = tline->next;
2403 if (!tline || tline->type != TOK_ID) {
2404 nasm_error(ERR_NONFATAL,
2405 "`%%local' missing argument parameter");
2406 free_tlist(origline);
2407 return DIRECTIVE_FOUND;
2409 local = tline->text;
2411 /* Find the argument size type */
2412 tline = tline->next;
2413 if (!tline || tline->type != TOK_OTHER
2414 || tline->text[0] != ':') {
2415 nasm_error(ERR_NONFATAL,
2416 "Syntax error processing `%%local' directive");
2417 free_tlist(origline);
2418 return DIRECTIVE_FOUND;
2420 tline = tline->next;
2421 if (!tline || tline->type != TOK_ID) {
2422 nasm_error(ERR_NONFATAL,
2423 "`%%local' missing size type parameter");
2424 free_tlist(origline);
2425 return DIRECTIVE_FOUND;
2428 /* Allow macro expansion of type parameter */
2429 tt = tokenize(tline->text);
2430 tt = expand_smacro(tt);
2431 size = parse_size(tt->text);
2432 if (!size) {
2433 nasm_error(ERR_NONFATAL,
2434 "Invalid size type for `%%local' missing directive");
2435 free_tlist(tt);
2436 free_tlist(origline);
2437 return DIRECTIVE_FOUND;
2439 free_tlist(tt);
2441 /* Round up to even stack slots */
2442 size = ALIGN(size, StackSize);
2444 offset += size; /* Negative offset, increment before */
2446 /* Now define the macro for the argument */
2447 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2448 local, StackPointer, offset);
2449 do_directive(tokenize(directive));
2451 /* Now define the assign to setup the enter_c macro correctly */
2452 snprintf(directive, sizeof(directive),
2453 "%%assign %%$localsize %%$localsize+%d", size);
2454 do_directive(tokenize(directive));
2456 /* Move to the next argument in the list */
2457 tline = tline->next;
2458 if (tline && tline->type == TOK_WHITESPACE)
2459 tline = tline->next;
2460 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2461 LocalOffset = offset;
2462 free_tlist(origline);
2463 return DIRECTIVE_FOUND;
2465 case PP_CLEAR:
2466 if (tline->next)
2467 nasm_error(ERR_WARNING|ERR_PASS1,
2468 "trailing garbage after `%%clear' ignored");
2469 free_macros();
2470 init_macros();
2471 free_tlist(origline);
2472 return DIRECTIVE_FOUND;
2474 case PP_DEPEND:
2475 t = tline->next = expand_smacro(tline->next);
2476 skip_white_(t);
2477 if (!t || (t->type != TOK_STRING &&
2478 t->type != TOK_INTERNAL_STRING)) {
2479 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2480 free_tlist(origline);
2481 return DIRECTIVE_FOUND; /* but we did _something_ */
2483 if (t->next)
2484 nasm_error(ERR_WARNING|ERR_PASS1,
2485 "trailing garbage after `%%depend' ignored");
2486 p = t->text;
2487 if (t->type != TOK_INTERNAL_STRING)
2488 nasm_unquote_cstr(p, i);
2489 if (dephead && !in_list(*dephead, p)) {
2490 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2491 sl->next = NULL;
2492 strcpy(sl->str, p);
2493 *deptail = sl;
2494 deptail = &sl->next;
2496 free_tlist(origline);
2497 return DIRECTIVE_FOUND;
2499 case PP_INCLUDE:
2500 t = tline->next = expand_smacro(tline->next);
2501 skip_white_(t);
2503 if (!t || (t->type != TOK_STRING &&
2504 t->type != TOK_INTERNAL_STRING)) {
2505 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2506 free_tlist(origline);
2507 return DIRECTIVE_FOUND; /* but we did _something_ */
2509 if (t->next)
2510 nasm_error(ERR_WARNING|ERR_PASS1,
2511 "trailing garbage after `%%include' ignored");
2512 p = t->text;
2513 if (t->type != TOK_INTERNAL_STRING)
2514 nasm_unquote_cstr(p, i);
2515 inc = nasm_malloc(sizeof(Include));
2516 inc->next = istk;
2517 inc->conds = NULL;
2518 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0, "r");
2519 if (!inc->fp) {
2520 /* -MG given but file not found */
2521 nasm_free(inc);
2522 } else {
2523 inc->fname = src_set_fname(p);
2524 inc->lineno = src_set_linnum(0);
2525 inc->lineinc = 1;
2526 inc->expansion = NULL;
2527 inc->mstk = NULL;
2528 istk = inc;
2529 lfmt->uplevel(LIST_INCLUDE);
2531 free_tlist(origline);
2532 return DIRECTIVE_FOUND;
2534 case PP_USE:
2536 static macros_t *use_pkg;
2537 const char *pkg_macro = NULL;
2539 tline = tline->next;
2540 skip_white_(tline);
2541 tline = expand_id(tline);
2543 if (!tline || (tline->type != TOK_STRING &&
2544 tline->type != TOK_INTERNAL_STRING &&
2545 tline->type != TOK_ID)) {
2546 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2547 free_tlist(origline);
2548 return DIRECTIVE_FOUND; /* but we did _something_ */
2550 if (tline->next)
2551 nasm_error(ERR_WARNING|ERR_PASS1,
2552 "trailing garbage after `%%use' ignored");
2553 if (tline->type == TOK_STRING)
2554 nasm_unquote_cstr(tline->text, i);
2555 use_pkg = nasm_stdmac_find_package(tline->text);
2556 if (!use_pkg)
2557 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2558 else
2559 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2560 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2561 /* Not already included, go ahead and include it */
2562 stdmacpos = use_pkg;
2564 free_tlist(origline);
2565 return DIRECTIVE_FOUND;
2567 case PP_PUSH:
2568 case PP_REPL:
2569 case PP_POP:
2570 tline = tline->next;
2571 skip_white_(tline);
2572 tline = expand_id(tline);
2573 if (tline) {
2574 if (!tok_type_(tline, TOK_ID)) {
2575 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2576 pp_directives[i]);
2577 free_tlist(origline);
2578 return DIRECTIVE_FOUND; /* but we did _something_ */
2580 if (tline->next)
2581 nasm_error(ERR_WARNING|ERR_PASS1,
2582 "trailing garbage after `%s' ignored",
2583 pp_directives[i]);
2584 p = nasm_strdup(tline->text);
2585 } else {
2586 p = NULL; /* Anonymous */
2589 if (i == PP_PUSH) {
2590 ctx = nasm_malloc(sizeof(Context));
2591 ctx->next = cstk;
2592 hash_init(&ctx->localmac, HASH_SMALL);
2593 ctx->name = p;
2594 ctx->number = unique++;
2595 cstk = ctx;
2596 } else {
2597 /* %pop or %repl */
2598 if (!cstk) {
2599 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2600 pp_directives[i]);
2601 } else if (i == PP_POP) {
2602 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2603 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2604 "expected %s",
2605 cstk->name ? cstk->name : "anonymous", p);
2606 else
2607 ctx_pop();
2608 } else {
2609 /* i == PP_REPL */
2610 nasm_free(cstk->name);
2611 cstk->name = p;
2612 p = NULL;
2614 nasm_free(p);
2616 free_tlist(origline);
2617 return DIRECTIVE_FOUND;
2618 case PP_FATAL:
2619 severity = ERR_FATAL;
2620 goto issue_error;
2621 case PP_ERROR:
2622 severity = ERR_NONFATAL;
2623 goto issue_error;
2624 case PP_WARNING:
2625 severity = ERR_WARNING|ERR_WARN_USER;
2626 goto issue_error;
2628 issue_error:
2630 /* Only error out if this is the final pass */
2631 if (pass != 2 && i != PP_FATAL)
2632 return DIRECTIVE_FOUND;
2634 tline->next = expand_smacro(tline->next);
2635 tline = tline->next;
2636 skip_white_(tline);
2637 t = tline ? tline->next : NULL;
2638 skip_white_(t);
2639 if (tok_type_(tline, TOK_STRING) && !t) {
2640 /* The line contains only a quoted string */
2641 p = tline->text;
2642 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2643 nasm_error(severity, "%s", p);
2644 } else {
2645 /* Not a quoted string, or more than a quoted string */
2646 p = detoken(tline, false);
2647 nasm_error(severity, "%s", p);
2648 nasm_free(p);
2650 free_tlist(origline);
2651 return DIRECTIVE_FOUND;
2654 CASE_PP_IF:
2655 if (istk->conds && !emitting(istk->conds->state))
2656 j = COND_NEVER;
2657 else {
2658 j = if_condition(tline->next, i);
2659 tline->next = NULL; /* it got freed */
2660 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2662 cond = nasm_malloc(sizeof(Cond));
2663 cond->next = istk->conds;
2664 cond->state = j;
2665 istk->conds = cond;
2666 if(istk->mstk)
2667 istk->mstk->condcnt ++;
2668 free_tlist(origline);
2669 return DIRECTIVE_FOUND;
2671 CASE_PP_ELIF:
2672 if (!istk->conds)
2673 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2674 switch(istk->conds->state) {
2675 case COND_IF_TRUE:
2676 istk->conds->state = COND_DONE;
2677 break;
2679 case COND_DONE:
2680 case COND_NEVER:
2681 break;
2683 case COND_ELSE_TRUE:
2684 case COND_ELSE_FALSE:
2685 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2686 "`%%elif' after `%%else' ignored");
2687 istk->conds->state = COND_NEVER;
2688 break;
2690 case COND_IF_FALSE:
2692 * IMPORTANT: In the case of %if, we will already have
2693 * called expand_mmac_params(); however, if we're
2694 * processing an %elif we must have been in a
2695 * non-emitting mode, which would have inhibited
2696 * the normal invocation of expand_mmac_params().
2697 * Therefore, we have to do it explicitly here.
2699 j = if_condition(expand_mmac_params(tline->next), i);
2700 tline->next = NULL; /* it got freed */
2701 istk->conds->state =
2702 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2703 break;
2705 free_tlist(origline);
2706 return DIRECTIVE_FOUND;
2708 case PP_ELSE:
2709 if (tline->next)
2710 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2711 "trailing garbage after `%%else' ignored");
2712 if (!istk->conds)
2713 nasm_fatal(0, "`%%else: no matching `%%if'");
2714 switch(istk->conds->state) {
2715 case COND_IF_TRUE:
2716 case COND_DONE:
2717 istk->conds->state = COND_ELSE_FALSE;
2718 break;
2720 case COND_NEVER:
2721 break;
2723 case COND_IF_FALSE:
2724 istk->conds->state = COND_ELSE_TRUE;
2725 break;
2727 case COND_ELSE_TRUE:
2728 case COND_ELSE_FALSE:
2729 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2730 "`%%else' after `%%else' ignored.");
2731 istk->conds->state = COND_NEVER;
2732 break;
2734 free_tlist(origline);
2735 return DIRECTIVE_FOUND;
2737 case PP_ENDIF:
2738 if (tline->next)
2739 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2740 "trailing garbage after `%%endif' ignored");
2741 if (!istk->conds)
2742 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2743 cond = istk->conds;
2744 istk->conds = cond->next;
2745 nasm_free(cond);
2746 if(istk->mstk)
2747 istk->mstk->condcnt --;
2748 free_tlist(origline);
2749 return DIRECTIVE_FOUND;
2751 case PP_RMACRO:
2752 case PP_IRMACRO:
2753 case PP_MACRO:
2754 case PP_IMACRO:
2755 if (defining) {
2756 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2757 pp_directives[i]);
2758 return DIRECTIVE_FOUND;
2760 defining = nasm_zalloc(sizeof(MMacro));
2761 defining->max_depth =
2762 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2763 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2764 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2765 nasm_free(defining);
2766 defining = NULL;
2767 return DIRECTIVE_FOUND;
2770 src_get(&defining->xline, &defining->fname);
2772 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2773 while (mmac) {
2774 if (!strcmp(mmac->name, defining->name) &&
2775 (mmac->nparam_min <= defining->nparam_max
2776 || defining->plus)
2777 && (defining->nparam_min <= mmac->nparam_max
2778 || mmac->plus)) {
2779 nasm_error(ERR_WARNING|ERR_PASS1,
2780 "redefining multi-line macro `%s'", defining->name);
2781 return DIRECTIVE_FOUND;
2783 mmac = mmac->next;
2785 free_tlist(origline);
2786 return DIRECTIVE_FOUND;
2788 case PP_ENDM:
2789 case PP_ENDMACRO:
2790 if (! (defining && defining->name)) {
2791 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2792 return DIRECTIVE_FOUND;
2794 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2795 defining->next = *mmhead;
2796 *mmhead = defining;
2797 defining = NULL;
2798 free_tlist(origline);
2799 return DIRECTIVE_FOUND;
2801 case PP_EXITMACRO:
2803 * We must search along istk->expansion until we hit a
2804 * macro-end marker for a macro with a name. Then we
2805 * bypass all lines between exitmacro and endmacro.
2807 list_for_each(l, istk->expansion)
2808 if (l->finishes && l->finishes->name)
2809 break;
2811 if (l) {
2813 * Remove all conditional entries relative to this
2814 * macro invocation. (safe to do in this context)
2816 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2817 cond = istk->conds;
2818 istk->conds = cond->next;
2819 nasm_free(cond);
2821 istk->expansion = l;
2822 } else {
2823 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2825 free_tlist(origline);
2826 return DIRECTIVE_FOUND;
2828 case PP_UNMACRO:
2829 case PP_UNIMACRO:
2831 MMacro **mmac_p;
2832 MMacro spec;
2834 spec.casesense = (i == PP_UNMACRO);
2835 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2836 return DIRECTIVE_FOUND;
2838 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2839 while (mmac_p && *mmac_p) {
2840 mmac = *mmac_p;
2841 if (mmac->casesense == spec.casesense &&
2842 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2843 mmac->nparam_min == spec.nparam_min &&
2844 mmac->nparam_max == spec.nparam_max &&
2845 mmac->plus == spec.plus) {
2846 *mmac_p = mmac->next;
2847 free_mmacro(mmac);
2848 } else {
2849 mmac_p = &mmac->next;
2852 free_tlist(origline);
2853 free_tlist(spec.dlist);
2854 return DIRECTIVE_FOUND;
2857 case PP_ROTATE:
2858 if (tline->next && tline->next->type == TOK_WHITESPACE)
2859 tline = tline->next;
2860 if (!tline->next) {
2861 free_tlist(origline);
2862 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2863 return DIRECTIVE_FOUND;
2865 t = expand_smacro(tline->next);
2866 tline->next = NULL;
2867 free_tlist(origline);
2868 tline = t;
2869 tptr = &t;
2870 tokval.t_type = TOKEN_INVALID;
2871 evalresult =
2872 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2873 free_tlist(tline);
2874 if (!evalresult)
2875 return DIRECTIVE_FOUND;
2876 if (tokval.t_type)
2877 nasm_error(ERR_WARNING|ERR_PASS1,
2878 "trailing garbage after expression ignored");
2879 if (!is_simple(evalresult)) {
2880 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2881 return DIRECTIVE_FOUND;
2883 mmac = istk->mstk;
2884 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2885 mmac = mmac->next_active;
2886 if (!mmac) {
2887 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2888 } else if (mmac->nparam == 0) {
2889 nasm_error(ERR_NONFATAL,
2890 "`%%rotate' invoked within macro without parameters");
2891 } else {
2892 int rotate = mmac->rotate + reloc_value(evalresult);
2894 rotate %= (int)mmac->nparam;
2895 if (rotate < 0)
2896 rotate += mmac->nparam;
2898 mmac->rotate = rotate;
2900 return DIRECTIVE_FOUND;
2902 case PP_REP:
2903 nolist = false;
2904 do {
2905 tline = tline->next;
2906 } while (tok_type_(tline, TOK_WHITESPACE));
2908 if (tok_type_(tline, TOK_ID) &&
2909 nasm_stricmp(tline->text, ".nolist") == 0) {
2910 nolist = true;
2911 do {
2912 tline = tline->next;
2913 } while (tok_type_(tline, TOK_WHITESPACE));
2916 if (tline) {
2917 t = expand_smacro(tline);
2918 tptr = &t;
2919 tokval.t_type = TOKEN_INVALID;
2920 evalresult =
2921 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2922 if (!evalresult) {
2923 free_tlist(origline);
2924 return DIRECTIVE_FOUND;
2926 if (tokval.t_type)
2927 nasm_error(ERR_WARNING|ERR_PASS1,
2928 "trailing garbage after expression ignored");
2929 if (!is_simple(evalresult)) {
2930 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2931 return DIRECTIVE_FOUND;
2933 count = reloc_value(evalresult);
2934 if (count >= REP_LIMIT) {
2935 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
2936 count = 0;
2937 } else
2938 count++;
2939 } else {
2940 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2941 count = 0;
2943 free_tlist(origline);
2945 tmp_defining = defining;
2946 defining = nasm_malloc(sizeof(MMacro));
2947 defining->prev = NULL;
2948 defining->name = NULL; /* flags this macro as a %rep block */
2949 defining->casesense = false;
2950 defining->plus = false;
2951 defining->nolist = nolist;
2952 defining->in_progress = count;
2953 defining->max_depth = 0;
2954 defining->nparam_min = defining->nparam_max = 0;
2955 defining->defaults = NULL;
2956 defining->dlist = NULL;
2957 defining->expansion = NULL;
2958 defining->next_active = istk->mstk;
2959 defining->rep_nest = tmp_defining;
2960 return DIRECTIVE_FOUND;
2962 case PP_ENDREP:
2963 if (!defining || defining->name) {
2964 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2965 return DIRECTIVE_FOUND;
2969 * Now we have a "macro" defined - although it has no name
2970 * and we won't be entering it in the hash tables - we must
2971 * push a macro-end marker for it on to istk->expansion.
2972 * After that, it will take care of propagating itself (a
2973 * macro-end marker line for a macro which is really a %rep
2974 * block will cause the macro to be re-expanded, complete
2975 * with another macro-end marker to ensure the process
2976 * continues) until the whole expansion is forcibly removed
2977 * from istk->expansion by a %exitrep.
2979 l = nasm_malloc(sizeof(Line));
2980 l->next = istk->expansion;
2981 l->finishes = defining;
2982 l->first = NULL;
2983 istk->expansion = l;
2985 istk->mstk = defining;
2987 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2988 tmp_defining = defining;
2989 defining = defining->rep_nest;
2990 free_tlist(origline);
2991 return DIRECTIVE_FOUND;
2993 case PP_EXITREP:
2995 * We must search along istk->expansion until we hit a
2996 * macro-end marker for a macro with no name. Then we set
2997 * its `in_progress' flag to 0.
2999 list_for_each(l, istk->expansion)
3000 if (l->finishes && !l->finishes->name)
3001 break;
3003 if (l)
3004 l->finishes->in_progress = 1;
3005 else
3006 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3007 free_tlist(origline);
3008 return DIRECTIVE_FOUND;
3010 case PP_XDEFINE:
3011 case PP_IXDEFINE:
3012 case PP_DEFINE:
3013 case PP_IDEFINE:
3014 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3016 tline = tline->next;
3017 skip_white_(tline);
3018 tline = expand_id(tline);
3019 if (!tline || (tline->type != TOK_ID &&
3020 (tline->type != TOK_PREPROC_ID ||
3021 tline->text[1] != '$'))) {
3022 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3023 pp_directives[i]);
3024 free_tlist(origline);
3025 return DIRECTIVE_FOUND;
3028 ctx = get_ctx(tline->text, &mname);
3029 last = tline;
3030 param_start = tline = tline->next;
3031 nparam = 0;
3033 /* Expand the macro definition now for %xdefine and %ixdefine */
3034 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3035 tline = expand_smacro(tline);
3037 if (tok_is_(tline, "(")) {
3039 * This macro has parameters.
3042 tline = tline->next;
3043 while (1) {
3044 skip_white_(tline);
3045 if (!tline) {
3046 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3047 free_tlist(origline);
3048 return DIRECTIVE_FOUND;
3050 if (tline->type != TOK_ID) {
3051 nasm_error(ERR_NONFATAL,
3052 "`%s': parameter identifier expected",
3053 tline->text);
3054 free_tlist(origline);
3055 return DIRECTIVE_FOUND;
3057 tline->type = TOK_SMAC_PARAM + nparam++;
3058 tline = tline->next;
3059 skip_white_(tline);
3060 if (tok_is_(tline, ",")) {
3061 tline = tline->next;
3062 } else {
3063 if (!tok_is_(tline, ")")) {
3064 nasm_error(ERR_NONFATAL,
3065 "`)' expected to terminate macro template");
3066 free_tlist(origline);
3067 return DIRECTIVE_FOUND;
3069 break;
3072 last = tline;
3073 tline = tline->next;
3075 if (tok_type_(tline, TOK_WHITESPACE))
3076 last = tline, tline = tline->next;
3077 macro_start = NULL;
3078 last->next = NULL;
3079 t = tline;
3080 while (t) {
3081 if (t->type == TOK_ID) {
3082 list_for_each(tt, param_start)
3083 if (tt->type >= TOK_SMAC_PARAM &&
3084 !strcmp(tt->text, t->text))
3085 t->type = tt->type;
3087 tt = t->next;
3088 t->next = macro_start;
3089 macro_start = t;
3090 t = tt;
3093 * Good. We now have a macro name, a parameter count, and a
3094 * token list (in reverse order) for an expansion. We ought
3095 * to be OK just to create an SMacro, store it, and let
3096 * free_tlist have the rest of the line (which we have
3097 * carefully re-terminated after chopping off the expansion
3098 * from the end).
3100 define_smacro(ctx, mname, casesense, nparam, macro_start);
3101 free_tlist(origline);
3102 return DIRECTIVE_FOUND;
3104 case PP_UNDEF:
3105 tline = tline->next;
3106 skip_white_(tline);
3107 tline = expand_id(tline);
3108 if (!tline || (tline->type != TOK_ID &&
3109 (tline->type != TOK_PREPROC_ID ||
3110 tline->text[1] != '$'))) {
3111 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3112 free_tlist(origline);
3113 return DIRECTIVE_FOUND;
3115 if (tline->next) {
3116 nasm_error(ERR_WARNING|ERR_PASS1,
3117 "trailing garbage after macro name ignored");
3120 /* Find the context that symbol belongs to */
3121 ctx = get_ctx(tline->text, &mname);
3122 undef_smacro(ctx, mname);
3123 free_tlist(origline);
3124 return DIRECTIVE_FOUND;
3126 case PP_DEFSTR:
3127 case PP_IDEFSTR:
3128 casesense = (i == PP_DEFSTR);
3130 tline = tline->next;
3131 skip_white_(tline);
3132 tline = expand_id(tline);
3133 if (!tline || (tline->type != TOK_ID &&
3134 (tline->type != TOK_PREPROC_ID ||
3135 tline->text[1] != '$'))) {
3136 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3137 pp_directives[i]);
3138 free_tlist(origline);
3139 return DIRECTIVE_FOUND;
3142 ctx = get_ctx(tline->text, &mname);
3143 last = tline;
3144 tline = expand_smacro(tline->next);
3145 last->next = NULL;
3147 while (tok_type_(tline, TOK_WHITESPACE))
3148 tline = delete_Token(tline);
3150 p = detoken(tline, false);
3151 macro_start = nasm_malloc(sizeof(*macro_start));
3152 macro_start->next = NULL;
3153 macro_start->text = nasm_quote(p, strlen(p));
3154 macro_start->type = TOK_STRING;
3155 macro_start->a.mac = NULL;
3156 nasm_free(p);
3159 * We now have a macro name, an implicit parameter count of
3160 * zero, and a string token to use as an expansion. Create
3161 * and store an SMacro.
3163 define_smacro(ctx, mname, casesense, 0, macro_start);
3164 free_tlist(origline);
3165 return DIRECTIVE_FOUND;
3167 case PP_DEFTOK:
3168 case PP_IDEFTOK:
3169 casesense = (i == PP_DEFTOK);
3171 tline = tline->next;
3172 skip_white_(tline);
3173 tline = expand_id(tline);
3174 if (!tline || (tline->type != TOK_ID &&
3175 (tline->type != TOK_PREPROC_ID ||
3176 tline->text[1] != '$'))) {
3177 nasm_error(ERR_NONFATAL,
3178 "`%s' expects a macro identifier as first parameter",
3179 pp_directives[i]);
3180 free_tlist(origline);
3181 return DIRECTIVE_FOUND;
3183 ctx = get_ctx(tline->text, &mname);
3184 last = tline;
3185 tline = expand_smacro(tline->next);
3186 last->next = NULL;
3188 t = tline;
3189 while (tok_type_(t, TOK_WHITESPACE))
3190 t = t->next;
3191 /* t should now point to the string */
3192 if (!tok_type_(t, TOK_STRING)) {
3193 nasm_error(ERR_NONFATAL,
3194 "`%s` requires string as second parameter",
3195 pp_directives[i]);
3196 free_tlist(tline);
3197 free_tlist(origline);
3198 return DIRECTIVE_FOUND;
3202 * Convert the string to a token stream. Note that smacros
3203 * are stored with the token stream reversed, so we have to
3204 * reverse the output of tokenize().
3206 nasm_unquote_cstr(t->text, i);
3207 macro_start = reverse_tokens(tokenize(t->text));
3210 * We now have a macro name, an implicit parameter count of
3211 * zero, and a numeric token to use as an expansion. Create
3212 * and store an SMacro.
3214 define_smacro(ctx, mname, casesense, 0, macro_start);
3215 free_tlist(tline);
3216 free_tlist(origline);
3217 return DIRECTIVE_FOUND;
3219 case PP_PATHSEARCH:
3221 FILE *fp;
3222 StrList *xsl = NULL;
3223 StrList **xst = &xsl;
3225 casesense = true;
3227 tline = tline->next;
3228 skip_white_(tline);
3229 tline = expand_id(tline);
3230 if (!tline || (tline->type != TOK_ID &&
3231 (tline->type != TOK_PREPROC_ID ||
3232 tline->text[1] != '$'))) {
3233 nasm_error(ERR_NONFATAL,
3234 "`%%pathsearch' expects a macro identifier as first parameter");
3235 free_tlist(origline);
3236 return DIRECTIVE_FOUND;
3238 ctx = get_ctx(tline->text, &mname);
3239 last = tline;
3240 tline = expand_smacro(tline->next);
3241 last->next = NULL;
3243 t = tline;
3244 while (tok_type_(t, TOK_WHITESPACE))
3245 t = t->next;
3247 if (!t || (t->type != TOK_STRING &&
3248 t->type != TOK_INTERNAL_STRING)) {
3249 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3250 free_tlist(tline);
3251 free_tlist(origline);
3252 return DIRECTIVE_FOUND; /* but we did _something_ */
3254 if (t->next)
3255 nasm_error(ERR_WARNING|ERR_PASS1,
3256 "trailing garbage after `%%pathsearch' ignored");
3257 p = t->text;
3258 if (t->type != TOK_INTERNAL_STRING)
3259 nasm_unquote(p, NULL);
3261 fp = inc_fopen(p, &xsl, &xst, true, "r");
3262 if (fp) {
3263 p = xsl->str;
3264 fclose(fp); /* Don't actually care about the file */
3266 macro_start = nasm_malloc(sizeof(*macro_start));
3267 macro_start->next = NULL;
3268 macro_start->text = nasm_quote(p, strlen(p));
3269 macro_start->type = TOK_STRING;
3270 macro_start->a.mac = NULL;
3271 if (xsl)
3272 nasm_free(xsl);
3275 * We now have a macro name, an implicit parameter count of
3276 * zero, and a string token to use as an expansion. Create
3277 * and store an SMacro.
3279 define_smacro(ctx, mname, casesense, 0, macro_start);
3280 free_tlist(tline);
3281 free_tlist(origline);
3282 return DIRECTIVE_FOUND;
3285 case PP_STRLEN:
3286 casesense = true;
3288 tline = tline->next;
3289 skip_white_(tline);
3290 tline = expand_id(tline);
3291 if (!tline || (tline->type != TOK_ID &&
3292 (tline->type != TOK_PREPROC_ID ||
3293 tline->text[1] != '$'))) {
3294 nasm_error(ERR_NONFATAL,
3295 "`%%strlen' expects a macro identifier as first parameter");
3296 free_tlist(origline);
3297 return DIRECTIVE_FOUND;
3299 ctx = get_ctx(tline->text, &mname);
3300 last = tline;
3301 tline = expand_smacro(tline->next);
3302 last->next = NULL;
3304 t = tline;
3305 while (tok_type_(t, TOK_WHITESPACE))
3306 t = t->next;
3307 /* t should now point to the string */
3308 if (!tok_type_(t, TOK_STRING)) {
3309 nasm_error(ERR_NONFATAL,
3310 "`%%strlen` requires string as second parameter");
3311 free_tlist(tline);
3312 free_tlist(origline);
3313 return DIRECTIVE_FOUND;
3316 macro_start = nasm_malloc(sizeof(*macro_start));
3317 macro_start->next = NULL;
3318 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3319 macro_start->a.mac = NULL;
3322 * We now have a macro name, an implicit parameter count of
3323 * zero, and a numeric token to use as an expansion. Create
3324 * and store an SMacro.
3326 define_smacro(ctx, mname, casesense, 0, macro_start);
3327 free_tlist(tline);
3328 free_tlist(origline);
3329 return DIRECTIVE_FOUND;
3331 case PP_STRCAT:
3332 casesense = true;
3334 tline = tline->next;
3335 skip_white_(tline);
3336 tline = expand_id(tline);
3337 if (!tline || (tline->type != TOK_ID &&
3338 (tline->type != TOK_PREPROC_ID ||
3339 tline->text[1] != '$'))) {
3340 nasm_error(ERR_NONFATAL,
3341 "`%%strcat' expects a macro identifier as first parameter");
3342 free_tlist(origline);
3343 return DIRECTIVE_FOUND;
3345 ctx = get_ctx(tline->text, &mname);
3346 last = tline;
3347 tline = expand_smacro(tline->next);
3348 last->next = NULL;
3350 len = 0;
3351 list_for_each(t, tline) {
3352 switch (t->type) {
3353 case TOK_WHITESPACE:
3354 break;
3355 case TOK_STRING:
3356 len += t->a.len = nasm_unquote(t->text, NULL);
3357 break;
3358 case TOK_OTHER:
3359 if (!strcmp(t->text, ",")) /* permit comma separators */
3360 break;
3361 /* else fall through */
3362 default:
3363 nasm_error(ERR_NONFATAL,
3364 "non-string passed to `%%strcat' (%d)", t->type);
3365 free_tlist(tline);
3366 free_tlist(origline);
3367 return DIRECTIVE_FOUND;
3371 p = pp = nasm_malloc(len);
3372 list_for_each(t, tline) {
3373 if (t->type == TOK_STRING) {
3374 memcpy(p, t->text, t->a.len);
3375 p += t->a.len;
3380 * We now have a macro name, an implicit parameter count of
3381 * zero, and a numeric token to use as an expansion. Create
3382 * and store an SMacro.
3384 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3385 macro_start->text = nasm_quote(pp, len);
3386 nasm_free(pp);
3387 define_smacro(ctx, mname, casesense, 0, macro_start);
3388 free_tlist(tline);
3389 free_tlist(origline);
3390 return DIRECTIVE_FOUND;
3392 case PP_SUBSTR:
3394 int64_t start, count;
3395 size_t len;
3397 casesense = true;
3399 tline = tline->next;
3400 skip_white_(tline);
3401 tline = expand_id(tline);
3402 if (!tline || (tline->type != TOK_ID &&
3403 (tline->type != TOK_PREPROC_ID ||
3404 tline->text[1] != '$'))) {
3405 nasm_error(ERR_NONFATAL,
3406 "`%%substr' expects a macro identifier as first parameter");
3407 free_tlist(origline);
3408 return DIRECTIVE_FOUND;
3410 ctx = get_ctx(tline->text, &mname);
3411 last = tline;
3412 tline = expand_smacro(tline->next);
3413 last->next = NULL;
3415 if (tline) /* skip expanded id */
3416 t = tline->next;
3417 while (tok_type_(t, TOK_WHITESPACE))
3418 t = t->next;
3420 /* t should now point to the string */
3421 if (!tok_type_(t, TOK_STRING)) {
3422 nasm_error(ERR_NONFATAL,
3423 "`%%substr` requires string as second parameter");
3424 free_tlist(tline);
3425 free_tlist(origline);
3426 return DIRECTIVE_FOUND;
3429 tt = t->next;
3430 tptr = &tt;
3431 tokval.t_type = TOKEN_INVALID;
3432 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3433 if (!evalresult) {
3434 free_tlist(tline);
3435 free_tlist(origline);
3436 return DIRECTIVE_FOUND;
3437 } else if (!is_simple(evalresult)) {
3438 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3439 free_tlist(tline);
3440 free_tlist(origline);
3441 return DIRECTIVE_FOUND;
3443 start = evalresult->value - 1;
3445 while (tok_type_(tt, TOK_WHITESPACE))
3446 tt = tt->next;
3447 if (!tt) {
3448 count = 1; /* Backwards compatibility: one character */
3449 } else {
3450 tokval.t_type = TOKEN_INVALID;
3451 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3452 if (!evalresult) {
3453 free_tlist(tline);
3454 free_tlist(origline);
3455 return DIRECTIVE_FOUND;
3456 } else if (!is_simple(evalresult)) {
3457 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3458 free_tlist(tline);
3459 free_tlist(origline);
3460 return DIRECTIVE_FOUND;
3462 count = evalresult->value;
3465 len = nasm_unquote(t->text, NULL);
3467 /* make start and count being in range */
3468 if (start < 0)
3469 start = 0;
3470 if (count < 0)
3471 count = len + count + 1 - start;
3472 if (start + count > (int64_t)len)
3473 count = len - start;
3474 if (!len || count < 0 || start >=(int64_t)len)
3475 start = -1, count = 0; /* empty string */
3477 macro_start = nasm_malloc(sizeof(*macro_start));
3478 macro_start->next = NULL;
3479 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3480 macro_start->type = TOK_STRING;
3481 macro_start->a.mac = NULL;
3484 * We now have a macro name, an implicit parameter count of
3485 * zero, and a numeric token to use as an expansion. Create
3486 * and store an SMacro.
3488 define_smacro(ctx, mname, casesense, 0, macro_start);
3489 free_tlist(tline);
3490 free_tlist(origline);
3491 return DIRECTIVE_FOUND;
3494 case PP_ASSIGN:
3495 case PP_IASSIGN:
3496 casesense = (i == PP_ASSIGN);
3498 tline = tline->next;
3499 skip_white_(tline);
3500 tline = expand_id(tline);
3501 if (!tline || (tline->type != TOK_ID &&
3502 (tline->type != TOK_PREPROC_ID ||
3503 tline->text[1] != '$'))) {
3504 nasm_error(ERR_NONFATAL,
3505 "`%%%sassign' expects a macro identifier",
3506 (i == PP_IASSIGN ? "i" : ""));
3507 free_tlist(origline);
3508 return DIRECTIVE_FOUND;
3510 ctx = get_ctx(tline->text, &mname);
3511 last = tline;
3512 tline = expand_smacro(tline->next);
3513 last->next = NULL;
3515 t = tline;
3516 tptr = &t;
3517 tokval.t_type = TOKEN_INVALID;
3518 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3519 free_tlist(tline);
3520 if (!evalresult) {
3521 free_tlist(origline);
3522 return DIRECTIVE_FOUND;
3525 if (tokval.t_type)
3526 nasm_error(ERR_WARNING|ERR_PASS1,
3527 "trailing garbage after expression ignored");
3529 if (!is_simple(evalresult)) {
3530 nasm_error(ERR_NONFATAL,
3531 "non-constant value given to `%%%sassign'",
3532 (i == PP_IASSIGN ? "i" : ""));
3533 free_tlist(origline);
3534 return DIRECTIVE_FOUND;
3537 macro_start = nasm_malloc(sizeof(*macro_start));
3538 macro_start->next = NULL;
3539 make_tok_num(macro_start, reloc_value(evalresult));
3540 macro_start->a.mac = NULL;
3543 * We now have a macro name, an implicit parameter count of
3544 * zero, and a numeric token to use as an expansion. Create
3545 * and store an SMacro.
3547 define_smacro(ctx, mname, casesense, 0, macro_start);
3548 free_tlist(origline);
3549 return DIRECTIVE_FOUND;
3551 case PP_LINE:
3553 * Syntax is `%line nnn[+mmm] [filename]'
3555 tline = tline->next;
3556 skip_white_(tline);
3557 if (!tok_type_(tline, TOK_NUMBER)) {
3558 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3559 free_tlist(origline);
3560 return DIRECTIVE_FOUND;
3562 k = readnum(tline->text, &err);
3563 m = 1;
3564 tline = tline->next;
3565 if (tok_is_(tline, "+")) {
3566 tline = tline->next;
3567 if (!tok_type_(tline, TOK_NUMBER)) {
3568 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3569 free_tlist(origline);
3570 return DIRECTIVE_FOUND;
3572 m = readnum(tline->text, &err);
3573 tline = tline->next;
3575 skip_white_(tline);
3576 src_set_linnum(k);
3577 istk->lineinc = m;
3578 if (tline) {
3579 char *fname = detoken(tline, false);
3580 src_set_fname(fname);
3581 nasm_free(fname);
3583 free_tlist(origline);
3584 return DIRECTIVE_FOUND;
3586 default:
3587 nasm_error(ERR_FATAL,
3588 "preprocessor directive `%s' not yet implemented",
3589 pp_directives[i]);
3590 return DIRECTIVE_FOUND;
3595 * Ensure that a macro parameter contains a condition code and
3596 * nothing else. Return the condition code index if so, or -1
3597 * otherwise.
3599 static int find_cc(Token * t)
3601 Token *tt;
3603 if (!t)
3604 return -1; /* Probably a %+ without a space */
3606 skip_white_(t);
3607 if (t->type != TOK_ID)
3608 return -1;
3609 tt = t->next;
3610 skip_white_(tt);
3611 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3612 return -1;
3614 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3618 * This routines walks over tokens strem and hadnles tokens
3619 * pasting, if @handle_explicit passed then explicit pasting
3620 * term is handled, otherwise -- implicit pastings only.
3622 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3623 size_t mnum, bool handle_explicit)
3625 Token *tok, *next, **prev_next, **prev_nonspace;
3626 bool pasted = false;
3627 char *buf, *p;
3628 size_t len, i;
3631 * The last token before pasting. We need it
3632 * to be able to connect new handled tokens.
3633 * In other words if there were a tokens stream
3635 * A -> B -> C -> D
3637 * and we've joined tokens B and C, the resulting
3638 * stream should be
3640 * A -> BC -> D
3642 tok = *head;
3643 prev_next = NULL;
3645 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3646 prev_nonspace = head;
3647 else
3648 prev_nonspace = NULL;
3650 while (tok && (next = tok->next)) {
3652 switch (tok->type) {
3653 case TOK_WHITESPACE:
3654 /* Zap redundant whitespaces */
3655 while (tok_type_(next, TOK_WHITESPACE))
3656 next = delete_Token(next);
3657 tok->next = next;
3658 break;
3660 case TOK_PASTE:
3661 /* Explicit pasting */
3662 if (!handle_explicit)
3663 break;
3664 next = delete_Token(tok);
3666 while (tok_type_(next, TOK_WHITESPACE))
3667 next = delete_Token(next);
3669 if (!pasted)
3670 pasted = true;
3672 /* Left pasting token is start of line */
3673 if (!prev_nonspace)
3674 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3677 * No ending token, this might happen in two
3678 * cases
3680 * 1) There indeed no right token at all
3681 * 2) There is a bare "%define ID" statement,
3682 * and @ID does expand to whitespace.
3684 * So technically we need to do a grammar analysis
3685 * in another stage of parsing, but for now lets don't
3686 * change the behaviour people used to. Simply allow
3687 * whitespace after paste token.
3689 if (!next) {
3691 * Zap ending space tokens and that's all.
3693 tok = (*prev_nonspace)->next;
3694 while (tok_type_(tok, TOK_WHITESPACE))
3695 tok = delete_Token(tok);
3696 tok = *prev_nonspace;
3697 tok->next = NULL;
3698 break;
3701 tok = *prev_nonspace;
3702 while (tok_type_(tok, TOK_WHITESPACE))
3703 tok = delete_Token(tok);
3704 len = strlen(tok->text);
3705 len += strlen(next->text);
3707 p = buf = nasm_malloc(len + 1);
3708 strcpy(p, tok->text);
3709 p = strchr(p, '\0');
3710 strcpy(p, next->text);
3712 delete_Token(tok);
3714 tok = tokenize(buf);
3715 nasm_free(buf);
3717 *prev_nonspace = tok;
3718 while (tok && tok->next)
3719 tok = tok->next;
3721 tok->next = delete_Token(next);
3723 /* Restart from pasted tokens head */
3724 tok = *prev_nonspace;
3725 break;
3727 default:
3728 /* implicit pasting */
3729 for (i = 0; i < mnum; i++) {
3730 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3731 continue;
3733 len = 0;
3734 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3735 len += strlen(next->text);
3736 next = next->next;
3739 /* No match */
3740 if (tok == next)
3741 break;
3743 len += strlen(tok->text);
3744 p = buf = nasm_malloc(len + 1);
3746 while (tok != next) {
3747 strcpy(p, tok->text);
3748 p = strchr(p, '\0');
3749 tok = delete_Token(tok);
3752 tok = tokenize(buf);
3753 nasm_free(buf);
3755 if (prev_next)
3756 *prev_next = tok;
3757 else
3758 *head = tok;
3761 * Connect pasted into original stream,
3762 * ie A -> new-tokens -> B
3764 while (tok && tok->next)
3765 tok = tok->next;
3766 tok->next = next;
3768 if (!pasted)
3769 pasted = true;
3771 /* Restart from pasted tokens head */
3772 tok = prev_next ? *prev_next : *head;
3775 break;
3778 prev_next = &tok->next;
3780 if (tok->next &&
3781 !tok_type_(tok->next, TOK_WHITESPACE) &&
3782 !tok_type_(tok->next, TOK_PASTE))
3783 prev_nonspace = prev_next;
3785 tok = tok->next;
3788 return pasted;
3792 * expands to a list of tokens from %{x:y}
3794 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3796 Token *t = tline, **tt, *tm, *head;
3797 char *pos;
3798 int fst, lst, j, i;
3800 pos = strchr(tline->text, ':');
3801 nasm_assert(pos);
3803 lst = atoi(pos + 1);
3804 fst = atoi(tline->text + 1);
3807 * only macros params are accounted so
3808 * if someone passes %0 -- we reject such
3809 * value(s)
3811 if (lst == 0 || fst == 0)
3812 goto err;
3814 /* the values should be sane */
3815 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3816 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3817 goto err;
3819 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3820 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3822 /* counted from zero */
3823 fst--, lst--;
3826 * It will be at least one token. Note we
3827 * need to scan params until separator, otherwise
3828 * only first token will be passed.
3830 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3831 head = new_Token(NULL, tm->type, tm->text, 0);
3832 tt = &head->next, tm = tm->next;
3833 while (tok_isnt_(tm, ",")) {
3834 t = new_Token(NULL, tm->type, tm->text, 0);
3835 *tt = t, tt = &t->next, tm = tm->next;
3838 if (fst < lst) {
3839 for (i = fst + 1; i <= lst; i++) {
3840 t = new_Token(NULL, TOK_OTHER, ",", 0);
3841 *tt = t, tt = &t->next;
3842 j = (i + mac->rotate) % mac->nparam;
3843 tm = mac->params[j];
3844 while (tok_isnt_(tm, ",")) {
3845 t = new_Token(NULL, tm->type, tm->text, 0);
3846 *tt = t, tt = &t->next, tm = tm->next;
3849 } else {
3850 for (i = fst - 1; i >= lst; i--) {
3851 t = new_Token(NULL, TOK_OTHER, ",", 0);
3852 *tt = t, tt = &t->next;
3853 j = (i + mac->rotate) % mac->nparam;
3854 tm = mac->params[j];
3855 while (tok_isnt_(tm, ",")) {
3856 t = new_Token(NULL, tm->type, tm->text, 0);
3857 *tt = t, tt = &t->next, tm = tm->next;
3862 *last = tt;
3863 return head;
3865 err:
3866 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3867 &tline->text[1]);
3868 return tline;
3872 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3873 * %-n) and MMacro-local identifiers (%%foo) as well as
3874 * macro indirection (%[...]) and range (%{..:..}).
3876 static Token *expand_mmac_params(Token * tline)
3878 Token *t, *tt, **tail, *thead;
3879 bool changed = false;
3880 char *pos;
3882 tail = &thead;
3883 thead = NULL;
3885 while (tline) {
3886 if (tline->type == TOK_PREPROC_ID &&
3887 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3888 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3889 tline->text[1] == '%')) {
3890 char *text = NULL;
3891 int type = 0, cc; /* type = 0 to placate optimisers */
3892 char tmpbuf[30];
3893 unsigned int n;
3894 int i;
3895 MMacro *mac;
3897 t = tline;
3898 tline = tline->next;
3900 mac = istk->mstk;
3901 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3902 mac = mac->next_active;
3903 if (!mac) {
3904 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3905 } else {
3906 pos = strchr(t->text, ':');
3907 if (!pos) {
3908 switch (t->text[1]) {
3910 * We have to make a substitution of one of the
3911 * forms %1, %-1, %+1, %%foo, %0.
3913 case '0':
3914 type = TOK_NUMBER;
3915 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3916 text = nasm_strdup(tmpbuf);
3917 break;
3918 case '%':
3919 type = TOK_ID;
3920 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3921 mac->unique);
3922 text = nasm_strcat(tmpbuf, t->text + 2);
3923 break;
3924 case '-':
3925 n = atoi(t->text + 2) - 1;
3926 if (n >= mac->nparam)
3927 tt = NULL;
3928 else {
3929 if (mac->nparam > 1)
3930 n = (n + mac->rotate) % mac->nparam;
3931 tt = mac->params[n];
3933 cc = find_cc(tt);
3934 if (cc == -1) {
3935 nasm_error(ERR_NONFATAL,
3936 "macro parameter %d is not a condition code",
3937 n + 1);
3938 text = NULL;
3939 } else {
3940 type = TOK_ID;
3941 if (inverse_ccs[cc] == -1) {
3942 nasm_error(ERR_NONFATAL,
3943 "condition code `%s' is not invertible",
3944 conditions[cc]);
3945 text = NULL;
3946 } else
3947 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3949 break;
3950 case '+':
3951 n = atoi(t->text + 2) - 1;
3952 if (n >= mac->nparam)
3953 tt = NULL;
3954 else {
3955 if (mac->nparam > 1)
3956 n = (n + mac->rotate) % mac->nparam;
3957 tt = mac->params[n];
3959 cc = find_cc(tt);
3960 if (cc == -1) {
3961 nasm_error(ERR_NONFATAL,
3962 "macro parameter %d is not a condition code",
3963 n + 1);
3964 text = NULL;
3965 } else {
3966 type = TOK_ID;
3967 text = nasm_strdup(conditions[cc]);
3969 break;
3970 default:
3971 n = atoi(t->text + 1) - 1;
3972 if (n >= mac->nparam)
3973 tt = NULL;
3974 else {
3975 if (mac->nparam > 1)
3976 n = (n + mac->rotate) % mac->nparam;
3977 tt = mac->params[n];
3979 if (tt) {
3980 for (i = 0; i < mac->paramlen[n]; i++) {
3981 *tail = new_Token(NULL, tt->type, tt->text, 0);
3982 tail = &(*tail)->next;
3983 tt = tt->next;
3986 text = NULL; /* we've done it here */
3987 break;
3989 } else {
3991 * seems we have a parameters range here
3993 Token *head, **last;
3994 head = expand_mmac_params_range(mac, t, &last);
3995 if (head != t) {
3996 *tail = head;
3997 *last = tline;
3998 tline = head;
3999 text = NULL;
4003 if (!text) {
4004 delete_Token(t);
4005 } else {
4006 *tail = t;
4007 tail = &t->next;
4008 t->type = type;
4009 nasm_free(t->text);
4010 t->text = text;
4011 t->a.mac = NULL;
4013 changed = true;
4014 continue;
4015 } else if (tline->type == TOK_INDIRECT) {
4016 t = tline;
4017 tline = tline->next;
4018 tt = tokenize(t->text);
4019 tt = expand_mmac_params(tt);
4020 tt = expand_smacro(tt);
4021 *tail = tt;
4022 while (tt) {
4023 tt->a.mac = NULL; /* Necessary? */
4024 tail = &tt->next;
4025 tt = tt->next;
4027 delete_Token(t);
4028 changed = true;
4029 } else {
4030 t = *tail = tline;
4031 tline = tline->next;
4032 t->a.mac = NULL;
4033 tail = &t->next;
4036 *tail = NULL;
4038 if (changed) {
4039 const struct tokseq_match t[] = {
4041 PP_CONCAT_MASK(TOK_ID) |
4042 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4043 PP_CONCAT_MASK(TOK_ID) |
4044 PP_CONCAT_MASK(TOK_NUMBER) |
4045 PP_CONCAT_MASK(TOK_FLOAT) |
4046 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4049 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4050 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4053 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4056 return thead;
4060 * Expand all single-line macro calls made in the given line.
4061 * Return the expanded version of the line. The original is deemed
4062 * to be destroyed in the process. (In reality we'll just move
4063 * Tokens from input to output a lot of the time, rather than
4064 * actually bothering to destroy and replicate.)
4067 static Token *expand_smacro(Token * tline)
4069 Token *t, *tt, *mstart, **tail, *thead;
4070 SMacro *head = NULL, *m;
4071 Token **params;
4072 int *paramsize;
4073 unsigned int nparam, sparam;
4074 int brackets;
4075 Token *org_tline = tline;
4076 Context *ctx;
4077 const char *mname;
4078 int deadman = DEADMAN_LIMIT;
4079 bool expanded;
4082 * Trick: we should avoid changing the start token pointer since it can
4083 * be contained in "next" field of other token. Because of this
4084 * we allocate a copy of first token and work with it; at the end of
4085 * routine we copy it back
4087 if (org_tline) {
4088 tline = new_Token(org_tline->next, org_tline->type,
4089 org_tline->text, 0);
4090 tline->a.mac = org_tline->a.mac;
4091 nasm_free(org_tline->text);
4092 org_tline->text = NULL;
4095 expanded = true; /* Always expand %+ at least once */
4097 again:
4098 thead = NULL;
4099 tail = &thead;
4101 while (tline) { /* main token loop */
4102 if (!--deadman) {
4103 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4104 goto err;
4107 if ((mname = tline->text)) {
4108 /* if this token is a local macro, look in local context */
4109 if (tline->type == TOK_ID) {
4110 head = (SMacro *)hash_findix(&smacros, mname);
4111 } else if (tline->type == TOK_PREPROC_ID) {
4112 ctx = get_ctx(mname, &mname);
4113 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4114 } else
4115 head = NULL;
4118 * We've hit an identifier. As in is_mmacro below, we first
4119 * check whether the identifier is a single-line macro at
4120 * all, then think about checking for parameters if
4121 * necessary.
4123 list_for_each(m, head)
4124 if (!mstrcmp(m->name, mname, m->casesense))
4125 break;
4126 if (m) {
4127 mstart = tline;
4128 params = NULL;
4129 paramsize = NULL;
4130 if (m->nparam == 0) {
4132 * Simple case: the macro is parameterless. Discard the
4133 * one token that the macro call took, and push the
4134 * expansion back on the to-do stack.
4136 if (!m->expansion) {
4137 if (!strcmp("__FILE__", m->name)) {
4138 const char *file = src_get_fname();
4139 /* nasm_free(tline->text); here? */
4140 tline->text = nasm_quote(file, strlen(file));
4141 tline->type = TOK_STRING;
4142 continue;
4144 if (!strcmp("__LINE__", m->name)) {
4145 nasm_free(tline->text);
4146 make_tok_num(tline, src_get_linnum());
4147 continue;
4149 if (!strcmp("__BITS__", m->name)) {
4150 nasm_free(tline->text);
4151 make_tok_num(tline, globalbits);
4152 continue;
4154 tline = delete_Token(tline);
4155 continue;
4157 } else {
4159 * Complicated case: at least one macro with this name
4160 * exists and takes parameters. We must find the
4161 * parameters in the call, count them, find the SMacro
4162 * that corresponds to that form of the macro call, and
4163 * substitute for the parameters when we expand. What a
4164 * pain.
4166 /*tline = tline->next;
4167 skip_white_(tline); */
4168 do {
4169 t = tline->next;
4170 while (tok_type_(t, TOK_SMAC_END)) {
4171 t->a.mac->in_progress = false;
4172 t->text = NULL;
4173 t = tline->next = delete_Token(t);
4175 tline = t;
4176 } while (tok_type_(tline, TOK_WHITESPACE));
4177 if (!tok_is_(tline, "(")) {
4179 * This macro wasn't called with parameters: ignore
4180 * the call. (Behaviour borrowed from gnu cpp.)
4182 tline = mstart;
4183 m = NULL;
4184 } else {
4185 int paren = 0;
4186 int white = 0;
4187 brackets = 0;
4188 nparam = 0;
4189 sparam = PARAM_DELTA;
4190 params = nasm_malloc(sparam * sizeof(Token *));
4191 params[0] = tline->next;
4192 paramsize = nasm_malloc(sparam * sizeof(int));
4193 paramsize[0] = 0;
4194 while (true) { /* parameter loop */
4196 * For some unusual expansions
4197 * which concatenates function call
4199 t = tline->next;
4200 while (tok_type_(t, TOK_SMAC_END)) {
4201 t->a.mac->in_progress = false;
4202 t->text = NULL;
4203 t = tline->next = delete_Token(t);
4205 tline = t;
4207 if (!tline) {
4208 nasm_error(ERR_NONFATAL,
4209 "macro call expects terminating `)'");
4210 break;
4212 if (tline->type == TOK_WHITESPACE
4213 && brackets <= 0) {
4214 if (paramsize[nparam])
4215 white++;
4216 else
4217 params[nparam] = tline->next;
4218 continue; /* parameter loop */
4220 if (tline->type == TOK_OTHER
4221 && tline->text[1] == 0) {
4222 char ch = tline->text[0];
4223 if (ch == ',' && !paren && brackets <= 0) {
4224 if (++nparam >= sparam) {
4225 sparam += PARAM_DELTA;
4226 params = nasm_realloc(params,
4227 sparam * sizeof(Token *));
4228 paramsize = nasm_realloc(paramsize,
4229 sparam * sizeof(int));
4231 params[nparam] = tline->next;
4232 paramsize[nparam] = 0;
4233 white = 0;
4234 continue; /* parameter loop */
4236 if (ch == '{' &&
4237 (brackets > 0 || (brackets == 0 &&
4238 !paramsize[nparam])))
4240 if (!(brackets++)) {
4241 params[nparam] = tline->next;
4242 continue; /* parameter loop */
4245 if (ch == '}' && brackets > 0)
4246 if (--brackets == 0) {
4247 brackets = -1;
4248 continue; /* parameter loop */
4250 if (ch == '(' && !brackets)
4251 paren++;
4252 if (ch == ')' && brackets <= 0)
4253 if (--paren < 0)
4254 break;
4256 if (brackets < 0) {
4257 brackets = 0;
4258 nasm_error(ERR_NONFATAL, "braces do not "
4259 "enclose all of macro parameter");
4261 paramsize[nparam] += white + 1;
4262 white = 0;
4263 } /* parameter loop */
4264 nparam++;
4265 while (m && (m->nparam != nparam ||
4266 mstrcmp(m->name, mname,
4267 m->casesense)))
4268 m = m->next;
4269 if (!m)
4270 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4271 "macro `%s' exists, "
4272 "but not taking %d parameters",
4273 mstart->text, nparam);
4276 if (m && m->in_progress)
4277 m = NULL;
4278 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4280 * Design question: should we handle !tline, which
4281 * indicates missing ')' here, or expand those
4282 * macros anyway, which requires the (t) test a few
4283 * lines down?
4285 nasm_free(params);
4286 nasm_free(paramsize);
4287 tline = mstart;
4288 } else {
4290 * Expand the macro: we are placed on the last token of the
4291 * call, so that we can easily split the call from the
4292 * following tokens. We also start by pushing an SMAC_END
4293 * token for the cycle removal.
4295 t = tline;
4296 if (t) {
4297 tline = t->next;
4298 t->next = NULL;
4300 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4301 tt->a.mac = m;
4302 m->in_progress = true;
4303 tline = tt;
4304 list_for_each(t, m->expansion) {
4305 if (t->type >= TOK_SMAC_PARAM) {
4306 Token *pcopy = tline, **ptail = &pcopy;
4307 Token *ttt, *pt;
4308 int i;
4310 ttt = params[t->type - TOK_SMAC_PARAM];
4311 i = paramsize[t->type - TOK_SMAC_PARAM];
4312 while (--i >= 0) {
4313 pt = *ptail = new_Token(tline, ttt->type,
4314 ttt->text, 0);
4315 ptail = &pt->next;
4316 ttt = ttt->next;
4318 tline = pcopy;
4319 } else if (t->type == TOK_PREPROC_Q) {
4320 tt = new_Token(tline, TOK_ID, mname, 0);
4321 tline = tt;
4322 } else if (t->type == TOK_PREPROC_QQ) {
4323 tt = new_Token(tline, TOK_ID, m->name, 0);
4324 tline = tt;
4325 } else {
4326 tt = new_Token(tline, t->type, t->text, 0);
4327 tline = tt;
4332 * Having done that, get rid of the macro call, and clean
4333 * up the parameters.
4335 nasm_free(params);
4336 nasm_free(paramsize);
4337 free_tlist(mstart);
4338 expanded = true;
4339 continue; /* main token loop */
4344 if (tline->type == TOK_SMAC_END) {
4345 tline->a.mac->in_progress = false;
4346 tline = delete_Token(tline);
4347 } else {
4348 t = *tail = tline;
4349 tline = tline->next;
4350 t->a.mac = NULL;
4351 t->next = NULL;
4352 tail = &t->next;
4357 * Now scan the entire line and look for successive TOK_IDs that resulted
4358 * after expansion (they can't be produced by tokenize()). The successive
4359 * TOK_IDs should be concatenated.
4360 * Also we look for %+ tokens and concatenate the tokens before and after
4361 * them (without white spaces in between).
4363 if (expanded) {
4364 const struct tokseq_match t[] = {
4366 PP_CONCAT_MASK(TOK_ID) |
4367 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4368 PP_CONCAT_MASK(TOK_ID) |
4369 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4370 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4373 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4375 * If we concatenated something, *and* we had previously expanded
4376 * an actual macro, scan the lines again for macros...
4378 tline = thead;
4379 expanded = false;
4380 goto again;
4384 err:
4385 if (org_tline) {
4386 if (thead) {
4387 *org_tline = *thead;
4388 /* since we just gave text to org_line, don't free it */
4389 thead->text = NULL;
4390 delete_Token(thead);
4391 } else {
4392 /* the expression expanded to empty line;
4393 we can't return NULL for some reasons
4394 we just set the line to a single WHITESPACE token. */
4395 memset(org_tline, 0, sizeof(*org_tline));
4396 org_tline->text = NULL;
4397 org_tline->type = TOK_WHITESPACE;
4399 thead = org_tline;
4402 return thead;
4406 * Similar to expand_smacro but used exclusively with macro identifiers
4407 * right before they are fetched in. The reason is that there can be
4408 * identifiers consisting of several subparts. We consider that if there
4409 * are more than one element forming the name, user wants a expansion,
4410 * otherwise it will be left as-is. Example:
4412 * %define %$abc cde
4414 * the identifier %$abc will be left as-is so that the handler for %define
4415 * will suck it and define the corresponding value. Other case:
4417 * %define _%$abc cde
4419 * In this case user wants name to be expanded *before* %define starts
4420 * working, so we'll expand %$abc into something (if it has a value;
4421 * otherwise it will be left as-is) then concatenate all successive
4422 * PP_IDs into one.
4424 static Token *expand_id(Token * tline)
4426 Token *cur, *oldnext = NULL;
4428 if (!tline || !tline->next)
4429 return tline;
4431 cur = tline;
4432 while (cur->next &&
4433 (cur->next->type == TOK_ID ||
4434 cur->next->type == TOK_PREPROC_ID
4435 || cur->next->type == TOK_NUMBER))
4436 cur = cur->next;
4438 /* If identifier consists of just one token, don't expand */
4439 if (cur == tline)
4440 return tline;
4442 if (cur) {
4443 oldnext = cur->next; /* Detach the tail past identifier */
4444 cur->next = NULL; /* so that expand_smacro stops here */
4447 tline = expand_smacro(tline);
4449 if (cur) {
4450 /* expand_smacro possibly changhed tline; re-scan for EOL */
4451 cur = tline;
4452 while (cur && cur->next)
4453 cur = cur->next;
4454 if (cur)
4455 cur->next = oldnext;
4458 return tline;
4462 * Determine whether the given line constitutes a multi-line macro
4463 * call, and return the MMacro structure called if so. Doesn't have
4464 * to check for an initial label - that's taken care of in
4465 * expand_mmacro - but must check numbers of parameters. Guaranteed
4466 * to be called with tline->type == TOK_ID, so the putative macro
4467 * name is easy to find.
4469 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4471 MMacro *head, *m;
4472 Token **params;
4473 int nparam;
4475 head = (MMacro *) hash_findix(&mmacros, tline->text);
4478 * Efficiency: first we see if any macro exists with the given
4479 * name. If not, we can return NULL immediately. _Then_ we
4480 * count the parameters, and then we look further along the
4481 * list if necessary to find the proper MMacro.
4483 list_for_each(m, head)
4484 if (!mstrcmp(m->name, tline->text, m->casesense))
4485 break;
4486 if (!m)
4487 return NULL;
4490 * OK, we have a potential macro. Count and demarcate the
4491 * parameters.
4493 count_mmac_params(tline->next, &nparam, &params);
4496 * So we know how many parameters we've got. Find the MMacro
4497 * structure that handles this number.
4499 while (m) {
4500 if (m->nparam_min <= nparam
4501 && (m->plus || nparam <= m->nparam_max)) {
4503 * This one is right. Just check if cycle removal
4504 * prohibits us using it before we actually celebrate...
4506 if (m->in_progress > m->max_depth) {
4507 if (m->max_depth > 0) {
4508 nasm_error(ERR_WARNING,
4509 "reached maximum recursion depth of %i",
4510 m->max_depth);
4512 nasm_free(params);
4513 return NULL;
4516 * It's right, and we can use it. Add its default
4517 * parameters to the end of our list if necessary.
4519 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4520 params =
4521 nasm_realloc(params,
4522 ((m->nparam_min + m->ndefs +
4523 1) * sizeof(*params)));
4524 while (nparam < m->nparam_min + m->ndefs) {
4525 params[nparam] = m->defaults[nparam - m->nparam_min];
4526 nparam++;
4530 * If we've gone over the maximum parameter count (and
4531 * we're in Plus mode), ignore parameters beyond
4532 * nparam_max.
4534 if (m->plus && nparam > m->nparam_max)
4535 nparam = m->nparam_max;
4537 * Then terminate the parameter list, and leave.
4539 if (!params) { /* need this special case */
4540 params = nasm_malloc(sizeof(*params));
4541 nparam = 0;
4543 params[nparam] = NULL;
4544 *params_array = params;
4545 return m;
4548 * This one wasn't right: look for the next one with the
4549 * same name.
4551 list_for_each(m, m->next)
4552 if (!mstrcmp(m->name, tline->text, m->casesense))
4553 break;
4557 * After all that, we didn't find one with the right number of
4558 * parameters. Issue a warning, and fail to expand the macro.
4560 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4561 "macro `%s' exists, but not taking %d parameters",
4562 tline->text, nparam);
4563 nasm_free(params);
4564 return NULL;
4569 * Save MMacro invocation specific fields in
4570 * preparation for a recursive macro expansion
4572 static void push_mmacro(MMacro *m)
4574 MMacroInvocation *i;
4576 i = nasm_malloc(sizeof(MMacroInvocation));
4577 i->prev = m->prev;
4578 i->params = m->params;
4579 i->iline = m->iline;
4580 i->nparam = m->nparam;
4581 i->rotate = m->rotate;
4582 i->paramlen = m->paramlen;
4583 i->unique = m->unique;
4584 i->condcnt = m->condcnt;
4585 m->prev = i;
4590 * Restore MMacro invocation specific fields that were
4591 * saved during a previous recursive macro expansion
4593 static void pop_mmacro(MMacro *m)
4595 MMacroInvocation *i;
4597 if (m->prev) {
4598 i = m->prev;
4599 m->prev = i->prev;
4600 m->params = i->params;
4601 m->iline = i->iline;
4602 m->nparam = i->nparam;
4603 m->rotate = i->rotate;
4604 m->paramlen = i->paramlen;
4605 m->unique = i->unique;
4606 m->condcnt = i->condcnt;
4607 nasm_free(i);
4613 * Expand the multi-line macro call made by the given line, if
4614 * there is one to be expanded. If there is, push the expansion on
4615 * istk->expansion and return 1. Otherwise return 0.
4617 static int expand_mmacro(Token * tline)
4619 Token *startline = tline;
4620 Token *label = NULL;
4621 int dont_prepend = 0;
4622 Token **params, *t, *tt;
4623 MMacro *m;
4624 Line *l, *ll;
4625 int i, nparam, *paramlen;
4626 const char *mname;
4628 t = tline;
4629 skip_white_(t);
4630 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4631 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4632 return 0;
4633 m = is_mmacro(t, &params);
4634 if (m) {
4635 mname = t->text;
4636 } else {
4637 Token *last;
4639 * We have an id which isn't a macro call. We'll assume
4640 * it might be a label; we'll also check to see if a
4641 * colon follows it. Then, if there's another id after
4642 * that lot, we'll check it again for macro-hood.
4644 label = last = t;
4645 t = t->next;
4646 if (tok_type_(t, TOK_WHITESPACE))
4647 last = t, t = t->next;
4648 if (tok_is_(t, ":")) {
4649 dont_prepend = 1;
4650 last = t, t = t->next;
4651 if (tok_type_(t, TOK_WHITESPACE))
4652 last = t, t = t->next;
4654 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4655 return 0;
4656 last->next = NULL;
4657 mname = t->text;
4658 tline = t;
4662 * Fix up the parameters: this involves stripping leading and
4663 * trailing whitespace, then stripping braces if they are
4664 * present.
4666 for (nparam = 0; params[nparam]; nparam++) ;
4667 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4669 for (i = 0; params[i]; i++) {
4670 int brace = 0;
4671 int comma = (!m->plus || i < nparam - 1);
4673 t = params[i];
4674 skip_white_(t);
4675 if (tok_is_(t, "{"))
4676 t = t->next, brace++, comma = false;
4677 params[i] = t;
4678 paramlen[i] = 0;
4679 while (t) {
4680 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4681 break; /* ... because we have hit a comma */
4682 if (comma && t->type == TOK_WHITESPACE
4683 && tok_is_(t->next, ","))
4684 break; /* ... or a space then a comma */
4685 if (brace && t->type == TOK_OTHER) {
4686 if (t->text[0] == '{')
4687 brace++; /* ... or a nested opening brace */
4688 else if (t->text[0] == '}')
4689 if (!--brace)
4690 break; /* ... or a brace */
4692 t = t->next;
4693 paramlen[i]++;
4695 if (brace)
4696 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4700 * OK, we have a MMacro structure together with a set of
4701 * parameters. We must now go through the expansion and push
4702 * copies of each Line on to istk->expansion. Substitution of
4703 * parameter tokens and macro-local tokens doesn't get done
4704 * until the single-line macro substitution process; this is
4705 * because delaying them allows us to change the semantics
4706 * later through %rotate.
4708 * First, push an end marker on to istk->expansion, mark this
4709 * macro as in progress, and set up its invocation-specific
4710 * variables.
4712 ll = nasm_malloc(sizeof(Line));
4713 ll->next = istk->expansion;
4714 ll->finishes = m;
4715 ll->first = NULL;
4716 istk->expansion = ll;
4719 * Save the previous MMacro expansion in the case of
4720 * macro recursion
4722 if (m->max_depth && m->in_progress)
4723 push_mmacro(m);
4725 m->in_progress ++;
4726 m->params = params;
4727 m->iline = tline;
4728 m->nparam = nparam;
4729 m->rotate = 0;
4730 m->paramlen = paramlen;
4731 m->unique = unique++;
4732 m->lineno = 0;
4733 m->condcnt = 0;
4735 m->next_active = istk->mstk;
4736 istk->mstk = m;
4738 list_for_each(l, m->expansion) {
4739 Token **tail;
4741 ll = nasm_malloc(sizeof(Line));
4742 ll->finishes = NULL;
4743 ll->next = istk->expansion;
4744 istk->expansion = ll;
4745 tail = &ll->first;
4747 list_for_each(t, l->first) {
4748 Token *x = t;
4749 switch (t->type) {
4750 case TOK_PREPROC_Q:
4751 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4752 break;
4753 case TOK_PREPROC_QQ:
4754 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4755 break;
4756 case TOK_PREPROC_ID:
4757 if (t->text[1] == '0' && t->text[2] == '0') {
4758 dont_prepend = -1;
4759 x = label;
4760 if (!x)
4761 continue;
4763 /* fall through */
4764 default:
4765 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4766 break;
4768 tail = &tt->next;
4770 *tail = NULL;
4774 * If we had a label, push it on as the first line of
4775 * the macro expansion.
4777 if (label) {
4778 if (dont_prepend < 0)
4779 free_tlist(startline);
4780 else {
4781 ll = nasm_malloc(sizeof(Line));
4782 ll->finishes = NULL;
4783 ll->next = istk->expansion;
4784 istk->expansion = ll;
4785 ll->first = startline;
4786 if (!dont_prepend) {
4787 while (label->next)
4788 label = label->next;
4789 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4794 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4796 return 1;
4800 * This function adds macro names to error messages, and suppresses
4801 * them if necessary.
4803 static void pp_verror(int severity, const char *fmt, va_list arg)
4805 char buff[BUFSIZ];
4806 MMacro *mmac = NULL;
4807 int delta = 0;
4810 * If we're in a dead branch of IF or something like it, ignore the error.
4811 * However, because %else etc are evaluated in the state context
4812 * of the previous branch, errors might get lost:
4813 * %if 0 ... %else trailing garbage ... %endif
4814 * So %else etc should set the ERR_PP_PRECOND flag.
4816 if ((severity & ERR_MASK) < ERR_FATAL &&
4817 istk && istk->conds &&
4818 ((severity & ERR_PP_PRECOND) ?
4819 istk->conds->state == COND_NEVER :
4820 !emitting(istk->conds->state)))
4821 return;
4823 /* get %macro name */
4824 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4825 mmac = istk->mstk;
4826 /* but %rep blocks should be skipped */
4827 while (mmac && !mmac->name)
4828 mmac = mmac->next_active, delta++;
4831 if (mmac) {
4832 vsnprintf(buff, sizeof(buff), fmt, arg);
4834 nasm_set_verror(real_verror);
4835 nasm_error(severity, "(%s:%d) %s",
4836 mmac->name, mmac->lineno - delta, buff);
4837 nasm_set_verror(pp_verror);
4838 } else {
4839 real_verror(severity, fmt, arg);
4843 static void
4844 pp_reset(char *file, int apass, StrList **deplist)
4846 Token *t;
4848 cstk = NULL;
4849 istk = nasm_malloc(sizeof(Include));
4850 istk->next = NULL;
4851 istk->conds = NULL;
4852 istk->expansion = NULL;
4853 istk->mstk = NULL;
4854 istk->fp = fopen(file, "r");
4855 istk->fname = NULL;
4856 src_set(0, file);
4857 istk->lineinc = 1;
4858 if (!istk->fp)
4859 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4860 defining = NULL;
4861 nested_mac_count = 0;
4862 nested_rep_count = 0;
4863 init_macros();
4864 unique = 0;
4865 if (tasm_compatible_mode) {
4866 stdmacpos = nasm_stdmac;
4867 } else {
4868 stdmacpos = nasm_stdmac_after_tasm;
4870 any_extrastdmac = extrastdmac && *extrastdmac;
4871 do_predef = true;
4874 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4875 * The caller, however, will also pass in 3 for preprocess-only so
4876 * we can set __PASS__ accordingly.
4878 pass = apass > 2 ? 2 : apass;
4880 dephead = deptail = deplist;
4881 if (deplist) {
4882 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4883 sl->next = NULL;
4884 strcpy(sl->str, file);
4885 *deptail = sl;
4886 deptail = &sl->next;
4890 * Define the __PASS__ macro. This is defined here unlike
4891 * all the other builtins, because it is special -- it varies between
4892 * passes.
4894 t = nasm_malloc(sizeof(*t));
4895 t->next = NULL;
4896 make_tok_num(t, apass);
4897 t->a.mac = NULL;
4898 define_smacro(NULL, "__PASS__", true, 0, t);
4901 static char *pp_getline(void)
4903 char *line;
4904 Token *tline;
4906 real_verror = nasm_set_verror(pp_verror);
4908 while (1) {
4910 * Fetch a tokenized line, either from the macro-expansion
4911 * buffer or from the input file.
4913 tline = NULL;
4914 while (istk->expansion && istk->expansion->finishes) {
4915 Line *l = istk->expansion;
4916 if (!l->finishes->name && l->finishes->in_progress > 1) {
4917 Line *ll;
4920 * This is a macro-end marker for a macro with no
4921 * name, which means it's not really a macro at all
4922 * but a %rep block, and the `in_progress' field is
4923 * more than 1, meaning that we still need to
4924 * repeat. (1 means the natural last repetition; 0
4925 * means termination by %exitrep.) We have
4926 * therefore expanded up to the %endrep, and must
4927 * push the whole block on to the expansion buffer
4928 * again. We don't bother to remove the macro-end
4929 * marker: we'd only have to generate another one
4930 * if we did.
4932 l->finishes->in_progress--;
4933 list_for_each(l, l->finishes->expansion) {
4934 Token *t, *tt, **tail;
4936 ll = nasm_malloc(sizeof(Line));
4937 ll->next = istk->expansion;
4938 ll->finishes = NULL;
4939 ll->first = NULL;
4940 tail = &ll->first;
4942 list_for_each(t, l->first) {
4943 if (t->text || t->type == TOK_WHITESPACE) {
4944 tt = *tail = new_Token(NULL, t->type, t->text, 0);
4945 tail = &tt->next;
4949 istk->expansion = ll;
4951 } else {
4953 * Check whether a `%rep' was started and not ended
4954 * within this macro expansion. This can happen and
4955 * should be detected. It's a fatal error because
4956 * I'm too confused to work out how to recover
4957 * sensibly from it.
4959 if (defining) {
4960 if (defining->name)
4961 nasm_panic(0, "defining with name in expansion");
4962 else if (istk->mstk->name)
4963 nasm_fatal(0, "`%%rep' without `%%endrep' within"
4964 " expansion of macro `%s'",
4965 istk->mstk->name);
4969 * FIXME: investigate the relationship at this point between
4970 * istk->mstk and l->finishes
4973 MMacro *m = istk->mstk;
4974 istk->mstk = m->next_active;
4975 if (m->name) {
4977 * This was a real macro call, not a %rep, and
4978 * therefore the parameter information needs to
4979 * be freed.
4981 if (m->prev) {
4982 pop_mmacro(m);
4983 l->finishes->in_progress --;
4984 } else {
4985 nasm_free(m->params);
4986 free_tlist(m->iline);
4987 nasm_free(m->paramlen);
4988 l->finishes->in_progress = 0;
4990 } else
4991 free_mmacro(m);
4993 istk->expansion = l->next;
4994 nasm_free(l);
4995 lfmt->downlevel(LIST_MACRO);
4998 while (1) { /* until we get a line we can use */
5000 if (istk->expansion) { /* from a macro expansion */
5001 char *p;
5002 Line *l = istk->expansion;
5003 if (istk->mstk)
5004 istk->mstk->lineno++;
5005 tline = l->first;
5006 istk->expansion = l->next;
5007 nasm_free(l);
5008 p = detoken(tline, false);
5009 lfmt->line(LIST_MACRO, p);
5010 nasm_free(p);
5011 break;
5013 line = read_line();
5014 if (line) { /* from the current input file */
5015 line = prepreproc(line);
5016 tline = tokenize(line);
5017 nasm_free(line);
5018 break;
5021 * The current file has ended; work down the istk
5024 Include *i = istk;
5025 fclose(i->fp);
5026 if (i->conds) {
5027 /* nasm_error can't be conditionally suppressed */
5028 nasm_fatal(0,
5029 "expected `%%endif' before end of file");
5031 /* only set line and file name if there's a next node */
5032 if (i->next)
5033 src_set(i->lineno, i->fname);
5034 istk = i->next;
5035 lfmt->downlevel(LIST_INCLUDE);
5036 nasm_free(i);
5037 if (!istk) {
5038 line = NULL;
5039 goto done;
5041 if (istk->expansion && istk->expansion->finishes)
5042 break;
5047 * We must expand MMacro parameters and MMacro-local labels
5048 * _before_ we plunge into directive processing, to cope
5049 * with things like `%define something %1' such as STRUC
5050 * uses. Unless we're _defining_ a MMacro, in which case
5051 * those tokens should be left alone to go into the
5052 * definition; and unless we're in a non-emitting
5053 * condition, in which case we don't want to meddle with
5054 * anything.
5056 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5057 && !(istk->mstk && !istk->mstk->in_progress)) {
5058 tline = expand_mmac_params(tline);
5062 * Check the line to see if it's a preprocessor directive.
5064 if (do_directive(tline) == DIRECTIVE_FOUND) {
5065 continue;
5066 } else if (defining) {
5068 * We're defining a multi-line macro. We emit nothing
5069 * at all, and just
5070 * shove the tokenized line on to the macro definition.
5072 Line *l = nasm_malloc(sizeof(Line));
5073 l->next = defining->expansion;
5074 l->first = tline;
5075 l->finishes = NULL;
5076 defining->expansion = l;
5077 continue;
5078 } else if (istk->conds && !emitting(istk->conds->state)) {
5080 * We're in a non-emitting branch of a condition block.
5081 * Emit nothing at all, not even a blank line: when we
5082 * emerge from the condition we'll give a line-number
5083 * directive so we keep our place correctly.
5085 free_tlist(tline);
5086 continue;
5087 } else if (istk->mstk && !istk->mstk->in_progress) {
5089 * We're in a %rep block which has been terminated, so
5090 * we're walking through to the %endrep without
5091 * emitting anything. Emit nothing at all, not even a
5092 * blank line: when we emerge from the %rep block we'll
5093 * give a line-number directive so we keep our place
5094 * correctly.
5096 free_tlist(tline);
5097 continue;
5098 } else {
5099 tline = expand_smacro(tline);
5100 if (!expand_mmacro(tline)) {
5102 * De-tokenize the line again, and emit it.
5104 line = detoken(tline, true);
5105 free_tlist(tline);
5106 break;
5107 } else {
5108 continue; /* expand_mmacro calls free_tlist */
5113 done:
5114 nasm_set_verror(real_verror);
5115 return line;
5118 static void pp_cleanup(int pass)
5120 real_verror = nasm_set_verror(pp_verror);
5122 if (defining) {
5123 if (defining->name) {
5124 nasm_error(ERR_NONFATAL,
5125 "end of file while still defining macro `%s'",
5126 defining->name);
5127 } else {
5128 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5131 free_mmacro(defining);
5132 defining = NULL;
5135 nasm_set_verror(real_verror);
5137 while (cstk)
5138 ctx_pop();
5139 free_macros();
5140 while (istk) {
5141 Include *i = istk;
5142 istk = istk->next;
5143 fclose(i->fp);
5144 nasm_free(i);
5146 while (cstk)
5147 ctx_pop();
5148 src_set_fname(NULL);
5149 if (pass == 0) {
5150 IncPath *i;
5151 free_llist(predef);
5152 predef = NULL;
5153 delete_Blocks();
5154 freeTokens = NULL;
5155 while ((i = ipath)) {
5156 ipath = i->next;
5157 if (i->path)
5158 nasm_free(i->path);
5159 nasm_free(i);
5164 static void pp_include_path(char *path)
5166 IncPath *i;
5168 i = nasm_malloc(sizeof(IncPath));
5169 i->path = path ? nasm_strdup(path) : NULL;
5170 i->next = NULL;
5172 if (ipath) {
5173 IncPath *j = ipath;
5174 while (j->next)
5175 j = j->next;
5176 j->next = i;
5177 } else {
5178 ipath = i;
5182 static void pp_pre_include(char *fname)
5184 Token *inc, *space, *name;
5185 Line *l;
5187 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5188 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5189 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5191 l = nasm_malloc(sizeof(Line));
5192 l->next = predef;
5193 l->first = inc;
5194 l->finishes = NULL;
5195 predef = l;
5198 static void pp_pre_define(char *definition)
5200 Token *def, *space;
5201 Line *l;
5202 char *equals;
5204 real_verror = nasm_set_verror(pp_verror);
5206 equals = strchr(definition, '=');
5207 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5208 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5209 if (equals)
5210 *equals = ' ';
5211 space->next = tokenize(definition);
5212 if (equals)
5213 *equals = '=';
5215 if (space->next->type != TOK_PREPROC_ID &&
5216 space->next->type != TOK_ID)
5217 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5219 l = nasm_malloc(sizeof(Line));
5220 l->next = predef;
5221 l->first = def;
5222 l->finishes = NULL;
5223 predef = l;
5225 nasm_set_verror(real_verror);
5228 static void pp_pre_undefine(char *definition)
5230 Token *def, *space;
5231 Line *l;
5233 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5234 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5235 space->next = tokenize(definition);
5237 l = nasm_malloc(sizeof(Line));
5238 l->next = predef;
5239 l->first = def;
5240 l->finishes = NULL;
5241 predef = l;
5244 static void pp_extra_stdmac(macros_t *macros)
5246 extrastdmac = macros;
5249 static void make_tok_num(Token * tok, int64_t val)
5251 char numbuf[32];
5252 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5253 tok->text = nasm_strdup(numbuf);
5254 tok->type = TOK_NUMBER;
5257 static void pp_list_one_macro(MMacro *m, int severity)
5259 if (!m)
5260 return;
5262 /* We need to print the next_active list in reverse order */
5263 pp_list_one_macro(m->next_active, severity);
5265 if (m->name && !m->nolist) {
5266 src_set(m->xline + m->lineno, m->fname);
5267 nasm_error(severity, "... from macro `%s' defined here", m->name);
5271 static void pp_error_list_macros(int severity)
5273 int32_t saved_line;
5274 const char *saved_fname = NULL;
5276 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5277 src_get(&saved_line, &saved_fname);
5279 if (istk)
5280 pp_list_one_macro(istk->mstk, severity);
5282 src_set(saved_line, saved_fname);
5285 const struct preproc_ops nasmpp = {
5286 pp_reset,
5287 pp_getline,
5288 pp_cleanup,
5289 pp_extra_stdmac,
5290 pp_pre_define,
5291 pp_pre_undefine,
5292 pp_pre_include,
5293 pp_include_path,
5294 pp_error_list_macros,