Fix global variables without declarations
[nasm.git] / asm / preproc.c
blob75d92f457377abb6e6cda988ec208e11055841e6
1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2016 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>
73 #include "nasm.h"
74 #include "nasmlib.h"
75 #include "error.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"
83 #include "listing.h"
85 typedef struct SMacro SMacro;
86 typedef struct MMacro MMacro;
87 typedef struct MMacroInvocation MMacroInvocation;
88 typedef struct Context Context;
89 typedef struct Token Token;
90 typedef struct Blocks Blocks;
91 typedef struct Line Line;
92 typedef struct Include Include;
93 typedef struct Cond Cond;
94 typedef struct IncPath IncPath;
97 * Note on the storage of both SMacro and MMacros: the hash table
98 * indexes them case-insensitively, and we then have to go through a
99 * linked list of potential case aliases (and, for MMacros, parameter
100 * ranges); this is to preserve the matching semantics of the earlier
101 * code. If the number of case aliases for a specific macro is a
102 * performance issue, you may want to reconsider your coding style.
106 * Store the definition of a single-line macro.
108 struct SMacro {
109 SMacro *next;
110 char *name;
111 bool casesense;
112 bool in_progress;
113 unsigned int nparam;
114 Token *expansion;
118 * Store the definition of a multi-line macro. This is also used to
119 * store the interiors of `%rep...%endrep' blocks, which are
120 * effectively self-re-invoking multi-line macros which simply
121 * don't have a name or bother to appear in the hash tables. %rep
122 * blocks are signified by having a NULL `name' field.
124 * In a MMacro describing a `%rep' block, the `in_progress' field
125 * isn't merely boolean, but gives the number of repeats left to
126 * run.
128 * The `next' field is used for storing MMacros in hash tables; the
129 * `next_active' field is for stacking them on istk entries.
131 * When a MMacro is being expanded, `params', `iline', `nparam',
132 * `paramlen', `rotate' and `unique' are local to the invocation.
134 struct MMacro {
135 MMacro *next;
136 MMacroInvocation *prev; /* previous invocation */
137 char *name;
138 int nparam_min, nparam_max;
139 bool casesense;
140 bool plus; /* is the last parameter greedy? */
141 bool nolist; /* is this macro listing-inhibited? */
142 int64_t in_progress; /* is this macro currently being expanded? */
143 int32_t max_depth; /* maximum number of recursive expansions allowed */
144 Token *dlist; /* All defaults as one list */
145 Token **defaults; /* Parameter default pointers */
146 int ndefs; /* number of default parameters */
147 Line *expansion;
149 MMacro *next_active;
150 MMacro *rep_nest; /* used for nesting %rep */
151 Token **params; /* actual parameters */
152 Token *iline; /* invocation line */
153 unsigned int nparam, rotate;
154 int *paramlen;
155 uint64_t unique;
156 int lineno; /* Current line number on expansion */
157 uint64_t condcnt; /* number of if blocks... */
159 const char *fname; /* File where defined */
160 int32_t xline; /* First line in macro */
164 /* Store the definition of a multi-line macro, as defined in a
165 * previous recursive macro expansion.
167 struct MMacroInvocation {
168 MMacroInvocation *prev; /* previous invocation */
169 Token **params; /* actual parameters */
170 Token *iline; /* invocation line */
171 unsigned int nparam, rotate;
172 int *paramlen;
173 uint64_t unique;
174 uint64_t condcnt;
179 * The context stack is composed of a linked list of these.
181 struct Context {
182 Context *next;
183 char *name;
184 struct hash_table localmac;
185 uint32_t number;
189 * This is the internal form which we break input lines up into.
190 * Typically stored in linked lists.
192 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
193 * necessarily used as-is, but is intended to denote the number of
194 * the substituted parameter. So in the definition
196 * %define a(x,y) ( (x) & ~(y) )
198 * the token representing `x' will have its type changed to
199 * TOK_SMAC_PARAM, but the one representing `y' will be
200 * TOK_SMAC_PARAM+1.
202 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
203 * which doesn't need quotes around it. Used in the pre-include
204 * mechanism as an alternative to trying to find a sensible type of
205 * quote to use on the filename we were passed.
207 enum pp_token_type {
208 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
209 TOK_PREPROC_ID, TOK_STRING,
210 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
211 TOK_INTERNAL_STRING,
212 TOK_PREPROC_Q, TOK_PREPROC_QQ,
213 TOK_PASTE, /* %+ */
214 TOK_INDIRECT, /* %[...] */
215 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
216 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
219 #define PP_CONCAT_MASK(x) (1 << (x))
220 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
222 struct tokseq_match {
223 int mask_head;
224 int mask_tail;
227 struct Token {
228 Token *next;
229 char *text;
230 union {
231 SMacro *mac; /* associated macro for TOK_SMAC_END */
232 size_t len; /* scratch length field */
233 } a; /* Auxiliary data */
234 enum pp_token_type type;
238 * Multi-line macro definitions are stored as a linked list of
239 * these, which is essentially a container to allow several linked
240 * lists of Tokens.
242 * Note that in this module, linked lists are treated as stacks
243 * wherever possible. For this reason, Lines are _pushed_ on to the
244 * `expansion' field in MMacro structures, so that the linked list,
245 * if walked, would give the macro lines in reverse order; this
246 * means that we can walk the list when expanding a macro, and thus
247 * push the lines on to the `expansion' field in _istk_ in reverse
248 * order (so that when popped back off they are in the right
249 * order). It may seem cockeyed, and it relies on my design having
250 * an even number of steps in, but it works...
252 * Some of these structures, rather than being actual lines, are
253 * markers delimiting the end of the expansion of a given macro.
254 * This is for use in the cycle-tracking and %rep-handling code.
255 * Such structures have `finishes' non-NULL, and `first' NULL. All
256 * others have `finishes' NULL, but `first' may still be NULL if
257 * the line is blank.
259 struct Line {
260 Line *next;
261 MMacro *finishes;
262 Token *first;
266 * To handle an arbitrary level of file inclusion, we maintain a
267 * stack (ie linked list) of these things.
269 struct Include {
270 Include *next;
271 FILE *fp;
272 Cond *conds;
273 Line *expansion;
274 const char *fname;
275 int lineno, lineinc;
276 MMacro *mstk; /* stack of active macros/reps */
280 * Include search path. This is simply a list of strings which get
281 * prepended, in turn, to the name of an include file, in an
282 * attempt to find the file if it's not in the current directory.
284 struct IncPath {
285 IncPath *next;
286 char *path;
290 * File real name hash, so we don't have to re-search the include
291 * path for every pass (and potentially more than that if a file
292 * is used more than once.)
294 struct hash_table FileHash;
297 * Conditional assembly: we maintain a separate stack of these for
298 * each level of file inclusion. (The only reason we keep the
299 * stacks separate is to ensure that a stray `%endif' in a file
300 * included from within the true branch of a `%if' won't terminate
301 * it and cause confusion: instead, rightly, it'll cause an error.)
303 struct Cond {
304 Cond *next;
305 int state;
307 enum {
309 * These states are for use just after %if or %elif: IF_TRUE
310 * means the condition has evaluated to truth so we are
311 * currently emitting, whereas IF_FALSE means we are not
312 * currently emitting but will start doing so if a %else comes
313 * up. In these states, all directives are admissible: %elif,
314 * %else and %endif. (And of course %if.)
316 COND_IF_TRUE, COND_IF_FALSE,
318 * These states come up after a %else: ELSE_TRUE means we're
319 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
320 * any %elif or %else will cause an error.
322 COND_ELSE_TRUE, COND_ELSE_FALSE,
324 * These states mean that we're not emitting now, and also that
325 * nothing until %endif will be emitted at all. COND_DONE is
326 * used when we've had our moment of emission
327 * and have now started seeing %elifs. COND_NEVER is used when
328 * the condition construct in question is contained within a
329 * non-emitting branch of a larger condition construct,
330 * or if there is an error.
332 COND_DONE, COND_NEVER
334 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
337 * These defines are used as the possible return values for do_directive
339 #define NO_DIRECTIVE_FOUND 0
340 #define DIRECTIVE_FOUND 1
343 * This define sets the upper limit for smacro and recursive mmacro
344 * expansions
346 #define DEADMAN_LIMIT (1 << 20)
348 /* max reps */
349 #define REP_LIMIT ((INT64_C(1) << 62))
352 * Condition codes. Note that we use c_ prefix not C_ because C_ is
353 * used in nasm.h for the "real" condition codes. At _this_ level,
354 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
355 * ones, so we need a different enum...
357 static const char * const conditions[] = {
358 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
359 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
360 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
362 enum pp_conds {
363 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
364 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
365 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
366 c_none = -1
368 static const enum pp_conds inverse_ccs[] = {
369 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
370 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,
371 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
375 * Directive names.
377 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
378 static int is_condition(enum preproc_token arg)
380 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
383 /* For TASM compatibility we need to be able to recognise TASM compatible
384 * conditional compilation directives. Using the NASM pre-processor does
385 * not work, so we look for them specifically from the following list and
386 * then jam in the equivalent NASM directive into the input stream.
389 enum {
390 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
391 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
394 static const char * const tasm_directives[] = {
395 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
396 "ifndef", "include", "local"
399 static int StackSize = 4;
400 static const char *StackPointer = "ebp";
401 static int ArgOffset = 8;
402 static int LocalOffset = 0;
404 static Context *cstk;
405 static Include *istk;
406 static IncPath *ipath = NULL;
408 static int pass; /* HACK: pass 0 = generate dependencies only */
409 static StrList **dephead;
411 static uint64_t unique; /* unique identifier numbers */
413 static Line *predef = NULL;
414 static bool do_predef;
417 * The current set of multi-line macros we have defined.
419 static struct hash_table mmacros;
422 * The current set of single-line macros we have defined.
424 static struct hash_table smacros;
427 * The multi-line macro we are currently defining, or the %rep
428 * block we are currently reading, if any.
430 static MMacro *defining;
432 static uint64_t nested_mac_count;
433 static uint64_t nested_rep_count;
436 * The number of macro parameters to allocate space for at a time.
438 #define PARAM_DELTA 16
441 * The standard macro set: defined in macros.c in a set of arrays.
442 * This gives our position in any macro set, while we are processing it.
443 * The stdmacset is an array of such macro sets.
445 static macros_t *stdmacpos;
446 static macros_t **stdmacnext;
447 static macros_t *stdmacros[8];
448 static macros_t *extrastdmac;
451 * Tokens are allocated in blocks to improve speed
453 #define TOKEN_BLOCKSIZE 4096
454 static Token *freeTokens = NULL;
455 struct Blocks {
456 Blocks *next;
457 void *chunk;
460 static Blocks blocks = { NULL, NULL };
463 * Forward declarations.
465 static void pp_add_stdmac(macros_t *macros);
466 static Token *expand_mmac_params(Token * tline);
467 static Token *expand_smacro(Token * tline);
468 static Token *expand_id(Token * tline);
469 static Context *get_ctx(const char *name, const char **namep);
470 static void make_tok_num(Token * tok, int64_t val);
471 static void pp_verror(int severity, const char *fmt, va_list ap);
472 static vefunc real_verror;
473 static void *new_Block(size_t size);
474 static void delete_Blocks(void);
475 static Token *new_Token(Token * next, enum pp_token_type type,
476 const char *text, int txtlen);
477 static Token *delete_Token(Token * t);
480 * Macros for safe checking of token pointers, avoid *(NULL)
482 #define tok_type_(x,t) ((x) && (x)->type == (t))
483 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
484 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
485 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
488 * nasm_unquote with error if the string contains NUL characters.
489 * If the string contains NUL characters, issue an error and return
490 * the C len, i.e. truncate at the NUL.
492 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
494 size_t len = nasm_unquote(qstr, NULL);
495 size_t clen = strlen(qstr);
497 if (len != clen)
498 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
499 pp_directives[directive]);
501 return clen;
505 * In-place reverse a list of tokens.
507 static Token *reverse_tokens(Token *t)
509 Token *prev = NULL;
510 Token *next;
512 while (t) {
513 next = t->next;
514 t->next = prev;
515 prev = t;
516 t = next;
519 return prev;
523 * Handle TASM specific directives, which do not contain a % in
524 * front of them. We do it here because I could not find any other
525 * place to do it for the moment, and it is a hack (ideally it would
526 * be nice to be able to use the NASM pre-processor to do it).
528 static char *check_tasm_directive(char *line)
530 int32_t i, j, k, m, len;
531 char *p, *q, *oldline, oldchar;
533 p = nasm_skip_spaces(line);
535 /* Binary search for the directive name */
536 i = -1;
537 j = ARRAY_SIZE(tasm_directives);
538 q = nasm_skip_word(p);
539 len = q - p;
540 if (len) {
541 oldchar = p[len];
542 p[len] = 0;
543 while (j - i > 1) {
544 k = (j + i) / 2;
545 m = nasm_stricmp(p, tasm_directives[k]);
546 if (m == 0) {
547 /* We have found a directive, so jam a % in front of it
548 * so that NASM will then recognise it as one if it's own.
550 p[len] = oldchar;
551 len = strlen(p);
552 oldline = line;
553 line = nasm_malloc(len + 2);
554 line[0] = '%';
555 if (k == TM_IFDIFI) {
557 * NASM does not recognise IFDIFI, so we convert
558 * it to %if 0. This is not used in NASM
559 * compatible code, but does need to parse for the
560 * TASM macro package.
562 strcpy(line + 1, "if 0");
563 } else {
564 memcpy(line + 1, p, len + 1);
566 nasm_free(oldline);
567 return line;
568 } else if (m < 0) {
569 j = k;
570 } else
571 i = k;
573 p[len] = oldchar;
575 return line;
579 * The pre-preprocessing stage... This function translates line
580 * number indications as they emerge from GNU cpp (`# lineno "file"
581 * flags') into NASM preprocessor line number indications (`%line
582 * lineno file').
584 static char *prepreproc(char *line)
586 int lineno, fnlen;
587 char *fname, *oldline;
589 if (line[0] == '#' && line[1] == ' ') {
590 oldline = line;
591 fname = oldline + 2;
592 lineno = atoi(fname);
593 fname += strspn(fname, "0123456789 ");
594 if (*fname == '"')
595 fname++;
596 fnlen = strcspn(fname, "\"");
597 line = nasm_malloc(20 + fnlen);
598 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
599 nasm_free(oldline);
601 if (tasm_compatible_mode)
602 return check_tasm_directive(line);
603 return line;
607 * Free a linked list of tokens.
609 static void free_tlist(Token * list)
611 while (list)
612 list = delete_Token(list);
616 * Free a linked list of lines.
618 static void free_llist(Line * list)
620 Line *l, *tmp;
621 list_for_each_safe(l, tmp, list) {
622 free_tlist(l->first);
623 nasm_free(l);
628 * Free an MMacro
630 static void free_mmacro(MMacro * m)
632 nasm_free(m->name);
633 free_tlist(m->dlist);
634 nasm_free(m->defaults);
635 free_llist(m->expansion);
636 nasm_free(m);
640 * Free all currently defined macros, and free the hash tables
642 static void free_smacro_table(struct hash_table *smt)
644 SMacro *s, *tmp;
645 const char *key;
646 struct hash_tbl_node *it = NULL;
648 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
649 nasm_free((void *)key);
650 list_for_each_safe(s, tmp, s) {
651 nasm_free(s->name);
652 free_tlist(s->expansion);
653 nasm_free(s);
656 hash_free(smt);
659 static void free_mmacro_table(struct hash_table *mmt)
661 MMacro *m, *tmp;
662 const char *key;
663 struct hash_tbl_node *it = NULL;
665 it = NULL;
666 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
667 nasm_free((void *)key);
668 list_for_each_safe(m ,tmp, m)
669 free_mmacro(m);
671 hash_free(mmt);
674 static void free_macros(void)
676 free_smacro_table(&smacros);
677 free_mmacro_table(&mmacros);
681 * Initialize the hash tables
683 static void init_macros(void)
685 hash_init(&smacros, HASH_LARGE);
686 hash_init(&mmacros, HASH_LARGE);
690 * Pop the context stack.
692 static void ctx_pop(void)
694 Context *c = cstk;
696 cstk = cstk->next;
697 free_smacro_table(&c->localmac);
698 nasm_free(c->name);
699 nasm_free(c);
703 * Search for a key in the hash index; adding it if necessary
704 * (in which case we initialize the data pointer to NULL.)
706 static void **
707 hash_findi_add(struct hash_table *hash, const char *str)
709 struct hash_insert hi;
710 void **r;
711 char *strx;
713 r = hash_findi(hash, str, &hi);
714 if (r)
715 return r;
717 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
718 return hash_add(&hi, strx, NULL);
722 * Like hash_findi, but returns the data element rather than a pointer
723 * to it. Used only when not adding a new element, hence no third
724 * argument.
726 static void *
727 hash_findix(struct hash_table *hash, const char *str)
729 void **p;
731 p = hash_findi(hash, str, NULL);
732 return p ? *p : NULL;
736 * read line from standart macros set,
737 * if there no more left -- return NULL
739 static char *line_from_stdmac(void)
741 unsigned char c;
742 const unsigned char *p = stdmacpos;
743 char *line, *q;
744 size_t len = 0;
746 if (!stdmacpos)
747 return NULL;
749 while ((c = *p++)) {
750 if (c >= 0x80)
751 len += pp_directives_len[c - 0x80] + 1;
752 else
753 len++;
756 line = nasm_malloc(len + 1);
757 q = line;
758 while ((c = *stdmacpos++)) {
759 if (c >= 0x80) {
760 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
761 q += pp_directives_len[c - 0x80];
762 *q++ = ' ';
763 } else {
764 *q++ = c;
767 stdmacpos = p;
768 *q = '\0';
770 if (!*stdmacpos) {
771 /* This was the last of this particular macro set */
772 stdmacpos = NULL;
773 if (*stdmacnext) {
774 stdmacpos = *stdmacnext++;
775 } else if (do_predef) {
776 Line *pd, *l;
777 Token *head, **tail, *t;
780 * Nasty hack: here we push the contents of
781 * `predef' on to the top-level expansion stack,
782 * since this is the most convenient way to
783 * implement the pre-include and pre-define
784 * features.
786 list_for_each(pd, predef) {
787 head = NULL;
788 tail = &head;
789 list_for_each(t, pd->first) {
790 *tail = new_Token(NULL, t->type, t->text, 0);
791 tail = &(*tail)->next;
794 l = nasm_malloc(sizeof(Line));
795 l->next = istk->expansion;
796 l->first = head;
797 l->finishes = NULL;
799 istk->expansion = l;
801 do_predef = false;
805 return line;
808 static char *read_line(void)
810 unsigned int size, c, next;
811 const unsigned int delta = 512;
812 const unsigned int pad = 8;
813 unsigned int nr_cont = 0;
814 bool cont = false;
815 char *buffer, *p;
817 /* Standart macros set (predefined) goes first */
818 p = line_from_stdmac();
819 if (p)
820 return p;
822 size = delta;
823 p = buffer = nasm_malloc(size);
825 for (;;) {
826 c = fgetc(istk->fp);
827 if ((int)(c) == EOF) {
828 p[0] = 0;
829 break;
832 switch (c) {
833 case '\r':
834 next = fgetc(istk->fp);
835 if (next != '\n')
836 ungetc(next, istk->fp);
837 if (cont) {
838 cont = false;
839 continue;
841 break;
843 case '\n':
844 if (cont) {
845 cont = false;
846 continue;
848 break;
850 case '\\':
851 next = fgetc(istk->fp);
852 ungetc(next, istk->fp);
853 if (next == '\r' || next == '\n') {
854 cont = true;
855 nr_cont++;
856 continue;
858 break;
861 if (c == '\r' || c == '\n') {
862 *p++ = 0;
863 break;
866 if (p >= (buffer + size - pad)) {
867 buffer = nasm_realloc(buffer, size + delta);
868 p = buffer + size - pad;
869 size += delta;
872 *p++ = (unsigned char)c;
875 if (p == buffer) {
876 nasm_free(buffer);
877 return NULL;
880 src_set_linnum(src_get_linnum() + istk->lineinc +
881 (nr_cont * istk->lineinc));
884 * Handle spurious ^Z, which may be inserted into source files
885 * by some file transfer utilities.
887 buffer[strcspn(buffer, "\032")] = '\0';
889 lfmt->line(LIST_READ, buffer);
891 return buffer;
895 * Tokenize a line of text. This is a very simple process since we
896 * don't need to parse the value out of e.g. numeric tokens: we
897 * simply split one string into many.
899 static Token *tokenize(char *line)
901 char c, *p = line;
902 enum pp_token_type type;
903 Token *list = NULL;
904 Token *t, **tail = &list;
906 while (*line) {
907 p = line;
908 if (*p == '%') {
909 p++;
910 if (*p == '+' && !nasm_isdigit(p[1])) {
911 p++;
912 type = TOK_PASTE;
913 } else if (nasm_isdigit(*p) ||
914 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
915 do {
916 p++;
918 while (nasm_isdigit(*p));
919 type = TOK_PREPROC_ID;
920 } else if (*p == '{') {
921 p++;
922 while (*p) {
923 if (*p == '}')
924 break;
925 p[-1] = *p;
926 p++;
928 if (*p != '}')
929 nasm_error(ERR_WARNING | ERR_PASS1,
930 "unterminated %%{ construct");
931 p[-1] = '\0';
932 if (*p)
933 p++;
934 type = TOK_PREPROC_ID;
935 } else if (*p == '[') {
936 int lvl = 1;
937 line += 2; /* Skip the leading %[ */
938 p++;
939 while (lvl && (c = *p++)) {
940 switch (c) {
941 case ']':
942 lvl--;
943 break;
944 case '%':
945 if (*p == '[')
946 lvl++;
947 break;
948 case '\'':
949 case '\"':
950 case '`':
951 p = nasm_skip_string(p - 1) + 1;
952 break;
953 default:
954 break;
957 p--;
958 if (*p)
959 *p++ = '\0';
960 if (lvl)
961 nasm_error(ERR_NONFATAL|ERR_PASS1,
962 "unterminated %%[ construct");
963 type = TOK_INDIRECT;
964 } else if (*p == '?') {
965 type = TOK_PREPROC_Q; /* %? */
966 p++;
967 if (*p == '?') {
968 type = TOK_PREPROC_QQ; /* %?? */
969 p++;
971 } else if (*p == '!') {
972 type = TOK_PREPROC_ID;
973 p++;
974 if (isidchar(*p)) {
975 do {
976 p++;
978 while (isidchar(*p));
979 } else if (*p == '\'' || *p == '\"' || *p == '`') {
980 p = nasm_skip_string(p);
981 if (*p)
982 p++;
983 else
984 nasm_error(ERR_NONFATAL|ERR_PASS1,
985 "unterminated %%! string");
986 } else {
987 /* %! without string or identifier */
988 type = TOK_OTHER; /* Legacy behavior... */
990 } else if (isidchar(*p) ||
991 ((*p == '!' || *p == '%' || *p == '$') &&
992 isidchar(p[1]))) {
993 do {
994 p++;
996 while (isidchar(*p));
997 type = TOK_PREPROC_ID;
998 } else {
999 type = TOK_OTHER;
1000 if (*p == '%')
1001 p++;
1003 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1004 type = TOK_ID;
1005 p++;
1006 while (*p && isidchar(*p))
1007 p++;
1008 } else if (*p == '\'' || *p == '"' || *p == '`') {
1010 * A string token.
1012 type = TOK_STRING;
1013 p = nasm_skip_string(p);
1015 if (*p) {
1016 p++;
1017 } else {
1018 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1019 /* Handling unterminated strings by UNV */
1020 /* type = -1; */
1022 } else if (p[0] == '$' && p[1] == '$') {
1023 type = TOK_OTHER; /* TOKEN_BASE */
1024 p += 2;
1025 } else if (isnumstart(*p)) {
1026 bool is_hex = false;
1027 bool is_float = false;
1028 bool has_e = false;
1029 char c, *r;
1032 * A numeric token.
1035 if (*p == '$') {
1036 p++;
1037 is_hex = true;
1040 for (;;) {
1041 c = *p++;
1043 if (!is_hex && (c == 'e' || c == 'E')) {
1044 has_e = true;
1045 if (*p == '+' || *p == '-') {
1047 * e can only be followed by +/- if it is either a
1048 * prefixed hex number or a floating-point number
1050 p++;
1051 is_float = true;
1053 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1054 is_hex = true;
1055 } else if (c == 'P' || c == 'p') {
1056 is_float = true;
1057 if (*p == '+' || *p == '-')
1058 p++;
1059 } else if (isnumchar(c))
1060 ; /* just advance */
1061 else if (c == '.') {
1063 * we need to deal with consequences of the legacy
1064 * parser, like "1.nolist" being two tokens
1065 * (TOK_NUMBER, TOK_ID) here; at least give it
1066 * a shot for now. In the future, we probably need
1067 * a flex-based scanner with proper pattern matching
1068 * to do it as well as it can be done. Nothing in
1069 * the world is going to help the person who wants
1070 * 0x123.p16 interpreted as two tokens, though.
1072 r = p;
1073 while (*r == '_')
1074 r++;
1076 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1077 (!is_hex && (*r == 'e' || *r == 'E')) ||
1078 (*r == 'p' || *r == 'P')) {
1079 p = r;
1080 is_float = true;
1081 } else
1082 break; /* Terminate the token */
1083 } else
1084 break;
1086 p--; /* Point to first character beyond number */
1088 if (p == line+1 && *line == '$') {
1089 type = TOK_OTHER; /* TOKEN_HERE */
1090 } else {
1091 if (has_e && !is_hex) {
1092 /* 1e13 is floating-point, but 1e13h is not */
1093 is_float = true;
1096 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1098 } else if (nasm_isspace(*p)) {
1099 type = TOK_WHITESPACE;
1100 p = nasm_skip_spaces(p);
1102 * Whitespace just before end-of-line is discarded by
1103 * pretending it's a comment; whitespace just before a
1104 * comment gets lumped into the comment.
1106 if (!*p || *p == ';') {
1107 type = TOK_COMMENT;
1108 while (*p)
1109 p++;
1111 } else if (*p == ';') {
1112 type = TOK_COMMENT;
1113 while (*p)
1114 p++;
1115 } else {
1117 * Anything else is an operator of some kind. We check
1118 * for all the double-character operators (>>, <<, //,
1119 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1120 * else is a single-character operator.
1122 type = TOK_OTHER;
1123 if ((p[0] == '>' && p[1] == '>') ||
1124 (p[0] == '<' && p[1] == '<') ||
1125 (p[0] == '/' && p[1] == '/') ||
1126 (p[0] == '<' && p[1] == '=') ||
1127 (p[0] == '>' && p[1] == '=') ||
1128 (p[0] == '=' && p[1] == '=') ||
1129 (p[0] == '!' && p[1] == '=') ||
1130 (p[0] == '<' && p[1] == '>') ||
1131 (p[0] == '&' && p[1] == '&') ||
1132 (p[0] == '|' && p[1] == '|') ||
1133 (p[0] == '^' && p[1] == '^')) {
1134 p++;
1136 p++;
1139 /* Handling unterminated string by UNV */
1140 /*if (type == -1)
1142 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1143 t->text[p-line] = *line;
1144 tail = &t->next;
1146 else */
1147 if (type != TOK_COMMENT) {
1148 *tail = t = new_Token(NULL, type, line, p - line);
1149 tail = &t->next;
1151 line = p;
1153 return list;
1157 * this function allocates a new managed block of memory and
1158 * returns a pointer to the block. The managed blocks are
1159 * deleted only all at once by the delete_Blocks function.
1161 static void *new_Block(size_t size)
1163 Blocks *b = &blocks;
1165 /* first, get to the end of the linked list */
1166 while (b->next)
1167 b = b->next;
1168 /* now allocate the requested chunk */
1169 b->chunk = nasm_malloc(size);
1171 /* now allocate a new block for the next request */
1172 b->next = nasm_zalloc(sizeof(Blocks));
1173 return b->chunk;
1177 * this function deletes all managed blocks of memory
1179 static void delete_Blocks(void)
1181 Blocks *a, *b = &blocks;
1184 * keep in mind that the first block, pointed to by blocks
1185 * is a static and not dynamically allocated, so we don't
1186 * free it.
1188 while (b) {
1189 if (b->chunk)
1190 nasm_free(b->chunk);
1191 a = b;
1192 b = b->next;
1193 if (a != &blocks)
1194 nasm_free(a);
1196 memset(&blocks, 0, sizeof(blocks));
1200 * this function creates a new Token and passes a pointer to it
1201 * back to the caller. It sets the type and text elements, and
1202 * also the a.mac and next elements to NULL.
1204 static Token *new_Token(Token * next, enum pp_token_type type,
1205 const char *text, int txtlen)
1207 Token *t;
1208 int i;
1210 if (!freeTokens) {
1211 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1212 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1213 freeTokens[i].next = &freeTokens[i + 1];
1214 freeTokens[i].next = NULL;
1216 t = freeTokens;
1217 freeTokens = t->next;
1218 t->next = next;
1219 t->a.mac = NULL;
1220 t->type = type;
1221 if (type == TOK_WHITESPACE || !text) {
1222 t->text = NULL;
1223 } else {
1224 if (txtlen == 0)
1225 txtlen = strlen(text);
1226 t->text = nasm_malloc(txtlen+1);
1227 memcpy(t->text, text, txtlen);
1228 t->text[txtlen] = '\0';
1230 return t;
1233 static Token *delete_Token(Token * t)
1235 Token *next = t->next;
1236 nasm_free(t->text);
1237 t->next = freeTokens;
1238 freeTokens = t;
1239 return next;
1243 * Convert a line of tokens back into text.
1244 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1245 * will be transformed into ..@ctxnum.xxx
1247 static char *detoken(Token * tlist, bool expand_locals)
1249 Token *t;
1250 char *line, *p;
1251 const char *q;
1252 int len = 0;
1254 list_for_each(t, tlist) {
1255 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1256 char *v;
1257 char *q = t->text;
1259 v = t->text + 2;
1260 if (*v == '\'' || *v == '\"' || *v == '`') {
1261 size_t len = nasm_unquote(v, NULL);
1262 size_t clen = strlen(v);
1264 if (len != clen) {
1265 nasm_error(ERR_NONFATAL | ERR_PASS1,
1266 "NUL character in %%! string");
1267 v = NULL;
1271 if (v) {
1272 char *p = getenv(v);
1273 if (!p) {
1274 nasm_error(ERR_NONFATAL | ERR_PASS1,
1275 "nonexistent environment variable `%s'", v);
1277 * FIXME We better should investigate if accessing
1278 * ->text[1] without ->text[0] is safe enough.
1280 t->text = nasm_zalloc(2);
1281 } else
1282 t->text = nasm_strdup(p);
1284 nasm_free(q);
1287 /* Expand local macros here and not during preprocessing */
1288 if (expand_locals &&
1289 t->type == TOK_PREPROC_ID && t->text &&
1290 t->text[0] == '%' && t->text[1] == '$') {
1291 const char *q;
1292 char *p;
1293 Context *ctx = get_ctx(t->text, &q);
1294 if (ctx) {
1295 char buffer[40];
1296 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1297 p = nasm_strcat(buffer, q);
1298 nasm_free(t->text);
1299 t->text = p;
1302 if (t->type == TOK_WHITESPACE)
1303 len++;
1304 else if (t->text)
1305 len += strlen(t->text);
1308 p = line = nasm_malloc(len + 1);
1310 list_for_each(t, tlist) {
1311 if (t->type == TOK_WHITESPACE) {
1312 *p++ = ' ';
1313 } else if (t->text) {
1314 q = t->text;
1315 while (*q)
1316 *p++ = *q++;
1319 *p = '\0';
1321 return line;
1325 * A scanner, suitable for use by the expression evaluator, which
1326 * operates on a line of Tokens. Expects a pointer to a pointer to
1327 * the first token in the line to be passed in as its private_data
1328 * field.
1330 * FIX: This really needs to be unified with stdscan.
1332 static int ppscan(void *private_data, struct tokenval *tokval)
1334 Token **tlineptr = private_data;
1335 Token *tline;
1336 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1338 do {
1339 tline = *tlineptr;
1340 *tlineptr = tline ? tline->next : NULL;
1341 } while (tline && (tline->type == TOK_WHITESPACE ||
1342 tline->type == TOK_COMMENT));
1344 if (!tline)
1345 return tokval->t_type = TOKEN_EOS;
1347 tokval->t_charptr = tline->text;
1349 if (tline->text[0] == '$' && !tline->text[1])
1350 return tokval->t_type = TOKEN_HERE;
1351 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1352 return tokval->t_type = TOKEN_BASE;
1354 if (tline->type == TOK_ID) {
1355 p = tokval->t_charptr = tline->text;
1356 if (p[0] == '$') {
1357 tokval->t_charptr++;
1358 return tokval->t_type = TOKEN_ID;
1361 for (r = p, s = ourcopy; *r; r++) {
1362 if (r >= p+MAX_KEYWORD)
1363 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1364 *s++ = nasm_tolower(*r);
1366 *s = '\0';
1367 /* right, so we have an identifier sitting in temp storage. now,
1368 * is it actually a register or instruction name, or what? */
1369 return nasm_token_hash(ourcopy, tokval);
1372 if (tline->type == TOK_NUMBER) {
1373 bool rn_error;
1374 tokval->t_integer = readnum(tline->text, &rn_error);
1375 tokval->t_charptr = tline->text;
1376 if (rn_error)
1377 return tokval->t_type = TOKEN_ERRNUM;
1378 else
1379 return tokval->t_type = TOKEN_NUM;
1382 if (tline->type == TOK_FLOAT) {
1383 return tokval->t_type = TOKEN_FLOAT;
1386 if (tline->type == TOK_STRING) {
1387 char bq, *ep;
1389 bq = tline->text[0];
1390 tokval->t_charptr = tline->text;
1391 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1393 if (ep[0] != bq || ep[1] != '\0')
1394 return tokval->t_type = TOKEN_ERRSTR;
1395 else
1396 return tokval->t_type = TOKEN_STR;
1399 if (tline->type == TOK_OTHER) {
1400 if (!strcmp(tline->text, "<<"))
1401 return tokval->t_type = TOKEN_SHL;
1402 if (!strcmp(tline->text, ">>"))
1403 return tokval->t_type = TOKEN_SHR;
1404 if (!strcmp(tline->text, "//"))
1405 return tokval->t_type = TOKEN_SDIV;
1406 if (!strcmp(tline->text, "%%"))
1407 return tokval->t_type = TOKEN_SMOD;
1408 if (!strcmp(tline->text, "=="))
1409 return tokval->t_type = TOKEN_EQ;
1410 if (!strcmp(tline->text, "<>"))
1411 return tokval->t_type = TOKEN_NE;
1412 if (!strcmp(tline->text, "!="))
1413 return tokval->t_type = TOKEN_NE;
1414 if (!strcmp(tline->text, "<="))
1415 return tokval->t_type = TOKEN_LE;
1416 if (!strcmp(tline->text, ">="))
1417 return tokval->t_type = TOKEN_GE;
1418 if (!strcmp(tline->text, "&&"))
1419 return tokval->t_type = TOKEN_DBL_AND;
1420 if (!strcmp(tline->text, "^^"))
1421 return tokval->t_type = TOKEN_DBL_XOR;
1422 if (!strcmp(tline->text, "||"))
1423 return tokval->t_type = TOKEN_DBL_OR;
1427 * We have no other options: just return the first character of
1428 * the token text.
1430 return tokval->t_type = tline->text[0];
1434 * Compare a string to the name of an existing macro; this is a
1435 * simple wrapper which calls either strcmp or nasm_stricmp
1436 * depending on the value of the `casesense' parameter.
1438 static int mstrcmp(const char *p, const char *q, bool casesense)
1440 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1444 * Compare a string to the name of an existing macro; this is a
1445 * simple wrapper which calls either strcmp or nasm_stricmp
1446 * depending on the value of the `casesense' parameter.
1448 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1450 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1454 * Return the Context structure associated with a %$ token. Return
1455 * NULL, having _already_ reported an error condition, if the
1456 * context stack isn't deep enough for the supplied number of $
1457 * signs.
1459 * If "namep" is non-NULL, set it to the pointer to the macro name
1460 * tail, i.e. the part beyond %$...
1462 static Context *get_ctx(const char *name, const char **namep)
1464 Context *ctx;
1465 int i;
1467 if (namep)
1468 *namep = name;
1470 if (!name || name[0] != '%' || name[1] != '$')
1471 return NULL;
1473 if (!cstk) {
1474 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1475 return NULL;
1478 name += 2;
1479 ctx = cstk;
1480 i = 0;
1481 while (ctx && *name == '$') {
1482 name++;
1483 i++;
1484 ctx = ctx->next;
1486 if (!ctx) {
1487 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1488 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1489 return NULL;
1492 if (namep)
1493 *namep = name;
1495 return ctx;
1499 * Open an include file. This routine must always return a valid
1500 * file pointer if it returns - it's responsible for throwing an
1501 * ERR_FATAL and bombing out completely if not. It should also try
1502 * the include path one by one until it finds the file or reaches
1503 * the end of the path.
1505 * Note: for INC_PROBE the function returns NULL at all times;
1506 * instead look for the
1508 enum incopen_mode {
1509 INC_NEEDED, /* File must exist */
1510 INC_OPTIONAL, /* Missing is OK */
1511 INC_PROBE /* Only an existence probe */
1514 /* This is conducts a full pathname search */
1515 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1516 enum incopen_mode omode, enum file_flags fmode)
1518 FILE *fp;
1519 char *prefix = "";
1520 const IncPath *ip = ipath;
1521 int len = strlen(file);
1522 size_t prefix_len = 0;
1523 StrList *sl;
1524 size_t path_len;
1525 bool found;
1527 while (1) {
1528 path_len = prefix_len + len + 1;
1530 sl = nasm_malloc(path_len + sizeof sl->next);
1531 memcpy(sl->str, prefix, prefix_len);
1532 memcpy(sl->str+prefix_len, file, len+1);
1533 sl->next = NULL;
1535 if (omode == INC_PROBE) {
1536 fp = NULL;
1537 found = nasm_file_exists(sl->str);
1538 } else {
1539 fp = nasm_open_read(sl->str, fmode);
1540 found = (fp != NULL);
1542 if (found) {
1543 *slpath = sl;
1544 return fp;
1547 nasm_free(sl);
1549 if (!ip)
1550 return NULL;
1552 prefix = ip->path;
1553 prefix_len = strlen(prefix);
1554 ip = ip->next;
1559 * Open a file, or test for the presence of one (depending on omode),
1560 * considering the include path.
1562 static FILE *inc_fopen(const char *file,
1563 StrList **dhead,
1564 const char **found_path,
1565 enum incopen_mode omode,
1566 enum file_flags fmode)
1568 StrList *sl;
1569 struct hash_insert hi;
1570 void **hp;
1571 char *path;
1572 FILE *fp = NULL;
1574 hp = hash_find(&FileHash, file, &hi);
1575 if (hp) {
1576 path = *hp;
1577 } else {
1578 /* Need to do the actual path search */
1579 size_t file_len;
1581 sl = NULL;
1582 fp = inc_fopen_search(file, &sl, omode, fmode);
1584 file_len = strlen(file);
1586 if (!sl) {
1587 /* Store negative result for this file */
1588 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1589 memcpy(sl->str, file, file_len+1);
1590 sl->next = NULL;
1591 file = sl->str;
1592 path = NULL;
1593 } else {
1594 path = sl->str;
1595 file = strchr(path, '\0') - file_len;
1598 hash_add(&hi, file, path); /* Positive or negative result */
1601 * Add file to dependency path. The in_list() is needed
1602 * in case the file was already added with %depend.
1604 if (path || omode != INC_NEEDED)
1605 nasm_add_to_strlist(dhead, sl);
1608 if (!path) {
1609 if (omode == INC_NEEDED)
1610 nasm_fatal(0, "unable to open include file `%s'", file);
1612 if (found_path)
1613 *found_path = NULL;
1615 return NULL;
1618 if (!fp && omode != INC_PROBE)
1619 fp = nasm_open_read(path, fmode);
1621 if (found_path)
1622 *found_path = path;
1624 return fp;
1628 * Opens an include or input file. Public version, for use by modules
1629 * that get a file:lineno pair and need to look at the file again
1630 * (e.g. the CodeView debug backend). Returns NULL on failure.
1632 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1634 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1638 * Determine if we should warn on defining a single-line macro of
1639 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1640 * return true if _any_ single-line macro of that name is defined.
1641 * Otherwise, will return true if a single-line macro with either
1642 * `nparam' or no parameters is defined.
1644 * If a macro with precisely the right number of parameters is
1645 * defined, or nparam is -1, the address of the definition structure
1646 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1647 * is NULL, no action will be taken regarding its contents, and no
1648 * error will occur.
1650 * Note that this is also called with nparam zero to resolve
1651 * `ifdef'.
1653 * If you already know which context macro belongs to, you can pass
1654 * the context pointer as first parameter; if you won't but name begins
1655 * with %$ the context will be automatically computed. If all_contexts
1656 * is true, macro will be searched in outer contexts as well.
1658 static bool
1659 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1660 bool nocase)
1662 struct hash_table *smtbl;
1663 SMacro *m;
1665 if (ctx) {
1666 smtbl = &ctx->localmac;
1667 } else if (name[0] == '%' && name[1] == '$') {
1668 if (cstk)
1669 ctx = get_ctx(name, &name);
1670 if (!ctx)
1671 return false; /* got to return _something_ */
1672 smtbl = &ctx->localmac;
1673 } else {
1674 smtbl = &smacros;
1676 m = (SMacro *) hash_findix(smtbl, name);
1678 while (m) {
1679 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1680 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1681 if (defn) {
1682 if (nparam == (int) m->nparam || nparam == -1)
1683 *defn = m;
1684 else
1685 *defn = NULL;
1687 return true;
1689 m = m->next;
1692 return false;
1696 * Count and mark off the parameters in a multi-line macro call.
1697 * This is called both from within the multi-line macro expansion
1698 * code, and also to mark off the default parameters when provided
1699 * in a %macro definition line.
1701 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1703 int paramsize, brace;
1705 *nparam = paramsize = 0;
1706 *params = NULL;
1707 while (t) {
1708 /* +1: we need space for the final NULL */
1709 if (*nparam+1 >= paramsize) {
1710 paramsize += PARAM_DELTA;
1711 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1713 skip_white_(t);
1714 brace = 0;
1715 if (tok_is_(t, "{"))
1716 brace++;
1717 (*params)[(*nparam)++] = t;
1718 if (brace) {
1719 while (brace && (t = t->next) != NULL) {
1720 if (tok_is_(t, "{"))
1721 brace++;
1722 else if (tok_is_(t, "}"))
1723 brace--;
1726 if (t) {
1728 * Now we've found the closing brace, look further
1729 * for the comma.
1731 t = t->next;
1732 skip_white_(t);
1733 if (tok_isnt_(t, ",")) {
1734 nasm_error(ERR_NONFATAL,
1735 "braces do not enclose all of macro parameter");
1736 while (tok_isnt_(t, ","))
1737 t = t->next;
1740 } else {
1741 while (tok_isnt_(t, ","))
1742 t = t->next;
1744 if (t) { /* got a comma/brace */
1745 t = t->next; /* eat the comma */
1751 * Determine whether one of the various `if' conditions is true or
1752 * not.
1754 * We must free the tline we get passed.
1756 static bool if_condition(Token * tline, enum preproc_token ct)
1758 enum pp_conditional i = PP_COND(ct);
1759 bool j;
1760 Token *t, *tt, **tptr, *origline;
1761 struct tokenval tokval;
1762 expr *evalresult;
1763 enum pp_token_type needtype;
1764 char *p;
1766 origline = tline;
1768 switch (i) {
1769 case PPC_IFCTX:
1770 j = false; /* have we matched yet? */
1771 while (true) {
1772 skip_white_(tline);
1773 if (!tline)
1774 break;
1775 if (tline->type != TOK_ID) {
1776 nasm_error(ERR_NONFATAL,
1777 "`%s' expects context identifiers", pp_directives[ct]);
1778 free_tlist(origline);
1779 return -1;
1781 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1782 j = true;
1783 tline = tline->next;
1785 break;
1787 case PPC_IFDEF:
1788 j = false; /* have we matched yet? */
1789 while (tline) {
1790 skip_white_(tline);
1791 if (!tline || (tline->type != TOK_ID &&
1792 (tline->type != TOK_PREPROC_ID ||
1793 tline->text[1] != '$'))) {
1794 nasm_error(ERR_NONFATAL,
1795 "`%s' expects macro identifiers", pp_directives[ct]);
1796 goto fail;
1798 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1799 j = true;
1800 tline = tline->next;
1802 break;
1804 case PPC_IFENV:
1805 tline = expand_smacro(tline);
1806 j = false; /* have we matched yet? */
1807 while (tline) {
1808 skip_white_(tline);
1809 if (!tline || (tline->type != TOK_ID &&
1810 tline->type != TOK_STRING &&
1811 (tline->type != TOK_PREPROC_ID ||
1812 tline->text[1] != '!'))) {
1813 nasm_error(ERR_NONFATAL,
1814 "`%s' expects environment variable names",
1815 pp_directives[ct]);
1816 goto fail;
1818 p = tline->text;
1819 if (tline->type == TOK_PREPROC_ID)
1820 p += 2; /* Skip leading %! */
1821 if (*p == '\'' || *p == '\"' || *p == '`')
1822 nasm_unquote_cstr(p, ct);
1823 if (getenv(p))
1824 j = true;
1825 tline = tline->next;
1827 break;
1829 case PPC_IFIDN:
1830 case PPC_IFIDNI:
1831 tline = expand_smacro(tline);
1832 t = tt = tline;
1833 while (tok_isnt_(tt, ","))
1834 tt = tt->next;
1835 if (!tt) {
1836 nasm_error(ERR_NONFATAL,
1837 "`%s' expects two comma-separated arguments",
1838 pp_directives[ct]);
1839 goto fail;
1841 tt = tt->next;
1842 j = true; /* assume equality unless proved not */
1843 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1844 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1845 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1846 pp_directives[ct]);
1847 goto fail;
1849 if (t->type == TOK_WHITESPACE) {
1850 t = t->next;
1851 continue;
1853 if (tt->type == TOK_WHITESPACE) {
1854 tt = tt->next;
1855 continue;
1857 if (tt->type != t->type) {
1858 j = false; /* found mismatching tokens */
1859 break;
1861 /* When comparing strings, need to unquote them first */
1862 if (t->type == TOK_STRING) {
1863 size_t l1 = nasm_unquote(t->text, NULL);
1864 size_t l2 = nasm_unquote(tt->text, NULL);
1866 if (l1 != l2) {
1867 j = false;
1868 break;
1870 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1871 j = false;
1872 break;
1874 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1875 j = false; /* found mismatching tokens */
1876 break;
1879 t = t->next;
1880 tt = tt->next;
1882 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1883 j = false; /* trailing gunk on one end or other */
1884 break;
1886 case PPC_IFMACRO:
1888 bool found = false;
1889 MMacro searching, *mmac;
1891 skip_white_(tline);
1892 tline = expand_id(tline);
1893 if (!tok_type_(tline, TOK_ID)) {
1894 nasm_error(ERR_NONFATAL,
1895 "`%s' expects a macro name", pp_directives[ct]);
1896 goto fail;
1898 searching.name = nasm_strdup(tline->text);
1899 searching.casesense = true;
1900 searching.plus = false;
1901 searching.nolist = false;
1902 searching.in_progress = 0;
1903 searching.max_depth = 0;
1904 searching.rep_nest = NULL;
1905 searching.nparam_min = 0;
1906 searching.nparam_max = INT_MAX;
1907 tline = expand_smacro(tline->next);
1908 skip_white_(tline);
1909 if (!tline) {
1910 } else if (!tok_type_(tline, TOK_NUMBER)) {
1911 nasm_error(ERR_NONFATAL,
1912 "`%s' expects a parameter count or nothing",
1913 pp_directives[ct]);
1914 } else {
1915 searching.nparam_min = searching.nparam_max =
1916 readnum(tline->text, &j);
1917 if (j)
1918 nasm_error(ERR_NONFATAL,
1919 "unable to parse parameter count `%s'",
1920 tline->text);
1922 if (tline && tok_is_(tline->next, "-")) {
1923 tline = tline->next->next;
1924 if (tok_is_(tline, "*"))
1925 searching.nparam_max = INT_MAX;
1926 else if (!tok_type_(tline, TOK_NUMBER))
1927 nasm_error(ERR_NONFATAL,
1928 "`%s' expects a parameter count after `-'",
1929 pp_directives[ct]);
1930 else {
1931 searching.nparam_max = readnum(tline->text, &j);
1932 if (j)
1933 nasm_error(ERR_NONFATAL,
1934 "unable to parse parameter count `%s'",
1935 tline->text);
1936 if (searching.nparam_min > searching.nparam_max)
1937 nasm_error(ERR_NONFATAL,
1938 "minimum parameter count exceeds maximum");
1941 if (tline && tok_is_(tline->next, "+")) {
1942 tline = tline->next;
1943 searching.plus = true;
1945 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1946 while (mmac) {
1947 if (!strcmp(mmac->name, searching.name) &&
1948 (mmac->nparam_min <= searching.nparam_max
1949 || searching.plus)
1950 && (searching.nparam_min <= mmac->nparam_max
1951 || mmac->plus)) {
1952 found = true;
1953 break;
1955 mmac = mmac->next;
1957 if (tline && tline->next)
1958 nasm_error(ERR_WARNING|ERR_PASS1,
1959 "trailing garbage after %%ifmacro ignored");
1960 nasm_free(searching.name);
1961 j = found;
1962 break;
1965 case PPC_IFID:
1966 needtype = TOK_ID;
1967 goto iftype;
1968 case PPC_IFNUM:
1969 needtype = TOK_NUMBER;
1970 goto iftype;
1971 case PPC_IFSTR:
1972 needtype = TOK_STRING;
1973 goto iftype;
1975 iftype:
1976 t = tline = expand_smacro(tline);
1978 while (tok_type_(t, TOK_WHITESPACE) ||
1979 (needtype == TOK_NUMBER &&
1980 tok_type_(t, TOK_OTHER) &&
1981 (t->text[0] == '-' || t->text[0] == '+') &&
1982 !t->text[1]))
1983 t = t->next;
1985 j = tok_type_(t, needtype);
1986 break;
1988 case PPC_IFTOKEN:
1989 t = tline = expand_smacro(tline);
1990 while (tok_type_(t, TOK_WHITESPACE))
1991 t = t->next;
1993 j = false;
1994 if (t) {
1995 t = t->next; /* Skip the actual token */
1996 while (tok_type_(t, TOK_WHITESPACE))
1997 t = t->next;
1998 j = !t; /* Should be nothing left */
2000 break;
2002 case PPC_IFEMPTY:
2003 t = tline = expand_smacro(tline);
2004 while (tok_type_(t, TOK_WHITESPACE))
2005 t = t->next;
2007 j = !t; /* Should be empty */
2008 break;
2010 case PPC_IF:
2011 t = tline = expand_smacro(tline);
2012 tptr = &t;
2013 tokval.t_type = TOKEN_INVALID;
2014 evalresult = evaluate(ppscan, tptr, &tokval,
2015 NULL, pass | CRITICAL, NULL);
2016 if (!evalresult)
2017 return -1;
2018 if (tokval.t_type)
2019 nasm_error(ERR_WARNING|ERR_PASS1,
2020 "trailing garbage after expression ignored");
2021 if (!is_simple(evalresult)) {
2022 nasm_error(ERR_NONFATAL,
2023 "non-constant value given to `%s'", pp_directives[ct]);
2024 goto fail;
2026 j = reloc_value(evalresult) != 0;
2027 break;
2029 default:
2030 nasm_error(ERR_FATAL,
2031 "preprocessor directive `%s' not yet implemented",
2032 pp_directives[ct]);
2033 goto fail;
2036 free_tlist(origline);
2037 return j ^ PP_NEGATIVE(ct);
2039 fail:
2040 free_tlist(origline);
2041 return -1;
2045 * Common code for defining an smacro
2047 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2048 int nparam, Token *expansion)
2050 SMacro *smac, **smhead;
2051 struct hash_table *smtbl;
2053 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2054 if (!smac) {
2055 nasm_error(ERR_WARNING|ERR_PASS1,
2056 "single-line macro `%s' defined both with and"
2057 " without parameters", mname);
2059 * Some instances of the old code considered this a failure,
2060 * some others didn't. What is the right thing to do here?
2062 free_tlist(expansion);
2063 return false; /* Failure */
2064 } else {
2066 * We're redefining, so we have to take over an
2067 * existing SMacro structure. This means freeing
2068 * what was already in it.
2070 nasm_free(smac->name);
2071 free_tlist(smac->expansion);
2073 } else {
2074 smtbl = ctx ? &ctx->localmac : &smacros;
2075 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2076 smac = nasm_malloc(sizeof(SMacro));
2077 smac->next = *smhead;
2078 *smhead = smac;
2080 smac->name = nasm_strdup(mname);
2081 smac->casesense = casesense;
2082 smac->nparam = nparam;
2083 smac->expansion = expansion;
2084 smac->in_progress = false;
2085 return true; /* Success */
2089 * Undefine an smacro
2091 static void undef_smacro(Context *ctx, const char *mname)
2093 SMacro **smhead, *s, **sp;
2094 struct hash_table *smtbl;
2096 smtbl = ctx ? &ctx->localmac : &smacros;
2097 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2099 if (smhead) {
2101 * We now have a macro name... go hunt for it.
2103 sp = smhead;
2104 while ((s = *sp) != NULL) {
2105 if (!mstrcmp(s->name, mname, s->casesense)) {
2106 *sp = s->next;
2107 nasm_free(s->name);
2108 free_tlist(s->expansion);
2109 nasm_free(s);
2110 } else {
2111 sp = &s->next;
2118 * Parse a mmacro specification.
2120 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2122 bool err;
2124 tline = tline->next;
2125 skip_white_(tline);
2126 tline = expand_id(tline);
2127 if (!tok_type_(tline, TOK_ID)) {
2128 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2129 return false;
2132 def->prev = NULL;
2133 def->name = nasm_strdup(tline->text);
2134 def->plus = false;
2135 def->nolist = false;
2136 def->in_progress = 0;
2137 def->rep_nest = NULL;
2138 def->nparam_min = 0;
2139 def->nparam_max = 0;
2141 tline = expand_smacro(tline->next);
2142 skip_white_(tline);
2143 if (!tok_type_(tline, TOK_NUMBER)) {
2144 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2145 } else {
2146 def->nparam_min = def->nparam_max =
2147 readnum(tline->text, &err);
2148 if (err)
2149 nasm_error(ERR_NONFATAL,
2150 "unable to parse parameter count `%s'", tline->text);
2152 if (tline && tok_is_(tline->next, "-")) {
2153 tline = tline->next->next;
2154 if (tok_is_(tline, "*")) {
2155 def->nparam_max = INT_MAX;
2156 } else if (!tok_type_(tline, TOK_NUMBER)) {
2157 nasm_error(ERR_NONFATAL,
2158 "`%s' expects a parameter count after `-'", directive);
2159 } else {
2160 def->nparam_max = readnum(tline->text, &err);
2161 if (err) {
2162 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2163 tline->text);
2165 if (def->nparam_min > def->nparam_max) {
2166 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2170 if (tline && tok_is_(tline->next, "+")) {
2171 tline = tline->next;
2172 def->plus = true;
2174 if (tline && tok_type_(tline->next, TOK_ID) &&
2175 !nasm_stricmp(tline->next->text, ".nolist")) {
2176 tline = tline->next;
2177 def->nolist = true;
2181 * Handle default parameters.
2183 if (tline && tline->next) {
2184 def->dlist = tline->next;
2185 tline->next = NULL;
2186 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2187 } else {
2188 def->dlist = NULL;
2189 def->defaults = NULL;
2191 def->expansion = NULL;
2193 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2194 !def->plus)
2195 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2196 "too many default macro parameters");
2198 return true;
2203 * Decode a size directive
2205 static int parse_size(const char *str) {
2206 static const char *size_names[] =
2207 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2208 static const int sizes[] =
2209 { 0, 1, 4, 16, 8, 10, 2, 32 };
2211 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2215 * Process a preprocessor %pragma directive. Currently there are none.
2216 * Gets passed the token list starting with the "preproc" token from
2217 * "%pragma preproc".
2219 static void do_pragma_preproc(Token *tline)
2221 /* Skip to the real stuff */
2222 tline = tline->next;
2223 skip_white_(tline);
2224 if (!tline)
2225 return;
2227 (void)tline; /* Nothing else to do at present */
2231 * find and process preprocessor directive in passed line
2232 * Find out if a line contains a preprocessor directive, and deal
2233 * with it if so.
2235 * If a directive _is_ found, it is the responsibility of this routine
2236 * (and not the caller) to free_tlist() the line.
2238 * @param tline a pointer to the current tokeninzed line linked list
2239 * @param output if this directive generated output
2240 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2243 static int do_directive(Token *tline, char **output)
2245 enum preproc_token i;
2246 int j;
2247 bool err;
2248 int nparam;
2249 bool nolist;
2250 bool casesense;
2251 int k, m;
2252 int offset;
2253 char *p, *pp;
2254 const char *found_path;
2255 const char *mname;
2256 Include *inc;
2257 Context *ctx;
2258 Cond *cond;
2259 MMacro *mmac, **mmhead;
2260 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2261 Line *l;
2262 struct tokenval tokval;
2263 expr *evalresult;
2264 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2265 int64_t count;
2266 size_t len;
2267 int severity;
2269 *output = NULL; /* No output generated */
2270 origline = tline;
2272 skip_white_(tline);
2273 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2274 (tline->text[1] == '%' || tline->text[1] == '$'
2275 || tline->text[1] == '!'))
2276 return NO_DIRECTIVE_FOUND;
2278 i = pp_token_hash(tline->text);
2281 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2282 * since they are known to be buggy at moment, we need to fix them
2283 * in future release (2.09-2.10)
2285 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2286 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2287 tline->text);
2288 return NO_DIRECTIVE_FOUND;
2292 * If we're in a non-emitting branch of a condition construct,
2293 * or walking to the end of an already terminated %rep block,
2294 * we should ignore all directives except for condition
2295 * directives.
2297 if (((istk->conds && !emitting(istk->conds->state)) ||
2298 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2299 return NO_DIRECTIVE_FOUND;
2303 * If we're defining a macro or reading a %rep block, we should
2304 * ignore all directives except for %macro/%imacro (which nest),
2305 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2306 * If we're in a %rep block, another %rep nests, so should be let through.
2308 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2309 i != PP_RMACRO && i != PP_IRMACRO &&
2310 i != PP_ENDMACRO && i != PP_ENDM &&
2311 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2312 return NO_DIRECTIVE_FOUND;
2315 if (defining) {
2316 if (i == PP_MACRO || i == PP_IMACRO ||
2317 i == PP_RMACRO || i == PP_IRMACRO) {
2318 nested_mac_count++;
2319 return NO_DIRECTIVE_FOUND;
2320 } else if (nested_mac_count > 0) {
2321 if (i == PP_ENDMACRO) {
2322 nested_mac_count--;
2323 return NO_DIRECTIVE_FOUND;
2326 if (!defining->name) {
2327 if (i == PP_REP) {
2328 nested_rep_count++;
2329 return NO_DIRECTIVE_FOUND;
2330 } else if (nested_rep_count > 0) {
2331 if (i == PP_ENDREP) {
2332 nested_rep_count--;
2333 return NO_DIRECTIVE_FOUND;
2339 switch (i) {
2340 case PP_INVALID:
2341 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2342 tline->text);
2343 return NO_DIRECTIVE_FOUND; /* didn't get it */
2345 case PP_PRAGMA:
2347 * %pragma namespace options...
2349 * The namespace "preproc" is reserved for the preprocessor;
2350 * all other namespaces generate a [pragma] assembly directive.
2352 * Invalid %pragmas are ignored and may have different
2353 * meaning in future versions of NASM.
2355 tline = tline->next;
2356 skip_white_(tline);
2357 tline = expand_smacro(tline);
2358 if (tok_type_(tline, TOK_ID)) {
2359 if (!nasm_stricmp(tline->text, "preproc")) {
2360 /* Preprocessor pragma */
2361 do_pragma_preproc(tline);
2362 } else {
2363 /* Build the assembler directive */
2364 t = new_Token(NULL, TOK_OTHER, "[", 1);
2365 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2366 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2367 tline = t;
2368 for (t = tline; t->next; t = t->next)
2370 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2371 /* true here can be revisited in the future */
2372 *output = detoken(tline, true);
2375 free_tlist(origline);
2376 return DIRECTIVE_FOUND;
2378 case PP_STACKSIZE:
2379 /* Directive to tell NASM what the default stack size is. The
2380 * default is for a 16-bit stack, and this can be overriden with
2381 * %stacksize large.
2383 tline = tline->next;
2384 if (tline && tline->type == TOK_WHITESPACE)
2385 tline = tline->next;
2386 if (!tline || tline->type != TOK_ID) {
2387 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2388 free_tlist(origline);
2389 return DIRECTIVE_FOUND;
2391 if (nasm_stricmp(tline->text, "flat") == 0) {
2392 /* All subsequent ARG directives are for a 32-bit stack */
2393 StackSize = 4;
2394 StackPointer = "ebp";
2395 ArgOffset = 8;
2396 LocalOffset = 0;
2397 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2398 /* All subsequent ARG directives are for a 64-bit stack */
2399 StackSize = 8;
2400 StackPointer = "rbp";
2401 ArgOffset = 16;
2402 LocalOffset = 0;
2403 } else if (nasm_stricmp(tline->text, "large") == 0) {
2404 /* All subsequent ARG directives are for a 16-bit stack,
2405 * far function call.
2407 StackSize = 2;
2408 StackPointer = "bp";
2409 ArgOffset = 4;
2410 LocalOffset = 0;
2411 } else if (nasm_stricmp(tline->text, "small") == 0) {
2412 /* All subsequent ARG directives are for a 16-bit stack,
2413 * far function call. We don't support near functions.
2415 StackSize = 2;
2416 StackPointer = "bp";
2417 ArgOffset = 6;
2418 LocalOffset = 0;
2419 } else {
2420 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2421 free_tlist(origline);
2422 return DIRECTIVE_FOUND;
2424 free_tlist(origline);
2425 return DIRECTIVE_FOUND;
2427 case PP_ARG:
2428 /* TASM like ARG directive to define arguments to functions, in
2429 * the following form:
2431 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2433 offset = ArgOffset;
2434 do {
2435 char *arg, directive[256];
2436 int size = StackSize;
2438 /* Find the argument name */
2439 tline = tline->next;
2440 if (tline && tline->type == TOK_WHITESPACE)
2441 tline = tline->next;
2442 if (!tline || tline->type != TOK_ID) {
2443 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2444 free_tlist(origline);
2445 return DIRECTIVE_FOUND;
2447 arg = tline->text;
2449 /* Find the argument size type */
2450 tline = tline->next;
2451 if (!tline || tline->type != TOK_OTHER
2452 || tline->text[0] != ':') {
2453 nasm_error(ERR_NONFATAL,
2454 "Syntax error processing `%%arg' directive");
2455 free_tlist(origline);
2456 return DIRECTIVE_FOUND;
2458 tline = tline->next;
2459 if (!tline || tline->type != TOK_ID) {
2460 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2461 free_tlist(origline);
2462 return DIRECTIVE_FOUND;
2465 /* Allow macro expansion of type parameter */
2466 tt = tokenize(tline->text);
2467 tt = expand_smacro(tt);
2468 size = parse_size(tt->text);
2469 if (!size) {
2470 nasm_error(ERR_NONFATAL,
2471 "Invalid size type for `%%arg' missing directive");
2472 free_tlist(tt);
2473 free_tlist(origline);
2474 return DIRECTIVE_FOUND;
2476 free_tlist(tt);
2478 /* Round up to even stack slots */
2479 size = ALIGN(size, StackSize);
2481 /* Now define the macro for the argument */
2482 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2483 arg, StackPointer, offset);
2484 do_directive(tokenize(directive), output);
2485 offset += size;
2487 /* Move to the next argument in the list */
2488 tline = tline->next;
2489 if (tline && tline->type == TOK_WHITESPACE)
2490 tline = tline->next;
2491 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2492 ArgOffset = offset;
2493 free_tlist(origline);
2494 return DIRECTIVE_FOUND;
2496 case PP_LOCAL:
2497 /* TASM like LOCAL directive to define local variables for a
2498 * function, in the following form:
2500 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2502 * The '= LocalSize' at the end is ignored by NASM, but is
2503 * required by TASM to define the local parameter size (and used
2504 * by the TASM macro package).
2506 offset = LocalOffset;
2507 do {
2508 char *local, directive[256];
2509 int size = StackSize;
2511 /* Find the argument name */
2512 tline = tline->next;
2513 if (tline && tline->type == TOK_WHITESPACE)
2514 tline = tline->next;
2515 if (!tline || tline->type != TOK_ID) {
2516 nasm_error(ERR_NONFATAL,
2517 "`%%local' missing argument parameter");
2518 free_tlist(origline);
2519 return DIRECTIVE_FOUND;
2521 local = tline->text;
2523 /* Find the argument size type */
2524 tline = tline->next;
2525 if (!tline || tline->type != TOK_OTHER
2526 || tline->text[0] != ':') {
2527 nasm_error(ERR_NONFATAL,
2528 "Syntax error processing `%%local' directive");
2529 free_tlist(origline);
2530 return DIRECTIVE_FOUND;
2532 tline = tline->next;
2533 if (!tline || tline->type != TOK_ID) {
2534 nasm_error(ERR_NONFATAL,
2535 "`%%local' missing size type parameter");
2536 free_tlist(origline);
2537 return DIRECTIVE_FOUND;
2540 /* Allow macro expansion of type parameter */
2541 tt = tokenize(tline->text);
2542 tt = expand_smacro(tt);
2543 size = parse_size(tt->text);
2544 if (!size) {
2545 nasm_error(ERR_NONFATAL,
2546 "Invalid size type for `%%local' missing directive");
2547 free_tlist(tt);
2548 free_tlist(origline);
2549 return DIRECTIVE_FOUND;
2551 free_tlist(tt);
2553 /* Round up to even stack slots */
2554 size = ALIGN(size, StackSize);
2556 offset += size; /* Negative offset, increment before */
2558 /* Now define the macro for the argument */
2559 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2560 local, StackPointer, offset);
2561 do_directive(tokenize(directive), output);
2563 /* Now define the assign to setup the enter_c macro correctly */
2564 snprintf(directive, sizeof(directive),
2565 "%%assign %%$localsize %%$localsize+%d", size);
2566 do_directive(tokenize(directive), output);
2568 /* Move to the next argument in the list */
2569 tline = tline->next;
2570 if (tline && tline->type == TOK_WHITESPACE)
2571 tline = tline->next;
2572 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2573 LocalOffset = offset;
2574 free_tlist(origline);
2575 return DIRECTIVE_FOUND;
2577 case PP_CLEAR:
2578 if (tline->next)
2579 nasm_error(ERR_WARNING|ERR_PASS1,
2580 "trailing garbage after `%%clear' ignored");
2581 free_macros();
2582 init_macros();
2583 free_tlist(origline);
2584 return DIRECTIVE_FOUND;
2586 case PP_DEPEND:
2587 t = tline->next = expand_smacro(tline->next);
2588 skip_white_(t);
2589 if (!t || (t->type != TOK_STRING &&
2590 t->type != TOK_INTERNAL_STRING)) {
2591 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2592 free_tlist(origline);
2593 return DIRECTIVE_FOUND; /* but we did _something_ */
2595 if (t->next)
2596 nasm_error(ERR_WARNING|ERR_PASS1,
2597 "trailing garbage after `%%depend' ignored");
2598 p = t->text;
2599 if (t->type != TOK_INTERNAL_STRING)
2600 nasm_unquote_cstr(p, i);
2601 nasm_add_string_to_strlist(dephead, p);
2602 free_tlist(origline);
2603 return DIRECTIVE_FOUND;
2605 case PP_INCLUDE:
2606 t = tline->next = expand_smacro(tline->next);
2607 skip_white_(t);
2609 if (!t || (t->type != TOK_STRING &&
2610 t->type != TOK_INTERNAL_STRING)) {
2611 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2612 free_tlist(origline);
2613 return DIRECTIVE_FOUND; /* but we did _something_ */
2615 if (t->next)
2616 nasm_error(ERR_WARNING|ERR_PASS1,
2617 "trailing garbage after `%%include' ignored");
2618 p = t->text;
2619 if (t->type != TOK_INTERNAL_STRING)
2620 nasm_unquote_cstr(p, i);
2621 inc = nasm_malloc(sizeof(Include));
2622 inc->next = istk;
2623 inc->conds = NULL;
2624 found_path = NULL;
2625 inc->fp = inc_fopen(p, dephead, &found_path,
2626 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2627 if (!inc->fp) {
2628 /* -MG given but file not found */
2629 nasm_free(inc);
2630 } else {
2631 inc->fname = src_set_fname(found_path ? found_path : p);
2632 inc->lineno = src_set_linnum(0);
2633 inc->lineinc = 1;
2634 inc->expansion = NULL;
2635 inc->mstk = NULL;
2636 istk = inc;
2637 lfmt->uplevel(LIST_INCLUDE);
2639 free_tlist(origline);
2640 return DIRECTIVE_FOUND;
2642 case PP_USE:
2644 static macros_t *use_pkg;
2645 const char *pkg_macro = NULL;
2647 tline = tline->next;
2648 skip_white_(tline);
2649 tline = expand_id(tline);
2651 if (!tline || (tline->type != TOK_STRING &&
2652 tline->type != TOK_INTERNAL_STRING &&
2653 tline->type != TOK_ID)) {
2654 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2655 free_tlist(origline);
2656 return DIRECTIVE_FOUND; /* but we did _something_ */
2658 if (tline->next)
2659 nasm_error(ERR_WARNING|ERR_PASS1,
2660 "trailing garbage after `%%use' ignored");
2661 if (tline->type == TOK_STRING)
2662 nasm_unquote_cstr(tline->text, i);
2663 use_pkg = nasm_stdmac_find_package(tline->text);
2664 if (!use_pkg)
2665 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2666 else
2667 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2668 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2669 /* Not already included, go ahead and include it */
2670 stdmacpos = use_pkg;
2672 free_tlist(origline);
2673 return DIRECTIVE_FOUND;
2675 case PP_PUSH:
2676 case PP_REPL:
2677 case PP_POP:
2678 tline = tline->next;
2679 skip_white_(tline);
2680 tline = expand_id(tline);
2681 if (tline) {
2682 if (!tok_type_(tline, TOK_ID)) {
2683 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2684 pp_directives[i]);
2685 free_tlist(origline);
2686 return DIRECTIVE_FOUND; /* but we did _something_ */
2688 if (tline->next)
2689 nasm_error(ERR_WARNING|ERR_PASS1,
2690 "trailing garbage after `%s' ignored",
2691 pp_directives[i]);
2692 p = nasm_strdup(tline->text);
2693 } else {
2694 p = NULL; /* Anonymous */
2697 if (i == PP_PUSH) {
2698 ctx = nasm_malloc(sizeof(Context));
2699 ctx->next = cstk;
2700 hash_init(&ctx->localmac, HASH_SMALL);
2701 ctx->name = p;
2702 ctx->number = unique++;
2703 cstk = ctx;
2704 } else {
2705 /* %pop or %repl */
2706 if (!cstk) {
2707 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2708 pp_directives[i]);
2709 } else if (i == PP_POP) {
2710 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2711 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2712 "expected %s",
2713 cstk->name ? cstk->name : "anonymous", p);
2714 else
2715 ctx_pop();
2716 } else {
2717 /* i == PP_REPL */
2718 nasm_free(cstk->name);
2719 cstk->name = p;
2720 p = NULL;
2722 nasm_free(p);
2724 free_tlist(origline);
2725 return DIRECTIVE_FOUND;
2726 case PP_FATAL:
2727 severity = ERR_FATAL;
2728 goto issue_error;
2729 case PP_ERROR:
2730 severity = ERR_NONFATAL;
2731 goto issue_error;
2732 case PP_WARNING:
2733 severity = ERR_WARNING|ERR_WARN_USER;
2734 goto issue_error;
2736 issue_error:
2738 /* Only error out if this is the final pass */
2739 if (pass != 2 && i != PP_FATAL)
2740 return DIRECTIVE_FOUND;
2742 tline->next = expand_smacro(tline->next);
2743 tline = tline->next;
2744 skip_white_(tline);
2745 t = tline ? tline->next : NULL;
2746 skip_white_(t);
2747 if (tok_type_(tline, TOK_STRING) && !t) {
2748 /* The line contains only a quoted string */
2749 p = tline->text;
2750 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2751 nasm_error(severity, "%s", p);
2752 } else {
2753 /* Not a quoted string, or more than a quoted string */
2754 p = detoken(tline, false);
2755 nasm_error(severity, "%s", p);
2756 nasm_free(p);
2758 free_tlist(origline);
2759 return DIRECTIVE_FOUND;
2762 CASE_PP_IF:
2763 if (istk->conds && !emitting(istk->conds->state))
2764 j = COND_NEVER;
2765 else {
2766 j = if_condition(tline->next, i);
2767 tline->next = NULL; /* it got freed */
2768 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2770 cond = nasm_malloc(sizeof(Cond));
2771 cond->next = istk->conds;
2772 cond->state = j;
2773 istk->conds = cond;
2774 if(istk->mstk)
2775 istk->mstk->condcnt ++;
2776 free_tlist(origline);
2777 return DIRECTIVE_FOUND;
2779 CASE_PP_ELIF:
2780 if (!istk->conds)
2781 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2782 switch(istk->conds->state) {
2783 case COND_IF_TRUE:
2784 istk->conds->state = COND_DONE;
2785 break;
2787 case COND_DONE:
2788 case COND_NEVER:
2789 break;
2791 case COND_ELSE_TRUE:
2792 case COND_ELSE_FALSE:
2793 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2794 "`%%elif' after `%%else' ignored");
2795 istk->conds->state = COND_NEVER;
2796 break;
2798 case COND_IF_FALSE:
2800 * IMPORTANT: In the case of %if, we will already have
2801 * called expand_mmac_params(); however, if we're
2802 * processing an %elif we must have been in a
2803 * non-emitting mode, which would have inhibited
2804 * the normal invocation of expand_mmac_params().
2805 * Therefore, we have to do it explicitly here.
2807 j = if_condition(expand_mmac_params(tline->next), i);
2808 tline->next = NULL; /* it got freed */
2809 istk->conds->state =
2810 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2811 break;
2813 free_tlist(origline);
2814 return DIRECTIVE_FOUND;
2816 case PP_ELSE:
2817 if (tline->next)
2818 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2819 "trailing garbage after `%%else' ignored");
2820 if (!istk->conds)
2821 nasm_fatal(0, "`%%else: no matching `%%if'");
2822 switch(istk->conds->state) {
2823 case COND_IF_TRUE:
2824 case COND_DONE:
2825 istk->conds->state = COND_ELSE_FALSE;
2826 break;
2828 case COND_NEVER:
2829 break;
2831 case COND_IF_FALSE:
2832 istk->conds->state = COND_ELSE_TRUE;
2833 break;
2835 case COND_ELSE_TRUE:
2836 case COND_ELSE_FALSE:
2837 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2838 "`%%else' after `%%else' ignored.");
2839 istk->conds->state = COND_NEVER;
2840 break;
2842 free_tlist(origline);
2843 return DIRECTIVE_FOUND;
2845 case PP_ENDIF:
2846 if (tline->next)
2847 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2848 "trailing garbage after `%%endif' ignored");
2849 if (!istk->conds)
2850 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2851 cond = istk->conds;
2852 istk->conds = cond->next;
2853 nasm_free(cond);
2854 if(istk->mstk)
2855 istk->mstk->condcnt --;
2856 free_tlist(origline);
2857 return DIRECTIVE_FOUND;
2859 case PP_RMACRO:
2860 case PP_IRMACRO:
2861 case PP_MACRO:
2862 case PP_IMACRO:
2863 if (defining) {
2864 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2865 pp_directives[i]);
2866 return DIRECTIVE_FOUND;
2868 defining = nasm_zalloc(sizeof(MMacro));
2869 defining->max_depth =
2870 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2871 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2872 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2873 nasm_free(defining);
2874 defining = NULL;
2875 return DIRECTIVE_FOUND;
2878 src_get(&defining->xline, &defining->fname);
2880 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2881 while (mmac) {
2882 if (!strcmp(mmac->name, defining->name) &&
2883 (mmac->nparam_min <= defining->nparam_max
2884 || defining->plus)
2885 && (defining->nparam_min <= mmac->nparam_max
2886 || mmac->plus)) {
2887 nasm_error(ERR_WARNING|ERR_PASS1,
2888 "redefining multi-line macro `%s'", defining->name);
2889 return DIRECTIVE_FOUND;
2891 mmac = mmac->next;
2893 free_tlist(origline);
2894 return DIRECTIVE_FOUND;
2896 case PP_ENDM:
2897 case PP_ENDMACRO:
2898 if (! (defining && defining->name)) {
2899 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2900 return DIRECTIVE_FOUND;
2902 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2903 defining->next = *mmhead;
2904 *mmhead = defining;
2905 defining = NULL;
2906 free_tlist(origline);
2907 return DIRECTIVE_FOUND;
2909 case PP_EXITMACRO:
2911 * We must search along istk->expansion until we hit a
2912 * macro-end marker for a macro with a name. Then we
2913 * bypass all lines between exitmacro and endmacro.
2915 list_for_each(l, istk->expansion)
2916 if (l->finishes && l->finishes->name)
2917 break;
2919 if (l) {
2921 * Remove all conditional entries relative to this
2922 * macro invocation. (safe to do in this context)
2924 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2925 cond = istk->conds;
2926 istk->conds = cond->next;
2927 nasm_free(cond);
2929 istk->expansion = l;
2930 } else {
2931 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2933 free_tlist(origline);
2934 return DIRECTIVE_FOUND;
2936 case PP_UNMACRO:
2937 case PP_UNIMACRO:
2939 MMacro **mmac_p;
2940 MMacro spec;
2942 spec.casesense = (i == PP_UNMACRO);
2943 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2944 return DIRECTIVE_FOUND;
2946 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2947 while (mmac_p && *mmac_p) {
2948 mmac = *mmac_p;
2949 if (mmac->casesense == spec.casesense &&
2950 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2951 mmac->nparam_min == spec.nparam_min &&
2952 mmac->nparam_max == spec.nparam_max &&
2953 mmac->plus == spec.plus) {
2954 *mmac_p = mmac->next;
2955 free_mmacro(mmac);
2956 } else {
2957 mmac_p = &mmac->next;
2960 free_tlist(origline);
2961 free_tlist(spec.dlist);
2962 return DIRECTIVE_FOUND;
2965 case PP_ROTATE:
2966 if (tline->next && tline->next->type == TOK_WHITESPACE)
2967 tline = tline->next;
2968 if (!tline->next) {
2969 free_tlist(origline);
2970 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2971 return DIRECTIVE_FOUND;
2973 t = expand_smacro(tline->next);
2974 tline->next = NULL;
2975 free_tlist(origline);
2976 tline = t;
2977 tptr = &t;
2978 tokval.t_type = TOKEN_INVALID;
2979 evalresult =
2980 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2981 free_tlist(tline);
2982 if (!evalresult)
2983 return DIRECTIVE_FOUND;
2984 if (tokval.t_type)
2985 nasm_error(ERR_WARNING|ERR_PASS1,
2986 "trailing garbage after expression ignored");
2987 if (!is_simple(evalresult)) {
2988 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2989 return DIRECTIVE_FOUND;
2991 mmac = istk->mstk;
2992 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2993 mmac = mmac->next_active;
2994 if (!mmac) {
2995 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2996 } else if (mmac->nparam == 0) {
2997 nasm_error(ERR_NONFATAL,
2998 "`%%rotate' invoked within macro without parameters");
2999 } else {
3000 int rotate = mmac->rotate + reloc_value(evalresult);
3002 rotate %= (int)mmac->nparam;
3003 if (rotate < 0)
3004 rotate += mmac->nparam;
3006 mmac->rotate = rotate;
3008 return DIRECTIVE_FOUND;
3010 case PP_REP:
3011 nolist = false;
3012 do {
3013 tline = tline->next;
3014 } while (tok_type_(tline, TOK_WHITESPACE));
3016 if (tok_type_(tline, TOK_ID) &&
3017 nasm_stricmp(tline->text, ".nolist") == 0) {
3018 nolist = true;
3019 do {
3020 tline = tline->next;
3021 } while (tok_type_(tline, TOK_WHITESPACE));
3024 if (tline) {
3025 t = expand_smacro(tline);
3026 tptr = &t;
3027 tokval.t_type = TOKEN_INVALID;
3028 evalresult =
3029 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3030 if (!evalresult) {
3031 free_tlist(origline);
3032 return DIRECTIVE_FOUND;
3034 if (tokval.t_type)
3035 nasm_error(ERR_WARNING|ERR_PASS1,
3036 "trailing garbage after expression ignored");
3037 if (!is_simple(evalresult)) {
3038 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3039 return DIRECTIVE_FOUND;
3041 count = reloc_value(evalresult);
3042 if (count >= REP_LIMIT) {
3043 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3044 count = 0;
3045 } else
3046 count++;
3047 } else {
3048 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3049 count = 0;
3051 free_tlist(origline);
3053 tmp_defining = defining;
3054 defining = nasm_malloc(sizeof(MMacro));
3055 defining->prev = NULL;
3056 defining->name = NULL; /* flags this macro as a %rep block */
3057 defining->casesense = false;
3058 defining->plus = false;
3059 defining->nolist = nolist;
3060 defining->in_progress = count;
3061 defining->max_depth = 0;
3062 defining->nparam_min = defining->nparam_max = 0;
3063 defining->defaults = NULL;
3064 defining->dlist = NULL;
3065 defining->expansion = NULL;
3066 defining->next_active = istk->mstk;
3067 defining->rep_nest = tmp_defining;
3068 return DIRECTIVE_FOUND;
3070 case PP_ENDREP:
3071 if (!defining || defining->name) {
3072 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3073 return DIRECTIVE_FOUND;
3077 * Now we have a "macro" defined - although it has no name
3078 * and we won't be entering it in the hash tables - we must
3079 * push a macro-end marker for it on to istk->expansion.
3080 * After that, it will take care of propagating itself (a
3081 * macro-end marker line for a macro which is really a %rep
3082 * block will cause the macro to be re-expanded, complete
3083 * with another macro-end marker to ensure the process
3084 * continues) until the whole expansion is forcibly removed
3085 * from istk->expansion by a %exitrep.
3087 l = nasm_malloc(sizeof(Line));
3088 l->next = istk->expansion;
3089 l->finishes = defining;
3090 l->first = NULL;
3091 istk->expansion = l;
3093 istk->mstk = defining;
3095 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3096 tmp_defining = defining;
3097 defining = defining->rep_nest;
3098 free_tlist(origline);
3099 return DIRECTIVE_FOUND;
3101 case PP_EXITREP:
3103 * We must search along istk->expansion until we hit a
3104 * macro-end marker for a macro with no name. Then we set
3105 * its `in_progress' flag to 0.
3107 list_for_each(l, istk->expansion)
3108 if (l->finishes && !l->finishes->name)
3109 break;
3111 if (l)
3112 l->finishes->in_progress = 1;
3113 else
3114 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3115 free_tlist(origline);
3116 return DIRECTIVE_FOUND;
3118 case PP_XDEFINE:
3119 case PP_IXDEFINE:
3120 case PP_DEFINE:
3121 case PP_IDEFINE:
3122 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3124 tline = tline->next;
3125 skip_white_(tline);
3126 tline = expand_id(tline);
3127 if (!tline || (tline->type != TOK_ID &&
3128 (tline->type != TOK_PREPROC_ID ||
3129 tline->text[1] != '$'))) {
3130 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3131 pp_directives[i]);
3132 free_tlist(origline);
3133 return DIRECTIVE_FOUND;
3136 ctx = get_ctx(tline->text, &mname);
3137 last = tline;
3138 param_start = tline = tline->next;
3139 nparam = 0;
3141 /* Expand the macro definition now for %xdefine and %ixdefine */
3142 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3143 tline = expand_smacro(tline);
3145 if (tok_is_(tline, "(")) {
3147 * This macro has parameters.
3150 tline = tline->next;
3151 while (1) {
3152 skip_white_(tline);
3153 if (!tline) {
3154 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3155 free_tlist(origline);
3156 return DIRECTIVE_FOUND;
3158 if (tline->type != TOK_ID) {
3159 nasm_error(ERR_NONFATAL,
3160 "`%s': parameter identifier expected",
3161 tline->text);
3162 free_tlist(origline);
3163 return DIRECTIVE_FOUND;
3165 tline->type = TOK_SMAC_PARAM + nparam++;
3166 tline = tline->next;
3167 skip_white_(tline);
3168 if (tok_is_(tline, ",")) {
3169 tline = tline->next;
3170 } else {
3171 if (!tok_is_(tline, ")")) {
3172 nasm_error(ERR_NONFATAL,
3173 "`)' expected to terminate macro template");
3174 free_tlist(origline);
3175 return DIRECTIVE_FOUND;
3177 break;
3180 last = tline;
3181 tline = tline->next;
3183 if (tok_type_(tline, TOK_WHITESPACE))
3184 last = tline, tline = tline->next;
3185 macro_start = NULL;
3186 last->next = NULL;
3187 t = tline;
3188 while (t) {
3189 if (t->type == TOK_ID) {
3190 list_for_each(tt, param_start)
3191 if (tt->type >= TOK_SMAC_PARAM &&
3192 !strcmp(tt->text, t->text))
3193 t->type = tt->type;
3195 tt = t->next;
3196 t->next = macro_start;
3197 macro_start = t;
3198 t = tt;
3201 * Good. We now have a macro name, a parameter count, and a
3202 * token list (in reverse order) for an expansion. We ought
3203 * to be OK just to create an SMacro, store it, and let
3204 * free_tlist have the rest of the line (which we have
3205 * carefully re-terminated after chopping off the expansion
3206 * from the end).
3208 define_smacro(ctx, mname, casesense, nparam, macro_start);
3209 free_tlist(origline);
3210 return DIRECTIVE_FOUND;
3212 case PP_UNDEF:
3213 tline = tline->next;
3214 skip_white_(tline);
3215 tline = expand_id(tline);
3216 if (!tline || (tline->type != TOK_ID &&
3217 (tline->type != TOK_PREPROC_ID ||
3218 tline->text[1] != '$'))) {
3219 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3220 free_tlist(origline);
3221 return DIRECTIVE_FOUND;
3223 if (tline->next) {
3224 nasm_error(ERR_WARNING|ERR_PASS1,
3225 "trailing garbage after macro name ignored");
3228 /* Find the context that symbol belongs to */
3229 ctx = get_ctx(tline->text, &mname);
3230 undef_smacro(ctx, mname);
3231 free_tlist(origline);
3232 return DIRECTIVE_FOUND;
3234 case PP_DEFSTR:
3235 case PP_IDEFSTR:
3236 casesense = (i == PP_DEFSTR);
3238 tline = tline->next;
3239 skip_white_(tline);
3240 tline = expand_id(tline);
3241 if (!tline || (tline->type != TOK_ID &&
3242 (tline->type != TOK_PREPROC_ID ||
3243 tline->text[1] != '$'))) {
3244 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3245 pp_directives[i]);
3246 free_tlist(origline);
3247 return DIRECTIVE_FOUND;
3250 ctx = get_ctx(tline->text, &mname);
3251 last = tline;
3252 tline = expand_smacro(tline->next);
3253 last->next = NULL;
3255 while (tok_type_(tline, TOK_WHITESPACE))
3256 tline = delete_Token(tline);
3258 p = detoken(tline, false);
3259 macro_start = nasm_malloc(sizeof(*macro_start));
3260 macro_start->next = NULL;
3261 macro_start->text = nasm_quote(p, strlen(p));
3262 macro_start->type = TOK_STRING;
3263 macro_start->a.mac = NULL;
3264 nasm_free(p);
3267 * We now have a macro name, an implicit parameter count of
3268 * zero, and a string token to use as an expansion. Create
3269 * and store an SMacro.
3271 define_smacro(ctx, mname, casesense, 0, macro_start);
3272 free_tlist(origline);
3273 return DIRECTIVE_FOUND;
3275 case PP_DEFTOK:
3276 case PP_IDEFTOK:
3277 casesense = (i == PP_DEFTOK);
3279 tline = tline->next;
3280 skip_white_(tline);
3281 tline = expand_id(tline);
3282 if (!tline || (tline->type != TOK_ID &&
3283 (tline->type != TOK_PREPROC_ID ||
3284 tline->text[1] != '$'))) {
3285 nasm_error(ERR_NONFATAL,
3286 "`%s' expects a macro identifier as first parameter",
3287 pp_directives[i]);
3288 free_tlist(origline);
3289 return DIRECTIVE_FOUND;
3291 ctx = get_ctx(tline->text, &mname);
3292 last = tline;
3293 tline = expand_smacro(tline->next);
3294 last->next = NULL;
3296 t = tline;
3297 while (tok_type_(t, TOK_WHITESPACE))
3298 t = t->next;
3299 /* t should now point to the string */
3300 if (!tok_type_(t, TOK_STRING)) {
3301 nasm_error(ERR_NONFATAL,
3302 "`%s` requires string as second parameter",
3303 pp_directives[i]);
3304 free_tlist(tline);
3305 free_tlist(origline);
3306 return DIRECTIVE_FOUND;
3310 * Convert the string to a token stream. Note that smacros
3311 * are stored with the token stream reversed, so we have to
3312 * reverse the output of tokenize().
3314 nasm_unquote_cstr(t->text, i);
3315 macro_start = reverse_tokens(tokenize(t->text));
3318 * We now have a macro name, an implicit parameter count of
3319 * zero, and a numeric token to use as an expansion. Create
3320 * and store an SMacro.
3322 define_smacro(ctx, mname, casesense, 0, macro_start);
3323 free_tlist(tline);
3324 free_tlist(origline);
3325 return DIRECTIVE_FOUND;
3327 case PP_PATHSEARCH:
3329 const char *found_path;
3331 casesense = true;
3333 tline = tline->next;
3334 skip_white_(tline);
3335 tline = expand_id(tline);
3336 if (!tline || (tline->type != TOK_ID &&
3337 (tline->type != TOK_PREPROC_ID ||
3338 tline->text[1] != '$'))) {
3339 nasm_error(ERR_NONFATAL,
3340 "`%%pathsearch' expects a macro identifier as first parameter");
3341 free_tlist(origline);
3342 return DIRECTIVE_FOUND;
3344 ctx = get_ctx(tline->text, &mname);
3345 last = tline;
3346 tline = expand_smacro(tline->next);
3347 last->next = NULL;
3349 t = tline;
3350 while (tok_type_(t, TOK_WHITESPACE))
3351 t = t->next;
3353 if (!t || (t->type != TOK_STRING &&
3354 t->type != TOK_INTERNAL_STRING)) {
3355 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3356 free_tlist(tline);
3357 free_tlist(origline);
3358 return DIRECTIVE_FOUND; /* but we did _something_ */
3360 if (t->next)
3361 nasm_error(ERR_WARNING|ERR_PASS1,
3362 "trailing garbage after `%%pathsearch' ignored");
3363 p = t->text;
3364 if (t->type != TOK_INTERNAL_STRING)
3365 nasm_unquote(p, NULL);
3367 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3368 if (!found_path)
3369 found_path = p;
3370 macro_start = nasm_malloc(sizeof(*macro_start));
3371 macro_start->next = NULL;
3372 macro_start->text = nasm_quote(found_path, strlen(found_path));
3373 macro_start->type = TOK_STRING;
3374 macro_start->a.mac = NULL;
3377 * We now have a macro name, an implicit parameter count of
3378 * zero, and a string token to use as an expansion. Create
3379 * and store an SMacro.
3381 define_smacro(ctx, mname, casesense, 0, macro_start);
3382 free_tlist(tline);
3383 free_tlist(origline);
3384 return DIRECTIVE_FOUND;
3387 case PP_STRLEN:
3388 casesense = true;
3390 tline = tline->next;
3391 skip_white_(tline);
3392 tline = expand_id(tline);
3393 if (!tline || (tline->type != TOK_ID &&
3394 (tline->type != TOK_PREPROC_ID ||
3395 tline->text[1] != '$'))) {
3396 nasm_error(ERR_NONFATAL,
3397 "`%%strlen' expects a macro identifier as first parameter");
3398 free_tlist(origline);
3399 return DIRECTIVE_FOUND;
3401 ctx = get_ctx(tline->text, &mname);
3402 last = tline;
3403 tline = expand_smacro(tline->next);
3404 last->next = NULL;
3406 t = tline;
3407 while (tok_type_(t, TOK_WHITESPACE))
3408 t = t->next;
3409 /* t should now point to the string */
3410 if (!tok_type_(t, TOK_STRING)) {
3411 nasm_error(ERR_NONFATAL,
3412 "`%%strlen` requires string as second parameter");
3413 free_tlist(tline);
3414 free_tlist(origline);
3415 return DIRECTIVE_FOUND;
3418 macro_start = nasm_malloc(sizeof(*macro_start));
3419 macro_start->next = NULL;
3420 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3421 macro_start->a.mac = NULL;
3424 * We now have a macro name, an implicit parameter count of
3425 * zero, and a numeric token to use as an expansion. Create
3426 * and store an SMacro.
3428 define_smacro(ctx, mname, casesense, 0, macro_start);
3429 free_tlist(tline);
3430 free_tlist(origline);
3431 return DIRECTIVE_FOUND;
3433 case PP_STRCAT:
3434 casesense = true;
3436 tline = tline->next;
3437 skip_white_(tline);
3438 tline = expand_id(tline);
3439 if (!tline || (tline->type != TOK_ID &&
3440 (tline->type != TOK_PREPROC_ID ||
3441 tline->text[1] != '$'))) {
3442 nasm_error(ERR_NONFATAL,
3443 "`%%strcat' expects a macro identifier as first parameter");
3444 free_tlist(origline);
3445 return DIRECTIVE_FOUND;
3447 ctx = get_ctx(tline->text, &mname);
3448 last = tline;
3449 tline = expand_smacro(tline->next);
3450 last->next = NULL;
3452 len = 0;
3453 list_for_each(t, tline) {
3454 switch (t->type) {
3455 case TOK_WHITESPACE:
3456 break;
3457 case TOK_STRING:
3458 len += t->a.len = nasm_unquote(t->text, NULL);
3459 break;
3460 case TOK_OTHER:
3461 if (!strcmp(t->text, ",")) /* permit comma separators */
3462 break;
3463 /* else fall through */
3464 default:
3465 nasm_error(ERR_NONFATAL,
3466 "non-string passed to `%%strcat' (%d)", t->type);
3467 free_tlist(tline);
3468 free_tlist(origline);
3469 return DIRECTIVE_FOUND;
3473 p = pp = nasm_malloc(len);
3474 list_for_each(t, tline) {
3475 if (t->type == TOK_STRING) {
3476 memcpy(p, t->text, t->a.len);
3477 p += t->a.len;
3482 * We now have a macro name, an implicit parameter count of
3483 * zero, and a numeric token to use as an expansion. Create
3484 * and store an SMacro.
3486 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3487 macro_start->text = nasm_quote(pp, len);
3488 nasm_free(pp);
3489 define_smacro(ctx, mname, casesense, 0, macro_start);
3490 free_tlist(tline);
3491 free_tlist(origline);
3492 return DIRECTIVE_FOUND;
3494 case PP_SUBSTR:
3496 int64_t start, count;
3497 size_t len;
3499 casesense = true;
3501 tline = tline->next;
3502 skip_white_(tline);
3503 tline = expand_id(tline);
3504 if (!tline || (tline->type != TOK_ID &&
3505 (tline->type != TOK_PREPROC_ID ||
3506 tline->text[1] != '$'))) {
3507 nasm_error(ERR_NONFATAL,
3508 "`%%substr' expects a macro identifier as first parameter");
3509 free_tlist(origline);
3510 return DIRECTIVE_FOUND;
3512 ctx = get_ctx(tline->text, &mname);
3513 last = tline;
3514 tline = expand_smacro(tline->next);
3515 last->next = NULL;
3517 if (tline) /* skip expanded id */
3518 t = tline->next;
3519 while (tok_type_(t, TOK_WHITESPACE))
3520 t = t->next;
3522 /* t should now point to the string */
3523 if (!tok_type_(t, TOK_STRING)) {
3524 nasm_error(ERR_NONFATAL,
3525 "`%%substr` requires string as second parameter");
3526 free_tlist(tline);
3527 free_tlist(origline);
3528 return DIRECTIVE_FOUND;
3531 tt = t->next;
3532 tptr = &tt;
3533 tokval.t_type = TOKEN_INVALID;
3534 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3535 if (!evalresult) {
3536 free_tlist(tline);
3537 free_tlist(origline);
3538 return DIRECTIVE_FOUND;
3539 } else if (!is_simple(evalresult)) {
3540 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3541 free_tlist(tline);
3542 free_tlist(origline);
3543 return DIRECTIVE_FOUND;
3545 start = evalresult->value - 1;
3547 while (tok_type_(tt, TOK_WHITESPACE))
3548 tt = tt->next;
3549 if (!tt) {
3550 count = 1; /* Backwards compatibility: one character */
3551 } else {
3552 tokval.t_type = TOKEN_INVALID;
3553 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3554 if (!evalresult) {
3555 free_tlist(tline);
3556 free_tlist(origline);
3557 return DIRECTIVE_FOUND;
3558 } else if (!is_simple(evalresult)) {
3559 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3560 free_tlist(tline);
3561 free_tlist(origline);
3562 return DIRECTIVE_FOUND;
3564 count = evalresult->value;
3567 len = nasm_unquote(t->text, NULL);
3569 /* make start and count being in range */
3570 if (start < 0)
3571 start = 0;
3572 if (count < 0)
3573 count = len + count + 1 - start;
3574 if (start + count > (int64_t)len)
3575 count = len - start;
3576 if (!len || count < 0 || start >=(int64_t)len)
3577 start = -1, count = 0; /* empty string */
3579 macro_start = nasm_malloc(sizeof(*macro_start));
3580 macro_start->next = NULL;
3581 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3582 macro_start->type = TOK_STRING;
3583 macro_start->a.mac = NULL;
3586 * We now have a macro name, an implicit parameter count of
3587 * zero, and a numeric token to use as an expansion. Create
3588 * and store an SMacro.
3590 define_smacro(ctx, mname, casesense, 0, macro_start);
3591 free_tlist(tline);
3592 free_tlist(origline);
3593 return DIRECTIVE_FOUND;
3596 case PP_ASSIGN:
3597 case PP_IASSIGN:
3598 casesense = (i == PP_ASSIGN);
3600 tline = tline->next;
3601 skip_white_(tline);
3602 tline = expand_id(tline);
3603 if (!tline || (tline->type != TOK_ID &&
3604 (tline->type != TOK_PREPROC_ID ||
3605 tline->text[1] != '$'))) {
3606 nasm_error(ERR_NONFATAL,
3607 "`%%%sassign' expects a macro identifier",
3608 (i == PP_IASSIGN ? "i" : ""));
3609 free_tlist(origline);
3610 return DIRECTIVE_FOUND;
3612 ctx = get_ctx(tline->text, &mname);
3613 last = tline;
3614 tline = expand_smacro(tline->next);
3615 last->next = NULL;
3617 t = tline;
3618 tptr = &t;
3619 tokval.t_type = TOKEN_INVALID;
3620 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3621 free_tlist(tline);
3622 if (!evalresult) {
3623 free_tlist(origline);
3624 return DIRECTIVE_FOUND;
3627 if (tokval.t_type)
3628 nasm_error(ERR_WARNING|ERR_PASS1,
3629 "trailing garbage after expression ignored");
3631 if (!is_simple(evalresult)) {
3632 nasm_error(ERR_NONFATAL,
3633 "non-constant value given to `%%%sassign'",
3634 (i == PP_IASSIGN ? "i" : ""));
3635 free_tlist(origline);
3636 return DIRECTIVE_FOUND;
3639 macro_start = nasm_malloc(sizeof(*macro_start));
3640 macro_start->next = NULL;
3641 make_tok_num(macro_start, reloc_value(evalresult));
3642 macro_start->a.mac = NULL;
3645 * We now have a macro name, an implicit parameter count of
3646 * zero, and a numeric token to use as an expansion. Create
3647 * and store an SMacro.
3649 define_smacro(ctx, mname, casesense, 0, macro_start);
3650 free_tlist(origline);
3651 return DIRECTIVE_FOUND;
3653 case PP_LINE:
3655 * Syntax is `%line nnn[+mmm] [filename]'
3657 tline = tline->next;
3658 skip_white_(tline);
3659 if (!tok_type_(tline, TOK_NUMBER)) {
3660 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3661 free_tlist(origline);
3662 return DIRECTIVE_FOUND;
3664 k = readnum(tline->text, &err);
3665 m = 1;
3666 tline = tline->next;
3667 if (tok_is_(tline, "+")) {
3668 tline = tline->next;
3669 if (!tok_type_(tline, TOK_NUMBER)) {
3670 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3671 free_tlist(origline);
3672 return DIRECTIVE_FOUND;
3674 m = readnum(tline->text, &err);
3675 tline = tline->next;
3677 skip_white_(tline);
3678 src_set_linnum(k);
3679 istk->lineinc = m;
3680 if (tline) {
3681 char *fname = detoken(tline, false);
3682 src_set_fname(fname);
3683 nasm_free(fname);
3685 free_tlist(origline);
3686 return DIRECTIVE_FOUND;
3688 default:
3689 nasm_error(ERR_FATAL,
3690 "preprocessor directive `%s' not yet implemented",
3691 pp_directives[i]);
3692 return DIRECTIVE_FOUND;
3697 * Ensure that a macro parameter contains a condition code and
3698 * nothing else. Return the condition code index if so, or -1
3699 * otherwise.
3701 static int find_cc(Token * t)
3703 Token *tt;
3705 if (!t)
3706 return -1; /* Probably a %+ without a space */
3708 skip_white_(t);
3709 if (t->type != TOK_ID)
3710 return -1;
3711 tt = t->next;
3712 skip_white_(tt);
3713 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3714 return -1;
3716 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3720 * This routines walks over tokens strem and hadnles tokens
3721 * pasting, if @handle_explicit passed then explicit pasting
3722 * term is handled, otherwise -- implicit pastings only.
3724 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3725 size_t mnum, bool handle_explicit)
3727 Token *tok, *next, **prev_next, **prev_nonspace;
3728 bool pasted = false;
3729 char *buf, *p;
3730 size_t len, i;
3733 * The last token before pasting. We need it
3734 * to be able to connect new handled tokens.
3735 * In other words if there were a tokens stream
3737 * A -> B -> C -> D
3739 * and we've joined tokens B and C, the resulting
3740 * stream should be
3742 * A -> BC -> D
3744 tok = *head;
3745 prev_next = NULL;
3747 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3748 prev_nonspace = head;
3749 else
3750 prev_nonspace = NULL;
3752 while (tok && (next = tok->next)) {
3754 switch (tok->type) {
3755 case TOK_WHITESPACE:
3756 /* Zap redundant whitespaces */
3757 while (tok_type_(next, TOK_WHITESPACE))
3758 next = delete_Token(next);
3759 tok->next = next;
3760 break;
3762 case TOK_PASTE:
3763 /* Explicit pasting */
3764 if (!handle_explicit)
3765 break;
3766 next = delete_Token(tok);
3768 while (tok_type_(next, TOK_WHITESPACE))
3769 next = delete_Token(next);
3771 if (!pasted)
3772 pasted = true;
3774 /* Left pasting token is start of line */
3775 if (!prev_nonspace)
3776 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3779 * No ending token, this might happen in two
3780 * cases
3782 * 1) There indeed no right token at all
3783 * 2) There is a bare "%define ID" statement,
3784 * and @ID does expand to whitespace.
3786 * So technically we need to do a grammar analysis
3787 * in another stage of parsing, but for now lets don't
3788 * change the behaviour people used to. Simply allow
3789 * whitespace after paste token.
3791 if (!next) {
3793 * Zap ending space tokens and that's all.
3795 tok = (*prev_nonspace)->next;
3796 while (tok_type_(tok, TOK_WHITESPACE))
3797 tok = delete_Token(tok);
3798 tok = *prev_nonspace;
3799 tok->next = NULL;
3800 break;
3803 tok = *prev_nonspace;
3804 while (tok_type_(tok, TOK_WHITESPACE))
3805 tok = delete_Token(tok);
3806 len = strlen(tok->text);
3807 len += strlen(next->text);
3809 p = buf = nasm_malloc(len + 1);
3810 strcpy(p, tok->text);
3811 p = strchr(p, '\0');
3812 strcpy(p, next->text);
3814 delete_Token(tok);
3816 tok = tokenize(buf);
3817 nasm_free(buf);
3819 *prev_nonspace = tok;
3820 while (tok && tok->next)
3821 tok = tok->next;
3823 tok->next = delete_Token(next);
3825 /* Restart from pasted tokens head */
3826 tok = *prev_nonspace;
3827 break;
3829 default:
3830 /* implicit pasting */
3831 for (i = 0; i < mnum; i++) {
3832 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3833 continue;
3835 len = 0;
3836 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3837 len += strlen(next->text);
3838 next = next->next;
3841 /* No match */
3842 if (tok == next)
3843 break;
3845 len += strlen(tok->text);
3846 p = buf = nasm_malloc(len + 1);
3848 while (tok != next) {
3849 strcpy(p, tok->text);
3850 p = strchr(p, '\0');
3851 tok = delete_Token(tok);
3854 tok = tokenize(buf);
3855 nasm_free(buf);
3857 if (prev_next)
3858 *prev_next = tok;
3859 else
3860 *head = tok;
3863 * Connect pasted into original stream,
3864 * ie A -> new-tokens -> B
3866 while (tok && tok->next)
3867 tok = tok->next;
3868 tok->next = next;
3870 if (!pasted)
3871 pasted = true;
3873 /* Restart from pasted tokens head */
3874 tok = prev_next ? *prev_next : *head;
3877 break;
3880 prev_next = &tok->next;
3882 if (tok->next &&
3883 !tok_type_(tok->next, TOK_WHITESPACE) &&
3884 !tok_type_(tok->next, TOK_PASTE))
3885 prev_nonspace = prev_next;
3887 tok = tok->next;
3890 return pasted;
3894 * expands to a list of tokens from %{x:y}
3896 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3898 Token *t = tline, **tt, *tm, *head;
3899 char *pos;
3900 int fst, lst, j, i;
3902 pos = strchr(tline->text, ':');
3903 nasm_assert(pos);
3905 lst = atoi(pos + 1);
3906 fst = atoi(tline->text + 1);
3909 * only macros params are accounted so
3910 * if someone passes %0 -- we reject such
3911 * value(s)
3913 if (lst == 0 || fst == 0)
3914 goto err;
3916 /* the values should be sane */
3917 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3918 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3919 goto err;
3921 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3922 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3924 /* counted from zero */
3925 fst--, lst--;
3928 * It will be at least one token. Note we
3929 * need to scan params until separator, otherwise
3930 * only first token will be passed.
3932 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3933 head = new_Token(NULL, tm->type, tm->text, 0);
3934 tt = &head->next, tm = tm->next;
3935 while (tok_isnt_(tm, ",")) {
3936 t = new_Token(NULL, tm->type, tm->text, 0);
3937 *tt = t, tt = &t->next, tm = tm->next;
3940 if (fst < lst) {
3941 for (i = fst + 1; i <= lst; i++) {
3942 t = new_Token(NULL, TOK_OTHER, ",", 0);
3943 *tt = t, tt = &t->next;
3944 j = (i + mac->rotate) % mac->nparam;
3945 tm = mac->params[j];
3946 while (tok_isnt_(tm, ",")) {
3947 t = new_Token(NULL, tm->type, tm->text, 0);
3948 *tt = t, tt = &t->next, tm = tm->next;
3951 } else {
3952 for (i = fst - 1; i >= lst; i--) {
3953 t = new_Token(NULL, TOK_OTHER, ",", 0);
3954 *tt = t, tt = &t->next;
3955 j = (i + mac->rotate) % mac->nparam;
3956 tm = mac->params[j];
3957 while (tok_isnt_(tm, ",")) {
3958 t = new_Token(NULL, tm->type, tm->text, 0);
3959 *tt = t, tt = &t->next, tm = tm->next;
3964 *last = tt;
3965 return head;
3967 err:
3968 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3969 &tline->text[1]);
3970 return tline;
3974 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3975 * %-n) and MMacro-local identifiers (%%foo) as well as
3976 * macro indirection (%[...]) and range (%{..:..}).
3978 static Token *expand_mmac_params(Token * tline)
3980 Token *t, *tt, **tail, *thead;
3981 bool changed = false;
3982 char *pos;
3984 tail = &thead;
3985 thead = NULL;
3987 while (tline) {
3988 if (tline->type == TOK_PREPROC_ID &&
3989 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3990 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3991 tline->text[1] == '%')) {
3992 char *text = NULL;
3993 int type = 0, cc; /* type = 0 to placate optimisers */
3994 char tmpbuf[30];
3995 unsigned int n;
3996 int i;
3997 MMacro *mac;
3999 t = tline;
4000 tline = tline->next;
4002 mac = istk->mstk;
4003 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4004 mac = mac->next_active;
4005 if (!mac) {
4006 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4007 } else {
4008 pos = strchr(t->text, ':');
4009 if (!pos) {
4010 switch (t->text[1]) {
4012 * We have to make a substitution of one of the
4013 * forms %1, %-1, %+1, %%foo, %0.
4015 case '0':
4016 type = TOK_NUMBER;
4017 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4018 text = nasm_strdup(tmpbuf);
4019 break;
4020 case '%':
4021 type = TOK_ID;
4022 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4023 mac->unique);
4024 text = nasm_strcat(tmpbuf, t->text + 2);
4025 break;
4026 case '-':
4027 n = atoi(t->text + 2) - 1;
4028 if (n >= mac->nparam)
4029 tt = NULL;
4030 else {
4031 if (mac->nparam > 1)
4032 n = (n + mac->rotate) % mac->nparam;
4033 tt = mac->params[n];
4035 cc = find_cc(tt);
4036 if (cc == -1) {
4037 nasm_error(ERR_NONFATAL,
4038 "macro parameter %d is not a condition code",
4039 n + 1);
4040 text = NULL;
4041 } else {
4042 type = TOK_ID;
4043 if (inverse_ccs[cc] == -1) {
4044 nasm_error(ERR_NONFATAL,
4045 "condition code `%s' is not invertible",
4046 conditions[cc]);
4047 text = NULL;
4048 } else
4049 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4051 break;
4052 case '+':
4053 n = atoi(t->text + 2) - 1;
4054 if (n >= mac->nparam)
4055 tt = NULL;
4056 else {
4057 if (mac->nparam > 1)
4058 n = (n + mac->rotate) % mac->nparam;
4059 tt = mac->params[n];
4061 cc = find_cc(tt);
4062 if (cc == -1) {
4063 nasm_error(ERR_NONFATAL,
4064 "macro parameter %d is not a condition code",
4065 n + 1);
4066 text = NULL;
4067 } else {
4068 type = TOK_ID;
4069 text = nasm_strdup(conditions[cc]);
4071 break;
4072 default:
4073 n = atoi(t->text + 1) - 1;
4074 if (n >= mac->nparam)
4075 tt = NULL;
4076 else {
4077 if (mac->nparam > 1)
4078 n = (n + mac->rotate) % mac->nparam;
4079 tt = mac->params[n];
4081 if (tt) {
4082 for (i = 0; i < mac->paramlen[n]; i++) {
4083 *tail = new_Token(NULL, tt->type, tt->text, 0);
4084 tail = &(*tail)->next;
4085 tt = tt->next;
4088 text = NULL; /* we've done it here */
4089 break;
4091 } else {
4093 * seems we have a parameters range here
4095 Token *head, **last;
4096 head = expand_mmac_params_range(mac, t, &last);
4097 if (head != t) {
4098 *tail = head;
4099 *last = tline;
4100 tline = head;
4101 text = NULL;
4105 if (!text) {
4106 delete_Token(t);
4107 } else {
4108 *tail = t;
4109 tail = &t->next;
4110 t->type = type;
4111 nasm_free(t->text);
4112 t->text = text;
4113 t->a.mac = NULL;
4115 changed = true;
4116 continue;
4117 } else if (tline->type == TOK_INDIRECT) {
4118 t = tline;
4119 tline = tline->next;
4120 tt = tokenize(t->text);
4121 tt = expand_mmac_params(tt);
4122 tt = expand_smacro(tt);
4123 *tail = tt;
4124 while (tt) {
4125 tt->a.mac = NULL; /* Necessary? */
4126 tail = &tt->next;
4127 tt = tt->next;
4129 delete_Token(t);
4130 changed = true;
4131 } else {
4132 t = *tail = tline;
4133 tline = tline->next;
4134 t->a.mac = NULL;
4135 tail = &t->next;
4138 *tail = NULL;
4140 if (changed) {
4141 const struct tokseq_match t[] = {
4143 PP_CONCAT_MASK(TOK_ID) |
4144 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4145 PP_CONCAT_MASK(TOK_ID) |
4146 PP_CONCAT_MASK(TOK_NUMBER) |
4147 PP_CONCAT_MASK(TOK_FLOAT) |
4148 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4151 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4152 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4155 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4158 return thead;
4162 * Expand all single-line macro calls made in the given line.
4163 * Return the expanded version of the line. The original is deemed
4164 * to be destroyed in the process. (In reality we'll just move
4165 * Tokens from input to output a lot of the time, rather than
4166 * actually bothering to destroy and replicate.)
4169 static Token *expand_smacro(Token * tline)
4171 Token *t, *tt, *mstart, **tail, *thead;
4172 SMacro *head = NULL, *m;
4173 Token **params;
4174 int *paramsize;
4175 unsigned int nparam, sparam;
4176 int brackets;
4177 Token *org_tline = tline;
4178 Context *ctx;
4179 const char *mname;
4180 int deadman = DEADMAN_LIMIT;
4181 bool expanded;
4184 * Trick: we should avoid changing the start token pointer since it can
4185 * be contained in "next" field of other token. Because of this
4186 * we allocate a copy of first token and work with it; at the end of
4187 * routine we copy it back
4189 if (org_tline) {
4190 tline = new_Token(org_tline->next, org_tline->type,
4191 org_tline->text, 0);
4192 tline->a.mac = org_tline->a.mac;
4193 nasm_free(org_tline->text);
4194 org_tline->text = NULL;
4197 expanded = true; /* Always expand %+ at least once */
4199 again:
4200 thead = NULL;
4201 tail = &thead;
4203 while (tline) { /* main token loop */
4204 if (!--deadman) {
4205 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4206 goto err;
4209 if ((mname = tline->text)) {
4210 /* if this token is a local macro, look in local context */
4211 if (tline->type == TOK_ID) {
4212 head = (SMacro *)hash_findix(&smacros, mname);
4213 } else if (tline->type == TOK_PREPROC_ID) {
4214 ctx = get_ctx(mname, &mname);
4215 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4216 } else
4217 head = NULL;
4220 * We've hit an identifier. As in is_mmacro below, we first
4221 * check whether the identifier is a single-line macro at
4222 * all, then think about checking for parameters if
4223 * necessary.
4225 list_for_each(m, head)
4226 if (!mstrcmp(m->name, mname, m->casesense))
4227 break;
4228 if (m) {
4229 mstart = tline;
4230 params = NULL;
4231 paramsize = NULL;
4232 if (m->nparam == 0) {
4234 * Simple case: the macro is parameterless. Discard the
4235 * one token that the macro call took, and push the
4236 * expansion back on the to-do stack.
4238 if (!m->expansion) {
4239 if (!strcmp("__FILE__", m->name)) {
4240 const char *file = src_get_fname();
4241 /* nasm_free(tline->text); here? */
4242 tline->text = nasm_quote(file, strlen(file));
4243 tline->type = TOK_STRING;
4244 continue;
4246 if (!strcmp("__LINE__", m->name)) {
4247 nasm_free(tline->text);
4248 make_tok_num(tline, src_get_linnum());
4249 continue;
4251 if (!strcmp("__BITS__", m->name)) {
4252 nasm_free(tline->text);
4253 make_tok_num(tline, globalbits);
4254 continue;
4256 tline = delete_Token(tline);
4257 continue;
4259 } else {
4261 * Complicated case: at least one macro with this name
4262 * exists and takes parameters. We must find the
4263 * parameters in the call, count them, find the SMacro
4264 * that corresponds to that form of the macro call, and
4265 * substitute for the parameters when we expand. What a
4266 * pain.
4268 /*tline = tline->next;
4269 skip_white_(tline); */
4270 do {
4271 t = tline->next;
4272 while (tok_type_(t, TOK_SMAC_END)) {
4273 t->a.mac->in_progress = false;
4274 t->text = NULL;
4275 t = tline->next = delete_Token(t);
4277 tline = t;
4278 } while (tok_type_(tline, TOK_WHITESPACE));
4279 if (!tok_is_(tline, "(")) {
4281 * This macro wasn't called with parameters: ignore
4282 * the call. (Behaviour borrowed from gnu cpp.)
4284 tline = mstart;
4285 m = NULL;
4286 } else {
4287 int paren = 0;
4288 int white = 0;
4289 brackets = 0;
4290 nparam = 0;
4291 sparam = PARAM_DELTA;
4292 params = nasm_malloc(sparam * sizeof(Token *));
4293 params[0] = tline->next;
4294 paramsize = nasm_malloc(sparam * sizeof(int));
4295 paramsize[0] = 0;
4296 while (true) { /* parameter loop */
4298 * For some unusual expansions
4299 * which concatenates function call
4301 t = tline->next;
4302 while (tok_type_(t, TOK_SMAC_END)) {
4303 t->a.mac->in_progress = false;
4304 t->text = NULL;
4305 t = tline->next = delete_Token(t);
4307 tline = t;
4309 if (!tline) {
4310 nasm_error(ERR_NONFATAL,
4311 "macro call expects terminating `)'");
4312 break;
4314 if (tline->type == TOK_WHITESPACE
4315 && brackets <= 0) {
4316 if (paramsize[nparam])
4317 white++;
4318 else
4319 params[nparam] = tline->next;
4320 continue; /* parameter loop */
4322 if (tline->type == TOK_OTHER
4323 && tline->text[1] == 0) {
4324 char ch = tline->text[0];
4325 if (ch == ',' && !paren && brackets <= 0) {
4326 if (++nparam >= sparam) {
4327 sparam += PARAM_DELTA;
4328 params = nasm_realloc(params,
4329 sparam * sizeof(Token *));
4330 paramsize = nasm_realloc(paramsize,
4331 sparam * sizeof(int));
4333 params[nparam] = tline->next;
4334 paramsize[nparam] = 0;
4335 white = 0;
4336 continue; /* parameter loop */
4338 if (ch == '{' &&
4339 (brackets > 0 || (brackets == 0 &&
4340 !paramsize[nparam])))
4342 if (!(brackets++)) {
4343 params[nparam] = tline->next;
4344 continue; /* parameter loop */
4347 if (ch == '}' && brackets > 0)
4348 if (--brackets == 0) {
4349 brackets = -1;
4350 continue; /* parameter loop */
4352 if (ch == '(' && !brackets)
4353 paren++;
4354 if (ch == ')' && brackets <= 0)
4355 if (--paren < 0)
4356 break;
4358 if (brackets < 0) {
4359 brackets = 0;
4360 nasm_error(ERR_NONFATAL, "braces do not "
4361 "enclose all of macro parameter");
4363 paramsize[nparam] += white + 1;
4364 white = 0;
4365 } /* parameter loop */
4366 nparam++;
4367 while (m && (m->nparam != nparam ||
4368 mstrcmp(m->name, mname,
4369 m->casesense)))
4370 m = m->next;
4371 if (!m)
4372 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4373 "macro `%s' exists, "
4374 "but not taking %d parameters",
4375 mstart->text, nparam);
4378 if (m && m->in_progress)
4379 m = NULL;
4380 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4382 * Design question: should we handle !tline, which
4383 * indicates missing ')' here, or expand those
4384 * macros anyway, which requires the (t) test a few
4385 * lines down?
4387 nasm_free(params);
4388 nasm_free(paramsize);
4389 tline = mstart;
4390 } else {
4392 * Expand the macro: we are placed on the last token of the
4393 * call, so that we can easily split the call from the
4394 * following tokens. We also start by pushing an SMAC_END
4395 * token for the cycle removal.
4397 t = tline;
4398 if (t) {
4399 tline = t->next;
4400 t->next = NULL;
4402 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4403 tt->a.mac = m;
4404 m->in_progress = true;
4405 tline = tt;
4406 list_for_each(t, m->expansion) {
4407 if (t->type >= TOK_SMAC_PARAM) {
4408 Token *pcopy = tline, **ptail = &pcopy;
4409 Token *ttt, *pt;
4410 int i;
4412 ttt = params[t->type - TOK_SMAC_PARAM];
4413 i = paramsize[t->type - TOK_SMAC_PARAM];
4414 while (--i >= 0) {
4415 pt = *ptail = new_Token(tline, ttt->type,
4416 ttt->text, 0);
4417 ptail = &pt->next;
4418 ttt = ttt->next;
4420 tline = pcopy;
4421 } else if (t->type == TOK_PREPROC_Q) {
4422 tt = new_Token(tline, TOK_ID, mname, 0);
4423 tline = tt;
4424 } else if (t->type == TOK_PREPROC_QQ) {
4425 tt = new_Token(tline, TOK_ID, m->name, 0);
4426 tline = tt;
4427 } else {
4428 tt = new_Token(tline, t->type, t->text, 0);
4429 tline = tt;
4434 * Having done that, get rid of the macro call, and clean
4435 * up the parameters.
4437 nasm_free(params);
4438 nasm_free(paramsize);
4439 free_tlist(mstart);
4440 expanded = true;
4441 continue; /* main token loop */
4446 if (tline->type == TOK_SMAC_END) {
4447 tline->a.mac->in_progress = false;
4448 tline = delete_Token(tline);
4449 } else {
4450 t = *tail = tline;
4451 tline = tline->next;
4452 t->a.mac = NULL;
4453 t->next = NULL;
4454 tail = &t->next;
4459 * Now scan the entire line and look for successive TOK_IDs that resulted
4460 * after expansion (they can't be produced by tokenize()). The successive
4461 * TOK_IDs should be concatenated.
4462 * Also we look for %+ tokens and concatenate the tokens before and after
4463 * them (without white spaces in between).
4465 if (expanded) {
4466 const struct tokseq_match t[] = {
4468 PP_CONCAT_MASK(TOK_ID) |
4469 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4470 PP_CONCAT_MASK(TOK_ID) |
4471 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4472 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4475 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4477 * If we concatenated something, *and* we had previously expanded
4478 * an actual macro, scan the lines again for macros...
4480 tline = thead;
4481 expanded = false;
4482 goto again;
4486 err:
4487 if (org_tline) {
4488 if (thead) {
4489 *org_tline = *thead;
4490 /* since we just gave text to org_line, don't free it */
4491 thead->text = NULL;
4492 delete_Token(thead);
4493 } else {
4494 /* the expression expanded to empty line;
4495 we can't return NULL for some reasons
4496 we just set the line to a single WHITESPACE token. */
4497 memset(org_tline, 0, sizeof(*org_tline));
4498 org_tline->text = NULL;
4499 org_tline->type = TOK_WHITESPACE;
4501 thead = org_tline;
4504 return thead;
4508 * Similar to expand_smacro but used exclusively with macro identifiers
4509 * right before they are fetched in. The reason is that there can be
4510 * identifiers consisting of several subparts. We consider that if there
4511 * are more than one element forming the name, user wants a expansion,
4512 * otherwise it will be left as-is. Example:
4514 * %define %$abc cde
4516 * the identifier %$abc will be left as-is so that the handler for %define
4517 * will suck it and define the corresponding value. Other case:
4519 * %define _%$abc cde
4521 * In this case user wants name to be expanded *before* %define starts
4522 * working, so we'll expand %$abc into something (if it has a value;
4523 * otherwise it will be left as-is) then concatenate all successive
4524 * PP_IDs into one.
4526 static Token *expand_id(Token * tline)
4528 Token *cur, *oldnext = NULL;
4530 if (!tline || !tline->next)
4531 return tline;
4533 cur = tline;
4534 while (cur->next &&
4535 (cur->next->type == TOK_ID ||
4536 cur->next->type == TOK_PREPROC_ID
4537 || cur->next->type == TOK_NUMBER))
4538 cur = cur->next;
4540 /* If identifier consists of just one token, don't expand */
4541 if (cur == tline)
4542 return tline;
4544 if (cur) {
4545 oldnext = cur->next; /* Detach the tail past identifier */
4546 cur->next = NULL; /* so that expand_smacro stops here */
4549 tline = expand_smacro(tline);
4551 if (cur) {
4552 /* expand_smacro possibly changhed tline; re-scan for EOL */
4553 cur = tline;
4554 while (cur && cur->next)
4555 cur = cur->next;
4556 if (cur)
4557 cur->next = oldnext;
4560 return tline;
4564 * Determine whether the given line constitutes a multi-line macro
4565 * call, and return the MMacro structure called if so. Doesn't have
4566 * to check for an initial label - that's taken care of in
4567 * expand_mmacro - but must check numbers of parameters. Guaranteed
4568 * to be called with tline->type == TOK_ID, so the putative macro
4569 * name is easy to find.
4571 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4573 MMacro *head, *m;
4574 Token **params;
4575 int nparam;
4577 head = (MMacro *) hash_findix(&mmacros, tline->text);
4580 * Efficiency: first we see if any macro exists with the given
4581 * name. If not, we can return NULL immediately. _Then_ we
4582 * count the parameters, and then we look further along the
4583 * list if necessary to find the proper MMacro.
4585 list_for_each(m, head)
4586 if (!mstrcmp(m->name, tline->text, m->casesense))
4587 break;
4588 if (!m)
4589 return NULL;
4592 * OK, we have a potential macro. Count and demarcate the
4593 * parameters.
4595 count_mmac_params(tline->next, &nparam, &params);
4598 * So we know how many parameters we've got. Find the MMacro
4599 * structure that handles this number.
4601 while (m) {
4602 if (m->nparam_min <= nparam
4603 && (m->plus || nparam <= m->nparam_max)) {
4605 * This one is right. Just check if cycle removal
4606 * prohibits us using it before we actually celebrate...
4608 if (m->in_progress > m->max_depth) {
4609 if (m->max_depth > 0) {
4610 nasm_error(ERR_WARNING,
4611 "reached maximum recursion depth of %i",
4612 m->max_depth);
4614 nasm_free(params);
4615 return NULL;
4618 * It's right, and we can use it. Add its default
4619 * parameters to the end of our list if necessary.
4621 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4622 params =
4623 nasm_realloc(params,
4624 ((m->nparam_min + m->ndefs +
4625 1) * sizeof(*params)));
4626 while (nparam < m->nparam_min + m->ndefs) {
4627 params[nparam] = m->defaults[nparam - m->nparam_min];
4628 nparam++;
4632 * If we've gone over the maximum parameter count (and
4633 * we're in Plus mode), ignore parameters beyond
4634 * nparam_max.
4636 if (m->plus && nparam > m->nparam_max)
4637 nparam = m->nparam_max;
4639 * Then terminate the parameter list, and leave.
4641 if (!params) { /* need this special case */
4642 params = nasm_malloc(sizeof(*params));
4643 nparam = 0;
4645 params[nparam] = NULL;
4646 *params_array = params;
4647 return m;
4650 * This one wasn't right: look for the next one with the
4651 * same name.
4653 list_for_each(m, m->next)
4654 if (!mstrcmp(m->name, tline->text, m->casesense))
4655 break;
4659 * After all that, we didn't find one with the right number of
4660 * parameters. Issue a warning, and fail to expand the macro.
4662 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4663 "macro `%s' exists, but not taking %d parameters",
4664 tline->text, nparam);
4665 nasm_free(params);
4666 return NULL;
4671 * Save MMacro invocation specific fields in
4672 * preparation for a recursive macro expansion
4674 static void push_mmacro(MMacro *m)
4676 MMacroInvocation *i;
4678 i = nasm_malloc(sizeof(MMacroInvocation));
4679 i->prev = m->prev;
4680 i->params = m->params;
4681 i->iline = m->iline;
4682 i->nparam = m->nparam;
4683 i->rotate = m->rotate;
4684 i->paramlen = m->paramlen;
4685 i->unique = m->unique;
4686 i->condcnt = m->condcnt;
4687 m->prev = i;
4692 * Restore MMacro invocation specific fields that were
4693 * saved during a previous recursive macro expansion
4695 static void pop_mmacro(MMacro *m)
4697 MMacroInvocation *i;
4699 if (m->prev) {
4700 i = m->prev;
4701 m->prev = i->prev;
4702 m->params = i->params;
4703 m->iline = i->iline;
4704 m->nparam = i->nparam;
4705 m->rotate = i->rotate;
4706 m->paramlen = i->paramlen;
4707 m->unique = i->unique;
4708 m->condcnt = i->condcnt;
4709 nasm_free(i);
4715 * Expand the multi-line macro call made by the given line, if
4716 * there is one to be expanded. If there is, push the expansion on
4717 * istk->expansion and return 1. Otherwise return 0.
4719 static int expand_mmacro(Token * tline)
4721 Token *startline = tline;
4722 Token *label = NULL;
4723 int dont_prepend = 0;
4724 Token **params, *t, *tt;
4725 MMacro *m;
4726 Line *l, *ll;
4727 int i, nparam, *paramlen;
4728 const char *mname;
4730 t = tline;
4731 skip_white_(t);
4732 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4733 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4734 return 0;
4735 m = is_mmacro(t, &params);
4736 if (m) {
4737 mname = t->text;
4738 } else {
4739 Token *last;
4741 * We have an id which isn't a macro call. We'll assume
4742 * it might be a label; we'll also check to see if a
4743 * colon follows it. Then, if there's another id after
4744 * that lot, we'll check it again for macro-hood.
4746 label = last = t;
4747 t = t->next;
4748 if (tok_type_(t, TOK_WHITESPACE))
4749 last = t, t = t->next;
4750 if (tok_is_(t, ":")) {
4751 dont_prepend = 1;
4752 last = t, t = t->next;
4753 if (tok_type_(t, TOK_WHITESPACE))
4754 last = t, t = t->next;
4756 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4757 return 0;
4758 last->next = NULL;
4759 mname = t->text;
4760 tline = t;
4764 * Fix up the parameters: this involves stripping leading and
4765 * trailing whitespace, then stripping braces if they are
4766 * present.
4768 for (nparam = 0; params[nparam]; nparam++) ;
4769 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4771 for (i = 0; params[i]; i++) {
4772 int brace = 0;
4773 int comma = (!m->plus || i < nparam - 1);
4775 t = params[i];
4776 skip_white_(t);
4777 if (tok_is_(t, "{"))
4778 t = t->next, brace++, comma = false;
4779 params[i] = t;
4780 paramlen[i] = 0;
4781 while (t) {
4782 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4783 break; /* ... because we have hit a comma */
4784 if (comma && t->type == TOK_WHITESPACE
4785 && tok_is_(t->next, ","))
4786 break; /* ... or a space then a comma */
4787 if (brace && t->type == TOK_OTHER) {
4788 if (t->text[0] == '{')
4789 brace++; /* ... or a nested opening brace */
4790 else if (t->text[0] == '}')
4791 if (!--brace)
4792 break; /* ... or a brace */
4794 t = t->next;
4795 paramlen[i]++;
4797 if (brace)
4798 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4802 * OK, we have a MMacro structure together with a set of
4803 * parameters. We must now go through the expansion and push
4804 * copies of each Line on to istk->expansion. Substitution of
4805 * parameter tokens and macro-local tokens doesn't get done
4806 * until the single-line macro substitution process; this is
4807 * because delaying them allows us to change the semantics
4808 * later through %rotate.
4810 * First, push an end marker on to istk->expansion, mark this
4811 * macro as in progress, and set up its invocation-specific
4812 * variables.
4814 ll = nasm_malloc(sizeof(Line));
4815 ll->next = istk->expansion;
4816 ll->finishes = m;
4817 ll->first = NULL;
4818 istk->expansion = ll;
4821 * Save the previous MMacro expansion in the case of
4822 * macro recursion
4824 if (m->max_depth && m->in_progress)
4825 push_mmacro(m);
4827 m->in_progress ++;
4828 m->params = params;
4829 m->iline = tline;
4830 m->nparam = nparam;
4831 m->rotate = 0;
4832 m->paramlen = paramlen;
4833 m->unique = unique++;
4834 m->lineno = 0;
4835 m->condcnt = 0;
4837 m->next_active = istk->mstk;
4838 istk->mstk = m;
4840 list_for_each(l, m->expansion) {
4841 Token **tail;
4843 ll = nasm_malloc(sizeof(Line));
4844 ll->finishes = NULL;
4845 ll->next = istk->expansion;
4846 istk->expansion = ll;
4847 tail = &ll->first;
4849 list_for_each(t, l->first) {
4850 Token *x = t;
4851 switch (t->type) {
4852 case TOK_PREPROC_Q:
4853 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4854 break;
4855 case TOK_PREPROC_QQ:
4856 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4857 break;
4858 case TOK_PREPROC_ID:
4859 if (t->text[1] == '0' && t->text[2] == '0') {
4860 dont_prepend = -1;
4861 x = label;
4862 if (!x)
4863 continue;
4865 /* fall through */
4866 default:
4867 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4868 break;
4870 tail = &tt->next;
4872 *tail = NULL;
4876 * If we had a label, push it on as the first line of
4877 * the macro expansion.
4879 if (label) {
4880 if (dont_prepend < 0)
4881 free_tlist(startline);
4882 else {
4883 ll = nasm_malloc(sizeof(Line));
4884 ll->finishes = NULL;
4885 ll->next = istk->expansion;
4886 istk->expansion = ll;
4887 ll->first = startline;
4888 if (!dont_prepend) {
4889 while (label->next)
4890 label = label->next;
4891 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4896 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4898 return 1;
4902 * This function adds macro names to error messages, and suppresses
4903 * them if necessary.
4905 static void pp_verror(int severity, const char *fmt, va_list arg)
4907 char buff[BUFSIZ];
4908 MMacro *mmac = NULL;
4909 int delta = 0;
4912 * If we're in a dead branch of IF or something like it, ignore the error.
4913 * However, because %else etc are evaluated in the state context
4914 * of the previous branch, errors might get lost:
4915 * %if 0 ... %else trailing garbage ... %endif
4916 * So %else etc should set the ERR_PP_PRECOND flag.
4918 if ((severity & ERR_MASK) < ERR_FATAL &&
4919 istk && istk->conds &&
4920 ((severity & ERR_PP_PRECOND) ?
4921 istk->conds->state == COND_NEVER :
4922 !emitting(istk->conds->state)))
4923 return;
4925 /* get %macro name */
4926 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4927 mmac = istk->mstk;
4928 /* but %rep blocks should be skipped */
4929 while (mmac && !mmac->name)
4930 mmac = mmac->next_active, delta++;
4933 if (mmac) {
4934 vsnprintf(buff, sizeof(buff), fmt, arg);
4936 nasm_set_verror(real_verror);
4937 nasm_error(severity, "(%s:%d) %s",
4938 mmac->name, mmac->lineno - delta, buff);
4939 nasm_set_verror(pp_verror);
4940 } else {
4941 real_verror(severity, fmt, arg);
4945 static void
4946 pp_reset(char *file, int apass, StrList **deplist)
4948 Token *t;
4950 cstk = NULL;
4951 istk = nasm_malloc(sizeof(Include));
4952 istk->next = NULL;
4953 istk->conds = NULL;
4954 istk->expansion = NULL;
4955 istk->mstk = NULL;
4956 istk->fp = nasm_open_read(file, NF_TEXT);
4957 istk->fname = NULL;
4958 src_set(0, file);
4959 istk->lineinc = 1;
4960 if (!istk->fp)
4961 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4962 defining = NULL;
4963 nested_mac_count = 0;
4964 nested_rep_count = 0;
4965 init_macros();
4966 unique = 0;
4968 if (tasm_compatible_mode)
4969 pp_add_stdmac(nasm_stdmac_tasm);
4971 pp_add_stdmac(nasm_stdmac_nasm);
4972 pp_add_stdmac(nasm_stdmac_version);
4974 if (extrastdmac)
4975 pp_add_stdmac(extrastdmac);
4977 stdmacpos = stdmacros[0];
4978 stdmacnext = &stdmacros[1];
4980 do_predef = true;
4983 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4984 * The caller, however, will also pass in 3 for preprocess-only so
4985 * we can set __PASS__ accordingly.
4987 pass = apass > 2 ? 2 : apass;
4989 dephead = deplist;
4990 nasm_add_string_to_strlist(dephead, file);
4993 * Define the __PASS__ macro. This is defined here unlike
4994 * all the other builtins, because it is special -- it varies between
4995 * passes.
4997 t = nasm_malloc(sizeof(*t));
4998 t->next = NULL;
4999 make_tok_num(t, apass);
5000 t->a.mac = NULL;
5001 define_smacro(NULL, "__PASS__", true, 0, t);
5004 static void pp_init(void)
5006 hash_init(&FileHash, HASH_MEDIUM);
5009 static char *pp_getline(void)
5011 char *line;
5012 Token *tline;
5014 real_verror = nasm_set_verror(pp_verror);
5016 while (1) {
5018 * Fetch a tokenized line, either from the macro-expansion
5019 * buffer or from the input file.
5021 tline = NULL;
5022 while (istk->expansion && istk->expansion->finishes) {
5023 Line *l = istk->expansion;
5024 if (!l->finishes->name && l->finishes->in_progress > 1) {
5025 Line *ll;
5028 * This is a macro-end marker for a macro with no
5029 * name, which means it's not really a macro at all
5030 * but a %rep block, and the `in_progress' field is
5031 * more than 1, meaning that we still need to
5032 * repeat. (1 means the natural last repetition; 0
5033 * means termination by %exitrep.) We have
5034 * therefore expanded up to the %endrep, and must
5035 * push the whole block on to the expansion buffer
5036 * again. We don't bother to remove the macro-end
5037 * marker: we'd only have to generate another one
5038 * if we did.
5040 l->finishes->in_progress--;
5041 list_for_each(l, l->finishes->expansion) {
5042 Token *t, *tt, **tail;
5044 ll = nasm_malloc(sizeof(Line));
5045 ll->next = istk->expansion;
5046 ll->finishes = NULL;
5047 ll->first = NULL;
5048 tail = &ll->first;
5050 list_for_each(t, l->first) {
5051 if (t->text || t->type == TOK_WHITESPACE) {
5052 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5053 tail = &tt->next;
5057 istk->expansion = ll;
5059 } else {
5061 * Check whether a `%rep' was started and not ended
5062 * within this macro expansion. This can happen and
5063 * should be detected. It's a fatal error because
5064 * I'm too confused to work out how to recover
5065 * sensibly from it.
5067 if (defining) {
5068 if (defining->name)
5069 nasm_panic(0, "defining with name in expansion");
5070 else if (istk->mstk->name)
5071 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5072 " expansion of macro `%s'",
5073 istk->mstk->name);
5077 * FIXME: investigate the relationship at this point between
5078 * istk->mstk and l->finishes
5081 MMacro *m = istk->mstk;
5082 istk->mstk = m->next_active;
5083 if (m->name) {
5085 * This was a real macro call, not a %rep, and
5086 * therefore the parameter information needs to
5087 * be freed.
5089 if (m->prev) {
5090 pop_mmacro(m);
5091 l->finishes->in_progress --;
5092 } else {
5093 nasm_free(m->params);
5094 free_tlist(m->iline);
5095 nasm_free(m->paramlen);
5096 l->finishes->in_progress = 0;
5098 } else
5099 free_mmacro(m);
5101 istk->expansion = l->next;
5102 nasm_free(l);
5103 lfmt->downlevel(LIST_MACRO);
5106 while (1) { /* until we get a line we can use */
5108 if (istk->expansion) { /* from a macro expansion */
5109 char *p;
5110 Line *l = istk->expansion;
5111 if (istk->mstk)
5112 istk->mstk->lineno++;
5113 tline = l->first;
5114 istk->expansion = l->next;
5115 nasm_free(l);
5116 p = detoken(tline, false);
5117 lfmt->line(LIST_MACRO, p);
5118 nasm_free(p);
5119 break;
5121 line = read_line();
5122 if (line) { /* from the current input file */
5123 line = prepreproc(line);
5124 tline = tokenize(line);
5125 nasm_free(line);
5126 break;
5129 * The current file has ended; work down the istk
5132 Include *i = istk;
5133 fclose(i->fp);
5134 if (i->conds) {
5135 /* nasm_error can't be conditionally suppressed */
5136 nasm_fatal(0,
5137 "expected `%%endif' before end of file");
5139 /* only set line and file name if there's a next node */
5140 if (i->next)
5141 src_set(i->lineno, i->fname);
5142 istk = i->next;
5143 lfmt->downlevel(LIST_INCLUDE);
5144 nasm_free(i);
5145 if (!istk) {
5146 line = NULL;
5147 goto done;
5149 if (istk->expansion && istk->expansion->finishes)
5150 break;
5155 * We must expand MMacro parameters and MMacro-local labels
5156 * _before_ we plunge into directive processing, to cope
5157 * with things like `%define something %1' such as STRUC
5158 * uses. Unless we're _defining_ a MMacro, in which case
5159 * those tokens should be left alone to go into the
5160 * definition; and unless we're in a non-emitting
5161 * condition, in which case we don't want to meddle with
5162 * anything.
5164 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5165 && !(istk->mstk && !istk->mstk->in_progress)) {
5166 tline = expand_mmac_params(tline);
5170 * Check the line to see if it's a preprocessor directive.
5172 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5173 if (line)
5174 break; /* Directive generated output */
5175 else
5176 continue;
5177 } else if (defining) {
5179 * We're defining a multi-line macro. We emit nothing
5180 * at all, and just
5181 * shove the tokenized line on to the macro definition.
5183 Line *l = nasm_malloc(sizeof(Line));
5184 l->next = defining->expansion;
5185 l->first = tline;
5186 l->finishes = NULL;
5187 defining->expansion = l;
5188 continue;
5189 } else if (istk->conds && !emitting(istk->conds->state)) {
5191 * We're in a non-emitting branch of a condition block.
5192 * Emit nothing at all, not even a blank line: when we
5193 * emerge from the condition we'll give a line-number
5194 * directive so we keep our place correctly.
5196 free_tlist(tline);
5197 continue;
5198 } else if (istk->mstk && !istk->mstk->in_progress) {
5200 * We're in a %rep block which has been terminated, so
5201 * we're walking through to the %endrep without
5202 * emitting anything. Emit nothing at all, not even a
5203 * blank line: when we emerge from the %rep block we'll
5204 * give a line-number directive so we keep our place
5205 * correctly.
5207 free_tlist(tline);
5208 continue;
5209 } else {
5210 tline = expand_smacro(tline);
5211 if (!expand_mmacro(tline)) {
5213 * De-tokenize the line again, and emit it.
5215 line = detoken(tline, true);
5216 free_tlist(tline);
5217 break;
5218 } else {
5219 continue; /* expand_mmacro calls free_tlist */
5224 done:
5225 nasm_set_verror(real_verror);
5226 return line;
5229 static void pp_cleanup(int pass)
5231 real_verror = nasm_set_verror(pp_verror);
5233 if (defining) {
5234 if (defining->name) {
5235 nasm_error(ERR_NONFATAL,
5236 "end of file while still defining macro `%s'",
5237 defining->name);
5238 } else {
5239 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5242 free_mmacro(defining);
5243 defining = NULL;
5246 nasm_set_verror(real_verror);
5248 while (cstk)
5249 ctx_pop();
5250 free_macros();
5251 while (istk) {
5252 Include *i = istk;
5253 istk = istk->next;
5254 fclose(i->fp);
5255 nasm_free(i);
5257 while (cstk)
5258 ctx_pop();
5259 src_set_fname(NULL);
5260 if (pass == 0) {
5261 IncPath *i;
5262 free_llist(predef);
5263 predef = NULL;
5264 delete_Blocks();
5265 freeTokens = NULL;
5266 while ((i = ipath)) {
5267 ipath = i->next;
5268 if (i->path)
5269 nasm_free(i->path);
5270 nasm_free(i);
5275 static void pp_include_path(char *path)
5277 IncPath *i;
5279 i = nasm_malloc(sizeof(IncPath));
5280 i->path = path ? nasm_strdup(path) : NULL;
5281 i->next = NULL;
5283 if (ipath) {
5284 IncPath *j = ipath;
5285 while (j->next)
5286 j = j->next;
5287 j->next = i;
5288 } else {
5289 ipath = i;
5293 static void pp_pre_include(char *fname)
5295 Token *inc, *space, *name;
5296 Line *l;
5298 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5299 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5300 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5302 l = nasm_malloc(sizeof(Line));
5303 l->next = predef;
5304 l->first = inc;
5305 l->finishes = NULL;
5306 predef = l;
5309 static void pp_pre_define(char *definition)
5311 Token *def, *space;
5312 Line *l;
5313 char *equals;
5315 real_verror = nasm_set_verror(pp_verror);
5317 equals = strchr(definition, '=');
5318 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5319 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5320 if (equals)
5321 *equals = ' ';
5322 space->next = tokenize(definition);
5323 if (equals)
5324 *equals = '=';
5326 if (space->next->type != TOK_PREPROC_ID &&
5327 space->next->type != TOK_ID)
5328 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5330 l = nasm_malloc(sizeof(Line));
5331 l->next = predef;
5332 l->first = def;
5333 l->finishes = NULL;
5334 predef = l;
5336 nasm_set_verror(real_verror);
5339 static void pp_pre_undefine(char *definition)
5341 Token *def, *space;
5342 Line *l;
5344 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5345 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5346 space->next = tokenize(definition);
5348 l = nasm_malloc(sizeof(Line));
5349 l->next = predef;
5350 l->first = def;
5351 l->finishes = NULL;
5352 predef = l;
5355 static void pp_add_stdmac(macros_t *macros)
5357 macros_t **mp;
5359 /* Find the end of the list and avoid duplicates */
5360 for (mp = stdmacros; *mp; mp++) {
5361 if (*mp == macros)
5362 return; /* Nothing to do */
5365 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5367 *mp = macros;
5370 static void pp_extra_stdmac(macros_t *macros)
5372 extrastdmac = macros;
5375 static void make_tok_num(Token * tok, int64_t val)
5377 char numbuf[32];
5378 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5379 tok->text = nasm_strdup(numbuf);
5380 tok->type = TOK_NUMBER;
5383 static void pp_list_one_macro(MMacro *m, int severity)
5385 if (!m)
5386 return;
5388 /* We need to print the next_active list in reverse order */
5389 pp_list_one_macro(m->next_active, severity);
5391 if (m->name && !m->nolist) {
5392 src_set(m->xline + m->lineno, m->fname);
5393 nasm_error(severity, "... from macro `%s' defined here", m->name);
5397 static void pp_error_list_macros(int severity)
5399 int32_t saved_line;
5400 const char *saved_fname = NULL;
5402 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5403 src_get(&saved_line, &saved_fname);
5405 if (istk)
5406 pp_list_one_macro(istk->mstk, severity);
5408 src_set(saved_line, saved_fname);
5411 const struct preproc_ops nasmpp = {
5412 pp_init,
5413 pp_reset,
5414 pp_getline,
5415 pp_cleanup,
5416 pp_extra_stdmac,
5417 pp_pre_define,
5418 pp_pre_undefine,
5419 pp_pre_include,
5420 pp_include_path,
5421 pp_error_list_macros,