expand_mmac_params: Don't forget to handle TOK_OTHER
[nasm/sigaren-mirror.git] / preproc.c
blob406d568ef53f3d5fa111370bccdc17bfc4063939
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 = elements(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);
565 * Free a linked list of lines.
567 static void free_llist(Line * list)
569 Line *l;
570 while (list) {
571 l = list;
572 list = list->next;
573 free_tlist(l->first);
574 nasm_free(l);
579 * Free an MMacro
581 static void free_mmacro(MMacro * m)
583 nasm_free(m->name);
584 free_tlist(m->dlist);
585 nasm_free(m->defaults);
586 free_llist(m->expansion);
587 nasm_free(m);
591 * Free all currently defined macros, and free the hash tables
593 static void free_smacro_table(struct hash_table *smt)
595 SMacro *s;
596 const char *key;
597 struct hash_tbl_node *it = NULL;
599 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
600 nasm_free((void *)key);
601 while (s) {
602 SMacro *ns = s->next;
603 nasm_free(s->name);
604 free_tlist(s->expansion);
605 nasm_free(s);
606 s = ns;
609 hash_free(smt);
612 static void free_mmacro_table(struct hash_table *mmt)
614 MMacro *m;
615 const char *key;
616 struct hash_tbl_node *it = NULL;
618 it = NULL;
619 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
620 nasm_free((void *)key);
621 while (m) {
622 MMacro *nm = m->next;
623 free_mmacro(m);
624 m = nm;
627 hash_free(mmt);
630 static void free_macros(void)
632 free_smacro_table(&smacros);
633 free_mmacro_table(&mmacros);
637 * Initialize the hash tables
639 static void init_macros(void)
641 hash_init(&smacros, HASH_LARGE);
642 hash_init(&mmacros, HASH_LARGE);
646 * Pop the context stack.
648 static void ctx_pop(void)
650 Context *c = cstk;
652 cstk = cstk->next;
653 free_smacro_table(&c->localmac);
654 nasm_free(c->name);
655 nasm_free(c);
659 * Search for a key in the hash index; adding it if necessary
660 * (in which case we initialize the data pointer to NULL.)
662 static void **
663 hash_findi_add(struct hash_table *hash, const char *str)
665 struct hash_insert hi;
666 void **r;
667 char *strx;
669 r = hash_findi(hash, str, &hi);
670 if (r)
671 return r;
673 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
674 return hash_add(&hi, strx, NULL);
678 * Like hash_findi, but returns the data element rather than a pointer
679 * to it. Used only when not adding a new element, hence no third
680 * argument.
682 static void *
683 hash_findix(struct hash_table *hash, const char *str)
685 void **p;
687 p = hash_findi(hash, str, NULL);
688 return p ? *p : NULL;
691 #define BUF_DELTA 512
693 * Read a line from the top file in istk, handling multiple CR/LFs
694 * at the end of the line read, and handling spurious ^Zs. Will
695 * return lines from the standard macro set if this has not already
696 * been done.
698 static char *read_line(void)
700 char *buffer, *p, *q;
701 int bufsize, continued_count;
703 if (stdmacpos) {
704 unsigned char c;
705 const unsigned char *p = stdmacpos;
706 char *ret, *q;
707 size_t len = 0;
708 while ((c = *p++)) {
709 if (c >= 0x80)
710 len += pp_directives_len[c-0x80]+1;
711 else
712 len++;
714 ret = nasm_malloc(len+1);
715 q = ret;
716 while ((c = *stdmacpos++)) {
717 if (c >= 0x80) {
718 memcpy(q, pp_directives[c-0x80], pp_directives_len[c-0x80]);
719 q += pp_directives_len[c-0x80];
720 *q++ = ' ';
721 } else {
722 *q++ = c;
725 stdmacpos = p;
726 *q = '\0';
728 if (!*stdmacpos) {
729 /* This was the last of the standard macro chain... */
730 stdmacpos = NULL;
731 if (any_extrastdmac) {
732 stdmacpos = extrastdmac;
733 any_extrastdmac = false;
734 } else if (do_predef) {
735 Line *pd, *l;
736 Token *head, **tail, *t;
739 * Nasty hack: here we push the contents of
740 * `predef' on to the top-level expansion stack,
741 * since this is the most convenient way to
742 * implement the pre-include and pre-define
743 * features.
745 for (pd = predef; pd; pd = pd->next) {
746 head = NULL;
747 tail = &head;
748 for (t = pd->first; t; t = t->next) {
749 *tail = new_Token(NULL, t->type, t->text, 0);
750 tail = &(*tail)->next;
752 l = nasm_malloc(sizeof(Line));
753 l->next = istk->expansion;
754 l->first = head;
755 l->finishes = NULL;
756 istk->expansion = l;
758 do_predef = false;
761 return ret;
764 bufsize = BUF_DELTA;
765 buffer = nasm_malloc(BUF_DELTA);
766 p = buffer;
767 continued_count = 0;
768 while (1) {
769 q = fgets(p, bufsize - (p - buffer), istk->fp);
770 if (!q)
771 break;
772 p += strlen(p);
773 if (p > buffer && p[-1] == '\n') {
775 * Convert backslash-CRLF line continuation sequences into
776 * nothing at all (for DOS and Windows)
778 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
779 p -= 3;
780 *p = 0;
781 continued_count++;
784 * Also convert backslash-LF line continuation sequences into
785 * nothing at all (for Unix)
787 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
788 p -= 2;
789 *p = 0;
790 continued_count++;
791 } else {
792 break;
795 if (p - buffer > bufsize - 10) {
796 int32_t offset = p - buffer;
797 bufsize += BUF_DELTA;
798 buffer = nasm_realloc(buffer, bufsize);
799 p = buffer + offset; /* prevent stale-pointer problems */
803 if (!q && p == buffer) {
804 nasm_free(buffer);
805 return NULL;
808 src_set_linnum(src_get_linnum() + istk->lineinc +
809 (continued_count * istk->lineinc));
812 * Play safe: remove CRs as well as LFs, if any of either are
813 * present at the end of the line.
815 while (--p >= buffer && (*p == '\n' || *p == '\r'))
816 *p = '\0';
819 * Handle spurious ^Z, which may be inserted into source files
820 * by some file transfer utilities.
822 buffer[strcspn(buffer, "\032")] = '\0';
824 list->line(LIST_READ, buffer);
826 return buffer;
830 * Tokenize a line of text. This is a very simple process since we
831 * don't need to parse the value out of e.g. numeric tokens: we
832 * simply split one string into many.
834 static Token *tokenize(char *line)
836 char c, *p = line;
837 enum pp_token_type type;
838 Token *list = NULL;
839 Token *t, **tail = &list;
841 while (*line) {
842 p = line;
843 if (*p == '%') {
844 p++;
845 if (*p == '+' && !nasm_isdigit(p[1])) {
846 p++;
847 type = TOK_PASTE;
848 } else if (nasm_isdigit(*p) ||
849 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
850 do {
851 p++;
853 while (nasm_isdigit(*p));
854 type = TOK_PREPROC_ID;
855 } else if (*p == '{') {
856 p++;
857 while (*p && *p != '}') {
858 p[-1] = *p;
859 p++;
861 p[-1] = '\0';
862 if (*p)
863 p++;
864 type = TOK_PREPROC_ID;
865 } else if (*p == '[') {
866 int lvl = 1;
867 line += 2; /* Skip the leading %[ */
868 p++;
869 while (lvl && (c = *p++)) {
870 switch (c) {
871 case ']':
872 lvl--;
873 break;
874 case '%':
875 if (*p == '[')
876 lvl++;
877 break;
878 case '\'':
879 case '\"':
880 case '`':
881 p = nasm_skip_string(p)+1;
882 break;
883 default:
884 break;
887 p--;
888 if (*p)
889 *p++ = '\0';
890 if (lvl)
891 error(ERR_NONFATAL, "unterminated %[ construct");
892 type = TOK_INDIRECT;
893 } else if (*p == '?') {
894 type = TOK_PREPROC_Q; /* %? */
895 p++;
896 if (*p == '?') {
897 type = TOK_PREPROC_QQ; /* %?? */
898 p++;
900 } else if (isidchar(*p) ||
901 ((*p == '!' || *p == '%' || *p == '$') &&
902 isidchar(p[1]))) {
903 do {
904 p++;
906 while (isidchar(*p));
907 type = TOK_PREPROC_ID;
908 } else {
909 type = TOK_OTHER;
910 if (*p == '%')
911 p++;
913 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
914 type = TOK_ID;
915 p++;
916 while (*p && isidchar(*p))
917 p++;
918 } else if (*p == '\'' || *p == '"' || *p == '`') {
920 * A string token.
922 type = TOK_STRING;
923 p = nasm_skip_string(p);
925 if (*p) {
926 p++;
927 } else {
928 error(ERR_WARNING|ERR_PASS1, "unterminated string");
929 /* Handling unterminated strings by UNV */
930 /* type = -1; */
932 } else if (p[0] == '$' && p[1] == '$') {
933 type = TOK_OTHER; /* TOKEN_BASE */
934 p += 2;
935 } else if (isnumstart(*p)) {
936 bool is_hex = false;
937 bool is_float = false;
938 bool has_e = false;
939 char c, *r;
942 * A numeric token.
945 if (*p == '$') {
946 p++;
947 is_hex = true;
950 for (;;) {
951 c = *p++;
953 if (!is_hex && (c == 'e' || c == 'E')) {
954 has_e = true;
955 if (*p == '+' || *p == '-') {
957 * e can only be followed by +/- if it is either a
958 * prefixed hex number or a floating-point number
960 p++;
961 is_float = true;
963 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
964 is_hex = true;
965 } else if (c == 'P' || c == 'p') {
966 is_float = true;
967 if (*p == '+' || *p == '-')
968 p++;
969 } else if (isnumchar(c) || c == '_')
970 ; /* just advance */
971 else if (c == '.') {
973 * we need to deal with consequences of the legacy
974 * parser, like "1.nolist" being two tokens
975 * (TOK_NUMBER, TOK_ID) here; at least give it
976 * a shot for now. In the future, we probably need
977 * a flex-based scanner with proper pattern matching
978 * to do it as well as it can be done. Nothing in
979 * the world is going to help the person who wants
980 * 0x123.p16 interpreted as two tokens, though.
982 r = p;
983 while (*r == '_')
984 r++;
986 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
987 (!is_hex && (*r == 'e' || *r == 'E')) ||
988 (*r == 'p' || *r == 'P')) {
989 p = r;
990 is_float = true;
991 } else
992 break; /* Terminate the token */
993 } else
994 break;
996 p--; /* Point to first character beyond number */
998 if (p == line+1 && *line == '$') {
999 type = TOK_OTHER; /* TOKEN_HERE */
1000 } else {
1001 if (has_e && !is_hex) {
1002 /* 1e13 is floating-point, but 1e13h is not */
1003 is_float = true;
1006 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1008 } else if (nasm_isspace(*p)) {
1009 type = TOK_WHITESPACE;
1010 p = nasm_skip_spaces(p);
1012 * Whitespace just before end-of-line is discarded by
1013 * pretending it's a comment; whitespace just before a
1014 * comment gets lumped into the comment.
1016 if (!*p || *p == ';') {
1017 type = TOK_COMMENT;
1018 while (*p)
1019 p++;
1021 } else if (*p == ';') {
1022 type = TOK_COMMENT;
1023 while (*p)
1024 p++;
1025 } else {
1027 * Anything else is an operator of some kind. We check
1028 * for all the double-character operators (>>, <<, //,
1029 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1030 * else is a single-character operator.
1032 type = TOK_OTHER;
1033 if ((p[0] == '>' && p[1] == '>') ||
1034 (p[0] == '<' && p[1] == '<') ||
1035 (p[0] == '/' && p[1] == '/') ||
1036 (p[0] == '<' && p[1] == '=') ||
1037 (p[0] == '>' && p[1] == '=') ||
1038 (p[0] == '=' && p[1] == '=') ||
1039 (p[0] == '!' && p[1] == '=') ||
1040 (p[0] == '<' && p[1] == '>') ||
1041 (p[0] == '&' && p[1] == '&') ||
1042 (p[0] == '|' && p[1] == '|') ||
1043 (p[0] == '^' && p[1] == '^')) {
1044 p++;
1046 p++;
1049 /* Handling unterminated string by UNV */
1050 /*if (type == -1)
1052 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1053 t->text[p-line] = *line;
1054 tail = &t->next;
1056 else */
1057 if (type != TOK_COMMENT) {
1058 *tail = t = new_Token(NULL, type, line, p - line);
1059 tail = &t->next;
1061 line = p;
1063 return list;
1067 * this function allocates a new managed block of memory and
1068 * returns a pointer to the block. The managed blocks are
1069 * deleted only all at once by the delete_Blocks function.
1071 static void *new_Block(size_t size)
1073 Blocks *b = &blocks;
1075 /* first, get to the end of the linked list */
1076 while (b->next)
1077 b = b->next;
1078 /* now allocate the requested chunk */
1079 b->chunk = nasm_malloc(size);
1081 /* now allocate a new block for the next request */
1082 b->next = nasm_malloc(sizeof(Blocks));
1083 /* and initialize the contents of the new block */
1084 b->next->next = NULL;
1085 b->next->chunk = NULL;
1086 return b->chunk;
1090 * this function deletes all managed blocks of memory
1092 static void delete_Blocks(void)
1094 Blocks *a, *b = &blocks;
1097 * keep in mind that the first block, pointed to by blocks
1098 * is a static and not dynamically allocated, so we don't
1099 * free it.
1101 while (b) {
1102 if (b->chunk)
1103 nasm_free(b->chunk);
1104 a = b;
1105 b = b->next;
1106 if (a != &blocks)
1107 nasm_free(a);
1112 * this function creates a new Token and passes a pointer to it
1113 * back to the caller. It sets the type and text elements, and
1114 * also the a.mac and next elements to NULL.
1116 static Token *new_Token(Token * next, enum pp_token_type type,
1117 const char *text, int txtlen)
1119 Token *t;
1120 int i;
1122 if (!freeTokens) {
1123 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1124 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1125 freeTokens[i].next = &freeTokens[i + 1];
1126 freeTokens[i].next = NULL;
1128 t = freeTokens;
1129 freeTokens = t->next;
1130 t->next = next;
1131 t->a.mac = NULL;
1132 t->type = type;
1133 if (type == TOK_WHITESPACE || !text) {
1134 t->text = NULL;
1135 } else {
1136 if (txtlen == 0)
1137 txtlen = strlen(text);
1138 t->text = nasm_malloc(txtlen+1);
1139 memcpy(t->text, text, txtlen);
1140 t->text[txtlen] = '\0';
1142 return t;
1145 static Token *delete_Token(Token * t)
1147 Token *next = t->next;
1148 nasm_free(t->text);
1149 t->next = freeTokens;
1150 freeTokens = t;
1151 return next;
1155 * Convert a line of tokens back into text.
1156 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1157 * will be transformed into ..@ctxnum.xxx
1159 static char *detoken(Token * tlist, bool expand_locals)
1161 Token *t;
1162 char *line, *p;
1163 const char *q;
1164 int len = 0;
1166 list_for_each(t, tlist) {
1167 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1168 char *p = getenv(t->text + 2);
1169 nasm_free(t->text);
1170 if (p)
1171 t->text = nasm_strdup(p);
1172 else
1173 t->text = NULL;
1175 /* Expand local macros here and not during preprocessing */
1176 if (expand_locals &&
1177 t->type == TOK_PREPROC_ID && t->text &&
1178 t->text[0] == '%' && t->text[1] == '$') {
1179 const char *q;
1180 char *p;
1181 Context *ctx = get_ctx(t->text, &q, false);
1182 if (ctx) {
1183 char buffer[40];
1184 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1185 p = nasm_strcat(buffer, q);
1186 nasm_free(t->text);
1187 t->text = p;
1190 if (t->type == TOK_WHITESPACE)
1191 len++;
1192 else if (t->text)
1193 len += strlen(t->text);
1196 p = line = nasm_malloc(len + 1);
1198 list_for_each(t, tlist) {
1199 if (t->type == TOK_WHITESPACE) {
1200 *p++ = ' ';
1201 } else if (t->text) {
1202 q = t->text;
1203 while (*q)
1204 *p++ = *q++;
1207 *p = '\0';
1209 return line;
1213 * A scanner, suitable for use by the expression evaluator, which
1214 * operates on a line of Tokens. Expects a pointer to a pointer to
1215 * the first token in the line to be passed in as its private_data
1216 * field.
1218 * FIX: This really needs to be unified with stdscan.
1220 static int ppscan(void *private_data, struct tokenval *tokval)
1222 Token **tlineptr = private_data;
1223 Token *tline;
1224 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1226 do {
1227 tline = *tlineptr;
1228 *tlineptr = tline ? tline->next : NULL;
1230 while (tline && (tline->type == TOK_WHITESPACE ||
1231 tline->type == TOK_COMMENT));
1233 if (!tline)
1234 return tokval->t_type = TOKEN_EOS;
1236 tokval->t_charptr = tline->text;
1238 if (tline->text[0] == '$' && !tline->text[1])
1239 return tokval->t_type = TOKEN_HERE;
1240 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1241 return tokval->t_type = TOKEN_BASE;
1243 if (tline->type == TOK_ID) {
1244 p = tokval->t_charptr = tline->text;
1245 if (p[0] == '$') {
1246 tokval->t_charptr++;
1247 return tokval->t_type = TOKEN_ID;
1250 for (r = p, s = ourcopy; *r; r++) {
1251 if (r >= p+MAX_KEYWORD)
1252 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1253 *s++ = nasm_tolower(*r);
1255 *s = '\0';
1256 /* right, so we have an identifier sitting in temp storage. now,
1257 * is it actually a register or instruction name, or what? */
1258 return nasm_token_hash(ourcopy, tokval);
1261 if (tline->type == TOK_NUMBER) {
1262 bool rn_error;
1263 tokval->t_integer = readnum(tline->text, &rn_error);
1264 tokval->t_charptr = tline->text;
1265 if (rn_error)
1266 return tokval->t_type = TOKEN_ERRNUM;
1267 else
1268 return tokval->t_type = TOKEN_NUM;
1271 if (tline->type == TOK_FLOAT) {
1272 return tokval->t_type = TOKEN_FLOAT;
1275 if (tline->type == TOK_STRING) {
1276 char bq, *ep;
1278 bq = tline->text[0];
1279 tokval->t_charptr = tline->text;
1280 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1282 if (ep[0] != bq || ep[1] != '\0')
1283 return tokval->t_type = TOKEN_ERRSTR;
1284 else
1285 return tokval->t_type = TOKEN_STR;
1288 if (tline->type == TOK_OTHER) {
1289 if (!strcmp(tline->text, "<<"))
1290 return tokval->t_type = TOKEN_SHL;
1291 if (!strcmp(tline->text, ">>"))
1292 return tokval->t_type = TOKEN_SHR;
1293 if (!strcmp(tline->text, "//"))
1294 return tokval->t_type = TOKEN_SDIV;
1295 if (!strcmp(tline->text, "%%"))
1296 return tokval->t_type = TOKEN_SMOD;
1297 if (!strcmp(tline->text, "=="))
1298 return tokval->t_type = TOKEN_EQ;
1299 if (!strcmp(tline->text, "<>"))
1300 return tokval->t_type = TOKEN_NE;
1301 if (!strcmp(tline->text, "!="))
1302 return tokval->t_type = TOKEN_NE;
1303 if (!strcmp(tline->text, "<="))
1304 return tokval->t_type = TOKEN_LE;
1305 if (!strcmp(tline->text, ">="))
1306 return tokval->t_type = TOKEN_GE;
1307 if (!strcmp(tline->text, "&&"))
1308 return tokval->t_type = TOKEN_DBL_AND;
1309 if (!strcmp(tline->text, "^^"))
1310 return tokval->t_type = TOKEN_DBL_XOR;
1311 if (!strcmp(tline->text, "||"))
1312 return tokval->t_type = TOKEN_DBL_OR;
1316 * We have no other options: just return the first character of
1317 * the token text.
1319 return tokval->t_type = tline->text[0];
1323 * Compare a string to the name of an existing macro; this is a
1324 * simple wrapper which calls either strcmp or nasm_stricmp
1325 * depending on the value of the `casesense' parameter.
1327 static int mstrcmp(const char *p, const char *q, bool casesense)
1329 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1333 * Compare a string to the name of an existing macro; this is a
1334 * simple wrapper which calls either strcmp or nasm_stricmp
1335 * depending on the value of the `casesense' parameter.
1337 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1339 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1343 * Return the Context structure associated with a %$ token. Return
1344 * NULL, having _already_ reported an error condition, if the
1345 * context stack isn't deep enough for the supplied number of $
1346 * signs.
1347 * If all_contexts == true, contexts that enclose current are
1348 * also scanned for such smacro, until it is found; if not -
1349 * only the context that directly results from the number of $'s
1350 * in variable's name.
1352 * If "namep" is non-NULL, set it to the pointer to the macro name
1353 * tail, i.e. the part beyond %$...
1355 static Context *get_ctx(const char *name, const char **namep,
1356 bool all_contexts)
1358 Context *ctx;
1359 SMacro *m;
1360 int i;
1362 if (namep)
1363 *namep = name;
1365 if (!name || name[0] != '%' || name[1] != '$')
1366 return NULL;
1368 if (!cstk) {
1369 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1370 return NULL;
1373 name += 2;
1374 ctx = cstk;
1375 i = 0;
1376 while (ctx && *name == '$') {
1377 name++;
1378 i++;
1379 ctx = ctx->next;
1381 if (!ctx) {
1382 error(ERR_NONFATAL, "`%s': context stack is only"
1383 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1384 return NULL;
1387 if (namep)
1388 *namep = name;
1390 if (!all_contexts)
1391 return ctx;
1393 do {
1394 /* Search for this smacro in found context */
1395 m = hash_findix(&ctx->localmac, name);
1396 while (m) {
1397 if (!mstrcmp(m->name, name, m->casesense))
1398 return ctx;
1399 m = m->next;
1401 ctx = ctx->next;
1403 while (ctx);
1404 return NULL;
1408 * Check to see if a file is already in a string list
1410 static bool in_list(const StrList *list, const char *str)
1412 while (list) {
1413 if (!strcmp(list->str, str))
1414 return true;
1415 list = list->next;
1417 return false;
1421 * Open an include file. This routine must always return a valid
1422 * file pointer if it returns - it's responsible for throwing an
1423 * ERR_FATAL and bombing out completely if not. It should also try
1424 * the include path one by one until it finds the file or reaches
1425 * the end of the path.
1427 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1428 bool missing_ok)
1430 FILE *fp;
1431 char *prefix = "";
1432 IncPath *ip = ipath;
1433 int len = strlen(file);
1434 size_t prefix_len = 0;
1435 StrList *sl;
1437 while (1) {
1438 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1439 memcpy(sl->str, prefix, prefix_len);
1440 memcpy(sl->str+prefix_len, file, len+1);
1441 fp = fopen(sl->str, "r");
1442 if (fp && dhead && !in_list(*dhead, sl->str)) {
1443 sl->next = NULL;
1444 **dtail = sl;
1445 *dtail = &sl->next;
1446 } else {
1447 nasm_free(sl);
1449 if (fp)
1450 return fp;
1451 if (!ip) {
1452 if (!missing_ok)
1453 break;
1454 prefix = NULL;
1455 } else {
1456 prefix = ip->path;
1457 ip = ip->next;
1459 if (prefix) {
1460 prefix_len = strlen(prefix);
1461 } else {
1462 /* -MG given and file not found */
1463 if (dhead && !in_list(*dhead, file)) {
1464 sl = nasm_malloc(len+1+sizeof sl->next);
1465 sl->next = NULL;
1466 strcpy(sl->str, file);
1467 **dtail = sl;
1468 *dtail = &sl->next;
1470 return NULL;
1474 error(ERR_FATAL, "unable to open include file `%s'", file);
1475 return NULL;
1479 * Determine if we should warn on defining a single-line macro of
1480 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1481 * return true if _any_ single-line macro of that name is defined.
1482 * Otherwise, will return true if a single-line macro with either
1483 * `nparam' or no parameters is defined.
1485 * If a macro with precisely the right number of parameters is
1486 * defined, or nparam is -1, the address of the definition structure
1487 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1488 * is NULL, no action will be taken regarding its contents, and no
1489 * error will occur.
1491 * Note that this is also called with nparam zero to resolve
1492 * `ifdef'.
1494 * If you already know which context macro belongs to, you can pass
1495 * the context pointer as first parameter; if you won't but name begins
1496 * with %$ the context will be automatically computed. If all_contexts
1497 * is true, macro will be searched in outer contexts as well.
1499 static bool
1500 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1501 bool nocase)
1503 struct hash_table *smtbl;
1504 SMacro *m;
1506 if (ctx) {
1507 smtbl = &ctx->localmac;
1508 } else if (name[0] == '%' && name[1] == '$') {
1509 if (cstk)
1510 ctx = get_ctx(name, &name, false);
1511 if (!ctx)
1512 return false; /* got to return _something_ */
1513 smtbl = &ctx->localmac;
1514 } else {
1515 smtbl = &smacros;
1517 m = (SMacro *) hash_findix(smtbl, name);
1519 while (m) {
1520 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1521 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1522 if (defn) {
1523 if (nparam == (int) m->nparam || nparam == -1)
1524 *defn = m;
1525 else
1526 *defn = NULL;
1528 return true;
1530 m = m->next;
1533 return false;
1537 * Count and mark off the parameters in a multi-line macro call.
1538 * This is called both from within the multi-line macro expansion
1539 * code, and also to mark off the default parameters when provided
1540 * in a %macro definition line.
1542 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1544 int paramsize, brace;
1546 *nparam = paramsize = 0;
1547 *params = NULL;
1548 while (t) {
1549 /* +1: we need space for the final NULL */
1550 if (*nparam+1 >= paramsize) {
1551 paramsize += PARAM_DELTA;
1552 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1554 skip_white_(t);
1555 brace = false;
1556 if (tok_is_(t, "{"))
1557 brace = true;
1558 (*params)[(*nparam)++] = t;
1559 while (tok_isnt_(t, brace ? "}" : ","))
1560 t = t->next;
1561 if (t) { /* got a comma/brace */
1562 t = t->next;
1563 if (brace) {
1565 * Now we've found the closing brace, look further
1566 * for the comma.
1568 skip_white_(t);
1569 if (tok_isnt_(t, ",")) {
1570 error(ERR_NONFATAL,
1571 "braces do not enclose all of macro parameter");
1572 while (tok_isnt_(t, ","))
1573 t = t->next;
1575 if (t)
1576 t = t->next; /* eat the comma */
1583 * Determine whether one of the various `if' conditions is true or
1584 * not.
1586 * We must free the tline we get passed.
1588 static bool if_condition(Token * tline, enum preproc_token ct)
1590 enum pp_conditional i = PP_COND(ct);
1591 bool j;
1592 Token *t, *tt, **tptr, *origline;
1593 struct tokenval tokval;
1594 expr *evalresult;
1595 enum pp_token_type needtype;
1597 origline = tline;
1599 switch (i) {
1600 case PPC_IFCTX:
1601 j = false; /* have we matched yet? */
1602 while (true) {
1603 skip_white_(tline);
1604 if (!tline)
1605 break;
1606 if (tline->type != TOK_ID) {
1607 error(ERR_NONFATAL,
1608 "`%s' expects context identifiers", pp_directives[ct]);
1609 free_tlist(origline);
1610 return -1;
1612 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1613 j = true;
1614 tline = tline->next;
1616 break;
1618 case PPC_IFDEF:
1619 j = false; /* have we matched yet? */
1620 while (tline) {
1621 skip_white_(tline);
1622 if (!tline || (tline->type != TOK_ID &&
1623 (tline->type != TOK_PREPROC_ID ||
1624 tline->text[1] != '$'))) {
1625 error(ERR_NONFATAL,
1626 "`%s' expects macro identifiers", pp_directives[ct]);
1627 goto fail;
1629 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1630 j = true;
1631 tline = tline->next;
1633 break;
1635 case PPC_IFIDN:
1636 case PPC_IFIDNI:
1637 tline = expand_smacro(tline);
1638 t = tt = tline;
1639 while (tok_isnt_(tt, ","))
1640 tt = tt->next;
1641 if (!tt) {
1642 error(ERR_NONFATAL,
1643 "`%s' expects two comma-separated arguments",
1644 pp_directives[ct]);
1645 goto fail;
1647 tt = tt->next;
1648 j = true; /* assume equality unless proved not */
1649 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1650 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1651 error(ERR_NONFATAL, "`%s': more than one comma on line",
1652 pp_directives[ct]);
1653 goto fail;
1655 if (t->type == TOK_WHITESPACE) {
1656 t = t->next;
1657 continue;
1659 if (tt->type == TOK_WHITESPACE) {
1660 tt = tt->next;
1661 continue;
1663 if (tt->type != t->type) {
1664 j = false; /* found mismatching tokens */
1665 break;
1667 /* When comparing strings, need to unquote them first */
1668 if (t->type == TOK_STRING) {
1669 size_t l1 = nasm_unquote(t->text, NULL);
1670 size_t l2 = nasm_unquote(tt->text, NULL);
1672 if (l1 != l2) {
1673 j = false;
1674 break;
1676 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1677 j = false;
1678 break;
1680 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1681 j = false; /* found mismatching tokens */
1682 break;
1685 t = t->next;
1686 tt = tt->next;
1688 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1689 j = false; /* trailing gunk on one end or other */
1690 break;
1692 case PPC_IFMACRO:
1694 bool found = false;
1695 MMacro searching, *mmac;
1697 skip_white_(tline);
1698 tline = expand_id(tline);
1699 if (!tok_type_(tline, TOK_ID)) {
1700 error(ERR_NONFATAL,
1701 "`%s' expects a macro name", pp_directives[ct]);
1702 goto fail;
1704 searching.name = nasm_strdup(tline->text);
1705 searching.casesense = true;
1706 searching.plus = false;
1707 searching.nolist = false;
1708 searching.in_progress = 0;
1709 searching.max_depth = 0;
1710 searching.rep_nest = NULL;
1711 searching.nparam_min = 0;
1712 searching.nparam_max = INT_MAX;
1713 tline = expand_smacro(tline->next);
1714 skip_white_(tline);
1715 if (!tline) {
1716 } else if (!tok_type_(tline, TOK_NUMBER)) {
1717 error(ERR_NONFATAL,
1718 "`%s' expects a parameter count or nothing",
1719 pp_directives[ct]);
1720 } else {
1721 searching.nparam_min = searching.nparam_max =
1722 readnum(tline->text, &j);
1723 if (j)
1724 error(ERR_NONFATAL,
1725 "unable to parse parameter count `%s'",
1726 tline->text);
1728 if (tline && tok_is_(tline->next, "-")) {
1729 tline = tline->next->next;
1730 if (tok_is_(tline, "*"))
1731 searching.nparam_max = INT_MAX;
1732 else if (!tok_type_(tline, TOK_NUMBER))
1733 error(ERR_NONFATAL,
1734 "`%s' expects a parameter count after `-'",
1735 pp_directives[ct]);
1736 else {
1737 searching.nparam_max = readnum(tline->text, &j);
1738 if (j)
1739 error(ERR_NONFATAL,
1740 "unable to parse parameter count `%s'",
1741 tline->text);
1742 if (searching.nparam_min > searching.nparam_max)
1743 error(ERR_NONFATAL,
1744 "minimum parameter count exceeds maximum");
1747 if (tline && tok_is_(tline->next, "+")) {
1748 tline = tline->next;
1749 searching.plus = true;
1751 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1752 while (mmac) {
1753 if (!strcmp(mmac->name, searching.name) &&
1754 (mmac->nparam_min <= searching.nparam_max
1755 || searching.plus)
1756 && (searching.nparam_min <= mmac->nparam_max
1757 || mmac->plus)) {
1758 found = true;
1759 break;
1761 mmac = mmac->next;
1763 if (tline && tline->next)
1764 error(ERR_WARNING|ERR_PASS1,
1765 "trailing garbage after %%ifmacro ignored");
1766 nasm_free(searching.name);
1767 j = found;
1768 break;
1771 case PPC_IFID:
1772 needtype = TOK_ID;
1773 goto iftype;
1774 case PPC_IFNUM:
1775 needtype = TOK_NUMBER;
1776 goto iftype;
1777 case PPC_IFSTR:
1778 needtype = TOK_STRING;
1779 goto iftype;
1781 iftype:
1782 t = tline = expand_smacro(tline);
1784 while (tok_type_(t, TOK_WHITESPACE) ||
1785 (needtype == TOK_NUMBER &&
1786 tok_type_(t, TOK_OTHER) &&
1787 (t->text[0] == '-' || t->text[0] == '+') &&
1788 !t->text[1]))
1789 t = t->next;
1791 j = tok_type_(t, needtype);
1792 break;
1794 case PPC_IFTOKEN:
1795 t = tline = expand_smacro(tline);
1796 while (tok_type_(t, TOK_WHITESPACE))
1797 t = t->next;
1799 j = false;
1800 if (t) {
1801 t = t->next; /* Skip the actual token */
1802 while (tok_type_(t, TOK_WHITESPACE))
1803 t = t->next;
1804 j = !t; /* Should be nothing left */
1806 break;
1808 case PPC_IFEMPTY:
1809 t = tline = expand_smacro(tline);
1810 while (tok_type_(t, TOK_WHITESPACE))
1811 t = t->next;
1813 j = !t; /* Should be empty */
1814 break;
1816 case PPC_IF:
1817 t = tline = expand_smacro(tline);
1818 tptr = &t;
1819 tokval.t_type = TOKEN_INVALID;
1820 evalresult = evaluate(ppscan, tptr, &tokval,
1821 NULL, pass | CRITICAL, error, NULL);
1822 if (!evalresult)
1823 return -1;
1824 if (tokval.t_type)
1825 error(ERR_WARNING|ERR_PASS1,
1826 "trailing garbage after expression ignored");
1827 if (!is_simple(evalresult)) {
1828 error(ERR_NONFATAL,
1829 "non-constant value given to `%s'", pp_directives[ct]);
1830 goto fail;
1832 j = reloc_value(evalresult) != 0;
1833 break;
1835 default:
1836 error(ERR_FATAL,
1837 "preprocessor directive `%s' not yet implemented",
1838 pp_directives[ct]);
1839 goto fail;
1842 free_tlist(origline);
1843 return j ^ PP_NEGATIVE(ct);
1845 fail:
1846 free_tlist(origline);
1847 return -1;
1851 * Common code for defining an smacro
1853 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1854 int nparam, Token *expansion)
1856 SMacro *smac, **smhead;
1857 struct hash_table *smtbl;
1859 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1860 if (!smac) {
1861 error(ERR_WARNING|ERR_PASS1,
1862 "single-line macro `%s' defined both with and"
1863 " without parameters", mname);
1865 * Some instances of the old code considered this a failure,
1866 * some others didn't. What is the right thing to do here?
1868 free_tlist(expansion);
1869 return false; /* Failure */
1870 } else {
1872 * We're redefining, so we have to take over an
1873 * existing SMacro structure. This means freeing
1874 * what was already in it.
1876 nasm_free(smac->name);
1877 free_tlist(smac->expansion);
1879 } else {
1880 smtbl = ctx ? &ctx->localmac : &smacros;
1881 smhead = (SMacro **) hash_findi_add(smtbl, mname);
1882 smac = nasm_malloc(sizeof(SMacro));
1883 smac->next = *smhead;
1884 *smhead = smac;
1886 smac->name = nasm_strdup(mname);
1887 smac->casesense = casesense;
1888 smac->nparam = nparam;
1889 smac->expansion = expansion;
1890 smac->in_progress = false;
1891 return true; /* Success */
1895 * Undefine an smacro
1897 static void undef_smacro(Context *ctx, const char *mname)
1899 SMacro **smhead, *s, **sp;
1900 struct hash_table *smtbl;
1902 smtbl = ctx ? &ctx->localmac : &smacros;
1903 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
1905 if (smhead) {
1907 * We now have a macro name... go hunt for it.
1909 sp = smhead;
1910 while ((s = *sp) != NULL) {
1911 if (!mstrcmp(s->name, mname, s->casesense)) {
1912 *sp = s->next;
1913 nasm_free(s->name);
1914 free_tlist(s->expansion);
1915 nasm_free(s);
1916 } else {
1917 sp = &s->next;
1924 * Parse a mmacro specification.
1926 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
1928 bool err;
1930 tline = tline->next;
1931 skip_white_(tline);
1932 tline = expand_id(tline);
1933 if (!tok_type_(tline, TOK_ID)) {
1934 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
1935 return false;
1938 def->prev = NULL;
1939 def->name = nasm_strdup(tline->text);
1940 def->plus = false;
1941 def->nolist = false;
1942 def->in_progress = 0;
1943 def->rep_nest = NULL;
1944 def->nparam_min = 0;
1945 def->nparam_max = 0;
1947 tline = expand_smacro(tline->next);
1948 skip_white_(tline);
1949 if (!tok_type_(tline, TOK_NUMBER)) {
1950 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
1951 } else {
1952 def->nparam_min = def->nparam_max =
1953 readnum(tline->text, &err);
1954 if (err)
1955 error(ERR_NONFATAL,
1956 "unable to parse parameter count `%s'", tline->text);
1958 if (tline && tok_is_(tline->next, "-")) {
1959 tline = tline->next->next;
1960 if (tok_is_(tline, "*")) {
1961 def->nparam_max = INT_MAX;
1962 } else if (!tok_type_(tline, TOK_NUMBER)) {
1963 error(ERR_NONFATAL,
1964 "`%s' expects a parameter count after `-'", directive);
1965 } else {
1966 def->nparam_max = readnum(tline->text, &err);
1967 if (err) {
1968 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
1969 tline->text);
1971 if (def->nparam_min > def->nparam_max) {
1972 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
1976 if (tline && tok_is_(tline->next, "+")) {
1977 tline = tline->next;
1978 def->plus = true;
1980 if (tline && tok_type_(tline->next, TOK_ID) &&
1981 !nasm_stricmp(tline->next->text, ".nolist")) {
1982 tline = tline->next;
1983 def->nolist = true;
1987 * Handle default parameters.
1989 if (tline && tline->next) {
1990 def->dlist = tline->next;
1991 tline->next = NULL;
1992 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
1993 } else {
1994 def->dlist = NULL;
1995 def->defaults = NULL;
1997 def->expansion = NULL;
1999 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2000 !def->plus)
2001 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2002 "too many default macro parameters");
2004 return true;
2009 * Decode a size directive
2011 static int parse_size(const char *str) {
2012 static const char *size_names[] =
2013 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2014 static const int sizes[] =
2015 { 0, 1, 4, 16, 8, 10, 2, 32 };
2017 return sizes[bsii(str, size_names, elements(size_names))+1];
2021 * nasm_unquote with error if the string contains NUL characters.
2022 * If the string contains NUL characters, issue an error and return
2023 * the C len, i.e. truncate at the NUL.
2025 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
2027 size_t len = nasm_unquote(qstr, NULL);
2028 size_t clen = strlen(qstr);
2030 if (len != clen)
2031 error(ERR_NONFATAL, "NUL character in `%s' directive",
2032 pp_directives[directive]);
2034 return clen;
2038 * find and process preprocessor directive in passed line
2039 * Find out if a line contains a preprocessor directive, and deal
2040 * with it if so.
2042 * If a directive _is_ found, it is the responsibility of this routine
2043 * (and not the caller) to free_tlist() the line.
2045 * @param tline a pointer to the current tokeninzed line linked list
2046 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2049 static int do_directive(Token * tline)
2051 enum preproc_token i;
2052 int j;
2053 bool err;
2054 int nparam;
2055 bool nolist;
2056 bool casesense;
2057 int k, m;
2058 int offset;
2059 char *p, *pp;
2060 const char *mname;
2061 Include *inc;
2062 Context *ctx;
2063 Cond *cond;
2064 MMacro *mmac, **mmhead;
2065 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2066 Line *l;
2067 struct tokenval tokval;
2068 expr *evalresult;
2069 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2070 int64_t count;
2071 size_t len;
2072 int severity;
2074 origline = tline;
2076 skip_white_(tline);
2077 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2078 (tline->text[1] == '%' || tline->text[1] == '$'
2079 || tline->text[1] == '!'))
2080 return NO_DIRECTIVE_FOUND;
2082 i = pp_token_hash(tline->text);
2085 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2086 * since they are known to be buggy at moment, we need to fix them
2087 * in future release (2.09-2.10)
2089 if (i == PP_RMACRO || i == PP_RMACRO || i == PP_EXITMACRO) {
2090 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2091 tline->text);
2092 return NO_DIRECTIVE_FOUND;
2096 * If we're in a non-emitting branch of a condition construct,
2097 * or walking to the end of an already terminated %rep block,
2098 * we should ignore all directives except for condition
2099 * directives.
2101 if (((istk->conds && !emitting(istk->conds->state)) ||
2102 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2103 return NO_DIRECTIVE_FOUND;
2107 * If we're defining a macro or reading a %rep block, we should
2108 * ignore all directives except for %macro/%imacro (which nest),
2109 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2110 * If we're in a %rep block, another %rep nests, so should be let through.
2112 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2113 i != PP_RMACRO && i != PP_IRMACRO &&
2114 i != PP_ENDMACRO && i != PP_ENDM &&
2115 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2116 return NO_DIRECTIVE_FOUND;
2119 if (defining) {
2120 if (i == PP_MACRO || i == PP_IMACRO ||
2121 i == PP_RMACRO || i == PP_IRMACRO) {
2122 nested_mac_count++;
2123 return NO_DIRECTIVE_FOUND;
2124 } else if (nested_mac_count > 0) {
2125 if (i == PP_ENDMACRO) {
2126 nested_mac_count--;
2127 return NO_DIRECTIVE_FOUND;
2130 if (!defining->name) {
2131 if (i == PP_REP) {
2132 nested_rep_count++;
2133 return NO_DIRECTIVE_FOUND;
2134 } else if (nested_rep_count > 0) {
2135 if (i == PP_ENDREP) {
2136 nested_rep_count--;
2137 return NO_DIRECTIVE_FOUND;
2143 switch (i) {
2144 case PP_INVALID:
2145 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2146 tline->text);
2147 return NO_DIRECTIVE_FOUND; /* didn't get it */
2149 case PP_STACKSIZE:
2150 /* Directive to tell NASM what the default stack size is. The
2151 * default is for a 16-bit stack, and this can be overriden with
2152 * %stacksize large.
2154 tline = tline->next;
2155 if (tline && tline->type == TOK_WHITESPACE)
2156 tline = tline->next;
2157 if (!tline || tline->type != TOK_ID) {
2158 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2159 free_tlist(origline);
2160 return DIRECTIVE_FOUND;
2162 if (nasm_stricmp(tline->text, "flat") == 0) {
2163 /* All subsequent ARG directives are for a 32-bit stack */
2164 StackSize = 4;
2165 StackPointer = "ebp";
2166 ArgOffset = 8;
2167 LocalOffset = 0;
2168 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2169 /* All subsequent ARG directives are for a 64-bit stack */
2170 StackSize = 8;
2171 StackPointer = "rbp";
2172 ArgOffset = 16;
2173 LocalOffset = 0;
2174 } else if (nasm_stricmp(tline->text, "large") == 0) {
2175 /* All subsequent ARG directives are for a 16-bit stack,
2176 * far function call.
2178 StackSize = 2;
2179 StackPointer = "bp";
2180 ArgOffset = 4;
2181 LocalOffset = 0;
2182 } else if (nasm_stricmp(tline->text, "small") == 0) {
2183 /* All subsequent ARG directives are for a 16-bit stack,
2184 * far function call. We don't support near functions.
2186 StackSize = 2;
2187 StackPointer = "bp";
2188 ArgOffset = 6;
2189 LocalOffset = 0;
2190 } else {
2191 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2192 free_tlist(origline);
2193 return DIRECTIVE_FOUND;
2195 free_tlist(origline);
2196 return DIRECTIVE_FOUND;
2198 case PP_ARG:
2199 /* TASM like ARG directive to define arguments to functions, in
2200 * the following form:
2202 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2204 offset = ArgOffset;
2205 do {
2206 char *arg, directive[256];
2207 int size = StackSize;
2209 /* Find the argument name */
2210 tline = tline->next;
2211 if (tline && tline->type == TOK_WHITESPACE)
2212 tline = tline->next;
2213 if (!tline || tline->type != TOK_ID) {
2214 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2215 free_tlist(origline);
2216 return DIRECTIVE_FOUND;
2218 arg = tline->text;
2220 /* Find the argument size type */
2221 tline = tline->next;
2222 if (!tline || tline->type != TOK_OTHER
2223 || tline->text[0] != ':') {
2224 error(ERR_NONFATAL,
2225 "Syntax error processing `%%arg' directive");
2226 free_tlist(origline);
2227 return DIRECTIVE_FOUND;
2229 tline = tline->next;
2230 if (!tline || tline->type != TOK_ID) {
2231 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2232 free_tlist(origline);
2233 return DIRECTIVE_FOUND;
2236 /* Allow macro expansion of type parameter */
2237 tt = tokenize(tline->text);
2238 tt = expand_smacro(tt);
2239 size = parse_size(tt->text);
2240 if (!size) {
2241 error(ERR_NONFATAL,
2242 "Invalid size type for `%%arg' missing directive");
2243 free_tlist(tt);
2244 free_tlist(origline);
2245 return DIRECTIVE_FOUND;
2247 free_tlist(tt);
2249 /* Round up to even stack slots */
2250 size = ALIGN(size, StackSize);
2252 /* Now define the macro for the argument */
2253 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2254 arg, StackPointer, offset);
2255 do_directive(tokenize(directive));
2256 offset += size;
2258 /* Move to the next argument in the list */
2259 tline = tline->next;
2260 if (tline && tline->type == TOK_WHITESPACE)
2261 tline = tline->next;
2262 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2263 ArgOffset = offset;
2264 free_tlist(origline);
2265 return DIRECTIVE_FOUND;
2267 case PP_LOCAL:
2268 /* TASM like LOCAL directive to define local variables for a
2269 * function, in the following form:
2271 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2273 * The '= LocalSize' at the end is ignored by NASM, but is
2274 * required by TASM to define the local parameter size (and used
2275 * by the TASM macro package).
2277 offset = LocalOffset;
2278 do {
2279 char *local, directive[256];
2280 int size = StackSize;
2282 /* Find the argument name */
2283 tline = tline->next;
2284 if (tline && tline->type == TOK_WHITESPACE)
2285 tline = tline->next;
2286 if (!tline || tline->type != TOK_ID) {
2287 error(ERR_NONFATAL,
2288 "`%%local' missing argument parameter");
2289 free_tlist(origline);
2290 return DIRECTIVE_FOUND;
2292 local = tline->text;
2294 /* Find the argument size type */
2295 tline = tline->next;
2296 if (!tline || tline->type != TOK_OTHER
2297 || tline->text[0] != ':') {
2298 error(ERR_NONFATAL,
2299 "Syntax error processing `%%local' directive");
2300 free_tlist(origline);
2301 return DIRECTIVE_FOUND;
2303 tline = tline->next;
2304 if (!tline || tline->type != TOK_ID) {
2305 error(ERR_NONFATAL,
2306 "`%%local' missing size type parameter");
2307 free_tlist(origline);
2308 return DIRECTIVE_FOUND;
2311 /* Allow macro expansion of type parameter */
2312 tt = tokenize(tline->text);
2313 tt = expand_smacro(tt);
2314 size = parse_size(tt->text);
2315 if (!size) {
2316 error(ERR_NONFATAL,
2317 "Invalid size type for `%%local' missing directive");
2318 free_tlist(tt);
2319 free_tlist(origline);
2320 return DIRECTIVE_FOUND;
2322 free_tlist(tt);
2324 /* Round up to even stack slots */
2325 size = ALIGN(size, StackSize);
2327 offset += size; /* Negative offset, increment before */
2329 /* Now define the macro for the argument */
2330 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2331 local, StackPointer, offset);
2332 do_directive(tokenize(directive));
2334 /* Now define the assign to setup the enter_c macro correctly */
2335 snprintf(directive, sizeof(directive),
2336 "%%assign %%$localsize %%$localsize+%d", size);
2337 do_directive(tokenize(directive));
2339 /* Move to the next argument in the list */
2340 tline = tline->next;
2341 if (tline && tline->type == TOK_WHITESPACE)
2342 tline = tline->next;
2343 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2344 LocalOffset = offset;
2345 free_tlist(origline);
2346 return DIRECTIVE_FOUND;
2348 case PP_CLEAR:
2349 if (tline->next)
2350 error(ERR_WARNING|ERR_PASS1,
2351 "trailing garbage after `%%clear' ignored");
2352 free_macros();
2353 init_macros();
2354 free_tlist(origline);
2355 return DIRECTIVE_FOUND;
2357 case PP_DEPEND:
2358 t = tline->next = expand_smacro(tline->next);
2359 skip_white_(t);
2360 if (!t || (t->type != TOK_STRING &&
2361 t->type != TOK_INTERNAL_STRING)) {
2362 error(ERR_NONFATAL, "`%%depend' expects a file name");
2363 free_tlist(origline);
2364 return DIRECTIVE_FOUND; /* but we did _something_ */
2366 if (t->next)
2367 error(ERR_WARNING|ERR_PASS1,
2368 "trailing garbage after `%%depend' ignored");
2369 p = t->text;
2370 if (t->type != TOK_INTERNAL_STRING)
2371 nasm_unquote_cstr(p, i);
2372 if (dephead && !in_list(*dephead, p)) {
2373 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2374 sl->next = NULL;
2375 strcpy(sl->str, p);
2376 *deptail = sl;
2377 deptail = &sl->next;
2379 free_tlist(origline);
2380 return DIRECTIVE_FOUND;
2382 case PP_INCLUDE:
2383 t = tline->next = expand_smacro(tline->next);
2384 skip_white_(t);
2386 if (!t || (t->type != TOK_STRING &&
2387 t->type != TOK_INTERNAL_STRING)) {
2388 error(ERR_NONFATAL, "`%%include' expects a file name");
2389 free_tlist(origline);
2390 return DIRECTIVE_FOUND; /* but we did _something_ */
2392 if (t->next)
2393 error(ERR_WARNING|ERR_PASS1,
2394 "trailing garbage after `%%include' ignored");
2395 p = t->text;
2396 if (t->type != TOK_INTERNAL_STRING)
2397 nasm_unquote_cstr(p, i);
2398 inc = nasm_malloc(sizeof(Include));
2399 inc->next = istk;
2400 inc->conds = NULL;
2401 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2402 if (!inc->fp) {
2403 /* -MG given but file not found */
2404 nasm_free(inc);
2405 } else {
2406 inc->fname = src_set_fname(nasm_strdup(p));
2407 inc->lineno = src_set_linnum(0);
2408 inc->lineinc = 1;
2409 inc->expansion = NULL;
2410 inc->mstk = NULL;
2411 istk = inc;
2412 list->uplevel(LIST_INCLUDE);
2414 free_tlist(origline);
2415 return DIRECTIVE_FOUND;
2417 case PP_USE:
2419 static macros_t *use_pkg;
2420 const char *pkg_macro = NULL;
2422 tline = tline->next;
2423 skip_white_(tline);
2424 tline = expand_id(tline);
2426 if (!tline || (tline->type != TOK_STRING &&
2427 tline->type != TOK_INTERNAL_STRING &&
2428 tline->type != TOK_ID)) {
2429 error(ERR_NONFATAL, "`%%use' expects a package name");
2430 free_tlist(origline);
2431 return DIRECTIVE_FOUND; /* but we did _something_ */
2433 if (tline->next)
2434 error(ERR_WARNING|ERR_PASS1,
2435 "trailing garbage after `%%use' ignored");
2436 if (tline->type == TOK_STRING)
2437 nasm_unquote_cstr(tline->text, i);
2438 use_pkg = nasm_stdmac_find_package(tline->text);
2439 if (!use_pkg)
2440 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2441 else
2442 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2443 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2444 /* Not already included, go ahead and include it */
2445 stdmacpos = use_pkg;
2447 free_tlist(origline);
2448 return DIRECTIVE_FOUND;
2450 case PP_PUSH:
2451 case PP_REPL:
2452 case PP_POP:
2453 tline = tline->next;
2454 skip_white_(tline);
2455 tline = expand_id(tline);
2456 if (tline) {
2457 if (!tok_type_(tline, TOK_ID)) {
2458 error(ERR_NONFATAL, "`%s' expects a context identifier",
2459 pp_directives[i]);
2460 free_tlist(origline);
2461 return DIRECTIVE_FOUND; /* but we did _something_ */
2463 if (tline->next)
2464 error(ERR_WARNING|ERR_PASS1,
2465 "trailing garbage after `%s' ignored",
2466 pp_directives[i]);
2467 p = nasm_strdup(tline->text);
2468 } else {
2469 p = NULL; /* Anonymous */
2472 if (i == PP_PUSH) {
2473 ctx = nasm_malloc(sizeof(Context));
2474 ctx->next = cstk;
2475 hash_init(&ctx->localmac, HASH_SMALL);
2476 ctx->name = p;
2477 ctx->number = unique++;
2478 cstk = ctx;
2479 } else {
2480 /* %pop or %repl */
2481 if (!cstk) {
2482 error(ERR_NONFATAL, "`%s': context stack is empty",
2483 pp_directives[i]);
2484 } else if (i == PP_POP) {
2485 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2486 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2487 "expected %s",
2488 cstk->name ? cstk->name : "anonymous", p);
2489 else
2490 ctx_pop();
2491 } else {
2492 /* i == PP_REPL */
2493 nasm_free(cstk->name);
2494 cstk->name = p;
2495 p = NULL;
2497 nasm_free(p);
2499 free_tlist(origline);
2500 return DIRECTIVE_FOUND;
2501 case PP_FATAL:
2502 severity = ERR_FATAL;
2503 goto issue_error;
2504 case PP_ERROR:
2505 severity = ERR_NONFATAL;
2506 goto issue_error;
2507 case PP_WARNING:
2508 severity = ERR_WARNING|ERR_WARN_USER;
2509 goto issue_error;
2511 issue_error:
2513 /* Only error out if this is the final pass */
2514 if (pass != 2 && i != PP_FATAL)
2515 return DIRECTIVE_FOUND;
2517 tline->next = expand_smacro(tline->next);
2518 tline = tline->next;
2519 skip_white_(tline);
2520 t = tline ? tline->next : NULL;
2521 skip_white_(t);
2522 if (tok_type_(tline, TOK_STRING) && !t) {
2523 /* The line contains only a quoted string */
2524 p = tline->text;
2525 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2526 error(severity, "%s", p);
2527 } else {
2528 /* Not a quoted string, or more than a quoted string */
2529 p = detoken(tline, false);
2530 error(severity, "%s", p);
2531 nasm_free(p);
2533 free_tlist(origline);
2534 return DIRECTIVE_FOUND;
2537 CASE_PP_IF:
2538 if (istk->conds && !emitting(istk->conds->state))
2539 j = COND_NEVER;
2540 else {
2541 j = if_condition(tline->next, i);
2542 tline->next = NULL; /* it got freed */
2543 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2545 cond = nasm_malloc(sizeof(Cond));
2546 cond->next = istk->conds;
2547 cond->state = j;
2548 istk->conds = cond;
2549 if(istk->mstk)
2550 istk->mstk->condcnt ++;
2551 free_tlist(origline);
2552 return DIRECTIVE_FOUND;
2554 CASE_PP_ELIF:
2555 if (!istk->conds)
2556 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2557 switch(istk->conds->state) {
2558 case COND_IF_TRUE:
2559 istk->conds->state = COND_DONE;
2560 break;
2562 case COND_DONE:
2563 case COND_NEVER:
2564 break;
2566 case COND_ELSE_TRUE:
2567 case COND_ELSE_FALSE:
2568 error_precond(ERR_WARNING|ERR_PASS1,
2569 "`%%elif' after `%%else' ignored");
2570 istk->conds->state = COND_NEVER;
2571 break;
2573 case COND_IF_FALSE:
2575 * IMPORTANT: In the case of %if, we will already have
2576 * called expand_mmac_params(); however, if we're
2577 * processing an %elif we must have been in a
2578 * non-emitting mode, which would have inhibited
2579 * the normal invocation of expand_mmac_params().
2580 * Therefore, we have to do it explicitly here.
2582 j = if_condition(expand_mmac_params(tline->next), i);
2583 tline->next = NULL; /* it got freed */
2584 istk->conds->state =
2585 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2586 break;
2588 free_tlist(origline);
2589 return DIRECTIVE_FOUND;
2591 case PP_ELSE:
2592 if (tline->next)
2593 error_precond(ERR_WARNING|ERR_PASS1,
2594 "trailing garbage after `%%else' ignored");
2595 if (!istk->conds)
2596 error(ERR_FATAL, "`%%else': no matching `%%if'");
2597 switch(istk->conds->state) {
2598 case COND_IF_TRUE:
2599 case COND_DONE:
2600 istk->conds->state = COND_ELSE_FALSE;
2601 break;
2603 case COND_NEVER:
2604 break;
2606 case COND_IF_FALSE:
2607 istk->conds->state = COND_ELSE_TRUE;
2608 break;
2610 case COND_ELSE_TRUE:
2611 case COND_ELSE_FALSE:
2612 error_precond(ERR_WARNING|ERR_PASS1,
2613 "`%%else' after `%%else' ignored.");
2614 istk->conds->state = COND_NEVER;
2615 break;
2617 free_tlist(origline);
2618 return DIRECTIVE_FOUND;
2620 case PP_ENDIF:
2621 if (tline->next)
2622 error_precond(ERR_WARNING|ERR_PASS1,
2623 "trailing garbage after `%%endif' ignored");
2624 if (!istk->conds)
2625 error(ERR_FATAL, "`%%endif': no matching `%%if'");
2626 cond = istk->conds;
2627 istk->conds = cond->next;
2628 nasm_free(cond);
2629 if(istk->mstk)
2630 istk->mstk->condcnt --;
2631 free_tlist(origline);
2632 return DIRECTIVE_FOUND;
2634 case PP_RMACRO:
2635 case PP_IRMACRO:
2636 case PP_MACRO:
2637 case PP_IMACRO:
2638 if (defining) {
2639 error(ERR_FATAL, "`%s': already defining a macro",
2640 pp_directives[i]);
2641 return DIRECTIVE_FOUND;
2643 defining = nasm_malloc(sizeof(MMacro));
2644 defining->max_depth =
2645 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2646 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2647 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2648 nasm_free(defining);
2649 defining = NULL;
2650 return DIRECTIVE_FOUND;
2653 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2654 while (mmac) {
2655 if (!strcmp(mmac->name, defining->name) &&
2656 (mmac->nparam_min <= defining->nparam_max
2657 || defining->plus)
2658 && (defining->nparam_min <= mmac->nparam_max
2659 || mmac->plus)) {
2660 error(ERR_WARNING|ERR_PASS1,
2661 "redefining multi-line macro `%s'", defining->name);
2662 return DIRECTIVE_FOUND;
2664 mmac = mmac->next;
2666 free_tlist(origline);
2667 return DIRECTIVE_FOUND;
2669 case PP_ENDM:
2670 case PP_ENDMACRO:
2671 if (! (defining && defining->name)) {
2672 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2673 return DIRECTIVE_FOUND;
2675 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2676 defining->next = *mmhead;
2677 *mmhead = defining;
2678 defining = NULL;
2679 free_tlist(origline);
2680 return DIRECTIVE_FOUND;
2682 case PP_EXITMACRO:
2684 * We must search along istk->expansion until we hit a
2685 * macro-end marker for a macro with a name. Then we
2686 * bypass all lines between exitmacro and endmacro.
2688 for (l = istk->expansion; l; l = l->next)
2689 if (l->finishes && l->finishes->name)
2690 break;
2692 if (l) {
2694 * Remove all conditional entries relative to this
2695 * macro invocation. (safe to do in this context)
2697 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2698 cond = istk->conds;
2699 istk->conds = cond->next;
2700 nasm_free(cond);
2702 istk->expansion = l;
2703 } else {
2704 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2706 free_tlist(origline);
2707 return DIRECTIVE_FOUND;
2709 case PP_UNMACRO:
2710 case PP_UNIMACRO:
2712 MMacro **mmac_p;
2713 MMacro spec;
2715 spec.casesense = (i == PP_UNMACRO);
2716 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2717 return DIRECTIVE_FOUND;
2719 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2720 while (mmac_p && *mmac_p) {
2721 mmac = *mmac_p;
2722 if (mmac->casesense == spec.casesense &&
2723 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2724 mmac->nparam_min == spec.nparam_min &&
2725 mmac->nparam_max == spec.nparam_max &&
2726 mmac->plus == spec.plus) {
2727 *mmac_p = mmac->next;
2728 free_mmacro(mmac);
2729 } else {
2730 mmac_p = &mmac->next;
2733 free_tlist(origline);
2734 free_tlist(spec.dlist);
2735 return DIRECTIVE_FOUND;
2738 case PP_ROTATE:
2739 if (tline->next && tline->next->type == TOK_WHITESPACE)
2740 tline = tline->next;
2741 if (!tline->next) {
2742 free_tlist(origline);
2743 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2744 return DIRECTIVE_FOUND;
2746 t = expand_smacro(tline->next);
2747 tline->next = NULL;
2748 free_tlist(origline);
2749 tline = t;
2750 tptr = &t;
2751 tokval.t_type = TOKEN_INVALID;
2752 evalresult =
2753 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2754 free_tlist(tline);
2755 if (!evalresult)
2756 return DIRECTIVE_FOUND;
2757 if (tokval.t_type)
2758 error(ERR_WARNING|ERR_PASS1,
2759 "trailing garbage after expression ignored");
2760 if (!is_simple(evalresult)) {
2761 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2762 return DIRECTIVE_FOUND;
2764 mmac = istk->mstk;
2765 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2766 mmac = mmac->next_active;
2767 if (!mmac) {
2768 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2769 } else if (mmac->nparam == 0) {
2770 error(ERR_NONFATAL,
2771 "`%%rotate' invoked within macro without parameters");
2772 } else {
2773 int rotate = mmac->rotate + reloc_value(evalresult);
2775 rotate %= (int)mmac->nparam;
2776 if (rotate < 0)
2777 rotate += mmac->nparam;
2779 mmac->rotate = rotate;
2781 return DIRECTIVE_FOUND;
2783 case PP_REP:
2784 nolist = false;
2785 do {
2786 tline = tline->next;
2787 } while (tok_type_(tline, TOK_WHITESPACE));
2789 if (tok_type_(tline, TOK_ID) &&
2790 nasm_stricmp(tline->text, ".nolist") == 0) {
2791 nolist = true;
2792 do {
2793 tline = tline->next;
2794 } while (tok_type_(tline, TOK_WHITESPACE));
2797 if (tline) {
2798 t = expand_smacro(tline);
2799 tptr = &t;
2800 tokval.t_type = TOKEN_INVALID;
2801 evalresult =
2802 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2803 if (!evalresult) {
2804 free_tlist(origline);
2805 return DIRECTIVE_FOUND;
2807 if (tokval.t_type)
2808 error(ERR_WARNING|ERR_PASS1,
2809 "trailing garbage after expression ignored");
2810 if (!is_simple(evalresult)) {
2811 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2812 return DIRECTIVE_FOUND;
2814 count = reloc_value(evalresult) + 1;
2815 } else {
2816 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2817 count = 0;
2819 free_tlist(origline);
2821 tmp_defining = defining;
2822 defining = nasm_malloc(sizeof(MMacro));
2823 defining->prev = NULL;
2824 defining->name = NULL; /* flags this macro as a %rep block */
2825 defining->casesense = false;
2826 defining->plus = false;
2827 defining->nolist = nolist;
2828 defining->in_progress = count;
2829 defining->max_depth = 0;
2830 defining->nparam_min = defining->nparam_max = 0;
2831 defining->defaults = NULL;
2832 defining->dlist = NULL;
2833 defining->expansion = NULL;
2834 defining->next_active = istk->mstk;
2835 defining->rep_nest = tmp_defining;
2836 return DIRECTIVE_FOUND;
2838 case PP_ENDREP:
2839 if (!defining || defining->name) {
2840 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2841 return DIRECTIVE_FOUND;
2845 * Now we have a "macro" defined - although it has no name
2846 * and we won't be entering it in the hash tables - we must
2847 * push a macro-end marker for it on to istk->expansion.
2848 * After that, it will take care of propagating itself (a
2849 * macro-end marker line for a macro which is really a %rep
2850 * block will cause the macro to be re-expanded, complete
2851 * with another macro-end marker to ensure the process
2852 * continues) until the whole expansion is forcibly removed
2853 * from istk->expansion by a %exitrep.
2855 l = nasm_malloc(sizeof(Line));
2856 l->next = istk->expansion;
2857 l->finishes = defining;
2858 l->first = NULL;
2859 istk->expansion = l;
2861 istk->mstk = defining;
2863 list->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2864 tmp_defining = defining;
2865 defining = defining->rep_nest;
2866 free_tlist(origline);
2867 return DIRECTIVE_FOUND;
2869 case PP_EXITREP:
2871 * We must search along istk->expansion until we hit a
2872 * macro-end marker for a macro with no name. Then we set
2873 * its `in_progress' flag to 0.
2875 for (l = istk->expansion; l; l = l->next)
2876 if (l->finishes && !l->finishes->name)
2877 break;
2879 if (l)
2880 l->finishes->in_progress = 1;
2881 else
2882 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
2883 free_tlist(origline);
2884 return DIRECTIVE_FOUND;
2886 case PP_XDEFINE:
2887 case PP_IXDEFINE:
2888 case PP_DEFINE:
2889 case PP_IDEFINE:
2890 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
2892 tline = tline->next;
2893 skip_white_(tline);
2894 tline = expand_id(tline);
2895 if (!tline || (tline->type != TOK_ID &&
2896 (tline->type != TOK_PREPROC_ID ||
2897 tline->text[1] != '$'))) {
2898 error(ERR_NONFATAL, "`%s' expects a macro identifier",
2899 pp_directives[i]);
2900 free_tlist(origline);
2901 return DIRECTIVE_FOUND;
2904 ctx = get_ctx(tline->text, &mname, false);
2905 last = tline;
2906 param_start = tline = tline->next;
2907 nparam = 0;
2909 /* Expand the macro definition now for %xdefine and %ixdefine */
2910 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
2911 tline = expand_smacro(tline);
2913 if (tok_is_(tline, "(")) {
2915 * This macro has parameters.
2918 tline = tline->next;
2919 while (1) {
2920 skip_white_(tline);
2921 if (!tline) {
2922 error(ERR_NONFATAL, "parameter identifier expected");
2923 free_tlist(origline);
2924 return DIRECTIVE_FOUND;
2926 if (tline->type != TOK_ID) {
2927 error(ERR_NONFATAL,
2928 "`%s': parameter identifier expected",
2929 tline->text);
2930 free_tlist(origline);
2931 return DIRECTIVE_FOUND;
2933 tline->type = TOK_SMAC_PARAM + nparam++;
2934 tline = tline->next;
2935 skip_white_(tline);
2936 if (tok_is_(tline, ",")) {
2937 tline = tline->next;
2938 } else {
2939 if (!tok_is_(tline, ")")) {
2940 error(ERR_NONFATAL,
2941 "`)' expected to terminate macro template");
2942 free_tlist(origline);
2943 return DIRECTIVE_FOUND;
2945 break;
2948 last = tline;
2949 tline = tline->next;
2951 if (tok_type_(tline, TOK_WHITESPACE))
2952 last = tline, tline = tline->next;
2953 macro_start = NULL;
2954 last->next = NULL;
2955 t = tline;
2956 while (t) {
2957 if (t->type == TOK_ID) {
2958 for (tt = param_start; tt; tt = tt->next)
2959 if (tt->type >= TOK_SMAC_PARAM &&
2960 !strcmp(tt->text, t->text))
2961 t->type = tt->type;
2963 tt = t->next;
2964 t->next = macro_start;
2965 macro_start = t;
2966 t = tt;
2969 * Good. We now have a macro name, a parameter count, and a
2970 * token list (in reverse order) for an expansion. We ought
2971 * to be OK just to create an SMacro, store it, and let
2972 * free_tlist have the rest of the line (which we have
2973 * carefully re-terminated after chopping off the expansion
2974 * from the end).
2976 define_smacro(ctx, mname, casesense, nparam, macro_start);
2977 free_tlist(origline);
2978 return DIRECTIVE_FOUND;
2980 case PP_UNDEF:
2981 tline = tline->next;
2982 skip_white_(tline);
2983 tline = expand_id(tline);
2984 if (!tline || (tline->type != TOK_ID &&
2985 (tline->type != TOK_PREPROC_ID ||
2986 tline->text[1] != '$'))) {
2987 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
2988 free_tlist(origline);
2989 return DIRECTIVE_FOUND;
2991 if (tline->next) {
2992 error(ERR_WARNING|ERR_PASS1,
2993 "trailing garbage after macro name ignored");
2996 /* Find the context that symbol belongs to */
2997 ctx = get_ctx(tline->text, &mname, false);
2998 undef_smacro(ctx, mname);
2999 free_tlist(origline);
3000 return DIRECTIVE_FOUND;
3002 case PP_DEFSTR:
3003 case PP_IDEFSTR:
3004 casesense = (i == PP_DEFSTR);
3006 tline = tline->next;
3007 skip_white_(tline);
3008 tline = expand_id(tline);
3009 if (!tline || (tline->type != TOK_ID &&
3010 (tline->type != TOK_PREPROC_ID ||
3011 tline->text[1] != '$'))) {
3012 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3013 pp_directives[i]);
3014 free_tlist(origline);
3015 return DIRECTIVE_FOUND;
3018 ctx = get_ctx(tline->text, &mname, false);
3019 last = tline;
3020 tline = expand_smacro(tline->next);
3021 last->next = NULL;
3023 while (tok_type_(tline, TOK_WHITESPACE))
3024 tline = delete_Token(tline);
3026 p = detoken(tline, false);
3027 macro_start = nasm_malloc(sizeof(*macro_start));
3028 macro_start->next = NULL;
3029 macro_start->text = nasm_quote(p, strlen(p));
3030 macro_start->type = TOK_STRING;
3031 macro_start->a.mac = NULL;
3032 nasm_free(p);
3035 * We now have a macro name, an implicit parameter count of
3036 * zero, and a string token to use as an expansion. Create
3037 * and store an SMacro.
3039 define_smacro(ctx, mname, casesense, 0, macro_start);
3040 free_tlist(origline);
3041 return DIRECTIVE_FOUND;
3043 case PP_DEFTOK:
3044 case PP_IDEFTOK:
3045 casesense = (i == PP_DEFTOK);
3047 tline = tline->next;
3048 skip_white_(tline);
3049 tline = expand_id(tline);
3050 if (!tline || (tline->type != TOK_ID &&
3051 (tline->type != TOK_PREPROC_ID ||
3052 tline->text[1] != '$'))) {
3053 error(ERR_NONFATAL,
3054 "`%s' expects a macro identifier as first parameter",
3055 pp_directives[i]);
3056 free_tlist(origline);
3057 return DIRECTIVE_FOUND;
3059 ctx = get_ctx(tline->text, &mname, false);
3060 last = tline;
3061 tline = expand_smacro(tline->next);
3062 last->next = NULL;
3064 t = tline;
3065 while (tok_type_(t, TOK_WHITESPACE))
3066 t = t->next;
3067 /* t should now point to the string */
3068 if (t->type != TOK_STRING) {
3069 error(ERR_NONFATAL,
3070 "`%s` requires string as second parameter",
3071 pp_directives[i]);
3072 free_tlist(tline);
3073 free_tlist(origline);
3074 return DIRECTIVE_FOUND;
3077 nasm_unquote_cstr(t->text, i);
3078 macro_start = tokenize(t->text);
3081 * We now have a macro name, an implicit parameter count of
3082 * zero, and a numeric token to use as an expansion. Create
3083 * and store an SMacro.
3085 define_smacro(ctx, mname, casesense, 0, macro_start);
3086 free_tlist(tline);
3087 free_tlist(origline);
3088 return DIRECTIVE_FOUND;
3090 case PP_PATHSEARCH:
3092 FILE *fp;
3093 StrList *xsl = NULL;
3094 StrList **xst = &xsl;
3096 casesense = true;
3098 tline = tline->next;
3099 skip_white_(tline);
3100 tline = expand_id(tline);
3101 if (!tline || (tline->type != TOK_ID &&
3102 (tline->type != TOK_PREPROC_ID ||
3103 tline->text[1] != '$'))) {
3104 error(ERR_NONFATAL,
3105 "`%%pathsearch' expects a macro identifier as first parameter");
3106 free_tlist(origline);
3107 return DIRECTIVE_FOUND;
3109 ctx = get_ctx(tline->text, &mname, false);
3110 last = tline;
3111 tline = expand_smacro(tline->next);
3112 last->next = NULL;
3114 t = tline;
3115 while (tok_type_(t, TOK_WHITESPACE))
3116 t = t->next;
3118 if (!t || (t->type != TOK_STRING &&
3119 t->type != TOK_INTERNAL_STRING)) {
3120 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3121 free_tlist(tline);
3122 free_tlist(origline);
3123 return DIRECTIVE_FOUND; /* but we did _something_ */
3125 if (t->next)
3126 error(ERR_WARNING|ERR_PASS1,
3127 "trailing garbage after `%%pathsearch' ignored");
3128 p = t->text;
3129 if (t->type != TOK_INTERNAL_STRING)
3130 nasm_unquote(p, NULL);
3132 fp = inc_fopen(p, &xsl, &xst, true);
3133 if (fp) {
3134 p = xsl->str;
3135 fclose(fp); /* Don't actually care about the file */
3137 macro_start = nasm_malloc(sizeof(*macro_start));
3138 macro_start->next = NULL;
3139 macro_start->text = nasm_quote(p, strlen(p));
3140 macro_start->type = TOK_STRING;
3141 macro_start->a.mac = NULL;
3142 if (xsl)
3143 nasm_free(xsl);
3146 * We now have a macro name, an implicit parameter count of
3147 * zero, and a string token to use as an expansion. Create
3148 * and store an SMacro.
3150 define_smacro(ctx, mname, casesense, 0, macro_start);
3151 free_tlist(tline);
3152 free_tlist(origline);
3153 return DIRECTIVE_FOUND;
3156 case PP_STRLEN:
3157 casesense = true;
3159 tline = tline->next;
3160 skip_white_(tline);
3161 tline = expand_id(tline);
3162 if (!tline || (tline->type != TOK_ID &&
3163 (tline->type != TOK_PREPROC_ID ||
3164 tline->text[1] != '$'))) {
3165 error(ERR_NONFATAL,
3166 "`%%strlen' expects a macro identifier as first parameter");
3167 free_tlist(origline);
3168 return DIRECTIVE_FOUND;
3170 ctx = get_ctx(tline->text, &mname, false);
3171 last = tline;
3172 tline = expand_smacro(tline->next);
3173 last->next = NULL;
3175 t = tline;
3176 while (tok_type_(t, TOK_WHITESPACE))
3177 t = t->next;
3178 /* t should now point to the string */
3179 if (t->type != TOK_STRING) {
3180 error(ERR_NONFATAL,
3181 "`%%strlen` requires string as second parameter");
3182 free_tlist(tline);
3183 free_tlist(origline);
3184 return DIRECTIVE_FOUND;
3187 macro_start = nasm_malloc(sizeof(*macro_start));
3188 macro_start->next = NULL;
3189 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3190 macro_start->a.mac = NULL;
3193 * We now have a macro name, an implicit parameter count of
3194 * zero, and a numeric token to use as an expansion. Create
3195 * and store an SMacro.
3197 define_smacro(ctx, mname, casesense, 0, macro_start);
3198 free_tlist(tline);
3199 free_tlist(origline);
3200 return DIRECTIVE_FOUND;
3202 case PP_STRCAT:
3203 casesense = true;
3205 tline = tline->next;
3206 skip_white_(tline);
3207 tline = expand_id(tline);
3208 if (!tline || (tline->type != TOK_ID &&
3209 (tline->type != TOK_PREPROC_ID ||
3210 tline->text[1] != '$'))) {
3211 error(ERR_NONFATAL,
3212 "`%%strcat' expects a macro identifier as first parameter");
3213 free_tlist(origline);
3214 return DIRECTIVE_FOUND;
3216 ctx = get_ctx(tline->text, &mname, false);
3217 last = tline;
3218 tline = expand_smacro(tline->next);
3219 last->next = NULL;
3221 len = 0;
3222 for (t = tline; t; t = t->next) {
3223 switch (t->type) {
3224 case TOK_WHITESPACE:
3225 break;
3226 case TOK_STRING:
3227 len += t->a.len = nasm_unquote(t->text, NULL);
3228 break;
3229 case TOK_OTHER:
3230 if (!strcmp(t->text, ",")) /* permit comma separators */
3231 break;
3232 /* else fall through */
3233 default:
3234 error(ERR_NONFATAL,
3235 "non-string passed to `%%strcat' (%d)", t->type);
3236 free_tlist(tline);
3237 free_tlist(origline);
3238 return DIRECTIVE_FOUND;
3242 p = pp = nasm_malloc(len);
3243 for (t = tline; t; t = t->next) {
3244 if (t->type == TOK_STRING) {
3245 memcpy(p, t->text, t->a.len);
3246 p += t->a.len;
3251 * We now have a macro name, an implicit parameter count of
3252 * zero, and a numeric token to use as an expansion. Create
3253 * and store an SMacro.
3255 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3256 macro_start->text = nasm_quote(pp, len);
3257 nasm_free(pp);
3258 define_smacro(ctx, mname, casesense, 0, macro_start);
3259 free_tlist(tline);
3260 free_tlist(origline);
3261 return DIRECTIVE_FOUND;
3263 case PP_SUBSTR:
3265 int64_t a1, a2;
3266 size_t len;
3268 casesense = true;
3270 tline = tline->next;
3271 skip_white_(tline);
3272 tline = expand_id(tline);
3273 if (!tline || (tline->type != TOK_ID &&
3274 (tline->type != TOK_PREPROC_ID ||
3275 tline->text[1] != '$'))) {
3276 error(ERR_NONFATAL,
3277 "`%%substr' expects a macro identifier as first parameter");
3278 free_tlist(origline);
3279 return DIRECTIVE_FOUND;
3281 ctx = get_ctx(tline->text, &mname, false);
3282 last = tline;
3283 tline = expand_smacro(tline->next);
3284 last->next = NULL;
3286 t = tline->next;
3287 while (tok_type_(t, TOK_WHITESPACE))
3288 t = t->next;
3290 /* t should now point to the string */
3291 if (t->type != TOK_STRING) {
3292 error(ERR_NONFATAL,
3293 "`%%substr` requires string as second parameter");
3294 free_tlist(tline);
3295 free_tlist(origline);
3296 return DIRECTIVE_FOUND;
3299 tt = t->next;
3300 tptr = &tt;
3301 tokval.t_type = TOKEN_INVALID;
3302 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3303 pass, error, NULL);
3304 if (!evalresult) {
3305 free_tlist(tline);
3306 free_tlist(origline);
3307 return DIRECTIVE_FOUND;
3308 } else if (!is_simple(evalresult)) {
3309 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3310 free_tlist(tline);
3311 free_tlist(origline);
3312 return DIRECTIVE_FOUND;
3314 a1 = evalresult->value-1;
3316 while (tok_type_(tt, TOK_WHITESPACE))
3317 tt = tt->next;
3318 if (!tt) {
3319 a2 = 1; /* Backwards compatibility: one character */
3320 } else {
3321 tokval.t_type = TOKEN_INVALID;
3322 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3323 pass, error, NULL);
3324 if (!evalresult) {
3325 free_tlist(tline);
3326 free_tlist(origline);
3327 return DIRECTIVE_FOUND;
3328 } else if (!is_simple(evalresult)) {
3329 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3330 free_tlist(tline);
3331 free_tlist(origline);
3332 return DIRECTIVE_FOUND;
3334 a2 = evalresult->value;
3337 len = nasm_unquote(t->text, NULL);
3338 if (a2 < 0)
3339 a2 = a2+1+len-a1;
3340 if (a1+a2 > (int64_t)len)
3341 a2 = len-a1;
3343 macro_start = nasm_malloc(sizeof(*macro_start));
3344 macro_start->next = NULL;
3345 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3346 macro_start->type = TOK_STRING;
3347 macro_start->a.mac = NULL;
3350 * We now have a macro name, an implicit parameter count of
3351 * zero, and a numeric token to use as an expansion. Create
3352 * and store an SMacro.
3354 define_smacro(ctx, mname, casesense, 0, macro_start);
3355 free_tlist(tline);
3356 free_tlist(origline);
3357 return DIRECTIVE_FOUND;
3360 case PP_ASSIGN:
3361 case PP_IASSIGN:
3362 casesense = (i == PP_ASSIGN);
3364 tline = tline->next;
3365 skip_white_(tline);
3366 tline = expand_id(tline);
3367 if (!tline || (tline->type != TOK_ID &&
3368 (tline->type != TOK_PREPROC_ID ||
3369 tline->text[1] != '$'))) {
3370 error(ERR_NONFATAL,
3371 "`%%%sassign' expects a macro identifier",
3372 (i == PP_IASSIGN ? "i" : ""));
3373 free_tlist(origline);
3374 return DIRECTIVE_FOUND;
3376 ctx = get_ctx(tline->text, &mname, false);
3377 last = tline;
3378 tline = expand_smacro(tline->next);
3379 last->next = NULL;
3381 t = tline;
3382 tptr = &t;
3383 tokval.t_type = TOKEN_INVALID;
3384 evalresult =
3385 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3386 free_tlist(tline);
3387 if (!evalresult) {
3388 free_tlist(origline);
3389 return DIRECTIVE_FOUND;
3392 if (tokval.t_type)
3393 error(ERR_WARNING|ERR_PASS1,
3394 "trailing garbage after expression ignored");
3396 if (!is_simple(evalresult)) {
3397 error(ERR_NONFATAL,
3398 "non-constant value given to `%%%sassign'",
3399 (i == PP_IASSIGN ? "i" : ""));
3400 free_tlist(origline);
3401 return DIRECTIVE_FOUND;
3404 macro_start = nasm_malloc(sizeof(*macro_start));
3405 macro_start->next = NULL;
3406 make_tok_num(macro_start, reloc_value(evalresult));
3407 macro_start->a.mac = NULL;
3410 * We now have a macro name, an implicit parameter count of
3411 * zero, and a numeric token to use as an expansion. Create
3412 * and store an SMacro.
3414 define_smacro(ctx, mname, casesense, 0, macro_start);
3415 free_tlist(origline);
3416 return DIRECTIVE_FOUND;
3418 case PP_LINE:
3420 * Syntax is `%line nnn[+mmm] [filename]'
3422 tline = tline->next;
3423 skip_white_(tline);
3424 if (!tok_type_(tline, TOK_NUMBER)) {
3425 error(ERR_NONFATAL, "`%%line' expects line number");
3426 free_tlist(origline);
3427 return DIRECTIVE_FOUND;
3429 k = readnum(tline->text, &err);
3430 m = 1;
3431 tline = tline->next;
3432 if (tok_is_(tline, "+")) {
3433 tline = tline->next;
3434 if (!tok_type_(tline, TOK_NUMBER)) {
3435 error(ERR_NONFATAL, "`%%line' expects line increment");
3436 free_tlist(origline);
3437 return DIRECTIVE_FOUND;
3439 m = readnum(tline->text, &err);
3440 tline = tline->next;
3442 skip_white_(tline);
3443 src_set_linnum(k);
3444 istk->lineinc = m;
3445 if (tline) {
3446 nasm_free(src_set_fname(detoken(tline, false)));
3448 free_tlist(origline);
3449 return DIRECTIVE_FOUND;
3451 default:
3452 error(ERR_FATAL,
3453 "preprocessor directive `%s' not yet implemented",
3454 pp_directives[i]);
3455 return DIRECTIVE_FOUND;
3460 * Ensure that a macro parameter contains a condition code and
3461 * nothing else. Return the condition code index if so, or -1
3462 * otherwise.
3464 static int find_cc(Token * t)
3466 Token *tt;
3467 int i, j, k, m;
3469 if (!t)
3470 return -1; /* Probably a %+ without a space */
3472 skip_white_(t);
3473 if (t->type != TOK_ID)
3474 return -1;
3475 tt = t->next;
3476 skip_white_(tt);
3477 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3478 return -1;
3480 i = -1;
3481 j = elements(conditions);
3482 while (j - i > 1) {
3483 k = (j + i) / 2;
3484 m = nasm_stricmp(t->text, conditions[k]);
3485 if (m == 0) {
3486 i = k;
3487 j = -2;
3488 break;
3489 } else if (m < 0) {
3490 j = k;
3491 } else
3492 i = k;
3494 if (j != -2)
3495 return -1;
3496 return i;
3499 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3501 Token **tail, *t, *tt;
3502 Token **paste_head;
3503 bool did_paste = false;
3504 char *tmp;
3506 /* Now handle token pasting... */
3507 paste_head = NULL;
3508 tail = head;
3509 while ((t = *tail) && (tt = t->next)) {
3510 switch (t->type) {
3511 case TOK_WHITESPACE:
3512 if (tt->type == TOK_WHITESPACE) {
3513 /* Zap adjacent whitespace tokens */
3514 t->next = delete_Token(tt);
3515 } else {
3516 /* Do not advance paste_head here */
3517 tail = &t->next;
3519 break;
3520 case TOK_ID:
3521 case TOK_PREPROC_ID:
3522 case TOK_NUMBER:
3523 case TOK_FLOAT:
3525 size_t len = 0;
3526 char *tmp, *p;
3528 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3529 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3530 tt->type == TOK_OTHER)) {
3531 len += strlen(tt->text);
3532 tt = tt->next;
3536 * Now tt points to the first token after
3537 * the potential paste area...
3539 if (tt != t->next) {
3540 /* We have at least two tokens... */
3541 len += strlen(t->text);
3542 p = tmp = nasm_malloc(len+1);
3544 while (t != tt) {
3545 strcpy(p, t->text);
3546 p = strchr(p, '\0');
3547 t = delete_Token(t);
3550 t = *tail = tokenize(tmp);
3551 nasm_free(tmp);
3553 while (t->next) {
3554 tail = &t->next;
3555 t = t->next;
3557 t->next = tt; /* Attach the remaining token chain */
3559 did_paste = true;
3561 paste_head = tail;
3562 tail = &t->next;
3563 break;
3565 case TOK_PASTE: /* %+ */
3566 if (handle_paste_tokens) {
3567 /* Zap %+ and whitespace tokens to the right */
3568 while (t && (t->type == TOK_WHITESPACE ||
3569 t->type == TOK_PASTE))
3570 t = *tail = delete_Token(t);
3571 if (!paste_head || !t)
3572 break; /* Nothing to paste with */
3573 tail = paste_head;
3574 t = *tail;
3575 tt = t->next;
3576 while (tok_type_(tt, TOK_WHITESPACE))
3577 tt = t->next = delete_Token(tt);
3579 if (tt) {
3580 tmp = nasm_strcat(t->text, tt->text);
3581 delete_Token(t);
3582 tt = delete_Token(tt);
3583 t = *tail = tokenize(tmp);
3584 nasm_free(tmp);
3585 while (t->next) {
3586 tail = &t->next;
3587 t = t->next;
3589 t->next = tt; /* Attach the remaining token chain */
3590 did_paste = true;
3592 paste_head = tail;
3593 tail = &t->next;
3594 break;
3596 /* else fall through */
3597 default:
3598 tail = paste_head = &t->next;
3599 break;
3602 return did_paste;
3605 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3606 * %-n) and MMacro-local identifiers (%%foo) as well as
3607 * macro indirection (%[...]).
3609 static Token *expand_mmac_params(Token * tline)
3611 Token *t, *tt, **tail, *thead;
3612 bool changed = false;
3614 tail = &thead;
3615 thead = NULL;
3617 while (tline) {
3618 if (tline->type == TOK_PREPROC_ID &&
3619 (((tline->text[1] == '+' || tline->text[1] == '-')
3620 && tline->text[2]) || tline->text[1] == '%'
3621 || (tline->text[1] >= '0' && tline->text[1] <= '9'))) {
3622 char *text = NULL;
3623 int type = 0, cc; /* type = 0 to placate optimisers */
3624 char tmpbuf[30];
3625 unsigned int n;
3626 int i;
3627 MMacro *mac;
3629 t = tline;
3630 tline = tline->next;
3632 mac = istk->mstk;
3633 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3634 mac = mac->next_active;
3635 if (!mac)
3636 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3637 else
3638 switch (t->text[1]) {
3640 * We have to make a substitution of one of the
3641 * forms %1, %-1, %+1, %%foo, %0.
3643 case '0':
3644 type = TOK_NUMBER;
3645 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3646 text = nasm_strdup(tmpbuf);
3647 break;
3648 case '%':
3649 type = TOK_ID;
3650 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3651 mac->unique);
3652 text = nasm_strcat(tmpbuf, t->text + 2);
3653 break;
3654 case '-':
3655 n = atoi(t->text + 2) - 1;
3656 if (n >= mac->nparam)
3657 tt = NULL;
3658 else {
3659 if (mac->nparam > 1)
3660 n = (n + mac->rotate) % mac->nparam;
3661 tt = mac->params[n];
3663 cc = find_cc(tt);
3664 if (cc == -1) {
3665 error(ERR_NONFATAL,
3666 "macro parameter %d is not a condition code",
3667 n + 1);
3668 text = NULL;
3669 } else {
3670 type = TOK_ID;
3671 if (inverse_ccs[cc] == -1) {
3672 error(ERR_NONFATAL,
3673 "condition code `%s' is not invertible",
3674 conditions[cc]);
3675 text = NULL;
3676 } else
3677 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3679 break;
3680 case '+':
3681 n = atoi(t->text + 2) - 1;
3682 if (n >= mac->nparam)
3683 tt = NULL;
3684 else {
3685 if (mac->nparam > 1)
3686 n = (n + mac->rotate) % mac->nparam;
3687 tt = mac->params[n];
3689 cc = find_cc(tt);
3690 if (cc == -1) {
3691 error(ERR_NONFATAL,
3692 "macro parameter %d is not a condition code",
3693 n + 1);
3694 text = NULL;
3695 } else {
3696 type = TOK_ID;
3697 text = nasm_strdup(conditions[cc]);
3699 break;
3700 default:
3701 n = atoi(t->text + 1) - 1;
3702 if (n >= mac->nparam)
3703 tt = NULL;
3704 else {
3705 if (mac->nparam > 1)
3706 n = (n + mac->rotate) % mac->nparam;
3707 tt = mac->params[n];
3709 if (tt) {
3710 for (i = 0; i < mac->paramlen[n]; i++) {
3711 *tail = new_Token(NULL, tt->type, tt->text, 0);
3712 tail = &(*tail)->next;
3713 tt = tt->next;
3716 text = NULL; /* we've done it here */
3717 break;
3719 if (!text) {
3720 delete_Token(t);
3721 } else {
3722 *tail = t;
3723 tail = &t->next;
3724 t->type = type;
3725 nasm_free(t->text);
3726 t->text = text;
3727 t->a.mac = NULL;
3729 changed = true;
3730 continue;
3731 } else if (tline->type == TOK_INDIRECT) {
3732 t = tline;
3733 tline = tline->next;
3734 tt = tokenize(t->text);
3735 tt = expand_mmac_params(tt);
3736 tt = expand_smacro(tt);
3737 *tail = tt;
3738 while (tt) {
3739 tt->a.mac = NULL; /* Necessary? */
3740 tail = &tt->next;
3741 tt = tt->next;
3743 delete_Token(t);
3744 changed = true;
3745 } else if (tline->type == TOK_PREPROC_ID &&
3746 tline->text[0] == '%' && tline->text[1] == '$' &&
3747 (tok_type_(tline->next, TOK_ID) ||
3748 tok_type_(tline->next, TOK_PREPROC_ID) ||
3749 tok_type_(tline->next, TOK_FLOAT) ||
3750 tok_type_(tline->next, TOK_NUMBER) ||
3751 tok_type_(tline->next, TOK_OTHER))) {
3753 * In a sake of backward compatibility we allow
3754 * to expand local single macro that early before
3755 * pasting token code have place
3757 * NOTE: that new code MUST use %+ macro to obtain
3758 * same result
3760 t = tline;
3761 tline = tline->next;
3762 tt = tokenize(t->text);
3763 tt = expand_smacro(tt);
3764 *tail = tt;
3765 while (tt) {
3766 tt->a.mac = NULL;
3767 tail = &tt->next;
3768 tt = tt->next;
3770 delete_Token(t);
3771 changed = true;
3772 } else {
3773 t = *tail = tline;
3774 tline = tline->next;
3775 t->a.mac = NULL;
3776 tail = &t->next;
3779 *tail = NULL;
3781 if (changed)
3782 paste_tokens(&thead, false);
3784 return thead;
3788 * Expand all single-line macro calls made in the given line.
3789 * Return the expanded version of the line. The original is deemed
3790 * to be destroyed in the process. (In reality we'll just move
3791 * Tokens from input to output a lot of the time, rather than
3792 * actually bothering to destroy and replicate.)
3795 static Token *expand_smacro(Token * tline)
3797 Token *t, *tt, *mstart, **tail, *thead;
3798 SMacro *head = NULL, *m;
3799 Token **params;
3800 int *paramsize;
3801 unsigned int nparam, sparam;
3802 int brackets;
3803 Token *org_tline = tline;
3804 Context *ctx;
3805 const char *mname;
3806 int deadman = DEADMAN_LIMIT;
3807 bool expanded;
3810 * Trick: we should avoid changing the start token pointer since it can
3811 * be contained in "next" field of other token. Because of this
3812 * we allocate a copy of first token and work with it; at the end of
3813 * routine we copy it back
3815 if (org_tline) {
3816 tline = new_Token(org_tline->next, org_tline->type,
3817 org_tline->text, 0);
3818 tline->a.mac = org_tline->a.mac;
3819 nasm_free(org_tline->text);
3820 org_tline->text = NULL;
3823 expanded = true; /* Always expand %+ at least once */
3825 again:
3826 thead = NULL;
3827 tail = &thead;
3829 while (tline) { /* main token loop */
3830 if (!--deadman) {
3831 error(ERR_NONFATAL, "interminable macro recursion");
3832 goto err;
3835 if ((mname = tline->text)) {
3836 /* if this token is a local macro, look in local context */
3837 if (tline->type == TOK_ID) {
3838 head = (SMacro *)hash_findix(&smacros, mname);
3839 } else if (tline->type == TOK_PREPROC_ID) {
3840 ctx = get_ctx(mname, &mname, true);
3841 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
3842 } else
3843 head = NULL;
3846 * We've hit an identifier. As in is_mmacro below, we first
3847 * check whether the identifier is a single-line macro at
3848 * all, then think about checking for parameters if
3849 * necessary.
3851 for (m = head; m; m = m->next)
3852 if (!mstrcmp(m->name, mname, m->casesense))
3853 break;
3854 if (m) {
3855 mstart = tline;
3856 params = NULL;
3857 paramsize = NULL;
3858 if (m->nparam == 0) {
3860 * Simple case: the macro is parameterless. Discard the
3861 * one token that the macro call took, and push the
3862 * expansion back on the to-do stack.
3864 if (!m->expansion) {
3865 if (!strcmp("__FILE__", m->name)) {
3866 int32_t num = 0;
3867 char *file = NULL;
3868 src_get(&num, &file);
3869 tline->text = nasm_quote(file, strlen(file));
3870 tline->type = TOK_STRING;
3871 nasm_free(file);
3872 continue;
3874 if (!strcmp("__LINE__", m->name)) {
3875 nasm_free(tline->text);
3876 make_tok_num(tline, src_get_linnum());
3877 continue;
3879 if (!strcmp("__BITS__", m->name)) {
3880 nasm_free(tline->text);
3881 make_tok_num(tline, globalbits);
3882 continue;
3884 tline = delete_Token(tline);
3885 continue;
3887 } else {
3889 * Complicated case: at least one macro with this name
3890 * exists and takes parameters. We must find the
3891 * parameters in the call, count them, find the SMacro
3892 * that corresponds to that form of the macro call, and
3893 * substitute for the parameters when we expand. What a
3894 * pain.
3896 /*tline = tline->next;
3897 skip_white_(tline); */
3898 do {
3899 t = tline->next;
3900 while (tok_type_(t, TOK_SMAC_END)) {
3901 t->a.mac->in_progress = false;
3902 t->text = NULL;
3903 t = tline->next = delete_Token(t);
3905 tline = t;
3906 } while (tok_type_(tline, TOK_WHITESPACE));
3907 if (!tok_is_(tline, "(")) {
3909 * This macro wasn't called with parameters: ignore
3910 * the call. (Behaviour borrowed from gnu cpp.)
3912 tline = mstart;
3913 m = NULL;
3914 } else {
3915 int paren = 0;
3916 int white = 0;
3917 brackets = 0;
3918 nparam = 0;
3919 sparam = PARAM_DELTA;
3920 params = nasm_malloc(sparam * sizeof(Token *));
3921 params[0] = tline->next;
3922 paramsize = nasm_malloc(sparam * sizeof(int));
3923 paramsize[0] = 0;
3924 while (true) { /* parameter loop */
3926 * For some unusual expansions
3927 * which concatenates function call
3929 t = tline->next;
3930 while (tok_type_(t, TOK_SMAC_END)) {
3931 t->a.mac->in_progress = false;
3932 t->text = NULL;
3933 t = tline->next = delete_Token(t);
3935 tline = t;
3937 if (!tline) {
3938 error(ERR_NONFATAL,
3939 "macro call expects terminating `)'");
3940 break;
3942 if (tline->type == TOK_WHITESPACE
3943 && brackets <= 0) {
3944 if (paramsize[nparam])
3945 white++;
3946 else
3947 params[nparam] = tline->next;
3948 continue; /* parameter loop */
3950 if (tline->type == TOK_OTHER
3951 && tline->text[1] == 0) {
3952 char ch = tline->text[0];
3953 if (ch == ',' && !paren && brackets <= 0) {
3954 if (++nparam >= sparam) {
3955 sparam += PARAM_DELTA;
3956 params = nasm_realloc(params,
3957 sparam * sizeof(Token *));
3958 paramsize = nasm_realloc(paramsize,
3959 sparam * sizeof(int));
3961 params[nparam] = tline->next;
3962 paramsize[nparam] = 0;
3963 white = 0;
3964 continue; /* parameter loop */
3966 if (ch == '{' &&
3967 (brackets > 0 || (brackets == 0 &&
3968 !paramsize[nparam])))
3970 if (!(brackets++)) {
3971 params[nparam] = tline->next;
3972 continue; /* parameter loop */
3975 if (ch == '}' && brackets > 0)
3976 if (--brackets == 0) {
3977 brackets = -1;
3978 continue; /* parameter loop */
3980 if (ch == '(' && !brackets)
3981 paren++;
3982 if (ch == ')' && brackets <= 0)
3983 if (--paren < 0)
3984 break;
3986 if (brackets < 0) {
3987 brackets = 0;
3988 error(ERR_NONFATAL, "braces do not "
3989 "enclose all of macro parameter");
3991 paramsize[nparam] += white + 1;
3992 white = 0;
3993 } /* parameter loop */
3994 nparam++;
3995 while (m && (m->nparam != nparam ||
3996 mstrcmp(m->name, mname,
3997 m->casesense)))
3998 m = m->next;
3999 if (!m)
4000 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4001 "macro `%s' exists, "
4002 "but not taking %d parameters",
4003 mstart->text, nparam);
4006 if (m && m->in_progress)
4007 m = NULL;
4008 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4010 * Design question: should we handle !tline, which
4011 * indicates missing ')' here, or expand those
4012 * macros anyway, which requires the (t) test a few
4013 * lines down?
4015 nasm_free(params);
4016 nasm_free(paramsize);
4017 tline = mstart;
4018 } else {
4020 * Expand the macro: we are placed on the last token of the
4021 * call, so that we can easily split the call from the
4022 * following tokens. We also start by pushing an SMAC_END
4023 * token for the cycle removal.
4025 t = tline;
4026 if (t) {
4027 tline = t->next;
4028 t->next = NULL;
4030 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4031 tt->a.mac = m;
4032 m->in_progress = true;
4033 tline = tt;
4034 for (t = m->expansion; t; t = t->next) {
4035 if (t->type >= TOK_SMAC_PARAM) {
4036 Token *pcopy = tline, **ptail = &pcopy;
4037 Token *ttt, *pt;
4038 int i;
4040 ttt = params[t->type - TOK_SMAC_PARAM];
4041 i = paramsize[t->type - TOK_SMAC_PARAM];
4042 while (--i >= 0) {
4043 pt = *ptail = new_Token(tline, ttt->type,
4044 ttt->text, 0);
4045 ptail = &pt->next;
4046 ttt = ttt->next;
4048 tline = pcopy;
4049 } else if (t->type == TOK_PREPROC_Q) {
4050 tt = new_Token(tline, TOK_ID, mname, 0);
4051 tline = tt;
4052 } else if (t->type == TOK_PREPROC_QQ) {
4053 tt = new_Token(tline, TOK_ID, m->name, 0);
4054 tline = tt;
4055 } else {
4056 tt = new_Token(tline, t->type, t->text, 0);
4057 tline = tt;
4062 * Having done that, get rid of the macro call, and clean
4063 * up the parameters.
4065 nasm_free(params);
4066 nasm_free(paramsize);
4067 free_tlist(mstart);
4068 expanded = true;
4069 continue; /* main token loop */
4074 if (tline->type == TOK_SMAC_END) {
4075 tline->a.mac->in_progress = false;
4076 tline = delete_Token(tline);
4077 } else {
4078 t = *tail = tline;
4079 tline = tline->next;
4080 t->a.mac = NULL;
4081 t->next = NULL;
4082 tail = &t->next;
4087 * Now scan the entire line and look for successive TOK_IDs that resulted
4088 * after expansion (they can't be produced by tokenize()). The successive
4089 * TOK_IDs should be concatenated.
4090 * Also we look for %+ tokens and concatenate the tokens before and after
4091 * them (without white spaces in between).
4093 if (expanded && paste_tokens(&thead, true)) {
4095 * If we concatenated something, *and* we had previously expanded
4096 * an actual macro, scan the lines again for macros...
4098 tline = thead;
4099 expanded = false;
4100 goto again;
4103 err:
4104 if (org_tline) {
4105 if (thead) {
4106 *org_tline = *thead;
4107 /* since we just gave text to org_line, don't free it */
4108 thead->text = NULL;
4109 delete_Token(thead);
4110 } else {
4111 /* the expression expanded to empty line;
4112 we can't return NULL for some reasons
4113 we just set the line to a single WHITESPACE token. */
4114 memset(org_tline, 0, sizeof(*org_tline));
4115 org_tline->text = NULL;
4116 org_tline->type = TOK_WHITESPACE;
4118 thead = org_tline;
4121 return thead;
4125 * Similar to expand_smacro but used exclusively with macro identifiers
4126 * right before they are fetched in. The reason is that there can be
4127 * identifiers consisting of several subparts. We consider that if there
4128 * are more than one element forming the name, user wants a expansion,
4129 * otherwise it will be left as-is. Example:
4131 * %define %$abc cde
4133 * the identifier %$abc will be left as-is so that the handler for %define
4134 * will suck it and define the corresponding value. Other case:
4136 * %define _%$abc cde
4138 * In this case user wants name to be expanded *before* %define starts
4139 * working, so we'll expand %$abc into something (if it has a value;
4140 * otherwise it will be left as-is) then concatenate all successive
4141 * PP_IDs into one.
4143 static Token *expand_id(Token * tline)
4145 Token *cur, *oldnext = NULL;
4147 if (!tline || !tline->next)
4148 return tline;
4150 cur = tline;
4151 while (cur->next &&
4152 (cur->next->type == TOK_ID ||
4153 cur->next->type == TOK_PREPROC_ID
4154 || cur->next->type == TOK_NUMBER))
4155 cur = cur->next;
4157 /* If identifier consists of just one token, don't expand */
4158 if (cur == tline)
4159 return tline;
4161 if (cur) {
4162 oldnext = cur->next; /* Detach the tail past identifier */
4163 cur->next = NULL; /* so that expand_smacro stops here */
4166 tline = expand_smacro(tline);
4168 if (cur) {
4169 /* expand_smacro possibly changhed tline; re-scan for EOL */
4170 cur = tline;
4171 while (cur && cur->next)
4172 cur = cur->next;
4173 if (cur)
4174 cur->next = oldnext;
4177 return tline;
4181 * Determine whether the given line constitutes a multi-line macro
4182 * call, and return the MMacro structure called if so. Doesn't have
4183 * to check for an initial label - that's taken care of in
4184 * expand_mmacro - but must check numbers of parameters. Guaranteed
4185 * to be called with tline->type == TOK_ID, so the putative macro
4186 * name is easy to find.
4188 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4190 MMacro *head, *m;
4191 Token **params;
4192 int nparam;
4194 head = (MMacro *) hash_findix(&mmacros, tline->text);
4197 * Efficiency: first we see if any macro exists with the given
4198 * name. If not, we can return NULL immediately. _Then_ we
4199 * count the parameters, and then we look further along the
4200 * list if necessary to find the proper MMacro.
4202 for (m = head; m; m = m->next)
4203 if (!mstrcmp(m->name, tline->text, m->casesense))
4204 break;
4205 if (!m)
4206 return NULL;
4209 * OK, we have a potential macro. Count and demarcate the
4210 * parameters.
4212 count_mmac_params(tline->next, &nparam, &params);
4215 * So we know how many parameters we've got. Find the MMacro
4216 * structure that handles this number.
4218 while (m) {
4219 if (m->nparam_min <= nparam
4220 && (m->plus || nparam <= m->nparam_max)) {
4222 * This one is right. Just check if cycle removal
4223 * prohibits us using it before we actually celebrate...
4225 if (m->in_progress > m->max_depth) {
4226 if (m->max_depth > 0) {
4227 error(ERR_WARNING,
4228 "reached maximum recursion depth of %i",
4229 m->max_depth);
4231 nasm_free(params);
4232 return NULL;
4235 * It's right, and we can use it. Add its default
4236 * parameters to the end of our list if necessary.
4238 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4239 params =
4240 nasm_realloc(params,
4241 ((m->nparam_min + m->ndefs +
4242 1) * sizeof(*params)));
4243 while (nparam < m->nparam_min + m->ndefs) {
4244 params[nparam] = m->defaults[nparam - m->nparam_min];
4245 nparam++;
4249 * If we've gone over the maximum parameter count (and
4250 * we're in Plus mode), ignore parameters beyond
4251 * nparam_max.
4253 if (m->plus && nparam > m->nparam_max)
4254 nparam = m->nparam_max;
4256 * Then terminate the parameter list, and leave.
4258 if (!params) { /* need this special case */
4259 params = nasm_malloc(sizeof(*params));
4260 nparam = 0;
4262 params[nparam] = NULL;
4263 *params_array = params;
4264 return m;
4267 * This one wasn't right: look for the next one with the
4268 * same name.
4270 for (m = m->next; m; m = m->next)
4271 if (!mstrcmp(m->name, tline->text, m->casesense))
4272 break;
4276 * After all that, we didn't find one with the right number of
4277 * parameters. Issue a warning, and fail to expand the macro.
4279 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4280 "macro `%s' exists, but not taking %d parameters",
4281 tline->text, nparam);
4282 nasm_free(params);
4283 return NULL;
4288 * Save MMacro invocation specific fields in
4289 * preparation for a recursive macro expansion
4291 static void push_mmacro(MMacro *m)
4293 MMacroInvocation *i;
4295 i = nasm_malloc(sizeof(MMacroInvocation));
4296 i->prev = m->prev;
4297 i->params = m->params;
4298 i->iline = m->iline;
4299 i->nparam = m->nparam;
4300 i->rotate = m->rotate;
4301 i->paramlen = m->paramlen;
4302 i->unique = m->unique;
4303 i->condcnt = m->condcnt;
4304 m->prev = i;
4309 * Restore MMacro invocation specific fields that were
4310 * saved during a previous recursive macro expansion
4312 static void pop_mmacro(MMacro *m)
4314 MMacroInvocation *i;
4316 if (m->prev) {
4317 i = m->prev;
4318 m->prev = i->prev;
4319 m->params = i->params;
4320 m->iline = i->iline;
4321 m->nparam = i->nparam;
4322 m->rotate = i->rotate;
4323 m->paramlen = i->paramlen;
4324 m->unique = i->unique;
4325 m->condcnt = i->condcnt;
4326 nasm_free(i);
4332 * Expand the multi-line macro call made by the given line, if
4333 * there is one to be expanded. If there is, push the expansion on
4334 * istk->expansion and return 1. Otherwise return 0.
4336 static int expand_mmacro(Token * tline)
4338 Token *startline = tline;
4339 Token *label = NULL;
4340 int dont_prepend = 0;
4341 Token **params, *t, *mtok, *tt;
4342 MMacro *m;
4343 Line *l, *ll;
4344 int i, nparam, *paramlen;
4345 const char *mname;
4347 t = tline;
4348 skip_white_(t);
4349 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4350 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4351 return 0;
4352 mtok = t;
4353 m = is_mmacro(t, &params);
4354 if (m) {
4355 mname = t->text;
4356 } else {
4357 Token *last;
4359 * We have an id which isn't a macro call. We'll assume
4360 * it might be a label; we'll also check to see if a
4361 * colon follows it. Then, if there's another id after
4362 * that lot, we'll check it again for macro-hood.
4364 label = last = t;
4365 t = t->next;
4366 if (tok_type_(t, TOK_WHITESPACE))
4367 last = t, t = t->next;
4368 if (tok_is_(t, ":")) {
4369 dont_prepend = 1;
4370 last = t, t = t->next;
4371 if (tok_type_(t, TOK_WHITESPACE))
4372 last = t, t = t->next;
4374 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4375 return 0;
4376 last->next = NULL;
4377 mname = t->text;
4378 tline = t;
4382 * Fix up the parameters: this involves stripping leading and
4383 * trailing whitespace, then stripping braces if they are
4384 * present.
4386 for (nparam = 0; params[nparam]; nparam++) ;
4387 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4389 for (i = 0; params[i]; i++) {
4390 int brace = false;
4391 int comma = (!m->plus || i < nparam - 1);
4393 t = params[i];
4394 skip_white_(t);
4395 if (tok_is_(t, "{"))
4396 t = t->next, brace = true, comma = false;
4397 params[i] = t;
4398 paramlen[i] = 0;
4399 while (t) {
4400 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4401 break; /* ... because we have hit a comma */
4402 if (comma && t->type == TOK_WHITESPACE
4403 && tok_is_(t->next, ","))
4404 break; /* ... or a space then a comma */
4405 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4406 break; /* ... or a brace */
4407 t = t->next;
4408 paramlen[i]++;
4413 * OK, we have a MMacro structure together with a set of
4414 * parameters. We must now go through the expansion and push
4415 * copies of each Line on to istk->expansion. Substitution of
4416 * parameter tokens and macro-local tokens doesn't get done
4417 * until the single-line macro substitution process; this is
4418 * because delaying them allows us to change the semantics
4419 * later through %rotate.
4421 * First, push an end marker on to istk->expansion, mark this
4422 * macro as in progress, and set up its invocation-specific
4423 * variables.
4425 ll = nasm_malloc(sizeof(Line));
4426 ll->next = istk->expansion;
4427 ll->finishes = m;
4428 ll->first = NULL;
4429 istk->expansion = ll;
4432 * Save the previous MMacro expansion in the case of
4433 * macro recursion
4435 if (m->max_depth && m->in_progress)
4436 push_mmacro(m);
4438 m->in_progress ++;
4439 m->params = params;
4440 m->iline = tline;
4441 m->nparam = nparam;
4442 m->rotate = 0;
4443 m->paramlen = paramlen;
4444 m->unique = unique++;
4445 m->lineno = 0;
4446 m->condcnt = 0;
4448 m->next_active = istk->mstk;
4449 istk->mstk = m;
4451 list_for_each(l, m->expansion) {
4452 Token **tail;
4454 ll = nasm_malloc(sizeof(Line));
4455 ll->finishes = NULL;
4456 ll->next = istk->expansion;
4457 istk->expansion = ll;
4458 tail = &ll->first;
4460 list_for_each(t, l->first) {
4461 Token *x = t;
4462 switch (t->type) {
4463 case TOK_PREPROC_Q:
4464 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4465 break;
4466 case TOK_PREPROC_QQ:
4467 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4468 break;
4469 case TOK_PREPROC_ID:
4470 if (t->text[1] == '0' && t->text[2] == '0') {
4471 dont_prepend = -1;
4472 x = label;
4473 if (!x)
4474 continue;
4476 /* fall through */
4477 default:
4478 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4479 break;
4481 tail = &tt->next;
4483 *tail = NULL;
4487 * If we had a label, push it on as the first line of
4488 * the macro expansion.
4490 if (label) {
4491 if (dont_prepend < 0)
4492 free_tlist(startline);
4493 else {
4494 ll = nasm_malloc(sizeof(Line));
4495 ll->finishes = NULL;
4496 ll->next = istk->expansion;
4497 istk->expansion = ll;
4498 ll->first = startline;
4499 if (!dont_prepend) {
4500 while (label->next)
4501 label = label->next;
4502 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4507 list->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4509 return 1;
4512 /* The function that actually does the error reporting */
4513 static void verror(int severity, const char *fmt, va_list arg)
4515 char buff[1024];
4517 vsnprintf(buff, sizeof(buff), fmt, arg);
4519 if (istk && istk->mstk && istk->mstk->name)
4520 nasm_error(severity, "(%s:%d) %s", istk->mstk->name,
4521 istk->mstk->lineno, buff);
4522 else
4523 nasm_error(severity, "%s", buff);
4527 * Since preprocessor always operate only on the line that didn't
4528 * arrived yet, we should always use ERR_OFFBY1.
4530 static void error(int severity, const char *fmt, ...)
4532 va_list arg;
4534 /* If we're in a dead branch of IF or something like it, ignore the error */
4535 if (istk && istk->conds && !emitting(istk->conds->state))
4536 return;
4538 va_start(arg, fmt);
4539 verror(severity, fmt, arg);
4540 va_end(arg);
4544 * Because %else etc are evaluated in the state context
4545 * of the previous branch, errors might get lost with error():
4546 * %if 0 ... %else trailing garbage ... %endif
4547 * So %else etc should report errors with this function.
4549 static void error_precond(int severity, const char *fmt, ...)
4551 va_list arg;
4553 /* Only ignore the error if it's really in a dead branch */
4554 if (istk && istk->conds && istk->conds->state == COND_NEVER)
4555 return;
4557 va_start(arg, fmt);
4558 verror(severity, fmt, arg);
4559 va_end(arg);
4562 static void
4563 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4565 Token *t;
4567 cstk = NULL;
4568 istk = nasm_malloc(sizeof(Include));
4569 istk->next = NULL;
4570 istk->conds = NULL;
4571 istk->expansion = NULL;
4572 istk->mstk = NULL;
4573 istk->fp = fopen(file, "r");
4574 istk->fname = NULL;
4575 src_set_fname(nasm_strdup(file));
4576 src_set_linnum(0);
4577 istk->lineinc = 1;
4578 if (!istk->fp)
4579 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4580 file);
4581 defining = NULL;
4582 nested_mac_count = 0;
4583 nested_rep_count = 0;
4584 init_macros();
4585 unique = 0;
4586 if (tasm_compatible_mode) {
4587 stdmacpos = nasm_stdmac;
4588 } else {
4589 stdmacpos = nasm_stdmac_after_tasm;
4591 any_extrastdmac = extrastdmac && *extrastdmac;
4592 do_predef = true;
4593 list = listgen;
4596 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4597 * The caller, however, will also pass in 3 for preprocess-only so
4598 * we can set __PASS__ accordingly.
4600 pass = apass > 2 ? 2 : apass;
4602 dephead = deptail = deplist;
4603 if (deplist) {
4604 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4605 sl->next = NULL;
4606 strcpy(sl->str, file);
4607 *deptail = sl;
4608 deptail = &sl->next;
4612 * Define the __PASS__ macro. This is defined here unlike
4613 * all the other builtins, because it is special -- it varies between
4614 * passes.
4616 t = nasm_malloc(sizeof(*t));
4617 t->next = NULL;
4618 make_tok_num(t, apass);
4619 t->a.mac = NULL;
4620 define_smacro(NULL, "__PASS__", true, 0, t);
4623 static char *pp_getline(void)
4625 char *line;
4626 Token *tline;
4628 while (1) {
4630 * Fetch a tokenized line, either from the macro-expansion
4631 * buffer or from the input file.
4633 tline = NULL;
4634 while (istk->expansion && istk->expansion->finishes) {
4635 Line *l = istk->expansion;
4636 if (!l->finishes->name && l->finishes->in_progress > 1) {
4637 Line *ll;
4640 * This is a macro-end marker for a macro with no
4641 * name, which means it's not really a macro at all
4642 * but a %rep block, and the `in_progress' field is
4643 * more than 1, meaning that we still need to
4644 * repeat. (1 means the natural last repetition; 0
4645 * means termination by %exitrep.) We have
4646 * therefore expanded up to the %endrep, and must
4647 * push the whole block on to the expansion buffer
4648 * again. We don't bother to remove the macro-end
4649 * marker: we'd only have to generate another one
4650 * if we did.
4652 l->finishes->in_progress--;
4653 for (l = l->finishes->expansion; l; l = l->next) {
4654 Token *t, *tt, **tail;
4656 ll = nasm_malloc(sizeof(Line));
4657 ll->next = istk->expansion;
4658 ll->finishes = NULL;
4659 ll->first = NULL;
4660 tail = &ll->first;
4662 for (t = l->first; t; t = t->next) {
4663 if (t->text || t->type == TOK_WHITESPACE) {
4664 tt = *tail =
4665 new_Token(NULL, t->type, t->text, 0);
4666 tail = &tt->next;
4670 istk->expansion = ll;
4672 } else {
4674 * Check whether a `%rep' was started and not ended
4675 * within this macro expansion. This can happen and
4676 * should be detected. It's a fatal error because
4677 * I'm too confused to work out how to recover
4678 * sensibly from it.
4680 if (defining) {
4681 if (defining->name)
4682 error(ERR_PANIC,
4683 "defining with name in expansion");
4684 else if (istk->mstk->name)
4685 error(ERR_FATAL,
4686 "`%%rep' without `%%endrep' within"
4687 " expansion of macro `%s'",
4688 istk->mstk->name);
4692 * FIXME: investigate the relationship at this point between
4693 * istk->mstk and l->finishes
4696 MMacro *m = istk->mstk;
4697 istk->mstk = m->next_active;
4698 if (m->name) {
4700 * This was a real macro call, not a %rep, and
4701 * therefore the parameter information needs to
4702 * be freed.
4704 if (m->prev) {
4705 pop_mmacro(m);
4706 l->finishes->in_progress --;
4707 } else {
4708 nasm_free(m->params);
4709 free_tlist(m->iline);
4710 nasm_free(m->paramlen);
4711 l->finishes->in_progress = 0;
4713 } else
4714 free_mmacro(m);
4716 istk->expansion = l->next;
4717 nasm_free(l);
4718 list->downlevel(LIST_MACRO);
4721 while (1) { /* until we get a line we can use */
4723 if (istk->expansion) { /* from a macro expansion */
4724 char *p;
4725 Line *l = istk->expansion;
4726 if (istk->mstk)
4727 istk->mstk->lineno++;
4728 tline = l->first;
4729 istk->expansion = l->next;
4730 nasm_free(l);
4731 p = detoken(tline, false);
4732 list->line(LIST_MACRO, p);
4733 nasm_free(p);
4734 break;
4736 line = read_line();
4737 if (line) { /* from the current input file */
4738 line = prepreproc(line);
4739 tline = tokenize(line);
4740 nasm_free(line);
4741 break;
4744 * The current file has ended; work down the istk
4747 Include *i = istk;
4748 fclose(i->fp);
4749 if (i->conds)
4750 error(ERR_FATAL,
4751 "expected `%%endif' before end of file");
4752 /* only set line and file name if there's a next node */
4753 if (i->next) {
4754 src_set_linnum(i->lineno);
4755 nasm_free(src_set_fname(i->fname));
4757 istk = i->next;
4758 list->downlevel(LIST_INCLUDE);
4759 nasm_free(i);
4760 if (!istk)
4761 return NULL;
4762 if (istk->expansion && istk->expansion->finishes)
4763 break;
4768 * We must expand MMacro parameters and MMacro-local labels
4769 * _before_ we plunge into directive processing, to cope
4770 * with things like `%define something %1' such as STRUC
4771 * uses. Unless we're _defining_ a MMacro, in which case
4772 * those tokens should be left alone to go into the
4773 * definition; and unless we're in a non-emitting
4774 * condition, in which case we don't want to meddle with
4775 * anything.
4777 if (!defining && !(istk->conds && !emitting(istk->conds->state))
4778 && !(istk->mstk && !istk->mstk->in_progress)) {
4779 tline = expand_mmac_params(tline);
4783 * Check the line to see if it's a preprocessor directive.
4785 if (do_directive(tline) == DIRECTIVE_FOUND) {
4786 continue;
4787 } else if (defining) {
4789 * We're defining a multi-line macro. We emit nothing
4790 * at all, and just
4791 * shove the tokenized line on to the macro definition.
4793 Line *l = nasm_malloc(sizeof(Line));
4794 l->next = defining->expansion;
4795 l->first = tline;
4796 l->finishes = NULL;
4797 defining->expansion = l;
4798 continue;
4799 } else if (istk->conds && !emitting(istk->conds->state)) {
4801 * We're in a non-emitting branch of a condition block.
4802 * Emit nothing at all, not even a blank line: when we
4803 * emerge from the condition we'll give a line-number
4804 * directive so we keep our place correctly.
4806 free_tlist(tline);
4807 continue;
4808 } else if (istk->mstk && !istk->mstk->in_progress) {
4810 * We're in a %rep block which has been terminated, so
4811 * we're walking through to the %endrep without
4812 * emitting anything. Emit nothing at all, not even a
4813 * blank line: when we emerge from the %rep block we'll
4814 * give a line-number directive so we keep our place
4815 * correctly.
4817 free_tlist(tline);
4818 continue;
4819 } else {
4820 tline = expand_smacro(tline);
4821 if (!expand_mmacro(tline)) {
4823 * De-tokenize the line again, and emit it.
4825 line = detoken(tline, true);
4826 free_tlist(tline);
4827 break;
4828 } else {
4829 continue; /* expand_mmacro calls free_tlist */
4834 return line;
4837 static void pp_cleanup(int pass)
4839 if (defining) {
4840 if (defining->name) {
4841 error(ERR_NONFATAL,
4842 "end of file while still defining macro `%s'",
4843 defining->name);
4844 } else {
4845 error(ERR_NONFATAL, "end of file while still in %%rep");
4848 free_mmacro(defining);
4849 defining = NULL;
4851 while (cstk)
4852 ctx_pop();
4853 free_macros();
4854 while (istk) {
4855 Include *i = istk;
4856 istk = istk->next;
4857 fclose(i->fp);
4858 nasm_free(i->fname);
4859 nasm_free(i);
4861 while (cstk)
4862 ctx_pop();
4863 nasm_free(src_set_fname(NULL));
4864 if (pass == 0) {
4865 IncPath *i;
4866 free_llist(predef);
4867 delete_Blocks();
4868 while ((i = ipath)) {
4869 ipath = i->next;
4870 if (i->path)
4871 nasm_free(i->path);
4872 nasm_free(i);
4877 void pp_include_path(char *path)
4879 IncPath *i;
4881 i = nasm_malloc(sizeof(IncPath));
4882 i->path = path ? nasm_strdup(path) : NULL;
4883 i->next = NULL;
4885 if (ipath) {
4886 IncPath *j = ipath;
4887 while (j->next)
4888 j = j->next;
4889 j->next = i;
4890 } else {
4891 ipath = i;
4895 void pp_pre_include(char *fname)
4897 Token *inc, *space, *name;
4898 Line *l;
4900 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
4901 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
4902 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
4904 l = nasm_malloc(sizeof(Line));
4905 l->next = predef;
4906 l->first = inc;
4907 l->finishes = NULL;
4908 predef = l;
4911 void pp_pre_define(char *definition)
4913 Token *def, *space;
4914 Line *l;
4915 char *equals;
4917 equals = strchr(definition, '=');
4918 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4919 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
4920 if (equals)
4921 *equals = ' ';
4922 space->next = tokenize(definition);
4923 if (equals)
4924 *equals = '=';
4926 l = nasm_malloc(sizeof(Line));
4927 l->next = predef;
4928 l->first = def;
4929 l->finishes = NULL;
4930 predef = l;
4933 void pp_pre_undefine(char *definition)
4935 Token *def, *space;
4936 Line *l;
4938 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4939 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
4940 space->next = tokenize(definition);
4942 l = nasm_malloc(sizeof(Line));
4943 l->next = predef;
4944 l->first = def;
4945 l->finishes = NULL;
4946 predef = l;
4950 * Added by Keith Kanios:
4952 * This function is used to assist with "runtime" preprocessor
4953 * directives. (e.g. pp_runtime("%define __BITS__ 64");)
4955 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
4956 * PASS A VALID STRING TO THIS FUNCTION!!!!!
4959 void pp_runtime(char *definition)
4961 Token *def;
4963 def = tokenize(definition);
4964 if (do_directive(def) == NO_DIRECTIVE_FOUND)
4965 free_tlist(def);
4969 void pp_extra_stdmac(macros_t *macros)
4971 extrastdmac = macros;
4974 static void make_tok_num(Token * tok, int64_t val)
4976 char numbuf[20];
4977 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
4978 tok->text = nasm_strdup(numbuf);
4979 tok->type = TOK_NUMBER;
4982 Preproc nasmpp = {
4983 pp_reset,
4984 pp_getline,
4985 pp_cleanup