outmacho: Fix relative relocations for 32-bit Mach-O (fix typo)
[nasm.git] / preproc.c
blob9dc3d88da5ad3dc33699d66f6f10ac9273600c47
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>
72 #include <inttypes.h>
74 #include "nasm.h"
75 #include "nasmlib.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
83 #include "listing.h"
85 typedef struct SMacro SMacro;
86 typedef struct MMacro MMacro;
87 typedef struct MMacroInvocation MMacroInvocation;
88 typedef struct Context Context;
89 typedef struct Token Token;
90 typedef struct Blocks Blocks;
91 typedef struct Line Line;
92 typedef struct Include Include;
93 typedef struct Cond Cond;
94 typedef struct IncPath IncPath;
97 * Note on the storage of both SMacro and MMacros: the hash table
98 * indexes them case-insensitively, and we then have to go through a
99 * linked list of potential case aliases (and, for MMacros, parameter
100 * ranges); this is to preserve the matching semantics of the earlier
101 * code. If the number of case aliases for a specific macro is a
102 * performance issue, you may want to reconsider your coding style.
106 * Store the definition of a single-line macro.
108 struct SMacro {
109 SMacro *next;
110 char *name;
111 bool casesense;
112 bool in_progress;
113 unsigned int nparam;
114 Token *expansion;
118 * Store the definition of a multi-line macro. This is also used to
119 * store the interiors of `%rep...%endrep' blocks, which are
120 * effectively self-re-invoking multi-line macros which simply
121 * don't have a name or bother to appear in the hash tables. %rep
122 * blocks are signified by having a NULL `name' field.
124 * In a MMacro describing a `%rep' block, the `in_progress' field
125 * isn't merely boolean, but gives the number of repeats left to
126 * run.
128 * The `next' field is used for storing MMacros in hash tables; the
129 * `next_active' field is for stacking them on istk entries.
131 * When a MMacro is being expanded, `params', `iline', `nparam',
132 * `paramlen', `rotate' and `unique' are local to the invocation.
134 struct MMacro {
135 MMacro *next;
136 MMacroInvocation *prev; /* previous invocation */
137 char *name;
138 int nparam_min, nparam_max;
139 bool casesense;
140 bool plus; /* is the last parameter greedy? */
141 bool nolist; /* is this macro listing-inhibited? */
142 int64_t in_progress; /* is this macro currently being expanded? */
143 int32_t max_depth; /* maximum number of recursive expansions allowed */
144 Token *dlist; /* All defaults as one list */
145 Token **defaults; /* Parameter default pointers */
146 int ndefs; /* number of default parameters */
147 Line *expansion;
149 MMacro *next_active;
150 MMacro *rep_nest; /* used for nesting %rep */
151 Token **params; /* actual parameters */
152 Token *iline; /* invocation line */
153 unsigned int nparam, rotate;
154 int *paramlen;
155 uint64_t unique;
156 int lineno; /* Current line number on expansion */
157 uint64_t condcnt; /* number of if blocks... */
159 const char *fname; /* File where defined */
160 int32_t xline; /* First line in macro */
164 /* Store the definition of a multi-line macro, as defined in a
165 * previous recursive macro expansion.
167 struct MMacroInvocation {
168 MMacroInvocation *prev; /* previous invocation */
169 Token **params; /* actual parameters */
170 Token *iline; /* invocation line */
171 unsigned int nparam, rotate;
172 int *paramlen;
173 uint64_t unique;
174 uint64_t condcnt;
179 * The context stack is composed of a linked list of these.
181 struct Context {
182 Context *next;
183 char *name;
184 struct hash_table localmac;
185 uint32_t number;
189 * This is the internal form which we break input lines up into.
190 * Typically stored in linked lists.
192 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
193 * necessarily used as-is, but is intended to denote the number of
194 * the substituted parameter. So in the definition
196 * %define a(x,y) ( (x) & ~(y) )
198 * the token representing `x' will have its type changed to
199 * TOK_SMAC_PARAM, but the one representing `y' will be
200 * TOK_SMAC_PARAM+1.
202 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
203 * which doesn't need quotes around it. Used in the pre-include
204 * mechanism as an alternative to trying to find a sensible type of
205 * quote to use on the filename we were passed.
207 enum pp_token_type {
208 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
209 TOK_PREPROC_ID, TOK_STRING,
210 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
211 TOK_INTERNAL_STRING,
212 TOK_PREPROC_Q, TOK_PREPROC_QQ,
213 TOK_PASTE, /* %+ */
214 TOK_INDIRECT, /* %[...] */
215 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
216 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
219 #define PP_CONCAT_MASK(x) (1 << (x))
220 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
222 struct tokseq_match {
223 int mask_head;
224 int mask_tail;
227 struct Token {
228 Token *next;
229 char *text;
230 union {
231 SMacro *mac; /* associated macro for TOK_SMAC_END */
232 size_t len; /* scratch length field */
233 } a; /* Auxiliary data */
234 enum pp_token_type type;
238 * Multi-line macro definitions are stored as a linked list of
239 * these, which is essentially a container to allow several linked
240 * lists of Tokens.
242 * Note that in this module, linked lists are treated as stacks
243 * wherever possible. For this reason, Lines are _pushed_ on to the
244 * `expansion' field in MMacro structures, so that the linked list,
245 * if walked, would give the macro lines in reverse order; this
246 * means that we can walk the list when expanding a macro, and thus
247 * push the lines on to the `expansion' field in _istk_ in reverse
248 * order (so that when popped back off they are in the right
249 * order). It may seem cockeyed, and it relies on my design having
250 * an even number of steps in, but it works...
252 * Some of these structures, rather than being actual lines, are
253 * markers delimiting the end of the expansion of a given macro.
254 * This is for use in the cycle-tracking and %rep-handling code.
255 * Such structures have `finishes' non-NULL, and `first' NULL. All
256 * others have `finishes' NULL, but `first' may still be NULL if
257 * the line is blank.
259 struct Line {
260 Line *next;
261 MMacro *finishes;
262 Token *first;
266 * To handle an arbitrary level of file inclusion, we maintain a
267 * stack (ie linked list) of these things.
269 struct Include {
270 Include *next;
271 FILE *fp;
272 Cond *conds;
273 Line *expansion;
274 const char *fname;
275 int lineno, lineinc;
276 MMacro *mstk; /* stack of active macros/reps */
280 * Include search path. This is simply a list of strings which get
281 * prepended, in turn, to the name of an include file, in an
282 * attempt to find the file if it's not in the current directory.
284 struct IncPath {
285 IncPath *next;
286 char *path;
290 * Conditional assembly: we maintain a separate stack of these for
291 * each level of file inclusion. (The only reason we keep the
292 * stacks separate is to ensure that a stray `%endif' in a file
293 * included from within the true branch of a `%if' won't terminate
294 * it and cause confusion: instead, rightly, it'll cause an error.)
296 struct Cond {
297 Cond *next;
298 int state;
300 enum {
302 * These states are for use just after %if or %elif: IF_TRUE
303 * means the condition has evaluated to truth so we are
304 * currently emitting, whereas IF_FALSE means we are not
305 * currently emitting but will start doing so if a %else comes
306 * up. In these states, all directives are admissible: %elif,
307 * %else and %endif. (And of course %if.)
309 COND_IF_TRUE, COND_IF_FALSE,
311 * These states come up after a %else: ELSE_TRUE means we're
312 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
313 * any %elif or %else will cause an error.
315 COND_ELSE_TRUE, COND_ELSE_FALSE,
317 * These states mean that we're not emitting now, and also that
318 * nothing until %endif will be emitted at all. COND_DONE is
319 * used when we've had our moment of emission
320 * and have now started seeing %elifs. COND_NEVER is used when
321 * the condition construct in question is contained within a
322 * non-emitting branch of a larger condition construct,
323 * or if there is an error.
325 COND_DONE, COND_NEVER
327 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
330 * These defines are used as the possible return values for do_directive
332 #define NO_DIRECTIVE_FOUND 0
333 #define DIRECTIVE_FOUND 1
336 * This define sets the upper limit for smacro and recursive mmacro
337 * expansions
339 #define DEADMAN_LIMIT (1 << 20)
341 /* max reps */
342 #define REP_LIMIT ((INT64_C(1) << 62))
345 * Condition codes. Note that we use c_ prefix not C_ because C_ is
346 * used in nasm.h for the "real" condition codes. At _this_ level,
347 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
348 * ones, so we need a different enum...
350 static const char * const conditions[] = {
351 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
352 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
353 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
355 enum pp_conds {
356 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
357 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
358 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
359 c_none = -1
361 static const enum pp_conds inverse_ccs[] = {
362 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
363 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,
364 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
368 * Directive names.
370 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
371 static int is_condition(enum preproc_token arg)
373 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
376 /* For TASM compatibility we need to be able to recognise TASM compatible
377 * conditional compilation directives. Using the NASM pre-processor does
378 * not work, so we look for them specifically from the following list and
379 * then jam in the equivalent NASM directive into the input stream.
382 enum {
383 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
384 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
387 static const char * const tasm_directives[] = {
388 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
389 "ifndef", "include", "local"
392 static int StackSize = 4;
393 static char *StackPointer = "ebp";
394 static int ArgOffset = 8;
395 static int LocalOffset = 0;
397 static Context *cstk;
398 static Include *istk;
399 static IncPath *ipath = NULL;
401 static int pass; /* HACK: pass 0 = generate dependencies only */
402 static StrList **dephead, **deptail; /* Dependency list */
404 static uint64_t unique; /* unique identifier numbers */
406 static Line *predef = NULL;
407 static bool do_predef;
410 * The current set of multi-line macros we have defined.
412 static struct hash_table mmacros;
415 * The current set of single-line macros we have defined.
417 static struct hash_table smacros;
420 * The multi-line macro we are currently defining, or the %rep
421 * block we are currently reading, if any.
423 static MMacro *defining;
425 static uint64_t nested_mac_count;
426 static uint64_t nested_rep_count;
429 * The number of macro parameters to allocate space for at a time.
431 #define PARAM_DELTA 16
434 * The standard macro set: defined in macros.c in the array nasm_stdmac.
435 * This gives our position in the macro set, when we're processing it.
437 static macros_t *stdmacpos;
440 * The extra standard macros that come from the object format, if
441 * any.
443 static macros_t *extrastdmac = NULL;
444 static bool any_extrastdmac;
447 * Tokens are allocated in blocks to improve speed
449 #define TOKEN_BLOCKSIZE 4096
450 static Token *freeTokens = NULL;
451 struct Blocks {
452 Blocks *next;
453 void *chunk;
456 static Blocks blocks = { NULL, NULL };
459 * Forward declarations.
461 static Token *expand_mmac_params(Token * tline);
462 static Token *expand_smacro(Token * tline);
463 static Token *expand_id(Token * tline);
464 static Context *get_ctx(const char *name, const char **namep);
465 static void make_tok_num(Token * tok, int64_t val);
466 static void pp_verror(int severity, const char *fmt, va_list ap);
467 static vefunc real_verror;
468 static void *new_Block(size_t size);
469 static void delete_Blocks(void);
470 static Token *new_Token(Token * next, enum pp_token_type type,
471 const char *text, int txtlen);
472 static Token *delete_Token(Token * t);
475 * Macros for safe checking of token pointers, avoid *(NULL)
477 #define tok_type_(x,t) ((x) && (x)->type == (t))
478 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
479 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
480 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
483 * nasm_unquote with error if the string contains NUL characters.
484 * If the string contains NUL characters, issue an error and return
485 * the C len, i.e. truncate at the NUL.
487 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
489 size_t len = nasm_unquote(qstr, NULL);
490 size_t clen = strlen(qstr);
492 if (len != clen)
493 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
494 pp_directives[directive]);
496 return clen;
500 * In-place reverse a list of tokens.
502 static Token *reverse_tokens(Token *t)
504 Token *prev = NULL;
505 Token *next;
507 while (t) {
508 next = t->next;
509 t->next = prev;
510 prev = t;
511 t = next;
514 return prev;
518 * Handle TASM specific directives, which do not contain a % in
519 * front of them. We do it here because I could not find any other
520 * place to do it for the moment, and it is a hack (ideally it would
521 * be nice to be able to use the NASM pre-processor to do it).
523 static char *check_tasm_directive(char *line)
525 int32_t i, j, k, m, len;
526 char *p, *q, *oldline, oldchar;
528 p = nasm_skip_spaces(line);
530 /* Binary search for the directive name */
531 i = -1;
532 j = ARRAY_SIZE(tasm_directives);
533 q = nasm_skip_word(p);
534 len = q - p;
535 if (len) {
536 oldchar = p[len];
537 p[len] = 0;
538 while (j - i > 1) {
539 k = (j + i) / 2;
540 m = nasm_stricmp(p, tasm_directives[k]);
541 if (m == 0) {
542 /* We have found a directive, so jam a % in front of it
543 * so that NASM will then recognise it as one if it's own.
545 p[len] = oldchar;
546 len = strlen(p);
547 oldline = line;
548 line = nasm_malloc(len + 2);
549 line[0] = '%';
550 if (k == TM_IFDIFI) {
552 * NASM does not recognise IFDIFI, so we convert
553 * it to %if 0. This is not used in NASM
554 * compatible code, but does need to parse for the
555 * TASM macro package.
557 strcpy(line + 1, "if 0");
558 } else {
559 memcpy(line + 1, p, len + 1);
561 nasm_free(oldline);
562 return line;
563 } else if (m < 0) {
564 j = k;
565 } else
566 i = k;
568 p[len] = oldchar;
570 return line;
574 * The pre-preprocessing stage... This function translates line
575 * number indications as they emerge from GNU cpp (`# lineno "file"
576 * flags') into NASM preprocessor line number indications (`%line
577 * lineno file').
579 static char *prepreproc(char *line)
581 int lineno, fnlen;
582 char *fname, *oldline;
584 if (line[0] == '#' && line[1] == ' ') {
585 oldline = line;
586 fname = oldline + 2;
587 lineno = atoi(fname);
588 fname += strspn(fname, "0123456789 ");
589 if (*fname == '"')
590 fname++;
591 fnlen = strcspn(fname, "\"");
592 line = nasm_malloc(20 + fnlen);
593 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
594 nasm_free(oldline);
596 if (tasm_compatible_mode)
597 return check_tasm_directive(line);
598 return line;
602 * Free a linked list of tokens.
604 static void free_tlist(Token * list)
606 while (list)
607 list = delete_Token(list);
611 * Free a linked list of lines.
613 static void free_llist(Line * list)
615 Line *l, *tmp;
616 list_for_each_safe(l, tmp, list) {
617 free_tlist(l->first);
618 nasm_free(l);
623 * Free an MMacro
625 static void free_mmacro(MMacro * m)
627 nasm_free(m->name);
628 free_tlist(m->dlist);
629 nasm_free(m->defaults);
630 free_llist(m->expansion);
631 nasm_free(m);
635 * Free all currently defined macros, and free the hash tables
637 static void free_smacro_table(struct hash_table *smt)
639 SMacro *s, *tmp;
640 const char *key;
641 struct hash_tbl_node *it = NULL;
643 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
644 nasm_free((void *)key);
645 list_for_each_safe(s, tmp, s) {
646 nasm_free(s->name);
647 free_tlist(s->expansion);
648 nasm_free(s);
651 hash_free(smt);
654 static void free_mmacro_table(struct hash_table *mmt)
656 MMacro *m, *tmp;
657 const char *key;
658 struct hash_tbl_node *it = NULL;
660 it = NULL;
661 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
662 nasm_free((void *)key);
663 list_for_each_safe(m ,tmp, m)
664 free_mmacro(m);
666 hash_free(mmt);
669 static void free_macros(void)
671 free_smacro_table(&smacros);
672 free_mmacro_table(&mmacros);
676 * Initialize the hash tables
678 static void init_macros(void)
680 hash_init(&smacros, HASH_LARGE);
681 hash_init(&mmacros, HASH_LARGE);
685 * Pop the context stack.
687 static void ctx_pop(void)
689 Context *c = cstk;
691 cstk = cstk->next;
692 free_smacro_table(&c->localmac);
693 nasm_free(c->name);
694 nasm_free(c);
698 * Search for a key in the hash index; adding it if necessary
699 * (in which case we initialize the data pointer to NULL.)
701 static void **
702 hash_findi_add(struct hash_table *hash, const char *str)
704 struct hash_insert hi;
705 void **r;
706 char *strx;
708 r = hash_findi(hash, str, &hi);
709 if (r)
710 return r;
712 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
713 return hash_add(&hi, strx, NULL);
717 * Like hash_findi, but returns the data element rather than a pointer
718 * to it. Used only when not adding a new element, hence no third
719 * argument.
721 static void *
722 hash_findix(struct hash_table *hash, const char *str)
724 void **p;
726 p = hash_findi(hash, str, NULL);
727 return p ? *p : NULL;
731 * read line from standart macros set,
732 * if there no more left -- return NULL
734 static char *line_from_stdmac(void)
736 unsigned char c;
737 const unsigned char *p = stdmacpos;
738 char *line, *q;
739 size_t len = 0;
741 if (!stdmacpos)
742 return NULL;
744 while ((c = *p++)) {
745 if (c >= 0x80)
746 len += pp_directives_len[c - 0x80] + 1;
747 else
748 len++;
751 line = nasm_malloc(len + 1);
752 q = line;
753 while ((c = *stdmacpos++)) {
754 if (c >= 0x80) {
755 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
756 q += pp_directives_len[c - 0x80];
757 *q++ = ' ';
758 } else {
759 *q++ = c;
762 stdmacpos = p;
763 *q = '\0';
765 if (!*stdmacpos) {
766 /* This was the last of the standard macro chain... */
767 stdmacpos = NULL;
768 if (any_extrastdmac) {
769 stdmacpos = extrastdmac;
770 any_extrastdmac = false;
771 } else if (do_predef) {
772 Line *pd, *l;
773 Token *head, **tail, *t;
776 * Nasty hack: here we push the contents of
777 * `predef' on to the top-level expansion stack,
778 * since this is the most convenient way to
779 * implement the pre-include and pre-define
780 * features.
782 list_for_each(pd, predef) {
783 head = NULL;
784 tail = &head;
785 list_for_each(t, pd->first) {
786 *tail = new_Token(NULL, t->type, t->text, 0);
787 tail = &(*tail)->next;
790 l = nasm_malloc(sizeof(Line));
791 l->next = istk->expansion;
792 l->first = head;
793 l->finishes = NULL;
795 istk->expansion = l;
797 do_predef = false;
801 return line;
804 static char *read_line(void)
806 unsigned int size, c, next;
807 const unsigned int delta = 512;
808 const unsigned int pad = 8;
809 unsigned int nr_cont = 0;
810 bool cont = false;
811 char *buffer, *p;
813 /* Standart macros set (predefined) goes first */
814 p = line_from_stdmac();
815 if (p)
816 return p;
818 size = delta;
819 p = buffer = nasm_malloc(size);
821 for (;;) {
822 c = fgetc(istk->fp);
823 if ((int)(c) == EOF) {
824 p[0] = 0;
825 break;
828 switch (c) {
829 case '\r':
830 next = fgetc(istk->fp);
831 if (next != '\n')
832 ungetc(next, istk->fp);
833 if (cont) {
834 cont = false;
835 continue;
837 break;
839 case '\n':
840 if (cont) {
841 cont = false;
842 continue;
844 break;
846 case '\\':
847 next = fgetc(istk->fp);
848 ungetc(next, istk->fp);
849 if (next == '\r' || next == '\n') {
850 cont = true;
851 nr_cont++;
852 continue;
854 break;
857 if (c == '\r' || c == '\n') {
858 *p++ = 0;
859 break;
862 if (p >= (buffer + size - pad)) {
863 buffer = nasm_realloc(buffer, size + delta);
864 p = buffer + size - pad;
865 size += delta;
868 *p++ = (unsigned char)c;
871 if (p == buffer) {
872 nasm_free(buffer);
873 return NULL;
876 src_set_linnum(src_get_linnum() + istk->lineinc +
877 (nr_cont * istk->lineinc));
880 * Handle spurious ^Z, which may be inserted into source files
881 * by some file transfer utilities.
883 buffer[strcspn(buffer, "\032")] = '\0';
885 lfmt->line(LIST_READ, buffer);
887 return buffer;
891 * Tokenize a line of text. This is a very simple process since we
892 * don't need to parse the value out of e.g. numeric tokens: we
893 * simply split one string into many.
895 static Token *tokenize(char *line)
897 char c, *p = line;
898 enum pp_token_type type;
899 Token *list = NULL;
900 Token *t, **tail = &list;
902 while (*line) {
903 p = line;
904 if (*p == '%') {
905 p++;
906 if (*p == '+' && !nasm_isdigit(p[1])) {
907 p++;
908 type = TOK_PASTE;
909 } else if (nasm_isdigit(*p) ||
910 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
911 do {
912 p++;
914 while (nasm_isdigit(*p));
915 type = TOK_PREPROC_ID;
916 } else if (*p == '{') {
917 p++;
918 while (*p) {
919 if (*p == '}')
920 break;
921 p[-1] = *p;
922 p++;
924 if (*p != '}')
925 nasm_error(ERR_WARNING | ERR_PASS1,
926 "unterminated %%{ construct");
927 p[-1] = '\0';
928 if (*p)
929 p++;
930 type = TOK_PREPROC_ID;
931 } else if (*p == '[') {
932 int lvl = 1;
933 line += 2; /* Skip the leading %[ */
934 p++;
935 while (lvl && (c = *p++)) {
936 switch (c) {
937 case ']':
938 lvl--;
939 break;
940 case '%':
941 if (*p == '[')
942 lvl++;
943 break;
944 case '\'':
945 case '\"':
946 case '`':
947 p = nasm_skip_string(p - 1) + 1;
948 break;
949 default:
950 break;
953 p--;
954 if (*p)
955 *p++ = '\0';
956 if (lvl)
957 nasm_error(ERR_NONFATAL|ERR_PASS1,
958 "unterminated %%[ construct");
959 type = TOK_INDIRECT;
960 } else if (*p == '?') {
961 type = TOK_PREPROC_Q; /* %? */
962 p++;
963 if (*p == '?') {
964 type = TOK_PREPROC_QQ; /* %?? */
965 p++;
967 } else if (*p == '!') {
968 type = TOK_PREPROC_ID;
969 p++;
970 if (isidchar(*p)) {
971 do {
972 p++;
974 while (isidchar(*p));
975 } else if (*p == '\'' || *p == '\"' || *p == '`') {
976 p = nasm_skip_string(p);
977 if (*p)
978 p++;
979 else
980 nasm_error(ERR_NONFATAL|ERR_PASS1,
981 "unterminated %%! string");
982 } else {
983 /* %! without string or identifier */
984 type = TOK_OTHER; /* Legacy behavior... */
986 } else if (isidchar(*p) ||
987 ((*p == '!' || *p == '%' || *p == '$') &&
988 isidchar(p[1]))) {
989 do {
990 p++;
992 while (isidchar(*p));
993 type = TOK_PREPROC_ID;
994 } else {
995 type = TOK_OTHER;
996 if (*p == '%')
997 p++;
999 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1000 type = TOK_ID;
1001 p++;
1002 while (*p && isidchar(*p))
1003 p++;
1004 } else if (*p == '\'' || *p == '"' || *p == '`') {
1006 * A string token.
1008 type = TOK_STRING;
1009 p = nasm_skip_string(p);
1011 if (*p) {
1012 p++;
1013 } else {
1014 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1015 /* Handling unterminated strings by UNV */
1016 /* type = -1; */
1018 } else if (p[0] == '$' && p[1] == '$') {
1019 type = TOK_OTHER; /* TOKEN_BASE */
1020 p += 2;
1021 } else if (isnumstart(*p)) {
1022 bool is_hex = false;
1023 bool is_float = false;
1024 bool has_e = false;
1025 char c, *r;
1028 * A numeric token.
1031 if (*p == '$') {
1032 p++;
1033 is_hex = true;
1036 for (;;) {
1037 c = *p++;
1039 if (!is_hex && (c == 'e' || c == 'E')) {
1040 has_e = true;
1041 if (*p == '+' || *p == '-') {
1043 * e can only be followed by +/- if it is either a
1044 * prefixed hex number or a floating-point number
1046 p++;
1047 is_float = true;
1049 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1050 is_hex = true;
1051 } else if (c == 'P' || c == 'p') {
1052 is_float = true;
1053 if (*p == '+' || *p == '-')
1054 p++;
1055 } else if (isnumchar(c) || c == '_')
1056 ; /* just advance */
1057 else if (c == '.') {
1059 * we need to deal with consequences of the legacy
1060 * parser, like "1.nolist" being two tokens
1061 * (TOK_NUMBER, TOK_ID) here; at least give it
1062 * a shot for now. In the future, we probably need
1063 * a flex-based scanner with proper pattern matching
1064 * to do it as well as it can be done. Nothing in
1065 * the world is going to help the person who wants
1066 * 0x123.p16 interpreted as two tokens, though.
1068 r = p;
1069 while (*r == '_')
1070 r++;
1072 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1073 (!is_hex && (*r == 'e' || *r == 'E')) ||
1074 (*r == 'p' || *r == 'P')) {
1075 p = r;
1076 is_float = true;
1077 } else
1078 break; /* Terminate the token */
1079 } else
1080 break;
1082 p--; /* Point to first character beyond number */
1084 if (p == line+1 && *line == '$') {
1085 type = TOK_OTHER; /* TOKEN_HERE */
1086 } else {
1087 if (has_e && !is_hex) {
1088 /* 1e13 is floating-point, but 1e13h is not */
1089 is_float = true;
1092 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1094 } else if (nasm_isspace(*p)) {
1095 type = TOK_WHITESPACE;
1096 p = nasm_skip_spaces(p);
1098 * Whitespace just before end-of-line is discarded by
1099 * pretending it's a comment; whitespace just before a
1100 * comment gets lumped into the comment.
1102 if (!*p || *p == ';') {
1103 type = TOK_COMMENT;
1104 while (*p)
1105 p++;
1107 } else if (*p == ';') {
1108 type = TOK_COMMENT;
1109 while (*p)
1110 p++;
1111 } else {
1113 * Anything else is an operator of some kind. We check
1114 * for all the double-character operators (>>, <<, //,
1115 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1116 * else is a single-character operator.
1118 type = TOK_OTHER;
1119 if ((p[0] == '>' && p[1] == '>') ||
1120 (p[0] == '<' && p[1] == '<') ||
1121 (p[0] == '/' && p[1] == '/') ||
1122 (p[0] == '<' && p[1] == '=') ||
1123 (p[0] == '>' && p[1] == '=') ||
1124 (p[0] == '=' && p[1] == '=') ||
1125 (p[0] == '!' && p[1] == '=') ||
1126 (p[0] == '<' && p[1] == '>') ||
1127 (p[0] == '&' && p[1] == '&') ||
1128 (p[0] == '|' && p[1] == '|') ||
1129 (p[0] == '^' && p[1] == '^')) {
1130 p++;
1132 p++;
1135 /* Handling unterminated string by UNV */
1136 /*if (type == -1)
1138 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1139 t->text[p-line] = *line;
1140 tail = &t->next;
1142 else */
1143 if (type != TOK_COMMENT) {
1144 *tail = t = new_Token(NULL, type, line, p - line);
1145 tail = &t->next;
1147 line = p;
1149 return list;
1153 * this function allocates a new managed block of memory and
1154 * returns a pointer to the block. The managed blocks are
1155 * deleted only all at once by the delete_Blocks function.
1157 static void *new_Block(size_t size)
1159 Blocks *b = &blocks;
1161 /* first, get to the end of the linked list */
1162 while (b->next)
1163 b = b->next;
1164 /* now allocate the requested chunk */
1165 b->chunk = nasm_malloc(size);
1167 /* now allocate a new block for the next request */
1168 b->next = nasm_zalloc(sizeof(Blocks));
1169 return b->chunk;
1173 * this function deletes all managed blocks of memory
1175 static void delete_Blocks(void)
1177 Blocks *a, *b = &blocks;
1180 * keep in mind that the first block, pointed to by blocks
1181 * is a static and not dynamically allocated, so we don't
1182 * free it.
1184 while (b) {
1185 if (b->chunk)
1186 nasm_free(b->chunk);
1187 a = b;
1188 b = b->next;
1189 if (a != &blocks)
1190 nasm_free(a);
1192 memset(&blocks, 0, sizeof(blocks));
1196 * this function creates a new Token and passes a pointer to it
1197 * back to the caller. It sets the type and text elements, and
1198 * also the a.mac and next elements to NULL.
1200 static Token *new_Token(Token * next, enum pp_token_type type,
1201 const char *text, int txtlen)
1203 Token *t;
1204 int i;
1206 if (!freeTokens) {
1207 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1208 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1209 freeTokens[i].next = &freeTokens[i + 1];
1210 freeTokens[i].next = NULL;
1212 t = freeTokens;
1213 freeTokens = t->next;
1214 t->next = next;
1215 t->a.mac = NULL;
1216 t->type = type;
1217 if (type == TOK_WHITESPACE || !text) {
1218 t->text = NULL;
1219 } else {
1220 if (txtlen == 0)
1221 txtlen = strlen(text);
1222 t->text = nasm_malloc(txtlen+1);
1223 memcpy(t->text, text, txtlen);
1224 t->text[txtlen] = '\0';
1226 return t;
1229 static Token *delete_Token(Token * t)
1231 Token *next = t->next;
1232 nasm_free(t->text);
1233 t->next = freeTokens;
1234 freeTokens = t;
1235 return next;
1239 * Convert a line of tokens back into text.
1240 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1241 * will be transformed into ..@ctxnum.xxx
1243 static char *detoken(Token * tlist, bool expand_locals)
1245 Token *t;
1246 char *line, *p;
1247 const char *q;
1248 int len = 0;
1250 list_for_each(t, tlist) {
1251 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1252 char *v;
1253 char *q = t->text;
1255 v = t->text + 2;
1256 if (*v == '\'' || *v == '\"' || *v == '`') {
1257 size_t len = nasm_unquote(v, NULL);
1258 size_t clen = strlen(v);
1260 if (len != clen) {
1261 nasm_error(ERR_NONFATAL | ERR_PASS1,
1262 "NUL character in %%! string");
1263 v = NULL;
1267 if (v) {
1268 char *p = getenv(v);
1269 if (!p) {
1270 nasm_error(ERR_NONFATAL | ERR_PASS1,
1271 "nonexistent environment variable `%s'", v);
1272 p = "";
1274 t->text = nasm_strdup(p);
1276 nasm_free(q);
1279 /* Expand local macros here and not during preprocessing */
1280 if (expand_locals &&
1281 t->type == TOK_PREPROC_ID && t->text &&
1282 t->text[0] == '%' && t->text[1] == '$') {
1283 const char *q;
1284 char *p;
1285 Context *ctx = get_ctx(t->text, &q);
1286 if (ctx) {
1287 char buffer[40];
1288 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1289 p = nasm_strcat(buffer, q);
1290 nasm_free(t->text);
1291 t->text = p;
1294 if (t->type == TOK_WHITESPACE)
1295 len++;
1296 else if (t->text)
1297 len += strlen(t->text);
1300 p = line = nasm_malloc(len + 1);
1302 list_for_each(t, tlist) {
1303 if (t->type == TOK_WHITESPACE) {
1304 *p++ = ' ';
1305 } else if (t->text) {
1306 q = t->text;
1307 while (*q)
1308 *p++ = *q++;
1311 *p = '\0';
1313 return line;
1317 * A scanner, suitable for use by the expression evaluator, which
1318 * operates on a line of Tokens. Expects a pointer to a pointer to
1319 * the first token in the line to be passed in as its private_data
1320 * field.
1322 * FIX: This really needs to be unified with stdscan.
1324 static int ppscan(void *private_data, struct tokenval *tokval)
1326 Token **tlineptr = private_data;
1327 Token *tline;
1328 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1330 do {
1331 tline = *tlineptr;
1332 *tlineptr = tline ? tline->next : NULL;
1333 } while (tline && (tline->type == TOK_WHITESPACE ||
1334 tline->type == TOK_COMMENT));
1336 if (!tline)
1337 return tokval->t_type = TOKEN_EOS;
1339 tokval->t_charptr = tline->text;
1341 if (tline->text[0] == '$' && !tline->text[1])
1342 return tokval->t_type = TOKEN_HERE;
1343 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1344 return tokval->t_type = TOKEN_BASE;
1346 if (tline->type == TOK_ID) {
1347 p = tokval->t_charptr = tline->text;
1348 if (p[0] == '$') {
1349 tokval->t_charptr++;
1350 return tokval->t_type = TOKEN_ID;
1353 for (r = p, s = ourcopy; *r; r++) {
1354 if (r >= p+MAX_KEYWORD)
1355 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1356 *s++ = nasm_tolower(*r);
1358 *s = '\0';
1359 /* right, so we have an identifier sitting in temp storage. now,
1360 * is it actually a register or instruction name, or what? */
1361 return nasm_token_hash(ourcopy, tokval);
1364 if (tline->type == TOK_NUMBER) {
1365 bool rn_error;
1366 tokval->t_integer = readnum(tline->text, &rn_error);
1367 tokval->t_charptr = tline->text;
1368 if (rn_error)
1369 return tokval->t_type = TOKEN_ERRNUM;
1370 else
1371 return tokval->t_type = TOKEN_NUM;
1374 if (tline->type == TOK_FLOAT) {
1375 return tokval->t_type = TOKEN_FLOAT;
1378 if (tline->type == TOK_STRING) {
1379 char bq, *ep;
1381 bq = tline->text[0];
1382 tokval->t_charptr = tline->text;
1383 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1385 if (ep[0] != bq || ep[1] != '\0')
1386 return tokval->t_type = TOKEN_ERRSTR;
1387 else
1388 return tokval->t_type = TOKEN_STR;
1391 if (tline->type == TOK_OTHER) {
1392 if (!strcmp(tline->text, "<<"))
1393 return tokval->t_type = TOKEN_SHL;
1394 if (!strcmp(tline->text, ">>"))
1395 return tokval->t_type = TOKEN_SHR;
1396 if (!strcmp(tline->text, "//"))
1397 return tokval->t_type = TOKEN_SDIV;
1398 if (!strcmp(tline->text, "%%"))
1399 return tokval->t_type = TOKEN_SMOD;
1400 if (!strcmp(tline->text, "=="))
1401 return tokval->t_type = TOKEN_EQ;
1402 if (!strcmp(tline->text, "<>"))
1403 return tokval->t_type = TOKEN_NE;
1404 if (!strcmp(tline->text, "!="))
1405 return tokval->t_type = TOKEN_NE;
1406 if (!strcmp(tline->text, "<="))
1407 return tokval->t_type = TOKEN_LE;
1408 if (!strcmp(tline->text, ">="))
1409 return tokval->t_type = TOKEN_GE;
1410 if (!strcmp(tline->text, "&&"))
1411 return tokval->t_type = TOKEN_DBL_AND;
1412 if (!strcmp(tline->text, "^^"))
1413 return tokval->t_type = TOKEN_DBL_XOR;
1414 if (!strcmp(tline->text, "||"))
1415 return tokval->t_type = TOKEN_DBL_OR;
1419 * We have no other options: just return the first character of
1420 * the token text.
1422 return tokval->t_type = tline->text[0];
1426 * Compare a string to the name of an existing macro; this is a
1427 * simple wrapper which calls either strcmp or nasm_stricmp
1428 * depending on the value of the `casesense' parameter.
1430 static int mstrcmp(const char *p, const char *q, bool casesense)
1432 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1436 * Compare a string to the name of an existing macro; this is a
1437 * simple wrapper which calls either strcmp or nasm_stricmp
1438 * depending on the value of the `casesense' parameter.
1440 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1442 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1446 * Return the Context structure associated with a %$ token. Return
1447 * NULL, having _already_ reported an error condition, if the
1448 * context stack isn't deep enough for the supplied number of $
1449 * signs.
1451 * If "namep" is non-NULL, set it to the pointer to the macro name
1452 * tail, i.e. the part beyond %$...
1454 static Context *get_ctx(const char *name, const char **namep)
1456 Context *ctx;
1457 int i;
1459 if (namep)
1460 *namep = name;
1462 if (!name || name[0] != '%' || name[1] != '$')
1463 return NULL;
1465 if (!cstk) {
1466 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1467 return NULL;
1470 name += 2;
1471 ctx = cstk;
1472 i = 0;
1473 while (ctx && *name == '$') {
1474 name++;
1475 i++;
1476 ctx = ctx->next;
1478 if (!ctx) {
1479 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1480 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1481 return NULL;
1484 if (namep)
1485 *namep = name;
1487 return ctx;
1491 * Check to see if a file is already in a string list
1493 static bool in_list(const StrList *list, const char *str)
1495 while (list) {
1496 if (!strcmp(list->str, str))
1497 return true;
1498 list = list->next;
1500 return false;
1504 * Open an include file. This routine must always return a valid
1505 * file pointer if it returns - it's responsible for throwing an
1506 * ERR_FATAL and bombing out completely if not. It should also try
1507 * the include path one by one until it finds the file or reaches
1508 * the end of the path.
1510 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1511 bool missing_ok, const char *mode)
1513 FILE *fp;
1514 char *prefix = "";
1515 IncPath *ip = ipath;
1516 int len = strlen(file);
1517 size_t prefix_len = 0;
1518 StrList *sl;
1520 while (1) {
1521 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1522 memcpy(sl->str, prefix, prefix_len);
1523 memcpy(sl->str+prefix_len, file, len+1);
1524 fp = fopen(sl->str, mode);
1525 if (fp && dhead && !in_list(*dhead, sl->str)) {
1526 sl->next = NULL;
1527 **dtail = sl;
1528 *dtail = &sl->next;
1529 } else {
1530 nasm_free(sl);
1532 if (fp)
1533 return fp;
1534 if (!ip) {
1535 if (!missing_ok)
1536 break;
1537 prefix = NULL;
1538 } else {
1539 prefix = ip->path;
1540 ip = ip->next;
1542 if (prefix) {
1543 prefix_len = strlen(prefix);
1544 } else {
1545 /* -MG given and file not found */
1546 if (dhead && !in_list(*dhead, file)) {
1547 sl = nasm_malloc(len+1+sizeof sl->next);
1548 sl->next = NULL;
1549 strcpy(sl->str, file);
1550 **dtail = sl;
1551 *dtail = &sl->next;
1553 return NULL;
1557 nasm_error(ERR_FATAL, "unable to open include file `%s'", file);
1558 return NULL;
1562 * Opens an include or input file. Public version, for use by modules
1563 * that get a file:lineno pair and need to look at the file again
1564 * (e.g. the CodeView debug backend). Returns NULL on failure.
1566 FILE *pp_input_fopen(const char *filename, const char *mode)
1568 FILE *fp;
1569 StrList *xsl = NULL;
1570 StrList **xst = &xsl;
1572 fp = inc_fopen(filename, &xsl, &xst, true, mode);
1573 if (xsl)
1574 nasm_free(xsl);
1575 return fp;
1579 * Determine if we should warn on defining a single-line macro of
1580 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1581 * return true if _any_ single-line macro of that name is defined.
1582 * Otherwise, will return true if a single-line macro with either
1583 * `nparam' or no parameters is defined.
1585 * If a macro with precisely the right number of parameters is
1586 * defined, or nparam is -1, the address of the definition structure
1587 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1588 * is NULL, no action will be taken regarding its contents, and no
1589 * error will occur.
1591 * Note that this is also called with nparam zero to resolve
1592 * `ifdef'.
1594 * If you already know which context macro belongs to, you can pass
1595 * the context pointer as first parameter; if you won't but name begins
1596 * with %$ the context will be automatically computed. If all_contexts
1597 * is true, macro will be searched in outer contexts as well.
1599 static bool
1600 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1601 bool nocase)
1603 struct hash_table *smtbl;
1604 SMacro *m;
1606 if (ctx) {
1607 smtbl = &ctx->localmac;
1608 } else if (name[0] == '%' && name[1] == '$') {
1609 if (cstk)
1610 ctx = get_ctx(name, &name);
1611 if (!ctx)
1612 return false; /* got to return _something_ */
1613 smtbl = &ctx->localmac;
1614 } else {
1615 smtbl = &smacros;
1617 m = (SMacro *) hash_findix(smtbl, name);
1619 while (m) {
1620 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1621 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1622 if (defn) {
1623 if (nparam == (int) m->nparam || nparam == -1)
1624 *defn = m;
1625 else
1626 *defn = NULL;
1628 return true;
1630 m = m->next;
1633 return false;
1637 * Count and mark off the parameters in a multi-line macro call.
1638 * This is called both from within the multi-line macro expansion
1639 * code, and also to mark off the default parameters when provided
1640 * in a %macro definition line.
1642 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1644 int paramsize, brace;
1646 *nparam = paramsize = 0;
1647 *params = NULL;
1648 while (t) {
1649 /* +1: we need space for the final NULL */
1650 if (*nparam+1 >= paramsize) {
1651 paramsize += PARAM_DELTA;
1652 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1654 skip_white_(t);
1655 brace = 0;
1656 if (tok_is_(t, "{"))
1657 brace++;
1658 (*params)[(*nparam)++] = t;
1659 if (brace) {
1660 while (brace && (t = t->next) != NULL) {
1661 if (tok_is_(t, "{"))
1662 brace++;
1663 else if (tok_is_(t, "}"))
1664 brace--;
1667 if (t) {
1669 * Now we've found the closing brace, look further
1670 * for the comma.
1672 t = t->next;
1673 skip_white_(t);
1674 if (tok_isnt_(t, ",")) {
1675 nasm_error(ERR_NONFATAL,
1676 "braces do not enclose all of macro parameter");
1677 while (tok_isnt_(t, ","))
1678 t = t->next;
1681 } else {
1682 while (tok_isnt_(t, ","))
1683 t = t->next;
1685 if (t) { /* got a comma/brace */
1686 t = t->next; /* eat the comma */
1692 * Determine whether one of the various `if' conditions is true or
1693 * not.
1695 * We must free the tline we get passed.
1697 static bool if_condition(Token * tline, enum preproc_token ct)
1699 enum pp_conditional i = PP_COND(ct);
1700 bool j;
1701 Token *t, *tt, **tptr, *origline;
1702 struct tokenval tokval;
1703 expr *evalresult;
1704 enum pp_token_type needtype;
1705 char *p;
1707 origline = tline;
1709 switch (i) {
1710 case PPC_IFCTX:
1711 j = false; /* have we matched yet? */
1712 while (true) {
1713 skip_white_(tline);
1714 if (!tline)
1715 break;
1716 if (tline->type != TOK_ID) {
1717 nasm_error(ERR_NONFATAL,
1718 "`%s' expects context identifiers", pp_directives[ct]);
1719 free_tlist(origline);
1720 return -1;
1722 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1723 j = true;
1724 tline = tline->next;
1726 break;
1728 case PPC_IFDEF:
1729 j = false; /* have we matched yet? */
1730 while (tline) {
1731 skip_white_(tline);
1732 if (!tline || (tline->type != TOK_ID &&
1733 (tline->type != TOK_PREPROC_ID ||
1734 tline->text[1] != '$'))) {
1735 nasm_error(ERR_NONFATAL,
1736 "`%s' expects macro identifiers", pp_directives[ct]);
1737 goto fail;
1739 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1740 j = true;
1741 tline = tline->next;
1743 break;
1745 case PPC_IFENV:
1746 tline = expand_smacro(tline);
1747 j = false; /* have we matched yet? */
1748 while (tline) {
1749 skip_white_(tline);
1750 if (!tline || (tline->type != TOK_ID &&
1751 tline->type != TOK_STRING &&
1752 (tline->type != TOK_PREPROC_ID ||
1753 tline->text[1] != '!'))) {
1754 nasm_error(ERR_NONFATAL,
1755 "`%s' expects environment variable names",
1756 pp_directives[ct]);
1757 goto fail;
1759 p = tline->text;
1760 if (tline->type == TOK_PREPROC_ID)
1761 p += 2; /* Skip leading %! */
1762 if (*p == '\'' || *p == '\"' || *p == '`')
1763 nasm_unquote_cstr(p, ct);
1764 if (getenv(p))
1765 j = true;
1766 tline = tline->next;
1768 break;
1770 case PPC_IFIDN:
1771 case PPC_IFIDNI:
1772 tline = expand_smacro(tline);
1773 t = tt = tline;
1774 while (tok_isnt_(tt, ","))
1775 tt = tt->next;
1776 if (!tt) {
1777 nasm_error(ERR_NONFATAL,
1778 "`%s' expects two comma-separated arguments",
1779 pp_directives[ct]);
1780 goto fail;
1782 tt = tt->next;
1783 j = true; /* assume equality unless proved not */
1784 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1785 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1786 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1787 pp_directives[ct]);
1788 goto fail;
1790 if (t->type == TOK_WHITESPACE) {
1791 t = t->next;
1792 continue;
1794 if (tt->type == TOK_WHITESPACE) {
1795 tt = tt->next;
1796 continue;
1798 if (tt->type != t->type) {
1799 j = false; /* found mismatching tokens */
1800 break;
1802 /* When comparing strings, need to unquote them first */
1803 if (t->type == TOK_STRING) {
1804 size_t l1 = nasm_unquote(t->text, NULL);
1805 size_t l2 = nasm_unquote(tt->text, NULL);
1807 if (l1 != l2) {
1808 j = false;
1809 break;
1811 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1812 j = false;
1813 break;
1815 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1816 j = false; /* found mismatching tokens */
1817 break;
1820 t = t->next;
1821 tt = tt->next;
1823 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1824 j = false; /* trailing gunk on one end or other */
1825 break;
1827 case PPC_IFMACRO:
1829 bool found = false;
1830 MMacro searching, *mmac;
1832 skip_white_(tline);
1833 tline = expand_id(tline);
1834 if (!tok_type_(tline, TOK_ID)) {
1835 nasm_error(ERR_NONFATAL,
1836 "`%s' expects a macro name", pp_directives[ct]);
1837 goto fail;
1839 searching.name = nasm_strdup(tline->text);
1840 searching.casesense = true;
1841 searching.plus = false;
1842 searching.nolist = false;
1843 searching.in_progress = 0;
1844 searching.max_depth = 0;
1845 searching.rep_nest = NULL;
1846 searching.nparam_min = 0;
1847 searching.nparam_max = INT_MAX;
1848 tline = expand_smacro(tline->next);
1849 skip_white_(tline);
1850 if (!tline) {
1851 } else if (!tok_type_(tline, TOK_NUMBER)) {
1852 nasm_error(ERR_NONFATAL,
1853 "`%s' expects a parameter count or nothing",
1854 pp_directives[ct]);
1855 } else {
1856 searching.nparam_min = searching.nparam_max =
1857 readnum(tline->text, &j);
1858 if (j)
1859 nasm_error(ERR_NONFATAL,
1860 "unable to parse parameter count `%s'",
1861 tline->text);
1863 if (tline && tok_is_(tline->next, "-")) {
1864 tline = tline->next->next;
1865 if (tok_is_(tline, "*"))
1866 searching.nparam_max = INT_MAX;
1867 else if (!tok_type_(tline, TOK_NUMBER))
1868 nasm_error(ERR_NONFATAL,
1869 "`%s' expects a parameter count after `-'",
1870 pp_directives[ct]);
1871 else {
1872 searching.nparam_max = readnum(tline->text, &j);
1873 if (j)
1874 nasm_error(ERR_NONFATAL,
1875 "unable to parse parameter count `%s'",
1876 tline->text);
1877 if (searching.nparam_min > searching.nparam_max)
1878 nasm_error(ERR_NONFATAL,
1879 "minimum parameter count exceeds maximum");
1882 if (tline && tok_is_(tline->next, "+")) {
1883 tline = tline->next;
1884 searching.plus = true;
1886 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1887 while (mmac) {
1888 if (!strcmp(mmac->name, searching.name) &&
1889 (mmac->nparam_min <= searching.nparam_max
1890 || searching.plus)
1891 && (searching.nparam_min <= mmac->nparam_max
1892 || mmac->plus)) {
1893 found = true;
1894 break;
1896 mmac = mmac->next;
1898 if (tline && tline->next)
1899 nasm_error(ERR_WARNING|ERR_PASS1,
1900 "trailing garbage after %%ifmacro ignored");
1901 nasm_free(searching.name);
1902 j = found;
1903 break;
1906 case PPC_IFID:
1907 needtype = TOK_ID;
1908 goto iftype;
1909 case PPC_IFNUM:
1910 needtype = TOK_NUMBER;
1911 goto iftype;
1912 case PPC_IFSTR:
1913 needtype = TOK_STRING;
1914 goto iftype;
1916 iftype:
1917 t = tline = expand_smacro(tline);
1919 while (tok_type_(t, TOK_WHITESPACE) ||
1920 (needtype == TOK_NUMBER &&
1921 tok_type_(t, TOK_OTHER) &&
1922 (t->text[0] == '-' || t->text[0] == '+') &&
1923 !t->text[1]))
1924 t = t->next;
1926 j = tok_type_(t, needtype);
1927 break;
1929 case PPC_IFTOKEN:
1930 t = tline = expand_smacro(tline);
1931 while (tok_type_(t, TOK_WHITESPACE))
1932 t = t->next;
1934 j = false;
1935 if (t) {
1936 t = t->next; /* Skip the actual token */
1937 while (tok_type_(t, TOK_WHITESPACE))
1938 t = t->next;
1939 j = !t; /* Should be nothing left */
1941 break;
1943 case PPC_IFEMPTY:
1944 t = tline = expand_smacro(tline);
1945 while (tok_type_(t, TOK_WHITESPACE))
1946 t = t->next;
1948 j = !t; /* Should be empty */
1949 break;
1951 case PPC_IF:
1952 t = tline = expand_smacro(tline);
1953 tptr = &t;
1954 tokval.t_type = TOKEN_INVALID;
1955 evalresult = evaluate(ppscan, tptr, &tokval,
1956 NULL, pass | CRITICAL, NULL);
1957 if (!evalresult)
1958 return -1;
1959 if (tokval.t_type)
1960 nasm_error(ERR_WARNING|ERR_PASS1,
1961 "trailing garbage after expression ignored");
1962 if (!is_simple(evalresult)) {
1963 nasm_error(ERR_NONFATAL,
1964 "non-constant value given to `%s'", pp_directives[ct]);
1965 goto fail;
1967 j = reloc_value(evalresult) != 0;
1968 break;
1970 default:
1971 nasm_error(ERR_FATAL,
1972 "preprocessor directive `%s' not yet implemented",
1973 pp_directives[ct]);
1974 goto fail;
1977 free_tlist(origline);
1978 return j ^ PP_NEGATIVE(ct);
1980 fail:
1981 free_tlist(origline);
1982 return -1;
1986 * Common code for defining an smacro
1988 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1989 int nparam, Token *expansion)
1991 SMacro *smac, **smhead;
1992 struct hash_table *smtbl;
1994 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1995 if (!smac) {
1996 nasm_error(ERR_WARNING|ERR_PASS1,
1997 "single-line macro `%s' defined both with and"
1998 " without parameters", mname);
2000 * Some instances of the old code considered this a failure,
2001 * some others didn't. What is the right thing to do here?
2003 free_tlist(expansion);
2004 return false; /* Failure */
2005 } else {
2007 * We're redefining, so we have to take over an
2008 * existing SMacro structure. This means freeing
2009 * what was already in it.
2011 nasm_free(smac->name);
2012 free_tlist(smac->expansion);
2014 } else {
2015 smtbl = ctx ? &ctx->localmac : &smacros;
2016 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2017 smac = nasm_malloc(sizeof(SMacro));
2018 smac->next = *smhead;
2019 *smhead = smac;
2021 smac->name = nasm_strdup(mname);
2022 smac->casesense = casesense;
2023 smac->nparam = nparam;
2024 smac->expansion = expansion;
2025 smac->in_progress = false;
2026 return true; /* Success */
2030 * Undefine an smacro
2032 static void undef_smacro(Context *ctx, const char *mname)
2034 SMacro **smhead, *s, **sp;
2035 struct hash_table *smtbl;
2037 smtbl = ctx ? &ctx->localmac : &smacros;
2038 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2040 if (smhead) {
2042 * We now have a macro name... go hunt for it.
2044 sp = smhead;
2045 while ((s = *sp) != NULL) {
2046 if (!mstrcmp(s->name, mname, s->casesense)) {
2047 *sp = s->next;
2048 nasm_free(s->name);
2049 free_tlist(s->expansion);
2050 nasm_free(s);
2051 } else {
2052 sp = &s->next;
2059 * Parse a mmacro specification.
2061 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2063 bool err;
2065 tline = tline->next;
2066 skip_white_(tline);
2067 tline = expand_id(tline);
2068 if (!tok_type_(tline, TOK_ID)) {
2069 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2070 return false;
2073 def->prev = NULL;
2074 def->name = nasm_strdup(tline->text);
2075 def->plus = false;
2076 def->nolist = false;
2077 def->in_progress = 0;
2078 def->rep_nest = NULL;
2079 def->nparam_min = 0;
2080 def->nparam_max = 0;
2082 tline = expand_smacro(tline->next);
2083 skip_white_(tline);
2084 if (!tok_type_(tline, TOK_NUMBER)) {
2085 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2086 } else {
2087 def->nparam_min = def->nparam_max =
2088 readnum(tline->text, &err);
2089 if (err)
2090 nasm_error(ERR_NONFATAL,
2091 "unable to parse parameter count `%s'", tline->text);
2093 if (tline && tok_is_(tline->next, "-")) {
2094 tline = tline->next->next;
2095 if (tok_is_(tline, "*")) {
2096 def->nparam_max = INT_MAX;
2097 } else if (!tok_type_(tline, TOK_NUMBER)) {
2098 nasm_error(ERR_NONFATAL,
2099 "`%s' expects a parameter count after `-'", directive);
2100 } else {
2101 def->nparam_max = readnum(tline->text, &err);
2102 if (err) {
2103 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2104 tline->text);
2106 if (def->nparam_min > def->nparam_max) {
2107 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2111 if (tline && tok_is_(tline->next, "+")) {
2112 tline = tline->next;
2113 def->plus = true;
2115 if (tline && tok_type_(tline->next, TOK_ID) &&
2116 !nasm_stricmp(tline->next->text, ".nolist")) {
2117 tline = tline->next;
2118 def->nolist = true;
2122 * Handle default parameters.
2124 if (tline && tline->next) {
2125 def->dlist = tline->next;
2126 tline->next = NULL;
2127 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2128 } else {
2129 def->dlist = NULL;
2130 def->defaults = NULL;
2132 def->expansion = NULL;
2134 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2135 !def->plus)
2136 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2137 "too many default macro parameters");
2139 return true;
2144 * Decode a size directive
2146 static int parse_size(const char *str) {
2147 static const char *size_names[] =
2148 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2149 static const int sizes[] =
2150 { 0, 1, 4, 16, 8, 10, 2, 32 };
2152 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2156 * find and process preprocessor directive in passed line
2157 * Find out if a line contains a preprocessor directive, and deal
2158 * with it if so.
2160 * If a directive _is_ found, it is the responsibility of this routine
2161 * (and not the caller) to free_tlist() the line.
2163 * @param tline a pointer to the current tokeninzed line linked list
2164 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2167 static int do_directive(Token * tline)
2169 enum preproc_token i;
2170 int j;
2171 bool err;
2172 int nparam;
2173 bool nolist;
2174 bool casesense;
2175 int k, m;
2176 int offset;
2177 char *p, *pp;
2178 const char *mname;
2179 Include *inc;
2180 Context *ctx;
2181 Cond *cond;
2182 MMacro *mmac, **mmhead;
2183 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2184 Line *l;
2185 struct tokenval tokval;
2186 expr *evalresult;
2187 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2188 int64_t count;
2189 size_t len;
2190 int severity;
2192 origline = tline;
2194 skip_white_(tline);
2195 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2196 (tline->text[1] == '%' || tline->text[1] == '$'
2197 || tline->text[1] == '!'))
2198 return NO_DIRECTIVE_FOUND;
2200 i = pp_token_hash(tline->text);
2203 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2204 * since they are known to be buggy at moment, we need to fix them
2205 * in future release (2.09-2.10)
2207 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2208 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2209 tline->text);
2210 return NO_DIRECTIVE_FOUND;
2214 * If we're in a non-emitting branch of a condition construct,
2215 * or walking to the end of an already terminated %rep block,
2216 * we should ignore all directives except for condition
2217 * directives.
2219 if (((istk->conds && !emitting(istk->conds->state)) ||
2220 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2221 return NO_DIRECTIVE_FOUND;
2225 * If we're defining a macro or reading a %rep block, we should
2226 * ignore all directives except for %macro/%imacro (which nest),
2227 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2228 * If we're in a %rep block, another %rep nests, so should be let through.
2230 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2231 i != PP_RMACRO && i != PP_IRMACRO &&
2232 i != PP_ENDMACRO && i != PP_ENDM &&
2233 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2234 return NO_DIRECTIVE_FOUND;
2237 if (defining) {
2238 if (i == PP_MACRO || i == PP_IMACRO ||
2239 i == PP_RMACRO || i == PP_IRMACRO) {
2240 nested_mac_count++;
2241 return NO_DIRECTIVE_FOUND;
2242 } else if (nested_mac_count > 0) {
2243 if (i == PP_ENDMACRO) {
2244 nested_mac_count--;
2245 return NO_DIRECTIVE_FOUND;
2248 if (!defining->name) {
2249 if (i == PP_REP) {
2250 nested_rep_count++;
2251 return NO_DIRECTIVE_FOUND;
2252 } else if (nested_rep_count > 0) {
2253 if (i == PP_ENDREP) {
2254 nested_rep_count--;
2255 return NO_DIRECTIVE_FOUND;
2261 switch (i) {
2262 case PP_INVALID:
2263 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2264 tline->text);
2265 return NO_DIRECTIVE_FOUND; /* didn't get it */
2267 case PP_STACKSIZE:
2268 /* Directive to tell NASM what the default stack size is. The
2269 * default is for a 16-bit stack, and this can be overriden with
2270 * %stacksize large.
2272 tline = tline->next;
2273 if (tline && tline->type == TOK_WHITESPACE)
2274 tline = tline->next;
2275 if (!tline || tline->type != TOK_ID) {
2276 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2277 free_tlist(origline);
2278 return DIRECTIVE_FOUND;
2280 if (nasm_stricmp(tline->text, "flat") == 0) {
2281 /* All subsequent ARG directives are for a 32-bit stack */
2282 StackSize = 4;
2283 StackPointer = "ebp";
2284 ArgOffset = 8;
2285 LocalOffset = 0;
2286 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2287 /* All subsequent ARG directives are for a 64-bit stack */
2288 StackSize = 8;
2289 StackPointer = "rbp";
2290 ArgOffset = 16;
2291 LocalOffset = 0;
2292 } else if (nasm_stricmp(tline->text, "large") == 0) {
2293 /* All subsequent ARG directives are for a 16-bit stack,
2294 * far function call.
2296 StackSize = 2;
2297 StackPointer = "bp";
2298 ArgOffset = 4;
2299 LocalOffset = 0;
2300 } else if (nasm_stricmp(tline->text, "small") == 0) {
2301 /* All subsequent ARG directives are for a 16-bit stack,
2302 * far function call. We don't support near functions.
2304 StackSize = 2;
2305 StackPointer = "bp";
2306 ArgOffset = 6;
2307 LocalOffset = 0;
2308 } else {
2309 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2310 free_tlist(origline);
2311 return DIRECTIVE_FOUND;
2313 free_tlist(origline);
2314 return DIRECTIVE_FOUND;
2316 case PP_ARG:
2317 /* TASM like ARG directive to define arguments to functions, in
2318 * the following form:
2320 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2322 offset = ArgOffset;
2323 do {
2324 char *arg, directive[256];
2325 int size = StackSize;
2327 /* Find the argument name */
2328 tline = tline->next;
2329 if (tline && tline->type == TOK_WHITESPACE)
2330 tline = tline->next;
2331 if (!tline || tline->type != TOK_ID) {
2332 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2333 free_tlist(origline);
2334 return DIRECTIVE_FOUND;
2336 arg = tline->text;
2338 /* Find the argument size type */
2339 tline = tline->next;
2340 if (!tline || tline->type != TOK_OTHER
2341 || tline->text[0] != ':') {
2342 nasm_error(ERR_NONFATAL,
2343 "Syntax error processing `%%arg' directive");
2344 free_tlist(origline);
2345 return DIRECTIVE_FOUND;
2347 tline = tline->next;
2348 if (!tline || tline->type != TOK_ID) {
2349 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2350 free_tlist(origline);
2351 return DIRECTIVE_FOUND;
2354 /* Allow macro expansion of type parameter */
2355 tt = tokenize(tline->text);
2356 tt = expand_smacro(tt);
2357 size = parse_size(tt->text);
2358 if (!size) {
2359 nasm_error(ERR_NONFATAL,
2360 "Invalid size type for `%%arg' missing directive");
2361 free_tlist(tt);
2362 free_tlist(origline);
2363 return DIRECTIVE_FOUND;
2365 free_tlist(tt);
2367 /* Round up to even stack slots */
2368 size = ALIGN(size, StackSize);
2370 /* Now define the macro for the argument */
2371 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2372 arg, StackPointer, offset);
2373 do_directive(tokenize(directive));
2374 offset += size;
2376 /* Move to the next argument in the list */
2377 tline = tline->next;
2378 if (tline && tline->type == TOK_WHITESPACE)
2379 tline = tline->next;
2380 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2381 ArgOffset = offset;
2382 free_tlist(origline);
2383 return DIRECTIVE_FOUND;
2385 case PP_LOCAL:
2386 /* TASM like LOCAL directive to define local variables for a
2387 * function, in the following form:
2389 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2391 * The '= LocalSize' at the end is ignored by NASM, but is
2392 * required by TASM to define the local parameter size (and used
2393 * by the TASM macro package).
2395 offset = LocalOffset;
2396 do {
2397 char *local, directive[256];
2398 int size = StackSize;
2400 /* Find the argument name */
2401 tline = tline->next;
2402 if (tline && tline->type == TOK_WHITESPACE)
2403 tline = tline->next;
2404 if (!tline || tline->type != TOK_ID) {
2405 nasm_error(ERR_NONFATAL,
2406 "`%%local' missing argument parameter");
2407 free_tlist(origline);
2408 return DIRECTIVE_FOUND;
2410 local = tline->text;
2412 /* Find the argument size type */
2413 tline = tline->next;
2414 if (!tline || tline->type != TOK_OTHER
2415 || tline->text[0] != ':') {
2416 nasm_error(ERR_NONFATAL,
2417 "Syntax error processing `%%local' directive");
2418 free_tlist(origline);
2419 return DIRECTIVE_FOUND;
2421 tline = tline->next;
2422 if (!tline || tline->type != TOK_ID) {
2423 nasm_error(ERR_NONFATAL,
2424 "`%%local' missing size type parameter");
2425 free_tlist(origline);
2426 return DIRECTIVE_FOUND;
2429 /* Allow macro expansion of type parameter */
2430 tt = tokenize(tline->text);
2431 tt = expand_smacro(tt);
2432 size = parse_size(tt->text);
2433 if (!size) {
2434 nasm_error(ERR_NONFATAL,
2435 "Invalid size type for `%%local' missing directive");
2436 free_tlist(tt);
2437 free_tlist(origline);
2438 return DIRECTIVE_FOUND;
2440 free_tlist(tt);
2442 /* Round up to even stack slots */
2443 size = ALIGN(size, StackSize);
2445 offset += size; /* Negative offset, increment before */
2447 /* Now define the macro for the argument */
2448 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2449 local, StackPointer, offset);
2450 do_directive(tokenize(directive));
2452 /* Now define the assign to setup the enter_c macro correctly */
2453 snprintf(directive, sizeof(directive),
2454 "%%assign %%$localsize %%$localsize+%d", size);
2455 do_directive(tokenize(directive));
2457 /* Move to the next argument in the list */
2458 tline = tline->next;
2459 if (tline && tline->type == TOK_WHITESPACE)
2460 tline = tline->next;
2461 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2462 LocalOffset = offset;
2463 free_tlist(origline);
2464 return DIRECTIVE_FOUND;
2466 case PP_CLEAR:
2467 if (tline->next)
2468 nasm_error(ERR_WARNING|ERR_PASS1,
2469 "trailing garbage after `%%clear' ignored");
2470 free_macros();
2471 init_macros();
2472 free_tlist(origline);
2473 return DIRECTIVE_FOUND;
2475 case PP_DEPEND:
2476 t = tline->next = expand_smacro(tline->next);
2477 skip_white_(t);
2478 if (!t || (t->type != TOK_STRING &&
2479 t->type != TOK_INTERNAL_STRING)) {
2480 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2481 free_tlist(origline);
2482 return DIRECTIVE_FOUND; /* but we did _something_ */
2484 if (t->next)
2485 nasm_error(ERR_WARNING|ERR_PASS1,
2486 "trailing garbage after `%%depend' ignored");
2487 p = t->text;
2488 if (t->type != TOK_INTERNAL_STRING)
2489 nasm_unquote_cstr(p, i);
2490 if (dephead && !in_list(*dephead, p)) {
2491 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2492 sl->next = NULL;
2493 strcpy(sl->str, p);
2494 *deptail = sl;
2495 deptail = &sl->next;
2497 free_tlist(origline);
2498 return DIRECTIVE_FOUND;
2500 case PP_INCLUDE:
2501 t = tline->next = expand_smacro(tline->next);
2502 skip_white_(t);
2504 if (!t || (t->type != TOK_STRING &&
2505 t->type != TOK_INTERNAL_STRING)) {
2506 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2507 free_tlist(origline);
2508 return DIRECTIVE_FOUND; /* but we did _something_ */
2510 if (t->next)
2511 nasm_error(ERR_WARNING|ERR_PASS1,
2512 "trailing garbage after `%%include' ignored");
2513 p = t->text;
2514 if (t->type != TOK_INTERNAL_STRING)
2515 nasm_unquote_cstr(p, i);
2516 inc = nasm_malloc(sizeof(Include));
2517 inc->next = istk;
2518 inc->conds = NULL;
2519 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0, "r");
2520 if (!inc->fp) {
2521 /* -MG given but file not found */
2522 nasm_free(inc);
2523 } else {
2524 inc->fname = src_set_fname(p);
2525 inc->lineno = src_set_linnum(0);
2526 inc->lineinc = 1;
2527 inc->expansion = NULL;
2528 inc->mstk = NULL;
2529 istk = inc;
2530 lfmt->uplevel(LIST_INCLUDE);
2532 free_tlist(origline);
2533 return DIRECTIVE_FOUND;
2535 case PP_USE:
2537 static macros_t *use_pkg;
2538 const char *pkg_macro = NULL;
2540 tline = tline->next;
2541 skip_white_(tline);
2542 tline = expand_id(tline);
2544 if (!tline || (tline->type != TOK_STRING &&
2545 tline->type != TOK_INTERNAL_STRING &&
2546 tline->type != TOK_ID)) {
2547 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2548 free_tlist(origline);
2549 return DIRECTIVE_FOUND; /* but we did _something_ */
2551 if (tline->next)
2552 nasm_error(ERR_WARNING|ERR_PASS1,
2553 "trailing garbage after `%%use' ignored");
2554 if (tline->type == TOK_STRING)
2555 nasm_unquote_cstr(tline->text, i);
2556 use_pkg = nasm_stdmac_find_package(tline->text);
2557 if (!use_pkg)
2558 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2559 else
2560 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2561 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2562 /* Not already included, go ahead and include it */
2563 stdmacpos = use_pkg;
2565 free_tlist(origline);
2566 return DIRECTIVE_FOUND;
2568 case PP_PUSH:
2569 case PP_REPL:
2570 case PP_POP:
2571 tline = tline->next;
2572 skip_white_(tline);
2573 tline = expand_id(tline);
2574 if (tline) {
2575 if (!tok_type_(tline, TOK_ID)) {
2576 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2577 pp_directives[i]);
2578 free_tlist(origline);
2579 return DIRECTIVE_FOUND; /* but we did _something_ */
2581 if (tline->next)
2582 nasm_error(ERR_WARNING|ERR_PASS1,
2583 "trailing garbage after `%s' ignored",
2584 pp_directives[i]);
2585 p = nasm_strdup(tline->text);
2586 } else {
2587 p = NULL; /* Anonymous */
2590 if (i == PP_PUSH) {
2591 ctx = nasm_malloc(sizeof(Context));
2592 ctx->next = cstk;
2593 hash_init(&ctx->localmac, HASH_SMALL);
2594 ctx->name = p;
2595 ctx->number = unique++;
2596 cstk = ctx;
2597 } else {
2598 /* %pop or %repl */
2599 if (!cstk) {
2600 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2601 pp_directives[i]);
2602 } else if (i == PP_POP) {
2603 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2604 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2605 "expected %s",
2606 cstk->name ? cstk->name : "anonymous", p);
2607 else
2608 ctx_pop();
2609 } else {
2610 /* i == PP_REPL */
2611 nasm_free(cstk->name);
2612 cstk->name = p;
2613 p = NULL;
2615 nasm_free(p);
2617 free_tlist(origline);
2618 return DIRECTIVE_FOUND;
2619 case PP_FATAL:
2620 severity = ERR_FATAL;
2621 goto issue_error;
2622 case PP_ERROR:
2623 severity = ERR_NONFATAL;
2624 goto issue_error;
2625 case PP_WARNING:
2626 severity = ERR_WARNING|ERR_WARN_USER;
2627 goto issue_error;
2629 issue_error:
2631 /* Only error out if this is the final pass */
2632 if (pass != 2 && i != PP_FATAL)
2633 return DIRECTIVE_FOUND;
2635 tline->next = expand_smacro(tline->next);
2636 tline = tline->next;
2637 skip_white_(tline);
2638 t = tline ? tline->next : NULL;
2639 skip_white_(t);
2640 if (tok_type_(tline, TOK_STRING) && !t) {
2641 /* The line contains only a quoted string */
2642 p = tline->text;
2643 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2644 nasm_error(severity, "%s", p);
2645 } else {
2646 /* Not a quoted string, or more than a quoted string */
2647 p = detoken(tline, false);
2648 nasm_error(severity, "%s", p);
2649 nasm_free(p);
2651 free_tlist(origline);
2652 return DIRECTIVE_FOUND;
2655 CASE_PP_IF:
2656 if (istk->conds && !emitting(istk->conds->state))
2657 j = COND_NEVER;
2658 else {
2659 j = if_condition(tline->next, i);
2660 tline->next = NULL; /* it got freed */
2661 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2663 cond = nasm_malloc(sizeof(Cond));
2664 cond->next = istk->conds;
2665 cond->state = j;
2666 istk->conds = cond;
2667 if(istk->mstk)
2668 istk->mstk->condcnt ++;
2669 free_tlist(origline);
2670 return DIRECTIVE_FOUND;
2672 CASE_PP_ELIF:
2673 if (!istk->conds)
2674 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2675 switch(istk->conds->state) {
2676 case COND_IF_TRUE:
2677 istk->conds->state = COND_DONE;
2678 break;
2680 case COND_DONE:
2681 case COND_NEVER:
2682 break;
2684 case COND_ELSE_TRUE:
2685 case COND_ELSE_FALSE:
2686 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2687 "`%%elif' after `%%else' ignored");
2688 istk->conds->state = COND_NEVER;
2689 break;
2691 case COND_IF_FALSE:
2693 * IMPORTANT: In the case of %if, we will already have
2694 * called expand_mmac_params(); however, if we're
2695 * processing an %elif we must have been in a
2696 * non-emitting mode, which would have inhibited
2697 * the normal invocation of expand_mmac_params().
2698 * Therefore, we have to do it explicitly here.
2700 j = if_condition(expand_mmac_params(tline->next), i);
2701 tline->next = NULL; /* it got freed */
2702 istk->conds->state =
2703 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2704 break;
2706 free_tlist(origline);
2707 return DIRECTIVE_FOUND;
2709 case PP_ELSE:
2710 if (tline->next)
2711 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2712 "trailing garbage after `%%else' ignored");
2713 if (!istk->conds)
2714 nasm_fatal(0, "`%%else: no matching `%%if'");
2715 switch(istk->conds->state) {
2716 case COND_IF_TRUE:
2717 case COND_DONE:
2718 istk->conds->state = COND_ELSE_FALSE;
2719 break;
2721 case COND_NEVER:
2722 break;
2724 case COND_IF_FALSE:
2725 istk->conds->state = COND_ELSE_TRUE;
2726 break;
2728 case COND_ELSE_TRUE:
2729 case COND_ELSE_FALSE:
2730 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2731 "`%%else' after `%%else' ignored.");
2732 istk->conds->state = COND_NEVER;
2733 break;
2735 free_tlist(origline);
2736 return DIRECTIVE_FOUND;
2738 case PP_ENDIF:
2739 if (tline->next)
2740 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2741 "trailing garbage after `%%endif' ignored");
2742 if (!istk->conds)
2743 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2744 cond = istk->conds;
2745 istk->conds = cond->next;
2746 nasm_free(cond);
2747 if(istk->mstk)
2748 istk->mstk->condcnt --;
2749 free_tlist(origline);
2750 return DIRECTIVE_FOUND;
2752 case PP_RMACRO:
2753 case PP_IRMACRO:
2754 case PP_MACRO:
2755 case PP_IMACRO:
2756 if (defining) {
2757 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2758 pp_directives[i]);
2759 return DIRECTIVE_FOUND;
2761 defining = nasm_zalloc(sizeof(MMacro));
2762 defining->max_depth =
2763 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2764 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2765 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2766 nasm_free(defining);
2767 defining = NULL;
2768 return DIRECTIVE_FOUND;
2771 src_get(&defining->xline, &defining->fname);
2773 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2774 while (mmac) {
2775 if (!strcmp(mmac->name, defining->name) &&
2776 (mmac->nparam_min <= defining->nparam_max
2777 || defining->plus)
2778 && (defining->nparam_min <= mmac->nparam_max
2779 || mmac->plus)) {
2780 nasm_error(ERR_WARNING|ERR_PASS1,
2781 "redefining multi-line macro `%s'", defining->name);
2782 return DIRECTIVE_FOUND;
2784 mmac = mmac->next;
2786 free_tlist(origline);
2787 return DIRECTIVE_FOUND;
2789 case PP_ENDM:
2790 case PP_ENDMACRO:
2791 if (! (defining && defining->name)) {
2792 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2793 return DIRECTIVE_FOUND;
2795 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2796 defining->next = *mmhead;
2797 *mmhead = defining;
2798 defining = NULL;
2799 free_tlist(origline);
2800 return DIRECTIVE_FOUND;
2802 case PP_EXITMACRO:
2804 * We must search along istk->expansion until we hit a
2805 * macro-end marker for a macro with a name. Then we
2806 * bypass all lines between exitmacro and endmacro.
2808 list_for_each(l, istk->expansion)
2809 if (l->finishes && l->finishes->name)
2810 break;
2812 if (l) {
2814 * Remove all conditional entries relative to this
2815 * macro invocation. (safe to do in this context)
2817 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2818 cond = istk->conds;
2819 istk->conds = cond->next;
2820 nasm_free(cond);
2822 istk->expansion = l;
2823 } else {
2824 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2826 free_tlist(origline);
2827 return DIRECTIVE_FOUND;
2829 case PP_UNMACRO:
2830 case PP_UNIMACRO:
2832 MMacro **mmac_p;
2833 MMacro spec;
2835 spec.casesense = (i == PP_UNMACRO);
2836 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2837 return DIRECTIVE_FOUND;
2839 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2840 while (mmac_p && *mmac_p) {
2841 mmac = *mmac_p;
2842 if (mmac->casesense == spec.casesense &&
2843 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2844 mmac->nparam_min == spec.nparam_min &&
2845 mmac->nparam_max == spec.nparam_max &&
2846 mmac->plus == spec.plus) {
2847 *mmac_p = mmac->next;
2848 free_mmacro(mmac);
2849 } else {
2850 mmac_p = &mmac->next;
2853 free_tlist(origline);
2854 free_tlist(spec.dlist);
2855 return DIRECTIVE_FOUND;
2858 case PP_ROTATE:
2859 if (tline->next && tline->next->type == TOK_WHITESPACE)
2860 tline = tline->next;
2861 if (!tline->next) {
2862 free_tlist(origline);
2863 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2864 return DIRECTIVE_FOUND;
2866 t = expand_smacro(tline->next);
2867 tline->next = NULL;
2868 free_tlist(origline);
2869 tline = t;
2870 tptr = &t;
2871 tokval.t_type = TOKEN_INVALID;
2872 evalresult =
2873 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2874 free_tlist(tline);
2875 if (!evalresult)
2876 return DIRECTIVE_FOUND;
2877 if (tokval.t_type)
2878 nasm_error(ERR_WARNING|ERR_PASS1,
2879 "trailing garbage after expression ignored");
2880 if (!is_simple(evalresult)) {
2881 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2882 return DIRECTIVE_FOUND;
2884 mmac = istk->mstk;
2885 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2886 mmac = mmac->next_active;
2887 if (!mmac) {
2888 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2889 } else if (mmac->nparam == 0) {
2890 nasm_error(ERR_NONFATAL,
2891 "`%%rotate' invoked within macro without parameters");
2892 } else {
2893 int rotate = mmac->rotate + reloc_value(evalresult);
2895 rotate %= (int)mmac->nparam;
2896 if (rotate < 0)
2897 rotate += mmac->nparam;
2899 mmac->rotate = rotate;
2901 return DIRECTIVE_FOUND;
2903 case PP_REP:
2904 nolist = false;
2905 do {
2906 tline = tline->next;
2907 } while (tok_type_(tline, TOK_WHITESPACE));
2909 if (tok_type_(tline, TOK_ID) &&
2910 nasm_stricmp(tline->text, ".nolist") == 0) {
2911 nolist = true;
2912 do {
2913 tline = tline->next;
2914 } while (tok_type_(tline, TOK_WHITESPACE));
2917 if (tline) {
2918 t = expand_smacro(tline);
2919 tptr = &t;
2920 tokval.t_type = TOKEN_INVALID;
2921 evalresult =
2922 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2923 if (!evalresult) {
2924 free_tlist(origline);
2925 return DIRECTIVE_FOUND;
2927 if (tokval.t_type)
2928 nasm_error(ERR_WARNING|ERR_PASS1,
2929 "trailing garbage after expression ignored");
2930 if (!is_simple(evalresult)) {
2931 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2932 return DIRECTIVE_FOUND;
2934 count = reloc_value(evalresult);
2935 if (count >= REP_LIMIT) {
2936 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
2937 count = 0;
2938 } else
2939 count++;
2940 } else {
2941 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2942 count = 0;
2944 free_tlist(origline);
2946 tmp_defining = defining;
2947 defining = nasm_malloc(sizeof(MMacro));
2948 defining->prev = NULL;
2949 defining->name = NULL; /* flags this macro as a %rep block */
2950 defining->casesense = false;
2951 defining->plus = false;
2952 defining->nolist = nolist;
2953 defining->in_progress = count;
2954 defining->max_depth = 0;
2955 defining->nparam_min = defining->nparam_max = 0;
2956 defining->defaults = NULL;
2957 defining->dlist = NULL;
2958 defining->expansion = NULL;
2959 defining->next_active = istk->mstk;
2960 defining->rep_nest = tmp_defining;
2961 return DIRECTIVE_FOUND;
2963 case PP_ENDREP:
2964 if (!defining || defining->name) {
2965 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2966 return DIRECTIVE_FOUND;
2970 * Now we have a "macro" defined - although it has no name
2971 * and we won't be entering it in the hash tables - we must
2972 * push a macro-end marker for it on to istk->expansion.
2973 * After that, it will take care of propagating itself (a
2974 * macro-end marker line for a macro which is really a %rep
2975 * block will cause the macro to be re-expanded, complete
2976 * with another macro-end marker to ensure the process
2977 * continues) until the whole expansion is forcibly removed
2978 * from istk->expansion by a %exitrep.
2980 l = nasm_malloc(sizeof(Line));
2981 l->next = istk->expansion;
2982 l->finishes = defining;
2983 l->first = NULL;
2984 istk->expansion = l;
2986 istk->mstk = defining;
2988 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2989 tmp_defining = defining;
2990 defining = defining->rep_nest;
2991 free_tlist(origline);
2992 return DIRECTIVE_FOUND;
2994 case PP_EXITREP:
2996 * We must search along istk->expansion until we hit a
2997 * macro-end marker for a macro with no name. Then we set
2998 * its `in_progress' flag to 0.
3000 list_for_each(l, istk->expansion)
3001 if (l->finishes && !l->finishes->name)
3002 break;
3004 if (l)
3005 l->finishes->in_progress = 1;
3006 else
3007 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3008 free_tlist(origline);
3009 return DIRECTIVE_FOUND;
3011 case PP_XDEFINE:
3012 case PP_IXDEFINE:
3013 case PP_DEFINE:
3014 case PP_IDEFINE:
3015 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3017 tline = tline->next;
3018 skip_white_(tline);
3019 tline = expand_id(tline);
3020 if (!tline || (tline->type != TOK_ID &&
3021 (tline->type != TOK_PREPROC_ID ||
3022 tline->text[1] != '$'))) {
3023 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3024 pp_directives[i]);
3025 free_tlist(origline);
3026 return DIRECTIVE_FOUND;
3029 ctx = get_ctx(tline->text, &mname);
3030 last = tline;
3031 param_start = tline = tline->next;
3032 nparam = 0;
3034 /* Expand the macro definition now for %xdefine and %ixdefine */
3035 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3036 tline = expand_smacro(tline);
3038 if (tok_is_(tline, "(")) {
3040 * This macro has parameters.
3043 tline = tline->next;
3044 while (1) {
3045 skip_white_(tline);
3046 if (!tline) {
3047 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3048 free_tlist(origline);
3049 return DIRECTIVE_FOUND;
3051 if (tline->type != TOK_ID) {
3052 nasm_error(ERR_NONFATAL,
3053 "`%s': parameter identifier expected",
3054 tline->text);
3055 free_tlist(origline);
3056 return DIRECTIVE_FOUND;
3058 tline->type = TOK_SMAC_PARAM + nparam++;
3059 tline = tline->next;
3060 skip_white_(tline);
3061 if (tok_is_(tline, ",")) {
3062 tline = tline->next;
3063 } else {
3064 if (!tok_is_(tline, ")")) {
3065 nasm_error(ERR_NONFATAL,
3066 "`)' expected to terminate macro template");
3067 free_tlist(origline);
3068 return DIRECTIVE_FOUND;
3070 break;
3073 last = tline;
3074 tline = tline->next;
3076 if (tok_type_(tline, TOK_WHITESPACE))
3077 last = tline, tline = tline->next;
3078 macro_start = NULL;
3079 last->next = NULL;
3080 t = tline;
3081 while (t) {
3082 if (t->type == TOK_ID) {
3083 list_for_each(tt, param_start)
3084 if (tt->type >= TOK_SMAC_PARAM &&
3085 !strcmp(tt->text, t->text))
3086 t->type = tt->type;
3088 tt = t->next;
3089 t->next = macro_start;
3090 macro_start = t;
3091 t = tt;
3094 * Good. We now have a macro name, a parameter count, and a
3095 * token list (in reverse order) for an expansion. We ought
3096 * to be OK just to create an SMacro, store it, and let
3097 * free_tlist have the rest of the line (which we have
3098 * carefully re-terminated after chopping off the expansion
3099 * from the end).
3101 define_smacro(ctx, mname, casesense, nparam, macro_start);
3102 free_tlist(origline);
3103 return DIRECTIVE_FOUND;
3105 case PP_UNDEF:
3106 tline = tline->next;
3107 skip_white_(tline);
3108 tline = expand_id(tline);
3109 if (!tline || (tline->type != TOK_ID &&
3110 (tline->type != TOK_PREPROC_ID ||
3111 tline->text[1] != '$'))) {
3112 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3113 free_tlist(origline);
3114 return DIRECTIVE_FOUND;
3116 if (tline->next) {
3117 nasm_error(ERR_WARNING|ERR_PASS1,
3118 "trailing garbage after macro name ignored");
3121 /* Find the context that symbol belongs to */
3122 ctx = get_ctx(tline->text, &mname);
3123 undef_smacro(ctx, mname);
3124 free_tlist(origline);
3125 return DIRECTIVE_FOUND;
3127 case PP_DEFSTR:
3128 case PP_IDEFSTR:
3129 casesense = (i == PP_DEFSTR);
3131 tline = tline->next;
3132 skip_white_(tline);
3133 tline = expand_id(tline);
3134 if (!tline || (tline->type != TOK_ID &&
3135 (tline->type != TOK_PREPROC_ID ||
3136 tline->text[1] != '$'))) {
3137 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3138 pp_directives[i]);
3139 free_tlist(origline);
3140 return DIRECTIVE_FOUND;
3143 ctx = get_ctx(tline->text, &mname);
3144 last = tline;
3145 tline = expand_smacro(tline->next);
3146 last->next = NULL;
3148 while (tok_type_(tline, TOK_WHITESPACE))
3149 tline = delete_Token(tline);
3151 p = detoken(tline, false);
3152 macro_start = nasm_malloc(sizeof(*macro_start));
3153 macro_start->next = NULL;
3154 macro_start->text = nasm_quote(p, strlen(p));
3155 macro_start->type = TOK_STRING;
3156 macro_start->a.mac = NULL;
3157 nasm_free(p);
3160 * We now have a macro name, an implicit parameter count of
3161 * zero, and a string token to use as an expansion. Create
3162 * and store an SMacro.
3164 define_smacro(ctx, mname, casesense, 0, macro_start);
3165 free_tlist(origline);
3166 return DIRECTIVE_FOUND;
3168 case PP_DEFTOK:
3169 case PP_IDEFTOK:
3170 casesense = (i == PP_DEFTOK);
3172 tline = tline->next;
3173 skip_white_(tline);
3174 tline = expand_id(tline);
3175 if (!tline || (tline->type != TOK_ID &&
3176 (tline->type != TOK_PREPROC_ID ||
3177 tline->text[1] != '$'))) {
3178 nasm_error(ERR_NONFATAL,
3179 "`%s' expects a macro identifier as first parameter",
3180 pp_directives[i]);
3181 free_tlist(origline);
3182 return DIRECTIVE_FOUND;
3184 ctx = get_ctx(tline->text, &mname);
3185 last = tline;
3186 tline = expand_smacro(tline->next);
3187 last->next = NULL;
3189 t = tline;
3190 while (tok_type_(t, TOK_WHITESPACE))
3191 t = t->next;
3192 /* t should now point to the string */
3193 if (!tok_type_(t, TOK_STRING)) {
3194 nasm_error(ERR_NONFATAL,
3195 "`%s` requires string as second parameter",
3196 pp_directives[i]);
3197 free_tlist(tline);
3198 free_tlist(origline);
3199 return DIRECTIVE_FOUND;
3203 * Convert the string to a token stream. Note that smacros
3204 * are stored with the token stream reversed, so we have to
3205 * reverse the output of tokenize().
3207 nasm_unquote_cstr(t->text, i);
3208 macro_start = reverse_tokens(tokenize(t->text));
3211 * We now have a macro name, an implicit parameter count of
3212 * zero, and a numeric token to use as an expansion. Create
3213 * and store an SMacro.
3215 define_smacro(ctx, mname, casesense, 0, macro_start);
3216 free_tlist(tline);
3217 free_tlist(origline);
3218 return DIRECTIVE_FOUND;
3220 case PP_PATHSEARCH:
3222 FILE *fp;
3223 StrList *xsl = NULL;
3224 StrList **xst = &xsl;
3226 casesense = true;
3228 tline = tline->next;
3229 skip_white_(tline);
3230 tline = expand_id(tline);
3231 if (!tline || (tline->type != TOK_ID &&
3232 (tline->type != TOK_PREPROC_ID ||
3233 tline->text[1] != '$'))) {
3234 nasm_error(ERR_NONFATAL,
3235 "`%%pathsearch' expects a macro identifier as first parameter");
3236 free_tlist(origline);
3237 return DIRECTIVE_FOUND;
3239 ctx = get_ctx(tline->text, &mname);
3240 last = tline;
3241 tline = expand_smacro(tline->next);
3242 last->next = NULL;
3244 t = tline;
3245 while (tok_type_(t, TOK_WHITESPACE))
3246 t = t->next;
3248 if (!t || (t->type != TOK_STRING &&
3249 t->type != TOK_INTERNAL_STRING)) {
3250 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3251 free_tlist(tline);
3252 free_tlist(origline);
3253 return DIRECTIVE_FOUND; /* but we did _something_ */
3255 if (t->next)
3256 nasm_error(ERR_WARNING|ERR_PASS1,
3257 "trailing garbage after `%%pathsearch' ignored");
3258 p = t->text;
3259 if (t->type != TOK_INTERNAL_STRING)
3260 nasm_unquote(p, NULL);
3262 fp = inc_fopen(p, &xsl, &xst, true, "r");
3263 if (fp) {
3264 p = xsl->str;
3265 fclose(fp); /* Don't actually care about the file */
3267 macro_start = nasm_malloc(sizeof(*macro_start));
3268 macro_start->next = NULL;
3269 macro_start->text = nasm_quote(p, strlen(p));
3270 macro_start->type = TOK_STRING;
3271 macro_start->a.mac = NULL;
3272 if (xsl)
3273 nasm_free(xsl);
3276 * We now have a macro name, an implicit parameter count of
3277 * zero, and a string token to use as an expansion. Create
3278 * and store an SMacro.
3280 define_smacro(ctx, mname, casesense, 0, macro_start);
3281 free_tlist(tline);
3282 free_tlist(origline);
3283 return DIRECTIVE_FOUND;
3286 case PP_STRLEN:
3287 casesense = true;
3289 tline = tline->next;
3290 skip_white_(tline);
3291 tline = expand_id(tline);
3292 if (!tline || (tline->type != TOK_ID &&
3293 (tline->type != TOK_PREPROC_ID ||
3294 tline->text[1] != '$'))) {
3295 nasm_error(ERR_NONFATAL,
3296 "`%%strlen' expects a macro identifier as first parameter");
3297 free_tlist(origline);
3298 return DIRECTIVE_FOUND;
3300 ctx = get_ctx(tline->text, &mname);
3301 last = tline;
3302 tline = expand_smacro(tline->next);
3303 last->next = NULL;
3305 t = tline;
3306 while (tok_type_(t, TOK_WHITESPACE))
3307 t = t->next;
3308 /* t should now point to the string */
3309 if (!tok_type_(t, TOK_STRING)) {
3310 nasm_error(ERR_NONFATAL,
3311 "`%%strlen` requires string as second parameter");
3312 free_tlist(tline);
3313 free_tlist(origline);
3314 return DIRECTIVE_FOUND;
3317 macro_start = nasm_malloc(sizeof(*macro_start));
3318 macro_start->next = NULL;
3319 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3320 macro_start->a.mac = NULL;
3323 * We now have a macro name, an implicit parameter count of
3324 * zero, and a numeric token to use as an expansion. Create
3325 * and store an SMacro.
3327 define_smacro(ctx, mname, casesense, 0, macro_start);
3328 free_tlist(tline);
3329 free_tlist(origline);
3330 return DIRECTIVE_FOUND;
3332 case PP_STRCAT:
3333 casesense = true;
3335 tline = tline->next;
3336 skip_white_(tline);
3337 tline = expand_id(tline);
3338 if (!tline || (tline->type != TOK_ID &&
3339 (tline->type != TOK_PREPROC_ID ||
3340 tline->text[1] != '$'))) {
3341 nasm_error(ERR_NONFATAL,
3342 "`%%strcat' expects a macro identifier as first parameter");
3343 free_tlist(origline);
3344 return DIRECTIVE_FOUND;
3346 ctx = get_ctx(tline->text, &mname);
3347 last = tline;
3348 tline = expand_smacro(tline->next);
3349 last->next = NULL;
3351 len = 0;
3352 list_for_each(t, tline) {
3353 switch (t->type) {
3354 case TOK_WHITESPACE:
3355 break;
3356 case TOK_STRING:
3357 len += t->a.len = nasm_unquote(t->text, NULL);
3358 break;
3359 case TOK_OTHER:
3360 if (!strcmp(t->text, ",")) /* permit comma separators */
3361 break;
3362 /* else fall through */
3363 default:
3364 nasm_error(ERR_NONFATAL,
3365 "non-string passed to `%%strcat' (%d)", t->type);
3366 free_tlist(tline);
3367 free_tlist(origline);
3368 return DIRECTIVE_FOUND;
3372 p = pp = nasm_malloc(len);
3373 list_for_each(t, tline) {
3374 if (t->type == TOK_STRING) {
3375 memcpy(p, t->text, t->a.len);
3376 p += t->a.len;
3381 * We now have a macro name, an implicit parameter count of
3382 * zero, and a numeric token to use as an expansion. Create
3383 * and store an SMacro.
3385 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3386 macro_start->text = nasm_quote(pp, len);
3387 nasm_free(pp);
3388 define_smacro(ctx, mname, casesense, 0, macro_start);
3389 free_tlist(tline);
3390 free_tlist(origline);
3391 return DIRECTIVE_FOUND;
3393 case PP_SUBSTR:
3395 int64_t start, count;
3396 size_t len;
3398 casesense = true;
3400 tline = tline->next;
3401 skip_white_(tline);
3402 tline = expand_id(tline);
3403 if (!tline || (tline->type != TOK_ID &&
3404 (tline->type != TOK_PREPROC_ID ||
3405 tline->text[1] != '$'))) {
3406 nasm_error(ERR_NONFATAL,
3407 "`%%substr' expects a macro identifier as first parameter");
3408 free_tlist(origline);
3409 return DIRECTIVE_FOUND;
3411 ctx = get_ctx(tline->text, &mname);
3412 last = tline;
3413 tline = expand_smacro(tline->next);
3414 last->next = NULL;
3416 if (tline) /* skip expanded id */
3417 t = tline->next;
3418 while (tok_type_(t, TOK_WHITESPACE))
3419 t = t->next;
3421 /* t should now point to the string */
3422 if (!tok_type_(t, TOK_STRING)) {
3423 nasm_error(ERR_NONFATAL,
3424 "`%%substr` requires string as second parameter");
3425 free_tlist(tline);
3426 free_tlist(origline);
3427 return DIRECTIVE_FOUND;
3430 tt = t->next;
3431 tptr = &tt;
3432 tokval.t_type = TOKEN_INVALID;
3433 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3434 if (!evalresult) {
3435 free_tlist(tline);
3436 free_tlist(origline);
3437 return DIRECTIVE_FOUND;
3438 } else if (!is_simple(evalresult)) {
3439 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3440 free_tlist(tline);
3441 free_tlist(origline);
3442 return DIRECTIVE_FOUND;
3444 start = evalresult->value - 1;
3446 while (tok_type_(tt, TOK_WHITESPACE))
3447 tt = tt->next;
3448 if (!tt) {
3449 count = 1; /* Backwards compatibility: one character */
3450 } else {
3451 tokval.t_type = TOKEN_INVALID;
3452 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3453 if (!evalresult) {
3454 free_tlist(tline);
3455 free_tlist(origline);
3456 return DIRECTIVE_FOUND;
3457 } else if (!is_simple(evalresult)) {
3458 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3459 free_tlist(tline);
3460 free_tlist(origline);
3461 return DIRECTIVE_FOUND;
3463 count = evalresult->value;
3466 len = nasm_unquote(t->text, NULL);
3468 /* make start and count being in range */
3469 if (start < 0)
3470 start = 0;
3471 if (count < 0)
3472 count = len + count + 1 - start;
3473 if (start + count > (int64_t)len)
3474 count = len - start;
3475 if (!len || count < 0 || start >=(int64_t)len)
3476 start = -1, count = 0; /* empty string */
3478 macro_start = nasm_malloc(sizeof(*macro_start));
3479 macro_start->next = NULL;
3480 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3481 macro_start->type = TOK_STRING;
3482 macro_start->a.mac = NULL;
3485 * We now have a macro name, an implicit parameter count of
3486 * zero, and a numeric token to use as an expansion. Create
3487 * and store an SMacro.
3489 define_smacro(ctx, mname, casesense, 0, macro_start);
3490 free_tlist(tline);
3491 free_tlist(origline);
3492 return DIRECTIVE_FOUND;
3495 case PP_ASSIGN:
3496 case PP_IASSIGN:
3497 casesense = (i == PP_ASSIGN);
3499 tline = tline->next;
3500 skip_white_(tline);
3501 tline = expand_id(tline);
3502 if (!tline || (tline->type != TOK_ID &&
3503 (tline->type != TOK_PREPROC_ID ||
3504 tline->text[1] != '$'))) {
3505 nasm_error(ERR_NONFATAL,
3506 "`%%%sassign' expects a macro identifier",
3507 (i == PP_IASSIGN ? "i" : ""));
3508 free_tlist(origline);
3509 return DIRECTIVE_FOUND;
3511 ctx = get_ctx(tline->text, &mname);
3512 last = tline;
3513 tline = expand_smacro(tline->next);
3514 last->next = NULL;
3516 t = tline;
3517 tptr = &t;
3518 tokval.t_type = TOKEN_INVALID;
3519 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3520 free_tlist(tline);
3521 if (!evalresult) {
3522 free_tlist(origline);
3523 return DIRECTIVE_FOUND;
3526 if (tokval.t_type)
3527 nasm_error(ERR_WARNING|ERR_PASS1,
3528 "trailing garbage after expression ignored");
3530 if (!is_simple(evalresult)) {
3531 nasm_error(ERR_NONFATAL,
3532 "non-constant value given to `%%%sassign'",
3533 (i == PP_IASSIGN ? "i" : ""));
3534 free_tlist(origline);
3535 return DIRECTIVE_FOUND;
3538 macro_start = nasm_malloc(sizeof(*macro_start));
3539 macro_start->next = NULL;
3540 make_tok_num(macro_start, reloc_value(evalresult));
3541 macro_start->a.mac = NULL;
3544 * We now have a macro name, an implicit parameter count of
3545 * zero, and a numeric token to use as an expansion. Create
3546 * and store an SMacro.
3548 define_smacro(ctx, mname, casesense, 0, macro_start);
3549 free_tlist(origline);
3550 return DIRECTIVE_FOUND;
3552 case PP_LINE:
3554 * Syntax is `%line nnn[+mmm] [filename]'
3556 tline = tline->next;
3557 skip_white_(tline);
3558 if (!tok_type_(tline, TOK_NUMBER)) {
3559 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3560 free_tlist(origline);
3561 return DIRECTIVE_FOUND;
3563 k = readnum(tline->text, &err);
3564 m = 1;
3565 tline = tline->next;
3566 if (tok_is_(tline, "+")) {
3567 tline = tline->next;
3568 if (!tok_type_(tline, TOK_NUMBER)) {
3569 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3570 free_tlist(origline);
3571 return DIRECTIVE_FOUND;
3573 m = readnum(tline->text, &err);
3574 tline = tline->next;
3576 skip_white_(tline);
3577 src_set_linnum(k);
3578 istk->lineinc = m;
3579 if (tline) {
3580 char *fname = detoken(tline, false);
3581 src_set_fname(fname);
3582 nasm_free(fname);
3584 free_tlist(origline);
3585 return DIRECTIVE_FOUND;
3587 default:
3588 nasm_error(ERR_FATAL,
3589 "preprocessor directive `%s' not yet implemented",
3590 pp_directives[i]);
3591 return DIRECTIVE_FOUND;
3596 * Ensure that a macro parameter contains a condition code and
3597 * nothing else. Return the condition code index if so, or -1
3598 * otherwise.
3600 static int find_cc(Token * t)
3602 Token *tt;
3604 if (!t)
3605 return -1; /* Probably a %+ without a space */
3607 skip_white_(t);
3608 if (t->type != TOK_ID)
3609 return -1;
3610 tt = t->next;
3611 skip_white_(tt);
3612 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3613 return -1;
3615 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3619 * This routines walks over tokens strem and hadnles tokens
3620 * pasting, if @handle_explicit passed then explicit pasting
3621 * term is handled, otherwise -- implicit pastings only.
3623 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3624 size_t mnum, bool handle_explicit)
3626 Token *tok, *next, **prev_next, **prev_nonspace;
3627 bool pasted = false;
3628 char *buf, *p;
3629 size_t len, i;
3632 * The last token before pasting. We need it
3633 * to be able to connect new handled tokens.
3634 * In other words if there were a tokens stream
3636 * A -> B -> C -> D
3638 * and we've joined tokens B and C, the resulting
3639 * stream should be
3641 * A -> BC -> D
3643 tok = *head;
3644 prev_next = NULL;
3646 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3647 prev_nonspace = head;
3648 else
3649 prev_nonspace = NULL;
3651 while (tok && (next = tok->next)) {
3653 switch (tok->type) {
3654 case TOK_WHITESPACE:
3655 /* Zap redundant whitespaces */
3656 while (tok_type_(next, TOK_WHITESPACE))
3657 next = delete_Token(next);
3658 tok->next = next;
3659 break;
3661 case TOK_PASTE:
3662 /* Explicit pasting */
3663 if (!handle_explicit)
3664 break;
3665 next = delete_Token(tok);
3667 while (tok_type_(next, TOK_WHITESPACE))
3668 next = delete_Token(next);
3670 if (!pasted)
3671 pasted = true;
3673 /* Left pasting token is start of line */
3674 if (!prev_nonspace)
3675 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3678 * No ending token, this might happen in two
3679 * cases
3681 * 1) There indeed no right token at all
3682 * 2) There is a bare "%define ID" statement,
3683 * and @ID does expand to whitespace.
3685 * So technically we need to do a grammar analysis
3686 * in another stage of parsing, but for now lets don't
3687 * change the behaviour people used to. Simply allow
3688 * whitespace after paste token.
3690 if (!next) {
3692 * Zap ending space tokens and that's all.
3694 tok = (*prev_nonspace)->next;
3695 while (tok_type_(tok, TOK_WHITESPACE))
3696 tok = delete_Token(tok);
3697 tok = *prev_nonspace;
3698 tok->next = NULL;
3699 break;
3702 tok = *prev_nonspace;
3703 while (tok_type_(tok, TOK_WHITESPACE))
3704 tok = delete_Token(tok);
3705 len = strlen(tok->text);
3706 len += strlen(next->text);
3708 p = buf = nasm_malloc(len + 1);
3709 strcpy(p, tok->text);
3710 p = strchr(p, '\0');
3711 strcpy(p, next->text);
3713 delete_Token(tok);
3715 tok = tokenize(buf);
3716 nasm_free(buf);
3718 *prev_nonspace = tok;
3719 while (tok && tok->next)
3720 tok = tok->next;
3722 tok->next = delete_Token(next);
3724 /* Restart from pasted tokens head */
3725 tok = *prev_nonspace;
3726 break;
3728 default:
3729 /* implicit pasting */
3730 for (i = 0; i < mnum; i++) {
3731 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3732 continue;
3734 len = 0;
3735 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3736 len += strlen(next->text);
3737 next = next->next;
3740 /* No match */
3741 if (tok == next)
3742 break;
3744 len += strlen(tok->text);
3745 p = buf = nasm_malloc(len + 1);
3747 while (tok != next) {
3748 strcpy(p, tok->text);
3749 p = strchr(p, '\0');
3750 tok = delete_Token(tok);
3753 tok = tokenize(buf);
3754 nasm_free(buf);
3756 if (prev_next)
3757 *prev_next = tok;
3758 else
3759 *head = tok;
3762 * Connect pasted into original stream,
3763 * ie A -> new-tokens -> B
3765 while (tok && tok->next)
3766 tok = tok->next;
3767 tok->next = next;
3769 if (!pasted)
3770 pasted = true;
3772 /* Restart from pasted tokens head */
3773 tok = prev_next ? *prev_next : *head;
3776 break;
3779 prev_next = &tok->next;
3781 if (tok->next &&
3782 !tok_type_(tok->next, TOK_WHITESPACE) &&
3783 !tok_type_(tok->next, TOK_PASTE))
3784 prev_nonspace = prev_next;
3786 tok = tok->next;
3789 return pasted;
3793 * expands to a list of tokens from %{x:y}
3795 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3797 Token *t = tline, **tt, *tm, *head;
3798 char *pos;
3799 int fst, lst, j, i;
3801 pos = strchr(tline->text, ':');
3802 nasm_assert(pos);
3804 lst = atoi(pos + 1);
3805 fst = atoi(tline->text + 1);
3808 * only macros params are accounted so
3809 * if someone passes %0 -- we reject such
3810 * value(s)
3812 if (lst == 0 || fst == 0)
3813 goto err;
3815 /* the values should be sane */
3816 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3817 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3818 goto err;
3820 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3821 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3823 /* counted from zero */
3824 fst--, lst--;
3827 * It will be at least one token. Note we
3828 * need to scan params until separator, otherwise
3829 * only first token will be passed.
3831 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3832 head = new_Token(NULL, tm->type, tm->text, 0);
3833 tt = &head->next, tm = tm->next;
3834 while (tok_isnt_(tm, ",")) {
3835 t = new_Token(NULL, tm->type, tm->text, 0);
3836 *tt = t, tt = &t->next, tm = tm->next;
3839 if (fst < lst) {
3840 for (i = fst + 1; i <= lst; i++) {
3841 t = new_Token(NULL, TOK_OTHER, ",", 0);
3842 *tt = t, tt = &t->next;
3843 j = (i + mac->rotate) % mac->nparam;
3844 tm = mac->params[j];
3845 while (tok_isnt_(tm, ",")) {
3846 t = new_Token(NULL, tm->type, tm->text, 0);
3847 *tt = t, tt = &t->next, tm = tm->next;
3850 } else {
3851 for (i = fst - 1; i >= lst; i--) {
3852 t = new_Token(NULL, TOK_OTHER, ",", 0);
3853 *tt = t, tt = &t->next;
3854 j = (i + mac->rotate) % mac->nparam;
3855 tm = mac->params[j];
3856 while (tok_isnt_(tm, ",")) {
3857 t = new_Token(NULL, tm->type, tm->text, 0);
3858 *tt = t, tt = &t->next, tm = tm->next;
3863 *last = tt;
3864 return head;
3866 err:
3867 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3868 &tline->text[1]);
3869 return tline;
3873 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3874 * %-n) and MMacro-local identifiers (%%foo) as well as
3875 * macro indirection (%[...]) and range (%{..:..}).
3877 static Token *expand_mmac_params(Token * tline)
3879 Token *t, *tt, **tail, *thead;
3880 bool changed = false;
3881 char *pos;
3883 tail = &thead;
3884 thead = NULL;
3886 while (tline) {
3887 if (tline->type == TOK_PREPROC_ID &&
3888 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3889 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3890 tline->text[1] == '%')) {
3891 char *text = NULL;
3892 int type = 0, cc; /* type = 0 to placate optimisers */
3893 char tmpbuf[30];
3894 unsigned int n;
3895 int i;
3896 MMacro *mac;
3898 t = tline;
3899 tline = tline->next;
3901 mac = istk->mstk;
3902 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3903 mac = mac->next_active;
3904 if (!mac) {
3905 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3906 } else {
3907 pos = strchr(t->text, ':');
3908 if (!pos) {
3909 switch (t->text[1]) {
3911 * We have to make a substitution of one of the
3912 * forms %1, %-1, %+1, %%foo, %0.
3914 case '0':
3915 type = TOK_NUMBER;
3916 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3917 text = nasm_strdup(tmpbuf);
3918 break;
3919 case '%':
3920 type = TOK_ID;
3921 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3922 mac->unique);
3923 text = nasm_strcat(tmpbuf, t->text + 2);
3924 break;
3925 case '-':
3926 n = atoi(t->text + 2) - 1;
3927 if (n >= mac->nparam)
3928 tt = NULL;
3929 else {
3930 if (mac->nparam > 1)
3931 n = (n + mac->rotate) % mac->nparam;
3932 tt = mac->params[n];
3934 cc = find_cc(tt);
3935 if (cc == -1) {
3936 nasm_error(ERR_NONFATAL,
3937 "macro parameter %d is not a condition code",
3938 n + 1);
3939 text = NULL;
3940 } else {
3941 type = TOK_ID;
3942 if (inverse_ccs[cc] == -1) {
3943 nasm_error(ERR_NONFATAL,
3944 "condition code `%s' is not invertible",
3945 conditions[cc]);
3946 text = NULL;
3947 } else
3948 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3950 break;
3951 case '+':
3952 n = atoi(t->text + 2) - 1;
3953 if (n >= mac->nparam)
3954 tt = NULL;
3955 else {
3956 if (mac->nparam > 1)
3957 n = (n + mac->rotate) % mac->nparam;
3958 tt = mac->params[n];
3960 cc = find_cc(tt);
3961 if (cc == -1) {
3962 nasm_error(ERR_NONFATAL,
3963 "macro parameter %d is not a condition code",
3964 n + 1);
3965 text = NULL;
3966 } else {
3967 type = TOK_ID;
3968 text = nasm_strdup(conditions[cc]);
3970 break;
3971 default:
3972 n = atoi(t->text + 1) - 1;
3973 if (n >= mac->nparam)
3974 tt = NULL;
3975 else {
3976 if (mac->nparam > 1)
3977 n = (n + mac->rotate) % mac->nparam;
3978 tt = mac->params[n];
3980 if (tt) {
3981 for (i = 0; i < mac->paramlen[n]; i++) {
3982 *tail = new_Token(NULL, tt->type, tt->text, 0);
3983 tail = &(*tail)->next;
3984 tt = tt->next;
3987 text = NULL; /* we've done it here */
3988 break;
3990 } else {
3992 * seems we have a parameters range here
3994 Token *head, **last;
3995 head = expand_mmac_params_range(mac, t, &last);
3996 if (head != t) {
3997 *tail = head;
3998 *last = tline;
3999 tline = head;
4000 text = NULL;
4004 if (!text) {
4005 delete_Token(t);
4006 } else {
4007 *tail = t;
4008 tail = &t->next;
4009 t->type = type;
4010 nasm_free(t->text);
4011 t->text = text;
4012 t->a.mac = NULL;
4014 changed = true;
4015 continue;
4016 } else if (tline->type == TOK_INDIRECT) {
4017 t = tline;
4018 tline = tline->next;
4019 tt = tokenize(t->text);
4020 tt = expand_mmac_params(tt);
4021 tt = expand_smacro(tt);
4022 *tail = tt;
4023 while (tt) {
4024 tt->a.mac = NULL; /* Necessary? */
4025 tail = &tt->next;
4026 tt = tt->next;
4028 delete_Token(t);
4029 changed = true;
4030 } else {
4031 t = *tail = tline;
4032 tline = tline->next;
4033 t->a.mac = NULL;
4034 tail = &t->next;
4037 *tail = NULL;
4039 if (changed) {
4040 const struct tokseq_match t[] = {
4042 PP_CONCAT_MASK(TOK_ID) |
4043 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4044 PP_CONCAT_MASK(TOK_ID) |
4045 PP_CONCAT_MASK(TOK_NUMBER) |
4046 PP_CONCAT_MASK(TOK_FLOAT) |
4047 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4050 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4051 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4054 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4057 return thead;
4061 * Expand all single-line macro calls made in the given line.
4062 * Return the expanded version of the line. The original is deemed
4063 * to be destroyed in the process. (In reality we'll just move
4064 * Tokens from input to output a lot of the time, rather than
4065 * actually bothering to destroy and replicate.)
4068 static Token *expand_smacro(Token * tline)
4070 Token *t, *tt, *mstart, **tail, *thead;
4071 SMacro *head = NULL, *m;
4072 Token **params;
4073 int *paramsize;
4074 unsigned int nparam, sparam;
4075 int brackets;
4076 Token *org_tline = tline;
4077 Context *ctx;
4078 const char *mname;
4079 int deadman = DEADMAN_LIMIT;
4080 bool expanded;
4083 * Trick: we should avoid changing the start token pointer since it can
4084 * be contained in "next" field of other token. Because of this
4085 * we allocate a copy of first token and work with it; at the end of
4086 * routine we copy it back
4088 if (org_tline) {
4089 tline = new_Token(org_tline->next, org_tline->type,
4090 org_tline->text, 0);
4091 tline->a.mac = org_tline->a.mac;
4092 nasm_free(org_tline->text);
4093 org_tline->text = NULL;
4096 expanded = true; /* Always expand %+ at least once */
4098 again:
4099 thead = NULL;
4100 tail = &thead;
4102 while (tline) { /* main token loop */
4103 if (!--deadman) {
4104 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4105 goto err;
4108 if ((mname = tline->text)) {
4109 /* if this token is a local macro, look in local context */
4110 if (tline->type == TOK_ID) {
4111 head = (SMacro *)hash_findix(&smacros, mname);
4112 } else if (tline->type == TOK_PREPROC_ID) {
4113 ctx = get_ctx(mname, &mname);
4114 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4115 } else
4116 head = NULL;
4119 * We've hit an identifier. As in is_mmacro below, we first
4120 * check whether the identifier is a single-line macro at
4121 * all, then think about checking for parameters if
4122 * necessary.
4124 list_for_each(m, head)
4125 if (!mstrcmp(m->name, mname, m->casesense))
4126 break;
4127 if (m) {
4128 mstart = tline;
4129 params = NULL;
4130 paramsize = NULL;
4131 if (m->nparam == 0) {
4133 * Simple case: the macro is parameterless. Discard the
4134 * one token that the macro call took, and push the
4135 * expansion back on the to-do stack.
4137 if (!m->expansion) {
4138 if (!strcmp("__FILE__", m->name)) {
4139 const char *file = src_get_fname();
4140 /* nasm_free(tline->text); here? */
4141 tline->text = nasm_quote(file, strlen(file));
4142 tline->type = TOK_STRING;
4143 continue;
4145 if (!strcmp("__LINE__", m->name)) {
4146 nasm_free(tline->text);
4147 make_tok_num(tline, src_get_linnum());
4148 continue;
4150 if (!strcmp("__BITS__", m->name)) {
4151 nasm_free(tline->text);
4152 make_tok_num(tline, globalbits);
4153 continue;
4155 tline = delete_Token(tline);
4156 continue;
4158 } else {
4160 * Complicated case: at least one macro with this name
4161 * exists and takes parameters. We must find the
4162 * parameters in the call, count them, find the SMacro
4163 * that corresponds to that form of the macro call, and
4164 * substitute for the parameters when we expand. What a
4165 * pain.
4167 /*tline = tline->next;
4168 skip_white_(tline); */
4169 do {
4170 t = tline->next;
4171 while (tok_type_(t, TOK_SMAC_END)) {
4172 t->a.mac->in_progress = false;
4173 t->text = NULL;
4174 t = tline->next = delete_Token(t);
4176 tline = t;
4177 } while (tok_type_(tline, TOK_WHITESPACE));
4178 if (!tok_is_(tline, "(")) {
4180 * This macro wasn't called with parameters: ignore
4181 * the call. (Behaviour borrowed from gnu cpp.)
4183 tline = mstart;
4184 m = NULL;
4185 } else {
4186 int paren = 0;
4187 int white = 0;
4188 brackets = 0;
4189 nparam = 0;
4190 sparam = PARAM_DELTA;
4191 params = nasm_malloc(sparam * sizeof(Token *));
4192 params[0] = tline->next;
4193 paramsize = nasm_malloc(sparam * sizeof(int));
4194 paramsize[0] = 0;
4195 while (true) { /* parameter loop */
4197 * For some unusual expansions
4198 * which concatenates function call
4200 t = tline->next;
4201 while (tok_type_(t, TOK_SMAC_END)) {
4202 t->a.mac->in_progress = false;
4203 t->text = NULL;
4204 t = tline->next = delete_Token(t);
4206 tline = t;
4208 if (!tline) {
4209 nasm_error(ERR_NONFATAL,
4210 "macro call expects terminating `)'");
4211 break;
4213 if (tline->type == TOK_WHITESPACE
4214 && brackets <= 0) {
4215 if (paramsize[nparam])
4216 white++;
4217 else
4218 params[nparam] = tline->next;
4219 continue; /* parameter loop */
4221 if (tline->type == TOK_OTHER
4222 && tline->text[1] == 0) {
4223 char ch = tline->text[0];
4224 if (ch == ',' && !paren && brackets <= 0) {
4225 if (++nparam >= sparam) {
4226 sparam += PARAM_DELTA;
4227 params = nasm_realloc(params,
4228 sparam * sizeof(Token *));
4229 paramsize = nasm_realloc(paramsize,
4230 sparam * sizeof(int));
4232 params[nparam] = tline->next;
4233 paramsize[nparam] = 0;
4234 white = 0;
4235 continue; /* parameter loop */
4237 if (ch == '{' &&
4238 (brackets > 0 || (brackets == 0 &&
4239 !paramsize[nparam])))
4241 if (!(brackets++)) {
4242 params[nparam] = tline->next;
4243 continue; /* parameter loop */
4246 if (ch == '}' && brackets > 0)
4247 if (--brackets == 0) {
4248 brackets = -1;
4249 continue; /* parameter loop */
4251 if (ch == '(' && !brackets)
4252 paren++;
4253 if (ch == ')' && brackets <= 0)
4254 if (--paren < 0)
4255 break;
4257 if (brackets < 0) {
4258 brackets = 0;
4259 nasm_error(ERR_NONFATAL, "braces do not "
4260 "enclose all of macro parameter");
4262 paramsize[nparam] += white + 1;
4263 white = 0;
4264 } /* parameter loop */
4265 nparam++;
4266 while (m && (m->nparam != nparam ||
4267 mstrcmp(m->name, mname,
4268 m->casesense)))
4269 m = m->next;
4270 if (!m)
4271 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4272 "macro `%s' exists, "
4273 "but not taking %d parameters",
4274 mstart->text, nparam);
4277 if (m && m->in_progress)
4278 m = NULL;
4279 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4281 * Design question: should we handle !tline, which
4282 * indicates missing ')' here, or expand those
4283 * macros anyway, which requires the (t) test a few
4284 * lines down?
4286 nasm_free(params);
4287 nasm_free(paramsize);
4288 tline = mstart;
4289 } else {
4291 * Expand the macro: we are placed on the last token of the
4292 * call, so that we can easily split the call from the
4293 * following tokens. We also start by pushing an SMAC_END
4294 * token for the cycle removal.
4296 t = tline;
4297 if (t) {
4298 tline = t->next;
4299 t->next = NULL;
4301 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4302 tt->a.mac = m;
4303 m->in_progress = true;
4304 tline = tt;
4305 list_for_each(t, m->expansion) {
4306 if (t->type >= TOK_SMAC_PARAM) {
4307 Token *pcopy = tline, **ptail = &pcopy;
4308 Token *ttt, *pt;
4309 int i;
4311 ttt = params[t->type - TOK_SMAC_PARAM];
4312 i = paramsize[t->type - TOK_SMAC_PARAM];
4313 while (--i >= 0) {
4314 pt = *ptail = new_Token(tline, ttt->type,
4315 ttt->text, 0);
4316 ptail = &pt->next;
4317 ttt = ttt->next;
4319 tline = pcopy;
4320 } else if (t->type == TOK_PREPROC_Q) {
4321 tt = new_Token(tline, TOK_ID, mname, 0);
4322 tline = tt;
4323 } else if (t->type == TOK_PREPROC_QQ) {
4324 tt = new_Token(tline, TOK_ID, m->name, 0);
4325 tline = tt;
4326 } else {
4327 tt = new_Token(tline, t->type, t->text, 0);
4328 tline = tt;
4333 * Having done that, get rid of the macro call, and clean
4334 * up the parameters.
4336 nasm_free(params);
4337 nasm_free(paramsize);
4338 free_tlist(mstart);
4339 expanded = true;
4340 continue; /* main token loop */
4345 if (tline->type == TOK_SMAC_END) {
4346 tline->a.mac->in_progress = false;
4347 tline = delete_Token(tline);
4348 } else {
4349 t = *tail = tline;
4350 tline = tline->next;
4351 t->a.mac = NULL;
4352 t->next = NULL;
4353 tail = &t->next;
4358 * Now scan the entire line and look for successive TOK_IDs that resulted
4359 * after expansion (they can't be produced by tokenize()). The successive
4360 * TOK_IDs should be concatenated.
4361 * Also we look for %+ tokens and concatenate the tokens before and after
4362 * them (without white spaces in between).
4364 if (expanded) {
4365 const struct tokseq_match t[] = {
4367 PP_CONCAT_MASK(TOK_ID) |
4368 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4369 PP_CONCAT_MASK(TOK_ID) |
4370 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4371 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4374 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4376 * If we concatenated something, *and* we had previously expanded
4377 * an actual macro, scan the lines again for macros...
4379 tline = thead;
4380 expanded = false;
4381 goto again;
4385 err:
4386 if (org_tline) {
4387 if (thead) {
4388 *org_tline = *thead;
4389 /* since we just gave text to org_line, don't free it */
4390 thead->text = NULL;
4391 delete_Token(thead);
4392 } else {
4393 /* the expression expanded to empty line;
4394 we can't return NULL for some reasons
4395 we just set the line to a single WHITESPACE token. */
4396 memset(org_tline, 0, sizeof(*org_tline));
4397 org_tline->text = NULL;
4398 org_tline->type = TOK_WHITESPACE;
4400 thead = org_tline;
4403 return thead;
4407 * Similar to expand_smacro but used exclusively with macro identifiers
4408 * right before they are fetched in. The reason is that there can be
4409 * identifiers consisting of several subparts. We consider that if there
4410 * are more than one element forming the name, user wants a expansion,
4411 * otherwise it will be left as-is. Example:
4413 * %define %$abc cde
4415 * the identifier %$abc will be left as-is so that the handler for %define
4416 * will suck it and define the corresponding value. Other case:
4418 * %define _%$abc cde
4420 * In this case user wants name to be expanded *before* %define starts
4421 * working, so we'll expand %$abc into something (if it has a value;
4422 * otherwise it will be left as-is) then concatenate all successive
4423 * PP_IDs into one.
4425 static Token *expand_id(Token * tline)
4427 Token *cur, *oldnext = NULL;
4429 if (!tline || !tline->next)
4430 return tline;
4432 cur = tline;
4433 while (cur->next &&
4434 (cur->next->type == TOK_ID ||
4435 cur->next->type == TOK_PREPROC_ID
4436 || cur->next->type == TOK_NUMBER))
4437 cur = cur->next;
4439 /* If identifier consists of just one token, don't expand */
4440 if (cur == tline)
4441 return tline;
4443 if (cur) {
4444 oldnext = cur->next; /* Detach the tail past identifier */
4445 cur->next = NULL; /* so that expand_smacro stops here */
4448 tline = expand_smacro(tline);
4450 if (cur) {
4451 /* expand_smacro possibly changhed tline; re-scan for EOL */
4452 cur = tline;
4453 while (cur && cur->next)
4454 cur = cur->next;
4455 if (cur)
4456 cur->next = oldnext;
4459 return tline;
4463 * Determine whether the given line constitutes a multi-line macro
4464 * call, and return the MMacro structure called if so. Doesn't have
4465 * to check for an initial label - that's taken care of in
4466 * expand_mmacro - but must check numbers of parameters. Guaranteed
4467 * to be called with tline->type == TOK_ID, so the putative macro
4468 * name is easy to find.
4470 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4472 MMacro *head, *m;
4473 Token **params;
4474 int nparam;
4476 head = (MMacro *) hash_findix(&mmacros, tline->text);
4479 * Efficiency: first we see if any macro exists with the given
4480 * name. If not, we can return NULL immediately. _Then_ we
4481 * count the parameters, and then we look further along the
4482 * list if necessary to find the proper MMacro.
4484 list_for_each(m, head)
4485 if (!mstrcmp(m->name, tline->text, m->casesense))
4486 break;
4487 if (!m)
4488 return NULL;
4491 * OK, we have a potential macro. Count and demarcate the
4492 * parameters.
4494 count_mmac_params(tline->next, &nparam, &params);
4497 * So we know how many parameters we've got. Find the MMacro
4498 * structure that handles this number.
4500 while (m) {
4501 if (m->nparam_min <= nparam
4502 && (m->plus || nparam <= m->nparam_max)) {
4504 * This one is right. Just check if cycle removal
4505 * prohibits us using it before we actually celebrate...
4507 if (m->in_progress > m->max_depth) {
4508 if (m->max_depth > 0) {
4509 nasm_error(ERR_WARNING,
4510 "reached maximum recursion depth of %i",
4511 m->max_depth);
4513 nasm_free(params);
4514 return NULL;
4517 * It's right, and we can use it. Add its default
4518 * parameters to the end of our list if necessary.
4520 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4521 params =
4522 nasm_realloc(params,
4523 ((m->nparam_min + m->ndefs +
4524 1) * sizeof(*params)));
4525 while (nparam < m->nparam_min + m->ndefs) {
4526 params[nparam] = m->defaults[nparam - m->nparam_min];
4527 nparam++;
4531 * If we've gone over the maximum parameter count (and
4532 * we're in Plus mode), ignore parameters beyond
4533 * nparam_max.
4535 if (m->plus && nparam > m->nparam_max)
4536 nparam = m->nparam_max;
4538 * Then terminate the parameter list, and leave.
4540 if (!params) { /* need this special case */
4541 params = nasm_malloc(sizeof(*params));
4542 nparam = 0;
4544 params[nparam] = NULL;
4545 *params_array = params;
4546 return m;
4549 * This one wasn't right: look for the next one with the
4550 * same name.
4552 list_for_each(m, m->next)
4553 if (!mstrcmp(m->name, tline->text, m->casesense))
4554 break;
4558 * After all that, we didn't find one with the right number of
4559 * parameters. Issue a warning, and fail to expand the macro.
4561 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4562 "macro `%s' exists, but not taking %d parameters",
4563 tline->text, nparam);
4564 nasm_free(params);
4565 return NULL;
4570 * Save MMacro invocation specific fields in
4571 * preparation for a recursive macro expansion
4573 static void push_mmacro(MMacro *m)
4575 MMacroInvocation *i;
4577 i = nasm_malloc(sizeof(MMacroInvocation));
4578 i->prev = m->prev;
4579 i->params = m->params;
4580 i->iline = m->iline;
4581 i->nparam = m->nparam;
4582 i->rotate = m->rotate;
4583 i->paramlen = m->paramlen;
4584 i->unique = m->unique;
4585 i->condcnt = m->condcnt;
4586 m->prev = i;
4591 * Restore MMacro invocation specific fields that were
4592 * saved during a previous recursive macro expansion
4594 static void pop_mmacro(MMacro *m)
4596 MMacroInvocation *i;
4598 if (m->prev) {
4599 i = m->prev;
4600 m->prev = i->prev;
4601 m->params = i->params;
4602 m->iline = i->iline;
4603 m->nparam = i->nparam;
4604 m->rotate = i->rotate;
4605 m->paramlen = i->paramlen;
4606 m->unique = i->unique;
4607 m->condcnt = i->condcnt;
4608 nasm_free(i);
4614 * Expand the multi-line macro call made by the given line, if
4615 * there is one to be expanded. If there is, push the expansion on
4616 * istk->expansion and return 1. Otherwise return 0.
4618 static int expand_mmacro(Token * tline)
4620 Token *startline = tline;
4621 Token *label = NULL;
4622 int dont_prepend = 0;
4623 Token **params, *t, *tt;
4624 MMacro *m;
4625 Line *l, *ll;
4626 int i, nparam, *paramlen;
4627 const char *mname;
4629 t = tline;
4630 skip_white_(t);
4631 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4632 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4633 return 0;
4634 m = is_mmacro(t, &params);
4635 if (m) {
4636 mname = t->text;
4637 } else {
4638 Token *last;
4640 * We have an id which isn't a macro call. We'll assume
4641 * it might be a label; we'll also check to see if a
4642 * colon follows it. Then, if there's another id after
4643 * that lot, we'll check it again for macro-hood.
4645 label = last = t;
4646 t = t->next;
4647 if (tok_type_(t, TOK_WHITESPACE))
4648 last = t, t = t->next;
4649 if (tok_is_(t, ":")) {
4650 dont_prepend = 1;
4651 last = t, t = t->next;
4652 if (tok_type_(t, TOK_WHITESPACE))
4653 last = t, t = t->next;
4655 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4656 return 0;
4657 last->next = NULL;
4658 mname = t->text;
4659 tline = t;
4663 * Fix up the parameters: this involves stripping leading and
4664 * trailing whitespace, then stripping braces if they are
4665 * present.
4667 for (nparam = 0; params[nparam]; nparam++) ;
4668 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4670 for (i = 0; params[i]; i++) {
4671 int brace = 0;
4672 int comma = (!m->plus || i < nparam - 1);
4674 t = params[i];
4675 skip_white_(t);
4676 if (tok_is_(t, "{"))
4677 t = t->next, brace++, comma = false;
4678 params[i] = t;
4679 paramlen[i] = 0;
4680 while (t) {
4681 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4682 break; /* ... because we have hit a comma */
4683 if (comma && t->type == TOK_WHITESPACE
4684 && tok_is_(t->next, ","))
4685 break; /* ... or a space then a comma */
4686 if (brace && t->type == TOK_OTHER) {
4687 if (t->text[0] == '{')
4688 brace++; /* ... or a nested opening brace */
4689 else if (t->text[0] == '}')
4690 if (!--brace)
4691 break; /* ... or a brace */
4693 t = t->next;
4694 paramlen[i]++;
4696 if (brace)
4697 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4701 * OK, we have a MMacro structure together with a set of
4702 * parameters. We must now go through the expansion and push
4703 * copies of each Line on to istk->expansion. Substitution of
4704 * parameter tokens and macro-local tokens doesn't get done
4705 * until the single-line macro substitution process; this is
4706 * because delaying them allows us to change the semantics
4707 * later through %rotate.
4709 * First, push an end marker on to istk->expansion, mark this
4710 * macro as in progress, and set up its invocation-specific
4711 * variables.
4713 ll = nasm_malloc(sizeof(Line));
4714 ll->next = istk->expansion;
4715 ll->finishes = m;
4716 ll->first = NULL;
4717 istk->expansion = ll;
4720 * Save the previous MMacro expansion in the case of
4721 * macro recursion
4723 if (m->max_depth && m->in_progress)
4724 push_mmacro(m);
4726 m->in_progress ++;
4727 m->params = params;
4728 m->iline = tline;
4729 m->nparam = nparam;
4730 m->rotate = 0;
4731 m->paramlen = paramlen;
4732 m->unique = unique++;
4733 m->lineno = 0;
4734 m->condcnt = 0;
4736 m->next_active = istk->mstk;
4737 istk->mstk = m;
4739 list_for_each(l, m->expansion) {
4740 Token **tail;
4742 ll = nasm_malloc(sizeof(Line));
4743 ll->finishes = NULL;
4744 ll->next = istk->expansion;
4745 istk->expansion = ll;
4746 tail = &ll->first;
4748 list_for_each(t, l->first) {
4749 Token *x = t;
4750 switch (t->type) {
4751 case TOK_PREPROC_Q:
4752 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4753 break;
4754 case TOK_PREPROC_QQ:
4755 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4756 break;
4757 case TOK_PREPROC_ID:
4758 if (t->text[1] == '0' && t->text[2] == '0') {
4759 dont_prepend = -1;
4760 x = label;
4761 if (!x)
4762 continue;
4764 /* fall through */
4765 default:
4766 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4767 break;
4769 tail = &tt->next;
4771 *tail = NULL;
4775 * If we had a label, push it on as the first line of
4776 * the macro expansion.
4778 if (label) {
4779 if (dont_prepend < 0)
4780 free_tlist(startline);
4781 else {
4782 ll = nasm_malloc(sizeof(Line));
4783 ll->finishes = NULL;
4784 ll->next = istk->expansion;
4785 istk->expansion = ll;
4786 ll->first = startline;
4787 if (!dont_prepend) {
4788 while (label->next)
4789 label = label->next;
4790 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4795 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4797 return 1;
4801 * This function adds macro names to error messages, and suppresses
4802 * them if necessary.
4804 static void pp_verror(int severity, const char *fmt, va_list arg)
4806 char buff[BUFSIZ];
4807 MMacro *mmac = NULL;
4808 int delta = 0;
4811 * If we're in a dead branch of IF or something like it, ignore the error.
4812 * However, because %else etc are evaluated in the state context
4813 * of the previous branch, errors might get lost:
4814 * %if 0 ... %else trailing garbage ... %endif
4815 * So %else etc should set the ERR_PP_PRECOND flag.
4817 if ((severity & ERR_MASK) < ERR_FATAL &&
4818 istk && istk->conds &&
4819 ((severity & ERR_PP_PRECOND) ?
4820 istk->conds->state == COND_NEVER :
4821 !emitting(istk->conds->state)))
4822 return;
4824 /* get %macro name */
4825 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4826 mmac = istk->mstk;
4827 /* but %rep blocks should be skipped */
4828 while (mmac && !mmac->name)
4829 mmac = mmac->next_active, delta++;
4832 if (mmac) {
4833 vsnprintf(buff, sizeof(buff), fmt, arg);
4835 nasm_set_verror(real_verror);
4836 nasm_error(severity, "(%s:%d) %s",
4837 mmac->name, mmac->lineno - delta, buff);
4838 nasm_set_verror(pp_verror);
4839 } else {
4840 real_verror(severity, fmt, arg);
4844 static void
4845 pp_reset(char *file, int apass, StrList **deplist)
4847 Token *t;
4849 cstk = NULL;
4850 istk = nasm_malloc(sizeof(Include));
4851 istk->next = NULL;
4852 istk->conds = NULL;
4853 istk->expansion = NULL;
4854 istk->mstk = NULL;
4855 istk->fp = fopen(file, "r");
4856 istk->fname = NULL;
4857 src_set(0, file);
4858 istk->lineinc = 1;
4859 if (!istk->fp)
4860 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4861 defining = NULL;
4862 nested_mac_count = 0;
4863 nested_rep_count = 0;
4864 init_macros();
4865 unique = 0;
4866 if (tasm_compatible_mode) {
4867 stdmacpos = nasm_stdmac;
4868 } else {
4869 stdmacpos = nasm_stdmac_after_tasm;
4871 any_extrastdmac = extrastdmac && *extrastdmac;
4872 do_predef = true;
4875 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4876 * The caller, however, will also pass in 3 for preprocess-only so
4877 * we can set __PASS__ accordingly.
4879 pass = apass > 2 ? 2 : apass;
4881 dephead = deptail = deplist;
4882 if (deplist) {
4883 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4884 sl->next = NULL;
4885 strcpy(sl->str, file);
4886 *deptail = sl;
4887 deptail = &sl->next;
4891 * Define the __PASS__ macro. This is defined here unlike
4892 * all the other builtins, because it is special -- it varies between
4893 * passes.
4895 t = nasm_malloc(sizeof(*t));
4896 t->next = NULL;
4897 make_tok_num(t, apass);
4898 t->a.mac = NULL;
4899 define_smacro(NULL, "__PASS__", true, 0, t);
4902 static char *pp_getline(void)
4904 char *line;
4905 Token *tline;
4907 real_verror = nasm_set_verror(pp_verror);
4909 while (1) {
4911 * Fetch a tokenized line, either from the macro-expansion
4912 * buffer or from the input file.
4914 tline = NULL;
4915 while (istk->expansion && istk->expansion->finishes) {
4916 Line *l = istk->expansion;
4917 if (!l->finishes->name && l->finishes->in_progress > 1) {
4918 Line *ll;
4921 * This is a macro-end marker for a macro with no
4922 * name, which means it's not really a macro at all
4923 * but a %rep block, and the `in_progress' field is
4924 * more than 1, meaning that we still need to
4925 * repeat. (1 means the natural last repetition; 0
4926 * means termination by %exitrep.) We have
4927 * therefore expanded up to the %endrep, and must
4928 * push the whole block on to the expansion buffer
4929 * again. We don't bother to remove the macro-end
4930 * marker: we'd only have to generate another one
4931 * if we did.
4933 l->finishes->in_progress--;
4934 list_for_each(l, l->finishes->expansion) {
4935 Token *t, *tt, **tail;
4937 ll = nasm_malloc(sizeof(Line));
4938 ll->next = istk->expansion;
4939 ll->finishes = NULL;
4940 ll->first = NULL;
4941 tail = &ll->first;
4943 list_for_each(t, l->first) {
4944 if (t->text || t->type == TOK_WHITESPACE) {
4945 tt = *tail = new_Token(NULL, t->type, t->text, 0);
4946 tail = &tt->next;
4950 istk->expansion = ll;
4952 } else {
4954 * Check whether a `%rep' was started and not ended
4955 * within this macro expansion. This can happen and
4956 * should be detected. It's a fatal error because
4957 * I'm too confused to work out how to recover
4958 * sensibly from it.
4960 if (defining) {
4961 if (defining->name)
4962 nasm_panic(0, "defining with name in expansion");
4963 else if (istk->mstk->name)
4964 nasm_fatal(0, "`%%rep' without `%%endrep' within"
4965 " expansion of macro `%s'",
4966 istk->mstk->name);
4970 * FIXME: investigate the relationship at this point between
4971 * istk->mstk and l->finishes
4974 MMacro *m = istk->mstk;
4975 istk->mstk = m->next_active;
4976 if (m->name) {
4978 * This was a real macro call, not a %rep, and
4979 * therefore the parameter information needs to
4980 * be freed.
4982 if (m->prev) {
4983 pop_mmacro(m);
4984 l->finishes->in_progress --;
4985 } else {
4986 nasm_free(m->params);
4987 free_tlist(m->iline);
4988 nasm_free(m->paramlen);
4989 l->finishes->in_progress = 0;
4991 } else
4992 free_mmacro(m);
4994 istk->expansion = l->next;
4995 nasm_free(l);
4996 lfmt->downlevel(LIST_MACRO);
4999 while (1) { /* until we get a line we can use */
5001 if (istk->expansion) { /* from a macro expansion */
5002 char *p;
5003 Line *l = istk->expansion;
5004 if (istk->mstk)
5005 istk->mstk->lineno++;
5006 tline = l->first;
5007 istk->expansion = l->next;
5008 nasm_free(l);
5009 p = detoken(tline, false);
5010 lfmt->line(LIST_MACRO, p);
5011 nasm_free(p);
5012 break;
5014 line = read_line();
5015 if (line) { /* from the current input file */
5016 line = prepreproc(line);
5017 tline = tokenize(line);
5018 nasm_free(line);
5019 break;
5022 * The current file has ended; work down the istk
5025 Include *i = istk;
5026 fclose(i->fp);
5027 if (i->conds) {
5028 /* nasm_error can't be conditionally suppressed */
5029 nasm_fatal(0,
5030 "expected `%%endif' before end of file");
5032 /* only set line and file name if there's a next node */
5033 if (i->next)
5034 src_set(i->lineno, i->fname);
5035 istk = i->next;
5036 lfmt->downlevel(LIST_INCLUDE);
5037 nasm_free(i);
5038 if (!istk) {
5039 line = NULL;
5040 goto done;
5042 if (istk->expansion && istk->expansion->finishes)
5043 break;
5048 * We must expand MMacro parameters and MMacro-local labels
5049 * _before_ we plunge into directive processing, to cope
5050 * with things like `%define something %1' such as STRUC
5051 * uses. Unless we're _defining_ a MMacro, in which case
5052 * those tokens should be left alone to go into the
5053 * definition; and unless we're in a non-emitting
5054 * condition, in which case we don't want to meddle with
5055 * anything.
5057 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5058 && !(istk->mstk && !istk->mstk->in_progress)) {
5059 tline = expand_mmac_params(tline);
5063 * Check the line to see if it's a preprocessor directive.
5065 if (do_directive(tline) == DIRECTIVE_FOUND) {
5066 continue;
5067 } else if (defining) {
5069 * We're defining a multi-line macro. We emit nothing
5070 * at all, and just
5071 * shove the tokenized line on to the macro definition.
5073 Line *l = nasm_malloc(sizeof(Line));
5074 l->next = defining->expansion;
5075 l->first = tline;
5076 l->finishes = NULL;
5077 defining->expansion = l;
5078 continue;
5079 } else if (istk->conds && !emitting(istk->conds->state)) {
5081 * We're in a non-emitting branch of a condition block.
5082 * Emit nothing at all, not even a blank line: when we
5083 * emerge from the condition we'll give a line-number
5084 * directive so we keep our place correctly.
5086 free_tlist(tline);
5087 continue;
5088 } else if (istk->mstk && !istk->mstk->in_progress) {
5090 * We're in a %rep block which has been terminated, so
5091 * we're walking through to the %endrep without
5092 * emitting anything. Emit nothing at all, not even a
5093 * blank line: when we emerge from the %rep block we'll
5094 * give a line-number directive so we keep our place
5095 * correctly.
5097 free_tlist(tline);
5098 continue;
5099 } else {
5100 tline = expand_smacro(tline);
5101 if (!expand_mmacro(tline)) {
5103 * De-tokenize the line again, and emit it.
5105 line = detoken(tline, true);
5106 free_tlist(tline);
5107 break;
5108 } else {
5109 continue; /* expand_mmacro calls free_tlist */
5114 done:
5115 nasm_set_verror(real_verror);
5116 return line;
5119 static void pp_cleanup(int pass)
5121 real_verror = nasm_set_verror(pp_verror);
5123 if (defining) {
5124 if (defining->name) {
5125 nasm_error(ERR_NONFATAL,
5126 "end of file while still defining macro `%s'",
5127 defining->name);
5128 } else {
5129 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5132 free_mmacro(defining);
5133 defining = NULL;
5136 nasm_set_verror(real_verror);
5138 while (cstk)
5139 ctx_pop();
5140 free_macros();
5141 while (istk) {
5142 Include *i = istk;
5143 istk = istk->next;
5144 fclose(i->fp);
5145 nasm_free(i);
5147 while (cstk)
5148 ctx_pop();
5149 src_set_fname(NULL);
5150 if (pass == 0) {
5151 IncPath *i;
5152 free_llist(predef);
5153 predef = NULL;
5154 delete_Blocks();
5155 freeTokens = NULL;
5156 while ((i = ipath)) {
5157 ipath = i->next;
5158 if (i->path)
5159 nasm_free(i->path);
5160 nasm_free(i);
5165 static void pp_include_path(char *path)
5167 IncPath *i;
5169 i = nasm_malloc(sizeof(IncPath));
5170 i->path = path ? nasm_strdup(path) : NULL;
5171 i->next = NULL;
5173 if (ipath) {
5174 IncPath *j = ipath;
5175 while (j->next)
5176 j = j->next;
5177 j->next = i;
5178 } else {
5179 ipath = i;
5183 static void pp_pre_include(char *fname)
5185 Token *inc, *space, *name;
5186 Line *l;
5188 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5189 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5190 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5192 l = nasm_malloc(sizeof(Line));
5193 l->next = predef;
5194 l->first = inc;
5195 l->finishes = NULL;
5196 predef = l;
5199 static void pp_pre_define(char *definition)
5201 Token *def, *space;
5202 Line *l;
5203 char *equals;
5205 real_verror = nasm_set_verror(pp_verror);
5207 equals = strchr(definition, '=');
5208 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5209 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5210 if (equals)
5211 *equals = ' ';
5212 space->next = tokenize(definition);
5213 if (equals)
5214 *equals = '=';
5216 if (space->next->type != TOK_PREPROC_ID &&
5217 space->next->type != TOK_ID)
5218 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5220 l = nasm_malloc(sizeof(Line));
5221 l->next = predef;
5222 l->first = def;
5223 l->finishes = NULL;
5224 predef = l;
5226 nasm_set_verror(real_verror);
5229 static void pp_pre_undefine(char *definition)
5231 Token *def, *space;
5232 Line *l;
5234 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5235 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5236 space->next = tokenize(definition);
5238 l = nasm_malloc(sizeof(Line));
5239 l->next = predef;
5240 l->first = def;
5241 l->finishes = NULL;
5242 predef = l;
5245 static void pp_extra_stdmac(macros_t *macros)
5247 extrastdmac = macros;
5250 static void make_tok_num(Token * tok, int64_t val)
5252 char numbuf[32];
5253 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5254 tok->text = nasm_strdup(numbuf);
5255 tok->type = TOK_NUMBER;
5258 static void pp_list_one_macro(MMacro *m, int severity)
5260 if (!m)
5261 return;
5263 /* We need to print the next_active list in reverse order */
5264 pp_list_one_macro(m->next_active, severity);
5266 if (m->name && !m->nolist) {
5267 src_set(m->xline + m->lineno, m->fname);
5268 nasm_error(severity, "... from macro `%s' defined here", m->name);
5272 static void pp_error_list_macros(int severity)
5274 int32_t saved_line;
5275 const char *saved_fname = NULL;
5277 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5278 src_get(&saved_line, &saved_fname);
5280 if (istk)
5281 pp_list_one_macro(istk->mstk, severity);
5283 src_set(saved_line, saved_fname);
5286 const struct preproc_ops nasmpp = {
5287 pp_reset,
5288 pp_getline,
5289 pp_cleanup,
5290 pp_extra_stdmac,
5291 pp_pre_define,
5292 pp_pre_undefine,
5293 pp_pre_include,
5294 pp_include_path,
5295 pp_error_list_macros,