preproc.c: completed deprecation of MMacro structure
[nasm.git] / preproc.c
blob298d8cebac2109866cf9a3123fafeab2dbb86de2
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2010 The NASM Authors - All Rights Reserved
4 * See the file AUTHORS included with the NASM distribution for
5 * the specific copyright holders.
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following
9 * conditions are met:
11 * * Redistributions of source code must retain the above copyright
12 * notice, this list of conditions and the following disclaimer.
13 * * Redistributions in binary form must reproduce the above
14 * copyright notice, this list of conditions and the following
15 * disclaimer in the documentation and/or other materials provided
16 * with the distribution.
18 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND
19 * CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
20 * INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
21 * MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
22 * DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR
23 * CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
24 * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
25 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
26 * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
27 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
28 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
29 * OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
30 * EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32 * ----------------------------------------------------------------------- */
35 * preproc.c macro preprocessor for the Netwide Assembler
38 /* Typical flow of text through preproc
40 * pp_getline gets tokenized lines, either
42 * from a macro expansion
44 * or
45 * {
46 * read_line gets raw text from stdmacpos, or predef, or current input file
47 * tokenize converts to tokens
48 * }
50 * expand_mmac_params is used to expand %1 etc., unless a macro is being
51 * defined or a false conditional is being processed
52 * (%0, %1, %+1, %-1, %%foo
54 * do_directive checks for directives
56 * expand_smacro is used to expand single line macros
58 * expand_mmacro is used to expand multi-line macros
60 * detoken is used to convert the line back to text
63 #include "compiler.h"
65 #include <stdio.h>
66 #include <stdarg.h>
67 #include <stdlib.h>
68 #include <stddef.h>
69 #include <string.h>
70 #include <ctype.h>
71 #include <limits.h>
72 #include <inttypes.h>
74 #include "nasm.h"
75 #include "nasmlib.h"
76 #include "preproc.h"
77 #include "hashtbl.h"
78 #include "quote.h"
79 #include "stdscan.h"
80 #include "eval.h"
81 #include "tokens.h"
82 #include "tables.h"
84 typedef struct SMacro SMacro;
85 typedef struct ExpDef ExpDef;
86 typedef struct ExpInv ExpInv;
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 * The context stack is composed of a linked list of these.
119 struct Context {
120 Context *next;
121 char *name;
122 struct hash_table localmac;
123 uint32_t number;
127 * This is the internal form which we break input lines up into.
128 * Typically stored in linked lists.
130 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
131 * necessarily used as-is, but is intended to denote the number of
132 * the substituted parameter. So in the definition
134 * %define a(x,y) ( (x) & ~(y) )
136 * the token representing `x' will have its type changed to
137 * TOK_SMAC_PARAM, but the one representing `y' will be
138 * TOK_SMAC_PARAM+1.
140 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
141 * which doesn't need quotes around it. Used in the pre-include
142 * mechanism as an alternative to trying to find a sensible type of
143 * quote to use on the filename we were passed.
145 enum pp_token_type {
146 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
147 TOK_PREPROC_ID, TOK_STRING,
148 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
149 TOK_INTERNAL_STRING,
150 TOK_PREPROC_Q, TOK_PREPROC_QQ,
151 TOK_PASTE, /* %+ */
152 TOK_INDIRECT, /* %[...] */
153 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
154 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
157 struct Token {
158 Token *next;
159 char *text;
160 union {
161 SMacro *mac; /* associated macro for TOK_SMAC_END */
162 size_t len; /* scratch length field */
163 } a; /* Auxiliary data */
164 enum pp_token_type type;
168 * Expansion definitions are stored as a linked list of
169 * these, which is essentially a container to allow several linked
170 * lists of Tokens.
172 * Note that in this module, linked lists are treated as stacks
173 * wherever possible. For this reason, Lines are _pushed_ on to the
174 * `last' field in ExpDef structures, so that the linked list,
175 * if walked, would emit the expansion lines in the proper order.
177 struct Line {
178 Line *next;
179 Token *first;
183 * Expansion Types
185 enum pp_exp_type {
186 EXP_NONE = 0, EXP_PREDEF,
187 EXP_MMACRO, EXP_REP,
188 EXP_IF,
189 EXP_MAX = INT_MAX /* Keep compiler from reducing the range */
193 * Store the definition of an expansion, in which is any
194 * preprocessor directive that has an ending pair.
196 * This design allows for arbitrary expansion/recursion depth,
197 * upto the DEADMAN_LIMIT.
199 * The `next' field is used for storing ExpDef in hash tables; the
200 * `prev' field is for the global `expansions` linked-list.
202 struct ExpDef {
203 ExpDef *prev; /* previous definition */
204 ExpDef *next; /* next in hash table */
205 enum pp_exp_type type; /* expansion type */
206 char *name;
207 int nparam_min, nparam_max;
208 bool casesense;
209 bool plus; /* is the last parameter greedy? */
210 bool nolist; /* is this expansion listing-inhibited? */
211 Token *dlist; /* all defaults as one list */
212 Token **defaults; /* parameter default pointers */
213 int ndefs; /* number of default parameters */
215 Line *label;
216 Line *line;
217 Line *last;
219 uint32_t def_depth; /* current number of definition pairs deep */
220 uint32_t cur_depth; /* current number of expansions */
221 uint32_t max_depth; /* maximum number of expansions allowed */
223 int state; /* condition state */
224 bool ignoring; /* ignoring definition lines */
228 * Store the invocation of an expansion.
230 * The `prev' field is for the `istk->expansion` linked-list.
232 * When an expansion is being expanded, `params', `iline', `nparam',
233 * `paramlen', `rotate' and `unique' are local to the invocation.
235 struct ExpInv {
236 ExpInv *prev; /* previous invocation */
237 enum pp_exp_type type; /* expansion type */
238 ExpDef *def; /* pointer to expansion definition */
239 Line *label; /* pointer to label */
240 char *label_text; /* pointer to label text */
241 Line *current; /* pointer to current line in invocation */
243 Token **params; /* actual parameters */
244 Token *iline; /* invocation line */
245 unsigned int nparam, rotate;
246 int *paramlen;
248 uint64_t unique;
249 bool emitting;
250 int lineno; /* current line number in expansion */
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 ExpInv *expansion;
262 char *fname;
263 int lineno, lineinc;
267 * Include search path. This is simply a list of strings which get
268 * prepended, in turn, to the name of an include file, in an
269 * attempt to find the file if it's not in the current directory.
271 struct IncPath {
272 IncPath *next;
273 char *path;
277 * Conditional assembly: we maintain a separate stack of these for
278 * each level of file inclusion. (The only reason we keep the
279 * stacks separate is to ensure that a stray `%endif' in a file
280 * included from within the true branch of a `%if' won't terminate
281 * it and cause confusion: instead, rightly, it'll cause an error.)
283 enum {
285 * These states are for use just after %if or %elif: IF_TRUE
286 * means the condition has evaluated to truth so we are
287 * currently emitting, whereas IF_FALSE means we are not
288 * currently emitting but will start doing so if a %else comes
289 * up. In these states, all directives are admissible: %elif,
290 * %else and %endif. (And of course %if.)
292 COND_IF_TRUE, COND_IF_FALSE,
294 * These states come up after a %else: ELSE_TRUE means we're
295 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
296 * any %elif or %else will cause an error.
298 COND_ELSE_TRUE, COND_ELSE_FALSE,
300 * These states mean that we're not emitting now, and also that
301 * nothing until %endif will be emitted at all. COND_DONE is
302 * used when we've had our moment of emission
303 * and have now started seeing %elifs. COND_NEVER is used when
304 * the condition construct in question is contained within a
305 * non-emitting branch of a larger condition construct,
306 * or if there is an error.
308 COND_DONE, COND_NEVER
310 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
313 * These defines are used as the possible return values for do_directive
315 #define NO_DIRECTIVE_FOUND 0
316 #define DIRECTIVE_FOUND 1
319 * This define sets the upper limit for smacro and expansions
321 #define DEADMAN_LIMIT (1 << 20)
324 * Condition codes. Note that we use c_ prefix not C_ because C_ is
325 * used in nasm.h for the "real" condition codes. At _this_ level,
326 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
327 * ones, so we need a different enum...
329 static const char * const conditions[] = {
330 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
331 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
332 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
334 enum pp_conds {
335 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
336 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
337 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
338 c_none = -1
340 static const enum pp_conds inverse_ccs[] = {
341 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
342 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,
343 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
346 /* For TASM compatibility we need to be able to recognise TASM compatible
347 * conditional compilation directives. Using the NASM pre-processor does
348 * not work, so we look for them specifically from the following list and
349 * then jam in the equivalent NASM directive into the input stream.
352 enum {
353 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
354 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
357 static const char * const tasm_directives[] = {
358 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
359 "ifndef", "include", "local"
362 static int StackSize = 4;
363 static char *StackPointer = "ebp";
364 static int ArgOffset = 8;
365 static int LocalOffset = 0;
367 static Context *cstk;
368 static Include *istk;
369 static IncPath *ipath = NULL;
371 static int pass; /* HACK: pass 0 = generate dependencies only */
372 static StrList **dephead, **deptail; /* Dependency list */
374 static uint64_t unique; /* unique identifier numbers */
376 static Line *predef = NULL;
377 static bool do_predef;
379 static ListGen *list;
382 * The current set of expansion definitions we have defined.
384 static struct hash_table expdefs;
387 * The current set of single-line macros we have defined.
389 static struct hash_table smacros;
392 * Linked List of all active expansion definitions
394 struct ExpDef *expansions = NULL;
397 * The expansion we are currently defining
399 static ExpDef *defining = NULL;
401 static uint64_t nested_mac_count;
402 static uint64_t nested_rep_count;
405 * The number of macro parameters to allocate space for at a time.
407 #define PARAM_DELTA 16
410 * The standard macro set: defined in macros.c in the array nasm_stdmac.
411 * This gives our position in the macro set, when we're processing it.
413 static macros_t *stdmacpos;
416 * The extra standard macros that come from the object format, if
417 * any.
419 static macros_t *extrastdmac = NULL;
420 static bool any_extrastdmac;
423 * Tokens are allocated in blocks to improve speed
425 #define TOKEN_BLOCKSIZE 4096
426 static Token *freeTokens = NULL;
427 struct Blocks {
428 Blocks *next;
429 void *chunk;
432 static Blocks blocks = { NULL, NULL };
435 * Forward declarations.
437 static Token *expand_mmac_params(Token * tline);
438 static Token *expand_smacro(Token * tline);
439 static Token *expand_id(Token * tline);
440 static Context *get_ctx(const char *name, const char **namep,
441 bool all_contexts);
442 static void make_tok_num(Token * tok, int64_t val);
443 static void error(int severity, const char *fmt, ...);
444 static void error_precond(int severity, const char *fmt, ...);
445 static void *new_Block(size_t size);
446 static void delete_Blocks(void);
447 static Token *new_Token(Token * next, enum pp_token_type type,
448 const char *text, int txtlen);
449 static Token *copy_Token(Token * tline);
450 static Token *delete_Token(Token * t);
451 static Line *new_Line(void);
452 static ExpDef *new_ExpDef(void);
453 static ExpInv *new_ExpInv(void);
456 * Macros for safe checking of token pointers, avoid *(NULL)
458 #define tok_type_(x,t) ((x) && (x)->type == (t))
459 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
460 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
461 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
464 * nasm_unquote with error if the string contains NUL characters.
465 * If the string contains NUL characters, issue an error and return
466 * the C len, i.e. truncate at the NUL.
468 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
470 size_t len = nasm_unquote(qstr, NULL);
471 size_t clen = strlen(qstr);
473 if (len != clen)
474 error(ERR_NONFATAL, "NUL character in `%s' directive",
475 pp_directives[directive]);
477 return clen;
481 * Handle TASM specific directives, which do not contain a % in
482 * front of them. We do it here because I could not find any other
483 * place to do it for the moment, and it is a hack (ideally it would
484 * be nice to be able to use the NASM pre-processor to do it).
486 static char *check_tasm_directive(char *line)
488 int32_t i, j, k, m, len;
489 char *p, *q, *oldline, oldchar;
491 p = nasm_skip_spaces(line);
493 /* Binary search for the directive name */
494 i = -1;
495 j = ARRAY_SIZE(tasm_directives);
496 q = nasm_skip_word(p);
497 len = q - p;
498 if (len) {
499 oldchar = p[len];
500 p[len] = 0;
501 while (j - i > 1) {
502 k = (j + i) / 2;
503 m = nasm_stricmp(p, tasm_directives[k]);
504 if (m == 0) {
505 /* We have found a directive, so jam a % in front of it
506 * so that NASM will then recognise it as one if it's own.
508 p[len] = oldchar;
509 len = strlen(p);
510 oldline = line;
511 line = nasm_malloc(len + 2);
512 line[0] = '%';
513 if (k == TM_IFDIFI) {
515 * NASM does not recognise IFDIFI, so we convert
516 * it to %if 0. This is not used in NASM
517 * compatible code, but does need to parse for the
518 * TASM macro package.
520 strcpy(line + 1, "if 0");
521 } else {
522 memcpy(line + 1, p, len + 1);
524 nasm_free(oldline);
525 return line;
526 } else if (m < 0) {
527 j = k;
528 } else
529 i = k;
531 p[len] = oldchar;
533 return line;
537 * The pre-preprocessing stage... This function translates line
538 * number indications as they emerge from GNU cpp (`# lineno "file"
539 * flags') into NASM preprocessor line number indications (`%line
540 * lineno file').
542 static char *prepreproc(char *line)
544 int lineno, fnlen;
545 char *fname, *oldline;
547 if (line[0] == '#' && line[1] == ' ') {
548 oldline = line;
549 fname = oldline + 2;
550 lineno = atoi(fname);
551 fname += strspn(fname, "0123456789 ");
552 if (*fname == '"')
553 fname++;
554 fnlen = strcspn(fname, "\"");
555 line = nasm_malloc(20 + fnlen);
556 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
557 nasm_free(oldline);
559 if (tasm_compatible_mode)
560 return check_tasm_directive(line);
561 return line;
565 * Free a linked list of tokens.
567 static void free_tlist(Token * list)
569 while (list)
570 list = delete_Token(list);
574 * Free a linked list of lines.
576 static void free_llist(Line * list)
578 Line *l, *tmp;
579 list_for_each_safe(l, tmp, list) {
580 free_tlist(l->first);
581 nasm_free(l);
586 * Free an ExpDef
588 static void free_expdef(ExpDef * ed)
590 nasm_free(ed->name);
591 free_tlist(ed->dlist);
592 nasm_free(ed->defaults);
593 free_llist(ed->line);
594 nasm_free(ed);
598 * Free all currently defined macros, and free the hash tables
600 static void free_smacro_table(struct hash_table *smt)
602 SMacro *s, *tmp;
603 const char *key;
604 struct hash_tbl_node *it = NULL;
606 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
607 nasm_free((void *)key);
608 list_for_each_safe(s, tmp, s) {
609 nasm_free(s->name);
610 free_tlist(s->expansion);
611 nasm_free(s);
614 hash_free(smt);
617 static void free_expdef_table(struct hash_table *edt)
619 ExpDef *ed, *tmp;
620 const char *key;
621 struct hash_tbl_node *it = NULL;
623 it = NULL;
624 while ((ed = hash_iterate(edt, &it, &key)) != NULL) {
625 nasm_free((void *)key);
626 list_for_each_safe(ed ,tmp, ed)
627 free_expdef(ed);
629 hash_free(edt);
632 static void free_macros(void)
634 free_smacro_table(&smacros);
635 free_expdef_table(&expdefs);
639 * Initialize the hash tables
641 static void init_macros(void)
643 hash_init(&smacros, HASH_LARGE);
644 hash_init(&expdefs, HASH_LARGE);
648 * Pop the context stack.
650 static void ctx_pop(void)
652 Context *c = cstk;
654 cstk = cstk->next;
655 free_smacro_table(&c->localmac);
656 nasm_free(c->name);
657 nasm_free(c);
661 * Search for a key in the hash index; adding it if necessary
662 * (in which case we initialize the data pointer to NULL.)
664 static void **
665 hash_findi_add(struct hash_table *hash, const char *str)
667 struct hash_insert hi;
668 void **r;
669 char *strx;
671 r = hash_findi(hash, str, &hi);
672 if (r)
673 return r;
675 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
676 return hash_add(&hi, strx, NULL);
680 * Like hash_findi, but returns the data element rather than a pointer
681 * to it. Used only when not adding a new element, hence no third
682 * argument.
684 static void *
685 hash_findix(struct hash_table *hash, const char *str)
687 void **p;
689 p = hash_findi(hash, str, NULL);
690 return p ? *p : NULL;
694 * read line from standard macros set,
695 * if there no more left -- return NULL
697 static char *line_from_stdmac(void)
699 unsigned char c;
700 const unsigned char *p = stdmacpos;
701 char *line, *q;
702 size_t len = 0;
704 if (!stdmacpos)
705 return NULL;
707 while ((c = *p++)) {
708 if (c >= 0x80)
709 len += pp_directives_len[c - 0x80] + 1;
710 else
711 len++;
714 line = nasm_malloc(len + 1);
715 q = line;
716 while ((c = *stdmacpos++)) {
717 if (c >= 0x80) {
718 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
719 q += pp_directives_len[c - 0x80];
720 *q++ = ' ';
721 } else {
722 *q++ = c;
725 stdmacpos = p;
726 *q = '\0';
728 if (!*stdmacpos) {
729 /* This was the last of the standard macro chain... */
730 stdmacpos = NULL;
731 if (any_extrastdmac) {
732 stdmacpos = extrastdmac;
733 any_extrastdmac = false;
734 } else if (do_predef) {
735 ExpInv *ei;
736 Line *pd, *l;
737 Token *head, **tail, *t;
740 * Nasty hack: here we push the contents of
741 * `predef' on to the top-level expansion stack,
742 * since this is the most convenient way to
743 * implement the pre-include and pre-define
744 * features.
746 list_for_each(pd, predef) {
747 head = NULL;
748 tail = &head;
749 list_for_each(t, pd->first) {
750 *tail = new_Token(NULL, t->type, t->text, 0);
751 tail = &(*tail)->next;
754 l = new_Line();
755 l->first = head;
756 ei = new_ExpInv();
757 ei->type = EXP_PREDEF;
758 ei->current = l;
759 ei->emitting = true;
760 ei->prev = istk->expansion;
761 istk->expansion = ei;
763 do_predef = false;
767 return line;
770 #define BUF_DELTA 512
772 * Read a line from the top file in istk, handling multiple CR/LFs
773 * at the end of the line read, and handling spurious ^Zs. Will
774 * return lines from the standard macro set if this has not already
775 * been done.
777 static char *read_line(void)
779 char *buffer, *p, *q;
780 int bufsize, continued_count;
783 * standart macros set (predefined) goes first
785 p = line_from_stdmac();
786 if (p)
787 return p;
790 * regular read from a file
792 bufsize = BUF_DELTA;
793 buffer = nasm_malloc(BUF_DELTA);
794 p = buffer;
795 continued_count = 0;
796 while (1) {
797 q = fgets(p, bufsize - (p - buffer), istk->fp);
798 if (!q)
799 break;
800 p += strlen(p);
801 if (p > buffer && p[-1] == '\n') {
803 * Convert backslash-CRLF line continuation sequences into
804 * nothing at all (for DOS and Windows)
806 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
807 p -= 3;
808 *p = 0;
809 continued_count++;
812 * Also convert backslash-LF line continuation sequences into
813 * nothing at all (for Unix)
815 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
816 p -= 2;
817 *p = 0;
818 continued_count++;
819 } else {
820 break;
823 if (p - buffer > bufsize - 10) {
824 int32_t offset = p - buffer;
825 bufsize += BUF_DELTA;
826 buffer = nasm_realloc(buffer, bufsize);
827 p = buffer + offset; /* prevent stale-pointer problems */
831 if (!q && p == buffer) {
832 nasm_free(buffer);
833 return NULL;
836 src_set_linnum(src_get_linnum() + istk->lineinc +
837 (continued_count * istk->lineinc));
840 * Play safe: remove CRs as well as LFs, if any of either are
841 * present at the end of the line.
843 while (--p >= buffer && (*p == '\n' || *p == '\r'))
844 *p = '\0';
847 * Handle spurious ^Z, which may be inserted into source files
848 * by some file transfer utilities.
850 buffer[strcspn(buffer, "\032")] = '\0';
852 list->line(LIST_READ, buffer);
854 return buffer;
858 * Tokenize a line of text. This is a very simple process since we
859 * don't need to parse the value out of e.g. numeric tokens: we
860 * simply split one string into many.
862 static Token *tokenize(char *line)
864 char c, *p = line;
865 enum pp_token_type type;
866 Token *list = NULL;
867 Token *t, **tail = &list;
869 while (*line) {
870 p = line;
871 if (*p == '%') {
872 p++;
873 if (*p == '+' && !nasm_isdigit(p[1])) {
874 p++;
875 type = TOK_PASTE;
876 } else if (nasm_isdigit(*p) ||
877 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
878 do {
879 p++;
881 while (nasm_isdigit(*p));
882 type = TOK_PREPROC_ID;
883 } else if (*p == '{') {
884 p++;
885 while (*p && *p != '}') {
886 p[-1] = *p;
887 p++;
889 p[-1] = '\0';
890 if (*p)
891 p++;
892 type = TOK_PREPROC_ID;
893 } else if (*p == '[') {
894 int lvl = 1;
895 line += 2; /* Skip the leading %[ */
896 p++;
897 while (lvl && (c = *p++)) {
898 switch (c) {
899 case ']':
900 lvl--;
901 break;
902 case '%':
903 if (*p == '[')
904 lvl++;
905 break;
906 case '\'':
907 case '\"':
908 case '`':
909 p = nasm_skip_string(p - 1) + 1;
910 break;
911 default:
912 break;
915 p--;
916 if (*p)
917 *p++ = '\0';
918 if (lvl)
919 error(ERR_NONFATAL, "unterminated %[ construct");
920 type = TOK_INDIRECT;
921 } else if (*p == '?') {
922 type = TOK_PREPROC_Q; /* %? */
923 p++;
924 if (*p == '?') {
925 type = TOK_PREPROC_QQ; /* %?? */
926 p++;
928 } else if (*p == '!') {
929 type = TOK_PREPROC_ID;
930 p++;
931 if (isidchar(*p)) {
932 do {
933 p++;
935 while (isidchar(*p));
936 } else if (*p == '\'' || *p == '\"' || *p == '`') {
937 p = nasm_skip_string(p);
938 if (*p)
939 p++;
940 else
941 error(ERR_NONFATAL|ERR_PASS1, "unterminated %! string");
942 } else {
943 /* %! without string or identifier */
944 type = TOK_OTHER; /* Legacy behavior... */
946 } else if (isidchar(*p) ||
947 ((*p == '!' || *p == '%' || *p == '$') &&
948 isidchar(p[1]))) {
949 do {
950 p++;
952 while (isidchar(*p));
953 type = TOK_PREPROC_ID;
954 } else {
955 type = TOK_OTHER;
956 if (*p == '%')
957 p++;
959 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
960 type = TOK_ID;
961 p++;
962 while (*p && isidchar(*p))
963 p++;
964 } else if (*p == '\'' || *p == '"' || *p == '`') {
966 * A string token.
968 type = TOK_STRING;
969 p = nasm_skip_string(p);
971 if (*p) {
972 p++;
973 } else {
974 error(ERR_WARNING|ERR_PASS1, "unterminated string");
975 /* Handling unterminated strings by UNV */
976 /* type = -1; */
978 } else if (p[0] == '$' && p[1] == '$') {
979 type = TOK_OTHER; /* TOKEN_BASE */
980 p += 2;
981 } else if (isnumstart(*p)) {
982 bool is_hex = false;
983 bool is_float = false;
984 bool has_e = false;
985 char c, *r;
988 * A numeric token.
991 if (*p == '$') {
992 p++;
993 is_hex = true;
996 for (;;) {
997 c = *p++;
999 if (!is_hex && (c == 'e' || c == 'E')) {
1000 has_e = true;
1001 if (*p == '+' || *p == '-') {
1003 * e can only be followed by +/- if it is either a
1004 * prefixed hex number or a floating-point number
1006 p++;
1007 is_float = true;
1009 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1010 is_hex = true;
1011 } else if (c == 'P' || c == 'p') {
1012 is_float = true;
1013 if (*p == '+' || *p == '-')
1014 p++;
1015 } else if (isnumchar(c) || c == '_')
1016 ; /* just advance */
1017 else if (c == '.') {
1019 * we need to deal with consequences of the legacy
1020 * parser, like "1.nolist" being two tokens
1021 * (TOK_NUMBER, TOK_ID) here; at least give it
1022 * a shot for now. In the future, we probably need
1023 * a flex-based scanner with proper pattern matching
1024 * to do it as well as it can be done. Nothing in
1025 * the world is going to help the person who wants
1026 * 0x123.p16 interpreted as two tokens, though.
1028 r = p;
1029 while (*r == '_')
1030 r++;
1032 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1033 (!is_hex && (*r == 'e' || *r == 'E')) ||
1034 (*r == 'p' || *r == 'P')) {
1035 p = r;
1036 is_float = true;
1037 } else
1038 break; /* Terminate the token */
1039 } else
1040 break;
1042 p--; /* Point to first character beyond number */
1044 if (p == line+1 && *line == '$') {
1045 type = TOK_OTHER; /* TOKEN_HERE */
1046 } else {
1047 if (has_e && !is_hex) {
1048 /* 1e13 is floating-point, but 1e13h is not */
1049 is_float = true;
1052 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1054 } else if (nasm_isspace(*p)) {
1055 type = TOK_WHITESPACE;
1056 p = nasm_skip_spaces(p);
1058 * Whitespace just before end-of-line is discarded by
1059 * pretending it's a comment; whitespace just before a
1060 * comment gets lumped into the comment.
1062 if (!*p || *p == ';') {
1063 type = TOK_COMMENT;
1064 while (*p)
1065 p++;
1067 } else if (*p == ';') {
1068 type = TOK_COMMENT;
1069 while (*p)
1070 p++;
1071 } else {
1073 * Anything else is an operator of some kind. We check
1074 * for all the double-character operators (>>, <<, //,
1075 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1076 * else is a single-character operator.
1078 type = TOK_OTHER;
1079 if ((p[0] == '>' && p[1] == '>') ||
1080 (p[0] == '<' && p[1] == '<') ||
1081 (p[0] == '/' && p[1] == '/') ||
1082 (p[0] == '<' && p[1] == '=') ||
1083 (p[0] == '>' && p[1] == '=') ||
1084 (p[0] == '=' && p[1] == '=') ||
1085 (p[0] == '!' && p[1] == '=') ||
1086 (p[0] == '<' && p[1] == '>') ||
1087 (p[0] == '&' && p[1] == '&') ||
1088 (p[0] == '|' && p[1] == '|') ||
1089 (p[0] == '^' && p[1] == '^')) {
1090 p++;
1092 p++;
1095 /* Handling unterminated string by UNV */
1096 /*if (type == -1)
1098 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1099 t->text[p-line] = *line;
1100 tail = &t->next;
1102 else */
1103 if (type != TOK_COMMENT) {
1104 *tail = t = new_Token(NULL, type, line, p - line);
1105 tail = &t->next;
1107 line = p;
1109 return list;
1113 * this function allocates a new managed block of memory and
1114 * returns a pointer to the block. The managed blocks are
1115 * deleted only all at once by the delete_Blocks function.
1117 static void *new_Block(size_t size)
1119 Blocks *b = &blocks;
1121 /* first, get to the end of the linked list */
1122 while (b->next)
1123 b = b->next;
1124 /* now allocate the requested chunk */
1125 b->chunk = nasm_malloc(size);
1127 /* now allocate a new block for the next request */
1128 b->next = nasm_malloc(sizeof(Blocks));
1129 /* and initialize the contents of the new block */
1130 b->next->next = NULL;
1131 b->next->chunk = NULL;
1132 return b->chunk;
1136 * this function deletes all managed blocks of memory
1138 static void delete_Blocks(void)
1140 Blocks *a, *b = &blocks;
1143 * keep in mind that the first block, pointed to by blocks
1144 * is a static and not dynamically allocated, so we don't
1145 * free it.
1147 while (b) {
1148 if (b->chunk)
1149 nasm_free(b->chunk);
1150 a = b;
1151 b = b->next;
1152 if (a != &blocks)
1153 nasm_free(a);
1158 * this function creates a new Token and passes a pointer to it
1159 * back to the caller. It sets the type and text elements, and
1160 * also the a.mac and next elements to NULL.
1162 static Token *new_Token(Token * next, enum pp_token_type type,
1163 const char *text, int txtlen)
1165 Token *t;
1166 int i;
1168 if (!freeTokens) {
1169 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1170 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1171 freeTokens[i].next = &freeTokens[i + 1];
1172 freeTokens[i].next = NULL;
1174 t = freeTokens;
1175 freeTokens = t->next;
1176 t->next = next;
1177 t->a.mac = NULL;
1178 t->type = type;
1179 if (type == TOK_WHITESPACE || !text) {
1180 t->text = NULL;
1181 } else {
1182 if (txtlen == 0)
1183 txtlen = strlen(text);
1184 t->text = nasm_malloc(txtlen+1);
1185 memcpy(t->text, text, txtlen);
1186 t->text[txtlen] = '\0';
1188 return t;
1191 static Token *copy_Token(Token * tline)
1193 Token *t, *tt, *first = NULL, *prev = NULL;
1194 int i;
1195 for (tt = tline; tt != NULL; tt = tt->next) {
1196 if (!freeTokens) {
1197 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1198 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1199 freeTokens[i].next = &freeTokens[i + 1];
1200 freeTokens[i].next = NULL;
1202 t = freeTokens;
1203 freeTokens = t->next;
1204 t->next = NULL;
1205 t->text = ((tt->text != NULL) ? strdup(tt->text) : NULL);
1206 t->a.mac = tt->a.mac;
1207 t->a.len = tt->a.len;
1208 t->type = tt->type;
1209 if (prev != NULL) {
1210 prev->next = t;
1211 } else {
1212 first = t;
1214 prev = t;
1216 return first;
1219 static Token *delete_Token(Token * t)
1221 Token *next = t->next;
1222 nasm_free(t->text);
1223 t->next = freeTokens;
1224 freeTokens = t;
1225 return next;
1229 * Convert a line of tokens back into text.
1230 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1231 * will be transformed into ..@ctxnum.xxx
1233 static char *detoken(Token * tlist, bool expand_locals)
1235 Token *t;
1236 char *line, *p;
1237 const char *q;
1238 int len = 0;
1240 list_for_each(t, tlist) {
1241 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1242 char *v;
1243 char *q = t->text;
1245 v = t->text + 2;
1246 if (*v == '\'' || *v == '\"' || *v == '`') {
1247 size_t len = nasm_unquote(v, NULL);
1248 size_t clen = strlen(v);
1250 if (len != clen) {
1251 error(ERR_NONFATAL | ERR_PASS1,
1252 "NUL character in %! string");
1253 v = NULL;
1257 if (v) {
1258 char *p = getenv(v);
1259 if (!p) {
1260 error(ERR_NONFATAL | ERR_PASS1,
1261 "nonexistent environment variable `%s'", v);
1262 p = "";
1264 t->text = nasm_strdup(p);
1266 nasm_free(q);
1269 /* Expand local macros here and not during preprocessing */
1270 if (expand_locals &&
1271 t->type == TOK_PREPROC_ID && t->text &&
1272 t->text[0] == '%' && t->text[1] == '$') {
1273 const char *q;
1274 char *p;
1275 Context *ctx = get_ctx(t->text, &q, false);
1276 if (ctx) {
1277 char buffer[40];
1278 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1279 p = nasm_strcat(buffer, q);
1280 nasm_free(t->text);
1281 t->text = p;
1284 if (t->type == TOK_WHITESPACE)
1285 len++;
1286 else if (t->text)
1287 len += strlen(t->text);
1290 p = line = nasm_malloc(len + 1);
1292 list_for_each(t, tlist) {
1293 if (t->type == TOK_WHITESPACE) {
1294 *p++ = ' ';
1295 } else if (t->text) {
1296 q = t->text;
1297 while (*q)
1298 *p++ = *q++;
1301 *p = '\0';
1303 return line;
1307 * Initialize a new Line
1309 static Line *new_Line(void)
1311 Line *l = nasm_malloc(sizeof(Line));
1312 l->next = NULL;
1313 l->first = NULL;
1314 return l;
1319 * Initialize a new Expansion Definition
1321 static ExpDef *new_ExpDef(void)
1323 ExpDef *ed = nasm_malloc(sizeof(ExpDef));
1324 ed->prev = NULL;
1325 ed->next = NULL;
1326 ed->type = EXP_NONE;
1327 ed->name = NULL;
1328 ed->nparam_min = 0;
1329 ed->nparam_max = 0;
1330 ed->casesense = true;
1331 ed->plus = false;
1332 ed->label = NULL;
1333 ed->line = NULL;
1334 ed->last = NULL;
1335 ed->dlist = NULL;
1336 ed->defaults = NULL;
1337 ed->ndefs = 0;
1338 ed->state = COND_NEVER;
1339 ed->nolist = false;
1340 ed->def_depth = 0;
1341 ed->cur_depth = 0;
1342 ed->max_depth = 0;
1343 ed->ignoring = false;
1344 return ed;
1349 * Initialize a new Expansion Instance
1351 static ExpInv *new_ExpInv(void)
1353 unique ++;
1354 ExpInv *ei = nasm_malloc(sizeof(ExpInv));
1355 ei->prev = NULL;
1356 ei->type = EXP_NONE;
1357 ei->def = NULL;
1358 ei->label = NULL;
1359 ei->label_text = NULL;
1360 ei->current = NULL;
1361 ei->params = NULL;
1362 ei->iline = NULL;
1363 ei->nparam = 0;
1364 ei->rotate = 0;
1365 ei->paramlen = NULL;
1366 ei->unique = unique;
1367 ei->emitting = false;
1368 ei->lineno = 0;
1369 return ei;
1373 * A scanner, suitable for use by the expression evaluator, which
1374 * operates on a line of Tokens. Expects a pointer to a pointer to
1375 * the first token in the line to be passed in as its private_data
1376 * field.
1378 * FIX: This really needs to be unified with stdscan.
1380 static int ppscan(void *private_data, struct tokenval *tokval)
1382 Token **tlineptr = private_data;
1383 Token *tline;
1384 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1386 do {
1387 tline = *tlineptr;
1388 *tlineptr = tline ? tline->next : NULL;
1389 } while (tline && (tline->type == TOK_WHITESPACE ||
1390 tline->type == TOK_COMMENT));
1392 if (!tline)
1393 return tokval->t_type = TOKEN_EOS;
1395 tokval->t_charptr = tline->text;
1397 if (tline->text[0] == '$' && !tline->text[1])
1398 return tokval->t_type = TOKEN_HERE;
1399 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1400 return tokval->t_type = TOKEN_BASE;
1402 if (tline->type == TOK_ID) {
1403 p = tokval->t_charptr = tline->text;
1404 if (p[0] == '$') {
1405 tokval->t_charptr++;
1406 return tokval->t_type = TOKEN_ID;
1409 for (r = p, s = ourcopy; *r; r++) {
1410 if (r >= p+MAX_KEYWORD)
1411 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1412 *s++ = nasm_tolower(*r);
1414 *s = '\0';
1415 /* right, so we have an identifier sitting in temp storage. now,
1416 * is it actually a register or instruction name, or what? */
1417 return nasm_token_hash(ourcopy, tokval);
1420 if (tline->type == TOK_NUMBER) {
1421 bool rn_error;
1422 tokval->t_integer = readnum(tline->text, &rn_error);
1423 tokval->t_charptr = tline->text;
1424 if (rn_error)
1425 return tokval->t_type = TOKEN_ERRNUM;
1426 else
1427 return tokval->t_type = TOKEN_NUM;
1430 if (tline->type == TOK_FLOAT) {
1431 return tokval->t_type = TOKEN_FLOAT;
1434 if (tline->type == TOK_STRING) {
1435 char bq, *ep;
1437 bq = tline->text[0];
1438 tokval->t_charptr = tline->text;
1439 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1441 if (ep[0] != bq || ep[1] != '\0')
1442 return tokval->t_type = TOKEN_ERRSTR;
1443 else
1444 return tokval->t_type = TOKEN_STR;
1447 if (tline->type == TOK_OTHER) {
1448 if (!strcmp(tline->text, "<<"))
1449 return tokval->t_type = TOKEN_SHL;
1450 if (!strcmp(tline->text, ">>"))
1451 return tokval->t_type = TOKEN_SHR;
1452 if (!strcmp(tline->text, "//"))
1453 return tokval->t_type = TOKEN_SDIV;
1454 if (!strcmp(tline->text, "%%"))
1455 return tokval->t_type = TOKEN_SMOD;
1456 if (!strcmp(tline->text, "=="))
1457 return tokval->t_type = TOKEN_EQ;
1458 if (!strcmp(tline->text, "<>"))
1459 return tokval->t_type = TOKEN_NE;
1460 if (!strcmp(tline->text, "!="))
1461 return tokval->t_type = TOKEN_NE;
1462 if (!strcmp(tline->text, "<="))
1463 return tokval->t_type = TOKEN_LE;
1464 if (!strcmp(tline->text, ">="))
1465 return tokval->t_type = TOKEN_GE;
1466 if (!strcmp(tline->text, "&&"))
1467 return tokval->t_type = TOKEN_DBL_AND;
1468 if (!strcmp(tline->text, "^^"))
1469 return tokval->t_type = TOKEN_DBL_XOR;
1470 if (!strcmp(tline->text, "||"))
1471 return tokval->t_type = TOKEN_DBL_OR;
1475 * We have no other options: just return the first character of
1476 * the token text.
1478 return tokval->t_type = tline->text[0];
1482 * Compare a string to the name of an existing macro; this is a
1483 * simple wrapper which calls either strcmp or nasm_stricmp
1484 * depending on the value of the `casesense' parameter.
1486 static int mstrcmp(const char *p, const char *q, bool casesense)
1488 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1492 * Compare a string to the name of an existing macro; this is a
1493 * simple wrapper which calls either strcmp or nasm_stricmp
1494 * depending on the value of the `casesense' parameter.
1496 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1498 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1502 * Return the Context structure associated with a %$ token. Return
1503 * NULL, having _already_ reported an error condition, if the
1504 * context stack isn't deep enough for the supplied number of $
1505 * signs.
1506 * If all_contexts == true, contexts that enclose current are
1507 * also scanned for such smacro, until it is found; if not -
1508 * only the context that directly results from the number of $'s
1509 * in variable's name.
1511 * If "namep" is non-NULL, set it to the pointer to the macro name
1512 * tail, i.e. the part beyond %$...
1514 static Context *get_ctx(const char *name, const char **namep,
1515 bool all_contexts)
1517 Context *ctx;
1518 SMacro *m;
1519 int i;
1521 if (namep)
1522 *namep = name;
1524 if (!name || name[0] != '%' || name[1] != '$')
1525 return NULL;
1527 if (!cstk) {
1528 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1529 return NULL;
1532 name += 2;
1533 ctx = cstk;
1534 i = 0;
1535 while (ctx && *name == '$') {
1536 name++;
1537 i++;
1538 ctx = ctx->next;
1540 if (!ctx) {
1541 error(ERR_NONFATAL, "`%s': context stack is only"
1542 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1543 return NULL;
1546 if (namep)
1547 *namep = name;
1549 if (!all_contexts)
1550 return ctx;
1552 do {
1553 /* Search for this smacro in found context */
1554 m = hash_findix(&ctx->localmac, name);
1555 while (m) {
1556 if (!mstrcmp(m->name, name, m->casesense))
1557 return ctx;
1558 m = m->next;
1560 ctx = ctx->next;
1562 while (ctx);
1563 return NULL;
1567 * Check to see if a file is already in a string list
1569 static bool in_list(const StrList *list, const char *str)
1571 while (list) {
1572 if (!strcmp(list->str, str))
1573 return true;
1574 list = list->next;
1576 return false;
1580 * Open an include file. This routine must always return a valid
1581 * file pointer if it returns - it's responsible for throwing an
1582 * ERR_FATAL and bombing out completely if not. It should also try
1583 * the include path one by one until it finds the file or reaches
1584 * the end of the path.
1586 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1587 bool missing_ok)
1589 FILE *fp;
1590 char *prefix = "";
1591 IncPath *ip = ipath;
1592 int len = strlen(file);
1593 size_t prefix_len = 0;
1594 StrList *sl;
1596 while (1) {
1597 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1598 memcpy(sl->str, prefix, prefix_len);
1599 memcpy(sl->str+prefix_len, file, len+1);
1600 fp = fopen(sl->str, "r");
1601 if (fp && dhead && !in_list(*dhead, sl->str)) {
1602 sl->next = NULL;
1603 **dtail = sl;
1604 *dtail = &sl->next;
1605 } else {
1606 nasm_free(sl);
1608 if (fp)
1609 return fp;
1610 if (!ip) {
1611 if (!missing_ok)
1612 break;
1613 prefix = NULL;
1614 } else {
1615 prefix = ip->path;
1616 ip = ip->next;
1618 if (prefix) {
1619 prefix_len = strlen(prefix);
1620 } else {
1621 /* -MG given and file not found */
1622 if (dhead && !in_list(*dhead, file)) {
1623 sl = nasm_malloc(len+1+sizeof sl->next);
1624 sl->next = NULL;
1625 strcpy(sl->str, file);
1626 **dtail = sl;
1627 *dtail = &sl->next;
1629 return NULL;
1633 error(ERR_FATAL, "unable to open include file `%s'", file);
1634 return NULL;
1638 * Determine if we should warn on defining a single-line macro of
1639 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1640 * return true if _any_ single-line macro of that name is defined.
1641 * Otherwise, will return true if a single-line macro with either
1642 * `nparam' or no parameters is defined.
1644 * If a macro with precisely the right number of parameters is
1645 * defined, or nparam is -1, the address of the definition structure
1646 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1647 * is NULL, no action will be taken regarding its contents, and no
1648 * error will occur.
1650 * Note that this is also called with nparam zero to resolve
1651 * `ifdef'.
1653 * If you already know which context macro belongs to, you can pass
1654 * the context pointer as first parameter; if you won't but name begins
1655 * with %$ the context will be automatically computed. If all_contexts
1656 * is true, macro will be searched in outer contexts as well.
1658 static bool
1659 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1660 bool nocase)
1662 struct hash_table *smtbl;
1663 SMacro *m;
1665 if (ctx) {
1666 smtbl = &ctx->localmac;
1667 } else if (name[0] == '%' && name[1] == '$') {
1668 if (cstk)
1669 ctx = get_ctx(name, &name, false);
1670 if (!ctx)
1671 return false; /* got to return _something_ */
1672 smtbl = &ctx->localmac;
1673 } else {
1674 smtbl = &smacros;
1676 m = (SMacro *) hash_findix(smtbl, name);
1678 while (m) {
1679 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1680 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1681 if (defn) {
1682 if (nparam == (int) m->nparam || nparam == -1)
1683 *defn = m;
1684 else
1685 *defn = NULL;
1687 return true;
1689 m = m->next;
1692 return false;
1696 * Count and mark off the parameters in a multi-line macro call.
1697 * This is called both from within the multi-line macro expansion
1698 * code, and also to mark off the default parameters when provided
1699 * in a %macro definition line.
1701 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1703 int paramsize, brace;
1705 *nparam = paramsize = 0;
1706 *params = NULL;
1707 while (t) {
1708 /* +1: we need space for the final NULL */
1709 if (*nparam+1 >= paramsize) {
1710 paramsize += PARAM_DELTA;
1711 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1713 skip_white_(t);
1714 brace = false;
1715 if (tok_is_(t, "{"))
1716 brace = true;
1717 (*params)[(*nparam)++] = t;
1718 while (tok_isnt_(t, brace ? "}" : ","))
1719 t = t->next;
1720 if (t) { /* got a comma/brace */
1721 t = t->next;
1722 if (brace) {
1724 * Now we've found the closing brace, look further
1725 * for the comma.
1727 skip_white_(t);
1728 if (tok_isnt_(t, ",")) {
1729 error(ERR_NONFATAL,
1730 "braces do not enclose all of macro parameter");
1731 while (tok_isnt_(t, ","))
1732 t = t->next;
1734 if (t)
1735 t = t->next; /* eat the comma */
1742 * Determine whether one of the various `if' conditions is true or
1743 * not.
1745 * We must free the tline we get passed.
1747 static bool if_condition(Token * tline, enum preproc_token ct)
1749 enum pp_conditional i = PP_COND(ct);
1750 bool j;
1751 Token *t, *tt, **tptr, *origline;
1752 struct tokenval tokval;
1753 expr *evalresult;
1754 enum pp_token_type needtype;
1755 char *p;
1757 origline = tline;
1759 switch (i) {
1760 case PPC_IFCTX:
1761 j = false; /* have we matched yet? */
1762 while (true) {
1763 skip_white_(tline);
1764 if (!tline)
1765 break;
1766 if (tline->type != TOK_ID) {
1767 error(ERR_NONFATAL,
1768 "`%s' expects context identifiers", pp_directives[ct]);
1769 free_tlist(origline);
1770 return -1;
1772 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1773 j = true;
1774 tline = tline->next;
1776 break;
1778 case PPC_IFDEF:
1779 j = false; /* have we matched yet? */
1780 while (tline) {
1781 skip_white_(tline);
1782 if (!tline || (tline->type != TOK_ID &&
1783 (tline->type != TOK_PREPROC_ID ||
1784 tline->text[1] != '$'))) {
1785 error(ERR_NONFATAL,
1786 "`%s' expects macro identifiers", pp_directives[ct]);
1787 goto fail;
1789 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1790 j = true;
1791 tline = tline->next;
1793 break;
1795 case PPC_IFENV:
1796 tline = expand_smacro(tline);
1797 j = false; /* have we matched yet? */
1798 while (tline) {
1799 skip_white_(tline);
1800 if (!tline || (tline->type != TOK_ID &&
1801 tline->type != TOK_STRING &&
1802 (tline->type != TOK_PREPROC_ID ||
1803 tline->text[1] != '!'))) {
1804 error(ERR_NONFATAL,
1805 "`%s' expects environment variable names",
1806 pp_directives[ct]);
1807 goto fail;
1809 p = tline->text;
1810 if (tline->type == TOK_PREPROC_ID)
1811 p += 2; /* Skip leading %! */
1812 if (*p == '\'' || *p == '\"' || *p == '`')
1813 nasm_unquote_cstr(p, ct);
1814 if (getenv(p))
1815 j = true;
1816 tline = tline->next;
1818 break;
1820 case PPC_IFIDN:
1821 case PPC_IFIDNI:
1822 tline = expand_smacro(tline);
1823 t = tt = tline;
1824 while (tok_isnt_(tt, ","))
1825 tt = tt->next;
1826 if (!tt) {
1827 error(ERR_NONFATAL,
1828 "`%s' expects two comma-separated arguments",
1829 pp_directives[ct]);
1830 goto fail;
1832 tt = tt->next;
1833 j = true; /* assume equality unless proved not */
1834 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1835 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1836 error(ERR_NONFATAL, "`%s': more than one comma on line",
1837 pp_directives[ct]);
1838 goto fail;
1840 if (t->type == TOK_WHITESPACE) {
1841 t = t->next;
1842 continue;
1844 if (tt->type == TOK_WHITESPACE) {
1845 tt = tt->next;
1846 continue;
1848 if (tt->type != t->type) {
1849 j = false; /* found mismatching tokens */
1850 break;
1852 /* When comparing strings, need to unquote them first */
1853 if (t->type == TOK_STRING) {
1854 size_t l1 = nasm_unquote(t->text, NULL);
1855 size_t l2 = nasm_unquote(tt->text, NULL);
1857 if (l1 != l2) {
1858 j = false;
1859 break;
1861 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1862 j = false;
1863 break;
1865 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1866 j = false; /* found mismatching tokens */
1867 break;
1870 t = t->next;
1871 tt = tt->next;
1873 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1874 j = false; /* trailing gunk on one end or other */
1875 break;
1877 case PPC_IFMACRO:
1879 bool found = false;
1880 ExpDef searching, *ed;
1882 skip_white_(tline);
1883 tline = expand_id(tline);
1884 if (!tok_type_(tline, TOK_ID)) {
1885 error(ERR_NONFATAL,
1886 "`%s' expects a macro name", pp_directives[ct]);
1887 goto fail;
1889 searching.name = nasm_strdup(tline->text);
1890 searching.casesense = true;
1891 searching.plus = false;
1892 searching.nolist = false;
1893 //searching.in_progress = 0;
1894 searching.max_depth = 0;
1895 //searching.rep_nest = NULL;
1896 searching.nparam_min = 0;
1897 searching.nparam_max = INT_MAX;
1898 tline = expand_smacro(tline->next);
1899 skip_white_(tline);
1900 if (!tline) {
1901 } else if (!tok_type_(tline, TOK_NUMBER)) {
1902 error(ERR_NONFATAL,
1903 "`%s' expects a parameter count or nothing",
1904 pp_directives[ct]);
1905 } else {
1906 searching.nparam_min = searching.nparam_max =
1907 readnum(tline->text, &j);
1908 if (j)
1909 error(ERR_NONFATAL,
1910 "unable to parse parameter count `%s'",
1911 tline->text);
1913 if (tline && tok_is_(tline->next, "-")) {
1914 tline = tline->next->next;
1915 if (tok_is_(tline, "*"))
1916 searching.nparam_max = INT_MAX;
1917 else if (!tok_type_(tline, TOK_NUMBER))
1918 error(ERR_NONFATAL,
1919 "`%s' expects a parameter count after `-'",
1920 pp_directives[ct]);
1921 else {
1922 searching.nparam_max = readnum(tline->text, &j);
1923 if (j)
1924 error(ERR_NONFATAL,
1925 "unable to parse parameter count `%s'",
1926 tline->text);
1927 if (searching.nparam_min > searching.nparam_max)
1928 error(ERR_NONFATAL,
1929 "minimum parameter count exceeds maximum");
1932 if (tline && tok_is_(tline->next, "+")) {
1933 tline = tline->next;
1934 searching.plus = true;
1936 ed = (ExpDef *) hash_findix(&expdefs, searching.name);
1937 while (ed != NULL) {
1938 if (!strcmp(ed->name, searching.name) &&
1939 (ed->nparam_min <= searching.nparam_max
1940 || searching.plus)
1941 && (searching.nparam_min <= ed->nparam_max
1942 || ed->plus)) {
1943 found = true;
1944 break;
1946 ed = ed->next;
1948 if (tline && tline->next)
1949 error(ERR_WARNING|ERR_PASS1,
1950 "trailing garbage after %%ifmacro ignored");
1951 nasm_free(searching.name);
1952 j = found;
1953 break;
1956 case PPC_IFID:
1957 needtype = TOK_ID;
1958 goto iftype;
1959 case PPC_IFNUM:
1960 needtype = TOK_NUMBER;
1961 goto iftype;
1962 case PPC_IFSTR:
1963 needtype = TOK_STRING;
1964 goto iftype;
1966 iftype:
1967 t = tline = expand_smacro(tline);
1969 while (tok_type_(t, TOK_WHITESPACE) ||
1970 (needtype == TOK_NUMBER &&
1971 tok_type_(t, TOK_OTHER) &&
1972 (t->text[0] == '-' || t->text[0] == '+') &&
1973 !t->text[1]))
1974 t = t->next;
1976 j = tok_type_(t, needtype);
1977 break;
1979 case PPC_IFTOKEN:
1980 t = tline = expand_smacro(tline);
1981 while (tok_type_(t, TOK_WHITESPACE))
1982 t = t->next;
1984 j = false;
1985 if (t) {
1986 t = t->next; /* Skip the actual token */
1987 while (tok_type_(t, TOK_WHITESPACE))
1988 t = t->next;
1989 j = !t; /* Should be nothing left */
1991 break;
1993 case PPC_IFEMPTY:
1994 t = tline = expand_smacro(tline);
1995 while (tok_type_(t, TOK_WHITESPACE))
1996 t = t->next;
1998 j = !t; /* Should be empty */
1999 break;
2001 case PPC_IF:
2002 t = tline = expand_smacro(tline);
2003 tptr = &t;
2004 tokval.t_type = TOKEN_INVALID;
2005 evalresult = evaluate(ppscan, tptr, &tokval,
2006 NULL, pass | CRITICAL, error, NULL);
2007 if (!evalresult)
2008 return -1;
2009 if (tokval.t_type)
2010 error(ERR_WARNING|ERR_PASS1,
2011 "trailing garbage after expression ignored");
2012 if (!is_simple(evalresult)) {
2013 error(ERR_NONFATAL,
2014 "non-constant value given to `%s'", pp_directives[ct]);
2015 goto fail;
2017 j = reloc_value(evalresult) != 0;
2018 break;
2020 default:
2021 error(ERR_FATAL,
2022 "preprocessor directive `%s' not yet implemented",
2023 pp_directives[ct]);
2024 goto fail;
2027 free_tlist(origline);
2028 return j ^ PP_NEGATIVE(ct);
2030 fail:
2031 free_tlist(origline);
2032 return -1;
2036 * Common code for defining an smacro
2038 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2039 int nparam, Token *expansion)
2041 SMacro *smac, **smhead;
2042 struct hash_table *smtbl;
2044 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2045 if (!smac) {
2046 error(ERR_WARNING|ERR_PASS1,
2047 "single-line macro `%s' defined both with and"
2048 " without parameters", mname);
2050 * Some instances of the old code considered this a failure,
2051 * some others didn't. What is the right thing to do here?
2053 free_tlist(expansion);
2054 return false; /* Failure */
2055 } else {
2057 * We're redefining, so we have to take over an
2058 * existing SMacro structure. This means freeing
2059 * what was already in it.
2061 nasm_free(smac->name);
2062 free_tlist(smac->expansion);
2064 } else {
2065 smtbl = ctx ? &ctx->localmac : &smacros;
2066 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2067 smac = nasm_malloc(sizeof(SMacro));
2068 smac->next = *smhead;
2069 *smhead = smac;
2071 smac->name = nasm_strdup(mname);
2072 smac->casesense = casesense;
2073 smac->nparam = nparam;
2074 smac->expansion = expansion;
2075 smac->in_progress = false;
2076 return true; /* Success */
2080 * Undefine an smacro
2082 static void undef_smacro(Context *ctx, const char *mname)
2084 SMacro **smhead, *s, **sp;
2085 struct hash_table *smtbl;
2087 smtbl = ctx ? &ctx->localmac : &smacros;
2088 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2090 if (smhead) {
2092 * We now have a macro name... go hunt for it.
2094 sp = smhead;
2095 while ((s = *sp) != NULL) {
2096 if (!mstrcmp(s->name, mname, s->casesense)) {
2097 *sp = s->next;
2098 nasm_free(s->name);
2099 free_tlist(s->expansion);
2100 nasm_free(s);
2101 } else {
2102 sp = &s->next;
2109 * Parse a mmacro specification.
2111 static bool parse_mmacro_spec(Token *tline, ExpDef *def, const char *directive)
2113 bool err;
2115 tline = tline->next;
2116 skip_white_(tline);
2117 tline = expand_id(tline);
2118 if (!tok_type_(tline, TOK_ID)) {
2119 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2120 return false;
2123 def->name = nasm_strdup(tline->text);
2124 def->plus = false;
2125 def->nolist = false;
2126 // def->in_progress = 0;
2127 // def->rep_nest = NULL;
2128 def->nparam_min = 0;
2129 def->nparam_max = 0;
2131 tline = expand_smacro(tline->next);
2132 skip_white_(tline);
2133 if (!tok_type_(tline, TOK_NUMBER)) {
2134 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2135 } else {
2136 def->nparam_min = def->nparam_max =
2137 readnum(tline->text, &err);
2138 if (err)
2139 error(ERR_NONFATAL,
2140 "unable to parse parameter count `%s'", tline->text);
2142 if (tline && tok_is_(tline->next, "-")) {
2143 tline = tline->next->next;
2144 if (tok_is_(tline, "*")) {
2145 def->nparam_max = INT_MAX;
2146 } else if (!tok_type_(tline, TOK_NUMBER)) {
2147 error(ERR_NONFATAL,
2148 "`%s' expects a parameter count after `-'", directive);
2149 } else {
2150 def->nparam_max = readnum(tline->text, &err);
2151 if (err) {
2152 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2153 tline->text);
2155 if (def->nparam_min > def->nparam_max) {
2156 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2160 if (tline && tok_is_(tline->next, "+")) {
2161 tline = tline->next;
2162 def->plus = true;
2164 if (tline && tok_type_(tline->next, TOK_ID) &&
2165 !nasm_stricmp(tline->next->text, ".nolist")) {
2166 tline = tline->next;
2167 def->nolist = true;
2171 * Handle default parameters.
2173 if (tline && tline->next) {
2174 def->dlist = tline->next;
2175 tline->next = NULL;
2176 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2177 } else {
2178 def->dlist = NULL;
2179 def->defaults = NULL;
2181 def->line = NULL;
2183 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2184 !def->plus)
2185 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2186 "too many default macro parameters");
2188 return true;
2193 * Decode a size directive
2195 static int parse_size(const char *str) {
2196 static const char *size_names[] =
2197 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2198 static const int sizes[] =
2199 { 0, 1, 4, 16, 8, 10, 2, 32 };
2201 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2205 * find and process preprocessor directive in passed line
2206 * Find out if a line contains a preprocessor directive, and deal
2207 * with it if so.
2209 * If a directive _is_ found, it is the responsibility of this routine
2210 * (and not the caller) to free_tlist() the line.
2212 * @param tline a pointer to the current tokeninzed line linked list
2213 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2216 static int do_directive(Token * tline)
2218 enum preproc_token i;
2219 int j;
2220 bool err;
2221 int nparam;
2222 bool nolist;
2223 bool casesense;
2224 int k, m;
2225 int offset;
2226 char *p, *pp;
2227 const char *mname;
2228 Include *inc;
2229 Context *ctx;
2230 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2231 struct tokenval tokval;
2232 expr *evalresult;
2233 ExpDef *ed, *eed, **edhead;
2234 ExpInv *ei, *eei;
2235 int64_t count;
2236 size_t len;
2237 int severity;
2239 origline = tline;
2241 skip_white_(tline);
2242 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2243 (tline->text[1] == '%' || tline->text[1] == '$'
2244 || tline->text[1] == '!'))
2245 return NO_DIRECTIVE_FOUND;
2247 i = pp_token_hash(tline->text);
2249 switch (i) {
2250 case PP_INVALID:
2251 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2252 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2253 tline->text);
2254 return NO_DIRECTIVE_FOUND; /* didn't get it */
2256 case PP_STACKSIZE:
2257 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2258 /* Directive to tell NASM what the default stack size is. The
2259 * default is for a 16-bit stack, and this can be overriden with
2260 * %stacksize large.
2262 tline = tline->next;
2263 if (tline && tline->type == TOK_WHITESPACE)
2264 tline = tline->next;
2265 if (!tline || tline->type != TOK_ID) {
2266 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2267 free_tlist(origline);
2268 return DIRECTIVE_FOUND;
2270 if (nasm_stricmp(tline->text, "flat") == 0) {
2271 /* All subsequent ARG directives are for a 32-bit stack */
2272 StackSize = 4;
2273 StackPointer = "ebp";
2274 ArgOffset = 8;
2275 LocalOffset = 0;
2276 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2277 /* All subsequent ARG directives are for a 64-bit stack */
2278 StackSize = 8;
2279 StackPointer = "rbp";
2280 ArgOffset = 16;
2281 LocalOffset = 0;
2282 } else if (nasm_stricmp(tline->text, "large") == 0) {
2283 /* All subsequent ARG directives are for a 16-bit stack,
2284 * far function call.
2286 StackSize = 2;
2287 StackPointer = "bp";
2288 ArgOffset = 4;
2289 LocalOffset = 0;
2290 } else if (nasm_stricmp(tline->text, "small") == 0) {
2291 /* All subsequent ARG directives are for a 16-bit stack,
2292 * far function call. We don't support near functions.
2294 StackSize = 2;
2295 StackPointer = "bp";
2296 ArgOffset = 6;
2297 LocalOffset = 0;
2298 } else {
2299 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2300 free_tlist(origline);
2301 return DIRECTIVE_FOUND;
2303 free_tlist(origline);
2304 return DIRECTIVE_FOUND;
2306 case PP_ARG:
2307 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2308 /* TASM like ARG directive to define arguments to functions, in
2309 * the following form:
2311 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2313 offset = ArgOffset;
2314 do {
2315 char *arg, directive[256];
2316 int size = StackSize;
2318 /* Find the argument name */
2319 tline = tline->next;
2320 if (tline && tline->type == TOK_WHITESPACE)
2321 tline = tline->next;
2322 if (!tline || tline->type != TOK_ID) {
2323 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2324 free_tlist(origline);
2325 return DIRECTIVE_FOUND;
2327 arg = tline->text;
2329 /* Find the argument size type */
2330 tline = tline->next;
2331 if (!tline || tline->type != TOK_OTHER
2332 || tline->text[0] != ':') {
2333 error(ERR_NONFATAL,
2334 "Syntax error processing `%%arg' directive");
2335 free_tlist(origline);
2336 return DIRECTIVE_FOUND;
2338 tline = tline->next;
2339 if (!tline || tline->type != TOK_ID) {
2340 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2341 free_tlist(origline);
2342 return DIRECTIVE_FOUND;
2345 /* Allow macro expansion of type parameter */
2346 tt = tokenize(tline->text);
2347 tt = expand_smacro(tt);
2348 size = parse_size(tt->text);
2349 if (!size) {
2350 error(ERR_NONFATAL,
2351 "Invalid size type for `%%arg' missing directive");
2352 free_tlist(tt);
2353 free_tlist(origline);
2354 return DIRECTIVE_FOUND;
2356 free_tlist(tt);
2358 /* Round up to even stack slots */
2359 size = ALIGN(size, StackSize);
2361 /* Now define the macro for the argument */
2362 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2363 arg, StackPointer, offset);
2364 do_directive(tokenize(directive));
2365 offset += size;
2367 /* Move to the next argument in the list */
2368 tline = tline->next;
2369 if (tline && tline->type == TOK_WHITESPACE)
2370 tline = tline->next;
2371 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2372 ArgOffset = offset;
2373 free_tlist(origline);
2374 return DIRECTIVE_FOUND;
2376 case PP_LOCAL:
2377 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2378 /* TASM like LOCAL directive to define local variables for a
2379 * function, in the following form:
2381 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2383 * The '= LocalSize' at the end is ignored by NASM, but is
2384 * required by TASM to define the local parameter size (and used
2385 * by the TASM macro package).
2387 offset = LocalOffset;
2388 do {
2389 char *local, directive[256];
2390 int size = StackSize;
2392 /* Find the argument name */
2393 tline = tline->next;
2394 if (tline && tline->type == TOK_WHITESPACE)
2395 tline = tline->next;
2396 if (!tline || tline->type != TOK_ID) {
2397 error(ERR_NONFATAL,
2398 "`%%local' missing argument parameter");
2399 free_tlist(origline);
2400 return DIRECTIVE_FOUND;
2402 local = tline->text;
2404 /* Find the argument size type */
2405 tline = tline->next;
2406 if (!tline || tline->type != TOK_OTHER
2407 || tline->text[0] != ':') {
2408 error(ERR_NONFATAL,
2409 "Syntax error processing `%%local' directive");
2410 free_tlist(origline);
2411 return DIRECTIVE_FOUND;
2413 tline = tline->next;
2414 if (!tline || tline->type != TOK_ID) {
2415 error(ERR_NONFATAL,
2416 "`%%local' missing size type parameter");
2417 free_tlist(origline);
2418 return DIRECTIVE_FOUND;
2421 /* Allow macro expansion of type parameter */
2422 tt = tokenize(tline->text);
2423 tt = expand_smacro(tt);
2424 size = parse_size(tt->text);
2425 if (!size) {
2426 error(ERR_NONFATAL,
2427 "Invalid size type for `%%local' missing directive");
2428 free_tlist(tt);
2429 free_tlist(origline);
2430 return DIRECTIVE_FOUND;
2432 free_tlist(tt);
2434 /* Round up to even stack slots */
2435 size = ALIGN(size, StackSize);
2437 offset += size; /* Negative offset, increment before */
2439 /* Now define the macro for the argument */
2440 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2441 local, StackPointer, offset);
2442 do_directive(tokenize(directive));
2444 /* Now define the assign to setup the enter_c macro correctly */
2445 snprintf(directive, sizeof(directive),
2446 "%%assign %%$localsize %%$localsize+%d", size);
2447 do_directive(tokenize(directive));
2449 /* Move to the next argument in the list */
2450 tline = tline->next;
2451 if (tline && tline->type == TOK_WHITESPACE)
2452 tline = tline->next;
2453 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2454 LocalOffset = offset;
2455 free_tlist(origline);
2456 return DIRECTIVE_FOUND;
2458 case PP_CLEAR:
2459 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2460 if (tline->next)
2461 error(ERR_WARNING|ERR_PASS1,
2462 "trailing garbage after `%%clear' ignored");
2463 free_macros();
2464 init_macros();
2465 free_tlist(origline);
2466 return DIRECTIVE_FOUND;
2468 case PP_DEPEND:
2469 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2470 t = tline->next = expand_smacro(tline->next);
2471 skip_white_(t);
2472 if (!t || (t->type != TOK_STRING &&
2473 t->type != TOK_INTERNAL_STRING)) {
2474 error(ERR_NONFATAL, "`%%depend' expects a file name");
2475 free_tlist(origline);
2476 return DIRECTIVE_FOUND; /* but we did _something_ */
2478 if (t->next)
2479 error(ERR_WARNING|ERR_PASS1,
2480 "trailing garbage after `%%depend' ignored");
2481 p = t->text;
2482 if (t->type != TOK_INTERNAL_STRING)
2483 nasm_unquote_cstr(p, i);
2484 if (dephead && !in_list(*dephead, p)) {
2485 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2486 sl->next = NULL;
2487 strcpy(sl->str, p);
2488 *deptail = sl;
2489 deptail = &sl->next;
2491 free_tlist(origline);
2492 return DIRECTIVE_FOUND;
2494 case PP_INCLUDE:
2495 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2496 t = tline->next = expand_smacro(tline->next);
2497 skip_white_(t);
2499 if (!t || (t->type != TOK_STRING &&
2500 t->type != TOK_INTERNAL_STRING)) {
2501 error(ERR_NONFATAL, "`%%include' expects a file name");
2502 free_tlist(origline);
2503 return DIRECTIVE_FOUND; /* but we did _something_ */
2505 if (t->next)
2506 error(ERR_WARNING|ERR_PASS1,
2507 "trailing garbage after `%%include' ignored");
2508 p = t->text;
2509 if (t->type != TOK_INTERNAL_STRING)
2510 nasm_unquote_cstr(p, i);
2511 inc = nasm_malloc(sizeof(Include));
2512 inc->next = istk;
2513 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2514 if (!inc->fp) {
2515 /* -MG given but file not found */
2516 nasm_free(inc);
2517 } else {
2518 inc->fname = src_set_fname(nasm_strdup(p));
2519 inc->lineno = src_set_linnum(0);
2520 inc->lineinc = 1;
2521 inc->expansion = NULL;
2522 istk = inc;
2523 list->uplevel(LIST_INCLUDE);
2525 free_tlist(origline);
2526 return DIRECTIVE_FOUND;
2528 case PP_USE:
2529 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2531 static macros_t *use_pkg;
2532 const char *pkg_macro = NULL;
2534 tline = tline->next;
2535 skip_white_(tline);
2536 tline = expand_id(tline);
2538 if (!tline || (tline->type != TOK_STRING &&
2539 tline->type != TOK_INTERNAL_STRING &&
2540 tline->type != TOK_ID)) {
2541 error(ERR_NONFATAL, "`%%use' expects a package name");
2542 free_tlist(origline);
2543 return DIRECTIVE_FOUND; /* but we did _something_ */
2545 if (tline->next)
2546 error(ERR_WARNING|ERR_PASS1,
2547 "trailing garbage after `%%use' ignored");
2548 if (tline->type == TOK_STRING)
2549 nasm_unquote_cstr(tline->text, i);
2550 use_pkg = nasm_stdmac_find_package(tline->text);
2551 if (!use_pkg)
2552 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2553 else
2554 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2555 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2556 /* Not already included, go ahead and include it */
2557 stdmacpos = use_pkg;
2559 free_tlist(origline);
2560 return DIRECTIVE_FOUND;
2562 case PP_PUSH:
2563 case PP_REPL:
2564 case PP_POP:
2565 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2566 tline = tline->next;
2567 skip_white_(tline);
2568 tline = expand_id(tline);
2569 if (tline) {
2570 if (!tok_type_(tline, TOK_ID)) {
2571 error(ERR_NONFATAL, "`%s' expects a context identifier",
2572 pp_directives[i]);
2573 free_tlist(origline);
2574 return DIRECTIVE_FOUND; /* but we did _something_ */
2576 if (tline->next)
2577 error(ERR_WARNING|ERR_PASS1,
2578 "trailing garbage after `%s' ignored",
2579 pp_directives[i]);
2580 p = nasm_strdup(tline->text);
2581 } else {
2582 p = NULL; /* Anonymous */
2585 if (i == PP_PUSH) {
2586 ctx = nasm_malloc(sizeof(Context));
2587 ctx->next = cstk;
2588 hash_init(&ctx->localmac, HASH_SMALL);
2589 ctx->name = p;
2590 ctx->number = unique++;
2591 cstk = ctx;
2592 } else {
2593 /* %pop or %repl */
2594 if (!cstk) {
2595 error(ERR_NONFATAL, "`%s': context stack is empty",
2596 pp_directives[i]);
2597 } else if (i == PP_POP) {
2598 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2599 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2600 "expected %s",
2601 cstk->name ? cstk->name : "anonymous", p);
2602 else
2603 ctx_pop();
2604 } else {
2605 /* i == PP_REPL */
2606 nasm_free(cstk->name);
2607 cstk->name = p;
2608 p = NULL;
2610 nasm_free(p);
2612 free_tlist(origline);
2613 return DIRECTIVE_FOUND;
2614 case PP_FATAL:
2615 severity = ERR_FATAL;
2616 goto issue_error;
2617 case PP_ERROR:
2618 severity = ERR_NONFATAL;
2619 goto issue_error;
2620 case PP_WARNING:
2621 severity = ERR_WARNING|ERR_WARN_USER;
2622 goto issue_error;
2624 issue_error:
2625 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2627 /* Only error out if this is the final pass */
2628 if (pass != 2 && i != PP_FATAL)
2629 return DIRECTIVE_FOUND;
2631 tline->next = expand_smacro(tline->next);
2632 tline = tline->next;
2633 skip_white_(tline);
2634 t = tline ? tline->next : NULL;
2635 skip_white_(t);
2636 if (tok_type_(tline, TOK_STRING) && !t) {
2637 /* The line contains only a quoted string */
2638 p = tline->text;
2639 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2640 error(severity, "%s", p);
2641 } else {
2642 /* Not a quoted string, or more than a quoted string */
2643 p = detoken(tline, false);
2644 error(severity, "%s", p);
2645 nasm_free(p);
2647 free_tlist(origline);
2648 return DIRECTIVE_FOUND;
2651 CASE_PP_IF:
2652 if (defining != NULL) {
2653 if (defining->type == EXP_IF) {
2654 defining->def_depth ++;
2656 return NO_DIRECTIVE_FOUND;
2658 if ((istk->expansion != NULL) &&
2659 (istk->expansion->emitting == false)) {
2660 j = COND_NEVER;
2661 } else {
2662 j = if_condition(tline->next, i);
2663 tline->next = NULL; /* it got freed */
2664 j = (((j < 0) ? COND_NEVER : j) ? COND_IF_TRUE : COND_IF_FALSE);
2666 ed = new_ExpDef();
2667 ed->type = EXP_IF;
2668 ed->state = j;
2669 ed->nolist = NULL;
2670 ed->def_depth = 0;
2671 ed->cur_depth = 0;
2672 ed->max_depth = 0;
2673 ed->ignoring = ((ed->state == COND_IF_TRUE) ? false : true);
2674 ed->prev = defining;
2675 defining = ed;
2676 free_tlist(origline);
2677 return DIRECTIVE_FOUND;
2679 CASE_PP_ELIF:
2680 if (defining != NULL) {
2681 if ((defining->type != EXP_IF) || (defining->def_depth > 0)) {
2682 return NO_DIRECTIVE_FOUND;
2685 if ((defining == NULL) || (defining->type != EXP_IF)) {
2686 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2688 switch (defining->state) {
2689 case COND_IF_TRUE:
2690 defining->state = COND_DONE;
2691 defining->ignoring = true;
2692 break;
2694 case COND_DONE:
2695 case COND_NEVER:
2696 defining->ignoring = true;
2697 break;
2699 case COND_ELSE_TRUE:
2700 case COND_ELSE_FALSE:
2701 error_precond(ERR_WARNING|ERR_PASS1,
2702 "`%%elif' after `%%else' ignored");
2703 defining->state = COND_NEVER;
2704 defining->ignoring = true;
2705 break;
2707 case COND_IF_FALSE:
2709 * IMPORTANT: In the case of %if, we will already have
2710 * called expand_mmac_params(); however, if we're
2711 * processing an %elif we must have been in a
2712 * non-emitting mode, which would have inhibited
2713 * the normal invocation of expand_mmac_params().
2714 * Therefore, we have to do it explicitly here.
2716 j = if_condition(expand_mmac_params(tline->next), i);
2717 tline->next = NULL; /* it got freed */
2718 defining->state =
2719 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2720 defining->ignoring = ((defining->state == COND_IF_TRUE) ? false : true);
2721 break;
2723 free_tlist(origline);
2724 return DIRECTIVE_FOUND;
2726 case PP_ELSE:
2727 if (defining != NULL) {
2728 if ((defining->type != EXP_IF) || (defining->def_depth > 0)) {
2729 return NO_DIRECTIVE_FOUND;
2732 if (tline->next)
2733 error_precond(ERR_WARNING|ERR_PASS1,
2734 "trailing garbage after `%%else' ignored");
2735 if ((defining == NULL) || (defining->type != EXP_IF)) {
2736 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2738 switch (defining->state) {
2739 case COND_IF_TRUE:
2740 case COND_DONE:
2741 defining->state = COND_ELSE_FALSE;
2742 defining->ignoring = true;
2743 break;
2745 case COND_NEVER:
2746 defining->ignoring = true;
2747 break;
2749 case COND_IF_FALSE:
2750 defining->state = COND_ELSE_TRUE;
2751 defining->ignoring = false;
2752 break;
2754 case COND_ELSE_TRUE:
2755 case COND_ELSE_FALSE:
2756 error_precond(ERR_WARNING|ERR_PASS1,
2757 "`%%else' after `%%else' ignored.");
2758 defining->state = COND_NEVER;
2759 defining->ignoring = true;
2760 break;
2762 free_tlist(origline);
2763 return DIRECTIVE_FOUND;
2765 case PP_ENDIF:
2766 if (defining != NULL) {
2767 if (defining->type == EXP_IF) {
2768 if (defining->def_depth > 0) {
2769 defining->def_depth --;
2770 return NO_DIRECTIVE_FOUND;
2772 } else {
2773 return NO_DIRECTIVE_FOUND;
2776 if (tline->next)
2777 error_precond(ERR_WARNING|ERR_PASS1,
2778 "trailing garbage after `%%endif' ignored");
2779 if ((defining == NULL) || (defining->type != EXP_IF)) {
2780 error(ERR_NONFATAL, "`%%endif': no matching `%%if'");
2782 ed = defining;
2783 defining = ed->prev;
2784 ed->prev = expansions;
2785 expansions = ed;
2786 ei = new_ExpInv();
2787 ei->type = EXP_IF;
2788 ei->def = ed;
2789 ei->current = ed->line;
2790 ei->emitting = true;
2791 ei->prev = istk->expansion;
2792 istk->expansion = ei;
2793 free_tlist(origline);
2794 return DIRECTIVE_FOUND;
2796 case PP_RMACRO:
2797 case PP_IRMACRO:
2798 case PP_MACRO:
2799 case PP_IMACRO:
2800 if (defining != NULL) {
2801 if (defining->type == EXP_MMACRO) {
2802 defining->def_depth ++;
2804 return NO_DIRECTIVE_FOUND;
2806 ed = new_ExpDef();
2807 ed->max_depth =
2808 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2809 ed->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2810 if (!parse_mmacro_spec(tline, ed, pp_directives[i])) {
2811 nasm_free(ed);
2812 ed = NULL;
2813 return DIRECTIVE_FOUND;
2815 ed->type = EXP_MMACRO;
2816 ed->def_depth = 0;
2817 ed->cur_depth = 0;
2818 ed->max_depth = (ed->max_depth + 1);
2819 ed->ignoring = false;
2820 ed->prev = defining;
2821 defining = ed;
2823 eed = (ExpDef *) hash_findix(&expdefs, ed->name);
2824 while (eed) {
2825 if (!strcmp(eed->name, ed->name) &&
2826 (eed->nparam_min <= ed->nparam_max
2827 || ed->plus)
2828 && (ed->nparam_min <= eed->nparam_max
2829 || eed->plus)) {
2830 error(ERR_WARNING|ERR_PASS1,
2831 "redefining multi-line macro `%s'", ed->name);
2832 return DIRECTIVE_FOUND;
2834 eed = eed->next;
2836 free_tlist(origline);
2837 return DIRECTIVE_FOUND;
2839 case PP_ENDM:
2840 case PP_ENDMACRO:
2841 if (defining != NULL) {
2842 if (defining->type == EXP_MMACRO) {
2843 if (defining->def_depth > 0) {
2844 defining->def_depth --;
2845 return NO_DIRECTIVE_FOUND;
2847 } else {
2848 return NO_DIRECTIVE_FOUND;
2851 if (!(defining) || (defining->type != EXP_MMACRO)) {
2852 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2853 return DIRECTIVE_FOUND;
2855 edhead = (ExpDef **) hash_findi_add(&expdefs, defining->name);
2856 defining->next = *edhead;
2857 *edhead = defining;
2858 ed = defining;
2859 defining = ed->prev;
2860 ed->prev = expansions;
2861 expansions = ed;
2862 ed = NULL;
2863 free_tlist(origline);
2864 return DIRECTIVE_FOUND;
2866 case PP_EXITMACRO:
2867 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2869 * We must search along istk->expansion until we hit a
2870 * macro invocation. Then we disable the emitting state(s)
2871 * between exitmacro and endmacro.
2873 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
2874 if(ei->type == EXP_MMACRO) {
2875 break;
2879 if (ei != NULL) {
2881 * Set all invocations leading back to the macro
2882 * invocation to a non-emitting state.
2884 for (eei = istk->expansion; eei != ei; eei = eei->prev) {
2885 eei->emitting = false;
2887 eei->emitting = false;
2888 } else {
2889 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2891 free_tlist(origline);
2892 return DIRECTIVE_FOUND;
2894 case PP_UNMACRO:
2895 case PP_UNIMACRO:
2896 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2898 ExpDef **ed_p;
2899 ExpDef spec;
2901 spec.casesense = (i == PP_UNMACRO);
2902 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2903 return DIRECTIVE_FOUND;
2905 ed_p = (ExpDef **) hash_findi(&expdefs, spec.name, NULL);
2906 while (ed_p && *ed_p) {
2907 ed = *ed_p;
2908 if (ed->casesense == spec.casesense &&
2909 !mstrcmp(ed->name, spec.name, spec.casesense) &&
2910 ed->nparam_min == spec.nparam_min &&
2911 ed->nparam_max == spec.nparam_max &&
2912 ed->plus == spec.plus) {
2913 *ed_p = ed->next;
2914 free_expdef(ed);
2915 } else {
2916 ed_p = &ed->next;
2919 free_tlist(origline);
2920 free_tlist(spec.dlist);
2921 return DIRECTIVE_FOUND;
2924 case PP_ROTATE:
2925 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2926 if (tline->next && tline->next->type == TOK_WHITESPACE)
2927 tline = tline->next;
2928 if (!tline->next) {
2929 free_tlist(origline);
2930 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2931 return DIRECTIVE_FOUND;
2933 t = expand_smacro(tline->next);
2934 tline->next = NULL;
2935 free_tlist(origline);
2936 tline = t;
2937 tptr = &t;
2938 tokval.t_type = TOKEN_INVALID;
2939 evalresult =
2940 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2941 free_tlist(tline);
2942 if (!evalresult)
2943 return DIRECTIVE_FOUND;
2944 if (tokval.t_type)
2945 error(ERR_WARNING|ERR_PASS1,
2946 "trailing garbage after expression ignored");
2947 if (!is_simple(evalresult)) {
2948 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2949 return DIRECTIVE_FOUND;
2951 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
2952 if (ei->type == EXP_MMACRO) {
2953 break;
2956 if (ei == NULL) {
2957 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2958 } else if (ei->nparam == 0) {
2959 error(ERR_NONFATAL,
2960 "`%%rotate' invoked within macro without parameters");
2961 } else {
2962 int rotate = ei->rotate + reloc_value(evalresult);
2964 rotate %= (int)ei->nparam;
2965 if (rotate < 0)
2966 rotate += ei->nparam;
2967 ei->rotate = rotate;
2969 return DIRECTIVE_FOUND;
2971 case PP_REP:
2972 if (defining != NULL) {
2973 if (defining->type == EXP_REP) {
2974 defining->def_depth ++;
2976 return NO_DIRECTIVE_FOUND;
2978 nolist = false;
2979 do {
2980 tline = tline->next;
2981 } while (tok_type_(tline, TOK_WHITESPACE));
2983 if (tok_type_(tline, TOK_ID) &&
2984 nasm_stricmp(tline->text, ".nolist") == 0) {
2985 nolist = true;
2986 do {
2987 tline = tline->next;
2988 } while (tok_type_(tline, TOK_WHITESPACE));
2991 if (tline) {
2992 t = expand_smacro(tline);
2993 tptr = &t;
2994 tokval.t_type = TOKEN_INVALID;
2995 evalresult =
2996 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2997 if (!evalresult) {
2998 free_tlist(origline);
2999 return DIRECTIVE_FOUND;
3001 if (tokval.t_type)
3002 error(ERR_WARNING|ERR_PASS1,
3003 "trailing garbage after expression ignored");
3004 if (!is_simple(evalresult)) {
3005 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3006 return DIRECTIVE_FOUND;
3008 count = reloc_value(evalresult) + 1;
3009 } else {
3010 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3011 count = 0;
3013 free_tlist(origline);
3014 ed = new_ExpDef();
3015 ed->type = EXP_REP;
3016 ed->nolist = nolist;
3017 ed->def_depth = 0;
3018 ed->cur_depth = 1;
3019 ed->max_depth = (count - 1);
3020 ed->ignoring = false;
3021 ed->prev = defining;
3022 defining = ed;
3023 return DIRECTIVE_FOUND;
3025 case PP_ENDREP:
3026 if (defining != NULL) {
3027 if (defining->type == EXP_REP) {
3028 if (defining->def_depth > 0) {
3029 defining->def_depth --;
3030 return NO_DIRECTIVE_FOUND;
3032 } else {
3033 return NO_DIRECTIVE_FOUND;
3036 if ((defining == NULL) || (defining->type != EXP_REP)) {
3037 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3038 return DIRECTIVE_FOUND;
3042 * Now we have a "macro" defined - although it has no name
3043 * and we won't be entering it in the hash tables - we must
3044 * push a macro-end marker for it on to istk->expansion.
3045 * After that, it will take care of propagating itself (a
3046 * macro-end marker line for a macro which is really a %rep
3047 * block will cause the macro to be re-expanded, complete
3048 * with another macro-end marker to ensure the process
3049 * continues) until the whole expansion is forcibly removed
3050 * from istk->expansion by a %exitrep.
3052 ed = defining;
3053 defining = ed->prev;
3054 ed->prev = expansions;
3055 expansions = ed;
3056 ei = new_ExpInv();
3057 ei->type = EXP_REP;
3058 ei->def = ed;
3059 ei->current = ed->line;
3060 ei->emitting = ((ed->max_depth > 0) ? true : false);
3061 list->uplevel(ed->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3062 ei->prev = istk->expansion;
3063 istk->expansion = ei;
3064 free_tlist(origline);
3065 return DIRECTIVE_FOUND;
3067 case PP_EXITREP:
3068 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3070 * We must search along istk->expansion until we hit a
3071 * rep invocation. Then we disable the emitting state(s)
3072 * between exitrep and endrep.
3074 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
3075 if (ei->type == EXP_REP) {
3076 break;
3080 if (ei != NULL) {
3082 * Set all invocations leading back to the rep
3083 * invocation to a non-emitting state.
3085 for (eei = istk->expansion; eei != ei; eei = eei->prev) {
3086 eei->emitting = false;
3088 eei->emitting = false;
3089 eei->current = NULL;
3090 eei->def->cur_depth = eei->def->max_depth;
3091 } else {
3092 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3094 free_tlist(origline);
3095 return DIRECTIVE_FOUND;
3097 case PP_XDEFINE:
3098 case PP_IXDEFINE:
3099 case PP_DEFINE:
3100 case PP_IDEFINE:
3101 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3102 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3104 tline = tline->next;
3105 skip_white_(tline);
3106 tline = expand_id(tline);
3107 if (!tline || (tline->type != TOK_ID &&
3108 (tline->type != TOK_PREPROC_ID ||
3109 tline->text[1] != '$'))) {
3110 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3111 pp_directives[i]);
3112 free_tlist(origline);
3113 return DIRECTIVE_FOUND;
3116 ctx = get_ctx(tline->text, &mname, false);
3117 last = tline;
3118 param_start = tline = tline->next;
3119 nparam = 0;
3121 /* Expand the macro definition now for %xdefine and %ixdefine */
3122 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3123 tline = expand_smacro(tline);
3125 if (tok_is_(tline, "(")) {
3127 * This macro has parameters.
3130 tline = tline->next;
3131 while (1) {
3132 skip_white_(tline);
3133 if (!tline) {
3134 error(ERR_NONFATAL, "parameter identifier expected");
3135 free_tlist(origline);
3136 return DIRECTIVE_FOUND;
3138 if (tline->type != TOK_ID) {
3139 error(ERR_NONFATAL,
3140 "`%s': parameter identifier expected",
3141 tline->text);
3142 free_tlist(origline);
3143 return DIRECTIVE_FOUND;
3145 tline->type = TOK_SMAC_PARAM + nparam++;
3146 tline = tline->next;
3147 skip_white_(tline);
3148 if (tok_is_(tline, ",")) {
3149 tline = tline->next;
3150 } else {
3151 if (!tok_is_(tline, ")")) {
3152 error(ERR_NONFATAL,
3153 "`)' expected to terminate macro template");
3154 free_tlist(origline);
3155 return DIRECTIVE_FOUND;
3157 break;
3160 last = tline;
3161 tline = tline->next;
3163 if (tok_type_(tline, TOK_WHITESPACE))
3164 last = tline, tline = tline->next;
3165 macro_start = NULL;
3166 last->next = NULL;
3167 t = tline;
3168 while (t) {
3169 if (t->type == TOK_ID) {
3170 list_for_each(tt, param_start)
3171 if (tt->type >= TOK_SMAC_PARAM &&
3172 !strcmp(tt->text, t->text))
3173 t->type = tt->type;
3175 tt = t->next;
3176 t->next = macro_start;
3177 macro_start = t;
3178 t = tt;
3181 * Good. We now have a macro name, a parameter count, and a
3182 * token list (in reverse order) for an expansion. We ought
3183 * to be OK just to create an SMacro, store it, and let
3184 * free_tlist have the rest of the line (which we have
3185 * carefully re-terminated after chopping off the expansion
3186 * from the end).
3188 define_smacro(ctx, mname, casesense, nparam, macro_start);
3189 free_tlist(origline);
3190 return DIRECTIVE_FOUND;
3192 case PP_UNDEF:
3193 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3194 tline = tline->next;
3195 skip_white_(tline);
3196 tline = expand_id(tline);
3197 if (!tline || (tline->type != TOK_ID &&
3198 (tline->type != TOK_PREPROC_ID ||
3199 tline->text[1] != '$'))) {
3200 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3201 free_tlist(origline);
3202 return DIRECTIVE_FOUND;
3204 if (tline->next) {
3205 error(ERR_WARNING|ERR_PASS1,
3206 "trailing garbage after macro name ignored");
3209 /* Find the context that symbol belongs to */
3210 ctx = get_ctx(tline->text, &mname, false);
3211 undef_smacro(ctx, mname);
3212 free_tlist(origline);
3213 return DIRECTIVE_FOUND;
3215 case PP_DEFSTR:
3216 case PP_IDEFSTR:
3217 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3218 casesense = (i == PP_DEFSTR);
3220 tline = tline->next;
3221 skip_white_(tline);
3222 tline = expand_id(tline);
3223 if (!tline || (tline->type != TOK_ID &&
3224 (tline->type != TOK_PREPROC_ID ||
3225 tline->text[1] != '$'))) {
3226 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3227 pp_directives[i]);
3228 free_tlist(origline);
3229 return DIRECTIVE_FOUND;
3232 ctx = get_ctx(tline->text, &mname, false);
3233 last = tline;
3234 tline = expand_smacro(tline->next);
3235 last->next = NULL;
3237 while (tok_type_(tline, TOK_WHITESPACE))
3238 tline = delete_Token(tline);
3240 p = detoken(tline, false);
3241 macro_start = nasm_malloc(sizeof(*macro_start));
3242 macro_start->next = NULL;
3243 macro_start->text = nasm_quote(p, strlen(p));
3244 macro_start->type = TOK_STRING;
3245 macro_start->a.mac = NULL;
3246 nasm_free(p);
3249 * We now have a macro name, an implicit parameter count of
3250 * zero, and a string token to use as an expansion. Create
3251 * and store an SMacro.
3253 define_smacro(ctx, mname, casesense, 0, macro_start);
3254 free_tlist(origline);
3255 return DIRECTIVE_FOUND;
3257 case PP_DEFTOK:
3258 case PP_IDEFTOK:
3259 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3260 casesense = (i == PP_DEFTOK);
3262 tline = tline->next;
3263 skip_white_(tline);
3264 tline = expand_id(tline);
3265 if (!tline || (tline->type != TOK_ID &&
3266 (tline->type != TOK_PREPROC_ID ||
3267 tline->text[1] != '$'))) {
3268 error(ERR_NONFATAL,
3269 "`%s' expects a macro identifier as first parameter",
3270 pp_directives[i]);
3271 free_tlist(origline);
3272 return DIRECTIVE_FOUND;
3274 ctx = get_ctx(tline->text, &mname, false);
3275 last = tline;
3276 tline = expand_smacro(tline->next);
3277 last->next = NULL;
3279 t = tline;
3280 while (tok_type_(t, TOK_WHITESPACE))
3281 t = t->next;
3282 /* t should now point to the string */
3283 if (t->type != TOK_STRING) {
3284 error(ERR_NONFATAL,
3285 "`%s` requires string as second parameter",
3286 pp_directives[i]);
3287 free_tlist(tline);
3288 free_tlist(origline);
3289 return DIRECTIVE_FOUND;
3292 nasm_unquote_cstr(t->text, i);
3293 macro_start = tokenize(t->text);
3296 * We now have a macro name, an implicit parameter count of
3297 * zero, and a numeric token to use as an expansion. Create
3298 * and store an SMacro.
3300 define_smacro(ctx, mname, casesense, 0, macro_start);
3301 free_tlist(tline);
3302 free_tlist(origline);
3303 return DIRECTIVE_FOUND;
3305 case PP_PATHSEARCH:
3306 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3308 FILE *fp;
3309 StrList *xsl = NULL;
3310 StrList **xst = &xsl;
3312 casesense = true;
3314 tline = tline->next;
3315 skip_white_(tline);
3316 tline = expand_id(tline);
3317 if (!tline || (tline->type != TOK_ID &&
3318 (tline->type != TOK_PREPROC_ID ||
3319 tline->text[1] != '$'))) {
3320 error(ERR_NONFATAL,
3321 "`%%pathsearch' expects a macro identifier as first parameter");
3322 free_tlist(origline);
3323 return DIRECTIVE_FOUND;
3325 ctx = get_ctx(tline->text, &mname, false);
3326 last = tline;
3327 tline = expand_smacro(tline->next);
3328 last->next = NULL;
3330 t = tline;
3331 while (tok_type_(t, TOK_WHITESPACE))
3332 t = t->next;
3334 if (!t || (t->type != TOK_STRING &&
3335 t->type != TOK_INTERNAL_STRING)) {
3336 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3337 free_tlist(tline);
3338 free_tlist(origline);
3339 return DIRECTIVE_FOUND; /* but we did _something_ */
3341 if (t->next)
3342 error(ERR_WARNING|ERR_PASS1,
3343 "trailing garbage after `%%pathsearch' ignored");
3344 p = t->text;
3345 if (t->type != TOK_INTERNAL_STRING)
3346 nasm_unquote(p, NULL);
3348 fp = inc_fopen(p, &xsl, &xst, true);
3349 if (fp) {
3350 p = xsl->str;
3351 fclose(fp); /* Don't actually care about the file */
3353 macro_start = nasm_malloc(sizeof(*macro_start));
3354 macro_start->next = NULL;
3355 macro_start->text = nasm_quote(p, strlen(p));
3356 macro_start->type = TOK_STRING;
3357 macro_start->a.mac = NULL;
3358 if (xsl)
3359 nasm_free(xsl);
3362 * We now have a macro name, an implicit parameter count of
3363 * zero, and a string token to use as an expansion. Create
3364 * and store an SMacro.
3366 define_smacro(ctx, mname, casesense, 0, macro_start);
3367 free_tlist(tline);
3368 free_tlist(origline);
3369 return DIRECTIVE_FOUND;
3372 case PP_STRLEN:
3373 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3374 casesense = true;
3376 tline = tline->next;
3377 skip_white_(tline);
3378 tline = expand_id(tline);
3379 if (!tline || (tline->type != TOK_ID &&
3380 (tline->type != TOK_PREPROC_ID ||
3381 tline->text[1] != '$'))) {
3382 error(ERR_NONFATAL,
3383 "`%%strlen' expects a macro identifier as first parameter");
3384 free_tlist(origline);
3385 return DIRECTIVE_FOUND;
3387 ctx = get_ctx(tline->text, &mname, false);
3388 last = tline;
3389 tline = expand_smacro(tline->next);
3390 last->next = NULL;
3392 t = tline;
3393 while (tok_type_(t, TOK_WHITESPACE))
3394 t = t->next;
3395 /* t should now point to the string */
3396 if (!tok_type_(t, TOK_STRING)) {
3397 error(ERR_NONFATAL,
3398 "`%%strlen` requires string as second parameter");
3399 free_tlist(tline);
3400 free_tlist(origline);
3401 return DIRECTIVE_FOUND;
3404 macro_start = nasm_malloc(sizeof(*macro_start));
3405 macro_start->next = NULL;
3406 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3407 macro_start->a.mac = NULL;
3410 * We now have a macro name, an implicit parameter count of
3411 * zero, and a numeric token to use as an expansion. Create
3412 * and store an SMacro.
3414 define_smacro(ctx, mname, casesense, 0, macro_start);
3415 free_tlist(tline);
3416 free_tlist(origline);
3417 return DIRECTIVE_FOUND;
3419 case PP_STRCAT:
3420 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3421 casesense = true;
3423 tline = tline->next;
3424 skip_white_(tline);
3425 tline = expand_id(tline);
3426 if (!tline || (tline->type != TOK_ID &&
3427 (tline->type != TOK_PREPROC_ID ||
3428 tline->text[1] != '$'))) {
3429 error(ERR_NONFATAL,
3430 "`%%strcat' expects a macro identifier as first parameter");
3431 free_tlist(origline);
3432 return DIRECTIVE_FOUND;
3434 ctx = get_ctx(tline->text, &mname, false);
3435 last = tline;
3436 tline = expand_smacro(tline->next);
3437 last->next = NULL;
3439 len = 0;
3440 list_for_each(t, tline) {
3441 switch (t->type) {
3442 case TOK_WHITESPACE:
3443 break;
3444 case TOK_STRING:
3445 len += t->a.len = nasm_unquote(t->text, NULL);
3446 break;
3447 case TOK_OTHER:
3448 if (!strcmp(t->text, ",")) /* permit comma separators */
3449 break;
3450 /* else fall through */
3451 default:
3452 error(ERR_NONFATAL,
3453 "non-string passed to `%%strcat' (%d)", t->type);
3454 free_tlist(tline);
3455 free_tlist(origline);
3456 return DIRECTIVE_FOUND;
3460 p = pp = nasm_malloc(len);
3461 list_for_each(t, tline) {
3462 if (t->type == TOK_STRING) {
3463 memcpy(p, t->text, t->a.len);
3464 p += t->a.len;
3469 * We now have a macro name, an implicit parameter count of
3470 * zero, and a numeric token to use as an expansion. Create
3471 * and store an SMacro.
3473 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3474 macro_start->text = nasm_quote(pp, len);
3475 nasm_free(pp);
3476 define_smacro(ctx, mname, casesense, 0, macro_start);
3477 free_tlist(tline);
3478 free_tlist(origline);
3479 return DIRECTIVE_FOUND;
3481 case PP_SUBSTR:
3482 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3484 int64_t a1, a2;
3485 size_t len;
3487 casesense = true;
3489 tline = tline->next;
3490 skip_white_(tline);
3491 tline = expand_id(tline);
3492 if (!tline || (tline->type != TOK_ID &&
3493 (tline->type != TOK_PREPROC_ID ||
3494 tline->text[1] != '$'))) {
3495 error(ERR_NONFATAL,
3496 "`%%substr' expects a macro identifier as first parameter");
3497 free_tlist(origline);
3498 return DIRECTIVE_FOUND;
3500 ctx = get_ctx(tline->text, &mname, false);
3501 last = tline;
3502 tline = expand_smacro(tline->next);
3503 last->next = NULL;
3505 t = tline->next;
3506 while (tok_type_(t, TOK_WHITESPACE))
3507 t = t->next;
3509 /* t should now point to the string */
3510 if (t->type != TOK_STRING) {
3511 error(ERR_NONFATAL,
3512 "`%%substr` requires string as second parameter");
3513 free_tlist(tline);
3514 free_tlist(origline);
3515 return DIRECTIVE_FOUND;
3518 tt = t->next;
3519 tptr = &tt;
3520 tokval.t_type = TOKEN_INVALID;
3521 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3522 pass, error, NULL);
3523 if (!evalresult) {
3524 free_tlist(tline);
3525 free_tlist(origline);
3526 return DIRECTIVE_FOUND;
3527 } else if (!is_simple(evalresult)) {
3528 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3529 free_tlist(tline);
3530 free_tlist(origline);
3531 return DIRECTIVE_FOUND;
3533 a1 = evalresult->value-1;
3535 while (tok_type_(tt, TOK_WHITESPACE))
3536 tt = tt->next;
3537 if (!tt) {
3538 a2 = 1; /* Backwards compatibility: one character */
3539 } else {
3540 tokval.t_type = TOKEN_INVALID;
3541 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3542 pass, error, NULL);
3543 if (!evalresult) {
3544 free_tlist(tline);
3545 free_tlist(origline);
3546 return DIRECTIVE_FOUND;
3547 } else if (!is_simple(evalresult)) {
3548 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3549 free_tlist(tline);
3550 free_tlist(origline);
3551 return DIRECTIVE_FOUND;
3553 a2 = evalresult->value;
3556 len = nasm_unquote(t->text, NULL);
3557 if (a2 < 0)
3558 a2 = a2+1+len-a1;
3559 if (a1+a2 > (int64_t)len)
3560 a2 = len-a1;
3562 macro_start = nasm_malloc(sizeof(*macro_start));
3563 macro_start->next = NULL;
3564 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3565 macro_start->type = TOK_STRING;
3566 macro_start->a.mac = NULL;
3569 * We now have a macro name, an implicit parameter count of
3570 * zero, and a numeric token to use as an expansion. Create
3571 * and store an SMacro.
3573 define_smacro(ctx, mname, casesense, 0, macro_start);
3574 free_tlist(tline);
3575 free_tlist(origline);
3576 return DIRECTIVE_FOUND;
3579 case PP_ASSIGN:
3580 case PP_IASSIGN:
3581 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3582 casesense = (i == PP_ASSIGN);
3584 tline = tline->next;
3585 skip_white_(tline);
3586 tline = expand_id(tline);
3587 if (!tline || (tline->type != TOK_ID &&
3588 (tline->type != TOK_PREPROC_ID ||
3589 tline->text[1] != '$'))) {
3590 error(ERR_NONFATAL,
3591 "`%%%sassign' expects a macro identifier",
3592 (i == PP_IASSIGN ? "i" : ""));
3593 free_tlist(origline);
3594 return DIRECTIVE_FOUND;
3596 ctx = get_ctx(tline->text, &mname, false);
3597 last = tline;
3598 tline = expand_smacro(tline->next);
3599 last->next = NULL;
3601 t = tline;
3602 tptr = &t;
3603 tokval.t_type = TOKEN_INVALID;
3604 evalresult =
3605 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3606 free_tlist(tline);
3607 if (!evalresult) {
3608 free_tlist(origline);
3609 return DIRECTIVE_FOUND;
3612 if (tokval.t_type)
3613 error(ERR_WARNING|ERR_PASS1,
3614 "trailing garbage after expression ignored");
3616 if (!is_simple(evalresult)) {
3617 error(ERR_NONFATAL,
3618 "non-constant value given to `%%%sassign'",
3619 (i == PP_IASSIGN ? "i" : ""));
3620 free_tlist(origline);
3621 return DIRECTIVE_FOUND;
3624 macro_start = nasm_malloc(sizeof(*macro_start));
3625 macro_start->next = NULL;
3626 make_tok_num(macro_start, reloc_value(evalresult));
3627 macro_start->a.mac = NULL;
3630 * We now have a macro name, an implicit parameter count of
3631 * zero, and a numeric token to use as an expansion. Create
3632 * and store an SMacro.
3634 define_smacro(ctx, mname, casesense, 0, macro_start);
3635 free_tlist(origline);
3636 return DIRECTIVE_FOUND;
3638 case PP_LINE:
3639 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3641 * Syntax is `%line nnn[+mmm] [filename]'
3643 tline = tline->next;
3644 skip_white_(tline);
3645 if (!tok_type_(tline, TOK_NUMBER)) {
3646 error(ERR_NONFATAL, "`%%line' expects line number");
3647 free_tlist(origline);
3648 return DIRECTIVE_FOUND;
3650 k = readnum(tline->text, &err);
3651 m = 1;
3652 tline = tline->next;
3653 if (tok_is_(tline, "+")) {
3654 tline = tline->next;
3655 if (!tok_type_(tline, TOK_NUMBER)) {
3656 error(ERR_NONFATAL, "`%%line' expects line increment");
3657 free_tlist(origline);
3658 return DIRECTIVE_FOUND;
3660 m = readnum(tline->text, &err);
3661 tline = tline->next;
3663 skip_white_(tline);
3664 src_set_linnum(k);
3665 istk->lineinc = m;
3666 if (tline) {
3667 nasm_free(src_set_fname(detoken(tline, false)));
3669 free_tlist(origline);
3670 return DIRECTIVE_FOUND;
3672 default:
3673 error(ERR_FATAL,
3674 "preprocessor directive `%s' not yet implemented",
3675 pp_directives[i]);
3676 return DIRECTIVE_FOUND;
3681 * Ensure that a macro parameter contains a condition code and
3682 * nothing else. Return the condition code index if so, or -1
3683 * otherwise.
3685 static int find_cc(Token * t)
3687 Token *tt;
3688 int i, j, k, m;
3690 if (!t)
3691 return -1; /* Probably a %+ without a space */
3693 skip_white_(t);
3694 if (t->type != TOK_ID)
3695 return -1;
3696 tt = t->next;
3697 skip_white_(tt);
3698 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3699 return -1;
3701 i = -1;
3702 j = ARRAY_SIZE(conditions);
3703 while (j - i > 1) {
3704 k = (j + i) / 2;
3705 m = nasm_stricmp(t->text, conditions[k]);
3706 if (m == 0) {
3707 i = k;
3708 j = -2;
3709 break;
3710 } else if (m < 0) {
3711 j = k;
3712 } else
3713 i = k;
3715 if (j != -2)
3716 return -1;
3717 return i;
3720 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3722 Token **tail, *t, *tt;
3723 Token **paste_head;
3724 bool did_paste = false;
3725 char *tmp;
3727 /* Now handle token pasting... */
3728 paste_head = NULL;
3729 tail = head;
3730 while ((t = *tail) && (tt = t->next)) {
3731 switch (t->type) {
3732 case TOK_WHITESPACE:
3733 if (tt->type == TOK_WHITESPACE) {
3734 /* Zap adjacent whitespace tokens */
3735 t->next = delete_Token(tt);
3736 } else {
3737 /* Do not advance paste_head here */
3738 tail = &t->next;
3740 break;
3741 case TOK_ID:
3742 case TOK_NUMBER:
3743 case TOK_FLOAT:
3745 size_t len = 0;
3746 char *tmp, *p;
3748 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3749 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3750 tt->type == TOK_OTHER)) {
3751 len += strlen(tt->text);
3752 tt = tt->next;
3756 * Now tt points to the first token after
3757 * the potential paste area...
3759 if (tt != t->next) {
3760 /* We have at least two tokens... */
3761 len += strlen(t->text);
3762 p = tmp = nasm_malloc(len+1);
3764 while (t != tt) {
3765 strcpy(p, t->text);
3766 p = strchr(p, '\0');
3767 t = delete_Token(t);
3770 t = *tail = tokenize(tmp);
3771 nasm_free(tmp);
3773 while (t->next) {
3774 tail = &t->next;
3775 t = t->next;
3777 t->next = tt; /* Attach the remaining token chain */
3779 did_paste = true;
3781 paste_head = tail;
3782 tail = &t->next;
3783 break;
3785 case TOK_PASTE: /* %+ */
3786 if (handle_paste_tokens) {
3787 /* Zap %+ and whitespace tokens to the right */
3788 while (t && (t->type == TOK_WHITESPACE ||
3789 t->type == TOK_PASTE))
3790 t = *tail = delete_Token(t);
3791 if (!paste_head || !t)
3792 break; /* Nothing to paste with */
3793 tail = paste_head;
3794 t = *tail;
3795 tt = t->next;
3796 while (tok_type_(tt, TOK_WHITESPACE))
3797 tt = t->next = delete_Token(tt);
3799 if (tt) {
3800 tmp = nasm_strcat(t->text, tt->text);
3801 delete_Token(t);
3802 tt = delete_Token(tt);
3803 t = *tail = tokenize(tmp);
3804 nasm_free(tmp);
3805 while (t->next) {
3806 tail = &t->next;
3807 t = t->next;
3809 t->next = tt; /* Attach the remaining token chain */
3810 did_paste = true;
3812 paste_head = tail;
3813 tail = &t->next;
3814 break;
3816 /* else fall through */
3817 default:
3818 tail = &t->next;
3819 if (!tok_type_(t->next, TOK_WHITESPACE))
3820 paste_head = tail;
3821 break;
3824 return did_paste;
3828 * expands to a list of tokens from %{x:y}
3830 static Token *expand_mmac_params_range(ExpInv *ei, Token *tline, Token ***last)
3832 Token *t = tline, **tt, *tm, *head;
3833 char *pos;
3834 int fst, lst, j, i;
3836 pos = strchr(tline->text, ':');
3837 nasm_assert(pos);
3839 lst = atoi(pos + 1);
3840 fst = atoi(tline->text + 1);
3843 * only macros params are accounted so
3844 * if someone passes %0 -- we reject such
3845 * value(s)
3847 if (lst == 0 || fst == 0)
3848 goto err;
3850 /* the values should be sane */
3851 if ((fst > (int)ei->nparam || fst < (-(int)ei->nparam)) ||
3852 (lst > (int)ei->nparam || lst < (-(int)ei->nparam)))
3853 goto err;
3855 fst = fst < 0 ? fst + (int)ei->nparam + 1: fst;
3856 lst = lst < 0 ? lst + (int)ei->nparam + 1: lst;
3858 /* counted from zero */
3859 fst--, lst--;
3862 * it will be at least one token
3864 tm = ei->params[(fst + ei->rotate) % ei->nparam];
3865 t = new_Token(NULL, tm->type, tm->text, 0);
3866 head = t, tt = &t->next;
3867 if (fst < lst) {
3868 for (i = fst + 1; i <= lst; i++) {
3869 t = new_Token(NULL, TOK_OTHER, ",", 0);
3870 *tt = t, tt = &t->next;
3871 j = (i + ei->rotate) % ei->nparam;
3872 tm = ei->params[j];
3873 t = new_Token(NULL, tm->type, tm->text, 0);
3874 *tt = t, tt = &t->next;
3876 } else {
3877 for (i = fst - 1; i >= lst; i--) {
3878 t = new_Token(NULL, TOK_OTHER, ",", 0);
3879 *tt = t, tt = &t->next;
3880 j = (i + ei->rotate) % ei->nparam;
3881 tm = ei->params[j];
3882 t = new_Token(NULL, tm->type, tm->text, 0);
3883 *tt = t, tt = &t->next;
3887 *last = tt;
3888 return head;
3890 err:
3891 error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3892 &tline->text[1]);
3893 return tline;
3897 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3898 * %-n) and MMacro-local identifiers (%%foo) as well as
3899 * macro indirection (%[...]) and range (%{..:..}).
3901 static Token *expand_mmac_params(Token * tline)
3903 Token *t, *tt, **tail, *thead;
3904 bool changed = false;
3905 char *pos;
3907 tail = &thead;
3908 thead = NULL;
3910 while (tline) {
3911 if (tline->type == TOK_PREPROC_ID &&
3912 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3913 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3914 tline->text[1] == '%')) {
3915 char *text = NULL;
3916 int type = 0, cc; /* type = 0 to placate optimisers */
3917 char tmpbuf[30];
3918 unsigned int n;
3919 int i;
3920 ExpInv *ei;
3922 t = tline;
3923 tline = tline->next;
3925 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
3926 if (ei->type == EXP_MMACRO) {
3927 break;
3930 if (ei == NULL) {
3931 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
3932 } else {
3933 pos = strchr(t->text, ':');
3934 if (!pos) {
3935 switch (t->text[1]) {
3937 * We have to make a substitution of one of the
3938 * forms %1, %-1, %+1, %%foo, %0.
3940 case '0':
3941 if ((strlen(t->text) > 2) && (t->text[2] == '0')) {
3942 type = TOK_ID;
3943 text = nasm_strdup(ei->label_text);
3944 } else {
3945 type = TOK_NUMBER;
3946 snprintf(tmpbuf, sizeof(tmpbuf), "%d", ei->nparam);
3947 text = nasm_strdup(tmpbuf);
3949 break;
3950 case '%':
3951 type = TOK_ID;
3952 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
3953 ei->unique);
3954 text = nasm_strcat(tmpbuf, t->text + 2);
3955 break;
3956 case '-':
3957 n = atoi(t->text + 2) - 1;
3958 if (n >= ei->nparam)
3959 tt = NULL;
3960 else {
3961 if (ei->nparam > 1)
3962 n = (n + ei->rotate) % ei->nparam;
3963 tt = ei->params[n];
3965 cc = find_cc(tt);
3966 if (cc == -1) {
3967 error(ERR_NONFATAL,
3968 "macro parameter %d is not a condition code",
3969 n + 1);
3970 text = NULL;
3971 } else {
3972 type = TOK_ID;
3973 if (inverse_ccs[cc] == -1) {
3974 error(ERR_NONFATAL,
3975 "condition code `%s' is not invertible",
3976 conditions[cc]);
3977 text = NULL;
3978 } else
3979 text = nasm_strdup(conditions[inverse_ccs[cc]]);
3981 break;
3982 case '+':
3983 n = atoi(t->text + 2) - 1;
3984 if (n >= ei->nparam)
3985 tt = NULL;
3986 else {
3987 if (ei->nparam > 1)
3988 n = (n + ei->rotate) % ei->nparam;
3989 tt = ei->params[n];
3991 cc = find_cc(tt);
3992 if (cc == -1) {
3993 error(ERR_NONFATAL,
3994 "macro parameter %d is not a condition code",
3995 n + 1);
3996 text = NULL;
3997 } else {
3998 type = TOK_ID;
3999 text = nasm_strdup(conditions[cc]);
4001 break;
4002 default:
4003 n = atoi(t->text + 1) - 1;
4004 if (n >= ei->nparam)
4005 tt = NULL;
4006 else {
4007 if (ei->nparam > 1)
4008 n = (n + ei->rotate) % ei->nparam;
4009 tt = ei->params[n];
4011 if (tt) {
4012 for (i = 0; i < ei->paramlen[n]; i++) {
4013 *tail = new_Token(NULL, tt->type, tt->text, 0);
4014 tail = &(*tail)->next;
4015 tt = tt->next;
4018 text = NULL; /* we've done it here */
4019 break;
4021 } else {
4023 * seems we have a parameters range here
4025 Token *head, **last;
4026 head = expand_mmac_params_range(ei, t, &last);
4027 if (head != t) {
4028 *tail = head;
4029 *last = tline;
4030 tline = head;
4031 text = NULL;
4035 if (!text) {
4036 delete_Token(t);
4037 } else {
4038 *tail = t;
4039 tail = &t->next;
4040 t->type = type;
4041 nasm_free(t->text);
4042 t->text = text;
4043 t->a.mac = NULL;
4045 changed = true;
4046 continue;
4047 } else if (tline->type == TOK_INDIRECT) {
4048 t = tline;
4049 tline = tline->next;
4050 tt = tokenize(t->text);
4051 tt = expand_mmac_params(tt);
4052 tt = expand_smacro(tt);
4053 *tail = tt;
4054 while (tt) {
4055 tt->a.mac = NULL; /* Necessary? */
4056 tail = &tt->next;
4057 tt = tt->next;
4059 delete_Token(t);
4060 changed = true;
4061 } else {
4062 t = *tail = tline;
4063 tline = tline->next;
4064 t->a.mac = NULL;
4065 tail = &t->next;
4068 *tail = NULL;
4070 if (changed)
4071 paste_tokens(&thead, false);
4073 return thead;
4077 * Expand all single-line macro calls made in the given line.
4078 * Return the expanded version of the line. The original is deemed
4079 * to be destroyed in the process. (In reality we'll just move
4080 * Tokens from input to output a lot of the time, rather than
4081 * actually bothering to destroy and replicate.)
4084 static Token *expand_smacro(Token * tline)
4086 Token *t, *tt, *mstart, **tail, *thead;
4087 SMacro *head = NULL, *m;
4088 Token **params;
4089 int *paramsize;
4090 unsigned int nparam, sparam;
4091 int brackets;
4092 Token *org_tline = tline;
4093 Context *ctx;
4094 const char *mname;
4095 int deadman = DEADMAN_LIMIT;
4096 bool expanded;
4099 * Trick: we should avoid changing the start token pointer since it can
4100 * be contained in "next" field of other token. Because of this
4101 * we allocate a copy of first token and work with it; at the end of
4102 * routine we copy it back
4104 if (org_tline) {
4105 tline = new_Token(org_tline->next, org_tline->type,
4106 org_tline->text, 0);
4107 tline->a.mac = org_tline->a.mac;
4108 nasm_free(org_tline->text);
4109 org_tline->text = NULL;
4112 expanded = true; /* Always expand %+ at least once */
4114 again:
4115 thead = NULL;
4116 tail = &thead;
4118 while (tline) { /* main token loop */
4119 if (!--deadman) {
4120 error(ERR_NONFATAL, "interminable macro recursion");
4121 goto err;
4124 if ((mname = tline->text)) {
4125 /* if this token is a local macro, look in local context */
4126 if (tline->type == TOK_ID) {
4127 head = (SMacro *)hash_findix(&smacros, mname);
4128 } else if (tline->type == TOK_PREPROC_ID) {
4129 ctx = get_ctx(mname, &mname, true);
4130 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4131 } else
4132 head = NULL;
4135 * We've hit an identifier. As in is_mmacro below, we first
4136 * check whether the identifier is a single-line macro at
4137 * all, then think about checking for parameters if
4138 * necessary.
4140 list_for_each(m, head)
4141 if (!mstrcmp(m->name, mname, m->casesense))
4142 break;
4143 if (m) {
4144 mstart = tline;
4145 params = NULL;
4146 paramsize = NULL;
4147 if (m->nparam == 0) {
4149 * Simple case: the macro is parameterless. Discard the
4150 * one token that the macro call took, and push the
4151 * expansion back on the to-do stack.
4153 if (!m->expansion) {
4154 if (!strcmp("__FILE__", m->name)) {
4155 int32_t num = 0;
4156 char *file = NULL;
4157 src_get(&num, &file);
4158 tline->text = nasm_quote(file, strlen(file));
4159 tline->type = TOK_STRING;
4160 nasm_free(file);
4161 continue;
4163 if (!strcmp("__LINE__", m->name)) {
4164 nasm_free(tline->text);
4165 make_tok_num(tline, src_get_linnum());
4166 continue;
4168 if (!strcmp("__BITS__", m->name)) {
4169 nasm_free(tline->text);
4170 make_tok_num(tline, globalbits);
4171 continue;
4173 tline = delete_Token(tline);
4174 continue;
4176 } else {
4178 * Complicated case: at least one macro with this name
4179 * exists and takes parameters. We must find the
4180 * parameters in the call, count them, find the SMacro
4181 * that corresponds to that form of the macro call, and
4182 * substitute for the parameters when we expand. What a
4183 * pain.
4185 /*tline = tline->next;
4186 skip_white_(tline); */
4187 do {
4188 t = tline->next;
4189 while (tok_type_(t, TOK_SMAC_END)) {
4190 t->a.mac->in_progress = false;
4191 t->text = NULL;
4192 t = tline->next = delete_Token(t);
4194 tline = t;
4195 } while (tok_type_(tline, TOK_WHITESPACE));
4196 if (!tok_is_(tline, "(")) {
4198 * This macro wasn't called with parameters: ignore
4199 * the call. (Behaviour borrowed from gnu cpp.)
4201 tline = mstart;
4202 m = NULL;
4203 } else {
4204 int paren = 0;
4205 int white = 0;
4206 brackets = 0;
4207 nparam = 0;
4208 sparam = PARAM_DELTA;
4209 params = nasm_malloc(sparam * sizeof(Token *));
4210 params[0] = tline->next;
4211 paramsize = nasm_malloc(sparam * sizeof(int));
4212 paramsize[0] = 0;
4213 while (true) { /* parameter loop */
4215 * For some unusual expansions
4216 * which concatenates function call
4218 t = tline->next;
4219 while (tok_type_(t, TOK_SMAC_END)) {
4220 t->a.mac->in_progress = false;
4221 t->text = NULL;
4222 t = tline->next = delete_Token(t);
4224 tline = t;
4226 if (!tline) {
4227 error(ERR_NONFATAL,
4228 "macro call expects terminating `)'");
4229 break;
4231 if (tline->type == TOK_WHITESPACE
4232 && brackets <= 0) {
4233 if (paramsize[nparam])
4234 white++;
4235 else
4236 params[nparam] = tline->next;
4237 continue; /* parameter loop */
4239 if (tline->type == TOK_OTHER
4240 && tline->text[1] == 0) {
4241 char ch = tline->text[0];
4242 if (ch == ',' && !paren && brackets <= 0) {
4243 if (++nparam >= sparam) {
4244 sparam += PARAM_DELTA;
4245 params = nasm_realloc(params,
4246 sparam * sizeof(Token *));
4247 paramsize = nasm_realloc(paramsize,
4248 sparam * sizeof(int));
4250 params[nparam] = tline->next;
4251 paramsize[nparam] = 0;
4252 white = 0;
4253 continue; /* parameter loop */
4255 if (ch == '{' &&
4256 (brackets > 0 || (brackets == 0 &&
4257 !paramsize[nparam])))
4259 if (!(brackets++)) {
4260 params[nparam] = tline->next;
4261 continue; /* parameter loop */
4264 if (ch == '}' && brackets > 0)
4265 if (--brackets == 0) {
4266 brackets = -1;
4267 continue; /* parameter loop */
4269 if (ch == '(' && !brackets)
4270 paren++;
4271 if (ch == ')' && brackets <= 0)
4272 if (--paren < 0)
4273 break;
4275 if (brackets < 0) {
4276 brackets = 0;
4277 error(ERR_NONFATAL, "braces do not "
4278 "enclose all of macro parameter");
4280 paramsize[nparam] += white + 1;
4281 white = 0;
4282 } /* parameter loop */
4283 nparam++;
4284 while (m && (m->nparam != nparam ||
4285 mstrcmp(m->name, mname,
4286 m->casesense)))
4287 m = m->next;
4288 if (!m)
4289 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4290 "macro `%s' exists, "
4291 "but not taking %d parameters",
4292 mstart->text, nparam);
4295 if (m && m->in_progress)
4296 m = NULL;
4297 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4299 * Design question: should we handle !tline, which
4300 * indicates missing ')' here, or expand those
4301 * macros anyway, which requires the (t) test a few
4302 * lines down?
4304 nasm_free(params);
4305 nasm_free(paramsize);
4306 tline = mstart;
4307 } else {
4309 * Expand the macro: we are placed on the last token of the
4310 * call, so that we can easily split the call from the
4311 * following tokens. We also start by pushing an SMAC_END
4312 * token for the cycle removal.
4314 t = tline;
4315 if (t) {
4316 tline = t->next;
4317 t->next = NULL;
4319 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4320 tt->a.mac = m;
4321 m->in_progress = true;
4322 tline = tt;
4323 list_for_each(t, m->expansion) {
4324 if (t->type >= TOK_SMAC_PARAM) {
4325 Token *pcopy = tline, **ptail = &pcopy;
4326 Token *ttt, *pt;
4327 int i;
4329 ttt = params[t->type - TOK_SMAC_PARAM];
4330 i = paramsize[t->type - TOK_SMAC_PARAM];
4331 while (--i >= 0) {
4332 pt = *ptail = new_Token(tline, ttt->type,
4333 ttt->text, 0);
4334 ptail = &pt->next;
4335 ttt = ttt->next;
4337 tline = pcopy;
4338 } else if (t->type == TOK_PREPROC_Q) {
4339 tt = new_Token(tline, TOK_ID, mname, 0);
4340 tline = tt;
4341 } else if (t->type == TOK_PREPROC_QQ) {
4342 tt = new_Token(tline, TOK_ID, m->name, 0);
4343 tline = tt;
4344 } else {
4345 tt = new_Token(tline, t->type, t->text, 0);
4346 tline = tt;
4351 * Having done that, get rid of the macro call, and clean
4352 * up the parameters.
4354 nasm_free(params);
4355 nasm_free(paramsize);
4356 free_tlist(mstart);
4357 expanded = true;
4358 continue; /* main token loop */
4363 if (tline->type == TOK_SMAC_END) {
4364 tline->a.mac->in_progress = false;
4365 tline = delete_Token(tline);
4366 } else {
4367 t = *tail = tline;
4368 tline = tline->next;
4369 t->a.mac = NULL;
4370 t->next = NULL;
4371 tail = &t->next;
4376 * Now scan the entire line and look for successive TOK_IDs that resulted
4377 * after expansion (they can't be produced by tokenize()). The successive
4378 * TOK_IDs should be concatenated.
4379 * Also we look for %+ tokens and concatenate the tokens before and after
4380 * them (without white spaces in between).
4382 if (expanded && paste_tokens(&thead, true)) {
4384 * If we concatenated something, *and* we had previously expanded
4385 * an actual macro, scan the lines again for macros...
4387 tline = thead;
4388 expanded = false;
4389 goto again;
4392 err:
4393 if (org_tline) {
4394 if (thead) {
4395 *org_tline = *thead;
4396 /* since we just gave text to org_line, don't free it */
4397 thead->text = NULL;
4398 delete_Token(thead);
4399 } else {
4400 /* the expression expanded to empty line;
4401 we can't return NULL for some reasons
4402 we just set the line to a single WHITESPACE token. */
4403 memset(org_tline, 0, sizeof(*org_tline));
4404 org_tline->text = NULL;
4405 org_tline->type = TOK_WHITESPACE;
4407 thead = org_tline;
4410 return thead;
4414 * Similar to expand_smacro but used exclusively with macro identifiers
4415 * right before they are fetched in. The reason is that there can be
4416 * identifiers consisting of several subparts. We consider that if there
4417 * are more than one element forming the name, user wants a expansion,
4418 * otherwise it will be left as-is. Example:
4420 * %define %$abc cde
4422 * the identifier %$abc will be left as-is so that the handler for %define
4423 * will suck it and define the corresponding value. Other case:
4425 * %define _%$abc cde
4427 * In this case user wants name to be expanded *before* %define starts
4428 * working, so we'll expand %$abc into something (if it has a value;
4429 * otherwise it will be left as-is) then concatenate all successive
4430 * PP_IDs into one.
4432 static Token *expand_id(Token * tline)
4434 Token *cur, *oldnext = NULL;
4436 if (!tline || !tline->next)
4437 return tline;
4439 cur = tline;
4440 while (cur->next &&
4441 (cur->next->type == TOK_ID ||
4442 cur->next->type == TOK_PREPROC_ID
4443 || cur->next->type == TOK_NUMBER))
4444 cur = cur->next;
4446 /* If identifier consists of just one token, don't expand */
4447 if (cur == tline)
4448 return tline;
4450 if (cur) {
4451 oldnext = cur->next; /* Detach the tail past identifier */
4452 cur->next = NULL; /* so that expand_smacro stops here */
4455 tline = expand_smacro(tline);
4457 if (cur) {
4458 /* expand_smacro possibly changhed tline; re-scan for EOL */
4459 cur = tline;
4460 while (cur && cur->next)
4461 cur = cur->next;
4462 if (cur)
4463 cur->next = oldnext;
4466 return tline;
4470 * Determine whether the given line constitutes a multi-line macro
4471 * call, and return the ExpDef structure called if so. Doesn't have
4472 * to check for an initial label - that's taken care of in
4473 * expand_mmacro - but must check numbers of parameters. Guaranteed
4474 * to be called with tline->type == TOK_ID, so the putative macro
4475 * name is easy to find.
4477 static ExpDef *is_mmacro(Token * tline, Token *** params_array)
4479 ExpDef *head, *ed;
4480 Token **params;
4481 int nparam;
4483 head = (ExpDef *) hash_findix(&expdefs, tline->text);
4486 * Efficiency: first we see if any macro exists with the given
4487 * name. If not, we can return NULL immediately. _Then_ we
4488 * count the parameters, and then we look further along the
4489 * list if necessary to find the proper ExpDef.
4491 list_for_each(ed, head)
4492 if (!mstrcmp(ed->name, tline->text, ed->casesense))
4493 break;
4494 if (!ed)
4495 return NULL;
4498 * OK, we have a potential macro. Count and demarcate the
4499 * parameters.
4501 count_mmac_params(tline->next, &nparam, &params);
4504 * So we know how many parameters we've got. Find the ExpDef
4505 * structure that handles this number.
4507 while (ed) {
4508 if (ed->nparam_min <= nparam
4509 && (ed->plus || nparam <= ed->nparam_max)) {
4511 * It's right, and we can use it. Add its default
4512 * parameters to the end of our list if necessary.
4514 if (ed->defaults && nparam < ed->nparam_min + ed->ndefs) {
4515 params =
4516 nasm_realloc(params,
4517 ((ed->nparam_min + ed->ndefs +
4518 1) * sizeof(*params)));
4519 while (nparam < ed->nparam_min + ed->ndefs) {
4520 params[nparam] = ed->defaults[nparam - ed->nparam_min];
4521 nparam++;
4525 * If we've gone over the maximum parameter count (and
4526 * we're in Plus mode), ignore parameters beyond
4527 * nparam_max.
4529 if (ed->plus && nparam > ed->nparam_max)
4530 nparam = ed->nparam_max;
4532 * Then terminate the parameter list, and leave.
4534 if (!params) { /* need this special case */
4535 params = nasm_malloc(sizeof(*params));
4536 nparam = 0;
4538 params[nparam] = NULL;
4539 *params_array = params;
4540 return ed;
4543 * This one wasn't right: look for the next one with the
4544 * same name.
4546 list_for_each(ed, ed->next)
4547 if (!mstrcmp(ed->name, tline->text, ed->casesense))
4548 break;
4552 * After all that, we didn't find one with the right number of
4553 * parameters. Issue a warning, and fail to expand the macro.
4555 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4556 "macro `%s' exists, but not taking %d parameters",
4557 tline->text, nparam);
4558 nasm_free(params);
4559 return NULL;
4563 * Expand the multi-line macro call made by the given line, if
4564 * there is one to be expanded. If there is, push the expansion on
4565 * istk->expansion and return 1. Otherwise return 0.
4567 static int expand_mmacro(Token * tline)
4569 Token *startline = tline;
4570 Token *label = NULL;
4571 int dont_prepend = 0;
4572 Token **params, *t, *mtok, *tt;
4573 Line *l;
4574 ExpDef *ed;
4575 ExpInv *ei;
4576 int i, nparam, *paramlen;
4577 const char *mname;
4579 t = tline;
4580 skip_white_(t);
4581 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4582 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4583 return 0;
4584 mtok = t;
4585 ed = is_mmacro(t, &params);
4586 if (ed != NULL) {
4587 mname = t->text;
4588 } else {
4589 Token *last;
4591 * We have an id which isn't a macro call. We'll assume
4592 * it might be a label; we'll also check to see if a
4593 * colon follows it. Then, if there's another id after
4594 * that lot, we'll check it again for macro-hood.
4596 label = last = t;
4597 t = t->next;
4598 if (tok_type_(t, TOK_WHITESPACE))
4599 last = t, t = t->next;
4600 if (tok_is_(t, ":")) {
4601 dont_prepend = 1;
4602 last = t, t = t->next;
4603 if (tok_type_(t, TOK_WHITESPACE))
4604 last = t, t = t->next;
4606 if (!tok_type_(t, TOK_ID) || !(ed = is_mmacro(t, &params)))
4607 return 0;
4608 last->next = NULL;
4609 mname = t->text;
4610 tline = t;
4614 * Fix up the parameters: this involves stripping leading and
4615 * trailing whitespace, then stripping braces if they are
4616 * present.
4618 for (nparam = 0; params[nparam]; nparam++) ;
4619 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4621 for (i = 0; params[i]; i++) {
4622 int brace = false;
4623 int comma = (!ed->plus || i < nparam - 1);
4625 t = params[i];
4626 skip_white_(t);
4627 if (tok_is_(t, "{"))
4628 t = t->next, brace = true, comma = false;
4629 params[i] = t;
4630 paramlen[i] = 0;
4631 while (t) {
4632 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4633 break; /* ... because we have hit a comma */
4634 if (comma && t->type == TOK_WHITESPACE
4635 && tok_is_(t->next, ","))
4636 break; /* ... or a space then a comma */
4637 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4638 break; /* ... or a brace */
4639 t = t->next;
4640 paramlen[i]++;
4644 if (ed->cur_depth >= ed->max_depth) {
4645 if (ed->max_depth > 1) {
4646 error(ERR_WARNING,
4647 "reached maximum macro recursion depth of %i for %s",
4648 ed->max_depth,ed->name);
4650 return 0;
4651 } else {
4652 ed->cur_depth ++;
4656 * OK, we have found a ExpDef structure representing a
4657 * previously defined mmacro. Create an expansion invocation
4658 * and point it back to the expansion definition. Substitution of
4659 * parameter tokens and macro-local tokens doesn't get done
4660 * until the single-line macro substitution process; this is
4661 * because delaying them allows us to change the semantics
4662 * later through %rotate.
4664 ei = new_ExpInv();
4665 ei->type = EXP_MMACRO;
4666 ei->def = ed;
4667 // ei->label = label;
4668 ei->label_text = detoken(label, false);
4669 ei->current = ed->line;
4670 ei->emitting = true;
4671 // ei->iline = tline;
4672 ei->params = params;
4673 ei->nparam = nparam;
4674 ei->rotate = 0;
4675 ei->paramlen = paramlen;
4676 ei->lineno = 0;
4678 ei->prev = istk->expansion;
4679 istk->expansion = ei;
4681 /***** todo: relocate %? (Q) and %?? (QQ); %00 already relocated *****/
4683 list_for_each(l, m->expansion) {
4684 Token **tail;
4686 l = new_Line();
4687 l->next = istk->expansion;
4688 istk->expansion = l;
4689 tail = &l->first;
4691 list_for_each(t, ei->current->first) {
4692 Token *x = t;
4693 switch (t->type) {
4694 case TOK_PREPROC_Q:
4695 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4696 break;
4697 case TOK_PREPROC_QQ:
4698 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4699 break;
4700 case TOK_PREPROC_ID:
4701 if (t->text[1] == '0' && t->text[2] == '0') {
4702 dont_prepend = -1;
4703 x = label;
4704 if (!x)
4705 continue;
4707 // fall through
4708 default:
4709 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4710 break;
4712 tail = &tt->next;
4714 *tail = NULL;
4718 * If we had a label, push it on as the first line of
4719 * the macro expansion.
4721 if (label) {
4722 if (dont_prepend < 0)
4723 free_tlist(startline);
4724 else {
4725 l = new_Line();
4726 ei->label = l;
4727 l->first = startline;
4728 if (!dont_prepend) {
4729 while (label->next)
4730 label = label->next;
4731 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4736 list->uplevel(ed->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4738 return 1;
4741 /* The function that actually does the error reporting */
4742 static void verror(int severity, const char *fmt, va_list arg)
4744 char buff[1024];
4746 vsnprintf(buff, sizeof(buff), fmt, arg);
4748 if ((istk != NULL) &&
4749 (istk->expansion != NULL) &&
4750 (istk->expansion->type == EXP_MMACRO)) {
4751 ExpDef *ed = istk->expansion->def;
4752 nasm_error(severity, "(%s:%d) %s", ed->name,
4753 istk->expansion->lineno, buff);
4754 } else {
4755 nasm_error(severity, "%s", buff);
4760 * Since preprocessor always operate only on the line that didn't
4761 * arrived yet, we should always use ERR_OFFBY1.
4763 static void error(int severity, const char *fmt, ...)
4765 va_list arg;
4767 /* If we're in a dead branch of IF or something like it, ignore the error */
4768 if ((istk != NULL) &&
4769 (istk->expansion != NULL) &&
4770 (istk->expansion->type == EXP_IF) &&
4771 !emitting(istk->expansion->def->state))
4772 return;
4774 va_start(arg, fmt);
4775 verror(severity, fmt, arg);
4776 va_end(arg);
4780 * Because %else etc are evaluated in the state context
4781 * of the previous branch, errors might get lost with error():
4782 * %if 0 ... %else trailing garbage ... %endif
4783 * So %else etc should report errors with this function.
4785 static void error_precond(int severity, const char *fmt, ...)
4787 va_list arg;
4789 /* Only ignore the error if it's really in a dead branch */
4790 if ((istk != NULL) &&
4791 (istk->expansion != NULL) &&
4792 (istk->expansion->type == EXP_IF) &&
4793 (istk->expansion->def->state == COND_NEVER))
4794 return;
4796 va_start(arg, fmt);
4797 verror(severity, fmt, arg);
4798 va_end(arg);
4801 static void
4802 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
4804 Token *t;
4806 cstk = NULL;
4807 istk = nasm_malloc(sizeof(Include));
4808 istk->next = NULL;
4809 istk->expansion = NULL;
4810 istk->fp = fopen(file, "r");
4811 istk->fname = NULL;
4812 src_set_fname(nasm_strdup(file));
4813 src_set_linnum(0);
4814 istk->lineinc = 1;
4815 if (!istk->fp)
4816 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
4817 file);
4818 defining = NULL;
4819 nested_mac_count = 0;
4820 nested_rep_count = 0;
4821 init_macros();
4822 unique = 0;
4823 if (tasm_compatible_mode) {
4824 stdmacpos = nasm_stdmac;
4825 } else {
4826 stdmacpos = nasm_stdmac_after_tasm;
4828 any_extrastdmac = extrastdmac && *extrastdmac;
4829 do_predef = true;
4830 list = listgen;
4833 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4834 * The caller, however, will also pass in 3 for preprocess-only so
4835 * we can set __PASS__ accordingly.
4837 pass = apass > 2 ? 2 : apass;
4839 dephead = deptail = deplist;
4840 if (deplist) {
4841 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
4842 sl->next = NULL;
4843 strcpy(sl->str, file);
4844 *deptail = sl;
4845 deptail = &sl->next;
4849 * Define the __PASS__ macro. This is defined here unlike
4850 * all the other builtins, because it is special -- it varies between
4851 * passes.
4853 t = nasm_malloc(sizeof(*t));
4854 t->next = NULL;
4855 make_tok_num(t, apass);
4856 t->a.mac = NULL;
4857 define_smacro(NULL, "__PASS__", true, 0, t);
4860 static char *pp_getline(void)
4862 char *line;
4863 Token *tline;
4865 while (1) {
4867 * Fetch a tokenized line, either from the expansion
4868 * buffer or from the input file.
4870 tline = NULL;
4872 while (1) { /* until we get a line we can use */
4874 * Fetch a tokenized line from the expansion buffer
4876 if (istk->expansion != NULL) {
4878 ExpInv *e = istk->expansion;
4879 if (e->current != NULL) {
4880 if (e->emitting == false) {
4881 e->current = NULL;
4882 continue;
4884 Line *l = NULL;
4885 l = e->current;
4886 e->current = l->next;
4887 e->lineno++;
4888 tline = copy_Token(l->first);
4889 if (((e->type == EXP_REP) || (e->type == EXP_MMACRO))
4890 && (e->def->nolist == false)) {
4891 char *p = detoken(tline, false);
4892 list->line(LIST_MACRO, p);
4893 nasm_free(p);
4895 break;
4896 } else if ((e->type == EXP_REP) &&
4897 (e->def->cur_depth < e->def->max_depth)) {
4898 e->def->cur_depth ++;
4899 e->current = e->def->line;
4900 e->lineno = 0;
4901 continue;
4902 } else {
4903 istk->expansion = e->prev;
4904 ExpDef *ed = e->def;
4905 if (ed != NULL) {
4906 if (ed->cur_depth > 0) {
4907 ed->cur_depth --;
4908 } else if ((ed->type != EXP_MMACRO) && (ed->type != EXP_IF)) {
4909 /***** should this really be right here??? *****/
4911 Line *l = NULL, *ll = NULL;
4912 for (l = ed->line; l != NULL;) {
4913 if (l->first != NULL) {
4914 free_tlist(l->first);
4915 l->first = NULL;
4917 ll = l;
4918 l = l->next;
4919 nasm_free(ll);
4921 expansions = ed->prev;
4922 nasm_free(ed);
4925 if ((e->type == EXP_REP) || (e->type == EXP_MMACRO)) {
4926 list->downlevel(LIST_MACRO);
4929 nasm_free(e);
4930 continue;
4935 * Read in line from input and tokenize
4937 line = read_line();
4938 if (line) { /* from the current input file */
4939 line = prepreproc(line);
4940 tline = tokenize(line);
4941 nasm_free(line);
4942 break;
4946 * The current file has ended; work down the istk
4949 Include *i = istk;
4950 fclose(i->fp);
4951 if (i->expansion != NULL) {
4952 error(ERR_FATAL,
4953 "end of file while still in an expansion");
4955 /* only set line and file name if there's a next node */
4956 if (i->next) {
4957 src_set_linnum(i->lineno);
4958 nasm_free(src_set_fname(i->fname));
4960 istk = i->next;
4961 list->downlevel(LIST_INCLUDE);
4962 nasm_free(i);
4963 if (istk == NULL) {
4964 return NULL;
4966 continue;
4970 if (defining == NULL) {
4971 tline = expand_mmac_params(tline);
4975 * Check the line to see if it's a preprocessor directive.
4977 if (do_directive(tline) == DIRECTIVE_FOUND) {
4978 continue;
4979 } else if (defining != NULL) {
4981 * We're defining an expansion. We emit nothing at all,
4982 * and just shove the tokenized line on to the definition.
4984 if (defining->ignoring == false) {
4985 Line *l = new_Line();
4986 l->first = tline;
4987 if (defining->line == NULL) {
4988 defining->line = l;
4989 defining->last = l;
4990 } else {
4991 defining->last->next = l;
4992 defining->last = l;
4994 } else {
4995 //free_tlist(tline); /***** sanity check: is this supposed to be here? *****/
4997 continue;
4998 } else if ((istk->expansion != NULL) &&
4999 (istk->expansion->emitting != true)) {
5001 * We're in a non-emitting branch of an expansion.
5002 * Emit nothing at all, not even a blank line: when we
5003 * emerge from the expansion we'll give a line-number
5004 * directive so we keep our place correctly.
5006 free_tlist(tline);
5007 continue;
5008 } else {
5009 tline = expand_smacro(tline);
5010 if (!expand_mmacro(tline)) {
5012 * De-tokenize the line again, and emit it.
5014 line = detoken(tline, true);
5015 free_tlist(tline);
5016 break;
5017 } else {
5018 continue; /* expand_mmacro calls free_tlist */
5022 return line;
5025 static void pp_cleanup(int pass)
5027 if (defining != NULL) {
5028 error(ERR_NONFATAL, "end of file while still defining an expansion");
5029 nasm_free(defining); /***** todo: free everything to avoid mem leaks *****/
5030 defining = NULL;
5032 while (cstk != NULL)
5033 ctx_pop();
5034 free_macros();
5035 while (istk != NULL) {
5036 Include *i = istk;
5037 istk = istk->next;
5038 fclose(i->fp);
5039 nasm_free(i->fname);
5040 nasm_free(i);
5042 while (cstk)
5043 ctx_pop();
5044 nasm_free(src_set_fname(NULL));
5045 if (pass == 0) {
5046 IncPath *i;
5047 free_llist(predef);
5048 delete_Blocks();
5049 while ((i = ipath)) {
5050 ipath = i->next;
5051 if (i->path)
5052 nasm_free(i->path);
5053 nasm_free(i);
5058 void pp_include_path(char *path)
5060 IncPath *i;
5062 i = nasm_malloc(sizeof(IncPath));
5063 i->path = path ? nasm_strdup(path) : NULL;
5064 i->next = NULL;
5066 if (ipath) {
5067 IncPath *j = ipath;
5068 while (j->next)
5069 j = j->next;
5070 j->next = i;
5071 } else {
5072 ipath = i;
5076 void pp_pre_include(char *fname)
5078 Token *inc, *space, *name;
5079 Line *l;
5081 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5082 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5083 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5085 l = new_Line();
5086 l->next = predef;
5087 l->first = inc;
5088 predef = l;
5091 void pp_pre_define(char *definition)
5093 Token *def, *space;
5094 Line *l;
5095 char *equals;
5097 equals = strchr(definition, '=');
5098 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5099 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5100 if (equals)
5101 *equals = ' ';
5102 space->next = tokenize(definition);
5103 if (equals)
5104 *equals = '=';
5106 l = new_Line();
5107 l->next = predef;
5108 l->first = def;
5109 predef = l;
5112 void pp_pre_undefine(char *definition)
5114 Token *def, *space;
5115 Line *l;
5117 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5118 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5119 space->next = tokenize(definition);
5121 l = new_Line();
5122 l->next = predef;
5123 l->first = def;
5124 predef = l;
5128 * This function is used to assist with "runtime" preprocessor
5129 * directives, e.g. pp_runtime("%define __BITS__ 64");
5131 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
5132 * PASS A VALID STRING TO THIS FUNCTION!!!!!
5135 void pp_runtime(char *definition)
5137 Token *def;
5139 def = tokenize(definition);
5140 if (do_directive(def) == NO_DIRECTIVE_FOUND)
5141 free_tlist(def);
5145 void pp_extra_stdmac(macros_t *macros)
5147 extrastdmac = macros;
5150 static void make_tok_num(Token * tok, int64_t val)
5152 char numbuf[20];
5153 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5154 tok->text = nasm_strdup(numbuf);
5155 tok->type = TOK_NUMBER;
5158 Preproc nasmpp = {
5159 pp_reset,
5160 pp_getline,
5161 pp_cleanup