Revert "nasmlib/file.c: Windows _chsize_s() *returns* errno"
[nasm.git] / preproc.c
blob08e3ad5a45fab6b8cd7c9a062e7731290000fc52
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... */
160 /* Store the definition of a multi-line macro, as defined in a
161 * previous recursive macro expansion.
163 struct MMacroInvocation {
164 MMacroInvocation *prev; /* previous invocation */
165 Token **params; /* actual parameters */
166 Token *iline; /* invocation line */
167 unsigned int nparam, rotate;
168 int *paramlen;
169 uint64_t unique;
170 uint64_t condcnt;
175 * The context stack is composed of a linked list of these.
177 struct Context {
178 Context *next;
179 char *name;
180 struct hash_table localmac;
181 uint32_t number;
185 * This is the internal form which we break input lines up into.
186 * Typically stored in linked lists.
188 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
189 * necessarily used as-is, but is intended to denote the number of
190 * the substituted parameter. So in the definition
192 * %define a(x,y) ( (x) & ~(y) )
194 * the token representing `x' will have its type changed to
195 * TOK_SMAC_PARAM, but the one representing `y' will be
196 * TOK_SMAC_PARAM+1.
198 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
199 * which doesn't need quotes around it. Used in the pre-include
200 * mechanism as an alternative to trying to find a sensible type of
201 * quote to use on the filename we were passed.
203 enum pp_token_type {
204 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
205 TOK_PREPROC_ID, TOK_STRING,
206 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
207 TOK_INTERNAL_STRING,
208 TOK_PREPROC_Q, TOK_PREPROC_QQ,
209 TOK_PASTE, /* %+ */
210 TOK_INDIRECT, /* %[...] */
211 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
212 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
215 #define PP_CONCAT_MASK(x) (1 << (x))
216 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
218 struct tokseq_match {
219 int mask_head;
220 int mask_tail;
223 struct Token {
224 Token *next;
225 char *text;
226 union {
227 SMacro *mac; /* associated macro for TOK_SMAC_END */
228 size_t len; /* scratch length field */
229 } a; /* Auxiliary data */
230 enum pp_token_type type;
234 * Multi-line macro definitions are stored as a linked list of
235 * these, which is essentially a container to allow several linked
236 * lists of Tokens.
238 * Note that in this module, linked lists are treated as stacks
239 * wherever possible. For this reason, Lines are _pushed_ on to the
240 * `expansion' field in MMacro structures, so that the linked list,
241 * if walked, would give the macro lines in reverse order; this
242 * means that we can walk the list when expanding a macro, and thus
243 * push the lines on to the `expansion' field in _istk_ in reverse
244 * order (so that when popped back off they are in the right
245 * order). It may seem cockeyed, and it relies on my design having
246 * an even number of steps in, but it works...
248 * Some of these structures, rather than being actual lines, are
249 * markers delimiting the end of the expansion of a given macro.
250 * This is for use in the cycle-tracking and %rep-handling code.
251 * Such structures have `finishes' non-NULL, and `first' NULL. All
252 * others have `finishes' NULL, but `first' may still be NULL if
253 * the line is blank.
255 struct Line {
256 Line *next;
257 MMacro *finishes;
258 Token *first;
262 * To handle an arbitrary level of file inclusion, we maintain a
263 * stack (ie linked list) of these things.
265 struct Include {
266 Include *next;
267 FILE *fp;
268 Cond *conds;
269 Line *expansion;
270 char *fname;
271 int lineno, lineinc;
272 MMacro *mstk; /* stack of active macros/reps */
276 * Include search path. This is simply a list of strings which get
277 * prepended, in turn, to the name of an include file, in an
278 * attempt to find the file if it's not in the current directory.
280 struct IncPath {
281 IncPath *next;
282 char *path;
286 * Conditional assembly: we maintain a separate stack of these for
287 * each level of file inclusion. (The only reason we keep the
288 * stacks separate is to ensure that a stray `%endif' in a file
289 * included from within the true branch of a `%if' won't terminate
290 * it and cause confusion: instead, rightly, it'll cause an error.)
292 struct Cond {
293 Cond *next;
294 int state;
296 enum {
298 * These states are for use just after %if or %elif: IF_TRUE
299 * means the condition has evaluated to truth so we are
300 * currently emitting, whereas IF_FALSE means we are not
301 * currently emitting but will start doing so if a %else comes
302 * up. In these states, all directives are admissible: %elif,
303 * %else and %endif. (And of course %if.)
305 COND_IF_TRUE, COND_IF_FALSE,
307 * These states come up after a %else: ELSE_TRUE means we're
308 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
309 * any %elif or %else will cause an error.
311 COND_ELSE_TRUE, COND_ELSE_FALSE,
313 * These states mean that we're not emitting now, and also that
314 * nothing until %endif will be emitted at all. COND_DONE is
315 * used when we've had our moment of emission
316 * and have now started seeing %elifs. COND_NEVER is used when
317 * the condition construct in question is contained within a
318 * non-emitting branch of a larger condition construct,
319 * or if there is an error.
321 COND_DONE, COND_NEVER
323 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
326 * These defines are used as the possible return values for do_directive
328 #define NO_DIRECTIVE_FOUND 0
329 #define DIRECTIVE_FOUND 1
332 * This define sets the upper limit for smacro and recursive mmacro
333 * expansions
335 #define DEADMAN_LIMIT (1 << 20)
337 /* max reps */
338 #define REP_LIMIT ((INT64_C(1) << 62))
341 * Condition codes. Note that we use c_ prefix not C_ because C_ is
342 * used in nasm.h for the "real" condition codes. At _this_ level,
343 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
344 * ones, so we need a different enum...
346 static const char * const conditions[] = {
347 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
348 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
349 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
351 enum pp_conds {
352 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
353 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
354 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
355 c_none = -1
357 static const enum pp_conds inverse_ccs[] = {
358 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
359 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,
360 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
364 * Directive names.
366 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
367 static int is_condition(enum preproc_token arg)
369 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
372 /* For TASM compatibility we need to be able to recognise TASM compatible
373 * conditional compilation directives. Using the NASM pre-processor does
374 * not work, so we look for them specifically from the following list and
375 * then jam in the equivalent NASM directive into the input stream.
378 enum {
379 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
380 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
383 static const char * const tasm_directives[] = {
384 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
385 "ifndef", "include", "local"
388 static int StackSize = 4;
389 static char *StackPointer = "ebp";
390 static int ArgOffset = 8;
391 static int LocalOffset = 0;
393 static Context *cstk;
394 static Include *istk;
395 static IncPath *ipath = NULL;
397 static int pass; /* HACK: pass 0 = generate dependencies only */
398 static StrList **dephead, **deptail; /* Dependency list */
400 static uint64_t unique; /* unique identifier numbers */
402 static Line *predef = NULL;
403 static bool do_predef;
406 * The current set of multi-line macros we have defined.
408 static struct hash_table mmacros;
411 * The current set of single-line macros we have defined.
413 static struct hash_table smacros;
416 * The multi-line macro we are currently defining, or the %rep
417 * block we are currently reading, if any.
419 static MMacro *defining;
421 static uint64_t nested_mac_count;
422 static uint64_t nested_rep_count;
425 * The number of macro parameters to allocate space for at a time.
427 #define PARAM_DELTA 16
430 * The standard macro set: defined in macros.c in the array nasm_stdmac.
431 * This gives our position in the macro set, when we're processing it.
433 static macros_t *stdmacpos;
436 * The extra standard macros that come from the object format, if
437 * any.
439 static macros_t *extrastdmac = NULL;
440 static bool any_extrastdmac;
443 * Tokens are allocated in blocks to improve speed
445 #define TOKEN_BLOCKSIZE 4096
446 static Token *freeTokens = NULL;
447 struct Blocks {
448 Blocks *next;
449 void *chunk;
452 static Blocks blocks = { NULL, NULL };
455 * Forward declarations.
457 static Token *expand_mmac_params(Token * tline);
458 static Token *expand_smacro(Token * tline);
459 static Token *expand_id(Token * tline);
460 static Context *get_ctx(const char *name, const char **namep);
461 static void make_tok_num(Token * tok, int64_t val);
462 static void pp_verror(int severity, const char *fmt, va_list ap);
463 static vefunc real_verror;
464 static void *new_Block(size_t size);
465 static void delete_Blocks(void);
466 static Token *new_Token(Token * next, enum pp_token_type type,
467 const char *text, int txtlen);
468 static Token *delete_Token(Token * t);
471 * Macros for safe checking of token pointers, avoid *(NULL)
473 #define tok_type_(x,t) ((x) && (x)->type == (t))
474 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
475 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
476 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
479 * nasm_unquote with error if the string contains NUL characters.
480 * If the string contains NUL characters, issue an error and return
481 * the C len, i.e. truncate at the NUL.
483 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
485 size_t len = nasm_unquote(qstr, NULL);
486 size_t clen = strlen(qstr);
488 if (len != clen)
489 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
490 pp_directives[directive]);
492 return clen;
496 * In-place reverse a list of tokens.
498 static Token *reverse_tokens(Token *t)
500 Token *prev = NULL;
501 Token *next;
503 while (t) {
504 next = t->next;
505 t->next = prev;
506 prev = t;
507 t = next;
510 return prev;
514 * Handle TASM specific directives, which do not contain a % in
515 * front of them. We do it here because I could not find any other
516 * place to do it for the moment, and it is a hack (ideally it would
517 * be nice to be able to use the NASM pre-processor to do it).
519 static char *check_tasm_directive(char *line)
521 int32_t i, j, k, m, len;
522 char *p, *q, *oldline, oldchar;
524 p = nasm_skip_spaces(line);
526 /* Binary search for the directive name */
527 i = -1;
528 j = ARRAY_SIZE(tasm_directives);
529 q = nasm_skip_word(p);
530 len = q - p;
531 if (len) {
532 oldchar = p[len];
533 p[len] = 0;
534 while (j - i > 1) {
535 k = (j + i) / 2;
536 m = nasm_stricmp(p, tasm_directives[k]);
537 if (m == 0) {
538 /* We have found a directive, so jam a % in front of it
539 * so that NASM will then recognise it as one if it's own.
541 p[len] = oldchar;
542 len = strlen(p);
543 oldline = line;
544 line = nasm_malloc(len + 2);
545 line[0] = '%';
546 if (k == TM_IFDIFI) {
548 * NASM does not recognise IFDIFI, so we convert
549 * it to %if 0. This is not used in NASM
550 * compatible code, but does need to parse for the
551 * TASM macro package.
553 strcpy(line + 1, "if 0");
554 } else {
555 memcpy(line + 1, p, len + 1);
557 nasm_free(oldline);
558 return line;
559 } else if (m < 0) {
560 j = k;
561 } else
562 i = k;
564 p[len] = oldchar;
566 return line;
570 * The pre-preprocessing stage... This function translates line
571 * number indications as they emerge from GNU cpp (`# lineno "file"
572 * flags') into NASM preprocessor line number indications (`%line
573 * lineno file').
575 static char *prepreproc(char *line)
577 int lineno, fnlen;
578 char *fname, *oldline;
580 if (line[0] == '#' && line[1] == ' ') {
581 oldline = line;
582 fname = oldline + 2;
583 lineno = atoi(fname);
584 fname += strspn(fname, "0123456789 ");
585 if (*fname == '"')
586 fname++;
587 fnlen = strcspn(fname, "\"");
588 line = nasm_malloc(20 + fnlen);
589 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
590 nasm_free(oldline);
592 if (tasm_compatible_mode)
593 return check_tasm_directive(line);
594 return line;
598 * Free a linked list of tokens.
600 static void free_tlist(Token * list)
602 while (list)
603 list = delete_Token(list);
607 * Free a linked list of lines.
609 static void free_llist(Line * list)
611 Line *l, *tmp;
612 list_for_each_safe(l, tmp, list) {
613 free_tlist(l->first);
614 nasm_free(l);
619 * Free an MMacro
621 static void free_mmacro(MMacro * m)
623 nasm_free(m->name);
624 free_tlist(m->dlist);
625 nasm_free(m->defaults);
626 free_llist(m->expansion);
627 nasm_free(m);
631 * Free all currently defined macros, and free the hash tables
633 static void free_smacro_table(struct hash_table *smt)
635 SMacro *s, *tmp;
636 const char *key;
637 struct hash_tbl_node *it = NULL;
639 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
640 nasm_free((void *)key);
641 list_for_each_safe(s, tmp, s) {
642 nasm_free(s->name);
643 free_tlist(s->expansion);
644 nasm_free(s);
647 hash_free(smt);
650 static void free_mmacro_table(struct hash_table *mmt)
652 MMacro *m, *tmp;
653 const char *key;
654 struct hash_tbl_node *it = NULL;
656 it = NULL;
657 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
658 nasm_free((void *)key);
659 list_for_each_safe(m ,tmp, m)
660 free_mmacro(m);
662 hash_free(mmt);
665 static void free_macros(void)
667 free_smacro_table(&smacros);
668 free_mmacro_table(&mmacros);
672 * Initialize the hash tables
674 static void init_macros(void)
676 hash_init(&smacros, HASH_LARGE);
677 hash_init(&mmacros, HASH_LARGE);
681 * Pop the context stack.
683 static void ctx_pop(void)
685 Context *c = cstk;
687 cstk = cstk->next;
688 free_smacro_table(&c->localmac);
689 nasm_free(c->name);
690 nasm_free(c);
694 * Search for a key in the hash index; adding it if necessary
695 * (in which case we initialize the data pointer to NULL.)
697 static void **
698 hash_findi_add(struct hash_table *hash, const char *str)
700 struct hash_insert hi;
701 void **r;
702 char *strx;
704 r = hash_findi(hash, str, &hi);
705 if (r)
706 return r;
708 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
709 return hash_add(&hi, strx, NULL);
713 * Like hash_findi, but returns the data element rather than a pointer
714 * to it. Used only when not adding a new element, hence no third
715 * argument.
717 static void *
718 hash_findix(struct hash_table *hash, const char *str)
720 void **p;
722 p = hash_findi(hash, str, NULL);
723 return p ? *p : NULL;
727 * read line from standart macros set,
728 * if there no more left -- return NULL
730 static char *line_from_stdmac(void)
732 unsigned char c;
733 const unsigned char *p = stdmacpos;
734 char *line, *q;
735 size_t len = 0;
737 if (!stdmacpos)
738 return NULL;
740 while ((c = *p++)) {
741 if (c >= 0x80)
742 len += pp_directives_len[c - 0x80] + 1;
743 else
744 len++;
747 line = nasm_malloc(len + 1);
748 q = line;
749 while ((c = *stdmacpos++)) {
750 if (c >= 0x80) {
751 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
752 q += pp_directives_len[c - 0x80];
753 *q++ = ' ';
754 } else {
755 *q++ = c;
758 stdmacpos = p;
759 *q = '\0';
761 if (!*stdmacpos) {
762 /* This was the last of the standard macro chain... */
763 stdmacpos = NULL;
764 if (any_extrastdmac) {
765 stdmacpos = extrastdmac;
766 any_extrastdmac = false;
767 } else if (do_predef) {
768 Line *pd, *l;
769 Token *head, **tail, *t;
772 * Nasty hack: here we push the contents of
773 * `predef' on to the top-level expansion stack,
774 * since this is the most convenient way to
775 * implement the pre-include and pre-define
776 * features.
778 list_for_each(pd, predef) {
779 head = NULL;
780 tail = &head;
781 list_for_each(t, pd->first) {
782 *tail = new_Token(NULL, t->type, t->text, 0);
783 tail = &(*tail)->next;
786 l = nasm_malloc(sizeof(Line));
787 l->next = istk->expansion;
788 l->first = head;
789 l->finishes = NULL;
791 istk->expansion = l;
793 do_predef = false;
797 return line;
800 static char *read_line(void)
802 unsigned int size, c, next;
803 const unsigned int delta = 512;
804 const unsigned int pad = 8;
805 unsigned int nr_cont = 0;
806 bool cont = false;
807 char *buffer, *p;
809 /* Standart macros set (predefined) goes first */
810 p = line_from_stdmac();
811 if (p)
812 return p;
814 size = delta;
815 p = buffer = nasm_malloc(size);
817 for (;;) {
818 c = fgetc(istk->fp);
819 if ((int)(c) == EOF) {
820 p[0] = 0;
821 break;
824 switch (c) {
825 case '\r':
826 next = fgetc(istk->fp);
827 if (next != '\n')
828 ungetc(next, istk->fp);
829 if (cont) {
830 cont = false;
831 continue;
833 break;
835 case '\n':
836 if (cont) {
837 cont = false;
838 continue;
840 break;
842 case '\\':
843 next = fgetc(istk->fp);
844 ungetc(next, istk->fp);
845 if (next == '\r' || next == '\n') {
846 cont = true;
847 nr_cont++;
848 continue;
850 break;
853 if (c == '\r' || c == '\n') {
854 *p++ = 0;
855 break;
858 if (p >= (buffer + size - pad)) {
859 buffer = nasm_realloc(buffer, size + delta);
860 p = buffer + size - pad;
861 size += delta;
864 *p++ = (unsigned char)c;
867 if (p == buffer) {
868 nasm_free(buffer);
869 return NULL;
872 src_set_linnum(src_get_linnum() + istk->lineinc +
873 (nr_cont * istk->lineinc));
876 * Handle spurious ^Z, which may be inserted into source files
877 * by some file transfer utilities.
879 buffer[strcspn(buffer, "\032")] = '\0';
881 lfmt->line(LIST_READ, buffer);
883 return buffer;
887 * Tokenize a line of text. This is a very simple process since we
888 * don't need to parse the value out of e.g. numeric tokens: we
889 * simply split one string into many.
891 static Token *tokenize(char *line)
893 char c, *p = line;
894 enum pp_token_type type;
895 Token *list = NULL;
896 Token *t, **tail = &list;
898 while (*line) {
899 p = line;
900 if (*p == '%') {
901 p++;
902 if (*p == '+' && !nasm_isdigit(p[1])) {
903 p++;
904 type = TOK_PASTE;
905 } else if (nasm_isdigit(*p) ||
906 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
907 do {
908 p++;
910 while (nasm_isdigit(*p));
911 type = TOK_PREPROC_ID;
912 } else if (*p == '{') {
913 p++;
914 while (*p) {
915 if (*p == '}')
916 break;
917 p[-1] = *p;
918 p++;
920 if (*p != '}')
921 nasm_error(ERR_WARNING | ERR_PASS1,
922 "unterminated %%{ construct");
923 p[-1] = '\0';
924 if (*p)
925 p++;
926 type = TOK_PREPROC_ID;
927 } else if (*p == '[') {
928 int lvl = 1;
929 line += 2; /* Skip the leading %[ */
930 p++;
931 while (lvl && (c = *p++)) {
932 switch (c) {
933 case ']':
934 lvl--;
935 break;
936 case '%':
937 if (*p == '[')
938 lvl++;
939 break;
940 case '\'':
941 case '\"':
942 case '`':
943 p = nasm_skip_string(p - 1) + 1;
944 break;
945 default:
946 break;
949 p--;
950 if (*p)
951 *p++ = '\0';
952 if (lvl)
953 nasm_error(ERR_NONFATAL|ERR_PASS1,
954 "unterminated %%[ construct");
955 type = TOK_INDIRECT;
956 } else if (*p == '?') {
957 type = TOK_PREPROC_Q; /* %? */
958 p++;
959 if (*p == '?') {
960 type = TOK_PREPROC_QQ; /* %?? */
961 p++;
963 } else if (*p == '!') {
964 type = TOK_PREPROC_ID;
965 p++;
966 if (isidchar(*p)) {
967 do {
968 p++;
970 while (isidchar(*p));
971 } else if (*p == '\'' || *p == '\"' || *p == '`') {
972 p = nasm_skip_string(p);
973 if (*p)
974 p++;
975 else
976 nasm_error(ERR_NONFATAL|ERR_PASS1,
977 "unterminated %%! string");
978 } else {
979 /* %! without string or identifier */
980 type = TOK_OTHER; /* Legacy behavior... */
982 } else if (isidchar(*p) ||
983 ((*p == '!' || *p == '%' || *p == '$') &&
984 isidchar(p[1]))) {
985 do {
986 p++;
988 while (isidchar(*p));
989 type = TOK_PREPROC_ID;
990 } else {
991 type = TOK_OTHER;
992 if (*p == '%')
993 p++;
995 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
996 type = TOK_ID;
997 p++;
998 while (*p && isidchar(*p))
999 p++;
1000 } else if (*p == '\'' || *p == '"' || *p == '`') {
1002 * A string token.
1004 type = TOK_STRING;
1005 p = nasm_skip_string(p);
1007 if (*p) {
1008 p++;
1009 } else {
1010 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1011 /* Handling unterminated strings by UNV */
1012 /* type = -1; */
1014 } else if (p[0] == '$' && p[1] == '$') {
1015 type = TOK_OTHER; /* TOKEN_BASE */
1016 p += 2;
1017 } else if (isnumstart(*p)) {
1018 bool is_hex = false;
1019 bool is_float = false;
1020 bool has_e = false;
1021 char c, *r;
1024 * A numeric token.
1027 if (*p == '$') {
1028 p++;
1029 is_hex = true;
1032 for (;;) {
1033 c = *p++;
1035 if (!is_hex && (c == 'e' || c == 'E')) {
1036 has_e = true;
1037 if (*p == '+' || *p == '-') {
1039 * e can only be followed by +/- if it is either a
1040 * prefixed hex number or a floating-point number
1042 p++;
1043 is_float = true;
1045 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1046 is_hex = true;
1047 } else if (c == 'P' || c == 'p') {
1048 is_float = true;
1049 if (*p == '+' || *p == '-')
1050 p++;
1051 } else if (isnumchar(c) || c == '_')
1052 ; /* just advance */
1053 else if (c == '.') {
1055 * we need to deal with consequences of the legacy
1056 * parser, like "1.nolist" being two tokens
1057 * (TOK_NUMBER, TOK_ID) here; at least give it
1058 * a shot for now. In the future, we probably need
1059 * a flex-based scanner with proper pattern matching
1060 * to do it as well as it can be done. Nothing in
1061 * the world is going to help the person who wants
1062 * 0x123.p16 interpreted as two tokens, though.
1064 r = p;
1065 while (*r == '_')
1066 r++;
1068 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1069 (!is_hex && (*r == 'e' || *r == 'E')) ||
1070 (*r == 'p' || *r == 'P')) {
1071 p = r;
1072 is_float = true;
1073 } else
1074 break; /* Terminate the token */
1075 } else
1076 break;
1078 p--; /* Point to first character beyond number */
1080 if (p == line+1 && *line == '$') {
1081 type = TOK_OTHER; /* TOKEN_HERE */
1082 } else {
1083 if (has_e && !is_hex) {
1084 /* 1e13 is floating-point, but 1e13h is not */
1085 is_float = true;
1088 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1090 } else if (nasm_isspace(*p)) {
1091 type = TOK_WHITESPACE;
1092 p = nasm_skip_spaces(p);
1094 * Whitespace just before end-of-line is discarded by
1095 * pretending it's a comment; whitespace just before a
1096 * comment gets lumped into the comment.
1098 if (!*p || *p == ';') {
1099 type = TOK_COMMENT;
1100 while (*p)
1101 p++;
1103 } else if (*p == ';') {
1104 type = TOK_COMMENT;
1105 while (*p)
1106 p++;
1107 } else {
1109 * Anything else is an operator of some kind. We check
1110 * for all the double-character operators (>>, <<, //,
1111 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1112 * else is a single-character operator.
1114 type = TOK_OTHER;
1115 if ((p[0] == '>' && p[1] == '>') ||
1116 (p[0] == '<' && p[1] == '<') ||
1117 (p[0] == '/' && p[1] == '/') ||
1118 (p[0] == '<' && p[1] == '=') ||
1119 (p[0] == '>' && p[1] == '=') ||
1120 (p[0] == '=' && p[1] == '=') ||
1121 (p[0] == '!' && p[1] == '=') ||
1122 (p[0] == '<' && p[1] == '>') ||
1123 (p[0] == '&' && p[1] == '&') ||
1124 (p[0] == '|' && p[1] == '|') ||
1125 (p[0] == '^' && p[1] == '^')) {
1126 p++;
1128 p++;
1131 /* Handling unterminated string by UNV */
1132 /*if (type == -1)
1134 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1135 t->text[p-line] = *line;
1136 tail = &t->next;
1138 else */
1139 if (type != TOK_COMMENT) {
1140 *tail = t = new_Token(NULL, type, line, p - line);
1141 tail = &t->next;
1143 line = p;
1145 return list;
1149 * this function allocates a new managed block of memory and
1150 * returns a pointer to the block. The managed blocks are
1151 * deleted only all at once by the delete_Blocks function.
1153 static void *new_Block(size_t size)
1155 Blocks *b = &blocks;
1157 /* first, get to the end of the linked list */
1158 while (b->next)
1159 b = b->next;
1160 /* now allocate the requested chunk */
1161 b->chunk = nasm_malloc(size);
1163 /* now allocate a new block for the next request */
1164 b->next = nasm_zalloc(sizeof(Blocks));
1165 return b->chunk;
1169 * this function deletes all managed blocks of memory
1171 static void delete_Blocks(void)
1173 Blocks *a, *b = &blocks;
1176 * keep in mind that the first block, pointed to by blocks
1177 * is a static and not dynamically allocated, so we don't
1178 * free it.
1180 while (b) {
1181 if (b->chunk)
1182 nasm_free(b->chunk);
1183 a = b;
1184 b = b->next;
1185 if (a != &blocks)
1186 nasm_free(a);
1188 memset(&blocks, 0, sizeof(blocks));
1192 * this function creates a new Token and passes a pointer to it
1193 * back to the caller. It sets the type and text elements, and
1194 * also the a.mac and next elements to NULL.
1196 static Token *new_Token(Token * next, enum pp_token_type type,
1197 const char *text, int txtlen)
1199 Token *t;
1200 int i;
1202 if (!freeTokens) {
1203 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1204 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1205 freeTokens[i].next = &freeTokens[i + 1];
1206 freeTokens[i].next = NULL;
1208 t = freeTokens;
1209 freeTokens = t->next;
1210 t->next = next;
1211 t->a.mac = NULL;
1212 t->type = type;
1213 if (type == TOK_WHITESPACE || !text) {
1214 t->text = NULL;
1215 } else {
1216 if (txtlen == 0)
1217 txtlen = strlen(text);
1218 t->text = nasm_malloc(txtlen+1);
1219 memcpy(t->text, text, txtlen);
1220 t->text[txtlen] = '\0';
1222 return t;
1225 static Token *delete_Token(Token * t)
1227 Token *next = t->next;
1228 nasm_free(t->text);
1229 t->next = freeTokens;
1230 freeTokens = t;
1231 return next;
1235 * Convert a line of tokens back into text.
1236 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1237 * will be transformed into ..@ctxnum.xxx
1239 static char *detoken(Token * tlist, bool expand_locals)
1241 Token *t;
1242 char *line, *p;
1243 const char *q;
1244 int len = 0;
1246 list_for_each(t, tlist) {
1247 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1248 char *v;
1249 char *q = t->text;
1251 v = t->text + 2;
1252 if (*v == '\'' || *v == '\"' || *v == '`') {
1253 size_t len = nasm_unquote(v, NULL);
1254 size_t clen = strlen(v);
1256 if (len != clen) {
1257 nasm_error(ERR_NONFATAL | ERR_PASS1,
1258 "NUL character in %%! string");
1259 v = NULL;
1263 if (v) {
1264 char *p = getenv(v);
1265 if (!p) {
1266 nasm_error(ERR_NONFATAL | ERR_PASS1,
1267 "nonexistent environment variable `%s'", v);
1268 p = "";
1270 t->text = nasm_strdup(p);
1272 nasm_free(q);
1275 /* Expand local macros here and not during preprocessing */
1276 if (expand_locals &&
1277 t->type == TOK_PREPROC_ID && t->text &&
1278 t->text[0] == '%' && t->text[1] == '$') {
1279 const char *q;
1280 char *p;
1281 Context *ctx = get_ctx(t->text, &q);
1282 if (ctx) {
1283 char buffer[40];
1284 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1285 p = nasm_strcat(buffer, q);
1286 nasm_free(t->text);
1287 t->text = p;
1290 if (t->type == TOK_WHITESPACE)
1291 len++;
1292 else if (t->text)
1293 len += strlen(t->text);
1296 p = line = nasm_malloc(len + 1);
1298 list_for_each(t, tlist) {
1299 if (t->type == TOK_WHITESPACE) {
1300 *p++ = ' ';
1301 } else if (t->text) {
1302 q = t->text;
1303 while (*q)
1304 *p++ = *q++;
1307 *p = '\0';
1309 return line;
1313 * A scanner, suitable for use by the expression evaluator, which
1314 * operates on a line of Tokens. Expects a pointer to a pointer to
1315 * the first token in the line to be passed in as its private_data
1316 * field.
1318 * FIX: This really needs to be unified with stdscan.
1320 static int ppscan(void *private_data, struct tokenval *tokval)
1322 Token **tlineptr = private_data;
1323 Token *tline;
1324 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1326 do {
1327 tline = *tlineptr;
1328 *tlineptr = tline ? tline->next : NULL;
1329 } while (tline && (tline->type == TOK_WHITESPACE ||
1330 tline->type == TOK_COMMENT));
1332 if (!tline)
1333 return tokval->t_type = TOKEN_EOS;
1335 tokval->t_charptr = tline->text;
1337 if (tline->text[0] == '$' && !tline->text[1])
1338 return tokval->t_type = TOKEN_HERE;
1339 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1340 return tokval->t_type = TOKEN_BASE;
1342 if (tline->type == TOK_ID) {
1343 p = tokval->t_charptr = tline->text;
1344 if (p[0] == '$') {
1345 tokval->t_charptr++;
1346 return tokval->t_type = TOKEN_ID;
1349 for (r = p, s = ourcopy; *r; r++) {
1350 if (r >= p+MAX_KEYWORD)
1351 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1352 *s++ = nasm_tolower(*r);
1354 *s = '\0';
1355 /* right, so we have an identifier sitting in temp storage. now,
1356 * is it actually a register or instruction name, or what? */
1357 return nasm_token_hash(ourcopy, tokval);
1360 if (tline->type == TOK_NUMBER) {
1361 bool rn_error;
1362 tokval->t_integer = readnum(tline->text, &rn_error);
1363 tokval->t_charptr = tline->text;
1364 if (rn_error)
1365 return tokval->t_type = TOKEN_ERRNUM;
1366 else
1367 return tokval->t_type = TOKEN_NUM;
1370 if (tline->type == TOK_FLOAT) {
1371 return tokval->t_type = TOKEN_FLOAT;
1374 if (tline->type == TOK_STRING) {
1375 char bq, *ep;
1377 bq = tline->text[0];
1378 tokval->t_charptr = tline->text;
1379 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1381 if (ep[0] != bq || ep[1] != '\0')
1382 return tokval->t_type = TOKEN_ERRSTR;
1383 else
1384 return tokval->t_type = TOKEN_STR;
1387 if (tline->type == TOK_OTHER) {
1388 if (!strcmp(tline->text, "<<"))
1389 return tokval->t_type = TOKEN_SHL;
1390 if (!strcmp(tline->text, ">>"))
1391 return tokval->t_type = TOKEN_SHR;
1392 if (!strcmp(tline->text, "//"))
1393 return tokval->t_type = TOKEN_SDIV;
1394 if (!strcmp(tline->text, "%%"))
1395 return tokval->t_type = TOKEN_SMOD;
1396 if (!strcmp(tline->text, "=="))
1397 return tokval->t_type = TOKEN_EQ;
1398 if (!strcmp(tline->text, "<>"))
1399 return tokval->t_type = TOKEN_NE;
1400 if (!strcmp(tline->text, "!="))
1401 return tokval->t_type = TOKEN_NE;
1402 if (!strcmp(tline->text, "<="))
1403 return tokval->t_type = TOKEN_LE;
1404 if (!strcmp(tline->text, ">="))
1405 return tokval->t_type = TOKEN_GE;
1406 if (!strcmp(tline->text, "&&"))
1407 return tokval->t_type = TOKEN_DBL_AND;
1408 if (!strcmp(tline->text, "^^"))
1409 return tokval->t_type = TOKEN_DBL_XOR;
1410 if (!strcmp(tline->text, "||"))
1411 return tokval->t_type = TOKEN_DBL_OR;
1415 * We have no other options: just return the first character of
1416 * the token text.
1418 return tokval->t_type = tline->text[0];
1422 * Compare a string to the name of an existing macro; this is a
1423 * simple wrapper which calls either strcmp or nasm_stricmp
1424 * depending on the value of the `casesense' parameter.
1426 static int mstrcmp(const char *p, const char *q, bool casesense)
1428 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1432 * Compare a string to the name of an existing macro; this is a
1433 * simple wrapper which calls either strcmp or nasm_stricmp
1434 * depending on the value of the `casesense' parameter.
1436 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1438 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1442 * Return the Context structure associated with a %$ token. Return
1443 * NULL, having _already_ reported an error condition, if the
1444 * context stack isn't deep enough for the supplied number of $
1445 * signs.
1447 * If "namep" is non-NULL, set it to the pointer to the macro name
1448 * tail, i.e. the part beyond %$...
1450 static Context *get_ctx(const char *name, const char **namep)
1452 Context *ctx;
1453 int i;
1455 if (namep)
1456 *namep = name;
1458 if (!name || name[0] != '%' || name[1] != '$')
1459 return NULL;
1461 if (!cstk) {
1462 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1463 return NULL;
1466 name += 2;
1467 ctx = cstk;
1468 i = 0;
1469 while (ctx && *name == '$') {
1470 name++;
1471 i++;
1472 ctx = ctx->next;
1474 if (!ctx) {
1475 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1476 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1477 return NULL;
1480 if (namep)
1481 *namep = name;
1483 return ctx;
1487 * Check to see if a file is already in a string list
1489 static bool in_list(const StrList *list, const char *str)
1491 while (list) {
1492 if (!strcmp(list->str, str))
1493 return true;
1494 list = list->next;
1496 return false;
1500 * Open an include file. This routine must always return a valid
1501 * file pointer if it returns - it's responsible for throwing an
1502 * ERR_FATAL and bombing out completely if not. It should also try
1503 * the include path one by one until it finds the file or reaches
1504 * the end of the path.
1506 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1507 bool missing_ok, const char *mode)
1509 FILE *fp;
1510 char *prefix = "";
1511 IncPath *ip = ipath;
1512 int len = strlen(file);
1513 size_t prefix_len = 0;
1514 StrList *sl;
1516 while (1) {
1517 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1518 memcpy(sl->str, prefix, prefix_len);
1519 memcpy(sl->str+prefix_len, file, len+1);
1520 fp = fopen(sl->str, mode);
1521 if (fp && dhead && !in_list(*dhead, sl->str)) {
1522 sl->next = NULL;
1523 **dtail = sl;
1524 *dtail = &sl->next;
1525 } else {
1526 nasm_free(sl);
1528 if (fp)
1529 return fp;
1530 if (!ip) {
1531 if (!missing_ok)
1532 break;
1533 prefix = NULL;
1534 } else {
1535 prefix = ip->path;
1536 ip = ip->next;
1538 if (prefix) {
1539 prefix_len = strlen(prefix);
1540 } else {
1541 /* -MG given and file not found */
1542 if (dhead && !in_list(*dhead, file)) {
1543 sl = nasm_malloc(len+1+sizeof sl->next);
1544 sl->next = NULL;
1545 strcpy(sl->str, file);
1546 **dtail = sl;
1547 *dtail = &sl->next;
1549 return NULL;
1553 nasm_error(ERR_FATAL, "unable to open include file `%s'", file);
1554 return NULL;
1558 * Opens an include or input file. Public version, for use by modules
1559 * that get a file:lineno pair and need to look at the file again
1560 * (e.g. the CodeView debug backend). Returns NULL on failure.
1562 FILE *pp_input_fopen(const char *filename, const char *mode)
1564 FILE *fp;
1565 StrList *xsl = NULL;
1566 StrList **xst = &xsl;
1568 fp = inc_fopen(filename, &xsl, &xst, true, mode);
1569 if (xsl)
1570 nasm_free(xsl);
1571 return fp;
1575 * Determine if we should warn on defining a single-line macro of
1576 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1577 * return true if _any_ single-line macro of that name is defined.
1578 * Otherwise, will return true if a single-line macro with either
1579 * `nparam' or no parameters is defined.
1581 * If a macro with precisely the right number of parameters is
1582 * defined, or nparam is -1, the address of the definition structure
1583 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1584 * is NULL, no action will be taken regarding its contents, and no
1585 * error will occur.
1587 * Note that this is also called with nparam zero to resolve
1588 * `ifdef'.
1590 * If you already know which context macro belongs to, you can pass
1591 * the context pointer as first parameter; if you won't but name begins
1592 * with %$ the context will be automatically computed. If all_contexts
1593 * is true, macro will be searched in outer contexts as well.
1595 static bool
1596 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1597 bool nocase)
1599 struct hash_table *smtbl;
1600 SMacro *m;
1602 if (ctx) {
1603 smtbl = &ctx->localmac;
1604 } else if (name[0] == '%' && name[1] == '$') {
1605 if (cstk)
1606 ctx = get_ctx(name, &name);
1607 if (!ctx)
1608 return false; /* got to return _something_ */
1609 smtbl = &ctx->localmac;
1610 } else {
1611 smtbl = &smacros;
1613 m = (SMacro *) hash_findix(smtbl, name);
1615 while (m) {
1616 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1617 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1618 if (defn) {
1619 if (nparam == (int) m->nparam || nparam == -1)
1620 *defn = m;
1621 else
1622 *defn = NULL;
1624 return true;
1626 m = m->next;
1629 return false;
1633 * Count and mark off the parameters in a multi-line macro call.
1634 * This is called both from within the multi-line macro expansion
1635 * code, and also to mark off the default parameters when provided
1636 * in a %macro definition line.
1638 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1640 int paramsize, brace;
1642 *nparam = paramsize = 0;
1643 *params = NULL;
1644 while (t) {
1645 /* +1: we need space for the final NULL */
1646 if (*nparam+1 >= paramsize) {
1647 paramsize += PARAM_DELTA;
1648 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1650 skip_white_(t);
1651 brace = 0;
1652 if (tok_is_(t, "{"))
1653 brace++;
1654 (*params)[(*nparam)++] = t;
1655 if (brace) {
1656 while (brace && (t = t->next) != NULL) {
1657 if (tok_is_(t, "{"))
1658 brace++;
1659 else if (tok_is_(t, "}"))
1660 brace--;
1663 if (t) {
1665 * Now we've found the closing brace, look further
1666 * for the comma.
1668 t = t->next;
1669 skip_white_(t);
1670 if (tok_isnt_(t, ",")) {
1671 nasm_error(ERR_NONFATAL,
1672 "braces do not enclose all of macro parameter");
1673 while (tok_isnt_(t, ","))
1674 t = t->next;
1677 } else {
1678 while (tok_isnt_(t, ","))
1679 t = t->next;
1681 if (t) { /* got a comma/brace */
1682 t = t->next; /* eat the comma */
1688 * Determine whether one of the various `if' conditions is true or
1689 * not.
1691 * We must free the tline we get passed.
1693 static bool if_condition(Token * tline, enum preproc_token ct)
1695 enum pp_conditional i = PP_COND(ct);
1696 bool j;
1697 Token *t, *tt, **tptr, *origline;
1698 struct tokenval tokval;
1699 expr *evalresult;
1700 enum pp_token_type needtype;
1701 char *p;
1703 origline = tline;
1705 switch (i) {
1706 case PPC_IFCTX:
1707 j = false; /* have we matched yet? */
1708 while (true) {
1709 skip_white_(tline);
1710 if (!tline)
1711 break;
1712 if (tline->type != TOK_ID) {
1713 nasm_error(ERR_NONFATAL,
1714 "`%s' expects context identifiers", pp_directives[ct]);
1715 free_tlist(origline);
1716 return -1;
1718 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1719 j = true;
1720 tline = tline->next;
1722 break;
1724 case PPC_IFDEF:
1725 j = false; /* have we matched yet? */
1726 while (tline) {
1727 skip_white_(tline);
1728 if (!tline || (tline->type != TOK_ID &&
1729 (tline->type != TOK_PREPROC_ID ||
1730 tline->text[1] != '$'))) {
1731 nasm_error(ERR_NONFATAL,
1732 "`%s' expects macro identifiers", pp_directives[ct]);
1733 goto fail;
1735 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1736 j = true;
1737 tline = tline->next;
1739 break;
1741 case PPC_IFENV:
1742 tline = expand_smacro(tline);
1743 j = false; /* have we matched yet? */
1744 while (tline) {
1745 skip_white_(tline);
1746 if (!tline || (tline->type != TOK_ID &&
1747 tline->type != TOK_STRING &&
1748 (tline->type != TOK_PREPROC_ID ||
1749 tline->text[1] != '!'))) {
1750 nasm_error(ERR_NONFATAL,
1751 "`%s' expects environment variable names",
1752 pp_directives[ct]);
1753 goto fail;
1755 p = tline->text;
1756 if (tline->type == TOK_PREPROC_ID)
1757 p += 2; /* Skip leading %! */
1758 if (*p == '\'' || *p == '\"' || *p == '`')
1759 nasm_unquote_cstr(p, ct);
1760 if (getenv(p))
1761 j = true;
1762 tline = tline->next;
1764 break;
1766 case PPC_IFIDN:
1767 case PPC_IFIDNI:
1768 tline = expand_smacro(tline);
1769 t = tt = tline;
1770 while (tok_isnt_(tt, ","))
1771 tt = tt->next;
1772 if (!tt) {
1773 nasm_error(ERR_NONFATAL,
1774 "`%s' expects two comma-separated arguments",
1775 pp_directives[ct]);
1776 goto fail;
1778 tt = tt->next;
1779 j = true; /* assume equality unless proved not */
1780 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1781 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1782 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1783 pp_directives[ct]);
1784 goto fail;
1786 if (t->type == TOK_WHITESPACE) {
1787 t = t->next;
1788 continue;
1790 if (tt->type == TOK_WHITESPACE) {
1791 tt = tt->next;
1792 continue;
1794 if (tt->type != t->type) {
1795 j = false; /* found mismatching tokens */
1796 break;
1798 /* When comparing strings, need to unquote them first */
1799 if (t->type == TOK_STRING) {
1800 size_t l1 = nasm_unquote(t->text, NULL);
1801 size_t l2 = nasm_unquote(tt->text, NULL);
1803 if (l1 != l2) {
1804 j = false;
1805 break;
1807 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1808 j = false;
1809 break;
1811 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1812 j = false; /* found mismatching tokens */
1813 break;
1816 t = t->next;
1817 tt = tt->next;
1819 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1820 j = false; /* trailing gunk on one end or other */
1821 break;
1823 case PPC_IFMACRO:
1825 bool found = false;
1826 MMacro searching, *mmac;
1828 skip_white_(tline);
1829 tline = expand_id(tline);
1830 if (!tok_type_(tline, TOK_ID)) {
1831 nasm_error(ERR_NONFATAL,
1832 "`%s' expects a macro name", pp_directives[ct]);
1833 goto fail;
1835 searching.name = nasm_strdup(tline->text);
1836 searching.casesense = true;
1837 searching.plus = false;
1838 searching.nolist = false;
1839 searching.in_progress = 0;
1840 searching.max_depth = 0;
1841 searching.rep_nest = NULL;
1842 searching.nparam_min = 0;
1843 searching.nparam_max = INT_MAX;
1844 tline = expand_smacro(tline->next);
1845 skip_white_(tline);
1846 if (!tline) {
1847 } else if (!tok_type_(tline, TOK_NUMBER)) {
1848 nasm_error(ERR_NONFATAL,
1849 "`%s' expects a parameter count or nothing",
1850 pp_directives[ct]);
1851 } else {
1852 searching.nparam_min = searching.nparam_max =
1853 readnum(tline->text, &j);
1854 if (j)
1855 nasm_error(ERR_NONFATAL,
1856 "unable to parse parameter count `%s'",
1857 tline->text);
1859 if (tline && tok_is_(tline->next, "-")) {
1860 tline = tline->next->next;
1861 if (tok_is_(tline, "*"))
1862 searching.nparam_max = INT_MAX;
1863 else if (!tok_type_(tline, TOK_NUMBER))
1864 nasm_error(ERR_NONFATAL,
1865 "`%s' expects a parameter count after `-'",
1866 pp_directives[ct]);
1867 else {
1868 searching.nparam_max = readnum(tline->text, &j);
1869 if (j)
1870 nasm_error(ERR_NONFATAL,
1871 "unable to parse parameter count `%s'",
1872 tline->text);
1873 if (searching.nparam_min > searching.nparam_max)
1874 nasm_error(ERR_NONFATAL,
1875 "minimum parameter count exceeds maximum");
1878 if (tline && tok_is_(tline->next, "+")) {
1879 tline = tline->next;
1880 searching.plus = true;
1882 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1883 while (mmac) {
1884 if (!strcmp(mmac->name, searching.name) &&
1885 (mmac->nparam_min <= searching.nparam_max
1886 || searching.plus)
1887 && (searching.nparam_min <= mmac->nparam_max
1888 || mmac->plus)) {
1889 found = true;
1890 break;
1892 mmac = mmac->next;
1894 if (tline && tline->next)
1895 nasm_error(ERR_WARNING|ERR_PASS1,
1896 "trailing garbage after %%ifmacro ignored");
1897 nasm_free(searching.name);
1898 j = found;
1899 break;
1902 case PPC_IFID:
1903 needtype = TOK_ID;
1904 goto iftype;
1905 case PPC_IFNUM:
1906 needtype = TOK_NUMBER;
1907 goto iftype;
1908 case PPC_IFSTR:
1909 needtype = TOK_STRING;
1910 goto iftype;
1912 iftype:
1913 t = tline = expand_smacro(tline);
1915 while (tok_type_(t, TOK_WHITESPACE) ||
1916 (needtype == TOK_NUMBER &&
1917 tok_type_(t, TOK_OTHER) &&
1918 (t->text[0] == '-' || t->text[0] == '+') &&
1919 !t->text[1]))
1920 t = t->next;
1922 j = tok_type_(t, needtype);
1923 break;
1925 case PPC_IFTOKEN:
1926 t = tline = expand_smacro(tline);
1927 while (tok_type_(t, TOK_WHITESPACE))
1928 t = t->next;
1930 j = false;
1931 if (t) {
1932 t = t->next; /* Skip the actual token */
1933 while (tok_type_(t, TOK_WHITESPACE))
1934 t = t->next;
1935 j = !t; /* Should be nothing left */
1937 break;
1939 case PPC_IFEMPTY:
1940 t = tline = expand_smacro(tline);
1941 while (tok_type_(t, TOK_WHITESPACE))
1942 t = t->next;
1944 j = !t; /* Should be empty */
1945 break;
1947 case PPC_IF:
1948 t = tline = expand_smacro(tline);
1949 tptr = &t;
1950 tokval.t_type = TOKEN_INVALID;
1951 evalresult = evaluate(ppscan, tptr, &tokval,
1952 NULL, pass | CRITICAL, NULL);
1953 if (!evalresult)
1954 return -1;
1955 if (tokval.t_type)
1956 nasm_error(ERR_WARNING|ERR_PASS1,
1957 "trailing garbage after expression ignored");
1958 if (!is_simple(evalresult)) {
1959 nasm_error(ERR_NONFATAL,
1960 "non-constant value given to `%s'", pp_directives[ct]);
1961 goto fail;
1963 j = reloc_value(evalresult) != 0;
1964 break;
1966 default:
1967 nasm_error(ERR_FATAL,
1968 "preprocessor directive `%s' not yet implemented",
1969 pp_directives[ct]);
1970 goto fail;
1973 free_tlist(origline);
1974 return j ^ PP_NEGATIVE(ct);
1976 fail:
1977 free_tlist(origline);
1978 return -1;
1982 * Common code for defining an smacro
1984 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1985 int nparam, Token *expansion)
1987 SMacro *smac, **smhead;
1988 struct hash_table *smtbl;
1990 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1991 if (!smac) {
1992 nasm_error(ERR_WARNING|ERR_PASS1,
1993 "single-line macro `%s' defined both with and"
1994 " without parameters", mname);
1996 * Some instances of the old code considered this a failure,
1997 * some others didn't. What is the right thing to do here?
1999 free_tlist(expansion);
2000 return false; /* Failure */
2001 } else {
2003 * We're redefining, so we have to take over an
2004 * existing SMacro structure. This means freeing
2005 * what was already in it.
2007 nasm_free(smac->name);
2008 free_tlist(smac->expansion);
2010 } else {
2011 smtbl = ctx ? &ctx->localmac : &smacros;
2012 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2013 smac = nasm_malloc(sizeof(SMacro));
2014 smac->next = *smhead;
2015 *smhead = smac;
2017 smac->name = nasm_strdup(mname);
2018 smac->casesense = casesense;
2019 smac->nparam = nparam;
2020 smac->expansion = expansion;
2021 smac->in_progress = false;
2022 return true; /* Success */
2026 * Undefine an smacro
2028 static void undef_smacro(Context *ctx, const char *mname)
2030 SMacro **smhead, *s, **sp;
2031 struct hash_table *smtbl;
2033 smtbl = ctx ? &ctx->localmac : &smacros;
2034 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2036 if (smhead) {
2038 * We now have a macro name... go hunt for it.
2040 sp = smhead;
2041 while ((s = *sp) != NULL) {
2042 if (!mstrcmp(s->name, mname, s->casesense)) {
2043 *sp = s->next;
2044 nasm_free(s->name);
2045 free_tlist(s->expansion);
2046 nasm_free(s);
2047 } else {
2048 sp = &s->next;
2055 * Parse a mmacro specification.
2057 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2059 bool err;
2061 tline = tline->next;
2062 skip_white_(tline);
2063 tline = expand_id(tline);
2064 if (!tok_type_(tline, TOK_ID)) {
2065 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2066 return false;
2069 def->prev = NULL;
2070 def->name = nasm_strdup(tline->text);
2071 def->plus = false;
2072 def->nolist = false;
2073 def->in_progress = 0;
2074 def->rep_nest = NULL;
2075 def->nparam_min = 0;
2076 def->nparam_max = 0;
2078 tline = expand_smacro(tline->next);
2079 skip_white_(tline);
2080 if (!tok_type_(tline, TOK_NUMBER)) {
2081 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2082 } else {
2083 def->nparam_min = def->nparam_max =
2084 readnum(tline->text, &err);
2085 if (err)
2086 nasm_error(ERR_NONFATAL,
2087 "unable to parse parameter count `%s'", tline->text);
2089 if (tline && tok_is_(tline->next, "-")) {
2090 tline = tline->next->next;
2091 if (tok_is_(tline, "*")) {
2092 def->nparam_max = INT_MAX;
2093 } else if (!tok_type_(tline, TOK_NUMBER)) {
2094 nasm_error(ERR_NONFATAL,
2095 "`%s' expects a parameter count after `-'", directive);
2096 } else {
2097 def->nparam_max = readnum(tline->text, &err);
2098 if (err) {
2099 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2100 tline->text);
2102 if (def->nparam_min > def->nparam_max) {
2103 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2107 if (tline && tok_is_(tline->next, "+")) {
2108 tline = tline->next;
2109 def->plus = true;
2111 if (tline && tok_type_(tline->next, TOK_ID) &&
2112 !nasm_stricmp(tline->next->text, ".nolist")) {
2113 tline = tline->next;
2114 def->nolist = true;
2118 * Handle default parameters.
2120 if (tline && tline->next) {
2121 def->dlist = tline->next;
2122 tline->next = NULL;
2123 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2124 } else {
2125 def->dlist = NULL;
2126 def->defaults = NULL;
2128 def->expansion = NULL;
2130 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2131 !def->plus)
2132 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2133 "too many default macro parameters");
2135 return true;
2140 * Decode a size directive
2142 static int parse_size(const char *str) {
2143 static const char *size_names[] =
2144 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2145 static const int sizes[] =
2146 { 0, 1, 4, 16, 8, 10, 2, 32 };
2148 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2152 * find and process preprocessor directive in passed line
2153 * Find out if a line contains a preprocessor directive, and deal
2154 * with it if so.
2156 * If a directive _is_ found, it is the responsibility of this routine
2157 * (and not the caller) to free_tlist() the line.
2159 * @param tline a pointer to the current tokeninzed line linked list
2160 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2163 static int do_directive(Token * tline)
2165 enum preproc_token i;
2166 int j;
2167 bool err;
2168 int nparam;
2169 bool nolist;
2170 bool casesense;
2171 int k, m;
2172 int offset;
2173 char *p, *pp;
2174 const char *mname;
2175 Include *inc;
2176 Context *ctx;
2177 Cond *cond;
2178 MMacro *mmac, **mmhead;
2179 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2180 Line *l;
2181 struct tokenval tokval;
2182 expr *evalresult;
2183 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2184 int64_t count;
2185 size_t len;
2186 int severity;
2188 origline = tline;
2190 skip_white_(tline);
2191 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2192 (tline->text[1] == '%' || tline->text[1] == '$'
2193 || tline->text[1] == '!'))
2194 return NO_DIRECTIVE_FOUND;
2196 i = pp_token_hash(tline->text);
2199 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2200 * since they are known to be buggy at moment, we need to fix them
2201 * in future release (2.09-2.10)
2203 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2204 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2205 tline->text);
2206 return NO_DIRECTIVE_FOUND;
2210 * If we're in a non-emitting branch of a condition construct,
2211 * or walking to the end of an already terminated %rep block,
2212 * we should ignore all directives except for condition
2213 * directives.
2215 if (((istk->conds && !emitting(istk->conds->state)) ||
2216 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2217 return NO_DIRECTIVE_FOUND;
2221 * If we're defining a macro or reading a %rep block, we should
2222 * ignore all directives except for %macro/%imacro (which nest),
2223 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2224 * If we're in a %rep block, another %rep nests, so should be let through.
2226 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2227 i != PP_RMACRO && i != PP_IRMACRO &&
2228 i != PP_ENDMACRO && i != PP_ENDM &&
2229 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2230 return NO_DIRECTIVE_FOUND;
2233 if (defining) {
2234 if (i == PP_MACRO || i == PP_IMACRO ||
2235 i == PP_RMACRO || i == PP_IRMACRO) {
2236 nested_mac_count++;
2237 return NO_DIRECTIVE_FOUND;
2238 } else if (nested_mac_count > 0) {
2239 if (i == PP_ENDMACRO) {
2240 nested_mac_count--;
2241 return NO_DIRECTIVE_FOUND;
2244 if (!defining->name) {
2245 if (i == PP_REP) {
2246 nested_rep_count++;
2247 return NO_DIRECTIVE_FOUND;
2248 } else if (nested_rep_count > 0) {
2249 if (i == PP_ENDREP) {
2250 nested_rep_count--;
2251 return NO_DIRECTIVE_FOUND;
2257 switch (i) {
2258 case PP_INVALID:
2259 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2260 tline->text);
2261 return NO_DIRECTIVE_FOUND; /* didn't get it */
2263 case PP_STACKSIZE:
2264 /* Directive to tell NASM what the default stack size is. The
2265 * default is for a 16-bit stack, and this can be overriden with
2266 * %stacksize large.
2268 tline = tline->next;
2269 if (tline && tline->type == TOK_WHITESPACE)
2270 tline = tline->next;
2271 if (!tline || tline->type != TOK_ID) {
2272 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2273 free_tlist(origline);
2274 return DIRECTIVE_FOUND;
2276 if (nasm_stricmp(tline->text, "flat") == 0) {
2277 /* All subsequent ARG directives are for a 32-bit stack */
2278 StackSize = 4;
2279 StackPointer = "ebp";
2280 ArgOffset = 8;
2281 LocalOffset = 0;
2282 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2283 /* All subsequent ARG directives are for a 64-bit stack */
2284 StackSize = 8;
2285 StackPointer = "rbp";
2286 ArgOffset = 16;
2287 LocalOffset = 0;
2288 } else if (nasm_stricmp(tline->text, "large") == 0) {
2289 /* All subsequent ARG directives are for a 16-bit stack,
2290 * far function call.
2292 StackSize = 2;
2293 StackPointer = "bp";
2294 ArgOffset = 4;
2295 LocalOffset = 0;
2296 } else if (nasm_stricmp(tline->text, "small") == 0) {
2297 /* All subsequent ARG directives are for a 16-bit stack,
2298 * far function call. We don't support near functions.
2300 StackSize = 2;
2301 StackPointer = "bp";
2302 ArgOffset = 6;
2303 LocalOffset = 0;
2304 } else {
2305 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2306 free_tlist(origline);
2307 return DIRECTIVE_FOUND;
2309 free_tlist(origline);
2310 return DIRECTIVE_FOUND;
2312 case PP_ARG:
2313 /* TASM like ARG directive to define arguments to functions, in
2314 * the following form:
2316 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2318 offset = ArgOffset;
2319 do {
2320 char *arg, directive[256];
2321 int size = StackSize;
2323 /* Find the argument name */
2324 tline = tline->next;
2325 if (tline && tline->type == TOK_WHITESPACE)
2326 tline = tline->next;
2327 if (!tline || tline->type != TOK_ID) {
2328 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2329 free_tlist(origline);
2330 return DIRECTIVE_FOUND;
2332 arg = tline->text;
2334 /* Find the argument size type */
2335 tline = tline->next;
2336 if (!tline || tline->type != TOK_OTHER
2337 || tline->text[0] != ':') {
2338 nasm_error(ERR_NONFATAL,
2339 "Syntax error processing `%%arg' directive");
2340 free_tlist(origline);
2341 return DIRECTIVE_FOUND;
2343 tline = tline->next;
2344 if (!tline || tline->type != TOK_ID) {
2345 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2346 free_tlist(origline);
2347 return DIRECTIVE_FOUND;
2350 /* Allow macro expansion of type parameter */
2351 tt = tokenize(tline->text);
2352 tt = expand_smacro(tt);
2353 size = parse_size(tt->text);
2354 if (!size) {
2355 nasm_error(ERR_NONFATAL,
2356 "Invalid size type for `%%arg' missing directive");
2357 free_tlist(tt);
2358 free_tlist(origline);
2359 return DIRECTIVE_FOUND;
2361 free_tlist(tt);
2363 /* Round up to even stack slots */
2364 size = ALIGN(size, StackSize);
2366 /* Now define the macro for the argument */
2367 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2368 arg, StackPointer, offset);
2369 do_directive(tokenize(directive));
2370 offset += size;
2372 /* Move to the next argument in the list */
2373 tline = tline->next;
2374 if (tline && tline->type == TOK_WHITESPACE)
2375 tline = tline->next;
2376 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2377 ArgOffset = offset;
2378 free_tlist(origline);
2379 return DIRECTIVE_FOUND;
2381 case PP_LOCAL:
2382 /* TASM like LOCAL directive to define local variables for a
2383 * function, in the following form:
2385 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2387 * The '= LocalSize' at the end is ignored by NASM, but is
2388 * required by TASM to define the local parameter size (and used
2389 * by the TASM macro package).
2391 offset = LocalOffset;
2392 do {
2393 char *local, directive[256];
2394 int size = StackSize;
2396 /* Find the argument name */
2397 tline = tline->next;
2398 if (tline && tline->type == TOK_WHITESPACE)
2399 tline = tline->next;
2400 if (!tline || tline->type != TOK_ID) {
2401 nasm_error(ERR_NONFATAL,
2402 "`%%local' missing argument parameter");
2403 free_tlist(origline);
2404 return DIRECTIVE_FOUND;
2406 local = tline->text;
2408 /* Find the argument size type */
2409 tline = tline->next;
2410 if (!tline || tline->type != TOK_OTHER
2411 || tline->text[0] != ':') {
2412 nasm_error(ERR_NONFATAL,
2413 "Syntax error processing `%%local' directive");
2414 free_tlist(origline);
2415 return DIRECTIVE_FOUND;
2417 tline = tline->next;
2418 if (!tline || tline->type != TOK_ID) {
2419 nasm_error(ERR_NONFATAL,
2420 "`%%local' missing size type parameter");
2421 free_tlist(origline);
2422 return DIRECTIVE_FOUND;
2425 /* Allow macro expansion of type parameter */
2426 tt = tokenize(tline->text);
2427 tt = expand_smacro(tt);
2428 size = parse_size(tt->text);
2429 if (!size) {
2430 nasm_error(ERR_NONFATAL,
2431 "Invalid size type for `%%local' missing directive");
2432 free_tlist(tt);
2433 free_tlist(origline);
2434 return DIRECTIVE_FOUND;
2436 free_tlist(tt);
2438 /* Round up to even stack slots */
2439 size = ALIGN(size, StackSize);
2441 offset += size; /* Negative offset, increment before */
2443 /* Now define the macro for the argument */
2444 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2445 local, StackPointer, offset);
2446 do_directive(tokenize(directive));
2448 /* Now define the assign to setup the enter_c macro correctly */
2449 snprintf(directive, sizeof(directive),
2450 "%%assign %%$localsize %%$localsize+%d", size);
2451 do_directive(tokenize(directive));
2453 /* Move to the next argument in the list */
2454 tline = tline->next;
2455 if (tline && tline->type == TOK_WHITESPACE)
2456 tline = tline->next;
2457 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2458 LocalOffset = offset;
2459 free_tlist(origline);
2460 return DIRECTIVE_FOUND;
2462 case PP_CLEAR:
2463 if (tline->next)
2464 nasm_error(ERR_WARNING|ERR_PASS1,
2465 "trailing garbage after `%%clear' ignored");
2466 free_macros();
2467 init_macros();
2468 free_tlist(origline);
2469 return DIRECTIVE_FOUND;
2471 case PP_DEPEND:
2472 t = tline->next = expand_smacro(tline->next);
2473 skip_white_(t);
2474 if (!t || (t->type != TOK_STRING &&
2475 t->type != TOK_INTERNAL_STRING)) {
2476 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2477 free_tlist(origline);
2478 return DIRECTIVE_FOUND; /* but we did _something_ */
2480 if (t->next)
2481 nasm_error(ERR_WARNING|ERR_PASS1,
2482 "trailing garbage after `%%depend' ignored");
2483 p = t->text;
2484 if (t->type != TOK_INTERNAL_STRING)
2485 nasm_unquote_cstr(p, i);
2486 if (dephead && !in_list(*dephead, p)) {
2487 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2488 sl->next = NULL;
2489 strcpy(sl->str, p);
2490 *deptail = sl;
2491 deptail = &sl->next;
2493 free_tlist(origline);
2494 return DIRECTIVE_FOUND;
2496 case PP_INCLUDE:
2497 t = tline->next = expand_smacro(tline->next);
2498 skip_white_(t);
2500 if (!t || (t->type != TOK_STRING &&
2501 t->type != TOK_INTERNAL_STRING)) {
2502 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2503 free_tlist(origline);
2504 return DIRECTIVE_FOUND; /* but we did _something_ */
2506 if (t->next)
2507 nasm_error(ERR_WARNING|ERR_PASS1,
2508 "trailing garbage after `%%include' ignored");
2509 p = t->text;
2510 if (t->type != TOK_INTERNAL_STRING)
2511 nasm_unquote_cstr(p, i);
2512 inc = nasm_malloc(sizeof(Include));
2513 inc->next = istk;
2514 inc->conds = NULL;
2515 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0, "r");
2516 if (!inc->fp) {
2517 /* -MG given but file not found */
2518 nasm_free(inc);
2519 } else {
2520 inc->fname = src_set_fname(nasm_strdup(p));
2521 inc->lineno = src_set_linnum(0);
2522 inc->lineinc = 1;
2523 inc->expansion = NULL;
2524 inc->mstk = NULL;
2525 istk = inc;
2526 lfmt->uplevel(LIST_INCLUDE);
2528 free_tlist(origline);
2529 return DIRECTIVE_FOUND;
2531 case PP_USE:
2533 static macros_t *use_pkg;
2534 const char *pkg_macro = NULL;
2536 tline = tline->next;
2537 skip_white_(tline);
2538 tline = expand_id(tline);
2540 if (!tline || (tline->type != TOK_STRING &&
2541 tline->type != TOK_INTERNAL_STRING &&
2542 tline->type != TOK_ID)) {
2543 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2544 free_tlist(origline);
2545 return DIRECTIVE_FOUND; /* but we did _something_ */
2547 if (tline->next)
2548 nasm_error(ERR_WARNING|ERR_PASS1,
2549 "trailing garbage after `%%use' ignored");
2550 if (tline->type == TOK_STRING)
2551 nasm_unquote_cstr(tline->text, i);
2552 use_pkg = nasm_stdmac_find_package(tline->text);
2553 if (!use_pkg)
2554 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2555 else
2556 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2557 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2558 /* Not already included, go ahead and include it */
2559 stdmacpos = use_pkg;
2561 free_tlist(origline);
2562 return DIRECTIVE_FOUND;
2564 case PP_PUSH:
2565 case PP_REPL:
2566 case PP_POP:
2567 tline = tline->next;
2568 skip_white_(tline);
2569 tline = expand_id(tline);
2570 if (tline) {
2571 if (!tok_type_(tline, TOK_ID)) {
2572 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2573 pp_directives[i]);
2574 free_tlist(origline);
2575 return DIRECTIVE_FOUND; /* but we did _something_ */
2577 if (tline->next)
2578 nasm_error(ERR_WARNING|ERR_PASS1,
2579 "trailing garbage after `%s' ignored",
2580 pp_directives[i]);
2581 p = nasm_strdup(tline->text);
2582 } else {
2583 p = NULL; /* Anonymous */
2586 if (i == PP_PUSH) {
2587 ctx = nasm_malloc(sizeof(Context));
2588 ctx->next = cstk;
2589 hash_init(&ctx->localmac, HASH_SMALL);
2590 ctx->name = p;
2591 ctx->number = unique++;
2592 cstk = ctx;
2593 } else {
2594 /* %pop or %repl */
2595 if (!cstk) {
2596 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2597 pp_directives[i]);
2598 } else if (i == PP_POP) {
2599 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2600 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2601 "expected %s",
2602 cstk->name ? cstk->name : "anonymous", p);
2603 else
2604 ctx_pop();
2605 } else {
2606 /* i == PP_REPL */
2607 nasm_free(cstk->name);
2608 cstk->name = p;
2609 p = NULL;
2611 nasm_free(p);
2613 free_tlist(origline);
2614 return DIRECTIVE_FOUND;
2615 case PP_FATAL:
2616 severity = ERR_FATAL;
2617 goto issue_error;
2618 case PP_ERROR:
2619 severity = ERR_NONFATAL;
2620 goto issue_error;
2621 case PP_WARNING:
2622 severity = ERR_WARNING|ERR_WARN_USER;
2623 goto issue_error;
2625 issue_error:
2627 /* Only error out if this is the final pass */
2628 if (pass != 2 && i != PP_FATAL)
2629 return DIRECTIVE_FOUND;
2631 tline->next = expand_smacro(tline->next);
2632 tline = tline->next;
2633 skip_white_(tline);
2634 t = tline ? tline->next : NULL;
2635 skip_white_(t);
2636 if (tok_type_(tline, TOK_STRING) && !t) {
2637 /* The line contains only a quoted string */
2638 p = tline->text;
2639 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2640 nasm_error(severity, "%s", p);
2641 } else {
2642 /* Not a quoted string, or more than a quoted string */
2643 p = detoken(tline, false);
2644 nasm_error(severity, "%s", p);
2645 nasm_free(p);
2647 free_tlist(origline);
2648 return DIRECTIVE_FOUND;
2651 CASE_PP_IF:
2652 if (istk->conds && !emitting(istk->conds->state))
2653 j = COND_NEVER;
2654 else {
2655 j = if_condition(tline->next, i);
2656 tline->next = NULL; /* it got freed */
2657 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2659 cond = nasm_malloc(sizeof(Cond));
2660 cond->next = istk->conds;
2661 cond->state = j;
2662 istk->conds = cond;
2663 if(istk->mstk)
2664 istk->mstk->condcnt ++;
2665 free_tlist(origline);
2666 return DIRECTIVE_FOUND;
2668 CASE_PP_ELIF:
2669 if (!istk->conds)
2670 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2671 switch(istk->conds->state) {
2672 case COND_IF_TRUE:
2673 istk->conds->state = COND_DONE;
2674 break;
2676 case COND_DONE:
2677 case COND_NEVER:
2678 break;
2680 case COND_ELSE_TRUE:
2681 case COND_ELSE_FALSE:
2682 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2683 "`%%elif' after `%%else' ignored");
2684 istk->conds->state = COND_NEVER;
2685 break;
2687 case COND_IF_FALSE:
2689 * IMPORTANT: In the case of %if, we will already have
2690 * called expand_mmac_params(); however, if we're
2691 * processing an %elif we must have been in a
2692 * non-emitting mode, which would have inhibited
2693 * the normal invocation of expand_mmac_params().
2694 * Therefore, we have to do it explicitly here.
2696 j = if_condition(expand_mmac_params(tline->next), i);
2697 tline->next = NULL; /* it got freed */
2698 istk->conds->state =
2699 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2700 break;
2702 free_tlist(origline);
2703 return DIRECTIVE_FOUND;
2705 case PP_ELSE:
2706 if (tline->next)
2707 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2708 "trailing garbage after `%%else' ignored");
2709 if (!istk->conds)
2710 nasm_fatal(0, "`%%else: no matching `%%if'");
2711 switch(istk->conds->state) {
2712 case COND_IF_TRUE:
2713 case COND_DONE:
2714 istk->conds->state = COND_ELSE_FALSE;
2715 break;
2717 case COND_NEVER:
2718 break;
2720 case COND_IF_FALSE:
2721 istk->conds->state = COND_ELSE_TRUE;
2722 break;
2724 case COND_ELSE_TRUE:
2725 case COND_ELSE_FALSE:
2726 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2727 "`%%else' after `%%else' ignored.");
2728 istk->conds->state = COND_NEVER;
2729 break;
2731 free_tlist(origline);
2732 return DIRECTIVE_FOUND;
2734 case PP_ENDIF:
2735 if (tline->next)
2736 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2737 "trailing garbage after `%%endif' ignored");
2738 if (!istk->conds)
2739 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2740 cond = istk->conds;
2741 istk->conds = cond->next;
2742 nasm_free(cond);
2743 if(istk->mstk)
2744 istk->mstk->condcnt --;
2745 free_tlist(origline);
2746 return DIRECTIVE_FOUND;
2748 case PP_RMACRO:
2749 case PP_IRMACRO:
2750 case PP_MACRO:
2751 case PP_IMACRO:
2752 if (defining) {
2753 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2754 pp_directives[i]);
2755 return DIRECTIVE_FOUND;
2757 defining = nasm_malloc(sizeof(MMacro));
2758 defining->max_depth =
2759 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2760 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2761 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2762 nasm_free(defining);
2763 defining = NULL;
2764 return DIRECTIVE_FOUND;
2767 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2768 while (mmac) {
2769 if (!strcmp(mmac->name, defining->name) &&
2770 (mmac->nparam_min <= defining->nparam_max
2771 || defining->plus)
2772 && (defining->nparam_min <= mmac->nparam_max
2773 || mmac->plus)) {
2774 nasm_error(ERR_WARNING|ERR_PASS1,
2775 "redefining multi-line macro `%s'", defining->name);
2776 return DIRECTIVE_FOUND;
2778 mmac = mmac->next;
2780 free_tlist(origline);
2781 return DIRECTIVE_FOUND;
2783 case PP_ENDM:
2784 case PP_ENDMACRO:
2785 if (! (defining && defining->name)) {
2786 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2787 return DIRECTIVE_FOUND;
2789 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2790 defining->next = *mmhead;
2791 *mmhead = defining;
2792 defining = NULL;
2793 free_tlist(origline);
2794 return DIRECTIVE_FOUND;
2796 case PP_EXITMACRO:
2798 * We must search along istk->expansion until we hit a
2799 * macro-end marker for a macro with a name. Then we
2800 * bypass all lines between exitmacro and endmacro.
2802 list_for_each(l, istk->expansion)
2803 if (l->finishes && l->finishes->name)
2804 break;
2806 if (l) {
2808 * Remove all conditional entries relative to this
2809 * macro invocation. (safe to do in this context)
2811 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2812 cond = istk->conds;
2813 istk->conds = cond->next;
2814 nasm_free(cond);
2816 istk->expansion = l;
2817 } else {
2818 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2820 free_tlist(origline);
2821 return DIRECTIVE_FOUND;
2823 case PP_UNMACRO:
2824 case PP_UNIMACRO:
2826 MMacro **mmac_p;
2827 MMacro spec;
2829 spec.casesense = (i == PP_UNMACRO);
2830 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2831 return DIRECTIVE_FOUND;
2833 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2834 while (mmac_p && *mmac_p) {
2835 mmac = *mmac_p;
2836 if (mmac->casesense == spec.casesense &&
2837 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2838 mmac->nparam_min == spec.nparam_min &&
2839 mmac->nparam_max == spec.nparam_max &&
2840 mmac->plus == spec.plus) {
2841 *mmac_p = mmac->next;
2842 free_mmacro(mmac);
2843 } else {
2844 mmac_p = &mmac->next;
2847 free_tlist(origline);
2848 free_tlist(spec.dlist);
2849 return DIRECTIVE_FOUND;
2852 case PP_ROTATE:
2853 if (tline->next && tline->next->type == TOK_WHITESPACE)
2854 tline = tline->next;
2855 if (!tline->next) {
2856 free_tlist(origline);
2857 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2858 return DIRECTIVE_FOUND;
2860 t = expand_smacro(tline->next);
2861 tline->next = NULL;
2862 free_tlist(origline);
2863 tline = t;
2864 tptr = &t;
2865 tokval.t_type = TOKEN_INVALID;
2866 evalresult =
2867 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2868 free_tlist(tline);
2869 if (!evalresult)
2870 return DIRECTIVE_FOUND;
2871 if (tokval.t_type)
2872 nasm_error(ERR_WARNING|ERR_PASS1,
2873 "trailing garbage after expression ignored");
2874 if (!is_simple(evalresult)) {
2875 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2876 return DIRECTIVE_FOUND;
2878 mmac = istk->mstk;
2879 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2880 mmac = mmac->next_active;
2881 if (!mmac) {
2882 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2883 } else if (mmac->nparam == 0) {
2884 nasm_error(ERR_NONFATAL,
2885 "`%%rotate' invoked within macro without parameters");
2886 } else {
2887 int rotate = mmac->rotate + reloc_value(evalresult);
2889 rotate %= (int)mmac->nparam;
2890 if (rotate < 0)
2891 rotate += mmac->nparam;
2893 mmac->rotate = rotate;
2895 return DIRECTIVE_FOUND;
2897 case PP_REP:
2898 nolist = false;
2899 do {
2900 tline = tline->next;
2901 } while (tok_type_(tline, TOK_WHITESPACE));
2903 if (tok_type_(tline, TOK_ID) &&
2904 nasm_stricmp(tline->text, ".nolist") == 0) {
2905 nolist = true;
2906 do {
2907 tline = tline->next;
2908 } while (tok_type_(tline, TOK_WHITESPACE));
2911 if (tline) {
2912 t = expand_smacro(tline);
2913 tptr = &t;
2914 tokval.t_type = TOKEN_INVALID;
2915 evalresult =
2916 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2917 if (!evalresult) {
2918 free_tlist(origline);
2919 return DIRECTIVE_FOUND;
2921 if (tokval.t_type)
2922 nasm_error(ERR_WARNING|ERR_PASS1,
2923 "trailing garbage after expression ignored");
2924 if (!is_simple(evalresult)) {
2925 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2926 return DIRECTIVE_FOUND;
2928 count = reloc_value(evalresult);
2929 if (count >= REP_LIMIT) {
2930 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
2931 count = 0;
2932 } else
2933 count++;
2934 } else {
2935 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2936 count = 0;
2938 free_tlist(origline);
2940 tmp_defining = defining;
2941 defining = nasm_malloc(sizeof(MMacro));
2942 defining->prev = NULL;
2943 defining->name = NULL; /* flags this macro as a %rep block */
2944 defining->casesense = false;
2945 defining->plus = false;
2946 defining->nolist = nolist;
2947 defining->in_progress = count;
2948 defining->max_depth = 0;
2949 defining->nparam_min = defining->nparam_max = 0;
2950 defining->defaults = NULL;
2951 defining->dlist = NULL;
2952 defining->expansion = NULL;
2953 defining->next_active = istk->mstk;
2954 defining->rep_nest = tmp_defining;
2955 return DIRECTIVE_FOUND;
2957 case PP_ENDREP:
2958 if (!defining || defining->name) {
2959 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2960 return DIRECTIVE_FOUND;
2964 * Now we have a "macro" defined - although it has no name
2965 * and we won't be entering it in the hash tables - we must
2966 * push a macro-end marker for it on to istk->expansion.
2967 * After that, it will take care of propagating itself (a
2968 * macro-end marker line for a macro which is really a %rep
2969 * block will cause the macro to be re-expanded, complete
2970 * with another macro-end marker to ensure the process
2971 * continues) until the whole expansion is forcibly removed
2972 * from istk->expansion by a %exitrep.
2974 l = nasm_malloc(sizeof(Line));
2975 l->next = istk->expansion;
2976 l->finishes = defining;
2977 l->first = NULL;
2978 istk->expansion = l;
2980 istk->mstk = defining;
2982 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2983 tmp_defining = defining;
2984 defining = defining->rep_nest;
2985 free_tlist(origline);
2986 return DIRECTIVE_FOUND;
2988 case PP_EXITREP:
2990 * We must search along istk->expansion until we hit a
2991 * macro-end marker for a macro with no name. Then we set
2992 * its `in_progress' flag to 0.
2994 list_for_each(l, istk->expansion)
2995 if (l->finishes && !l->finishes->name)
2996 break;
2998 if (l)
2999 l->finishes->in_progress = 1;
3000 else
3001 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3002 free_tlist(origline);
3003 return DIRECTIVE_FOUND;
3005 case PP_XDEFINE:
3006 case PP_IXDEFINE:
3007 case PP_DEFINE:
3008 case PP_IDEFINE:
3009 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3011 tline = tline->next;
3012 skip_white_(tline);
3013 tline = expand_id(tline);
3014 if (!tline || (tline->type != TOK_ID &&
3015 (tline->type != TOK_PREPROC_ID ||
3016 tline->text[1] != '$'))) {
3017 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3018 pp_directives[i]);
3019 free_tlist(origline);
3020 return DIRECTIVE_FOUND;
3023 ctx = get_ctx(tline->text, &mname);
3024 last = tline;
3025 param_start = tline = tline->next;
3026 nparam = 0;
3028 /* Expand the macro definition now for %xdefine and %ixdefine */
3029 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3030 tline = expand_smacro(tline);
3032 if (tok_is_(tline, "(")) {
3034 * This macro has parameters.
3037 tline = tline->next;
3038 while (1) {
3039 skip_white_(tline);
3040 if (!tline) {
3041 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3042 free_tlist(origline);
3043 return DIRECTIVE_FOUND;
3045 if (tline->type != TOK_ID) {
3046 nasm_error(ERR_NONFATAL,
3047 "`%s': parameter identifier expected",
3048 tline->text);
3049 free_tlist(origline);
3050 return DIRECTIVE_FOUND;
3052 tline->type = TOK_SMAC_PARAM + nparam++;
3053 tline = tline->next;
3054 skip_white_(tline);
3055 if (tok_is_(tline, ",")) {
3056 tline = tline->next;
3057 } else {
3058 if (!tok_is_(tline, ")")) {
3059 nasm_error(ERR_NONFATAL,
3060 "`)' expected to terminate macro template");
3061 free_tlist(origline);
3062 return DIRECTIVE_FOUND;
3064 break;
3067 last = tline;
3068 tline = tline->next;
3070 if (tok_type_(tline, TOK_WHITESPACE))
3071 last = tline, tline = tline->next;
3072 macro_start = NULL;
3073 last->next = NULL;
3074 t = tline;
3075 while (t) {
3076 if (t->type == TOK_ID) {
3077 list_for_each(tt, param_start)
3078 if (tt->type >= TOK_SMAC_PARAM &&
3079 !strcmp(tt->text, t->text))
3080 t->type = tt->type;
3082 tt = t->next;
3083 t->next = macro_start;
3084 macro_start = t;
3085 t = tt;
3088 * Good. We now have a macro name, a parameter count, and a
3089 * token list (in reverse order) for an expansion. We ought
3090 * to be OK just to create an SMacro, store it, and let
3091 * free_tlist have the rest of the line (which we have
3092 * carefully re-terminated after chopping off the expansion
3093 * from the end).
3095 define_smacro(ctx, mname, casesense, nparam, macro_start);
3096 free_tlist(origline);
3097 return DIRECTIVE_FOUND;
3099 case PP_UNDEF:
3100 tline = tline->next;
3101 skip_white_(tline);
3102 tline = expand_id(tline);
3103 if (!tline || (tline->type != TOK_ID &&
3104 (tline->type != TOK_PREPROC_ID ||
3105 tline->text[1] != '$'))) {
3106 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3107 free_tlist(origline);
3108 return DIRECTIVE_FOUND;
3110 if (tline->next) {
3111 nasm_error(ERR_WARNING|ERR_PASS1,
3112 "trailing garbage after macro name ignored");
3115 /* Find the context that symbol belongs to */
3116 ctx = get_ctx(tline->text, &mname);
3117 undef_smacro(ctx, mname);
3118 free_tlist(origline);
3119 return DIRECTIVE_FOUND;
3121 case PP_DEFSTR:
3122 case PP_IDEFSTR:
3123 casesense = (i == PP_DEFSTR);
3125 tline = tline->next;
3126 skip_white_(tline);
3127 tline = expand_id(tline);
3128 if (!tline || (tline->type != TOK_ID &&
3129 (tline->type != TOK_PREPROC_ID ||
3130 tline->text[1] != '$'))) {
3131 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3132 pp_directives[i]);
3133 free_tlist(origline);
3134 return DIRECTIVE_FOUND;
3137 ctx = get_ctx(tline->text, &mname);
3138 last = tline;
3139 tline = expand_smacro(tline->next);
3140 last->next = NULL;
3142 while (tok_type_(tline, TOK_WHITESPACE))
3143 tline = delete_Token(tline);
3145 p = detoken(tline, false);
3146 macro_start = nasm_malloc(sizeof(*macro_start));
3147 macro_start->next = NULL;
3148 macro_start->text = nasm_quote(p, strlen(p));
3149 macro_start->type = TOK_STRING;
3150 macro_start->a.mac = NULL;
3151 nasm_free(p);
3154 * We now have a macro name, an implicit parameter count of
3155 * zero, and a string token to use as an expansion. Create
3156 * and store an SMacro.
3158 define_smacro(ctx, mname, casesense, 0, macro_start);
3159 free_tlist(origline);
3160 return DIRECTIVE_FOUND;
3162 case PP_DEFTOK:
3163 case PP_IDEFTOK:
3164 casesense = (i == PP_DEFTOK);
3166 tline = tline->next;
3167 skip_white_(tline);
3168 tline = expand_id(tline);
3169 if (!tline || (tline->type != TOK_ID &&
3170 (tline->type != TOK_PREPROC_ID ||
3171 tline->text[1] != '$'))) {
3172 nasm_error(ERR_NONFATAL,
3173 "`%s' expects a macro identifier as first parameter",
3174 pp_directives[i]);
3175 free_tlist(origline);
3176 return DIRECTIVE_FOUND;
3178 ctx = get_ctx(tline->text, &mname);
3179 last = tline;
3180 tline = expand_smacro(tline->next);
3181 last->next = NULL;
3183 t = tline;
3184 while (tok_type_(t, TOK_WHITESPACE))
3185 t = t->next;
3186 /* t should now point to the string */
3187 if (!tok_type_(t, TOK_STRING)) {
3188 nasm_error(ERR_NONFATAL,
3189 "`%s` requires string as second parameter",
3190 pp_directives[i]);
3191 free_tlist(tline);
3192 free_tlist(origline);
3193 return DIRECTIVE_FOUND;
3197 * Convert the string to a token stream. Note that smacros
3198 * are stored with the token stream reversed, so we have to
3199 * reverse the output of tokenize().
3201 nasm_unquote_cstr(t->text, i);
3202 macro_start = reverse_tokens(tokenize(t->text));
3205 * We now have a macro name, an implicit parameter count of
3206 * zero, and a numeric token to use as an expansion. Create
3207 * and store an SMacro.
3209 define_smacro(ctx, mname, casesense, 0, macro_start);
3210 free_tlist(tline);
3211 free_tlist(origline);
3212 return DIRECTIVE_FOUND;
3214 case PP_PATHSEARCH:
3216 FILE *fp;
3217 StrList *xsl = NULL;
3218 StrList **xst = &xsl;
3220 casesense = true;
3222 tline = tline->next;
3223 skip_white_(tline);
3224 tline = expand_id(tline);
3225 if (!tline || (tline->type != TOK_ID &&
3226 (tline->type != TOK_PREPROC_ID ||
3227 tline->text[1] != '$'))) {
3228 nasm_error(ERR_NONFATAL,
3229 "`%%pathsearch' expects a macro identifier as first parameter");
3230 free_tlist(origline);
3231 return DIRECTIVE_FOUND;
3233 ctx = get_ctx(tline->text, &mname);
3234 last = tline;
3235 tline = expand_smacro(tline->next);
3236 last->next = NULL;
3238 t = tline;
3239 while (tok_type_(t, TOK_WHITESPACE))
3240 t = t->next;
3242 if (!t || (t->type != TOK_STRING &&
3243 t->type != TOK_INTERNAL_STRING)) {
3244 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3245 free_tlist(tline);
3246 free_tlist(origline);
3247 return DIRECTIVE_FOUND; /* but we did _something_ */
3249 if (t->next)
3250 nasm_error(ERR_WARNING|ERR_PASS1,
3251 "trailing garbage after `%%pathsearch' ignored");
3252 p = t->text;
3253 if (t->type != TOK_INTERNAL_STRING)
3254 nasm_unquote(p, NULL);
3256 fp = inc_fopen(p, &xsl, &xst, true, "r");
3257 if (fp) {
3258 p = xsl->str;
3259 fclose(fp); /* Don't actually care about the file */
3261 macro_start = nasm_malloc(sizeof(*macro_start));
3262 macro_start->next = NULL;
3263 macro_start->text = nasm_quote(p, strlen(p));
3264 macro_start->type = TOK_STRING;
3265 macro_start->a.mac = NULL;
3266 if (xsl)
3267 nasm_free(xsl);
3270 * We now have a macro name, an implicit parameter count of
3271 * zero, and a string token to use as an expansion. Create
3272 * and store an SMacro.
3274 define_smacro(ctx, mname, casesense, 0, macro_start);
3275 free_tlist(tline);
3276 free_tlist(origline);
3277 return DIRECTIVE_FOUND;
3280 case PP_STRLEN:
3281 casesense = true;
3283 tline = tline->next;
3284 skip_white_(tline);
3285 tline = expand_id(tline);
3286 if (!tline || (tline->type != TOK_ID &&
3287 (tline->type != TOK_PREPROC_ID ||
3288 tline->text[1] != '$'))) {
3289 nasm_error(ERR_NONFATAL,
3290 "`%%strlen' expects a macro identifier as first parameter");
3291 free_tlist(origline);
3292 return DIRECTIVE_FOUND;
3294 ctx = get_ctx(tline->text, &mname);
3295 last = tline;
3296 tline = expand_smacro(tline->next);
3297 last->next = NULL;
3299 t = tline;
3300 while (tok_type_(t, TOK_WHITESPACE))
3301 t = t->next;
3302 /* t should now point to the string */
3303 if (!tok_type_(t, TOK_STRING)) {
3304 nasm_error(ERR_NONFATAL,
3305 "`%%strlen` requires string as second parameter");
3306 free_tlist(tline);
3307 free_tlist(origline);
3308 return DIRECTIVE_FOUND;
3311 macro_start = nasm_malloc(sizeof(*macro_start));
3312 macro_start->next = NULL;
3313 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3314 macro_start->a.mac = NULL;
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_STRCAT:
3327 casesense = true;
3329 tline = tline->next;
3330 skip_white_(tline);
3331 tline = expand_id(tline);
3332 if (!tline || (tline->type != TOK_ID &&
3333 (tline->type != TOK_PREPROC_ID ||
3334 tline->text[1] != '$'))) {
3335 nasm_error(ERR_NONFATAL,
3336 "`%%strcat' expects a macro identifier as first parameter");
3337 free_tlist(origline);
3338 return DIRECTIVE_FOUND;
3340 ctx = get_ctx(tline->text, &mname);
3341 last = tline;
3342 tline = expand_smacro(tline->next);
3343 last->next = NULL;
3345 len = 0;
3346 list_for_each(t, tline) {
3347 switch (t->type) {
3348 case TOK_WHITESPACE:
3349 break;
3350 case TOK_STRING:
3351 len += t->a.len = nasm_unquote(t->text, NULL);
3352 break;
3353 case TOK_OTHER:
3354 if (!strcmp(t->text, ",")) /* permit comma separators */
3355 break;
3356 /* else fall through */
3357 default:
3358 nasm_error(ERR_NONFATAL,
3359 "non-string passed to `%%strcat' (%d)", t->type);
3360 free_tlist(tline);
3361 free_tlist(origline);
3362 return DIRECTIVE_FOUND;
3366 p = pp = nasm_malloc(len);
3367 list_for_each(t, tline) {
3368 if (t->type == TOK_STRING) {
3369 memcpy(p, t->text, t->a.len);
3370 p += t->a.len;
3375 * We now have a macro name, an implicit parameter count of
3376 * zero, and a numeric token to use as an expansion. Create
3377 * and store an SMacro.
3379 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3380 macro_start->text = nasm_quote(pp, len);
3381 nasm_free(pp);
3382 define_smacro(ctx, mname, casesense, 0, macro_start);
3383 free_tlist(tline);
3384 free_tlist(origline);
3385 return DIRECTIVE_FOUND;
3387 case PP_SUBSTR:
3389 int64_t start, count;
3390 size_t len;
3392 casesense = true;
3394 tline = tline->next;
3395 skip_white_(tline);
3396 tline = expand_id(tline);
3397 if (!tline || (tline->type != TOK_ID &&
3398 (tline->type != TOK_PREPROC_ID ||
3399 tline->text[1] != '$'))) {
3400 nasm_error(ERR_NONFATAL,
3401 "`%%substr' expects a macro identifier as first parameter");
3402 free_tlist(origline);
3403 return DIRECTIVE_FOUND;
3405 ctx = get_ctx(tline->text, &mname);
3406 last = tline;
3407 tline = expand_smacro(tline->next);
3408 last->next = NULL;
3410 if (tline) /* skip expanded id */
3411 t = tline->next;
3412 while (tok_type_(t, TOK_WHITESPACE))
3413 t = t->next;
3415 /* t should now point to the string */
3416 if (!tok_type_(t, TOK_STRING)) {
3417 nasm_error(ERR_NONFATAL,
3418 "`%%substr` requires string as second parameter");
3419 free_tlist(tline);
3420 free_tlist(origline);
3421 return DIRECTIVE_FOUND;
3424 tt = t->next;
3425 tptr = &tt;
3426 tokval.t_type = TOKEN_INVALID;
3427 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3428 if (!evalresult) {
3429 free_tlist(tline);
3430 free_tlist(origline);
3431 return DIRECTIVE_FOUND;
3432 } else if (!is_simple(evalresult)) {
3433 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3434 free_tlist(tline);
3435 free_tlist(origline);
3436 return DIRECTIVE_FOUND;
3438 start = evalresult->value - 1;
3440 while (tok_type_(tt, TOK_WHITESPACE))
3441 tt = tt->next;
3442 if (!tt) {
3443 count = 1; /* Backwards compatibility: one character */
3444 } else {
3445 tokval.t_type = TOKEN_INVALID;
3446 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3447 if (!evalresult) {
3448 free_tlist(tline);
3449 free_tlist(origline);
3450 return DIRECTIVE_FOUND;
3451 } else if (!is_simple(evalresult)) {
3452 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3453 free_tlist(tline);
3454 free_tlist(origline);
3455 return DIRECTIVE_FOUND;
3457 count = evalresult->value;
3460 len = nasm_unquote(t->text, NULL);
3462 /* make start and count being in range */
3463 if (start < 0)
3464 start = 0;
3465 if (count < 0)
3466 count = len + count + 1 - start;
3467 if (start + count > (int64_t)len)
3468 count = len - start;
3469 if (!len || count < 0 || start >=(int64_t)len)
3470 start = -1, count = 0; /* empty string */
3472 macro_start = nasm_malloc(sizeof(*macro_start));
3473 macro_start->next = NULL;
3474 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3475 macro_start->type = TOK_STRING;
3476 macro_start->a.mac = NULL;
3479 * We now have a macro name, an implicit parameter count of
3480 * zero, and a numeric token to use as an expansion. Create
3481 * and store an SMacro.
3483 define_smacro(ctx, mname, casesense, 0, macro_start);
3484 free_tlist(tline);
3485 free_tlist(origline);
3486 return DIRECTIVE_FOUND;
3489 case PP_ASSIGN:
3490 case PP_IASSIGN:
3491 casesense = (i == PP_ASSIGN);
3493 tline = tline->next;
3494 skip_white_(tline);
3495 tline = expand_id(tline);
3496 if (!tline || (tline->type != TOK_ID &&
3497 (tline->type != TOK_PREPROC_ID ||
3498 tline->text[1] != '$'))) {
3499 nasm_error(ERR_NONFATAL,
3500 "`%%%sassign' expects a macro identifier",
3501 (i == PP_IASSIGN ? "i" : ""));
3502 free_tlist(origline);
3503 return DIRECTIVE_FOUND;
3505 ctx = get_ctx(tline->text, &mname);
3506 last = tline;
3507 tline = expand_smacro(tline->next);
3508 last->next = NULL;
3510 t = tline;
3511 tptr = &t;
3512 tokval.t_type = TOKEN_INVALID;
3513 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3514 free_tlist(tline);
3515 if (!evalresult) {
3516 free_tlist(origline);
3517 return DIRECTIVE_FOUND;
3520 if (tokval.t_type)
3521 nasm_error(ERR_WARNING|ERR_PASS1,
3522 "trailing garbage after expression ignored");
3524 if (!is_simple(evalresult)) {
3525 nasm_error(ERR_NONFATAL,
3526 "non-constant value given to `%%%sassign'",
3527 (i == PP_IASSIGN ? "i" : ""));
3528 free_tlist(origline);
3529 return DIRECTIVE_FOUND;
3532 macro_start = nasm_malloc(sizeof(*macro_start));
3533 macro_start->next = NULL;
3534 make_tok_num(macro_start, reloc_value(evalresult));
3535 macro_start->a.mac = NULL;
3538 * We now have a macro name, an implicit parameter count of
3539 * zero, and a numeric token to use as an expansion. Create
3540 * and store an SMacro.
3542 define_smacro(ctx, mname, casesense, 0, macro_start);
3543 free_tlist(origline);
3544 return DIRECTIVE_FOUND;
3546 case PP_LINE:
3548 * Syntax is `%line nnn[+mmm] [filename]'
3550 tline = tline->next;
3551 skip_white_(tline);
3552 if (!tok_type_(tline, TOK_NUMBER)) {
3553 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3554 free_tlist(origline);
3555 return DIRECTIVE_FOUND;
3557 k = readnum(tline->text, &err);
3558 m = 1;
3559 tline = tline->next;
3560 if (tok_is_(tline, "+")) {
3561 tline = tline->next;
3562 if (!tok_type_(tline, TOK_NUMBER)) {
3563 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3564 free_tlist(origline);
3565 return DIRECTIVE_FOUND;
3567 m = readnum(tline->text, &err);
3568 tline = tline->next;
3570 skip_white_(tline);
3571 src_set_linnum(k);
3572 istk->lineinc = m;
3573 if (tline) {
3574 nasm_free(src_set_fname(detoken(tline, false)));
3576 free_tlist(origline);
3577 return DIRECTIVE_FOUND;
3579 default:
3580 nasm_error(ERR_FATAL,
3581 "preprocessor directive `%s' not yet implemented",
3582 pp_directives[i]);
3583 return DIRECTIVE_FOUND;
3588 * Ensure that a macro parameter contains a condition code and
3589 * nothing else. Return the condition code index if so, or -1
3590 * otherwise.
3592 static int find_cc(Token * t)
3594 Token *tt;
3596 if (!t)
3597 return -1; /* Probably a %+ without a space */
3599 skip_white_(t);
3600 if (t->type != TOK_ID)
3601 return -1;
3602 tt = t->next;
3603 skip_white_(tt);
3604 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3605 return -1;
3607 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3611 * This routines walks over tokens strem and hadnles tokens
3612 * pasting, if @handle_explicit passed then explicit pasting
3613 * term is handled, otherwise -- implicit pastings only.
3615 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3616 size_t mnum, bool handle_explicit)
3618 Token *tok, *next, **prev_next, **prev_nonspace;
3619 bool pasted = false;
3620 char *buf, *p;
3621 size_t len, i;
3624 * The last token before pasting. We need it
3625 * to be able to connect new handled tokens.
3626 * In other words if there were a tokens stream
3628 * A -> B -> C -> D
3630 * and we've joined tokens B and C, the resulting
3631 * stream should be
3633 * A -> BC -> D
3635 tok = *head;
3636 prev_next = NULL;
3638 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3639 prev_nonspace = head;
3640 else
3641 prev_nonspace = NULL;
3643 while (tok && (next = tok->next)) {
3645 switch (tok->type) {
3646 case TOK_WHITESPACE:
3647 /* Zap redundant whitespaces */
3648 while (tok_type_(next, TOK_WHITESPACE))
3649 next = delete_Token(next);
3650 tok->next = next;
3651 break;
3653 case TOK_PASTE:
3654 /* Explicit pasting */
3655 if (!handle_explicit)
3656 break;
3657 next = delete_Token(tok);
3659 while (tok_type_(next, TOK_WHITESPACE))
3660 next = delete_Token(next);
3662 if (!pasted)
3663 pasted = true;
3665 /* Left pasting token is start of line */
3666 if (!prev_nonspace)
3667 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3670 * No ending token, this might happen in two
3671 * cases
3673 * 1) There indeed no right token at all
3674 * 2) There is a bare "%define ID" statement,
3675 * and @ID does expand to whitespace.
3677 * So technically we need to do a grammar analysis
3678 * in another stage of parsing, but for now lets don't
3679 * change the behaviour people used to. Simply allow
3680 * whitespace after paste token.
3682 if (!next) {
3684 * Zap ending space tokens and that's all.
3686 tok = (*prev_nonspace)->next;
3687 while (tok_type_(tok, TOK_WHITESPACE))
3688 tok = delete_Token(tok);
3689 tok = *prev_nonspace;
3690 tok->next = NULL;
3691 break;
3694 tok = *prev_nonspace;
3695 while (tok_type_(tok, TOK_WHITESPACE))
3696 tok = delete_Token(tok);
3697 len = strlen(tok->text);
3698 len += strlen(next->text);
3700 p = buf = nasm_malloc(len + 1);
3701 strcpy(p, tok->text);
3702 p = strchr(p, '\0');
3703 strcpy(p, next->text);
3705 delete_Token(tok);
3707 tok = tokenize(buf);
3708 nasm_free(buf);
3710 *prev_nonspace = tok;
3711 while (tok && tok->next)
3712 tok = tok->next;
3714 tok->next = delete_Token(next);
3716 /* Restart from pasted tokens head */
3717 tok = *prev_nonspace;
3718 break;
3720 default:
3721 /* implicit pasting */
3722 for (i = 0; i < mnum; i++) {
3723 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3724 continue;
3726 len = 0;
3727 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3728 len += strlen(next->text);
3729 next = next->next;
3732 /* No match */
3733 if (tok == next)
3734 break;
3736 len += strlen(tok->text);
3737 p = buf = nasm_malloc(len + 1);
3739 while (tok != next) {
3740 strcpy(p, tok->text);
3741 p = strchr(p, '\0');
3742 tok = delete_Token(tok);
3745 tok = tokenize(buf);
3746 nasm_free(buf);
3748 if (prev_next)
3749 *prev_next = tok;
3750 else
3751 *head = tok;
3754 * Connect pasted into original stream,
3755 * ie A -> new-tokens -> B
3757 while (tok && tok->next)
3758 tok = tok->next;
3759 tok->next = next;
3761 if (!pasted)
3762 pasted = true;
3764 /* Restart from pasted tokens head */
3765 tok = prev_next ? *prev_next : *head;
3768 break;
3771 prev_next = &tok->next;
3773 if (tok->next &&
3774 !tok_type_(tok->next, TOK_WHITESPACE) &&
3775 !tok_type_(tok->next, TOK_PASTE))
3776 prev_nonspace = prev_next;
3778 tok = tok->next;
3781 return pasted;
3785 * expands to a list of tokens from %{x:y}
3787 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3789 Token *t = tline, **tt, *tm, *head;
3790 char *pos;
3791 int fst, lst, j, i;
3793 pos = strchr(tline->text, ':');
3794 nasm_assert(pos);
3796 lst = atoi(pos + 1);
3797 fst = atoi(tline->text + 1);
3800 * only macros params are accounted so
3801 * if someone passes %0 -- we reject such
3802 * value(s)
3804 if (lst == 0 || fst == 0)
3805 goto err;
3807 /* the values should be sane */
3808 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3809 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3810 goto err;
3812 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3813 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3815 /* counted from zero */
3816 fst--, lst--;
3819 * It will be at least one token. Note we
3820 * need to scan params until separator, otherwise
3821 * only first token will be passed.
3823 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3824 head = new_Token(NULL, tm->type, tm->text, 0);
3825 tt = &head->next, tm = tm->next;
3826 while (tok_isnt_(tm, ",")) {
3827 t = new_Token(NULL, tm->type, tm->text, 0);
3828 *tt = t, tt = &t->next, tm = tm->next;
3831 if (fst < lst) {
3832 for (i = fst + 1; i <= lst; i++) {
3833 t = new_Token(NULL, TOK_OTHER, ",", 0);
3834 *tt = t, tt = &t->next;
3835 j = (i + mac->rotate) % mac->nparam;
3836 tm = mac->params[j];
3837 while (tok_isnt_(tm, ",")) {
3838 t = new_Token(NULL, tm->type, tm->text, 0);
3839 *tt = t, tt = &t->next, tm = tm->next;
3842 } else {
3843 for (i = fst - 1; i >= lst; i--) {
3844 t = new_Token(NULL, TOK_OTHER, ",", 0);
3845 *tt = t, tt = &t->next;
3846 j = (i + mac->rotate) % mac->nparam;
3847 tm = mac->params[j];
3848 while (tok_isnt_(tm, ",")) {
3849 t = new_Token(NULL, tm->type, tm->text, 0);
3850 *tt = t, tt = &t->next, tm = tm->next;
3855 *last = tt;
3856 return head;
3858 err:
3859 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3860 &tline->text[1]);
3861 return tline;
3865 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3866 * %-n) and MMacro-local identifiers (%%foo) as well as
3867 * macro indirection (%[...]) and range (%{..:..}).
3869 static Token *expand_mmac_params(Token * tline)
3871 Token *t, *tt, **tail, *thead;
3872 bool changed = false;
3873 char *pos;
3875 tail = &thead;
3876 thead = NULL;
3878 while (tline) {
3879 if (tline->type == TOK_PREPROC_ID &&
3880 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3881 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3882 tline->text[1] == '%')) {
3883 char *text = NULL;
3884 int type = 0, cc; /* type = 0 to placate optimisers */
3885 char tmpbuf[30];
3886 unsigned int n;
3887 int i;
3888 MMacro *mac;
3890 t = tline;
3891 tline = tline->next;
3893 mac = istk->mstk;
3894 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3895 mac = mac->next_active;
3896 if (!mac) {
3897 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3898 } else {
3899 pos = strchr(t->text, ':');
3900 if (!pos) {
3901 switch (t->text[1]) {
3903 * We have to make a substitution of one of the
3904 * forms %1, %-1, %+1, %%foo, %0.
3906 case '0':
3907 type = TOK_NUMBER;
3908 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3909 text = nasm_strdup(tmpbuf);
3910 break;
3911 case '%':
3912 type = TOK_ID;
3913 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3914 mac->unique);
3915 text = nasm_strcat(tmpbuf, t->text + 2);
3916 break;
3917 case '-':
3918 n = atoi(t->text + 2) - 1;
3919 if (n >= mac->nparam)
3920 tt = NULL;
3921 else {
3922 if (mac->nparam > 1)
3923 n = (n + mac->rotate) % mac->nparam;
3924 tt = mac->params[n];
3926 cc = find_cc(tt);
3927 if (cc == -1) {
3928 nasm_error(ERR_NONFATAL,
3929 "macro parameter %d is not a condition code",
3930 n + 1);
3931 text = NULL;
3932 } else {
3933 type = TOK_ID;
3934 if (inverse_ccs[cc] == -1) {
3935 nasm_error(ERR_NONFATAL,
3936 "condition code `%s' is not invertible",
3937 conditions[cc]);
3938 text = NULL;
3939 } else
3940 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3942 break;
3943 case '+':
3944 n = atoi(t->text + 2) - 1;
3945 if (n >= mac->nparam)
3946 tt = NULL;
3947 else {
3948 if (mac->nparam > 1)
3949 n = (n + mac->rotate) % mac->nparam;
3950 tt = mac->params[n];
3952 cc = find_cc(tt);
3953 if (cc == -1) {
3954 nasm_error(ERR_NONFATAL,
3955 "macro parameter %d is not a condition code",
3956 n + 1);
3957 text = NULL;
3958 } else {
3959 type = TOK_ID;
3960 text = nasm_strdup(conditions[cc]);
3962 break;
3963 default:
3964 n = atoi(t->text + 1) - 1;
3965 if (n >= mac->nparam)
3966 tt = NULL;
3967 else {
3968 if (mac->nparam > 1)
3969 n = (n + mac->rotate) % mac->nparam;
3970 tt = mac->params[n];
3972 if (tt) {
3973 for (i = 0; i < mac->paramlen[n]; i++) {
3974 *tail = new_Token(NULL, tt->type, tt->text, 0);
3975 tail = &(*tail)->next;
3976 tt = tt->next;
3979 text = NULL; /* we've done it here */
3980 break;
3982 } else {
3984 * seems we have a parameters range here
3986 Token *head, **last;
3987 head = expand_mmac_params_range(mac, t, &last);
3988 if (head != t) {
3989 *tail = head;
3990 *last = tline;
3991 tline = head;
3992 text = NULL;
3996 if (!text) {
3997 delete_Token(t);
3998 } else {
3999 *tail = t;
4000 tail = &t->next;
4001 t->type = type;
4002 nasm_free(t->text);
4003 t->text = text;
4004 t->a.mac = NULL;
4006 changed = true;
4007 continue;
4008 } else if (tline->type == TOK_INDIRECT) {
4009 t = tline;
4010 tline = tline->next;
4011 tt = tokenize(t->text);
4012 tt = expand_mmac_params(tt);
4013 tt = expand_smacro(tt);
4014 *tail = tt;
4015 while (tt) {
4016 tt->a.mac = NULL; /* Necessary? */
4017 tail = &tt->next;
4018 tt = tt->next;
4020 delete_Token(t);
4021 changed = true;
4022 } else {
4023 t = *tail = tline;
4024 tline = tline->next;
4025 t->a.mac = NULL;
4026 tail = &t->next;
4029 *tail = NULL;
4031 if (changed) {
4032 const struct tokseq_match t[] = {
4034 PP_CONCAT_MASK(TOK_ID) |
4035 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4036 PP_CONCAT_MASK(TOK_ID) |
4037 PP_CONCAT_MASK(TOK_NUMBER) |
4038 PP_CONCAT_MASK(TOK_FLOAT) |
4039 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4042 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4043 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4046 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4049 return thead;
4053 * Expand all single-line macro calls made in the given line.
4054 * Return the expanded version of the line. The original is deemed
4055 * to be destroyed in the process. (In reality we'll just move
4056 * Tokens from input to output a lot of the time, rather than
4057 * actually bothering to destroy and replicate.)
4060 static Token *expand_smacro(Token * tline)
4062 Token *t, *tt, *mstart, **tail, *thead;
4063 SMacro *head = NULL, *m;
4064 Token **params;
4065 int *paramsize;
4066 unsigned int nparam, sparam;
4067 int brackets;
4068 Token *org_tline = tline;
4069 Context *ctx;
4070 const char *mname;
4071 int deadman = DEADMAN_LIMIT;
4072 bool expanded;
4075 * Trick: we should avoid changing the start token pointer since it can
4076 * be contained in "next" field of other token. Because of this
4077 * we allocate a copy of first token and work with it; at the end of
4078 * routine we copy it back
4080 if (org_tline) {
4081 tline = new_Token(org_tline->next, org_tline->type,
4082 org_tline->text, 0);
4083 tline->a.mac = org_tline->a.mac;
4084 nasm_free(org_tline->text);
4085 org_tline->text = NULL;
4088 expanded = true; /* Always expand %+ at least once */
4090 again:
4091 thead = NULL;
4092 tail = &thead;
4094 while (tline) { /* main token loop */
4095 if (!--deadman) {
4096 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4097 goto err;
4100 if ((mname = tline->text)) {
4101 /* if this token is a local macro, look in local context */
4102 if (tline->type == TOK_ID) {
4103 head = (SMacro *)hash_findix(&smacros, mname);
4104 } else if (tline->type == TOK_PREPROC_ID) {
4105 ctx = get_ctx(mname, &mname);
4106 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4107 } else
4108 head = NULL;
4111 * We've hit an identifier. As in is_mmacro below, we first
4112 * check whether the identifier is a single-line macro at
4113 * all, then think about checking for parameters if
4114 * necessary.
4116 list_for_each(m, head)
4117 if (!mstrcmp(m->name, mname, m->casesense))
4118 break;
4119 if (m) {
4120 mstart = tline;
4121 params = NULL;
4122 paramsize = NULL;
4123 if (m->nparam == 0) {
4125 * Simple case: the macro is parameterless. Discard the
4126 * one token that the macro call took, and push the
4127 * expansion back on the to-do stack.
4129 if (!m->expansion) {
4130 if (!strcmp("__FILE__", m->name)) {
4131 int32_t num = 0;
4132 char *file = NULL;
4133 src_get(&num, &file);
4134 tline->text = nasm_quote(file, strlen(file));
4135 tline->type = TOK_STRING;
4136 nasm_free(file);
4137 continue;
4139 if (!strcmp("__LINE__", m->name)) {
4140 nasm_free(tline->text);
4141 make_tok_num(tline, src_get_linnum());
4142 continue;
4144 if (!strcmp("__BITS__", m->name)) {
4145 nasm_free(tline->text);
4146 make_tok_num(tline, globalbits);
4147 continue;
4149 tline = delete_Token(tline);
4150 continue;
4152 } else {
4154 * Complicated case: at least one macro with this name
4155 * exists and takes parameters. We must find the
4156 * parameters in the call, count them, find the SMacro
4157 * that corresponds to that form of the macro call, and
4158 * substitute for the parameters when we expand. What a
4159 * pain.
4161 /*tline = tline->next;
4162 skip_white_(tline); */
4163 do {
4164 t = tline->next;
4165 while (tok_type_(t, TOK_SMAC_END)) {
4166 t->a.mac->in_progress = false;
4167 t->text = NULL;
4168 t = tline->next = delete_Token(t);
4170 tline = t;
4171 } while (tok_type_(tline, TOK_WHITESPACE));
4172 if (!tok_is_(tline, "(")) {
4174 * This macro wasn't called with parameters: ignore
4175 * the call. (Behaviour borrowed from gnu cpp.)
4177 tline = mstart;
4178 m = NULL;
4179 } else {
4180 int paren = 0;
4181 int white = 0;
4182 brackets = 0;
4183 nparam = 0;
4184 sparam = PARAM_DELTA;
4185 params = nasm_malloc(sparam * sizeof(Token *));
4186 params[0] = tline->next;
4187 paramsize = nasm_malloc(sparam * sizeof(int));
4188 paramsize[0] = 0;
4189 while (true) { /* parameter loop */
4191 * For some unusual expansions
4192 * which concatenates function call
4194 t = tline->next;
4195 while (tok_type_(t, TOK_SMAC_END)) {
4196 t->a.mac->in_progress = false;
4197 t->text = NULL;
4198 t = tline->next = delete_Token(t);
4200 tline = t;
4202 if (!tline) {
4203 nasm_error(ERR_NONFATAL,
4204 "macro call expects terminating `)'");
4205 break;
4207 if (tline->type == TOK_WHITESPACE
4208 && brackets <= 0) {
4209 if (paramsize[nparam])
4210 white++;
4211 else
4212 params[nparam] = tline->next;
4213 continue; /* parameter loop */
4215 if (tline->type == TOK_OTHER
4216 && tline->text[1] == 0) {
4217 char ch = tline->text[0];
4218 if (ch == ',' && !paren && brackets <= 0) {
4219 if (++nparam >= sparam) {
4220 sparam += PARAM_DELTA;
4221 params = nasm_realloc(params,
4222 sparam * sizeof(Token *));
4223 paramsize = nasm_realloc(paramsize,
4224 sparam * sizeof(int));
4226 params[nparam] = tline->next;
4227 paramsize[nparam] = 0;
4228 white = 0;
4229 continue; /* parameter loop */
4231 if (ch == '{' &&
4232 (brackets > 0 || (brackets == 0 &&
4233 !paramsize[nparam])))
4235 if (!(brackets++)) {
4236 params[nparam] = tline->next;
4237 continue; /* parameter loop */
4240 if (ch == '}' && brackets > 0)
4241 if (--brackets == 0) {
4242 brackets = -1;
4243 continue; /* parameter loop */
4245 if (ch == '(' && !brackets)
4246 paren++;
4247 if (ch == ')' && brackets <= 0)
4248 if (--paren < 0)
4249 break;
4251 if (brackets < 0) {
4252 brackets = 0;
4253 nasm_error(ERR_NONFATAL, "braces do not "
4254 "enclose all of macro parameter");
4256 paramsize[nparam] += white + 1;
4257 white = 0;
4258 } /* parameter loop */
4259 nparam++;
4260 while (m && (m->nparam != nparam ||
4261 mstrcmp(m->name, mname,
4262 m->casesense)))
4263 m = m->next;
4264 if (!m)
4265 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4266 "macro `%s' exists, "
4267 "but not taking %d parameters",
4268 mstart->text, nparam);
4271 if (m && m->in_progress)
4272 m = NULL;
4273 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4275 * Design question: should we handle !tline, which
4276 * indicates missing ')' here, or expand those
4277 * macros anyway, which requires the (t) test a few
4278 * lines down?
4280 nasm_free(params);
4281 nasm_free(paramsize);
4282 tline = mstart;
4283 } else {
4285 * Expand the macro: we are placed on the last token of the
4286 * call, so that we can easily split the call from the
4287 * following tokens. We also start by pushing an SMAC_END
4288 * token for the cycle removal.
4290 t = tline;
4291 if (t) {
4292 tline = t->next;
4293 t->next = NULL;
4295 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4296 tt->a.mac = m;
4297 m->in_progress = true;
4298 tline = tt;
4299 list_for_each(t, m->expansion) {
4300 if (t->type >= TOK_SMAC_PARAM) {
4301 Token *pcopy = tline, **ptail = &pcopy;
4302 Token *ttt, *pt;
4303 int i;
4305 ttt = params[t->type - TOK_SMAC_PARAM];
4306 i = paramsize[t->type - TOK_SMAC_PARAM];
4307 while (--i >= 0) {
4308 pt = *ptail = new_Token(tline, ttt->type,
4309 ttt->text, 0);
4310 ptail = &pt->next;
4311 ttt = ttt->next;
4313 tline = pcopy;
4314 } else if (t->type == TOK_PREPROC_Q) {
4315 tt = new_Token(tline, TOK_ID, mname, 0);
4316 tline = tt;
4317 } else if (t->type == TOK_PREPROC_QQ) {
4318 tt = new_Token(tline, TOK_ID, m->name, 0);
4319 tline = tt;
4320 } else {
4321 tt = new_Token(tline, t->type, t->text, 0);
4322 tline = tt;
4327 * Having done that, get rid of the macro call, and clean
4328 * up the parameters.
4330 nasm_free(params);
4331 nasm_free(paramsize);
4332 free_tlist(mstart);
4333 expanded = true;
4334 continue; /* main token loop */
4339 if (tline->type == TOK_SMAC_END) {
4340 tline->a.mac->in_progress = false;
4341 tline = delete_Token(tline);
4342 } else {
4343 t = *tail = tline;
4344 tline = tline->next;
4345 t->a.mac = NULL;
4346 t->next = NULL;
4347 tail = &t->next;
4352 * Now scan the entire line and look for successive TOK_IDs that resulted
4353 * after expansion (they can't be produced by tokenize()). The successive
4354 * TOK_IDs should be concatenated.
4355 * Also we look for %+ tokens and concatenate the tokens before and after
4356 * them (without white spaces in between).
4358 if (expanded) {
4359 const struct tokseq_match t[] = {
4361 PP_CONCAT_MASK(TOK_ID) |
4362 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4363 PP_CONCAT_MASK(TOK_ID) |
4364 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4365 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4368 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4370 * If we concatenated something, *and* we had previously expanded
4371 * an actual macro, scan the lines again for macros...
4373 tline = thead;
4374 expanded = false;
4375 goto again;
4379 err:
4380 if (org_tline) {
4381 if (thead) {
4382 *org_tline = *thead;
4383 /* since we just gave text to org_line, don't free it */
4384 thead->text = NULL;
4385 delete_Token(thead);
4386 } else {
4387 /* the expression expanded to empty line;
4388 we can't return NULL for some reasons
4389 we just set the line to a single WHITESPACE token. */
4390 memset(org_tline, 0, sizeof(*org_tline));
4391 org_tline->text = NULL;
4392 org_tline->type = TOK_WHITESPACE;
4394 thead = org_tline;
4397 return thead;
4401 * Similar to expand_smacro but used exclusively with macro identifiers
4402 * right before they are fetched in. The reason is that there can be
4403 * identifiers consisting of several subparts. We consider that if there
4404 * are more than one element forming the name, user wants a expansion,
4405 * otherwise it will be left as-is. Example:
4407 * %define %$abc cde
4409 * the identifier %$abc will be left as-is so that the handler for %define
4410 * will suck it and define the corresponding value. Other case:
4412 * %define _%$abc cde
4414 * In this case user wants name to be expanded *before* %define starts
4415 * working, so we'll expand %$abc into something (if it has a value;
4416 * otherwise it will be left as-is) then concatenate all successive
4417 * PP_IDs into one.
4419 static Token *expand_id(Token * tline)
4421 Token *cur, *oldnext = NULL;
4423 if (!tline || !tline->next)
4424 return tline;
4426 cur = tline;
4427 while (cur->next &&
4428 (cur->next->type == TOK_ID ||
4429 cur->next->type == TOK_PREPROC_ID
4430 || cur->next->type == TOK_NUMBER))
4431 cur = cur->next;
4433 /* If identifier consists of just one token, don't expand */
4434 if (cur == tline)
4435 return tline;
4437 if (cur) {
4438 oldnext = cur->next; /* Detach the tail past identifier */
4439 cur->next = NULL; /* so that expand_smacro stops here */
4442 tline = expand_smacro(tline);
4444 if (cur) {
4445 /* expand_smacro possibly changhed tline; re-scan for EOL */
4446 cur = tline;
4447 while (cur && cur->next)
4448 cur = cur->next;
4449 if (cur)
4450 cur->next = oldnext;
4453 return tline;
4457 * Determine whether the given line constitutes a multi-line macro
4458 * call, and return the MMacro structure called if so. Doesn't have
4459 * to check for an initial label - that's taken care of in
4460 * expand_mmacro - but must check numbers of parameters. Guaranteed
4461 * to be called with tline->type == TOK_ID, so the putative macro
4462 * name is easy to find.
4464 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4466 MMacro *head, *m;
4467 Token **params;
4468 int nparam;
4470 head = (MMacro *) hash_findix(&mmacros, tline->text);
4473 * Efficiency: first we see if any macro exists with the given
4474 * name. If not, we can return NULL immediately. _Then_ we
4475 * count the parameters, and then we look further along the
4476 * list if necessary to find the proper MMacro.
4478 list_for_each(m, head)
4479 if (!mstrcmp(m->name, tline->text, m->casesense))
4480 break;
4481 if (!m)
4482 return NULL;
4485 * OK, we have a potential macro. Count and demarcate the
4486 * parameters.
4488 count_mmac_params(tline->next, &nparam, &params);
4491 * So we know how many parameters we've got. Find the MMacro
4492 * structure that handles this number.
4494 while (m) {
4495 if (m->nparam_min <= nparam
4496 && (m->plus || nparam <= m->nparam_max)) {
4498 * This one is right. Just check if cycle removal
4499 * prohibits us using it before we actually celebrate...
4501 if (m->in_progress > m->max_depth) {
4502 if (m->max_depth > 0) {
4503 nasm_error(ERR_WARNING,
4504 "reached maximum recursion depth of %i",
4505 m->max_depth);
4507 nasm_free(params);
4508 return NULL;
4511 * It's right, and we can use it. Add its default
4512 * parameters to the end of our list if necessary.
4514 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4515 params =
4516 nasm_realloc(params,
4517 ((m->nparam_min + m->ndefs +
4518 1) * sizeof(*params)));
4519 while (nparam < m->nparam_min + m->ndefs) {
4520 params[nparam] = m->defaults[nparam - m->nparam_min];
4521 nparam++;
4525 * If we've gone over the maximum parameter count (and
4526 * we're in Plus mode), ignore parameters beyond
4527 * nparam_max.
4529 if (m->plus && nparam > m->nparam_max)
4530 nparam = m->nparam_max;
4532 * Then terminate the parameter list, and leave.
4534 if (!params) { /* need this special case */
4535 params = nasm_malloc(sizeof(*params));
4536 nparam = 0;
4538 params[nparam] = NULL;
4539 *params_array = params;
4540 return m;
4543 * This one wasn't right: look for the next one with the
4544 * same name.
4546 list_for_each(m, m->next)
4547 if (!mstrcmp(m->name, tline->text, m->casesense))
4548 break;
4552 * After all that, we didn't find one with the right number of
4553 * parameters. Issue a warning, and fail to expand the macro.
4555 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4556 "macro `%s' exists, but not taking %d parameters",
4557 tline->text, nparam);
4558 nasm_free(params);
4559 return NULL;
4564 * Save MMacro invocation specific fields in
4565 * preparation for a recursive macro expansion
4567 static void push_mmacro(MMacro *m)
4569 MMacroInvocation *i;
4571 i = nasm_malloc(sizeof(MMacroInvocation));
4572 i->prev = m->prev;
4573 i->params = m->params;
4574 i->iline = m->iline;
4575 i->nparam = m->nparam;
4576 i->rotate = m->rotate;
4577 i->paramlen = m->paramlen;
4578 i->unique = m->unique;
4579 i->condcnt = m->condcnt;
4580 m->prev = i;
4585 * Restore MMacro invocation specific fields that were
4586 * saved during a previous recursive macro expansion
4588 static void pop_mmacro(MMacro *m)
4590 MMacroInvocation *i;
4592 if (m->prev) {
4593 i = m->prev;
4594 m->prev = i->prev;
4595 m->params = i->params;
4596 m->iline = i->iline;
4597 m->nparam = i->nparam;
4598 m->rotate = i->rotate;
4599 m->paramlen = i->paramlen;
4600 m->unique = i->unique;
4601 m->condcnt = i->condcnt;
4602 nasm_free(i);
4608 * Expand the multi-line macro call made by the given line, if
4609 * there is one to be expanded. If there is, push the expansion on
4610 * istk->expansion and return 1. Otherwise return 0.
4612 static int expand_mmacro(Token * tline)
4614 Token *startline = tline;
4615 Token *label = NULL;
4616 int dont_prepend = 0;
4617 Token **params, *t, *tt;
4618 MMacro *m;
4619 Line *l, *ll;
4620 int i, nparam, *paramlen;
4621 const char *mname;
4623 t = tline;
4624 skip_white_(t);
4625 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4626 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4627 return 0;
4628 m = is_mmacro(t, &params);
4629 if (m) {
4630 mname = t->text;
4631 } else {
4632 Token *last;
4634 * We have an id which isn't a macro call. We'll assume
4635 * it might be a label; we'll also check to see if a
4636 * colon follows it. Then, if there's another id after
4637 * that lot, we'll check it again for macro-hood.
4639 label = last = t;
4640 t = t->next;
4641 if (tok_type_(t, TOK_WHITESPACE))
4642 last = t, t = t->next;
4643 if (tok_is_(t, ":")) {
4644 dont_prepend = 1;
4645 last = t, t = t->next;
4646 if (tok_type_(t, TOK_WHITESPACE))
4647 last = t, t = t->next;
4649 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4650 return 0;
4651 last->next = NULL;
4652 mname = t->text;
4653 tline = t;
4657 * Fix up the parameters: this involves stripping leading and
4658 * trailing whitespace, then stripping braces if they are
4659 * present.
4661 for (nparam = 0; params[nparam]; nparam++) ;
4662 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4664 for (i = 0; params[i]; i++) {
4665 int brace = 0;
4666 int comma = (!m->plus || i < nparam - 1);
4668 t = params[i];
4669 skip_white_(t);
4670 if (tok_is_(t, "{"))
4671 t = t->next, brace++, comma = false;
4672 params[i] = t;
4673 paramlen[i] = 0;
4674 while (t) {
4675 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4676 break; /* ... because we have hit a comma */
4677 if (comma && t->type == TOK_WHITESPACE
4678 && tok_is_(t->next, ","))
4679 break; /* ... or a space then a comma */
4680 if (brace && t->type == TOK_OTHER) {
4681 if (t->text[0] == '{')
4682 brace++; /* ... or a nested opening brace */
4683 else if (t->text[0] == '}')
4684 if (!--brace)
4685 break; /* ... or a brace */
4687 t = t->next;
4688 paramlen[i]++;
4690 if (brace)
4691 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4695 * OK, we have a MMacro structure together with a set of
4696 * parameters. We must now go through the expansion and push
4697 * copies of each Line on to istk->expansion. Substitution of
4698 * parameter tokens and macro-local tokens doesn't get done
4699 * until the single-line macro substitution process; this is
4700 * because delaying them allows us to change the semantics
4701 * later through %rotate.
4703 * First, push an end marker on to istk->expansion, mark this
4704 * macro as in progress, and set up its invocation-specific
4705 * variables.
4707 ll = nasm_malloc(sizeof(Line));
4708 ll->next = istk->expansion;
4709 ll->finishes = m;
4710 ll->first = NULL;
4711 istk->expansion = ll;
4714 * Save the previous MMacro expansion in the case of
4715 * macro recursion
4717 if (m->max_depth && m->in_progress)
4718 push_mmacro(m);
4720 m->in_progress ++;
4721 m->params = params;
4722 m->iline = tline;
4723 m->nparam = nparam;
4724 m->rotate = 0;
4725 m->paramlen = paramlen;
4726 m->unique = unique++;
4727 m->lineno = 0;
4728 m->condcnt = 0;
4730 m->next_active = istk->mstk;
4731 istk->mstk = m;
4733 list_for_each(l, m->expansion) {
4734 Token **tail;
4736 ll = nasm_malloc(sizeof(Line));
4737 ll->finishes = NULL;
4738 ll->next = istk->expansion;
4739 istk->expansion = ll;
4740 tail = &ll->first;
4742 list_for_each(t, l->first) {
4743 Token *x = t;
4744 switch (t->type) {
4745 case TOK_PREPROC_Q:
4746 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4747 break;
4748 case TOK_PREPROC_QQ:
4749 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4750 break;
4751 case TOK_PREPROC_ID:
4752 if (t->text[1] == '0' && t->text[2] == '0') {
4753 dont_prepend = -1;
4754 x = label;
4755 if (!x)
4756 continue;
4758 /* fall through */
4759 default:
4760 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4761 break;
4763 tail = &tt->next;
4765 *tail = NULL;
4769 * If we had a label, push it on as the first line of
4770 * the macro expansion.
4772 if (label) {
4773 if (dont_prepend < 0)
4774 free_tlist(startline);
4775 else {
4776 ll = nasm_malloc(sizeof(Line));
4777 ll->finishes = NULL;
4778 ll->next = istk->expansion;
4779 istk->expansion = ll;
4780 ll->first = startline;
4781 if (!dont_prepend) {
4782 while (label->next)
4783 label = label->next;
4784 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4789 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4791 return 1;
4795 * This function adds macro names to error messages, and suppresses
4796 * them if necessary.
4798 static void pp_verror(int severity, const char *fmt, va_list arg)
4800 char buff[BUFSIZ];
4801 MMacro *mmac = NULL;
4802 int delta = 0;
4805 * If we're in a dead branch of IF or something like it, ignore the error.
4806 * However, because %else etc are evaluated in the state context
4807 * of the previous branch, errors might get lost:
4808 * %if 0 ... %else trailing garbage ... %endif
4809 * So %else etc should set the ERR_PP_PRECOND flag.
4811 if ((severity & ERR_MASK) < ERR_FATAL &&
4812 istk && istk->conds &&
4813 ((severity & ERR_PP_PRECOND) ?
4814 istk->conds->state == COND_NEVER :
4815 emitting(istk->conds->state)))
4816 return;
4818 /* get %macro name */
4819 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4820 mmac = istk->mstk;
4821 /* but %rep blocks should be skipped */
4822 while (mmac && !mmac->name)
4823 mmac = mmac->next_active, delta++;
4826 if (mmac) {
4827 vsnprintf(buff, sizeof(buff), fmt, arg);
4829 nasm_set_verror(real_verror);
4830 nasm_error(severity, "(%s:%d) %s",
4831 mmac->name, mmac->lineno - delta, buff);
4832 nasm_set_verror(pp_verror);
4833 } else {
4834 real_verror(severity, fmt, arg);
4838 static void
4839 pp_reset(char *file, int apass, StrList **deplist)
4841 Token *t;
4843 cstk = NULL;
4844 istk = nasm_malloc(sizeof(Include));
4845 istk->next = NULL;
4846 istk->conds = NULL;
4847 istk->expansion = NULL;
4848 istk->mstk = NULL;
4849 istk->fp = fopen(file, "r");
4850 istk->fname = NULL;
4851 src_set_fname(nasm_strdup(file));
4852 src_set_linnum(0);
4853 istk->lineinc = 1;
4854 if (!istk->fp)
4855 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4856 defining = NULL;
4857 nested_mac_count = 0;
4858 nested_rep_count = 0;
4859 init_macros();
4860 unique = 0;
4861 if (tasm_compatible_mode) {
4862 stdmacpos = nasm_stdmac;
4863 } else {
4864 stdmacpos = nasm_stdmac_after_tasm;
4866 any_extrastdmac = extrastdmac && *extrastdmac;
4867 do_predef = true;
4870 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4871 * The caller, however, will also pass in 3 for preprocess-only so
4872 * we can set __PASS__ accordingly.
4874 pass = apass > 2 ? 2 : apass;
4876 dephead = deptail = deplist;
4877 if (deplist) {
4878 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4879 sl->next = NULL;
4880 strcpy(sl->str, file);
4881 *deptail = sl;
4882 deptail = &sl->next;
4886 * Define the __PASS__ macro. This is defined here unlike
4887 * all the other builtins, because it is special -- it varies between
4888 * passes.
4890 t = nasm_malloc(sizeof(*t));
4891 t->next = NULL;
4892 make_tok_num(t, apass);
4893 t->a.mac = NULL;
4894 define_smacro(NULL, "__PASS__", true, 0, t);
4897 static char *pp_getline(void)
4899 char *line;
4900 Token *tline;
4902 real_verror = nasm_set_verror(pp_verror);
4904 while (1) {
4906 * Fetch a tokenized line, either from the macro-expansion
4907 * buffer or from the input file.
4909 tline = NULL;
4910 while (istk->expansion && istk->expansion->finishes) {
4911 Line *l = istk->expansion;
4912 if (!l->finishes->name && l->finishes->in_progress > 1) {
4913 Line *ll;
4916 * This is a macro-end marker for a macro with no
4917 * name, which means it's not really a macro at all
4918 * but a %rep block, and the `in_progress' field is
4919 * more than 1, meaning that we still need to
4920 * repeat. (1 means the natural last repetition; 0
4921 * means termination by %exitrep.) We have
4922 * therefore expanded up to the %endrep, and must
4923 * push the whole block on to the expansion buffer
4924 * again. We don't bother to remove the macro-end
4925 * marker: we'd only have to generate another one
4926 * if we did.
4928 l->finishes->in_progress--;
4929 list_for_each(l, l->finishes->expansion) {
4930 Token *t, *tt, **tail;
4932 ll = nasm_malloc(sizeof(Line));
4933 ll->next = istk->expansion;
4934 ll->finishes = NULL;
4935 ll->first = NULL;
4936 tail = &ll->first;
4938 list_for_each(t, l->first) {
4939 if (t->text || t->type == TOK_WHITESPACE) {
4940 tt = *tail = new_Token(NULL, t->type, t->text, 0);
4941 tail = &tt->next;
4945 istk->expansion = ll;
4947 } else {
4949 * Check whether a `%rep' was started and not ended
4950 * within this macro expansion. This can happen and
4951 * should be detected. It's a fatal error because
4952 * I'm too confused to work out how to recover
4953 * sensibly from it.
4955 if (defining) {
4956 if (defining->name)
4957 nasm_panic(0, "defining with name in expansion");
4958 else if (istk->mstk->name)
4959 nasm_fatal(0, "`%%rep' without `%%endrep' within"
4960 " expansion of macro `%s'",
4961 istk->mstk->name);
4965 * FIXME: investigate the relationship at this point between
4966 * istk->mstk and l->finishes
4969 MMacro *m = istk->mstk;
4970 istk->mstk = m->next_active;
4971 if (m->name) {
4973 * This was a real macro call, not a %rep, and
4974 * therefore the parameter information needs to
4975 * be freed.
4977 if (m->prev) {
4978 pop_mmacro(m);
4979 l->finishes->in_progress --;
4980 } else {
4981 nasm_free(m->params);
4982 free_tlist(m->iline);
4983 nasm_free(m->paramlen);
4984 l->finishes->in_progress = 0;
4986 } else
4987 free_mmacro(m);
4989 istk->expansion = l->next;
4990 nasm_free(l);
4991 lfmt->downlevel(LIST_MACRO);
4994 while (1) { /* until we get a line we can use */
4996 if (istk->expansion) { /* from a macro expansion */
4997 char *p;
4998 Line *l = istk->expansion;
4999 if (istk->mstk)
5000 istk->mstk->lineno++;
5001 tline = l->first;
5002 istk->expansion = l->next;
5003 nasm_free(l);
5004 p = detoken(tline, false);
5005 lfmt->line(LIST_MACRO, p);
5006 nasm_free(p);
5007 break;
5009 line = read_line();
5010 if (line) { /* from the current input file */
5011 line = prepreproc(line);
5012 tline = tokenize(line);
5013 nasm_free(line);
5014 break;
5017 * The current file has ended; work down the istk
5020 Include *i = istk;
5021 fclose(i->fp);
5022 if (i->conds) {
5023 /* nasm_error can't be conditionally suppressed */
5024 nasm_fatal(0,
5025 "expected `%%endif' before end of file");
5027 /* only set line and file name if there's a next node */
5028 if (i->next) {
5029 src_set_linnum(i->lineno);
5030 nasm_free(src_set_fname(nasm_strdup(i->fname)));
5032 istk = i->next;
5033 lfmt->downlevel(LIST_INCLUDE);
5034 nasm_free(i);
5035 if (!istk) {
5036 line = NULL;
5037 goto done;
5039 if (istk->expansion && istk->expansion->finishes)
5040 break;
5045 * We must expand MMacro parameters and MMacro-local labels
5046 * _before_ we plunge into directive processing, to cope
5047 * with things like `%define something %1' such as STRUC
5048 * uses. Unless we're _defining_ a MMacro, in which case
5049 * those tokens should be left alone to go into the
5050 * definition; and unless we're in a non-emitting
5051 * condition, in which case we don't want to meddle with
5052 * anything.
5054 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5055 && !(istk->mstk && !istk->mstk->in_progress)) {
5056 tline = expand_mmac_params(tline);
5060 * Check the line to see if it's a preprocessor directive.
5062 if (do_directive(tline) == DIRECTIVE_FOUND) {
5063 continue;
5064 } else if (defining) {
5066 * We're defining a multi-line macro. We emit nothing
5067 * at all, and just
5068 * shove the tokenized line on to the macro definition.
5070 Line *l = nasm_malloc(sizeof(Line));
5071 l->next = defining->expansion;
5072 l->first = tline;
5073 l->finishes = NULL;
5074 defining->expansion = l;
5075 continue;
5076 } else if (istk->conds && !emitting(istk->conds->state)) {
5078 * We're in a non-emitting branch of a condition block.
5079 * Emit nothing at all, not even a blank line: when we
5080 * emerge from the condition we'll give a line-number
5081 * directive so we keep our place correctly.
5083 free_tlist(tline);
5084 continue;
5085 } else if (istk->mstk && !istk->mstk->in_progress) {
5087 * We're in a %rep block which has been terminated, so
5088 * we're walking through to the %endrep without
5089 * emitting anything. Emit nothing at all, not even a
5090 * blank line: when we emerge from the %rep block we'll
5091 * give a line-number directive so we keep our place
5092 * correctly.
5094 free_tlist(tline);
5095 continue;
5096 } else {
5097 tline = expand_smacro(tline);
5098 if (!expand_mmacro(tline)) {
5100 * De-tokenize the line again, and emit it.
5102 line = detoken(tline, true);
5103 free_tlist(tline);
5104 break;
5105 } else {
5106 continue; /* expand_mmacro calls free_tlist */
5111 done:
5112 nasm_set_verror(real_verror);
5113 return line;
5116 static void pp_cleanup(int pass)
5118 real_verror = nasm_set_verror(pp_verror);
5120 if (defining) {
5121 if (defining->name) {
5122 nasm_error(ERR_NONFATAL,
5123 "end of file while still defining macro `%s'",
5124 defining->name);
5125 } else {
5126 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5129 free_mmacro(defining);
5130 defining = NULL;
5133 nasm_set_verror(real_verror);
5135 while (cstk)
5136 ctx_pop();
5137 free_macros();
5138 while (istk) {
5139 Include *i = istk;
5140 istk = istk->next;
5141 fclose(i->fp);
5142 nasm_free(i->fname);
5143 nasm_free(i);
5145 while (cstk)
5146 ctx_pop();
5147 nasm_free(src_set_fname(NULL));
5148 if (pass == 0) {
5149 IncPath *i;
5150 free_llist(predef);
5151 predef = NULL;
5152 delete_Blocks();
5153 freeTokens = NULL;
5154 while ((i = ipath)) {
5155 ipath = i->next;
5156 if (i->path)
5157 nasm_free(i->path);
5158 nasm_free(i);
5163 static void pp_include_path(char *path)
5165 IncPath *i;
5167 i = nasm_malloc(sizeof(IncPath));
5168 i->path = path ? nasm_strdup(path) : NULL;
5169 i->next = NULL;
5171 if (ipath) {
5172 IncPath *j = ipath;
5173 while (j->next)
5174 j = j->next;
5175 j->next = i;
5176 } else {
5177 ipath = i;
5181 static void pp_pre_include(char *fname)
5183 Token *inc, *space, *name;
5184 Line *l;
5186 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5187 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5188 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5190 l = nasm_malloc(sizeof(Line));
5191 l->next = predef;
5192 l->first = inc;
5193 l->finishes = NULL;
5194 predef = l;
5197 static void pp_pre_define(char *definition)
5199 Token *def, *space;
5200 Line *l;
5201 char *equals;
5203 real_verror = nasm_set_verror(pp_verror);
5205 equals = strchr(definition, '=');
5206 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5207 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5208 if (equals)
5209 *equals = ' ';
5210 space->next = tokenize(definition);
5211 if (equals)
5212 *equals = '=';
5214 if (space->next->type != TOK_PREPROC_ID &&
5215 space->next->type != TOK_ID)
5216 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5218 l = nasm_malloc(sizeof(Line));
5219 l->next = predef;
5220 l->first = def;
5221 l->finishes = NULL;
5222 predef = l;
5224 nasm_set_verror(real_verror);
5227 static void pp_pre_undefine(char *definition)
5229 Token *def, *space;
5230 Line *l;
5232 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5233 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5234 space->next = tokenize(definition);
5236 l = nasm_malloc(sizeof(Line));
5237 l->next = predef;
5238 l->first = def;
5239 l->finishes = NULL;
5240 predef = l;
5243 static void pp_extra_stdmac(macros_t *macros)
5245 extrastdmac = macros;
5248 static void make_tok_num(Token * tok, int64_t val)
5250 char numbuf[32];
5251 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5252 tok->text = nasm_strdup(numbuf);
5253 tok->type = TOK_NUMBER;
5256 const struct preproc_ops nasmpp = {
5257 pp_reset,
5258 pp_getline,
5259 pp_cleanup,
5260 pp_extra_stdmac,
5261 pp_pre_define,
5262 pp_pre_undefine,
5263 pp_pre_include,
5264 pp_include_path