BR3028880: Revert to nonfatal, better error message, cleanup
[nasm/sigaren-mirror.git] / preproc.c
blobcc5034f355590bc87bf93e6092aad585024cb1a6
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2010 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"
84 typedef struct SMacro SMacro;
85 typedef struct MMacro MMacro;
86 typedef struct MMacroInvocation MMacroInvocation;
87 typedef struct Context Context;
88 typedef struct Token Token;
89 typedef struct Blocks Blocks;
90 typedef struct Line Line;
91 typedef struct Include Include;
92 typedef struct Cond Cond;
93 typedef struct IncPath IncPath;
96 * Note on the storage of both SMacro and MMacros: the hash table
97 * indexes them case-insensitively, and we then have to go through a
98 * linked list of potential case aliases (and, for MMacros, parameter
99 * ranges); this is to preserve the matching semantics of the earlier
100 * code. If the number of case aliases for a specific macro is a
101 * performance issue, you may want to reconsider your coding style.
105 * Store the definition of a single-line macro.
107 struct SMacro {
108 SMacro *next;
109 char *name;
110 bool casesense;
111 bool in_progress;
112 unsigned int nparam;
113 Token *expansion;
117 * Store the definition of a multi-line macro. This is also used to
118 * store the interiors of `%rep...%endrep' blocks, which are
119 * effectively self-re-invoking multi-line macros which simply
120 * don't have a name or bother to appear in the hash tables. %rep
121 * blocks are signified by having a NULL `name' field.
123 * In a MMacro describing a `%rep' block, the `in_progress' field
124 * isn't merely boolean, but gives the number of repeats left to
125 * run.
127 * The `next' field is used for storing MMacros in hash tables; the
128 * `next_active' field is for stacking them on istk entries.
130 * When a MMacro is being expanded, `params', `iline', `nparam',
131 * `paramlen', `rotate' and `unique' are local to the invocation.
133 struct MMacro {
134 MMacro *next;
135 MMacroInvocation *prev; /* previous invocation */
136 char *name;
137 int nparam_min, nparam_max;
138 bool casesense;
139 bool plus; /* is the last parameter greedy? */
140 bool nolist; /* is this macro listing-inhibited? */
141 int64_t in_progress; /* is this macro currently being expanded? */
142 int32_t max_depth; /* maximum number of recursive expansions allowed */
143 Token *dlist; /* All defaults as one list */
144 Token **defaults; /* Parameter default pointers */
145 int ndefs; /* number of default parameters */
146 Line *expansion;
148 MMacro *next_active;
149 MMacro *rep_nest; /* used for nesting %rep */
150 Token **params; /* actual parameters */
151 Token *iline; /* invocation line */
152 unsigned int nparam, rotate;
153 int *paramlen;
154 uint64_t unique;
155 int lineno; /* Current line number on expansion */
156 uint64_t condcnt; /* number of if blocks... */
160 /* Store the definition of a multi-line macro, as defined in a
161 * previous recursive macro expansion.
163 struct MMacroInvocation {
164 MMacroInvocation *prev; /* previous invocation */
165 Token **params; /* actual parameters */
166 Token *iline; /* invocation line */
167 unsigned int nparam, rotate;
168 int *paramlen;
169 uint64_t unique;
170 uint64_t condcnt;
175 * The context stack is composed of a linked list of these.
177 struct Context {
178 Context *next;
179 char *name;
180 struct hash_table localmac;
181 uint32_t number;
185 * This is the internal form which we break input lines up into.
186 * Typically stored in linked lists.
188 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
189 * necessarily used as-is, but is intended to denote the number of
190 * the substituted parameter. So in the definition
192 * %define a(x,y) ( (x) & ~(y) )
194 * the token representing `x' will have its type changed to
195 * TOK_SMAC_PARAM, but the one representing `y' will be
196 * TOK_SMAC_PARAM+1.
198 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
199 * which doesn't need quotes around it. Used in the pre-include
200 * mechanism as an alternative to trying to find a sensible type of
201 * quote to use on the filename we were passed.
203 enum pp_token_type {
204 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
205 TOK_PREPROC_ID, TOK_STRING,
206 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
207 TOK_INTERNAL_STRING,
208 TOK_PREPROC_Q, TOK_PREPROC_QQ,
209 TOK_PASTE, /* %+ */
210 TOK_INDIRECT, /* %[...] */
211 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
212 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
215 struct Token {
216 Token *next;
217 char *text;
218 union {
219 SMacro *mac; /* associated macro for TOK_SMAC_END */
220 size_t len; /* scratch length field */
221 } a; /* Auxiliary data */
222 enum pp_token_type type;
226 * Multi-line macro definitions are stored as a linked list of
227 * these, which is essentially a container to allow several linked
228 * lists of Tokens.
230 * Note that in this module, linked lists are treated as stacks
231 * wherever possible. For this reason, Lines are _pushed_ on to the
232 * `expansion' field in MMacro structures, so that the linked list,
233 * if walked, would give the macro lines in reverse order; this
234 * means that we can walk the list when expanding a macro, and thus
235 * push the lines on to the `expansion' field in _istk_ in reverse
236 * order (so that when popped back off they are in the right
237 * order). It may seem cockeyed, and it relies on my design having
238 * an even number of steps in, but it works...
240 * Some of these structures, rather than being actual lines, are
241 * markers delimiting the end of the expansion of a given macro.
242 * This is for use in the cycle-tracking and %rep-handling code.
243 * Such structures have `finishes' non-NULL, and `first' NULL. All
244 * others have `finishes' NULL, but `first' may still be NULL if
245 * the line is blank.
247 struct Line {
248 Line *next;
249 MMacro *finishes;
250 Token *first;
254 * To handle an arbitrary level of file inclusion, we maintain a
255 * stack (ie linked list) of these things.
257 struct Include {
258 Include *next;
259 FILE *fp;
260 Cond *conds;
261 Line *expansion;
262 char *fname;
263 int lineno, lineinc;
264 MMacro *mstk; /* stack of active macros/reps */
268 * Include search path. This is simply a list of strings which get
269 * prepended, in turn, to the name of an include file, in an
270 * attempt to find the file if it's not in the current directory.
272 struct IncPath {
273 IncPath *next;
274 char *path;
278 * Conditional assembly: we maintain a separate stack of these for
279 * each level of file inclusion. (The only reason we keep the
280 * stacks separate is to ensure that a stray `%endif' in a file
281 * included from within the true branch of a `%if' won't terminate
282 * it and cause confusion: instead, rightly, it'll cause an error.)
284 struct Cond {
285 Cond *next;
286 int state;
288 enum {
290 * These states are for use just after %if or %elif: IF_TRUE
291 * means the condition has evaluated to truth so we are
292 * currently emitting, whereas IF_FALSE means we are not
293 * currently emitting but will start doing so if a %else comes
294 * up. In these states, all directives are admissible: %elif,
295 * %else and %endif. (And of course %if.)
297 COND_IF_TRUE, COND_IF_FALSE,
299 * These states come up after a %else: ELSE_TRUE means we're
300 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
301 * any %elif or %else will cause an error.
303 COND_ELSE_TRUE, COND_ELSE_FALSE,
305 * These states mean that we're not emitting now, and also that
306 * nothing until %endif will be emitted at all. COND_DONE is
307 * used when we've had our moment of emission
308 * and have now started seeing %elifs. COND_NEVER is used when
309 * the condition construct in question is contained within a
310 * non-emitting branch of a larger condition construct,
311 * or if there is an error.
313 COND_DONE, COND_NEVER
315 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
318 * These defines are used as the possible return values for do_directive
320 #define NO_DIRECTIVE_FOUND 0
321 #define DIRECTIVE_FOUND 1
324 * This define sets the upper limit for smacro and recursive mmacro
325 * expansions
327 #define DEADMAN_LIMIT (1 << 20)
330 * Condition codes. Note that we use c_ prefix not C_ because C_ is
331 * used in nasm.h for the "real" condition codes. At _this_ level,
332 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
333 * ones, so we need a different enum...
335 static const char * const conditions[] = {
336 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
337 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
338 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
340 enum pp_conds {
341 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
342 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
343 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
344 c_none = -1
346 static const enum pp_conds inverse_ccs[] = {
347 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
348 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,
349 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
353 * Directive names.
355 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
356 static int is_condition(enum preproc_token arg)
358 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
361 /* For TASM compatibility we need to be able to recognise TASM compatible
362 * conditional compilation directives. Using the NASM pre-processor does
363 * not work, so we look for them specifically from the following list and
364 * then jam in the equivalent NASM directive into the input stream.
367 enum {
368 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
369 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
372 static const char * const tasm_directives[] = {
373 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
374 "ifndef", "include", "local"
377 static int StackSize = 4;
378 static char *StackPointer = "ebp";
379 static int ArgOffset = 8;
380 static int LocalOffset = 0;
382 static Context *cstk;
383 static Include *istk;
384 static IncPath *ipath = NULL;
386 static int pass; /* HACK: pass 0 = generate dependencies only */
387 static StrList **dephead, **deptail; /* Dependency list */
389 static uint64_t unique; /* unique identifier numbers */
391 static Line *predef = NULL;
392 static bool do_predef;
394 static ListGen *list;
397 * The current set of multi-line macros we have defined.
399 static struct hash_table mmacros;
402 * The current set of single-line macros we have defined.
404 static struct hash_table smacros;
407 * The multi-line macro we are currently defining, or the %rep
408 * block we are currently reading, if any.
410 static MMacro *defining;
412 static uint64_t nested_mac_count;
413 static uint64_t nested_rep_count;
416 * The number of macro parameters to allocate space for at a time.
418 #define PARAM_DELTA 16
421 * The standard macro set: defined in macros.c in the array nasm_stdmac.
422 * This gives our position in the macro set, when we're processing it.
424 static macros_t *stdmacpos;
427 * The extra standard macros that come from the object format, if
428 * any.
430 static macros_t *extrastdmac = NULL;
431 static bool any_extrastdmac;
434 * Tokens are allocated in blocks to improve speed
436 #define TOKEN_BLOCKSIZE 4096
437 static Token *freeTokens = NULL;
438 struct Blocks {
439 Blocks *next;
440 void *chunk;
443 static Blocks blocks = { NULL, NULL };
446 * Forward declarations.
448 static Token *expand_mmac_params(Token * tline);
449 static Token *expand_smacro(Token * tline);
450 static Token *expand_id(Token * tline);
451 static Context *get_ctx(const char *name, const char **namep,
452 bool all_contexts);
453 static void make_tok_num(Token * tok, int64_t val);
454 static void error(int severity, const char *fmt, ...);
455 static void error_precond(int severity, const char *fmt, ...);
456 static void *new_Block(size_t size);
457 static void delete_Blocks(void);
458 static Token *new_Token(Token * next, enum pp_token_type type,
459 const char *text, int txtlen);
460 static Token *delete_Token(Token * t);
463 * Macros for safe checking of token pointers, avoid *(NULL)
465 #define tok_type_(x,t) ((x) && (x)->type == (t))
466 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
467 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
468 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
471 * Handle TASM specific directives, which do not contain a % in
472 * front of them. We do it here because I could not find any other
473 * place to do it for the moment, and it is a hack (ideally it would
474 * be nice to be able to use the NASM pre-processor to do it).
476 static char *check_tasm_directive(char *line)
478 int32_t i, j, k, m, len;
479 char *p, *q, *oldline, oldchar;
481 p = nasm_skip_spaces(line);
483 /* Binary search for the directive name */
484 i = -1;
485 j = ARRAY_SIZE(tasm_directives);
486 q = nasm_skip_word(p);
487 len = q - p;
488 if (len) {
489 oldchar = p[len];
490 p[len] = 0;
491 while (j - i > 1) {
492 k = (j + i) / 2;
493 m = nasm_stricmp(p, tasm_directives[k]);
494 if (m == 0) {
495 /* We have found a directive, so jam a % in front of it
496 * so that NASM will then recognise it as one if it's own.
498 p[len] = oldchar;
499 len = strlen(p);
500 oldline = line;
501 line = nasm_malloc(len + 2);
502 line[0] = '%';
503 if (k == TM_IFDIFI) {
505 * NASM does not recognise IFDIFI, so we convert
506 * it to %if 0. This is not used in NASM
507 * compatible code, but does need to parse for the
508 * TASM macro package.
510 strcpy(line + 1, "if 0");
511 } else {
512 memcpy(line + 1, p, len + 1);
514 nasm_free(oldline);
515 return line;
516 } else if (m < 0) {
517 j = k;
518 } else
519 i = k;
521 p[len] = oldchar;
523 return line;
527 * The pre-preprocessing stage... This function translates line
528 * number indications as they emerge from GNU cpp (`# lineno "file"
529 * flags') into NASM preprocessor line number indications (`%line
530 * lineno file').
532 static char *prepreproc(char *line)
534 int lineno, fnlen;
535 char *fname, *oldline;
537 if (line[0] == '#' && line[1] == ' ') {
538 oldline = line;
539 fname = oldline + 2;
540 lineno = atoi(fname);
541 fname += strspn(fname, "0123456789 ");
542 if (*fname == '"')
543 fname++;
544 fnlen = strcspn(fname, "\"");
545 line = nasm_malloc(20 + fnlen);
546 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
547 nasm_free(oldline);
549 if (tasm_compatible_mode)
550 return check_tasm_directive(line);
551 return line;
555 * Free a linked list of tokens.
557 static void free_tlist(Token * list)
559 while (list)
560 list = delete_Token(list);
564 * Free a linked list of lines.
566 static void free_llist(Line * list)
568 Line *l, *tmp;
569 list_for_each_safe(l, tmp, list) {
570 free_tlist(l->first);
571 nasm_free(l);
576 * Free an MMacro
578 static void free_mmacro(MMacro * m)
580 nasm_free(m->name);
581 free_tlist(m->dlist);
582 nasm_free(m->defaults);
583 free_llist(m->expansion);
584 nasm_free(m);
588 * Free all currently defined macros, and free the hash tables
590 static void free_smacro_table(struct hash_table *smt)
592 SMacro *s, *tmp;
593 const char *key;
594 struct hash_tbl_node *it = NULL;
596 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
597 nasm_free((void *)key);
598 list_for_each_safe(s, tmp, s) {
599 nasm_free(s->name);
600 free_tlist(s->expansion);
601 nasm_free(s);
604 hash_free(smt);
607 static void free_mmacro_table(struct hash_table *mmt)
609 MMacro *m, *tmp;
610 const char *key;
611 struct hash_tbl_node *it = NULL;
613 it = NULL;
614 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
615 nasm_free((void *)key);
616 list_for_each_safe(m ,tmp, m)
617 free_mmacro(m);
619 hash_free(mmt);
622 static void free_macros(void)
624 free_smacro_table(&smacros);
625 free_mmacro_table(&mmacros);
629 * Initialize the hash tables
631 static void init_macros(void)
633 hash_init(&smacros, HASH_LARGE);
634 hash_init(&mmacros, HASH_LARGE);
638 * Pop the context stack.
640 static void ctx_pop(void)
642 Context *c = cstk;
644 cstk = cstk->next;
645 free_smacro_table(&c->localmac);
646 nasm_free(c->name);
647 nasm_free(c);
651 * Search for a key in the hash index; adding it if necessary
652 * (in which case we initialize the data pointer to NULL.)
654 static void **
655 hash_findi_add(struct hash_table *hash, const char *str)
657 struct hash_insert hi;
658 void **r;
659 char *strx;
661 r = hash_findi(hash, str, &hi);
662 if (r)
663 return r;
665 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
666 return hash_add(&hi, strx, NULL);
670 * Like hash_findi, but returns the data element rather than a pointer
671 * to it. Used only when not adding a new element, hence no third
672 * argument.
674 static void *
675 hash_findix(struct hash_table *hash, const char *str)
677 void **p;
679 p = hash_findi(hash, str, NULL);
680 return p ? *p : NULL;
684 * read line from standart macros set,
685 * if there no more left -- return NULL
687 static char *line_from_stdmac(void)
689 unsigned char c;
690 const unsigned char *p = stdmacpos;
691 char *line, *q;
692 size_t len = 0;
694 if (!stdmacpos)
695 return NULL;
697 while ((c = *p++)) {
698 if (c >= 0x80)
699 len += pp_directives_len[c - 0x80] + 1;
700 else
701 len++;
704 line = nasm_malloc(len + 1);
705 q = line;
706 while ((c = *stdmacpos++)) {
707 if (c >= 0x80) {
708 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
709 q += pp_directives_len[c - 0x80];
710 *q++ = ' ';
711 } else {
712 *q++ = c;
715 stdmacpos = p;
716 *q = '\0';
718 if (!*stdmacpos) {
719 /* This was the last of the standard macro chain... */
720 stdmacpos = NULL;
721 if (any_extrastdmac) {
722 stdmacpos = extrastdmac;
723 any_extrastdmac = false;
724 } else if (do_predef) {
725 Line *pd, *l;
726 Token *head, **tail, *t;
729 * Nasty hack: here we push the contents of
730 * `predef' on to the top-level expansion stack,
731 * since this is the most convenient way to
732 * implement the pre-include and pre-define
733 * features.
735 list_for_each(pd, predef) {
736 head = NULL;
737 tail = &head;
738 list_for_each(t, pd->first) {
739 *tail = new_Token(NULL, t->type, t->text, 0);
740 tail = &(*tail)->next;
743 l = nasm_malloc(sizeof(Line));
744 l->next = istk->expansion;
745 l->first = head;
746 l->finishes = NULL;
748 istk->expansion = l;
750 do_predef = false;
754 return line;
757 #define BUF_DELTA 512
759 * Read a line from the top file in istk, handling multiple CR/LFs
760 * at the end of the line read, and handling spurious ^Zs. Will
761 * return lines from the standard macro set if this has not already
762 * been done.
764 static char *read_line(void)
766 char *buffer, *p, *q;
767 int bufsize, continued_count;
770 * standart macros set (predefined) goes first
772 p = line_from_stdmac();
773 if (p)
774 return p;
777 * regular read from a file
779 bufsize = BUF_DELTA;
780 buffer = nasm_malloc(BUF_DELTA);
781 p = buffer;
782 continued_count = 0;
783 while (1) {
784 q = fgets(p, bufsize - (p - buffer), istk->fp);
785 if (!q)
786 break;
787 p += strlen(p);
788 if (p > buffer && p[-1] == '\n') {
790 * Convert backslash-CRLF line continuation sequences into
791 * nothing at all (for DOS and Windows)
793 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
794 p -= 3;
795 *p = 0;
796 continued_count++;
799 * Also convert backslash-LF line continuation sequences into
800 * nothing at all (for Unix)
802 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
803 p -= 2;
804 *p = 0;
805 continued_count++;
806 } else {
807 break;
810 if (p - buffer > bufsize - 10) {
811 int32_t offset = p - buffer;
812 bufsize += BUF_DELTA;
813 buffer = nasm_realloc(buffer, bufsize);
814 p = buffer + offset; /* prevent stale-pointer problems */
818 if (!q && p == buffer) {
819 nasm_free(buffer);
820 return NULL;
823 src_set_linnum(src_get_linnum() + istk->lineinc +
824 (continued_count * istk->lineinc));
827 * Play safe: remove CRs as well as LFs, if any of either are
828 * present at the end of the line.
830 while (--p >= buffer && (*p == '\n' || *p == '\r'))
831 *p = '\0';
834 * Handle spurious ^Z, which may be inserted into source files
835 * by some file transfer utilities.
837 buffer[strcspn(buffer, "\032")] = '\0';
839 list->line(LIST_READ, buffer);
841 return buffer;
845 * Tokenize a line of text. This is a very simple process since we
846 * don't need to parse the value out of e.g. numeric tokens: we
847 * simply split one string into many.
849 static Token *tokenize(char *line)
851 char c, *p = line;
852 enum pp_token_type type;
853 Token *list = NULL;
854 Token *t, **tail = &list;
856 while (*line) {
857 p = line;
858 if (*p == '%') {
859 p++;
860 if (*p == '+' && !nasm_isdigit(p[1])) {
861 p++;
862 type = TOK_PASTE;
863 } else if (nasm_isdigit(*p) ||
864 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
865 do {
866 p++;
868 while (nasm_isdigit(*p));
869 type = TOK_PREPROC_ID;
870 } else if (*p == '{') {
871 p++;
872 while (*p && *p != '}') {
873 p[-1] = *p;
874 p++;
876 p[-1] = '\0';
877 if (*p)
878 p++;
879 type = TOK_PREPROC_ID;
880 } else if (*p == '[') {
881 int lvl = 1;
882 line += 2; /* Skip the leading %[ */
883 p++;
884 while (lvl && (c = *p++)) {
885 switch (c) {
886 case ']':
887 lvl--;
888 break;
889 case '%':
890 if (*p == '[')
891 lvl++;
892 break;
893 case '\'':
894 case '\"':
895 case '`':
896 p = nasm_skip_string(p - 1) + 1;
897 break;
898 default:
899 break;
902 p--;
903 if (*p)
904 *p++ = '\0';
905 if (lvl)
906 error(ERR_NONFATAL, "unterminated %[ construct");
907 type = TOK_INDIRECT;
908 } else if (*p == '?') {
909 type = TOK_PREPROC_Q; /* %? */
910 p++;
911 if (*p == '?') {
912 type = TOK_PREPROC_QQ; /* %?? */
913 p++;
915 } else if (isidchar(*p) ||
916 ((*p == '!' || *p == '%' || *p == '$') &&
917 isidchar(p[1]))) {
918 do {
919 p++;
921 while (isidchar(*p));
922 type = TOK_PREPROC_ID;
923 } else {
924 type = TOK_OTHER;
925 if (*p == '%')
926 p++;
928 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
929 type = TOK_ID;
930 p++;
931 while (*p && isidchar(*p))
932 p++;
933 } else if (*p == '\'' || *p == '"' || *p == '`') {
935 * A string token.
937 type = TOK_STRING;
938 p = nasm_skip_string(p);
940 if (*p) {
941 p++;
942 } else {
943 error(ERR_WARNING|ERR_PASS1, "unterminated string");
944 /* Handling unterminated strings by UNV */
945 /* type = -1; */
947 } else if (p[0] == '$' && p[1] == '$') {
948 type = TOK_OTHER; /* TOKEN_BASE */
949 p += 2;
950 } else if (isnumstart(*p)) {
951 bool is_hex = false;
952 bool is_float = false;
953 bool has_e = false;
954 char c, *r;
957 * A numeric token.
960 if (*p == '$') {
961 p++;
962 is_hex = true;
965 for (;;) {
966 c = *p++;
968 if (!is_hex && (c == 'e' || c == 'E')) {
969 has_e = true;
970 if (*p == '+' || *p == '-') {
972 * e can only be followed by +/- if it is either a
973 * prefixed hex number or a floating-point number
975 p++;
976 is_float = true;
978 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
979 is_hex = true;
980 } else if (c == 'P' || c == 'p') {
981 is_float = true;
982 if (*p == '+' || *p == '-')
983 p++;
984 } else if (isnumchar(c) || c == '_')
985 ; /* just advance */
986 else if (c == '.') {
988 * we need to deal with consequences of the legacy
989 * parser, like "1.nolist" being two tokens
990 * (TOK_NUMBER, TOK_ID) here; at least give it
991 * a shot for now. In the future, we probably need
992 * a flex-based scanner with proper pattern matching
993 * to do it as well as it can be done. Nothing in
994 * the world is going to help the person who wants
995 * 0x123.p16 interpreted as two tokens, though.
997 r = p;
998 while (*r == '_')
999 r++;
1001 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1002 (!is_hex && (*r == 'e' || *r == 'E')) ||
1003 (*r == 'p' || *r == 'P')) {
1004 p = r;
1005 is_float = true;
1006 } else
1007 break; /* Terminate the token */
1008 } else
1009 break;
1011 p--; /* Point to first character beyond number */
1013 if (p == line+1 && *line == '$') {
1014 type = TOK_OTHER; /* TOKEN_HERE */
1015 } else {
1016 if (has_e && !is_hex) {
1017 /* 1e13 is floating-point, but 1e13h is not */
1018 is_float = true;
1021 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1023 } else if (nasm_isspace(*p)) {
1024 type = TOK_WHITESPACE;
1025 p = nasm_skip_spaces(p);
1027 * Whitespace just before end-of-line is discarded by
1028 * pretending it's a comment; whitespace just before a
1029 * comment gets lumped into the comment.
1031 if (!*p || *p == ';') {
1032 type = TOK_COMMENT;
1033 while (*p)
1034 p++;
1036 } else if (*p == ';') {
1037 type = TOK_COMMENT;
1038 while (*p)
1039 p++;
1040 } else {
1042 * Anything else is an operator of some kind. We check
1043 * for all the double-character operators (>>, <<, //,
1044 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1045 * else is a single-character operator.
1047 type = TOK_OTHER;
1048 if ((p[0] == '>' && p[1] == '>') ||
1049 (p[0] == '<' && p[1] == '<') ||
1050 (p[0] == '/' && p[1] == '/') ||
1051 (p[0] == '<' && p[1] == '=') ||
1052 (p[0] == '>' && p[1] == '=') ||
1053 (p[0] == '=' && p[1] == '=') ||
1054 (p[0] == '!' && p[1] == '=') ||
1055 (p[0] == '<' && p[1] == '>') ||
1056 (p[0] == '&' && p[1] == '&') ||
1057 (p[0] == '|' && p[1] == '|') ||
1058 (p[0] == '^' && p[1] == '^')) {
1059 p++;
1061 p++;
1064 /* Handling unterminated string by UNV */
1065 /*if (type == -1)
1067 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1068 t->text[p-line] = *line;
1069 tail = &t->next;
1071 else */
1072 if (type != TOK_COMMENT) {
1073 *tail = t = new_Token(NULL, type, line, p - line);
1074 tail = &t->next;
1076 line = p;
1078 return list;
1082 * this function allocates a new managed block of memory and
1083 * returns a pointer to the block. The managed blocks are
1084 * deleted only all at once by the delete_Blocks function.
1086 static void *new_Block(size_t size)
1088 Blocks *b = &blocks;
1090 /* first, get to the end of the linked list */
1091 while (b->next)
1092 b = b->next;
1093 /* now allocate the requested chunk */
1094 b->chunk = nasm_malloc(size);
1096 /* now allocate a new block for the next request */
1097 b->next = nasm_malloc(sizeof(Blocks));
1098 /* and initialize the contents of the new block */
1099 b->next->next = NULL;
1100 b->next->chunk = NULL;
1101 return b->chunk;
1105 * this function deletes all managed blocks of memory
1107 static void delete_Blocks(void)
1109 Blocks *a, *b = &blocks;
1112 * keep in mind that the first block, pointed to by blocks
1113 * is a static and not dynamically allocated, so we don't
1114 * free it.
1116 while (b) {
1117 if (b->chunk)
1118 nasm_free(b->chunk);
1119 a = b;
1120 b = b->next;
1121 if (a != &blocks)
1122 nasm_free(a);
1127 * this function creates a new Token and passes a pointer to it
1128 * back to the caller. It sets the type and text elements, and
1129 * also the a.mac and next elements to NULL.
1131 static Token *new_Token(Token * next, enum pp_token_type type,
1132 const char *text, int txtlen)
1134 Token *t;
1135 int i;
1137 if (!freeTokens) {
1138 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1139 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1140 freeTokens[i].next = &freeTokens[i + 1];
1141 freeTokens[i].next = NULL;
1143 t = freeTokens;
1144 freeTokens = t->next;
1145 t->next = next;
1146 t->a.mac = NULL;
1147 t->type = type;
1148 if (type == TOK_WHITESPACE || !text) {
1149 t->text = NULL;
1150 } else {
1151 if (txtlen == 0)
1152 txtlen = strlen(text);
1153 t->text = nasm_malloc(txtlen+1);
1154 memcpy(t->text, text, txtlen);
1155 t->text[txtlen] = '\0';
1157 return t;
1160 static Token *delete_Token(Token * t)
1162 Token *next = t->next;
1163 nasm_free(t->text);
1164 t->next = freeTokens;
1165 freeTokens = t;
1166 return next;
1170 * Convert a line of tokens back into text.
1171 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1172 * will be transformed into ..@ctxnum.xxx
1174 static char *detoken(Token * tlist, bool expand_locals)
1176 Token *t;
1177 char *line, *p;
1178 const char *q;
1179 int len = 0;
1181 list_for_each(t, tlist) {
1182 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1183 char *p = getenv(t->text + 2);
1184 char *q = t->text;
1185 if (!p) {
1186 error(ERR_NONFATAL | ERR_PASS1,
1187 "nonexistent environment variable `%s'", q + 2);
1188 p = "";
1190 t->text = nasm_strdup(p);
1191 nasm_free(q);
1193 /* Expand local macros here and not during preprocessing */
1194 if (expand_locals &&
1195 t->type == TOK_PREPROC_ID && t->text &&
1196 t->text[0] == '%' && t->text[1] == '$') {
1197 const char *q;
1198 char *p;
1199 Context *ctx = get_ctx(t->text, &q, false);
1200 if (ctx) {
1201 char buffer[40];
1202 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1203 p = nasm_strcat(buffer, q);
1204 nasm_free(t->text);
1205 t->text = p;
1208 if (t->type == TOK_WHITESPACE)
1209 len++;
1210 else if (t->text)
1211 len += strlen(t->text);
1214 p = line = nasm_malloc(len + 1);
1216 list_for_each(t, tlist) {
1217 if (t->type == TOK_WHITESPACE) {
1218 *p++ = ' ';
1219 } else if (t->text) {
1220 q = t->text;
1221 while (*q)
1222 *p++ = *q++;
1225 *p = '\0';
1227 return line;
1231 * A scanner, suitable for use by the expression evaluator, which
1232 * operates on a line of Tokens. Expects a pointer to a pointer to
1233 * the first token in the line to be passed in as its private_data
1234 * field.
1236 * FIX: This really needs to be unified with stdscan.
1238 static int ppscan(void *private_data, struct tokenval *tokval)
1240 Token **tlineptr = private_data;
1241 Token *tline;
1242 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1244 do {
1245 tline = *tlineptr;
1246 *tlineptr = tline ? tline->next : NULL;
1247 } while (tline && (tline->type == TOK_WHITESPACE ||
1248 tline->type == TOK_COMMENT));
1250 if (!tline)
1251 return tokval->t_type = TOKEN_EOS;
1253 tokval->t_charptr = tline->text;
1255 if (tline->text[0] == '$' && !tline->text[1])
1256 return tokval->t_type = TOKEN_HERE;
1257 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1258 return tokval->t_type = TOKEN_BASE;
1260 if (tline->type == TOK_ID) {
1261 p = tokval->t_charptr = tline->text;
1262 if (p[0] == '$') {
1263 tokval->t_charptr++;
1264 return tokval->t_type = TOKEN_ID;
1267 for (r = p, s = ourcopy; *r; r++) {
1268 if (r >= p+MAX_KEYWORD)
1269 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1270 *s++ = nasm_tolower(*r);
1272 *s = '\0';
1273 /* right, so we have an identifier sitting in temp storage. now,
1274 * is it actually a register or instruction name, or what? */
1275 return nasm_token_hash(ourcopy, tokval);
1278 if (tline->type == TOK_NUMBER) {
1279 bool rn_error;
1280 tokval->t_integer = readnum(tline->text, &rn_error);
1281 tokval->t_charptr = tline->text;
1282 if (rn_error)
1283 return tokval->t_type = TOKEN_ERRNUM;
1284 else
1285 return tokval->t_type = TOKEN_NUM;
1288 if (tline->type == TOK_FLOAT) {
1289 return tokval->t_type = TOKEN_FLOAT;
1292 if (tline->type == TOK_STRING) {
1293 char bq, *ep;
1295 bq = tline->text[0];
1296 tokval->t_charptr = tline->text;
1297 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1299 if (ep[0] != bq || ep[1] != '\0')
1300 return tokval->t_type = TOKEN_ERRSTR;
1301 else
1302 return tokval->t_type = TOKEN_STR;
1305 if (tline->type == TOK_OTHER) {
1306 if (!strcmp(tline->text, "<<"))
1307 return tokval->t_type = TOKEN_SHL;
1308 if (!strcmp(tline->text, ">>"))
1309 return tokval->t_type = TOKEN_SHR;
1310 if (!strcmp(tline->text, "//"))
1311 return tokval->t_type = TOKEN_SDIV;
1312 if (!strcmp(tline->text, "%%"))
1313 return tokval->t_type = TOKEN_SMOD;
1314 if (!strcmp(tline->text, "=="))
1315 return tokval->t_type = TOKEN_EQ;
1316 if (!strcmp(tline->text, "<>"))
1317 return tokval->t_type = TOKEN_NE;
1318 if (!strcmp(tline->text, "!="))
1319 return tokval->t_type = TOKEN_NE;
1320 if (!strcmp(tline->text, "<="))
1321 return tokval->t_type = TOKEN_LE;
1322 if (!strcmp(tline->text, ">="))
1323 return tokval->t_type = TOKEN_GE;
1324 if (!strcmp(tline->text, "&&"))
1325 return tokval->t_type = TOKEN_DBL_AND;
1326 if (!strcmp(tline->text, "^^"))
1327 return tokval->t_type = TOKEN_DBL_XOR;
1328 if (!strcmp(tline->text, "||"))
1329 return tokval->t_type = TOKEN_DBL_OR;
1333 * We have no other options: just return the first character of
1334 * the token text.
1336 return tokval->t_type = tline->text[0];
1340 * Compare a string to the name of an existing macro; this is a
1341 * simple wrapper which calls either strcmp or nasm_stricmp
1342 * depending on the value of the `casesense' parameter.
1344 static int mstrcmp(const char *p, const char *q, bool casesense)
1346 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1350 * Compare a string to the name of an existing macro; this is a
1351 * simple wrapper which calls either strcmp or nasm_stricmp
1352 * depending on the value of the `casesense' parameter.
1354 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1356 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1360 * Return the Context structure associated with a %$ token. Return
1361 * NULL, having _already_ reported an error condition, if the
1362 * context stack isn't deep enough for the supplied number of $
1363 * signs.
1364 * If all_contexts == true, contexts that enclose current are
1365 * also scanned for such smacro, until it is found; if not -
1366 * only the context that directly results from the number of $'s
1367 * in variable's name.
1369 * If "namep" is non-NULL, set it to the pointer to the macro name
1370 * tail, i.e. the part beyond %$...
1372 static Context *get_ctx(const char *name, const char **namep,
1373 bool all_contexts)
1375 Context *ctx;
1376 SMacro *m;
1377 int i;
1379 if (namep)
1380 *namep = name;
1382 if (!name || name[0] != '%' || name[1] != '$')
1383 return NULL;
1385 if (!cstk) {
1386 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1387 return NULL;
1390 name += 2;
1391 ctx = cstk;
1392 i = 0;
1393 while (ctx && *name == '$') {
1394 name++;
1395 i++;
1396 ctx = ctx->next;
1398 if (!ctx) {
1399 error(ERR_NONFATAL, "`%s': context stack is only"
1400 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1401 return NULL;
1404 if (namep)
1405 *namep = name;
1407 if (!all_contexts)
1408 return ctx;
1410 do {
1411 /* Search for this smacro in found context */
1412 m = hash_findix(&ctx->localmac, name);
1413 while (m) {
1414 if (!mstrcmp(m->name, name, m->casesense))
1415 return ctx;
1416 m = m->next;
1418 ctx = ctx->next;
1420 while (ctx);
1421 return NULL;
1425 * Check to see if a file is already in a string list
1427 static bool in_list(const StrList *list, const char *str)
1429 while (list) {
1430 if (!strcmp(list->str, str))
1431 return true;
1432 list = list->next;
1434 return false;
1438 * Open an include file. This routine must always return a valid
1439 * file pointer if it returns - it's responsible for throwing an
1440 * ERR_FATAL and bombing out completely if not. It should also try
1441 * the include path one by one until it finds the file or reaches
1442 * the end of the path.
1444 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1445 bool missing_ok)
1447 FILE *fp;
1448 char *prefix = "";
1449 IncPath *ip = ipath;
1450 int len = strlen(file);
1451 size_t prefix_len = 0;
1452 StrList *sl;
1454 while (1) {
1455 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1456 memcpy(sl->str, prefix, prefix_len);
1457 memcpy(sl->str+prefix_len, file, len+1);
1458 fp = fopen(sl->str, "r");
1459 if (fp && dhead && !in_list(*dhead, sl->str)) {
1460 sl->next = NULL;
1461 **dtail = sl;
1462 *dtail = &sl->next;
1463 } else {
1464 nasm_free(sl);
1466 if (fp)
1467 return fp;
1468 if (!ip) {
1469 if (!missing_ok)
1470 break;
1471 prefix = NULL;
1472 } else {
1473 prefix = ip->path;
1474 ip = ip->next;
1476 if (prefix) {
1477 prefix_len = strlen(prefix);
1478 } else {
1479 /* -MG given and file not found */
1480 if (dhead && !in_list(*dhead, file)) {
1481 sl = nasm_malloc(len+1+sizeof sl->next);
1482 sl->next = NULL;
1483 strcpy(sl->str, file);
1484 **dtail = sl;
1485 *dtail = &sl->next;
1487 return NULL;
1491 error(ERR_FATAL, "unable to open include file `%s'", file);
1492 return NULL;
1496 * Determine if we should warn on defining a single-line macro of
1497 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1498 * return true if _any_ single-line macro of that name is defined.
1499 * Otherwise, will return true if a single-line macro with either
1500 * `nparam' or no parameters is defined.
1502 * If a macro with precisely the right number of parameters is
1503 * defined, or nparam is -1, the address of the definition structure
1504 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1505 * is NULL, no action will be taken regarding its contents, and no
1506 * error will occur.
1508 * Note that this is also called with nparam zero to resolve
1509 * `ifdef'.
1511 * If you already know which context macro belongs to, you can pass
1512 * the context pointer as first parameter; if you won't but name begins
1513 * with %$ the context will be automatically computed. If all_contexts
1514 * is true, macro will be searched in outer contexts as well.
1516 static bool
1517 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1518 bool nocase)
1520 struct hash_table *smtbl;
1521 SMacro *m;
1523 if (ctx) {
1524 smtbl = &ctx->localmac;
1525 } else if (name[0] == '%' && name[1] == '$') {
1526 if (cstk)
1527 ctx = get_ctx(name, &name, false);
1528 if (!ctx)
1529 return false; /* got to return _something_ */
1530 smtbl = &ctx->localmac;
1531 } else {
1532 smtbl = &smacros;
1534 m = (SMacro *) hash_findix(smtbl, name);
1536 while (m) {
1537 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1538 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1539 if (defn) {
1540 if (nparam == (int) m->nparam || nparam == -1)
1541 *defn = m;
1542 else
1543 *defn = NULL;
1545 return true;
1547 m = m->next;
1550 return false;
1554 * Count and mark off the parameters in a multi-line macro call.
1555 * This is called both from within the multi-line macro expansion
1556 * code, and also to mark off the default parameters when provided
1557 * in a %macro definition line.
1559 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1561 int paramsize, brace;
1563 *nparam = paramsize = 0;
1564 *params = NULL;
1565 while (t) {
1566 /* +1: we need space for the final NULL */
1567 if (*nparam+1 >= paramsize) {
1568 paramsize += PARAM_DELTA;
1569 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1571 skip_white_(t);
1572 brace = false;
1573 if (tok_is_(t, "{"))
1574 brace = true;
1575 (*params)[(*nparam)++] = t;
1576 while (tok_isnt_(t, brace ? "}" : ","))
1577 t = t->next;
1578 if (t) { /* got a comma/brace */
1579 t = t->next;
1580 if (brace) {
1582 * Now we've found the closing brace, look further
1583 * for the comma.
1585 skip_white_(t);
1586 if (tok_isnt_(t, ",")) {
1587 error(ERR_NONFATAL,
1588 "braces do not enclose all of macro parameter");
1589 while (tok_isnt_(t, ","))
1590 t = t->next;
1592 if (t)
1593 t = t->next; /* eat the comma */
1600 * Determine whether one of the various `if' conditions is true or
1601 * not.
1603 * We must free the tline we get passed.
1605 static bool if_condition(Token * tline, enum preproc_token ct)
1607 enum pp_conditional i = PP_COND(ct);
1608 bool j;
1609 Token *t, *tt, **tptr, *origline;
1610 struct tokenval tokval;
1611 expr *evalresult;
1612 enum pp_token_type needtype;
1614 origline = tline;
1616 switch (i) {
1617 case PPC_IFCTX:
1618 j = false; /* have we matched yet? */
1619 while (true) {
1620 skip_white_(tline);
1621 if (!tline)
1622 break;
1623 if (tline->type != TOK_ID) {
1624 error(ERR_NONFATAL,
1625 "`%s' expects context identifiers", pp_directives[ct]);
1626 free_tlist(origline);
1627 return -1;
1629 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1630 j = true;
1631 tline = tline->next;
1633 break;
1635 case PPC_IFDEF:
1636 j = false; /* have we matched yet? */
1637 while (tline) {
1638 skip_white_(tline);
1639 if (!tline || (tline->type != TOK_ID &&
1640 (tline->type != TOK_PREPROC_ID ||
1641 tline->text[1] != '$'))) {
1642 error(ERR_NONFATAL,
1643 "`%s' expects macro identifiers", pp_directives[ct]);
1644 goto fail;
1646 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1647 j = true;
1648 tline = tline->next;
1650 break;
1652 case PPC_IFIDN:
1653 case PPC_IFIDNI:
1654 tline = expand_smacro(tline);
1655 t = tt = tline;
1656 while (tok_isnt_(tt, ","))
1657 tt = tt->next;
1658 if (!tt) {
1659 error(ERR_NONFATAL,
1660 "`%s' expects two comma-separated arguments",
1661 pp_directives[ct]);
1662 goto fail;
1664 tt = tt->next;
1665 j = true; /* assume equality unless proved not */
1666 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1667 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1668 error(ERR_NONFATAL, "`%s': more than one comma on line",
1669 pp_directives[ct]);
1670 goto fail;
1672 if (t->type == TOK_WHITESPACE) {
1673 t = t->next;
1674 continue;
1676 if (tt->type == TOK_WHITESPACE) {
1677 tt = tt->next;
1678 continue;
1680 if (tt->type != t->type) {
1681 j = false; /* found mismatching tokens */
1682 break;
1684 /* When comparing strings, need to unquote them first */
1685 if (t->type == TOK_STRING) {
1686 size_t l1 = nasm_unquote(t->text, NULL);
1687 size_t l2 = nasm_unquote(tt->text, NULL);
1689 if (l1 != l2) {
1690 j = false;
1691 break;
1693 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1694 j = false;
1695 break;
1697 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1698 j = false; /* found mismatching tokens */
1699 break;
1702 t = t->next;
1703 tt = tt->next;
1705 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1706 j = false; /* trailing gunk on one end or other */
1707 break;
1709 case PPC_IFMACRO:
1711 bool found = false;
1712 MMacro searching, *mmac;
1714 skip_white_(tline);
1715 tline = expand_id(tline);
1716 if (!tok_type_(tline, TOK_ID)) {
1717 error(ERR_NONFATAL,
1718 "`%s' expects a macro name", pp_directives[ct]);
1719 goto fail;
1721 searching.name = nasm_strdup(tline->text);
1722 searching.casesense = true;
1723 searching.plus = false;
1724 searching.nolist = false;
1725 searching.in_progress = 0;
1726 searching.max_depth = 0;
1727 searching.rep_nest = NULL;
1728 searching.nparam_min = 0;
1729 searching.nparam_max = INT_MAX;
1730 tline = expand_smacro(tline->next);
1731 skip_white_(tline);
1732 if (!tline) {
1733 } else if (!tok_type_(tline, TOK_NUMBER)) {
1734 error(ERR_NONFATAL,
1735 "`%s' expects a parameter count or nothing",
1736 pp_directives[ct]);
1737 } else {
1738 searching.nparam_min = searching.nparam_max =
1739 readnum(tline->text, &j);
1740 if (j)
1741 error(ERR_NONFATAL,
1742 "unable to parse parameter count `%s'",
1743 tline->text);
1745 if (tline && tok_is_(tline->next, "-")) {
1746 tline = tline->next->next;
1747 if (tok_is_(tline, "*"))
1748 searching.nparam_max = INT_MAX;
1749 else if (!tok_type_(tline, TOK_NUMBER))
1750 error(ERR_NONFATAL,
1751 "`%s' expects a parameter count after `-'",
1752 pp_directives[ct]);
1753 else {
1754 searching.nparam_max = readnum(tline->text, &j);
1755 if (j)
1756 error(ERR_NONFATAL,
1757 "unable to parse parameter count `%s'",
1758 tline->text);
1759 if (searching.nparam_min > searching.nparam_max)
1760 error(ERR_NONFATAL,
1761 "minimum parameter count exceeds maximum");
1764 if (tline && tok_is_(tline->next, "+")) {
1765 tline = tline->next;
1766 searching.plus = true;
1768 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1769 while (mmac) {
1770 if (!strcmp(mmac->name, searching.name) &&
1771 (mmac->nparam_min <= searching.nparam_max
1772 || searching.plus)
1773 && (searching.nparam_min <= mmac->nparam_max
1774 || mmac->plus)) {
1775 found = true;
1776 break;
1778 mmac = mmac->next;
1780 if (tline && tline->next)
1781 error(ERR_WARNING|ERR_PASS1,
1782 "trailing garbage after %%ifmacro ignored");
1783 nasm_free(searching.name);
1784 j = found;
1785 break;
1788 case PPC_IFID:
1789 needtype = TOK_ID;
1790 goto iftype;
1791 case PPC_IFNUM:
1792 needtype = TOK_NUMBER;
1793 goto iftype;
1794 case PPC_IFSTR:
1795 needtype = TOK_STRING;
1796 goto iftype;
1798 iftype:
1799 t = tline = expand_smacro(tline);
1801 while (tok_type_(t, TOK_WHITESPACE) ||
1802 (needtype == TOK_NUMBER &&
1803 tok_type_(t, TOK_OTHER) &&
1804 (t->text[0] == '-' || t->text[0] == '+') &&
1805 !t->text[1]))
1806 t = t->next;
1808 j = tok_type_(t, needtype);
1809 break;
1811 case PPC_IFTOKEN:
1812 t = tline = expand_smacro(tline);
1813 while (tok_type_(t, TOK_WHITESPACE))
1814 t = t->next;
1816 j = false;
1817 if (t) {
1818 t = t->next; /* Skip the actual token */
1819 while (tok_type_(t, TOK_WHITESPACE))
1820 t = t->next;
1821 j = !t; /* Should be nothing left */
1823 break;
1825 case PPC_IFEMPTY:
1826 t = tline = expand_smacro(tline);
1827 while (tok_type_(t, TOK_WHITESPACE))
1828 t = t->next;
1830 j = !t; /* Should be empty */
1831 break;
1833 case PPC_IF:
1834 t = tline = expand_smacro(tline);
1835 tptr = &t;
1836 tokval.t_type = TOKEN_INVALID;
1837 evalresult = evaluate(ppscan, tptr, &tokval,
1838 NULL, pass | CRITICAL, error, NULL);
1839 if (!evalresult)
1840 return -1;
1841 if (tokval.t_type)
1842 error(ERR_WARNING|ERR_PASS1,
1843 "trailing garbage after expression ignored");
1844 if (!is_simple(evalresult)) {
1845 error(ERR_NONFATAL,
1846 "non-constant value given to `%s'", pp_directives[ct]);
1847 goto fail;
1849 j = reloc_value(evalresult) != 0;
1850 break;
1852 default:
1853 error(ERR_FATAL,
1854 "preprocessor directive `%s' not yet implemented",
1855 pp_directives[ct]);
1856 goto fail;
1859 free_tlist(origline);
1860 return j ^ PP_NEGATIVE(ct);
1862 fail:
1863 free_tlist(origline);
1864 return -1;
1868 * Common code for defining an smacro
1870 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1871 int nparam, Token *expansion)
1873 SMacro *smac, **smhead;
1874 struct hash_table *smtbl;
1876 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1877 if (!smac) {
1878 error(ERR_WARNING|ERR_PASS1,
1879 "single-line macro `%s' defined both with and"
1880 " without parameters", mname);
1882 * Some instances of the old code considered this a failure,
1883 * some others didn't. What is the right thing to do here?
1885 free_tlist(expansion);
1886 return false; /* Failure */
1887 } else {
1889 * We're redefining, so we have to take over an
1890 * existing SMacro structure. This means freeing
1891 * what was already in it.
1893 nasm_free(smac->name);
1894 free_tlist(smac->expansion);
1896 } else {
1897 smtbl = ctx ? &ctx->localmac : &smacros;
1898 smhead = (SMacro **) hash_findi_add(smtbl, mname);
1899 smac = nasm_malloc(sizeof(SMacro));
1900 smac->next = *smhead;
1901 *smhead = smac;
1903 smac->name = nasm_strdup(mname);
1904 smac->casesense = casesense;
1905 smac->nparam = nparam;
1906 smac->expansion = expansion;
1907 smac->in_progress = false;
1908 return true; /* Success */
1912 * Undefine an smacro
1914 static void undef_smacro(Context *ctx, const char *mname)
1916 SMacro **smhead, *s, **sp;
1917 struct hash_table *smtbl;
1919 smtbl = ctx ? &ctx->localmac : &smacros;
1920 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
1922 if (smhead) {
1924 * We now have a macro name... go hunt for it.
1926 sp = smhead;
1927 while ((s = *sp) != NULL) {
1928 if (!mstrcmp(s->name, mname, s->casesense)) {
1929 *sp = s->next;
1930 nasm_free(s->name);
1931 free_tlist(s->expansion);
1932 nasm_free(s);
1933 } else {
1934 sp = &s->next;
1941 * Parse a mmacro specification.
1943 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
1945 bool err;
1947 tline = tline->next;
1948 skip_white_(tline);
1949 tline = expand_id(tline);
1950 if (!tok_type_(tline, TOK_ID)) {
1951 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
1952 return false;
1955 def->prev = NULL;
1956 def->name = nasm_strdup(tline->text);
1957 def->plus = false;
1958 def->nolist = false;
1959 def->in_progress = 0;
1960 def->rep_nest = NULL;
1961 def->nparam_min = 0;
1962 def->nparam_max = 0;
1964 tline = expand_smacro(tline->next);
1965 skip_white_(tline);
1966 if (!tok_type_(tline, TOK_NUMBER)) {
1967 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
1968 } else {
1969 def->nparam_min = def->nparam_max =
1970 readnum(tline->text, &err);
1971 if (err)
1972 error(ERR_NONFATAL,
1973 "unable to parse parameter count `%s'", tline->text);
1975 if (tline && tok_is_(tline->next, "-")) {
1976 tline = tline->next->next;
1977 if (tok_is_(tline, "*")) {
1978 def->nparam_max = INT_MAX;
1979 } else if (!tok_type_(tline, TOK_NUMBER)) {
1980 error(ERR_NONFATAL,
1981 "`%s' expects a parameter count after `-'", directive);
1982 } else {
1983 def->nparam_max = readnum(tline->text, &err);
1984 if (err) {
1985 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
1986 tline->text);
1988 if (def->nparam_min > def->nparam_max) {
1989 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
1993 if (tline && tok_is_(tline->next, "+")) {
1994 tline = tline->next;
1995 def->plus = true;
1997 if (tline && tok_type_(tline->next, TOK_ID) &&
1998 !nasm_stricmp(tline->next->text, ".nolist")) {
1999 tline = tline->next;
2000 def->nolist = true;
2004 * Handle default parameters.
2006 if (tline && tline->next) {
2007 def->dlist = tline->next;
2008 tline->next = NULL;
2009 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2010 } else {
2011 def->dlist = NULL;
2012 def->defaults = NULL;
2014 def->expansion = NULL;
2016 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2017 !def->plus)
2018 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2019 "too many default macro parameters");
2021 return true;
2026 * Decode a size directive
2028 static int parse_size(const char *str) {
2029 static const char *size_names[] =
2030 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2031 static const int sizes[] =
2032 { 0, 1, 4, 16, 8, 10, 2, 32 };
2034 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2038 * nasm_unquote with error if the string contains NUL characters.
2039 * If the string contains NUL characters, issue an error and return
2040 * the C len, i.e. truncate at the NUL.
2042 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
2044 size_t len = nasm_unquote(qstr, NULL);
2045 size_t clen = strlen(qstr);
2047 if (len != clen)
2048 error(ERR_NONFATAL, "NUL character in `%s' directive",
2049 pp_directives[directive]);
2051 return clen;
2055 * find and process preprocessor directive in passed line
2056 * Find out if a line contains a preprocessor directive, and deal
2057 * with it if so.
2059 * If a directive _is_ found, it is the responsibility of this routine
2060 * (and not the caller) to free_tlist() the line.
2062 * @param tline a pointer to the current tokeninzed line linked list
2063 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2066 static int do_directive(Token * tline)
2068 enum preproc_token i;
2069 int j;
2070 bool err;
2071 int nparam;
2072 bool nolist;
2073 bool casesense;
2074 int k, m;
2075 int offset;
2076 char *p, *pp;
2077 const char *mname;
2078 Include *inc;
2079 Context *ctx;
2080 Cond *cond;
2081 MMacro *mmac, **mmhead;
2082 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2083 Line *l;
2084 struct tokenval tokval;
2085 expr *evalresult;
2086 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2087 int64_t count;
2088 size_t len;
2089 int severity;
2091 origline = tline;
2093 skip_white_(tline);
2094 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2095 (tline->text[1] == '%' || tline->text[1] == '$'
2096 || tline->text[1] == '!'))
2097 return NO_DIRECTIVE_FOUND;
2099 i = pp_token_hash(tline->text);
2102 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2103 * since they are known to be buggy at moment, we need to fix them
2104 * in future release (2.09-2.10)
2106 if (i == PP_RMACRO || i == PP_RMACRO || i == PP_EXITMACRO) {
2107 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2108 tline->text);
2109 return NO_DIRECTIVE_FOUND;
2113 * If we're in a non-emitting branch of a condition construct,
2114 * or walking to the end of an already terminated %rep block,
2115 * we should ignore all directives except for condition
2116 * directives.
2118 if (((istk->conds && !emitting(istk->conds->state)) ||
2119 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2120 return NO_DIRECTIVE_FOUND;
2124 * If we're defining a macro or reading a %rep block, we should
2125 * ignore all directives except for %macro/%imacro (which nest),
2126 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2127 * If we're in a %rep block, another %rep nests, so should be let through.
2129 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2130 i != PP_RMACRO && i != PP_IRMACRO &&
2131 i != PP_ENDMACRO && i != PP_ENDM &&
2132 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2133 return NO_DIRECTIVE_FOUND;
2136 if (defining) {
2137 if (i == PP_MACRO || i == PP_IMACRO ||
2138 i == PP_RMACRO || i == PP_IRMACRO) {
2139 nested_mac_count++;
2140 return NO_DIRECTIVE_FOUND;
2141 } else if (nested_mac_count > 0) {
2142 if (i == PP_ENDMACRO) {
2143 nested_mac_count--;
2144 return NO_DIRECTIVE_FOUND;
2147 if (!defining->name) {
2148 if (i == PP_REP) {
2149 nested_rep_count++;
2150 return NO_DIRECTIVE_FOUND;
2151 } else if (nested_rep_count > 0) {
2152 if (i == PP_ENDREP) {
2153 nested_rep_count--;
2154 return NO_DIRECTIVE_FOUND;
2160 switch (i) {
2161 case PP_INVALID:
2162 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2163 tline->text);
2164 return NO_DIRECTIVE_FOUND; /* didn't get it */
2166 case PP_STACKSIZE:
2167 /* Directive to tell NASM what the default stack size is. The
2168 * default is for a 16-bit stack, and this can be overriden with
2169 * %stacksize large.
2171 tline = tline->next;
2172 if (tline && tline->type == TOK_WHITESPACE)
2173 tline = tline->next;
2174 if (!tline || tline->type != TOK_ID) {
2175 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2176 free_tlist(origline);
2177 return DIRECTIVE_FOUND;
2179 if (nasm_stricmp(tline->text, "flat") == 0) {
2180 /* All subsequent ARG directives are for a 32-bit stack */
2181 StackSize = 4;
2182 StackPointer = "ebp";
2183 ArgOffset = 8;
2184 LocalOffset = 0;
2185 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2186 /* All subsequent ARG directives are for a 64-bit stack */
2187 StackSize = 8;
2188 StackPointer = "rbp";
2189 ArgOffset = 16;
2190 LocalOffset = 0;
2191 } else if (nasm_stricmp(tline->text, "large") == 0) {
2192 /* All subsequent ARG directives are for a 16-bit stack,
2193 * far function call.
2195 StackSize = 2;
2196 StackPointer = "bp";
2197 ArgOffset = 4;
2198 LocalOffset = 0;
2199 } else if (nasm_stricmp(tline->text, "small") == 0) {
2200 /* All subsequent ARG directives are for a 16-bit stack,
2201 * far function call. We don't support near functions.
2203 StackSize = 2;
2204 StackPointer = "bp";
2205 ArgOffset = 6;
2206 LocalOffset = 0;
2207 } else {
2208 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2209 free_tlist(origline);
2210 return DIRECTIVE_FOUND;
2212 free_tlist(origline);
2213 return DIRECTIVE_FOUND;
2215 case PP_ARG:
2216 /* TASM like ARG directive to define arguments to functions, in
2217 * the following form:
2219 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2221 offset = ArgOffset;
2222 do {
2223 char *arg, directive[256];
2224 int size = StackSize;
2226 /* Find the argument name */
2227 tline = tline->next;
2228 if (tline && tline->type == TOK_WHITESPACE)
2229 tline = tline->next;
2230 if (!tline || tline->type != TOK_ID) {
2231 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2232 free_tlist(origline);
2233 return DIRECTIVE_FOUND;
2235 arg = tline->text;
2237 /* Find the argument size type */
2238 tline = tline->next;
2239 if (!tline || tline->type != TOK_OTHER
2240 || tline->text[0] != ':') {
2241 error(ERR_NONFATAL,
2242 "Syntax error processing `%%arg' directive");
2243 free_tlist(origline);
2244 return DIRECTIVE_FOUND;
2246 tline = tline->next;
2247 if (!tline || tline->type != TOK_ID) {
2248 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2249 free_tlist(origline);
2250 return DIRECTIVE_FOUND;
2253 /* Allow macro expansion of type parameter */
2254 tt = tokenize(tline->text);
2255 tt = expand_smacro(tt);
2256 size = parse_size(tt->text);
2257 if (!size) {
2258 error(ERR_NONFATAL,
2259 "Invalid size type for `%%arg' missing directive");
2260 free_tlist(tt);
2261 free_tlist(origline);
2262 return DIRECTIVE_FOUND;
2264 free_tlist(tt);
2266 /* Round up to even stack slots */
2267 size = ALIGN(size, StackSize);
2269 /* Now define the macro for the argument */
2270 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2271 arg, StackPointer, offset);
2272 do_directive(tokenize(directive));
2273 offset += size;
2275 /* Move to the next argument in the list */
2276 tline = tline->next;
2277 if (tline && tline->type == TOK_WHITESPACE)
2278 tline = tline->next;
2279 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2280 ArgOffset = offset;
2281 free_tlist(origline);
2282 return DIRECTIVE_FOUND;
2284 case PP_LOCAL:
2285 /* TASM like LOCAL directive to define local variables for a
2286 * function, in the following form:
2288 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2290 * The '= LocalSize' at the end is ignored by NASM, but is
2291 * required by TASM to define the local parameter size (and used
2292 * by the TASM macro package).
2294 offset = LocalOffset;
2295 do {
2296 char *local, directive[256];
2297 int size = StackSize;
2299 /* Find the argument name */
2300 tline = tline->next;
2301 if (tline && tline->type == TOK_WHITESPACE)
2302 tline = tline->next;
2303 if (!tline || tline->type != TOK_ID) {
2304 error(ERR_NONFATAL,
2305 "`%%local' missing argument parameter");
2306 free_tlist(origline);
2307 return DIRECTIVE_FOUND;
2309 local = tline->text;
2311 /* Find the argument size type */
2312 tline = tline->next;
2313 if (!tline || tline->type != TOK_OTHER
2314 || tline->text[0] != ':') {
2315 error(ERR_NONFATAL,
2316 "Syntax error processing `%%local' directive");
2317 free_tlist(origline);
2318 return DIRECTIVE_FOUND;
2320 tline = tline->next;
2321 if (!tline || tline->type != TOK_ID) {
2322 error(ERR_NONFATAL,
2323 "`%%local' missing size type parameter");
2324 free_tlist(origline);
2325 return DIRECTIVE_FOUND;
2328 /* Allow macro expansion of type parameter */
2329 tt = tokenize(tline->text);
2330 tt = expand_smacro(tt);
2331 size = parse_size(tt->text);
2332 if (!size) {
2333 error(ERR_NONFATAL,
2334 "Invalid size type for `%%local' missing directive");
2335 free_tlist(tt);
2336 free_tlist(origline);
2337 return DIRECTIVE_FOUND;
2339 free_tlist(tt);
2341 /* Round up to even stack slots */
2342 size = ALIGN(size, StackSize);
2344 offset += size; /* Negative offset, increment before */
2346 /* Now define the macro for the argument */
2347 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2348 local, StackPointer, offset);
2349 do_directive(tokenize(directive));
2351 /* Now define the assign to setup the enter_c macro correctly */
2352 snprintf(directive, sizeof(directive),
2353 "%%assign %%$localsize %%$localsize+%d", size);
2354 do_directive(tokenize(directive));
2356 /* Move to the next argument in the list */
2357 tline = tline->next;
2358 if (tline && tline->type == TOK_WHITESPACE)
2359 tline = tline->next;
2360 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2361 LocalOffset = offset;
2362 free_tlist(origline);
2363 return DIRECTIVE_FOUND;
2365 case PP_CLEAR:
2366 if (tline->next)
2367 error(ERR_WARNING|ERR_PASS1,
2368 "trailing garbage after `%%clear' ignored");
2369 free_macros();
2370 init_macros();
2371 free_tlist(origline);
2372 return DIRECTIVE_FOUND;
2374 case PP_DEPEND:
2375 t = tline->next = expand_smacro(tline->next);
2376 skip_white_(t);
2377 if (!t || (t->type != TOK_STRING &&
2378 t->type != TOK_INTERNAL_STRING)) {
2379 error(ERR_NONFATAL, "`%%depend' expects a file name");
2380 free_tlist(origline);
2381 return DIRECTIVE_FOUND; /* but we did _something_ */
2383 if (t->next)
2384 error(ERR_WARNING|ERR_PASS1,
2385 "trailing garbage after `%%depend' ignored");
2386 p = t->text;
2387 if (t->type != TOK_INTERNAL_STRING)
2388 nasm_unquote_cstr(p, i);
2389 if (dephead && !in_list(*dephead, p)) {
2390 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2391 sl->next = NULL;
2392 strcpy(sl->str, p);
2393 *deptail = sl;
2394 deptail = &sl->next;
2396 free_tlist(origline);
2397 return DIRECTIVE_FOUND;
2399 case PP_INCLUDE:
2400 t = tline->next = expand_smacro(tline->next);
2401 skip_white_(t);
2403 if (!t || (t->type != TOK_STRING &&
2404 t->type != TOK_INTERNAL_STRING)) {
2405 error(ERR_NONFATAL, "`%%include' expects a file name");
2406 free_tlist(origline);
2407 return DIRECTIVE_FOUND; /* but we did _something_ */
2409 if (t->next)
2410 error(ERR_WARNING|ERR_PASS1,
2411 "trailing garbage after `%%include' ignored");
2412 p = t->text;
2413 if (t->type != TOK_INTERNAL_STRING)
2414 nasm_unquote_cstr(p, i);
2415 inc = nasm_malloc(sizeof(Include));
2416 inc->next = istk;
2417 inc->conds = NULL;
2418 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2419 if (!inc->fp) {
2420 /* -MG given but file not found */
2421 nasm_free(inc);
2422 } else {
2423 inc->fname = src_set_fname(nasm_strdup(p));
2424 inc->lineno = src_set_linnum(0);
2425 inc->lineinc = 1;
2426 inc->expansion = NULL;
2427 inc->mstk = NULL;
2428 istk = inc;
2429 list->uplevel(LIST_INCLUDE);
2431 free_tlist(origline);
2432 return DIRECTIVE_FOUND;
2434 case PP_USE:
2436 static macros_t *use_pkg;
2437 const char *pkg_macro = NULL;
2439 tline = tline->next;
2440 skip_white_(tline);
2441 tline = expand_id(tline);
2443 if (!tline || (tline->type != TOK_STRING &&
2444 tline->type != TOK_INTERNAL_STRING &&
2445 tline->type != TOK_ID)) {
2446 error(ERR_NONFATAL, "`%%use' expects a package name");
2447 free_tlist(origline);
2448 return DIRECTIVE_FOUND; /* but we did _something_ */
2450 if (tline->next)
2451 error(ERR_WARNING|ERR_PASS1,
2452 "trailing garbage after `%%use' ignored");
2453 if (tline->type == TOK_STRING)
2454 nasm_unquote_cstr(tline->text, i);
2455 use_pkg = nasm_stdmac_find_package(tline->text);
2456 if (!use_pkg)
2457 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2458 else
2459 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2460 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2461 /* Not already included, go ahead and include it */
2462 stdmacpos = use_pkg;
2464 free_tlist(origline);
2465 return DIRECTIVE_FOUND;
2467 case PP_PUSH:
2468 case PP_REPL:
2469 case PP_POP:
2470 tline = tline->next;
2471 skip_white_(tline);
2472 tline = expand_id(tline);
2473 if (tline) {
2474 if (!tok_type_(tline, TOK_ID)) {
2475 error(ERR_NONFATAL, "`%s' expects a context identifier",
2476 pp_directives[i]);
2477 free_tlist(origline);
2478 return DIRECTIVE_FOUND; /* but we did _something_ */
2480 if (tline->next)
2481 error(ERR_WARNING|ERR_PASS1,
2482 "trailing garbage after `%s' ignored",
2483 pp_directives[i]);
2484 p = nasm_strdup(tline->text);
2485 } else {
2486 p = NULL; /* Anonymous */
2489 if (i == PP_PUSH) {
2490 ctx = nasm_malloc(sizeof(Context));
2491 ctx->next = cstk;
2492 hash_init(&ctx->localmac, HASH_SMALL);
2493 ctx->name = p;
2494 ctx->number = unique++;
2495 cstk = ctx;
2496 } else {
2497 /* %pop or %repl */
2498 if (!cstk) {
2499 error(ERR_NONFATAL, "`%s': context stack is empty",
2500 pp_directives[i]);
2501 } else if (i == PP_POP) {
2502 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2503 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2504 "expected %s",
2505 cstk->name ? cstk->name : "anonymous", p);
2506 else
2507 ctx_pop();
2508 } else {
2509 /* i == PP_REPL */
2510 nasm_free(cstk->name);
2511 cstk->name = p;
2512 p = NULL;
2514 nasm_free(p);
2516 free_tlist(origline);
2517 return DIRECTIVE_FOUND;
2518 case PP_FATAL:
2519 severity = ERR_FATAL;
2520 goto issue_error;
2521 case PP_ERROR:
2522 severity = ERR_NONFATAL;
2523 goto issue_error;
2524 case PP_WARNING:
2525 severity = ERR_WARNING|ERR_WARN_USER;
2526 goto issue_error;
2528 issue_error:
2530 /* Only error out if this is the final pass */
2531 if (pass != 2 && i != PP_FATAL)
2532 return DIRECTIVE_FOUND;
2534 tline->next = expand_smacro(tline->next);
2535 tline = tline->next;
2536 skip_white_(tline);
2537 t = tline ? tline->next : NULL;
2538 skip_white_(t);
2539 if (tok_type_(tline, TOK_STRING) && !t) {
2540 /* The line contains only a quoted string */
2541 p = tline->text;
2542 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2543 error(severity, "%s", p);
2544 } else {
2545 /* Not a quoted string, or more than a quoted string */
2546 p = detoken(tline, false);
2547 error(severity, "%s", p);
2548 nasm_free(p);
2550 free_tlist(origline);
2551 return DIRECTIVE_FOUND;
2554 CASE_PP_IF:
2555 if (istk->conds && !emitting(istk->conds->state))
2556 j = COND_NEVER;
2557 else {
2558 j = if_condition(tline->next, i);
2559 tline->next = NULL; /* it got freed */
2560 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2562 cond = nasm_malloc(sizeof(Cond));
2563 cond->next = istk->conds;
2564 cond->state = j;
2565 istk->conds = cond;
2566 if(istk->mstk)
2567 istk->mstk->condcnt ++;
2568 free_tlist(origline);
2569 return DIRECTIVE_FOUND;
2571 CASE_PP_ELIF:
2572 if (!istk->conds)
2573 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2574 switch(istk->conds->state) {
2575 case COND_IF_TRUE:
2576 istk->conds->state = COND_DONE;
2577 break;
2579 case COND_DONE:
2580 case COND_NEVER:
2581 break;
2583 case COND_ELSE_TRUE:
2584 case COND_ELSE_FALSE:
2585 error_precond(ERR_WARNING|ERR_PASS1,
2586 "`%%elif' after `%%else' ignored");
2587 istk->conds->state = COND_NEVER;
2588 break;
2590 case COND_IF_FALSE:
2592 * IMPORTANT: In the case of %if, we will already have
2593 * called expand_mmac_params(); however, if we're
2594 * processing an %elif we must have been in a
2595 * non-emitting mode, which would have inhibited
2596 * the normal invocation of expand_mmac_params().
2597 * Therefore, we have to do it explicitly here.
2599 j = if_condition(expand_mmac_params(tline->next), i);
2600 tline->next = NULL; /* it got freed */
2601 istk->conds->state =
2602 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2603 break;
2605 free_tlist(origline);
2606 return DIRECTIVE_FOUND;
2608 case PP_ELSE:
2609 if (tline->next)
2610 error_precond(ERR_WARNING|ERR_PASS1,
2611 "trailing garbage after `%%else' ignored");
2612 if (!istk->conds)
2613 error(ERR_FATAL, "`%%else': no matching `%%if'");
2614 switch(istk->conds->state) {
2615 case COND_IF_TRUE:
2616 case COND_DONE:
2617 istk->conds->state = COND_ELSE_FALSE;
2618 break;
2620 case COND_NEVER:
2621 break;
2623 case COND_IF_FALSE:
2624 istk->conds->state = COND_ELSE_TRUE;
2625 break;
2627 case COND_ELSE_TRUE:
2628 case COND_ELSE_FALSE:
2629 error_precond(ERR_WARNING|ERR_PASS1,
2630 "`%%else' after `%%else' ignored.");
2631 istk->conds->state = COND_NEVER;
2632 break;
2634 free_tlist(origline);
2635 return DIRECTIVE_FOUND;
2637 case PP_ENDIF:
2638 if (tline->next)
2639 error_precond(ERR_WARNING|ERR_PASS1,
2640 "trailing garbage after `%%endif' ignored");
2641 if (!istk->conds)
2642 error(ERR_FATAL, "`%%endif': no matching `%%if'");
2643 cond = istk->conds;
2644 istk->conds = cond->next;
2645 nasm_free(cond);
2646 if(istk->mstk)
2647 istk->mstk->condcnt --;
2648 free_tlist(origline);
2649 return DIRECTIVE_FOUND;
2651 case PP_RMACRO:
2652 case PP_IRMACRO:
2653 case PP_MACRO:
2654 case PP_IMACRO:
2655 if (defining) {
2656 error(ERR_FATAL, "`%s': already defining a macro",
2657 pp_directives[i]);
2658 return DIRECTIVE_FOUND;
2660 defining = nasm_malloc(sizeof(MMacro));
2661 defining->max_depth =
2662 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2663 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2664 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2665 nasm_free(defining);
2666 defining = NULL;
2667 return DIRECTIVE_FOUND;
2670 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2671 while (mmac) {
2672 if (!strcmp(mmac->name, defining->name) &&
2673 (mmac->nparam_min <= defining->nparam_max
2674 || defining->plus)
2675 && (defining->nparam_min <= mmac->nparam_max
2676 || mmac->plus)) {
2677 error(ERR_WARNING|ERR_PASS1,
2678 "redefining multi-line macro `%s'", defining->name);
2679 return DIRECTIVE_FOUND;
2681 mmac = mmac->next;
2683 free_tlist(origline);
2684 return DIRECTIVE_FOUND;
2686 case PP_ENDM:
2687 case PP_ENDMACRO:
2688 if (! (defining && defining->name)) {
2689 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2690 return DIRECTIVE_FOUND;
2692 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2693 defining->next = *mmhead;
2694 *mmhead = defining;
2695 defining = NULL;
2696 free_tlist(origline);
2697 return DIRECTIVE_FOUND;
2699 case PP_EXITMACRO:
2701 * We must search along istk->expansion until we hit a
2702 * macro-end marker for a macro with a name. Then we
2703 * bypass all lines between exitmacro and endmacro.
2705 list_for_each(l, istk->expansion)
2706 if (l->finishes && l->finishes->name)
2707 break;
2709 if (l) {
2711 * Remove all conditional entries relative to this
2712 * macro invocation. (safe to do in this context)
2714 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2715 cond = istk->conds;
2716 istk->conds = cond->next;
2717 nasm_free(cond);
2719 istk->expansion = l;
2720 } else {
2721 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2723 free_tlist(origline);
2724 return DIRECTIVE_FOUND;
2726 case PP_UNMACRO:
2727 case PP_UNIMACRO:
2729 MMacro **mmac_p;
2730 MMacro spec;
2732 spec.casesense = (i == PP_UNMACRO);
2733 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2734 return DIRECTIVE_FOUND;
2736 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2737 while (mmac_p && *mmac_p) {
2738 mmac = *mmac_p;
2739 if (mmac->casesense == spec.casesense &&
2740 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2741 mmac->nparam_min == spec.nparam_min &&
2742 mmac->nparam_max == spec.nparam_max &&
2743 mmac->plus == spec.plus) {
2744 *mmac_p = mmac->next;
2745 free_mmacro(mmac);
2746 } else {
2747 mmac_p = &mmac->next;
2750 free_tlist(origline);
2751 free_tlist(spec.dlist);
2752 return DIRECTIVE_FOUND;
2755 case PP_ROTATE:
2756 if (tline->next && tline->next->type == TOK_WHITESPACE)
2757 tline = tline->next;
2758 if (!tline->next) {
2759 free_tlist(origline);
2760 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2761 return DIRECTIVE_FOUND;
2763 t = expand_smacro(tline->next);
2764 tline->next = NULL;
2765 free_tlist(origline);
2766 tline = t;
2767 tptr = &t;
2768 tokval.t_type = TOKEN_INVALID;
2769 evalresult =
2770 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2771 free_tlist(tline);
2772 if (!evalresult)
2773 return DIRECTIVE_FOUND;
2774 if (tokval.t_type)
2775 error(ERR_WARNING|ERR_PASS1,
2776 "trailing garbage after expression ignored");
2777 if (!is_simple(evalresult)) {
2778 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2779 return DIRECTIVE_FOUND;
2781 mmac = istk->mstk;
2782 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2783 mmac = mmac->next_active;
2784 if (!mmac) {
2785 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2786 } else if (mmac->nparam == 0) {
2787 error(ERR_NONFATAL,
2788 "`%%rotate' invoked within macro without parameters");
2789 } else {
2790 int rotate = mmac->rotate + reloc_value(evalresult);
2792 rotate %= (int)mmac->nparam;
2793 if (rotate < 0)
2794 rotate += mmac->nparam;
2796 mmac->rotate = rotate;
2798 return DIRECTIVE_FOUND;
2800 case PP_REP:
2801 nolist = false;
2802 do {
2803 tline = tline->next;
2804 } while (tok_type_(tline, TOK_WHITESPACE));
2806 if (tok_type_(tline, TOK_ID) &&
2807 nasm_stricmp(tline->text, ".nolist") == 0) {
2808 nolist = true;
2809 do {
2810 tline = tline->next;
2811 } while (tok_type_(tline, TOK_WHITESPACE));
2814 if (tline) {
2815 t = expand_smacro(tline);
2816 tptr = &t;
2817 tokval.t_type = TOKEN_INVALID;
2818 evalresult =
2819 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2820 if (!evalresult) {
2821 free_tlist(origline);
2822 return DIRECTIVE_FOUND;
2824 if (tokval.t_type)
2825 error(ERR_WARNING|ERR_PASS1,
2826 "trailing garbage after expression ignored");
2827 if (!is_simple(evalresult)) {
2828 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2829 return DIRECTIVE_FOUND;
2831 count = reloc_value(evalresult) + 1;
2832 } else {
2833 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2834 count = 0;
2836 free_tlist(origline);
2838 tmp_defining = defining;
2839 defining = nasm_malloc(sizeof(MMacro));
2840 defining->prev = NULL;
2841 defining->name = NULL; /* flags this macro as a %rep block */
2842 defining->casesense = false;
2843 defining->plus = false;
2844 defining->nolist = nolist;
2845 defining->in_progress = count;
2846 defining->max_depth = 0;
2847 defining->nparam_min = defining->nparam_max = 0;
2848 defining->defaults = NULL;
2849 defining->dlist = NULL;
2850 defining->expansion = NULL;
2851 defining->next_active = istk->mstk;
2852 defining->rep_nest = tmp_defining;
2853 return DIRECTIVE_FOUND;
2855 case PP_ENDREP:
2856 if (!defining || defining->name) {
2857 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2858 return DIRECTIVE_FOUND;
2862 * Now we have a "macro" defined - although it has no name
2863 * and we won't be entering it in the hash tables - we must
2864 * push a macro-end marker for it on to istk->expansion.
2865 * After that, it will take care of propagating itself (a
2866 * macro-end marker line for a macro which is really a %rep
2867 * block will cause the macro to be re-expanded, complete
2868 * with another macro-end marker to ensure the process
2869 * continues) until the whole expansion is forcibly removed
2870 * from istk->expansion by a %exitrep.
2872 l = nasm_malloc(sizeof(Line));
2873 l->next = istk->expansion;
2874 l->finishes = defining;
2875 l->first = NULL;
2876 istk->expansion = l;
2878 istk->mstk = defining;
2880 list->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2881 tmp_defining = defining;
2882 defining = defining->rep_nest;
2883 free_tlist(origline);
2884 return DIRECTIVE_FOUND;
2886 case PP_EXITREP:
2888 * We must search along istk->expansion until we hit a
2889 * macro-end marker for a macro with no name. Then we set
2890 * its `in_progress' flag to 0.
2892 list_for_each(l, istk->expansion)
2893 if (l->finishes && !l->finishes->name)
2894 break;
2896 if (l)
2897 l->finishes->in_progress = 1;
2898 else
2899 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
2900 free_tlist(origline);
2901 return DIRECTIVE_FOUND;
2903 case PP_XDEFINE:
2904 case PP_IXDEFINE:
2905 case PP_DEFINE:
2906 case PP_IDEFINE:
2907 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
2909 tline = tline->next;
2910 skip_white_(tline);
2911 tline = expand_id(tline);
2912 if (!tline || (tline->type != TOK_ID &&
2913 (tline->type != TOK_PREPROC_ID ||
2914 tline->text[1] != '$'))) {
2915 error(ERR_NONFATAL, "`%s' expects a macro identifier",
2916 pp_directives[i]);
2917 free_tlist(origline);
2918 return DIRECTIVE_FOUND;
2921 ctx = get_ctx(tline->text, &mname, false);
2922 last = tline;
2923 param_start = tline = tline->next;
2924 nparam = 0;
2926 /* Expand the macro definition now for %xdefine and %ixdefine */
2927 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
2928 tline = expand_smacro(tline);
2930 if (tok_is_(tline, "(")) {
2932 * This macro has parameters.
2935 tline = tline->next;
2936 while (1) {
2937 skip_white_(tline);
2938 if (!tline) {
2939 error(ERR_NONFATAL, "parameter identifier expected");
2940 free_tlist(origline);
2941 return DIRECTIVE_FOUND;
2943 if (tline->type != TOK_ID) {
2944 error(ERR_NONFATAL,
2945 "`%s': parameter identifier expected",
2946 tline->text);
2947 free_tlist(origline);
2948 return DIRECTIVE_FOUND;
2950 tline->type = TOK_SMAC_PARAM + nparam++;
2951 tline = tline->next;
2952 skip_white_(tline);
2953 if (tok_is_(tline, ",")) {
2954 tline = tline->next;
2955 } else {
2956 if (!tok_is_(tline, ")")) {
2957 error(ERR_NONFATAL,
2958 "`)' expected to terminate macro template");
2959 free_tlist(origline);
2960 return DIRECTIVE_FOUND;
2962 break;
2965 last = tline;
2966 tline = tline->next;
2968 if (tok_type_(tline, TOK_WHITESPACE))
2969 last = tline, tline = tline->next;
2970 macro_start = NULL;
2971 last->next = NULL;
2972 t = tline;
2973 while (t) {
2974 if (t->type == TOK_ID) {
2975 list_for_each(tt, param_start)
2976 if (tt->type >= TOK_SMAC_PARAM &&
2977 !strcmp(tt->text, t->text))
2978 t->type = tt->type;
2980 tt = t->next;
2981 t->next = macro_start;
2982 macro_start = t;
2983 t = tt;
2986 * Good. We now have a macro name, a parameter count, and a
2987 * token list (in reverse order) for an expansion. We ought
2988 * to be OK just to create an SMacro, store it, and let
2989 * free_tlist have the rest of the line (which we have
2990 * carefully re-terminated after chopping off the expansion
2991 * from the end).
2993 define_smacro(ctx, mname, casesense, nparam, macro_start);
2994 free_tlist(origline);
2995 return DIRECTIVE_FOUND;
2997 case PP_UNDEF:
2998 tline = tline->next;
2999 skip_white_(tline);
3000 tline = expand_id(tline);
3001 if (!tline || (tline->type != TOK_ID &&
3002 (tline->type != TOK_PREPROC_ID ||
3003 tline->text[1] != '$'))) {
3004 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3005 free_tlist(origline);
3006 return DIRECTIVE_FOUND;
3008 if (tline->next) {
3009 error(ERR_WARNING|ERR_PASS1,
3010 "trailing garbage after macro name ignored");
3013 /* Find the context that symbol belongs to */
3014 ctx = get_ctx(tline->text, &mname, false);
3015 undef_smacro(ctx, mname);
3016 free_tlist(origline);
3017 return DIRECTIVE_FOUND;
3019 case PP_DEFSTR:
3020 case PP_IDEFSTR:
3021 casesense = (i == PP_DEFSTR);
3023 tline = tline->next;
3024 skip_white_(tline);
3025 tline = expand_id(tline);
3026 if (!tline || (tline->type != TOK_ID &&
3027 (tline->type != TOK_PREPROC_ID ||
3028 tline->text[1] != '$'))) {
3029 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3030 pp_directives[i]);
3031 free_tlist(origline);
3032 return DIRECTIVE_FOUND;
3035 ctx = get_ctx(tline->text, &mname, false);
3036 last = tline;
3037 tline = expand_smacro(tline->next);
3038 last->next = NULL;
3040 while (tok_type_(tline, TOK_WHITESPACE))
3041 tline = delete_Token(tline);
3043 p = detoken(tline, false);
3044 macro_start = nasm_malloc(sizeof(*macro_start));
3045 macro_start->next = NULL;
3046 macro_start->text = nasm_quote(p, strlen(p));
3047 macro_start->type = TOK_STRING;
3048 macro_start->a.mac = NULL;
3049 nasm_free(p);
3052 * We now have a macro name, an implicit parameter count of
3053 * zero, and a string token to use as an expansion. Create
3054 * and store an SMacro.
3056 define_smacro(ctx, mname, casesense, 0, macro_start);
3057 free_tlist(origline);
3058 return DIRECTIVE_FOUND;
3060 case PP_DEFTOK:
3061 case PP_IDEFTOK:
3062 casesense = (i == PP_DEFTOK);
3064 tline = tline->next;
3065 skip_white_(tline);
3066 tline = expand_id(tline);
3067 if (!tline || (tline->type != TOK_ID &&
3068 (tline->type != TOK_PREPROC_ID ||
3069 tline->text[1] != '$'))) {
3070 error(ERR_NONFATAL,
3071 "`%s' expects a macro identifier as first parameter",
3072 pp_directives[i]);
3073 free_tlist(origline);
3074 return DIRECTIVE_FOUND;
3076 ctx = get_ctx(tline->text, &mname, false);
3077 last = tline;
3078 tline = expand_smacro(tline->next);
3079 last->next = NULL;
3081 t = tline;
3082 while (tok_type_(t, TOK_WHITESPACE))
3083 t = t->next;
3084 /* t should now point to the string */
3085 if (t->type != TOK_STRING) {
3086 error(ERR_NONFATAL,
3087 "`%s` requires string as second parameter",
3088 pp_directives[i]);
3089 free_tlist(tline);
3090 free_tlist(origline);
3091 return DIRECTIVE_FOUND;
3094 nasm_unquote_cstr(t->text, i);
3095 macro_start = tokenize(t->text);
3098 * We now have a macro name, an implicit parameter count of
3099 * zero, and a numeric token to use as an expansion. Create
3100 * and store an SMacro.
3102 define_smacro(ctx, mname, casesense, 0, macro_start);
3103 free_tlist(tline);
3104 free_tlist(origline);
3105 return DIRECTIVE_FOUND;
3107 case PP_PATHSEARCH:
3109 FILE *fp;
3110 StrList *xsl = NULL;
3111 StrList **xst = &xsl;
3113 casesense = true;
3115 tline = tline->next;
3116 skip_white_(tline);
3117 tline = expand_id(tline);
3118 if (!tline || (tline->type != TOK_ID &&
3119 (tline->type != TOK_PREPROC_ID ||
3120 tline->text[1] != '$'))) {
3121 error(ERR_NONFATAL,
3122 "`%%pathsearch' expects a macro identifier as first parameter");
3123 free_tlist(origline);
3124 return DIRECTIVE_FOUND;
3126 ctx = get_ctx(tline->text, &mname, false);
3127 last = tline;
3128 tline = expand_smacro(tline->next);
3129 last->next = NULL;
3131 t = tline;
3132 while (tok_type_(t, TOK_WHITESPACE))
3133 t = t->next;
3135 if (!t || (t->type != TOK_STRING &&
3136 t->type != TOK_INTERNAL_STRING)) {
3137 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3138 free_tlist(tline);
3139 free_tlist(origline);
3140 return DIRECTIVE_FOUND; /* but we did _something_ */
3142 if (t->next)
3143 error(ERR_WARNING|ERR_PASS1,
3144 "trailing garbage after `%%pathsearch' ignored");
3145 p = t->text;
3146 if (t->type != TOK_INTERNAL_STRING)
3147 nasm_unquote(p, NULL);
3149 fp = inc_fopen(p, &xsl, &xst, true);
3150 if (fp) {
3151 p = xsl->str;
3152 fclose(fp); /* Don't actually care about the file */
3154 macro_start = nasm_malloc(sizeof(*macro_start));
3155 macro_start->next = NULL;
3156 macro_start->text = nasm_quote(p, strlen(p));
3157 macro_start->type = TOK_STRING;
3158 macro_start->a.mac = NULL;
3159 if (xsl)
3160 nasm_free(xsl);
3163 * We now have a macro name, an implicit parameter count of
3164 * zero, and a string token to use as an expansion. Create
3165 * and store an SMacro.
3167 define_smacro(ctx, mname, casesense, 0, macro_start);
3168 free_tlist(tline);
3169 free_tlist(origline);
3170 return DIRECTIVE_FOUND;
3173 case PP_STRLEN:
3174 casesense = true;
3176 tline = tline->next;
3177 skip_white_(tline);
3178 tline = expand_id(tline);
3179 if (!tline || (tline->type != TOK_ID &&
3180 (tline->type != TOK_PREPROC_ID ||
3181 tline->text[1] != '$'))) {
3182 error(ERR_NONFATAL,
3183 "`%%strlen' expects a macro identifier as first parameter");
3184 free_tlist(origline);
3185 return DIRECTIVE_FOUND;
3187 ctx = get_ctx(tline->text, &mname, false);
3188 last = tline;
3189 tline = expand_smacro(tline->next);
3190 last->next = NULL;
3192 t = tline;
3193 while (tok_type_(t, TOK_WHITESPACE))
3194 t = t->next;
3195 /* t should now point to the string */
3196 if (t->type != TOK_STRING) {
3197 error(ERR_NONFATAL,
3198 "`%%strlen` requires string as second parameter");
3199 free_tlist(tline);
3200 free_tlist(origline);
3201 return DIRECTIVE_FOUND;
3204 macro_start = nasm_malloc(sizeof(*macro_start));
3205 macro_start->next = NULL;
3206 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3207 macro_start->a.mac = NULL;
3210 * We now have a macro name, an implicit parameter count of
3211 * zero, and a numeric token to use as an expansion. Create
3212 * and store an SMacro.
3214 define_smacro(ctx, mname, casesense, 0, macro_start);
3215 free_tlist(tline);
3216 free_tlist(origline);
3217 return DIRECTIVE_FOUND;
3219 case PP_STRCAT:
3220 casesense = true;
3222 tline = tline->next;
3223 skip_white_(tline);
3224 tline = expand_id(tline);
3225 if (!tline || (tline->type != TOK_ID &&
3226 (tline->type != TOK_PREPROC_ID ||
3227 tline->text[1] != '$'))) {
3228 error(ERR_NONFATAL,
3229 "`%%strcat' expects a macro identifier as first parameter");
3230 free_tlist(origline);
3231 return DIRECTIVE_FOUND;
3233 ctx = get_ctx(tline->text, &mname, false);
3234 last = tline;
3235 tline = expand_smacro(tline->next);
3236 last->next = NULL;
3238 len = 0;
3239 list_for_each(t, tline) {
3240 switch (t->type) {
3241 case TOK_WHITESPACE:
3242 break;
3243 case TOK_STRING:
3244 len += t->a.len = nasm_unquote(t->text, NULL);
3245 break;
3246 case TOK_OTHER:
3247 if (!strcmp(t->text, ",")) /* permit comma separators */
3248 break;
3249 /* else fall through */
3250 default:
3251 error(ERR_NONFATAL,
3252 "non-string passed to `%%strcat' (%d)", t->type);
3253 free_tlist(tline);
3254 free_tlist(origline);
3255 return DIRECTIVE_FOUND;
3259 p = pp = nasm_malloc(len);
3260 list_for_each(t, tline) {
3261 if (t->type == TOK_STRING) {
3262 memcpy(p, t->text, t->a.len);
3263 p += t->a.len;
3268 * We now have a macro name, an implicit parameter count of
3269 * zero, and a numeric token to use as an expansion. Create
3270 * and store an SMacro.
3272 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3273 macro_start->text = nasm_quote(pp, len);
3274 nasm_free(pp);
3275 define_smacro(ctx, mname, casesense, 0, macro_start);
3276 free_tlist(tline);
3277 free_tlist(origline);
3278 return DIRECTIVE_FOUND;
3280 case PP_SUBSTR:
3282 int64_t a1, a2;
3283 size_t len;
3285 casesense = true;
3287 tline = tline->next;
3288 skip_white_(tline);
3289 tline = expand_id(tline);
3290 if (!tline || (tline->type != TOK_ID &&
3291 (tline->type != TOK_PREPROC_ID ||
3292 tline->text[1] != '$'))) {
3293 error(ERR_NONFATAL,
3294 "`%%substr' expects a macro identifier as first parameter");
3295 free_tlist(origline);
3296 return DIRECTIVE_FOUND;
3298 ctx = get_ctx(tline->text, &mname, false);
3299 last = tline;
3300 tline = expand_smacro(tline->next);
3301 last->next = NULL;
3303 t = tline->next;
3304 while (tok_type_(t, TOK_WHITESPACE))
3305 t = t->next;
3307 /* t should now point to the string */
3308 if (t->type != TOK_STRING) {
3309 error(ERR_NONFATAL,
3310 "`%%substr` requires string as second parameter");
3311 free_tlist(tline);
3312 free_tlist(origline);
3313 return DIRECTIVE_FOUND;
3316 tt = t->next;
3317 tptr = &tt;
3318 tokval.t_type = TOKEN_INVALID;
3319 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3320 pass, error, NULL);
3321 if (!evalresult) {
3322 free_tlist(tline);
3323 free_tlist(origline);
3324 return DIRECTIVE_FOUND;
3325 } else if (!is_simple(evalresult)) {
3326 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3327 free_tlist(tline);
3328 free_tlist(origline);
3329 return DIRECTIVE_FOUND;
3331 a1 = evalresult->value-1;
3333 while (tok_type_(tt, TOK_WHITESPACE))
3334 tt = tt->next;
3335 if (!tt) {
3336 a2 = 1; /* Backwards compatibility: one character */
3337 } else {
3338 tokval.t_type = TOKEN_INVALID;
3339 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3340 pass, error, NULL);
3341 if (!evalresult) {
3342 free_tlist(tline);
3343 free_tlist(origline);
3344 return DIRECTIVE_FOUND;
3345 } else if (!is_simple(evalresult)) {
3346 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3347 free_tlist(tline);
3348 free_tlist(origline);
3349 return DIRECTIVE_FOUND;
3351 a2 = evalresult->value;
3354 len = nasm_unquote(t->text, NULL);
3355 if (a2 < 0)
3356 a2 = a2+1+len-a1;
3357 if (a1+a2 > (int64_t)len)
3358 a2 = len-a1;
3360 macro_start = nasm_malloc(sizeof(*macro_start));
3361 macro_start->next = NULL;
3362 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3363 macro_start->type = TOK_STRING;
3364 macro_start->a.mac = NULL;
3367 * We now have a macro name, an implicit parameter count of
3368 * zero, and a numeric token to use as an expansion. Create
3369 * and store an SMacro.
3371 define_smacro(ctx, mname, casesense, 0, macro_start);
3372 free_tlist(tline);
3373 free_tlist(origline);
3374 return DIRECTIVE_FOUND;
3377 case PP_ASSIGN:
3378 case PP_IASSIGN:
3379 casesense = (i == PP_ASSIGN);
3381 tline = tline->next;
3382 skip_white_(tline);
3383 tline = expand_id(tline);
3384 if (!tline || (tline->type != TOK_ID &&
3385 (tline->type != TOK_PREPROC_ID ||
3386 tline->text[1] != '$'))) {
3387 error(ERR_NONFATAL,
3388 "`%%%sassign' expects a macro identifier",
3389 (i == PP_IASSIGN ? "i" : ""));
3390 free_tlist(origline);
3391 return DIRECTIVE_FOUND;
3393 ctx = get_ctx(tline->text, &mname, false);
3394 last = tline;
3395 tline = expand_smacro(tline->next);
3396 last->next = NULL;
3398 t = tline;
3399 tptr = &t;
3400 tokval.t_type = TOKEN_INVALID;
3401 evalresult =
3402 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3403 free_tlist(tline);
3404 if (!evalresult) {
3405 free_tlist(origline);
3406 return DIRECTIVE_FOUND;
3409 if (tokval.t_type)
3410 error(ERR_WARNING|ERR_PASS1,
3411 "trailing garbage after expression ignored");
3413 if (!is_simple(evalresult)) {
3414 error(ERR_NONFATAL,
3415 "non-constant value given to `%%%sassign'",
3416 (i == PP_IASSIGN ? "i" : ""));
3417 free_tlist(origline);
3418 return DIRECTIVE_FOUND;
3421 macro_start = nasm_malloc(sizeof(*macro_start));
3422 macro_start->next = NULL;
3423 make_tok_num(macro_start, reloc_value(evalresult));
3424 macro_start->a.mac = NULL;
3427 * We now have a macro name, an implicit parameter count of
3428 * zero, and a numeric token to use as an expansion. Create
3429 * and store an SMacro.
3431 define_smacro(ctx, mname, casesense, 0, macro_start);
3432 free_tlist(origline);
3433 return DIRECTIVE_FOUND;
3435 case PP_LINE:
3437 * Syntax is `%line nnn[+mmm] [filename]'
3439 tline = tline->next;
3440 skip_white_(tline);
3441 if (!tok_type_(tline, TOK_NUMBER)) {
3442 error(ERR_NONFATAL, "`%%line' expects line number");
3443 free_tlist(origline);
3444 return DIRECTIVE_FOUND;
3446 k = readnum(tline->text, &err);
3447 m = 1;
3448 tline = tline->next;
3449 if (tok_is_(tline, "+")) {
3450 tline = tline->next;
3451 if (!tok_type_(tline, TOK_NUMBER)) {
3452 error(ERR_NONFATAL, "`%%line' expects line increment");
3453 free_tlist(origline);
3454 return DIRECTIVE_FOUND;
3456 m = readnum(tline->text, &err);
3457 tline = tline->next;
3459 skip_white_(tline);
3460 src_set_linnum(k);
3461 istk->lineinc = m;
3462 if (tline) {
3463 nasm_free(src_set_fname(detoken(tline, false)));
3465 free_tlist(origline);
3466 return DIRECTIVE_FOUND;
3468 default:
3469 error(ERR_FATAL,
3470 "preprocessor directive `%s' not yet implemented",
3471 pp_directives[i]);
3472 return DIRECTIVE_FOUND;
3477 * Ensure that a macro parameter contains a condition code and
3478 * nothing else. Return the condition code index if so, or -1
3479 * otherwise.
3481 static int find_cc(Token * t)
3483 Token *tt;
3484 int i, j, k, m;
3486 if (!t)
3487 return -1; /* Probably a %+ without a space */
3489 skip_white_(t);
3490 if (t->type != TOK_ID)
3491 return -1;
3492 tt = t->next;
3493 skip_white_(tt);
3494 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3495 return -1;
3497 i = -1;
3498 j = ARRAY_SIZE(conditions);
3499 while (j - i > 1) {
3500 k = (j + i) / 2;
3501 m = nasm_stricmp(t->text, conditions[k]);
3502 if (m == 0) {
3503 i = k;
3504 j = -2;
3505 break;
3506 } else if (m < 0) {
3507 j = k;
3508 } else
3509 i = k;
3511 if (j != -2)
3512 return -1;
3513 return i;
3516 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3518 Token **tail, *t, *tt;
3519 Token **paste_head;
3520 bool did_paste = false;
3521 char *tmp;
3523 /* Now handle token pasting... */
3524 paste_head = NULL;
3525 tail = head;
3526 while ((t = *tail) && (tt = t->next)) {
3527 switch (t->type) {
3528 case TOK_WHITESPACE:
3529 if (tt->type == TOK_WHITESPACE) {
3530 /* Zap adjacent whitespace tokens */
3531 t->next = delete_Token(tt);
3532 } else {
3533 /* Do not advance paste_head here */
3534 tail = &t->next;
3536 break;
3537 case TOK_ID:
3538 case TOK_NUMBER:
3539 case TOK_FLOAT:
3541 size_t len = 0;
3542 char *tmp, *p;
3544 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3545 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3546 tt->type == TOK_OTHER)) {
3547 len += strlen(tt->text);
3548 tt = tt->next;
3552 * Now tt points to the first token after
3553 * the potential paste area...
3555 if (tt != t->next) {
3556 /* We have at least two tokens... */
3557 len += strlen(t->text);
3558 p = tmp = nasm_malloc(len+1);
3560 while (t != tt) {
3561 strcpy(p, t->text);
3562 p = strchr(p, '\0');
3563 t = delete_Token(t);
3566 t = *tail = tokenize(tmp);
3567 nasm_free(tmp);
3569 while (t->next) {
3570 tail = &t->next;
3571 t = t->next;
3573 t->next = tt; /* Attach the remaining token chain */
3575 did_paste = true;
3577 paste_head = tail;
3578 tail = &t->next;
3579 break;
3581 case TOK_PASTE: /* %+ */
3582 if (handle_paste_tokens) {
3583 /* Zap %+ and whitespace tokens to the right */
3584 while (t && (t->type == TOK_WHITESPACE ||
3585 t->type == TOK_PASTE))
3586 t = *tail = delete_Token(t);
3587 if (!paste_head || !t)
3588 break; /* Nothing to paste with */
3589 tail = paste_head;
3590 t = *tail;
3591 tt = t->next;
3592 while (tok_type_(tt, TOK_WHITESPACE))
3593 tt = t->next = delete_Token(tt);
3595 if (tt) {
3596 tmp = nasm_strcat(t->text, tt->text);
3597 delete_Token(t);
3598 tt = delete_Token(tt);
3599 t = *tail = tokenize(tmp);
3600 nasm_free(tmp);
3601 while (t->next) {
3602 tail = &t->next;
3603 t = t->next;
3605 t->next = tt; /* Attach the remaining token chain */
3606 did_paste = true;
3608 paste_head = tail;
3609 tail = &t->next;
3610 break;
3612 /* else fall through */
3613 default:
3614 tail = &t->next;
3615 if (!tok_type_(t->next, TOK_WHITESPACE))
3616 paste_head = tail;
3617 break;
3620 return did_paste;
3624 * expands to a list of tokens from %{x:y}
3626 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3628 Token *t = tline, **tt, *tm, *head;
3629 char *pos;
3630 int fst, lst, j, i;
3632 pos = strchr(tline->text, ':');
3633 nasm_assert(pos);
3635 lst = atoi(pos + 1);
3636 fst = atoi(tline->text + 1);
3639 * only macros params are accounted so
3640 * if someone passes %0 -- we reject such
3641 * value(s)
3643 if (lst == 0 || fst == 0)
3644 goto err;
3646 /* the values should be sane */
3647 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3648 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3649 goto err;
3651 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3652 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3654 /* counted from zero */
3655 fst--, lst--;
3658 * it will be at least one token
3660 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3661 t = new_Token(NULL, tm->type, tm->text, 0);
3662 head = t, tt = &t->next;
3663 if (fst < lst) {
3664 for (i = fst + 1; i <= lst; i++) {
3665 t = new_Token(NULL, TOK_OTHER, ",", 0);
3666 *tt = t, tt = &t->next;
3667 j = (i + mac->rotate) % mac->nparam;
3668 tm = mac->params[j];
3669 t = new_Token(NULL, tm->type, tm->text, 0);
3670 *tt = t, tt = &t->next;
3672 } else {
3673 for (i = fst - 1; i >= lst; i--) {
3674 t = new_Token(NULL, TOK_OTHER, ",", 0);
3675 *tt = t, tt = &t->next;
3676 j = (i + mac->rotate) % mac->nparam;
3677 tm = mac->params[j];
3678 t = new_Token(NULL, tm->type, tm->text, 0);
3679 *tt = t, tt = &t->next;
3683 *last = tt;
3684 return head;
3686 err:
3687 error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3688 &tline->text[1]);
3689 return tline;
3693 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3694 * %-n) and MMacro-local identifiers (%%foo) as well as
3695 * macro indirection (%[...]) and range (%{..:..}).
3697 static Token *expand_mmac_params(Token * tline)
3699 Token *t, *tt, **tail, *thead;
3700 bool changed = false;
3701 char *pos;
3703 tail = &thead;
3704 thead = NULL;
3706 while (tline) {
3707 if (tline->type == TOK_PREPROC_ID &&
3708 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3709 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3710 tline->text[1] == '%')) {
3711 char *text = NULL;
3712 int type = 0, cc; /* type = 0 to placate optimisers */
3713 char tmpbuf[30];
3714 unsigned int n;
3715 int i;
3716 MMacro *mac;
3718 t = tline;
3719 tline = tline->next;
3721 mac = istk->mstk;
3722 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3723 mac = mac->next_active;
3724 if (!mac) {
3725 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3726 } else {
3727 pos = strchr(t->text, ':');
3728 if (!pos) {
3729 switch (t->text[1]) {
3731 * We have to make a substitution of one of the
3732 * forms %1, %-1, %+1, %%foo, %0.
3734 case '0':
3735 type = TOK_NUMBER;
3736 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3737 text = nasm_strdup(tmpbuf);
3738 break;
3739 case '%':
3740 type = TOK_ID;
3741 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3742 mac->unique);
3743 text = nasm_strcat(tmpbuf, t->text + 2);
3744 break;
3745 case '-':
3746 n = atoi(t->text + 2) - 1;
3747 if (n >= mac->nparam)
3748 tt = NULL;
3749 else {
3750 if (mac->nparam > 1)
3751 n = (n + mac->rotate) % mac->nparam;
3752 tt = mac->params[n];
3754 cc = find_cc(tt);
3755 if (cc == -1) {
3756 error(ERR_NONFATAL,
3757 "macro parameter %d is not a condition code",
3758 n + 1);
3759 text = NULL;
3760 } else {
3761 type = TOK_ID;
3762 if (inverse_ccs[cc] == -1) {
3763 error(ERR_NONFATAL,
3764 "condition code `%s' is not invertible",
3765 conditions[cc]);
3766 text = NULL;
3767 } else
3768 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3770 break;
3771 case '+':
3772 n = atoi(t->text + 2) - 1;
3773 if (n >= mac->nparam)
3774 tt = NULL;
3775 else {
3776 if (mac->nparam > 1)
3777 n = (n + mac->rotate) % mac->nparam;
3778 tt = mac->params[n];
3780 cc = find_cc(tt);
3781 if (cc == -1) {
3782 error(ERR_NONFATAL,
3783 "macro parameter %d is not a condition code",
3784 n + 1);
3785 text = NULL;
3786 } else {
3787 type = TOK_ID;
3788 text = nasm_strdup(conditions[cc]);
3790 break;
3791 default:
3792 n = atoi(t->text + 1) - 1;
3793 if (n >= mac->nparam)
3794 tt = NULL;
3795 else {
3796 if (mac->nparam > 1)
3797 n = (n + mac->rotate) % mac->nparam;
3798 tt = mac->params[n];
3800 if (tt) {
3801 for (i = 0; i < mac->paramlen[n]; i++) {
3802 *tail = new_Token(NULL, tt->type, tt->text, 0);
3803 tail = &(*tail)->next;
3804 tt = tt->next;
3807 text = NULL; /* we've done it here */
3808 break;
3810 } else {
3812 * seems we have a parameters range here
3814 Token *head, **last;
3815 head = expand_mmac_params_range(mac, t, &last);
3816 if (head != t) {
3817 *tail = head;
3818 *last = tline;
3819 tline = head;
3820 text = NULL;
3824 if (!text) {
3825 delete_Token(t);
3826 } else {
3827 *tail = t;
3828 tail = &t->next;
3829 t->type = type;
3830 nasm_free(t->text);
3831 t->text = text;
3832 t->a.mac = NULL;
3834 changed = true;
3835 continue;
3836 } else if (tline->type == TOK_INDIRECT) {
3837 t = tline;
3838 tline = tline->next;
3839 tt = tokenize(t->text);
3840 tt = expand_mmac_params(tt);
3841 tt = expand_smacro(tt);
3842 *tail = tt;
3843 while (tt) {
3844 tt->a.mac = NULL; /* Necessary? */
3845 tail = &tt->next;
3846 tt = tt->next;
3848 delete_Token(t);
3849 changed = true;
3850 } else {
3851 t = *tail = tline;
3852 tline = tline->next;
3853 t->a.mac = NULL;
3854 tail = &t->next;
3857 *tail = NULL;
3859 if (changed)
3860 paste_tokens(&thead, false);
3862 return thead;
3866 * Expand all single-line macro calls made in the given line.
3867 * Return the expanded version of the line. The original is deemed
3868 * to be destroyed in the process. (In reality we'll just move
3869 * Tokens from input to output a lot of the time, rather than
3870 * actually bothering to destroy and replicate.)
3873 static Token *expand_smacro(Token * tline)
3875 Token *t, *tt, *mstart, **tail, *thead;
3876 SMacro *head = NULL, *m;
3877 Token **params;
3878 int *paramsize;
3879 unsigned int nparam, sparam;
3880 int brackets;
3881 Token *org_tline = tline;
3882 Context *ctx;
3883 const char *mname;
3884 int deadman = DEADMAN_LIMIT;
3885 bool expanded;
3888 * Trick: we should avoid changing the start token pointer since it can
3889 * be contained in "next" field of other token. Because of this
3890 * we allocate a copy of first token and work with it; at the end of
3891 * routine we copy it back
3893 if (org_tline) {
3894 tline = new_Token(org_tline->next, org_tline->type,
3895 org_tline->text, 0);
3896 tline->a.mac = org_tline->a.mac;
3897 nasm_free(org_tline->text);
3898 org_tline->text = NULL;
3901 expanded = true; /* Always expand %+ at least once */
3903 again:
3904 thead = NULL;
3905 tail = &thead;
3907 while (tline) { /* main token loop */
3908 if (!--deadman) {
3909 error(ERR_NONFATAL, "interminable macro recursion");
3910 goto err;
3913 if ((mname = tline->text)) {
3914 /* if this token is a local macro, look in local context */
3915 if (tline->type == TOK_ID) {
3916 head = (SMacro *)hash_findix(&smacros, mname);
3917 } else if (tline->type == TOK_PREPROC_ID) {
3918 ctx = get_ctx(mname, &mname, true);
3919 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
3920 } else
3921 head = NULL;
3924 * We've hit an identifier. As in is_mmacro below, we first
3925 * check whether the identifier is a single-line macro at
3926 * all, then think about checking for parameters if
3927 * necessary.
3929 list_for_each(m, head)
3930 if (!mstrcmp(m->name, mname, m->casesense))
3931 break;
3932 if (m) {
3933 mstart = tline;
3934 params = NULL;
3935 paramsize = NULL;
3936 if (m->nparam == 0) {
3938 * Simple case: the macro is parameterless. Discard the
3939 * one token that the macro call took, and push the
3940 * expansion back on the to-do stack.
3942 if (!m->expansion) {
3943 if (!strcmp("__FILE__", m->name)) {
3944 int32_t num = 0;
3945 char *file = NULL;
3946 src_get(&num, &file);
3947 tline->text = nasm_quote(file, strlen(file));
3948 tline->type = TOK_STRING;
3949 nasm_free(file);
3950 continue;
3952 if (!strcmp("__LINE__", m->name)) {
3953 nasm_free(tline->text);
3954 make_tok_num(tline, src_get_linnum());
3955 continue;
3957 if (!strcmp("__BITS__", m->name)) {
3958 nasm_free(tline->text);
3959 make_tok_num(tline, globalbits);
3960 continue;
3962 tline = delete_Token(tline);
3963 continue;
3965 } else {
3967 * Complicated case: at least one macro with this name
3968 * exists and takes parameters. We must find the
3969 * parameters in the call, count them, find the SMacro
3970 * that corresponds to that form of the macro call, and
3971 * substitute for the parameters when we expand. What a
3972 * pain.
3974 /*tline = tline->next;
3975 skip_white_(tline); */
3976 do {
3977 t = tline->next;
3978 while (tok_type_(t, TOK_SMAC_END)) {
3979 t->a.mac->in_progress = false;
3980 t->text = NULL;
3981 t = tline->next = delete_Token(t);
3983 tline = t;
3984 } while (tok_type_(tline, TOK_WHITESPACE));
3985 if (!tok_is_(tline, "(")) {
3987 * This macro wasn't called with parameters: ignore
3988 * the call. (Behaviour borrowed from gnu cpp.)
3990 tline = mstart;
3991 m = NULL;
3992 } else {
3993 int paren = 0;
3994 int white = 0;
3995 brackets = 0;
3996 nparam = 0;
3997 sparam = PARAM_DELTA;
3998 params = nasm_malloc(sparam * sizeof(Token *));
3999 params[0] = tline->next;
4000 paramsize = nasm_malloc(sparam * sizeof(int));
4001 paramsize[0] = 0;
4002 while (true) { /* parameter loop */
4004 * For some unusual expansions
4005 * which concatenates function call
4007 t = tline->next;
4008 while (tok_type_(t, TOK_SMAC_END)) {
4009 t->a.mac->in_progress = false;
4010 t->text = NULL;
4011 t = tline->next = delete_Token(t);
4013 tline = t;
4015 if (!tline) {
4016 error(ERR_NONFATAL,
4017 "macro call expects terminating `)'");
4018 break;
4020 if (tline->type == TOK_WHITESPACE
4021 && brackets <= 0) {
4022 if (paramsize[nparam])
4023 white++;
4024 else
4025 params[nparam] = tline->next;
4026 continue; /* parameter loop */
4028 if (tline->type == TOK_OTHER
4029 && tline->text[1] == 0) {
4030 char ch = tline->text[0];
4031 if (ch == ',' && !paren && brackets <= 0) {
4032 if (++nparam >= sparam) {
4033 sparam += PARAM_DELTA;
4034 params = nasm_realloc(params,
4035 sparam * sizeof(Token *));
4036 paramsize = nasm_realloc(paramsize,
4037 sparam * sizeof(int));
4039 params[nparam] = tline->next;
4040 paramsize[nparam] = 0;
4041 white = 0;
4042 continue; /* parameter loop */
4044 if (ch == '{' &&
4045 (brackets > 0 || (brackets == 0 &&
4046 !paramsize[nparam])))
4048 if (!(brackets++)) {
4049 params[nparam] = tline->next;
4050 continue; /* parameter loop */
4053 if (ch == '}' && brackets > 0)
4054 if (--brackets == 0) {
4055 brackets = -1;
4056 continue; /* parameter loop */
4058 if (ch == '(' && !brackets)
4059 paren++;
4060 if (ch == ')' && brackets <= 0)
4061 if (--paren < 0)
4062 break;
4064 if (brackets < 0) {
4065 brackets = 0;
4066 error(ERR_NONFATAL, "braces do not "
4067 "enclose all of macro parameter");
4069 paramsize[nparam] += white + 1;
4070 white = 0;
4071 } /* parameter loop */
4072 nparam++;
4073 while (m && (m->nparam != nparam ||
4074 mstrcmp(m->name, mname,
4075 m->casesense)))
4076 m = m->next;
4077 if (!m)
4078 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4079 "macro `%s' exists, "
4080 "but not taking %d parameters",
4081 mstart->text, nparam);
4084 if (m && m->in_progress)
4085 m = NULL;
4086 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4088 * Design question: should we handle !tline, which
4089 * indicates missing ')' here, or expand those
4090 * macros anyway, which requires the (t) test a few
4091 * lines down?
4093 nasm_free(params);
4094 nasm_free(paramsize);
4095 tline = mstart;
4096 } else {
4098 * Expand the macro: we are placed on the last token of the
4099 * call, so that we can easily split the call from the
4100 * following tokens. We also start by pushing an SMAC_END
4101 * token for the cycle removal.
4103 t = tline;
4104 if (t) {
4105 tline = t->next;
4106 t->next = NULL;
4108 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4109 tt->a.mac = m;
4110 m->in_progress = true;
4111 tline = tt;
4112 list_for_each(t, m->expansion) {
4113 if (t->type >= TOK_SMAC_PARAM) {
4114 Token *pcopy = tline, **ptail = &pcopy;
4115 Token *ttt, *pt;
4116 int i;
4118 ttt = params[t->type - TOK_SMAC_PARAM];
4119 i = paramsize[t->type - TOK_SMAC_PARAM];
4120 while (--i >= 0) {
4121 pt = *ptail = new_Token(tline, ttt->type,
4122 ttt->text, 0);
4123 ptail = &pt->next;
4124 ttt = ttt->next;
4126 tline = pcopy;
4127 } else if (t->type == TOK_PREPROC_Q) {
4128 tt = new_Token(tline, TOK_ID, mname, 0);
4129 tline = tt;
4130 } else if (t->type == TOK_PREPROC_QQ) {
4131 tt = new_Token(tline, TOK_ID, m->name, 0);
4132 tline = tt;
4133 } else {
4134 tt = new_Token(tline, t->type, t->text, 0);
4135 tline = tt;
4140 * Having done that, get rid of the macro call, and clean
4141 * up the parameters.
4143 nasm_free(params);
4144 nasm_free(paramsize);
4145 free_tlist(mstart);
4146 expanded = true;
4147 continue; /* main token loop */
4152 if (tline->type == TOK_SMAC_END) {
4153 tline->a.mac->in_progress = false;
4154 tline = delete_Token(tline);
4155 } else {
4156 t = *tail = tline;
4157 tline = tline->next;
4158 t->a.mac = NULL;
4159 t->next = NULL;
4160 tail = &t->next;
4165 * Now scan the entire line and look for successive TOK_IDs that resulted
4166 * after expansion (they can't be produced by tokenize()). The successive
4167 * TOK_IDs should be concatenated.
4168 * Also we look for %+ tokens and concatenate the tokens before and after
4169 * them (without white spaces in between).
4171 if (expanded && paste_tokens(&thead, true)) {
4173 * If we concatenated something, *and* we had previously expanded
4174 * an actual macro, scan the lines again for macros...
4176 tline = thead;
4177 expanded = false;
4178 goto again;
4181 err:
4182 if (org_tline) {
4183 if (thead) {
4184 *org_tline = *thead;
4185 /* since we just gave text to org_line, don't free it */
4186 thead->text = NULL;
4187 delete_Token(thead);
4188 } else {
4189 /* the expression expanded to empty line;
4190 we can't return NULL for some reasons
4191 we just set the line to a single WHITESPACE token. */
4192 memset(org_tline, 0, sizeof(*org_tline));
4193 org_tline->text = NULL;
4194 org_tline->type = TOK_WHITESPACE;
4196 thead = org_tline;
4199 return thead;
4203 * Similar to expand_smacro but used exclusively with macro identifiers
4204 * right before they are fetched in. The reason is that there can be
4205 * identifiers consisting of several subparts. We consider that if there
4206 * are more than one element forming the name, user wants a expansion,
4207 * otherwise it will be left as-is. Example:
4209 * %define %$abc cde
4211 * the identifier %$abc will be left as-is so that the handler for %define
4212 * will suck it and define the corresponding value. Other case:
4214 * %define _%$abc cde
4216 * In this case user wants name to be expanded *before* %define starts
4217 * working, so we'll expand %$abc into something (if it has a value;
4218 * otherwise it will be left as-is) then concatenate all successive
4219 * PP_IDs into one.
4221 static Token *expand_id(Token * tline)
4223 Token *cur, *oldnext = NULL;
4225 if (!tline || !tline->next)
4226 return tline;
4228 cur = tline;
4229 while (cur->next &&
4230 (cur->next->type == TOK_ID ||
4231 cur->next->type == TOK_PREPROC_ID
4232 || cur->next->type == TOK_NUMBER))
4233 cur = cur->next;
4235 /* If identifier consists of just one token, don't expand */
4236 if (cur == tline)
4237 return tline;
4239 if (cur) {
4240 oldnext = cur->next; /* Detach the tail past identifier */
4241 cur->next = NULL; /* so that expand_smacro stops here */
4244 tline = expand_smacro(tline);
4246 if (cur) {
4247 /* expand_smacro possibly changhed tline; re-scan for EOL */
4248 cur = tline;
4249 while (cur && cur->next)
4250 cur = cur->next;
4251 if (cur)
4252 cur->next = oldnext;
4255 return tline;
4259 * Determine whether the given line constitutes a multi-line macro
4260 * call, and return the MMacro structure called if so. Doesn't have
4261 * to check for an initial label - that's taken care of in
4262 * expand_mmacro - but must check numbers of parameters. Guaranteed
4263 * to be called with tline->type == TOK_ID, so the putative macro
4264 * name is easy to find.
4266 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4268 MMacro *head, *m;
4269 Token **params;
4270 int nparam;
4272 head = (MMacro *) hash_findix(&mmacros, tline->text);
4275 * Efficiency: first we see if any macro exists with the given
4276 * name. If not, we can return NULL immediately. _Then_ we
4277 * count the parameters, and then we look further along the
4278 * list if necessary to find the proper MMacro.
4280 list_for_each(m, head)
4281 if (!mstrcmp(m->name, tline->text, m->casesense))
4282 break;
4283 if (!m)
4284 return NULL;
4287 * OK, we have a potential macro. Count and demarcate the
4288 * parameters.
4290 count_mmac_params(tline->next, &nparam, &params);
4293 * So we know how many parameters we've got. Find the MMacro
4294 * structure that handles this number.
4296 while (m) {
4297 if (m->nparam_min <= nparam
4298 && (m->plus || nparam <= m->nparam_max)) {
4300 * This one is right. Just check if cycle removal
4301 * prohibits us using it before we actually celebrate...
4303 if (m->in_progress > m->max_depth) {
4304 if (m->max_depth > 0) {
4305 error(ERR_WARNING,
4306 "reached maximum recursion depth of %i",
4307 m->max_depth);
4309 nasm_free(params);
4310 return NULL;
4313 * It's right, and we can use it. Add its default
4314 * parameters to the end of our list if necessary.
4316 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4317 params =
4318 nasm_realloc(params,
4319 ((m->nparam_min + m->ndefs +
4320 1) * sizeof(*params)));
4321 while (nparam < m->nparam_min + m->ndefs) {
4322 params[nparam] = m->defaults[nparam - m->nparam_min];
4323 nparam++;
4327 * If we've gone over the maximum parameter count (and
4328 * we're in Plus mode), ignore parameters beyond
4329 * nparam_max.
4331 if (m->plus && nparam > m->nparam_max)
4332 nparam = m->nparam_max;
4334 * Then terminate the parameter list, and leave.
4336 if (!params) { /* need this special case */
4337 params = nasm_malloc(sizeof(*params));
4338 nparam = 0;
4340 params[nparam] = NULL;
4341 *params_array = params;
4342 return m;
4345 * This one wasn't right: look for the next one with the
4346 * same name.
4348 list_for_each(m, m->next)
4349 if (!mstrcmp(m->name, tline->text, m->casesense))
4350 break;
4354 * After all that, we didn't find one with the right number of
4355 * parameters. Issue a warning, and fail to expand the macro.
4357 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4358 "macro `%s' exists, but not taking %d parameters",
4359 tline->text, nparam);
4360 nasm_free(params);
4361 return NULL;
4366 * Save MMacro invocation specific fields in
4367 * preparation for a recursive macro expansion
4369 static void push_mmacro(MMacro *m)
4371 MMacroInvocation *i;
4373 i = nasm_malloc(sizeof(MMacroInvocation));
4374 i->prev = m->prev;
4375 i->params = m->params;
4376 i->iline = m->iline;
4377 i->nparam = m->nparam;
4378 i->rotate = m->rotate;
4379 i->paramlen = m->paramlen;
4380 i->unique = m->unique;
4381 i->condcnt = m->condcnt;
4382 m->prev = i;
4387 * Restore MMacro invocation specific fields that were
4388 * saved during a previous recursive macro expansion
4390 static void pop_mmacro(MMacro *m)
4392 MMacroInvocation *i;
4394 if (m->prev) {
4395 i = m->prev;
4396 m->prev = i->prev;
4397 m->params = i->params;
4398 m->iline = i->iline;
4399 m->nparam = i->nparam;
4400 m->rotate = i->rotate;
4401 m->paramlen = i->paramlen;
4402 m->unique = i->unique;
4403 m->condcnt = i->condcnt;
4404 nasm_free(i);
4410 * Expand the multi-line macro call made by the given line, if
4411 * there is one to be expanded. If there is, push the expansion on
4412 * istk->expansion and return 1. Otherwise return 0.
4414 static int expand_mmacro(Token * tline)
4416 Token *startline = tline;
4417 Token *label = NULL;
4418 int dont_prepend = 0;
4419 Token **params, *t, *mtok, *tt;
4420 MMacro *m;
4421 Line *l, *ll;
4422 int i, nparam, *paramlen;
4423 const char *mname;
4425 t = tline;
4426 skip_white_(t);
4427 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4428 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4429 return 0;
4430 mtok = t;
4431 m = is_mmacro(t, &params);
4432 if (m) {
4433 mname = t->text;
4434 } else {
4435 Token *last;
4437 * We have an id which isn't a macro call. We'll assume
4438 * it might be a label; we'll also check to see if a
4439 * colon follows it. Then, if there's another id after
4440 * that lot, we'll check it again for macro-hood.
4442 label = last = t;
4443 t = t->next;
4444 if (tok_type_(t, TOK_WHITESPACE))
4445 last = t, t = t->next;
4446 if (tok_is_(t, ":")) {
4447 dont_prepend = 1;
4448 last = t, t = t->next;
4449 if (tok_type_(t, TOK_WHITESPACE))
4450 last = t, t = t->next;
4452 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4453 return 0;
4454 last->next = NULL;
4455 mname = t->text;
4456 tline = t;
4460 * Fix up the parameters: this involves stripping leading and
4461 * trailing whitespace, then stripping braces if they are
4462 * present.
4464 for (nparam = 0; params[nparam]; nparam++) ;
4465 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4467 for (i = 0; params[i]; i++) {
4468 int brace = false;
4469 int comma = (!m->plus || i < nparam - 1);
4471 t = params[i];
4472 skip_white_(t);
4473 if (tok_is_(t, "{"))
4474 t = t->next, brace = true, comma = false;
4475 params[i] = t;
4476 paramlen[i] = 0;
4477 while (t) {
4478 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4479 break; /* ... because we have hit a comma */
4480 if (comma && t->type == TOK_WHITESPACE
4481 && tok_is_(t->next, ","))
4482 break; /* ... or a space then a comma */
4483 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4484 break; /* ... or a brace */
4485 t = t->next;
4486 paramlen[i]++;
4491 * OK, we have a MMacro structure together with a set of
4492 * parameters. We must now go through the expansion and push
4493 * copies of each Line on to istk->expansion. Substitution of
4494 * parameter tokens and macro-local tokens doesn't get done
4495 * until the single-line macro substitution process; this is
4496 * because delaying them allows us to change the semantics
4497 * later through %rotate.
4499 * First, push an end marker on to istk->expansion, mark this
4500 * macro as in progress, and set up its invocation-specific
4501 * variables.
4503 ll = nasm_malloc(sizeof(Line));
4504 ll->next = istk->expansion;
4505 ll->finishes = m;
4506 ll->first = NULL;
4507 istk->expansion = ll;
4510 * Save the previous MMacro expansion in the case of
4511 * macro recursion
4513 if (m->max_depth && m->in_progress)
4514 push_mmacro(m);
4516 m->in_progress ++;
4517 m->params = params;
4518 m->iline = tline;
4519 m->nparam = nparam;
4520 m->rotate = 0;
4521 m->paramlen = paramlen;
4522 m->unique = unique++;
4523 m->lineno = 0;
4524 m->condcnt = 0;
4526 m->next_active = istk->mstk;
4527 istk->mstk = m;
4529 list_for_each(l, m->expansion) {
4530 Token **tail;
4532 ll = nasm_malloc(sizeof(Line));
4533 ll->finishes = NULL;
4534 ll->next = istk->expansion;
4535 istk->expansion = ll;
4536 tail = &ll->first;
4538 list_for_each(t, l->first) {
4539 Token *x = t;
4540 switch (t->type) {
4541 case TOK_PREPROC_Q:
4542 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4543 break;
4544 case TOK_PREPROC_QQ:
4545 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4546 break;
4547 case TOK_PREPROC_ID:
4548 if (t->text[1] == '0' && t->text[2] == '0') {
4549 dont_prepend = -1;
4550 x = label;
4551 if (!x)
4552 continue;
4554 /* fall through */
4555 default:
4556 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4557 break;
4559 tail = &tt->next;
4561 *tail = NULL;
4565 * If we had a label, push it on as the first line of
4566 * the macro expansion.
4568 if (label) {
4569 if (dont_prepend < 0)
4570 free_tlist(startline);
4571 else {
4572 ll = nasm_malloc(sizeof(Line));
4573 ll->finishes = NULL;
4574 ll->next = istk->expansion;
4575 istk->expansion = ll;
4576 ll->first = startline;
4577 if (!dont_prepend) {
4578 while (label->next)
4579 label = label->next;
4580 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4585 list->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4587 return 1;
4590 /* The function that actually does the error reporting */
4591 static void verror(int severity, const char *fmt, va_list arg)
4593 char buff[1024];
4595 vsnprintf(buff, sizeof(buff), fmt, arg);
4597 if (istk && istk->mstk && istk->mstk->name)
4598 nasm_error(severity, "(%s:%d) %s", istk->mstk->name,
4599 istk->mstk->lineno, buff);
4600 else
4601 nasm_error(severity, "%s", buff);
4605 * Since preprocessor always operate only on the line that didn't
4606 * arrived yet, we should always use ERR_OFFBY1.
4608 static void error(int severity, const char *fmt, ...)
4610 va_list arg;
4612 /* If we're in a dead branch of IF or something like it, ignore the error */
4613 if (istk && istk->conds && !emitting(istk->conds->state))
4614 return;
4616 va_start(arg, fmt);
4617 verror(severity, fmt, arg);
4618 va_end(arg);
4622 * Because %else etc are evaluated in the state context
4623 * of the previous branch, errors might get lost with error():
4624 * %if 0 ... %else trailing garbage ... %endif
4625 * So %else etc should report errors with this function.
4627 static void error_precond(int severity, const char *fmt, ...)
4629 va_list arg;
4631 /* Only ignore the error if it's really in a dead branch */
4632 if (istk && istk->conds && istk->conds->state == COND_NEVER)
4633 return;
4635 va_start(arg, fmt);
4636 verror(severity, fmt, arg);
4637 va_end(arg);
4640 static void
4641 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4643 Token *t;
4645 cstk = NULL;
4646 istk = nasm_malloc(sizeof(Include));
4647 istk->next = NULL;
4648 istk->conds = NULL;
4649 istk->expansion = NULL;
4650 istk->mstk = NULL;
4651 istk->fp = fopen(file, "r");
4652 istk->fname = NULL;
4653 src_set_fname(nasm_strdup(file));
4654 src_set_linnum(0);
4655 istk->lineinc = 1;
4656 if (!istk->fp)
4657 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4658 file);
4659 defining = NULL;
4660 nested_mac_count = 0;
4661 nested_rep_count = 0;
4662 init_macros();
4663 unique = 0;
4664 if (tasm_compatible_mode) {
4665 stdmacpos = nasm_stdmac;
4666 } else {
4667 stdmacpos = nasm_stdmac_after_tasm;
4669 any_extrastdmac = extrastdmac && *extrastdmac;
4670 do_predef = true;
4671 list = listgen;
4674 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4675 * The caller, however, will also pass in 3 for preprocess-only so
4676 * we can set __PASS__ accordingly.
4678 pass = apass > 2 ? 2 : apass;
4680 dephead = deptail = deplist;
4681 if (deplist) {
4682 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4683 sl->next = NULL;
4684 strcpy(sl->str, file);
4685 *deptail = sl;
4686 deptail = &sl->next;
4690 * Define the __PASS__ macro. This is defined here unlike
4691 * all the other builtins, because it is special -- it varies between
4692 * passes.
4694 t = nasm_malloc(sizeof(*t));
4695 t->next = NULL;
4696 make_tok_num(t, apass);
4697 t->a.mac = NULL;
4698 define_smacro(NULL, "__PASS__", true, 0, t);
4701 static char *pp_getline(void)
4703 char *line;
4704 Token *tline;
4706 while (1) {
4708 * Fetch a tokenized line, either from the macro-expansion
4709 * buffer or from the input file.
4711 tline = NULL;
4712 while (istk->expansion && istk->expansion->finishes) {
4713 Line *l = istk->expansion;
4714 if (!l->finishes->name && l->finishes->in_progress > 1) {
4715 Line *ll;
4718 * This is a macro-end marker for a macro with no
4719 * name, which means it's not really a macro at all
4720 * but a %rep block, and the `in_progress' field is
4721 * more than 1, meaning that we still need to
4722 * repeat. (1 means the natural last repetition; 0
4723 * means termination by %exitrep.) We have
4724 * therefore expanded up to the %endrep, and must
4725 * push the whole block on to the expansion buffer
4726 * again. We don't bother to remove the macro-end
4727 * marker: we'd only have to generate another one
4728 * if we did.
4730 l->finishes->in_progress--;
4731 list_for_each(l, l->finishes->expansion) {
4732 Token *t, *tt, **tail;
4734 ll = nasm_malloc(sizeof(Line));
4735 ll->next = istk->expansion;
4736 ll->finishes = NULL;
4737 ll->first = NULL;
4738 tail = &ll->first;
4740 list_for_each(t, l->first) {
4741 if (t->text || t->type == TOK_WHITESPACE) {
4742 tt = *tail = new_Token(NULL, t->type, t->text, 0);
4743 tail = &tt->next;
4747 istk->expansion = ll;
4749 } else {
4751 * Check whether a `%rep' was started and not ended
4752 * within this macro expansion. This can happen and
4753 * should be detected. It's a fatal error because
4754 * I'm too confused to work out how to recover
4755 * sensibly from it.
4757 if (defining) {
4758 if (defining->name)
4759 error(ERR_PANIC,
4760 "defining with name in expansion");
4761 else if (istk->mstk->name)
4762 error(ERR_FATAL,
4763 "`%%rep' without `%%endrep' within"
4764 " expansion of macro `%s'",
4765 istk->mstk->name);
4769 * FIXME: investigate the relationship at this point between
4770 * istk->mstk and l->finishes
4773 MMacro *m = istk->mstk;
4774 istk->mstk = m->next_active;
4775 if (m->name) {
4777 * This was a real macro call, not a %rep, and
4778 * therefore the parameter information needs to
4779 * be freed.
4781 if (m->prev) {
4782 pop_mmacro(m);
4783 l->finishes->in_progress --;
4784 } else {
4785 nasm_free(m->params);
4786 free_tlist(m->iline);
4787 nasm_free(m->paramlen);
4788 l->finishes->in_progress = 0;
4790 } else
4791 free_mmacro(m);
4793 istk->expansion = l->next;
4794 nasm_free(l);
4795 list->downlevel(LIST_MACRO);
4798 while (1) { /* until we get a line we can use */
4800 if (istk->expansion) { /* from a macro expansion */
4801 char *p;
4802 Line *l = istk->expansion;
4803 if (istk->mstk)
4804 istk->mstk->lineno++;
4805 tline = l->first;
4806 istk->expansion = l->next;
4807 nasm_free(l);
4808 p = detoken(tline, false);
4809 list->line(LIST_MACRO, p);
4810 nasm_free(p);
4811 break;
4813 line = read_line();
4814 if (line) { /* from the current input file */
4815 line = prepreproc(line);
4816 tline = tokenize(line);
4817 nasm_free(line);
4818 break;
4821 * The current file has ended; work down the istk
4824 Include *i = istk;
4825 fclose(i->fp);
4826 if (i->conds)
4827 error(ERR_FATAL,
4828 "expected `%%endif' before end of file");
4829 /* only set line and file name if there's a next node */
4830 if (i->next) {
4831 src_set_linnum(i->lineno);
4832 nasm_free(src_set_fname(i->fname));
4834 istk = i->next;
4835 list->downlevel(LIST_INCLUDE);
4836 nasm_free(i);
4837 if (!istk)
4838 return NULL;
4839 if (istk->expansion && istk->expansion->finishes)
4840 break;
4845 * We must expand MMacro parameters and MMacro-local labels
4846 * _before_ we plunge into directive processing, to cope
4847 * with things like `%define something %1' such as STRUC
4848 * uses. Unless we're _defining_ a MMacro, in which case
4849 * those tokens should be left alone to go into the
4850 * definition; and unless we're in a non-emitting
4851 * condition, in which case we don't want to meddle with
4852 * anything.
4854 if (!defining && !(istk->conds && !emitting(istk->conds->state))
4855 && !(istk->mstk && !istk->mstk->in_progress)) {
4856 tline = expand_mmac_params(tline);
4860 * Check the line to see if it's a preprocessor directive.
4862 if (do_directive(tline) == DIRECTIVE_FOUND) {
4863 continue;
4864 } else if (defining) {
4866 * We're defining a multi-line macro. We emit nothing
4867 * at all, and just
4868 * shove the tokenized line on to the macro definition.
4870 Line *l = nasm_malloc(sizeof(Line));
4871 l->next = defining->expansion;
4872 l->first = tline;
4873 l->finishes = NULL;
4874 defining->expansion = l;
4875 continue;
4876 } else if (istk->conds && !emitting(istk->conds->state)) {
4878 * We're in a non-emitting branch of a condition block.
4879 * Emit nothing at all, not even a blank line: when we
4880 * emerge from the condition we'll give a line-number
4881 * directive so we keep our place correctly.
4883 free_tlist(tline);
4884 continue;
4885 } else if (istk->mstk && !istk->mstk->in_progress) {
4887 * We're in a %rep block which has been terminated, so
4888 * we're walking through to the %endrep without
4889 * emitting anything. Emit nothing at all, not even a
4890 * blank line: when we emerge from the %rep block we'll
4891 * give a line-number directive so we keep our place
4892 * correctly.
4894 free_tlist(tline);
4895 continue;
4896 } else {
4897 tline = expand_smacro(tline);
4898 if (!expand_mmacro(tline)) {
4900 * De-tokenize the line again, and emit it.
4902 line = detoken(tline, true);
4903 free_tlist(tline);
4904 break;
4905 } else {
4906 continue; /* expand_mmacro calls free_tlist */
4911 return line;
4914 static void pp_cleanup(int pass)
4916 if (defining) {
4917 if (defining->name) {
4918 error(ERR_NONFATAL,
4919 "end of file while still defining macro `%s'",
4920 defining->name);
4921 } else {
4922 error(ERR_NONFATAL, "end of file while still in %%rep");
4925 free_mmacro(defining);
4926 defining = NULL;
4928 while (cstk)
4929 ctx_pop();
4930 free_macros();
4931 while (istk) {
4932 Include *i = istk;
4933 istk = istk->next;
4934 fclose(i->fp);
4935 nasm_free(i->fname);
4936 nasm_free(i);
4938 while (cstk)
4939 ctx_pop();
4940 nasm_free(src_set_fname(NULL));
4941 if (pass == 0) {
4942 IncPath *i;
4943 free_llist(predef);
4944 delete_Blocks();
4945 while ((i = ipath)) {
4946 ipath = i->next;
4947 if (i->path)
4948 nasm_free(i->path);
4949 nasm_free(i);
4954 void pp_include_path(char *path)
4956 IncPath *i;
4958 i = nasm_malloc(sizeof(IncPath));
4959 i->path = path ? nasm_strdup(path) : NULL;
4960 i->next = NULL;
4962 if (ipath) {
4963 IncPath *j = ipath;
4964 while (j->next)
4965 j = j->next;
4966 j->next = i;
4967 } else {
4968 ipath = i;
4972 void pp_pre_include(char *fname)
4974 Token *inc, *space, *name;
4975 Line *l;
4977 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
4978 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
4979 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
4981 l = nasm_malloc(sizeof(Line));
4982 l->next = predef;
4983 l->first = inc;
4984 l->finishes = NULL;
4985 predef = l;
4988 void pp_pre_define(char *definition)
4990 Token *def, *space;
4991 Line *l;
4992 char *equals;
4994 equals = strchr(definition, '=');
4995 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4996 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
4997 if (equals)
4998 *equals = ' ';
4999 space->next = tokenize(definition);
5000 if (equals)
5001 *equals = '=';
5003 l = nasm_malloc(sizeof(Line));
5004 l->next = predef;
5005 l->first = def;
5006 l->finishes = NULL;
5007 predef = l;
5010 void pp_pre_undefine(char *definition)
5012 Token *def, *space;
5013 Line *l;
5015 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5016 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5017 space->next = tokenize(definition);
5019 l = nasm_malloc(sizeof(Line));
5020 l->next = predef;
5021 l->first = def;
5022 l->finishes = NULL;
5023 predef = l;
5027 * Added by Keith Kanios:
5029 * This function is used to assist with "runtime" preprocessor
5030 * directives. (e.g. pp_runtime("%define __BITS__ 64");)
5032 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
5033 * PASS A VALID STRING TO THIS FUNCTION!!!!!
5036 void pp_runtime(char *definition)
5038 Token *def;
5040 def = tokenize(definition);
5041 if (do_directive(def) == NO_DIRECTIVE_FOUND)
5042 free_tlist(def);
5046 void pp_extra_stdmac(macros_t *macros)
5048 extrastdmac = macros;
5051 static void make_tok_num(Token * tok, int64_t val)
5053 char numbuf[20];
5054 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5055 tok->text = nasm_strdup(numbuf);
5056 tok->type = TOK_NUMBER;
5059 Preproc nasmpp = {
5060 pp_reset,
5061 pp_getline,
5062 pp_cleanup