README: add note to see the AUTHORS file
[nasm.git] / preproc.c
blob45c02647883e0e825bc7c00b534d5c9f488ea10d
1 /* ----------------------------------------------------------------------- *
2 *
3 * Copyright 1996-2009 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))))
470 /* Handle TASM specific directives, which do not contain a % in
471 * front of them. We do it here because I could not find any other
472 * place to do it for the moment, and it is a hack (ideally it would
473 * be nice to be able to use the NASM pre-processor to do it).
475 static char *check_tasm_directive(char *line)
477 int32_t i, j, k, m, len;
478 char *p, *q, *oldline, oldchar;
480 p = nasm_skip_spaces(line);
482 /* Binary search for the directive name */
483 i = -1;
484 j = elements(tasm_directives);
485 q = nasm_skip_word(p);
486 len = q - p;
487 if (len) {
488 oldchar = p[len];
489 p[len] = 0;
490 while (j - i > 1) {
491 k = (j + i) / 2;
492 m = nasm_stricmp(p, tasm_directives[k]);
493 if (m == 0) {
494 /* We have found a directive, so jam a % in front of it
495 * so that NASM will then recognise it as one if it's own.
497 p[len] = oldchar;
498 len = strlen(p);
499 oldline = line;
500 line = nasm_malloc(len + 2);
501 line[0] = '%';
502 if (k == TM_IFDIFI) {
504 * NASM does not recognise IFDIFI, so we convert
505 * it to %if 0. This is not used in NASM
506 * compatible code, but does need to parse for the
507 * TASM macro package.
509 strcpy(line + 1, "if 0");
510 } else {
511 memcpy(line + 1, p, len + 1);
513 nasm_free(oldline);
514 return line;
515 } else if (m < 0) {
516 j = k;
517 } else
518 i = k;
520 p[len] = oldchar;
522 return line;
526 * The pre-preprocessing stage... This function translates line
527 * number indications as they emerge from GNU cpp (`# lineno "file"
528 * flags') into NASM preprocessor line number indications (`%line
529 * lineno file').
531 static char *prepreproc(char *line)
533 int lineno, fnlen;
534 char *fname, *oldline;
536 if (line[0] == '#' && line[1] == ' ') {
537 oldline = line;
538 fname = oldline + 2;
539 lineno = atoi(fname);
540 fname += strspn(fname, "0123456789 ");
541 if (*fname == '"')
542 fname++;
543 fnlen = strcspn(fname, "\"");
544 line = nasm_malloc(20 + fnlen);
545 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
546 nasm_free(oldline);
548 if (tasm_compatible_mode)
549 return check_tasm_directive(line);
550 return line;
554 * Free a linked list of tokens.
556 static void free_tlist(Token * list)
558 while (list) {
559 list = delete_Token(list);
564 * Free a linked list of lines.
566 static void free_llist(Line * list)
568 Line *l;
569 while (list) {
570 l = list;
571 list = list->next;
572 free_tlist(l->first);
573 nasm_free(l);
578 * Free an MMacro
580 static void free_mmacro(MMacro * m)
582 nasm_free(m->name);
583 free_tlist(m->dlist);
584 nasm_free(m->defaults);
585 free_llist(m->expansion);
586 nasm_free(m);
590 * Free all currently defined macros, and free the hash tables
592 static void free_smacro_table(struct hash_table *smt)
594 SMacro *s;
595 const char *key;
596 struct hash_tbl_node *it = NULL;
598 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
599 nasm_free((void *)key);
600 while (s) {
601 SMacro *ns = s->next;
602 nasm_free(s->name);
603 free_tlist(s->expansion);
604 nasm_free(s);
605 s = ns;
608 hash_free(smt);
611 static void free_mmacro_table(struct hash_table *mmt)
613 MMacro *m;
614 const char *key;
615 struct hash_tbl_node *it = NULL;
617 it = NULL;
618 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
619 nasm_free((void *)key);
620 while (m) {
621 MMacro *nm = m->next;
622 free_mmacro(m);
623 m = nm;
626 hash_free(mmt);
629 static void free_macros(void)
631 free_smacro_table(&smacros);
632 free_mmacro_table(&mmacros);
636 * Initialize the hash tables
638 static void init_macros(void)
640 hash_init(&smacros, HASH_LARGE);
641 hash_init(&mmacros, HASH_LARGE);
645 * Pop the context stack.
647 static void ctx_pop(void)
649 Context *c = cstk;
651 cstk = cstk->next;
652 free_smacro_table(&c->localmac);
653 nasm_free(c->name);
654 nasm_free(c);
658 * Search for a key in the hash index; adding it if necessary
659 * (in which case we initialize the data pointer to NULL.)
661 static void **
662 hash_findi_add(struct hash_table *hash, const char *str)
664 struct hash_insert hi;
665 void **r;
666 char *strx;
668 r = hash_findi(hash, str, &hi);
669 if (r)
670 return r;
672 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
673 return hash_add(&hi, strx, NULL);
677 * Like hash_findi, but returns the data element rather than a pointer
678 * to it. Used only when not adding a new element, hence no third
679 * argument.
681 static void *
682 hash_findix(struct hash_table *hash, const char *str)
684 void **p;
686 p = hash_findi(hash, str, NULL);
687 return p ? *p : NULL;
690 #define BUF_DELTA 512
692 * Read a line from the top file in istk, handling multiple CR/LFs
693 * at the end of the line read, and handling spurious ^Zs. Will
694 * return lines from the standard macro set if this has not already
695 * been done.
697 static char *read_line(void)
699 char *buffer, *p, *q;
700 int bufsize, continued_count;
702 if (stdmacpos) {
703 unsigned char c;
704 const unsigned char *p = stdmacpos;
705 char *ret, *q;
706 size_t len = 0;
707 while ((c = *p++)) {
708 if (c >= 0x80)
709 len += pp_directives_len[c-0x80]+1;
710 else
711 len++;
713 ret = nasm_malloc(len+1);
714 q = ret;
715 while ((c = *stdmacpos++)) {
716 if (c >= 0x80) {
717 memcpy(q, pp_directives[c-0x80], pp_directives_len[c-0x80]);
718 q += pp_directives_len[c-0x80];
719 *q++ = ' ';
720 } else {
721 *q++ = c;
724 stdmacpos = p;
725 *q = '\0';
727 if (!*stdmacpos) {
728 /* This was the last of the standard macro chain... */
729 stdmacpos = NULL;
730 if (any_extrastdmac) {
731 stdmacpos = extrastdmac;
732 any_extrastdmac = false;
733 } else if (do_predef) {
734 Line *pd, *l;
735 Token *head, **tail, *t;
738 * Nasty hack: here we push the contents of
739 * `predef' on to the top-level expansion stack,
740 * since this is the most convenient way to
741 * implement the pre-include and pre-define
742 * features.
744 for (pd = predef; pd; pd = pd->next) {
745 head = NULL;
746 tail = &head;
747 for (t = pd->first; t; t = t->next) {
748 *tail = new_Token(NULL, t->type, t->text, 0);
749 tail = &(*tail)->next;
751 l = nasm_malloc(sizeof(Line));
752 l->next = istk->expansion;
753 l->first = head;
754 l->finishes = NULL;
755 istk->expansion = l;
757 do_predef = false;
760 return ret;
763 bufsize = BUF_DELTA;
764 buffer = nasm_malloc(BUF_DELTA);
765 p = buffer;
766 continued_count = 0;
767 while (1) {
768 q = fgets(p, bufsize - (p - buffer), istk->fp);
769 if (!q)
770 break;
771 p += strlen(p);
772 if (p > buffer && p[-1] == '\n') {
773 /* Convert backslash-CRLF line continuation sequences into
774 nothing at all (for DOS and Windows) */
775 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
776 p -= 3;
777 *p = 0;
778 continued_count++;
780 /* Also convert backslash-LF line continuation sequences into
781 nothing at all (for Unix) */
782 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
783 p -= 2;
784 *p = 0;
785 continued_count++;
786 } else {
787 break;
790 if (p - buffer > bufsize - 10) {
791 int32_t offset = p - buffer;
792 bufsize += BUF_DELTA;
793 buffer = nasm_realloc(buffer, bufsize);
794 p = buffer + offset; /* prevent stale-pointer problems */
798 if (!q && p == buffer) {
799 nasm_free(buffer);
800 return NULL;
803 src_set_linnum(src_get_linnum() + istk->lineinc +
804 (continued_count * istk->lineinc));
807 * Play safe: remove CRs as well as LFs, if any of either are
808 * present at the end of the line.
810 while (--p >= buffer && (*p == '\n' || *p == '\r'))
811 *p = '\0';
814 * Handle spurious ^Z, which may be inserted into source files
815 * by some file transfer utilities.
817 buffer[strcspn(buffer, "\032")] = '\0';
819 list->line(LIST_READ, buffer);
821 return buffer;
825 * Tokenize a line of text. This is a very simple process since we
826 * don't need to parse the value out of e.g. numeric tokens: we
827 * simply split one string into many.
829 static Token *tokenize(char *line)
831 char c, *p = line;
832 enum pp_token_type type;
833 Token *list = NULL;
834 Token *t, **tail = &list;
836 while (*line) {
837 p = line;
838 if (*p == '%') {
839 p++;
840 if (*p == '+' && !nasm_isdigit(p[1])) {
841 p++;
842 type = TOK_PASTE;
843 } else if (nasm_isdigit(*p) ||
844 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
845 do {
846 p++;
848 while (nasm_isdigit(*p));
849 type = TOK_PREPROC_ID;
850 } else if (*p == '{') {
851 p++;
852 while (*p && *p != '}') {
853 p[-1] = *p;
854 p++;
856 p[-1] = '\0';
857 if (*p)
858 p++;
859 type = TOK_PREPROC_ID;
860 } else if (*p == '[') {
861 int lvl = 1;
862 line += 2; /* Skip the leading %[ */
863 p++;
864 while (lvl && (c = *p++)) {
865 switch (c) {
866 case ']':
867 lvl--;
868 break;
869 case '%':
870 if (*p == '[')
871 lvl++;
872 break;
873 case '\'':
874 case '\"':
875 case '`':
876 p = nasm_skip_string(p)+1;
877 break;
878 default:
879 break;
882 p--;
883 if (*p)
884 *p++ = '\0';
885 if (lvl)
886 error(ERR_NONFATAL, "unterminated %[ construct");
887 type = TOK_INDIRECT;
888 } else if (*p == '?') {
889 type = TOK_PREPROC_Q; /* %? */
890 p++;
891 if (*p == '?') {
892 type = TOK_PREPROC_QQ; /* %?? */
893 p++;
895 } else if (isidchar(*p) ||
896 ((*p == '!' || *p == '%' || *p == '$') &&
897 isidchar(p[1]))) {
898 do {
899 p++;
901 while (isidchar(*p));
902 type = TOK_PREPROC_ID;
903 } else {
904 type = TOK_OTHER;
905 if (*p == '%')
906 p++;
908 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
909 type = TOK_ID;
910 p++;
911 while (*p && isidchar(*p))
912 p++;
913 } else if (*p == '\'' || *p == '"' || *p == '`') {
915 * A string token.
917 type = TOK_STRING;
918 p = nasm_skip_string(p);
920 if (*p) {
921 p++;
922 } else {
923 error(ERR_WARNING|ERR_PASS1, "unterminated string");
924 /* Handling unterminated strings by UNV */
925 /* type = -1; */
927 } else if (p[0] == '$' && p[1] == '$') {
928 type = TOK_OTHER; /* TOKEN_BASE */
929 p += 2;
930 } else if (isnumstart(*p)) {
931 bool is_hex = false;
932 bool is_float = false;
933 bool has_e = false;
934 char c, *r;
937 * A numeric token.
940 if (*p == '$') {
941 p++;
942 is_hex = true;
945 for (;;) {
946 c = *p++;
948 if (!is_hex && (c == 'e' || c == 'E')) {
949 has_e = true;
950 if (*p == '+' || *p == '-') {
951 /* e can only be followed by +/- if it is either a
952 prefixed hex number or a floating-point number */
953 p++;
954 is_float = true;
956 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
957 is_hex = true;
958 } else if (c == 'P' || c == 'p') {
959 is_float = true;
960 if (*p == '+' || *p == '-')
961 p++;
962 } else if (isnumchar(c) || c == '_')
963 ; /* just advance */
964 else if (c == '.') {
965 /* we need to deal with consequences of the legacy
966 parser, like "1.nolist" being two tokens
967 (TOK_NUMBER, TOK_ID) here; at least give it
968 a shot for now. In the future, we probably need
969 a flex-based scanner with proper pattern matching
970 to do it as well as it can be done. Nothing in
971 the world is going to help the person who wants
972 0x123.p16 interpreted as two tokens, though. */
973 r = p;
974 while (*r == '_')
975 r++;
977 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
978 (!is_hex && (*r == 'e' || *r == 'E')) ||
979 (*r == 'p' || *r == 'P')) {
980 p = r;
981 is_float = true;
982 } else
983 break; /* Terminate the token */
984 } else
985 break;
987 p--; /* Point to first character beyond number */
989 if (p == line+1 && *line == '$') {
990 type = TOK_OTHER; /* TOKEN_HERE */
991 } else {
992 if (has_e && !is_hex) {
993 /* 1e13 is floating-point, but 1e13h is not */
994 is_float = true;
997 type = is_float ? TOK_FLOAT : TOK_NUMBER;
999 } else if (nasm_isspace(*p)) {
1000 type = TOK_WHITESPACE;
1001 p = nasm_skip_spaces(p);
1003 * Whitespace just before end-of-line is discarded by
1004 * pretending it's a comment; whitespace just before a
1005 * comment gets lumped into the comment.
1007 if (!*p || *p == ';') {
1008 type = TOK_COMMENT;
1009 while (*p)
1010 p++;
1012 } else if (*p == ';') {
1013 type = TOK_COMMENT;
1014 while (*p)
1015 p++;
1016 } else {
1018 * Anything else is an operator of some kind. We check
1019 * for all the double-character operators (>>, <<, //,
1020 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1021 * else is a single-character operator.
1023 type = TOK_OTHER;
1024 if ((p[0] == '>' && p[1] == '>') ||
1025 (p[0] == '<' && p[1] == '<') ||
1026 (p[0] == '/' && p[1] == '/') ||
1027 (p[0] == '<' && p[1] == '=') ||
1028 (p[0] == '>' && p[1] == '=') ||
1029 (p[0] == '=' && p[1] == '=') ||
1030 (p[0] == '!' && p[1] == '=') ||
1031 (p[0] == '<' && p[1] == '>') ||
1032 (p[0] == '&' && p[1] == '&') ||
1033 (p[0] == '|' && p[1] == '|') ||
1034 (p[0] == '^' && p[1] == '^')) {
1035 p++;
1037 p++;
1040 /* Handling unterminated string by UNV */
1041 /*if (type == -1)
1043 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1044 t->text[p-line] = *line;
1045 tail = &t->next;
1047 else */
1048 if (type != TOK_COMMENT) {
1049 *tail = t = new_Token(NULL, type, line, p - line);
1050 tail = &t->next;
1052 line = p;
1054 return list;
1058 * this function allocates a new managed block of memory and
1059 * returns a pointer to the block. The managed blocks are
1060 * deleted only all at once by the delete_Blocks function.
1062 static void *new_Block(size_t size)
1064 Blocks *b = &blocks;
1066 /* first, get to the end of the linked list */
1067 while (b->next)
1068 b = b->next;
1069 /* now allocate the requested chunk */
1070 b->chunk = nasm_malloc(size);
1072 /* now allocate a new block for the next request */
1073 b->next = nasm_malloc(sizeof(Blocks));
1074 /* and initialize the contents of the new block */
1075 b->next->next = NULL;
1076 b->next->chunk = NULL;
1077 return b->chunk;
1081 * this function deletes all managed blocks of memory
1083 static void delete_Blocks(void)
1085 Blocks *a, *b = &blocks;
1088 * keep in mind that the first block, pointed to by blocks
1089 * is a static and not dynamically allocated, so we don't
1090 * free it.
1092 while (b) {
1093 if (b->chunk)
1094 nasm_free(b->chunk);
1095 a = b;
1096 b = b->next;
1097 if (a != &blocks)
1098 nasm_free(a);
1103 * this function creates a new Token and passes a pointer to it
1104 * back to the caller. It sets the type and text elements, and
1105 * also the a.mac and next elements to NULL.
1107 static Token *new_Token(Token * next, enum pp_token_type type,
1108 const char *text, int txtlen)
1110 Token *t;
1111 int i;
1113 if (!freeTokens) {
1114 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1115 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1116 freeTokens[i].next = &freeTokens[i + 1];
1117 freeTokens[i].next = NULL;
1119 t = freeTokens;
1120 freeTokens = t->next;
1121 t->next = next;
1122 t->a.mac = NULL;
1123 t->type = type;
1124 if (type == TOK_WHITESPACE || !text) {
1125 t->text = NULL;
1126 } else {
1127 if (txtlen == 0)
1128 txtlen = strlen(text);
1129 t->text = nasm_malloc(txtlen+1);
1130 memcpy(t->text, text, txtlen);
1131 t->text[txtlen] = '\0';
1133 return t;
1136 static Token *delete_Token(Token * t)
1138 Token *next = t->next;
1139 nasm_free(t->text);
1140 t->next = freeTokens;
1141 freeTokens = t;
1142 return next;
1146 * Convert a line of tokens back into text.
1147 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1148 * will be transformed into ..@ctxnum.xxx
1150 static char *detoken(Token * tlist, bool expand_locals)
1152 Token *t;
1153 int len;
1154 char *line, *p;
1155 const char *q;
1157 len = 0;
1158 for (t = tlist; t; t = t->next) {
1159 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1160 char *p = getenv(t->text + 2);
1161 nasm_free(t->text);
1162 if (p)
1163 t->text = nasm_strdup(p);
1164 else
1165 t->text = NULL;
1167 /* Expand local macros here and not during preprocessing */
1168 if (expand_locals &&
1169 t->type == TOK_PREPROC_ID && t->text &&
1170 t->text[0] == '%' && t->text[1] == '$') {
1171 const char *q;
1172 char *p;
1173 Context *ctx = get_ctx(t->text, &q, false);
1174 if (ctx) {
1175 char buffer[40];
1176 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1177 p = nasm_strcat(buffer, q);
1178 nasm_free(t->text);
1179 t->text = p;
1182 if (t->type == TOK_WHITESPACE) {
1183 len++;
1184 } else if (t->text) {
1185 len += strlen(t->text);
1188 p = line = nasm_malloc(len + 1);
1189 for (t = tlist; t; t = t->next) {
1190 if (t->type == TOK_WHITESPACE) {
1191 *p++ = ' ';
1192 } else if (t->text) {
1193 q = t->text;
1194 while (*q)
1195 *p++ = *q++;
1198 *p = '\0';
1199 return line;
1203 * A scanner, suitable for use by the expression evaluator, which
1204 * operates on a line of Tokens. Expects a pointer to a pointer to
1205 * the first token in the line to be passed in as its private_data
1206 * field.
1208 * FIX: This really needs to be unified with stdscan.
1210 static int ppscan(void *private_data, struct tokenval *tokval)
1212 Token **tlineptr = private_data;
1213 Token *tline;
1214 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1216 do {
1217 tline = *tlineptr;
1218 *tlineptr = tline ? tline->next : NULL;
1220 while (tline && (tline->type == TOK_WHITESPACE ||
1221 tline->type == TOK_COMMENT));
1223 if (!tline)
1224 return tokval->t_type = TOKEN_EOS;
1226 tokval->t_charptr = tline->text;
1228 if (tline->text[0] == '$' && !tline->text[1])
1229 return tokval->t_type = TOKEN_HERE;
1230 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1231 return tokval->t_type = TOKEN_BASE;
1233 if (tline->type == TOK_ID) {
1234 p = tokval->t_charptr = tline->text;
1235 if (p[0] == '$') {
1236 tokval->t_charptr++;
1237 return tokval->t_type = TOKEN_ID;
1240 for (r = p, s = ourcopy; *r; r++) {
1241 if (r >= p+MAX_KEYWORD)
1242 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1243 *s++ = nasm_tolower(*r);
1245 *s = '\0';
1246 /* right, so we have an identifier sitting in temp storage. now,
1247 * is it actually a register or instruction name, or what? */
1248 return nasm_token_hash(ourcopy, tokval);
1251 if (tline->type == TOK_NUMBER) {
1252 bool rn_error;
1253 tokval->t_integer = readnum(tline->text, &rn_error);
1254 tokval->t_charptr = tline->text;
1255 if (rn_error)
1256 return tokval->t_type = TOKEN_ERRNUM;
1257 else
1258 return tokval->t_type = TOKEN_NUM;
1261 if (tline->type == TOK_FLOAT) {
1262 return tokval->t_type = TOKEN_FLOAT;
1265 if (tline->type == TOK_STRING) {
1266 char bq, *ep;
1268 bq = tline->text[0];
1269 tokval->t_charptr = tline->text;
1270 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1272 if (ep[0] != bq || ep[1] != '\0')
1273 return tokval->t_type = TOKEN_ERRSTR;
1274 else
1275 return tokval->t_type = TOKEN_STR;
1278 if (tline->type == TOK_OTHER) {
1279 if (!strcmp(tline->text, "<<"))
1280 return tokval->t_type = TOKEN_SHL;
1281 if (!strcmp(tline->text, ">>"))
1282 return tokval->t_type = TOKEN_SHR;
1283 if (!strcmp(tline->text, "//"))
1284 return tokval->t_type = TOKEN_SDIV;
1285 if (!strcmp(tline->text, "%%"))
1286 return tokval->t_type = TOKEN_SMOD;
1287 if (!strcmp(tline->text, "=="))
1288 return tokval->t_type = TOKEN_EQ;
1289 if (!strcmp(tline->text, "<>"))
1290 return tokval->t_type = TOKEN_NE;
1291 if (!strcmp(tline->text, "!="))
1292 return tokval->t_type = TOKEN_NE;
1293 if (!strcmp(tline->text, "<="))
1294 return tokval->t_type = TOKEN_LE;
1295 if (!strcmp(tline->text, ">="))
1296 return tokval->t_type = TOKEN_GE;
1297 if (!strcmp(tline->text, "&&"))
1298 return tokval->t_type = TOKEN_DBL_AND;
1299 if (!strcmp(tline->text, "^^"))
1300 return tokval->t_type = TOKEN_DBL_XOR;
1301 if (!strcmp(tline->text, "||"))
1302 return tokval->t_type = TOKEN_DBL_OR;
1306 * We have no other options: just return the first character of
1307 * the token text.
1309 return tokval->t_type = tline->text[0];
1313 * Compare a string to the name of an existing macro; this is a
1314 * simple wrapper which calls either strcmp or nasm_stricmp
1315 * depending on the value of the `casesense' parameter.
1317 static int mstrcmp(const char *p, const char *q, bool casesense)
1319 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
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 mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1329 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1333 * Return the Context structure associated with a %$ token. Return
1334 * NULL, having _already_ reported an error condition, if the
1335 * context stack isn't deep enough for the supplied number of $
1336 * signs.
1337 * If all_contexts == true, contexts that enclose current are
1338 * also scanned for such smacro, until it is found; if not -
1339 * only the context that directly results from the number of $'s
1340 * in variable's name.
1342 * If "namep" is non-NULL, set it to the pointer to the macro name
1343 * tail, i.e. the part beyond %$...
1345 static Context *get_ctx(const char *name, const char **namep,
1346 bool all_contexts)
1348 Context *ctx;
1349 SMacro *m;
1350 int i;
1352 if (namep)
1353 *namep = name;
1355 if (!name || name[0] != '%' || name[1] != '$')
1356 return NULL;
1358 if (!cstk) {
1359 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1360 return NULL;
1363 name += 2;
1364 ctx = cstk;
1365 i = 0;
1366 while (ctx && *name == '$') {
1367 name++;
1368 i++;
1369 ctx = ctx->next;
1371 if (!ctx) {
1372 error(ERR_NONFATAL, "`%s': context stack is only"
1373 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1374 return NULL;
1377 if (namep)
1378 *namep = name;
1380 if (!all_contexts)
1381 return ctx;
1383 do {
1384 /* Search for this smacro in found context */
1385 m = hash_findix(&ctx->localmac, name);
1386 while (m) {
1387 if (!mstrcmp(m->name, name, m->casesense))
1388 return ctx;
1389 m = m->next;
1391 ctx = ctx->next;
1393 while (ctx);
1394 return NULL;
1398 * Check to see if a file is already in a string list
1400 static bool in_list(const StrList *list, const char *str)
1402 while (list) {
1403 if (!strcmp(list->str, str))
1404 return true;
1405 list = list->next;
1407 return false;
1411 * Open an include file. This routine must always return a valid
1412 * file pointer if it returns - it's responsible for throwing an
1413 * ERR_FATAL and bombing out completely if not. It should also try
1414 * the include path one by one until it finds the file or reaches
1415 * the end of the path.
1417 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1418 bool missing_ok)
1420 FILE *fp;
1421 char *prefix = "";
1422 IncPath *ip = ipath;
1423 int len = strlen(file);
1424 size_t prefix_len = 0;
1425 StrList *sl;
1427 while (1) {
1428 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1429 memcpy(sl->str, prefix, prefix_len);
1430 memcpy(sl->str+prefix_len, file, len+1);
1431 fp = fopen(sl->str, "r");
1432 if (fp && dhead && !in_list(*dhead, sl->str)) {
1433 sl->next = NULL;
1434 **dtail = sl;
1435 *dtail = &sl->next;
1436 } else {
1437 nasm_free(sl);
1439 if (fp)
1440 return fp;
1441 if (!ip) {
1442 if (!missing_ok)
1443 break;
1444 prefix = NULL;
1445 } else {
1446 prefix = ip->path;
1447 ip = ip->next;
1449 if (prefix) {
1450 prefix_len = strlen(prefix);
1451 } else {
1452 /* -MG given and file not found */
1453 if (dhead && !in_list(*dhead, file)) {
1454 sl = nasm_malloc(len+1+sizeof sl->next);
1455 sl->next = NULL;
1456 strcpy(sl->str, file);
1457 **dtail = sl;
1458 *dtail = &sl->next;
1460 return NULL;
1464 error(ERR_FATAL, "unable to open include file `%s'", file);
1465 return NULL; /* never reached - placate compilers */
1469 * Determine if we should warn on defining a single-line macro of
1470 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1471 * return true if _any_ single-line macro of that name is defined.
1472 * Otherwise, will return true if a single-line macro with either
1473 * `nparam' or no parameters is defined.
1475 * If a macro with precisely the right number of parameters is
1476 * defined, or nparam is -1, the address of the definition structure
1477 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1478 * is NULL, no action will be taken regarding its contents, and no
1479 * error will occur.
1481 * Note that this is also called with nparam zero to resolve
1482 * `ifdef'.
1484 * If you already know which context macro belongs to, you can pass
1485 * the context pointer as first parameter; if you won't but name begins
1486 * with %$ the context will be automatically computed. If all_contexts
1487 * is true, macro will be searched in outer contexts as well.
1489 static bool
1490 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1491 bool nocase)
1493 struct hash_table *smtbl;
1494 SMacro *m;
1496 if (ctx) {
1497 smtbl = &ctx->localmac;
1498 } else if (name[0] == '%' && name[1] == '$') {
1499 if (cstk)
1500 ctx = get_ctx(name, &name, false);
1501 if (!ctx)
1502 return false; /* got to return _something_ */
1503 smtbl = &ctx->localmac;
1504 } else {
1505 smtbl = &smacros;
1507 m = (SMacro *) hash_findix(smtbl, name);
1509 while (m) {
1510 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1511 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1512 if (defn) {
1513 if (nparam == (int) m->nparam || nparam == -1)
1514 *defn = m;
1515 else
1516 *defn = NULL;
1518 return true;
1520 m = m->next;
1523 return false;
1527 * Count and mark off the parameters in a multi-line macro call.
1528 * This is called both from within the multi-line macro expansion
1529 * code, and also to mark off the default parameters when provided
1530 * in a %macro definition line.
1532 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1534 int paramsize, brace;
1536 *nparam = paramsize = 0;
1537 *params = NULL;
1538 while (t) {
1539 /* +1: we need space for the final NULL */
1540 if (*nparam+1 >= paramsize) {
1541 paramsize += PARAM_DELTA;
1542 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1544 skip_white_(t);
1545 brace = false;
1546 if (tok_is_(t, "{"))
1547 brace = true;
1548 (*params)[(*nparam)++] = t;
1549 while (tok_isnt_(t, brace ? "}" : ","))
1550 t = t->next;
1551 if (t) { /* got a comma/brace */
1552 t = t->next;
1553 if (brace) {
1555 * Now we've found the closing brace, look further
1556 * for the comma.
1558 skip_white_(t);
1559 if (tok_isnt_(t, ",")) {
1560 error(ERR_NONFATAL,
1561 "braces do not enclose all of macro parameter");
1562 while (tok_isnt_(t, ","))
1563 t = t->next;
1565 if (t)
1566 t = t->next; /* eat the comma */
1573 * Determine whether one of the various `if' conditions is true or
1574 * not.
1576 * We must free the tline we get passed.
1578 static bool if_condition(Token * tline, enum preproc_token ct)
1580 enum pp_conditional i = PP_COND(ct);
1581 bool j;
1582 Token *t, *tt, **tptr, *origline;
1583 struct tokenval tokval;
1584 expr *evalresult;
1585 enum pp_token_type needtype;
1587 origline = tline;
1589 switch (i) {
1590 case PPC_IFCTX:
1591 j = false; /* have we matched yet? */
1592 while (true) {
1593 skip_white_(tline);
1594 if (!tline)
1595 break;
1596 if (tline->type != TOK_ID) {
1597 error(ERR_NONFATAL,
1598 "`%s' expects context identifiers", pp_directives[ct]);
1599 free_tlist(origline);
1600 return -1;
1602 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1603 j = true;
1604 tline = tline->next;
1606 break;
1608 case PPC_IFDEF:
1609 j = false; /* have we matched yet? */
1610 while (tline) {
1611 skip_white_(tline);
1612 if (!tline || (tline->type != TOK_ID &&
1613 (tline->type != TOK_PREPROC_ID ||
1614 tline->text[1] != '$'))) {
1615 error(ERR_NONFATAL,
1616 "`%s' expects macro identifiers", pp_directives[ct]);
1617 goto fail;
1619 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1620 j = true;
1621 tline = tline->next;
1623 break;
1625 case PPC_IFIDN:
1626 case PPC_IFIDNI:
1627 tline = expand_smacro(tline);
1628 t = tt = tline;
1629 while (tok_isnt_(tt, ","))
1630 tt = tt->next;
1631 if (!tt) {
1632 error(ERR_NONFATAL,
1633 "`%s' expects two comma-separated arguments",
1634 pp_directives[ct]);
1635 goto fail;
1637 tt = tt->next;
1638 j = true; /* assume equality unless proved not */
1639 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1640 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1641 error(ERR_NONFATAL, "`%s': more than one comma on line",
1642 pp_directives[ct]);
1643 goto fail;
1645 if (t->type == TOK_WHITESPACE) {
1646 t = t->next;
1647 continue;
1649 if (tt->type == TOK_WHITESPACE) {
1650 tt = tt->next;
1651 continue;
1653 if (tt->type != t->type) {
1654 j = false; /* found mismatching tokens */
1655 break;
1657 /* When comparing strings, need to unquote them first */
1658 if (t->type == TOK_STRING) {
1659 size_t l1 = nasm_unquote(t->text, NULL);
1660 size_t l2 = nasm_unquote(tt->text, NULL);
1662 if (l1 != l2) {
1663 j = false;
1664 break;
1666 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1667 j = false;
1668 break;
1670 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1671 j = false; /* found mismatching tokens */
1672 break;
1675 t = t->next;
1676 tt = tt->next;
1678 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1679 j = false; /* trailing gunk on one end or other */
1680 break;
1682 case PPC_IFMACRO:
1684 bool found = false;
1685 MMacro searching, *mmac;
1687 skip_white_(tline);
1688 tline = expand_id(tline);
1689 if (!tok_type_(tline, TOK_ID)) {
1690 error(ERR_NONFATAL,
1691 "`%s' expects a macro name", pp_directives[ct]);
1692 goto fail;
1694 searching.name = nasm_strdup(tline->text);
1695 searching.casesense = true;
1696 searching.plus = false;
1697 searching.nolist = false;
1698 searching.in_progress = 0;
1699 searching.max_depth = 0;
1700 searching.rep_nest = NULL;
1701 searching.nparam_min = 0;
1702 searching.nparam_max = INT_MAX;
1703 tline = expand_smacro(tline->next);
1704 skip_white_(tline);
1705 if (!tline) {
1706 } else if (!tok_type_(tline, TOK_NUMBER)) {
1707 error(ERR_NONFATAL,
1708 "`%s' expects a parameter count or nothing",
1709 pp_directives[ct]);
1710 } else {
1711 searching.nparam_min = searching.nparam_max =
1712 readnum(tline->text, &j);
1713 if (j)
1714 error(ERR_NONFATAL,
1715 "unable to parse parameter count `%s'",
1716 tline->text);
1718 if (tline && tok_is_(tline->next, "-")) {
1719 tline = tline->next->next;
1720 if (tok_is_(tline, "*"))
1721 searching.nparam_max = INT_MAX;
1722 else if (!tok_type_(tline, TOK_NUMBER))
1723 error(ERR_NONFATAL,
1724 "`%s' expects a parameter count after `-'",
1725 pp_directives[ct]);
1726 else {
1727 searching.nparam_max = readnum(tline->text, &j);
1728 if (j)
1729 error(ERR_NONFATAL,
1730 "unable to parse parameter count `%s'",
1731 tline->text);
1732 if (searching.nparam_min > searching.nparam_max)
1733 error(ERR_NONFATAL,
1734 "minimum parameter count exceeds maximum");
1737 if (tline && tok_is_(tline->next, "+")) {
1738 tline = tline->next;
1739 searching.plus = true;
1741 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1742 while (mmac) {
1743 if (!strcmp(mmac->name, searching.name) &&
1744 (mmac->nparam_min <= searching.nparam_max
1745 || searching.plus)
1746 && (searching.nparam_min <= mmac->nparam_max
1747 || mmac->plus)) {
1748 found = true;
1749 break;
1751 mmac = mmac->next;
1753 if (tline && tline->next)
1754 error(ERR_WARNING|ERR_PASS1,
1755 "trailing garbage after %%ifmacro ignored");
1756 nasm_free(searching.name);
1757 j = found;
1758 break;
1761 case PPC_IFID:
1762 needtype = TOK_ID;
1763 goto iftype;
1764 case PPC_IFNUM:
1765 needtype = TOK_NUMBER;
1766 goto iftype;
1767 case PPC_IFSTR:
1768 needtype = TOK_STRING;
1769 goto iftype;
1771 iftype:
1772 t = tline = expand_smacro(tline);
1774 while (tok_type_(t, TOK_WHITESPACE) ||
1775 (needtype == TOK_NUMBER &&
1776 tok_type_(t, TOK_OTHER) &&
1777 (t->text[0] == '-' || t->text[0] == '+') &&
1778 !t->text[1]))
1779 t = t->next;
1781 j = tok_type_(t, needtype);
1782 break;
1784 case PPC_IFTOKEN:
1785 t = tline = expand_smacro(tline);
1786 while (tok_type_(t, TOK_WHITESPACE))
1787 t = t->next;
1789 j = false;
1790 if (t) {
1791 t = t->next; /* Skip the actual token */
1792 while (tok_type_(t, TOK_WHITESPACE))
1793 t = t->next;
1794 j = !t; /* Should be nothing left */
1796 break;
1798 case PPC_IFEMPTY:
1799 t = tline = expand_smacro(tline);
1800 while (tok_type_(t, TOK_WHITESPACE))
1801 t = t->next;
1803 j = !t; /* Should be empty */
1804 break;
1806 case PPC_IF:
1807 t = tline = expand_smacro(tline);
1808 tptr = &t;
1809 tokval.t_type = TOKEN_INVALID;
1810 evalresult = evaluate(ppscan, tptr, &tokval,
1811 NULL, pass | CRITICAL, error, NULL);
1812 if (!evalresult)
1813 return -1;
1814 if (tokval.t_type)
1815 error(ERR_WARNING|ERR_PASS1,
1816 "trailing garbage after expression ignored");
1817 if (!is_simple(evalresult)) {
1818 error(ERR_NONFATAL,
1819 "non-constant value given to `%s'", pp_directives[ct]);
1820 goto fail;
1822 j = reloc_value(evalresult) != 0;
1823 break;
1825 default:
1826 error(ERR_FATAL,
1827 "preprocessor directive `%s' not yet implemented",
1828 pp_directives[ct]);
1829 goto fail;
1832 free_tlist(origline);
1833 return j ^ PP_NEGATIVE(ct);
1835 fail:
1836 free_tlist(origline);
1837 return -1;
1841 * Common code for defining an smacro
1843 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
1844 int nparam, Token *expansion)
1846 SMacro *smac, **smhead;
1847 struct hash_table *smtbl;
1849 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
1850 if (!smac) {
1851 error(ERR_WARNING|ERR_PASS1,
1852 "single-line macro `%s' defined both with and"
1853 " without parameters", mname);
1855 /* Some instances of the old code considered this a failure,
1856 some others didn't. What is the right thing to do here? */
1857 free_tlist(expansion);
1858 return false; /* Failure */
1859 } else {
1861 * We're redefining, so we have to take over an
1862 * existing SMacro structure. This means freeing
1863 * what was already in it.
1865 nasm_free(smac->name);
1866 free_tlist(smac->expansion);
1868 } else {
1869 smtbl = ctx ? &ctx->localmac : &smacros;
1870 smhead = (SMacro **) hash_findi_add(smtbl, mname);
1871 smac = nasm_malloc(sizeof(SMacro));
1872 smac->next = *smhead;
1873 *smhead = smac;
1875 smac->name = nasm_strdup(mname);
1876 smac->casesense = casesense;
1877 smac->nparam = nparam;
1878 smac->expansion = expansion;
1879 smac->in_progress = false;
1880 return true; /* Success */
1884 * Undefine an smacro
1886 static void undef_smacro(Context *ctx, const char *mname)
1888 SMacro **smhead, *s, **sp;
1889 struct hash_table *smtbl;
1891 smtbl = ctx ? &ctx->localmac : &smacros;
1892 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
1894 if (smhead) {
1896 * We now have a macro name... go hunt for it.
1898 sp = smhead;
1899 while ((s = *sp) != NULL) {
1900 if (!mstrcmp(s->name, mname, s->casesense)) {
1901 *sp = s->next;
1902 nasm_free(s->name);
1903 free_tlist(s->expansion);
1904 nasm_free(s);
1905 } else {
1906 sp = &s->next;
1913 * Parse a mmacro specification.
1915 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
1917 bool err;
1919 tline = tline->next;
1920 skip_white_(tline);
1921 tline = expand_id(tline);
1922 if (!tok_type_(tline, TOK_ID)) {
1923 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
1924 return false;
1927 def->prev = NULL;
1928 def->name = nasm_strdup(tline->text);
1929 def->plus = false;
1930 def->nolist = false;
1931 def->in_progress = 0;
1932 def->rep_nest = NULL;
1933 def->nparam_min = 0;
1934 def->nparam_max = 0;
1936 tline = expand_smacro(tline->next);
1937 skip_white_(tline);
1938 if (!tok_type_(tline, TOK_NUMBER)) {
1939 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
1940 } else {
1941 def->nparam_min = def->nparam_max =
1942 readnum(tline->text, &err);
1943 if (err)
1944 error(ERR_NONFATAL,
1945 "unable to parse parameter count `%s'", tline->text);
1947 if (tline && tok_is_(tline->next, "-")) {
1948 tline = tline->next->next;
1949 if (tok_is_(tline, "*")) {
1950 def->nparam_max = INT_MAX;
1951 } else if (!tok_type_(tline, TOK_NUMBER)) {
1952 error(ERR_NONFATAL,
1953 "`%s' expects a parameter count after `-'", directive);
1954 } else {
1955 def->nparam_max = readnum(tline->text, &err);
1956 if (err) {
1957 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
1958 tline->text);
1960 if (def->nparam_min > def->nparam_max) {
1961 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
1965 if (tline && tok_is_(tline->next, "+")) {
1966 tline = tline->next;
1967 def->plus = true;
1969 if (tline && tok_type_(tline->next, TOK_ID) &&
1970 !nasm_stricmp(tline->next->text, ".nolist")) {
1971 tline = tline->next;
1972 def->nolist = true;
1976 * Handle default parameters.
1978 if (tline && tline->next) {
1979 def->dlist = tline->next;
1980 tline->next = NULL;
1981 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
1982 } else {
1983 def->dlist = NULL;
1984 def->defaults = NULL;
1986 def->expansion = NULL;
1988 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
1989 !def->plus)
1990 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
1991 "too many default macro parameters");
1993 return true;
1998 * Decode a size directive
2000 static int parse_size(const char *str) {
2001 static const char *size_names[] =
2002 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2003 static const int sizes[] =
2004 { 0, 1, 4, 16, 8, 10, 2, 32 };
2006 return sizes[bsii(str, size_names, elements(size_names))+1];
2010 * nasm_unquote with error if the string contains NUL characters.
2011 * If the string contains NUL characters, issue an error and return
2012 * the C len, i.e. truncate at the NUL.
2014 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
2016 size_t len = nasm_unquote(qstr, NULL);
2017 size_t clen = strlen(qstr);
2019 if (len != clen)
2020 error(ERR_NONFATAL, "NUL character in `%s' directive",
2021 pp_directives[directive]);
2023 return clen;
2027 * find and process preprocessor directive in passed line
2028 * Find out if a line contains a preprocessor directive, and deal
2029 * with it if so.
2031 * If a directive _is_ found, it is the responsibility of this routine
2032 * (and not the caller) to free_tlist() the line.
2034 * @param tline a pointer to the current tokeninzed line linked list
2035 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2038 static int do_directive(Token * tline)
2040 enum preproc_token i;
2041 int j;
2042 bool err;
2043 int nparam;
2044 bool nolist;
2045 bool casesense;
2046 int k, m;
2047 int offset;
2048 char *p, *pp;
2049 const char *mname;
2050 Include *inc;
2051 Context *ctx;
2052 Cond *cond;
2053 MMacro *mmac, **mmhead;
2054 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2055 Line *l;
2056 struct tokenval tokval;
2057 expr *evalresult;
2058 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2059 int64_t count;
2060 size_t len;
2061 int severity;
2063 origline = tline;
2065 skip_white_(tline);
2066 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2067 (tline->text[1] == '%' || tline->text[1] == '$'
2068 || tline->text[1] == '!'))
2069 return NO_DIRECTIVE_FOUND;
2071 i = pp_token_hash(tline->text);
2074 * If we're in a non-emitting branch of a condition construct,
2075 * or walking to the end of an already terminated %rep block,
2076 * we should ignore all directives except for condition
2077 * directives.
2079 if (((istk->conds && !emitting(istk->conds->state)) ||
2080 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2081 return NO_DIRECTIVE_FOUND;
2085 * If we're defining a macro or reading a %rep block, we should
2086 * ignore all directives except for %macro/%imacro (which nest),
2087 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2088 * If we're in a %rep block, another %rep nests, so should be let through.
2090 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2091 i != PP_RMACRO && i != PP_IRMACRO &&
2092 i != PP_ENDMACRO && i != PP_ENDM &&
2093 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2094 return NO_DIRECTIVE_FOUND;
2097 if (defining) {
2098 if (i == PP_MACRO || i == PP_IMACRO ||
2099 i == PP_RMACRO || i == PP_IRMACRO) {
2100 nested_mac_count++;
2101 return NO_DIRECTIVE_FOUND;
2102 } else if (nested_mac_count > 0) {
2103 if (i == PP_ENDMACRO) {
2104 nested_mac_count--;
2105 return NO_DIRECTIVE_FOUND;
2108 if (!defining->name) {
2109 if (i == PP_REP) {
2110 nested_rep_count++;
2111 return NO_DIRECTIVE_FOUND;
2112 } else if (nested_rep_count > 0) {
2113 if (i == PP_ENDREP) {
2114 nested_rep_count--;
2115 return NO_DIRECTIVE_FOUND;
2121 switch (i) {
2122 case PP_INVALID:
2123 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2124 tline->text);
2125 return NO_DIRECTIVE_FOUND; /* didn't get it */
2127 case PP_STACKSIZE:
2128 /* Directive to tell NASM what the default stack size is. The
2129 * default is for a 16-bit stack, and this can be overriden with
2130 * %stacksize large.
2131 * the following form:
2133 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2135 tline = tline->next;
2136 if (tline && tline->type == TOK_WHITESPACE)
2137 tline = tline->next;
2138 if (!tline || tline->type != TOK_ID) {
2139 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2140 free_tlist(origline);
2141 return DIRECTIVE_FOUND;
2143 if (nasm_stricmp(tline->text, "flat") == 0) {
2144 /* All subsequent ARG directives are for a 32-bit stack */
2145 StackSize = 4;
2146 StackPointer = "ebp";
2147 ArgOffset = 8;
2148 LocalOffset = 0;
2149 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2150 /* All subsequent ARG directives are for a 64-bit stack */
2151 StackSize = 8;
2152 StackPointer = "rbp";
2153 ArgOffset = 8;
2154 LocalOffset = 0;
2155 } else if (nasm_stricmp(tline->text, "large") == 0) {
2156 /* All subsequent ARG directives are for a 16-bit stack,
2157 * far function call.
2159 StackSize = 2;
2160 StackPointer = "bp";
2161 ArgOffset = 4;
2162 LocalOffset = 0;
2163 } else if (nasm_stricmp(tline->text, "small") == 0) {
2164 /* All subsequent ARG directives are for a 16-bit stack,
2165 * far function call. We don't support near functions.
2167 StackSize = 2;
2168 StackPointer = "bp";
2169 ArgOffset = 6;
2170 LocalOffset = 0;
2171 } else {
2172 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2173 free_tlist(origline);
2174 return DIRECTIVE_FOUND;
2176 free_tlist(origline);
2177 return DIRECTIVE_FOUND;
2179 case PP_ARG:
2180 /* TASM like ARG directive to define arguments to functions, in
2181 * the following form:
2183 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2185 offset = ArgOffset;
2186 do {
2187 char *arg, directive[256];
2188 int size = StackSize;
2190 /* Find the argument name */
2191 tline = tline->next;
2192 if (tline && tline->type == TOK_WHITESPACE)
2193 tline = tline->next;
2194 if (!tline || tline->type != TOK_ID) {
2195 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2196 free_tlist(origline);
2197 return DIRECTIVE_FOUND;
2199 arg = tline->text;
2201 /* Find the argument size type */
2202 tline = tline->next;
2203 if (!tline || tline->type != TOK_OTHER
2204 || tline->text[0] != ':') {
2205 error(ERR_NONFATAL,
2206 "Syntax error processing `%%arg' directive");
2207 free_tlist(origline);
2208 return DIRECTIVE_FOUND;
2210 tline = tline->next;
2211 if (!tline || tline->type != TOK_ID) {
2212 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2213 free_tlist(origline);
2214 return DIRECTIVE_FOUND;
2217 /* Allow macro expansion of type parameter */
2218 tt = tokenize(tline->text);
2219 tt = expand_smacro(tt);
2220 size = parse_size(tt->text);
2221 if (!size) {
2222 error(ERR_NONFATAL,
2223 "Invalid size type for `%%arg' missing directive");
2224 free_tlist(tt);
2225 free_tlist(origline);
2226 return DIRECTIVE_FOUND;
2228 free_tlist(tt);
2230 /* Round up to even stack slots */
2231 size = (size+StackSize-1) & ~(StackSize-1);
2233 /* Now define the macro for the argument */
2234 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2235 arg, StackPointer, offset);
2236 do_directive(tokenize(directive));
2237 offset += size;
2239 /* Move to the next argument in the list */
2240 tline = tline->next;
2241 if (tline && tline->type == TOK_WHITESPACE)
2242 tline = tline->next;
2243 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2244 ArgOffset = offset;
2245 free_tlist(origline);
2246 return DIRECTIVE_FOUND;
2248 case PP_LOCAL:
2249 /* TASM like LOCAL directive to define local variables for a
2250 * function, in the following form:
2252 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2254 * The '= LocalSize' at the end is ignored by NASM, but is
2255 * required by TASM to define the local parameter size (and used
2256 * by the TASM macro package).
2258 offset = LocalOffset;
2259 do {
2260 char *local, directive[256];
2261 int size = StackSize;
2263 /* Find the argument name */
2264 tline = tline->next;
2265 if (tline && tline->type == TOK_WHITESPACE)
2266 tline = tline->next;
2267 if (!tline || tline->type != TOK_ID) {
2268 error(ERR_NONFATAL,
2269 "`%%local' missing argument parameter");
2270 free_tlist(origline);
2271 return DIRECTIVE_FOUND;
2273 local = tline->text;
2275 /* Find the argument size type */
2276 tline = tline->next;
2277 if (!tline || tline->type != TOK_OTHER
2278 || tline->text[0] != ':') {
2279 error(ERR_NONFATAL,
2280 "Syntax error processing `%%local' directive");
2281 free_tlist(origline);
2282 return DIRECTIVE_FOUND;
2284 tline = tline->next;
2285 if (!tline || tline->type != TOK_ID) {
2286 error(ERR_NONFATAL,
2287 "`%%local' missing size type parameter");
2288 free_tlist(origline);
2289 return DIRECTIVE_FOUND;
2292 /* Allow macro expansion of type parameter */
2293 tt = tokenize(tline->text);
2294 tt = expand_smacro(tt);
2295 size = parse_size(tt->text);
2296 if (!size) {
2297 error(ERR_NONFATAL,
2298 "Invalid size type for `%%local' missing directive");
2299 free_tlist(tt);
2300 free_tlist(origline);
2301 return DIRECTIVE_FOUND;
2303 free_tlist(tt);
2305 /* Round up to even stack slots */
2306 size = (size+StackSize-1) & ~(StackSize-1);
2308 offset += size; /* Negative offset, increment before */
2310 /* Now define the macro for the argument */
2311 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2312 local, StackPointer, offset);
2313 do_directive(tokenize(directive));
2315 /* Now define the assign to setup the enter_c macro correctly */
2316 snprintf(directive, sizeof(directive),
2317 "%%assign %%$localsize %%$localsize+%d", size);
2318 do_directive(tokenize(directive));
2320 /* Move to the next argument in the list */
2321 tline = tline->next;
2322 if (tline && tline->type == TOK_WHITESPACE)
2323 tline = tline->next;
2324 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2325 LocalOffset = offset;
2326 free_tlist(origline);
2327 return DIRECTIVE_FOUND;
2329 case PP_CLEAR:
2330 if (tline->next)
2331 error(ERR_WARNING|ERR_PASS1,
2332 "trailing garbage after `%%clear' ignored");
2333 free_macros();
2334 init_macros();
2335 free_tlist(origline);
2336 return DIRECTIVE_FOUND;
2338 case PP_DEPEND:
2339 t = tline->next = expand_smacro(tline->next);
2340 skip_white_(t);
2341 if (!t || (t->type != TOK_STRING &&
2342 t->type != TOK_INTERNAL_STRING)) {
2343 error(ERR_NONFATAL, "`%%depend' expects a file name");
2344 free_tlist(origline);
2345 return DIRECTIVE_FOUND; /* but we did _something_ */
2347 if (t->next)
2348 error(ERR_WARNING|ERR_PASS1,
2349 "trailing garbage after `%%depend' ignored");
2350 p = t->text;
2351 if (t->type != TOK_INTERNAL_STRING)
2352 nasm_unquote_cstr(p, i);
2353 if (dephead && !in_list(*dephead, p)) {
2354 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2355 sl->next = NULL;
2356 strcpy(sl->str, p);
2357 *deptail = sl;
2358 deptail = &sl->next;
2360 free_tlist(origline);
2361 return DIRECTIVE_FOUND;
2363 case PP_INCLUDE:
2364 t = tline->next = expand_smacro(tline->next);
2365 skip_white_(t);
2367 if (!t || (t->type != TOK_STRING &&
2368 t->type != TOK_INTERNAL_STRING)) {
2369 error(ERR_NONFATAL, "`%%include' expects a file name");
2370 free_tlist(origline);
2371 return DIRECTIVE_FOUND; /* but we did _something_ */
2373 if (t->next)
2374 error(ERR_WARNING|ERR_PASS1,
2375 "trailing garbage after `%%include' ignored");
2376 p = t->text;
2377 if (t->type != TOK_INTERNAL_STRING)
2378 nasm_unquote_cstr(p, i);
2379 inc = nasm_malloc(sizeof(Include));
2380 inc->next = istk;
2381 inc->conds = NULL;
2382 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2383 if (!inc->fp) {
2384 /* -MG given but file not found */
2385 nasm_free(inc);
2386 } else {
2387 inc->fname = src_set_fname(nasm_strdup(p));
2388 inc->lineno = src_set_linnum(0);
2389 inc->lineinc = 1;
2390 inc->expansion = NULL;
2391 inc->mstk = NULL;
2392 istk = inc;
2393 list->uplevel(LIST_INCLUDE);
2395 free_tlist(origline);
2396 return DIRECTIVE_FOUND;
2398 case PP_USE:
2400 static macros_t *use_pkg;
2401 const char *pkg_macro;
2403 tline = tline->next;
2404 skip_white_(tline);
2405 tline = expand_id(tline);
2407 if (!tline || (tline->type != TOK_STRING &&
2408 tline->type != TOK_INTERNAL_STRING &&
2409 tline->type != TOK_ID)) {
2410 error(ERR_NONFATAL, "`%%use' expects a package name");
2411 free_tlist(origline);
2412 return DIRECTIVE_FOUND; /* but we did _something_ */
2414 if (tline->next)
2415 error(ERR_WARNING|ERR_PASS1,
2416 "trailing garbage after `%%use' ignored");
2417 if (tline->type == TOK_STRING)
2418 nasm_unquote_cstr(tline->text, i);
2419 use_pkg = nasm_stdmac_find_package(tline->text);
2420 if (!use_pkg)
2421 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2422 /* The first string will be <%define>__USE_*__ */
2423 pkg_macro = (char *)use_pkg + 1;
2424 if (!smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2425 /* Not already included, go ahead and include it */
2426 stdmacpos = use_pkg;
2428 free_tlist(origline);
2429 return DIRECTIVE_FOUND;
2431 case PP_PUSH:
2432 case PP_REPL:
2433 case PP_POP:
2434 tline = tline->next;
2435 skip_white_(tline);
2436 tline = expand_id(tline);
2437 if (tline) {
2438 if (!tok_type_(tline, TOK_ID)) {
2439 error(ERR_NONFATAL, "`%s' expects a context identifier",
2440 pp_directives[i]);
2441 free_tlist(origline);
2442 return DIRECTIVE_FOUND; /* but we did _something_ */
2444 if (tline->next)
2445 error(ERR_WARNING|ERR_PASS1,
2446 "trailing garbage after `%s' ignored",
2447 pp_directives[i]);
2448 p = nasm_strdup(tline->text);
2449 } else {
2450 p = NULL; /* Anonymous */
2453 if (i == PP_PUSH) {
2454 ctx = nasm_malloc(sizeof(Context));
2455 ctx->next = cstk;
2456 hash_init(&ctx->localmac, HASH_SMALL);
2457 ctx->name = p;
2458 ctx->number = unique++;
2459 cstk = ctx;
2460 } else {
2461 /* %pop or %repl */
2462 if (!cstk) {
2463 error(ERR_NONFATAL, "`%s': context stack is empty",
2464 pp_directives[i]);
2465 } else if (i == PP_POP) {
2466 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2467 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2468 "expected %s",
2469 cstk->name ? cstk->name : "anonymous", p);
2470 else
2471 ctx_pop();
2472 } else {
2473 /* i == PP_REPL */
2474 nasm_free(cstk->name);
2475 cstk->name = p;
2476 p = NULL;
2478 nasm_free(p);
2480 free_tlist(origline);
2481 return DIRECTIVE_FOUND;
2482 case PP_FATAL:
2483 severity = ERR_FATAL;
2484 goto issue_error;
2485 case PP_ERROR:
2486 severity = ERR_NONFATAL;
2487 goto issue_error;
2488 case PP_WARNING:
2489 severity = ERR_WARNING|ERR_WARN_USER;
2490 goto issue_error;
2492 issue_error:
2494 /* Only error out if this is the final pass */
2495 if (pass != 2 && i != PP_FATAL)
2496 return DIRECTIVE_FOUND;
2498 tline->next = expand_smacro(tline->next);
2499 tline = tline->next;
2500 skip_white_(tline);
2501 t = tline ? tline->next : NULL;
2502 skip_white_(t);
2503 if (tok_type_(tline, TOK_STRING) && !t) {
2504 /* The line contains only a quoted string */
2505 p = tline->text;
2506 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2507 error(severity, "%s", p);
2508 } else {
2509 /* Not a quoted string, or more than a quoted string */
2510 p = detoken(tline, false);
2511 error(severity, "%s", p);
2512 nasm_free(p);
2514 free_tlist(origline);
2515 return DIRECTIVE_FOUND;
2518 CASE_PP_IF:
2519 if (istk->conds && !emitting(istk->conds->state))
2520 j = COND_NEVER;
2521 else {
2522 j = if_condition(tline->next, i);
2523 tline->next = NULL; /* it got freed */
2524 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2526 cond = nasm_malloc(sizeof(Cond));
2527 cond->next = istk->conds;
2528 cond->state = j;
2529 istk->conds = cond;
2530 if(istk->mstk)
2531 istk->mstk->condcnt ++;
2532 free_tlist(origline);
2533 return DIRECTIVE_FOUND;
2535 CASE_PP_ELIF:
2536 if (!istk->conds)
2537 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2538 switch(istk->conds->state) {
2539 case COND_IF_TRUE:
2540 istk->conds->state = COND_DONE;
2541 break;
2543 case COND_DONE:
2544 case COND_NEVER:
2545 break;
2547 case COND_ELSE_TRUE:
2548 case COND_ELSE_FALSE:
2549 error_precond(ERR_WARNING|ERR_PASS1,
2550 "`%%elif' after `%%else' ignored");
2551 istk->conds->state = COND_NEVER;
2552 break;
2554 case COND_IF_FALSE:
2556 * IMPORTANT: In the case of %if, we will already have
2557 * called expand_mmac_params(); however, if we're
2558 * processing an %elif we must have been in a
2559 * non-emitting mode, which would have inhibited
2560 * the normal invocation of expand_mmac_params().
2561 * Therefore, we have to do it explicitly here.
2563 j = if_condition(expand_mmac_params(tline->next), i);
2564 tline->next = NULL; /* it got freed */
2565 istk->conds->state =
2566 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2567 break;
2569 free_tlist(origline);
2570 return DIRECTIVE_FOUND;
2572 case PP_ELSE:
2573 if (tline->next)
2574 error_precond(ERR_WARNING|ERR_PASS1,
2575 "trailing garbage after `%%else' ignored");
2576 if (!istk->conds)
2577 error(ERR_FATAL, "`%%else': no matching `%%if'");
2578 switch(istk->conds->state) {
2579 case COND_IF_TRUE:
2580 case COND_DONE:
2581 istk->conds->state = COND_ELSE_FALSE;
2582 break;
2584 case COND_NEVER:
2585 break;
2587 case COND_IF_FALSE:
2588 istk->conds->state = COND_ELSE_TRUE;
2589 break;
2591 case COND_ELSE_TRUE:
2592 case COND_ELSE_FALSE:
2593 error_precond(ERR_WARNING|ERR_PASS1,
2594 "`%%else' after `%%else' ignored.");
2595 istk->conds->state = COND_NEVER;
2596 break;
2598 free_tlist(origline);
2599 return DIRECTIVE_FOUND;
2601 case PP_ENDIF:
2602 if (tline->next)
2603 error_precond(ERR_WARNING|ERR_PASS1,
2604 "trailing garbage after `%%endif' ignored");
2605 if (!istk->conds)
2606 error(ERR_FATAL, "`%%endif': no matching `%%if'");
2607 cond = istk->conds;
2608 istk->conds = cond->next;
2609 nasm_free(cond);
2610 if(istk->mstk)
2611 istk->mstk->condcnt --;
2612 free_tlist(origline);
2613 return DIRECTIVE_FOUND;
2615 case PP_RMACRO:
2616 case PP_IRMACRO:
2617 case PP_MACRO:
2618 case PP_IMACRO:
2619 if (defining) {
2620 error(ERR_FATAL, "`%s': already defining a macro",
2621 pp_directives[i]);
2622 return DIRECTIVE_FOUND;
2624 defining = nasm_malloc(sizeof(MMacro));
2625 defining->max_depth =
2626 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2627 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2628 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2629 nasm_free(defining);
2630 defining = NULL;
2631 return DIRECTIVE_FOUND;
2634 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2635 while (mmac) {
2636 if (!strcmp(mmac->name, defining->name) &&
2637 (mmac->nparam_min <= defining->nparam_max
2638 || defining->plus)
2639 && (defining->nparam_min <= mmac->nparam_max
2640 || mmac->plus)) {
2641 error(ERR_WARNING|ERR_PASS1,
2642 "redefining multi-line macro `%s'", defining->name);
2643 return DIRECTIVE_FOUND;
2645 mmac = mmac->next;
2647 free_tlist(origline);
2648 return DIRECTIVE_FOUND;
2650 case PP_ENDM:
2651 case PP_ENDMACRO:
2652 if (! (defining && defining->name)) {
2653 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2654 return DIRECTIVE_FOUND;
2656 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2657 defining->next = *mmhead;
2658 *mmhead = defining;
2659 defining = NULL;
2660 free_tlist(origline);
2661 return DIRECTIVE_FOUND;
2663 case PP_EXITMACRO:
2665 * We must search along istk->expansion until we hit a
2666 * macro-end marker for a macro with a name. Then we
2667 * bypass all lines between exitmacro and endmacro.
2669 for (l = istk->expansion; l; l = l->next)
2670 if (l->finishes && l->finishes->name)
2671 break;
2673 if (l) {
2675 * Remove all conditional entries relative to this
2676 * macro invocation. (safe to do in this context)
2678 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2679 cond = istk->conds;
2680 istk->conds = cond->next;
2681 nasm_free(cond);
2683 istk->expansion = l;
2684 } else {
2685 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2687 free_tlist(origline);
2688 return DIRECTIVE_FOUND;
2690 case PP_UNMACRO:
2691 case PP_UNIMACRO:
2693 MMacro **mmac_p;
2694 MMacro spec;
2696 spec.casesense = (i == PP_UNMACRO);
2697 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2698 return DIRECTIVE_FOUND;
2700 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2701 while (mmac_p && *mmac_p) {
2702 mmac = *mmac_p;
2703 if (mmac->casesense == spec.casesense &&
2704 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2705 mmac->nparam_min == spec.nparam_min &&
2706 mmac->nparam_max == spec.nparam_max &&
2707 mmac->plus == spec.plus) {
2708 *mmac_p = mmac->next;
2709 free_mmacro(mmac);
2710 } else {
2711 mmac_p = &mmac->next;
2714 free_tlist(origline);
2715 free_tlist(spec.dlist);
2716 return DIRECTIVE_FOUND;
2719 case PP_ROTATE:
2720 if (tline->next && tline->next->type == TOK_WHITESPACE)
2721 tline = tline->next;
2722 if (!tline->next) {
2723 free_tlist(origline);
2724 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2725 return DIRECTIVE_FOUND;
2727 t = expand_smacro(tline->next);
2728 tline->next = NULL;
2729 free_tlist(origline);
2730 tline = t;
2731 tptr = &t;
2732 tokval.t_type = TOKEN_INVALID;
2733 evalresult =
2734 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2735 free_tlist(tline);
2736 if (!evalresult)
2737 return DIRECTIVE_FOUND;
2738 if (tokval.t_type)
2739 error(ERR_WARNING|ERR_PASS1,
2740 "trailing garbage after expression ignored");
2741 if (!is_simple(evalresult)) {
2742 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2743 return DIRECTIVE_FOUND;
2745 mmac = istk->mstk;
2746 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2747 mmac = mmac->next_active;
2748 if (!mmac) {
2749 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2750 } else if (mmac->nparam == 0) {
2751 error(ERR_NONFATAL,
2752 "`%%rotate' invoked within macro without parameters");
2753 } else {
2754 int rotate = mmac->rotate + reloc_value(evalresult);
2756 rotate %= (int)mmac->nparam;
2757 if (rotate < 0)
2758 rotate += mmac->nparam;
2760 mmac->rotate = rotate;
2762 return DIRECTIVE_FOUND;
2764 case PP_REP:
2765 nolist = false;
2766 do {
2767 tline = tline->next;
2768 } while (tok_type_(tline, TOK_WHITESPACE));
2770 if (tok_type_(tline, TOK_ID) &&
2771 nasm_stricmp(tline->text, ".nolist") == 0) {
2772 nolist = true;
2773 do {
2774 tline = tline->next;
2775 } while (tok_type_(tline, TOK_WHITESPACE));
2778 if (tline) {
2779 t = expand_smacro(tline);
2780 tptr = &t;
2781 tokval.t_type = TOKEN_INVALID;
2782 evalresult =
2783 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2784 if (!evalresult) {
2785 free_tlist(origline);
2786 return DIRECTIVE_FOUND;
2788 if (tokval.t_type)
2789 error(ERR_WARNING|ERR_PASS1,
2790 "trailing garbage after expression ignored");
2791 if (!is_simple(evalresult)) {
2792 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
2793 return DIRECTIVE_FOUND;
2795 count = reloc_value(evalresult) + 1;
2796 } else {
2797 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
2798 count = 0;
2800 free_tlist(origline);
2802 tmp_defining = defining;
2803 defining = nasm_malloc(sizeof(MMacro));
2804 defining->prev = NULL;
2805 defining->name = NULL; /* flags this macro as a %rep block */
2806 defining->casesense = false;
2807 defining->plus = false;
2808 defining->nolist = nolist;
2809 defining->in_progress = count;
2810 defining->max_depth = 0;
2811 defining->nparam_min = defining->nparam_max = 0;
2812 defining->defaults = NULL;
2813 defining->dlist = NULL;
2814 defining->expansion = NULL;
2815 defining->next_active = istk->mstk;
2816 defining->rep_nest = tmp_defining;
2817 return DIRECTIVE_FOUND;
2819 case PP_ENDREP:
2820 if (!defining || defining->name) {
2821 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
2822 return DIRECTIVE_FOUND;
2826 * Now we have a "macro" defined - although it has no name
2827 * and we won't be entering it in the hash tables - we must
2828 * push a macro-end marker for it on to istk->expansion.
2829 * After that, it will take care of propagating itself (a
2830 * macro-end marker line for a macro which is really a %rep
2831 * block will cause the macro to be re-expanded, complete
2832 * with another macro-end marker to ensure the process
2833 * continues) until the whole expansion is forcibly removed
2834 * from istk->expansion by a %exitrep.
2836 l = nasm_malloc(sizeof(Line));
2837 l->next = istk->expansion;
2838 l->finishes = defining;
2839 l->first = NULL;
2840 istk->expansion = l;
2842 istk->mstk = defining;
2844 list->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
2845 tmp_defining = defining;
2846 defining = defining->rep_nest;
2847 free_tlist(origline);
2848 return DIRECTIVE_FOUND;
2850 case PP_EXITREP:
2852 * We must search along istk->expansion until we hit a
2853 * macro-end marker for a macro with no name. Then we set
2854 * its `in_progress' flag to 0.
2856 for (l = istk->expansion; l; l = l->next)
2857 if (l->finishes && !l->finishes->name)
2858 break;
2860 if (l)
2861 l->finishes->in_progress = 1;
2862 else
2863 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
2864 free_tlist(origline);
2865 return DIRECTIVE_FOUND;
2867 case PP_XDEFINE:
2868 case PP_IXDEFINE:
2869 case PP_DEFINE:
2870 case PP_IDEFINE:
2871 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
2873 tline = tline->next;
2874 skip_white_(tline);
2875 tline = expand_id(tline);
2876 if (!tline || (tline->type != TOK_ID &&
2877 (tline->type != TOK_PREPROC_ID ||
2878 tline->text[1] != '$'))) {
2879 error(ERR_NONFATAL, "`%s' expects a macro identifier",
2880 pp_directives[i]);
2881 free_tlist(origline);
2882 return DIRECTIVE_FOUND;
2885 ctx = get_ctx(tline->text, &mname, false);
2886 last = tline;
2887 param_start = tline = tline->next;
2888 nparam = 0;
2890 /* Expand the macro definition now for %xdefine and %ixdefine */
2891 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
2892 tline = expand_smacro(tline);
2894 if (tok_is_(tline, "(")) {
2896 * This macro has parameters.
2899 tline = tline->next;
2900 while (1) {
2901 skip_white_(tline);
2902 if (!tline) {
2903 error(ERR_NONFATAL, "parameter identifier expected");
2904 free_tlist(origline);
2905 return DIRECTIVE_FOUND;
2907 if (tline->type != TOK_ID) {
2908 error(ERR_NONFATAL,
2909 "`%s': parameter identifier expected",
2910 tline->text);
2911 free_tlist(origline);
2912 return DIRECTIVE_FOUND;
2914 tline->type = TOK_SMAC_PARAM + nparam++;
2915 tline = tline->next;
2916 skip_white_(tline);
2917 if (tok_is_(tline, ",")) {
2918 tline = tline->next;
2919 } else {
2920 if (!tok_is_(tline, ")")) {
2921 error(ERR_NONFATAL,
2922 "`)' expected to terminate macro template");
2923 free_tlist(origline);
2924 return DIRECTIVE_FOUND;
2926 break;
2929 last = tline;
2930 tline = tline->next;
2932 if (tok_type_(tline, TOK_WHITESPACE))
2933 last = tline, tline = tline->next;
2934 macro_start = NULL;
2935 last->next = NULL;
2936 t = tline;
2937 while (t) {
2938 if (t->type == TOK_ID) {
2939 for (tt = param_start; tt; tt = tt->next)
2940 if (tt->type >= TOK_SMAC_PARAM &&
2941 !strcmp(tt->text, t->text))
2942 t->type = tt->type;
2944 tt = t->next;
2945 t->next = macro_start;
2946 macro_start = t;
2947 t = tt;
2950 * Good. We now have a macro name, a parameter count, and a
2951 * token list (in reverse order) for an expansion. We ought
2952 * to be OK just to create an SMacro, store it, and let
2953 * free_tlist have the rest of the line (which we have
2954 * carefully re-terminated after chopping off the expansion
2955 * from the end).
2957 define_smacro(ctx, mname, casesense, nparam, macro_start);
2958 free_tlist(origline);
2959 return DIRECTIVE_FOUND;
2961 case PP_UNDEF:
2962 tline = tline->next;
2963 skip_white_(tline);
2964 tline = expand_id(tline);
2965 if (!tline || (tline->type != TOK_ID &&
2966 (tline->type != TOK_PREPROC_ID ||
2967 tline->text[1] != '$'))) {
2968 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
2969 free_tlist(origline);
2970 return DIRECTIVE_FOUND;
2972 if (tline->next) {
2973 error(ERR_WARNING|ERR_PASS1,
2974 "trailing garbage after macro name ignored");
2977 /* Find the context that symbol belongs to */
2978 ctx = get_ctx(tline->text, &mname, false);
2979 undef_smacro(ctx, mname);
2980 free_tlist(origline);
2981 return DIRECTIVE_FOUND;
2983 case PP_DEFSTR:
2984 case PP_IDEFSTR:
2985 casesense = (i == PP_DEFSTR);
2987 tline = tline->next;
2988 skip_white_(tline);
2989 tline = expand_id(tline);
2990 if (!tline || (tline->type != TOK_ID &&
2991 (tline->type != TOK_PREPROC_ID ||
2992 tline->text[1] != '$'))) {
2993 error(ERR_NONFATAL, "`%s' expects a macro identifier",
2994 pp_directives[i]);
2995 free_tlist(origline);
2996 return DIRECTIVE_FOUND;
2999 ctx = get_ctx(tline->text, &mname, false);
3000 last = tline;
3001 tline = expand_smacro(tline->next);
3002 last->next = NULL;
3004 while (tok_type_(tline, TOK_WHITESPACE))
3005 tline = delete_Token(tline);
3007 p = detoken(tline, false);
3008 macro_start = nasm_malloc(sizeof(*macro_start));
3009 macro_start->next = NULL;
3010 macro_start->text = nasm_quote(p, strlen(p));
3011 macro_start->type = TOK_STRING;
3012 macro_start->a.mac = NULL;
3013 nasm_free(p);
3016 * We now have a macro name, an implicit parameter count of
3017 * zero, and a string token to use as an expansion. Create
3018 * and store an SMacro.
3020 define_smacro(ctx, mname, casesense, 0, macro_start);
3021 free_tlist(origline);
3022 return DIRECTIVE_FOUND;
3024 case PP_DEFTOK:
3025 case PP_IDEFTOK:
3026 casesense = (i == PP_DEFTOK);
3028 tline = tline->next;
3029 skip_white_(tline);
3030 tline = expand_id(tline);
3031 if (!tline || (tline->type != TOK_ID &&
3032 (tline->type != TOK_PREPROC_ID ||
3033 tline->text[1] != '$'))) {
3034 error(ERR_NONFATAL,
3035 "`%s' expects a macro identifier as first parameter",
3036 pp_directives[i]);
3037 free_tlist(origline);
3038 return DIRECTIVE_FOUND;
3040 ctx = get_ctx(tline->text, &mname, false);
3041 last = tline;
3042 tline = expand_smacro(tline->next);
3043 last->next = NULL;
3045 t = tline;
3046 while (tok_type_(t, TOK_WHITESPACE))
3047 t = t->next;
3048 /* t should now point to the string */
3049 if (t->type != TOK_STRING) {
3050 error(ERR_NONFATAL,
3051 "`%s` requires string as second parameter",
3052 pp_directives[i]);
3053 free_tlist(tline);
3054 free_tlist(origline);
3055 return DIRECTIVE_FOUND;
3058 nasm_unquote_cstr(t->text, i);
3059 macro_start = tokenize(t->text);
3062 * We now have a macro name, an implicit parameter count of
3063 * zero, and a numeric token to use as an expansion. Create
3064 * and store an SMacro.
3066 define_smacro(ctx, mname, casesense, 0, macro_start);
3067 free_tlist(tline);
3068 free_tlist(origline);
3069 return DIRECTIVE_FOUND;
3071 case PP_PATHSEARCH:
3073 FILE *fp;
3074 StrList *xsl = NULL;
3075 StrList **xst = &xsl;
3077 casesense = true;
3079 tline = tline->next;
3080 skip_white_(tline);
3081 tline = expand_id(tline);
3082 if (!tline || (tline->type != TOK_ID &&
3083 (tline->type != TOK_PREPROC_ID ||
3084 tline->text[1] != '$'))) {
3085 error(ERR_NONFATAL,
3086 "`%%pathsearch' expects a macro identifier as first parameter");
3087 free_tlist(origline);
3088 return DIRECTIVE_FOUND;
3090 ctx = get_ctx(tline->text, &mname, false);
3091 last = tline;
3092 tline = expand_smacro(tline->next);
3093 last->next = NULL;
3095 t = tline;
3096 while (tok_type_(t, TOK_WHITESPACE))
3097 t = t->next;
3099 if (!t || (t->type != TOK_STRING &&
3100 t->type != TOK_INTERNAL_STRING)) {
3101 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3102 free_tlist(tline);
3103 free_tlist(origline);
3104 return DIRECTIVE_FOUND; /* but we did _something_ */
3106 if (t->next)
3107 error(ERR_WARNING|ERR_PASS1,
3108 "trailing garbage after `%%pathsearch' ignored");
3109 p = t->text;
3110 if (t->type != TOK_INTERNAL_STRING)
3111 nasm_unquote(p, NULL);
3113 fp = inc_fopen(p, &xsl, &xst, true);
3114 if (fp) {
3115 p = xsl->str;
3116 fclose(fp); /* Don't actually care about the file */
3118 macro_start = nasm_malloc(sizeof(*macro_start));
3119 macro_start->next = NULL;
3120 macro_start->text = nasm_quote(p, strlen(p));
3121 macro_start->type = TOK_STRING;
3122 macro_start->a.mac = NULL;
3123 if (xsl)
3124 nasm_free(xsl);
3127 * We now have a macro name, an implicit parameter count of
3128 * zero, and a string token to use as an expansion. Create
3129 * and store an SMacro.
3131 define_smacro(ctx, mname, casesense, 0, macro_start);
3132 free_tlist(tline);
3133 free_tlist(origline);
3134 return DIRECTIVE_FOUND;
3137 case PP_STRLEN:
3138 casesense = true;
3140 tline = tline->next;
3141 skip_white_(tline);
3142 tline = expand_id(tline);
3143 if (!tline || (tline->type != TOK_ID &&
3144 (tline->type != TOK_PREPROC_ID ||
3145 tline->text[1] != '$'))) {
3146 error(ERR_NONFATAL,
3147 "`%%strlen' expects a macro identifier as first parameter");
3148 free_tlist(origline);
3149 return DIRECTIVE_FOUND;
3151 ctx = get_ctx(tline->text, &mname, false);
3152 last = tline;
3153 tline = expand_smacro(tline->next);
3154 last->next = NULL;
3156 t = tline;
3157 while (tok_type_(t, TOK_WHITESPACE))
3158 t = t->next;
3159 /* t should now point to the string */
3160 if (t->type != TOK_STRING) {
3161 error(ERR_NONFATAL,
3162 "`%%strlen` requires string as second parameter");
3163 free_tlist(tline);
3164 free_tlist(origline);
3165 return DIRECTIVE_FOUND;
3168 macro_start = nasm_malloc(sizeof(*macro_start));
3169 macro_start->next = NULL;
3170 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3171 macro_start->a.mac = NULL;
3174 * We now have a macro name, an implicit parameter count of
3175 * zero, and a numeric token to use as an expansion. Create
3176 * and store an SMacro.
3178 define_smacro(ctx, mname, casesense, 0, macro_start);
3179 free_tlist(tline);
3180 free_tlist(origline);
3181 return DIRECTIVE_FOUND;
3183 case PP_STRCAT:
3184 casesense = true;
3186 tline = tline->next;
3187 skip_white_(tline);
3188 tline = expand_id(tline);
3189 if (!tline || (tline->type != TOK_ID &&
3190 (tline->type != TOK_PREPROC_ID ||
3191 tline->text[1] != '$'))) {
3192 error(ERR_NONFATAL,
3193 "`%%strcat' expects a macro identifier as first parameter");
3194 free_tlist(origline);
3195 return DIRECTIVE_FOUND;
3197 ctx = get_ctx(tline->text, &mname, false);
3198 last = tline;
3199 tline = expand_smacro(tline->next);
3200 last->next = NULL;
3202 len = 0;
3203 for (t = tline; t; t = t->next) {
3204 switch (t->type) {
3205 case TOK_WHITESPACE:
3206 break;
3207 case TOK_STRING:
3208 len += t->a.len = nasm_unquote(t->text, NULL);
3209 break;
3210 case TOK_OTHER:
3211 if (!strcmp(t->text, ",")) /* permit comma separators */
3212 break;
3213 /* else fall through */
3214 default:
3215 error(ERR_NONFATAL,
3216 "non-string passed to `%%strcat' (%d)", t->type);
3217 free_tlist(tline);
3218 free_tlist(origline);
3219 return DIRECTIVE_FOUND;
3223 p = pp = nasm_malloc(len);
3224 for (t = tline; t; t = t->next) {
3225 if (t->type == TOK_STRING) {
3226 memcpy(p, t->text, t->a.len);
3227 p += t->a.len;
3232 * We now have a macro name, an implicit parameter count of
3233 * zero, and a numeric token to use as an expansion. Create
3234 * and store an SMacro.
3236 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3237 macro_start->text = nasm_quote(pp, len);
3238 nasm_free(pp);
3239 define_smacro(ctx, mname, casesense, 0, macro_start);
3240 free_tlist(tline);
3241 free_tlist(origline);
3242 return DIRECTIVE_FOUND;
3244 case PP_SUBSTR:
3246 int64_t a1, a2;
3247 size_t len;
3249 casesense = true;
3251 tline = tline->next;
3252 skip_white_(tline);
3253 tline = expand_id(tline);
3254 if (!tline || (tline->type != TOK_ID &&
3255 (tline->type != TOK_PREPROC_ID ||
3256 tline->text[1] != '$'))) {
3257 error(ERR_NONFATAL,
3258 "`%%substr' expects a macro identifier as first parameter");
3259 free_tlist(origline);
3260 return DIRECTIVE_FOUND;
3262 ctx = get_ctx(tline->text, &mname, false);
3263 last = tline;
3264 tline = expand_smacro(tline->next);
3265 last->next = NULL;
3267 t = tline->next;
3268 while (tok_type_(t, TOK_WHITESPACE))
3269 t = t->next;
3271 /* t should now point to the string */
3272 if (t->type != TOK_STRING) {
3273 error(ERR_NONFATAL,
3274 "`%%substr` requires string as second parameter");
3275 free_tlist(tline);
3276 free_tlist(origline);
3277 return DIRECTIVE_FOUND;
3280 tt = t->next;
3281 tptr = &tt;
3282 tokval.t_type = TOKEN_INVALID;
3283 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3284 pass, error, NULL);
3285 if (!evalresult) {
3286 free_tlist(tline);
3287 free_tlist(origline);
3288 return DIRECTIVE_FOUND;
3289 } else if (!is_simple(evalresult)) {
3290 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3291 free_tlist(tline);
3292 free_tlist(origline);
3293 return DIRECTIVE_FOUND;
3295 a1 = evalresult->value-1;
3297 while (tok_type_(tt, TOK_WHITESPACE))
3298 tt = tt->next;
3299 if (!tt) {
3300 a2 = 1; /* Backwards compatibility: one character */
3301 } else {
3302 tokval.t_type = TOKEN_INVALID;
3303 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3304 pass, error, NULL);
3305 if (!evalresult) {
3306 free_tlist(tline);
3307 free_tlist(origline);
3308 return DIRECTIVE_FOUND;
3309 } else if (!is_simple(evalresult)) {
3310 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3311 free_tlist(tline);
3312 free_tlist(origline);
3313 return DIRECTIVE_FOUND;
3315 a2 = evalresult->value;
3318 len = nasm_unquote(t->text, NULL);
3319 if (a2 < 0)
3320 a2 = a2+1+len-a1;
3321 if (a1+a2 > (int64_t)len)
3322 a2 = len-a1;
3324 macro_start = nasm_malloc(sizeof(*macro_start));
3325 macro_start->next = NULL;
3326 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3327 macro_start->type = TOK_STRING;
3328 macro_start->a.mac = NULL;
3331 * We now have a macro name, an implicit parameter count of
3332 * zero, and a numeric token to use as an expansion. Create
3333 * and store an SMacro.
3335 define_smacro(ctx, mname, casesense, 0, macro_start);
3336 free_tlist(tline);
3337 free_tlist(origline);
3338 return DIRECTIVE_FOUND;
3341 case PP_ASSIGN:
3342 case PP_IASSIGN:
3343 casesense = (i == PP_ASSIGN);
3345 tline = tline->next;
3346 skip_white_(tline);
3347 tline = expand_id(tline);
3348 if (!tline || (tline->type != TOK_ID &&
3349 (tline->type != TOK_PREPROC_ID ||
3350 tline->text[1] != '$'))) {
3351 error(ERR_NONFATAL,
3352 "`%%%sassign' expects a macro identifier",
3353 (i == PP_IASSIGN ? "i" : ""));
3354 free_tlist(origline);
3355 return DIRECTIVE_FOUND;
3357 ctx = get_ctx(tline->text, &mname, false);
3358 last = tline;
3359 tline = expand_smacro(tline->next);
3360 last->next = NULL;
3362 t = tline;
3363 tptr = &t;
3364 tokval.t_type = TOKEN_INVALID;
3365 evalresult =
3366 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3367 free_tlist(tline);
3368 if (!evalresult) {
3369 free_tlist(origline);
3370 return DIRECTIVE_FOUND;
3373 if (tokval.t_type)
3374 error(ERR_WARNING|ERR_PASS1,
3375 "trailing garbage after expression ignored");
3377 if (!is_simple(evalresult)) {
3378 error(ERR_NONFATAL,
3379 "non-constant value given to `%%%sassign'",
3380 (i == PP_IASSIGN ? "i" : ""));
3381 free_tlist(origline);
3382 return DIRECTIVE_FOUND;
3385 macro_start = nasm_malloc(sizeof(*macro_start));
3386 macro_start->next = NULL;
3387 make_tok_num(macro_start, reloc_value(evalresult));
3388 macro_start->a.mac = NULL;
3391 * We now have a macro name, an implicit parameter count of
3392 * zero, and a numeric token to use as an expansion. Create
3393 * and store an SMacro.
3395 define_smacro(ctx, mname, casesense, 0, macro_start);
3396 free_tlist(origline);
3397 return DIRECTIVE_FOUND;
3399 case PP_LINE:
3401 * Syntax is `%line nnn[+mmm] [filename]'
3403 tline = tline->next;
3404 skip_white_(tline);
3405 if (!tok_type_(tline, TOK_NUMBER)) {
3406 error(ERR_NONFATAL, "`%%line' expects line number");
3407 free_tlist(origline);
3408 return DIRECTIVE_FOUND;
3410 k = readnum(tline->text, &err);
3411 m = 1;
3412 tline = tline->next;
3413 if (tok_is_(tline, "+")) {
3414 tline = tline->next;
3415 if (!tok_type_(tline, TOK_NUMBER)) {
3416 error(ERR_NONFATAL, "`%%line' expects line increment");
3417 free_tlist(origline);
3418 return DIRECTIVE_FOUND;
3420 m = readnum(tline->text, &err);
3421 tline = tline->next;
3423 skip_white_(tline);
3424 src_set_linnum(k);
3425 istk->lineinc = m;
3426 if (tline) {
3427 nasm_free(src_set_fname(detoken(tline, false)));
3429 free_tlist(origline);
3430 return DIRECTIVE_FOUND;
3432 default:
3433 error(ERR_FATAL,
3434 "preprocessor directive `%s' not yet implemented",
3435 pp_directives[i]);
3436 return DIRECTIVE_FOUND;
3441 * Ensure that a macro parameter contains a condition code and
3442 * nothing else. Return the condition code index if so, or -1
3443 * otherwise.
3445 static int find_cc(Token * t)
3447 Token *tt;
3448 int i, j, k, m;
3450 if (!t)
3451 return -1; /* Probably a %+ without a space */
3453 skip_white_(t);
3454 if (t->type != TOK_ID)
3455 return -1;
3456 tt = t->next;
3457 skip_white_(tt);
3458 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3459 return -1;
3461 i = -1;
3462 j = elements(conditions);
3463 while (j - i > 1) {
3464 k = (j + i) / 2;
3465 m = nasm_stricmp(t->text, conditions[k]);
3466 if (m == 0) {
3467 i = k;
3468 j = -2;
3469 break;
3470 } else if (m < 0) {
3471 j = k;
3472 } else
3473 i = k;
3475 if (j != -2)
3476 return -1;
3477 return i;
3480 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3482 Token **tail, *t, *tt;
3483 Token **paste_head;
3484 bool did_paste = false;
3485 char *tmp;
3487 /* Now handle token pasting... */
3488 paste_head = NULL;
3489 tail = head;
3490 while ((t = *tail) && (tt = t->next)) {
3491 switch (t->type) {
3492 case TOK_WHITESPACE:
3493 if (tt->type == TOK_WHITESPACE) {
3494 /* Zap adjacent whitespace tokens */
3495 t->next = delete_Token(tt);
3496 } else {
3497 /* Do not advance paste_head here */
3498 tail = &t->next;
3500 break;
3501 case TOK_ID:
3502 case TOK_PREPROC_ID:
3503 case TOK_NUMBER:
3504 case TOK_FLOAT:
3506 size_t len = 0;
3507 char *tmp, *p;
3509 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3510 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3511 tt->type == TOK_OTHER)) {
3512 len += strlen(tt->text);
3513 tt = tt->next;
3516 /* Now tt points to the first token after the potential
3517 paste area... */
3518 if (tt != t->next) {
3519 /* We have at least two tokens... */
3520 len += strlen(t->text);
3521 p = tmp = nasm_malloc(len+1);
3523 while (t != tt) {
3524 strcpy(p, t->text);
3525 p = strchr(p, '\0');
3526 t = delete_Token(t);
3529 t = *tail = tokenize(tmp);
3530 nasm_free(tmp);
3532 while (t->next) {
3533 tail = &t->next;
3534 t = t->next;
3536 t->next = tt; /* Attach the remaining token chain */
3538 did_paste = true;
3540 paste_head = tail;
3541 tail = &t->next;
3542 break;
3544 case TOK_PASTE: /* %+ */
3545 if (handle_paste_tokens) {
3546 /* Zap %+ and whitespace tokens to the right */
3547 while (t && (t->type == TOK_WHITESPACE ||
3548 t->type == TOK_PASTE))
3549 t = *tail = delete_Token(t);
3550 if (!paste_head || !t)
3551 break; /* Nothing to paste with */
3552 tail = paste_head;
3553 t = *tail;
3554 tt = t->next;
3555 while (tok_type_(tt, TOK_WHITESPACE))
3556 tt = t->next = delete_Token(tt);
3558 if (tt) {
3559 tmp = nasm_strcat(t->text, tt->text);
3560 delete_Token(t);
3561 tt = delete_Token(tt);
3562 t = *tail = tokenize(tmp);
3563 nasm_free(tmp);
3564 while (t->next) {
3565 tail = &t->next;
3566 t = t->next;
3568 t->next = tt; /* Attach the remaining token chain */
3569 did_paste = true;
3571 paste_head = tail;
3572 tail = &t->next;
3573 break;
3575 /* else fall through */
3576 default:
3577 tail = paste_head = &t->next;
3578 break;
3581 return did_paste;
3584 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3585 * %-n) and MMacro-local identifiers (%%foo) as well as
3586 * macro indirection (%[...]).
3588 static Token *expand_mmac_params(Token * tline)
3590 Token *t, *tt, **tail, *thead;
3591 bool changed = false;
3593 tail = &thead;
3594 thead = NULL;
3596 while (tline) {
3597 if (tline->type == TOK_PREPROC_ID &&
3598 (((tline->text[1] == '+' || tline->text[1] == '-')
3599 && tline->text[2]) || tline->text[1] == '%'
3600 || (tline->text[1] >= '0' && tline->text[1] <= '9'))) {
3601 char *text = NULL;
3602 int type = 0, cc; /* type = 0 to placate optimisers */
3603 char tmpbuf[30];
3604 unsigned int n;
3605 int i;
3606 MMacro *mac;
3608 t = tline;
3609 tline = tline->next;
3611 mac = istk->mstk;
3612 while (mac && !mac->name) /* avoid mistaking %reps for macros */
3613 mac = mac->next_active;
3614 if (!mac)
3615 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3616 else
3617 switch (t->text[1]) {
3619 * We have to make a substitution of one of the
3620 * forms %1, %-1, %+1, %%foo, %0.
3622 case '0':
3623 type = TOK_NUMBER;
3624 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
3625 text = nasm_strdup(tmpbuf);
3626 break;
3627 case '%':
3628 type = TOK_ID;
3629 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3630 mac->unique);
3631 text = nasm_strcat(tmpbuf, t->text + 2);
3632 break;
3633 case '-':
3634 n = atoi(t->text + 2) - 1;
3635 if (n >= mac->nparam)
3636 tt = NULL;
3637 else {
3638 if (mac->nparam > 1)
3639 n = (n + mac->rotate) % mac->nparam;
3640 tt = mac->params[n];
3642 cc = find_cc(tt);
3643 if (cc == -1) {
3644 error(ERR_NONFATAL,
3645 "macro parameter %d is not a condition code",
3646 n + 1);
3647 text = NULL;
3648 } else {
3649 type = TOK_ID;
3650 if (inverse_ccs[cc] == -1) {
3651 error(ERR_NONFATAL,
3652 "condition code `%s' is not invertible",
3653 conditions[cc]);
3654 text = NULL;
3655 } else
3656 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3658 break;
3659 case '+':
3660 n = atoi(t->text + 2) - 1;
3661 if (n >= mac->nparam)
3662 tt = NULL;
3663 else {
3664 if (mac->nparam > 1)
3665 n = (n + mac->rotate) % mac->nparam;
3666 tt = mac->params[n];
3668 cc = find_cc(tt);
3669 if (cc == -1) {
3670 error(ERR_NONFATAL,
3671 "macro parameter %d is not a condition code",
3672 n + 1);
3673 text = NULL;
3674 } else {
3675 type = TOK_ID;
3676 text = nasm_strdup(conditions[cc]);
3678 break;
3679 default:
3680 n = atoi(t->text + 1) - 1;
3681 if (n >= mac->nparam)
3682 tt = NULL;
3683 else {
3684 if (mac->nparam > 1)
3685 n = (n + mac->rotate) % mac->nparam;
3686 tt = mac->params[n];
3688 if (tt) {
3689 for (i = 0; i < mac->paramlen[n]; i++) {
3690 *tail = new_Token(NULL, tt->type, tt->text, 0);
3691 tail = &(*tail)->next;
3692 tt = tt->next;
3695 text = NULL; /* we've done it here */
3696 break;
3698 if (!text) {
3699 delete_Token(t);
3700 } else {
3701 *tail = t;
3702 tail = &t->next;
3703 t->type = type;
3704 nasm_free(t->text);
3705 t->text = text;
3706 t->a.mac = NULL;
3708 changed = true;
3709 continue;
3710 } else if (tline->type == TOK_INDIRECT) {
3711 t = tline;
3712 tline = tline->next;
3713 tt = tokenize(t->text);
3714 tt = expand_mmac_params(tt);
3715 tt = expand_smacro(tt);
3716 *tail = tt;
3717 while (tt) {
3718 tt->a.mac = NULL; /* Necessary? */
3719 tail = &tt->next;
3720 tt = tt->next;
3722 delete_Token(t);
3723 changed = true;
3724 } else {
3725 t = *tail = tline;
3726 tline = tline->next;
3727 t->a.mac = NULL;
3728 tail = &t->next;
3731 *tail = NULL;
3733 if (changed)
3734 paste_tokens(&thead, false);
3736 return thead;
3740 * Expand all single-line macro calls made in the given line.
3741 * Return the expanded version of the line. The original is deemed
3742 * to be destroyed in the process. (In reality we'll just move
3743 * Tokens from input to output a lot of the time, rather than
3744 * actually bothering to destroy and replicate.)
3747 static Token *expand_smacro(Token * tline)
3749 Token *t, *tt, *mstart, **tail, *thead;
3750 struct hash_table *smtbl;
3751 SMacro *head = NULL, *m;
3752 Token **params;
3753 int *paramsize;
3754 unsigned int nparam, sparam;
3755 int brackets;
3756 Token *org_tline = tline;
3757 Context *ctx;
3758 const char *mname;
3759 int deadman = DEADMAN_LIMIT;
3760 bool expanded;
3763 * Trick: we should avoid changing the start token pointer since it can
3764 * be contained in "next" field of other token. Because of this
3765 * we allocate a copy of first token and work with it; at the end of
3766 * routine we copy it back
3768 if (org_tline) {
3769 tline =
3770 new_Token(org_tline->next, org_tline->type, org_tline->text,
3772 tline->a.mac = org_tline->a.mac;
3773 nasm_free(org_tline->text);
3774 org_tline->text = NULL;
3777 expanded = true; /* Always expand %+ at least once */
3779 again:
3780 tail = &thead;
3781 thead = NULL;
3783 while (tline) { /* main token loop */
3784 if (!--deadman) {
3785 error(ERR_NONFATAL, "interminable macro recursion");
3786 goto err;
3789 if ((mname = tline->text)) {
3790 /* if this token is a local macro, look in local context */
3791 if (tline->type == TOK_ID || tline->type == TOK_PREPROC_ID)
3792 ctx = get_ctx(mname, &mname, true);
3793 else
3794 ctx = NULL;
3795 smtbl = ctx ? &ctx->localmac : &smacros;
3796 head = (SMacro *) hash_findix(smtbl, mname);
3799 * We've hit an identifier. As in is_mmacro below, we first
3800 * check whether the identifier is a single-line macro at
3801 * all, then think about checking for parameters if
3802 * necessary.
3804 for (m = head; m; m = m->next)
3805 if (!mstrcmp(m->name, mname, m->casesense))
3806 break;
3807 if (m) {
3808 mstart = tline;
3809 params = NULL;
3810 paramsize = NULL;
3811 if (m->nparam == 0) {
3813 * Simple case: the macro is parameterless. Discard the
3814 * one token that the macro call took, and push the
3815 * expansion back on the to-do stack.
3817 if (!m->expansion) {
3818 if (!strcmp("__FILE__", m->name)) {
3819 int32_t num = 0;
3820 char *file = NULL;
3821 src_get(&num, &file);
3822 tline->text = nasm_quote(file, strlen(file));
3823 tline->type = TOK_STRING;
3824 nasm_free(file);
3825 continue;
3827 if (!strcmp("__LINE__", m->name)) {
3828 nasm_free(tline->text);
3829 make_tok_num(tline, src_get_linnum());
3830 continue;
3832 if (!strcmp("__BITS__", m->name)) {
3833 nasm_free(tline->text);
3834 make_tok_num(tline, globalbits);
3835 continue;
3837 tline = delete_Token(tline);
3838 continue;
3840 } else {
3842 * Complicated case: at least one macro with this name
3843 * exists and takes parameters. We must find the
3844 * parameters in the call, count them, find the SMacro
3845 * that corresponds to that form of the macro call, and
3846 * substitute for the parameters when we expand. What a
3847 * pain.
3849 /*tline = tline->next;
3850 skip_white_(tline); */
3851 do {
3852 t = tline->next;
3853 while (tok_type_(t, TOK_SMAC_END)) {
3854 t->a.mac->in_progress = false;
3855 t->text = NULL;
3856 t = tline->next = delete_Token(t);
3858 tline = t;
3859 } while (tok_type_(tline, TOK_WHITESPACE));
3860 if (!tok_is_(tline, "(")) {
3862 * This macro wasn't called with parameters: ignore
3863 * the call. (Behaviour borrowed from gnu cpp.)
3865 tline = mstart;
3866 m = NULL;
3867 } else {
3868 int paren = 0;
3869 int white = 0;
3870 brackets = 0;
3871 nparam = 0;
3872 sparam = PARAM_DELTA;
3873 params = nasm_malloc(sparam * sizeof(Token *));
3874 params[0] = tline->next;
3875 paramsize = nasm_malloc(sparam * sizeof(int));
3876 paramsize[0] = 0;
3877 while (true) { /* parameter loop */
3879 * For some unusual expansions
3880 * which concatenates function call
3882 t = tline->next;
3883 while (tok_type_(t, TOK_SMAC_END)) {
3884 t->a.mac->in_progress = false;
3885 t->text = NULL;
3886 t = tline->next = delete_Token(t);
3888 tline = t;
3890 if (!tline) {
3891 error(ERR_NONFATAL,
3892 "macro call expects terminating `)'");
3893 break;
3895 if (tline->type == TOK_WHITESPACE
3896 && brackets <= 0) {
3897 if (paramsize[nparam])
3898 white++;
3899 else
3900 params[nparam] = tline->next;
3901 continue; /* parameter loop */
3903 if (tline->type == TOK_OTHER
3904 && tline->text[1] == 0) {
3905 char ch = tline->text[0];
3906 if (ch == ',' && !paren && brackets <= 0) {
3907 if (++nparam >= sparam) {
3908 sparam += PARAM_DELTA;
3909 params = nasm_realloc(params,
3910 sparam *
3911 sizeof(Token
3912 *));
3913 paramsize =
3914 nasm_realloc(paramsize,
3915 sparam *
3916 sizeof(int));
3918 params[nparam] = tline->next;
3919 paramsize[nparam] = 0;
3920 white = 0;
3921 continue; /* parameter loop */
3923 if (ch == '{' &&
3924 (brackets > 0 || (brackets == 0 &&
3925 !paramsize[nparam])))
3927 if (!(brackets++)) {
3928 params[nparam] = tline->next;
3929 continue; /* parameter loop */
3932 if (ch == '}' && brackets > 0)
3933 if (--brackets == 0) {
3934 brackets = -1;
3935 continue; /* parameter loop */
3937 if (ch == '(' && !brackets)
3938 paren++;
3939 if (ch == ')' && brackets <= 0)
3940 if (--paren < 0)
3941 break;
3943 if (brackets < 0) {
3944 brackets = 0;
3945 error(ERR_NONFATAL, "braces do not "
3946 "enclose all of macro parameter");
3948 paramsize[nparam] += white + 1;
3949 white = 0;
3950 } /* parameter loop */
3951 nparam++;
3952 while (m && (m->nparam != nparam ||
3953 mstrcmp(m->name, mname,
3954 m->casesense)))
3955 m = m->next;
3956 if (!m)
3957 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
3958 "macro `%s' exists, "
3959 "but not taking %d parameters",
3960 mstart->text, nparam);
3963 if (m && m->in_progress)
3964 m = NULL;
3965 if (!m) { /* in progess or didn't find '(' or wrong nparam */
3967 * Design question: should we handle !tline, which
3968 * indicates missing ')' here, or expand those
3969 * macros anyway, which requires the (t) test a few
3970 * lines down?
3972 nasm_free(params);
3973 nasm_free(paramsize);
3974 tline = mstart;
3975 } else {
3977 * Expand the macro: we are placed on the last token of the
3978 * call, so that we can easily split the call from the
3979 * following tokens. We also start by pushing an SMAC_END
3980 * token for the cycle removal.
3982 t = tline;
3983 if (t) {
3984 tline = t->next;
3985 t->next = NULL;
3987 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
3988 tt->a.mac = m;
3989 m->in_progress = true;
3990 tline = tt;
3991 for (t = m->expansion; t; t = t->next) {
3992 if (t->type >= TOK_SMAC_PARAM) {
3993 Token *pcopy = tline, **ptail = &pcopy;
3994 Token *ttt, *pt;
3995 int i;
3997 ttt = params[t->type - TOK_SMAC_PARAM];
3998 for (i = paramsize[t->type - TOK_SMAC_PARAM];
3999 --i >= 0;) {
4000 pt = *ptail =
4001 new_Token(tline, ttt->type, ttt->text,
4003 ptail = &pt->next;
4004 ttt = ttt->next;
4006 tline = pcopy;
4007 } else if (t->type == TOK_PREPROC_Q) {
4008 tt = new_Token(tline, TOK_ID, mname, 0);
4009 tline = tt;
4010 } else if (t->type == TOK_PREPROC_QQ) {
4011 tt = new_Token(tline, TOK_ID, m->name, 0);
4012 tline = tt;
4013 } else {
4014 tt = new_Token(tline, t->type, t->text, 0);
4015 tline = tt;
4020 * Having done that, get rid of the macro call, and clean
4021 * up the parameters.
4023 nasm_free(params);
4024 nasm_free(paramsize);
4025 free_tlist(mstart);
4026 expanded = true;
4027 continue; /* main token loop */
4032 if (tline->type == TOK_SMAC_END) {
4033 tline->a.mac->in_progress = false;
4034 tline = delete_Token(tline);
4035 } else {
4036 t = *tail = tline;
4037 tline = tline->next;
4038 t->a.mac = NULL;
4039 t->next = NULL;
4040 tail = &t->next;
4045 * Now scan the entire line and look for successive TOK_IDs that resulted
4046 * after expansion (they can't be produced by tokenize()). The successive
4047 * TOK_IDs should be concatenated.
4048 * Also we look for %+ tokens and concatenate the tokens before and after
4049 * them (without white spaces in between).
4051 if (expanded && paste_tokens(&thead, true)) {
4053 * If we concatenated something, *and* we had previously expanded
4054 * an actual macro, scan the lines again for macros...
4056 tline = thead;
4057 expanded = false;
4058 goto again;
4061 err:
4062 if (org_tline) {
4063 if (thead) {
4064 *org_tline = *thead;
4065 /* since we just gave text to org_line, don't free it */
4066 thead->text = NULL;
4067 delete_Token(thead);
4068 } else {
4069 /* the expression expanded to empty line;
4070 we can't return NULL for some reasons
4071 we just set the line to a single WHITESPACE token. */
4072 memset(org_tline, 0, sizeof(*org_tline));
4073 org_tline->text = NULL;
4074 org_tline->type = TOK_WHITESPACE;
4076 thead = org_tline;
4079 return thead;
4083 * Similar to expand_smacro but used exclusively with macro identifiers
4084 * right before they are fetched in. The reason is that there can be
4085 * identifiers consisting of several subparts. We consider that if there
4086 * are more than one element forming the name, user wants a expansion,
4087 * otherwise it will be left as-is. Example:
4089 * %define %$abc cde
4091 * the identifier %$abc will be left as-is so that the handler for %define
4092 * will suck it and define the corresponding value. Other case:
4094 * %define _%$abc cde
4096 * In this case user wants name to be expanded *before* %define starts
4097 * working, so we'll expand %$abc into something (if it has a value;
4098 * otherwise it will be left as-is) then concatenate all successive
4099 * PP_IDs into one.
4101 static Token *expand_id(Token * tline)
4103 Token *cur, *oldnext = NULL;
4105 if (!tline || !tline->next)
4106 return tline;
4108 cur = tline;
4109 while (cur->next &&
4110 (cur->next->type == TOK_ID ||
4111 cur->next->type == TOK_PREPROC_ID
4112 || cur->next->type == TOK_NUMBER))
4113 cur = cur->next;
4115 /* If identifier consists of just one token, don't expand */
4116 if (cur == tline)
4117 return tline;
4119 if (cur) {
4120 oldnext = cur->next; /* Detach the tail past identifier */
4121 cur->next = NULL; /* so that expand_smacro stops here */
4124 tline = expand_smacro(tline);
4126 if (cur) {
4127 /* expand_smacro possibly changhed tline; re-scan for EOL */
4128 cur = tline;
4129 while (cur && cur->next)
4130 cur = cur->next;
4131 if (cur)
4132 cur->next = oldnext;
4135 return tline;
4139 * Determine whether the given line constitutes a multi-line macro
4140 * call, and return the MMacro structure called if so. Doesn't have
4141 * to check for an initial label - that's taken care of in
4142 * expand_mmacro - but must check numbers of parameters. Guaranteed
4143 * to be called with tline->type == TOK_ID, so the putative macro
4144 * name is easy to find.
4146 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4148 MMacro *head, *m;
4149 Token **params;
4150 int nparam;
4152 head = (MMacro *) hash_findix(&mmacros, tline->text);
4155 * Efficiency: first we see if any macro exists with the given
4156 * name. If not, we can return NULL immediately. _Then_ we
4157 * count the parameters, and then we look further along the
4158 * list if necessary to find the proper MMacro.
4160 for (m = head; m; m = m->next)
4161 if (!mstrcmp(m->name, tline->text, m->casesense))
4162 break;
4163 if (!m)
4164 return NULL;
4167 * OK, we have a potential macro. Count and demarcate the
4168 * parameters.
4170 count_mmac_params(tline->next, &nparam, &params);
4173 * So we know how many parameters we've got. Find the MMacro
4174 * structure that handles this number.
4176 while (m) {
4177 if (m->nparam_min <= nparam
4178 && (m->plus || nparam <= m->nparam_max)) {
4180 * This one is right. Just check if cycle removal
4181 * prohibits us using it before we actually celebrate...
4183 if (m->in_progress > m->max_depth) {
4184 if (m->max_depth > 0) {
4185 error(ERR_WARNING,
4186 "reached maximum recursion depth of %i",
4187 m->max_depth);
4189 nasm_free(params);
4190 return NULL;
4193 * It's right, and we can use it. Add its default
4194 * parameters to the end of our list if necessary.
4196 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4197 params =
4198 nasm_realloc(params,
4199 ((m->nparam_min + m->ndefs +
4200 1) * sizeof(*params)));
4201 while (nparam < m->nparam_min + m->ndefs) {
4202 params[nparam] = m->defaults[nparam - m->nparam_min];
4203 nparam++;
4207 * If we've gone over the maximum parameter count (and
4208 * we're in Plus mode), ignore parameters beyond
4209 * nparam_max.
4211 if (m->plus && nparam > m->nparam_max)
4212 nparam = m->nparam_max;
4214 * Then terminate the parameter list, and leave.
4216 if (!params) { /* need this special case */
4217 params = nasm_malloc(sizeof(*params));
4218 nparam = 0;
4220 params[nparam] = NULL;
4221 *params_array = params;
4222 return m;
4225 * This one wasn't right: look for the next one with the
4226 * same name.
4228 for (m = m->next; m; m = m->next)
4229 if (!mstrcmp(m->name, tline->text, m->casesense))
4230 break;
4234 * After all that, we didn't find one with the right number of
4235 * parameters. Issue a warning, and fail to expand the macro.
4237 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4238 "macro `%s' exists, but not taking %d parameters",
4239 tline->text, nparam);
4240 nasm_free(params);
4241 return NULL;
4246 * Save MMacro invocation specific fields in
4247 * preparation for a recursive macro expansion
4249 static void push_mmacro(MMacro *m)
4251 MMacroInvocation *i;
4253 i = nasm_malloc(sizeof(MMacroInvocation));
4254 i->prev = m->prev;
4255 i->params = m->params;
4256 i->iline = m->iline;
4257 i->nparam = m->nparam;
4258 i->rotate = m->rotate;
4259 i->paramlen = m->paramlen;
4260 i->unique = m->unique;
4261 i->condcnt = m->condcnt;
4262 m->prev = i;
4267 * Restore MMacro invocation specific fields that were
4268 * saved during a previous recursive macro expansion
4270 static void pop_mmacro(MMacro *m)
4272 MMacroInvocation *i;
4274 if (m->prev) {
4275 i = m->prev;
4276 m->prev = i->prev;
4277 m->params = i->params;
4278 m->iline = i->iline;
4279 m->nparam = i->nparam;
4280 m->rotate = i->rotate;
4281 m->paramlen = i->paramlen;
4282 m->unique = i->unique;
4283 m->condcnt = i->condcnt;
4284 nasm_free(i);
4290 * Expand the multi-line macro call made by the given line, if
4291 * there is one to be expanded. If there is, push the expansion on
4292 * istk->expansion and return 1. Otherwise return 0.
4294 static int expand_mmacro(Token * tline)
4296 Token *startline = tline;
4297 Token *label = NULL;
4298 int dont_prepend = 0;
4299 Token **params, *t, *mtok, *tt;
4300 MMacro *m;
4301 Line *l, *ll;
4302 int i, nparam, *paramlen;
4303 const char *mname;
4305 t = tline;
4306 skip_white_(t);
4307 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4308 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4309 return 0;
4310 mtok = t;
4311 m = is_mmacro(t, &params);
4312 if (m) {
4313 mname = t->text;
4314 } else {
4315 Token *last;
4317 * We have an id which isn't a macro call. We'll assume
4318 * it might be a label; we'll also check to see if a
4319 * colon follows it. Then, if there's another id after
4320 * that lot, we'll check it again for macro-hood.
4322 label = last = t;
4323 t = t->next;
4324 if (tok_type_(t, TOK_WHITESPACE))
4325 last = t, t = t->next;
4326 if (tok_is_(t, ":")) {
4327 dont_prepend = 1;
4328 last = t, t = t->next;
4329 if (tok_type_(t, TOK_WHITESPACE))
4330 last = t, t = t->next;
4332 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4333 return 0;
4334 last->next = NULL;
4335 mname = t->text;
4336 tline = t;
4340 * Fix up the parameters: this involves stripping leading and
4341 * trailing whitespace, then stripping braces if they are
4342 * present.
4344 for (nparam = 0; params[nparam]; nparam++) ;
4345 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4347 for (i = 0; params[i]; i++) {
4348 int brace = false;
4349 int comma = (!m->plus || i < nparam - 1);
4351 t = params[i];
4352 skip_white_(t);
4353 if (tok_is_(t, "{"))
4354 t = t->next, brace = true, comma = false;
4355 params[i] = t;
4356 paramlen[i] = 0;
4357 while (t) {
4358 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4359 break; /* ... because we have hit a comma */
4360 if (comma && t->type == TOK_WHITESPACE
4361 && tok_is_(t->next, ","))
4362 break; /* ... or a space then a comma */
4363 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4364 break; /* ... or a brace */
4365 t = t->next;
4366 paramlen[i]++;
4371 * OK, we have a MMacro structure together with a set of
4372 * parameters. We must now go through the expansion and push
4373 * copies of each Line on to istk->expansion. Substitution of
4374 * parameter tokens and macro-local tokens doesn't get done
4375 * until the single-line macro substitution process; this is
4376 * because delaying them allows us to change the semantics
4377 * later through %rotate.
4379 * First, push an end marker on to istk->expansion, mark this
4380 * macro as in progress, and set up its invocation-specific
4381 * variables.
4383 ll = nasm_malloc(sizeof(Line));
4384 ll->next = istk->expansion;
4385 ll->finishes = m;
4386 ll->first = NULL;
4387 istk->expansion = ll;
4390 * Save the previous MMacro expansion in the case of
4391 * macro recursion
4393 if (m->max_depth && m->in_progress)
4394 push_mmacro(m);
4396 m->in_progress ++;
4397 m->params = params;
4398 m->iline = tline;
4399 m->nparam = nparam;
4400 m->rotate = 0;
4401 m->paramlen = paramlen;
4402 m->unique = unique++;
4403 m->lineno = 0;
4404 m->condcnt = 0;
4406 m->next_active = istk->mstk;
4407 istk->mstk = m;
4409 for (l = m->expansion; l; l = l->next) {
4410 Token **tail;
4412 ll = nasm_malloc(sizeof(Line));
4413 ll->finishes = NULL;
4414 ll->next = istk->expansion;
4415 istk->expansion = ll;
4416 tail = &ll->first;
4418 for (t = l->first; t; t = t->next) {
4419 Token *x = t;
4420 switch (t->type) {
4421 case TOK_PREPROC_Q:
4422 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4423 break;
4424 case TOK_PREPROC_QQ:
4425 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4426 break;
4427 case TOK_PREPROC_ID:
4428 if (t->text[1] == '0' && t->text[2] == '0') {
4429 dont_prepend = -1;
4430 x = label;
4431 if (!x)
4432 continue;
4434 /* fall through */
4435 default:
4436 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4437 break;
4439 tail = &tt->next;
4441 *tail = NULL;
4445 * If we had a label, push it on as the first line of
4446 * the macro expansion.
4448 if (label) {
4449 if (dont_prepend < 0)
4450 free_tlist(startline);
4451 else {
4452 ll = nasm_malloc(sizeof(Line));
4453 ll->finishes = NULL;
4454 ll->next = istk->expansion;
4455 istk->expansion = ll;
4456 ll->first = startline;
4457 if (!dont_prepend) {
4458 while (label->next)
4459 label = label->next;
4460 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4465 list->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4467 return 1;
4470 /* The function that actually does the error reporting */
4471 static void verror(int severity, const char *fmt, va_list arg)
4473 char buff[1024];
4475 vsnprintf(buff, sizeof(buff), fmt, arg);
4477 if (istk && istk->mstk && istk->mstk->name)
4478 nasm_error(severity, "(%s:%d) %s", istk->mstk->name,
4479 istk->mstk->lineno, buff);
4480 else
4481 nasm_error(severity, "%s", buff);
4485 * Since preprocessor always operate only on the line that didn't
4486 * arrived yet, we should always use ERR_OFFBY1.
4488 static void error(int severity, const char *fmt, ...)
4490 va_list arg;
4492 /* If we're in a dead branch of IF or something like it, ignore the error */
4493 if (istk && istk->conds && !emitting(istk->conds->state))
4494 return;
4496 va_start(arg, fmt);
4497 verror(severity, fmt, arg);
4498 va_end(arg);
4502 * Because %else etc are evaluated in the state context
4503 * of the previous branch, errors might get lost with error():
4504 * %if 0 ... %else trailing garbage ... %endif
4505 * So %else etc should report errors with this function.
4507 static void error_precond(int severity, const char *fmt, ...)
4509 va_list arg;
4511 /* Only ignore the error if it's really in a dead branch */
4512 if (istk && istk->conds && istk->conds->state == COND_NEVER)
4513 return;
4515 va_start(arg, fmt);
4516 verror(severity, fmt, arg);
4517 va_end(arg);
4520 static void
4521 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4523 Token *t;
4525 cstk = NULL;
4526 istk = nasm_malloc(sizeof(Include));
4527 istk->next = NULL;
4528 istk->conds = NULL;
4529 istk->expansion = NULL;
4530 istk->mstk = NULL;
4531 istk->fp = fopen(file, "r");
4532 istk->fname = NULL;
4533 src_set_fname(nasm_strdup(file));
4534 src_set_linnum(0);
4535 istk->lineinc = 1;
4536 if (!istk->fp)
4537 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4538 file);
4539 defining = NULL;
4540 nested_mac_count = 0;
4541 nested_rep_count = 0;
4542 init_macros();
4543 unique = 0;
4544 if (tasm_compatible_mode) {
4545 stdmacpos = nasm_stdmac;
4546 } else {
4547 stdmacpos = nasm_stdmac_after_tasm;
4549 any_extrastdmac = extrastdmac && *extrastdmac;
4550 do_predef = true;
4551 list = listgen;
4554 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4555 * The caller, however, will also pass in 3 for preprocess-only so
4556 * we can set __PASS__ accordingly.
4558 pass = apass > 2 ? 2 : apass;
4560 dephead = deptail = deplist;
4561 if (deplist) {
4562 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4563 sl->next = NULL;
4564 strcpy(sl->str, file);
4565 *deptail = sl;
4566 deptail = &sl->next;
4570 * Define the __PASS__ macro. This is defined here unlike
4571 * all the other builtins, because it is special -- it varies between
4572 * passes.
4574 t = nasm_malloc(sizeof(*t));
4575 t->next = NULL;
4576 make_tok_num(t, apass);
4577 t->a.mac = NULL;
4578 define_smacro(NULL, "__PASS__", true, 0, t);
4581 static char *pp_getline(void)
4583 char *line;
4584 Token *tline;
4586 while (1) {
4588 * Fetch a tokenized line, either from the macro-expansion
4589 * buffer or from the input file.
4591 tline = NULL;
4592 while (istk->expansion && istk->expansion->finishes) {
4593 Line *l = istk->expansion;
4594 if (!l->finishes->name && l->finishes->in_progress > 1) {
4595 Line *ll;
4598 * This is a macro-end marker for a macro with no
4599 * name, which means it's not really a macro at all
4600 * but a %rep block, and the `in_progress' field is
4601 * more than 1, meaning that we still need to
4602 * repeat. (1 means the natural last repetition; 0
4603 * means termination by %exitrep.) We have
4604 * therefore expanded up to the %endrep, and must
4605 * push the whole block on to the expansion buffer
4606 * again. We don't bother to remove the macro-end
4607 * marker: we'd only have to generate another one
4608 * if we did.
4610 l->finishes->in_progress--;
4611 for (l = l->finishes->expansion; l; l = l->next) {
4612 Token *t, *tt, **tail;
4614 ll = nasm_malloc(sizeof(Line));
4615 ll->next = istk->expansion;
4616 ll->finishes = NULL;
4617 ll->first = NULL;
4618 tail = &ll->first;
4620 for (t = l->first; t; t = t->next) {
4621 if (t->text || t->type == TOK_WHITESPACE) {
4622 tt = *tail =
4623 new_Token(NULL, t->type, t->text, 0);
4624 tail = &tt->next;
4628 istk->expansion = ll;
4630 } else {
4632 * Check whether a `%rep' was started and not ended
4633 * within this macro expansion. This can happen and
4634 * should be detected. It's a fatal error because
4635 * I'm too confused to work out how to recover
4636 * sensibly from it.
4638 if (defining) {
4639 if (defining->name)
4640 error(ERR_PANIC,
4641 "defining with name in expansion");
4642 else if (istk->mstk->name)
4643 error(ERR_FATAL,
4644 "`%%rep' without `%%endrep' within"
4645 " expansion of macro `%s'",
4646 istk->mstk->name);
4650 * FIXME: investigate the relationship at this point between
4651 * istk->mstk and l->finishes
4654 MMacro *m = istk->mstk;
4655 istk->mstk = m->next_active;
4656 if (m->name) {
4658 * This was a real macro call, not a %rep, and
4659 * therefore the parameter information needs to
4660 * be freed.
4662 if (m->prev) {
4663 pop_mmacro(m);
4664 l->finishes->in_progress --;
4665 } else {
4666 nasm_free(m->params);
4667 free_tlist(m->iline);
4668 nasm_free(m->paramlen);
4669 l->finishes->in_progress = 0;
4671 } else
4672 free_mmacro(m);
4674 istk->expansion = l->next;
4675 nasm_free(l);
4676 list->downlevel(LIST_MACRO);
4679 while (1) { /* until we get a line we can use */
4681 if (istk->expansion) { /* from a macro expansion */
4682 char *p;
4683 Line *l = istk->expansion;
4684 if (istk->mstk)
4685 istk->mstk->lineno++;
4686 tline = l->first;
4687 istk->expansion = l->next;
4688 nasm_free(l);
4689 p = detoken(tline, false);
4690 list->line(LIST_MACRO, p);
4691 nasm_free(p);
4692 break;
4694 line = read_line();
4695 if (line) { /* from the current input file */
4696 line = prepreproc(line);
4697 tline = tokenize(line);
4698 nasm_free(line);
4699 break;
4702 * The current file has ended; work down the istk
4705 Include *i = istk;
4706 fclose(i->fp);
4707 if (i->conds)
4708 error(ERR_FATAL,
4709 "expected `%%endif' before end of file");
4710 /* only set line and file name if there's a next node */
4711 if (i->next) {
4712 src_set_linnum(i->lineno);
4713 nasm_free(src_set_fname(i->fname));
4715 istk = i->next;
4716 list->downlevel(LIST_INCLUDE);
4717 nasm_free(i);
4718 if (!istk)
4719 return NULL;
4720 if (istk->expansion && istk->expansion->finishes)
4721 break;
4726 * We must expand MMacro parameters and MMacro-local labels
4727 * _before_ we plunge into directive processing, to cope
4728 * with things like `%define something %1' such as STRUC
4729 * uses. Unless we're _defining_ a MMacro, in which case
4730 * those tokens should be left alone to go into the
4731 * definition; and unless we're in a non-emitting
4732 * condition, in which case we don't want to meddle with
4733 * anything.
4735 if (!defining && !(istk->conds && !emitting(istk->conds->state))
4736 && !(istk->mstk && !istk->mstk->in_progress)) {
4737 tline = expand_mmac_params(tline);
4741 * Check the line to see if it's a preprocessor directive.
4743 if (do_directive(tline) == DIRECTIVE_FOUND) {
4744 continue;
4745 } else if (defining) {
4747 * We're defining a multi-line macro. We emit nothing
4748 * at all, and just
4749 * shove the tokenized line on to the macro definition.
4751 Line *l = nasm_malloc(sizeof(Line));
4752 l->next = defining->expansion;
4753 l->first = tline;
4754 l->finishes = NULL;
4755 defining->expansion = l;
4756 continue;
4757 } else if (istk->conds && !emitting(istk->conds->state)) {
4759 * We're in a non-emitting branch of a condition block.
4760 * Emit nothing at all, not even a blank line: when we
4761 * emerge from the condition we'll give a line-number
4762 * directive so we keep our place correctly.
4764 free_tlist(tline);
4765 continue;
4766 } else if (istk->mstk && !istk->mstk->in_progress) {
4768 * We're in a %rep block which has been terminated, so
4769 * we're walking through to the %endrep without
4770 * emitting anything. Emit nothing at all, not even a
4771 * blank line: when we emerge from the %rep block we'll
4772 * give a line-number directive so we keep our place
4773 * correctly.
4775 free_tlist(tline);
4776 continue;
4777 } else {
4778 tline = expand_smacro(tline);
4779 if (!expand_mmacro(tline)) {
4781 * De-tokenize the line again, and emit it.
4783 line = detoken(tline, true);
4784 free_tlist(tline);
4785 break;
4786 } else {
4787 continue; /* expand_mmacro calls free_tlist */
4792 return line;
4795 static void pp_cleanup(int pass)
4797 if (defining) {
4798 if (defining->name) {
4799 error(ERR_NONFATAL,
4800 "end of file while still defining macro `%s'",
4801 defining->name);
4802 } else {
4803 error(ERR_NONFATAL, "end of file while still in %%rep");
4806 free_mmacro(defining);
4808 while (cstk)
4809 ctx_pop();
4810 free_macros();
4811 while (istk) {
4812 Include *i = istk;
4813 istk = istk->next;
4814 fclose(i->fp);
4815 nasm_free(i->fname);
4816 nasm_free(i);
4818 while (cstk)
4819 ctx_pop();
4820 nasm_free(src_set_fname(NULL));
4821 if (pass == 0) {
4822 IncPath *i;
4823 free_llist(predef);
4824 delete_Blocks();
4825 while ((i = ipath)) {
4826 ipath = i->next;
4827 if (i->path)
4828 nasm_free(i->path);
4829 nasm_free(i);
4834 void pp_include_path(char *path)
4836 IncPath *i;
4838 i = nasm_malloc(sizeof(IncPath));
4839 i->path = path ? nasm_strdup(path) : NULL;
4840 i->next = NULL;
4842 if (ipath) {
4843 IncPath *j = ipath;
4844 while (j->next)
4845 j = j->next;
4846 j->next = i;
4847 } else {
4848 ipath = i;
4852 void pp_pre_include(char *fname)
4854 Token *inc, *space, *name;
4855 Line *l;
4857 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
4858 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
4859 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
4861 l = nasm_malloc(sizeof(Line));
4862 l->next = predef;
4863 l->first = inc;
4864 l->finishes = NULL;
4865 predef = l;
4868 void pp_pre_define(char *definition)
4870 Token *def, *space;
4871 Line *l;
4872 char *equals;
4874 equals = strchr(definition, '=');
4875 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4876 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
4877 if (equals)
4878 *equals = ' ';
4879 space->next = tokenize(definition);
4880 if (equals)
4881 *equals = '=';
4883 l = nasm_malloc(sizeof(Line));
4884 l->next = predef;
4885 l->first = def;
4886 l->finishes = NULL;
4887 predef = l;
4890 void pp_pre_undefine(char *definition)
4892 Token *def, *space;
4893 Line *l;
4895 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
4896 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
4897 space->next = tokenize(definition);
4899 l = nasm_malloc(sizeof(Line));
4900 l->next = predef;
4901 l->first = def;
4902 l->finishes = NULL;
4903 predef = l;
4907 * Added by Keith Kanios:
4909 * This function is used to assist with "runtime" preprocessor
4910 * directives. (e.g. pp_runtime("%define __BITS__ 64");)
4912 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
4913 * PASS A VALID STRING TO THIS FUNCTION!!!!!
4916 void pp_runtime(char *definition)
4918 Token *def;
4920 def = tokenize(definition);
4921 if (do_directive(def) == NO_DIRECTIVE_FOUND)
4922 free_tlist(def);
4926 void pp_extra_stdmac(macros_t *macros)
4928 extrastdmac = macros;
4931 static void make_tok_num(Token * tok, int64_t val)
4933 char numbuf[20];
4934 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
4935 tok->text = nasm_strdup(numbuf);
4936 tok->type = TOK_NUMBER;
4939 Preproc nasmpp = {
4940 pp_reset,
4941 pp_getline,
4942 pp_cleanup