macros: Define ofmt specific macros late
[nasm.git] / asm / preproc.c
blobee91d15beb77f60856a06b04de39324729037754
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 * File real name hash, so we don't have to re-search the include
290 * path for every pass (and potentially more than that if a file
291 * is used more than once.)
293 struct hash_table FileHash;
296 * Conditional assembly: we maintain a separate stack of these for
297 * each level of file inclusion. (The only reason we keep the
298 * stacks separate is to ensure that a stray `%endif' in a file
299 * included from within the true branch of a `%if' won't terminate
300 * it and cause confusion: instead, rightly, it'll cause an error.)
302 struct Cond {
303 Cond *next;
304 int state;
306 enum {
308 * These states are for use just after %if or %elif: IF_TRUE
309 * means the condition has evaluated to truth so we are
310 * currently emitting, whereas IF_FALSE means we are not
311 * currently emitting but will start doing so if a %else comes
312 * up. In these states, all directives are admissible: %elif,
313 * %else and %endif. (And of course %if.)
315 COND_IF_TRUE, COND_IF_FALSE,
317 * These states come up after a %else: ELSE_TRUE means we're
318 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
319 * any %elif or %else will cause an error.
321 COND_ELSE_TRUE, COND_ELSE_FALSE,
323 * These states mean that we're not emitting now, and also that
324 * nothing until %endif will be emitted at all. COND_DONE is
325 * used when we've had our moment of emission
326 * and have now started seeing %elifs. COND_NEVER is used when
327 * the condition construct in question is contained within a
328 * non-emitting branch of a larger condition construct,
329 * or if there is an error.
331 COND_DONE, COND_NEVER
333 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
336 * These defines are used as the possible return values for do_directive
338 #define NO_DIRECTIVE_FOUND 0
339 #define DIRECTIVE_FOUND 1
342 * This define sets the upper limit for smacro and recursive mmacro
343 * expansions
345 #define DEADMAN_LIMIT (1 << 20)
347 /* max reps */
348 #define REP_LIMIT ((INT64_C(1) << 62))
351 * Condition codes. Note that we use c_ prefix not C_ because C_ is
352 * used in nasm.h for the "real" condition codes. At _this_ level,
353 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
354 * ones, so we need a different enum...
356 static const char * const conditions[] = {
357 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
358 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
359 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
361 enum pp_conds {
362 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
363 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
364 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
365 c_none = -1
367 static const enum pp_conds inverse_ccs[] = {
368 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
369 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,
370 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
374 * Directive names.
376 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
377 static int is_condition(enum preproc_token arg)
379 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
382 /* For TASM compatibility we need to be able to recognise TASM compatible
383 * conditional compilation directives. Using the NASM pre-processor does
384 * not work, so we look for them specifically from the following list and
385 * then jam in the equivalent NASM directive into the input stream.
388 enum {
389 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
390 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
393 static const char * const tasm_directives[] = {
394 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
395 "ifndef", "include", "local"
398 static int StackSize = 4;
399 static const char *StackPointer = "ebp";
400 static int ArgOffset = 8;
401 static int LocalOffset = 0;
403 static Context *cstk;
404 static Include *istk;
405 static IncPath *ipath = NULL;
407 static int pass; /* HACK: pass 0 = generate dependencies only */
408 static StrList **dephead;
410 static uint64_t unique; /* unique identifier numbers */
412 static Line *predef = NULL;
413 static bool do_predef;
416 * The current set of multi-line macros we have defined.
418 static struct hash_table mmacros;
421 * The current set of single-line macros we have defined.
423 static struct hash_table smacros;
426 * The multi-line macro we are currently defining, or the %rep
427 * block we are currently reading, if any.
429 static MMacro *defining;
431 static uint64_t nested_mac_count;
432 static uint64_t nested_rep_count;
435 * The number of macro parameters to allocate space for at a time.
437 #define PARAM_DELTA 16
440 * The standard macro set: defined in macros.c in a set of arrays.
441 * This gives our position in any macro set, while we are processing it.
442 * The stdmacset is an array of such macro sets.
444 static macros_t *stdmacpos;
445 static macros_t **stdmacnext;
446 static macros_t *stdmacros[8];
447 static macros_t *extrastdmac;
450 * Tokens are allocated in blocks to improve speed
452 #define TOKEN_BLOCKSIZE 4096
453 static Token *freeTokens = NULL;
454 struct Blocks {
455 Blocks *next;
456 void *chunk;
459 static Blocks blocks = { NULL, NULL };
462 * Forward declarations.
464 static void pp_add_stdmac(macros_t *macros);
465 static Token *expand_mmac_params(Token * tline);
466 static Token *expand_smacro(Token * tline);
467 static Token *expand_id(Token * tline);
468 static Context *get_ctx(const char *name, const char **namep);
469 static void make_tok_num(Token * tok, int64_t val);
470 static void pp_verror(int severity, const char *fmt, va_list ap);
471 static vefunc real_verror;
472 static void *new_Block(size_t size);
473 static void delete_Blocks(void);
474 static Token *new_Token(Token * next, enum pp_token_type type,
475 const char *text, int txtlen);
476 static Token *delete_Token(Token * t);
479 * Macros for safe checking of token pointers, avoid *(NULL)
481 #define tok_type_(x,t) ((x) && (x)->type == (t))
482 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
483 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
484 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
487 * nasm_unquote with error if the string contains NUL characters.
488 * If the string contains NUL characters, issue an error and return
489 * the C len, i.e. truncate at the NUL.
491 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
493 size_t len = nasm_unquote(qstr, NULL);
494 size_t clen = strlen(qstr);
496 if (len != clen)
497 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
498 pp_directives[directive]);
500 return clen;
504 * In-place reverse a list of tokens.
506 static Token *reverse_tokens(Token *t)
508 Token *prev = NULL;
509 Token *next;
511 while (t) {
512 next = t->next;
513 t->next = prev;
514 prev = t;
515 t = next;
518 return prev;
522 * Handle TASM specific directives, which do not contain a % in
523 * front of them. We do it here because I could not find any other
524 * place to do it for the moment, and it is a hack (ideally it would
525 * be nice to be able to use the NASM pre-processor to do it).
527 static char *check_tasm_directive(char *line)
529 int32_t i, j, k, m, len;
530 char *p, *q, *oldline, oldchar;
532 p = nasm_skip_spaces(line);
534 /* Binary search for the directive name */
535 i = -1;
536 j = ARRAY_SIZE(tasm_directives);
537 q = nasm_skip_word(p);
538 len = q - p;
539 if (len) {
540 oldchar = p[len];
541 p[len] = 0;
542 while (j - i > 1) {
543 k = (j + i) / 2;
544 m = nasm_stricmp(p, tasm_directives[k]);
545 if (m == 0) {
546 /* We have found a directive, so jam a % in front of it
547 * so that NASM will then recognise it as one if it's own.
549 p[len] = oldchar;
550 len = strlen(p);
551 oldline = line;
552 line = nasm_malloc(len + 2);
553 line[0] = '%';
554 if (k == TM_IFDIFI) {
556 * NASM does not recognise IFDIFI, so we convert
557 * it to %if 0. This is not used in NASM
558 * compatible code, but does need to parse for the
559 * TASM macro package.
561 strcpy(line + 1, "if 0");
562 } else {
563 memcpy(line + 1, p, len + 1);
565 nasm_free(oldline);
566 return line;
567 } else if (m < 0) {
568 j = k;
569 } else
570 i = k;
572 p[len] = oldchar;
574 return line;
578 * The pre-preprocessing stage... This function translates line
579 * number indications as they emerge from GNU cpp (`# lineno "file"
580 * flags') into NASM preprocessor line number indications (`%line
581 * lineno file').
583 static char *prepreproc(char *line)
585 int lineno, fnlen;
586 char *fname, *oldline;
588 if (line[0] == '#' && line[1] == ' ') {
589 oldline = line;
590 fname = oldline + 2;
591 lineno = atoi(fname);
592 fname += strspn(fname, "0123456789 ");
593 if (*fname == '"')
594 fname++;
595 fnlen = strcspn(fname, "\"");
596 line = nasm_malloc(20 + fnlen);
597 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
598 nasm_free(oldline);
600 if (tasm_compatible_mode)
601 return check_tasm_directive(line);
602 return line;
606 * Free a linked list of tokens.
608 static void free_tlist(Token * list)
610 while (list)
611 list = delete_Token(list);
615 * Free a linked list of lines.
617 static void free_llist(Line * list)
619 Line *l, *tmp;
620 list_for_each_safe(l, tmp, list) {
621 free_tlist(l->first);
622 nasm_free(l);
627 * Free an MMacro
629 static void free_mmacro(MMacro * m)
631 nasm_free(m->name);
632 free_tlist(m->dlist);
633 nasm_free(m->defaults);
634 free_llist(m->expansion);
635 nasm_free(m);
639 * Free all currently defined macros, and free the hash tables
641 static void free_smacro_table(struct hash_table *smt)
643 SMacro *s, *tmp;
644 const char *key;
645 struct hash_tbl_node *it = NULL;
647 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
648 nasm_free((void *)key);
649 list_for_each_safe(s, tmp, s) {
650 nasm_free(s->name);
651 free_tlist(s->expansion);
652 nasm_free(s);
655 hash_free(smt);
658 static void free_mmacro_table(struct hash_table *mmt)
660 MMacro *m, *tmp;
661 const char *key;
662 struct hash_tbl_node *it = NULL;
664 it = NULL;
665 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
666 nasm_free((void *)key);
667 list_for_each_safe(m ,tmp, m)
668 free_mmacro(m);
670 hash_free(mmt);
673 static void free_macros(void)
675 free_smacro_table(&smacros);
676 free_mmacro_table(&mmacros);
680 * Initialize the hash tables
682 static void init_macros(void)
684 hash_init(&smacros, HASH_LARGE);
685 hash_init(&mmacros, HASH_LARGE);
689 * Pop the context stack.
691 static void ctx_pop(void)
693 Context *c = cstk;
695 cstk = cstk->next;
696 free_smacro_table(&c->localmac);
697 nasm_free(c->name);
698 nasm_free(c);
702 * Search for a key in the hash index; adding it if necessary
703 * (in which case we initialize the data pointer to NULL.)
705 static void **
706 hash_findi_add(struct hash_table *hash, const char *str)
708 struct hash_insert hi;
709 void **r;
710 char *strx;
712 r = hash_findi(hash, str, &hi);
713 if (r)
714 return r;
716 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
717 return hash_add(&hi, strx, NULL);
721 * Like hash_findi, but returns the data element rather than a pointer
722 * to it. Used only when not adding a new element, hence no third
723 * argument.
725 static void *
726 hash_findix(struct hash_table *hash, const char *str)
728 void **p;
730 p = hash_findi(hash, str, NULL);
731 return p ? *p : NULL;
735 * read line from standart macros set,
736 * if there no more left -- return NULL
738 static char *line_from_stdmac(void)
740 unsigned char c;
741 const unsigned char *p = stdmacpos;
742 char *line, *q;
743 size_t len = 0;
745 if (!stdmacpos)
746 return NULL;
748 while ((c = *p++)) {
749 if (c >= 0x80)
750 len += pp_directives_len[c - 0x80] + 1;
751 else
752 len++;
755 line = nasm_malloc(len + 1);
756 q = line;
757 while ((c = *stdmacpos++)) {
758 if (c >= 0x80) {
759 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
760 q += pp_directives_len[c - 0x80];
761 *q++ = ' ';
762 } else {
763 *q++ = c;
766 stdmacpos = p;
767 *q = '\0';
769 if (!*stdmacpos) {
770 /* This was the last of this particular macro set */
771 stdmacpos = NULL;
772 if (*stdmacnext) {
773 stdmacpos = *stdmacnext++;
774 } else if (do_predef) {
775 Line *pd, *l;
776 Token *head, **tail, *t;
779 * Nasty hack: here we push the contents of
780 * `predef' on to the top-level expansion stack,
781 * since this is the most convenient way to
782 * implement the pre-include and pre-define
783 * features.
785 list_for_each(pd, predef) {
786 head = NULL;
787 tail = &head;
788 list_for_each(t, pd->first) {
789 *tail = new_Token(NULL, t->type, t->text, 0);
790 tail = &(*tail)->next;
793 l = nasm_malloc(sizeof(Line));
794 l->next = istk->expansion;
795 l->first = head;
796 l->finishes = NULL;
798 istk->expansion = l;
800 do_predef = false;
804 return line;
807 static char *read_line(void)
809 unsigned int size, c, next;
810 const unsigned int delta = 512;
811 const unsigned int pad = 8;
812 unsigned int nr_cont = 0;
813 bool cont = false;
814 char *buffer, *p;
816 /* Standart macros set (predefined) goes first */
817 p = line_from_stdmac();
818 if (p)
819 return p;
821 size = delta;
822 p = buffer = nasm_malloc(size);
824 for (;;) {
825 c = fgetc(istk->fp);
826 if ((int)(c) == EOF) {
827 p[0] = 0;
828 break;
831 switch (c) {
832 case '\r':
833 next = fgetc(istk->fp);
834 if (next != '\n')
835 ungetc(next, istk->fp);
836 if (cont) {
837 cont = false;
838 continue;
840 break;
842 case '\n':
843 if (cont) {
844 cont = false;
845 continue;
847 break;
849 case '\\':
850 next = fgetc(istk->fp);
851 ungetc(next, istk->fp);
852 if (next == '\r' || next == '\n') {
853 cont = true;
854 nr_cont++;
855 continue;
857 break;
860 if (c == '\r' || c == '\n') {
861 *p++ = 0;
862 break;
865 if (p >= (buffer + size - pad)) {
866 buffer = nasm_realloc(buffer, size + delta);
867 p = buffer + size - pad;
868 size += delta;
871 *p++ = (unsigned char)c;
874 if (p == buffer) {
875 nasm_free(buffer);
876 return NULL;
879 src_set_linnum(src_get_linnum() + istk->lineinc +
880 (nr_cont * istk->lineinc));
883 * Handle spurious ^Z, which may be inserted into source files
884 * by some file transfer utilities.
886 buffer[strcspn(buffer, "\032")] = '\0';
888 lfmt->line(LIST_READ, buffer);
890 return buffer;
894 * Tokenize a line of text. This is a very simple process since we
895 * don't need to parse the value out of e.g. numeric tokens: we
896 * simply split one string into many.
898 static Token *tokenize(char *line)
900 char c, *p = line;
901 enum pp_token_type type;
902 Token *list = NULL;
903 Token *t, **tail = &list;
905 while (*line) {
906 p = line;
907 if (*p == '%') {
908 p++;
909 if (*p == '+' && !nasm_isdigit(p[1])) {
910 p++;
911 type = TOK_PASTE;
912 } else if (nasm_isdigit(*p) ||
913 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
914 do {
915 p++;
917 while (nasm_isdigit(*p));
918 type = TOK_PREPROC_ID;
919 } else if (*p == '{') {
920 p++;
921 while (*p) {
922 if (*p == '}')
923 break;
924 p[-1] = *p;
925 p++;
927 if (*p != '}')
928 nasm_error(ERR_WARNING | ERR_PASS1,
929 "unterminated %%{ construct");
930 p[-1] = '\0';
931 if (*p)
932 p++;
933 type = TOK_PREPROC_ID;
934 } else if (*p == '[') {
935 int lvl = 1;
936 line += 2; /* Skip the leading %[ */
937 p++;
938 while (lvl && (c = *p++)) {
939 switch (c) {
940 case ']':
941 lvl--;
942 break;
943 case '%':
944 if (*p == '[')
945 lvl++;
946 break;
947 case '\'':
948 case '\"':
949 case '`':
950 p = nasm_skip_string(p - 1) + 1;
951 break;
952 default:
953 break;
956 p--;
957 if (*p)
958 *p++ = '\0';
959 if (lvl)
960 nasm_error(ERR_NONFATAL|ERR_PASS1,
961 "unterminated %%[ construct");
962 type = TOK_INDIRECT;
963 } else if (*p == '?') {
964 type = TOK_PREPROC_Q; /* %? */
965 p++;
966 if (*p == '?') {
967 type = TOK_PREPROC_QQ; /* %?? */
968 p++;
970 } else if (*p == '!') {
971 type = TOK_PREPROC_ID;
972 p++;
973 if (isidchar(*p)) {
974 do {
975 p++;
977 while (isidchar(*p));
978 } else if (*p == '\'' || *p == '\"' || *p == '`') {
979 p = nasm_skip_string(p);
980 if (*p)
981 p++;
982 else
983 nasm_error(ERR_NONFATAL|ERR_PASS1,
984 "unterminated %%! string");
985 } else {
986 /* %! without string or identifier */
987 type = TOK_OTHER; /* Legacy behavior... */
989 } else if (isidchar(*p) ||
990 ((*p == '!' || *p == '%' || *p == '$') &&
991 isidchar(p[1]))) {
992 do {
993 p++;
995 while (isidchar(*p));
996 type = TOK_PREPROC_ID;
997 } else {
998 type = TOK_OTHER;
999 if (*p == '%')
1000 p++;
1002 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1003 type = TOK_ID;
1004 p++;
1005 while (*p && isidchar(*p))
1006 p++;
1007 } else if (*p == '\'' || *p == '"' || *p == '`') {
1009 * A string token.
1011 type = TOK_STRING;
1012 p = nasm_skip_string(p);
1014 if (*p) {
1015 p++;
1016 } else {
1017 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1018 /* Handling unterminated strings by UNV */
1019 /* type = -1; */
1021 } else if (p[0] == '$' && p[1] == '$') {
1022 type = TOK_OTHER; /* TOKEN_BASE */
1023 p += 2;
1024 } else if (isnumstart(*p)) {
1025 bool is_hex = false;
1026 bool is_float = false;
1027 bool has_e = false;
1028 char c, *r;
1031 * A numeric token.
1034 if (*p == '$') {
1035 p++;
1036 is_hex = true;
1039 for (;;) {
1040 c = *p++;
1042 if (!is_hex && (c == 'e' || c == 'E')) {
1043 has_e = true;
1044 if (*p == '+' || *p == '-') {
1046 * e can only be followed by +/- if it is either a
1047 * prefixed hex number or a floating-point number
1049 p++;
1050 is_float = true;
1052 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1053 is_hex = true;
1054 } else if (c == 'P' || c == 'p') {
1055 is_float = true;
1056 if (*p == '+' || *p == '-')
1057 p++;
1058 } else if (isnumchar(c))
1059 ; /* just advance */
1060 else if (c == '.') {
1062 * we need to deal with consequences of the legacy
1063 * parser, like "1.nolist" being two tokens
1064 * (TOK_NUMBER, TOK_ID) here; at least give it
1065 * a shot for now. In the future, we probably need
1066 * a flex-based scanner with proper pattern matching
1067 * to do it as well as it can be done. Nothing in
1068 * the world is going to help the person who wants
1069 * 0x123.p16 interpreted as two tokens, though.
1071 r = p;
1072 while (*r == '_')
1073 r++;
1075 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1076 (!is_hex && (*r == 'e' || *r == 'E')) ||
1077 (*r == 'p' || *r == 'P')) {
1078 p = r;
1079 is_float = true;
1080 } else
1081 break; /* Terminate the token */
1082 } else
1083 break;
1085 p--; /* Point to first character beyond number */
1087 if (p == line+1 && *line == '$') {
1088 type = TOK_OTHER; /* TOKEN_HERE */
1089 } else {
1090 if (has_e && !is_hex) {
1091 /* 1e13 is floating-point, but 1e13h is not */
1092 is_float = true;
1095 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1097 } else if (nasm_isspace(*p)) {
1098 type = TOK_WHITESPACE;
1099 p = nasm_skip_spaces(p);
1101 * Whitespace just before end-of-line is discarded by
1102 * pretending it's a comment; whitespace just before a
1103 * comment gets lumped into the comment.
1105 if (!*p || *p == ';') {
1106 type = TOK_COMMENT;
1107 while (*p)
1108 p++;
1110 } else if (*p == ';') {
1111 type = TOK_COMMENT;
1112 while (*p)
1113 p++;
1114 } else {
1116 * Anything else is an operator of some kind. We check
1117 * for all the double-character operators (>>, <<, //,
1118 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1119 * else is a single-character operator.
1121 type = TOK_OTHER;
1122 if ((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[0] == '<' && p[1] == '>') ||
1130 (p[0] == '&' && p[1] == '&') ||
1131 (p[0] == '|' && p[1] == '|') ||
1132 (p[0] == '^' && p[1] == '^')) {
1133 p++;
1135 p++;
1138 /* Handling unterminated string by UNV */
1139 /*if (type == -1)
1141 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1142 t->text[p-line] = *line;
1143 tail = &t->next;
1145 else */
1146 if (type != TOK_COMMENT) {
1147 *tail = t = new_Token(NULL, type, line, p - line);
1148 tail = &t->next;
1150 line = p;
1152 return list;
1156 * this function allocates a new managed block of memory and
1157 * returns a pointer to the block. The managed blocks are
1158 * deleted only all at once by the delete_Blocks function.
1160 static void *new_Block(size_t size)
1162 Blocks *b = &blocks;
1164 /* first, get to the end of the linked list */
1165 while (b->next)
1166 b = b->next;
1167 /* now allocate the requested chunk */
1168 b->chunk = nasm_malloc(size);
1170 /* now allocate a new block for the next request */
1171 b->next = nasm_zalloc(sizeof(Blocks));
1172 return b->chunk;
1176 * this function deletes all managed blocks of memory
1178 static void delete_Blocks(void)
1180 Blocks *a, *b = &blocks;
1183 * keep in mind that the first block, pointed to by blocks
1184 * is a static and not dynamically allocated, so we don't
1185 * free it.
1187 while (b) {
1188 if (b->chunk)
1189 nasm_free(b->chunk);
1190 a = b;
1191 b = b->next;
1192 if (a != &blocks)
1193 nasm_free(a);
1195 memset(&blocks, 0, sizeof(blocks));
1199 * this function creates a new Token and passes a pointer to it
1200 * back to the caller. It sets the type and text elements, and
1201 * also the a.mac and next elements to NULL.
1203 static Token *new_Token(Token * next, enum pp_token_type type,
1204 const char *text, int txtlen)
1206 Token *t;
1207 int i;
1209 if (!freeTokens) {
1210 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1211 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1212 freeTokens[i].next = &freeTokens[i + 1];
1213 freeTokens[i].next = NULL;
1215 t = freeTokens;
1216 freeTokens = t->next;
1217 t->next = next;
1218 t->a.mac = NULL;
1219 t->type = type;
1220 if (type == TOK_WHITESPACE || !text) {
1221 t->text = NULL;
1222 } else {
1223 if (txtlen == 0)
1224 txtlen = strlen(text);
1225 t->text = nasm_malloc(txtlen+1);
1226 memcpy(t->text, text, txtlen);
1227 t->text[txtlen] = '\0';
1229 return t;
1232 static Token *delete_Token(Token * t)
1234 Token *next = t->next;
1235 nasm_free(t->text);
1236 t->next = freeTokens;
1237 freeTokens = t;
1238 return next;
1242 * Convert a line of tokens back into text.
1243 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1244 * will be transformed into ..@ctxnum.xxx
1246 static char *detoken(Token * tlist, bool expand_locals)
1248 Token *t;
1249 char *line, *p;
1250 const char *q;
1251 int len = 0;
1253 list_for_each(t, tlist) {
1254 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1255 char *v;
1256 char *q = t->text;
1258 v = t->text + 2;
1259 if (*v == '\'' || *v == '\"' || *v == '`') {
1260 size_t len = nasm_unquote(v, NULL);
1261 size_t clen = strlen(v);
1263 if (len != clen) {
1264 nasm_error(ERR_NONFATAL | ERR_PASS1,
1265 "NUL character in %%! string");
1266 v = NULL;
1270 if (v) {
1271 char *p = getenv(v);
1272 if (!p) {
1273 nasm_error(ERR_NONFATAL | ERR_PASS1,
1274 "nonexistent environment variable `%s'", v);
1276 * FIXME We better should investigate if accessing
1277 * ->text[1] without ->text[0] is safe enough.
1279 t->text = nasm_zalloc(2);
1280 } else
1281 t->text = nasm_strdup(p);
1283 nasm_free(q);
1286 /* Expand local macros here and not during preprocessing */
1287 if (expand_locals &&
1288 t->type == TOK_PREPROC_ID && t->text &&
1289 t->text[0] == '%' && t->text[1] == '$') {
1290 const char *q;
1291 char *p;
1292 Context *ctx = get_ctx(t->text, &q);
1293 if (ctx) {
1294 char buffer[40];
1295 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1296 p = nasm_strcat(buffer, q);
1297 nasm_free(t->text);
1298 t->text = p;
1301 if (t->type == TOK_WHITESPACE)
1302 len++;
1303 else if (t->text)
1304 len += strlen(t->text);
1307 p = line = nasm_malloc(len + 1);
1309 list_for_each(t, tlist) {
1310 if (t->type == TOK_WHITESPACE) {
1311 *p++ = ' ';
1312 } else if (t->text) {
1313 q = t->text;
1314 while (*q)
1315 *p++ = *q++;
1318 *p = '\0';
1320 return line;
1324 * A scanner, suitable for use by the expression evaluator, which
1325 * operates on a line of Tokens. Expects a pointer to a pointer to
1326 * the first token in the line to be passed in as its private_data
1327 * field.
1329 * FIX: This really needs to be unified with stdscan.
1331 static int ppscan(void *private_data, struct tokenval *tokval)
1333 Token **tlineptr = private_data;
1334 Token *tline;
1335 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1337 do {
1338 tline = *tlineptr;
1339 *tlineptr = tline ? tline->next : NULL;
1340 } while (tline && (tline->type == TOK_WHITESPACE ||
1341 tline->type == TOK_COMMENT));
1343 if (!tline)
1344 return tokval->t_type = TOKEN_EOS;
1346 tokval->t_charptr = tline->text;
1348 if (tline->text[0] == '$' && !tline->text[1])
1349 return tokval->t_type = TOKEN_HERE;
1350 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1351 return tokval->t_type = TOKEN_BASE;
1353 if (tline->type == TOK_ID) {
1354 p = tokval->t_charptr = tline->text;
1355 if (p[0] == '$') {
1356 tokval->t_charptr++;
1357 return tokval->t_type = TOKEN_ID;
1360 for (r = p, s = ourcopy; *r; r++) {
1361 if (r >= p+MAX_KEYWORD)
1362 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1363 *s++ = nasm_tolower(*r);
1365 *s = '\0';
1366 /* right, so we have an identifier sitting in temp storage. now,
1367 * is it actually a register or instruction name, or what? */
1368 return nasm_token_hash(ourcopy, tokval);
1371 if (tline->type == TOK_NUMBER) {
1372 bool rn_error;
1373 tokval->t_integer = readnum(tline->text, &rn_error);
1374 tokval->t_charptr = tline->text;
1375 if (rn_error)
1376 return tokval->t_type = TOKEN_ERRNUM;
1377 else
1378 return tokval->t_type = TOKEN_NUM;
1381 if (tline->type == TOK_FLOAT) {
1382 return tokval->t_type = TOKEN_FLOAT;
1385 if (tline->type == TOK_STRING) {
1386 char bq, *ep;
1388 bq = tline->text[0];
1389 tokval->t_charptr = tline->text;
1390 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1392 if (ep[0] != bq || ep[1] != '\0')
1393 return tokval->t_type = TOKEN_ERRSTR;
1394 else
1395 return tokval->t_type = TOKEN_STR;
1398 if (tline->type == TOK_OTHER) {
1399 if (!strcmp(tline->text, "<<"))
1400 return tokval->t_type = TOKEN_SHL;
1401 if (!strcmp(tline->text, ">>"))
1402 return tokval->t_type = TOKEN_SHR;
1403 if (!strcmp(tline->text, "//"))
1404 return tokval->t_type = TOKEN_SDIV;
1405 if (!strcmp(tline->text, "%%"))
1406 return tokval->t_type = TOKEN_SMOD;
1407 if (!strcmp(tline->text, "=="))
1408 return tokval->t_type = TOKEN_EQ;
1409 if (!strcmp(tline->text, "<>"))
1410 return tokval->t_type = TOKEN_NE;
1411 if (!strcmp(tline->text, "!="))
1412 return tokval->t_type = TOKEN_NE;
1413 if (!strcmp(tline->text, "<="))
1414 return tokval->t_type = TOKEN_LE;
1415 if (!strcmp(tline->text, ">="))
1416 return tokval->t_type = TOKEN_GE;
1417 if (!strcmp(tline->text, "&&"))
1418 return tokval->t_type = TOKEN_DBL_AND;
1419 if (!strcmp(tline->text, "^^"))
1420 return tokval->t_type = TOKEN_DBL_XOR;
1421 if (!strcmp(tline->text, "||"))
1422 return tokval->t_type = TOKEN_DBL_OR;
1426 * We have no other options: just return the first character of
1427 * the token text.
1429 return tokval->t_type = tline->text[0];
1433 * Compare a string to the name of an existing macro; this is a
1434 * simple wrapper which calls either strcmp or nasm_stricmp
1435 * depending on the value of the `casesense' parameter.
1437 static int mstrcmp(const char *p, const char *q, bool casesense)
1439 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1443 * Compare a string to the name of an existing macro; this is a
1444 * simple wrapper which calls either strcmp or nasm_stricmp
1445 * depending on the value of the `casesense' parameter.
1447 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1449 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1453 * Return the Context structure associated with a %$ token. Return
1454 * NULL, having _already_ reported an error condition, if the
1455 * context stack isn't deep enough for the supplied number of $
1456 * signs.
1458 * If "namep" is non-NULL, set it to the pointer to the macro name
1459 * tail, i.e. the part beyond %$...
1461 static Context *get_ctx(const char *name, const char **namep)
1463 Context *ctx;
1464 int i;
1466 if (namep)
1467 *namep = name;
1469 if (!name || name[0] != '%' || name[1] != '$')
1470 return NULL;
1472 if (!cstk) {
1473 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1474 return NULL;
1477 name += 2;
1478 ctx = cstk;
1479 i = 0;
1480 while (ctx && *name == '$') {
1481 name++;
1482 i++;
1483 ctx = ctx->next;
1485 if (!ctx) {
1486 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1487 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1488 return NULL;
1491 if (namep)
1492 *namep = name;
1494 return ctx;
1498 * Open an include file. This routine must always return a valid
1499 * file pointer if it returns - it's responsible for throwing an
1500 * ERR_FATAL and bombing out completely if not. It should also try
1501 * the include path one by one until it finds the file or reaches
1502 * the end of the path.
1504 * Note: for INC_PROBE the function returns NULL at all times;
1505 * instead look for the
1507 enum incopen_mode {
1508 INC_NEEDED, /* File must exist */
1509 INC_OPTIONAL, /* Missing is OK */
1510 INC_PROBE /* Only an existence probe */
1513 /* This is conducts a full pathname search */
1514 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1515 enum incopen_mode omode, enum file_flags fmode)
1517 FILE *fp;
1518 char *prefix = "";
1519 const IncPath *ip = ipath;
1520 int len = strlen(file);
1521 size_t prefix_len = 0;
1522 StrList *sl;
1523 size_t path_len;
1524 bool found;
1526 while (1) {
1527 path_len = prefix_len + len + 1;
1529 sl = nasm_malloc(path_len + sizeof sl->next);
1530 memcpy(sl->str, prefix, prefix_len);
1531 memcpy(sl->str+prefix_len, file, len+1);
1532 sl->next = NULL;
1534 if (omode == INC_PROBE) {
1535 fp = NULL;
1536 found = nasm_file_exists(sl->str);
1537 } else {
1538 fp = nasm_open_read(sl->str, fmode);
1539 found = (fp != NULL);
1541 if (found) {
1542 *slpath = sl;
1543 return fp;
1546 nasm_free(sl);
1548 if (!ip)
1549 return NULL;
1551 prefix = ip->path;
1552 prefix_len = strlen(prefix);
1553 ip = ip->next;
1558 * Open a file, or test for the presence of one (depending on omode),
1559 * considering the include path.
1561 static FILE *inc_fopen(const char *file,
1562 StrList **dhead,
1563 const char **found_path,
1564 enum incopen_mode omode,
1565 enum file_flags fmode)
1567 StrList *sl;
1568 struct hash_insert hi;
1569 void **hp;
1570 char *path;
1571 FILE *fp = NULL;
1573 hp = hash_find(&FileHash, file, &hi);
1574 if (hp) {
1575 path = *hp;
1576 } else {
1577 /* Need to do the actual path search */
1578 size_t file_len;
1580 sl = NULL;
1581 fp = inc_fopen_search(file, &sl, omode, fmode);
1583 file_len = strlen(file);
1585 if (!sl) {
1586 /* Store negative result for this file */
1587 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1588 memcpy(sl->str, file, file_len+1);
1589 sl->next = NULL;
1590 file = sl->str;
1591 path = NULL;
1592 } else {
1593 path = sl->str;
1594 file = strchr(path, '\0') - file_len;
1597 hash_add(&hi, file, path); /* Positive or negative result */
1600 * Add file to dependency path. The in_list() is needed
1601 * in case the file was already added with %depend.
1603 if (path || omode != INC_NEEDED)
1604 nasm_add_to_strlist(dhead, sl);
1607 if (!path) {
1608 if (omode == INC_NEEDED)
1609 nasm_fatal(0, "unable to open include file `%s'", file);
1611 if (found_path)
1612 *found_path = NULL;
1614 return NULL;
1617 if (!fp && omode != INC_PROBE)
1618 fp = nasm_open_read(path, fmode);
1620 if (found_path)
1621 *found_path = path;
1623 return fp;
1627 * Opens an include or input file. Public version, for use by modules
1628 * that get a file:lineno pair and need to look at the file again
1629 * (e.g. the CodeView debug backend). Returns NULL on failure.
1631 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1633 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1637 * Determine if we should warn on defining a single-line macro of
1638 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1639 * return true if _any_ single-line macro of that name is defined.
1640 * Otherwise, will return true if a single-line macro with either
1641 * `nparam' or no parameters is defined.
1643 * If a macro with precisely the right number of parameters is
1644 * defined, or nparam is -1, the address of the definition structure
1645 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1646 * is NULL, no action will be taken regarding its contents, and no
1647 * error will occur.
1649 * Note that this is also called with nparam zero to resolve
1650 * `ifdef'.
1652 * If you already know which context macro belongs to, you can pass
1653 * the context pointer as first parameter; if you won't but name begins
1654 * with %$ the context will be automatically computed. If all_contexts
1655 * is true, macro will be searched in outer contexts as well.
1657 static bool
1658 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1659 bool nocase)
1661 struct hash_table *smtbl;
1662 SMacro *m;
1664 if (ctx) {
1665 smtbl = &ctx->localmac;
1666 } else if (name[0] == '%' && name[1] == '$') {
1667 if (cstk)
1668 ctx = get_ctx(name, &name);
1669 if (!ctx)
1670 return false; /* got to return _something_ */
1671 smtbl = &ctx->localmac;
1672 } else {
1673 smtbl = &smacros;
1675 m = (SMacro *) hash_findix(smtbl, name);
1677 while (m) {
1678 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1679 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1680 if (defn) {
1681 if (nparam == (int) m->nparam || nparam == -1)
1682 *defn = m;
1683 else
1684 *defn = NULL;
1686 return true;
1688 m = m->next;
1691 return false;
1695 * Count and mark off the parameters in a multi-line macro call.
1696 * This is called both from within the multi-line macro expansion
1697 * code, and also to mark off the default parameters when provided
1698 * in a %macro definition line.
1700 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1702 int paramsize, brace;
1704 *nparam = paramsize = 0;
1705 *params = NULL;
1706 while (t) {
1707 /* +1: we need space for the final NULL */
1708 if (*nparam+1 >= paramsize) {
1709 paramsize += PARAM_DELTA;
1710 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1712 skip_white_(t);
1713 brace = 0;
1714 if (tok_is_(t, "{"))
1715 brace++;
1716 (*params)[(*nparam)++] = t;
1717 if (brace) {
1718 while (brace && (t = t->next) != NULL) {
1719 if (tok_is_(t, "{"))
1720 brace++;
1721 else if (tok_is_(t, "}"))
1722 brace--;
1725 if (t) {
1727 * Now we've found the closing brace, look further
1728 * for the comma.
1730 t = t->next;
1731 skip_white_(t);
1732 if (tok_isnt_(t, ",")) {
1733 nasm_error(ERR_NONFATAL,
1734 "braces do not enclose all of macro parameter");
1735 while (tok_isnt_(t, ","))
1736 t = t->next;
1739 } else {
1740 while (tok_isnt_(t, ","))
1741 t = t->next;
1743 if (t) { /* got a comma/brace */
1744 t = t->next; /* eat the comma */
1750 * Determine whether one of the various `if' conditions is true or
1751 * not.
1753 * We must free the tline we get passed.
1755 static bool if_condition(Token * tline, enum preproc_token ct)
1757 enum pp_conditional i = PP_COND(ct);
1758 bool j;
1759 Token *t, *tt, **tptr, *origline;
1760 struct tokenval tokval;
1761 expr *evalresult;
1762 enum pp_token_type needtype;
1763 char *p;
1765 origline = tline;
1767 switch (i) {
1768 case PPC_IFCTX:
1769 j = false; /* have we matched yet? */
1770 while (true) {
1771 skip_white_(tline);
1772 if (!tline)
1773 break;
1774 if (tline->type != TOK_ID) {
1775 nasm_error(ERR_NONFATAL,
1776 "`%s' expects context identifiers", pp_directives[ct]);
1777 free_tlist(origline);
1778 return -1;
1780 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1781 j = true;
1782 tline = tline->next;
1784 break;
1786 case PPC_IFDEF:
1787 j = false; /* have we matched yet? */
1788 while (tline) {
1789 skip_white_(tline);
1790 if (!tline || (tline->type != TOK_ID &&
1791 (tline->type != TOK_PREPROC_ID ||
1792 tline->text[1] != '$'))) {
1793 nasm_error(ERR_NONFATAL,
1794 "`%s' expects macro identifiers", pp_directives[ct]);
1795 goto fail;
1797 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1798 j = true;
1799 tline = tline->next;
1801 break;
1803 case PPC_IFENV:
1804 tline = expand_smacro(tline);
1805 j = false; /* have we matched yet? */
1806 while (tline) {
1807 skip_white_(tline);
1808 if (!tline || (tline->type != TOK_ID &&
1809 tline->type != TOK_STRING &&
1810 (tline->type != TOK_PREPROC_ID ||
1811 tline->text[1] != '!'))) {
1812 nasm_error(ERR_NONFATAL,
1813 "`%s' expects environment variable names",
1814 pp_directives[ct]);
1815 goto fail;
1817 p = tline->text;
1818 if (tline->type == TOK_PREPROC_ID)
1819 p += 2; /* Skip leading %! */
1820 if (*p == '\'' || *p == '\"' || *p == '`')
1821 nasm_unquote_cstr(p, ct);
1822 if (getenv(p))
1823 j = true;
1824 tline = tline->next;
1826 break;
1828 case PPC_IFIDN:
1829 case PPC_IFIDNI:
1830 tline = expand_smacro(tline);
1831 t = tt = tline;
1832 while (tok_isnt_(tt, ","))
1833 tt = tt->next;
1834 if (!tt) {
1835 nasm_error(ERR_NONFATAL,
1836 "`%s' expects two comma-separated arguments",
1837 pp_directives[ct]);
1838 goto fail;
1840 tt = tt->next;
1841 j = true; /* assume equality unless proved not */
1842 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1843 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1844 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1845 pp_directives[ct]);
1846 goto fail;
1848 if (t->type == TOK_WHITESPACE) {
1849 t = t->next;
1850 continue;
1852 if (tt->type == TOK_WHITESPACE) {
1853 tt = tt->next;
1854 continue;
1856 if (tt->type != t->type) {
1857 j = false; /* found mismatching tokens */
1858 break;
1860 /* When comparing strings, need to unquote them first */
1861 if (t->type == TOK_STRING) {
1862 size_t l1 = nasm_unquote(t->text, NULL);
1863 size_t l2 = nasm_unquote(tt->text, NULL);
1865 if (l1 != l2) {
1866 j = false;
1867 break;
1869 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1870 j = false;
1871 break;
1873 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1874 j = false; /* found mismatching tokens */
1875 break;
1878 t = t->next;
1879 tt = tt->next;
1881 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1882 j = false; /* trailing gunk on one end or other */
1883 break;
1885 case PPC_IFMACRO:
1887 bool found = false;
1888 MMacro searching, *mmac;
1890 skip_white_(tline);
1891 tline = expand_id(tline);
1892 if (!tok_type_(tline, TOK_ID)) {
1893 nasm_error(ERR_NONFATAL,
1894 "`%s' expects a macro name", pp_directives[ct]);
1895 goto fail;
1897 searching.name = nasm_strdup(tline->text);
1898 searching.casesense = true;
1899 searching.plus = false;
1900 searching.nolist = false;
1901 searching.in_progress = 0;
1902 searching.max_depth = 0;
1903 searching.rep_nest = NULL;
1904 searching.nparam_min = 0;
1905 searching.nparam_max = INT_MAX;
1906 tline = expand_smacro(tline->next);
1907 skip_white_(tline);
1908 if (!tline) {
1909 } else if (!tok_type_(tline, TOK_NUMBER)) {
1910 nasm_error(ERR_NONFATAL,
1911 "`%s' expects a parameter count or nothing",
1912 pp_directives[ct]);
1913 } else {
1914 searching.nparam_min = searching.nparam_max =
1915 readnum(tline->text, &j);
1916 if (j)
1917 nasm_error(ERR_NONFATAL,
1918 "unable to parse parameter count `%s'",
1919 tline->text);
1921 if (tline && tok_is_(tline->next, "-")) {
1922 tline = tline->next->next;
1923 if (tok_is_(tline, "*"))
1924 searching.nparam_max = INT_MAX;
1925 else if (!tok_type_(tline, TOK_NUMBER))
1926 nasm_error(ERR_NONFATAL,
1927 "`%s' expects a parameter count after `-'",
1928 pp_directives[ct]);
1929 else {
1930 searching.nparam_max = readnum(tline->text, &j);
1931 if (j)
1932 nasm_error(ERR_NONFATAL,
1933 "unable to parse parameter count `%s'",
1934 tline->text);
1935 if (searching.nparam_min > searching.nparam_max)
1936 nasm_error(ERR_NONFATAL,
1937 "minimum parameter count exceeds maximum");
1940 if (tline && tok_is_(tline->next, "+")) {
1941 tline = tline->next;
1942 searching.plus = true;
1944 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1945 while (mmac) {
1946 if (!strcmp(mmac->name, searching.name) &&
1947 (mmac->nparam_min <= searching.nparam_max
1948 || searching.plus)
1949 && (searching.nparam_min <= mmac->nparam_max
1950 || mmac->plus)) {
1951 found = true;
1952 break;
1954 mmac = mmac->next;
1956 if (tline && tline->next)
1957 nasm_error(ERR_WARNING|ERR_PASS1,
1958 "trailing garbage after %%ifmacro ignored");
1959 nasm_free(searching.name);
1960 j = found;
1961 break;
1964 case PPC_IFID:
1965 needtype = TOK_ID;
1966 goto iftype;
1967 case PPC_IFNUM:
1968 needtype = TOK_NUMBER;
1969 goto iftype;
1970 case PPC_IFSTR:
1971 needtype = TOK_STRING;
1972 goto iftype;
1974 iftype:
1975 t = tline = expand_smacro(tline);
1977 while (tok_type_(t, TOK_WHITESPACE) ||
1978 (needtype == TOK_NUMBER &&
1979 tok_type_(t, TOK_OTHER) &&
1980 (t->text[0] == '-' || t->text[0] == '+') &&
1981 !t->text[1]))
1982 t = t->next;
1984 j = tok_type_(t, needtype);
1985 break;
1987 case PPC_IFTOKEN:
1988 t = tline = expand_smacro(tline);
1989 while (tok_type_(t, TOK_WHITESPACE))
1990 t = t->next;
1992 j = false;
1993 if (t) {
1994 t = t->next; /* Skip the actual token */
1995 while (tok_type_(t, TOK_WHITESPACE))
1996 t = t->next;
1997 j = !t; /* Should be nothing left */
1999 break;
2001 case PPC_IFEMPTY:
2002 t = tline = expand_smacro(tline);
2003 while (tok_type_(t, TOK_WHITESPACE))
2004 t = t->next;
2006 j = !t; /* Should be empty */
2007 break;
2009 case PPC_IF:
2010 t = tline = expand_smacro(tline);
2011 tptr = &t;
2012 tokval.t_type = TOKEN_INVALID;
2013 evalresult = evaluate(ppscan, tptr, &tokval,
2014 NULL, pass | CRITICAL, NULL);
2015 if (!evalresult)
2016 return -1;
2017 if (tokval.t_type)
2018 nasm_error(ERR_WARNING|ERR_PASS1,
2019 "trailing garbage after expression ignored");
2020 if (!is_simple(evalresult)) {
2021 nasm_error(ERR_NONFATAL,
2022 "non-constant value given to `%s'", pp_directives[ct]);
2023 goto fail;
2025 j = reloc_value(evalresult) != 0;
2026 break;
2028 default:
2029 nasm_error(ERR_FATAL,
2030 "preprocessor directive `%s' not yet implemented",
2031 pp_directives[ct]);
2032 goto fail;
2035 free_tlist(origline);
2036 return j ^ PP_NEGATIVE(ct);
2038 fail:
2039 free_tlist(origline);
2040 return -1;
2044 * Common code for defining an smacro
2046 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2047 int nparam, Token *expansion)
2049 SMacro *smac, **smhead;
2050 struct hash_table *smtbl;
2052 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2053 if (!smac) {
2054 nasm_error(ERR_WARNING|ERR_PASS1,
2055 "single-line macro `%s' defined both with and"
2056 " without parameters", mname);
2058 * Some instances of the old code considered this a failure,
2059 * some others didn't. What is the right thing to do here?
2061 free_tlist(expansion);
2062 return false; /* Failure */
2063 } else {
2065 * We're redefining, so we have to take over an
2066 * existing SMacro structure. This means freeing
2067 * what was already in it.
2069 nasm_free(smac->name);
2070 free_tlist(smac->expansion);
2072 } else {
2073 smtbl = ctx ? &ctx->localmac : &smacros;
2074 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2075 smac = nasm_malloc(sizeof(SMacro));
2076 smac->next = *smhead;
2077 *smhead = smac;
2079 smac->name = nasm_strdup(mname);
2080 smac->casesense = casesense;
2081 smac->nparam = nparam;
2082 smac->expansion = expansion;
2083 smac->in_progress = false;
2084 return true; /* Success */
2088 * Undefine an smacro
2090 static void undef_smacro(Context *ctx, const char *mname)
2092 SMacro **smhead, *s, **sp;
2093 struct hash_table *smtbl;
2095 smtbl = ctx ? &ctx->localmac : &smacros;
2096 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2098 if (smhead) {
2100 * We now have a macro name... go hunt for it.
2102 sp = smhead;
2103 while ((s = *sp) != NULL) {
2104 if (!mstrcmp(s->name, mname, s->casesense)) {
2105 *sp = s->next;
2106 nasm_free(s->name);
2107 free_tlist(s->expansion);
2108 nasm_free(s);
2109 } else {
2110 sp = &s->next;
2117 * Parse a mmacro specification.
2119 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2121 bool err;
2123 tline = tline->next;
2124 skip_white_(tline);
2125 tline = expand_id(tline);
2126 if (!tok_type_(tline, TOK_ID)) {
2127 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2128 return false;
2131 def->prev = NULL;
2132 def->name = nasm_strdup(tline->text);
2133 def->plus = false;
2134 def->nolist = false;
2135 def->in_progress = 0;
2136 def->rep_nest = NULL;
2137 def->nparam_min = 0;
2138 def->nparam_max = 0;
2140 tline = expand_smacro(tline->next);
2141 skip_white_(tline);
2142 if (!tok_type_(tline, TOK_NUMBER)) {
2143 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2144 } else {
2145 def->nparam_min = def->nparam_max =
2146 readnum(tline->text, &err);
2147 if (err)
2148 nasm_error(ERR_NONFATAL,
2149 "unable to parse parameter count `%s'", tline->text);
2151 if (tline && tok_is_(tline->next, "-")) {
2152 tline = tline->next->next;
2153 if (tok_is_(tline, "*")) {
2154 def->nparam_max = INT_MAX;
2155 } else if (!tok_type_(tline, TOK_NUMBER)) {
2156 nasm_error(ERR_NONFATAL,
2157 "`%s' expects a parameter count after `-'", directive);
2158 } else {
2159 def->nparam_max = readnum(tline->text, &err);
2160 if (err) {
2161 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2162 tline->text);
2164 if (def->nparam_min > def->nparam_max) {
2165 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2169 if (tline && tok_is_(tline->next, "+")) {
2170 tline = tline->next;
2171 def->plus = true;
2173 if (tline && tok_type_(tline->next, TOK_ID) &&
2174 !nasm_stricmp(tline->next->text, ".nolist")) {
2175 tline = tline->next;
2176 def->nolist = true;
2180 * Handle default parameters.
2182 if (tline && tline->next) {
2183 def->dlist = tline->next;
2184 tline->next = NULL;
2185 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2186 } else {
2187 def->dlist = NULL;
2188 def->defaults = NULL;
2190 def->expansion = NULL;
2192 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2193 !def->plus)
2194 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2195 "too many default macro parameters");
2197 return true;
2202 * Decode a size directive
2204 static int parse_size(const char *str) {
2205 static const char *size_names[] =
2206 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2207 static const int sizes[] =
2208 { 0, 1, 4, 16, 8, 10, 2, 32 };
2210 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2214 * Process a preprocessor %pragma directive. Currently there are none.
2215 * Gets passed the token list starting with the "preproc" token from
2216 * "%pragma preproc".
2218 static void do_pragma_preproc(Token *tline)
2220 /* Skip to the real stuff */
2221 tline = tline->next;
2222 skip_white_(tline);
2223 if (!tline)
2224 return;
2226 (void)tline; /* Nothing else to do at present */
2230 * find and process preprocessor directive in passed line
2231 * Find out if a line contains a preprocessor directive, and deal
2232 * with it if so.
2234 * If a directive _is_ found, it is the responsibility of this routine
2235 * (and not the caller) to free_tlist() the line.
2237 * @param tline a pointer to the current tokeninzed line linked list
2238 * @param output if this directive generated output
2239 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2242 static int do_directive(Token *tline, char **output)
2244 enum preproc_token i;
2245 int j;
2246 bool err;
2247 int nparam;
2248 bool nolist;
2249 bool casesense;
2250 int k, m;
2251 int offset;
2252 char *p, *pp;
2253 const char *found_path;
2254 const char *mname;
2255 Include *inc;
2256 Context *ctx;
2257 Cond *cond;
2258 MMacro *mmac, **mmhead;
2259 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2260 Line *l;
2261 struct tokenval tokval;
2262 expr *evalresult;
2263 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2264 int64_t count;
2265 size_t len;
2266 int severity;
2268 *output = NULL; /* No output generated */
2269 origline = tline;
2271 skip_white_(tline);
2272 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2273 (tline->text[1] == '%' || tline->text[1] == '$'
2274 || tline->text[1] == '!'))
2275 return NO_DIRECTIVE_FOUND;
2277 i = pp_token_hash(tline->text);
2280 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2281 * since they are known to be buggy at moment, we need to fix them
2282 * in future release (2.09-2.10)
2284 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2285 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2286 tline->text);
2287 return NO_DIRECTIVE_FOUND;
2291 * If we're in a non-emitting branch of a condition construct,
2292 * or walking to the end of an already terminated %rep block,
2293 * we should ignore all directives except for condition
2294 * directives.
2296 if (((istk->conds && !emitting(istk->conds->state)) ||
2297 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2298 return NO_DIRECTIVE_FOUND;
2302 * If we're defining a macro or reading a %rep block, we should
2303 * ignore all directives except for %macro/%imacro (which nest),
2304 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2305 * If we're in a %rep block, another %rep nests, so should be let through.
2307 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2308 i != PP_RMACRO && i != PP_IRMACRO &&
2309 i != PP_ENDMACRO && i != PP_ENDM &&
2310 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2311 return NO_DIRECTIVE_FOUND;
2314 if (defining) {
2315 if (i == PP_MACRO || i == PP_IMACRO ||
2316 i == PP_RMACRO || i == PP_IRMACRO) {
2317 nested_mac_count++;
2318 return NO_DIRECTIVE_FOUND;
2319 } else if (nested_mac_count > 0) {
2320 if (i == PP_ENDMACRO) {
2321 nested_mac_count--;
2322 return NO_DIRECTIVE_FOUND;
2325 if (!defining->name) {
2326 if (i == PP_REP) {
2327 nested_rep_count++;
2328 return NO_DIRECTIVE_FOUND;
2329 } else if (nested_rep_count > 0) {
2330 if (i == PP_ENDREP) {
2331 nested_rep_count--;
2332 return NO_DIRECTIVE_FOUND;
2338 switch (i) {
2339 case PP_INVALID:
2340 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2341 tline->text);
2342 return NO_DIRECTIVE_FOUND; /* didn't get it */
2344 case PP_PRAGMA:
2346 * %pragma namespace options...
2348 * The namespace "preproc" is reserved for the preprocessor;
2349 * all other namespaces generate a [pragma] assembly directive.
2351 * Invalid %pragmas are ignored and may have different
2352 * meaning in future versions of NASM.
2354 tline = tline->next;
2355 skip_white_(tline);
2356 tline = expand_smacro(tline);
2357 if (tok_type_(tline, TOK_ID)) {
2358 if (!nasm_stricmp(tline->text, "preproc")) {
2359 /* Preprocessor pragma */
2360 do_pragma_preproc(tline);
2361 } else {
2362 /* Build the assembler directive */
2363 t = new_Token(NULL, TOK_OTHER, "[", 1);
2364 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2365 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2366 tline = t;
2367 for (t = tline; t->next; t = t->next)
2369 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2370 /* true here can be revisited in the future */
2371 *output = detoken(tline, true);
2374 free_tlist(origline);
2375 return DIRECTIVE_FOUND;
2377 case PP_STACKSIZE:
2378 /* Directive to tell NASM what the default stack size is. The
2379 * default is for a 16-bit stack, and this can be overriden with
2380 * %stacksize large.
2382 tline = tline->next;
2383 if (tline && tline->type == TOK_WHITESPACE)
2384 tline = tline->next;
2385 if (!tline || tline->type != TOK_ID) {
2386 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2387 free_tlist(origline);
2388 return DIRECTIVE_FOUND;
2390 if (nasm_stricmp(tline->text, "flat") == 0) {
2391 /* All subsequent ARG directives are for a 32-bit stack */
2392 StackSize = 4;
2393 StackPointer = "ebp";
2394 ArgOffset = 8;
2395 LocalOffset = 0;
2396 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2397 /* All subsequent ARG directives are for a 64-bit stack */
2398 StackSize = 8;
2399 StackPointer = "rbp";
2400 ArgOffset = 16;
2401 LocalOffset = 0;
2402 } else if (nasm_stricmp(tline->text, "large") == 0) {
2403 /* All subsequent ARG directives are for a 16-bit stack,
2404 * far function call.
2406 StackSize = 2;
2407 StackPointer = "bp";
2408 ArgOffset = 4;
2409 LocalOffset = 0;
2410 } else if (nasm_stricmp(tline->text, "small") == 0) {
2411 /* All subsequent ARG directives are for a 16-bit stack,
2412 * far function call. We don't support near functions.
2414 StackSize = 2;
2415 StackPointer = "bp";
2416 ArgOffset = 6;
2417 LocalOffset = 0;
2418 } else {
2419 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2420 free_tlist(origline);
2421 return DIRECTIVE_FOUND;
2423 free_tlist(origline);
2424 return DIRECTIVE_FOUND;
2426 case PP_ARG:
2427 /* TASM like ARG directive to define arguments to functions, in
2428 * the following form:
2430 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2432 offset = ArgOffset;
2433 do {
2434 char *arg, directive[256];
2435 int size = StackSize;
2437 /* Find the argument name */
2438 tline = tline->next;
2439 if (tline && tline->type == TOK_WHITESPACE)
2440 tline = tline->next;
2441 if (!tline || tline->type != TOK_ID) {
2442 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2443 free_tlist(origline);
2444 return DIRECTIVE_FOUND;
2446 arg = tline->text;
2448 /* Find the argument size type */
2449 tline = tline->next;
2450 if (!tline || tline->type != TOK_OTHER
2451 || tline->text[0] != ':') {
2452 nasm_error(ERR_NONFATAL,
2453 "Syntax error processing `%%arg' directive");
2454 free_tlist(origline);
2455 return DIRECTIVE_FOUND;
2457 tline = tline->next;
2458 if (!tline || tline->type != TOK_ID) {
2459 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2460 free_tlist(origline);
2461 return DIRECTIVE_FOUND;
2464 /* Allow macro expansion of type parameter */
2465 tt = tokenize(tline->text);
2466 tt = expand_smacro(tt);
2467 size = parse_size(tt->text);
2468 if (!size) {
2469 nasm_error(ERR_NONFATAL,
2470 "Invalid size type for `%%arg' missing directive");
2471 free_tlist(tt);
2472 free_tlist(origline);
2473 return DIRECTIVE_FOUND;
2475 free_tlist(tt);
2477 /* Round up to even stack slots */
2478 size = ALIGN(size, StackSize);
2480 /* Now define the macro for the argument */
2481 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2482 arg, StackPointer, offset);
2483 do_directive(tokenize(directive), output);
2484 offset += size;
2486 /* Move to the next argument in the list */
2487 tline = tline->next;
2488 if (tline && tline->type == TOK_WHITESPACE)
2489 tline = tline->next;
2490 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2491 ArgOffset = offset;
2492 free_tlist(origline);
2493 return DIRECTIVE_FOUND;
2495 case PP_LOCAL:
2496 /* TASM like LOCAL directive to define local variables for a
2497 * function, in the following form:
2499 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2501 * The '= LocalSize' at the end is ignored by NASM, but is
2502 * required by TASM to define the local parameter size (and used
2503 * by the TASM macro package).
2505 offset = LocalOffset;
2506 do {
2507 char *local, directive[256];
2508 int size = StackSize;
2510 /* Find the argument name */
2511 tline = tline->next;
2512 if (tline && tline->type == TOK_WHITESPACE)
2513 tline = tline->next;
2514 if (!tline || tline->type != TOK_ID) {
2515 nasm_error(ERR_NONFATAL,
2516 "`%%local' missing argument parameter");
2517 free_tlist(origline);
2518 return DIRECTIVE_FOUND;
2520 local = tline->text;
2522 /* Find the argument size type */
2523 tline = tline->next;
2524 if (!tline || tline->type != TOK_OTHER
2525 || tline->text[0] != ':') {
2526 nasm_error(ERR_NONFATAL,
2527 "Syntax error processing `%%local' directive");
2528 free_tlist(origline);
2529 return DIRECTIVE_FOUND;
2531 tline = tline->next;
2532 if (!tline || tline->type != TOK_ID) {
2533 nasm_error(ERR_NONFATAL,
2534 "`%%local' missing size type parameter");
2535 free_tlist(origline);
2536 return DIRECTIVE_FOUND;
2539 /* Allow macro expansion of type parameter */
2540 tt = tokenize(tline->text);
2541 tt = expand_smacro(tt);
2542 size = parse_size(tt->text);
2543 if (!size) {
2544 nasm_error(ERR_NONFATAL,
2545 "Invalid size type for `%%local' missing directive");
2546 free_tlist(tt);
2547 free_tlist(origline);
2548 return DIRECTIVE_FOUND;
2550 free_tlist(tt);
2552 /* Round up to even stack slots */
2553 size = ALIGN(size, StackSize);
2555 offset += size; /* Negative offset, increment before */
2557 /* Now define the macro for the argument */
2558 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2559 local, StackPointer, offset);
2560 do_directive(tokenize(directive), output);
2562 /* Now define the assign to setup the enter_c macro correctly */
2563 snprintf(directive, sizeof(directive),
2564 "%%assign %%$localsize %%$localsize+%d", size);
2565 do_directive(tokenize(directive), output);
2567 /* Move to the next argument in the list */
2568 tline = tline->next;
2569 if (tline && tline->type == TOK_WHITESPACE)
2570 tline = tline->next;
2571 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2572 LocalOffset = offset;
2573 free_tlist(origline);
2574 return DIRECTIVE_FOUND;
2576 case PP_CLEAR:
2577 if (tline->next)
2578 nasm_error(ERR_WARNING|ERR_PASS1,
2579 "trailing garbage after `%%clear' ignored");
2580 free_macros();
2581 init_macros();
2582 free_tlist(origline);
2583 return DIRECTIVE_FOUND;
2585 case PP_DEPEND:
2586 t = tline->next = expand_smacro(tline->next);
2587 skip_white_(t);
2588 if (!t || (t->type != TOK_STRING &&
2589 t->type != TOK_INTERNAL_STRING)) {
2590 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2591 free_tlist(origline);
2592 return DIRECTIVE_FOUND; /* but we did _something_ */
2594 if (t->next)
2595 nasm_error(ERR_WARNING|ERR_PASS1,
2596 "trailing garbage after `%%depend' ignored");
2597 p = t->text;
2598 if (t->type != TOK_INTERNAL_STRING)
2599 nasm_unquote_cstr(p, i);
2600 nasm_add_string_to_strlist(dephead, p);
2601 free_tlist(origline);
2602 return DIRECTIVE_FOUND;
2604 case PP_INCLUDE:
2605 t = tline->next = expand_smacro(tline->next);
2606 skip_white_(t);
2608 if (!t || (t->type != TOK_STRING &&
2609 t->type != TOK_INTERNAL_STRING)) {
2610 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2611 free_tlist(origline);
2612 return DIRECTIVE_FOUND; /* but we did _something_ */
2614 if (t->next)
2615 nasm_error(ERR_WARNING|ERR_PASS1,
2616 "trailing garbage after `%%include' ignored");
2617 p = t->text;
2618 if (t->type != TOK_INTERNAL_STRING)
2619 nasm_unquote_cstr(p, i);
2620 inc = nasm_malloc(sizeof(Include));
2621 inc->next = istk;
2622 inc->conds = NULL;
2623 found_path = NULL;
2624 inc->fp = inc_fopen(p, dephead, &found_path,
2625 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2626 if (!inc->fp) {
2627 /* -MG given but file not found */
2628 nasm_free(inc);
2629 } else {
2630 inc->fname = src_set_fname(found_path ? found_path : p);
2631 inc->lineno = src_set_linnum(0);
2632 inc->lineinc = 1;
2633 inc->expansion = NULL;
2634 inc->mstk = NULL;
2635 istk = inc;
2636 lfmt->uplevel(LIST_INCLUDE);
2638 free_tlist(origline);
2639 return DIRECTIVE_FOUND;
2641 case PP_USE:
2643 static macros_t *use_pkg;
2644 const char *pkg_macro = NULL;
2646 tline = tline->next;
2647 skip_white_(tline);
2648 tline = expand_id(tline);
2650 if (!tline || (tline->type != TOK_STRING &&
2651 tline->type != TOK_INTERNAL_STRING &&
2652 tline->type != TOK_ID)) {
2653 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2654 free_tlist(origline);
2655 return DIRECTIVE_FOUND; /* but we did _something_ */
2657 if (tline->next)
2658 nasm_error(ERR_WARNING|ERR_PASS1,
2659 "trailing garbage after `%%use' ignored");
2660 if (tline->type == TOK_STRING)
2661 nasm_unquote_cstr(tline->text, i);
2662 use_pkg = nasm_stdmac_find_package(tline->text);
2663 if (!use_pkg)
2664 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2665 else
2666 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2667 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2668 /* Not already included, go ahead and include it */
2669 stdmacpos = use_pkg;
2671 free_tlist(origline);
2672 return DIRECTIVE_FOUND;
2674 case PP_PUSH:
2675 case PP_REPL:
2676 case PP_POP:
2677 tline = tline->next;
2678 skip_white_(tline);
2679 tline = expand_id(tline);
2680 if (tline) {
2681 if (!tok_type_(tline, TOK_ID)) {
2682 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2683 pp_directives[i]);
2684 free_tlist(origline);
2685 return DIRECTIVE_FOUND; /* but we did _something_ */
2687 if (tline->next)
2688 nasm_error(ERR_WARNING|ERR_PASS1,
2689 "trailing garbage after `%s' ignored",
2690 pp_directives[i]);
2691 p = nasm_strdup(tline->text);
2692 } else {
2693 p = NULL; /* Anonymous */
2696 if (i == PP_PUSH) {
2697 ctx = nasm_malloc(sizeof(Context));
2698 ctx->next = cstk;
2699 hash_init(&ctx->localmac, HASH_SMALL);
2700 ctx->name = p;
2701 ctx->number = unique++;
2702 cstk = ctx;
2703 } else {
2704 /* %pop or %repl */
2705 if (!cstk) {
2706 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2707 pp_directives[i]);
2708 } else if (i == PP_POP) {
2709 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2710 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2711 "expected %s",
2712 cstk->name ? cstk->name : "anonymous", p);
2713 else
2714 ctx_pop();
2715 } else {
2716 /* i == PP_REPL */
2717 nasm_free(cstk->name);
2718 cstk->name = p;
2719 p = NULL;
2721 nasm_free(p);
2723 free_tlist(origline);
2724 return DIRECTIVE_FOUND;
2725 case PP_FATAL:
2726 severity = ERR_FATAL;
2727 goto issue_error;
2728 case PP_ERROR:
2729 severity = ERR_NONFATAL;
2730 goto issue_error;
2731 case PP_WARNING:
2732 severity = ERR_WARNING|ERR_WARN_USER;
2733 goto issue_error;
2735 issue_error:
2737 /* Only error out if this is the final pass */
2738 if (pass != 2 && i != PP_FATAL)
2739 return DIRECTIVE_FOUND;
2741 tline->next = expand_smacro(tline->next);
2742 tline = tline->next;
2743 skip_white_(tline);
2744 t = tline ? tline->next : NULL;
2745 skip_white_(t);
2746 if (tok_type_(tline, TOK_STRING) && !t) {
2747 /* The line contains only a quoted string */
2748 p = tline->text;
2749 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2750 nasm_error(severity, "%s", p);
2751 } else {
2752 /* Not a quoted string, or more than a quoted string */
2753 p = detoken(tline, false);
2754 nasm_error(severity, "%s", p);
2755 nasm_free(p);
2757 free_tlist(origline);
2758 return DIRECTIVE_FOUND;
2761 CASE_PP_IF:
2762 if (istk->conds && !emitting(istk->conds->state))
2763 j = COND_NEVER;
2764 else {
2765 j = if_condition(tline->next, i);
2766 tline->next = NULL; /* it got freed */
2767 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2769 cond = nasm_malloc(sizeof(Cond));
2770 cond->next = istk->conds;
2771 cond->state = j;
2772 istk->conds = cond;
2773 if(istk->mstk)
2774 istk->mstk->condcnt ++;
2775 free_tlist(origline);
2776 return DIRECTIVE_FOUND;
2778 CASE_PP_ELIF:
2779 if (!istk->conds)
2780 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2781 switch(istk->conds->state) {
2782 case COND_IF_TRUE:
2783 istk->conds->state = COND_DONE;
2784 break;
2786 case COND_DONE:
2787 case COND_NEVER:
2788 break;
2790 case COND_ELSE_TRUE:
2791 case COND_ELSE_FALSE:
2792 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2793 "`%%elif' after `%%else' ignored");
2794 istk->conds->state = COND_NEVER;
2795 break;
2797 case COND_IF_FALSE:
2799 * IMPORTANT: In the case of %if, we will already have
2800 * called expand_mmac_params(); however, if we're
2801 * processing an %elif we must have been in a
2802 * non-emitting mode, which would have inhibited
2803 * the normal invocation of expand_mmac_params().
2804 * Therefore, we have to do it explicitly here.
2806 j = if_condition(expand_mmac_params(tline->next), i);
2807 tline->next = NULL; /* it got freed */
2808 istk->conds->state =
2809 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2810 break;
2812 free_tlist(origline);
2813 return DIRECTIVE_FOUND;
2815 case PP_ELSE:
2816 if (tline->next)
2817 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2818 "trailing garbage after `%%else' ignored");
2819 if (!istk->conds)
2820 nasm_fatal(0, "`%%else: no matching `%%if'");
2821 switch(istk->conds->state) {
2822 case COND_IF_TRUE:
2823 case COND_DONE:
2824 istk->conds->state = COND_ELSE_FALSE;
2825 break;
2827 case COND_NEVER:
2828 break;
2830 case COND_IF_FALSE:
2831 istk->conds->state = COND_ELSE_TRUE;
2832 break;
2834 case COND_ELSE_TRUE:
2835 case COND_ELSE_FALSE:
2836 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2837 "`%%else' after `%%else' ignored.");
2838 istk->conds->state = COND_NEVER;
2839 break;
2841 free_tlist(origline);
2842 return DIRECTIVE_FOUND;
2844 case PP_ENDIF:
2845 if (tline->next)
2846 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2847 "trailing garbage after `%%endif' ignored");
2848 if (!istk->conds)
2849 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2850 cond = istk->conds;
2851 istk->conds = cond->next;
2852 nasm_free(cond);
2853 if(istk->mstk)
2854 istk->mstk->condcnt --;
2855 free_tlist(origline);
2856 return DIRECTIVE_FOUND;
2858 case PP_RMACRO:
2859 case PP_IRMACRO:
2860 case PP_MACRO:
2861 case PP_IMACRO:
2862 if (defining) {
2863 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2864 pp_directives[i]);
2865 return DIRECTIVE_FOUND;
2867 defining = nasm_zalloc(sizeof(MMacro));
2868 defining->max_depth =
2869 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2870 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2871 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2872 nasm_free(defining);
2873 defining = NULL;
2874 return DIRECTIVE_FOUND;
2877 src_get(&defining->xline, &defining->fname);
2879 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2880 while (mmac) {
2881 if (!strcmp(mmac->name, defining->name) &&
2882 (mmac->nparam_min <= defining->nparam_max
2883 || defining->plus)
2884 && (defining->nparam_min <= mmac->nparam_max
2885 || mmac->plus)) {
2886 nasm_error(ERR_WARNING|ERR_PASS1,
2887 "redefining multi-line macro `%s'", defining->name);
2888 return DIRECTIVE_FOUND;
2890 mmac = mmac->next;
2892 free_tlist(origline);
2893 return DIRECTIVE_FOUND;
2895 case PP_ENDM:
2896 case PP_ENDMACRO:
2897 if (! (defining && defining->name)) {
2898 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2899 return DIRECTIVE_FOUND;
2901 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2902 defining->next = *mmhead;
2903 *mmhead = defining;
2904 defining = NULL;
2905 free_tlist(origline);
2906 return DIRECTIVE_FOUND;
2908 case PP_EXITMACRO:
2910 * We must search along istk->expansion until we hit a
2911 * macro-end marker for a macro with a name. Then we
2912 * bypass all lines between exitmacro and endmacro.
2914 list_for_each(l, istk->expansion)
2915 if (l->finishes && l->finishes->name)
2916 break;
2918 if (l) {
2920 * Remove all conditional entries relative to this
2921 * macro invocation. (safe to do in this context)
2923 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2924 cond = istk->conds;
2925 istk->conds = cond->next;
2926 nasm_free(cond);
2928 istk->expansion = l;
2929 } else {
2930 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2932 free_tlist(origline);
2933 return DIRECTIVE_FOUND;
2935 case PP_UNMACRO:
2936 case PP_UNIMACRO:
2938 MMacro **mmac_p;
2939 MMacro spec;
2941 spec.casesense = (i == PP_UNMACRO);
2942 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2943 return DIRECTIVE_FOUND;
2945 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2946 while (mmac_p && *mmac_p) {
2947 mmac = *mmac_p;
2948 if (mmac->casesense == spec.casesense &&
2949 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2950 mmac->nparam_min == spec.nparam_min &&
2951 mmac->nparam_max == spec.nparam_max &&
2952 mmac->plus == spec.plus) {
2953 *mmac_p = mmac->next;
2954 free_mmacro(mmac);
2955 } else {
2956 mmac_p = &mmac->next;
2959 free_tlist(origline);
2960 free_tlist(spec.dlist);
2961 return DIRECTIVE_FOUND;
2964 case PP_ROTATE:
2965 if (tline->next && tline->next->type == TOK_WHITESPACE)
2966 tline = tline->next;
2967 if (!tline->next) {
2968 free_tlist(origline);
2969 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2970 return DIRECTIVE_FOUND;
2972 t = expand_smacro(tline->next);
2973 tline->next = NULL;
2974 free_tlist(origline);
2975 tline = t;
2976 tptr = &t;
2977 tokval.t_type = TOKEN_INVALID;
2978 evalresult =
2979 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2980 free_tlist(tline);
2981 if (!evalresult)
2982 return DIRECTIVE_FOUND;
2983 if (tokval.t_type)
2984 nasm_error(ERR_WARNING|ERR_PASS1,
2985 "trailing garbage after expression ignored");
2986 if (!is_simple(evalresult)) {
2987 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2988 return DIRECTIVE_FOUND;
2990 mmac = istk->mstk;
2991 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2992 mmac = mmac->next_active;
2993 if (!mmac) {
2994 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2995 } else if (mmac->nparam == 0) {
2996 nasm_error(ERR_NONFATAL,
2997 "`%%rotate' invoked within macro without parameters");
2998 } else {
2999 int rotate = mmac->rotate + reloc_value(evalresult);
3001 rotate %= (int)mmac->nparam;
3002 if (rotate < 0)
3003 rotate += mmac->nparam;
3005 mmac->rotate = rotate;
3007 return DIRECTIVE_FOUND;
3009 case PP_REP:
3010 nolist = false;
3011 do {
3012 tline = tline->next;
3013 } while (tok_type_(tline, TOK_WHITESPACE));
3015 if (tok_type_(tline, TOK_ID) &&
3016 nasm_stricmp(tline->text, ".nolist") == 0) {
3017 nolist = true;
3018 do {
3019 tline = tline->next;
3020 } while (tok_type_(tline, TOK_WHITESPACE));
3023 if (tline) {
3024 t = expand_smacro(tline);
3025 tptr = &t;
3026 tokval.t_type = TOKEN_INVALID;
3027 evalresult =
3028 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3029 if (!evalresult) {
3030 free_tlist(origline);
3031 return DIRECTIVE_FOUND;
3033 if (tokval.t_type)
3034 nasm_error(ERR_WARNING|ERR_PASS1,
3035 "trailing garbage after expression ignored");
3036 if (!is_simple(evalresult)) {
3037 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3038 return DIRECTIVE_FOUND;
3040 count = reloc_value(evalresult);
3041 if (count >= REP_LIMIT) {
3042 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3043 count = 0;
3044 } else
3045 count++;
3046 } else {
3047 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3048 count = 0;
3050 free_tlist(origline);
3052 tmp_defining = defining;
3053 defining = nasm_malloc(sizeof(MMacro));
3054 defining->prev = NULL;
3055 defining->name = NULL; /* flags this macro as a %rep block */
3056 defining->casesense = false;
3057 defining->plus = false;
3058 defining->nolist = nolist;
3059 defining->in_progress = count;
3060 defining->max_depth = 0;
3061 defining->nparam_min = defining->nparam_max = 0;
3062 defining->defaults = NULL;
3063 defining->dlist = NULL;
3064 defining->expansion = NULL;
3065 defining->next_active = istk->mstk;
3066 defining->rep_nest = tmp_defining;
3067 return DIRECTIVE_FOUND;
3069 case PP_ENDREP:
3070 if (!defining || defining->name) {
3071 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3072 return DIRECTIVE_FOUND;
3076 * Now we have a "macro" defined - although it has no name
3077 * and we won't be entering it in the hash tables - we must
3078 * push a macro-end marker for it on to istk->expansion.
3079 * After that, it will take care of propagating itself (a
3080 * macro-end marker line for a macro which is really a %rep
3081 * block will cause the macro to be re-expanded, complete
3082 * with another macro-end marker to ensure the process
3083 * continues) until the whole expansion is forcibly removed
3084 * from istk->expansion by a %exitrep.
3086 l = nasm_malloc(sizeof(Line));
3087 l->next = istk->expansion;
3088 l->finishes = defining;
3089 l->first = NULL;
3090 istk->expansion = l;
3092 istk->mstk = defining;
3094 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3095 tmp_defining = defining;
3096 defining = defining->rep_nest;
3097 free_tlist(origline);
3098 return DIRECTIVE_FOUND;
3100 case PP_EXITREP:
3102 * We must search along istk->expansion until we hit a
3103 * macro-end marker for a macro with no name. Then we set
3104 * its `in_progress' flag to 0.
3106 list_for_each(l, istk->expansion)
3107 if (l->finishes && !l->finishes->name)
3108 break;
3110 if (l)
3111 l->finishes->in_progress = 1;
3112 else
3113 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3114 free_tlist(origline);
3115 return DIRECTIVE_FOUND;
3117 case PP_XDEFINE:
3118 case PP_IXDEFINE:
3119 case PP_DEFINE:
3120 case PP_IDEFINE:
3121 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3123 tline = tline->next;
3124 skip_white_(tline);
3125 tline = expand_id(tline);
3126 if (!tline || (tline->type != TOK_ID &&
3127 (tline->type != TOK_PREPROC_ID ||
3128 tline->text[1] != '$'))) {
3129 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3130 pp_directives[i]);
3131 free_tlist(origline);
3132 return DIRECTIVE_FOUND;
3135 ctx = get_ctx(tline->text, &mname);
3136 last = tline;
3137 param_start = tline = tline->next;
3138 nparam = 0;
3140 /* Expand the macro definition now for %xdefine and %ixdefine */
3141 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3142 tline = expand_smacro(tline);
3144 if (tok_is_(tline, "(")) {
3146 * This macro has parameters.
3149 tline = tline->next;
3150 while (1) {
3151 skip_white_(tline);
3152 if (!tline) {
3153 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3154 free_tlist(origline);
3155 return DIRECTIVE_FOUND;
3157 if (tline->type != TOK_ID) {
3158 nasm_error(ERR_NONFATAL,
3159 "`%s': parameter identifier expected",
3160 tline->text);
3161 free_tlist(origline);
3162 return DIRECTIVE_FOUND;
3164 tline->type = TOK_SMAC_PARAM + nparam++;
3165 tline = tline->next;
3166 skip_white_(tline);
3167 if (tok_is_(tline, ",")) {
3168 tline = tline->next;
3169 } else {
3170 if (!tok_is_(tline, ")")) {
3171 nasm_error(ERR_NONFATAL,
3172 "`)' expected to terminate macro template");
3173 free_tlist(origline);
3174 return DIRECTIVE_FOUND;
3176 break;
3179 last = tline;
3180 tline = tline->next;
3182 if (tok_type_(tline, TOK_WHITESPACE))
3183 last = tline, tline = tline->next;
3184 macro_start = NULL;
3185 last->next = NULL;
3186 t = tline;
3187 while (t) {
3188 if (t->type == TOK_ID) {
3189 list_for_each(tt, param_start)
3190 if (tt->type >= TOK_SMAC_PARAM &&
3191 !strcmp(tt->text, t->text))
3192 t->type = tt->type;
3194 tt = t->next;
3195 t->next = macro_start;
3196 macro_start = t;
3197 t = tt;
3200 * Good. We now have a macro name, a parameter count, and a
3201 * token list (in reverse order) for an expansion. We ought
3202 * to be OK just to create an SMacro, store it, and let
3203 * free_tlist have the rest of the line (which we have
3204 * carefully re-terminated after chopping off the expansion
3205 * from the end).
3207 define_smacro(ctx, mname, casesense, nparam, macro_start);
3208 free_tlist(origline);
3209 return DIRECTIVE_FOUND;
3211 case PP_UNDEF:
3212 tline = tline->next;
3213 skip_white_(tline);
3214 tline = expand_id(tline);
3215 if (!tline || (tline->type != TOK_ID &&
3216 (tline->type != TOK_PREPROC_ID ||
3217 tline->text[1] != '$'))) {
3218 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3219 free_tlist(origline);
3220 return DIRECTIVE_FOUND;
3222 if (tline->next) {
3223 nasm_error(ERR_WARNING|ERR_PASS1,
3224 "trailing garbage after macro name ignored");
3227 /* Find the context that symbol belongs to */
3228 ctx = get_ctx(tline->text, &mname);
3229 undef_smacro(ctx, mname);
3230 free_tlist(origline);
3231 return DIRECTIVE_FOUND;
3233 case PP_DEFSTR:
3234 case PP_IDEFSTR:
3235 casesense = (i == PP_DEFSTR);
3237 tline = tline->next;
3238 skip_white_(tline);
3239 tline = expand_id(tline);
3240 if (!tline || (tline->type != TOK_ID &&
3241 (tline->type != TOK_PREPROC_ID ||
3242 tline->text[1] != '$'))) {
3243 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3244 pp_directives[i]);
3245 free_tlist(origline);
3246 return DIRECTIVE_FOUND;
3249 ctx = get_ctx(tline->text, &mname);
3250 last = tline;
3251 tline = expand_smacro(tline->next);
3252 last->next = NULL;
3254 while (tok_type_(tline, TOK_WHITESPACE))
3255 tline = delete_Token(tline);
3257 p = detoken(tline, false);
3258 macro_start = nasm_malloc(sizeof(*macro_start));
3259 macro_start->next = NULL;
3260 macro_start->text = nasm_quote(p, strlen(p));
3261 macro_start->type = TOK_STRING;
3262 macro_start->a.mac = NULL;
3263 nasm_free(p);
3266 * We now have a macro name, an implicit parameter count of
3267 * zero, and a string token to use as an expansion. Create
3268 * and store an SMacro.
3270 define_smacro(ctx, mname, casesense, 0, macro_start);
3271 free_tlist(origline);
3272 return DIRECTIVE_FOUND;
3274 case PP_DEFTOK:
3275 case PP_IDEFTOK:
3276 casesense = (i == PP_DEFTOK);
3278 tline = tline->next;
3279 skip_white_(tline);
3280 tline = expand_id(tline);
3281 if (!tline || (tline->type != TOK_ID &&
3282 (tline->type != TOK_PREPROC_ID ||
3283 tline->text[1] != '$'))) {
3284 nasm_error(ERR_NONFATAL,
3285 "`%s' expects a macro identifier as first parameter",
3286 pp_directives[i]);
3287 free_tlist(origline);
3288 return DIRECTIVE_FOUND;
3290 ctx = get_ctx(tline->text, &mname);
3291 last = tline;
3292 tline = expand_smacro(tline->next);
3293 last->next = NULL;
3295 t = tline;
3296 while (tok_type_(t, TOK_WHITESPACE))
3297 t = t->next;
3298 /* t should now point to the string */
3299 if (!tok_type_(t, TOK_STRING)) {
3300 nasm_error(ERR_NONFATAL,
3301 "`%s` requires string as second parameter",
3302 pp_directives[i]);
3303 free_tlist(tline);
3304 free_tlist(origline);
3305 return DIRECTIVE_FOUND;
3309 * Convert the string to a token stream. Note that smacros
3310 * are stored with the token stream reversed, so we have to
3311 * reverse the output of tokenize().
3313 nasm_unquote_cstr(t->text, i);
3314 macro_start = reverse_tokens(tokenize(t->text));
3317 * We now have a macro name, an implicit parameter count of
3318 * zero, and a numeric token to use as an expansion. Create
3319 * and store an SMacro.
3321 define_smacro(ctx, mname, casesense, 0, macro_start);
3322 free_tlist(tline);
3323 free_tlist(origline);
3324 return DIRECTIVE_FOUND;
3326 case PP_PATHSEARCH:
3328 const char *found_path;
3330 casesense = true;
3332 tline = tline->next;
3333 skip_white_(tline);
3334 tline = expand_id(tline);
3335 if (!tline || (tline->type != TOK_ID &&
3336 (tline->type != TOK_PREPROC_ID ||
3337 tline->text[1] != '$'))) {
3338 nasm_error(ERR_NONFATAL,
3339 "`%%pathsearch' expects a macro identifier as first parameter");
3340 free_tlist(origline);
3341 return DIRECTIVE_FOUND;
3343 ctx = get_ctx(tline->text, &mname);
3344 last = tline;
3345 tline = expand_smacro(tline->next);
3346 last->next = NULL;
3348 t = tline;
3349 while (tok_type_(t, TOK_WHITESPACE))
3350 t = t->next;
3352 if (!t || (t->type != TOK_STRING &&
3353 t->type != TOK_INTERNAL_STRING)) {
3354 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3355 free_tlist(tline);
3356 free_tlist(origline);
3357 return DIRECTIVE_FOUND; /* but we did _something_ */
3359 if (t->next)
3360 nasm_error(ERR_WARNING|ERR_PASS1,
3361 "trailing garbage after `%%pathsearch' ignored");
3362 p = t->text;
3363 if (t->type != TOK_INTERNAL_STRING)
3364 nasm_unquote(p, NULL);
3366 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3367 if (!found_path)
3368 found_path = p;
3369 macro_start = nasm_malloc(sizeof(*macro_start));
3370 macro_start->next = NULL;
3371 macro_start->text = nasm_quote(found_path, strlen(found_path));
3372 macro_start->type = TOK_STRING;
3373 macro_start->a.mac = NULL;
3376 * We now have a macro name, an implicit parameter count of
3377 * zero, and a string token to use as an expansion. Create
3378 * and store an SMacro.
3380 define_smacro(ctx, mname, casesense, 0, macro_start);
3381 free_tlist(tline);
3382 free_tlist(origline);
3383 return DIRECTIVE_FOUND;
3386 case PP_STRLEN:
3387 casesense = true;
3389 tline = tline->next;
3390 skip_white_(tline);
3391 tline = expand_id(tline);
3392 if (!tline || (tline->type != TOK_ID &&
3393 (tline->type != TOK_PREPROC_ID ||
3394 tline->text[1] != '$'))) {
3395 nasm_error(ERR_NONFATAL,
3396 "`%%strlen' expects a macro identifier as first parameter");
3397 free_tlist(origline);
3398 return DIRECTIVE_FOUND;
3400 ctx = get_ctx(tline->text, &mname);
3401 last = tline;
3402 tline = expand_smacro(tline->next);
3403 last->next = NULL;
3405 t = tline;
3406 while (tok_type_(t, TOK_WHITESPACE))
3407 t = t->next;
3408 /* t should now point to the string */
3409 if (!tok_type_(t, TOK_STRING)) {
3410 nasm_error(ERR_NONFATAL,
3411 "`%%strlen` requires string as second parameter");
3412 free_tlist(tline);
3413 free_tlist(origline);
3414 return DIRECTIVE_FOUND;
3417 macro_start = nasm_malloc(sizeof(*macro_start));
3418 macro_start->next = NULL;
3419 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3420 macro_start->a.mac = NULL;
3423 * We now have a macro name, an implicit parameter count of
3424 * zero, and a numeric token to use as an expansion. Create
3425 * and store an SMacro.
3427 define_smacro(ctx, mname, casesense, 0, macro_start);
3428 free_tlist(tline);
3429 free_tlist(origline);
3430 return DIRECTIVE_FOUND;
3432 case PP_STRCAT:
3433 casesense = true;
3435 tline = tline->next;
3436 skip_white_(tline);
3437 tline = expand_id(tline);
3438 if (!tline || (tline->type != TOK_ID &&
3439 (tline->type != TOK_PREPROC_ID ||
3440 tline->text[1] != '$'))) {
3441 nasm_error(ERR_NONFATAL,
3442 "`%%strcat' expects a macro identifier as first parameter");
3443 free_tlist(origline);
3444 return DIRECTIVE_FOUND;
3446 ctx = get_ctx(tline->text, &mname);
3447 last = tline;
3448 tline = expand_smacro(tline->next);
3449 last->next = NULL;
3451 len = 0;
3452 list_for_each(t, tline) {
3453 switch (t->type) {
3454 case TOK_WHITESPACE:
3455 break;
3456 case TOK_STRING:
3457 len += t->a.len = nasm_unquote(t->text, NULL);
3458 break;
3459 case TOK_OTHER:
3460 if (!strcmp(t->text, ",")) /* permit comma separators */
3461 break;
3462 /* else fall through */
3463 default:
3464 nasm_error(ERR_NONFATAL,
3465 "non-string passed to `%%strcat' (%d)", t->type);
3466 free_tlist(tline);
3467 free_tlist(origline);
3468 return DIRECTIVE_FOUND;
3472 p = pp = nasm_malloc(len);
3473 list_for_each(t, tline) {
3474 if (t->type == TOK_STRING) {
3475 memcpy(p, t->text, t->a.len);
3476 p += t->a.len;
3481 * We now have a macro name, an implicit parameter count of
3482 * zero, and a numeric token to use as an expansion. Create
3483 * and store an SMacro.
3485 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3486 macro_start->text = nasm_quote(pp, len);
3487 nasm_free(pp);
3488 define_smacro(ctx, mname, casesense, 0, macro_start);
3489 free_tlist(tline);
3490 free_tlist(origline);
3491 return DIRECTIVE_FOUND;
3493 case PP_SUBSTR:
3495 int64_t start, count;
3496 size_t len;
3498 casesense = true;
3500 tline = tline->next;
3501 skip_white_(tline);
3502 tline = expand_id(tline);
3503 if (!tline || (tline->type != TOK_ID &&
3504 (tline->type != TOK_PREPROC_ID ||
3505 tline->text[1] != '$'))) {
3506 nasm_error(ERR_NONFATAL,
3507 "`%%substr' expects a macro identifier as first parameter");
3508 free_tlist(origline);
3509 return DIRECTIVE_FOUND;
3511 ctx = get_ctx(tline->text, &mname);
3512 last = tline;
3513 tline = expand_smacro(tline->next);
3514 last->next = NULL;
3516 if (tline) /* skip expanded id */
3517 t = tline->next;
3518 while (tok_type_(t, TOK_WHITESPACE))
3519 t = t->next;
3521 /* t should now point to the string */
3522 if (!tok_type_(t, TOK_STRING)) {
3523 nasm_error(ERR_NONFATAL,
3524 "`%%substr` requires string as second parameter");
3525 free_tlist(tline);
3526 free_tlist(origline);
3527 return DIRECTIVE_FOUND;
3530 tt = t->next;
3531 tptr = &tt;
3532 tokval.t_type = TOKEN_INVALID;
3533 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3534 if (!evalresult) {
3535 free_tlist(tline);
3536 free_tlist(origline);
3537 return DIRECTIVE_FOUND;
3538 } else if (!is_simple(evalresult)) {
3539 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3540 free_tlist(tline);
3541 free_tlist(origline);
3542 return DIRECTIVE_FOUND;
3544 start = evalresult->value - 1;
3546 while (tok_type_(tt, TOK_WHITESPACE))
3547 tt = tt->next;
3548 if (!tt) {
3549 count = 1; /* Backwards compatibility: one character */
3550 } else {
3551 tokval.t_type = TOKEN_INVALID;
3552 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3553 if (!evalresult) {
3554 free_tlist(tline);
3555 free_tlist(origline);
3556 return DIRECTIVE_FOUND;
3557 } else if (!is_simple(evalresult)) {
3558 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3559 free_tlist(tline);
3560 free_tlist(origline);
3561 return DIRECTIVE_FOUND;
3563 count = evalresult->value;
3566 len = nasm_unquote(t->text, NULL);
3568 /* make start and count being in range */
3569 if (start < 0)
3570 start = 0;
3571 if (count < 0)
3572 count = len + count + 1 - start;
3573 if (start + count > (int64_t)len)
3574 count = len - start;
3575 if (!len || count < 0 || start >=(int64_t)len)
3576 start = -1, count = 0; /* empty string */
3578 macro_start = nasm_malloc(sizeof(*macro_start));
3579 macro_start->next = NULL;
3580 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3581 macro_start->type = TOK_STRING;
3582 macro_start->a.mac = NULL;
3585 * We now have a macro name, an implicit parameter count of
3586 * zero, and a numeric token to use as an expansion. Create
3587 * and store an SMacro.
3589 define_smacro(ctx, mname, casesense, 0, macro_start);
3590 free_tlist(tline);
3591 free_tlist(origline);
3592 return DIRECTIVE_FOUND;
3595 case PP_ASSIGN:
3596 case PP_IASSIGN:
3597 casesense = (i == PP_ASSIGN);
3599 tline = tline->next;
3600 skip_white_(tline);
3601 tline = expand_id(tline);
3602 if (!tline || (tline->type != TOK_ID &&
3603 (tline->type != TOK_PREPROC_ID ||
3604 tline->text[1] != '$'))) {
3605 nasm_error(ERR_NONFATAL,
3606 "`%%%sassign' expects a macro identifier",
3607 (i == PP_IASSIGN ? "i" : ""));
3608 free_tlist(origline);
3609 return DIRECTIVE_FOUND;
3611 ctx = get_ctx(tline->text, &mname);
3612 last = tline;
3613 tline = expand_smacro(tline->next);
3614 last->next = NULL;
3616 t = tline;
3617 tptr = &t;
3618 tokval.t_type = TOKEN_INVALID;
3619 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3620 free_tlist(tline);
3621 if (!evalresult) {
3622 free_tlist(origline);
3623 return DIRECTIVE_FOUND;
3626 if (tokval.t_type)
3627 nasm_error(ERR_WARNING|ERR_PASS1,
3628 "trailing garbage after expression ignored");
3630 if (!is_simple(evalresult)) {
3631 nasm_error(ERR_NONFATAL,
3632 "non-constant value given to `%%%sassign'",
3633 (i == PP_IASSIGN ? "i" : ""));
3634 free_tlist(origline);
3635 return DIRECTIVE_FOUND;
3638 macro_start = nasm_malloc(sizeof(*macro_start));
3639 macro_start->next = NULL;
3640 make_tok_num(macro_start, reloc_value(evalresult));
3641 macro_start->a.mac = NULL;
3644 * We now have a macro name, an implicit parameter count of
3645 * zero, and a numeric token to use as an expansion. Create
3646 * and store an SMacro.
3648 define_smacro(ctx, mname, casesense, 0, macro_start);
3649 free_tlist(origline);
3650 return DIRECTIVE_FOUND;
3652 case PP_LINE:
3654 * Syntax is `%line nnn[+mmm] [filename]'
3656 tline = tline->next;
3657 skip_white_(tline);
3658 if (!tok_type_(tline, TOK_NUMBER)) {
3659 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3660 free_tlist(origline);
3661 return DIRECTIVE_FOUND;
3663 k = readnum(tline->text, &err);
3664 m = 1;
3665 tline = tline->next;
3666 if (tok_is_(tline, "+")) {
3667 tline = tline->next;
3668 if (!tok_type_(tline, TOK_NUMBER)) {
3669 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3670 free_tlist(origline);
3671 return DIRECTIVE_FOUND;
3673 m = readnum(tline->text, &err);
3674 tline = tline->next;
3676 skip_white_(tline);
3677 src_set_linnum(k);
3678 istk->lineinc = m;
3679 if (tline) {
3680 char *fname = detoken(tline, false);
3681 src_set_fname(fname);
3682 nasm_free(fname);
3684 free_tlist(origline);
3685 return DIRECTIVE_FOUND;
3687 default:
3688 nasm_error(ERR_FATAL,
3689 "preprocessor directive `%s' not yet implemented",
3690 pp_directives[i]);
3691 return DIRECTIVE_FOUND;
3696 * Ensure that a macro parameter contains a condition code and
3697 * nothing else. Return the condition code index if so, or -1
3698 * otherwise.
3700 static int find_cc(Token * t)
3702 Token *tt;
3704 if (!t)
3705 return -1; /* Probably a %+ without a space */
3707 skip_white_(t);
3708 if (t->type != TOK_ID)
3709 return -1;
3710 tt = t->next;
3711 skip_white_(tt);
3712 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3713 return -1;
3715 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3719 * This routines walks over tokens strem and hadnles tokens
3720 * pasting, if @handle_explicit passed then explicit pasting
3721 * term is handled, otherwise -- implicit pastings only.
3723 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3724 size_t mnum, bool handle_explicit)
3726 Token *tok, *next, **prev_next, **prev_nonspace;
3727 bool pasted = false;
3728 char *buf, *p;
3729 size_t len, i;
3732 * The last token before pasting. We need it
3733 * to be able to connect new handled tokens.
3734 * In other words if there were a tokens stream
3736 * A -> B -> C -> D
3738 * and we've joined tokens B and C, the resulting
3739 * stream should be
3741 * A -> BC -> D
3743 tok = *head;
3744 prev_next = NULL;
3746 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3747 prev_nonspace = head;
3748 else
3749 prev_nonspace = NULL;
3751 while (tok && (next = tok->next)) {
3753 switch (tok->type) {
3754 case TOK_WHITESPACE:
3755 /* Zap redundant whitespaces */
3756 while (tok_type_(next, TOK_WHITESPACE))
3757 next = delete_Token(next);
3758 tok->next = next;
3759 break;
3761 case TOK_PASTE:
3762 /* Explicit pasting */
3763 if (!handle_explicit)
3764 break;
3765 next = delete_Token(tok);
3767 while (tok_type_(next, TOK_WHITESPACE))
3768 next = delete_Token(next);
3770 if (!pasted)
3771 pasted = true;
3773 /* Left pasting token is start of line */
3774 if (!prev_nonspace)
3775 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3778 * No ending token, this might happen in two
3779 * cases
3781 * 1) There indeed no right token at all
3782 * 2) There is a bare "%define ID" statement,
3783 * and @ID does expand to whitespace.
3785 * So technically we need to do a grammar analysis
3786 * in another stage of parsing, but for now lets don't
3787 * change the behaviour people used to. Simply allow
3788 * whitespace after paste token.
3790 if (!next) {
3792 * Zap ending space tokens and that's all.
3794 tok = (*prev_nonspace)->next;
3795 while (tok_type_(tok, TOK_WHITESPACE))
3796 tok = delete_Token(tok);
3797 tok = *prev_nonspace;
3798 tok->next = NULL;
3799 break;
3802 tok = *prev_nonspace;
3803 while (tok_type_(tok, TOK_WHITESPACE))
3804 tok = delete_Token(tok);
3805 len = strlen(tok->text);
3806 len += strlen(next->text);
3808 p = buf = nasm_malloc(len + 1);
3809 strcpy(p, tok->text);
3810 p = strchr(p, '\0');
3811 strcpy(p, next->text);
3813 delete_Token(tok);
3815 tok = tokenize(buf);
3816 nasm_free(buf);
3818 *prev_nonspace = tok;
3819 while (tok && tok->next)
3820 tok = tok->next;
3822 tok->next = delete_Token(next);
3824 /* Restart from pasted tokens head */
3825 tok = *prev_nonspace;
3826 break;
3828 default:
3829 /* implicit pasting */
3830 for (i = 0; i < mnum; i++) {
3831 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3832 continue;
3834 len = 0;
3835 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3836 len += strlen(next->text);
3837 next = next->next;
3840 /* No match */
3841 if (tok == next)
3842 break;
3844 len += strlen(tok->text);
3845 p = buf = nasm_malloc(len + 1);
3847 while (tok != next) {
3848 strcpy(p, tok->text);
3849 p = strchr(p, '\0');
3850 tok = delete_Token(tok);
3853 tok = tokenize(buf);
3854 nasm_free(buf);
3856 if (prev_next)
3857 *prev_next = tok;
3858 else
3859 *head = tok;
3862 * Connect pasted into original stream,
3863 * ie A -> new-tokens -> B
3865 while (tok && tok->next)
3866 tok = tok->next;
3867 tok->next = next;
3869 if (!pasted)
3870 pasted = true;
3872 /* Restart from pasted tokens head */
3873 tok = prev_next ? *prev_next : *head;
3876 break;
3879 prev_next = &tok->next;
3881 if (tok->next &&
3882 !tok_type_(tok->next, TOK_WHITESPACE) &&
3883 !tok_type_(tok->next, TOK_PASTE))
3884 prev_nonspace = prev_next;
3886 tok = tok->next;
3889 return pasted;
3893 * expands to a list of tokens from %{x:y}
3895 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3897 Token *t = tline, **tt, *tm, *head;
3898 char *pos;
3899 int fst, lst, j, i;
3901 pos = strchr(tline->text, ':');
3902 nasm_assert(pos);
3904 lst = atoi(pos + 1);
3905 fst = atoi(tline->text + 1);
3908 * only macros params are accounted so
3909 * if someone passes %0 -- we reject such
3910 * value(s)
3912 if (lst == 0 || fst == 0)
3913 goto err;
3915 /* the values should be sane */
3916 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3917 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3918 goto err;
3920 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3921 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3923 /* counted from zero */
3924 fst--, lst--;
3927 * It will be at least one token. Note we
3928 * need to scan params until separator, otherwise
3929 * only first token will be passed.
3931 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3932 head = new_Token(NULL, tm->type, tm->text, 0);
3933 tt = &head->next, tm = tm->next;
3934 while (tok_isnt_(tm, ",")) {
3935 t = new_Token(NULL, tm->type, tm->text, 0);
3936 *tt = t, tt = &t->next, tm = tm->next;
3939 if (fst < lst) {
3940 for (i = fst + 1; i <= lst; i++) {
3941 t = new_Token(NULL, TOK_OTHER, ",", 0);
3942 *tt = t, tt = &t->next;
3943 j = (i + mac->rotate) % mac->nparam;
3944 tm = mac->params[j];
3945 while (tok_isnt_(tm, ",")) {
3946 t = new_Token(NULL, tm->type, tm->text, 0);
3947 *tt = t, tt = &t->next, tm = tm->next;
3950 } else {
3951 for (i = fst - 1; i >= lst; i--) {
3952 t = new_Token(NULL, TOK_OTHER, ",", 0);
3953 *tt = t, tt = &t->next;
3954 j = (i + mac->rotate) % mac->nparam;
3955 tm = mac->params[j];
3956 while (tok_isnt_(tm, ",")) {
3957 t = new_Token(NULL, tm->type, tm->text, 0);
3958 *tt = t, tt = &t->next, tm = tm->next;
3963 *last = tt;
3964 return head;
3966 err:
3967 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3968 &tline->text[1]);
3969 return tline;
3973 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3974 * %-n) and MMacro-local identifiers (%%foo) as well as
3975 * macro indirection (%[...]) and range (%{..:..}).
3977 static Token *expand_mmac_params(Token * tline)
3979 Token *t, *tt, **tail, *thead;
3980 bool changed = false;
3981 char *pos;
3983 tail = &thead;
3984 thead = NULL;
3986 while (tline) {
3987 if (tline->type == TOK_PREPROC_ID &&
3988 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3989 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3990 tline->text[1] == '%')) {
3991 char *text = NULL;
3992 int type = 0, cc; /* type = 0 to placate optimisers */
3993 char tmpbuf[30];
3994 unsigned int n;
3995 int i;
3996 MMacro *mac;
3998 t = tline;
3999 tline = tline->next;
4001 mac = istk->mstk;
4002 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4003 mac = mac->next_active;
4004 if (!mac) {
4005 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4006 } else {
4007 pos = strchr(t->text, ':');
4008 if (!pos) {
4009 switch (t->text[1]) {
4011 * We have to make a substitution of one of the
4012 * forms %1, %-1, %+1, %%foo, %0.
4014 case '0':
4015 type = TOK_NUMBER;
4016 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4017 text = nasm_strdup(tmpbuf);
4018 break;
4019 case '%':
4020 type = TOK_ID;
4021 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4022 mac->unique);
4023 text = nasm_strcat(tmpbuf, t->text + 2);
4024 break;
4025 case '-':
4026 n = atoi(t->text + 2) - 1;
4027 if (n >= mac->nparam)
4028 tt = NULL;
4029 else {
4030 if (mac->nparam > 1)
4031 n = (n + mac->rotate) % mac->nparam;
4032 tt = mac->params[n];
4034 cc = find_cc(tt);
4035 if (cc == -1) {
4036 nasm_error(ERR_NONFATAL,
4037 "macro parameter %d is not a condition code",
4038 n + 1);
4039 text = NULL;
4040 } else {
4041 type = TOK_ID;
4042 if (inverse_ccs[cc] == -1) {
4043 nasm_error(ERR_NONFATAL,
4044 "condition code `%s' is not invertible",
4045 conditions[cc]);
4046 text = NULL;
4047 } else
4048 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4050 break;
4051 case '+':
4052 n = atoi(t->text + 2) - 1;
4053 if (n >= mac->nparam)
4054 tt = NULL;
4055 else {
4056 if (mac->nparam > 1)
4057 n = (n + mac->rotate) % mac->nparam;
4058 tt = mac->params[n];
4060 cc = find_cc(tt);
4061 if (cc == -1) {
4062 nasm_error(ERR_NONFATAL,
4063 "macro parameter %d is not a condition code",
4064 n + 1);
4065 text = NULL;
4066 } else {
4067 type = TOK_ID;
4068 text = nasm_strdup(conditions[cc]);
4070 break;
4071 default:
4072 n = atoi(t->text + 1) - 1;
4073 if (n >= mac->nparam)
4074 tt = NULL;
4075 else {
4076 if (mac->nparam > 1)
4077 n = (n + mac->rotate) % mac->nparam;
4078 tt = mac->params[n];
4080 if (tt) {
4081 for (i = 0; i < mac->paramlen[n]; i++) {
4082 *tail = new_Token(NULL, tt->type, tt->text, 0);
4083 tail = &(*tail)->next;
4084 tt = tt->next;
4087 text = NULL; /* we've done it here */
4088 break;
4090 } else {
4092 * seems we have a parameters range here
4094 Token *head, **last;
4095 head = expand_mmac_params_range(mac, t, &last);
4096 if (head != t) {
4097 *tail = head;
4098 *last = tline;
4099 tline = head;
4100 text = NULL;
4104 if (!text) {
4105 delete_Token(t);
4106 } else {
4107 *tail = t;
4108 tail = &t->next;
4109 t->type = type;
4110 nasm_free(t->text);
4111 t->text = text;
4112 t->a.mac = NULL;
4114 changed = true;
4115 continue;
4116 } else if (tline->type == TOK_INDIRECT) {
4117 t = tline;
4118 tline = tline->next;
4119 tt = tokenize(t->text);
4120 tt = expand_mmac_params(tt);
4121 tt = expand_smacro(tt);
4122 *tail = tt;
4123 while (tt) {
4124 tt->a.mac = NULL; /* Necessary? */
4125 tail = &tt->next;
4126 tt = tt->next;
4128 delete_Token(t);
4129 changed = true;
4130 } else {
4131 t = *tail = tline;
4132 tline = tline->next;
4133 t->a.mac = NULL;
4134 tail = &t->next;
4137 *tail = NULL;
4139 if (changed) {
4140 const struct tokseq_match t[] = {
4142 PP_CONCAT_MASK(TOK_ID) |
4143 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4144 PP_CONCAT_MASK(TOK_ID) |
4145 PP_CONCAT_MASK(TOK_NUMBER) |
4146 PP_CONCAT_MASK(TOK_FLOAT) |
4147 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4150 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4151 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4154 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4157 return thead;
4161 * Expand all single-line macro calls made in the given line.
4162 * Return the expanded version of the line. The original is deemed
4163 * to be destroyed in the process. (In reality we'll just move
4164 * Tokens from input to output a lot of the time, rather than
4165 * actually bothering to destroy and replicate.)
4168 static Token *expand_smacro(Token * tline)
4170 Token *t, *tt, *mstart, **tail, *thead;
4171 SMacro *head = NULL, *m;
4172 Token **params;
4173 int *paramsize;
4174 unsigned int nparam, sparam;
4175 int brackets;
4176 Token *org_tline = tline;
4177 Context *ctx;
4178 const char *mname;
4179 int deadman = DEADMAN_LIMIT;
4180 bool expanded;
4183 * Trick: we should avoid changing the start token pointer since it can
4184 * be contained in "next" field of other token. Because of this
4185 * we allocate a copy of first token and work with it; at the end of
4186 * routine we copy it back
4188 if (org_tline) {
4189 tline = new_Token(org_tline->next, org_tline->type,
4190 org_tline->text, 0);
4191 tline->a.mac = org_tline->a.mac;
4192 nasm_free(org_tline->text);
4193 org_tline->text = NULL;
4196 expanded = true; /* Always expand %+ at least once */
4198 again:
4199 thead = NULL;
4200 tail = &thead;
4202 while (tline) { /* main token loop */
4203 if (!--deadman) {
4204 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4205 goto err;
4208 if ((mname = tline->text)) {
4209 /* if this token is a local macro, look in local context */
4210 if (tline->type == TOK_ID) {
4211 head = (SMacro *)hash_findix(&smacros, mname);
4212 } else if (tline->type == TOK_PREPROC_ID) {
4213 ctx = get_ctx(mname, &mname);
4214 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4215 } else
4216 head = NULL;
4219 * We've hit an identifier. As in is_mmacro below, we first
4220 * check whether the identifier is a single-line macro at
4221 * all, then think about checking for parameters if
4222 * necessary.
4224 list_for_each(m, head)
4225 if (!mstrcmp(m->name, mname, m->casesense))
4226 break;
4227 if (m) {
4228 mstart = tline;
4229 params = NULL;
4230 paramsize = NULL;
4231 if (m->nparam == 0) {
4233 * Simple case: the macro is parameterless. Discard the
4234 * one token that the macro call took, and push the
4235 * expansion back on the to-do stack.
4237 if (!m->expansion) {
4238 if (!strcmp("__FILE__", m->name)) {
4239 const char *file = src_get_fname();
4240 /* nasm_free(tline->text); here? */
4241 tline->text = nasm_quote(file, strlen(file));
4242 tline->type = TOK_STRING;
4243 continue;
4245 if (!strcmp("__LINE__", m->name)) {
4246 nasm_free(tline->text);
4247 make_tok_num(tline, src_get_linnum());
4248 continue;
4250 if (!strcmp("__BITS__", m->name)) {
4251 nasm_free(tline->text);
4252 make_tok_num(tline, globalbits);
4253 continue;
4255 tline = delete_Token(tline);
4256 continue;
4258 } else {
4260 * Complicated case: at least one macro with this name
4261 * exists and takes parameters. We must find the
4262 * parameters in the call, count them, find the SMacro
4263 * that corresponds to that form of the macro call, and
4264 * substitute for the parameters when we expand. What a
4265 * pain.
4267 /*tline = tline->next;
4268 skip_white_(tline); */
4269 do {
4270 t = tline->next;
4271 while (tok_type_(t, TOK_SMAC_END)) {
4272 t->a.mac->in_progress = false;
4273 t->text = NULL;
4274 t = tline->next = delete_Token(t);
4276 tline = t;
4277 } while (tok_type_(tline, TOK_WHITESPACE));
4278 if (!tok_is_(tline, "(")) {
4280 * This macro wasn't called with parameters: ignore
4281 * the call. (Behaviour borrowed from gnu cpp.)
4283 tline = mstart;
4284 m = NULL;
4285 } else {
4286 int paren = 0;
4287 int white = 0;
4288 brackets = 0;
4289 nparam = 0;
4290 sparam = PARAM_DELTA;
4291 params = nasm_malloc(sparam * sizeof(Token *));
4292 params[0] = tline->next;
4293 paramsize = nasm_malloc(sparam * sizeof(int));
4294 paramsize[0] = 0;
4295 while (true) { /* parameter loop */
4297 * For some unusual expansions
4298 * which concatenates function call
4300 t = tline->next;
4301 while (tok_type_(t, TOK_SMAC_END)) {
4302 t->a.mac->in_progress = false;
4303 t->text = NULL;
4304 t = tline->next = delete_Token(t);
4306 tline = t;
4308 if (!tline) {
4309 nasm_error(ERR_NONFATAL,
4310 "macro call expects terminating `)'");
4311 break;
4313 if (tline->type == TOK_WHITESPACE
4314 && brackets <= 0) {
4315 if (paramsize[nparam])
4316 white++;
4317 else
4318 params[nparam] = tline->next;
4319 continue; /* parameter loop */
4321 if (tline->type == TOK_OTHER
4322 && tline->text[1] == 0) {
4323 char ch = tline->text[0];
4324 if (ch == ',' && !paren && brackets <= 0) {
4325 if (++nparam >= sparam) {
4326 sparam += PARAM_DELTA;
4327 params = nasm_realloc(params,
4328 sparam * sizeof(Token *));
4329 paramsize = nasm_realloc(paramsize,
4330 sparam * sizeof(int));
4332 params[nparam] = tline->next;
4333 paramsize[nparam] = 0;
4334 white = 0;
4335 continue; /* parameter loop */
4337 if (ch == '{' &&
4338 (brackets > 0 || (brackets == 0 &&
4339 !paramsize[nparam])))
4341 if (!(brackets++)) {
4342 params[nparam] = tline->next;
4343 continue; /* parameter loop */
4346 if (ch == '}' && brackets > 0)
4347 if (--brackets == 0) {
4348 brackets = -1;
4349 continue; /* parameter loop */
4351 if (ch == '(' && !brackets)
4352 paren++;
4353 if (ch == ')' && brackets <= 0)
4354 if (--paren < 0)
4355 break;
4357 if (brackets < 0) {
4358 brackets = 0;
4359 nasm_error(ERR_NONFATAL, "braces do not "
4360 "enclose all of macro parameter");
4362 paramsize[nparam] += white + 1;
4363 white = 0;
4364 } /* parameter loop */
4365 nparam++;
4366 while (m && (m->nparam != nparam ||
4367 mstrcmp(m->name, mname,
4368 m->casesense)))
4369 m = m->next;
4370 if (!m)
4371 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4372 "macro `%s' exists, "
4373 "but not taking %d parameters",
4374 mstart->text, nparam);
4377 if (m && m->in_progress)
4378 m = NULL;
4379 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4381 * Design question: should we handle !tline, which
4382 * indicates missing ')' here, or expand those
4383 * macros anyway, which requires the (t) test a few
4384 * lines down?
4386 nasm_free(params);
4387 nasm_free(paramsize);
4388 tline = mstart;
4389 } else {
4391 * Expand the macro: we are placed on the last token of the
4392 * call, so that we can easily split the call from the
4393 * following tokens. We also start by pushing an SMAC_END
4394 * token for the cycle removal.
4396 t = tline;
4397 if (t) {
4398 tline = t->next;
4399 t->next = NULL;
4401 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4402 tt->a.mac = m;
4403 m->in_progress = true;
4404 tline = tt;
4405 list_for_each(t, m->expansion) {
4406 if (t->type >= TOK_SMAC_PARAM) {
4407 Token *pcopy = tline, **ptail = &pcopy;
4408 Token *ttt, *pt;
4409 int i;
4411 ttt = params[t->type - TOK_SMAC_PARAM];
4412 i = paramsize[t->type - TOK_SMAC_PARAM];
4413 while (--i >= 0) {
4414 pt = *ptail = new_Token(tline, ttt->type,
4415 ttt->text, 0);
4416 ptail = &pt->next;
4417 ttt = ttt->next;
4419 tline = pcopy;
4420 } else if (t->type == TOK_PREPROC_Q) {
4421 tt = new_Token(tline, TOK_ID, mname, 0);
4422 tline = tt;
4423 } else if (t->type == TOK_PREPROC_QQ) {
4424 tt = new_Token(tline, TOK_ID, m->name, 0);
4425 tline = tt;
4426 } else {
4427 tt = new_Token(tline, t->type, t->text, 0);
4428 tline = tt;
4433 * Having done that, get rid of the macro call, and clean
4434 * up the parameters.
4436 nasm_free(params);
4437 nasm_free(paramsize);
4438 free_tlist(mstart);
4439 expanded = true;
4440 continue; /* main token loop */
4445 if (tline->type == TOK_SMAC_END) {
4446 tline->a.mac->in_progress = false;
4447 tline = delete_Token(tline);
4448 } else {
4449 t = *tail = tline;
4450 tline = tline->next;
4451 t->a.mac = NULL;
4452 t->next = NULL;
4453 tail = &t->next;
4458 * Now scan the entire line and look for successive TOK_IDs that resulted
4459 * after expansion (they can't be produced by tokenize()). The successive
4460 * TOK_IDs should be concatenated.
4461 * Also we look for %+ tokens and concatenate the tokens before and after
4462 * them (without white spaces in between).
4464 if (expanded) {
4465 const struct tokseq_match t[] = {
4467 PP_CONCAT_MASK(TOK_ID) |
4468 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4469 PP_CONCAT_MASK(TOK_ID) |
4470 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4471 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4474 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4476 * If we concatenated something, *and* we had previously expanded
4477 * an actual macro, scan the lines again for macros...
4479 tline = thead;
4480 expanded = false;
4481 goto again;
4485 err:
4486 if (org_tline) {
4487 if (thead) {
4488 *org_tline = *thead;
4489 /* since we just gave text to org_line, don't free it */
4490 thead->text = NULL;
4491 delete_Token(thead);
4492 } else {
4493 /* the expression expanded to empty line;
4494 we can't return NULL for some reasons
4495 we just set the line to a single WHITESPACE token. */
4496 memset(org_tline, 0, sizeof(*org_tline));
4497 org_tline->text = NULL;
4498 org_tline->type = TOK_WHITESPACE;
4500 thead = org_tline;
4503 return thead;
4507 * Similar to expand_smacro but used exclusively with macro identifiers
4508 * right before they are fetched in. The reason is that there can be
4509 * identifiers consisting of several subparts. We consider that if there
4510 * are more than one element forming the name, user wants a expansion,
4511 * otherwise it will be left as-is. Example:
4513 * %define %$abc cde
4515 * the identifier %$abc will be left as-is so that the handler for %define
4516 * will suck it and define the corresponding value. Other case:
4518 * %define _%$abc cde
4520 * In this case user wants name to be expanded *before* %define starts
4521 * working, so we'll expand %$abc into something (if it has a value;
4522 * otherwise it will be left as-is) then concatenate all successive
4523 * PP_IDs into one.
4525 static Token *expand_id(Token * tline)
4527 Token *cur, *oldnext = NULL;
4529 if (!tline || !tline->next)
4530 return tline;
4532 cur = tline;
4533 while (cur->next &&
4534 (cur->next->type == TOK_ID ||
4535 cur->next->type == TOK_PREPROC_ID
4536 || cur->next->type == TOK_NUMBER))
4537 cur = cur->next;
4539 /* If identifier consists of just one token, don't expand */
4540 if (cur == tline)
4541 return tline;
4543 if (cur) {
4544 oldnext = cur->next; /* Detach the tail past identifier */
4545 cur->next = NULL; /* so that expand_smacro stops here */
4548 tline = expand_smacro(tline);
4550 if (cur) {
4551 /* expand_smacro possibly changhed tline; re-scan for EOL */
4552 cur = tline;
4553 while (cur && cur->next)
4554 cur = cur->next;
4555 if (cur)
4556 cur->next = oldnext;
4559 return tline;
4563 * Determine whether the given line constitutes a multi-line macro
4564 * call, and return the MMacro structure called if so. Doesn't have
4565 * to check for an initial label - that's taken care of in
4566 * expand_mmacro - but must check numbers of parameters. Guaranteed
4567 * to be called with tline->type == TOK_ID, so the putative macro
4568 * name is easy to find.
4570 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4572 MMacro *head, *m;
4573 Token **params;
4574 int nparam;
4576 head = (MMacro *) hash_findix(&mmacros, tline->text);
4579 * Efficiency: first we see if any macro exists with the given
4580 * name. If not, we can return NULL immediately. _Then_ we
4581 * count the parameters, and then we look further along the
4582 * list if necessary to find the proper MMacro.
4584 list_for_each(m, head)
4585 if (!mstrcmp(m->name, tline->text, m->casesense))
4586 break;
4587 if (!m)
4588 return NULL;
4591 * OK, we have a potential macro. Count and demarcate the
4592 * parameters.
4594 count_mmac_params(tline->next, &nparam, &params);
4597 * So we know how many parameters we've got. Find the MMacro
4598 * structure that handles this number.
4600 while (m) {
4601 if (m->nparam_min <= nparam
4602 && (m->plus || nparam <= m->nparam_max)) {
4604 * This one is right. Just check if cycle removal
4605 * prohibits us using it before we actually celebrate...
4607 if (m->in_progress > m->max_depth) {
4608 if (m->max_depth > 0) {
4609 nasm_error(ERR_WARNING,
4610 "reached maximum recursion depth of %i",
4611 m->max_depth);
4613 nasm_free(params);
4614 return NULL;
4617 * It's right, and we can use it. Add its default
4618 * parameters to the end of our list if necessary.
4620 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4621 params =
4622 nasm_realloc(params,
4623 ((m->nparam_min + m->ndefs +
4624 1) * sizeof(*params)));
4625 while (nparam < m->nparam_min + m->ndefs) {
4626 params[nparam] = m->defaults[nparam - m->nparam_min];
4627 nparam++;
4631 * If we've gone over the maximum parameter count (and
4632 * we're in Plus mode), ignore parameters beyond
4633 * nparam_max.
4635 if (m->plus && nparam > m->nparam_max)
4636 nparam = m->nparam_max;
4638 * Then terminate the parameter list, and leave.
4640 if (!params) { /* need this special case */
4641 params = nasm_malloc(sizeof(*params));
4642 nparam = 0;
4644 params[nparam] = NULL;
4645 *params_array = params;
4646 return m;
4649 * This one wasn't right: look for the next one with the
4650 * same name.
4652 list_for_each(m, m->next)
4653 if (!mstrcmp(m->name, tline->text, m->casesense))
4654 break;
4658 * After all that, we didn't find one with the right number of
4659 * parameters. Issue a warning, and fail to expand the macro.
4661 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4662 "macro `%s' exists, but not taking %d parameters",
4663 tline->text, nparam);
4664 nasm_free(params);
4665 return NULL;
4670 * Save MMacro invocation specific fields in
4671 * preparation for a recursive macro expansion
4673 static void push_mmacro(MMacro *m)
4675 MMacroInvocation *i;
4677 i = nasm_malloc(sizeof(MMacroInvocation));
4678 i->prev = m->prev;
4679 i->params = m->params;
4680 i->iline = m->iline;
4681 i->nparam = m->nparam;
4682 i->rotate = m->rotate;
4683 i->paramlen = m->paramlen;
4684 i->unique = m->unique;
4685 i->condcnt = m->condcnt;
4686 m->prev = i;
4691 * Restore MMacro invocation specific fields that were
4692 * saved during a previous recursive macro expansion
4694 static void pop_mmacro(MMacro *m)
4696 MMacroInvocation *i;
4698 if (m->prev) {
4699 i = m->prev;
4700 m->prev = i->prev;
4701 m->params = i->params;
4702 m->iline = i->iline;
4703 m->nparam = i->nparam;
4704 m->rotate = i->rotate;
4705 m->paramlen = i->paramlen;
4706 m->unique = i->unique;
4707 m->condcnt = i->condcnt;
4708 nasm_free(i);
4714 * Expand the multi-line macro call made by the given line, if
4715 * there is one to be expanded. If there is, push the expansion on
4716 * istk->expansion and return 1. Otherwise return 0.
4718 static int expand_mmacro(Token * tline)
4720 Token *startline = tline;
4721 Token *label = NULL;
4722 int dont_prepend = 0;
4723 Token **params, *t, *tt;
4724 MMacro *m;
4725 Line *l, *ll;
4726 int i, nparam, *paramlen;
4727 const char *mname;
4729 t = tline;
4730 skip_white_(t);
4731 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4732 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4733 return 0;
4734 m = is_mmacro(t, &params);
4735 if (m) {
4736 mname = t->text;
4737 } else {
4738 Token *last;
4740 * We have an id which isn't a macro call. We'll assume
4741 * it might be a label; we'll also check to see if a
4742 * colon follows it. Then, if there's another id after
4743 * that lot, we'll check it again for macro-hood.
4745 label = last = t;
4746 t = t->next;
4747 if (tok_type_(t, TOK_WHITESPACE))
4748 last = t, t = t->next;
4749 if (tok_is_(t, ":")) {
4750 dont_prepend = 1;
4751 last = t, t = t->next;
4752 if (tok_type_(t, TOK_WHITESPACE))
4753 last = t, t = t->next;
4755 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4756 return 0;
4757 last->next = NULL;
4758 mname = t->text;
4759 tline = t;
4763 * Fix up the parameters: this involves stripping leading and
4764 * trailing whitespace, then stripping braces if they are
4765 * present.
4767 for (nparam = 0; params[nparam]; nparam++) ;
4768 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4770 for (i = 0; params[i]; i++) {
4771 int brace = 0;
4772 int comma = (!m->plus || i < nparam - 1);
4774 t = params[i];
4775 skip_white_(t);
4776 if (tok_is_(t, "{"))
4777 t = t->next, brace++, comma = false;
4778 params[i] = t;
4779 paramlen[i] = 0;
4780 while (t) {
4781 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4782 break; /* ... because we have hit a comma */
4783 if (comma && t->type == TOK_WHITESPACE
4784 && tok_is_(t->next, ","))
4785 break; /* ... or a space then a comma */
4786 if (brace && t->type == TOK_OTHER) {
4787 if (t->text[0] == '{')
4788 brace++; /* ... or a nested opening brace */
4789 else if (t->text[0] == '}')
4790 if (!--brace)
4791 break; /* ... or a brace */
4793 t = t->next;
4794 paramlen[i]++;
4796 if (brace)
4797 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4801 * OK, we have a MMacro structure together with a set of
4802 * parameters. We must now go through the expansion and push
4803 * copies of each Line on to istk->expansion. Substitution of
4804 * parameter tokens and macro-local tokens doesn't get done
4805 * until the single-line macro substitution process; this is
4806 * because delaying them allows us to change the semantics
4807 * later through %rotate.
4809 * First, push an end marker on to istk->expansion, mark this
4810 * macro as in progress, and set up its invocation-specific
4811 * variables.
4813 ll = nasm_malloc(sizeof(Line));
4814 ll->next = istk->expansion;
4815 ll->finishes = m;
4816 ll->first = NULL;
4817 istk->expansion = ll;
4820 * Save the previous MMacro expansion in the case of
4821 * macro recursion
4823 if (m->max_depth && m->in_progress)
4824 push_mmacro(m);
4826 m->in_progress ++;
4827 m->params = params;
4828 m->iline = tline;
4829 m->nparam = nparam;
4830 m->rotate = 0;
4831 m->paramlen = paramlen;
4832 m->unique = unique++;
4833 m->lineno = 0;
4834 m->condcnt = 0;
4836 m->next_active = istk->mstk;
4837 istk->mstk = m;
4839 list_for_each(l, m->expansion) {
4840 Token **tail;
4842 ll = nasm_malloc(sizeof(Line));
4843 ll->finishes = NULL;
4844 ll->next = istk->expansion;
4845 istk->expansion = ll;
4846 tail = &ll->first;
4848 list_for_each(t, l->first) {
4849 Token *x = t;
4850 switch (t->type) {
4851 case TOK_PREPROC_Q:
4852 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4853 break;
4854 case TOK_PREPROC_QQ:
4855 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4856 break;
4857 case TOK_PREPROC_ID:
4858 if (t->text[1] == '0' && t->text[2] == '0') {
4859 dont_prepend = -1;
4860 x = label;
4861 if (!x)
4862 continue;
4864 /* fall through */
4865 default:
4866 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4867 break;
4869 tail = &tt->next;
4871 *tail = NULL;
4875 * If we had a label, push it on as the first line of
4876 * the macro expansion.
4878 if (label) {
4879 if (dont_prepend < 0)
4880 free_tlist(startline);
4881 else {
4882 ll = nasm_malloc(sizeof(Line));
4883 ll->finishes = NULL;
4884 ll->next = istk->expansion;
4885 istk->expansion = ll;
4886 ll->first = startline;
4887 if (!dont_prepend) {
4888 while (label->next)
4889 label = label->next;
4890 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4895 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4897 return 1;
4901 * This function adds macro names to error messages, and suppresses
4902 * them if necessary.
4904 static void pp_verror(int severity, const char *fmt, va_list arg)
4906 char buff[BUFSIZ];
4907 MMacro *mmac = NULL;
4908 int delta = 0;
4911 * If we're in a dead branch of IF or something like it, ignore the error.
4912 * However, because %else etc are evaluated in the state context
4913 * of the previous branch, errors might get lost:
4914 * %if 0 ... %else trailing garbage ... %endif
4915 * So %else etc should set the ERR_PP_PRECOND flag.
4917 if ((severity & ERR_MASK) < ERR_FATAL &&
4918 istk && istk->conds &&
4919 ((severity & ERR_PP_PRECOND) ?
4920 istk->conds->state == COND_NEVER :
4921 !emitting(istk->conds->state)))
4922 return;
4924 /* get %macro name */
4925 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4926 mmac = istk->mstk;
4927 /* but %rep blocks should be skipped */
4928 while (mmac && !mmac->name)
4929 mmac = mmac->next_active, delta++;
4932 if (mmac) {
4933 vsnprintf(buff, sizeof(buff), fmt, arg);
4935 nasm_set_verror(real_verror);
4936 nasm_error(severity, "(%s:%d) %s",
4937 mmac->name, mmac->lineno - delta, buff);
4938 nasm_set_verror(pp_verror);
4939 } else {
4940 real_verror(severity, fmt, arg);
4944 static void
4945 pp_reset(char *file, int apass, StrList **deplist)
4947 Token *t;
4949 cstk = NULL;
4950 istk = nasm_malloc(sizeof(Include));
4951 istk->next = NULL;
4952 istk->conds = NULL;
4953 istk->expansion = NULL;
4954 istk->mstk = NULL;
4955 istk->fp = nasm_open_read(file, NF_TEXT);
4956 istk->fname = NULL;
4957 src_set(0, file);
4958 istk->lineinc = 1;
4959 if (!istk->fp)
4960 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4961 defining = NULL;
4962 nested_mac_count = 0;
4963 nested_rep_count = 0;
4964 init_macros();
4965 unique = 0;
4967 if (tasm_compatible_mode)
4968 pp_add_stdmac(nasm_stdmac_tasm);
4970 pp_add_stdmac(nasm_stdmac_nasm);
4971 pp_add_stdmac(nasm_stdmac_version);
4973 if (extrastdmac)
4974 pp_add_stdmac(extrastdmac);
4976 stdmacpos = stdmacros[0];
4977 stdmacnext = &stdmacros[1];
4979 do_predef = true;
4982 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4983 * The caller, however, will also pass in 3 for preprocess-only so
4984 * we can set __PASS__ accordingly.
4986 pass = apass > 2 ? 2 : apass;
4988 dephead = deplist;
4989 nasm_add_string_to_strlist(dephead, file);
4992 * Define the __PASS__ macro. This is defined here unlike
4993 * all the other builtins, because it is special -- it varies between
4994 * passes.
4996 t = nasm_malloc(sizeof(*t));
4997 t->next = NULL;
4998 make_tok_num(t, apass);
4999 t->a.mac = NULL;
5000 define_smacro(NULL, "__PASS__", true, 0, t);
5003 static void pp_init(void)
5005 hash_init(&FileHash, HASH_MEDIUM);
5008 static char *pp_getline(void)
5010 char *line;
5011 Token *tline;
5013 real_verror = nasm_set_verror(pp_verror);
5015 while (1) {
5017 * Fetch a tokenized line, either from the macro-expansion
5018 * buffer or from the input file.
5020 tline = NULL;
5021 while (istk->expansion && istk->expansion->finishes) {
5022 Line *l = istk->expansion;
5023 if (!l->finishes->name && l->finishes->in_progress > 1) {
5024 Line *ll;
5027 * This is a macro-end marker for a macro with no
5028 * name, which means it's not really a macro at all
5029 * but a %rep block, and the `in_progress' field is
5030 * more than 1, meaning that we still need to
5031 * repeat. (1 means the natural last repetition; 0
5032 * means termination by %exitrep.) We have
5033 * therefore expanded up to the %endrep, and must
5034 * push the whole block on to the expansion buffer
5035 * again. We don't bother to remove the macro-end
5036 * marker: we'd only have to generate another one
5037 * if we did.
5039 l->finishes->in_progress--;
5040 list_for_each(l, l->finishes->expansion) {
5041 Token *t, *tt, **tail;
5043 ll = nasm_malloc(sizeof(Line));
5044 ll->next = istk->expansion;
5045 ll->finishes = NULL;
5046 ll->first = NULL;
5047 tail = &ll->first;
5049 list_for_each(t, l->first) {
5050 if (t->text || t->type == TOK_WHITESPACE) {
5051 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5052 tail = &tt->next;
5056 istk->expansion = ll;
5058 } else {
5060 * Check whether a `%rep' was started and not ended
5061 * within this macro expansion. This can happen and
5062 * should be detected. It's a fatal error because
5063 * I'm too confused to work out how to recover
5064 * sensibly from it.
5066 if (defining) {
5067 if (defining->name)
5068 nasm_panic(0, "defining with name in expansion");
5069 else if (istk->mstk->name)
5070 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5071 " expansion of macro `%s'",
5072 istk->mstk->name);
5076 * FIXME: investigate the relationship at this point between
5077 * istk->mstk and l->finishes
5080 MMacro *m = istk->mstk;
5081 istk->mstk = m->next_active;
5082 if (m->name) {
5084 * This was a real macro call, not a %rep, and
5085 * therefore the parameter information needs to
5086 * be freed.
5088 if (m->prev) {
5089 pop_mmacro(m);
5090 l->finishes->in_progress --;
5091 } else {
5092 nasm_free(m->params);
5093 free_tlist(m->iline);
5094 nasm_free(m->paramlen);
5095 l->finishes->in_progress = 0;
5097 } else
5098 free_mmacro(m);
5100 istk->expansion = l->next;
5101 nasm_free(l);
5102 lfmt->downlevel(LIST_MACRO);
5105 while (1) { /* until we get a line we can use */
5107 if (istk->expansion) { /* from a macro expansion */
5108 char *p;
5109 Line *l = istk->expansion;
5110 if (istk->mstk)
5111 istk->mstk->lineno++;
5112 tline = l->first;
5113 istk->expansion = l->next;
5114 nasm_free(l);
5115 p = detoken(tline, false);
5116 lfmt->line(LIST_MACRO, p);
5117 nasm_free(p);
5118 break;
5120 line = read_line();
5121 if (line) { /* from the current input file */
5122 line = prepreproc(line);
5123 tline = tokenize(line);
5124 nasm_free(line);
5125 break;
5128 * The current file has ended; work down the istk
5131 Include *i = istk;
5132 fclose(i->fp);
5133 if (i->conds) {
5134 /* nasm_error can't be conditionally suppressed */
5135 nasm_fatal(0,
5136 "expected `%%endif' before end of file");
5138 /* only set line and file name if there's a next node */
5139 if (i->next)
5140 src_set(i->lineno, i->fname);
5141 istk = i->next;
5142 lfmt->downlevel(LIST_INCLUDE);
5143 nasm_free(i);
5144 if (!istk) {
5145 line = NULL;
5146 goto done;
5148 if (istk->expansion && istk->expansion->finishes)
5149 break;
5154 * We must expand MMacro parameters and MMacro-local labels
5155 * _before_ we plunge into directive processing, to cope
5156 * with things like `%define something %1' such as STRUC
5157 * uses. Unless we're _defining_ a MMacro, in which case
5158 * those tokens should be left alone to go into the
5159 * definition; and unless we're in a non-emitting
5160 * condition, in which case we don't want to meddle with
5161 * anything.
5163 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5164 && !(istk->mstk && !istk->mstk->in_progress)) {
5165 tline = expand_mmac_params(tline);
5169 * Check the line to see if it's a preprocessor directive.
5171 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5172 if (line)
5173 break; /* Directive generated output */
5174 else
5175 continue;
5176 } else if (defining) {
5178 * We're defining a multi-line macro. We emit nothing
5179 * at all, and just
5180 * shove the tokenized line on to the macro definition.
5182 Line *l = nasm_malloc(sizeof(Line));
5183 l->next = defining->expansion;
5184 l->first = tline;
5185 l->finishes = NULL;
5186 defining->expansion = l;
5187 continue;
5188 } else if (istk->conds && !emitting(istk->conds->state)) {
5190 * We're in a non-emitting branch of a condition block.
5191 * Emit nothing at all, not even a blank line: when we
5192 * emerge from the condition we'll give a line-number
5193 * directive so we keep our place correctly.
5195 free_tlist(tline);
5196 continue;
5197 } else if (istk->mstk && !istk->mstk->in_progress) {
5199 * We're in a %rep block which has been terminated, so
5200 * we're walking through to the %endrep without
5201 * emitting anything. Emit nothing at all, not even a
5202 * blank line: when we emerge from the %rep block we'll
5203 * give a line-number directive so we keep our place
5204 * correctly.
5206 free_tlist(tline);
5207 continue;
5208 } else {
5209 tline = expand_smacro(tline);
5210 if (!expand_mmacro(tline)) {
5212 * De-tokenize the line again, and emit it.
5214 line = detoken(tline, true);
5215 free_tlist(tline);
5216 break;
5217 } else {
5218 continue; /* expand_mmacro calls free_tlist */
5223 done:
5224 nasm_set_verror(real_verror);
5225 return line;
5228 static void pp_cleanup(int pass)
5230 real_verror = nasm_set_verror(pp_verror);
5232 if (defining) {
5233 if (defining->name) {
5234 nasm_error(ERR_NONFATAL,
5235 "end of file while still defining macro `%s'",
5236 defining->name);
5237 } else {
5238 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5241 free_mmacro(defining);
5242 defining = NULL;
5245 nasm_set_verror(real_verror);
5247 while (cstk)
5248 ctx_pop();
5249 free_macros();
5250 while (istk) {
5251 Include *i = istk;
5252 istk = istk->next;
5253 fclose(i->fp);
5254 nasm_free(i);
5256 while (cstk)
5257 ctx_pop();
5258 src_set_fname(NULL);
5259 if (pass == 0) {
5260 IncPath *i;
5261 free_llist(predef);
5262 predef = NULL;
5263 delete_Blocks();
5264 freeTokens = NULL;
5265 while ((i = ipath)) {
5266 ipath = i->next;
5267 if (i->path)
5268 nasm_free(i->path);
5269 nasm_free(i);
5274 static void pp_include_path(char *path)
5276 IncPath *i;
5278 i = nasm_malloc(sizeof(IncPath));
5279 i->path = path ? nasm_strdup(path) : NULL;
5280 i->next = NULL;
5282 if (ipath) {
5283 IncPath *j = ipath;
5284 while (j->next)
5285 j = j->next;
5286 j->next = i;
5287 } else {
5288 ipath = i;
5292 static void pp_pre_include(char *fname)
5294 Token *inc, *space, *name;
5295 Line *l;
5297 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5298 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5299 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5301 l = nasm_malloc(sizeof(Line));
5302 l->next = predef;
5303 l->first = inc;
5304 l->finishes = NULL;
5305 predef = l;
5308 static void pp_pre_define(char *definition)
5310 Token *def, *space;
5311 Line *l;
5312 char *equals;
5314 real_verror = nasm_set_verror(pp_verror);
5316 equals = strchr(definition, '=');
5317 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5318 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5319 if (equals)
5320 *equals = ' ';
5321 space->next = tokenize(definition);
5322 if (equals)
5323 *equals = '=';
5325 if (space->next->type != TOK_PREPROC_ID &&
5326 space->next->type != TOK_ID)
5327 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5329 l = nasm_malloc(sizeof(Line));
5330 l->next = predef;
5331 l->first = def;
5332 l->finishes = NULL;
5333 predef = l;
5335 nasm_set_verror(real_verror);
5338 static void pp_pre_undefine(char *definition)
5340 Token *def, *space;
5341 Line *l;
5343 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5344 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5345 space->next = tokenize(definition);
5347 l = nasm_malloc(sizeof(Line));
5348 l->next = predef;
5349 l->first = def;
5350 l->finishes = NULL;
5351 predef = l;
5354 static void pp_add_stdmac(macros_t *macros)
5356 macros_t **mp;
5358 /* Find the end of the list and avoid duplicates */
5359 for (mp = stdmacros; *mp; mp++) {
5360 if (*mp == macros)
5361 return; /* Nothing to do */
5364 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5366 *mp = macros;
5369 static void pp_extra_stdmac(macros_t *macros)
5371 extrastdmac = macros;
5374 static void make_tok_num(Token * tok, int64_t val)
5376 char numbuf[32];
5377 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5378 tok->text = nasm_strdup(numbuf);
5379 tok->type = TOK_NUMBER;
5382 static void pp_list_one_macro(MMacro *m, int severity)
5384 if (!m)
5385 return;
5387 /* We need to print the next_active list in reverse order */
5388 pp_list_one_macro(m->next_active, severity);
5390 if (m->name && !m->nolist) {
5391 src_set(m->xline + m->lineno, m->fname);
5392 nasm_error(severity, "... from macro `%s' defined here", m->name);
5396 static void pp_error_list_macros(int severity)
5398 int32_t saved_line;
5399 const char *saved_fname = NULL;
5401 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5402 src_get(&saved_line, &saved_fname);
5404 if (istk)
5405 pp_list_one_macro(istk->mstk, severity);
5407 src_set(saved_line, saved_fname);
5410 const struct preproc_ops nasmpp = {
5411 pp_init,
5412 pp_reset,
5413 pp_getline,
5414 pp_cleanup,
5415 pp_extra_stdmac,
5416 pp_pre_define,
5417 pp_pre_undefine,
5418 pp_pre_include,
5419 pp_include_path,
5420 pp_error_list_macros,