macho: Improve macho_calculate_sizes
[nasm.git] / asm / preproc.c
blobb4c90aad0fe0aa7ca4652073e83cf7b89b7ad671
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 "preproc.h"
76 #include "hashtbl.h"
77 #include "quote.h"
78 #include "stdscan.h"
79 #include "eval.h"
80 #include "tokens.h"
81 #include "tables.h"
82 #include "listing.h"
84 typedef struct SMacro SMacro;
85 typedef struct MMacro MMacro;
86 typedef struct MMacroInvocation MMacroInvocation;
87 typedef struct Context Context;
88 typedef struct Token Token;
89 typedef struct Blocks Blocks;
90 typedef struct Line Line;
91 typedef struct Include Include;
92 typedef struct Cond Cond;
93 typedef struct IncPath IncPath;
96 * Note on the storage of both SMacro and MMacros: the hash table
97 * indexes them case-insensitively, and we then have to go through a
98 * linked list of potential case aliases (and, for MMacros, parameter
99 * ranges); this is to preserve the matching semantics of the earlier
100 * code. If the number of case aliases for a specific macro is a
101 * performance issue, you may want to reconsider your coding style.
105 * Store the definition of a single-line macro.
107 struct SMacro {
108 SMacro *next;
109 char *name;
110 bool casesense;
111 bool in_progress;
112 unsigned int nparam;
113 Token *expansion;
117 * Store the definition of a multi-line macro. This is also used to
118 * store the interiors of `%rep...%endrep' blocks, which are
119 * effectively self-re-invoking multi-line macros which simply
120 * don't have a name or bother to appear in the hash tables. %rep
121 * blocks are signified by having a NULL `name' field.
123 * In a MMacro describing a `%rep' block, the `in_progress' field
124 * isn't merely boolean, but gives the number of repeats left to
125 * run.
127 * The `next' field is used for storing MMacros in hash tables; the
128 * `next_active' field is for stacking them on istk entries.
130 * When a MMacro is being expanded, `params', `iline', `nparam',
131 * `paramlen', `rotate' and `unique' are local to the invocation.
133 struct MMacro {
134 MMacro *next;
135 MMacroInvocation *prev; /* previous invocation */
136 char *name;
137 int nparam_min, nparam_max;
138 bool casesense;
139 bool plus; /* is the last parameter greedy? */
140 bool nolist; /* is this macro listing-inhibited? */
141 int64_t in_progress; /* is this macro currently being expanded? */
142 int32_t max_depth; /* maximum number of recursive expansions allowed */
143 Token *dlist; /* All defaults as one list */
144 Token **defaults; /* Parameter default pointers */
145 int ndefs; /* number of default parameters */
146 Line *expansion;
148 MMacro *next_active;
149 MMacro *rep_nest; /* used for nesting %rep */
150 Token **params; /* actual parameters */
151 Token *iline; /* invocation line */
152 unsigned int nparam, rotate;
153 int *paramlen;
154 uint64_t unique;
155 int lineno; /* Current line number on expansion */
156 uint64_t condcnt; /* number of if blocks... */
158 const char *fname; /* File where defined */
159 int32_t xline; /* First line in macro */
163 /* Store the definition of a multi-line macro, as defined in a
164 * previous recursive macro expansion.
166 struct MMacroInvocation {
167 MMacroInvocation *prev; /* previous invocation */
168 Token **params; /* actual parameters */
169 Token *iline; /* invocation line */
170 unsigned int nparam, rotate;
171 int *paramlen;
172 uint64_t unique;
173 uint64_t condcnt;
178 * The context stack is composed of a linked list of these.
180 struct Context {
181 Context *next;
182 char *name;
183 struct hash_table localmac;
184 uint32_t number;
188 * This is the internal form which we break input lines up into.
189 * Typically stored in linked lists.
191 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
192 * necessarily used as-is, but is intended to denote the number of
193 * the substituted parameter. So in the definition
195 * %define a(x,y) ( (x) & ~(y) )
197 * the token representing `x' will have its type changed to
198 * TOK_SMAC_PARAM, but the one representing `y' will be
199 * TOK_SMAC_PARAM+1.
201 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
202 * which doesn't need quotes around it. Used in the pre-include
203 * mechanism as an alternative to trying to find a sensible type of
204 * quote to use on the filename we were passed.
206 enum pp_token_type {
207 TOK_NONE = 0, TOK_WHITESPACE, TOK_COMMENT, TOK_ID,
208 TOK_PREPROC_ID, TOK_STRING,
209 TOK_NUMBER, TOK_FLOAT, TOK_SMAC_END, TOK_OTHER,
210 TOK_INTERNAL_STRING,
211 TOK_PREPROC_Q, TOK_PREPROC_QQ,
212 TOK_PASTE, /* %+ */
213 TOK_INDIRECT, /* %[...] */
214 TOK_SMAC_PARAM, /* MUST BE LAST IN THE LIST!!! */
215 TOK_MAX = INT_MAX /* Keep compiler from reducing the range */
218 #define PP_CONCAT_MASK(x) (1 << (x))
219 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
221 struct tokseq_match {
222 int mask_head;
223 int mask_tail;
226 struct Token {
227 Token *next;
228 char *text;
229 union {
230 SMacro *mac; /* associated macro for TOK_SMAC_END */
231 size_t len; /* scratch length field */
232 } a; /* Auxiliary data */
233 enum pp_token_type type;
237 * Multi-line macro definitions are stored as a linked list of
238 * these, which is essentially a container to allow several linked
239 * lists of Tokens.
241 * Note that in this module, linked lists are treated as stacks
242 * wherever possible. For this reason, Lines are _pushed_ on to the
243 * `expansion' field in MMacro structures, so that the linked list,
244 * if walked, would give the macro lines in reverse order; this
245 * means that we can walk the list when expanding a macro, and thus
246 * push the lines on to the `expansion' field in _istk_ in reverse
247 * order (so that when popped back off they are in the right
248 * order). It may seem cockeyed, and it relies on my design having
249 * an even number of steps in, but it works...
251 * Some of these structures, rather than being actual lines, are
252 * markers delimiting the end of the expansion of a given macro.
253 * This is for use in the cycle-tracking and %rep-handling code.
254 * Such structures have `finishes' non-NULL, and `first' NULL. All
255 * others have `finishes' NULL, but `first' may still be NULL if
256 * the line is blank.
258 struct Line {
259 Line *next;
260 MMacro *finishes;
261 Token *first;
265 * To handle an arbitrary level of file inclusion, we maintain a
266 * stack (ie linked list) of these things.
268 struct Include {
269 Include *next;
270 FILE *fp;
271 Cond *conds;
272 Line *expansion;
273 const char *fname;
274 int lineno, lineinc;
275 MMacro *mstk; /* stack of active macros/reps */
279 * Include search path. This is simply a list of strings which get
280 * prepended, in turn, to the name of an include file, in an
281 * attempt to find the file if it's not in the current directory.
283 struct IncPath {
284 IncPath *next;
285 char *path;
289 * File real name hash, so we don't have to re-search the include
290 * path for every pass (and potentially more than that if a file
291 * is used more than once.)
293 struct hash_table FileHash;
296 * Conditional assembly: we maintain a separate stack of these for
297 * each level of file inclusion. (The only reason we keep the
298 * stacks separate is to ensure that a stray `%endif' in a file
299 * included from within the true branch of a `%if' won't terminate
300 * it and cause confusion: instead, rightly, it'll cause an error.)
302 struct Cond {
303 Cond *next;
304 int state;
306 enum {
308 * These states are for use just after %if or %elif: IF_TRUE
309 * means the condition has evaluated to truth so we are
310 * currently emitting, whereas IF_FALSE means we are not
311 * currently emitting but will start doing so if a %else comes
312 * up. In these states, all directives are admissible: %elif,
313 * %else and %endif. (And of course %if.)
315 COND_IF_TRUE, COND_IF_FALSE,
317 * These states come up after a %else: ELSE_TRUE means we're
318 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
319 * any %elif or %else will cause an error.
321 COND_ELSE_TRUE, COND_ELSE_FALSE,
323 * These states mean that we're not emitting now, and also that
324 * nothing until %endif will be emitted at all. COND_DONE is
325 * used when we've had our moment of emission
326 * and have now started seeing %elifs. COND_NEVER is used when
327 * the condition construct in question is contained within a
328 * non-emitting branch of a larger condition construct,
329 * or if there is an error.
331 COND_DONE, COND_NEVER
333 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
336 * These defines are used as the possible return values for do_directive
338 #define NO_DIRECTIVE_FOUND 0
339 #define DIRECTIVE_FOUND 1
342 * This define sets the upper limit for smacro and recursive mmacro
343 * expansions
345 #define DEADMAN_LIMIT (1 << 20)
347 /* max reps */
348 #define REP_LIMIT ((INT64_C(1) << 62))
351 * Condition codes. Note that we use c_ prefix not C_ because C_ is
352 * used in nasm.h for the "real" condition codes. At _this_ level,
353 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
354 * ones, so we need a different enum...
356 static const char * const conditions[] = {
357 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
358 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
359 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
361 enum pp_conds {
362 c_A, c_AE, c_B, c_BE, c_C, c_CXZ, c_E, c_ECXZ, c_G, c_GE, c_L, c_LE,
363 c_NA, c_NAE, c_NB, c_NBE, c_NC, c_NE, c_NG, c_NGE, c_NL, c_NLE, c_NO,
364 c_NP, c_NS, c_NZ, c_O, c_P, c_PE, c_PO, c_RCXZ, c_S, c_Z,
365 c_none = -1
367 static const enum pp_conds inverse_ccs[] = {
368 c_NA, c_NAE, c_NB, c_NBE, c_NC, -1, c_NE, -1, c_NG, c_NGE, c_NL, c_NLE,
369 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,
370 c_Z, c_NO, c_NP, c_PO, c_PE, -1, c_NS, c_NZ
374 * Directive names.
376 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
377 static int is_condition(enum preproc_token arg)
379 return PP_IS_COND(arg) || (arg == PP_ELSE) || (arg == PP_ENDIF);
382 /* For TASM compatibility we need to be able to recognise TASM compatible
383 * conditional compilation directives. Using the NASM pre-processor does
384 * not work, so we look for them specifically from the following list and
385 * then jam in the equivalent NASM directive into the input stream.
388 enum {
389 TM_ARG, TM_ELIF, TM_ELSE, TM_ENDIF, TM_IF, TM_IFDEF, TM_IFDIFI,
390 TM_IFNDEF, TM_INCLUDE, TM_LOCAL
393 static const char * const tasm_directives[] = {
394 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
395 "ifndef", "include", "local"
398 static int StackSize = 4;
399 static const char *StackPointer = "ebp";
400 static int ArgOffset = 8;
401 static int LocalOffset = 0;
403 static Context *cstk;
404 static Include *istk;
405 static IncPath *ipath = NULL;
407 static int pass; /* HACK: pass 0 = generate dependencies only */
408 static StrList **dephead;
410 static uint64_t unique; /* unique identifier numbers */
412 static Line *predef = NULL;
413 static bool do_predef;
416 * The current set of multi-line macros we have defined.
418 static struct hash_table mmacros;
421 * The current set of single-line macros we have defined.
423 static struct hash_table smacros;
426 * The multi-line macro we are currently defining, or the %rep
427 * block we are currently reading, if any.
429 static MMacro *defining;
431 static uint64_t nested_mac_count;
432 static uint64_t nested_rep_count;
435 * The number of macro parameters to allocate space for at a time.
437 #define PARAM_DELTA 16
440 * The standard macro set: defined in macros.c in a set of arrays.
441 * This gives our position in any macro set, while we are processing it.
442 * The stdmacset is an array of such macro sets.
444 static macros_t *stdmacpos;
445 static macros_t **stdmacnext;
446 static macros_t *stdmacros[8];
449 * Tokens are allocated in blocks to improve speed
451 #define TOKEN_BLOCKSIZE 4096
452 static Token *freeTokens = NULL;
453 struct Blocks {
454 Blocks *next;
455 void *chunk;
458 static Blocks blocks = { NULL, NULL };
461 * Forward declarations.
463 static void pp_add_stdmac(macros_t *macros);
464 static Token *expand_mmac_params(Token * tline);
465 static Token *expand_smacro(Token * tline);
466 static Token *expand_id(Token * tline);
467 static Context *get_ctx(const char *name, const char **namep);
468 static void make_tok_num(Token * tok, int64_t val);
469 static void pp_verror(int severity, const char *fmt, va_list ap);
470 static vefunc real_verror;
471 static void *new_Block(size_t size);
472 static void delete_Blocks(void);
473 static Token *new_Token(Token * next, enum pp_token_type type,
474 const char *text, int txtlen);
475 static Token *delete_Token(Token * t);
478 * Macros for safe checking of token pointers, avoid *(NULL)
480 #define tok_type_(x,t) ((x) && (x)->type == (t))
481 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
482 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
483 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
486 * nasm_unquote with error if the string contains NUL characters.
487 * If the string contains NUL characters, issue an error and return
488 * the C len, i.e. truncate at the NUL.
490 static size_t nasm_unquote_cstr(char *qstr, enum preproc_token directive)
492 size_t len = nasm_unquote(qstr, NULL);
493 size_t clen = strlen(qstr);
495 if (len != clen)
496 nasm_error(ERR_NONFATAL, "NUL character in `%s' directive",
497 pp_directives[directive]);
499 return clen;
503 * In-place reverse a list of tokens.
505 static Token *reverse_tokens(Token *t)
507 Token *prev = NULL;
508 Token *next;
510 while (t) {
511 next = t->next;
512 t->next = prev;
513 prev = t;
514 t = next;
517 return prev;
521 * Handle TASM specific directives, which do not contain a % in
522 * front of them. We do it here because I could not find any other
523 * place to do it for the moment, and it is a hack (ideally it would
524 * be nice to be able to use the NASM pre-processor to do it).
526 static char *check_tasm_directive(char *line)
528 int32_t i, j, k, m, len;
529 char *p, *q, *oldline, oldchar;
531 p = nasm_skip_spaces(line);
533 /* Binary search for the directive name */
534 i = -1;
535 j = ARRAY_SIZE(tasm_directives);
536 q = nasm_skip_word(p);
537 len = q - p;
538 if (len) {
539 oldchar = p[len];
540 p[len] = 0;
541 while (j - i > 1) {
542 k = (j + i) / 2;
543 m = nasm_stricmp(p, tasm_directives[k]);
544 if (m == 0) {
545 /* We have found a directive, so jam a % in front of it
546 * so that NASM will then recognise it as one if it's own.
548 p[len] = oldchar;
549 len = strlen(p);
550 oldline = line;
551 line = nasm_malloc(len + 2);
552 line[0] = '%';
553 if (k == TM_IFDIFI) {
555 * NASM does not recognise IFDIFI, so we convert
556 * it to %if 0. This is not used in NASM
557 * compatible code, but does need to parse for the
558 * TASM macro package.
560 strcpy(line + 1, "if 0");
561 } else {
562 memcpy(line + 1, p, len + 1);
564 nasm_free(oldline);
565 return line;
566 } else if (m < 0) {
567 j = k;
568 } else
569 i = k;
571 p[len] = oldchar;
573 return line;
577 * The pre-preprocessing stage... This function translates line
578 * number indications as they emerge from GNU cpp (`# lineno "file"
579 * flags') into NASM preprocessor line number indications (`%line
580 * lineno file').
582 static char *prepreproc(char *line)
584 int lineno, fnlen;
585 char *fname, *oldline;
587 if (line[0] == '#' && line[1] == ' ') {
588 oldline = line;
589 fname = oldline + 2;
590 lineno = atoi(fname);
591 fname += strspn(fname, "0123456789 ");
592 if (*fname == '"')
593 fname++;
594 fnlen = strcspn(fname, "\"");
595 line = nasm_malloc(20 + fnlen);
596 snprintf(line, 20 + fnlen, "%%line %d %.*s", lineno, fnlen, fname);
597 nasm_free(oldline);
599 if (tasm_compatible_mode)
600 return check_tasm_directive(line);
601 return line;
605 * Free a linked list of tokens.
607 static void free_tlist(Token * list)
609 while (list)
610 list = delete_Token(list);
614 * Free a linked list of lines.
616 static void free_llist(Line * list)
618 Line *l, *tmp;
619 list_for_each_safe(l, tmp, list) {
620 free_tlist(l->first);
621 nasm_free(l);
626 * Free an MMacro
628 static void free_mmacro(MMacro * m)
630 nasm_free(m->name);
631 free_tlist(m->dlist);
632 nasm_free(m->defaults);
633 free_llist(m->expansion);
634 nasm_free(m);
638 * Free all currently defined macros, and free the hash tables
640 static void free_smacro_table(struct hash_table *smt)
642 SMacro *s, *tmp;
643 const char *key;
644 struct hash_tbl_node *it = NULL;
646 while ((s = hash_iterate(smt, &it, &key)) != NULL) {
647 nasm_free((void *)key);
648 list_for_each_safe(s, tmp, s) {
649 nasm_free(s->name);
650 free_tlist(s->expansion);
651 nasm_free(s);
654 hash_free(smt);
657 static void free_mmacro_table(struct hash_table *mmt)
659 MMacro *m, *tmp;
660 const char *key;
661 struct hash_tbl_node *it = NULL;
663 it = NULL;
664 while ((m = hash_iterate(mmt, &it, &key)) != NULL) {
665 nasm_free((void *)key);
666 list_for_each_safe(m ,tmp, m)
667 free_mmacro(m);
669 hash_free(mmt);
672 static void free_macros(void)
674 free_smacro_table(&smacros);
675 free_mmacro_table(&mmacros);
679 * Initialize the hash tables
681 static void init_macros(void)
683 hash_init(&smacros, HASH_LARGE);
684 hash_init(&mmacros, HASH_LARGE);
688 * Pop the context stack.
690 static void ctx_pop(void)
692 Context *c = cstk;
694 cstk = cstk->next;
695 free_smacro_table(&c->localmac);
696 nasm_free(c->name);
697 nasm_free(c);
701 * Search for a key in the hash index; adding it if necessary
702 * (in which case we initialize the data pointer to NULL.)
704 static void **
705 hash_findi_add(struct hash_table *hash, const char *str)
707 struct hash_insert hi;
708 void **r;
709 char *strx;
711 r = hash_findi(hash, str, &hi);
712 if (r)
713 return r;
715 strx = nasm_strdup(str); /* Use a more efficient allocator here? */
716 return hash_add(&hi, strx, NULL);
720 * Like hash_findi, but returns the data element rather than a pointer
721 * to it. Used only when not adding a new element, hence no third
722 * argument.
724 static void *
725 hash_findix(struct hash_table *hash, const char *str)
727 void **p;
729 p = hash_findi(hash, str, NULL);
730 return p ? *p : NULL;
734 * read line from standart macros set,
735 * if there no more left -- return NULL
737 static char *line_from_stdmac(void)
739 unsigned char c;
740 const unsigned char *p = stdmacpos;
741 char *line, *q;
742 size_t len = 0;
744 if (!stdmacpos)
745 return NULL;
747 while ((c = *p++)) {
748 if (c >= 0x80)
749 len += pp_directives_len[c - 0x80] + 1;
750 else
751 len++;
754 line = nasm_malloc(len + 1);
755 q = line;
756 while ((c = *stdmacpos++)) {
757 if (c >= 0x80) {
758 memcpy(q, pp_directives[c - 0x80], pp_directives_len[c - 0x80]);
759 q += pp_directives_len[c - 0x80];
760 *q++ = ' ';
761 } else {
762 *q++ = c;
765 stdmacpos = p;
766 *q = '\0';
768 if (!*stdmacpos) {
769 /* This was the last of this particular macro set */
770 stdmacpos = NULL;
771 if (*stdmacnext) {
772 stdmacpos = *stdmacnext++;
773 } else if (do_predef) {
774 Line *pd, *l;
775 Token *head, **tail, *t;
778 * Nasty hack: here we push the contents of
779 * `predef' on to the top-level expansion stack,
780 * since this is the most convenient way to
781 * implement the pre-include and pre-define
782 * features.
784 list_for_each(pd, predef) {
785 head = NULL;
786 tail = &head;
787 list_for_each(t, pd->first) {
788 *tail = new_Token(NULL, t->type, t->text, 0);
789 tail = &(*tail)->next;
792 l = nasm_malloc(sizeof(Line));
793 l->next = istk->expansion;
794 l->first = head;
795 l->finishes = NULL;
797 istk->expansion = l;
799 do_predef = false;
803 return line;
806 static char *read_line(void)
808 unsigned int size, c, next;
809 const unsigned int delta = 512;
810 const unsigned int pad = 8;
811 unsigned int nr_cont = 0;
812 bool cont = false;
813 char *buffer, *p;
815 /* Standart macros set (predefined) goes first */
816 p = line_from_stdmac();
817 if (p)
818 return p;
820 size = delta;
821 p = buffer = nasm_malloc(size);
823 for (;;) {
824 c = fgetc(istk->fp);
825 if ((int)(c) == EOF) {
826 p[0] = 0;
827 break;
830 switch (c) {
831 case '\r':
832 next = fgetc(istk->fp);
833 if (next != '\n')
834 ungetc(next, istk->fp);
835 if (cont) {
836 cont = false;
837 continue;
839 break;
841 case '\n':
842 if (cont) {
843 cont = false;
844 continue;
846 break;
848 case '\\':
849 next = fgetc(istk->fp);
850 ungetc(next, istk->fp);
851 if (next == '\r' || next == '\n') {
852 cont = true;
853 nr_cont++;
854 continue;
856 break;
859 if (c == '\r' || c == '\n') {
860 *p++ = 0;
861 break;
864 if (p >= (buffer + size - pad)) {
865 buffer = nasm_realloc(buffer, size + delta);
866 p = buffer + size - pad;
867 size += delta;
870 *p++ = (unsigned char)c;
873 if (p == buffer) {
874 nasm_free(buffer);
875 return NULL;
878 src_set_linnum(src_get_linnum() + istk->lineinc +
879 (nr_cont * istk->lineinc));
882 * Handle spurious ^Z, which may be inserted into source files
883 * by some file transfer utilities.
885 buffer[strcspn(buffer, "\032")] = '\0';
887 lfmt->line(LIST_READ, buffer);
889 return buffer;
893 * Tokenize a line of text. This is a very simple process since we
894 * don't need to parse the value out of e.g. numeric tokens: we
895 * simply split one string into many.
897 static Token *tokenize(char *line)
899 char c, *p = line;
900 enum pp_token_type type;
901 Token *list = NULL;
902 Token *t, **tail = &list;
904 while (*line) {
905 p = line;
906 if (*p == '%') {
907 p++;
908 if (*p == '+' && !nasm_isdigit(p[1])) {
909 p++;
910 type = TOK_PASTE;
911 } else if (nasm_isdigit(*p) ||
912 ((*p == '-' || *p == '+') && nasm_isdigit(p[1]))) {
913 do {
914 p++;
916 while (nasm_isdigit(*p));
917 type = TOK_PREPROC_ID;
918 } else if (*p == '{') {
919 p++;
920 while (*p) {
921 if (*p == '}')
922 break;
923 p[-1] = *p;
924 p++;
926 if (*p != '}')
927 nasm_error(ERR_WARNING | ERR_PASS1,
928 "unterminated %%{ construct");
929 p[-1] = '\0';
930 if (*p)
931 p++;
932 type = TOK_PREPROC_ID;
933 } else if (*p == '[') {
934 int lvl = 1;
935 line += 2; /* Skip the leading %[ */
936 p++;
937 while (lvl && (c = *p++)) {
938 switch (c) {
939 case ']':
940 lvl--;
941 break;
942 case '%':
943 if (*p == '[')
944 lvl++;
945 break;
946 case '\'':
947 case '\"':
948 case '`':
949 p = nasm_skip_string(p - 1) + 1;
950 break;
951 default:
952 break;
955 p--;
956 if (*p)
957 *p++ = '\0';
958 if (lvl)
959 nasm_error(ERR_NONFATAL|ERR_PASS1,
960 "unterminated %%[ construct");
961 type = TOK_INDIRECT;
962 } else if (*p == '?') {
963 type = TOK_PREPROC_Q; /* %? */
964 p++;
965 if (*p == '?') {
966 type = TOK_PREPROC_QQ; /* %?? */
967 p++;
969 } else if (*p == '!') {
970 type = TOK_PREPROC_ID;
971 p++;
972 if (isidchar(*p)) {
973 do {
974 p++;
976 while (isidchar(*p));
977 } else if (*p == '\'' || *p == '\"' || *p == '`') {
978 p = nasm_skip_string(p);
979 if (*p)
980 p++;
981 else
982 nasm_error(ERR_NONFATAL|ERR_PASS1,
983 "unterminated %%! string");
984 } else {
985 /* %! without string or identifier */
986 type = TOK_OTHER; /* Legacy behavior... */
988 } else if (isidchar(*p) ||
989 ((*p == '!' || *p == '%' || *p == '$') &&
990 isidchar(p[1]))) {
991 do {
992 p++;
994 while (isidchar(*p));
995 type = TOK_PREPROC_ID;
996 } else {
997 type = TOK_OTHER;
998 if (*p == '%')
999 p++;
1001 } else if (isidstart(*p) || (*p == '$' && isidstart(p[1]))) {
1002 type = TOK_ID;
1003 p++;
1004 while (*p && isidchar(*p))
1005 p++;
1006 } else if (*p == '\'' || *p == '"' || *p == '`') {
1008 * A string token.
1010 type = TOK_STRING;
1011 p = nasm_skip_string(p);
1013 if (*p) {
1014 p++;
1015 } else {
1016 nasm_error(ERR_WARNING|ERR_PASS1, "unterminated string");
1017 /* Handling unterminated strings by UNV */
1018 /* type = -1; */
1020 } else if (p[0] == '$' && p[1] == '$') {
1021 type = TOK_OTHER; /* TOKEN_BASE */
1022 p += 2;
1023 } else if (isnumstart(*p)) {
1024 bool is_hex = false;
1025 bool is_float = false;
1026 bool has_e = false;
1027 char c, *r;
1030 * A numeric token.
1033 if (*p == '$') {
1034 p++;
1035 is_hex = true;
1038 for (;;) {
1039 c = *p++;
1041 if (!is_hex && (c == 'e' || c == 'E')) {
1042 has_e = true;
1043 if (*p == '+' || *p == '-') {
1045 * e can only be followed by +/- if it is either a
1046 * prefixed hex number or a floating-point number
1048 p++;
1049 is_float = true;
1051 } else if (c == 'H' || c == 'h' || c == 'X' || c == 'x') {
1052 is_hex = true;
1053 } else if (c == 'P' || c == 'p') {
1054 is_float = true;
1055 if (*p == '+' || *p == '-')
1056 p++;
1057 } else if (isnumchar(c))
1058 ; /* just advance */
1059 else if (c == '.') {
1061 * we need to deal with consequences of the legacy
1062 * parser, like "1.nolist" being two tokens
1063 * (TOK_NUMBER, TOK_ID) here; at least give it
1064 * a shot for now. In the future, we probably need
1065 * a flex-based scanner with proper pattern matching
1066 * to do it as well as it can be done. Nothing in
1067 * the world is going to help the person who wants
1068 * 0x123.p16 interpreted as two tokens, though.
1070 r = p;
1071 while (*r == '_')
1072 r++;
1074 if (nasm_isdigit(*r) || (is_hex && nasm_isxdigit(*r)) ||
1075 (!is_hex && (*r == 'e' || *r == 'E')) ||
1076 (*r == 'p' || *r == 'P')) {
1077 p = r;
1078 is_float = true;
1079 } else
1080 break; /* Terminate the token */
1081 } else
1082 break;
1084 p--; /* Point to first character beyond number */
1086 if (p == line+1 && *line == '$') {
1087 type = TOK_OTHER; /* TOKEN_HERE */
1088 } else {
1089 if (has_e && !is_hex) {
1090 /* 1e13 is floating-point, but 1e13h is not */
1091 is_float = true;
1094 type = is_float ? TOK_FLOAT : TOK_NUMBER;
1096 } else if (nasm_isspace(*p)) {
1097 type = TOK_WHITESPACE;
1098 p = nasm_skip_spaces(p);
1100 * Whitespace just before end-of-line is discarded by
1101 * pretending it's a comment; whitespace just before a
1102 * comment gets lumped into the comment.
1104 if (!*p || *p == ';') {
1105 type = TOK_COMMENT;
1106 while (*p)
1107 p++;
1109 } else if (*p == ';') {
1110 type = TOK_COMMENT;
1111 while (*p)
1112 p++;
1113 } else {
1115 * Anything else is an operator of some kind. We check
1116 * for all the double-character operators (>>, <<, //,
1117 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1118 * else is a single-character operator.
1120 type = TOK_OTHER;
1121 if ((p[0] == '>' && p[1] == '>') ||
1122 (p[0] == '<' && p[1] == '<') ||
1123 (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++;
1134 p++;
1137 /* Handling unterminated string by UNV */
1138 /*if (type == -1)
1140 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1141 t->text[p-line] = *line;
1142 tail = &t->next;
1144 else */
1145 if (type != TOK_COMMENT) {
1146 *tail = t = new_Token(NULL, type, line, p - line);
1147 tail = &t->next;
1149 line = p;
1151 return list;
1155 * this function allocates a new managed block of memory and
1156 * returns a pointer to the block. The managed blocks are
1157 * deleted only all at once by the delete_Blocks function.
1159 static void *new_Block(size_t size)
1161 Blocks *b = &blocks;
1163 /* first, get to the end of the linked list */
1164 while (b->next)
1165 b = b->next;
1166 /* now allocate the requested chunk */
1167 b->chunk = nasm_malloc(size);
1169 /* now allocate a new block for the next request */
1170 b->next = nasm_zalloc(sizeof(Blocks));
1171 return b->chunk;
1175 * this function deletes all managed blocks of memory
1177 static void delete_Blocks(void)
1179 Blocks *a, *b = &blocks;
1182 * keep in mind that the first block, pointed to by blocks
1183 * is a static and not dynamically allocated, so we don't
1184 * free it.
1186 while (b) {
1187 if (b->chunk)
1188 nasm_free(b->chunk);
1189 a = b;
1190 b = b->next;
1191 if (a != &blocks)
1192 nasm_free(a);
1194 memset(&blocks, 0, sizeof(blocks));
1198 * this function creates a new Token and passes a pointer to it
1199 * back to the caller. It sets the type and text elements, and
1200 * also the a.mac and next elements to NULL.
1202 static Token *new_Token(Token * next, enum pp_token_type type,
1203 const char *text, int txtlen)
1205 Token *t;
1206 int i;
1208 if (!freeTokens) {
1209 freeTokens = (Token *) new_Block(TOKEN_BLOCKSIZE * sizeof(Token));
1210 for (i = 0; i < TOKEN_BLOCKSIZE - 1; i++)
1211 freeTokens[i].next = &freeTokens[i + 1];
1212 freeTokens[i].next = NULL;
1214 t = freeTokens;
1215 freeTokens = t->next;
1216 t->next = next;
1217 t->a.mac = NULL;
1218 t->type = type;
1219 if (type == TOK_WHITESPACE || !text) {
1220 t->text = NULL;
1221 } else {
1222 if (txtlen == 0)
1223 txtlen = strlen(text);
1224 t->text = nasm_malloc(txtlen+1);
1225 memcpy(t->text, text, txtlen);
1226 t->text[txtlen] = '\0';
1228 return t;
1231 static Token *delete_Token(Token * t)
1233 Token *next = t->next;
1234 nasm_free(t->text);
1235 t->next = freeTokens;
1236 freeTokens = t;
1237 return next;
1241 * Convert a line of tokens back into text.
1242 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1243 * will be transformed into ..@ctxnum.xxx
1245 static char *detoken(Token * tlist, bool expand_locals)
1247 Token *t;
1248 char *line, *p;
1249 const char *q;
1250 int len = 0;
1252 list_for_each(t, tlist) {
1253 if (t->type == TOK_PREPROC_ID && t->text[1] == '!') {
1254 char *v;
1255 char *q = t->text;
1257 v = t->text + 2;
1258 if (*v == '\'' || *v == '\"' || *v == '`') {
1259 size_t len = nasm_unquote(v, NULL);
1260 size_t clen = strlen(v);
1262 if (len != clen) {
1263 nasm_error(ERR_NONFATAL | ERR_PASS1,
1264 "NUL character in %%! string");
1265 v = NULL;
1269 if (v) {
1270 char *p = getenv(v);
1271 if (!p) {
1272 nasm_error(ERR_NONFATAL | ERR_PASS1,
1273 "nonexistent environment variable `%s'", v);
1275 * FIXME We better should investigate if accessing
1276 * ->text[1] without ->text[0] is safe enough.
1278 t->text = nasm_zalloc(2);
1279 } else
1280 t->text = nasm_strdup(p);
1282 nasm_free(q);
1285 /* Expand local macros here and not during preprocessing */
1286 if (expand_locals &&
1287 t->type == TOK_PREPROC_ID && t->text &&
1288 t->text[0] == '%' && t->text[1] == '$') {
1289 const char *q;
1290 char *p;
1291 Context *ctx = get_ctx(t->text, &q);
1292 if (ctx) {
1293 char buffer[40];
1294 snprintf(buffer, sizeof(buffer), "..@%"PRIu32".", ctx->number);
1295 p = nasm_strcat(buffer, q);
1296 nasm_free(t->text);
1297 t->text = p;
1300 if (t->type == TOK_WHITESPACE)
1301 len++;
1302 else if (t->text)
1303 len += strlen(t->text);
1306 p = line = nasm_malloc(len + 1);
1308 list_for_each(t, tlist) {
1309 if (t->type == TOK_WHITESPACE) {
1310 *p++ = ' ';
1311 } else if (t->text) {
1312 q = t->text;
1313 while (*q)
1314 *p++ = *q++;
1317 *p = '\0';
1319 return line;
1323 * A scanner, suitable for use by the expression evaluator, which
1324 * operates on a line of Tokens. Expects a pointer to a pointer to
1325 * the first token in the line to be passed in as its private_data
1326 * field.
1328 * FIX: This really needs to be unified with stdscan.
1330 static int ppscan(void *private_data, struct tokenval *tokval)
1332 Token **tlineptr = private_data;
1333 Token *tline;
1334 char ourcopy[MAX_KEYWORD+1], *p, *r, *s;
1336 do {
1337 tline = *tlineptr;
1338 *tlineptr = tline ? tline->next : NULL;
1339 } while (tline && (tline->type == TOK_WHITESPACE ||
1340 tline->type == TOK_COMMENT));
1342 if (!tline)
1343 return tokval->t_type = TOKEN_EOS;
1345 tokval->t_charptr = tline->text;
1347 if (tline->text[0] == '$' && !tline->text[1])
1348 return tokval->t_type = TOKEN_HERE;
1349 if (tline->text[0] == '$' && tline->text[1] == '$' && !tline->text[2])
1350 return tokval->t_type = TOKEN_BASE;
1352 if (tline->type == TOK_ID) {
1353 p = tokval->t_charptr = tline->text;
1354 if (p[0] == '$') {
1355 tokval->t_charptr++;
1356 return tokval->t_type = TOKEN_ID;
1359 for (r = p, s = ourcopy; *r; r++) {
1360 if (r >= p+MAX_KEYWORD)
1361 return tokval->t_type = TOKEN_ID; /* Not a keyword */
1362 *s++ = nasm_tolower(*r);
1364 *s = '\0';
1365 /* right, so we have an identifier sitting in temp storage. now,
1366 * is it actually a register or instruction name, or what? */
1367 return nasm_token_hash(ourcopy, tokval);
1370 if (tline->type == TOK_NUMBER) {
1371 bool rn_error;
1372 tokval->t_integer = readnum(tline->text, &rn_error);
1373 tokval->t_charptr = tline->text;
1374 if (rn_error)
1375 return tokval->t_type = TOKEN_ERRNUM;
1376 else
1377 return tokval->t_type = TOKEN_NUM;
1380 if (tline->type == TOK_FLOAT) {
1381 return tokval->t_type = TOKEN_FLOAT;
1384 if (tline->type == TOK_STRING) {
1385 char bq, *ep;
1387 bq = tline->text[0];
1388 tokval->t_charptr = tline->text;
1389 tokval->t_inttwo = nasm_unquote(tline->text, &ep);
1391 if (ep[0] != bq || ep[1] != '\0')
1392 return tokval->t_type = TOKEN_ERRSTR;
1393 else
1394 return tokval->t_type = TOKEN_STR;
1397 if (tline->type == TOK_OTHER) {
1398 if (!strcmp(tline->text, "<<"))
1399 return tokval->t_type = TOKEN_SHL;
1400 if (!strcmp(tline->text, ">>"))
1401 return tokval->t_type = TOKEN_SHR;
1402 if (!strcmp(tline->text, "//"))
1403 return tokval->t_type = TOKEN_SDIV;
1404 if (!strcmp(tline->text, "%%"))
1405 return tokval->t_type = TOKEN_SMOD;
1406 if (!strcmp(tline->text, "=="))
1407 return tokval->t_type = TOKEN_EQ;
1408 if (!strcmp(tline->text, "<>"))
1409 return tokval->t_type = TOKEN_NE;
1410 if (!strcmp(tline->text, "!="))
1411 return tokval->t_type = TOKEN_NE;
1412 if (!strcmp(tline->text, "<="))
1413 return tokval->t_type = TOKEN_LE;
1414 if (!strcmp(tline->text, ">="))
1415 return tokval->t_type = TOKEN_GE;
1416 if (!strcmp(tline->text, "&&"))
1417 return tokval->t_type = TOKEN_DBL_AND;
1418 if (!strcmp(tline->text, "^^"))
1419 return tokval->t_type = TOKEN_DBL_XOR;
1420 if (!strcmp(tline->text, "||"))
1421 return tokval->t_type = TOKEN_DBL_OR;
1425 * We have no other options: just return the first character of
1426 * the token text.
1428 return tokval->t_type = tline->text[0];
1432 * Compare a string to the name of an existing macro; this is a
1433 * simple wrapper which calls either strcmp or nasm_stricmp
1434 * depending on the value of the `casesense' parameter.
1436 static int mstrcmp(const char *p, const char *q, bool casesense)
1438 return casesense ? strcmp(p, q) : nasm_stricmp(p, q);
1442 * Compare a string to the name of an existing macro; this is a
1443 * simple wrapper which calls either strcmp or nasm_stricmp
1444 * depending on the value of the `casesense' parameter.
1446 static int mmemcmp(const char *p, const char *q, size_t l, bool casesense)
1448 return casesense ? memcmp(p, q, l) : nasm_memicmp(p, q, l);
1452 * Return the Context structure associated with a %$ token. Return
1453 * NULL, having _already_ reported an error condition, if the
1454 * context stack isn't deep enough for the supplied number of $
1455 * signs.
1457 * If "namep" is non-NULL, set it to the pointer to the macro name
1458 * tail, i.e. the part beyond %$...
1460 static Context *get_ctx(const char *name, const char **namep)
1462 Context *ctx;
1463 int i;
1465 if (namep)
1466 *namep = name;
1468 if (!name || name[0] != '%' || name[1] != '$')
1469 return NULL;
1471 if (!cstk) {
1472 nasm_error(ERR_NONFATAL, "`%s': context stack is empty", name);
1473 return NULL;
1476 name += 2;
1477 ctx = cstk;
1478 i = 0;
1479 while (ctx && *name == '$') {
1480 name++;
1481 i++;
1482 ctx = ctx->next;
1484 if (!ctx) {
1485 nasm_error(ERR_NONFATAL, "`%s': context stack is only"
1486 " %d level%s deep", name, i, (i == 1 ? "" : "s"));
1487 return NULL;
1490 if (namep)
1491 *namep = name;
1493 return ctx;
1497 * Open an include file. This routine must always return a valid
1498 * file pointer if it returns - it's responsible for throwing an
1499 * ERR_FATAL and bombing out completely if not. It should also try
1500 * the include path one by one until it finds the file or reaches
1501 * the end of the path.
1503 * Note: for INC_PROBE the function returns NULL at all times;
1504 * instead look for the
1506 enum incopen_mode {
1507 INC_NEEDED, /* File must exist */
1508 INC_OPTIONAL, /* Missing is OK */
1509 INC_PROBE /* Only an existence probe */
1512 /* This is conducts a full pathname search */
1513 static FILE *inc_fopen_search(const char *file, StrList **slpath,
1514 enum incopen_mode omode, enum file_flags fmode)
1516 FILE *fp;
1517 char *prefix = "";
1518 const IncPath *ip = ipath;
1519 int len = strlen(file);
1520 size_t prefix_len = 0;
1521 StrList *sl;
1522 size_t path_len;
1523 bool found;
1525 while (1) {
1526 path_len = prefix_len + len + 1;
1528 sl = nasm_malloc(path_len + sizeof sl->next);
1529 memcpy(sl->str, prefix, prefix_len);
1530 memcpy(sl->str+prefix_len, file, len+1);
1531 sl->next = NULL;
1533 if (omode == INC_PROBE) {
1534 fp = NULL;
1535 found = nasm_file_exists(sl->str);
1536 } else {
1537 fp = nasm_open_read(sl->str, fmode);
1538 found = (fp != NULL);
1540 if (found) {
1541 *slpath = sl;
1542 return fp;
1545 nasm_free(sl);
1547 if (!ip)
1548 return NULL;
1550 prefix = ip->path;
1551 prefix_len = strlen(prefix);
1552 ip = ip->next;
1557 * Open a file, or test for the presence of one (depending on omode),
1558 * considering the include path.
1560 static FILE *inc_fopen(const char *file,
1561 StrList **dhead,
1562 const char **found_path,
1563 enum incopen_mode omode,
1564 enum file_flags fmode)
1566 StrList *sl;
1567 struct hash_insert hi;
1568 void **hp;
1569 char *path;
1570 FILE *fp = NULL;
1572 hp = hash_find(&FileHash, file, &hi);
1573 if (hp) {
1574 path = *hp;
1575 } else {
1576 /* Need to do the actual path search */
1577 size_t file_len;
1579 sl = NULL;
1580 fp = inc_fopen_search(file, &sl, omode, fmode);
1582 file_len = strlen(file);
1584 if (!sl) {
1585 /* Store negative result for this file */
1586 sl = nasm_malloc(file_len + 1 + sizeof sl->next);
1587 memcpy(sl->str, file, file_len+1);
1588 sl->next = NULL;
1589 file = sl->str;
1590 path = NULL;
1591 } else {
1592 path = sl->str;
1593 file = strchr(path, '\0') - file_len;
1596 hash_add(&hi, file, path); /* Positive or negative result */
1599 * Add file to dependency path. The in_list() is needed
1600 * in case the file was already added with %depend.
1602 if (path || omode != INC_NEEDED)
1603 nasm_add_to_strlist(dhead, sl);
1606 if (!path) {
1607 if (omode == INC_NEEDED)
1608 nasm_fatal(0, "unable to open include file `%s'", file);
1610 if (found_path)
1611 *found_path = NULL;
1613 return NULL;
1616 if (!fp && omode != INC_PROBE)
1617 fp = nasm_open_read(file, fmode);
1619 if (found_path)
1620 *found_path = path;
1622 return fp;
1626 * Opens an include or input file. Public version, for use by modules
1627 * that get a file:lineno pair and need to look at the file again
1628 * (e.g. the CodeView debug backend). Returns NULL on failure.
1630 FILE *pp_input_fopen(const char *filename, enum file_flags mode)
1632 return inc_fopen(filename, NULL, NULL, INC_OPTIONAL, mode);
1636 * Determine if we should warn on defining a single-line macro of
1637 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1638 * return true if _any_ single-line macro of that name is defined.
1639 * Otherwise, will return true if a single-line macro with either
1640 * `nparam' or no parameters is defined.
1642 * If a macro with precisely the right number of parameters is
1643 * defined, or nparam is -1, the address of the definition structure
1644 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1645 * is NULL, no action will be taken regarding its contents, and no
1646 * error will occur.
1648 * Note that this is also called with nparam zero to resolve
1649 * `ifdef'.
1651 * If you already know which context macro belongs to, you can pass
1652 * the context pointer as first parameter; if you won't but name begins
1653 * with %$ the context will be automatically computed. If all_contexts
1654 * is true, macro will be searched in outer contexts as well.
1656 static bool
1657 smacro_defined(Context * ctx, const char *name, int nparam, SMacro ** defn,
1658 bool nocase)
1660 struct hash_table *smtbl;
1661 SMacro *m;
1663 if (ctx) {
1664 smtbl = &ctx->localmac;
1665 } else if (name[0] == '%' && name[1] == '$') {
1666 if (cstk)
1667 ctx = get_ctx(name, &name);
1668 if (!ctx)
1669 return false; /* got to return _something_ */
1670 smtbl = &ctx->localmac;
1671 } else {
1672 smtbl = &smacros;
1674 m = (SMacro *) hash_findix(smtbl, name);
1676 while (m) {
1677 if (!mstrcmp(m->name, name, m->casesense && nocase) &&
1678 (nparam <= 0 || m->nparam == 0 || nparam == (int) m->nparam)) {
1679 if (defn) {
1680 if (nparam == (int) m->nparam || nparam == -1)
1681 *defn = m;
1682 else
1683 *defn = NULL;
1685 return true;
1687 m = m->next;
1690 return false;
1694 * Count and mark off the parameters in a multi-line macro call.
1695 * This is called both from within the multi-line macro expansion
1696 * code, and also to mark off the default parameters when provided
1697 * in a %macro definition line.
1699 static void count_mmac_params(Token * t, int *nparam, Token *** params)
1701 int paramsize, brace;
1703 *nparam = paramsize = 0;
1704 *params = NULL;
1705 while (t) {
1706 /* +1: we need space for the final NULL */
1707 if (*nparam+1 >= paramsize) {
1708 paramsize += PARAM_DELTA;
1709 *params = nasm_realloc(*params, sizeof(**params) * paramsize);
1711 skip_white_(t);
1712 brace = 0;
1713 if (tok_is_(t, "{"))
1714 brace++;
1715 (*params)[(*nparam)++] = t;
1716 if (brace) {
1717 while (brace && (t = t->next) != NULL) {
1718 if (tok_is_(t, "{"))
1719 brace++;
1720 else if (tok_is_(t, "}"))
1721 brace--;
1724 if (t) {
1726 * Now we've found the closing brace, look further
1727 * for the comma.
1729 t = t->next;
1730 skip_white_(t);
1731 if (tok_isnt_(t, ",")) {
1732 nasm_error(ERR_NONFATAL,
1733 "braces do not enclose all of macro parameter");
1734 while (tok_isnt_(t, ","))
1735 t = t->next;
1738 } else {
1739 while (tok_isnt_(t, ","))
1740 t = t->next;
1742 if (t) { /* got a comma/brace */
1743 t = t->next; /* eat the comma */
1749 * Determine whether one of the various `if' conditions is true or
1750 * not.
1752 * We must free the tline we get passed.
1754 static bool if_condition(Token * tline, enum preproc_token ct)
1756 enum pp_conditional i = PP_COND(ct);
1757 bool j;
1758 Token *t, *tt, **tptr, *origline;
1759 struct tokenval tokval;
1760 expr *evalresult;
1761 enum pp_token_type needtype;
1762 char *p;
1764 origline = tline;
1766 switch (i) {
1767 case PPC_IFCTX:
1768 j = false; /* have we matched yet? */
1769 while (true) {
1770 skip_white_(tline);
1771 if (!tline)
1772 break;
1773 if (tline->type != TOK_ID) {
1774 nasm_error(ERR_NONFATAL,
1775 "`%s' expects context identifiers", pp_directives[ct]);
1776 free_tlist(origline);
1777 return -1;
1779 if (cstk && cstk->name && !nasm_stricmp(tline->text, cstk->name))
1780 j = true;
1781 tline = tline->next;
1783 break;
1785 case PPC_IFDEF:
1786 j = false; /* have we matched yet? */
1787 while (tline) {
1788 skip_white_(tline);
1789 if (!tline || (tline->type != TOK_ID &&
1790 (tline->type != TOK_PREPROC_ID ||
1791 tline->text[1] != '$'))) {
1792 nasm_error(ERR_NONFATAL,
1793 "`%s' expects macro identifiers", pp_directives[ct]);
1794 goto fail;
1796 if (smacro_defined(NULL, tline->text, 0, NULL, true))
1797 j = true;
1798 tline = tline->next;
1800 break;
1802 case PPC_IFENV:
1803 tline = expand_smacro(tline);
1804 j = false; /* have we matched yet? */
1805 while (tline) {
1806 skip_white_(tline);
1807 if (!tline || (tline->type != TOK_ID &&
1808 tline->type != TOK_STRING &&
1809 (tline->type != TOK_PREPROC_ID ||
1810 tline->text[1] != '!'))) {
1811 nasm_error(ERR_NONFATAL,
1812 "`%s' expects environment variable names",
1813 pp_directives[ct]);
1814 goto fail;
1816 p = tline->text;
1817 if (tline->type == TOK_PREPROC_ID)
1818 p += 2; /* Skip leading %! */
1819 if (*p == '\'' || *p == '\"' || *p == '`')
1820 nasm_unquote_cstr(p, ct);
1821 if (getenv(p))
1822 j = true;
1823 tline = tline->next;
1825 break;
1827 case PPC_IFIDN:
1828 case PPC_IFIDNI:
1829 tline = expand_smacro(tline);
1830 t = tt = tline;
1831 while (tok_isnt_(tt, ","))
1832 tt = tt->next;
1833 if (!tt) {
1834 nasm_error(ERR_NONFATAL,
1835 "`%s' expects two comma-separated arguments",
1836 pp_directives[ct]);
1837 goto fail;
1839 tt = tt->next;
1840 j = true; /* assume equality unless proved not */
1841 while ((t->type != TOK_OTHER || strcmp(t->text, ",")) && tt) {
1842 if (tt->type == TOK_OTHER && !strcmp(tt->text, ",")) {
1843 nasm_error(ERR_NONFATAL, "`%s': more than one comma on line",
1844 pp_directives[ct]);
1845 goto fail;
1847 if (t->type == TOK_WHITESPACE) {
1848 t = t->next;
1849 continue;
1851 if (tt->type == TOK_WHITESPACE) {
1852 tt = tt->next;
1853 continue;
1855 if (tt->type != t->type) {
1856 j = false; /* found mismatching tokens */
1857 break;
1859 /* When comparing strings, need to unquote them first */
1860 if (t->type == TOK_STRING) {
1861 size_t l1 = nasm_unquote(t->text, NULL);
1862 size_t l2 = nasm_unquote(tt->text, NULL);
1864 if (l1 != l2) {
1865 j = false;
1866 break;
1868 if (mmemcmp(t->text, tt->text, l1, i == PPC_IFIDN)) {
1869 j = false;
1870 break;
1872 } else if (mstrcmp(tt->text, t->text, i == PPC_IFIDN) != 0) {
1873 j = false; /* found mismatching tokens */
1874 break;
1877 t = t->next;
1878 tt = tt->next;
1880 if ((t->type != TOK_OTHER || strcmp(t->text, ",")) || tt)
1881 j = false; /* trailing gunk on one end or other */
1882 break;
1884 case PPC_IFMACRO:
1886 bool found = false;
1887 MMacro searching, *mmac;
1889 skip_white_(tline);
1890 tline = expand_id(tline);
1891 if (!tok_type_(tline, TOK_ID)) {
1892 nasm_error(ERR_NONFATAL,
1893 "`%s' expects a macro name", pp_directives[ct]);
1894 goto fail;
1896 searching.name = nasm_strdup(tline->text);
1897 searching.casesense = true;
1898 searching.plus = false;
1899 searching.nolist = false;
1900 searching.in_progress = 0;
1901 searching.max_depth = 0;
1902 searching.rep_nest = NULL;
1903 searching.nparam_min = 0;
1904 searching.nparam_max = INT_MAX;
1905 tline = expand_smacro(tline->next);
1906 skip_white_(tline);
1907 if (!tline) {
1908 } else if (!tok_type_(tline, TOK_NUMBER)) {
1909 nasm_error(ERR_NONFATAL,
1910 "`%s' expects a parameter count or nothing",
1911 pp_directives[ct]);
1912 } else {
1913 searching.nparam_min = searching.nparam_max =
1914 readnum(tline->text, &j);
1915 if (j)
1916 nasm_error(ERR_NONFATAL,
1917 "unable to parse parameter count `%s'",
1918 tline->text);
1920 if (tline && tok_is_(tline->next, "-")) {
1921 tline = tline->next->next;
1922 if (tok_is_(tline, "*"))
1923 searching.nparam_max = INT_MAX;
1924 else if (!tok_type_(tline, TOK_NUMBER))
1925 nasm_error(ERR_NONFATAL,
1926 "`%s' expects a parameter count after `-'",
1927 pp_directives[ct]);
1928 else {
1929 searching.nparam_max = readnum(tline->text, &j);
1930 if (j)
1931 nasm_error(ERR_NONFATAL,
1932 "unable to parse parameter count `%s'",
1933 tline->text);
1934 if (searching.nparam_min > searching.nparam_max)
1935 nasm_error(ERR_NONFATAL,
1936 "minimum parameter count exceeds maximum");
1939 if (tline && tok_is_(tline->next, "+")) {
1940 tline = tline->next;
1941 searching.plus = true;
1943 mmac = (MMacro *) hash_findix(&mmacros, searching.name);
1944 while (mmac) {
1945 if (!strcmp(mmac->name, searching.name) &&
1946 (mmac->nparam_min <= searching.nparam_max
1947 || searching.plus)
1948 && (searching.nparam_min <= mmac->nparam_max
1949 || mmac->plus)) {
1950 found = true;
1951 break;
1953 mmac = mmac->next;
1955 if (tline && tline->next)
1956 nasm_error(ERR_WARNING|ERR_PASS1,
1957 "trailing garbage after %%ifmacro ignored");
1958 nasm_free(searching.name);
1959 j = found;
1960 break;
1963 case PPC_IFID:
1964 needtype = TOK_ID;
1965 goto iftype;
1966 case PPC_IFNUM:
1967 needtype = TOK_NUMBER;
1968 goto iftype;
1969 case PPC_IFSTR:
1970 needtype = TOK_STRING;
1971 goto iftype;
1973 iftype:
1974 t = tline = expand_smacro(tline);
1976 while (tok_type_(t, TOK_WHITESPACE) ||
1977 (needtype == TOK_NUMBER &&
1978 tok_type_(t, TOK_OTHER) &&
1979 (t->text[0] == '-' || t->text[0] == '+') &&
1980 !t->text[1]))
1981 t = t->next;
1983 j = tok_type_(t, needtype);
1984 break;
1986 case PPC_IFTOKEN:
1987 t = tline = expand_smacro(tline);
1988 while (tok_type_(t, TOK_WHITESPACE))
1989 t = t->next;
1991 j = false;
1992 if (t) {
1993 t = t->next; /* Skip the actual token */
1994 while (tok_type_(t, TOK_WHITESPACE))
1995 t = t->next;
1996 j = !t; /* Should be nothing left */
1998 break;
2000 case PPC_IFEMPTY:
2001 t = tline = expand_smacro(tline);
2002 while (tok_type_(t, TOK_WHITESPACE))
2003 t = t->next;
2005 j = !t; /* Should be empty */
2006 break;
2008 case PPC_IF:
2009 t = tline = expand_smacro(tline);
2010 tptr = &t;
2011 tokval.t_type = TOKEN_INVALID;
2012 evalresult = evaluate(ppscan, tptr, &tokval,
2013 NULL, pass | CRITICAL, NULL);
2014 if (!evalresult)
2015 return -1;
2016 if (tokval.t_type)
2017 nasm_error(ERR_WARNING|ERR_PASS1,
2018 "trailing garbage after expression ignored");
2019 if (!is_simple(evalresult)) {
2020 nasm_error(ERR_NONFATAL,
2021 "non-constant value given to `%s'", pp_directives[ct]);
2022 goto fail;
2024 j = reloc_value(evalresult) != 0;
2025 break;
2027 default:
2028 nasm_error(ERR_FATAL,
2029 "preprocessor directive `%s' not yet implemented",
2030 pp_directives[ct]);
2031 goto fail;
2034 free_tlist(origline);
2035 return j ^ PP_NEGATIVE(ct);
2037 fail:
2038 free_tlist(origline);
2039 return -1;
2043 * Common code for defining an smacro
2045 static bool define_smacro(Context *ctx, const char *mname, bool casesense,
2046 int nparam, Token *expansion)
2048 SMacro *smac, **smhead;
2049 struct hash_table *smtbl;
2051 if (smacro_defined(ctx, mname, nparam, &smac, casesense)) {
2052 if (!smac) {
2053 nasm_error(ERR_WARNING|ERR_PASS1,
2054 "single-line macro `%s' defined both with and"
2055 " without parameters", mname);
2057 * Some instances of the old code considered this a failure,
2058 * some others didn't. What is the right thing to do here?
2060 free_tlist(expansion);
2061 return false; /* Failure */
2062 } else {
2064 * We're redefining, so we have to take over an
2065 * existing SMacro structure. This means freeing
2066 * what was already in it.
2068 nasm_free(smac->name);
2069 free_tlist(smac->expansion);
2071 } else {
2072 smtbl = ctx ? &ctx->localmac : &smacros;
2073 smhead = (SMacro **) hash_findi_add(smtbl, mname);
2074 smac = nasm_malloc(sizeof(SMacro));
2075 smac->next = *smhead;
2076 *smhead = smac;
2078 smac->name = nasm_strdup(mname);
2079 smac->casesense = casesense;
2080 smac->nparam = nparam;
2081 smac->expansion = expansion;
2082 smac->in_progress = false;
2083 return true; /* Success */
2087 * Undefine an smacro
2089 static void undef_smacro(Context *ctx, const char *mname)
2091 SMacro **smhead, *s, **sp;
2092 struct hash_table *smtbl;
2094 smtbl = ctx ? &ctx->localmac : &smacros;
2095 smhead = (SMacro **)hash_findi(smtbl, mname, NULL);
2097 if (smhead) {
2099 * We now have a macro name... go hunt for it.
2101 sp = smhead;
2102 while ((s = *sp) != NULL) {
2103 if (!mstrcmp(s->name, mname, s->casesense)) {
2104 *sp = s->next;
2105 nasm_free(s->name);
2106 free_tlist(s->expansion);
2107 nasm_free(s);
2108 } else {
2109 sp = &s->next;
2116 * Parse a mmacro specification.
2118 static bool parse_mmacro_spec(Token *tline, MMacro *def, const char *directive)
2120 bool err;
2122 tline = tline->next;
2123 skip_white_(tline);
2124 tline = expand_id(tline);
2125 if (!tok_type_(tline, TOK_ID)) {
2126 nasm_error(ERR_NONFATAL, "`%s' expects a macro name", directive);
2127 return false;
2130 def->prev = NULL;
2131 def->name = nasm_strdup(tline->text);
2132 def->plus = false;
2133 def->nolist = false;
2134 def->in_progress = 0;
2135 def->rep_nest = NULL;
2136 def->nparam_min = 0;
2137 def->nparam_max = 0;
2139 tline = expand_smacro(tline->next);
2140 skip_white_(tline);
2141 if (!tok_type_(tline, TOK_NUMBER)) {
2142 nasm_error(ERR_NONFATAL, "`%s' expects a parameter count", directive);
2143 } else {
2144 def->nparam_min = def->nparam_max =
2145 readnum(tline->text, &err);
2146 if (err)
2147 nasm_error(ERR_NONFATAL,
2148 "unable to parse parameter count `%s'", tline->text);
2150 if (tline && tok_is_(tline->next, "-")) {
2151 tline = tline->next->next;
2152 if (tok_is_(tline, "*")) {
2153 def->nparam_max = INT_MAX;
2154 } else if (!tok_type_(tline, TOK_NUMBER)) {
2155 nasm_error(ERR_NONFATAL,
2156 "`%s' expects a parameter count after `-'", directive);
2157 } else {
2158 def->nparam_max = readnum(tline->text, &err);
2159 if (err) {
2160 nasm_error(ERR_NONFATAL, "unable to parse parameter count `%s'",
2161 tline->text);
2163 if (def->nparam_min > def->nparam_max) {
2164 nasm_error(ERR_NONFATAL, "minimum parameter count exceeds maximum");
2168 if (tline && tok_is_(tline->next, "+")) {
2169 tline = tline->next;
2170 def->plus = true;
2172 if (tline && tok_type_(tline->next, TOK_ID) &&
2173 !nasm_stricmp(tline->next->text, ".nolist")) {
2174 tline = tline->next;
2175 def->nolist = true;
2179 * Handle default parameters.
2181 if (tline && tline->next) {
2182 def->dlist = tline->next;
2183 tline->next = NULL;
2184 count_mmac_params(def->dlist, &def->ndefs, &def->defaults);
2185 } else {
2186 def->dlist = NULL;
2187 def->defaults = NULL;
2189 def->expansion = NULL;
2191 if (def->defaults && def->ndefs > def->nparam_max - def->nparam_min &&
2192 !def->plus)
2193 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MDP,
2194 "too many default macro parameters");
2196 return true;
2201 * Decode a size directive
2203 static int parse_size(const char *str) {
2204 static const char *size_names[] =
2205 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2206 static const int sizes[] =
2207 { 0, 1, 4, 16, 8, 10, 2, 32 };
2209 return sizes[bsii(str, size_names, ARRAY_SIZE(size_names))+1];
2213 * Process a preprocessor %pragma directive. Currently there are none.
2214 * Gets passed the token list starting with the "preproc" token from
2215 * "%pragma preproc".
2217 static void do_pragma_preproc(Token *tline)
2219 /* Skip to the real stuff */
2220 tline = tline->next;
2221 skip_white_(tline);
2222 if (!tline)
2223 return;
2225 (void)tline; /* Nothing else to do at present */
2229 * find and process preprocessor directive in passed line
2230 * Find out if a line contains a preprocessor directive, and deal
2231 * with it if so.
2233 * If a directive _is_ found, it is the responsibility of this routine
2234 * (and not the caller) to free_tlist() the line.
2236 * @param tline a pointer to the current tokeninzed line linked list
2237 * @param output if this directive generated output
2238 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2241 static int do_directive(Token *tline, char **output)
2243 enum preproc_token i;
2244 int j;
2245 bool err;
2246 int nparam;
2247 bool nolist;
2248 bool casesense;
2249 int k, m;
2250 int offset;
2251 char *p, *pp;
2252 const char *found_path;
2253 const char *mname;
2254 Include *inc;
2255 Context *ctx;
2256 Cond *cond;
2257 MMacro *mmac, **mmhead;
2258 Token *t = NULL, *tt, *param_start, *macro_start, *last, **tptr, *origline;
2259 Line *l;
2260 struct tokenval tokval;
2261 expr *evalresult;
2262 MMacro *tmp_defining; /* Used when manipulating rep_nest */
2263 int64_t count;
2264 size_t len;
2265 int severity;
2267 *output = NULL; /* No output generated */
2268 origline = tline;
2270 skip_white_(tline);
2271 if (!tline || !tok_type_(tline, TOK_PREPROC_ID) ||
2272 (tline->text[1] == '%' || tline->text[1] == '$'
2273 || tline->text[1] == '!'))
2274 return NO_DIRECTIVE_FOUND;
2276 i = pp_token_hash(tline->text);
2279 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2280 * since they are known to be buggy at moment, we need to fix them
2281 * in future release (2.09-2.10)
2283 if (i == PP_RMACRO || i == PP_IRMACRO || i == PP_EXITMACRO) {
2284 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2285 tline->text);
2286 return NO_DIRECTIVE_FOUND;
2290 * If we're in a non-emitting branch of a condition construct,
2291 * or walking to the end of an already terminated %rep block,
2292 * we should ignore all directives except for condition
2293 * directives.
2295 if (((istk->conds && !emitting(istk->conds->state)) ||
2296 (istk->mstk && !istk->mstk->in_progress)) && !is_condition(i)) {
2297 return NO_DIRECTIVE_FOUND;
2301 * If we're defining a macro or reading a %rep block, we should
2302 * ignore all directives except for %macro/%imacro (which nest),
2303 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2304 * If we're in a %rep block, another %rep nests, so should be let through.
2306 if (defining && i != PP_MACRO && i != PP_IMACRO &&
2307 i != PP_RMACRO && i != PP_IRMACRO &&
2308 i != PP_ENDMACRO && i != PP_ENDM &&
2309 (defining->name || (i != PP_ENDREP && i != PP_REP))) {
2310 return NO_DIRECTIVE_FOUND;
2313 if (defining) {
2314 if (i == PP_MACRO || i == PP_IMACRO ||
2315 i == PP_RMACRO || i == PP_IRMACRO) {
2316 nested_mac_count++;
2317 return NO_DIRECTIVE_FOUND;
2318 } else if (nested_mac_count > 0) {
2319 if (i == PP_ENDMACRO) {
2320 nested_mac_count--;
2321 return NO_DIRECTIVE_FOUND;
2324 if (!defining->name) {
2325 if (i == PP_REP) {
2326 nested_rep_count++;
2327 return NO_DIRECTIVE_FOUND;
2328 } else if (nested_rep_count > 0) {
2329 if (i == PP_ENDREP) {
2330 nested_rep_count--;
2331 return NO_DIRECTIVE_FOUND;
2337 switch (i) {
2338 case PP_INVALID:
2339 nasm_error(ERR_NONFATAL, "unknown preprocessor directive `%s'",
2340 tline->text);
2341 return NO_DIRECTIVE_FOUND; /* didn't get it */
2343 case PP_PRAGMA:
2345 * %pragma namespace options...
2347 * The namespace "preproc" is reserved for the preprocessor;
2348 * all other namespaces generate a [pragma] assembly directive.
2350 * Invalid %pragmas are ignored and may have different
2351 * meaning in future versions of NASM.
2353 tline = tline->next;
2354 skip_white_(tline);
2355 tline = expand_smacro(tline);
2356 if (tok_type_(tline, TOK_ID)) {
2357 if (!nasm_stricmp(tline->text, "preproc")) {
2358 /* Preprocessor pragma */
2359 do_pragma_preproc(tline);
2360 } else {
2361 /* Build the assembler directive */
2362 t = new_Token(NULL, TOK_OTHER, "[", 1);
2363 t->next = new_Token(NULL, TOK_ID, "pragma", 6);
2364 t->next->next = new_Token(tline, TOK_WHITESPACE, NULL, 0);
2365 tline = t;
2366 for (t = tline; t->next; t = t->next)
2368 t->next = new_Token(NULL, TOK_OTHER, "]", 1);
2369 /* true here can be revisited in the future */
2370 *output = detoken(tline, true);
2373 free_tlist(origline);
2374 return DIRECTIVE_FOUND;
2376 case PP_STACKSIZE:
2377 /* Directive to tell NASM what the default stack size is. The
2378 * default is for a 16-bit stack, and this can be overriden with
2379 * %stacksize large.
2381 tline = tline->next;
2382 if (tline && tline->type == TOK_WHITESPACE)
2383 tline = tline->next;
2384 if (!tline || tline->type != TOK_ID) {
2385 nasm_error(ERR_NONFATAL, "`%%stacksize' missing size parameter");
2386 free_tlist(origline);
2387 return DIRECTIVE_FOUND;
2389 if (nasm_stricmp(tline->text, "flat") == 0) {
2390 /* All subsequent ARG directives are for a 32-bit stack */
2391 StackSize = 4;
2392 StackPointer = "ebp";
2393 ArgOffset = 8;
2394 LocalOffset = 0;
2395 } else if (nasm_stricmp(tline->text, "flat64") == 0) {
2396 /* All subsequent ARG directives are for a 64-bit stack */
2397 StackSize = 8;
2398 StackPointer = "rbp";
2399 ArgOffset = 16;
2400 LocalOffset = 0;
2401 } else if (nasm_stricmp(tline->text, "large") == 0) {
2402 /* All subsequent ARG directives are for a 16-bit stack,
2403 * far function call.
2405 StackSize = 2;
2406 StackPointer = "bp";
2407 ArgOffset = 4;
2408 LocalOffset = 0;
2409 } else if (nasm_stricmp(tline->text, "small") == 0) {
2410 /* All subsequent ARG directives are for a 16-bit stack,
2411 * far function call. We don't support near functions.
2413 StackSize = 2;
2414 StackPointer = "bp";
2415 ArgOffset = 6;
2416 LocalOffset = 0;
2417 } else {
2418 nasm_error(ERR_NONFATAL, "`%%stacksize' invalid size type");
2419 free_tlist(origline);
2420 return DIRECTIVE_FOUND;
2422 free_tlist(origline);
2423 return DIRECTIVE_FOUND;
2425 case PP_ARG:
2426 /* TASM like ARG directive to define arguments to functions, in
2427 * the following form:
2429 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2431 offset = ArgOffset;
2432 do {
2433 char *arg, directive[256];
2434 int size = StackSize;
2436 /* Find the argument name */
2437 tline = tline->next;
2438 if (tline && tline->type == TOK_WHITESPACE)
2439 tline = tline->next;
2440 if (!tline || tline->type != TOK_ID) {
2441 nasm_error(ERR_NONFATAL, "`%%arg' missing argument parameter");
2442 free_tlist(origline);
2443 return DIRECTIVE_FOUND;
2445 arg = tline->text;
2447 /* Find the argument size type */
2448 tline = tline->next;
2449 if (!tline || tline->type != TOK_OTHER
2450 || tline->text[0] != ':') {
2451 nasm_error(ERR_NONFATAL,
2452 "Syntax error processing `%%arg' directive");
2453 free_tlist(origline);
2454 return DIRECTIVE_FOUND;
2456 tline = tline->next;
2457 if (!tline || tline->type != TOK_ID) {
2458 nasm_error(ERR_NONFATAL, "`%%arg' missing size type parameter");
2459 free_tlist(origline);
2460 return DIRECTIVE_FOUND;
2463 /* Allow macro expansion of type parameter */
2464 tt = tokenize(tline->text);
2465 tt = expand_smacro(tt);
2466 size = parse_size(tt->text);
2467 if (!size) {
2468 nasm_error(ERR_NONFATAL,
2469 "Invalid size type for `%%arg' missing directive");
2470 free_tlist(tt);
2471 free_tlist(origline);
2472 return DIRECTIVE_FOUND;
2474 free_tlist(tt);
2476 /* Round up to even stack slots */
2477 size = ALIGN(size, StackSize);
2479 /* Now define the macro for the argument */
2480 snprintf(directive, sizeof(directive), "%%define %s (%s+%d)",
2481 arg, StackPointer, offset);
2482 do_directive(tokenize(directive), output);
2483 offset += size;
2485 /* Move to the next argument in the list */
2486 tline = tline->next;
2487 if (tline && tline->type == TOK_WHITESPACE)
2488 tline = tline->next;
2489 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2490 ArgOffset = offset;
2491 free_tlist(origline);
2492 return DIRECTIVE_FOUND;
2494 case PP_LOCAL:
2495 /* TASM like LOCAL directive to define local variables for a
2496 * function, in the following form:
2498 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2500 * The '= LocalSize' at the end is ignored by NASM, but is
2501 * required by TASM to define the local parameter size (and used
2502 * by the TASM macro package).
2504 offset = LocalOffset;
2505 do {
2506 char *local, directive[256];
2507 int size = StackSize;
2509 /* Find the argument name */
2510 tline = tline->next;
2511 if (tline && tline->type == TOK_WHITESPACE)
2512 tline = tline->next;
2513 if (!tline || tline->type != TOK_ID) {
2514 nasm_error(ERR_NONFATAL,
2515 "`%%local' missing argument parameter");
2516 free_tlist(origline);
2517 return DIRECTIVE_FOUND;
2519 local = tline->text;
2521 /* Find the argument size type */
2522 tline = tline->next;
2523 if (!tline || tline->type != TOK_OTHER
2524 || tline->text[0] != ':') {
2525 nasm_error(ERR_NONFATAL,
2526 "Syntax error processing `%%local' directive");
2527 free_tlist(origline);
2528 return DIRECTIVE_FOUND;
2530 tline = tline->next;
2531 if (!tline || tline->type != TOK_ID) {
2532 nasm_error(ERR_NONFATAL,
2533 "`%%local' missing size type parameter");
2534 free_tlist(origline);
2535 return DIRECTIVE_FOUND;
2538 /* Allow macro expansion of type parameter */
2539 tt = tokenize(tline->text);
2540 tt = expand_smacro(tt);
2541 size = parse_size(tt->text);
2542 if (!size) {
2543 nasm_error(ERR_NONFATAL,
2544 "Invalid size type for `%%local' missing directive");
2545 free_tlist(tt);
2546 free_tlist(origline);
2547 return DIRECTIVE_FOUND;
2549 free_tlist(tt);
2551 /* Round up to even stack slots */
2552 size = ALIGN(size, StackSize);
2554 offset += size; /* Negative offset, increment before */
2556 /* Now define the macro for the argument */
2557 snprintf(directive, sizeof(directive), "%%define %s (%s-%d)",
2558 local, StackPointer, offset);
2559 do_directive(tokenize(directive), output);
2561 /* Now define the assign to setup the enter_c macro correctly */
2562 snprintf(directive, sizeof(directive),
2563 "%%assign %%$localsize %%$localsize+%d", size);
2564 do_directive(tokenize(directive), output);
2566 /* Move to the next argument in the list */
2567 tline = tline->next;
2568 if (tline && tline->type == TOK_WHITESPACE)
2569 tline = tline->next;
2570 } while (tline && tline->type == TOK_OTHER && tline->text[0] == ',');
2571 LocalOffset = offset;
2572 free_tlist(origline);
2573 return DIRECTIVE_FOUND;
2575 case PP_CLEAR:
2576 if (tline->next)
2577 nasm_error(ERR_WARNING|ERR_PASS1,
2578 "trailing garbage after `%%clear' ignored");
2579 free_macros();
2580 init_macros();
2581 free_tlist(origline);
2582 return DIRECTIVE_FOUND;
2584 case PP_DEPEND:
2585 t = tline->next = expand_smacro(tline->next);
2586 skip_white_(t);
2587 if (!t || (t->type != TOK_STRING &&
2588 t->type != TOK_INTERNAL_STRING)) {
2589 nasm_error(ERR_NONFATAL, "`%%depend' expects a file name");
2590 free_tlist(origline);
2591 return DIRECTIVE_FOUND; /* but we did _something_ */
2593 if (t->next)
2594 nasm_error(ERR_WARNING|ERR_PASS1,
2595 "trailing garbage after `%%depend' ignored");
2596 p = t->text;
2597 if (t->type != TOK_INTERNAL_STRING)
2598 nasm_unquote_cstr(p, i);
2599 nasm_add_string_to_strlist(dephead, p);
2600 free_tlist(origline);
2601 return DIRECTIVE_FOUND;
2603 case PP_INCLUDE:
2604 t = tline->next = expand_smacro(tline->next);
2605 skip_white_(t);
2607 if (!t || (t->type != TOK_STRING &&
2608 t->type != TOK_INTERNAL_STRING)) {
2609 nasm_error(ERR_NONFATAL, "`%%include' expects a file name");
2610 free_tlist(origline);
2611 return DIRECTIVE_FOUND; /* but we did _something_ */
2613 if (t->next)
2614 nasm_error(ERR_WARNING|ERR_PASS1,
2615 "trailing garbage after `%%include' ignored");
2616 p = t->text;
2617 if (t->type != TOK_INTERNAL_STRING)
2618 nasm_unquote_cstr(p, i);
2619 inc = nasm_malloc(sizeof(Include));
2620 inc->next = istk;
2621 inc->conds = NULL;
2622 found_path = NULL;
2623 inc->fp = inc_fopen(p, dephead, &found_path,
2624 pass == 0 ? INC_OPTIONAL : INC_NEEDED, NF_TEXT);
2625 if (!inc->fp) {
2626 /* -MG given but file not found */
2627 nasm_free(inc);
2628 } else {
2629 inc->fname = src_set_fname(found_path ? found_path : p);
2630 inc->lineno = src_set_linnum(0);
2631 inc->lineinc = 1;
2632 inc->expansion = NULL;
2633 inc->mstk = NULL;
2634 istk = inc;
2635 lfmt->uplevel(LIST_INCLUDE);
2637 free_tlist(origline);
2638 return DIRECTIVE_FOUND;
2640 case PP_USE:
2642 static macros_t *use_pkg;
2643 const char *pkg_macro = NULL;
2645 tline = tline->next;
2646 skip_white_(tline);
2647 tline = expand_id(tline);
2649 if (!tline || (tline->type != TOK_STRING &&
2650 tline->type != TOK_INTERNAL_STRING &&
2651 tline->type != TOK_ID)) {
2652 nasm_error(ERR_NONFATAL, "`%%use' expects a package name");
2653 free_tlist(origline);
2654 return DIRECTIVE_FOUND; /* but we did _something_ */
2656 if (tline->next)
2657 nasm_error(ERR_WARNING|ERR_PASS1,
2658 "trailing garbage after `%%use' ignored");
2659 if (tline->type == TOK_STRING)
2660 nasm_unquote_cstr(tline->text, i);
2661 use_pkg = nasm_stdmac_find_package(tline->text);
2662 if (!use_pkg)
2663 nasm_error(ERR_NONFATAL, "unknown `%%use' package: %s", tline->text);
2664 else
2665 pkg_macro = (char *)use_pkg + 1; /* The first string will be <%define>__USE_*__ */
2666 if (use_pkg && ! smacro_defined(NULL, pkg_macro, 0, NULL, true)) {
2667 /* Not already included, go ahead and include it */
2668 stdmacpos = use_pkg;
2670 free_tlist(origline);
2671 return DIRECTIVE_FOUND;
2673 case PP_PUSH:
2674 case PP_REPL:
2675 case PP_POP:
2676 tline = tline->next;
2677 skip_white_(tline);
2678 tline = expand_id(tline);
2679 if (tline) {
2680 if (!tok_type_(tline, TOK_ID)) {
2681 nasm_error(ERR_NONFATAL, "`%s' expects a context identifier",
2682 pp_directives[i]);
2683 free_tlist(origline);
2684 return DIRECTIVE_FOUND; /* but we did _something_ */
2686 if (tline->next)
2687 nasm_error(ERR_WARNING|ERR_PASS1,
2688 "trailing garbage after `%s' ignored",
2689 pp_directives[i]);
2690 p = nasm_strdup(tline->text);
2691 } else {
2692 p = NULL; /* Anonymous */
2695 if (i == PP_PUSH) {
2696 ctx = nasm_malloc(sizeof(Context));
2697 ctx->next = cstk;
2698 hash_init(&ctx->localmac, HASH_SMALL);
2699 ctx->name = p;
2700 ctx->number = unique++;
2701 cstk = ctx;
2702 } else {
2703 /* %pop or %repl */
2704 if (!cstk) {
2705 nasm_error(ERR_NONFATAL, "`%s': context stack is empty",
2706 pp_directives[i]);
2707 } else if (i == PP_POP) {
2708 if (p && (!cstk->name || nasm_stricmp(p, cstk->name)))
2709 nasm_error(ERR_NONFATAL, "`%%pop' in wrong context: %s, "
2710 "expected %s",
2711 cstk->name ? cstk->name : "anonymous", p);
2712 else
2713 ctx_pop();
2714 } else {
2715 /* i == PP_REPL */
2716 nasm_free(cstk->name);
2717 cstk->name = p;
2718 p = NULL;
2720 nasm_free(p);
2722 free_tlist(origline);
2723 return DIRECTIVE_FOUND;
2724 case PP_FATAL:
2725 severity = ERR_FATAL;
2726 goto issue_error;
2727 case PP_ERROR:
2728 severity = ERR_NONFATAL;
2729 goto issue_error;
2730 case PP_WARNING:
2731 severity = ERR_WARNING|ERR_WARN_USER;
2732 goto issue_error;
2734 issue_error:
2736 /* Only error out if this is the final pass */
2737 if (pass != 2 && i != PP_FATAL)
2738 return DIRECTIVE_FOUND;
2740 tline->next = expand_smacro(tline->next);
2741 tline = tline->next;
2742 skip_white_(tline);
2743 t = tline ? tline->next : NULL;
2744 skip_white_(t);
2745 if (tok_type_(tline, TOK_STRING) && !t) {
2746 /* The line contains only a quoted string */
2747 p = tline->text;
2748 nasm_unquote(p, NULL); /* Ignore NUL character truncation */
2749 nasm_error(severity, "%s", p);
2750 } else {
2751 /* Not a quoted string, or more than a quoted string */
2752 p = detoken(tline, false);
2753 nasm_error(severity, "%s", p);
2754 nasm_free(p);
2756 free_tlist(origline);
2757 return DIRECTIVE_FOUND;
2760 CASE_PP_IF:
2761 if (istk->conds && !emitting(istk->conds->state))
2762 j = COND_NEVER;
2763 else {
2764 j = if_condition(tline->next, i);
2765 tline->next = NULL; /* it got freed */
2766 j = j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2768 cond = nasm_malloc(sizeof(Cond));
2769 cond->next = istk->conds;
2770 cond->state = j;
2771 istk->conds = cond;
2772 if(istk->mstk)
2773 istk->mstk->condcnt ++;
2774 free_tlist(origline);
2775 return DIRECTIVE_FOUND;
2777 CASE_PP_ELIF:
2778 if (!istk->conds)
2779 nasm_error(ERR_FATAL, "`%s': no matching `%%if'", pp_directives[i]);
2780 switch(istk->conds->state) {
2781 case COND_IF_TRUE:
2782 istk->conds->state = COND_DONE;
2783 break;
2785 case COND_DONE:
2786 case COND_NEVER:
2787 break;
2789 case COND_ELSE_TRUE:
2790 case COND_ELSE_FALSE:
2791 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2792 "`%%elif' after `%%else' ignored");
2793 istk->conds->state = COND_NEVER;
2794 break;
2796 case COND_IF_FALSE:
2798 * IMPORTANT: In the case of %if, we will already have
2799 * called expand_mmac_params(); however, if we're
2800 * processing an %elif we must have been in a
2801 * non-emitting mode, which would have inhibited
2802 * the normal invocation of expand_mmac_params().
2803 * Therefore, we have to do it explicitly here.
2805 j = if_condition(expand_mmac_params(tline->next), i);
2806 tline->next = NULL; /* it got freed */
2807 istk->conds->state =
2808 j < 0 ? COND_NEVER : j ? COND_IF_TRUE : COND_IF_FALSE;
2809 break;
2811 free_tlist(origline);
2812 return DIRECTIVE_FOUND;
2814 case PP_ELSE:
2815 if (tline->next)
2816 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2817 "trailing garbage after `%%else' ignored");
2818 if (!istk->conds)
2819 nasm_fatal(0, "`%%else: no matching `%%if'");
2820 switch(istk->conds->state) {
2821 case COND_IF_TRUE:
2822 case COND_DONE:
2823 istk->conds->state = COND_ELSE_FALSE;
2824 break;
2826 case COND_NEVER:
2827 break;
2829 case COND_IF_FALSE:
2830 istk->conds->state = COND_ELSE_TRUE;
2831 break;
2833 case COND_ELSE_TRUE:
2834 case COND_ELSE_FALSE:
2835 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2836 "`%%else' after `%%else' ignored.");
2837 istk->conds->state = COND_NEVER;
2838 break;
2840 free_tlist(origline);
2841 return DIRECTIVE_FOUND;
2843 case PP_ENDIF:
2844 if (tline->next)
2845 nasm_error(ERR_WARNING|ERR_PASS1|ERR_PP_PRECOND,
2846 "trailing garbage after `%%endif' ignored");
2847 if (!istk->conds)
2848 nasm_error(ERR_FATAL, "`%%endif': no matching `%%if'");
2849 cond = istk->conds;
2850 istk->conds = cond->next;
2851 nasm_free(cond);
2852 if(istk->mstk)
2853 istk->mstk->condcnt --;
2854 free_tlist(origline);
2855 return DIRECTIVE_FOUND;
2857 case PP_RMACRO:
2858 case PP_IRMACRO:
2859 case PP_MACRO:
2860 case PP_IMACRO:
2861 if (defining) {
2862 nasm_error(ERR_FATAL, "`%s': already defining a macro",
2863 pp_directives[i]);
2864 return DIRECTIVE_FOUND;
2866 defining = nasm_zalloc(sizeof(MMacro));
2867 defining->max_depth =
2868 (i == PP_RMACRO) || (i == PP_IRMACRO) ? DEADMAN_LIMIT : 0;
2869 defining->casesense = (i == PP_MACRO) || (i == PP_RMACRO);
2870 if (!parse_mmacro_spec(tline, defining, pp_directives[i])) {
2871 nasm_free(defining);
2872 defining = NULL;
2873 return DIRECTIVE_FOUND;
2876 src_get(&defining->xline, &defining->fname);
2878 mmac = (MMacro *) hash_findix(&mmacros, defining->name);
2879 while (mmac) {
2880 if (!strcmp(mmac->name, defining->name) &&
2881 (mmac->nparam_min <= defining->nparam_max
2882 || defining->plus)
2883 && (defining->nparam_min <= mmac->nparam_max
2884 || mmac->plus)) {
2885 nasm_error(ERR_WARNING|ERR_PASS1,
2886 "redefining multi-line macro `%s'", defining->name);
2887 return DIRECTIVE_FOUND;
2889 mmac = mmac->next;
2891 free_tlist(origline);
2892 return DIRECTIVE_FOUND;
2894 case PP_ENDM:
2895 case PP_ENDMACRO:
2896 if (! (defining && defining->name)) {
2897 nasm_error(ERR_NONFATAL, "`%s': not defining a macro", tline->text);
2898 return DIRECTIVE_FOUND;
2900 mmhead = (MMacro **) hash_findi_add(&mmacros, defining->name);
2901 defining->next = *mmhead;
2902 *mmhead = defining;
2903 defining = NULL;
2904 free_tlist(origline);
2905 return DIRECTIVE_FOUND;
2907 case PP_EXITMACRO:
2909 * We must search along istk->expansion until we hit a
2910 * macro-end marker for a macro with a name. Then we
2911 * bypass all lines between exitmacro and endmacro.
2913 list_for_each(l, istk->expansion)
2914 if (l->finishes && l->finishes->name)
2915 break;
2917 if (l) {
2919 * Remove all conditional entries relative to this
2920 * macro invocation. (safe to do in this context)
2922 for ( ; l->finishes->condcnt > 0; l->finishes->condcnt --) {
2923 cond = istk->conds;
2924 istk->conds = cond->next;
2925 nasm_free(cond);
2927 istk->expansion = l;
2928 } else {
2929 nasm_error(ERR_NONFATAL, "`%%exitmacro' not within `%%macro' block");
2931 free_tlist(origline);
2932 return DIRECTIVE_FOUND;
2934 case PP_UNMACRO:
2935 case PP_UNIMACRO:
2937 MMacro **mmac_p;
2938 MMacro spec;
2940 spec.casesense = (i == PP_UNMACRO);
2941 if (!parse_mmacro_spec(tline, &spec, pp_directives[i])) {
2942 return DIRECTIVE_FOUND;
2944 mmac_p = (MMacro **) hash_findi(&mmacros, spec.name, NULL);
2945 while (mmac_p && *mmac_p) {
2946 mmac = *mmac_p;
2947 if (mmac->casesense == spec.casesense &&
2948 !mstrcmp(mmac->name, spec.name, spec.casesense) &&
2949 mmac->nparam_min == spec.nparam_min &&
2950 mmac->nparam_max == spec.nparam_max &&
2951 mmac->plus == spec.plus) {
2952 *mmac_p = mmac->next;
2953 free_mmacro(mmac);
2954 } else {
2955 mmac_p = &mmac->next;
2958 free_tlist(origline);
2959 free_tlist(spec.dlist);
2960 return DIRECTIVE_FOUND;
2963 case PP_ROTATE:
2964 if (tline->next && tline->next->type == TOK_WHITESPACE)
2965 tline = tline->next;
2966 if (!tline->next) {
2967 free_tlist(origline);
2968 nasm_error(ERR_NONFATAL, "`%%rotate' missing rotate count");
2969 return DIRECTIVE_FOUND;
2971 t = expand_smacro(tline->next);
2972 tline->next = NULL;
2973 free_tlist(origline);
2974 tline = t;
2975 tptr = &t;
2976 tokval.t_type = TOKEN_INVALID;
2977 evalresult =
2978 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
2979 free_tlist(tline);
2980 if (!evalresult)
2981 return DIRECTIVE_FOUND;
2982 if (tokval.t_type)
2983 nasm_error(ERR_WARNING|ERR_PASS1,
2984 "trailing garbage after expression ignored");
2985 if (!is_simple(evalresult)) {
2986 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rotate'");
2987 return DIRECTIVE_FOUND;
2989 mmac = istk->mstk;
2990 while (mmac && !mmac->name) /* avoid mistaking %reps for macros */
2991 mmac = mmac->next_active;
2992 if (!mmac) {
2993 nasm_error(ERR_NONFATAL, "`%%rotate' invoked outside a macro call");
2994 } else if (mmac->nparam == 0) {
2995 nasm_error(ERR_NONFATAL,
2996 "`%%rotate' invoked within macro without parameters");
2997 } else {
2998 int rotate = mmac->rotate + reloc_value(evalresult);
3000 rotate %= (int)mmac->nparam;
3001 if (rotate < 0)
3002 rotate += mmac->nparam;
3004 mmac->rotate = rotate;
3006 return DIRECTIVE_FOUND;
3008 case PP_REP:
3009 nolist = false;
3010 do {
3011 tline = tline->next;
3012 } while (tok_type_(tline, TOK_WHITESPACE));
3014 if (tok_type_(tline, TOK_ID) &&
3015 nasm_stricmp(tline->text, ".nolist") == 0) {
3016 nolist = true;
3017 do {
3018 tline = tline->next;
3019 } while (tok_type_(tline, TOK_WHITESPACE));
3022 if (tline) {
3023 t = expand_smacro(tline);
3024 tptr = &t;
3025 tokval.t_type = TOKEN_INVALID;
3026 evalresult =
3027 evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3028 if (!evalresult) {
3029 free_tlist(origline);
3030 return DIRECTIVE_FOUND;
3032 if (tokval.t_type)
3033 nasm_error(ERR_WARNING|ERR_PASS1,
3034 "trailing garbage after expression ignored");
3035 if (!is_simple(evalresult)) {
3036 nasm_error(ERR_NONFATAL, "non-constant value given to `%%rep'");
3037 return DIRECTIVE_FOUND;
3039 count = reloc_value(evalresult);
3040 if (count >= REP_LIMIT) {
3041 nasm_error(ERR_NONFATAL, "`%%rep' value exceeds limit");
3042 count = 0;
3043 } else
3044 count++;
3045 } else {
3046 nasm_error(ERR_NONFATAL, "`%%rep' expects a repeat count");
3047 count = 0;
3049 free_tlist(origline);
3051 tmp_defining = defining;
3052 defining = nasm_malloc(sizeof(MMacro));
3053 defining->prev = NULL;
3054 defining->name = NULL; /* flags this macro as a %rep block */
3055 defining->casesense = false;
3056 defining->plus = false;
3057 defining->nolist = nolist;
3058 defining->in_progress = count;
3059 defining->max_depth = 0;
3060 defining->nparam_min = defining->nparam_max = 0;
3061 defining->defaults = NULL;
3062 defining->dlist = NULL;
3063 defining->expansion = NULL;
3064 defining->next_active = istk->mstk;
3065 defining->rep_nest = tmp_defining;
3066 return DIRECTIVE_FOUND;
3068 case PP_ENDREP:
3069 if (!defining || defining->name) {
3070 nasm_error(ERR_NONFATAL, "`%%endrep': no matching `%%rep'");
3071 return DIRECTIVE_FOUND;
3075 * Now we have a "macro" defined - although it has no name
3076 * and we won't be entering it in the hash tables - we must
3077 * push a macro-end marker for it on to istk->expansion.
3078 * After that, it will take care of propagating itself (a
3079 * macro-end marker line for a macro which is really a %rep
3080 * block will cause the macro to be re-expanded, complete
3081 * with another macro-end marker to ensure the process
3082 * continues) until the whole expansion is forcibly removed
3083 * from istk->expansion by a %exitrep.
3085 l = nasm_malloc(sizeof(Line));
3086 l->next = istk->expansion;
3087 l->finishes = defining;
3088 l->first = NULL;
3089 istk->expansion = l;
3091 istk->mstk = defining;
3093 lfmt->uplevel(defining->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
3094 tmp_defining = defining;
3095 defining = defining->rep_nest;
3096 free_tlist(origline);
3097 return DIRECTIVE_FOUND;
3099 case PP_EXITREP:
3101 * We must search along istk->expansion until we hit a
3102 * macro-end marker for a macro with no name. Then we set
3103 * its `in_progress' flag to 0.
3105 list_for_each(l, istk->expansion)
3106 if (l->finishes && !l->finishes->name)
3107 break;
3109 if (l)
3110 l->finishes->in_progress = 1;
3111 else
3112 nasm_error(ERR_NONFATAL, "`%%exitrep' not within `%%rep' block");
3113 free_tlist(origline);
3114 return DIRECTIVE_FOUND;
3116 case PP_XDEFINE:
3117 case PP_IXDEFINE:
3118 case PP_DEFINE:
3119 case PP_IDEFINE:
3120 casesense = (i == PP_DEFINE || i == PP_XDEFINE);
3122 tline = tline->next;
3123 skip_white_(tline);
3124 tline = expand_id(tline);
3125 if (!tline || (tline->type != TOK_ID &&
3126 (tline->type != TOK_PREPROC_ID ||
3127 tline->text[1] != '$'))) {
3128 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3129 pp_directives[i]);
3130 free_tlist(origline);
3131 return DIRECTIVE_FOUND;
3134 ctx = get_ctx(tline->text, &mname);
3135 last = tline;
3136 param_start = tline = tline->next;
3137 nparam = 0;
3139 /* Expand the macro definition now for %xdefine and %ixdefine */
3140 if ((i == PP_XDEFINE) || (i == PP_IXDEFINE))
3141 tline = expand_smacro(tline);
3143 if (tok_is_(tline, "(")) {
3145 * This macro has parameters.
3148 tline = tline->next;
3149 while (1) {
3150 skip_white_(tline);
3151 if (!tline) {
3152 nasm_error(ERR_NONFATAL, "parameter identifier expected");
3153 free_tlist(origline);
3154 return DIRECTIVE_FOUND;
3156 if (tline->type != TOK_ID) {
3157 nasm_error(ERR_NONFATAL,
3158 "`%s': parameter identifier expected",
3159 tline->text);
3160 free_tlist(origline);
3161 return DIRECTIVE_FOUND;
3163 tline->type = TOK_SMAC_PARAM + nparam++;
3164 tline = tline->next;
3165 skip_white_(tline);
3166 if (tok_is_(tline, ",")) {
3167 tline = tline->next;
3168 } else {
3169 if (!tok_is_(tline, ")")) {
3170 nasm_error(ERR_NONFATAL,
3171 "`)' expected to terminate macro template");
3172 free_tlist(origline);
3173 return DIRECTIVE_FOUND;
3175 break;
3178 last = tline;
3179 tline = tline->next;
3181 if (tok_type_(tline, TOK_WHITESPACE))
3182 last = tline, tline = tline->next;
3183 macro_start = NULL;
3184 last->next = NULL;
3185 t = tline;
3186 while (t) {
3187 if (t->type == TOK_ID) {
3188 list_for_each(tt, param_start)
3189 if (tt->type >= TOK_SMAC_PARAM &&
3190 !strcmp(tt->text, t->text))
3191 t->type = tt->type;
3193 tt = t->next;
3194 t->next = macro_start;
3195 macro_start = t;
3196 t = tt;
3199 * Good. We now have a macro name, a parameter count, and a
3200 * token list (in reverse order) for an expansion. We ought
3201 * to be OK just to create an SMacro, store it, and let
3202 * free_tlist have the rest of the line (which we have
3203 * carefully re-terminated after chopping off the expansion
3204 * from the end).
3206 define_smacro(ctx, mname, casesense, nparam, macro_start);
3207 free_tlist(origline);
3208 return DIRECTIVE_FOUND;
3210 case PP_UNDEF:
3211 tline = tline->next;
3212 skip_white_(tline);
3213 tline = expand_id(tline);
3214 if (!tline || (tline->type != TOK_ID &&
3215 (tline->type != TOK_PREPROC_ID ||
3216 tline->text[1] != '$'))) {
3217 nasm_error(ERR_NONFATAL, "`%%undef' expects a macro identifier");
3218 free_tlist(origline);
3219 return DIRECTIVE_FOUND;
3221 if (tline->next) {
3222 nasm_error(ERR_WARNING|ERR_PASS1,
3223 "trailing garbage after macro name ignored");
3226 /* Find the context that symbol belongs to */
3227 ctx = get_ctx(tline->text, &mname);
3228 undef_smacro(ctx, mname);
3229 free_tlist(origline);
3230 return DIRECTIVE_FOUND;
3232 case PP_DEFSTR:
3233 case PP_IDEFSTR:
3234 casesense = (i == PP_DEFSTR);
3236 tline = tline->next;
3237 skip_white_(tline);
3238 tline = expand_id(tline);
3239 if (!tline || (tline->type != TOK_ID &&
3240 (tline->type != TOK_PREPROC_ID ||
3241 tline->text[1] != '$'))) {
3242 nasm_error(ERR_NONFATAL, "`%s' expects a macro identifier",
3243 pp_directives[i]);
3244 free_tlist(origline);
3245 return DIRECTIVE_FOUND;
3248 ctx = get_ctx(tline->text, &mname);
3249 last = tline;
3250 tline = expand_smacro(tline->next);
3251 last->next = NULL;
3253 while (tok_type_(tline, TOK_WHITESPACE))
3254 tline = delete_Token(tline);
3256 p = detoken(tline, false);
3257 macro_start = nasm_malloc(sizeof(*macro_start));
3258 macro_start->next = NULL;
3259 macro_start->text = nasm_quote(p, strlen(p));
3260 macro_start->type = TOK_STRING;
3261 macro_start->a.mac = NULL;
3262 nasm_free(p);
3265 * We now have a macro name, an implicit parameter count of
3266 * zero, and a string token to use as an expansion. Create
3267 * and store an SMacro.
3269 define_smacro(ctx, mname, casesense, 0, macro_start);
3270 free_tlist(origline);
3271 return DIRECTIVE_FOUND;
3273 case PP_DEFTOK:
3274 case PP_IDEFTOK:
3275 casesense = (i == PP_DEFTOK);
3277 tline = tline->next;
3278 skip_white_(tline);
3279 tline = expand_id(tline);
3280 if (!tline || (tline->type != TOK_ID &&
3281 (tline->type != TOK_PREPROC_ID ||
3282 tline->text[1] != '$'))) {
3283 nasm_error(ERR_NONFATAL,
3284 "`%s' expects a macro identifier as first parameter",
3285 pp_directives[i]);
3286 free_tlist(origline);
3287 return DIRECTIVE_FOUND;
3289 ctx = get_ctx(tline->text, &mname);
3290 last = tline;
3291 tline = expand_smacro(tline->next);
3292 last->next = NULL;
3294 t = tline;
3295 while (tok_type_(t, TOK_WHITESPACE))
3296 t = t->next;
3297 /* t should now point to the string */
3298 if (!tok_type_(t, TOK_STRING)) {
3299 nasm_error(ERR_NONFATAL,
3300 "`%s` requires string as second parameter",
3301 pp_directives[i]);
3302 free_tlist(tline);
3303 free_tlist(origline);
3304 return DIRECTIVE_FOUND;
3308 * Convert the string to a token stream. Note that smacros
3309 * are stored with the token stream reversed, so we have to
3310 * reverse the output of tokenize().
3312 nasm_unquote_cstr(t->text, i);
3313 macro_start = reverse_tokens(tokenize(t->text));
3316 * We now have a macro name, an implicit parameter count of
3317 * zero, and a numeric token to use as an expansion. Create
3318 * and store an SMacro.
3320 define_smacro(ctx, mname, casesense, 0, macro_start);
3321 free_tlist(tline);
3322 free_tlist(origline);
3323 return DIRECTIVE_FOUND;
3325 case PP_PATHSEARCH:
3327 const char *found_path;
3329 casesense = true;
3331 tline = tline->next;
3332 skip_white_(tline);
3333 tline = expand_id(tline);
3334 if (!tline || (tline->type != TOK_ID &&
3335 (tline->type != TOK_PREPROC_ID ||
3336 tline->text[1] != '$'))) {
3337 nasm_error(ERR_NONFATAL,
3338 "`%%pathsearch' expects a macro identifier as first parameter");
3339 free_tlist(origline);
3340 return DIRECTIVE_FOUND;
3342 ctx = get_ctx(tline->text, &mname);
3343 last = tline;
3344 tline = expand_smacro(tline->next);
3345 last->next = NULL;
3347 t = tline;
3348 while (tok_type_(t, TOK_WHITESPACE))
3349 t = t->next;
3351 if (!t || (t->type != TOK_STRING &&
3352 t->type != TOK_INTERNAL_STRING)) {
3353 nasm_error(ERR_NONFATAL, "`%%pathsearch' expects a file name");
3354 free_tlist(tline);
3355 free_tlist(origline);
3356 return DIRECTIVE_FOUND; /* but we did _something_ */
3358 if (t->next)
3359 nasm_error(ERR_WARNING|ERR_PASS1,
3360 "trailing garbage after `%%pathsearch' ignored");
3361 p = t->text;
3362 if (t->type != TOK_INTERNAL_STRING)
3363 nasm_unquote(p, NULL);
3365 inc_fopen(p, NULL, &found_path, INC_PROBE, NF_BINARY);
3366 if (!found_path)
3367 found_path = p;
3368 macro_start = nasm_malloc(sizeof(*macro_start));
3369 macro_start->next = NULL;
3370 macro_start->text = nasm_quote(found_path, strlen(found_path));
3371 macro_start->type = TOK_STRING;
3372 macro_start->a.mac = NULL;
3375 * We now have a macro name, an implicit parameter count of
3376 * zero, and a string token to use as an expansion. Create
3377 * and store an SMacro.
3379 define_smacro(ctx, mname, casesense, 0, macro_start);
3380 free_tlist(tline);
3381 free_tlist(origline);
3382 return DIRECTIVE_FOUND;
3385 case PP_STRLEN:
3386 casesense = true;
3388 tline = tline->next;
3389 skip_white_(tline);
3390 tline = expand_id(tline);
3391 if (!tline || (tline->type != TOK_ID &&
3392 (tline->type != TOK_PREPROC_ID ||
3393 tline->text[1] != '$'))) {
3394 nasm_error(ERR_NONFATAL,
3395 "`%%strlen' expects a macro identifier as first parameter");
3396 free_tlist(origline);
3397 return DIRECTIVE_FOUND;
3399 ctx = get_ctx(tline->text, &mname);
3400 last = tline;
3401 tline = expand_smacro(tline->next);
3402 last->next = NULL;
3404 t = tline;
3405 while (tok_type_(t, TOK_WHITESPACE))
3406 t = t->next;
3407 /* t should now point to the string */
3408 if (!tok_type_(t, TOK_STRING)) {
3409 nasm_error(ERR_NONFATAL,
3410 "`%%strlen` requires string as second parameter");
3411 free_tlist(tline);
3412 free_tlist(origline);
3413 return DIRECTIVE_FOUND;
3416 macro_start = nasm_malloc(sizeof(*macro_start));
3417 macro_start->next = NULL;
3418 make_tok_num(macro_start, nasm_unquote(t->text, NULL));
3419 macro_start->a.mac = NULL;
3422 * We now have a macro name, an implicit parameter count of
3423 * zero, and a numeric token to use as an expansion. Create
3424 * and store an SMacro.
3426 define_smacro(ctx, mname, casesense, 0, macro_start);
3427 free_tlist(tline);
3428 free_tlist(origline);
3429 return DIRECTIVE_FOUND;
3431 case PP_STRCAT:
3432 casesense = true;
3434 tline = tline->next;
3435 skip_white_(tline);
3436 tline = expand_id(tline);
3437 if (!tline || (tline->type != TOK_ID &&
3438 (tline->type != TOK_PREPROC_ID ||
3439 tline->text[1] != '$'))) {
3440 nasm_error(ERR_NONFATAL,
3441 "`%%strcat' expects a macro identifier as first parameter");
3442 free_tlist(origline);
3443 return DIRECTIVE_FOUND;
3445 ctx = get_ctx(tline->text, &mname);
3446 last = tline;
3447 tline = expand_smacro(tline->next);
3448 last->next = NULL;
3450 len = 0;
3451 list_for_each(t, tline) {
3452 switch (t->type) {
3453 case TOK_WHITESPACE:
3454 break;
3455 case TOK_STRING:
3456 len += t->a.len = nasm_unquote(t->text, NULL);
3457 break;
3458 case TOK_OTHER:
3459 if (!strcmp(t->text, ",")) /* permit comma separators */
3460 break;
3461 /* else fall through */
3462 default:
3463 nasm_error(ERR_NONFATAL,
3464 "non-string passed to `%%strcat' (%d)", t->type);
3465 free_tlist(tline);
3466 free_tlist(origline);
3467 return DIRECTIVE_FOUND;
3471 p = pp = nasm_malloc(len);
3472 list_for_each(t, tline) {
3473 if (t->type == TOK_STRING) {
3474 memcpy(p, t->text, t->a.len);
3475 p += t->a.len;
3480 * We now have a macro name, an implicit parameter count of
3481 * zero, and a numeric token to use as an expansion. Create
3482 * and store an SMacro.
3484 macro_start = new_Token(NULL, TOK_STRING, NULL, 0);
3485 macro_start->text = nasm_quote(pp, len);
3486 nasm_free(pp);
3487 define_smacro(ctx, mname, casesense, 0, macro_start);
3488 free_tlist(tline);
3489 free_tlist(origline);
3490 return DIRECTIVE_FOUND;
3492 case PP_SUBSTR:
3494 int64_t start, count;
3495 size_t len;
3497 casesense = true;
3499 tline = tline->next;
3500 skip_white_(tline);
3501 tline = expand_id(tline);
3502 if (!tline || (tline->type != TOK_ID &&
3503 (tline->type != TOK_PREPROC_ID ||
3504 tline->text[1] != '$'))) {
3505 nasm_error(ERR_NONFATAL,
3506 "`%%substr' expects a macro identifier as first parameter");
3507 free_tlist(origline);
3508 return DIRECTIVE_FOUND;
3510 ctx = get_ctx(tline->text, &mname);
3511 last = tline;
3512 tline = expand_smacro(tline->next);
3513 last->next = NULL;
3515 if (tline) /* skip expanded id */
3516 t = tline->next;
3517 while (tok_type_(t, TOK_WHITESPACE))
3518 t = t->next;
3520 /* t should now point to the string */
3521 if (!tok_type_(t, TOK_STRING)) {
3522 nasm_error(ERR_NONFATAL,
3523 "`%%substr` requires string as second parameter");
3524 free_tlist(tline);
3525 free_tlist(origline);
3526 return DIRECTIVE_FOUND;
3529 tt = t->next;
3530 tptr = &tt;
3531 tokval.t_type = TOKEN_INVALID;
3532 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3533 if (!evalresult) {
3534 free_tlist(tline);
3535 free_tlist(origline);
3536 return DIRECTIVE_FOUND;
3537 } else if (!is_simple(evalresult)) {
3538 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3539 free_tlist(tline);
3540 free_tlist(origline);
3541 return DIRECTIVE_FOUND;
3543 start = evalresult->value - 1;
3545 while (tok_type_(tt, TOK_WHITESPACE))
3546 tt = tt->next;
3547 if (!tt) {
3548 count = 1; /* Backwards compatibility: one character */
3549 } else {
3550 tokval.t_type = TOKEN_INVALID;
3551 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3552 if (!evalresult) {
3553 free_tlist(tline);
3554 free_tlist(origline);
3555 return DIRECTIVE_FOUND;
3556 } else if (!is_simple(evalresult)) {
3557 nasm_error(ERR_NONFATAL, "non-constant value given to `%%substr`");
3558 free_tlist(tline);
3559 free_tlist(origline);
3560 return DIRECTIVE_FOUND;
3562 count = evalresult->value;
3565 len = nasm_unquote(t->text, NULL);
3567 /* make start and count being in range */
3568 if (start < 0)
3569 start = 0;
3570 if (count < 0)
3571 count = len + count + 1 - start;
3572 if (start + count > (int64_t)len)
3573 count = len - start;
3574 if (!len || count < 0 || start >=(int64_t)len)
3575 start = -1, count = 0; /* empty string */
3577 macro_start = nasm_malloc(sizeof(*macro_start));
3578 macro_start->next = NULL;
3579 macro_start->text = nasm_quote((start < 0) ? "" : t->text + start, count);
3580 macro_start->type = TOK_STRING;
3581 macro_start->a.mac = NULL;
3584 * We now have a macro name, an implicit parameter count of
3585 * zero, and a numeric token to use as an expansion. Create
3586 * and store an SMacro.
3588 define_smacro(ctx, mname, casesense, 0, macro_start);
3589 free_tlist(tline);
3590 free_tlist(origline);
3591 return DIRECTIVE_FOUND;
3594 case PP_ASSIGN:
3595 case PP_IASSIGN:
3596 casesense = (i == PP_ASSIGN);
3598 tline = tline->next;
3599 skip_white_(tline);
3600 tline = expand_id(tline);
3601 if (!tline || (tline->type != TOK_ID &&
3602 (tline->type != TOK_PREPROC_ID ||
3603 tline->text[1] != '$'))) {
3604 nasm_error(ERR_NONFATAL,
3605 "`%%%sassign' expects a macro identifier",
3606 (i == PP_IASSIGN ? "i" : ""));
3607 free_tlist(origline);
3608 return DIRECTIVE_FOUND;
3610 ctx = get_ctx(tline->text, &mname);
3611 last = tline;
3612 tline = expand_smacro(tline->next);
3613 last->next = NULL;
3615 t = tline;
3616 tptr = &t;
3617 tokval.t_type = TOKEN_INVALID;
3618 evalresult = evaluate(ppscan, tptr, &tokval, NULL, pass, NULL);
3619 free_tlist(tline);
3620 if (!evalresult) {
3621 free_tlist(origline);
3622 return DIRECTIVE_FOUND;
3625 if (tokval.t_type)
3626 nasm_error(ERR_WARNING|ERR_PASS1,
3627 "trailing garbage after expression ignored");
3629 if (!is_simple(evalresult)) {
3630 nasm_error(ERR_NONFATAL,
3631 "non-constant value given to `%%%sassign'",
3632 (i == PP_IASSIGN ? "i" : ""));
3633 free_tlist(origline);
3634 return DIRECTIVE_FOUND;
3637 macro_start = nasm_malloc(sizeof(*macro_start));
3638 macro_start->next = NULL;
3639 make_tok_num(macro_start, reloc_value(evalresult));
3640 macro_start->a.mac = NULL;
3643 * We now have a macro name, an implicit parameter count of
3644 * zero, and a numeric token to use as an expansion. Create
3645 * and store an SMacro.
3647 define_smacro(ctx, mname, casesense, 0, macro_start);
3648 free_tlist(origline);
3649 return DIRECTIVE_FOUND;
3651 case PP_LINE:
3653 * Syntax is `%line nnn[+mmm] [filename]'
3655 tline = tline->next;
3656 skip_white_(tline);
3657 if (!tok_type_(tline, TOK_NUMBER)) {
3658 nasm_error(ERR_NONFATAL, "`%%line' expects line number");
3659 free_tlist(origline);
3660 return DIRECTIVE_FOUND;
3662 k = readnum(tline->text, &err);
3663 m = 1;
3664 tline = tline->next;
3665 if (tok_is_(tline, "+")) {
3666 tline = tline->next;
3667 if (!tok_type_(tline, TOK_NUMBER)) {
3668 nasm_error(ERR_NONFATAL, "`%%line' expects line increment");
3669 free_tlist(origline);
3670 return DIRECTIVE_FOUND;
3672 m = readnum(tline->text, &err);
3673 tline = tline->next;
3675 skip_white_(tline);
3676 src_set_linnum(k);
3677 istk->lineinc = m;
3678 if (tline) {
3679 char *fname = detoken(tline, false);
3680 src_set_fname(fname);
3681 nasm_free(fname);
3683 free_tlist(origline);
3684 return DIRECTIVE_FOUND;
3686 default:
3687 nasm_error(ERR_FATAL,
3688 "preprocessor directive `%s' not yet implemented",
3689 pp_directives[i]);
3690 return DIRECTIVE_FOUND;
3695 * Ensure that a macro parameter contains a condition code and
3696 * nothing else. Return the condition code index if so, or -1
3697 * otherwise.
3699 static int find_cc(Token * t)
3701 Token *tt;
3703 if (!t)
3704 return -1; /* Probably a %+ without a space */
3706 skip_white_(t);
3707 if (t->type != TOK_ID)
3708 return -1;
3709 tt = t->next;
3710 skip_white_(tt);
3711 if (tt && (tt->type != TOK_OTHER || strcmp(tt->text, ",")))
3712 return -1;
3714 return bsii(t->text, (const char **)conditions, ARRAY_SIZE(conditions));
3718 * This routines walks over tokens strem and hadnles tokens
3719 * pasting, if @handle_explicit passed then explicit pasting
3720 * term is handled, otherwise -- implicit pastings only.
3722 static bool paste_tokens(Token **head, const struct tokseq_match *m,
3723 size_t mnum, bool handle_explicit)
3725 Token *tok, *next, **prev_next, **prev_nonspace;
3726 bool pasted = false;
3727 char *buf, *p;
3728 size_t len, i;
3731 * The last token before pasting. We need it
3732 * to be able to connect new handled tokens.
3733 * In other words if there were a tokens stream
3735 * A -> B -> C -> D
3737 * and we've joined tokens B and C, the resulting
3738 * stream should be
3740 * A -> BC -> D
3742 tok = *head;
3743 prev_next = NULL;
3745 if (!tok_type_(tok, TOK_WHITESPACE) && !tok_type_(tok, TOK_PASTE))
3746 prev_nonspace = head;
3747 else
3748 prev_nonspace = NULL;
3750 while (tok && (next = tok->next)) {
3752 switch (tok->type) {
3753 case TOK_WHITESPACE:
3754 /* Zap redundant whitespaces */
3755 while (tok_type_(next, TOK_WHITESPACE))
3756 next = delete_Token(next);
3757 tok->next = next;
3758 break;
3760 case TOK_PASTE:
3761 /* Explicit pasting */
3762 if (!handle_explicit)
3763 break;
3764 next = delete_Token(tok);
3766 while (tok_type_(next, TOK_WHITESPACE))
3767 next = delete_Token(next);
3769 if (!pasted)
3770 pasted = true;
3772 /* Left pasting token is start of line */
3773 if (!prev_nonspace)
3774 nasm_error(ERR_FATAL, "No lvalue found on pasting");
3777 * No ending token, this might happen in two
3778 * cases
3780 * 1) There indeed no right token at all
3781 * 2) There is a bare "%define ID" statement,
3782 * and @ID does expand to whitespace.
3784 * So technically we need to do a grammar analysis
3785 * in another stage of parsing, but for now lets don't
3786 * change the behaviour people used to. Simply allow
3787 * whitespace after paste token.
3789 if (!next) {
3791 * Zap ending space tokens and that's all.
3793 tok = (*prev_nonspace)->next;
3794 while (tok_type_(tok, TOK_WHITESPACE))
3795 tok = delete_Token(tok);
3796 tok = *prev_nonspace;
3797 tok->next = NULL;
3798 break;
3801 tok = *prev_nonspace;
3802 while (tok_type_(tok, TOK_WHITESPACE))
3803 tok = delete_Token(tok);
3804 len = strlen(tok->text);
3805 len += strlen(next->text);
3807 p = buf = nasm_malloc(len + 1);
3808 strcpy(p, tok->text);
3809 p = strchr(p, '\0');
3810 strcpy(p, next->text);
3812 delete_Token(tok);
3814 tok = tokenize(buf);
3815 nasm_free(buf);
3817 *prev_nonspace = tok;
3818 while (tok && tok->next)
3819 tok = tok->next;
3821 tok->next = delete_Token(next);
3823 /* Restart from pasted tokens head */
3824 tok = *prev_nonspace;
3825 break;
3827 default:
3828 /* implicit pasting */
3829 for (i = 0; i < mnum; i++) {
3830 if (!(PP_CONCAT_MATCH(tok, m[i].mask_head)))
3831 continue;
3833 len = 0;
3834 while (next && PP_CONCAT_MATCH(next, m[i].mask_tail)) {
3835 len += strlen(next->text);
3836 next = next->next;
3839 /* No match */
3840 if (tok == next)
3841 break;
3843 len += strlen(tok->text);
3844 p = buf = nasm_malloc(len + 1);
3846 while (tok != next) {
3847 strcpy(p, tok->text);
3848 p = strchr(p, '\0');
3849 tok = delete_Token(tok);
3852 tok = tokenize(buf);
3853 nasm_free(buf);
3855 if (prev_next)
3856 *prev_next = tok;
3857 else
3858 *head = tok;
3861 * Connect pasted into original stream,
3862 * ie A -> new-tokens -> B
3864 while (tok && tok->next)
3865 tok = tok->next;
3866 tok->next = next;
3868 if (!pasted)
3869 pasted = true;
3871 /* Restart from pasted tokens head */
3872 tok = prev_next ? *prev_next : *head;
3875 break;
3878 prev_next = &tok->next;
3880 if (tok->next &&
3881 !tok_type_(tok->next, TOK_WHITESPACE) &&
3882 !tok_type_(tok->next, TOK_PASTE))
3883 prev_nonspace = prev_next;
3885 tok = tok->next;
3888 return pasted;
3892 * expands to a list of tokens from %{x:y}
3894 static Token *expand_mmac_params_range(MMacro *mac, Token *tline, Token ***last)
3896 Token *t = tline, **tt, *tm, *head;
3897 char *pos;
3898 int fst, lst, j, i;
3900 pos = strchr(tline->text, ':');
3901 nasm_assert(pos);
3903 lst = atoi(pos + 1);
3904 fst = atoi(tline->text + 1);
3907 * only macros params are accounted so
3908 * if someone passes %0 -- we reject such
3909 * value(s)
3911 if (lst == 0 || fst == 0)
3912 goto err;
3914 /* the values should be sane */
3915 if ((fst > (int)mac->nparam || fst < (-(int)mac->nparam)) ||
3916 (lst > (int)mac->nparam || lst < (-(int)mac->nparam)))
3917 goto err;
3919 fst = fst < 0 ? fst + (int)mac->nparam + 1: fst;
3920 lst = lst < 0 ? lst + (int)mac->nparam + 1: lst;
3922 /* counted from zero */
3923 fst--, lst--;
3926 * It will be at least one token. Note we
3927 * need to scan params until separator, otherwise
3928 * only first token will be passed.
3930 tm = mac->params[(fst + mac->rotate) % mac->nparam];
3931 head = new_Token(NULL, tm->type, tm->text, 0);
3932 tt = &head->next, tm = tm->next;
3933 while (tok_isnt_(tm, ",")) {
3934 t = new_Token(NULL, tm->type, tm->text, 0);
3935 *tt = t, tt = &t->next, tm = tm->next;
3938 if (fst < lst) {
3939 for (i = fst + 1; i <= lst; i++) {
3940 t = new_Token(NULL, TOK_OTHER, ",", 0);
3941 *tt = t, tt = &t->next;
3942 j = (i + mac->rotate) % mac->nparam;
3943 tm = mac->params[j];
3944 while (tok_isnt_(tm, ",")) {
3945 t = new_Token(NULL, tm->type, tm->text, 0);
3946 *tt = t, tt = &t->next, tm = tm->next;
3949 } else {
3950 for (i = fst - 1; i >= lst; i--) {
3951 t = new_Token(NULL, TOK_OTHER, ",", 0);
3952 *tt = t, tt = &t->next;
3953 j = (i + mac->rotate) % mac->nparam;
3954 tm = mac->params[j];
3955 while (tok_isnt_(tm, ",")) {
3956 t = new_Token(NULL, tm->type, tm->text, 0);
3957 *tt = t, tt = &t->next, tm = tm->next;
3962 *last = tt;
3963 return head;
3965 err:
3966 nasm_error(ERR_NONFATAL, "`%%{%s}': macro parameters out of range",
3967 &tline->text[1]);
3968 return tline;
3972 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3973 * %-n) and MMacro-local identifiers (%%foo) as well as
3974 * macro indirection (%[...]) and range (%{..:..}).
3976 static Token *expand_mmac_params(Token * tline)
3978 Token *t, *tt, **tail, *thead;
3979 bool changed = false;
3980 char *pos;
3982 tail = &thead;
3983 thead = NULL;
3985 while (tline) {
3986 if (tline->type == TOK_PREPROC_ID &&
3987 (((tline->text[1] == '+' || tline->text[1] == '-') && tline->text[2]) ||
3988 (tline->text[1] >= '0' && tline->text[1] <= '9') ||
3989 tline->text[1] == '%')) {
3990 char *text = NULL;
3991 int type = 0, cc; /* type = 0 to placate optimisers */
3992 char tmpbuf[30];
3993 unsigned int n;
3994 int i;
3995 MMacro *mac;
3997 t = tline;
3998 tline = tline->next;
4000 mac = istk->mstk;
4001 while (mac && !mac->name) /* avoid mistaking %reps for macros */
4002 mac = mac->next_active;
4003 if (!mac) {
4004 nasm_error(ERR_NONFATAL, "`%s': not in a macro call", t->text);
4005 } else {
4006 pos = strchr(t->text, ':');
4007 if (!pos) {
4008 switch (t->text[1]) {
4010 * We have to make a substitution of one of the
4011 * forms %1, %-1, %+1, %%foo, %0.
4013 case '0':
4014 type = TOK_NUMBER;
4015 snprintf(tmpbuf, sizeof(tmpbuf), "%d", mac->nparam);
4016 text = nasm_strdup(tmpbuf);
4017 break;
4018 case '%':
4019 type = TOK_ID;
4020 snprintf(tmpbuf, sizeof(tmpbuf), "..@%"PRIu64".",
4021 mac->unique);
4022 text = nasm_strcat(tmpbuf, t->text + 2);
4023 break;
4024 case '-':
4025 n = atoi(t->text + 2) - 1;
4026 if (n >= mac->nparam)
4027 tt = NULL;
4028 else {
4029 if (mac->nparam > 1)
4030 n = (n + mac->rotate) % mac->nparam;
4031 tt = mac->params[n];
4033 cc = find_cc(tt);
4034 if (cc == -1) {
4035 nasm_error(ERR_NONFATAL,
4036 "macro parameter %d is not a condition code",
4037 n + 1);
4038 text = NULL;
4039 } else {
4040 type = TOK_ID;
4041 if (inverse_ccs[cc] == -1) {
4042 nasm_error(ERR_NONFATAL,
4043 "condition code `%s' is not invertible",
4044 conditions[cc]);
4045 text = NULL;
4046 } else
4047 text = nasm_strdup(conditions[inverse_ccs[cc]]);
4049 break;
4050 case '+':
4051 n = atoi(t->text + 2) - 1;
4052 if (n >= mac->nparam)
4053 tt = NULL;
4054 else {
4055 if (mac->nparam > 1)
4056 n = (n + mac->rotate) % mac->nparam;
4057 tt = mac->params[n];
4059 cc = find_cc(tt);
4060 if (cc == -1) {
4061 nasm_error(ERR_NONFATAL,
4062 "macro parameter %d is not a condition code",
4063 n + 1);
4064 text = NULL;
4065 } else {
4066 type = TOK_ID;
4067 text = nasm_strdup(conditions[cc]);
4069 break;
4070 default:
4071 n = atoi(t->text + 1) - 1;
4072 if (n >= mac->nparam)
4073 tt = NULL;
4074 else {
4075 if (mac->nparam > 1)
4076 n = (n + mac->rotate) % mac->nparam;
4077 tt = mac->params[n];
4079 if (tt) {
4080 for (i = 0; i < mac->paramlen[n]; i++) {
4081 *tail = new_Token(NULL, tt->type, tt->text, 0);
4082 tail = &(*tail)->next;
4083 tt = tt->next;
4086 text = NULL; /* we've done it here */
4087 break;
4089 } else {
4091 * seems we have a parameters range here
4093 Token *head, **last;
4094 head = expand_mmac_params_range(mac, t, &last);
4095 if (head != t) {
4096 *tail = head;
4097 *last = tline;
4098 tline = head;
4099 text = NULL;
4103 if (!text) {
4104 delete_Token(t);
4105 } else {
4106 *tail = t;
4107 tail = &t->next;
4108 t->type = type;
4109 nasm_free(t->text);
4110 t->text = text;
4111 t->a.mac = NULL;
4113 changed = true;
4114 continue;
4115 } else if (tline->type == TOK_INDIRECT) {
4116 t = tline;
4117 tline = tline->next;
4118 tt = tokenize(t->text);
4119 tt = expand_mmac_params(tt);
4120 tt = expand_smacro(tt);
4121 *tail = tt;
4122 while (tt) {
4123 tt->a.mac = NULL; /* Necessary? */
4124 tail = &tt->next;
4125 tt = tt->next;
4127 delete_Token(t);
4128 changed = true;
4129 } else {
4130 t = *tail = tline;
4131 tline = tline->next;
4132 t->a.mac = NULL;
4133 tail = &t->next;
4136 *tail = NULL;
4138 if (changed) {
4139 const struct tokseq_match t[] = {
4141 PP_CONCAT_MASK(TOK_ID) |
4142 PP_CONCAT_MASK(TOK_FLOAT), /* head */
4143 PP_CONCAT_MASK(TOK_ID) |
4144 PP_CONCAT_MASK(TOK_NUMBER) |
4145 PP_CONCAT_MASK(TOK_FLOAT) |
4146 PP_CONCAT_MASK(TOK_OTHER) /* tail */
4149 PP_CONCAT_MASK(TOK_NUMBER), /* head */
4150 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4153 paste_tokens(&thead, t, ARRAY_SIZE(t), false);
4156 return thead;
4160 * Expand all single-line macro calls made in the given line.
4161 * Return the expanded version of the line. The original is deemed
4162 * to be destroyed in the process. (In reality we'll just move
4163 * Tokens from input to output a lot of the time, rather than
4164 * actually bothering to destroy and replicate.)
4167 static Token *expand_smacro(Token * tline)
4169 Token *t, *tt, *mstart, **tail, *thead;
4170 SMacro *head = NULL, *m;
4171 Token **params;
4172 int *paramsize;
4173 unsigned int nparam, sparam;
4174 int brackets;
4175 Token *org_tline = tline;
4176 Context *ctx;
4177 const char *mname;
4178 int deadman = DEADMAN_LIMIT;
4179 bool expanded;
4182 * Trick: we should avoid changing the start token pointer since it can
4183 * be contained in "next" field of other token. Because of this
4184 * we allocate a copy of first token and work with it; at the end of
4185 * routine we copy it back
4187 if (org_tline) {
4188 tline = new_Token(org_tline->next, org_tline->type,
4189 org_tline->text, 0);
4190 tline->a.mac = org_tline->a.mac;
4191 nasm_free(org_tline->text);
4192 org_tline->text = NULL;
4195 expanded = true; /* Always expand %+ at least once */
4197 again:
4198 thead = NULL;
4199 tail = &thead;
4201 while (tline) { /* main token loop */
4202 if (!--deadman) {
4203 nasm_error(ERR_NONFATAL, "interminable macro recursion");
4204 goto err;
4207 if ((mname = tline->text)) {
4208 /* if this token is a local macro, look in local context */
4209 if (tline->type == TOK_ID) {
4210 head = (SMacro *)hash_findix(&smacros, mname);
4211 } else if (tline->type == TOK_PREPROC_ID) {
4212 ctx = get_ctx(mname, &mname);
4213 head = ctx ? (SMacro *)hash_findix(&ctx->localmac, mname) : NULL;
4214 } else
4215 head = NULL;
4218 * We've hit an identifier. As in is_mmacro below, we first
4219 * check whether the identifier is a single-line macro at
4220 * all, then think about checking for parameters if
4221 * necessary.
4223 list_for_each(m, head)
4224 if (!mstrcmp(m->name, mname, m->casesense))
4225 break;
4226 if (m) {
4227 mstart = tline;
4228 params = NULL;
4229 paramsize = NULL;
4230 if (m->nparam == 0) {
4232 * Simple case: the macro is parameterless. Discard the
4233 * one token that the macro call took, and push the
4234 * expansion back on the to-do stack.
4236 if (!m->expansion) {
4237 if (!strcmp("__FILE__", m->name)) {
4238 const char *file = src_get_fname();
4239 /* nasm_free(tline->text); here? */
4240 tline->text = nasm_quote(file, strlen(file));
4241 tline->type = TOK_STRING;
4242 continue;
4244 if (!strcmp("__LINE__", m->name)) {
4245 nasm_free(tline->text);
4246 make_tok_num(tline, src_get_linnum());
4247 continue;
4249 if (!strcmp("__BITS__", m->name)) {
4250 nasm_free(tline->text);
4251 make_tok_num(tline, globalbits);
4252 continue;
4254 tline = delete_Token(tline);
4255 continue;
4257 } else {
4259 * Complicated case: at least one macro with this name
4260 * exists and takes parameters. We must find the
4261 * parameters in the call, count them, find the SMacro
4262 * that corresponds to that form of the macro call, and
4263 * substitute for the parameters when we expand. What a
4264 * pain.
4266 /*tline = tline->next;
4267 skip_white_(tline); */
4268 do {
4269 t = tline->next;
4270 while (tok_type_(t, TOK_SMAC_END)) {
4271 t->a.mac->in_progress = false;
4272 t->text = NULL;
4273 t = tline->next = delete_Token(t);
4275 tline = t;
4276 } while (tok_type_(tline, TOK_WHITESPACE));
4277 if (!tok_is_(tline, "(")) {
4279 * This macro wasn't called with parameters: ignore
4280 * the call. (Behaviour borrowed from gnu cpp.)
4282 tline = mstart;
4283 m = NULL;
4284 } else {
4285 int paren = 0;
4286 int white = 0;
4287 brackets = 0;
4288 nparam = 0;
4289 sparam = PARAM_DELTA;
4290 params = nasm_malloc(sparam * sizeof(Token *));
4291 params[0] = tline->next;
4292 paramsize = nasm_malloc(sparam * sizeof(int));
4293 paramsize[0] = 0;
4294 while (true) { /* parameter loop */
4296 * For some unusual expansions
4297 * which concatenates function call
4299 t = tline->next;
4300 while (tok_type_(t, TOK_SMAC_END)) {
4301 t->a.mac->in_progress = false;
4302 t->text = NULL;
4303 t = tline->next = delete_Token(t);
4305 tline = t;
4307 if (!tline) {
4308 nasm_error(ERR_NONFATAL,
4309 "macro call expects terminating `)'");
4310 break;
4312 if (tline->type == TOK_WHITESPACE
4313 && brackets <= 0) {
4314 if (paramsize[nparam])
4315 white++;
4316 else
4317 params[nparam] = tline->next;
4318 continue; /* parameter loop */
4320 if (tline->type == TOK_OTHER
4321 && tline->text[1] == 0) {
4322 char ch = tline->text[0];
4323 if (ch == ',' && !paren && brackets <= 0) {
4324 if (++nparam >= sparam) {
4325 sparam += PARAM_DELTA;
4326 params = nasm_realloc(params,
4327 sparam * sizeof(Token *));
4328 paramsize = nasm_realloc(paramsize,
4329 sparam * sizeof(int));
4331 params[nparam] = tline->next;
4332 paramsize[nparam] = 0;
4333 white = 0;
4334 continue; /* parameter loop */
4336 if (ch == '{' &&
4337 (brackets > 0 || (brackets == 0 &&
4338 !paramsize[nparam])))
4340 if (!(brackets++)) {
4341 params[nparam] = tline->next;
4342 continue; /* parameter loop */
4345 if (ch == '}' && brackets > 0)
4346 if (--brackets == 0) {
4347 brackets = -1;
4348 continue; /* parameter loop */
4350 if (ch == '(' && !brackets)
4351 paren++;
4352 if (ch == ')' && brackets <= 0)
4353 if (--paren < 0)
4354 break;
4356 if (brackets < 0) {
4357 brackets = 0;
4358 nasm_error(ERR_NONFATAL, "braces do not "
4359 "enclose all of macro parameter");
4361 paramsize[nparam] += white + 1;
4362 white = 0;
4363 } /* parameter loop */
4364 nparam++;
4365 while (m && (m->nparam != nparam ||
4366 mstrcmp(m->name, mname,
4367 m->casesense)))
4368 m = m->next;
4369 if (!m)
4370 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4371 "macro `%s' exists, "
4372 "but not taking %d parameters",
4373 mstart->text, nparam);
4376 if (m && m->in_progress)
4377 m = NULL;
4378 if (!m) { /* in progess or didn't find '(' or wrong nparam */
4380 * Design question: should we handle !tline, which
4381 * indicates missing ')' here, or expand those
4382 * macros anyway, which requires the (t) test a few
4383 * lines down?
4385 nasm_free(params);
4386 nasm_free(paramsize);
4387 tline = mstart;
4388 } else {
4390 * Expand the macro: we are placed on the last token of the
4391 * call, so that we can easily split the call from the
4392 * following tokens. We also start by pushing an SMAC_END
4393 * token for the cycle removal.
4395 t = tline;
4396 if (t) {
4397 tline = t->next;
4398 t->next = NULL;
4400 tt = new_Token(tline, TOK_SMAC_END, NULL, 0);
4401 tt->a.mac = m;
4402 m->in_progress = true;
4403 tline = tt;
4404 list_for_each(t, m->expansion) {
4405 if (t->type >= TOK_SMAC_PARAM) {
4406 Token *pcopy = tline, **ptail = &pcopy;
4407 Token *ttt, *pt;
4408 int i;
4410 ttt = params[t->type - TOK_SMAC_PARAM];
4411 i = paramsize[t->type - TOK_SMAC_PARAM];
4412 while (--i >= 0) {
4413 pt = *ptail = new_Token(tline, ttt->type,
4414 ttt->text, 0);
4415 ptail = &pt->next;
4416 ttt = ttt->next;
4418 tline = pcopy;
4419 } else if (t->type == TOK_PREPROC_Q) {
4420 tt = new_Token(tline, TOK_ID, mname, 0);
4421 tline = tt;
4422 } else if (t->type == TOK_PREPROC_QQ) {
4423 tt = new_Token(tline, TOK_ID, m->name, 0);
4424 tline = tt;
4425 } else {
4426 tt = new_Token(tline, t->type, t->text, 0);
4427 tline = tt;
4432 * Having done that, get rid of the macro call, and clean
4433 * up the parameters.
4435 nasm_free(params);
4436 nasm_free(paramsize);
4437 free_tlist(mstart);
4438 expanded = true;
4439 continue; /* main token loop */
4444 if (tline->type == TOK_SMAC_END) {
4445 tline->a.mac->in_progress = false;
4446 tline = delete_Token(tline);
4447 } else {
4448 t = *tail = tline;
4449 tline = tline->next;
4450 t->a.mac = NULL;
4451 t->next = NULL;
4452 tail = &t->next;
4457 * Now scan the entire line and look for successive TOK_IDs that resulted
4458 * after expansion (they can't be produced by tokenize()). The successive
4459 * TOK_IDs should be concatenated.
4460 * Also we look for %+ tokens and concatenate the tokens before and after
4461 * them (without white spaces in between).
4463 if (expanded) {
4464 const struct tokseq_match t[] = {
4466 PP_CONCAT_MASK(TOK_ID) |
4467 PP_CONCAT_MASK(TOK_PREPROC_ID), /* head */
4468 PP_CONCAT_MASK(TOK_ID) |
4469 PP_CONCAT_MASK(TOK_PREPROC_ID) |
4470 PP_CONCAT_MASK(TOK_NUMBER) /* tail */
4473 if (paste_tokens(&thead, t, ARRAY_SIZE(t), true)) {
4475 * If we concatenated something, *and* we had previously expanded
4476 * an actual macro, scan the lines again for macros...
4478 tline = thead;
4479 expanded = false;
4480 goto again;
4484 err:
4485 if (org_tline) {
4486 if (thead) {
4487 *org_tline = *thead;
4488 /* since we just gave text to org_line, don't free it */
4489 thead->text = NULL;
4490 delete_Token(thead);
4491 } else {
4492 /* the expression expanded to empty line;
4493 we can't return NULL for some reasons
4494 we just set the line to a single WHITESPACE token. */
4495 memset(org_tline, 0, sizeof(*org_tline));
4496 org_tline->text = NULL;
4497 org_tline->type = TOK_WHITESPACE;
4499 thead = org_tline;
4502 return thead;
4506 * Similar to expand_smacro but used exclusively with macro identifiers
4507 * right before they are fetched in. The reason is that there can be
4508 * identifiers consisting of several subparts. We consider that if there
4509 * are more than one element forming the name, user wants a expansion,
4510 * otherwise it will be left as-is. Example:
4512 * %define %$abc cde
4514 * the identifier %$abc will be left as-is so that the handler for %define
4515 * will suck it and define the corresponding value. Other case:
4517 * %define _%$abc cde
4519 * In this case user wants name to be expanded *before* %define starts
4520 * working, so we'll expand %$abc into something (if it has a value;
4521 * otherwise it will be left as-is) then concatenate all successive
4522 * PP_IDs into one.
4524 static Token *expand_id(Token * tline)
4526 Token *cur, *oldnext = NULL;
4528 if (!tline || !tline->next)
4529 return tline;
4531 cur = tline;
4532 while (cur->next &&
4533 (cur->next->type == TOK_ID ||
4534 cur->next->type == TOK_PREPROC_ID
4535 || cur->next->type == TOK_NUMBER))
4536 cur = cur->next;
4538 /* If identifier consists of just one token, don't expand */
4539 if (cur == tline)
4540 return tline;
4542 if (cur) {
4543 oldnext = cur->next; /* Detach the tail past identifier */
4544 cur->next = NULL; /* so that expand_smacro stops here */
4547 tline = expand_smacro(tline);
4549 if (cur) {
4550 /* expand_smacro possibly changhed tline; re-scan for EOL */
4551 cur = tline;
4552 while (cur && cur->next)
4553 cur = cur->next;
4554 if (cur)
4555 cur->next = oldnext;
4558 return tline;
4562 * Determine whether the given line constitutes a multi-line macro
4563 * call, and return the MMacro structure called if so. Doesn't have
4564 * to check for an initial label - that's taken care of in
4565 * expand_mmacro - but must check numbers of parameters. Guaranteed
4566 * to be called with tline->type == TOK_ID, so the putative macro
4567 * name is easy to find.
4569 static MMacro *is_mmacro(Token * tline, Token *** params_array)
4571 MMacro *head, *m;
4572 Token **params;
4573 int nparam;
4575 head = (MMacro *) hash_findix(&mmacros, tline->text);
4578 * Efficiency: first we see if any macro exists with the given
4579 * name. If not, we can return NULL immediately. _Then_ we
4580 * count the parameters, and then we look further along the
4581 * list if necessary to find the proper MMacro.
4583 list_for_each(m, head)
4584 if (!mstrcmp(m->name, tline->text, m->casesense))
4585 break;
4586 if (!m)
4587 return NULL;
4590 * OK, we have a potential macro. Count and demarcate the
4591 * parameters.
4593 count_mmac_params(tline->next, &nparam, &params);
4596 * So we know how many parameters we've got. Find the MMacro
4597 * structure that handles this number.
4599 while (m) {
4600 if (m->nparam_min <= nparam
4601 && (m->plus || nparam <= m->nparam_max)) {
4603 * This one is right. Just check if cycle removal
4604 * prohibits us using it before we actually celebrate...
4606 if (m->in_progress > m->max_depth) {
4607 if (m->max_depth > 0) {
4608 nasm_error(ERR_WARNING,
4609 "reached maximum recursion depth of %i",
4610 m->max_depth);
4612 nasm_free(params);
4613 return NULL;
4616 * It's right, and we can use it. Add its default
4617 * parameters to the end of our list if necessary.
4619 if (m->defaults && nparam < m->nparam_min + m->ndefs) {
4620 params =
4621 nasm_realloc(params,
4622 ((m->nparam_min + m->ndefs +
4623 1) * sizeof(*params)));
4624 while (nparam < m->nparam_min + m->ndefs) {
4625 params[nparam] = m->defaults[nparam - m->nparam_min];
4626 nparam++;
4630 * If we've gone over the maximum parameter count (and
4631 * we're in Plus mode), ignore parameters beyond
4632 * nparam_max.
4634 if (m->plus && nparam > m->nparam_max)
4635 nparam = m->nparam_max;
4637 * Then terminate the parameter list, and leave.
4639 if (!params) { /* need this special case */
4640 params = nasm_malloc(sizeof(*params));
4641 nparam = 0;
4643 params[nparam] = NULL;
4644 *params_array = params;
4645 return m;
4648 * This one wasn't right: look for the next one with the
4649 * same name.
4651 list_for_each(m, m->next)
4652 if (!mstrcmp(m->name, tline->text, m->casesense))
4653 break;
4657 * After all that, we didn't find one with the right number of
4658 * parameters. Issue a warning, and fail to expand the macro.
4660 nasm_error(ERR_WARNING|ERR_PASS1|ERR_WARN_MNP,
4661 "macro `%s' exists, but not taking %d parameters",
4662 tline->text, nparam);
4663 nasm_free(params);
4664 return NULL;
4669 * Save MMacro invocation specific fields in
4670 * preparation for a recursive macro expansion
4672 static void push_mmacro(MMacro *m)
4674 MMacroInvocation *i;
4676 i = nasm_malloc(sizeof(MMacroInvocation));
4677 i->prev = m->prev;
4678 i->params = m->params;
4679 i->iline = m->iline;
4680 i->nparam = m->nparam;
4681 i->rotate = m->rotate;
4682 i->paramlen = m->paramlen;
4683 i->unique = m->unique;
4684 i->condcnt = m->condcnt;
4685 m->prev = i;
4690 * Restore MMacro invocation specific fields that were
4691 * saved during a previous recursive macro expansion
4693 static void pop_mmacro(MMacro *m)
4695 MMacroInvocation *i;
4697 if (m->prev) {
4698 i = m->prev;
4699 m->prev = i->prev;
4700 m->params = i->params;
4701 m->iline = i->iline;
4702 m->nparam = i->nparam;
4703 m->rotate = i->rotate;
4704 m->paramlen = i->paramlen;
4705 m->unique = i->unique;
4706 m->condcnt = i->condcnt;
4707 nasm_free(i);
4713 * Expand the multi-line macro call made by the given line, if
4714 * there is one to be expanded. If there is, push the expansion on
4715 * istk->expansion and return 1. Otherwise return 0.
4717 static int expand_mmacro(Token * tline)
4719 Token *startline = tline;
4720 Token *label = NULL;
4721 int dont_prepend = 0;
4722 Token **params, *t, *tt;
4723 MMacro *m;
4724 Line *l, *ll;
4725 int i, nparam, *paramlen;
4726 const char *mname;
4728 t = tline;
4729 skip_white_(t);
4730 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4731 if (!tok_type_(t, TOK_ID) && !tok_type_(t, TOK_PREPROC_ID))
4732 return 0;
4733 m = is_mmacro(t, &params);
4734 if (m) {
4735 mname = t->text;
4736 } else {
4737 Token *last;
4739 * We have an id which isn't a macro call. We'll assume
4740 * it might be a label; we'll also check to see if a
4741 * colon follows it. Then, if there's another id after
4742 * that lot, we'll check it again for macro-hood.
4744 label = last = t;
4745 t = t->next;
4746 if (tok_type_(t, TOK_WHITESPACE))
4747 last = t, t = t->next;
4748 if (tok_is_(t, ":")) {
4749 dont_prepend = 1;
4750 last = t, t = t->next;
4751 if (tok_type_(t, TOK_WHITESPACE))
4752 last = t, t = t->next;
4754 if (!tok_type_(t, TOK_ID) || !(m = is_mmacro(t, &params)))
4755 return 0;
4756 last->next = NULL;
4757 mname = t->text;
4758 tline = t;
4762 * Fix up the parameters: this involves stripping leading and
4763 * trailing whitespace, then stripping braces if they are
4764 * present.
4766 for (nparam = 0; params[nparam]; nparam++) ;
4767 paramlen = nparam ? nasm_malloc(nparam * sizeof(*paramlen)) : NULL;
4769 for (i = 0; params[i]; i++) {
4770 int brace = 0;
4771 int comma = (!m->plus || i < nparam - 1);
4773 t = params[i];
4774 skip_white_(t);
4775 if (tok_is_(t, "{"))
4776 t = t->next, brace++, comma = false;
4777 params[i] = t;
4778 paramlen[i] = 0;
4779 while (t) {
4780 if (comma && t->type == TOK_OTHER && !strcmp(t->text, ","))
4781 break; /* ... because we have hit a comma */
4782 if (comma && t->type == TOK_WHITESPACE
4783 && tok_is_(t->next, ","))
4784 break; /* ... or a space then a comma */
4785 if (brace && t->type == TOK_OTHER) {
4786 if (t->text[0] == '{')
4787 brace++; /* ... or a nested opening brace */
4788 else if (t->text[0] == '}')
4789 if (!--brace)
4790 break; /* ... or a brace */
4792 t = t->next;
4793 paramlen[i]++;
4795 if (brace)
4796 nasm_error(ERR_NONFATAL, "macro params should be enclosed in braces");
4800 * OK, we have a MMacro structure together with a set of
4801 * parameters. We must now go through the expansion and push
4802 * copies of each Line on to istk->expansion. Substitution of
4803 * parameter tokens and macro-local tokens doesn't get done
4804 * until the single-line macro substitution process; this is
4805 * because delaying them allows us to change the semantics
4806 * later through %rotate.
4808 * First, push an end marker on to istk->expansion, mark this
4809 * macro as in progress, and set up its invocation-specific
4810 * variables.
4812 ll = nasm_malloc(sizeof(Line));
4813 ll->next = istk->expansion;
4814 ll->finishes = m;
4815 ll->first = NULL;
4816 istk->expansion = ll;
4819 * Save the previous MMacro expansion in the case of
4820 * macro recursion
4822 if (m->max_depth && m->in_progress)
4823 push_mmacro(m);
4825 m->in_progress ++;
4826 m->params = params;
4827 m->iline = tline;
4828 m->nparam = nparam;
4829 m->rotate = 0;
4830 m->paramlen = paramlen;
4831 m->unique = unique++;
4832 m->lineno = 0;
4833 m->condcnt = 0;
4835 m->next_active = istk->mstk;
4836 istk->mstk = m;
4838 list_for_each(l, m->expansion) {
4839 Token **tail;
4841 ll = nasm_malloc(sizeof(Line));
4842 ll->finishes = NULL;
4843 ll->next = istk->expansion;
4844 istk->expansion = ll;
4845 tail = &ll->first;
4847 list_for_each(t, l->first) {
4848 Token *x = t;
4849 switch (t->type) {
4850 case TOK_PREPROC_Q:
4851 tt = *tail = new_Token(NULL, TOK_ID, mname, 0);
4852 break;
4853 case TOK_PREPROC_QQ:
4854 tt = *tail = new_Token(NULL, TOK_ID, m->name, 0);
4855 break;
4856 case TOK_PREPROC_ID:
4857 if (t->text[1] == '0' && t->text[2] == '0') {
4858 dont_prepend = -1;
4859 x = label;
4860 if (!x)
4861 continue;
4863 /* fall through */
4864 default:
4865 tt = *tail = new_Token(NULL, x->type, x->text, 0);
4866 break;
4868 tail = &tt->next;
4870 *tail = NULL;
4874 * If we had a label, push it on as the first line of
4875 * the macro expansion.
4877 if (label) {
4878 if (dont_prepend < 0)
4879 free_tlist(startline);
4880 else {
4881 ll = nasm_malloc(sizeof(Line));
4882 ll->finishes = NULL;
4883 ll->next = istk->expansion;
4884 istk->expansion = ll;
4885 ll->first = startline;
4886 if (!dont_prepend) {
4887 while (label->next)
4888 label = label->next;
4889 label->next = tt = new_Token(NULL, TOK_OTHER, ":", 0);
4894 lfmt->uplevel(m->nolist ? LIST_MACRO_NOLIST : LIST_MACRO);
4896 return 1;
4900 * This function adds macro names to error messages, and suppresses
4901 * them if necessary.
4903 static void pp_verror(int severity, const char *fmt, va_list arg)
4905 char buff[BUFSIZ];
4906 MMacro *mmac = NULL;
4907 int delta = 0;
4910 * If we're in a dead branch of IF or something like it, ignore the error.
4911 * However, because %else etc are evaluated in the state context
4912 * of the previous branch, errors might get lost:
4913 * %if 0 ... %else trailing garbage ... %endif
4914 * So %else etc should set the ERR_PP_PRECOND flag.
4916 if ((severity & ERR_MASK) < ERR_FATAL &&
4917 istk && istk->conds &&
4918 ((severity & ERR_PP_PRECOND) ?
4919 istk->conds->state == COND_NEVER :
4920 !emitting(istk->conds->state)))
4921 return;
4923 /* get %macro name */
4924 if (!(severity & ERR_NOFILE) && istk && istk->mstk) {
4925 mmac = istk->mstk;
4926 /* but %rep blocks should be skipped */
4927 while (mmac && !mmac->name)
4928 mmac = mmac->next_active, delta++;
4931 if (mmac) {
4932 vsnprintf(buff, sizeof(buff), fmt, arg);
4934 nasm_set_verror(real_verror);
4935 nasm_error(severity, "(%s:%d) %s",
4936 mmac->name, mmac->lineno - delta, buff);
4937 nasm_set_verror(pp_verror);
4938 } else {
4939 real_verror(severity, fmt, arg);
4943 static void
4944 pp_reset(char *file, int apass, StrList **deplist)
4946 Token *t;
4948 cstk = NULL;
4949 istk = nasm_malloc(sizeof(Include));
4950 istk->next = NULL;
4951 istk->conds = NULL;
4952 istk->expansion = NULL;
4953 istk->mstk = NULL;
4954 istk->fp = nasm_open_read(file, NF_TEXT);
4955 istk->fname = NULL;
4956 src_set(0, file);
4957 istk->lineinc = 1;
4958 if (!istk->fp)
4959 nasm_fatal(ERR_NOFILE, "unable to open input file `%s'", file);
4960 defining = NULL;
4961 nested_mac_count = 0;
4962 nested_rep_count = 0;
4963 init_macros();
4964 unique = 0;
4966 if (tasm_compatible_mode)
4967 pp_add_stdmac(nasm_stdmac_tasm);
4969 pp_add_stdmac(nasm_stdmac_nasm);
4970 pp_add_stdmac(nasm_stdmac_version);
4972 stdmacpos = stdmacros[0];
4973 stdmacnext = &stdmacros[1];
4975 do_predef = true;
4978 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4979 * The caller, however, will also pass in 3 for preprocess-only so
4980 * we can set __PASS__ accordingly.
4982 pass = apass > 2 ? 2 : apass;
4984 dephead = deplist;
4985 nasm_add_string_to_strlist(dephead, file);
4988 * Define the __PASS__ macro. This is defined here unlike
4989 * all the other builtins, because it is special -- it varies between
4990 * passes.
4992 t = nasm_malloc(sizeof(*t));
4993 t->next = NULL;
4994 make_tok_num(t, apass);
4995 t->a.mac = NULL;
4996 define_smacro(NULL, "__PASS__", true, 0, t);
4999 static void pp_init(void)
5001 hash_init(&FileHash, HASH_MEDIUM);
5004 static char *pp_getline(void)
5006 char *line;
5007 Token *tline;
5009 real_verror = nasm_set_verror(pp_verror);
5011 while (1) {
5013 * Fetch a tokenized line, either from the macro-expansion
5014 * buffer or from the input file.
5016 tline = NULL;
5017 while (istk->expansion && istk->expansion->finishes) {
5018 Line *l = istk->expansion;
5019 if (!l->finishes->name && l->finishes->in_progress > 1) {
5020 Line *ll;
5023 * This is a macro-end marker for a macro with no
5024 * name, which means it's not really a macro at all
5025 * but a %rep block, and the `in_progress' field is
5026 * more than 1, meaning that we still need to
5027 * repeat. (1 means the natural last repetition; 0
5028 * means termination by %exitrep.) We have
5029 * therefore expanded up to the %endrep, and must
5030 * push the whole block on to the expansion buffer
5031 * again. We don't bother to remove the macro-end
5032 * marker: we'd only have to generate another one
5033 * if we did.
5035 l->finishes->in_progress--;
5036 list_for_each(l, l->finishes->expansion) {
5037 Token *t, *tt, **tail;
5039 ll = nasm_malloc(sizeof(Line));
5040 ll->next = istk->expansion;
5041 ll->finishes = NULL;
5042 ll->first = NULL;
5043 tail = &ll->first;
5045 list_for_each(t, l->first) {
5046 if (t->text || t->type == TOK_WHITESPACE) {
5047 tt = *tail = new_Token(NULL, t->type, t->text, 0);
5048 tail = &tt->next;
5052 istk->expansion = ll;
5054 } else {
5056 * Check whether a `%rep' was started and not ended
5057 * within this macro expansion. This can happen and
5058 * should be detected. It's a fatal error because
5059 * I'm too confused to work out how to recover
5060 * sensibly from it.
5062 if (defining) {
5063 if (defining->name)
5064 nasm_panic(0, "defining with name in expansion");
5065 else if (istk->mstk->name)
5066 nasm_fatal(0, "`%%rep' without `%%endrep' within"
5067 " expansion of macro `%s'",
5068 istk->mstk->name);
5072 * FIXME: investigate the relationship at this point between
5073 * istk->mstk and l->finishes
5076 MMacro *m = istk->mstk;
5077 istk->mstk = m->next_active;
5078 if (m->name) {
5080 * This was a real macro call, not a %rep, and
5081 * therefore the parameter information needs to
5082 * be freed.
5084 if (m->prev) {
5085 pop_mmacro(m);
5086 l->finishes->in_progress --;
5087 } else {
5088 nasm_free(m->params);
5089 free_tlist(m->iline);
5090 nasm_free(m->paramlen);
5091 l->finishes->in_progress = 0;
5093 } else
5094 free_mmacro(m);
5096 istk->expansion = l->next;
5097 nasm_free(l);
5098 lfmt->downlevel(LIST_MACRO);
5101 while (1) { /* until we get a line we can use */
5103 if (istk->expansion) { /* from a macro expansion */
5104 char *p;
5105 Line *l = istk->expansion;
5106 if (istk->mstk)
5107 istk->mstk->lineno++;
5108 tline = l->first;
5109 istk->expansion = l->next;
5110 nasm_free(l);
5111 p = detoken(tline, false);
5112 lfmt->line(LIST_MACRO, p);
5113 nasm_free(p);
5114 break;
5116 line = read_line();
5117 if (line) { /* from the current input file */
5118 line = prepreproc(line);
5119 tline = tokenize(line);
5120 nasm_free(line);
5121 break;
5124 * The current file has ended; work down the istk
5127 Include *i = istk;
5128 fclose(i->fp);
5129 if (i->conds) {
5130 /* nasm_error can't be conditionally suppressed */
5131 nasm_fatal(0,
5132 "expected `%%endif' before end of file");
5134 /* only set line and file name if there's a next node */
5135 if (i->next)
5136 src_set(i->lineno, i->fname);
5137 istk = i->next;
5138 lfmt->downlevel(LIST_INCLUDE);
5139 nasm_free(i);
5140 if (!istk) {
5141 line = NULL;
5142 goto done;
5144 if (istk->expansion && istk->expansion->finishes)
5145 break;
5150 * We must expand MMacro parameters and MMacro-local labels
5151 * _before_ we plunge into directive processing, to cope
5152 * with things like `%define something %1' such as STRUC
5153 * uses. Unless we're _defining_ a MMacro, in which case
5154 * those tokens should be left alone to go into the
5155 * definition; and unless we're in a non-emitting
5156 * condition, in which case we don't want to meddle with
5157 * anything.
5159 if (!defining && !(istk->conds && !emitting(istk->conds->state))
5160 && !(istk->mstk && !istk->mstk->in_progress)) {
5161 tline = expand_mmac_params(tline);
5165 * Check the line to see if it's a preprocessor directive.
5167 if (do_directive(tline, &line) == DIRECTIVE_FOUND) {
5168 if (line)
5169 break; /* Directive generated output */
5170 else
5171 continue;
5172 } else if (defining) {
5174 * We're defining a multi-line macro. We emit nothing
5175 * at all, and just
5176 * shove the tokenized line on to the macro definition.
5178 Line *l = nasm_malloc(sizeof(Line));
5179 l->next = defining->expansion;
5180 l->first = tline;
5181 l->finishes = NULL;
5182 defining->expansion = l;
5183 continue;
5184 } else if (istk->conds && !emitting(istk->conds->state)) {
5186 * We're in a non-emitting branch of a condition block.
5187 * Emit nothing at all, not even a blank line: when we
5188 * emerge from the condition we'll give a line-number
5189 * directive so we keep our place correctly.
5191 free_tlist(tline);
5192 continue;
5193 } else if (istk->mstk && !istk->mstk->in_progress) {
5195 * We're in a %rep block which has been terminated, so
5196 * we're walking through to the %endrep without
5197 * emitting anything. Emit nothing at all, not even a
5198 * blank line: when we emerge from the %rep block we'll
5199 * give a line-number directive so we keep our place
5200 * correctly.
5202 free_tlist(tline);
5203 continue;
5204 } else {
5205 tline = expand_smacro(tline);
5206 if (!expand_mmacro(tline)) {
5208 * De-tokenize the line again, and emit it.
5210 line = detoken(tline, true);
5211 free_tlist(tline);
5212 break;
5213 } else {
5214 continue; /* expand_mmacro calls free_tlist */
5219 done:
5220 nasm_set_verror(real_verror);
5221 return line;
5224 static void pp_cleanup(int pass)
5226 real_verror = nasm_set_verror(pp_verror);
5228 if (defining) {
5229 if (defining->name) {
5230 nasm_error(ERR_NONFATAL,
5231 "end of file while still defining macro `%s'",
5232 defining->name);
5233 } else {
5234 nasm_error(ERR_NONFATAL, "end of file while still in %%rep");
5237 free_mmacro(defining);
5238 defining = NULL;
5241 nasm_set_verror(real_verror);
5243 while (cstk)
5244 ctx_pop();
5245 free_macros();
5246 while (istk) {
5247 Include *i = istk;
5248 istk = istk->next;
5249 fclose(i->fp);
5250 nasm_free(i);
5252 while (cstk)
5253 ctx_pop();
5254 src_set_fname(NULL);
5255 if (pass == 0) {
5256 IncPath *i;
5257 free_llist(predef);
5258 predef = NULL;
5259 delete_Blocks();
5260 freeTokens = NULL;
5261 while ((i = ipath)) {
5262 ipath = i->next;
5263 if (i->path)
5264 nasm_free(i->path);
5265 nasm_free(i);
5270 static void pp_include_path(char *path)
5272 IncPath *i;
5274 i = nasm_malloc(sizeof(IncPath));
5275 i->path = path ? nasm_strdup(path) : NULL;
5276 i->next = NULL;
5278 if (ipath) {
5279 IncPath *j = ipath;
5280 while (j->next)
5281 j = j->next;
5282 j->next = i;
5283 } else {
5284 ipath = i;
5288 static void pp_pre_include(char *fname)
5290 Token *inc, *space, *name;
5291 Line *l;
5293 name = new_Token(NULL, TOK_INTERNAL_STRING, fname, 0);
5294 space = new_Token(name, TOK_WHITESPACE, NULL, 0);
5295 inc = new_Token(space, TOK_PREPROC_ID, "%include", 0);
5297 l = nasm_malloc(sizeof(Line));
5298 l->next = predef;
5299 l->first = inc;
5300 l->finishes = NULL;
5301 predef = l;
5304 static void pp_pre_define(char *definition)
5306 Token *def, *space;
5307 Line *l;
5308 char *equals;
5310 real_verror = nasm_set_verror(pp_verror);
5312 equals = strchr(definition, '=');
5313 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5314 def = new_Token(space, TOK_PREPROC_ID, "%define", 0);
5315 if (equals)
5316 *equals = ' ';
5317 space->next = tokenize(definition);
5318 if (equals)
5319 *equals = '=';
5321 if (space->next->type != TOK_PREPROC_ID &&
5322 space->next->type != TOK_ID)
5323 nasm_error(ERR_WARNING, "pre-defining non ID `%s\'\n", definition);
5325 l = nasm_malloc(sizeof(Line));
5326 l->next = predef;
5327 l->first = def;
5328 l->finishes = NULL;
5329 predef = l;
5331 nasm_set_verror(real_verror);
5334 static void pp_pre_undefine(char *definition)
5336 Token *def, *space;
5337 Line *l;
5339 space = new_Token(NULL, TOK_WHITESPACE, NULL, 0);
5340 def = new_Token(space, TOK_PREPROC_ID, "%undef", 0);
5341 space->next = tokenize(definition);
5343 l = nasm_malloc(sizeof(Line));
5344 l->next = predef;
5345 l->first = def;
5346 l->finishes = NULL;
5347 predef = l;
5350 static void pp_add_stdmac(macros_t *macros)
5352 macros_t **mp;
5354 /* Find the end of the list and avoid duplicates */
5355 for (mp = stdmacros; *mp; mp++) {
5356 if (*mp == macros)
5357 return; /* Nothing to do */
5360 nasm_assert(mp < &stdmacros[ARRAY_SIZE(stdmacros)-1]);
5362 *mp = macros;
5365 static void make_tok_num(Token * tok, int64_t val)
5367 char numbuf[32];
5368 snprintf(numbuf, sizeof(numbuf), "%"PRId64"", val);
5369 tok->text = nasm_strdup(numbuf);
5370 tok->type = TOK_NUMBER;
5373 static void pp_list_one_macro(MMacro *m, int severity)
5375 if (!m)
5376 return;
5378 /* We need to print the next_active list in reverse order */
5379 pp_list_one_macro(m->next_active, severity);
5381 if (m->name && !m->nolist) {
5382 src_set(m->xline + m->lineno, m->fname);
5383 nasm_error(severity, "... from macro `%s' defined here", m->name);
5387 static void pp_error_list_macros(int severity)
5389 int32_t saved_line;
5390 const char *saved_fname = NULL;
5392 severity |= ERR_PP_LISTMACRO | ERR_NO_SEVERITY;
5393 src_get(&saved_line, &saved_fname);
5395 if (istk)
5396 pp_list_one_macro(istk->mstk, severity);
5398 src_set(saved_line, saved_fname);
5401 const struct preproc_ops nasmpp = {
5402 pp_init,
5403 pp_reset,
5404 pp_getline,
5405 pp_cleanup,
5406 pp_add_stdmac,
5407 pp_pre_define,
5408 pp_pre_undefine,
5409 pp_pre_include,
5410 pp_include_path,
5411 pp_error_list_macros,