preproc.c: fixed macro-relative line number handling for warning/error/fatal
[nasm.git] / preproc.c
blobbdaf45dc1bd33a023060d46759d15571625cb99a
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, EXP_WHILE,
189 EXP_COMMENT, EXP_FINAL,
190 EXP_MAX = INT_MAX /* Keep compiler from reducing the range */
194 * Store the definition of an expansion, in which is any
195 * preprocessor directive that has an ending pair.
197 * This design allows for arbitrary expansion/recursion depth,
198 * upto the DEADMAN_LIMIT.
200 * The `next' field is used for storing ExpDef in hash tables; the
201 * `prev' field is for the global `expansions` linked-list.
203 struct ExpDef {
204 ExpDef *prev; /* previous definition */
205 ExpDef *next; /* next in hash table */
206 enum pp_exp_type type; /* expansion type */
207 char *name;
208 int nparam_min, nparam_max;
209 bool casesense;
210 bool plus; /* is the last parameter greedy? */
211 bool nolist; /* is this expansion listing-inhibited? */
212 Token *dlist; /* all defaults as one list */
213 Token **defaults; /* parameter default pointers */
214 int ndefs; /* number of default parameters */
216 int prepend; /* label prepend state */
217 Line *label;
218 Line *line;
219 Line *last;
220 int linecount; /* number of lines within expansion */
222 uint32_t def_depth; /* current number of definition pairs deep */
223 uint32_t cur_depth; /* current number of expansions */
224 uint32_t max_depth; /* maximum number of expansions allowed */
226 int state; /* condition state */
227 bool ignoring; /* ignoring definition lines */
231 * Store the invocation of an expansion.
233 * The `prev' field is for the `istk->expansion` linked-list.
235 * When an expansion is being expanded, `params', `iline', `nparam',
236 * `paramlen', `rotate' and `unique' are local to the invocation.
238 struct ExpInv {
239 ExpInv *prev; /* previous invocation */
240 enum pp_exp_type type; /* expansion type */
241 ExpDef *def; /* pointer to expansion definition */
242 Line *label; /* pointer to label */
243 char *label_text; /* pointer to label text */
244 Line *current; /* pointer to current line in invocation */
246 Token **params; /* actual parameters */
247 Token *iline; /* invocation line */
248 unsigned int nparam, rotate;
249 int *paramlen;
251 uint64_t unique;
252 bool emitting;
253 int lineno; /* current line number in expansion */
254 int linnum; /* line number at invocation */
255 int relno; /* relative line number at invocation */
259 * To handle an arbitrary level of file inclusion, we maintain a
260 * stack (ie linked list) of these things.
262 struct Include {
263 Include *next;
264 FILE *fp;
265 Cond *conds;
266 ExpInv *expansion;
267 char *fname;
268 int lineno, lineinc;
269 int mmac_depth;
273 * Include search path. This is simply a list of strings which get
274 * prepended, in turn, to the name of an include file, in an
275 * attempt to find the file if it's not in the current directory.
277 struct IncPath {
278 IncPath *next;
279 char *path;
283 * Conditional assembly: we maintain a separate stack of these for
284 * each level of file inclusion. (The only reason we keep the
285 * stacks separate is to ensure that a stray `%endif' in a file
286 * included from within the true branch of a `%if' won't terminate
287 * it and cause confusion: instead, rightly, it'll cause an error.)
289 enum {
291 * These states are for use just after %if or %elif: IF_TRUE
292 * means the condition has evaluated to truth so we are
293 * currently emitting, whereas IF_FALSE means we are not
294 * currently emitting but will start doing so if a %else comes
295 * up. In these states, all directives are admissible: %elif,
296 * %else and %endif. (And of course %if.)
298 COND_IF_TRUE, COND_IF_FALSE,
300 * These states come up after a %else: ELSE_TRUE means we're
301 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
302 * any %elif or %else will cause an error.
304 COND_ELSE_TRUE, COND_ELSE_FALSE,
306 * These states mean that we're not emitting now, and also that
307 * nothing until %endif will be emitted at all. COND_DONE is
308 * used when we've had our moment of emission
309 * and have now started seeing %elifs. COND_NEVER is used when
310 * the condition construct in question is contained within a
311 * non-emitting branch of a larger condition construct,
312 * or if there is an error.
314 COND_DONE, COND_NEVER
316 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
319 * These defines are used as the possible return values for do_directive
321 #define NO_DIRECTIVE_FOUND 0
322 #define DIRECTIVE_FOUND 1
325 * This define sets the upper limit for smacro and expansions
327 #define DEADMAN_LIMIT (1 << 20)
330 * Condition codes. Note that we use c_ prefix not C_ because C_ is
331 * used in nasm.h for the "real" condition codes. At _this_ level,
332 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
333 * ones, so we need a different enum...
335 static const char * const conditions[] = {
336 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
337 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
338 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
340 enum pp_conds {
341 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
342 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
343 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
344 c_none = -1
346 static const enum pp_conds inverse_ccs[] = {
347 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
348 c_A, c_AE, c_B, c_BE, c_C, c_E, c_G, c_GE, c_L, c_LE, c_O, c_P, c_S,
349 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
352 /* For TASM compatibility we need to be able to recognise TASM compatible
353 * conditional compilation directives. Using the NASM pre-processor does
354 * not work, so we look for them specifically from the following list and
355 * then jam in the equivalent NASM directive into the input stream.
358 enum {
359 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
360 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
363 static const char * const tasm_directives[] = {
364 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
365 "ifndef", "include", "local"
368 static int StackSize = 4;
369 static char *StackPointer = "ebp";
370 static int ArgOffset = 8;
371 static int LocalOffset = 0;
373 static Context *cstk;
374 static Include *istk;
375 static IncPath *ipath = NULL;
377 static int pass; /* HACK: pass 0 = generate dependencies only */
378 static StrList **dephead, **deptail; /* Dependency list */
380 static uint64_t unique; /* unique identifier numbers */
382 static Line *predef = NULL;
383 static bool do_predef;
385 static ListGen *list;
388 * The current set of expansion definitions we have defined.
390 static struct hash_table expdefs;
393 * The current set of single-line macros we have defined.
395 static struct hash_table smacros;
398 * Linked List of all active expansion definitions
400 struct ExpDef *expansions = NULL;
403 * The expansion we are currently defining
405 static ExpDef *defining = NULL;
407 static uint64_t nested_mac_count;
408 static uint64_t nested_rep_count;
411 * Linked-list of lines to preprocess, prior to cleanup
413 static Line *finals = NULL;
414 static bool in_final = false;
417 * The number of macro parameters to allocate space for at a time.
419 #define PARAM_DELTA 16
422 * The standard macro set: defined in macros.c in the array nasm_stdmac.
423 * This gives our position in the macro set, when we're processing it.
425 static macros_t *stdmacpos;
428 * The extra standard macros that come from the object format, if
429 * any.
431 static macros_t *extrastdmac = NULL;
432 static bool any_extrastdmac;
435 * Tokens are allocated in blocks to improve speed
437 #define TOKEN_BLOCKSIZE 4096
438 static Token *freeTokens = NULL;
439 struct Blocks {
440 Blocks *next;
441 void *chunk;
444 static Blocks blocks = { NULL, NULL };
447 * Forward declarations.
449 static Token *expand_mmac_params(Token * tline);
450 static Token *expand_smacro(Token * tline);
451 static Token *expand_id(Token * tline);
452 static Context *get_ctx(const char *name, const char **namep,
453 bool all_contexts);
454 static void make_tok_num(Token * tok, int64_t val);
455 static void error(int severity, const char *fmt, ...);
456 static void error_precond(int severity, const char *fmt, ...);
457 static void *new_Block(size_t size);
458 static void delete_Blocks(void);
459 static Token *new_Token(Token * next, enum pp_token_type type,
460 const char *text, int txtlen);
461 static Token *copy_Token(Token * tline);
462 static Token *delete_Token(Token * t);
463 static Line *new_Line(void);
464 static ExpDef *new_ExpDef(int exp_type);
465 static ExpInv *new_ExpInv(int exp_type, ExpDef *ed);
468 * Macros for safe checking of token pointers, avoid *(NULL)
470 #define tok_type_(x,t) ((x) && (x)->type == (t))
471 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
472 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
473 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
476 * nasm_unquote with error if the string contains NUL characters.
477 * If the string contains NUL characters, issue an error and return
478 * the C len, i.e. truncate at the NUL.
480 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
482 size_t len = nasm_unquote(qstr, NULL);
483 size_t clen = strlen(qstr);
485 if (len != clen)
486 error(ERR_NONFATAL, "NUL character in `%s' directive",
487 pp_directives[directive]);
489 return clen;
493 * Handle TASM specific directives, which do not contain a % in
494 * front of them. We do it here because I could not find any other
495 * place to do it for the moment, and it is a hack (ideally it would
496 * be nice to be able to use the NASM pre-processor to do it).
498 static char *check_tasm_directive(char *line)
500 int32_t i, j, k, m, len;
501 char *p, *q, *oldline, oldchar;
503 p = nasm_skip_spaces(line);
505 /* Binary search for the directive name */
506 i = -1;
507 j = ARRAY_SIZE(tasm_directives);
508 q = nasm_skip_word(p);
509 len = q - p;
510 if (len) {
511 oldchar = p[len];
512 p[len] = 0;
513 while (j - i > 1) {
514 k = (j + i) / 2;
515 m = nasm_stricmp(p, tasm_directives[k]);
516 if (m == 0) {
517 /* We have found a directive, so jam a % in front of it
518 * so that NASM will then recognise it as one if it's own.
520 p[len] = oldchar;
521 len = strlen(p);
522 oldline = line;
523 line = nasm_malloc(len + 2);
524 line[0] = '%';
525 if (k == TM_IFDIFI) {
527 * NASM does not recognise IFDIFI, so we convert
528 * it to %if 0. This is not used in NASM
529 * compatible code, but does need to parse for the
530 * TASM macro package.
532 strcpy(line + 1, "if 0");
533 } else {
534 memcpy(line + 1, p, len + 1);
536 nasm_free(oldline);
537 return line;
538 } else if (m < 0) {
539 j = k;
540 } else
541 i = k;
543 p[len] = oldchar;
545 return line;
549 * The pre-preprocessing stage... This function translates line
550 * number indications as they emerge from GNU cpp (`# lineno "file"
551 * flags') into NASM preprocessor line number indications (`%line
552 * lineno file').
554 static char *prepreproc(char *line)
556 int lineno, fnlen;
557 char *fname, *oldline;
559 if (line[0] == '#' && line[1] == ' ') {
560 oldline = line;
561 fname = oldline + 2;
562 lineno = atoi(fname);
563 fname += strspn(fname, "0123456789 ");
564 if (*fname == '"')
565 fname++;
566 fnlen = strcspn(fname, "\"");
567 line = nasm_malloc(20 + fnlen);
568 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
569 nasm_free(oldline);
571 if (tasm_compatible_mode)
572 return check_tasm_directive(line);
573 return line;
577 * Free a linked list of tokens.
579 static void free_tlist(Token * list)
581 while (list)
582 list = delete_Token(list);
586 * Free a linked list of lines.
588 static void free_llist(Line * list)
590 Line *l, *tmp;
591 list_for_each_safe(l, tmp, list) {
592 free_tlist(l->first);
593 nasm_free(l);
598 * Free an ExpDef
600 static void free_expdef(ExpDef * ed)
602 nasm_free(ed->name);
603 free_tlist(ed->dlist);
604 nasm_free(ed->defaults);
605 free_llist(ed->line);
606 nasm_free(ed);
610 * Free all currently defined macros, and free the hash tables
612 static void free_smacro_table(struct hash_table *smt)
614 SMacro *s, *tmp;
615 const char *key;
616 struct hash_tbl_node *it = NULL;
618 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
619 nasm_free((void *)key);
620 list_for_each_safe(s, tmp, s) {
621 nasm_free(s->name);
622 free_tlist(s->expansion);
623 nasm_free(s);
626 hash_free(smt);
629 static void free_expdef_table(struct hash_table *edt)
631 ExpDef *ed, *tmp;
632 const char *key;
633 struct hash_tbl_node *it = NULL;
635 it = NULL;
636 while ((ed = hash_iterate(edt, &it, &key)) != NULL) {
637 nasm_free((void *)key);
638 list_for_each_safe(ed ,tmp, ed)
639 free_expdef(ed);
641 hash_free(edt);
644 static void free_macros(void)
646 free_smacro_table(&smacros);
647 free_expdef_table(&expdefs);
651 * Initialize the hash tables
653 static void init_macros(void)
655 hash_init(&smacros, HASH_LARGE);
656 hash_init(&expdefs, HASH_LARGE);
660 * Pop the context stack.
662 static void ctx_pop(void)
664 Context *c = cstk;
666 cstk = cstk->next;
667 free_smacro_table(&c->localmac);
668 nasm_free(c->name);
669 nasm_free(c);
673 * Search for a key in the hash index; adding it if necessary
674 * (in which case we initialize the data pointer to NULL.)
676 static void **
677 hash_findi_add(struct hash_table *hash, const char *str)
679 struct hash_insert hi;
680 void **r;
681 char *strx;
683 r = hash_findi(hash, str, &hi);
684 if (r)
685 return r;
687 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
688 return hash_add(&hi, strx, NULL);
692 * Like hash_findi, but returns the data element rather than a pointer
693 * to it. Used only when not adding a new element, hence no third
694 * argument.
696 static void *
697 hash_findix(struct hash_table *hash, const char *str)
699 void **p;
701 p = hash_findi(hash, str, NULL);
702 return p ? *p : NULL;
706 * read line from standard macros set,
707 * if there no more left -- return NULL
709 static char *line_from_stdmac(void)
711 unsigned char c;
712 const unsigned char *p = stdmacpos;
713 char *line, *q;
714 size_t len = 0;
716 if (!stdmacpos)
717 return NULL;
719 while ((c = *p++)) {
720 if (c >= 0x80)
721 len += pp_directives_len[c - 0x80] + 1;
722 else
723 len++;
726 line = nasm_malloc(len + 1);
727 q = line;
728 while ((c = *stdmacpos++)) {
729 if (c >= 0x80) {
730 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
731 q += pp_directives_len[c - 0x80];
732 *q++ = ' ';
733 } else {
734 *q++ = c;
737 stdmacpos = p;
738 *q = '\0';
740 if (!*stdmacpos) {
741 /* This was the last of the standard macro chain... */
742 stdmacpos = NULL;
743 if (any_extrastdmac) {
744 stdmacpos = extrastdmac;
745 any_extrastdmac = false;
746 } else if (do_predef) {
747 ExpInv *ei;
748 Line *pd, *l;
749 Token *head, **tail, *t;
752 * Nasty hack: here we push the contents of
753 * `predef' on to the top-level expansion stack,
754 * since this is the most convenient way to
755 * implement the pre-include and pre-define
756 * features.
758 list_for_each(pd, predef) {
759 head = NULL;
760 tail = &head;
761 list_for_each(t, pd->first) {
762 *tail = new_Token(NULL, t->type, t->text, 0);
763 tail = &(*tail)->next;
766 l = new_Line();
767 l->first = head;
768 ei = new_ExpInv(EXP_PREDEF, NULL);
769 ei->current = l;
770 ei->emitting = true;
771 ei->prev = istk->expansion;
772 istk->expansion = ei;
774 do_predef = false;
778 return line;
781 #define BUF_DELTA 512
783 * Read a line from the top file in istk, handling multiple CR/LFs
784 * at the end of the line read, and handling spurious ^Zs. Will
785 * return lines from the standard macro set if this has not already
786 * been done.
788 static char *read_line(void)
790 char *buffer, *p, *q;
791 int bufsize, continued_count;
794 * standart macros set (predefined) goes first
796 p = line_from_stdmac();
797 if (p)
798 return p;
801 * regular read from a file
803 bufsize = BUF_DELTA;
804 buffer = nasm_malloc(BUF_DELTA);
805 p = buffer;
806 continued_count = 0;
807 while (1) {
808 q = fgets(p, bufsize - (p - buffer), istk->fp);
809 if (!q)
810 break;
811 p += strlen(p);
812 if (p > buffer && p[-1] == '\n') {
814 * Convert backslash-CRLF line continuation sequences into
815 * nothing at all (for DOS and Windows)
817 if (((p - 2) > buffer) && (p[-3] == '\\') && (p[-2] == '\r')) {
818 p -= 3;
819 *p = 0;
820 continued_count++;
823 * Also convert backslash-LF line continuation sequences into
824 * nothing at all (for Unix)
826 else if (((p - 1) > buffer) && (p[-2] == '\\')) {
827 p -= 2;
828 *p = 0;
829 continued_count++;
830 } else {
831 break;
834 if (p - buffer > bufsize - 10) {
835 int32_t offset = p - buffer;
836 bufsize += BUF_DELTA;
837 buffer = nasm_realloc(buffer, bufsize);
838 p = buffer + offset; /* prevent stale-pointer problems */
842 if (!q && p == buffer) {
843 nasm_free(buffer);
844 return NULL;
847 src_set_linnum(src_get_linnum() + istk->lineinc +
848 (continued_count * istk->lineinc));
851 * Play safe: remove CRs as well as LFs, if any of either are
852 * present at the end of the line.
854 while (--p >= buffer && (*p == '\n' || *p == '\r'))
855 *p = '\0';
858 * Handle spurious ^Z, which may be inserted into source files
859 * by some file transfer utilities.
861 buffer[strcspn(buffer, "\032")] = '\0';
863 list->line(LIST_READ, buffer);
865 return buffer;
869 * Tokenize a line of text. This is a very simple process since we
870 * don't need to parse the value out of e.g. numeric tokens: we
871 * simply split one string into many.
873 static Token *tokenize(char *line)
875 char c, *p = line;
876 enum pp_token_type type;
877 Token *list = NULL;
878 Token *t, **tail = &list;
880 while (*line) {
881 p = line;
882 if (*p == '%') {
883 p++;
884 if (*p == '+' && !nasm_isdigit(p[1])) {
885 p++;
886 type = TOK_PASTE;
887 } else if (nasm_isdigit(*p) ||
888 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
889 do {
890 p++;
892 while (nasm_isdigit(*p));
893 type = TOK_PREPROC_ID;
894 } else if (*p == '{') {
895 p++;
896 while (*p && *p != '}') {
897 p[-1] = *p;
898 p++;
900 p[-1] = '\0';
901 if (*p)
902 p++;
903 type = TOK_PREPROC_ID;
904 } else if (*p == '[') {
905 int lvl = 1;
906 line += 2; /* Skip the leading %[ */
907 p++;
908 while (lvl && (c = *p++)) {
909 switch (c) {
910 case ']':
911 lvl--;
912 break;
913 case '%':
914 if (*p == '[')
915 lvl++;
916 break;
917 case '\'':
918 case '\"':
919 case '`':
920 p = nasm_skip_string(p - 1) + 1;
921 break;
922 default:
923 break;
926 p--;
927 if (*p)
928 *p++ = '\0';
929 if (lvl)
930 error(ERR_NONFATAL, "unterminated %[ construct");
931 type = TOK_INDIRECT;
932 } else if (*p == '?') {
933 type = TOK_PREPROC_Q; /* %? */
934 p++;
935 if (*p == '?') {
936 type = TOK_PREPROC_QQ; /* %?? */
937 p++;
939 } else if (*p == '!') {
940 type = TOK_PREPROC_ID;
941 p++;
942 if (isidchar(*p)) {
943 do {
944 p++;
946 while (isidchar(*p));
947 } else if (*p == '\'' || *p == '\"' || *p == '`') {
948 p = nasm_skip_string(p);
949 if (*p)
950 p++;
951 else
952 error(ERR_NONFATAL|ERR_PASS1, "unterminated %! string");
953 } else {
954 /* %! without string or identifier */
955 type = TOK_OTHER; /* Legacy behavior... */
957 } else if (isidchar(*p) ||
958 ((*p == '!' || *p == '%' || *p == '$') &&
959 isidchar(p[1]))) {
960 do {
961 p++;
963 while (isidchar(*p));
964 type = TOK_PREPROC_ID;
965 } else {
966 type = TOK_OTHER;
967 if (*p == '%')
968 p++;
970 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
971 type = TOK_ID;
972 p++;
973 while (*p && isidchar(*p))
974 p++;
975 } else if (*p == '\'' || *p == '"' || *p == '`') {
977 * A string token.
979 type = TOK_STRING;
980 p = nasm_skip_string(p);
982 if (*p) {
983 p++;
984 } else {
985 error(ERR_WARNING|ERR_PASS1, "unterminated string");
986 /* Handling unterminated strings by UNV */
987 /* type = -1; */
989 } else if (p[0] == '$' && p[1] == '$') {
990 type = TOK_OTHER; /* TOKEN_BASE */
991 p += 2;
992 } else if (isnumstart(*p)) {
993 bool is_hex = false;
994 bool is_float = false;
995 bool has_e = false;
996 char c, *r;
999 * A numeric token.
1002 if (*p == '$') {
1003 p++;
1004 is_hex = true;
1007 for (;;) {
1008 c = *p++;
1010 if (!is_hex && (c == 'e' || c == 'E')) {
1011 has_e = true;
1012 if (*p == '+' || *p == '-') {
1014 * e can only be followed by +/- if it is either a
1015 * prefixed hex number or a floating-point number
1017 p++;
1018 is_float = true;
1020 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1021 is_hex = true;
1022 } else if (c == 'P' || c == 'p') {
1023 is_float = true;
1024 if (*p == '+' || *p == '-')
1025 p++;
1026 } else if (isnumchar(c) || c == '_')
1027 ; /* just advance */
1028 else if (c == '.') {
1030 * we need to deal with consequences of the legacy
1031 * parser, like "1.nolist" being two tokens
1032 * (TOK_NUMBER, TOK_ID) here; at least give it
1033 * a shot for now. In the future, we probably need
1034 * a flex-based scanner with proper pattern matching
1035 * to do it as well as it can be done. Nothing in
1036 * the world is going to help the person who wants
1037 * 0x123.p16 interpreted as two tokens, though.
1039 r = p;
1040 while (*r == '_')
1041 r++;
1043 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1044 (!is_hex && (*r == 'e' || *r == 'E')) ||
1045 (*r == 'p' || *r == 'P')) {
1046 p = r;
1047 is_float = true;
1048 } else
1049 break; /* Terminate the token */
1050 } else
1051 break;
1053 p--; /* Point to first character beyond number */
1055 if (p == line+1 && *line == '$') {
1056 type = TOK_OTHER; /* TOKEN_HERE */
1057 } else {
1058 if (has_e && !is_hex) {
1059 /* 1e13 is floating-point, but 1e13h is not */
1060 is_float = true;
1063 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1065 } else if (nasm_isspace(*p)) {
1066 type = TOK_WHITESPACE;
1067 p = nasm_skip_spaces(p);
1069 * Whitespace just before end-of-line is discarded by
1070 * pretending it's a comment; whitespace just before a
1071 * comment gets lumped into the comment.
1073 if (!*p || *p == ';') {
1074 type = TOK_COMMENT;
1075 while (*p)
1076 p++;
1078 } else if (*p == ';') {
1079 type = TOK_COMMENT;
1080 while (*p)
1081 p++;
1082 } else {
1084 * Anything else is an operator of some kind. We check
1085 * for all the double-character operators (>>, <<, //,
1086 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1087 * else is a single-character operator.
1089 type = TOK_OTHER;
1090 if ((p[0] == '>' && p[1] == '>') ||
1091 (p[0] == '<' && p[1] == '<') ||
1092 (p[0] == '/' && p[1] == '/') ||
1093 (p[0] == '<' && p[1] == '=') ||
1094 (p[0] == '>' && p[1] == '=') ||
1095 (p[0] == '=' && p[1] == '=') ||
1096 (p[0] == '!' && p[1] == '=') ||
1097 (p[0] == '<' && p[1] == '>') ||
1098 (p[0] == '&' && p[1] == '&') ||
1099 (p[0] == '|' && p[1] == '|') ||
1100 (p[0] == '^' && p[1] == '^')) {
1101 p++;
1103 p++;
1106 /* Handling unterminated string by UNV */
1107 /*if (type == -1)
1109 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1110 t->text[p-line] = *line;
1111 tail = &t->next;
1113 else */
1114 if (type != TOK_COMMENT) {
1115 *tail = t = new_Token(NULL, type, line, p - line);
1116 tail = &t->next;
1118 line = p;
1120 return list;
1124 * this function allocates a new managed block of memory and
1125 * returns a pointer to the block. The managed blocks are
1126 * deleted only all at once by the delete_Blocks function.
1128 static void *new_Block(size_t size)
1130 Blocks *b = &blocks;
1132 /* first, get to the end of the linked list */
1133 while (b->next)
1134 b = b->next;
1135 /* now allocate the requested chunk */
1136 b->chunk = nasm_malloc(size);
1138 /* now allocate a new block for the next request */
1139 b->next = nasm_malloc(sizeof(Blocks));
1140 /* and initialize the contents of the new block */
1141 b->next->next = NULL;
1142 b->next->chunk = NULL;
1143 return b->chunk;
1147 * this function deletes all managed blocks of memory
1149 static void delete_Blocks(void)
1151 Blocks *a, *b = &blocks;
1154 * keep in mind that the first block, pointed to by blocks
1155 * is a static and not dynamically allocated, so we don't
1156 * free it.
1158 while (b) {
1159 if (b->chunk)
1160 nasm_free(b->chunk);
1161 a = b;
1162 b = b->next;
1163 if (a != &blocks)
1164 nasm_free(a);
1169 * this function creates a new Token and passes a pointer to it
1170 * back to the caller. It sets the type and text elements, and
1171 * also the a.mac and next elements to NULL.
1173 static Token *new_Token(Token * next, enum pp_token_type type,
1174 const char *text, int txtlen)
1176 Token *t;
1177 int i;
1179 if (!freeTokens) {
1180 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1181 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1182 freeTokens[i].next = &freeTokens[i + 1];
1183 freeTokens[i].next = NULL;
1185 t = freeTokens;
1186 freeTokens = t->next;
1187 t->next = next;
1188 t->a.mac = NULL;
1189 t->type = type;
1190 if (type == TOK_WHITESPACE || !text) {
1191 t->text = NULL;
1192 } else {
1193 if (txtlen == 0)
1194 txtlen = strlen(text);
1195 t->text = nasm_malloc(txtlen+1);
1196 memcpy(t->text, text, txtlen);
1197 t->text[txtlen] = '\0';
1199 return t;
1202 static Token *copy_Token(Token * tline)
1204 Token *t, *tt, *first = NULL, *prev = NULL;
1205 int i;
1206 for (tt = tline; tt != NULL; tt = tt->next) {
1207 if (!freeTokens) {
1208 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1209 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1210 freeTokens[i].next = &freeTokens[i + 1];
1211 freeTokens[i].next = NULL;
1213 t = freeTokens;
1214 freeTokens = t->next;
1215 t->next = NULL;
1216 t->text = ((tt->text != NULL) ? strdup(tt->text) : NULL);
1217 t->a.mac = tt->a.mac;
1218 t->a.len = tt->a.len;
1219 t->type = tt->type;
1220 if (prev != NULL) {
1221 prev->next = t;
1222 } else {
1223 first = t;
1225 prev = t;
1227 return first;
1230 static Token *delete_Token(Token * t)
1232 Token *next = t->next;
1233 nasm_free(t->text);
1234 t->next = freeTokens;
1235 freeTokens = t;
1236 return next;
1240 * Convert a line of tokens back into text.
1241 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1242 * will be transformed into ..@ctxnum.xxx
1244 static char *detoken(Token * tlist, bool expand_locals)
1246 Token *t;
1247 char *line, *p;
1248 const char *q;
1249 int len = 0;
1251 list_for_each(t, tlist) {
1252 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1253 char *v;
1254 char *q = t->text;
1256 v = t->text + 2;
1257 if (*v == '\'' || *v == '\"' || *v == '`') {
1258 size_t len = nasm_unquote(v, NULL);
1259 size_t clen = strlen(v);
1261 if (len != clen) {
1262 error(ERR_NONFATAL | ERR_PASS1,
1263 "NUL character in %! string");
1264 v = NULL;
1268 if (v) {
1269 char *p = getenv(v);
1270 if (!p) {
1271 error(ERR_NONFATAL | ERR_PASS1,
1272 "nonexistent environment variable `%s'", v);
1273 p = "";
1275 t->text = nasm_strdup(p);
1277 nasm_free(q);
1280 /* Expand local macros here and not during preprocessing */
1281 if (expand_locals &&
1282 t->type == TOK_PREPROC_ID && t->text &&
1283 t->text[0] == '%' && t->text[1] == '$') {
1284 const char *q;
1285 char *p;
1286 Context *ctx = get_ctx(t->text, &q, false);
1287 if (ctx) {
1288 char buffer[40];
1289 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1290 p = nasm_strcat(buffer, q);
1291 nasm_free(t->text);
1292 t->text = p;
1295 if (t->type == TOK_WHITESPACE)
1296 len++;
1297 else if (t->text)
1298 len += strlen(t->text);
1301 p = line = nasm_malloc(len + 1);
1303 list_for_each(t, tlist) {
1304 if (t->type == TOK_WHITESPACE) {
1305 *p++ = ' ';
1306 } else if (t->text) {
1307 q = t->text;
1308 while (*q)
1309 *p++ = *q++;
1312 *p = '\0';
1314 return line;
1318 * Initialize a new Line
1320 static Line *new_Line(void)
1322 Line *l = nasm_malloc(sizeof(Line));
1323 l->next = NULL;
1324 l->first = NULL;
1325 return l;
1330 * Initialize a new Expansion Definition
1332 static ExpDef *new_ExpDef(int exp_type)
1334 ExpDef *ed = nasm_malloc(sizeof(ExpDef));
1335 ed->prev = NULL;
1336 ed->next = NULL;
1337 ed->type = exp_type;
1338 ed->name = NULL;
1339 ed->nparam_min = 0;
1340 ed->nparam_max = 0;
1341 ed->casesense = true;
1342 ed->plus = false;
1343 ed->prepend = 0;
1344 ed->label = NULL;
1345 ed->line = NULL;
1346 ed->last = NULL;
1347 ed->linecount = 0;
1348 ed->dlist = NULL;
1349 ed->defaults = NULL;
1350 ed->ndefs = 0;
1351 ed->state = COND_NEVER;
1352 ed->nolist = false;
1353 ed->def_depth = 0;
1354 ed->cur_depth = 0;
1355 ed->max_depth = 0;
1356 ed->ignoring = false;
1357 return ed;
1362 * Initialize a new Expansion Instance
1364 static ExpInv *new_ExpInv(int exp_type, ExpDef *ed)
1366 unique ++;
1367 ExpInv *ei = nasm_malloc(sizeof(ExpInv));
1368 ei->prev = NULL;
1369 ei->type = exp_type;
1370 ei->def = ed;
1371 ei->label = NULL;
1372 ei->label_text = NULL;
1373 ei->current = NULL;
1374 ei->params = NULL;
1375 ei->iline = NULL;
1376 ei->nparam = 0;
1377 ei->rotate = 0;
1378 ei->paramlen = NULL;
1379 ei->unique = unique;
1380 ei->emitting = false;
1381 ei->lineno = 0;
1382 if ((istk->mmac_depth < 1) &&
1383 (istk->expansion == NULL) &&
1384 (ed != NULL) &&
1385 (ed->type != EXP_MMACRO) &&
1386 (ed->type != EXP_REP) &&
1387 (ed->type != EXP_WHILE)) {
1388 ei->linnum = src_get_linnum();
1389 src_set_linnum(ei->linnum - ed->linecount - 1);
1390 } else {
1391 ei->linnum = -1;
1393 if ((istk->expansion == NULL) ||
1394 (ei->type == EXP_MMACRO)) {
1395 ei->relno = 0;
1396 } else {
1397 ei->relno = istk->expansion->lineno;
1398 if (ed != NULL) {
1399 ei->relno -= (ed->linecount + 1);
1402 return ei;
1406 * A scanner, suitable for use by the expression evaluator, which
1407 * operates on a line of Tokens. Expects a pointer to a pointer to
1408 * the first token in the line to be passed in as its private_data
1409 * field.
1411 * FIX: This really needs to be unified with stdscan.
1413 static int ppscan(void *private_data, struct tokenval *tokval)
1415 Token **tlineptr = private_data;
1416 Token *tline;
1417 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1419 do {
1420 tline = *tlineptr;
1421 *tlineptr = tline ? tline->next : NULL;
1422 } while (tline && (tline->type == TOK_WHITESPACE ||
1423 tline->type == TOK_COMMENT));
1425 if (!tline)
1426 return tokval->t_type = TOKEN_EOS;
1428 tokval->t_charptr = tline->text;
1430 if (tline->text[0] == '$' && !tline->text[1])
1431 return tokval->t_type = TOKEN_HERE;
1432 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1433 return tokval->t_type = TOKEN_BASE;
1435 if (tline->type == TOK_ID) {
1436 p = tokval->t_charptr = tline->text;
1437 if (p[0] == '$') {
1438 tokval->t_charptr++;
1439 return tokval->t_type = TOKEN_ID;
1442 for (r = p, s = ourcopy; *r; r++) {
1443 if (r >= p+MAX_KEYWORD)
1444 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1445 *s++ = nasm_tolower(*r);
1447 *s = '\0';
1448 /* right, so we have an identifier sitting in temp storage. now,
1449 * is it actually a register or instruction name, or what? */
1450 return nasm_token_hash(ourcopy, tokval);
1453 if (tline->type == TOK_NUMBER) {
1454 bool rn_error;
1455 tokval->t_integer = readnum(tline->text, &rn_error);
1456 tokval->t_charptr = tline->text;
1457 if (rn_error)
1458 return tokval->t_type = TOKEN_ERRNUM;
1459 else
1460 return tokval->t_type = TOKEN_NUM;
1463 if (tline->type == TOK_FLOAT) {
1464 return tokval->t_type = TOKEN_FLOAT;
1467 if (tline->type == TOK_STRING) {
1468 char bq, *ep;
1470 bq = tline->text[0];
1471 tokval->t_charptr = tline->text;
1472 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1474 if (ep[0] != bq || ep[1] != '\0')
1475 return tokval->t_type = TOKEN_ERRSTR;
1476 else
1477 return tokval->t_type = TOKEN_STR;
1480 if (tline->type == TOK_OTHER) {
1481 if (!strcmp(tline->text, "<<"))
1482 return tokval->t_type = TOKEN_SHL;
1483 if (!strcmp(tline->text, ">>"))
1484 return tokval->t_type = TOKEN_SHR;
1485 if (!strcmp(tline->text, "//"))
1486 return tokval->t_type = TOKEN_SDIV;
1487 if (!strcmp(tline->text, "%%"))
1488 return tokval->t_type = TOKEN_SMOD;
1489 if (!strcmp(tline->text, "=="))
1490 return tokval->t_type = TOKEN_EQ;
1491 if (!strcmp(tline->text, "<>"))
1492 return tokval->t_type = TOKEN_NE;
1493 if (!strcmp(tline->text, "!="))
1494 return tokval->t_type = TOKEN_NE;
1495 if (!strcmp(tline->text, "<="))
1496 return tokval->t_type = TOKEN_LE;
1497 if (!strcmp(tline->text, ">="))
1498 return tokval->t_type = TOKEN_GE;
1499 if (!strcmp(tline->text, "&&"))
1500 return tokval->t_type = TOKEN_DBL_AND;
1501 if (!strcmp(tline->text, "^^"))
1502 return tokval->t_type = TOKEN_DBL_XOR;
1503 if (!strcmp(tline->text, "||"))
1504 return tokval->t_type = TOKEN_DBL_OR;
1508 * We have no other options: just return the first character of
1509 * the token text.
1511 return tokval->t_type = tline->text[0];
1515 * Compare a string to the name of an existing macro; this is a
1516 * simple wrapper which calls either strcmp or nasm_stricmp
1517 * depending on the value of the `casesense' parameter.
1519 static int mstrcmp(const char *p, const char *q, bool casesense)
1521 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1525 * Compare a string to the name of an existing macro; this is a
1526 * simple wrapper which calls either strcmp or nasm_stricmp
1527 * depending on the value of the `casesense' parameter.
1529 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1531 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1535 * Return the Context structure associated with a %$ token. Return
1536 * NULL, having _already_ reported an error condition, if the
1537 * context stack isn't deep enough for the supplied number of $
1538 * signs.
1539 * If all_contexts == true, contexts that enclose current are
1540 * also scanned for such smacro, until it is found; if not -
1541 * only the context that directly results from the number of $'s
1542 * in variable's name.
1544 * If "namep" is non-NULL, set it to the pointer to the macro name
1545 * tail, i.e. the part beyond %$...
1547 static Context *get_ctx(const char *name, const char **namep,
1548 bool all_contexts)
1550 Context *ctx;
1551 SMacro *m;
1552 int i;
1554 if (namep)
1555 *namep = name;
1557 if (!name || name[0] != '%' || name[1] != '$')
1558 return NULL;
1560 if (!cstk) {
1561 error(ERR_NONFATAL, "`%s': context stack is empty", name);
1562 return NULL;
1565 name += 2;
1566 ctx = cstk;
1567 i = 0;
1568 while (ctx && *name == '$') {
1569 name++;
1570 i++;
1571 ctx = ctx->next;
1573 if (!ctx) {
1574 error(ERR_NONFATAL, "`%s': context stack is only"
1575 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1576 return NULL;
1579 if (namep)
1580 *namep = name;
1582 if (!all_contexts)
1583 return ctx;
1585 do {
1586 /* Search for this smacro in found context */
1587 m = hash_findix(&ctx->localmac, name);
1588 while (m) {
1589 if (!mstrcmp(m->name, name, m->casesense))
1590 return ctx;
1591 m = m->next;
1593 ctx = ctx->next;
1595 while (ctx);
1596 return NULL;
1600 * Check to see if a file is already in a string list
1602 static bool in_list(const StrList *list, const char *str)
1604 while (list) {
1605 if (!strcmp(list->str, str))
1606 return true;
1607 list = list->next;
1609 return false;
1613 * Open an include file. This routine must always return a valid
1614 * file pointer if it returns - it's responsible for throwing an
1615 * ERR_FATAL and bombing out completely if not. It should also try
1616 * the include path one by one until it finds the file or reaches
1617 * the end of the path.
1619 static FILE *inc_fopen(const char *file, StrList **dhead, StrList ***dtail,
1620 bool missing_ok)
1622 FILE *fp;
1623 char *prefix = "";
1624 IncPath *ip = ipath;
1625 int len = strlen(file);
1626 size_t prefix_len = 0;
1627 StrList *sl;
1629 while (1) {
1630 sl = nasm_malloc(prefix_len+len+1+sizeof sl->next);
1631 memcpy(sl->str, prefix, prefix_len);
1632 memcpy(sl->str+prefix_len, file, len+1);
1633 fp = fopen(sl->str, "r");
1634 if (fp && dhead && !in_list(*dhead, sl->str)) {
1635 sl->next = NULL;
1636 **dtail = sl;
1637 *dtail = &sl->next;
1638 } else {
1639 nasm_free(sl);
1641 if (fp)
1642 return fp;
1643 if (!ip) {
1644 if (!missing_ok)
1645 break;
1646 prefix = NULL;
1647 } else {
1648 prefix = ip->path;
1649 ip = ip->next;
1651 if (prefix) {
1652 prefix_len = strlen(prefix);
1653 } else {
1654 /* -MG given and file not found */
1655 if (dhead && !in_list(*dhead, file)) {
1656 sl = nasm_malloc(len+1+sizeof sl->next);
1657 sl->next = NULL;
1658 strcpy(sl->str, file);
1659 **dtail = sl;
1660 *dtail = &sl->next;
1662 return NULL;
1666 error(ERR_FATAL, "unable to open include file `%s'", file);
1667 return NULL;
1671 * Determine if we should warn on defining a single-line macro of
1672 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1673 * return true if _any_ single-line macro of that name is defined.
1674 * Otherwise, will return true if a single-line macro with either
1675 * `nparam' or no parameters is defined.
1677 * If a macro with precisely the right number of parameters is
1678 * defined, or nparam is -1, the address of the definition structure
1679 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1680 * is NULL, no action will be taken regarding its contents, and no
1681 * error will occur.
1683 * Note that this is also called with nparam zero to resolve
1684 * `ifdef'.
1686 * If you already know which context macro belongs to, you can pass
1687 * the context pointer as first parameter; if you won't but name begins
1688 * with %$ the context will be automatically computed. If all_contexts
1689 * is true, macro will be searched in outer contexts as well.
1691 static bool
1692 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1693 bool nocase)
1695 struct hash_table *smtbl;
1696 SMacro *m;
1698 if (ctx) {
1699 smtbl = &ctx->localmac;
1700 } else if (name[0] == '%' && name[1] == '$') {
1701 if (cstk)
1702 ctx = get_ctx(name, &name, false);
1703 if (!ctx)
1704 return false; /* got to return _something_ */
1705 smtbl = &ctx->localmac;
1706 } else {
1707 smtbl = &smacros;
1709 m = (SMacro *) hash_findix(smtbl, name);
1711 while (m) {
1712 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1713 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1714 if (defn) {
1715 if (nparam == (int) m->nparam || nparam == -1)
1716 *defn = m;
1717 else
1718 *defn = NULL;
1720 return true;
1722 m = m->next;
1725 return false;
1729 * Count and mark off the parameters in a multi-line macro call.
1730 * This is called both from within the multi-line macro expansion
1731 * code, and also to mark off the default parameters when provided
1732 * in a %macro definition line.
1734 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1736 int paramsize, brace;
1738 *nparam = paramsize = 0;
1739 *params = NULL;
1740 while (t) {
1741 /* +1: we need space for the final NULL */
1742 if (*nparam+1 >= paramsize) {
1743 paramsize += PARAM_DELTA;
1744 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1746 skip_white_(t);
1747 brace = false;
1748 if (tok_is_(t, "{"))
1749 brace = true;
1750 (*params)[(*nparam)++] = t;
1751 while (tok_isnt_(t, brace ? "}" : ","))
1752 t = t->next;
1753 if (t) { /* got a comma/brace */
1754 t = t->next;
1755 if (brace) {
1757 * Now we've found the closing brace, look further
1758 * for the comma.
1760 skip_white_(t);
1761 if (tok_isnt_(t, ",")) {
1762 error(ERR_NONFATAL,
1763 "braces do not enclose all of macro parameter");
1764 while (tok_isnt_(t, ","))
1765 t = t->next;
1767 if (t)
1768 t = t->next; /* eat the comma */
1775 * Determine whether one of the various `if' conditions is true or
1776 * not.
1778 * We must free the tline we get passed.
1780 static bool if_condition(Token * tline, enum preproc_token ct)
1782 enum pp_conditional i = PP_COND(ct);
1783 bool j;
1784 Token *t, *tt, **tptr, *origline;
1785 struct tokenval tokval;
1786 expr *evalresult;
1787 enum pp_token_type needtype;
1788 char *p;
1790 origline = tline;
1792 switch (i) {
1793 case PPC_IFCTX:
1794 j = false; /* have we matched yet? */
1795 while (true) {
1796 skip_white_(tline);
1797 if (!tline)
1798 break;
1799 if (tline->type != TOK_ID) {
1800 error(ERR_NONFATAL,
1801 "`%s' expects context identifiers", pp_directives[ct]);
1802 free_tlist(origline);
1803 return -1;
1805 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1806 j = true;
1807 tline = tline->next;
1809 break;
1811 case PPC_IFDEF:
1812 j = false; /* have we matched yet? */
1813 while (tline) {
1814 skip_white_(tline);
1815 if (!tline || (tline->type != TOK_ID &&
1816 (tline->type != TOK_PREPROC_ID ||
1817 tline->text[1] != '$'))) {
1818 error(ERR_NONFATAL,
1819 "`%s' expects macro identifiers", pp_directives[ct]);
1820 goto fail;
1822 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1823 j = true;
1824 tline = tline->next;
1826 break;
1828 case PPC_IFENV:
1829 tline = expand_smacro(tline);
1830 j = false; /* have we matched yet? */
1831 while (tline) {
1832 skip_white_(tline);
1833 if (!tline || (tline->type != TOK_ID &&
1834 tline->type != TOK_STRING &&
1835 (tline->type != TOK_PREPROC_ID ||
1836 tline->text[1] != '!'))) {
1837 error(ERR_NONFATAL,
1838 "`%s' expects environment variable names",
1839 pp_directives[ct]);
1840 goto fail;
1842 p = tline->text;
1843 if (tline->type == TOK_PREPROC_ID)
1844 p += 2; /* Skip leading %! */
1845 if (*p == '\'' || *p == '\"' || *p == '`')
1846 nasm_unquote_cstr(p, ct);
1847 if (getenv(p))
1848 j = true;
1849 tline = tline->next;
1851 break;
1853 case PPC_IFIDN:
1854 case PPC_IFIDNI:
1855 tline = expand_smacro(tline);
1856 t = tt = tline;
1857 while (tok_isnt_(tt, ","))
1858 tt = tt->next;
1859 if (!tt) {
1860 error(ERR_NONFATAL,
1861 "`%s' expects two comma-separated arguments",
1862 pp_directives[ct]);
1863 goto fail;
1865 tt = tt->next;
1866 j = true; /* assume equality unless proved not */
1867 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1868 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1869 error(ERR_NONFATAL, "`%s': more than one comma on line",
1870 pp_directives[ct]);
1871 goto fail;
1873 if (t->type == TOK_WHITESPACE) {
1874 t = t->next;
1875 continue;
1877 if (tt->type == TOK_WHITESPACE) {
1878 tt = tt->next;
1879 continue;
1881 if (tt->type != t->type) {
1882 j = false; /* found mismatching tokens */
1883 break;
1885 /* When comparing strings, need to unquote them first */
1886 if (t->type == TOK_STRING) {
1887 size_t l1 = nasm_unquote(t->text, NULL);
1888 size_t l2 = nasm_unquote(tt->text, NULL);
1890 if (l1 != l2) {
1891 j = false;
1892 break;
1894 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1895 j = false;
1896 break;
1898 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1899 j = false; /* found mismatching tokens */
1900 break;
1903 t = t->next;
1904 tt = tt->next;
1906 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1907 j = false; /* trailing gunk on one end or other */
1908 break;
1910 case PPC_IFMACRO:
1912 bool found = false;
1913 ExpDef searching, *ed;
1915 skip_white_(tline);
1916 tline = expand_id(tline);
1917 if (!tok_type_(tline, TOK_ID)) {
1918 error(ERR_NONFATAL,
1919 "`%s' expects a macro name", pp_directives[ct]);
1920 goto fail;
1922 searching.name = nasm_strdup(tline->text);
1923 searching.casesense = true;
1924 searching.plus = false;
1925 searching.nolist = false;
1926 //searching.in_progress = 0;
1927 searching.max_depth = 0;
1928 //searching.rep_nest = NULL;
1929 searching.nparam_min = 0;
1930 searching.nparam_max = INT_MAX;
1931 tline = expand_smacro(tline->next);
1932 skip_white_(tline);
1933 if (!tline) {
1934 } else if (!tok_type_(tline, TOK_NUMBER)) {
1935 error(ERR_NONFATAL,
1936 "`%s' expects a parameter count or nothing",
1937 pp_directives[ct]);
1938 } else {
1939 searching.nparam_min = searching.nparam_max =
1940 readnum(tline->text, &j);
1941 if (j)
1942 error(ERR_NONFATAL,
1943 "unable to parse parameter count `%s'",
1944 tline->text);
1946 if (tline && tok_is_(tline->next, "-")) {
1947 tline = tline->next->next;
1948 if (tok_is_(tline, "*"))
1949 searching.nparam_max = INT_MAX;
1950 else if (!tok_type_(tline, TOK_NUMBER))
1951 error(ERR_NONFATAL,
1952 "`%s' expects a parameter count after `-'",
1953 pp_directives[ct]);
1954 else {
1955 searching.nparam_max = readnum(tline->text, &j);
1956 if (j)
1957 error(ERR_NONFATAL,
1958 "unable to parse parameter count `%s'",
1959 tline->text);
1960 if (searching.nparam_min > searching.nparam_max)
1961 error(ERR_NONFATAL,
1962 "minimum parameter count exceeds maximum");
1965 if (tline && tok_is_(tline->next, "+")) {
1966 tline = tline->next;
1967 searching.plus = true;
1969 ed = (ExpDef *) hash_findix(&expdefs, searching.name);
1970 while (ed != NULL) {
1971 if (!strcmp(ed->name, searching.name) &&
1972 (ed->nparam_min <= searching.nparam_max
1973 || searching.plus)
1974 && (searching.nparam_min <= ed->nparam_max
1975 || ed->plus)) {
1976 found = true;
1977 break;
1979 ed = ed->next;
1981 if (tline && tline->next)
1982 error(ERR_WARNING|ERR_PASS1,
1983 "trailing garbage after %%ifmacro ignored");
1984 nasm_free(searching.name);
1985 j = found;
1986 break;
1989 case PPC_IFID:
1990 needtype = TOK_ID;
1991 goto iftype;
1992 case PPC_IFNUM:
1993 needtype = TOK_NUMBER;
1994 goto iftype;
1995 case PPC_IFSTR:
1996 needtype = TOK_STRING;
1997 goto iftype;
1999 iftype:
2000 t = tline = expand_smacro(tline);
2002 while (tok_type_(t, TOK_WHITESPACE) ||
2003 (needtype == TOK_NUMBER &&
2004 tok_type_(t, TOK_OTHER) &&
2005 (t->text[0] == '-' || t->text[0] == '+') &&
2006 !t->text[1]))
2007 t = t->next;
2009 j = tok_type_(t, needtype);
2010 break;
2012 case PPC_IFTOKEN:
2013 t = tline = expand_smacro(tline);
2014 while (tok_type_(t, TOK_WHITESPACE))
2015 t = t->next;
2017 j = false;
2018 if (t) {
2019 t = t->next; /* Skip the actual token */
2020 while (tok_type_(t, TOK_WHITESPACE))
2021 t = t->next;
2022 j = !t; /* Should be nothing left */
2024 break;
2026 case PPC_IFEMPTY:
2027 t = tline = expand_smacro(tline);
2028 while (tok_type_(t, TOK_WHITESPACE))
2029 t = t->next;
2031 j = !t; /* Should be empty */
2032 break;
2034 case PPC_IF:
2035 t = tline = expand_smacro(tline);
2036 tptr = &t;
2037 tokval.t_type = TOKEN_INVALID;
2038 evalresult = evaluate(ppscan, tptr, &tokval,
2039 NULL, pass | CRITICAL, error, NULL);
2040 if (!evalresult)
2041 return -1;
2042 if (tokval.t_type)
2043 error(ERR_WARNING|ERR_PASS1,
2044 "trailing garbage after expression ignored");
2045 if (!is_simple(evalresult)) {
2046 error(ERR_NONFATAL,
2047 "non-constant value given to `%s'", pp_directives[ct]);
2048 goto fail;
2050 j = reloc_value(evalresult) != 0;
2051 break;
2053 default:
2054 error(ERR_FATAL,
2055 "preprocessor directive `%s' not yet implemented",
2056 pp_directives[ct]);
2057 goto fail;
2060 free_tlist(origline);
2061 return j ^ PP_NEGATIVE(ct);
2063 fail:
2064 free_tlist(origline);
2065 return -1;
2069 * Common code for defining an smacro
2071 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2072 int nparam, Token *expansion)
2074 SMacro *smac, **smhead;
2075 struct hash_table *smtbl;
2077 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2078 if (!smac) {
2079 error(ERR_WARNING|ERR_PASS1,
2080 "single-line macro `%s' defined both with and"
2081 " without parameters", mname);
2083 * Some instances of the old code considered this a failure,
2084 * some others didn't. What is the right thing to do here?
2086 free_tlist(expansion);
2087 return false; /* Failure */
2088 } else {
2090 * We're redefining, so we have to take over an
2091 * existing SMacro structure. This means freeing
2092 * what was already in it.
2094 nasm_free(smac->name);
2095 free_tlist(smac->expansion);
2097 } else {
2098 smtbl = ctx ? &ctx->localmac : &smacros;
2099 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2100 smac = nasm_malloc(sizeof(SMacro));
2101 smac->next = *smhead;
2102 *smhead = smac;
2104 smac->name = nasm_strdup(mname);
2105 smac->casesense = casesense;
2106 smac->nparam = nparam;
2107 smac->expansion = expansion;
2108 smac->in_progress = false;
2109 return true; /* Success */
2113 * Undefine an smacro
2115 static void undef_smacro(Context *ctx, const char *mname)
2117 SMacro **smhead, *s, **sp;
2118 struct hash_table *smtbl;
2120 smtbl = ctx ? &ctx->localmac : &smacros;
2121 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2123 if (smhead) {
2125 * We now have a macro name... go hunt for it.
2127 sp = smhead;
2128 while ((s = *sp) != NULL) {
2129 if (!mstrcmp(s->name, mname, s->casesense)) {
2130 *sp = s->next;
2131 nasm_free(s->name);
2132 free_tlist(s->expansion);
2133 nasm_free(s);
2134 } else {
2135 sp = &s->next;
2142 * Parse a mmacro specification.
2144 static bool parse_mmacro_spec(Token *tline, ExpDef *def, const char *directive)
2146 bool err;
2148 tline = tline->next;
2149 skip_white_(tline);
2150 tline = expand_id(tline);
2151 if (!tok_type_(tline, TOK_ID)) {
2152 error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2153 return false;
2156 def->name = nasm_strdup(tline->text);
2157 def->plus = false;
2158 def->nolist = false;
2159 // def->in_progress = 0;
2160 // def->rep_nest = NULL;
2161 def->nparam_min = 0;
2162 def->nparam_max = 0;
2164 tline = expand_smacro(tline->next);
2165 skip_white_(tline);
2166 if (!tok_type_(tline, TOK_NUMBER)) {
2167 error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2168 } else {
2169 def->nparam_min = def->nparam_max =
2170 readnum(tline->text, &err);
2171 if (err)
2172 error(ERR_NONFATAL,
2173 "unable to parse parameter count `%s'", tline->text);
2175 if (tline && tok_is_(tline->next, "-")) {
2176 tline = tline->next->next;
2177 if (tok_is_(tline, "*")) {
2178 def->nparam_max = INT_MAX;
2179 } else if (!tok_type_(tline, TOK_NUMBER)) {
2180 error(ERR_NONFATAL,
2181 "`%s' expects a parameter count after `-'", directive);
2182 } else {
2183 def->nparam_max = readnum(tline->text, &err);
2184 if (err) {
2185 error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2186 tline->text);
2188 if (def->nparam_min > def->nparam_max) {
2189 error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2193 if (tline && tok_is_(tline->next, "+")) {
2194 tline = tline->next;
2195 def->plus = true;
2197 if (tline && tok_type_(tline->next, TOK_ID) &&
2198 !nasm_stricmp(tline->next->text, ".nolist")) {
2199 tline = tline->next;
2200 def->nolist = true;
2204 * Handle default parameters.
2206 if (tline && tline->next) {
2207 def->dlist = tline->next;
2208 tline->next = NULL;
2209 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2210 } else {
2211 def->dlist = NULL;
2212 def->defaults = NULL;
2214 def->line = NULL;
2216 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2217 !def->plus)
2218 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2219 "too many default macro parameters");
2221 return true;
2226 * Decode a size directive
2228 static int parse_size(const char *str) {
2229 static const char *size_names[] =
2230 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2231 static const int sizes[] =
2232 { 0, 1, 4, 16, 8, 10, 2, 32 };
2234 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2238 * find and process preprocessor directive in passed line
2239 * Find out if a line contains a preprocessor directive, and deal
2240 * with it if so.
2242 * If a directive _is_ found, it is the responsibility of this routine
2243 * (and not the caller) to free_tlist() the line.
2245 * @param tline a pointer to the current tokeninzed line linked list
2246 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2249 static int do_directive(Token * tline)
2251 enum preproc_token i;
2252 int j;
2253 bool err;
2254 int nparam;
2255 bool nolist;
2256 bool casesense;
2257 int k, m;
2258 int offset;
2259 char *p, *pp;
2260 const char *mname;
2261 Include *inc;
2262 Context *ctx;
2263 Line *l;
2264 Token *t, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2265 struct tokenval tokval;
2266 expr *evalresult;
2267 ExpDef *ed, *eed, **edhead;
2268 ExpInv *ei, *eei;
2269 int64_t count;
2270 size_t len;
2271 int severity;
2273 origline = tline;
2275 skip_white_(tline);
2276 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2277 (tline->text[1] == '%' || tline->text[1] == '$'
2278 || tline->text[1] == '!'))
2279 return NO_DIRECTIVE_FOUND;
2281 i = pp_token_hash(tline->text);
2283 switch (i) {
2284 case PP_INVALID:
2285 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2286 error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2287 tline->text);
2288 return NO_DIRECTIVE_FOUND; /* didn't get it */
2290 case PP_STACKSIZE:
2291 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2292 /* Directive to tell NASM what the default stack size is. The
2293 * default is for a 16-bit stack, and this can be overriden with
2294 * %stacksize large.
2296 tline = tline->next;
2297 if (tline && tline->type == TOK_WHITESPACE)
2298 tline = tline->next;
2299 if (!tline || tline->type != TOK_ID) {
2300 error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2301 free_tlist(origline);
2302 return DIRECTIVE_FOUND;
2304 if (nasm_stricmp(tline->text, "flat") == 0) {
2305 /* All subsequent ARG directives are for a 32-bit stack */
2306 StackSize = 4;
2307 StackPointer = "ebp";
2308 ArgOffset = 8;
2309 LocalOffset = 0;
2310 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2311 /* All subsequent ARG directives are for a 64-bit stack */
2312 StackSize = 8;
2313 StackPointer = "rbp";
2314 ArgOffset = 16;
2315 LocalOffset = 0;
2316 } else if (nasm_stricmp(tline->text, "large") == 0) {
2317 /* All subsequent ARG directives are for a 16-bit stack,
2318 * far function call.
2320 StackSize = 2;
2321 StackPointer = "bp";
2322 ArgOffset = 4;
2323 LocalOffset = 0;
2324 } else if (nasm_stricmp(tline->text, "small") == 0) {
2325 /* All subsequent ARG directives are for a 16-bit stack,
2326 * far function call. We don't support near functions.
2328 StackSize = 2;
2329 StackPointer = "bp";
2330 ArgOffset = 6;
2331 LocalOffset = 0;
2332 } else {
2333 error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2334 free_tlist(origline);
2335 return DIRECTIVE_FOUND;
2337 free_tlist(origline);
2338 return DIRECTIVE_FOUND;
2340 case PP_ARG:
2341 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2342 /* TASM like ARG directive to define arguments to functions, in
2343 * the following form:
2345 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2347 offset = ArgOffset;
2348 do {
2349 char *arg, directive[256];
2350 int size = StackSize;
2352 /* Find the argument name */
2353 tline = tline->next;
2354 if (tline && tline->type == TOK_WHITESPACE)
2355 tline = tline->next;
2356 if (!tline || tline->type != TOK_ID) {
2357 error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2358 free_tlist(origline);
2359 return DIRECTIVE_FOUND;
2361 arg = tline->text;
2363 /* Find the argument size type */
2364 tline = tline->next;
2365 if (!tline || tline->type != TOK_OTHER
2366 || tline->text[0] != ':') {
2367 error(ERR_NONFATAL,
2368 "Syntax error processing `%%arg' directive");
2369 free_tlist(origline);
2370 return DIRECTIVE_FOUND;
2372 tline = tline->next;
2373 if (!tline || tline->type != TOK_ID) {
2374 error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2375 free_tlist(origline);
2376 return DIRECTIVE_FOUND;
2379 /* Allow macro expansion of type parameter */
2380 tt = tokenize(tline->text);
2381 tt = expand_smacro(tt);
2382 size = parse_size(tt->text);
2383 if (!size) {
2384 error(ERR_NONFATAL,
2385 "Invalid size type for `%%arg' missing directive");
2386 free_tlist(tt);
2387 free_tlist(origline);
2388 return DIRECTIVE_FOUND;
2390 free_tlist(tt);
2392 /* Round up to even stack slots */
2393 size = ALIGN(size, StackSize);
2395 /* Now define the macro for the argument */
2396 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2397 arg, StackPointer, offset);
2398 do_directive(tokenize(directive));
2399 offset += size;
2401 /* Move to the next argument in the list */
2402 tline = tline->next;
2403 if (tline && tline->type == TOK_WHITESPACE)
2404 tline = tline->next;
2405 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2406 ArgOffset = offset;
2407 free_tlist(origline);
2408 return DIRECTIVE_FOUND;
2410 case PP_LOCAL:
2411 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2412 /* TASM like LOCAL directive to define local variables for a
2413 * function, in the following form:
2415 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2417 * The '= LocalSize' at the end is ignored by NASM, but is
2418 * required by TASM to define the local parameter size (and used
2419 * by the TASM macro package).
2421 offset = LocalOffset;
2422 do {
2423 char *local, directive[256];
2424 int size = StackSize;
2426 /* Find the argument name */
2427 tline = tline->next;
2428 if (tline && tline->type == TOK_WHITESPACE)
2429 tline = tline->next;
2430 if (!tline || tline->type != TOK_ID) {
2431 error(ERR_NONFATAL,
2432 "`%%local' missing argument parameter");
2433 free_tlist(origline);
2434 return DIRECTIVE_FOUND;
2436 local = tline->text;
2438 /* Find the argument size type */
2439 tline = tline->next;
2440 if (!tline || tline->type != TOK_OTHER
2441 || tline->text[0] != ':') {
2442 error(ERR_NONFATAL,
2443 "Syntax error processing `%%local' directive");
2444 free_tlist(origline);
2445 return DIRECTIVE_FOUND;
2447 tline = tline->next;
2448 if (!tline || tline->type != TOK_ID) {
2449 error(ERR_NONFATAL,
2450 "`%%local' missing size type parameter");
2451 free_tlist(origline);
2452 return DIRECTIVE_FOUND;
2455 /* Allow macro expansion of type parameter */
2456 tt = tokenize(tline->text);
2457 tt = expand_smacro(tt);
2458 size = parse_size(tt->text);
2459 if (!size) {
2460 error(ERR_NONFATAL,
2461 "Invalid size type for `%%local' missing directive");
2462 free_tlist(tt);
2463 free_tlist(origline);
2464 return DIRECTIVE_FOUND;
2466 free_tlist(tt);
2468 /* Round up to even stack slots */
2469 size = ALIGN(size, StackSize);
2471 offset += size; /* Negative offset, increment before */
2473 /* Now define the macro for the argument */
2474 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2475 local, StackPointer, offset);
2476 do_directive(tokenize(directive));
2478 /* Now define the assign to setup the enter_c macro correctly */
2479 snprintf(directive, sizeof(directive),
2480 "%%assign %%$localsize %%$localsize+%d", size);
2481 do_directive(tokenize(directive));
2483 /* Move to the next argument in the list */
2484 tline = tline->next;
2485 if (tline && tline->type == TOK_WHITESPACE)
2486 tline = tline->next;
2487 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2488 LocalOffset = offset;
2489 free_tlist(origline);
2490 return DIRECTIVE_FOUND;
2492 case PP_CLEAR:
2493 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2494 if (tline->next)
2495 error(ERR_WARNING|ERR_PASS1,
2496 "trailing garbage after `%%clear' ignored");
2497 free_macros();
2498 init_macros();
2499 free_tlist(origline);
2500 return DIRECTIVE_FOUND;
2502 case PP_DEPEND:
2503 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2504 t = tline->next = expand_smacro(tline->next);
2505 skip_white_(t);
2506 if (!t || (t->type != TOK_STRING &&
2507 t->type != TOK_INTERNAL_STRING)) {
2508 error(ERR_NONFATAL, "`%%depend' expects a file name");
2509 free_tlist(origline);
2510 return DIRECTIVE_FOUND; /* but we did _something_ */
2512 if (t->next)
2513 error(ERR_WARNING|ERR_PASS1,
2514 "trailing garbage after `%%depend' ignored");
2515 p = t->text;
2516 if (t->type != TOK_INTERNAL_STRING)
2517 nasm_unquote_cstr(p, i);
2518 if (dephead && !in_list(*dephead, p)) {
2519 StrList *sl = nasm_malloc(strlen(p)+1+sizeof sl->next);
2520 sl->next = NULL;
2521 strcpy(sl->str, p);
2522 *deptail = sl;
2523 deptail = &sl->next;
2525 free_tlist(origline);
2526 return DIRECTIVE_FOUND;
2528 case PP_INCLUDE:
2529 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2530 t = tline->next = expand_smacro(tline->next);
2531 skip_white_(t);
2533 if (!t || (t->type != TOK_STRING &&
2534 t->type != TOK_INTERNAL_STRING)) {
2535 error(ERR_NONFATAL, "`%%include' expects a file name");
2536 free_tlist(origline);
2537 return DIRECTIVE_FOUND; /* but we did _something_ */
2539 if (t->next)
2540 error(ERR_WARNING|ERR_PASS1,
2541 "trailing garbage after `%%include' ignored");
2542 p = t->text;
2543 if (t->type != TOK_INTERNAL_STRING)
2544 nasm_unquote_cstr(p, i);
2545 inc = nasm_malloc(sizeof(Include));
2546 inc->next = istk;
2547 inc->fp = inc_fopen(p, dephead, &deptail, pass == 0);
2548 if (!inc->fp) {
2549 /* -MG given but file not found */
2550 nasm_free(inc);
2551 } else {
2552 inc->fname = src_set_fname(nasm_strdup(p));
2553 inc->lineno = src_set_linnum(0);
2554 inc->lineinc = 1;
2555 inc->expansion = NULL;
2556 istk = inc;
2557 list->uplevel(LIST_INCLUDE);
2559 free_tlist(origline);
2560 return DIRECTIVE_FOUND;
2562 case PP_USE:
2563 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2565 static macros_t *use_pkg;
2566 const char *pkg_macro = NULL;
2568 tline = tline->next;
2569 skip_white_(tline);
2570 tline = expand_id(tline);
2572 if (!tline || (tline->type != TOK_STRING &&
2573 tline->type != TOK_INTERNAL_STRING &&
2574 tline->type != TOK_ID)) {
2575 error(ERR_NONFATAL, "`%%use' expects a package name");
2576 free_tlist(origline);
2577 return DIRECTIVE_FOUND; /* but we did _something_ */
2579 if (tline->next)
2580 error(ERR_WARNING|ERR_PASS1,
2581 "trailing garbage after `%%use' ignored");
2582 if (tline->type == TOK_STRING)
2583 nasm_unquote_cstr(tline->text, i);
2584 use_pkg = nasm_stdmac_find_package(tline->text);
2585 if (!use_pkg)
2586 error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2587 else
2588 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2589 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2590 /* Not already included, go ahead and include it */
2591 stdmacpos = use_pkg;
2593 free_tlist(origline);
2594 return DIRECTIVE_FOUND;
2596 case PP_PUSH:
2597 case PP_REPL:
2598 case PP_POP:
2599 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2600 tline = tline->next;
2601 skip_white_(tline);
2602 tline = expand_id(tline);
2603 if (tline) {
2604 if (!tok_type_(tline, TOK_ID)) {
2605 error(ERR_NONFATAL, "`%s' expects a context identifier",
2606 pp_directives[i]);
2607 free_tlist(origline);
2608 return DIRECTIVE_FOUND; /* but we did _something_ */
2610 if (tline->next)
2611 error(ERR_WARNING|ERR_PASS1,
2612 "trailing garbage after `%s' ignored",
2613 pp_directives[i]);
2614 p = nasm_strdup(tline->text);
2615 } else {
2616 p = NULL; /* Anonymous */
2619 if (i == PP_PUSH) {
2620 ctx = nasm_malloc(sizeof(Context));
2621 ctx->next = cstk;
2622 hash_init(&ctx->localmac, HASH_SMALL);
2623 ctx->name = p;
2624 ctx->number = unique++;
2625 cstk = ctx;
2626 } else {
2627 /* %pop or %repl */
2628 if (!cstk) {
2629 error(ERR_NONFATAL, "`%s': context stack is empty",
2630 pp_directives[i]);
2631 } else if (i == PP_POP) {
2632 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2633 error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2634 "expected %s",
2635 cstk->name ? cstk->name : "anonymous", p);
2636 else
2637 ctx_pop();
2638 } else {
2639 /* i == PP_REPL */
2640 nasm_free(cstk->name);
2641 cstk->name = p;
2642 p = NULL;
2644 nasm_free(p);
2646 free_tlist(origline);
2647 return DIRECTIVE_FOUND;
2648 case PP_FATAL:
2649 severity = ERR_FATAL;
2650 goto issue_error;
2651 case PP_ERROR:
2652 severity = ERR_NONFATAL;
2653 goto issue_error;
2654 case PP_WARNING:
2655 severity = ERR_WARNING|ERR_WARN_USER;
2656 goto issue_error;
2658 issue_error:
2659 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2661 /* Only error out if this is the final pass */
2662 if (pass != 2 && i != PP_FATAL)
2663 return DIRECTIVE_FOUND;
2665 tline->next = expand_smacro(tline->next);
2666 tline = tline->next;
2667 skip_white_(tline);
2668 t = tline ? tline->next : NULL;
2669 skip_white_(t);
2670 if (tok_type_(tline, TOK_STRING) && !t) {
2671 /* The line contains only a quoted string */
2672 p = tline->text;
2673 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2674 error(severity, "%s", p);
2675 } else {
2676 /* Not a quoted string, or more than a quoted string */
2677 p = detoken(tline, false);
2678 error(severity, "%s", p);
2679 nasm_free(p);
2681 free_tlist(origline);
2682 return DIRECTIVE_FOUND;
2685 CASE_PP_IF:
2686 if (defining != NULL) {
2687 if (defining->type == EXP_IF) {
2688 defining->def_depth ++;
2690 return NO_DIRECTIVE_FOUND;
2692 if ((istk->expansion != NULL) &&
2693 (istk->expansion->emitting == false)) {
2694 j = COND_NEVER;
2695 } else {
2696 j = if_condition(tline->next, i);
2697 tline->next = NULL; /* it got freed */
2698 j = (((j < 0) ? COND_NEVER : j) ? COND_IF_TRUE : COND_IF_FALSE);
2700 ed = new_ExpDef(EXP_IF);
2701 ed->state = j;
2702 ed->nolist = NULL;
2703 ed->def_depth = 0;
2704 ed->cur_depth = 0;
2705 ed->max_depth = 0;
2706 ed->ignoring = ((ed->state == COND_IF_TRUE) ? false : true);
2707 ed->prev = defining;
2708 defining = ed;
2709 free_tlist(origline);
2710 return DIRECTIVE_FOUND;
2712 CASE_PP_ELIF:
2713 if (defining != NULL) {
2714 if ((defining->type != EXP_IF) || (defining->def_depth > 0)) {
2715 return NO_DIRECTIVE_FOUND;
2718 if ((defining == NULL) || (defining->type != EXP_IF)) {
2719 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2721 switch (defining->state) {
2722 case COND_IF_TRUE:
2723 defining->state = COND_DONE;
2724 defining->ignoring = true;
2725 break;
2727 case COND_DONE:
2728 case COND_NEVER:
2729 defining->ignoring = true;
2730 break;
2732 case COND_ELSE_TRUE:
2733 case COND_ELSE_FALSE:
2734 error_precond(ERR_WARNING|ERR_PASS1,
2735 "`%%elif' after `%%else' ignored");
2736 defining->state = COND_NEVER;
2737 defining->ignoring = true;
2738 break;
2740 case COND_IF_FALSE:
2742 * IMPORTANT: In the case of %if, we will already have
2743 * called expand_mmac_params(); however, if we're
2744 * processing an %elif we must have been in a
2745 * non-emitting mode, which would have inhibited
2746 * the normal invocation of expand_mmac_params().
2747 * Therefore, we have to do it explicitly here.
2749 j = if_condition(expand_mmac_params(tline->next), i);
2750 tline->next = NULL; /* it got freed */
2751 defining->state =
2752 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2753 defining->ignoring = ((defining->state == COND_IF_TRUE) ? false : true);
2754 break;
2756 free_tlist(origline);
2757 return DIRECTIVE_FOUND;
2759 case PP_ELSE:
2760 if (defining != NULL) {
2761 if ((defining->type != EXP_IF) || (defining->def_depth > 0)) {
2762 return NO_DIRECTIVE_FOUND;
2765 if (tline->next)
2766 error_precond(ERR_WARNING|ERR_PASS1,
2767 "trailing garbage after `%%else' ignored");
2768 if ((defining == NULL) || (defining->type != EXP_IF)) {
2769 error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2771 switch (defining->state) {
2772 case COND_IF_TRUE:
2773 case COND_DONE:
2774 defining->state = COND_ELSE_FALSE;
2775 defining->ignoring = true;
2776 break;
2778 case COND_NEVER:
2779 defining->ignoring = true;
2780 break;
2782 case COND_IF_FALSE:
2783 defining->state = COND_ELSE_TRUE;
2784 defining->ignoring = false;
2785 break;
2787 case COND_ELSE_TRUE:
2788 case COND_ELSE_FALSE:
2789 error_precond(ERR_WARNING|ERR_PASS1,
2790 "`%%else' after `%%else' ignored.");
2791 defining->state = COND_NEVER;
2792 defining->ignoring = true;
2793 break;
2795 free_tlist(origline);
2796 return DIRECTIVE_FOUND;
2798 case PP_ENDIF:
2799 if (defining != NULL) {
2800 if (defining->type == EXP_IF) {
2801 if (defining->def_depth > 0) {
2802 defining->def_depth --;
2803 return NO_DIRECTIVE_FOUND;
2805 } else {
2806 return NO_DIRECTIVE_FOUND;
2809 if (tline->next)
2810 error_precond(ERR_WARNING|ERR_PASS1,
2811 "trailing garbage after `%%endif' ignored");
2812 if ((defining == NULL) || (defining->type != EXP_IF)) {
2813 error(ERR_NONFATAL, "`%%endif': no matching `%%if'");
2815 ed = defining;
2816 defining = ed->prev;
2817 ed->prev = expansions;
2818 expansions = ed;
2819 ei = new_ExpInv(EXP_IF, ed);
2820 ei->current = ed->line;
2821 ei->emitting = true;
2822 ei->prev = istk->expansion;
2823 istk->expansion = ei;
2824 free_tlist(origline);
2825 return DIRECTIVE_FOUND;
2827 case PP_RMACRO:
2828 case PP_IRMACRO:
2829 case PP_MACRO:
2830 case PP_IMACRO:
2831 if (defining != NULL) {
2832 if (defining->type == EXP_MMACRO) {
2833 defining->def_depth ++;
2835 return NO_DIRECTIVE_FOUND;
2837 ed = new_ExpDef(EXP_MMACRO);
2838 ed->max_depth =
2839 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2840 ed->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2841 if (!parse_mmacro_spec(tline, ed, pp_directives[i])) {
2842 nasm_free(ed);
2843 ed = NULL;
2844 return DIRECTIVE_FOUND;
2846 ed->def_depth = 0;
2847 ed->cur_depth = 0;
2848 ed->max_depth = (ed->max_depth + 1);
2849 ed->ignoring = false;
2850 ed->prev = defining;
2851 defining = ed;
2853 eed = (ExpDef *) hash_findix(&expdefs, ed->name);
2854 while (eed) {
2855 if (!strcmp(eed->name, ed->name) &&
2856 (eed->nparam_min <= ed->nparam_max
2857 || ed->plus)
2858 && (ed->nparam_min <= eed->nparam_max
2859 || eed->plus)) {
2860 error(ERR_WARNING|ERR_PASS1,
2861 "redefining multi-line macro `%s'", ed->name);
2862 return DIRECTIVE_FOUND;
2864 eed = eed->next;
2866 free_tlist(origline);
2867 return DIRECTIVE_FOUND;
2869 case PP_ENDM:
2870 case PP_ENDMACRO:
2871 if (defining != NULL) {
2872 if (defining->type == EXP_MMACRO) {
2873 if (defining->def_depth > 0) {
2874 defining->def_depth --;
2875 return NO_DIRECTIVE_FOUND;
2877 } else {
2878 return NO_DIRECTIVE_FOUND;
2881 if (!(defining) || (defining->type != EXP_MMACRO)) {
2882 error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2883 return DIRECTIVE_FOUND;
2885 edhead = (ExpDef **) hash_findi_add(&expdefs, defining->name);
2886 defining->next = *edhead;
2887 *edhead = defining;
2888 ed = defining;
2889 defining = ed->prev;
2890 ed->prev = expansions;
2891 expansions = ed;
2892 ed = NULL;
2893 free_tlist(origline);
2894 return DIRECTIVE_FOUND;
2896 case PP_EXITMACRO:
2897 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2899 * We must search along istk->expansion until we hit a
2900 * macro invocation. Then we disable the emitting state(s)
2901 * between exitmacro and endmacro.
2903 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
2904 if(ei->type == EXP_MMACRO) {
2905 break;
2909 if (ei != NULL) {
2911 * Set all invocations leading back to the macro
2912 * invocation to a non-emitting state.
2914 for (eei = istk->expansion; eei != ei; eei = eei->prev) {
2915 eei->emitting = false;
2917 eei->emitting = false;
2918 } else {
2919 error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2921 free_tlist(origline);
2922 return DIRECTIVE_FOUND;
2924 case PP_UNMACRO:
2925 case PP_UNIMACRO:
2926 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2928 ExpDef **ed_p;
2929 ExpDef spec;
2931 spec.casesense = (i == PP_UNMACRO);
2932 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2933 return DIRECTIVE_FOUND;
2935 ed_p = (ExpDef **) hash_findi(&expdefs, spec.name, NULL);
2936 while (ed_p && *ed_p) {
2937 ed = *ed_p;
2938 if (ed->casesense == spec.casesense &&
2939 !mstrcmp(ed->name, spec.name, spec.casesense) &&
2940 ed->nparam_min == spec.nparam_min &&
2941 ed->nparam_max == spec.nparam_max &&
2942 ed->plus == spec.plus) {
2943 *ed_p = ed->next;
2944 free_expdef(ed);
2945 } else {
2946 ed_p = &ed->next;
2949 free_tlist(origline);
2950 free_tlist(spec.dlist);
2951 return DIRECTIVE_FOUND;
2954 case PP_ROTATE:
2955 if (defining != NULL) return NO_DIRECTIVE_FOUND;
2956 if (tline->next && tline->next->type == TOK_WHITESPACE)
2957 tline = tline->next;
2958 if (!tline->next) {
2959 free_tlist(origline);
2960 error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2961 return DIRECTIVE_FOUND;
2963 t = expand_smacro(tline->next);
2964 tline->next = NULL;
2965 free_tlist(origline);
2966 tline = t;
2967 tptr = &t;
2968 tokval.t_type = TOKEN_INVALID;
2969 evalresult =
2970 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
2971 free_tlist(tline);
2972 if (!evalresult)
2973 return DIRECTIVE_FOUND;
2974 if (tokval.t_type)
2975 error(ERR_WARNING|ERR_PASS1,
2976 "trailing garbage after expression ignored");
2977 if (!is_simple(evalresult)) {
2978 error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2979 return DIRECTIVE_FOUND;
2981 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
2982 if (ei->type == EXP_MMACRO) {
2983 break;
2986 if (ei == NULL) {
2987 error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2988 } else if (ei->nparam == 0) {
2989 error(ERR_NONFATAL,
2990 "`%%rotate' invoked within macro without parameters");
2991 } else {
2992 int rotate = ei->rotate + reloc_value(evalresult);
2994 rotate %= (int)ei->nparam;
2995 if (rotate < 0)
2996 rotate += ei->nparam;
2997 ei->rotate = rotate;
2999 return DIRECTIVE_FOUND;
3001 case PP_REP:
3002 if (defining != NULL) {
3003 if (defining->type == EXP_REP) {
3004 defining->def_depth ++;
3006 return NO_DIRECTIVE_FOUND;
3008 nolist = false;
3009 do {
3010 tline = tline->next;
3011 } while (tok_type_(tline, TOK_WHITESPACE));
3013 if (tok_type_(tline, TOK_ID) &&
3014 nasm_stricmp(tline->text, ".nolist") == 0) {
3015 nolist = true;
3016 do {
3017 tline = tline->next;
3018 } while (tok_type_(tline, TOK_WHITESPACE));
3021 if (tline) {
3022 t = expand_smacro(tline);
3023 tptr = &t;
3024 tokval.t_type = TOKEN_INVALID;
3025 evalresult =
3026 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3027 if (!evalresult) {
3028 free_tlist(origline);
3029 return DIRECTIVE_FOUND;
3031 if (tokval.t_type)
3032 error(ERR_WARNING|ERR_PASS1,
3033 "trailing garbage after expression ignored");
3034 if (!is_simple(evalresult)) {
3035 error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3036 return DIRECTIVE_FOUND;
3038 count = reloc_value(evalresult) + 1;
3039 } else {
3040 error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3041 count = 0;
3043 free_tlist(origline);
3044 ed = new_ExpDef(EXP_REP);
3045 ed->nolist = nolist;
3046 ed->def_depth = 0;
3047 ed->cur_depth = 1;
3048 ed->max_depth = (count - 1);
3049 ed->ignoring = false;
3050 ed->prev = defining;
3051 defining = ed;
3052 return DIRECTIVE_FOUND;
3054 case PP_ENDREP:
3055 if (defining != NULL) {
3056 if (defining->type == EXP_REP) {
3057 if (defining->def_depth > 0) {
3058 defining->def_depth --;
3059 return NO_DIRECTIVE_FOUND;
3061 } else {
3062 return NO_DIRECTIVE_FOUND;
3065 if ((defining == NULL) || (defining->type != EXP_REP)) {
3066 error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3067 return DIRECTIVE_FOUND;
3071 * Now we have a "macro" defined - although it has no name
3072 * and we won't be entering it in the hash tables - we must
3073 * push a macro-end marker for it on to istk->expansion.
3074 * After that, it will take care of propagating itself (a
3075 * macro-end marker line for a macro which is really a %rep
3076 * block will cause the macro to be re-expanded, complete
3077 * with another macro-end marker to ensure the process
3078 * continues) until the whole expansion is forcibly removed
3079 * from istk->expansion by a %exitrep.
3081 ed = defining;
3082 defining = ed->prev;
3083 ed->prev = expansions;
3084 expansions = ed;
3085 ei = new_ExpInv(EXP_REP, ed);
3086 ei->current = ed->line;
3087 ei->emitting = ((ed->max_depth > 0) ? true : false);
3088 list->uplevel(ed->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3089 ei->prev = istk->expansion;
3090 istk->expansion = ei;
3091 free_tlist(origline);
3092 return DIRECTIVE_FOUND;
3094 case PP_EXITREP:
3095 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3097 * We must search along istk->expansion until we hit a
3098 * rep invocation. Then we disable the emitting state(s)
3099 * between exitrep and endrep.
3101 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
3102 if (ei->type == EXP_REP) {
3103 break;
3107 if (ei != NULL) {
3109 * Set all invocations leading back to the rep
3110 * invocation to a non-emitting state.
3112 for (eei = istk->expansion; eei != ei; eei = eei->prev) {
3113 eei->emitting = false;
3115 eei->emitting = false;
3116 eei->current = NULL;
3117 eei->def->cur_depth = eei->def->max_depth;
3118 } else {
3119 error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3121 free_tlist(origline);
3122 return DIRECTIVE_FOUND;
3124 case PP_XDEFINE:
3125 case PP_IXDEFINE:
3126 case PP_DEFINE:
3127 case PP_IDEFINE:
3128 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3129 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3131 tline = tline->next;
3132 skip_white_(tline);
3133 tline = expand_id(tline);
3134 if (!tline || (tline->type != TOK_ID &&
3135 (tline->type != TOK_PREPROC_ID ||
3136 tline->text[1] != '$'))) {
3137 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3138 pp_directives[i]);
3139 free_tlist(origline);
3140 return DIRECTIVE_FOUND;
3143 ctx = get_ctx(tline->text, &mname, false);
3144 last = tline;
3145 param_start = tline = tline->next;
3146 nparam = 0;
3148 /* Expand the macro definition now for %xdefine and %ixdefine */
3149 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3150 tline = expand_smacro(tline);
3152 if (tok_is_(tline, "(")) {
3154 * This macro has parameters.
3157 tline = tline->next;
3158 while (1) {
3159 skip_white_(tline);
3160 if (!tline) {
3161 error(ERR_NONFATAL, "parameter identifier expected");
3162 free_tlist(origline);
3163 return DIRECTIVE_FOUND;
3165 if (tline->type != TOK_ID) {
3166 error(ERR_NONFATAL,
3167 "`%s': parameter identifier expected",
3168 tline->text);
3169 free_tlist(origline);
3170 return DIRECTIVE_FOUND;
3172 tline->type = TOK_SMAC_PARAM + nparam++;
3173 tline = tline->next;
3174 skip_white_(tline);
3175 if (tok_is_(tline, ",")) {
3176 tline = tline->next;
3177 } else {
3178 if (!tok_is_(tline, ")")) {
3179 error(ERR_NONFATAL,
3180 "`)' expected to terminate macro template");
3181 free_tlist(origline);
3182 return DIRECTIVE_FOUND;
3184 break;
3187 last = tline;
3188 tline = tline->next;
3190 if (tok_type_(tline, TOK_WHITESPACE))
3191 last = tline, tline = tline->next;
3192 macro_start = NULL;
3193 last->next = NULL;
3194 t = tline;
3195 while (t) {
3196 if (t->type == TOK_ID) {
3197 list_for_each(tt, param_start)
3198 if (tt->type >= TOK_SMAC_PARAM &&
3199 !strcmp(tt->text, t->text))
3200 t->type = tt->type;
3202 tt = t->next;
3203 t->next = macro_start;
3204 macro_start = t;
3205 t = tt;
3208 * Good. We now have a macro name, a parameter count, and a
3209 * token list (in reverse order) for an expansion. We ought
3210 * to be OK just to create an SMacro, store it, and let
3211 * free_tlist have the rest of the line (which we have
3212 * carefully re-terminated after chopping off the expansion
3213 * from the end).
3215 define_smacro(ctx, mname, casesense, nparam, macro_start);
3216 free_tlist(origline);
3217 return DIRECTIVE_FOUND;
3219 case PP_UNDEF:
3220 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3221 tline = tline->next;
3222 skip_white_(tline);
3223 tline = expand_id(tline);
3224 if (!tline || (tline->type != TOK_ID &&
3225 (tline->type != TOK_PREPROC_ID ||
3226 tline->text[1] != '$'))) {
3227 error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3228 free_tlist(origline);
3229 return DIRECTIVE_FOUND;
3231 if (tline->next) {
3232 error(ERR_WARNING|ERR_PASS1,
3233 "trailing garbage after macro name ignored");
3236 /* Find the context that symbol belongs to */
3237 ctx = get_ctx(tline->text, &mname, false);
3238 undef_smacro(ctx, mname);
3239 free_tlist(origline);
3240 return DIRECTIVE_FOUND;
3242 case PP_DEFSTR:
3243 case PP_IDEFSTR:
3244 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3245 casesense = (i == PP_DEFSTR);
3247 tline = tline->next;
3248 skip_white_(tline);
3249 tline = expand_id(tline);
3250 if (!tline || (tline->type != TOK_ID &&
3251 (tline->type != TOK_PREPROC_ID ||
3252 tline->text[1] != '$'))) {
3253 error(ERR_NONFATAL, "`%s' expects a macro identifier",
3254 pp_directives[i]);
3255 free_tlist(origline);
3256 return DIRECTIVE_FOUND;
3259 ctx = get_ctx(tline->text, &mname, false);
3260 last = tline;
3261 tline = expand_smacro(tline->next);
3262 last->next = NULL;
3264 while (tok_type_(tline, TOK_WHITESPACE))
3265 tline = delete_Token(tline);
3267 p = detoken(tline, false);
3268 macro_start = nasm_malloc(sizeof(*macro_start));
3269 macro_start->next = NULL;
3270 macro_start->text = nasm_quote(p, strlen(p));
3271 macro_start->type = TOK_STRING;
3272 macro_start->a.mac = NULL;
3273 nasm_free(p);
3276 * We now have a macro name, an implicit parameter count of
3277 * zero, and a string token to use as an expansion. Create
3278 * and store an SMacro.
3280 define_smacro(ctx, mname, casesense, 0, macro_start);
3281 free_tlist(origline);
3282 return DIRECTIVE_FOUND;
3284 case PP_DEFTOK:
3285 case PP_IDEFTOK:
3286 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3287 casesense = (i == PP_DEFTOK);
3289 tline = tline->next;
3290 skip_white_(tline);
3291 tline = expand_id(tline);
3292 if (!tline || (tline->type != TOK_ID &&
3293 (tline->type != TOK_PREPROC_ID ||
3294 tline->text[1] != '$'))) {
3295 error(ERR_NONFATAL,
3296 "`%s' expects a macro identifier as first parameter",
3297 pp_directives[i]);
3298 free_tlist(origline);
3299 return DIRECTIVE_FOUND;
3301 ctx = get_ctx(tline->text, &mname, false);
3302 last = tline;
3303 tline = expand_smacro(tline->next);
3304 last->next = NULL;
3306 t = tline;
3307 while (tok_type_(t, TOK_WHITESPACE))
3308 t = t->next;
3309 /* t should now point to the string */
3310 if (t->type != TOK_STRING) {
3311 error(ERR_NONFATAL,
3312 "`%s` requires string as second parameter",
3313 pp_directives[i]);
3314 free_tlist(tline);
3315 free_tlist(origline);
3316 return DIRECTIVE_FOUND;
3319 nasm_unquote_cstr(t->text, i);
3320 macro_start = tokenize(t->text);
3323 * We now have a macro name, an implicit parameter count of
3324 * zero, and a numeric token to use as an expansion. Create
3325 * and store an SMacro.
3327 define_smacro(ctx, mname, casesense, 0, macro_start);
3328 free_tlist(tline);
3329 free_tlist(origline);
3330 return DIRECTIVE_FOUND;
3332 case PP_PATHSEARCH:
3333 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3335 FILE *fp;
3336 StrList *xsl = NULL;
3337 StrList **xst = &xsl;
3339 casesense = true;
3341 tline = tline->next;
3342 skip_white_(tline);
3343 tline = expand_id(tline);
3344 if (!tline || (tline->type != TOK_ID &&
3345 (tline->type != TOK_PREPROC_ID ||
3346 tline->text[1] != '$'))) {
3347 error(ERR_NONFATAL,
3348 "`%%pathsearch' expects a macro identifier as first parameter");
3349 free_tlist(origline);
3350 return DIRECTIVE_FOUND;
3352 ctx = get_ctx(tline->text, &mname, false);
3353 last = tline;
3354 tline = expand_smacro(tline->next);
3355 last->next = NULL;
3357 t = tline;
3358 while (tok_type_(t, TOK_WHITESPACE))
3359 t = t->next;
3361 if (!t || (t->type != TOK_STRING &&
3362 t->type != TOK_INTERNAL_STRING)) {
3363 error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3364 free_tlist(tline);
3365 free_tlist(origline);
3366 return DIRECTIVE_FOUND; /* but we did _something_ */
3368 if (t->next)
3369 error(ERR_WARNING|ERR_PASS1,
3370 "trailing garbage after `%%pathsearch' ignored");
3371 p = t->text;
3372 if (t->type != TOK_INTERNAL_STRING)
3373 nasm_unquote(p, NULL);
3375 fp = inc_fopen(p, &xsl, &xst, true);
3376 if (fp) {
3377 p = xsl->str;
3378 fclose(fp); /* Don't actually care about the file */
3380 macro_start = nasm_malloc(sizeof(*macro_start));
3381 macro_start->next = NULL;
3382 macro_start->text = nasm_quote(p, strlen(p));
3383 macro_start->type = TOK_STRING;
3384 macro_start->a.mac = NULL;
3385 if (xsl)
3386 nasm_free(xsl);
3389 * We now have a macro name, an implicit parameter count of
3390 * zero, and a string token to use as an expansion. Create
3391 * and store an SMacro.
3393 define_smacro(ctx, mname, casesense, 0, macro_start);
3394 free_tlist(tline);
3395 free_tlist(origline);
3396 return DIRECTIVE_FOUND;
3399 case PP_STRLEN:
3400 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3401 casesense = true;
3403 tline = tline->next;
3404 skip_white_(tline);
3405 tline = expand_id(tline);
3406 if (!tline || (tline->type != TOK_ID &&
3407 (tline->type != TOK_PREPROC_ID ||
3408 tline->text[1] != '$'))) {
3409 error(ERR_NONFATAL,
3410 "`%%strlen' expects a macro identifier as first parameter");
3411 free_tlist(origline);
3412 return DIRECTIVE_FOUND;
3414 ctx = get_ctx(tline->text, &mname, false);
3415 last = tline;
3416 tline = expand_smacro(tline->next);
3417 last->next = NULL;
3419 t = tline;
3420 while (tok_type_(t, TOK_WHITESPACE))
3421 t = t->next;
3422 /* t should now point to the string */
3423 if (!tok_type_(t, TOK_STRING)) {
3424 error(ERR_NONFATAL,
3425 "`%%strlen` requires string as second parameter");
3426 free_tlist(tline);
3427 free_tlist(origline);
3428 return DIRECTIVE_FOUND;
3431 macro_start = nasm_malloc(sizeof(*macro_start));
3432 macro_start->next = NULL;
3433 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3434 macro_start->a.mac = NULL;
3437 * We now have a macro name, an implicit parameter count of
3438 * zero, and a numeric token to use as an expansion. Create
3439 * and store an SMacro.
3441 define_smacro(ctx, mname, casesense, 0, macro_start);
3442 free_tlist(tline);
3443 free_tlist(origline);
3444 return DIRECTIVE_FOUND;
3446 case PP_STRCAT:
3447 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3448 casesense = true;
3450 tline = tline->next;
3451 skip_white_(tline);
3452 tline = expand_id(tline);
3453 if (!tline || (tline->type != TOK_ID &&
3454 (tline->type != TOK_PREPROC_ID ||
3455 tline->text[1] != '$'))) {
3456 error(ERR_NONFATAL,
3457 "`%%strcat' expects a macro identifier as first parameter");
3458 free_tlist(origline);
3459 return DIRECTIVE_FOUND;
3461 ctx = get_ctx(tline->text, &mname, false);
3462 last = tline;
3463 tline = expand_smacro(tline->next);
3464 last->next = NULL;
3466 len = 0;
3467 list_for_each(t, tline) {
3468 switch (t->type) {
3469 case TOK_WHITESPACE:
3470 break;
3471 case TOK_STRING:
3472 len += t->a.len = nasm_unquote(t->text, NULL);
3473 break;
3474 case TOK_OTHER:
3475 if (!strcmp(t->text, ",")) /* permit comma separators */
3476 break;
3477 /* else fall through */
3478 default:
3479 error(ERR_NONFATAL,
3480 "non-string passed to `%%strcat' (%d)", t->type);
3481 free_tlist(tline);
3482 free_tlist(origline);
3483 return DIRECTIVE_FOUND;
3487 p = pp = nasm_malloc(len);
3488 list_for_each(t, tline) {
3489 if (t->type == TOK_STRING) {
3490 memcpy(p, t->text, t->a.len);
3491 p += t->a.len;
3496 * We now have a macro name, an implicit parameter count of
3497 * zero, and a numeric token to use as an expansion. Create
3498 * and store an SMacro.
3500 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3501 macro_start->text = nasm_quote(pp, len);
3502 nasm_free(pp);
3503 define_smacro(ctx, mname, casesense, 0, macro_start);
3504 free_tlist(tline);
3505 free_tlist(origline);
3506 return DIRECTIVE_FOUND;
3508 case PP_SUBSTR:
3509 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3511 int64_t a1, a2;
3512 size_t len;
3514 casesense = true;
3516 tline = tline->next;
3517 skip_white_(tline);
3518 tline = expand_id(tline);
3519 if (!tline || (tline->type != TOK_ID &&
3520 (tline->type != TOK_PREPROC_ID ||
3521 tline->text[1] != '$'))) {
3522 error(ERR_NONFATAL,
3523 "`%%substr' expects a macro identifier as first parameter");
3524 free_tlist(origline);
3525 return DIRECTIVE_FOUND;
3527 ctx = get_ctx(tline->text, &mname, false);
3528 last = tline;
3529 tline = expand_smacro(tline->next);
3530 last->next = NULL;
3532 t = tline->next;
3533 while (tok_type_(t, TOK_WHITESPACE))
3534 t = t->next;
3536 /* t should now point to the string */
3537 if (t->type != TOK_STRING) {
3538 error(ERR_NONFATAL,
3539 "`%%substr` requires string as second parameter");
3540 free_tlist(tline);
3541 free_tlist(origline);
3542 return DIRECTIVE_FOUND;
3545 tt = t->next;
3546 tptr = &tt;
3547 tokval.t_type = TOKEN_INVALID;
3548 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3549 pass, error, NULL);
3550 if (!evalresult) {
3551 free_tlist(tline);
3552 free_tlist(origline);
3553 return DIRECTIVE_FOUND;
3554 } else if (!is_simple(evalresult)) {
3555 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3556 free_tlist(tline);
3557 free_tlist(origline);
3558 return DIRECTIVE_FOUND;
3560 a1 = evalresult->value-1;
3562 while (tok_type_(tt, TOK_WHITESPACE))
3563 tt = tt->next;
3564 if (!tt) {
3565 a2 = 1; /* Backwards compatibility: one character */
3566 } else {
3567 tokval.t_type = TOKEN_INVALID;
3568 evalresult = evaluate(ppscan, tptr, &tokval, NULL,
3569 pass, error, NULL);
3570 if (!evalresult) {
3571 free_tlist(tline);
3572 free_tlist(origline);
3573 return DIRECTIVE_FOUND;
3574 } else if (!is_simple(evalresult)) {
3575 error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3576 free_tlist(tline);
3577 free_tlist(origline);
3578 return DIRECTIVE_FOUND;
3580 a2 = evalresult->value;
3583 len = nasm_unquote(t->text, NULL);
3584 if (a2 < 0)
3585 a2 = a2+1+len-a1;
3586 if (a1+a2 > (int64_t)len)
3587 a2 = len-a1;
3589 macro_start = nasm_malloc(sizeof(*macro_start));
3590 macro_start->next = NULL;
3591 macro_start->text = nasm_quote((a1 < 0) ? "" : t->text+a1, a2);
3592 macro_start->type = TOK_STRING;
3593 macro_start->a.mac = NULL;
3596 * We now have a macro name, an implicit parameter count of
3597 * zero, and a numeric token to use as an expansion. Create
3598 * and store an SMacro.
3600 define_smacro(ctx, mname, casesense, 0, macro_start);
3601 free_tlist(tline);
3602 free_tlist(origline);
3603 return DIRECTIVE_FOUND;
3606 case PP_ASSIGN:
3607 case PP_IASSIGN:
3608 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3609 casesense = (i == PP_ASSIGN);
3611 tline = tline->next;
3612 skip_white_(tline);
3613 tline = expand_id(tline);
3614 if (!tline || (tline->type != TOK_ID &&
3615 (tline->type != TOK_PREPROC_ID ||
3616 tline->text[1] != '$'))) {
3617 error(ERR_NONFATAL,
3618 "`%%%sassign' expects a macro identifier",
3619 (i == PP_IASSIGN ? "i" : ""));
3620 free_tlist(origline);
3621 return DIRECTIVE_FOUND;
3623 ctx = get_ctx(tline->text, &mname, false);
3624 last = tline;
3625 tline = expand_smacro(tline->next);
3626 last->next = NULL;
3628 t = tline;
3629 tptr = &t;
3630 tokval.t_type = TOKEN_INVALID;
3631 evalresult =
3632 evaluate(ppscan, tptr, &tokval, NULL, pass, error, NULL);
3633 free_tlist(tline);
3634 if (!evalresult) {
3635 free_tlist(origline);
3636 return DIRECTIVE_FOUND;
3639 if (tokval.t_type)
3640 error(ERR_WARNING|ERR_PASS1,
3641 "trailing garbage after expression ignored");
3643 if (!is_simple(evalresult)) {
3644 error(ERR_NONFATAL,
3645 "non-constant value given to `%%%sassign'",
3646 (i == PP_IASSIGN ? "i" : ""));
3647 free_tlist(origline);
3648 return DIRECTIVE_FOUND;
3651 macro_start = nasm_malloc(sizeof(*macro_start));
3652 macro_start->next = NULL;
3653 make_tok_num(macro_start, reloc_value(evalresult));
3654 macro_start->a.mac = NULL;
3657 * We now have a macro name, an implicit parameter count of
3658 * zero, and a numeric token to use as an expansion. Create
3659 * and store an SMacro.
3661 define_smacro(ctx, mname, casesense, 0, macro_start);
3662 free_tlist(origline);
3663 return DIRECTIVE_FOUND;
3665 case PP_LINE:
3666 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3668 * Syntax is `%line nnn[+mmm] [filename]'
3670 tline = tline->next;
3671 skip_white_(tline);
3672 if (!tok_type_(tline, TOK_NUMBER)) {
3673 error(ERR_NONFATAL, "`%%line' expects line number");
3674 free_tlist(origline);
3675 return DIRECTIVE_FOUND;
3677 k = readnum(tline->text, &err);
3678 m = 1;
3679 tline = tline->next;
3680 if (tok_is_(tline, "+")) {
3681 tline = tline->next;
3682 if (!tok_type_(tline, TOK_NUMBER)) {
3683 error(ERR_NONFATAL, "`%%line' expects line increment");
3684 free_tlist(origline);
3685 return DIRECTIVE_FOUND;
3687 m = readnum(tline->text, &err);
3688 tline = tline->next;
3690 skip_white_(tline);
3691 src_set_linnum(k);
3692 istk->lineinc = m;
3693 if (tline) {
3694 nasm_free(src_set_fname(detoken(tline, false)));
3696 free_tlist(origline);
3697 return DIRECTIVE_FOUND;
3699 case PP_WHILE:
3700 if (defining != NULL) {
3701 if (defining->type == EXP_WHILE) {
3702 defining->def_depth ++;
3704 return NO_DIRECTIVE_FOUND;
3706 l = NULL;
3707 if ((istk->expansion != NULL) &&
3708 (istk->expansion->emitting == false)) {
3709 j = COND_NEVER;
3710 } else {
3711 l = new_Line();
3712 l->first = copy_Token(tline->next);
3713 j = if_condition(tline->next, i);
3714 tline->next = NULL; /* it got freed */
3715 j = (((j < 0) ? COND_NEVER : j) ? COND_IF_TRUE : COND_IF_FALSE);
3717 ed = new_ExpDef(EXP_WHILE);
3718 ed->state = j;
3719 ed->cur_depth = 1;
3720 ed->max_depth = DEADMAN_LIMIT;
3721 ed->ignoring = ((ed->state == COND_IF_TRUE) ? false : true);
3722 if (ed->ignoring == false) {
3723 ed->line = l;
3724 ed->last = l;
3725 } else if (l != NULL) {
3726 delete_Token(l->first);
3727 nasm_free(l);
3728 l = NULL;
3730 ed->prev = defining;
3731 defining = ed;
3732 free_tlist(origline);
3733 return DIRECTIVE_FOUND;
3735 case PP_ENDWHILE:
3736 if (defining != NULL) {
3737 if (defining->type == EXP_WHILE) {
3738 if (defining->def_depth > 0) {
3739 defining->def_depth --;
3740 return NO_DIRECTIVE_FOUND;
3742 } else {
3743 return NO_DIRECTIVE_FOUND;
3746 if (tline->next != NULL) {
3747 error_precond(ERR_WARNING|ERR_PASS1,
3748 "trailing garbage after `%%endwhile' ignored");
3750 if ((defining == NULL) || (defining->type != EXP_WHILE)) {
3751 error(ERR_NONFATAL, "`%%endwhile': no matching `%%while'");
3752 return DIRECTIVE_FOUND;
3754 ed = defining;
3755 defining = ed->prev;
3756 if (ed->ignoring == false) {
3757 ed->prev = expansions;
3758 expansions = ed;
3759 ei = new_ExpInv(EXP_WHILE, ed);
3760 ei->current = ed->line->next;
3761 ei->emitting = true;
3762 ei->prev = istk->expansion;
3763 istk->expansion = ei;
3764 } else {
3765 nasm_free(ed);
3767 free_tlist(origline);
3768 return DIRECTIVE_FOUND;
3770 case PP_EXITWHILE:
3771 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3773 * We must search along istk->expansion until we hit a
3774 * while invocation. Then we disable the emitting state(s)
3775 * between exitwhile and endwhile.
3777 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
3778 if (ei->type == EXP_WHILE) {
3779 break;
3783 if (ei != NULL) {
3785 * Set all invocations leading back to the while
3786 * invocation to a non-emitting state.
3788 for (eei = istk->expansion; eei != ei; eei = eei->prev) {
3789 eei->emitting = false;
3791 eei->emitting = false;
3792 eei->current = NULL;
3793 eei->def->cur_depth = eei->def->max_depth;
3794 } else {
3795 error(ERR_NONFATAL, "`%%exitwhile' not within `%%while' block");
3797 free_tlist(origline);
3798 return DIRECTIVE_FOUND;
3800 case PP_COMMENT:
3801 if (defining != NULL) {
3802 if (defining->type == EXP_COMMENT) {
3803 defining->def_depth ++;
3805 return NO_DIRECTIVE_FOUND;
3807 ed = new_ExpDef(EXP_COMMENT);
3808 ed->ignoring = true;
3809 ed->prev = defining;
3810 defining = ed;
3811 free_tlist(origline);
3812 return DIRECTIVE_FOUND;
3814 case PP_ENDCOMMENT:
3815 if (defining != NULL) {
3816 if (defining->type == EXP_COMMENT) {
3817 if (defining->def_depth > 0) {
3818 defining->def_depth --;
3819 return NO_DIRECTIVE_FOUND;
3821 } else {
3822 return NO_DIRECTIVE_FOUND;
3825 if ((defining == NULL) || (defining->type != EXP_COMMENT)) {
3826 error(ERR_NONFATAL, "`%%endcomment': no matching `%%comment'");
3827 return DIRECTIVE_FOUND;
3829 ed = defining;
3830 defining = ed->prev;
3831 nasm_free(ed);
3832 free_tlist(origline);
3833 return DIRECTIVE_FOUND;
3835 case PP_FINAL:
3836 if (defining != NULL) return NO_DIRECTIVE_FOUND;
3837 if (in_final != false) {
3838 error(ERR_FATAL, "`%%final' cannot be used recursively");
3840 tline = tline->next;
3841 skip_white_(tline);
3842 if (tline == NULL) {
3843 error(ERR_NONFATAL, "`%%final' expects at least one parameter");
3844 } else {
3845 l = new_Line();
3846 l->first = copy_Token(tline);
3847 l->next = finals;
3848 finals = l;
3850 free_tlist(origline);
3851 return DIRECTIVE_FOUND;
3853 default:
3854 error(ERR_FATAL,
3855 "preprocessor directive `%s' not yet implemented",
3856 pp_directives[i]);
3857 return DIRECTIVE_FOUND;
3862 * Ensure that a macro parameter contains a condition code and
3863 * nothing else. Return the condition code index if so, or -1
3864 * otherwise.
3866 static int find_cc(Token * t)
3868 Token *tt;
3869 int i, j, k, m;
3871 if (!t)
3872 return -1; /* Probably a %+ without a space */
3874 skip_white_(t);
3875 if (t->type != TOK_ID)
3876 return -1;
3877 tt = t->next;
3878 skip_white_(tt);
3879 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3880 return -1;
3882 i = -1;
3883 j = ARRAY_SIZE(conditions);
3884 while (j - i > 1) {
3885 k = (j + i) / 2;
3886 m = nasm_stricmp(t->text, conditions[k]);
3887 if (m == 0) {
3888 i = k;
3889 j = -2;
3890 break;
3891 } else if (m < 0) {
3892 j = k;
3893 } else
3894 i = k;
3896 if (j != -2)
3897 return -1;
3898 return i;
3901 static bool paste_tokens(Token **head, bool handle_paste_tokens)
3903 Token **tail, *t, *tt;
3904 Token **paste_head;
3905 bool did_paste = false;
3906 char *tmp;
3908 /* Now handle token pasting... */
3909 paste_head = NULL;
3910 tail = head;
3911 while ((t = *tail) && (tt = t->next)) {
3912 switch (t->type) {
3913 case TOK_WHITESPACE:
3914 if (tt->type == TOK_WHITESPACE) {
3915 /* Zap adjacent whitespace tokens */
3916 t->next = delete_Token(tt);
3917 } else {
3918 /* Do not advance paste_head here */
3919 tail = &t->next;
3921 break;
3922 case TOK_ID:
3923 case TOK_NUMBER:
3924 case TOK_FLOAT:
3926 size_t len = 0;
3927 char *tmp, *p;
3929 while (tt && (tt->type == TOK_ID || tt->type == TOK_PREPROC_ID ||
3930 tt->type == TOK_NUMBER || tt->type == TOK_FLOAT ||
3931 tt->type == TOK_OTHER)) {
3932 len += strlen(tt->text);
3933 tt = tt->next;
3937 * Now tt points to the first token after
3938 * the potential paste area...
3940 if (tt != t->next) {
3941 /* We have at least two tokens... */
3942 len += strlen(t->text);
3943 p = tmp = nasm_malloc(len+1);
3945 while (t != tt) {
3946 strcpy(p, t->text);
3947 p = strchr(p, '\0');
3948 t = delete_Token(t);
3951 t = *tail = tokenize(tmp);
3952 nasm_free(tmp);
3954 while (t->next) {
3955 tail = &t->next;
3956 t = t->next;
3958 t->next = tt; /* Attach the remaining token chain */
3960 did_paste = true;
3962 paste_head = tail;
3963 tail = &t->next;
3964 break;
3966 case TOK_PASTE: /* %+ */
3967 if (handle_paste_tokens) {
3968 /* Zap %+ and whitespace tokens to the right */
3969 while (t && (t->type == TOK_WHITESPACE ||
3970 t->type == TOK_PASTE))
3971 t = *tail = delete_Token(t);
3972 if (!paste_head || !t)
3973 break; /* Nothing to paste with */
3974 tail = paste_head;
3975 t = *tail;
3976 tt = t->next;
3977 while (tok_type_(tt, TOK_WHITESPACE))
3978 tt = t->next = delete_Token(tt);
3980 if (tt) {
3981 tmp = nasm_strcat(t->text, tt->text);
3982 delete_Token(t);
3983 tt = delete_Token(tt);
3984 t = *tail = tokenize(tmp);
3985 nasm_free(tmp);
3986 while (t->next) {
3987 tail = &t->next;
3988 t = t->next;
3990 t->next = tt; /* Attach the remaining token chain */
3991 did_paste = true;
3993 paste_head = tail;
3994 tail = &t->next;
3995 break;
3997 /* else fall through */
3998 default:
3999 tail = &t->next;
4000 if (!tok_type_(t->next, TOK_WHITESPACE))
4001 paste_head = tail;
4002 break;
4005 return did_paste;
4009 * expands to a list of tokens from %{x:y}
4011 static Token *expand_mmac_params_range(ExpInv *ei, Token *tline, Token ***last)
4013 Token *t = tline, **tt, *tm, *head;
4014 char *pos;
4015 int fst, lst, j, i;
4017 pos = strchr(tline->text, ':');
4018 nasm_assert(pos);
4020 lst = atoi(pos + 1);
4021 fst = atoi(tline->text + 1);
4024 * only macros params are accounted so
4025 * if someone passes %0 -- we reject such
4026 * value(s)
4028 if (lst == 0 || fst == 0)
4029 goto err;
4031 /* the values should be sane */
4032 if ((fst > (int)ei->nparam || fst < (-(int)ei->nparam)) ||
4033 (lst > (int)ei->nparam || lst < (-(int)ei->nparam)))
4034 goto err;
4036 fst = fst < 0 ? fst + (int)ei->nparam + 1: fst;
4037 lst = lst < 0 ? lst + (int)ei->nparam + 1: lst;
4039 /* counted from zero */
4040 fst--, lst--;
4043 * it will be at least one token
4045 tm = ei->params[(fst + ei->rotate) % ei->nparam];
4046 t = new_Token(NULL, tm->type, tm->text, 0);
4047 head = t, tt = &t->next;
4048 if (fst < lst) {
4049 for (i = fst + 1; i <= lst; i++) {
4050 t = new_Token(NULL, TOK_OTHER, ",", 0);
4051 *tt = t, tt = &t->next;
4052 j = (i + ei->rotate) % ei->nparam;
4053 tm = ei->params[j];
4054 t = new_Token(NULL, tm->type, tm->text, 0);
4055 *tt = t, tt = &t->next;
4057 } else {
4058 for (i = fst - 1; i >= lst; i--) {
4059 t = new_Token(NULL, TOK_OTHER, ",", 0);
4060 *tt = t, tt = &t->next;
4061 j = (i + ei->rotate) % ei->nparam;
4062 tm = ei->params[j];
4063 t = new_Token(NULL, tm->type, tm->text, 0);
4064 *tt = t, tt = &t->next;
4068 *last = tt;
4069 return head;
4071 err:
4072 error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
4073 &tline->text[1]);
4074 return tline;
4078 * Expand MMacro-local things: parameter references (%0, %n, %+n,
4079 * %-n) and MMacro-local identifiers (%%foo) as well as
4080 * macro indirection (%[...]) and range (%{..:..}).
4082 static Token *expand_mmac_params(Token * tline)
4084 Token *t, *tt, **tail, *thead;
4085 bool changed = false;
4086 char *pos;
4088 tail = &thead;
4089 thead = NULL;
4091 while (tline) {
4092 if (tline->type == TOK_PREPROC_ID &&
4093 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
4094 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
4095 tline->text[1] == '%')) {
4096 char *text = NULL;
4097 int type = 0, cc; /* type = 0 to placate optimisers */
4098 char tmpbuf[30];
4099 unsigned int n;
4100 int i;
4101 ExpInv *ei;
4103 t = tline;
4104 tline = tline->next;
4106 for (ei = istk->expansion; ei != NULL; ei = ei->prev) {
4107 if (ei->type == EXP_MMACRO) {
4108 break;
4111 if (ei == NULL) {
4112 error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4113 } else {
4114 pos = strchr(t->text, ':');
4115 if (!pos) {
4116 switch (t->text[1]) {
4118 * We have to make a substitution of one of the
4119 * forms %1, %-1, %+1, %%foo, %0.
4121 case '0':
4122 if ((strlen(t->text) > 2) && (t->text[2] == '0')) {
4123 type = TOK_ID;
4124 text = nasm_strdup(ei->label_text);
4125 } else {
4126 type = TOK_NUMBER;
4127 snprintf(tmpbuf, sizeof(tmpbuf), "%d", ei->nparam);
4128 text = nasm_strdup(tmpbuf);
4130 break;
4131 case '%':
4132 type = TOK_ID;
4133 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4134 ei->unique);
4135 text = nasm_strcat(tmpbuf, t->text + 2);
4136 break;
4137 case '-':
4138 n = atoi(t->text + 2) - 1;
4139 if (n >= ei->nparam)
4140 tt = NULL;
4141 else {
4142 if (ei->nparam > 1)
4143 n = (n + ei->rotate) % ei->nparam;
4144 tt = ei->params[n];
4146 cc = find_cc(tt);
4147 if (cc == -1) {
4148 error(ERR_NONFATAL,
4149 "macro parameter %d is not a condition code",
4150 n + 1);
4151 text = NULL;
4152 } else {
4153 type = TOK_ID;
4154 if (inverse_ccs[cc] == -1) {
4155 error(ERR_NONFATAL,
4156 "condition code `%s' is not invertible",
4157 conditions[cc]);
4158 text = NULL;
4159 } else
4160 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4162 break;
4163 case '+':
4164 n = atoi(t->text + 2) - 1;
4165 if (n >= ei->nparam)
4166 tt = NULL;
4167 else {
4168 if (ei->nparam > 1)
4169 n = (n + ei->rotate) % ei->nparam;
4170 tt = ei->params[n];
4172 cc = find_cc(tt);
4173 if (cc == -1) {
4174 error(ERR_NONFATAL,
4175 "macro parameter %d is not a condition code",
4176 n + 1);
4177 text = NULL;
4178 } else {
4179 type = TOK_ID;
4180 text = nasm_strdup(conditions[cc]);
4182 break;
4183 default:
4184 n = atoi(t->text + 1) - 1;
4185 if (n >= ei->nparam)
4186 tt = NULL;
4187 else {
4188 if (ei->nparam > 1)
4189 n = (n + ei->rotate) % ei->nparam;
4190 tt = ei->params[n];
4192 if (tt) {
4193 for (i = 0; i < ei->paramlen[n]; i++) {
4194 *tail = new_Token(NULL, tt->type, tt->text, 0);
4195 tail = &(*tail)->next;
4196 tt = tt->next;
4199 text = NULL; /* we've done it here */
4200 break;
4202 } else {
4204 * seems we have a parameters range here
4206 Token *head, **last;
4207 head = expand_mmac_params_range(ei, t, &last);
4208 if (head != t) {
4209 *tail = head;
4210 *last = tline;
4211 tline = head;
4212 text = NULL;
4216 if (!text) {
4217 delete_Token(t);
4218 } else {
4219 *tail = t;
4220 tail = &t->next;
4221 t->type = type;
4222 nasm_free(t->text);
4223 t->text = text;
4224 t->a.mac = NULL;
4226 changed = true;
4227 continue;
4228 } else if (tline->type == TOK_INDIRECT) {
4229 t = tline;
4230 tline = tline->next;
4231 tt = tokenize(t->text);
4232 tt = expand_mmac_params(tt);
4233 tt = expand_smacro(tt);
4234 *tail = tt;
4235 while (tt) {
4236 tt->a.mac = NULL; /* Necessary? */
4237 tail = &tt->next;
4238 tt = tt->next;
4240 delete_Token(t);
4241 changed = true;
4242 } else {
4243 t = *tail = tline;
4244 tline = tline->next;
4245 t->a.mac = NULL;
4246 tail = &t->next;
4249 *tail = NULL;
4251 if (changed)
4252 paste_tokens(&thead, false);
4254 return thead;
4258 * Expand all single-line macro calls made in the given line.
4259 * Return the expanded version of the line. The original is deemed
4260 * to be destroyed in the process. (In reality we'll just move
4261 * Tokens from input to output a lot of the time, rather than
4262 * actually bothering to destroy and replicate.)
4265 static Token *expand_smacro(Token * tline)
4267 Token *t, *tt, *mstart, **tail, *thead;
4268 SMacro *head = NULL, *m;
4269 Token **params;
4270 int *paramsize;
4271 unsigned int nparam, sparam;
4272 int brackets;
4273 Token *org_tline = tline;
4274 Context *ctx;
4275 const char *mname;
4276 int deadman = DEADMAN_LIMIT;
4277 bool expanded;
4280 * Trick: we should avoid changing the start token pointer since it can
4281 * be contained in "next" field of other token. Because of this
4282 * we allocate a copy of first token and work with it; at the end of
4283 * routine we copy it back
4285 if (org_tline) {
4286 tline = new_Token(org_tline->next, org_tline->type,
4287 org_tline->text, 0);
4288 tline->a.mac = org_tline->a.mac;
4289 nasm_free(org_tline->text);
4290 org_tline->text = NULL;
4293 expanded = true; /* Always expand %+ at least once */
4295 again:
4296 thead = NULL;
4297 tail = &thead;
4299 while (tline) { /* main token loop */
4300 if (!--deadman) {
4301 error(ERR_NONFATAL, "interminable macro recursion");
4302 goto err;
4305 if ((mname = tline->text)) {
4306 /* if this token is a local macro, look in local context */
4307 if (tline->type == TOK_ID) {
4308 head = (SMacro *)hash_findix(&smacros, mname);
4309 } else if (tline->type == TOK_PREPROC_ID) {
4310 ctx = get_ctx(mname, &mname, true);
4311 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4312 } else
4313 head = NULL;
4316 * We've hit an identifier. As in is_mmacro below, we first
4317 * check whether the identifier is a single-line macro at
4318 * all, then think about checking for parameters if
4319 * necessary.
4321 list_for_each(m, head)
4322 if (!mstrcmp(m->name, mname, m->casesense))
4323 break;
4324 if (m) {
4325 mstart = tline;
4326 params = NULL;
4327 paramsize = NULL;
4328 if (m->nparam == 0) {
4330 * Simple case: the macro is parameterless. Discard the
4331 * one token that the macro call took, and push the
4332 * expansion back on the to-do stack.
4334 if (!m->expansion) {
4335 if (!strcmp("__FILE__", m->name)) {
4336 int32_t num = 0;
4337 char *file = NULL;
4338 src_get(&num, &file);
4339 tline->text = nasm_quote(file, strlen(file));
4340 tline->type = TOK_STRING;
4341 nasm_free(file);
4342 continue;
4344 if (!strcmp("__LINE__", m->name)) {
4345 nasm_free(tline->text);
4346 make_tok_num(tline, src_get_linnum());
4347 continue;
4349 if (!strcmp("__BITS__", m->name)) {
4350 nasm_free(tline->text);
4351 make_tok_num(tline, globalbits);
4352 continue;
4354 tline = delete_Token(tline);
4355 continue;
4357 } else {
4359 * Complicated case: at least one macro with this name
4360 * exists and takes parameters. We must find the
4361 * parameters in the call, count them, find the SMacro
4362 * that corresponds to that form of the macro call, and
4363 * substitute for the parameters when we expand. What a
4364 * pain.
4366 /*tline = tline->next;
4367 skip_white_(tline); */
4368 do {
4369 t = tline->next;
4370 while (tok_type_(t, TOK_SMAC_END)) {
4371 t->a.mac->in_progress = false;
4372 t->text = NULL;
4373 t = tline->next = delete_Token(t);
4375 tline = t;
4376 } while (tok_type_(tline, TOK_WHITESPACE));
4377 if (!tok_is_(tline, "(")) {
4379 * This macro wasn't called with parameters: ignore
4380 * the call. (Behaviour borrowed from gnu cpp.)
4382 tline = mstart;
4383 m = NULL;
4384 } else {
4385 int paren = 0;
4386 int white = 0;
4387 brackets = 0;
4388 nparam = 0;
4389 sparam = PARAM_DELTA;
4390 params = nasm_malloc(sparam * sizeof(Token *));
4391 params[0] = tline->next;
4392 paramsize = nasm_malloc(sparam * sizeof(int));
4393 paramsize[0] = 0;
4394 while (true) { /* parameter loop */
4396 * For some unusual expansions
4397 * which concatenates function call
4399 t = tline->next;
4400 while (tok_type_(t, TOK_SMAC_END)) {
4401 t->a.mac->in_progress = false;
4402 t->text = NULL;
4403 t = tline->next = delete_Token(t);
4405 tline = t;
4407 if (!tline) {
4408 error(ERR_NONFATAL,
4409 "macro call expects terminating `)'");
4410 break;
4412 if (tline->type == TOK_WHITESPACE
4413 && brackets <= 0) {
4414 if (paramsize[nparam])
4415 white++;
4416 else
4417 params[nparam] = tline->next;
4418 continue; /* parameter loop */
4420 if (tline->type == TOK_OTHER
4421 && tline->text[1] == 0) {
4422 char ch = tline->text[0];
4423 if (ch == ',' && !paren && brackets <= 0) {
4424 if (++nparam >= sparam) {
4425 sparam += PARAM_DELTA;
4426 params = nasm_realloc(params,
4427 sparam * sizeof(Token *));
4428 paramsize = nasm_realloc(paramsize,
4429 sparam * sizeof(int));
4431 params[nparam] = tline->next;
4432 paramsize[nparam] = 0;
4433 white = 0;
4434 continue; /* parameter loop */
4436 if (ch == '{' &&
4437 (brackets > 0 || (brackets == 0 &&
4438 !paramsize[nparam])))
4440 if (!(brackets++)) {
4441 params[nparam] = tline->next;
4442 continue; /* parameter loop */
4445 if (ch == '}' && brackets > 0)
4446 if (--brackets == 0) {
4447 brackets = -1;
4448 continue; /* parameter loop */
4450 if (ch == '(' && !brackets)
4451 paren++;
4452 if (ch == ')' && brackets <= 0)
4453 if (--paren < 0)
4454 break;
4456 if (brackets < 0) {
4457 brackets = 0;
4458 error(ERR_NONFATAL, "braces do not "
4459 "enclose all of macro parameter");
4461 paramsize[nparam] += white + 1;
4462 white = 0;
4463 } /* parameter loop */
4464 nparam++;
4465 while (m && (m->nparam != nparam ||
4466 mstrcmp(m->name, mname,
4467 m->casesense)))
4468 m = m->next;
4469 if (!m)
4470 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4471 "macro `%s' exists, "
4472 "but not taking %d parameters",
4473 mstart->text, nparam);
4476 if (m && m->in_progress)
4477 m = NULL;
4478 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4480 * Design question: should we handle !tline, which
4481 * indicates missing ')' here, or expand those
4482 * macros anyway, which requires the (t) test a few
4483 * lines down?
4485 nasm_free(params);
4486 nasm_free(paramsize);
4487 tline = mstart;
4488 } else {
4490 * Expand the macro: we are placed on the last token of the
4491 * call, so that we can easily split the call from the
4492 * following tokens. We also start by pushing an SMAC_END
4493 * token for the cycle removal.
4495 t = tline;
4496 if (t) {
4497 tline = t->next;
4498 t->next = NULL;
4500 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4501 tt->a.mac = m;
4502 m->in_progress = true;
4503 tline = tt;
4504 list_for_each(t, m->expansion) {
4505 if (t->type >= TOK_SMAC_PARAM) {
4506 Token *pcopy = tline, **ptail = &pcopy;
4507 Token *ttt, *pt;
4508 int i;
4510 ttt = params[t->type - TOK_SMAC_PARAM];
4511 i = paramsize[t->type - TOK_SMAC_PARAM];
4512 while (--i >= 0) {
4513 pt = *ptail = new_Token(tline, ttt->type,
4514 ttt->text, 0);
4515 ptail = &pt->next;
4516 ttt = ttt->next;
4518 tline = pcopy;
4519 } else if (t->type == TOK_PREPROC_Q) {
4520 tt = new_Token(tline, TOK_ID, mname, 0);
4521 tline = tt;
4522 } else if (t->type == TOK_PREPROC_QQ) {
4523 tt = new_Token(tline, TOK_ID, m->name, 0);
4524 tline = tt;
4525 } else {
4526 tt = new_Token(tline, t->type, t->text, 0);
4527 tline = tt;
4532 * Having done that, get rid of the macro call, and clean
4533 * up the parameters.
4535 nasm_free(params);
4536 nasm_free(paramsize);
4537 free_tlist(mstart);
4538 expanded = true;
4539 continue; /* main token loop */
4544 if (tline->type == TOK_SMAC_END) {
4545 tline->a.mac->in_progress = false;
4546 tline = delete_Token(tline);
4547 } else {
4548 t = *tail = tline;
4549 tline = tline->next;
4550 t->a.mac = NULL;
4551 t->next = NULL;
4552 tail = &t->next;
4557 * Now scan the entire line and look for successive TOK_IDs that resulted
4558 * after expansion (they can't be produced by tokenize()). The successive
4559 * TOK_IDs should be concatenated.
4560 * Also we look for %+ tokens and concatenate the tokens before and after
4561 * them (without white spaces in between).
4563 if (expanded && paste_tokens(&thead, true)) {
4565 * If we concatenated something, *and* we had previously expanded
4566 * an actual macro, scan the lines again for macros...
4568 tline = thead;
4569 expanded = false;
4570 goto again;
4573 err:
4574 if (org_tline) {
4575 if (thead) {
4576 *org_tline = *thead;
4577 /* since we just gave text to org_line, don't free it */
4578 thead->text = NULL;
4579 delete_Token(thead);
4580 } else {
4581 /* the expression expanded to empty line;
4582 we can't return NULL for some reasons
4583 we just set the line to a single WHITESPACE token. */
4584 memset(org_tline, 0, sizeof(*org_tline));
4585 org_tline->text = NULL;
4586 org_tline->type = TOK_WHITESPACE;
4588 thead = org_tline;
4591 return thead;
4595 * Similar to expand_smacro but used exclusively with macro identifiers
4596 * right before they are fetched in. The reason is that there can be
4597 * identifiers consisting of several subparts. We consider that if there
4598 * are more than one element forming the name, user wants a expansion,
4599 * otherwise it will be left as-is. Example:
4601 * %define %$abc cde
4603 * the identifier %$abc will be left as-is so that the handler for %define
4604 * will suck it and define the corresponding value. Other case:
4606 * %define _%$abc cde
4608 * In this case user wants name to be expanded *before* %define starts
4609 * working, so we'll expand %$abc into something (if it has a value;
4610 * otherwise it will be left as-is) then concatenate all successive
4611 * PP_IDs into one.
4613 static Token *expand_id(Token * tline)
4615 Token *cur, *oldnext = NULL;
4617 if (!tline || !tline->next)
4618 return tline;
4620 cur = tline;
4621 while (cur->next &&
4622 (cur->next->type == TOK_ID ||
4623 cur->next->type == TOK_PREPROC_ID
4624 || cur->next->type == TOK_NUMBER))
4625 cur = cur->next;
4627 /* If identifier consists of just one token, don't expand */
4628 if (cur == tline)
4629 return tline;
4631 if (cur) {
4632 oldnext = cur->next; /* Detach the tail past identifier */
4633 cur->next = NULL; /* so that expand_smacro stops here */
4636 tline = expand_smacro(tline);
4638 if (cur) {
4639 /* expand_smacro possibly changhed tline; re-scan for EOL */
4640 cur = tline;
4641 while (cur && cur->next)
4642 cur = cur->next;
4643 if (cur)
4644 cur->next = oldnext;
4647 return tline;
4651 * Determine whether the given line constitutes a multi-line macro
4652 * call, and return the ExpDef structure called if so. Doesn't have
4653 * to check for an initial label - that's taken care of in
4654 * expand_mmacro - but must check numbers of parameters. Guaranteed
4655 * to be called with tline->type == TOK_ID, so the putative macro
4656 * name is easy to find.
4658 static ExpDef *is_mmacro(Token * tline, Token *** params_array)
4660 ExpDef *head, *ed;
4661 Token **params;
4662 int nparam;
4664 head = (ExpDef *) hash_findix(&expdefs, tline->text);
4667 * Efficiency: first we see if any macro exists with the given
4668 * name. If not, we can return NULL immediately. _Then_ we
4669 * count the parameters, and then we look further along the
4670 * list if necessary to find the proper ExpDef.
4672 list_for_each(ed, head)
4673 if (!mstrcmp(ed->name, tline->text, ed->casesense))
4674 break;
4675 if (!ed)
4676 return NULL;
4679 * OK, we have a potential macro. Count and demarcate the
4680 * parameters.
4682 count_mmac_params(tline->next, &nparam, &params);
4685 * So we know how many parameters we've got. Find the ExpDef
4686 * structure that handles this number.
4688 while (ed) {
4689 if (ed->nparam_min <= nparam
4690 && (ed->plus || nparam <= ed->nparam_max)) {
4692 * It's right, and we can use it. Add its default
4693 * parameters to the end of our list if necessary.
4695 if (ed->defaults && nparam < ed->nparam_min + ed->ndefs) {
4696 params =
4697 nasm_realloc(params,
4698 ((ed->nparam_min + ed->ndefs +
4699 1) * sizeof(*params)));
4700 while (nparam < ed->nparam_min + ed->ndefs) {
4701 params[nparam] = ed->defaults[nparam - ed->nparam_min];
4702 nparam++;
4706 * If we've gone over the maximum parameter count (and
4707 * we're in Plus mode), ignore parameters beyond
4708 * nparam_max.
4710 if (ed->plus && nparam > ed->nparam_max)
4711 nparam = ed->nparam_max;
4713 * Then terminate the parameter list, and leave.
4715 if (!params) { /* need this special case */
4716 params = nasm_malloc(sizeof(*params));
4717 nparam = 0;
4719 params[nparam] = NULL;
4720 *params_array = params;
4721 return ed;
4724 * This one wasn't right: look for the next one with the
4725 * same name.
4727 list_for_each(ed, ed->next)
4728 if (!mstrcmp(ed->name, tline->text, ed->casesense))
4729 break;
4733 * After all that, we didn't find one with the right number of
4734 * parameters. Issue a warning, and fail to expand the macro.
4736 error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4737 "macro `%s' exists, but not taking %d parameters",
4738 tline->text, nparam);
4739 nasm_free(params);
4740 return NULL;
4744 * Expand the multi-line macro call made by the given line, if
4745 * there is one to be expanded. If there is, push the expansion on
4746 * istk->expansion and return true. Otherwise return false.
4748 static bool expand_mmacro(Token * tline)
4750 Token *label = NULL;
4751 int dont_prepend = 0;
4752 Token **params, *t, *mtok;
4753 Line *l = NULL;
4754 ExpDef *ed;
4755 ExpInv *ei;
4756 int i, nparam, *paramlen;
4757 const char *mname;
4759 t = tline;
4760 skip_white_(t);
4761 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4762 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4763 return false;
4764 mtok = t;
4765 ed = is_mmacro(t, &params);
4766 if (ed != NULL) {
4767 mname = t->text;
4768 } else {
4769 Token *last;
4771 * We have an id which isn't a macro call. We'll assume
4772 * it might be a label; we'll also check to see if a
4773 * colon follows it. Then, if there's another id after
4774 * that lot, we'll check it again for macro-hood.
4776 label = last = t;
4777 t = t->next;
4778 if (tok_type_(t, TOK_WHITESPACE))
4779 last = t, t = t->next;
4780 if (tok_is_(t, ":")) {
4781 dont_prepend = 1;
4782 last = t, t = t->next;
4783 if (tok_type_(t, TOK_WHITESPACE))
4784 last = t, t = t->next;
4786 if (!tok_type_(t, TOK_ID) || !(ed = is_mmacro(t, &params)))
4787 return false;
4788 last->next = NULL;
4789 mname = t->text;
4790 tline = t;
4794 * Fix up the parameters: this involves stripping leading and
4795 * trailing whitespace, then stripping braces if they are
4796 * present.
4798 for (nparam = 0; params[nparam]; nparam++) ;
4799 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4801 for (i = 0; params[i]; i++) {
4802 int brace = false;
4803 int comma = (!ed->plus || i < nparam - 1);
4805 t = params[i];
4806 skip_white_(t);
4807 if (tok_is_(t, "{"))
4808 t = t->next, brace = true, comma = false;
4809 params[i] = t;
4810 paramlen[i] = 0;
4811 while (t) {
4812 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4813 break; /* ... because we have hit a comma */
4814 if (comma && t->type == TOK_WHITESPACE
4815 && tok_is_(t->next, ","))
4816 break; /* ... or a space then a comma */
4817 if (brace && t->type == TOK_OTHER && !strcmp(t->text, "}"))
4818 break; /* ... or a brace */
4819 t = t->next;
4820 paramlen[i]++;
4824 if (ed->cur_depth >= ed->max_depth) {
4825 if (ed->max_depth > 1) {
4826 error(ERR_WARNING,
4827 "reached maximum macro recursion depth of %i for %s",
4828 ed->max_depth,ed->name);
4830 return false;
4831 } else {
4832 ed->cur_depth ++;
4836 * OK, we have found a ExpDef structure representing a
4837 * previously defined mmacro. Create an expansion invocation
4838 * and point it back to the expansion definition. Substitution of
4839 * parameter tokens and macro-local tokens doesn't get done
4840 * until the single-line macro substitution process; this is
4841 * because delaying them allows us to change the semantics
4842 * later through %rotate.
4844 ei = new_ExpInv(EXP_MMACRO, ed);
4845 // ei->label = label;
4846 // ei->label_text = detoken(label, false);
4847 ei->current = ed->line;
4848 ei->emitting = true;
4849 // ei->iline = tline;
4850 ei->params = params;
4851 ei->nparam = nparam;
4852 ei->rotate = 0;
4853 ei->paramlen = paramlen;
4854 ei->lineno = 0;
4856 ei->prev = istk->expansion;
4857 istk->expansion = ei;
4859 /***** todo: relocate %? (Q) and %?? (QQ); %00 already relocated *****/
4861 list_for_each(l, m->expansion) {
4862 Token **tail;
4864 l = new_Line();
4865 l->next = istk->expansion;
4866 istk->expansion = l;
4867 tail = &l->first;
4869 list_for_each(t, ei->current->first) {
4870 Token *x = t;
4871 switch (t->type) {
4872 case TOK_PREPROC_Q:
4873 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4874 break;
4875 case TOK_PREPROC_QQ:
4876 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4877 break;
4878 case TOK_PREPROC_ID:
4879 if (t->text[1] == '0' && t->text[2] == '0') {
4880 dont_prepend = -1;
4881 x = label;
4882 if (!x)
4883 continue;
4885 // fall through
4886 default:
4887 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4888 break;
4890 tail = &tt->next;
4892 *tail = NULL;
4897 * Special case: detect %00 on first invocation; if found,
4898 * avoid emitting any labels that precede the mmacro call.
4899 * ed->prepend is set to -1 when %00 is detected, else 1.
4901 if (ed->prepend == 0) {
4902 for (l = ed->line; l != NULL; l = l->next) {
4903 for (t = l->first; t != NULL; t = t->next) {
4904 if ((t->type == TOK_PREPROC_ID) &&
4905 (strlen(t->text) == 3) &&
4906 (t->text[1] == '0') && (t->text[2] == '0')) {
4907 dont_prepend = -1;
4908 break;
4911 if (dont_prepend < 0) {
4912 break;
4915 ed->prepend = ((dont_prepend < 0) ? -1 : 1);
4919 * If we had a label, push it on as the first line of
4920 * the macro expansion.
4922 if (label != NULL) {
4923 if (ed->prepend < 0) {
4924 ei->label_text = detoken(label, false);
4925 } else {
4926 if (dont_prepend == 0) {
4927 t = label;
4928 while (t->next != NULL) {
4929 t = t->next;
4931 t->next = new_Token(NULL, TOK_OTHER, ":", 0);
4933 Line *l = new_Line();
4934 l->first = copy_Token(label);
4935 l->next = ei->current;
4936 ei->current = l;
4940 list->uplevel(ed->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4942 istk->mmac_depth++;
4943 return true;
4946 /* The function that actually does the error reporting */
4947 static void verror(int severity, const char *fmt, va_list arg)
4949 char buff[1024];
4951 vsnprintf(buff, sizeof(buff), fmt, arg);
4953 if ((istk != NULL) && (istk->mmac_depth > 0)) {
4954 ExpInv *ei = istk->expansion;
4955 int lineno = ei->lineno;
4956 while (ei != NULL) {
4957 if (ei->type == EXP_MMACRO) {
4958 break;
4960 lineno += ei->relno;
4961 ei = ei->prev;
4963 nasm_error(severity, "(%s:%d) %s", ei->def->name,
4964 lineno, buff);
4965 } else {
4966 nasm_error(severity, "%s", buff);
4971 * Since preprocessor always operate only on the line that didn't
4972 * arrived yet, we should always use ERR_OFFBY1.
4974 static void error(int severity, const char *fmt, ...)
4976 va_list arg;
4977 va_start(arg, fmt);
4978 verror(severity, fmt, arg);
4979 va_end(arg);
4983 * Because %else etc are evaluated in the state context
4984 * of the previous branch, errors might get lost with error():
4985 * %if 0 ... %else trailing garbage ... %endif
4986 * So %else etc should report errors with this function.
4988 static void error_precond(int severity, const char *fmt, ...)
4990 va_list arg;
4992 /* Only ignore the error if it's really in a dead branch */
4993 if ((istk != NULL) &&
4994 (istk->expansion != NULL) &&
4995 (istk->expansion->type == EXP_IF) &&
4996 (istk->expansion->def->state == COND_NEVER))
4997 return;
4999 va_start(arg, fmt);
5000 verror(severity, fmt, arg);
5001 va_end(arg);
5004 static void
5005 pp_reset(char *file, int apass, ListGen * listgen, StrList **deplist)
5007 Token *t;
5009 cstk = NULL;
5010 istk = nasm_malloc(sizeof(Include));
5011 istk->next = NULL;
5012 istk->expansion = NULL;
5013 istk->fp = fopen(file, "r");
5014 istk->fname = NULL;
5015 src_set_fname(nasm_strdup(file));
5016 src_set_linnum(0);
5017 istk->lineinc = 1;
5018 istk->mmac_depth = 0;
5019 if (!istk->fp)
5020 error(ERR_FATAL|ERR_NOFILE, "unable to open input file `%s'",
5021 file);
5022 defining = NULL;
5023 finals = NULL;
5024 in_final = false;
5025 nested_mac_count = 0;
5026 nested_rep_count = 0;
5027 init_macros();
5028 unique = 0;
5029 if (tasm_compatible_mode) {
5030 stdmacpos = nasm_stdmac;
5031 } else {
5032 stdmacpos = nasm_stdmac_after_tasm;
5034 any_extrastdmac = extrastdmac && *extrastdmac;
5035 do_predef = true;
5036 list = listgen;
5039 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
5040 * The caller, however, will also pass in 3 for preprocess-only so
5041 * we can set __PASS__ accordingly.
5043 pass = apass > 2 ? 2 : apass;
5045 dephead = deptail = deplist;
5046 if (deplist) {
5047 StrList *sl = nasm_malloc(strlen(file)+1+sizeof sl->next);
5048 sl->next = NULL;
5049 strcpy(sl->str, file);
5050 *deptail = sl;
5051 deptail = &sl->next;
5055 * Define the __PASS__ macro. This is defined here unlike
5056 * all the other builtins, because it is special -- it varies between
5057 * passes.
5059 t = nasm_malloc(sizeof(*t));
5060 t->next = NULL;
5061 make_tok_num(t, apass);
5062 t->a.mac = NULL;
5063 define_smacro(NULL, "__PASS__", true, 0, t);
5066 static char *pp_getline(void)
5068 char *line;
5069 Token *tline;
5070 ExpInv *ei;
5072 while (1) {
5074 * Fetch a tokenized line, either from the expansion
5075 * buffer or from the input file.
5077 tline = NULL;
5079 while (1) { /* until we get a line we can use */
5081 * Fetch a tokenized line from the expansion buffer
5083 if (istk->expansion != NULL) {
5084 ei = istk->expansion;
5085 if (ei->current != NULL) {
5086 if (ei->emitting == false) {
5087 ei->current = NULL;
5088 continue;
5090 Line *l = NULL;
5091 l = ei->current;
5092 ei->current = l->next;
5093 ei->lineno++;
5094 tline = copy_Token(l->first);
5095 if (((ei->type == EXP_REP) ||
5096 (ei->type == EXP_MMACRO) ||
5097 (ei->type == EXP_WHILE))
5098 && (ei->def->nolist == false)) {
5099 char *p = detoken(tline, false);
5100 list->line(LIST_MACRO, p);
5101 nasm_free(p);
5103 if (ei->linnum > -1) {
5104 src_set_linnum(src_get_linnum() + 1);
5106 break;
5107 } else if ((ei->type == EXP_REP) &&
5108 (ei->def->cur_depth < ei->def->max_depth)) {
5109 ei->def->cur_depth ++;
5110 ei->current = ei->def->line;
5111 ei->lineno = 0;
5112 continue;
5113 } else if ((ei->type == EXP_WHILE) &&
5114 (ei->def->cur_depth < ei->def->max_depth)) {
5115 ei->current = ei->def->line;
5116 ei->lineno = 0;
5117 tline = copy_Token(ei->current->first);
5118 int j = if_condition(tline, PP_WHILE);
5119 tline = NULL;
5120 j = (((j < 0) ? COND_NEVER : j) ? COND_IF_TRUE : COND_IF_FALSE);
5121 if (j == COND_IF_TRUE) {
5122 ei->current = ei->current->next;
5123 ei->def->cur_depth ++;
5124 } else {
5125 ei->emitting = false;
5126 ei->current = NULL;
5127 ei->def->cur_depth = ei->def->max_depth;
5129 continue;
5130 } else {
5131 istk->expansion = ei->prev;
5132 ExpDef *ed = ei->def;
5133 if (ed != NULL) {
5134 if ((ei->emitting == true) &&
5135 (ed->max_depth == DEADMAN_LIMIT) &&
5136 (ed->cur_depth == DEADMAN_LIMIT)
5138 error(ERR_FATAL, "runaway expansion detected, aborting");
5140 if (ed->cur_depth > 0) {
5141 ed->cur_depth --;
5142 } else if ((ed->type != EXP_MMACRO) && (ed->type != EXP_IF)) {
5143 /***** should this really be right here??? *****/
5145 Line *l = NULL, *ll = NULL;
5146 for (l = ed->line; l != NULL;) {
5147 if (l->first != NULL) {
5148 free_tlist(l->first);
5149 l->first = NULL;
5151 ll = l;
5152 l = l->next;
5153 nasm_free(ll);
5155 expansions = ed->prev;
5156 nasm_free(ed);
5159 if ((ei->type == EXP_REP) ||
5160 (ei->type == EXP_MMACRO) ||
5161 (ei->type == EXP_WHILE)) {
5162 list->downlevel(LIST_MACRO);
5163 if (ei->type == EXP_MMACRO) {
5164 istk->mmac_depth--;
5168 if (ei->linnum > -1) {
5169 src_set_linnum(ei->linnum);
5171 nasm_free(ei);
5172 continue;
5177 * Read in line from input and tokenize
5179 line = read_line();
5180 if (line) { /* from the current input file */
5181 line = prepreproc(line);
5182 tline = tokenize(line);
5183 nasm_free(line);
5184 break;
5188 * The current file has ended; work down the istk
5191 Include *i = istk;
5192 fclose(i->fp);
5193 if (i->expansion != NULL) {
5194 error(ERR_FATAL,
5195 "end of file while still in an expansion");
5197 /* only set line and file name if there's a next node */
5198 if (i->next) {
5199 src_set_linnum(i->lineno);
5200 nasm_free(src_set_fname(i->fname));
5202 if ((i->next == NULL) && (finals != NULL)) {
5203 in_final = true;
5204 ei = new_ExpInv(EXP_FINAL, NULL);
5205 ei->emitting = true;
5206 ei->current = finals;
5207 istk->expansion = ei;
5208 finals = NULL;
5209 continue;
5211 istk = i->next;
5212 list->downlevel(LIST_INCLUDE);
5213 nasm_free(i);
5214 if (istk == NULL) {
5215 if (finals != NULL) {
5216 in_final = true;
5217 } else {
5218 return NULL;
5221 continue;
5225 if (defining == NULL) {
5226 tline = expand_mmac_params(tline);
5230 * Check the line to see if it's a preprocessor directive.
5232 if (do_directive(tline) == DIRECTIVE_FOUND) {
5233 continue;
5234 } else if (defining != NULL) {
5236 * We're defining an expansion. We emit nothing at all,
5237 * and just shove the tokenized line on to the definition.
5239 if (defining->ignoring == false) {
5240 Line *l = new_Line();
5241 l->first = tline;
5242 if (defining->line == NULL) {
5243 defining->line = l;
5244 defining->last = l;
5245 } else {
5246 defining->last->next = l;
5247 defining->last = l;
5249 } else {
5250 //free_tlist(tline); /***** sanity check: is this supposed to be here? *****/
5252 defining->linecount++;
5253 continue;
5254 } else if ((istk->expansion != NULL) &&
5255 (istk->expansion->emitting != true)) {
5257 * We're in a non-emitting branch of an expansion.
5258 * Emit nothing at all, not even a blank line: when we
5259 * emerge from the expansion we'll give a line-number
5260 * directive so we keep our place correctly.
5262 free_tlist(tline);
5263 continue;
5264 } else {
5265 tline = expand_smacro(tline);
5266 if (expand_mmacro(tline) != true) {
5268 * De-tokenize the line again, and emit it.
5270 line = detoken(tline, true);
5271 free_tlist(tline);
5272 break;
5273 } else {
5274 continue;
5278 return line;
5281 static void pp_cleanup(int pass)
5283 if (defining != NULL) {
5284 error(ERR_NONFATAL, "end of file while still defining an expansion");
5285 nasm_free(defining); /***** todo: free everything to avoid mem leaks *****/
5286 defining = NULL;
5288 while (cstk != NULL)
5289 ctx_pop();
5290 free_macros();
5291 while (istk != NULL) {
5292 Include *i = istk;
5293 istk = istk->next;
5294 fclose(i->fp);
5295 nasm_free(i->fname);
5296 nasm_free(i);
5298 while (cstk)
5299 ctx_pop();
5300 nasm_free(src_set_fname(NULL));
5301 if (pass == 0) {
5302 IncPath *i;
5303 free_llist(predef);
5304 delete_Blocks();
5305 while ((i = ipath)) {
5306 ipath = i->next;
5307 if (i->path)
5308 nasm_free(i->path);
5309 nasm_free(i);
5314 void pp_include_path(char *path)
5316 IncPath *i;
5318 i = nasm_malloc(sizeof(IncPath));
5319 i->path = path ? nasm_strdup(path) : NULL;
5320 i->next = NULL;
5322 if (ipath) {
5323 IncPath *j = ipath;
5324 while (j->next)
5325 j = j->next;
5326 j->next = i;
5327 } else {
5328 ipath = i;
5332 void pp_pre_include(char *fname)
5334 Token *inc, *space, *name;
5335 Line *l;
5337 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5338 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5339 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5341 l = new_Line();
5342 l->next = predef;
5343 l->first = inc;
5344 predef = l;
5347 void pp_pre_define(char *definition)
5349 Token *def, *space;
5350 Line *l;
5351 char *equals;
5353 equals = strchr(definition, '=');
5354 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5355 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5356 if (equals)
5357 *equals = ' ';
5358 space->next = tokenize(definition);
5359 if (equals)
5360 *equals = '=';
5362 l = new_Line();
5363 l->next = predef;
5364 l->first = def;
5365 predef = l;
5368 void pp_pre_undefine(char *definition)
5370 Token *def, *space;
5371 Line *l;
5373 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5374 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5375 space->next = tokenize(definition);
5377 l = new_Line();
5378 l->next = predef;
5379 l->first = def;
5380 predef = l;
5384 * This function is used to assist with "runtime" preprocessor
5385 * directives, e.g. pp_runtime("%define __BITS__ 64");
5387 * ERRORS ARE IGNORED HERE, SO MAKE COMPLETELY SURE THAT YOU
5388 * PASS A VALID STRING TO THIS FUNCTION!!!!!
5391 void pp_runtime(char *definition)
5393 Token *def;
5395 def = tokenize(definition);
5396 if (do_directive(def) == NO_DIRECTIVE_FOUND)
5397 free_tlist(def);
5401 void pp_extra_stdmac(macros_t *macros)
5403 extrastdmac = macros;
5406 static void make_tok_num(Token * tok, int64_t val)
5408 char numbuf[20];
5409 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5410 tok->text = nasm_strdup(numbuf);
5411 tok->type = TOK_NUMBER;
5414 Preproc nasmpp = {
5415 pp_reset,
5416 pp_getline,
5417 pp_cleanup