1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2020 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
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
46 * read_line gets raw text from stdmacpos, or predef, or current input file
47 * tokenize converts to tokens
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
80 * Preprocessor execution options that can be controlled by %pragma or
81 * other directives. This structure is initialized to zero on each
82 * pass; this *must* reflect the default initial state.
84 static struct pp_opts
{
86 bool sane_empty_expansion
;
89 typedef struct SMacro SMacro
;
90 typedef struct MMacro MMacro
;
91 typedef struct MMacroInvocation MMacroInvocation
;
92 typedef struct Context Context
;
93 typedef struct Token Token
;
94 typedef struct Line Line
;
95 typedef struct Include Include
;
96 typedef struct Cond Cond
;
99 * This is the internal form which we break input lines up into.
100 * Typically stored in linked lists.
102 * Note that `type' serves a double meaning: TOK_SMAC_START_PARAMS is
103 * not necessarily used as-is, but is also used to encode the number
104 * and expansion type of substituted parameter. So in the definition
106 * %define a(x,=y) ( (x) & ~(y) )
108 * the token representing `x' will have its type changed to
109 * tok_smac_param(0) but the one representing `y' will be
110 * tok_smac_param(1); see the accessor functions below.
112 * TOK_INTERNAL_STRING is a string which has been unquoted, but should
113 * be treated as if it was a quoted string. The code is free to change
114 * one into the other at will. TOK_NAKED_STRING is a text token which
115 * should be treated as a string, but which MUST NOT be turned into a
116 * quoted string. TOK_INTERNAL_STRINGs can contain any character,
117 * including NUL, but TOK_NAKED_STRING must be a valid C string.
120 TOK_NONE
= 0, TOK_WHITESPACE
, TOK_COMMENT
,
121 TOK_CORRUPT
, /* Token text modified in an unsafe manner, now bogus */
122 TOK_BLOCK
, /* Storage block pointer, not a real token */
124 TOK_PREPROC_ID
, TOK_MMACRO_PARAM
, TOK_LOCAL_SYMBOL
,
125 TOK_LOCAL_MACRO
, TOK_ENVIRON
, TOK_STRING
,
126 TOK_NUMBER
, TOK_FLOAT
, TOK_OTHER
,
127 TOK_INTERNAL_STRING
, TOK_NAKED_STRING
,
128 TOK_PREPROC_Q
, TOK_PREPROC_QQ
,
130 TOK_COND_COMMA
, /* %, */
131 TOK_INDIRECT
, /* %[...] */
132 TOK_XDEF_PARAM
, /* Used during %xdefine processing */
133 TOK_SMAC_START_PARAMS
, /* MUST BE LAST IN THE LIST!!! */
134 TOK_MAX
= INT_MAX
/* Keep compiler from reducing the range */
137 static inline enum pp_token_type
tok_smac_param(int param
)
139 return TOK_SMAC_START_PARAMS
+ param
;
141 static int smac_nparam(enum pp_token_type toktype
)
143 return toktype
- TOK_SMAC_START_PARAMS
;
145 static bool is_smac_param(enum pp_token_type toktype
)
147 return toktype
>= TOK_SMAC_START_PARAMS
;
150 #define PP_CONCAT_MASK(x) (1U << (x))
152 struct tokseq_match
{
158 * This is tuned so struct Token should be 64 bytes on 64-bit
159 * systems and 32 bytes on 32-bit systems. It enables them
160 * to be nicely cache aligned, and the text to still be kept
161 * inline for nearly all tokens.
163 * We prohibit tokens of length > MAX_TEXT even though
164 * length here is an unsigned int; this avoids problems
165 * if the length is passed through an interface with type "int",
166 * and is absurdly large anyway.
168 * For the text mode, in pointer mode the pointer is stored at the end
169 * of the union and the pad field is cleared. This allows short tokens
170 * to be unconditionally tested for by only looking at the first text
171 * bytes and not examining the type or len fields.
173 #define INLINE_TEXT (7*sizeof(char *)-sizeof(enum pp_token_type)-sizeof(unsigned int)-1)
174 #define MAX_TEXT (INT_MAX-2)
178 enum pp_token_type type
;
181 char a
[INLINE_TEXT
+1];
183 char pad
[INLINE_TEXT
+1 - sizeof(char *)];
190 * Note on the storage of both SMacro and MMacros: the hash table
191 * indexes them case-insensitively, and we then have to go through a
192 * linked list of potential case aliases (and, for MMacros, parameter
193 * ranges); this is to preserve the matching semantics of the earlier
194 * code. If the number of case aliases for a specific macro is a
195 * performance issue, you may want to reconsider your coding style.
199 * Function call tp obtain the expansion of an smacro
201 typedef Token
*(*ExpandSMacro
)(const SMacro
*s
, Token
**params
, int nparams
);
204 * Store the definition of a single-line macro.
208 SPARM_EVAL
= 1, /* Evaluate as a numeric expression (=) */
209 SPARM_STR
= 2, /* Convert to quoted string ($) */
210 SPARM_NOSTRIP
= 4, /* Don't strip braces (!) */
211 SPARM_GREEDY
= 8 /* Greedy final parameter (+) */
216 enum sparmflags flags
;
220 SMacro
*next
; /* MUST BE FIRST - see free_smacro() */
225 struct smac_param
*params
;
230 bool alias
; /* This is an alias macro */
234 * "No listing" flags. Inside a loop (%rep..%endrep) we may have
235 * macro listing suppressed with .nolist, but we still need to
236 * update line numbers for error messages and debug information...
237 * unless we are nested inside an actual .nolist macro.
240 NL_LIST
= 1, /* Suppress list output */
241 NL_LINE
= 2 /* Don't update line information */
245 * Store the definition of a multi-line macro. This is also used to
246 * store the interiors of `%rep...%endrep' blocks, which are
247 * effectively self-re-invoking multi-line macros which simply
248 * don't have a name or bother to appear in the hash tables. %rep
249 * blocks are signified by having a NULL `name' field.
251 * In a MMacro describing a `%rep' block, the `in_progress' field
252 * isn't merely boolean, but gives the number of repeats left to
255 * The `next' field is used for storing MMacros in hash tables; the
256 * `next_active' field is for stacking them on istk entries.
258 * When a MMacro is being expanded, `params', `iline', `nparam',
259 * `paramlen', `rotate' and `unique' are local to the invocation.
263 * Expansion stack. Note that .mmac can point back to the macro itself,
264 * whereas .mstk cannot.
267 MMacro
*mstk
; /* Any expansion, real macro or not */
268 MMacro
*mmac
; /* Highest level actual mmacro */
274 MMacroInvocation
*prev
; /* previous invocation */
277 int nparam_min
, nparam_max
;
278 enum nolist_flags nolist
; /* is this macro listing-inhibited? */
280 bool plus
; /* is the last parameter greedy? */
281 bool capture_label
; /* macro definition has %00; capture label */
282 int32_t in_progress
; /* is this macro currently being expanded? */
283 int32_t max_depth
; /* maximum number of recursive expansions allowed */
284 Token
*dlist
; /* All defaults as one list */
285 Token
**defaults
; /* Parameter default pointers */
286 int ndefs
; /* number of default parameters */
289 struct mstk mstk
; /* Macro expansion stack */
290 struct mstk dstk
; /* Macro definitions stack */
291 Token
**params
; /* actual parameters */
292 Token
*iline
; /* invocation line */
293 struct src_location where
; /* location of definition */
294 unsigned int nparam
, rotate
;
295 char *iname
; /* name invoked as */
298 uint64_t condcnt
; /* number of if blocks... */
302 /* Store the definition of a multi-line macro, as defined in a
303 * previous recursive macro expansion.
307 struct MMacroInvocation
{
308 MMacroInvocation
*prev
; /* previous invocation */
309 Token
**params
; /* actual parameters */
310 Token
*iline
; /* invocation line */
311 unsigned int nparam
, rotate
;
320 * The context stack is composed of a linked list of these.
325 struct hash_table localmac
;
331 static inline const char *tok_text(const struct Token
*t
)
333 return (t
->len
<= INLINE_TEXT
) ? t
->text
.a
: t
->text
.p
.ptr
;
337 * Returns a mutable pointer to the text buffer. The text can be changed,
338 * but the length MUST NOT CHANGE, in either direction; nor is it permitted
339 * to pad with null characters to create an artificially shorter string.
341 static inline char *tok_text_buf(struct Token
*t
)
343 return (t
->len
<= INLINE_TEXT
) ? t
->text
.a
: t
->text
.p
.ptr
;
346 static inline unsigned int tok_check_len(size_t len
)
348 if (unlikely(len
> MAX_TEXT
))
349 nasm_fatal("impossibly large token");
354 static inline bool tok_text_match(const struct Token
*a
, const struct Token
*b
)
356 return a
->len
== b
->len
&& !memcmp(tok_text(a
), tok_text(b
), a
->len
);
359 static inline unused_func
bool
360 tok_match(const struct Token
*a
, const struct Token
*b
)
362 return a
->type
== b
->type
&& tok_text_match(a
, b
);
365 /* strlen() variant useful for set_text() and its variants */
366 static size_t tok_strlen(const char *str
)
368 return strnlen(str
, MAX_TEXT
+1);
372 * Set the text field to a copy of the given string; the length if
373 * not given should be obtained with tok_strlen().
375 static Token
*set_text(struct Token
*t
, const char *text
, size_t len
)
379 if (t
->len
> INLINE_TEXT
)
380 nasm_free(t
->text
.p
.ptr
);
384 t
->len
= len
= tok_check_len(len
);
385 textp
= (len
> INLINE_TEXT
)
386 ? (t
->text
.p
.ptr
= nasm_malloc(len
+1)) : t
->text
.a
;
387 memcpy(textp
, text
, len
);
393 * Set the text field to the existing pre-allocated string, either
394 * taking over or freeing the allocation in the process.
396 static Token
*set_text_free(struct Token
*t
, char *text
, unsigned int len
)
400 if (t
->len
> INLINE_TEXT
)
401 nasm_free(t
->text
.p
.ptr
);
405 t
->len
= len
= tok_check_len(len
);
406 if (len
> INLINE_TEXT
) {
407 textp
= t
->text
.p
.ptr
= text
;
409 textp
= memcpy(t
->text
.a
, text
, len
);
418 * Allocate a new buffer containing a copy of the text field
421 static char *dup_text(const struct Token
*t
)
423 size_t size
= t
->len
+ 1;
424 char *p
= nasm_malloc(size
);
426 return memcpy(p
, tok_text(t
), size
);
430 * Multi-line macro definitions are stored as a linked list of
431 * these, which is essentially a container to allow several linked
434 * Note that in this module, linked lists are treated as stacks
435 * wherever possible. For this reason, Lines are _pushed_ on to the
436 * `expansion' field in MMacro structures, so that the linked list,
437 * if walked, would give the macro lines in reverse order; this
438 * means that we can walk the list when expanding a macro, and thus
439 * push the lines on to the `expansion' field in _istk_ in reverse
440 * order (so that when popped back off they are in the right
441 * order). It may seem cockeyed, and it relies on my design having
442 * an even number of steps in, but it works...
444 * Some of these structures, rather than being actual lines, are
445 * markers delimiting the end of the expansion of a given macro.
446 * This is for use in the cycle-tracking and %rep-handling code.
447 * Such structures have `finishes' non-NULL, and `first' NULL. All
448 * others have `finishes' NULL, but `first' may still be NULL if
455 struct src_location where
; /* Where defined */
459 * To handle an arbitrary level of file inclusion, we maintain a
460 * stack (ie linked list) of these things.
462 * Note: when we issue a message for a continuation line, we want to
463 * issue it for the actual *start* of the continuation line. This means
464 * we need to remember how many lines to skip over for the next one.
471 uint64_t nolist
; /* Listing inhibit counter */
472 uint64_t noline
; /* Line number update inhibit counter */
474 struct src_location where
; /* Filename and current line number */
475 int32_t lineinc
; /* Increment given by %line */
476 int32_t lineskip
; /* Accounting for passed continuation lines */
480 * File real name hash, so we don't have to re-search the include
481 * path for every pass (and potentially more than that if a file
482 * is used more than once.)
484 struct hash_table FileHash
;
487 * Counters to trap on insane macro recursion or processing.
488 * Note: for smacros these count *down*, for mmacros they count *up*.
491 int64_t total
; /* Total number of macros/tokens */
492 int64_t levels
; /* Descent depth across all macros */
493 bool triggered
; /* Already triggered, no need for error msg */
496 static struct deadman smacro_deadman
, mmacro_deadman
;
499 * Conditional assembly: we maintain a separate stack of these for
500 * each level of file inclusion. (The only reason we keep the
501 * stacks separate is to ensure that a stray `%endif' in a file
502 * included from within the true branch of a `%if' won't terminate
503 * it and cause confusion: instead, rightly, it'll cause an error.)
507 * These states are for use just after %if or %elif: IF_TRUE
508 * means the condition has evaluated to truth so we are
509 * currently emitting, whereas IF_FALSE means we are not
510 * currently emitting but will start doing so if a %else comes
511 * up. In these states, all directives are admissible: %elif,
512 * %else and %endif. (And of course %if.)
514 COND_IF_TRUE
, COND_IF_FALSE
,
516 * These states come up after a %else: ELSE_TRUE means we're
517 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
518 * any %elif or %else will cause an error.
520 COND_ELSE_TRUE
, COND_ELSE_FALSE
,
522 * These states mean that we're not emitting now, and also that
523 * nothing until %endif will be emitted at all. COND_DONE is
524 * used when we've had our moment of emission
525 * and have now started seeing %elifs. COND_NEVER is used when
526 * the condition construct in question is contained within a
527 * non-emitting branch of a larger condition construct,
528 * or if there is an error.
530 COND_DONE
, COND_NEVER
534 enum cond_state state
;
536 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
539 * These defines are used as the possible return values for do_directive
541 #define NO_DIRECTIVE_FOUND 0
542 #define DIRECTIVE_FOUND 1
545 * Condition codes. Note that we use c_ prefix not C_ because C_ is
546 * used in nasm.h for the "real" condition codes. At _this_ level,
547 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
548 * ones, so we need a different enum...
550 static const char * const conditions
[] = {
551 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
552 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
553 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
556 c_A
, c_AE
, c_B
, c_BE
, c_C
, c_CXZ
, c_E
, c_ECXZ
, c_G
, c_GE
, c_L
, c_LE
,
557 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, c_NE
, c_NG
, c_NGE
, c_NL
, c_NLE
, c_NO
,
558 c_NP
, c_NS
, c_NZ
, c_O
, c_P
, c_PE
, c_PO
, c_RCXZ
, c_S
, c_Z
,
561 static const enum pp_conds inverse_ccs
[] = {
562 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, -1, c_NE
, -1, c_NG
, c_NGE
, c_NL
, c_NLE
,
563 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
,
564 c_Z
, c_NO
, c_NP
, c_PO
, c_PE
, -1, c_NS
, c_NZ
570 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
571 static int is_condition(enum preproc_token arg
)
573 return PP_IS_COND(arg
) || (arg
== PP_ELSE
) || (arg
== PP_ENDIF
);
576 /* For TASM compatibility we need to be able to recognise TASM compatible
577 * conditional compilation directives. Using the NASM pre-processor does
578 * not work, so we look for them specifically from the following list and
579 * then jam in the equivalent NASM directive into the input stream.
583 TM_ARG
, TM_ELIF
, TM_ELSE
, TM_ENDIF
, TM_IF
, TM_IFDEF
, TM_IFDIFI
,
584 TM_IFNDEF
, TM_INCLUDE
, TM_LOCAL
587 static const char * const tasm_directives
[] = {
588 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
589 "ifndef", "include", "local"
592 static int StackSize
= 4;
593 static const char *StackPointer
= "ebp";
594 static int ArgOffset
= 8;
595 static int LocalOffset
= 0;
597 static Context
*cstk
;
598 static Include
*istk
;
599 static const struct strlist
*ipath_list
;
601 static struct strlist
*deplist
;
603 static uint64_t unique
; /* unique identifier numbers */
605 static Line
*predef
= NULL
;
606 static bool do_predef
;
607 static enum preproc_mode pp_mode
;
610 * The current set of multi-line macros we have defined.
612 static struct hash_table mmacros
;
615 * The current set of single-line macros we have defined.
617 static struct hash_table smacros
;
620 * The multi-line macro we are currently defining, or the %rep
621 * block we are currently reading, if any.
623 static MMacro
*defining
;
625 static uint64_t nested_mac_count
;
626 static uint64_t nested_rep_count
;
629 * The number of macro parameters to allocate space for at a time.
631 #define PARAM_DELTA 16
634 * The standard macro set: defined in macros.c in a set of arrays.
635 * This gives our position in any macro set, while we are processing it.
636 * The stdmacset is an array of such macro sets.
638 static macros_t
*stdmacpos
;
639 static macros_t
**stdmacnext
;
640 static macros_t
*stdmacros
[8];
641 static macros_t
*extrastdmac
;
644 * Map of which %use packages have been loaded
646 static bool *use_loaded
;
649 * Forward declarations.
651 static void pp_add_stdmac(macros_t
*macros
);
652 static Token
*expand_mmac_params(Token
* tline
);
653 static Token
*expand_smacro(Token
* tline
);
654 static Token
*expand_id(Token
* tline
);
655 static Context
*get_ctx(const char *name
, const char **namep
);
656 static Token
*make_tok_num(Token
*next
, int64_t val
);
657 static Token
*make_tok_qstr(Token
*next
, const char *str
);
658 static Token
*make_tok_qstr_len(Token
*next
, const char *str
, size_t len
);
659 static Token
*make_tok_char(Token
*next
, char op
);
660 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
661 const char *text
, size_t txtlen
);
662 static Token
*new_Token_free(Token
* next
, enum pp_token_type type
,
663 char *text
, size_t txtlen
);
664 static Token
*dup_Token(Token
*next
, const Token
*src
);
665 static Token
*new_White(Token
*next
);
666 static Token
*delete_Token(Token
*t
);
667 static Token
*steal_Token(Token
*dst
, Token
*src
);
668 static const struct use_package
*
669 get_use_pkg(Token
*t
, const char *dname
, const char **name
);
670 static void mark_smac_params(Token
*tline
, const SMacro
*tmpl
,
671 enum pp_token_type type
);
673 /* Safe test for token type, false on x == NULL */
674 static inline bool tok_type(const Token
*x
, enum pp_token_type t
)
676 return x
&& x
->type
== t
;
679 /* Whitespace token? */
680 static inline bool tok_white(const Token
*x
)
682 return tok_type(x
, TOK_WHITESPACE
);
685 /* Skip past any whitespace */
686 static inline Token
*skip_white(Token
*x
)
694 /* Delete any whitespace */
695 static Token
*zap_white(Token
*x
)
704 * Single special character tests. The use of & rather than && is intentional; it
705 * tells the compiler that it is safe to access text.a[1] unconditionally; hopefully
706 * a smart compiler should turn it into a 16-bit memory reference.
708 static inline bool tok_is(const Token
*x
, char c
)
710 return x
&& ((x
->text
.a
[0] == c
) & !x
->text
.a
[1]);
713 /* True if any other kind of token that "c", but not NULL */
714 static inline bool tok_isnt(const Token
*x
, char c
)
716 return x
&& !((x
->text
.a
[0] == c
) & !x
->text
.a
[1]);
720 * Unquote a token if it is a string, and set its type to
721 * TOK_INTERNAL_STRING.
723 static const char *unquote_token(Token
*t
)
725 if (t
->type
!= TOK_STRING
)
728 t
->type
= TOK_INTERNAL_STRING
;
730 if (t
->len
> INLINE_TEXT
) {
731 char *p
= t
->text
.p
.ptr
;
733 t
->len
= nasm_unquote(p
, NULL
);
735 if (t
->len
<= INLINE_TEXT
) {
736 nasm_zero(t
->text
.a
);
737 memcpy(t
->text
.a
, p
, t
->len
);
744 t
->len
= nasm_unquote(t
->text
.a
, NULL
);
750 * Same as unquote_token(), but error out if the resulting string
751 * contains unacceptable control characters.
753 static const char *unquote_token_cstr(Token
*t
)
755 if (t
->type
!= TOK_STRING
)
758 t
->type
= TOK_INTERNAL_STRING
;
760 if (t
->len
> INLINE_TEXT
) {
761 char *p
= t
->text
.p
.ptr
;
763 t
->len
= nasm_unquote_cstr(p
, NULL
);
765 if (t
->len
<= INLINE_TEXT
) {
766 nasm_zero(t
->text
.a
);
767 memcpy(t
->text
.a
, p
, t
->len
);
774 t
->len
= nasm_unquote_cstr(t
->text
.a
, NULL
);
780 * Convert a TOK_INTERNAL_STRING token to a quoted
783 static Token
*quote_any_token(Token
*t
);
784 static inline unused_func
785 Token
*quote_token(Token
*t
)
787 if (likely(!tok_is(t
, TOK_INTERNAL_STRING
)))
790 return quote_any_token(t
);
794 * Convert *any* kind of token to a quoted
797 static Token
*quote_any_token(Token
*t
)
802 p
= nasm_quote(tok_text(t
), &len
);
803 t
->type
= TOK_STRING
;
804 return set_text_free(t
, p
, len
);
808 * In-place reverse a list of tokens.
810 static Token
*reverse_tokens(Token
*t
)
826 * getenv() variant operating on an input token
828 static const char *pp_getenv(const Token
*t
, bool warn
)
830 const char *txt
= tok_text(t
);
833 bool is_string
= false;
840 txt
+= 2; /* Skip leading %! */
841 is_string
= nasm_isquote(*txt
);
848 case TOK_INTERNAL_STRING
:
849 case TOK_NAKED_STRING
:
859 buf
= nasm_strdup(txt
);
860 nasm_unquote_cstr(buf
, NULL
);
867 *!environment [on] nonexistent environment variable
868 *! warns if a nonexistent environment variable
869 *! is accessed using the \c{%!} preprocessor
870 *! construct (see \k{getenv}.) Such environment
871 *! variables are treated as empty (with this
872 *! warning issued) starting in NASM 2.15;
873 *! earlier versions of NASM would treat this as
876 nasm_warn(WARN_ENVIRONMENT
, "nonexistent environment variable `%s'", txt
);
887 * Handle TASM specific directives, which do not contain a % in
888 * front of them. We do it here because I could not find any other
889 * place to do it for the moment, and it is a hack (ideally it would
890 * be nice to be able to use the NASM pre-processor to do it).
892 static char *check_tasm_directive(char *line
)
894 int32_t i
, j
, k
, m
, len
;
895 char *p
, *q
, *oldline
, oldchar
;
897 p
= nasm_skip_spaces(line
);
899 /* Binary search for the directive name */
901 j
= ARRAY_SIZE(tasm_directives
);
902 q
= nasm_skip_word(p
);
909 m
= nasm_stricmp(p
, tasm_directives
[k
]);
911 /* We have found a directive, so jam a % in front of it
912 * so that NASM will then recognise it as one if it's own.
917 line
= nasm_malloc(len
+ 2);
919 if (k
== TM_IFDIFI
) {
921 * NASM does not recognise IFDIFI, so we convert
922 * it to %if 0. This is not used in NASM
923 * compatible code, but does need to parse for the
924 * TASM macro package.
926 strcpy(line
+ 1, "if 0");
928 memcpy(line
+ 1, p
, len
+ 1);
943 * The pre-preprocessing stage... This function translates line
944 * number indications as they emerge from GNU cpp (`# lineno "file"
945 * flags') into NASM preprocessor line number indications (`%line
948 static char *prepreproc(char *line
)
951 char *fname
, *oldline
;
953 if (line
[0] == '#' && line
[1] == ' ') {
956 lineno
= atoi(fname
);
957 fname
+= strspn(fname
, "0123456789 ");
960 fnlen
= strcspn(fname
, "\"");
961 line
= nasm_malloc(20 + fnlen
);
962 snprintf(line
, 20 + fnlen
, "%%line %d %.*s", lineno
, fnlen
, fname
);
965 if (tasm_compatible_mode
)
966 return check_tasm_directive(line
);
971 * Free a linked list of tokens.
973 static void free_tlist(Token
* list
)
976 list
= delete_Token(list
);
980 * Free a linked list of lines.
982 static void free_llist(Line
* list
)
985 list_for_each_safe(l
, tmp
, list
) {
986 free_tlist(l
->first
);
992 * Free an array of linked lists of tokens
994 static void free_tlist_array(Token
**array
, size_t nlists
)
996 Token
**listp
= array
;
999 free_tlist(*listp
++);
1005 * Duplicate a linked list of tokens.
1007 static Token
*dup_tlist(const Token
*list
, Token
***tailp
)
1009 Token
*newlist
= NULL
;
1010 Token
**tailpp
= &newlist
;
1013 list_for_each(t
, list
) {
1015 *tailpp
= nt
= dup_Token(NULL
, t
);
1028 * Duplicate a linked list of tokens with a maximum count
1030 static Token
*dup_tlistn(const Token
*list
, size_t cnt
, Token
***tailp
)
1032 Token
*newlist
= NULL
;
1033 Token
**tailpp
= &newlist
;
1036 list_for_each(t
, list
) {
1040 *tailpp
= nt
= dup_Token(NULL
, t
);
1054 * Duplicate a linked list of tokens in reverse order
1056 static Token
*dup_tlist_reverse(const Token
*list
, Token
*tail
)
1060 list_for_each(t
, list
)
1061 tail
= dup_Token(tail
, t
);
1069 static void free_mmacro(MMacro
* m
)
1072 free_tlist(m
->dlist
);
1073 nasm_free(m
->defaults
);
1074 free_llist(m
->expansion
);
1079 * Clear or free an SMacro
1081 static void free_smacro_members(SMacro
*s
)
1085 for (i
= 0; i
< s
->nparam
; i
++) {
1086 if (s
->params
[i
].name
.len
> INLINE_TEXT
)
1087 nasm_free(s
->params
[i
].name
.text
.p
.ptr
);
1089 nasm_free(s
->params
);
1092 free_tlist(s
->expansion
);
1095 static void clear_smacro(SMacro
*s
)
1097 free_smacro_members(s
);
1098 /* Wipe everything except the next pointer */
1099 memset(&s
->next
+ 1, 0, sizeof *s
- sizeof s
->next
);
1105 static void free_smacro(SMacro
*s
)
1107 free_smacro_members(s
);
1112 * Free all currently defined macros, and free the hash tables if empty
1116 CLEAR_DEFINE
= 1, /* Clear smacros */
1117 CLEAR_DEFALIAS
= 2, /* Clear smacro aliases */
1118 CLEAR_ALLDEFINE
= CLEAR_DEFINE
|CLEAR_DEFALIAS
,
1120 CLEAR_ALL
= CLEAR_ALLDEFINE
|CLEAR_MMACRO
1123 static void clear_smacro_table(struct hash_table
*smt
, enum clear_what what
)
1125 struct hash_iterator it
;
1126 const struct hash_node
*np
;
1130 * Walk the hash table and clear out anything we don't want
1132 hash_for_each(smt
, it
, np
) {
1134 SMacro
*s
= np
->data
;
1135 SMacro
**head
= (SMacro
**)&np
->data
;
1137 list_for_each_safe(s
, tmp
, s
) {
1138 if (what
& ((enum clear_what
)s
->alias
+ 1)) {
1148 * Free the hash table and keys if and only if it is now empty.
1149 * Note: we cannot free keys even for an empty list above, as that
1150 * mucks up the hash algorithm.
1153 hash_free_all(smt
, true);
1156 static void free_smacro_table(struct hash_table
*smt
)
1158 clear_smacro_table(smt
, CLEAR_ALLDEFINE
);
1161 static void free_mmacro_table(struct hash_table
*mmt
)
1163 struct hash_iterator it
;
1164 const struct hash_node
*np
;
1166 hash_for_each(mmt
, it
, np
) {
1168 MMacro
*m
= np
->data
;
1169 nasm_free((void *)np
->key
);
1170 list_for_each_safe(m
, tmp
, m
)
1176 static void free_macros(void)
1178 free_smacro_table(&smacros
);
1179 free_mmacro_table(&mmacros
);
1183 * Initialize the hash tables
1185 static void init_macros(void)
1190 * Pop the context stack.
1192 static void ctx_pop(void)
1197 free_smacro_table(&c
->localmac
);
1198 nasm_free((char *)c
->name
);
1203 * Search for a key in the hash index; adding it if necessary
1204 * (in which case we initialize the data pointer to NULL.)
1207 hash_findi_add(struct hash_table
*hash
, const char *str
)
1209 struct hash_insert hi
;
1212 size_t l
= strlen(str
) + 1;
1214 r
= hash_findib(hash
, str
, l
, &hi
);
1218 strx
= nasm_malloc(l
); /* Use a more efficient allocator here? */
1219 memcpy(strx
, str
, l
);
1220 return hash_add(&hi
, strx
, NULL
);
1224 * Like hash_findi, but returns the data element rather than a pointer
1225 * to it. Used only when not adding a new element, hence no third
1229 hash_findix(struct hash_table
*hash
, const char *str
)
1233 p
= hash_findi(hash
, str
, NULL
);
1234 return p
? *p
: NULL
;
1238 * read line from standart macros set,
1239 * if there no more left -- return NULL
1241 static char *line_from_stdmac(void)
1244 const unsigned char *p
= stdmacpos
;
1252 * 32-126 is ASCII, 127 is end of line, 128-31 are directives
1253 * (allowed to wrap around) corresponding to PP_* tokens 0-159.
1255 while ((c
= *p
++) != 127) {
1256 uint8_t ndir
= c
- 128;
1258 len
+= pp_directives_len
[ndir
] + 1;
1263 line
= nasm_malloc(len
+ 1);
1266 while ((c
= *stdmacpos
++) != 127) {
1267 uint8_t ndir
= c
- 128;
1268 if (ndir
< 256-96) {
1269 memcpy(q
, pp_directives
[ndir
], pp_directives_len
[ndir
]);
1270 q
+= pp_directives_len
[ndir
];
1279 if (*stdmacpos
== 127) {
1280 /* This was the last of this particular macro set */
1283 stdmacpos
= *stdmacnext
++;
1284 } else if (do_predef
) {
1288 * Nasty hack: here we push the contents of
1289 * `predef' on to the top-level expansion stack,
1290 * since this is the most convenient way to
1291 * implement the pre-include and pre-define
1294 list_for_each(pd
, predef
) {
1296 l
->next
= istk
->expansion
;
1297 l
->first
= dup_tlist(pd
->first
, NULL
);
1300 istk
->expansion
= l
;
1310 * Read a line from a file. Return NULL on end of file.
1312 static char *line_from_file(FILE *f
)
1315 unsigned int size
, next
;
1316 const unsigned int delta
= 512;
1317 const unsigned int pad
= 8;
1321 istk
->where
.lineno
+= istk
->lineskip
+ istk
->lineinc
;
1322 src_set_linnum(istk
->where
.lineno
);
1326 p
= buffer
= nasm_malloc(size
);
1359 case 032: /* ^Z = legacy MS-DOS end of file mark */
1366 if (next
== '\r' || next
== '\n') {
1368 istk
->lineskip
+= istk
->lineinc
;
1374 if (p
>= (buffer
+ size
- pad
)) {
1375 buffer
= nasm_realloc(buffer
, size
+ delta
);
1376 p
= buffer
+ size
- pad
;
1387 * Common read routine regardless of source
1389 static char *read_line(void)
1395 line
= line_from_file(f
);
1397 line
= line_from_stdmac();
1403 lfmt
->line(LIST_READ
, istk
->where
.lineno
, line
);
1409 * Tokenize a line of text. This is a very simple process since we
1410 * don't need to parse the value out of e.g. numeric tokens: we
1411 * simply split one string into many.
1413 static Token
*tokenize(const char *line
)
1415 enum pp_token_type type
;
1417 Token
*t
, **tail
= &list
;
1420 const char *p
= line
;
1421 const char *ep
= NULL
; /* End of token, for trimming the end */
1423 char firstchar
= *p
; /* Can be used to override the first char */
1427 * Preprocessor construct; find the end of the token.
1428 * Classification is handled later, because %{...} can be
1429 * used to create any preprocessor token.
1432 if (*p
== '+' && !nasm_isdigit(p
[1])) {
1435 } else if (nasm_isdigit(*p
) ||
1436 ((*p
== '-' || *p
== '+') && nasm_isdigit(p
[1]))) {
1440 while (nasm_isdigit(*p
));
1441 } else if (*p
== '{' || *p
== '[') {
1442 /* %{...} or %[...] */
1443 char firstchar
= *p
;
1444 char endchar
= *p
+ 2; /* } or ] */
1446 line
+= (*p
++ == '{'); /* Skip { but not [ (yet) */
1448 if (*p
== firstchar
) {
1450 } else if (*p
== endchar
) {
1452 } else if (nasm_isquote(*p
)) {
1453 p
= nasm_skip_string(p
);
1457 * *p can have been advanced to a null character by
1458 * nasm_skip_string()
1461 nasm_warn(WARN_OTHER
, "unterminated %%%c construct",
1467 ep
= lvl
? p
: p
-1; /* Terminal character not part of token */
1468 } else if (*p
== '?') {
1473 } else if (*p
== '!') {
1474 /* Environment variable reference */
1476 if (nasm_isidchar(*p
)) {
1480 while (nasm_isidchar(*p
));
1481 } else if (nasm_isquote(*p
)) {
1482 p
= nasm_skip_string(p
);
1486 nasm_nonfatalf(ERR_PASS1
, "unterminated %%! string");
1488 /* %! without anything else... */
1490 } else if (*p
== ',') {
1491 /* Conditional comma */
1493 } else if (nasm_isidchar(*p
) ||
1494 ((*p
== '%' || *p
== '$') && nasm_isidchar(p
[1]))) {
1495 /* Identifier or some sort */
1499 while (nasm_isidchar(*p
));
1500 } else if (*p
== '%') {
1509 /* Classify here, to handle %{...} correctly */
1511 type
= TOK_OTHER
; /* % operator */
1517 type
= (toklen
== 2) ? TOK_PASTE
: TOK_MMACRO_PARAM
;
1521 type
= TOK_MMACRO_PARAM
;
1526 type
= TOK_PREPROC_Q
;
1527 else if (toklen
== 3 && line
[2] == '?')
1528 type
= TOK_PREPROC_QQ
;
1530 type
= TOK_PREPROC_ID
;
1534 type
= (toklen
== 2) ? TOK_OTHER
: TOK_ENVIRON
;
1538 type
= (toklen
== 2) ? TOK_OTHER
: TOK_LOCAL_SYMBOL
;
1542 type
= (toklen
== 2) ? TOK_OTHER
: TOK_LOCAL_MACRO
;
1546 line
+= 2; /* Skip %[ */
1547 firstchar
= *line
; /* Don't clobber */
1549 type
= TOK_INDIRECT
;
1553 type
= (toklen
== 2) ? TOK_COND_COMMA
: TOK_PREPROC_ID
;
1560 type
= TOK_PREPROC_ID
;
1564 type
= TOK_MMACRO_PARAM
; /* %{:..} */
1568 if (nasm_isdigit(c0
))
1569 type
= TOK_MMACRO_PARAM
;
1570 else if (nasm_isidchar(c0
) || toklen
> 2)
1571 type
= TOK_PREPROC_ID
;
1577 } else if (nasm_isidstart(*p
) || (*p
== '$' && nasm_isidstart(p
[1]))) {
1579 * An identifier. This includes the ? operator, which is
1580 * treated as a keyword, not as a special character
1584 while (nasm_isidchar(*++p
))
1586 } else if (nasm_isquote(*p
)) {
1591 p
= nasm_skip_string(p
);
1596 nasm_warn(WARN_OTHER
, "unterminated string");
1597 /* Handling unterminated strings by UNV */
1600 } else if (p
[0] == '$' && p
[1] == '$') {
1601 type
= TOK_OTHER
; /* TOKEN_BASE */
1603 } else if (nasm_isnumstart(*p
)) {
1604 bool is_hex
= false;
1605 bool is_float
= false;
1621 if (!is_hex
&& (c
== 'e' || c
== 'E')) {
1623 if (*p
== '+' || *p
== '-') {
1625 * e can only be followed by +/- if it is either a
1626 * prefixed hex number or a floating-point number
1631 } else if (c
== 'H' || c
== 'h' || c
== 'X' || c
== 'x') {
1633 } else if (c
== 'P' || c
== 'p') {
1635 if (*p
== '+' || *p
== '-')
1637 } else if (nasm_isnumchar(c
))
1638 ; /* just advance */
1639 else if (c
== '.') {
1641 * we need to deal with consequences of the legacy
1642 * parser, like "1.nolist" being two tokens
1643 * (TOK_NUMBER, TOK_ID) here; at least give it
1644 * a shot for now. In the future, we probably need
1645 * a flex-based scanner with proper pattern matching
1646 * to do it as well as it can be done. Nothing in
1647 * the world is going to help the person who wants
1648 * 0x123.p16 interpreted as two tokens, though.
1654 if (nasm_isdigit(*r
) || (is_hex
&& nasm_isxdigit(*r
)) ||
1655 (!is_hex
&& (*r
== 'e' || *r
== 'E')) ||
1656 (*r
== 'p' || *r
== 'P')) {
1660 break; /* Terminate the token */
1664 p
--; /* Point to first character beyond number */
1666 if (p
== line
+1 && *line
== '$') {
1667 type
= TOK_OTHER
; /* TOKEN_HERE */
1669 if (has_e
&& !is_hex
) {
1670 /* 1e13 is floating-point, but 1e13h is not */
1674 type
= is_float
? TOK_FLOAT
: TOK_NUMBER
;
1676 } else if (nasm_isspace(*p
)) {
1677 type
= TOK_WHITESPACE
;
1678 p
= nasm_skip_spaces(p
);
1680 * Whitespace just before end-of-line is discarded by
1681 * pretending it's a comment; whitespace just before a
1682 * comment gets lumped into the comment.
1684 if (!*p
|| *p
== ';') {
1689 } else if (*p
== ';') {
1695 * Anything else is an operator of some kind. We check
1696 * for all the double-character operators (>>, <<, //,
1697 * %%, <=, >=, ==, !=, <>, &&, ||, ^^) and the triple-
1698 * character operators (<<<, >>>, <=>) but anything
1699 * else is a single-character operator.
1708 } else if (*p
== '=') {
1718 } else if (*p
== '=') {
1722 } else if (*p
== '>') {
1737 /* These operators can be doubled but nothing else */
1747 if (type
== TOK_WHITESPACE
) {
1748 *tail
= t
= new_White(NULL
);
1750 } else if (type
!= TOK_COMMENT
) {
1753 *tail
= t
= new_Token(NULL
, type
, line
, ep
- line
);
1754 *tok_text_buf(t
) = firstchar
; /* E.g. %{foo} -> {foo -> %foo */
1763 * Tokens are allocated in blocks to improve speed. Set the blocksize
1764 * to 0 to use regular nasm_malloc(); this is useful for debugging.
1766 * alloc_Token() returns a zero-initialized token structure.
1768 #define TOKEN_BLOCKSIZE 4096
1772 static Token
*freeTokens
= NULL
;
1773 static Token
*tokenblocks
= NULL
;
1775 static Token
*alloc_Token(void)
1777 Token
*t
= freeTokens
;
1783 nasm_newn(block
, TOKEN_BLOCKSIZE
);
1786 * The first entry in each array are a linked list of
1787 * block allocations and is not used for data.
1789 block
[0].next
= tokenblocks
;
1790 block
[0].type
= TOK_BLOCK
;
1791 tokenblocks
= block
;
1794 * Add the rest to the free list
1796 for (i
= 2; i
< TOKEN_BLOCKSIZE
- 1; i
++)
1797 block
[i
].next
= &block
[i
+1];
1799 freeTokens
= &block
[2];
1802 * Return the topmost usable token
1807 freeTokens
= t
->next
;
1812 static Token
*delete_Token(Token
*t
)
1814 Token
*next
= t
->next
;
1817 t
->next
= freeTokens
;
1823 static void delete_Blocks(void)
1825 Token
*block
, *blocktmp
;
1827 list_for_each_safe(block
, blocktmp
, tokenblocks
)
1830 freeTokens
= tokenblocks
= NULL
;
1835 static inline Token
*alloc_Token(void)
1842 static Token
*delete_Token(Token
*t
)
1844 Token
*next
= t
->next
;
1849 static inline void delete_Blocks(void)
1857 * this function creates a new Token and passes a pointer to it
1858 * back to the caller. It sets the type, text, and next pointer elements.
1860 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
1861 const char *text
, size_t txtlen
)
1863 Token
*t
= alloc_Token();
1868 if (type
== TOK_WHITESPACE
) {
1872 if (text
&& text
[0] && !txtlen
)
1873 txtlen
= tok_strlen(text
);
1875 t
->len
= tok_check_len(txtlen
);
1878 textp
= (txtlen
> INLINE_TEXT
)
1879 ? (t
->text
.p
.ptr
= nasm_malloc(txtlen
+1)) : t
->text
.a
;
1880 memcpy(textp
, text
, txtlen
);
1881 textp
[txtlen
] = '\0'; /* In case we needed malloc() */
1884 * Allocate a buffer but do not fill it. The caller
1885 * can fill in text, but must not change the length.
1886 * The filled in text must be exactly txtlen once
1887 * the buffer is filled and before the token is added
1888 * to any line lists.
1890 if (txtlen
> INLINE_TEXT
)
1891 t
->text
.p
.ptr
= nasm_zalloc(txtlen
+1);
1898 * Same as new_Token(), but text belongs to the new token and is
1899 * either taken over or freed. This function MUST be called
1900 * with valid txt and txtlen, unlike new_Token().
1902 static Token
*new_Token_free(Token
* next
, enum pp_token_type type
,
1903 char *text
, size_t txtlen
)
1905 Token
*t
= alloc_Token();
1909 t
->len
= tok_check_len(txtlen
);
1911 if (txtlen
<= INLINE_TEXT
) {
1912 memcpy(t
->text
.a
, text
, txtlen
);
1915 t
->text
.p
.ptr
= text
;
1921 static Token
*dup_Token(Token
*next
, const Token
*src
)
1923 Token
*t
= alloc_Token();
1925 memcpy(t
, src
, sizeof *src
);
1928 if (t
->len
> INLINE_TEXT
) {
1929 t
->text
.p
.ptr
= nasm_malloc(t
->len
+ 1);
1930 memcpy(t
->text
.p
.ptr
, src
->text
.p
.ptr
, t
->len
+1);
1936 static Token
*new_White(Token
*next
)
1938 Token
*t
= alloc_Token();
1941 t
->type
= TOK_WHITESPACE
;
1949 * This *transfers* the content from one token to another, leaving the
1950 * next pointer of the latter intact. Unlike dup_Token(), the old
1951 * token is destroyed, except for its next pointer, and the text
1952 * pointer allocation, if any, is simply transferred.
1954 static Token
*steal_Token(Token
*dst
, Token
*src
)
1956 /* Overwrite everything except the next pointers */
1957 memcpy((char *)dst
+ sizeof(Token
*), (char *)src
+ sizeof(Token
*),
1958 sizeof(Token
) - sizeof(Token
*));
1960 /* Clear the donor token */
1961 memset((char *)src
+ sizeof(Token
*), 0, sizeof(Token
) - sizeof(Token
*));
1967 * Convert a line of tokens back into text. This modifies the list
1968 * by expanding environment variables.
1970 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1971 * are also transformed into ..@ctxnum.xxx
1973 static char *detoken(Token
* tlist
, bool expand_locals
)
1979 list_for_each(t
, tlist
) {
1983 const char *v
= pp_getenv(t
, true);
1984 set_text(t
, v
, tok_strlen(v
));
1985 t
->type
= TOK_NAKED_STRING
;
1989 case TOK_LOCAL_MACRO
:
1990 case TOK_LOCAL_SYMBOL
:
1991 if (expand_locals
) {
1994 Context
*ctx
= get_ctx(tok_text(t
), &q
);
1996 p
= nasm_asprintf("..@%"PRIu64
".%s", ctx
->number
, q
);
1997 set_text_free(t
, p
, nasm_last_string_len());
2004 break; /* No modifications */
2007 if (debug_level(2)) {
2008 unsigned int t_len
= t
->len
;
2009 unsigned int s_len
= tok_strlen(tok_text(t
));
2010 if (t_len
!= s_len
) {
2011 nasm_panic("assertion failed: token \"%s\" type %u len %u has t->len %u\n",
2012 tok_text(t
), t
->type
, s_len
, t_len
);
2020 p
= line
= nasm_malloc(len
+ 1);
2022 list_for_each(t
, tlist
)
2023 p
= mempcpy(p
, tok_text(t
), t
->len
);
2030 * A scanner, suitable for use by the expression evaluator, which
2031 * operates on a line of Tokens. Expects a pointer to a pointer to
2032 * the first token in the line to be passed in as its private_data
2035 * FIX: This really needs to be unified with stdscan.
2042 static int ppscan(void *private_data
, struct tokenval
*tokval
)
2044 struct ppscan
*pps
= private_data
;
2049 if (pps
->ntokens
&& (tline
= pps
->tptr
)) {
2051 pps
->tptr
= tline
->next
;
2055 return tokval
->t_type
= TOKEN_EOS
;
2057 } while (tline
->type
== TOK_WHITESPACE
|| tline
->type
== TOK_COMMENT
);
2059 txt
= tok_text(tline
);
2060 tokval
->t_charptr
= (char *)txt
; /* Fix this */
2062 if (txt
[0] == '$') {
2064 return tokval
->t_type
= TOKEN_HERE
;
2065 } else if (txt
[1] == '$' && !txt
[2]) {
2066 return tokval
->t_type
= TOKEN_BASE
;
2067 } else if (tline
->type
== TOK_ID
) {
2068 tokval
->t_charptr
++;
2069 return tokval
->t_type
= TOKEN_ID
;
2073 switch (tline
->type
) {
2075 if (tline
->len
== 1)
2076 return tokval
->t_type
= txt
[0];
2079 return nasm_token_hash(txt
, tokval
);
2084 tokval
->t_integer
= readnum(txt
, &rn_error
);
2086 return tokval
->t_type
= TOKEN_ERRNUM
;
2088 return tokval
->t_type
= TOKEN_NUM
;
2092 return tokval
->t_type
= TOKEN_FLOAT
;
2095 tokval
->t_charptr
= (char *)unquote_token(tline
);
2096 tokval
->t_inttwo
= tline
->len
;
2097 return tokval
->t_type
= TOKEN_STR
;
2102 * 1. An expression (true if nonzero 0)
2103 * 2. The keywords true, on, yes for true
2104 * 3. The keywords false, off, no for false
2105 * 4. An empty line, for true
2107 * On error, return defval (usually the previous value)
2109 static bool pp_get_boolean_option(Token
*tline
, bool defval
)
2111 static const char * const noyes
[] = {
2117 struct tokenval tokval
;
2120 tline
= skip_white(tline
);
2124 if (tline
->type
== TOK_ID
) {
2126 const char *txt
= tok_text(tline
);
2128 for (i
= 0; i
< ARRAY_SIZE(noyes
); i
++)
2129 if (!nasm_stricmp(txt
, noyes
[i
]))
2136 tokval
.t_type
= TOKEN_INVALID
;
2137 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
2143 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
2144 if (!is_really_simple(evalresult
)) {
2145 nasm_nonfatal("boolean flag expression must be a constant");
2149 return reloc_value(evalresult
) != 0;
2153 * Compare a string to the name of an existing macro; this is a
2154 * simple wrapper which calls either strcmp or nasm_stricmp
2155 * depending on the value of the `casesense' parameter.
2157 static int mstrcmp(const char *p
, const char *q
, bool casesense
)
2159 return casesense
? strcmp(p
, q
) : nasm_stricmp(p
, q
);
2163 * Compare a string to the name of an existing macro; this is a
2164 * simple wrapper which calls either strcmp or nasm_stricmp
2165 * depending on the value of the `casesense' parameter.
2167 static int mmemcmp(const char *p
, const char *q
, size_t l
, bool casesense
)
2169 return casesense
? memcmp(p
, q
, l
) : nasm_memicmp(p
, q
, l
);
2173 * Return the Context structure associated with a %$ token. Return
2174 * NULL, having _already_ reported an error condition, if the
2175 * context stack isn't deep enough for the supplied number of $
2178 * If "namep" is non-NULL, set it to the pointer to the macro name
2179 * tail, i.e. the part beyond %$...
2181 static Context
*get_ctx(const char *name
, const char **namep
)
2189 if (!name
|| name
[0] != '%' || name
[1] != '$')
2193 nasm_nonfatal("`%s': context stack is empty", name
);
2200 while (ctx
&& *name
== '$') {
2206 nasm_nonfatal("`%s': context stack is only"
2207 " %d level%s deep", name
, i
, (i
== 1 ? "" : "s"));
2218 * Open an include file. This routine must always return a valid
2219 * file pointer if it returns - it's responsible for throwing an
2220 * ERR_FATAL and bombing out completely if not. It should also try
2221 * the include path one by one until it finds the file or reaches
2222 * the end of the path.
2224 * Note: for INC_PROBE the function returns NULL at all times;
2225 * instead look for a filename in *slpath.
2228 INC_NEEDED
, /* File must exist */
2229 INC_REQUIRED
, /* File must exist, but only open once/pass */
2230 INC_OPTIONAL
, /* Missing is OK */
2231 INC_PROBE
/* Only an existence probe */
2234 /* This is conducts a full pathname search */
2235 static FILE *inc_fopen_search(const char *file
, char **slpath
,
2236 enum incopen_mode omode
, enum file_flags fmode
)
2238 const struct strlist_entry
*ip
= strlist_head(ipath_list
);
2240 const char *prefix
= "";
2245 sp
= nasm_catfile(prefix
, file
);
2246 if (omode
== INC_PROBE
) {
2248 found
= nasm_file_exists(sp
);
2250 fp
= nasm_open_read(sp
, fmode
);
2251 found
= (fp
!= NULL
);
2271 * Open a file, or test for the presence of one (depending on omode),
2272 * considering the include path.
2274 struct file_hash_entry
{
2276 struct file_hash_entry
*full
; /* Hash entry for the full path */
2277 int64_t include_pass
; /* Pass in which last included (for %require) */
2280 static FILE *inc_fopen(const char *file
,
2281 struct strlist
*dhead
,
2282 const char **found_path
,
2283 enum incopen_mode omode
,
2284 enum file_flags fmode
)
2286 struct file_hash_entry
**fhep
;
2287 struct file_hash_entry
*fhe
= NULL
;
2288 struct hash_insert hi
;
2289 const char *path
= NULL
;
2291 const int64_t pass
= pass_count();
2292 bool skip_open
= (omode
== INC_PROBE
);
2294 fhep
= (struct file_hash_entry
**)hash_find(&FileHash
, file
, &hi
);
2299 skip_open
|= (omode
== INC_REQUIRED
) &&
2300 (fhe
->full
->include_pass
>= pass
);
2303 /* Need to do the actual path search */
2305 fp
= inc_fopen_search(file
, &pptr
, omode
, fmode
);
2308 /* Positive or negative result */
2312 fhe
->full
= fhe
; /* It is *possible*... */
2314 hash_add(&hi
, nasm_strdup(file
), fhe
);
2317 * Add a hash entry for the canonical path if there isn't one
2318 * already. Try to get the unique name from the OS best we can.
2319 * Note that ->path and ->full->path can be different, and that
2320 * is okay (we don't want to print out a full canonical path
2321 * in messages, for example.)
2324 char *fullpath
= nasm_realpath(path
);
2326 if (!strcmp(file
, fullpath
)) {
2327 nasm_free(fullpath
);
2329 struct file_hash_entry
**fullp
, *full
;
2330 fullp
= (struct file_hash_entry
**)
2331 hash_find(&FileHash
, fullpath
, &hi
);
2335 nasm_free(fullpath
);
2338 full
->path
= fullpath
;
2340 hash_add(&hi
, path
, full
);
2347 * Add file to dependency path.
2349 strlist_add(dhead
, path
? path
: file
);
2352 if (path
&& !fp
&& omode
!= INC_PROBE
)
2353 fp
= nasm_open_read(path
, fmode
);
2355 if (omode
< INC_OPTIONAL
&& !fp
) {
2359 nasm_nonfatal("unable to open include file `%s': %s",
2360 file
, strerror(errno
));
2364 fhe
->full
->include_pass
= pass
;
2373 * Opens an include or input file. Public version, for use by modules
2374 * that get a file:lineno pair and need to look at the file again
2375 * (e.g. the CodeView debug backend). Returns NULL on failure.
2377 FILE *pp_input_fopen(const char *filename
, enum file_flags mode
)
2379 return inc_fopen(filename
, NULL
, NULL
, INC_OPTIONAL
, mode
);
2383 * Determine if we should warn on defining a single-line macro of
2384 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
2385 * return true if _any_ single-line macro of that name is defined.
2386 * Otherwise, will return true if a single-line macro with either
2387 * `nparam' or no parameters is defined.
2389 * If a macro with precisely the right number of parameters is
2390 * defined, or nparam is -1, the address of the definition structure
2391 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
2392 * is NULL, no action will be taken regarding its contents, and no
2395 * Note that this is also called with nparam zero to resolve
2399 smacro_defined(Context
*ctx
, const char *name
, int nparam
, SMacro
**defn
,
2400 bool nocase
, bool find_alias
)
2402 struct hash_table
*smtbl
;
2405 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
2408 m
= (SMacro
*) hash_findix(smtbl
, name
);
2411 if (!mstrcmp(m
->name
, name
, m
->casesense
&& nocase
) &&
2412 (nparam
<= 0 || m
->nparam
== 0 || nparam
== m
->nparam
||
2413 (m
->greedy
&& nparam
>= m
->nparam
-1))) {
2414 if (m
->alias
&& !find_alias
) {
2415 if (!ppopt
.noaliases
) {
2416 name
= tok_text(m
->expansion
);
2423 *defn
= (nparam
== m
->nparam
|| nparam
== -1) ? m
: NULL
;
2433 /* param should be a natural number [0; INT_MAX] */
2434 static int read_param_count(const char *str
)
2439 result
= readnum(str
, &err
);
2440 if (result
< 0 || result
> INT_MAX
) {
2442 nasm_nonfatal("parameter count `%s' is out of bounds [%d; %d]",
2445 nasm_nonfatal("unable to parse parameter count `%s'", str
);
2450 * Count and mark off the parameters in a multi-line macro call.
2451 * This is called both from within the multi-line macro expansion
2452 * code, and also to mark off the default parameters when provided
2453 * in a %macro definition line.
2455 * Note that we need space in the params array for parameter 0 being
2456 * a possible captured label as well as the final NULL.
2458 * Returns a pointer to the pointer to a terminal comma if present;
2459 * used to drop an empty terminal argument for legacy reasons.
2461 static Token
**count_mmac_params(Token
*tline
, int *nparamp
, Token
***paramsp
)
2466 Token
**comma
= NULL
, **maybe_comma
= NULL
;
2469 paramsize
= PARAM_DELTA
;
2470 nasm_newn(params
, paramsize
);
2472 t
= skip_white(tline
);
2475 /* Need two slots for captured label and NULL */
2476 if (unlikely(nparam
+2 >= paramsize
)) {
2477 paramsize
+= PARAM_DELTA
;
2478 params
= nasm_realloc(params
, sizeof(*params
) * paramsize
);
2480 params
[++nparam
] = t
;
2481 if (tok_is(t
, '{')) {
2484 comma
= NULL
; /* Non-empty parameter */
2486 while (brace
&& (t
= t
->next
)) {
2487 brace
+= tok_is(t
, '{');
2488 brace
-= tok_is(t
, '}');
2493 * Now we've found the closing brace, look further
2496 t
= skip_white(t
->next
);
2497 if (tok_isnt(t
, ','))
2498 nasm_nonfatal("braces do not enclose all of macro parameter");
2500 nasm_nonfatal("expecting closing brace in macro parameter");
2504 /* Advance to the next comma */
2505 maybe_comma
= &t
->next
;
2506 while (tok_isnt(t
, ',')) {
2508 comma
= NULL
; /* Non-empty parameter */
2509 maybe_comma
= &t
->next
;
2514 break; /* End of string, no comma */
2516 comma
= maybe_comma
; /* Point to comma pointer */
2517 t
= skip_white(t
->next
); /* Eat the comma and whitespace */
2521 params
[nparam
+1] = NULL
;
2529 * Determine whether one of the various `if' conditions is true or
2532 * We must free the tline we get passed.
2534 static enum cond_state
if_condition(Token
* tline
, enum preproc_token ct
)
2537 Token
*t
, *tt
, *origline
;
2539 struct tokenval tokval
;
2541 enum pp_token_type needtype
;
2542 const char *dname
= pp_directives
[ct
];
2543 bool casesense
= true;
2544 enum preproc_token cond
= PP_COND(ct
);
2550 j
= false; /* have we matched yet? */
2552 tline
= skip_white(tline
);
2555 if (tline
->type
!= TOK_ID
) {
2556 nasm_nonfatal("`%s' expects context identifiers",
2560 if (cstk
&& cstk
->name
&& !nasm_stricmp(tok_text(tline
), cstk
->name
))
2562 tline
= tline
->next
;
2569 bool alias
= cond
== PP_IFDEFALIAS
;
2574 j
= false; /* have we matched yet? */
2576 tline
= skip_white(tline
);
2577 if (!tline
|| (tline
->type
!= TOK_ID
&&
2578 tline
->type
!= TOK_LOCAL_MACRO
)) {
2579 nasm_nonfatal("`%s' expects macro identifiers",
2584 mname
= tok_text(tline
);
2585 ctx
= get_ctx(mname
, &mname
);
2586 if (smacro_defined(ctx
, mname
, -1, &smac
, true, alias
) && smac
2587 && smac
->alias
== alias
) {
2591 tline
= tline
->next
;
2597 tline
= expand_smacro(tline
);
2598 j
= false; /* have we matched yet? */
2600 tline
= skip_white(tline
);
2601 if (!tline
|| (tline
->type
!= TOK_ID
&&
2602 tline
->type
!= TOK_STRING
&&
2603 tline
->type
!= TOK_INTERNAL_STRING
&&
2604 tline
->type
!= TOK_ENVIRON
)) {
2605 nasm_nonfatal("`%s' expects environment variable names",
2610 j
|= !!pp_getenv(tline
, false);
2611 tline
= tline
->next
;
2619 tline
= expand_smacro(tline
);
2621 while (tok_isnt(tt
, ','))
2624 nasm_nonfatal("`%s' expects two comma-separated arguments",
2629 j
= true; /* assume equality unless proved not */
2630 while (tok_isnt(t
, ',') && tt
) {
2631 unsigned int l1
, l2
;
2632 const char *t1
, *t2
;
2634 if (tok_is(tt
, ',')) {
2635 nasm_nonfatal("`%s': more than one comma on line",
2639 if (t
->type
== TOK_WHITESPACE
) {
2643 if (tt
->type
== TOK_WHITESPACE
) {
2647 if (tt
->type
!= t
->type
) {
2648 j
= false; /* found mismatching tokens */
2652 t1
= unquote_token(t
);
2653 t2
= unquote_token(tt
);
2657 if (l1
!= l2
|| mmemcmp(t1
, t2
, l1
, casesense
)) {
2665 if (!tok_is(t
, ',') || tt
)
2666 j
= false; /* trailing gunk on one end or other */
2672 MMacro searching
, *mmac
;
2674 tline
= skip_white(tline
);
2675 tline
= expand_id(tline
);
2676 if (!tok_type(tline
, TOK_ID
)) {
2677 nasm_nonfatal("`%s' expects a macro name", dname
);
2680 nasm_zero(searching
);
2681 searching
.name
= dup_text(tline
);
2682 searching
.casesense
= true;
2683 searching
.nparam_min
= 0;
2684 searching
.nparam_max
= INT_MAX
;
2685 tline
= expand_smacro(tline
->next
);
2686 tline
= skip_white(tline
);
2688 } else if (!tok_type(tline
, TOK_NUMBER
)) {
2689 nasm_nonfatal("`%s' expects a parameter count or nothing",
2692 searching
.nparam_min
= searching
.nparam_max
=
2693 read_param_count(tok_text(tline
));
2695 if (tline
&& tok_is(tline
->next
, '-')) {
2696 tline
= tline
->next
->next
;
2697 if (tok_is(tline
, '*'))
2698 searching
.nparam_max
= INT_MAX
;
2699 else if (!tok_type(tline
, TOK_NUMBER
))
2700 nasm_nonfatal("`%s' expects a parameter count after `-'",
2703 searching
.nparam_max
= read_param_count(tok_text(tline
));
2704 if (searching
.nparam_min
> searching
.nparam_max
) {
2705 nasm_nonfatal("minimum parameter count exceeds maximum");
2706 searching
.nparam_max
= searching
.nparam_min
;
2710 if (tline
&& tok_is(tline
->next
, '+')) {
2711 tline
= tline
->next
;
2712 searching
.plus
= true;
2714 mmac
= (MMacro
*) hash_findix(&mmacros
, searching
.name
);
2716 if (!strcmp(mmac
->name
, searching
.name
) &&
2717 (mmac
->nparam_min
<= searching
.nparam_max
2719 && (searching
.nparam_min
<= mmac
->nparam_max
2726 if (tline
&& tline
->next
)
2727 nasm_warn(WARN_OTHER
, "trailing garbage after %%ifmacro ignored");
2728 nasm_free(searching
.name
);
2737 needtype
= TOK_NUMBER
;
2740 needtype
= TOK_STRING
;
2744 t
= tline
= expand_smacro(tline
);
2746 while (tok_white(t
) ||
2747 (needtype
== TOK_NUMBER
&& (tok_is(t
, '-') | tok_is(t
, '+'))))
2750 j
= tok_type(t
, needtype
);
2754 tline
= expand_smacro(tline
);
2755 t
= skip_white(tline
);
2759 t
= skip_white(t
->next
); /* Skip the actual token + whitespace */
2765 tline
= expand_smacro(tline
);
2766 t
= skip_white(tline
);
2767 j
= !t
; /* Should be empty */
2771 pps
.tptr
= tline
= expand_smacro(tline
);
2773 tokval
.t_type
= TOKEN_INVALID
;
2774 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
2778 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
2779 if (!is_simple(evalresult
)) {
2780 nasm_nonfatal("non-constant value given to `%s'",
2784 j
= reloc_value(evalresult
) != 0;
2790 const struct use_package
*pkg
;
2793 pkg
= get_use_pkg(tline
, dname
, &name
);
2797 j
= pkg
&& ((cond
== PP_IFUSABLE
) | use_loaded
[pkg
->index
]);
2802 nasm_nonfatal("unknown preprocessor directive `%s'", dname
);
2806 free_tlist(origline
);
2807 return (j
^ PP_COND_NEGATIVE(ct
)) ? COND_IF_TRUE
: COND_IF_FALSE
;
2810 free_tlist(origline
);
2815 * Default smacro expansion routine: just returns a copy of the
2819 smacro_expand_default(const SMacro
*s
, Token
**params
, int nparams
)
2824 return dup_tlist(s
->expansion
, NULL
);
2828 * Emit a macro defintion or undef to the listing file, if
2829 * desired. This is similar to detoken(), but it handles the reverse
2830 * expansion list, does not expand %! or local variable tokens, and
2831 * does some special handling for macro parameters.
2834 list_smacro_def(enum preproc_token op
, const Context
*ctx
, const SMacro
*m
)
2837 size_t namelen
, size
;
2839 char *context_prefix
= NULL
;
2842 namelen
= strlen(m
->name
);
2843 size
= namelen
+ 2; /* Include room for space after name + NUL */
2846 int context_depth
= cstk
->depth
- ctx
->depth
+ 1;
2848 nasm_asprintf("[%s::%"PRIu64
"] %%%-*s",
2849 ctx
->name
? ctx
->name
: "",
2850 ctx
->number
, context_depth
, "");
2852 context_len
= nasm_last_string_len();
2853 memset(context_prefix
+ context_len
- context_depth
,
2854 '$', context_depth
);
2855 size
+= context_len
;
2858 list_for_each(t
, m
->expansion
)
2863 * Space for ( and either , or ) around each
2864 * parameter, plus up to 4 flags.
2868 size
+= 1 + 4 * m
->nparam
;
2869 for (i
= 0; i
< m
->nparam
; i
++)
2870 size
+= m
->params
[i
].name
.len
;
2873 def
= nasm_malloc(size
);
2877 list_for_each(t
, m
->expansion
) {
2879 memcpy(p
, tok_text(t
), t
->len
);
2888 for (i
= m
->nparam
-1; i
>= 0; i
--) {
2889 enum sparmflags flags
= m
->params
[i
].flags
;
2890 if (flags
& SPARM_GREEDY
)
2892 p
-= m
->params
[i
].name
.len
;
2893 memcpy(p
, tok_text(&m
->params
[i
].name
), m
->params
[i
].name
.len
);
2895 if (flags
& SPARM_NOSTRIP
)
2897 if (flags
& SPARM_STR
)
2899 if (flags
& SPARM_EVAL
)
2903 *p
= '('; /* First parameter starts with ( not , */
2907 memcpy(p
, m
->name
, namelen
);
2909 if (context_prefix
) {
2911 memcpy(p
, context_prefix
, context_len
);
2912 nasm_free(context_prefix
);
2915 nasm_listmsg("%s %s", pp_directives
[op
], p
);
2920 * Parse smacro arguments, return argument count. If the tmpl argument
2921 * is set, set the nparam, greedy and params field in the template.
2922 * *tpp is updated to point to the pointer to the first token after the
2925 * The text values from any argument tokens are "stolen" and the
2926 * corresponding text fields set to NULL.
2928 static int parse_smacro_template(Token
***tpp
, SMacro
*tmpl
)
2931 enum sparmflags flags
;
2932 struct smac_param
*params
= NULL
;
2934 bool greedy
= false;
2940 * DO NOT skip whitespace here, or we won't be able to distinguish:
2942 * %define foo (a,b) ; no arguments, (a,b) is the expansion
2943 * %define bar(a,b) ; two arguments, empty expansion
2945 * This ambiguity was inherited from C.
2948 if (!tok_is(t
, '('))
2956 /* Count parameters first */
2957 sparam
= parse_smacro_template(&txpp
, NULL
);
2959 goto finish
; /* No parameters, we're done */
2960 nasm_newn(params
, sparam
);
2963 /* Skip leading paren */
2972 if (!t
|| !t
->type
) {
2974 nasm_nonfatal("`)' expected to terminate macro template");
2976 nasm_nonfatal("parameter identifier expected");
2990 switch (t
->text
.a
[0]) {
2992 flags
|= SPARM_EVAL
;
2998 flags
|= SPARM_NOSTRIP
;
3001 flags
|= SPARM_GREEDY
;
3006 nasm_nonfatal("greedy parameter must be last");
3011 steal_Token(¶ms
[nparam
].name
, name
);
3012 params
[nparam
].flags
= flags
;
3017 done
= t
->text
.a
[0] == ')';
3024 case TOK_WHITESPACE
:
3030 nasm_nonfatal("garbage `%s' in macro parameter list", tok_text(t
));
3041 while (t
&& t
->type
== TOK_WHITESPACE
) {
3047 tmpl
->nparam
= nparam
;
3048 tmpl
->greedy
= greedy
;
3049 tmpl
->params
= params
;
3055 * Common code for defining an smacro. The tmpl argument, if not NULL,
3056 * contains any macro parameters that aren't explicit arguments;
3057 * those are the more uncommon macro variants.
3059 static SMacro
*define_smacro(const char *mname
, bool casesense
,
3060 Token
*expansion
, SMacro
*tmpl
)
3062 SMacro
*smac
, **smhead
;
3063 struct hash_table
*smtbl
;
3065 bool defining_alias
= false;
3066 unsigned int nparam
= 0;
3069 defining_alias
= tmpl
->alias
;
3070 nparam
= tmpl
->nparam
;
3071 if (nparam
&& !defining_alias
)
3072 mark_smac_params(expansion
, tmpl
, 0);
3076 ctx
= get_ctx(mname
, &mname
);
3078 if (!smacro_defined(ctx
, mname
, nparam
, &smac
, casesense
, true)) {
3079 /* Create a new macro */
3080 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
3081 smhead
= (SMacro
**) hash_findi_add(smtbl
, mname
);
3083 smac
->next
= *smhead
;
3087 nasm_warn(WARN_OTHER
, "single-line macro `%s' defined both with and"
3088 " without parameters", mname
);
3090 * Some instances of the old code considered this a failure,
3091 * some others didn't. What is the right thing to do here?
3094 } else if (!smac
->alias
|| ppopt
.noaliases
|| defining_alias
) {
3096 * We're redefining, so we have to take over an
3097 * existing SMacro structure. This means freeing
3098 * what was already in it, but not the structure itself.
3102 } else if (smac
->in_progress
) {
3103 nasm_nonfatal("macro alias loop");
3106 /* It is an alias macro; follow the alias link */
3109 smac
->in_progress
= true;
3110 s
= define_smacro(tok_text(smac
->expansion
), casesense
,
3112 smac
->in_progress
= false;
3117 smac
->name
= nasm_strdup(mname
);
3118 smac
->casesense
= casesense
;
3119 smac
->expansion
= expansion
;
3120 smac
->expand
= smacro_expand_default
;
3122 smac
->nparam
= tmpl
->nparam
;
3123 smac
->params
= tmpl
->params
;
3124 smac
->alias
= tmpl
->alias
;
3125 smac
->greedy
= tmpl
->greedy
;
3127 smac
->expand
= tmpl
->expand
;
3129 if (list_option('s')) {
3130 list_smacro_def((smac
->alias
? PP_DEFALIAS
: PP_DEFINE
)
3131 + !casesense
, ctx
, smac
);
3136 free_tlist(expansion
);
3138 free_smacro_members(tmpl
);
3143 * Undefine an smacro
3145 static void undef_smacro(const char *mname
, bool undefalias
)
3147 SMacro
**smhead
, *s
, **sp
;
3148 struct hash_table
*smtbl
;
3151 ctx
= get_ctx(mname
, &mname
);
3152 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
3153 smhead
= (SMacro
**)hash_findi(smtbl
, mname
, NULL
);
3157 * We now have a macro name... go hunt for it.
3160 while ((s
= *sp
) != NULL
) {
3161 if (!mstrcmp(s
->name
, mname
, s
->casesense
)) {
3162 if (s
->alias
&& !undefalias
) {
3163 if (!ppopt
.noaliases
) {
3164 if (s
->in_progress
) {
3165 nasm_nonfatal("macro alias loop");
3167 s
->in_progress
= true;
3168 undef_smacro(tok_text(s
->expansion
), false);
3169 s
->in_progress
= false;
3173 if (list_option('d'))
3174 list_smacro_def(s
->alias
? PP_UNDEFALIAS
: PP_UNDEF
,
3187 * Parse a mmacro specification.
3189 static bool parse_mmacro_spec(Token
*tline
, MMacro
*def
, const char *directive
)
3191 tline
= tline
->next
;
3192 tline
= skip_white(tline
);
3193 tline
= expand_id(tline
);
3194 if (!tok_type(tline
, TOK_ID
)) {
3195 nasm_nonfatal("`%s' expects a macro name", directive
);
3202 def
->name
= dup_text(tline
);
3205 def
->nparam_min
= 0;
3206 def
->nparam_max
= 0;
3208 tline
= expand_smacro(tline
->next
);
3209 tline
= skip_white(tline
);
3210 if (!tok_type(tline
, TOK_NUMBER
))
3211 nasm_nonfatal("`%s' expects a parameter count", directive
);
3213 def
->nparam_min
= def
->nparam_max
= read_param_count(tok_text(tline
));
3214 if (tline
&& tok_is(tline
->next
, '-')) {
3215 tline
= tline
->next
->next
;
3216 if (tok_is(tline
, '*')) {
3217 def
->nparam_max
= INT_MAX
;
3218 } else if (!tok_type(tline
, TOK_NUMBER
)) {
3219 nasm_nonfatal("`%s' expects a parameter count after `-'", directive
);
3221 def
->nparam_max
= read_param_count(tok_text(tline
));
3222 if (def
->nparam_min
> def
->nparam_max
) {
3223 nasm_nonfatal("minimum parameter count exceeds maximum");
3224 def
->nparam_max
= def
->nparam_min
;
3228 if (tline
&& tok_is(tline
->next
, '+')) {
3229 tline
= tline
->next
;
3232 if (tline
&& tok_type(tline
->next
, TOK_ID
) &&
3233 tline
->next
->len
== 7 &&
3234 !nasm_stricmp(tline
->next
->text
.a
, ".nolist")) {
3235 tline
= tline
->next
;
3236 if (!list_option('f'))
3237 def
->nolist
|= NL_LIST
|NL_LINE
;
3241 * Handle default parameters.
3244 if (tline
&& tline
->next
) {
3246 def
->dlist
= tline
->next
;
3248 comma
= count_mmac_params(def
->dlist
, &def
->ndefs
, &def
->defaults
);
3249 if (!ppopt
.sane_empty_expansion
&& comma
) {
3252 nasm_warn(WARN_MACRO_PARAMS_LEGACY
,
3253 "dropping trailing empty default parameter in defintion of multi-line macro `%s'",
3258 def
->defaults
= NULL
;
3260 def
->expansion
= NULL
;
3262 if (def
->defaults
&& def
->ndefs
> def
->nparam_max
- def
->nparam_min
&&
3265 *!macro-defaults [on] macros with more default than optional parameters
3266 *! warns when a macro has more default parameters than optional parameters.
3267 *! See \k{mlmacdef} for why might want to disable this warning.
3269 nasm_warn(WARN_MACRO_DEFAULTS
,
3270 "too many default macro parameters in macro `%s'", def
->name
);
3278 * Decode a size directive
3280 static int parse_size(const char *str
) {
3281 static const char *size_names
[] =
3282 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
3283 static const int sizes
[] =
3284 { 0, 1, 4, 16, 8, 10, 2, 32 };
3285 return str
? sizes
[bsii(str
, size_names
, ARRAY_SIZE(size_names
))+1] : 0;
3289 * Process a preprocessor %pragma directive. Currently there are none.
3290 * Gets passed the token list starting with the "preproc" token from
3291 * "%pragma preproc".
3293 static void do_pragma_preproc(Token
*tline
)
3297 /* Skip to the real stuff */
3298 tline
= tline
->next
;
3299 tline
= skip_white(tline
);
3301 if (!tok_type(tline
, TOK_ID
))
3304 txt
= tok_text(tline
);
3305 if (!nasm_stricmp(txt
, "sane_empty_expansion")) {
3306 tline
= skip_white(tline
->next
);
3307 ppopt
.sane_empty_expansion
=
3308 pp_get_boolean_option(tline
, ppopt
.sane_empty_expansion
);
3310 /* Unknown pragma, ignore for now */
3314 static bool is_macro_id(const Token
*t
)
3316 return tok_type(t
, TOK_ID
) || tok_type(t
, TOK_LOCAL_MACRO
);
3319 static const char *get_id(Token
**tp
, const char *dname
)
3324 t
= t
->next
; /* Skip directive */
3328 if (!is_macro_id(t
)) {
3329 nasm_nonfatal("`%s' expects a macro identifier", dname
);
3339 /* Parse a %use package name and find the package. Set *err on syntax error. */
3340 static const struct use_package
*
3341 get_use_pkg(Token
*t
, const char *dname
, const char **name
)
3346 t
= expand_smacro(t
);
3351 nasm_nonfatal("`%s' expects a package name, got end of line", dname
);
3353 } else if (t
->type
!= TOK_ID
&& t
->type
!= TOK_STRING
) {
3354 nasm_nonfatal("`%s' expects a package name, got `%s'",
3355 dname
, tok_text(t
));
3359 *name
= id
= unquote_token(t
);
3364 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3366 return nasm_find_use_package(id
);
3370 * Mark parameter tokens in an smacro definition. If the type argument
3371 * is 0, create smac param tokens, otherwise use the type specified;
3372 * normally this is used for TOK_XDEF_PARAM, which is used to protect
3373 * parameter tokens during expansion during %xdefine.
3375 * tmpl may not be NULL here.
3377 static void mark_smac_params(Token
*tline
, const SMacro
*tmpl
,
3378 enum pp_token_type type
)
3380 const struct smac_param
*params
= tmpl
->params
;
3381 int nparam
= tmpl
->nparam
;
3385 list_for_each(t
, tline
) {
3386 if (t
->type
!= TOK_ID
&& t
->type
!= TOK_XDEF_PARAM
)
3389 for (i
= 0; i
< nparam
; i
++) {
3390 if (tok_text_match(t
, ¶ms
[i
].name
))
3391 t
->type
= type
? type
: tok_smac_param(i
);
3397 * %clear selected macro sets either globally or in contexts
3399 static void do_clear(enum clear_what what
, bool context
)
3402 if (what
& CLEAR_ALLDEFINE
) {
3404 list_for_each(ctx
, cstk
)
3405 clear_smacro_table(&ctx
->localmac
, what
);
3407 /* Nothing else can be context-local */
3409 if (what
& CLEAR_ALLDEFINE
)
3410 clear_smacro_table(&smacros
, what
);
3411 if (what
& CLEAR_MMACRO
)
3412 free_mmacro_table(&mmacros
);
3417 * find and process preprocessor directive in passed line
3418 * Find out if a line contains a preprocessor directive, and deal
3421 * If a directive _is_ found, it is the responsibility of this routine
3422 * (and not the caller) to free_tlist() the line.
3424 * @param tline a pointer to the current tokeninzed line linked list
3425 * @param output if this directive generated output
3426 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
3429 static int do_directive(Token
*tline
, Token
**output
)
3431 enum preproc_token op
;
3434 enum nolist_flags nolist
;
3440 const char *found_path
;
3446 MMacro
*mmac
, **mmhead
;
3447 Token
*t
= NULL
, *tt
, *macro_start
, *last
, *origline
;
3449 struct tokenval tokval
;
3454 const char *dname
; /* Name of directive, for messages */
3456 *output
= NULL
; /* No output generated */
3459 tline
= skip_white(tline
);
3460 if (!tline
|| !tok_type(tline
, TOK_PREPROC_ID
))
3461 return NO_DIRECTIVE_FOUND
;
3463 dname
= tok_text(tline
);
3464 if (dname
[1] == '%')
3465 return NO_DIRECTIVE_FOUND
;
3467 op
= pp_token_hash(dname
);
3470 if (PP_HAS_CASE(op
) & PP_INSENSITIVE(op
)) {
3476 * %line directives are always processed immediately and
3477 * unconditionally, as they are intended to reflect position
3478 * in externally preprocessed sources.
3480 if (op
== PP_LINE
) {
3482 * Syntax is `%line nnn[+mmm] [filename]'
3484 if (pp_noline
|| istk
->mstk
.mstk
)
3487 tline
= tline
->next
;
3488 tline
= skip_white(tline
);
3489 if (!tok_type(tline
, TOK_NUMBER
)) {
3490 nasm_nonfatal("`%s' expects line number", dname
);
3493 k
= readnum(tok_text(tline
), &err
);
3495 tline
= tline
->next
;
3496 if (tok_is(tline
, '+') || tok_is(tline
, '-')) {
3497 bool minus
= tok_is(tline
, '-');
3498 tline
= tline
->next
;
3499 if (!tok_type(tline
, TOK_NUMBER
)) {
3500 nasm_nonfatal("`%s' expects line increment", dname
);
3503 m
= readnum(tok_text(tline
), &err
);
3506 tline
= tline
->next
;
3508 tline
= skip_white(tline
);
3510 if (tline
->type
== TOK_STRING
) {
3511 src_set_fname(unquote_token(tline
));
3513 char *fname
= detoken(tline
, false);
3514 src_set_fname(fname
);
3520 istk
->where
= src_where();
3526 * If we're in a non-emitting branch of a condition construct,
3527 * or walking to the end of an already terminated %rep block,
3528 * we should ignore all directives except for condition
3531 if (((istk
->conds
&& !emitting(istk
->conds
->state
)) ||
3532 (istk
->mstk
.mstk
&& !istk
->mstk
.mstk
->in_progress
)) &&
3533 !is_condition(op
)) {
3534 return NO_DIRECTIVE_FOUND
;
3538 * If we're defining a macro or reading a %rep block, we should
3539 * ignore all directives except for %macro/%imacro (which nest),
3540 * %endm/%endmacro, %line and (only if we're in a %rep block) %endrep.
3541 * If we're in a %rep block, another %rep nests, so should be let through.
3543 if (defining
&& op
!= PP_MACRO
&& op
!= PP_RMACRO
&&
3544 op
!= PP_ENDMACRO
&& op
!= PP_ENDM
&&
3545 (defining
->name
|| (op
!= PP_ENDREP
&& op
!= PP_REP
))) {
3546 return NO_DIRECTIVE_FOUND
;
3550 if (op
== PP_MACRO
|| op
== PP_RMACRO
) {
3552 return NO_DIRECTIVE_FOUND
;
3553 } else if (nested_mac_count
> 0) {
3554 if (op
== PP_ENDMACRO
) {
3556 return NO_DIRECTIVE_FOUND
;
3559 if (!defining
->name
) {
3562 return NO_DIRECTIVE_FOUND
;
3563 } else if (nested_rep_count
> 0) {
3564 if (op
== PP_ENDREP
) {
3566 return NO_DIRECTIVE_FOUND
;
3574 nasm_nonfatal("unknown preprocessor directive `%s'", dname
);
3575 return NO_DIRECTIVE_FOUND
; /* didn't get it */
3579 * %pragma namespace options...
3581 * The namespace "preproc" is reserved for the preprocessor;
3582 * all other namespaces generate a [pragma] assembly directive.
3584 * Invalid %pragmas are ignored and may have different
3585 * meaning in future versions of NASM.
3588 tline
= tline
->next
;
3590 tline
= zap_white(expand_smacro(tline
));
3591 if (tok_type(tline
, TOK_ID
)) {
3592 if (!nasm_stricmp(tok_text(tline
), "preproc")) {
3593 /* Preprocessor pragma */
3594 do_pragma_preproc(tline
);
3597 /* Build the assembler directive */
3599 /* Append bracket to the end of the output */
3600 for (t
= tline
; t
->next
; t
= t
->next
)
3602 t
->next
= make_tok_char(NULL
, ']');
3604 /* Prepend "[pragma " */
3605 t
= new_White(tline
);
3606 t
= new_Token(t
, TOK_ID
, "pragma", 6);
3607 t
= make_tok_char(t
, '[');
3615 /* Directive to tell NASM what the default stack size is. The
3616 * default is for a 16-bit stack, and this can be overriden with
3619 tline
= skip_white(tline
->next
);
3620 if (!tline
|| tline
->type
!= TOK_ID
) {
3621 nasm_nonfatal("`%s' missing size parameter", dname
);
3623 if (nasm_stricmp(tok_text(tline
), "flat") == 0) {
3624 /* All subsequent ARG directives are for a 32-bit stack */
3626 StackPointer
= "ebp";
3629 } else if (nasm_stricmp(tok_text(tline
), "flat64") == 0) {
3630 /* All subsequent ARG directives are for a 64-bit stack */
3632 StackPointer
= "rbp";
3635 } else if (nasm_stricmp(tok_text(tline
), "large") == 0) {
3636 /* All subsequent ARG directives are for a 16-bit stack,
3637 * far function call.
3640 StackPointer
= "bp";
3643 } else if (nasm_stricmp(tok_text(tline
), "small") == 0) {
3644 /* All subsequent ARG directives are for a 16-bit stack,
3645 * far function call. We don't support near functions.
3648 StackPointer
= "bp";
3652 nasm_nonfatal("`%s' invalid size type", dname
);
3657 /* TASM like ARG directive to define arguments to functions, in
3658 * the following form:
3660 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
3665 char directive
[256];
3666 int size
= StackSize
;
3668 /* Find the argument name */
3669 tline
= skip_white(tline
->next
);
3670 if (!tline
|| tline
->type
!= TOK_ID
) {
3671 nasm_nonfatal("`%s' missing argument parameter", dname
);
3674 arg
= tok_text(tline
);
3676 /* Find the argument size type */
3677 tline
= tline
->next
;
3678 if (!tok_is(tline
, ':')) {
3679 nasm_nonfatal("syntax error processing `%s' directive", dname
);
3682 tline
= tline
->next
;
3683 if (!tok_type(tline
, TOK_ID
)) {
3684 nasm_nonfatal("`%s' missing size type parameter", dname
);
3688 /* Allow macro expansion of type parameter */
3689 tt
= tokenize(tok_text(tline
));
3690 tt
= expand_smacro(tt
);
3691 size
= parse_size(tok_text(tt
));
3693 nasm_nonfatal("invalid size type for `%s' missing directive", dname
);
3699 /* Round up to even stack slots */
3700 size
= ALIGN(size
, StackSize
);
3702 /* Now define the macro for the argument */
3703 snprintf(directive
, sizeof(directive
), "%%define %s (%s+%d)",
3704 arg
, StackPointer
, offset
);
3705 do_directive(tokenize(directive
), output
);
3708 /* Move to the next argument in the list */
3709 tline
= skip_white(tline
->next
);
3710 } while (tok_is(tline
, ','));
3715 /* TASM like LOCAL directive to define local variables for a
3716 * function, in the following form:
3718 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
3720 * The '= LocalSize' at the end is ignored by NASM, but is
3721 * required by TASM to define the local parameter size (and used
3722 * by the TASM macro package).
3724 offset
= LocalOffset
;
3727 char directive
[256];
3728 int size
= StackSize
;
3730 /* Find the argument name */
3731 tline
= skip_white(tline
->next
);
3732 if (!tline
|| tline
->type
!= TOK_ID
) {
3733 nasm_nonfatal("`%s' missing argument parameter", dname
);
3736 local
= tok_text(tline
);
3738 /* Find the argument size type */
3739 tline
= tline
->next
;
3740 if (!tok_is(tline
, ':')) {
3741 nasm_nonfatal("syntax error processing `%s' directive", dname
);
3744 tline
= tline
->next
;
3745 if (!tok_type(tline
, TOK_ID
)) {
3746 nasm_nonfatal("`%s' missing size type parameter", dname
);
3750 /* Allow macro expansion of type parameter */
3751 tt
= tokenize(tok_text(tline
));
3752 tt
= expand_smacro(tt
);
3753 size
= parse_size(tok_text(tt
));
3755 nasm_nonfatal("invalid size type for `%s' missing directive", dname
);
3761 /* Round up to even stack slots */
3762 size
= ALIGN(size
, StackSize
);
3764 offset
+= size
; /* Negative offset, increment before */
3766 /* Now define the macro for the argument */
3767 snprintf(directive
, sizeof(directive
), "%%define %s (%s-%d)",
3768 local
, StackPointer
, offset
);
3769 do_directive(tokenize(directive
), output
);
3771 /* Now define the assign to setup the enter_c macro correctly */
3772 snprintf(directive
, sizeof(directive
),
3773 "%%assign %%$localsize %%$localsize+%d", size
);
3774 do_directive(tokenize(directive
), output
);
3776 /* Move to the next argument in the list */
3777 tline
= skip_white(tline
->next
);
3778 } while (tok_is(tline
, ','));
3779 LocalOffset
= offset
;
3784 bool context
= false;
3786 t
= tline
->next
= expand_smacro(tline
->next
);
3789 /* Emulate legacy behavior */
3790 do_clear(CLEAR_DEFINE
|CLEAR_MMACRO
, false);
3792 while ((t
= skip_white(t
)) && t
->type
== TOK_ID
) {
3793 const char *txt
= tok_text(t
);
3794 if (!nasm_stricmp(txt
, "all")) {
3795 do_clear(CLEAR_ALL
, context
);
3796 } else if (!nasm_stricmp(txt
, "define") ||
3797 !nasm_stricmp(txt
, "def") ||
3798 !nasm_stricmp(txt
, "smacro")) {
3799 do_clear(CLEAR_DEFINE
, context
);
3800 } else if (!nasm_stricmp(txt
, "defalias") ||
3801 !nasm_stricmp(txt
, "alias") ||
3802 !nasm_stricmp(txt
, "salias")) {
3803 do_clear(CLEAR_DEFALIAS
, context
);
3804 } else if (!nasm_stricmp(txt
, "alldef") ||
3805 !nasm_stricmp(txt
, "alldefine")) {
3806 do_clear(CLEAR_ALLDEFINE
, context
);
3807 } else if (!nasm_stricmp(txt
, "macro") ||
3808 !nasm_stricmp(txt
, "mmacro")) {
3809 do_clear(CLEAR_MMACRO
, context
);
3810 } else if (!nasm_stricmp(txt
, "context") ||
3811 !nasm_stricmp(txt
, "ctx")) {
3813 } else if (!nasm_stricmp(txt
, "global")) {
3815 } else if (!nasm_stricmp(txt
, "nothing") ||
3816 !nasm_stricmp(txt
, "none") ||
3817 !nasm_stricmp(txt
, "ignore") ||
3818 !nasm_stricmp(txt
, "-") ||
3819 !nasm_stricmp(txt
, "--")) {
3822 nasm_nonfatal("invalid option to %s: %s", dname
, txt
);
3830 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3835 t
= tline
->next
= expand_smacro(tline
->next
);
3837 if (!t
|| (t
->type
!= TOK_STRING
&&
3838 t
->type
!= TOK_INTERNAL_STRING
)) {
3839 nasm_nonfatal("`%s' expects a file name", dname
);
3843 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3845 strlist_add(deplist
, unquote_token_cstr(t
));
3850 t
= tline
->next
= expand_smacro(tline
->next
);
3853 if (!t
|| (t
->type
!= TOK_STRING
&&
3854 t
->type
!= TOK_INTERNAL_STRING
)) {
3855 nasm_nonfatal("`%s' expects a file name", dname
);
3859 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3860 p
= unquote_token_cstr(t
);
3864 inc
->fp
= inc_fopen(p
, deplist
, &found_path
,
3865 (pp_mode
== PP_DEPS
) ? INC_OPTIONAL
:
3866 (op
== PP_REQUIRE
) ? INC_REQUIRED
:
3867 INC_NEEDED
, NF_TEXT
);
3869 /* -MG given but file not found, or repeated %require */
3872 inc
->where
= src_where();
3874 inc
->nolist
= istk
->nolist
;
3875 inc
->noline
= istk
->noline
;
3877 src_set(0, found_path
? found_path
: p
);
3879 lfmt
->uplevel(LIST_INCLUDE
, 0);
3885 const struct use_package
*pkg
;
3888 pkg
= get_use_pkg(tline
->next
, dname
, &name
);
3892 nasm_nonfatal("unknown `%s' package: `%s'", dname
, name
);
3893 } else if (!use_loaded
[pkg
->index
]) {
3895 * Not already included, go ahead and include it.
3896 * Treat it as an include file for the purpose of
3897 * producing a listing.
3899 use_loaded
[pkg
->index
] = true;
3900 stdmacpos
= pkg
->macros
;
3903 inc
->nolist
= istk
->nolist
+ !list_option('b');
3904 inc
->noline
= istk
->noline
;
3908 lfmt
->uplevel(LIST_INCLUDE
, 0);
3915 tline
= tline
->next
;
3916 tline
= skip_white(tline
);
3917 tline
= expand_id(tline
);
3919 if (!tok_type(tline
, TOK_ID
)) {
3920 nasm_nonfatal("`%s' expects a context identifier", dname
);
3924 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored",
3926 p
= tok_text(tline
);
3928 p
= NULL
; /* Anonymous */
3931 if (op
== PP_PUSH
) {
3933 ctx
->depth
= cstk
? cstk
->depth
+ 1 : 1;
3935 ctx
->name
= p
? nasm_strdup(p
) : NULL
;
3936 ctx
->number
= unique
++;
3941 nasm_nonfatal("`%s': context stack is empty", dname
);
3942 } else if (op
== PP_POP
) {
3943 if (p
&& (!cstk
->name
|| nasm_stricmp(p
, cstk
->name
)))
3944 nasm_nonfatal("`%s' in wrong context: %s, "
3946 dname
, cstk
->name
? cstk
->name
: "anonymous", p
);
3951 nasm_free((char *)cstk
->name
);
3952 cstk
->name
= p
? nasm_strdup(p
) : NULL
;
3958 severity
= ERR_FATAL
;
3961 severity
= ERR_NONFATAL
|ERR_PASS2
;
3965 *!user [on] %warning directives
3966 *! controls output of \c{%warning} directives (see \k{pperror}).
3968 severity
= ERR_WARNING
|WARN_USER
|ERR_PASS2
;
3973 /* Only error out if this is the final pass */
3974 tline
->next
= expand_smacro(tline
->next
);
3975 tline
= tline
->next
;
3976 tline
= skip_white(tline
);
3977 t
= tline
? tline
->next
: NULL
;
3979 if (tok_type(tline
, TOK_STRING
) && !t
) {
3980 /* The line contains only a quoted string */
3981 p
= unquote_token(tline
); /* Ignore NUL character truncation */
3982 nasm_error(severity
, "%s", p
);
3984 /* Not a quoted string, or more than a quoted string */
3985 q
= detoken(tline
, false);
3986 nasm_error(severity
, "%s", q
);
3993 if (istk
->conds
&& !emitting(istk
->conds
->state
))
3996 j
= if_condition(tline
->next
, op
);
3997 tline
->next
= NULL
; /* it got freed */
3999 cond
= nasm_malloc(sizeof(Cond
));
4000 cond
->next
= istk
->conds
;
4004 istk
->mstk
.mstk
->condcnt
++;
4009 nasm_fatal("`%s': no matching `%%if'", dname
);
4010 switch(istk
->conds
->state
) {
4012 istk
->conds
->state
= COND_DONE
;
4019 case COND_ELSE_TRUE
:
4020 case COND_ELSE_FALSE
:
4021 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
4022 "`%%elif' after `%%else' ignored");
4023 istk
->conds
->state
= COND_NEVER
;
4028 * IMPORTANT: In the case of %if, we will already have
4029 * called expand_mmac_params(); however, if we're
4030 * processing an %elif we must have been in a
4031 * non-emitting mode, which would have inhibited
4032 * the normal invocation of expand_mmac_params().
4033 * Therefore, we have to do it explicitly here.
4035 j
= if_condition(expand_mmac_params(tline
->next
), op
);
4036 tline
->next
= NULL
; /* it got freed */
4037 istk
->conds
->state
= j
;
4044 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
4045 "trailing garbage after `%%else' ignored");
4047 nasm_fatal("`%%else: no matching `%%if'");
4048 switch(istk
->conds
->state
) {
4051 istk
->conds
->state
= COND_ELSE_FALSE
;
4058 istk
->conds
->state
= COND_ELSE_TRUE
;
4061 case COND_ELSE_TRUE
:
4062 case COND_ELSE_FALSE
:
4063 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
4064 "`%%else' after `%%else' ignored.");
4065 istk
->conds
->state
= COND_NEVER
;
4072 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
4073 "trailing garbage after `%%endif' ignored");
4075 nasm_fatal("`%%endif': no matching `%%if'");
4077 istk
->conds
= cond
->next
;
4080 istk
->mstk
.mstk
->condcnt
--;
4088 nasm_assert(!defining
);
4090 def
->casesense
= casesense
;
4091 def
->dstk
.mmac
= defining
;
4092 if (op
== PP_RMACRO
)
4093 def
->max_depth
= nasm_limit
[LIMIT_MACRO_LEVELS
];
4094 if (!parse_mmacro_spec(tline
, def
, dname
)) {
4100 defining
->where
= istk
->where
;
4102 mmac
= (MMacro
*) hash_findix(&mmacros
, defining
->name
);
4104 if (!strcmp(mmac
->name
, defining
->name
) &&
4105 (mmac
->nparam_min
<= defining
->nparam_max
4107 && (defining
->nparam_min
<= mmac
->nparam_max
4109 nasm_warn(WARN_OTHER
, "redefining multi-line macro `%s'",
4120 if (!(defining
&& defining
->name
)) {
4121 nasm_nonfatal("`%s': not defining a macro", tok_text(tline
));
4124 mmhead
= (MMacro
**) hash_findi_add(&mmacros
, defining
->name
);
4125 defining
->next
= *mmhead
;
4132 * We must search along istk->expansion until we hit a
4133 * macro-end marker for a macro with a name. Then we
4134 * bypass all lines between exitmacro and endmacro.
4136 list_for_each(l
, istk
->expansion
)
4137 if (l
->finishes
&& l
->finishes
->name
)
4142 * Remove all conditional entries relative to this
4143 * macro invocation. (safe to do in this context)
4145 for ( ; l
->finishes
->condcnt
> 0; l
->finishes
->condcnt
--) {
4147 istk
->conds
= cond
->next
;
4150 istk
->expansion
= l
;
4152 nasm_nonfatal("`%%exitmacro' not within `%%macro' block");
4165 spec
.casesense
= casesense
;
4166 if (!parse_mmacro_spec(tline
, &spec
, dname
)) {
4169 mmac_p
= (MMacro
**) hash_findi(&mmacros
, spec
.name
, NULL
);
4170 while (mmac_p
&& *mmac_p
) {
4172 if (mmac
->casesense
== spec
.casesense
&&
4173 !mstrcmp(mmac
->name
, spec
.name
, spec
.casesense
) &&
4174 mmac
->nparam_min
== spec
.nparam_min
&&
4175 mmac
->nparam_max
== spec
.nparam_max
&&
4176 mmac
->plus
== spec
.plus
) {
4177 *mmac_p
= mmac
->next
;
4180 mmac_p
= &mmac
->next
;
4183 free_tlist(spec
.dlist
);
4188 while (tok_white(tline
->next
))
4189 tline
= tline
->next
;
4191 free_tlist(origline
);
4192 nasm_nonfatal("`%%rotate' missing rotate count");
4193 return DIRECTIVE_FOUND
;
4195 t
= expand_smacro(tline
->next
);
4197 pps
.tptr
= tline
= t
;
4199 tokval
.t_type
= TOKEN_INVALID
;
4201 evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4204 return DIRECTIVE_FOUND
;
4206 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
4207 if (!is_simple(evalresult
)) {
4208 nasm_nonfatal("non-constant value given to `%%rotate'");
4209 return DIRECTIVE_FOUND
;
4211 mmac
= istk
->mstk
.mmac
;
4213 nasm_nonfatal("`%%rotate' invoked outside a macro call");
4214 } else if (mmac
->nparam
== 0) {
4215 nasm_nonfatal("`%%rotate' invoked within macro without parameters");
4217 int rotate
= mmac
->rotate
+ reloc_value(evalresult
);
4219 rotate
%= (int)mmac
->nparam
;
4221 rotate
+= mmac
->nparam
;
4223 mmac
->rotate
= rotate
;
4229 MMacro
*tmp_defining
;
4232 tline
= skip_white(tline
->next
);
4233 if (tok_type(tline
, TOK_ID
) && tline
->len
== 7 &&
4234 !nasm_memicmp(tline
->text
.a
, ".nolist", 7)) {
4235 if (!list_option('f'))
4236 nolist
|= NL_LIST
; /* ... but update line numbers */
4237 tline
= skip_white(tline
->next
);
4241 pps
.tptr
= expand_smacro(tline
);
4243 tokval
.t_type
= TOKEN_INVALID
;
4244 /* XXX: really critical?! */
4246 evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4250 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
4251 if (!is_simple(evalresult
)) {
4252 nasm_nonfatal("non-constant value given to `%%rep'");
4255 count
= reloc_value(evalresult
);
4256 if (count
> nasm_limit
[LIMIT_REP
]) {
4257 nasm_nonfatal("`%%rep' count %"PRId64
" exceeds limit (currently %"PRId64
")",
4258 count
, nasm_limit
[LIMIT_REP
]);
4260 } else if (count
< 0) {
4262 *!negative-rep [on] regative %rep count
4263 *! warns about negative counts given to the \c{%rep}
4264 *! preprocessor directive.
4266 nasm_warn(ERR_PASS2
|WARN_NEGATIVE_REP
,
4267 "negative `%%rep' count: %"PRId64
, count
);
4273 nasm_nonfatal("`%%rep' expects a repeat count");
4276 tmp_defining
= defining
;
4278 defining
->nolist
= nolist
;
4279 defining
->in_progress
= count
;
4280 defining
->mstk
= istk
->mstk
;
4281 defining
->dstk
.mstk
= tmp_defining
;
4282 defining
->dstk
.mmac
= tmp_defining
? tmp_defining
->dstk
.mmac
: NULL
;
4283 defining
->where
= istk
->where
;
4288 if (!defining
|| defining
->name
) {
4289 nasm_nonfatal("`%%endrep': no matching `%%rep'");
4294 * Now we have a "macro" defined - although it has no name
4295 * and we won't be entering it in the hash tables - we must
4296 * push a macro-end marker for it on to istk->expansion.
4297 * After that, it will take care of propagating itself (a
4298 * macro-end marker line for a macro which is really a %rep
4299 * block will cause the macro to be re-expanded, complete
4300 * with another macro-end marker to ensure the process
4301 * continues) until the whole expansion is forcibly removed
4302 * from istk->expansion by a %exitrep.
4305 l
->next
= istk
->expansion
;
4306 l
->finishes
= defining
;
4308 l
->where
= src_where();
4309 istk
->expansion
= l
;
4311 istk
->mstk
.mstk
= defining
;
4313 /* A loop does not change istk->noline */
4314 istk
->nolist
+= !!(defining
->nolist
& NL_LIST
);
4316 lfmt
->uplevel(LIST_MACRO
, 0);
4318 defining
= defining
->dstk
.mstk
;
4323 * We must search along istk->expansion until we hit a
4324 * macro-end marker for a macro with no name. Then we set
4325 * its `in_progress' flag to 0.
4327 list_for_each(l
, istk
->expansion
)
4328 if (l
->finishes
&& !l
->finishes
->name
)
4332 l
->finishes
->in_progress
= 0;
4334 nasm_nonfatal("`%%exitrep' not within `%%rep' block");
4345 if (!(mname
= get_id(&tline
, dname
)))
4349 lastp
= &tline
->next
;
4350 nparam
= parse_smacro_template(&lastp
, &tmpl
);
4354 if (unlikely(op
== PP_DEFALIAS
)) {
4355 macro_start
= tline
;
4356 if (!is_macro_id(macro_start
)) {
4357 nasm_nonfatal("`%s' expects a macro identifier to alias",
4361 tt
= macro_start
->next
;
4362 macro_start
->next
= NULL
;
4363 tline
= tline
->next
;
4364 tline
= skip_white(tline
);
4365 if (tline
&& tline
->type
) {
4366 nasm_warn(WARN_OTHER
,
4367 "trailing garbage after aliasing identifier ignored");
4372 if (op
== PP_XDEFINE
) {
4373 /* Protect macro parameter tokens */
4375 mark_smac_params(tline
, &tmpl
, TOK_XDEF_PARAM
);
4376 tline
= expand_smacro(tline
);
4378 /* NB: Does this still make sense? */
4379 macro_start
= reverse_tokens(tline
);
4383 * Good. We now have a macro name, a parameter count, and a
4384 * token list (in reverse order) for an expansion. We ought
4385 * to be OK just to create an SMacro, store it, and let
4386 * free_tlist have the rest of the line (which we have
4387 * carefully re-terminated after chopping off the expansion
4390 define_smacro(mname
, casesense
, macro_start
, &tmpl
);
4396 if (!(mname
= get_id(&tline
, dname
)))
4399 nasm_warn(WARN_OTHER
, "trailing garbage after macro name ignored");
4401 undef_smacro(mname
, op
== PP_UNDEFALIAS
);
4405 if (!(mname
= get_id(&tline
, dname
)))
4409 tline
= expand_smacro(tline
->next
);
4412 tline
= zap_white(tline
);
4413 q
= detoken(tline
, false);
4414 macro_start
= make_tok_qstr(NULL
, q
);
4418 * We now have a macro name, an implicit parameter count of
4419 * zero, and a string token to use as an expansion. Create
4420 * and store an SMacro.
4422 define_smacro(mname
, casesense
, macro_start
, NULL
);
4426 if (!(mname
= get_id(&tline
, dname
)))
4430 tline
= expand_smacro(tline
->next
);
4433 t
= skip_white(tline
);
4434 /* t should now point to the string */
4435 if (!tok_type(t
, TOK_STRING
)) {
4436 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4442 * Convert the string to a token stream. Note that smacros
4443 * are stored with the token stream reversed, so we have to
4444 * reverse the output of tokenize().
4446 macro_start
= reverse_tokens(tokenize(unquote_token_cstr(t
)));
4449 * We now have a macro name, an implicit parameter count of
4450 * zero, and a numeric token to use as an expansion. Create
4451 * and store an SMacro.
4453 define_smacro(mname
, casesense
, macro_start
, NULL
);
4459 const char *found_path
;
4461 if (!(mname
= get_id(&tline
, dname
)))
4465 tline
= expand_smacro(tline
->next
);
4468 t
= skip_white(tline
);
4469 if (!t
|| (t
->type
!= TOK_STRING
&&
4470 t
->type
!= TOK_INTERNAL_STRING
)) {
4471 nasm_nonfatal("`%s' expects a file name", dname
);
4476 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
4478 p
= unquote_token_cstr(t
);
4480 inc_fopen(p
, NULL
, &found_path
, INC_PROBE
, NF_BINARY
);
4483 macro_start
= make_tok_qstr(NULL
, found_path
);
4486 * We now have a macro name, an implicit parameter count of
4487 * zero, and a string token to use as an expansion. Create
4488 * and store an SMacro.
4490 define_smacro(mname
, casesense
, macro_start
, NULL
);
4496 if (!(mname
= get_id(&tline
, dname
)))
4500 tline
= expand_smacro(tline
->next
);
4503 t
= skip_white(tline
);
4504 /* t should now point to the string */
4505 if (!tok_type(t
, TOK_STRING
)) {
4506 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4508 free_tlist(origline
);
4509 return DIRECTIVE_FOUND
;
4513 macro_start
= make_tok_num(NULL
, t
->len
);
4516 * We now have a macro name, an implicit parameter count of
4517 * zero, and a numeric token to use as an expansion. Create
4518 * and store an SMacro.
4520 define_smacro(mname
, casesense
, macro_start
, NULL
);
4522 free_tlist(origline
);
4523 return DIRECTIVE_FOUND
;
4526 if (!(mname
= get_id(&tline
, dname
)))
4530 tline
= expand_smacro(tline
->next
);
4534 list_for_each(t
, tline
) {
4536 case TOK_WHITESPACE
:
4543 if (tok_is(t
, ',')) /* permit comma separators */
4545 /* else fall through */
4547 nasm_nonfatal("non-string passed to `%s': %s", dname
,
4554 q
= qbuf
= nasm_malloc(len
+1);
4555 list_for_each(t
, tline
) {
4556 if (t
->type
== TOK_INTERNAL_STRING
)
4557 q
= mempcpy(q
, tok_text(t
), t
->len
);
4562 * We now have a macro name, an implicit parameter count of
4563 * zero, and a numeric token to use as an expansion. Create
4564 * and store an SMacro.
4566 macro_start
= make_tok_qstr_len(NULL
, qbuf
, len
);
4568 define_smacro(mname
, casesense
, macro_start
, NULL
);
4574 int64_t start
, count
;
4578 if (!(mname
= get_id(&tline
, dname
)))
4582 tline
= expand_smacro(tline
->next
);
4585 if (tline
) /* skip expanded id */
4590 /* t should now point to the string */
4591 if (!tok_type(t
, TOK_STRING
)) {
4592 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4599 tokval
.t_type
= TOKEN_INVALID
;
4600 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4604 } else if (!is_simple(evalresult
)) {
4605 nasm_nonfatal("non-constant value given to `%s'", dname
);
4609 start
= evalresult
->value
- 1;
4611 pps
.tptr
= skip_white(pps
.tptr
);
4613 count
= 1; /* Backwards compatibility: one character */
4615 tokval
.t_type
= TOKEN_INVALID
;
4616 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4620 } else if (!is_simple(evalresult
)) {
4621 nasm_nonfatal("non-constant value given to `%s'", dname
);
4625 count
= evalresult
->value
;
4631 /* make start and count being in range */
4635 count
= len
+ count
+ 1 - start
;
4636 if (start
+ count
> (int64_t)len
)
4637 count
= len
- start
;
4638 if (!len
|| count
< 0 || start
>=(int64_t)len
)
4639 start
= -1, count
= 0; /* empty string */
4641 txt
= (start
< 0) ? "" : tok_text(t
) + start
;
4643 macro_start
= make_tok_qstr_len(NULL
, txt
, len
);
4646 * We now have a macro name, an implicit parameter count of
4647 * zero, and a numeric token to use as an expansion. Create
4648 * and store an SMacro.
4650 define_smacro(mname
, casesense
, macro_start
, NULL
);
4656 if (!(mname
= get_id(&tline
, dname
)))
4660 tline
= expand_smacro(tline
->next
);
4665 tokval
.t_type
= TOKEN_INVALID
;
4666 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4672 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
4674 if (!is_simple(evalresult
)) {
4675 nasm_nonfatal("non-constant value given to `%s'", dname
);
4676 free_tlist(origline
);
4677 return DIRECTIVE_FOUND
;
4680 macro_start
= make_tok_num(NULL
, reloc_value(evalresult
));
4683 * We now have a macro name, an implicit parameter count of
4684 * zero, and a numeric token to use as an expansion. Create
4685 * and store an SMacro.
4687 define_smacro(mname
, casesense
, macro_start
, NULL
);
4691 tline
= tline
->next
;
4692 tline
= expand_smacro(tline
);
4693 ppopt
.noaliases
= !pp_get_boolean_option(tline
, !ppopt
.noaliases
);
4697 nasm_panic("`%s' directive not preprocessed early", dname
);
4702 free_tlist(origline
);
4703 return DIRECTIVE_FOUND
;
4707 * Ensure that a macro parameter contains a condition code and
4708 * nothing else. Return the condition code index if so, or -1
4711 static int find_cc(Token
* t
)
4716 return -1; /* Probably a %+ without a space */
4719 if (!tok_type(t
, TOK_ID
))
4722 tt
= skip_white(tt
);
4723 if (tok_isnt(tt
, ','))
4726 return bsii(tok_text(t
), (const char **)conditions
,
4727 ARRAY_SIZE(conditions
));
4730 static inline bool pp_concat_match(const Token
*t
, unsigned int mask
)
4732 return t
&& (PP_CONCAT_MASK(t
->type
) & mask
);
4736 * This routines walks over tokens strem and handles tokens
4737 * pasting, if @handle_explicit passed then explicit pasting
4738 * term is handled, otherwise -- implicit pastings only.
4739 * The @m array can contain a series of token types which are
4740 * executed as separate passes.
4742 static bool paste_tokens(Token
**head
, const struct tokseq_match
*m
,
4743 size_t mnum
, bool handle_explicit
)
4745 Token
*tok
, *t
, *next
, **prev_next
, **prev_nonspace
;
4746 bool pasted
= false;
4751 * The last token before pasting. We need it
4752 * to be able to connect new handled tokens.
4753 * In other words if there were a tokens stream
4757 * and we've joined tokens B and C, the resulting
4763 prev_next
= prev_nonspace
= head
;
4765 if (tok_white(tok
) || tok_type(tok
, TOK_PASTE
))
4766 prev_nonspace
= NULL
;
4768 while (tok
&& (next
= tok
->next
)) {
4769 bool did_paste
= false;
4771 switch (tok
->type
) {
4772 case TOK_WHITESPACE
:
4773 /* Zap redundant whitespaces */
4774 tok
->next
= next
= zap_white(next
);
4778 /* Explicit pasting */
4779 if (!handle_explicit
)
4782 /* Left pasting token is start of line, just drop %+ */
4783 if (!prev_nonspace
) {
4784 tok
= delete_Token(tok
);
4790 prev_next
= prev_nonspace
;
4793 /* Delete leading whitespace */
4794 next
= zap_white(t
->next
);
4797 * Delete the %+ token itself, followed by any whitespace.
4798 * In a sequence of %+ ... %+ ... %+ pasting sequences where
4799 * some expansions in the middle have ended up empty,
4800 * we can end up having multiple %+ tokens in a row;
4801 * just drop whem in that case.
4804 if (next
->type
== TOK_PASTE
|| next
->type
== TOK_WHITESPACE
)
4805 next
= delete_Token(next
);
4811 * Nothing after? Just leave the existing token.
4814 t
->next
= tok
= NULL
; /* End of line */
4818 p
= buf
= nasm_malloc(t
->len
+ next
->len
+ 1);
4819 p
= mempcpy(p
, tok_text(t
), t
->len
);
4820 p
= mempcpy(p
, tok_text(next
), next
->len
);
4828 * No output at all? Replace with a single whitespace.
4829 * This should never happen.
4831 t
= new_White(NULL
);
4834 *prev_nonspace
= tok
= t
;
4836 t
= t
->next
; /* Find the last token produced */
4838 /* Delete the second token and attach to the end of the list */
4839 t
->next
= delete_Token(next
);
4841 /* We want to restart from the head of the pasted token */
4846 /* implicit pasting */
4847 for (i
= 0; i
< mnum
; i
++) {
4848 if (pp_concat_match(tok
, m
[i
].mask_head
))
4856 while (pp_concat_match(next
, m
[i
].mask_tail
)) {
4861 /* No match or no text to process */
4862 if (len
== tok
->len
)
4865 p
= buf
= nasm_malloc(len
+ 1);
4866 while (tok
!= next
) {
4867 p
= mempcpy(p
, tok_text(tok
), tok
->len
);
4868 tok
= delete_Token(tok
);
4871 *prev_next
= tok
= t
= tokenize(buf
);
4875 * Connect pasted into original stream,
4876 * ie A -> new-tokens -> B
4881 prev_next
= prev_nonspace
= &t
->next
;
4889 prev_next
= &tok
->next
;
4890 if (next
&& next
->type
!= TOK_WHITESPACE
&& next
->type
!= TOK_PASTE
)
4891 prev_nonspace
= prev_next
;
4901 * Computes the proper rotation of mmacro parameters
4903 static int mmac_rotate(const MMacro
*mac
, unsigned int n
)
4905 if (--n
< mac
->nparam
)
4906 n
= (n
+ mac
->rotate
) % mac
->nparam
;
4912 * expands to a list of tokens from %{x:y}
4914 static void expand_mmac_params_range(MMacro
*mac
, Token
*tline
, Token
***tail
)
4917 const char *arg
= tok_text(tline
) + 1;
4918 int fst
, lst
, incr
, n
;
4921 parsed
= sscanf(arg
, "%d:%d", &fst
, &lst
);
4922 nasm_assert(parsed
== 2);
4925 * only macros params are accounted so
4926 * if someone passes %0 -- we reject such
4929 if (lst
== 0 || fst
== 0)
4932 /* the values should be sane */
4933 if ((fst
> (int)mac
->nparam
|| fst
< (-(int)mac
->nparam
)) ||
4934 (lst
> (int)mac
->nparam
|| lst
< (-(int)mac
->nparam
)))
4937 fst
= fst
< 0 ? fst
+ (int)mac
->nparam
+ 1: fst
;
4938 lst
= lst
< 0 ? lst
+ (int)mac
->nparam
+ 1: lst
;
4941 * It will be at least one parameter, as we can loop
4942 * in either direction.
4944 incr
= (fst
< lst
) ? 1 : -1;
4947 n
= mmac_rotate(mac
, fst
);
4948 dup_tlistn(mac
->params
[n
], mac
->paramlen
[n
], tail
);
4951 t
= make_tok_char(NULL
, ',');
4960 nasm_nonfatal("`%%{%s}': macro parameters out of range", arg
);
4965 * Expand MMacro-local things: parameter references (%0, %n, %+n,
4966 * %-n) and MMacro-local identifiers (%%foo) as well as
4967 * macro indirection (%[...]) and range (%{..:..}).
4969 static Token
*expand_mmac_params(Token
* tline
)
4971 Token
**tail
, *thead
;
4972 bool changed
= false;
4973 MMacro
*mac
= istk
->mstk
.mmac
;
4980 bool err_not_mac
= false;
4982 const char *text
= tok_text(t
);
4985 tline
= tline
->next
;
4989 case TOK_LOCAL_SYMBOL
:
4998 text
= nasm_asprintf("..@%"PRIu64
".%s", mac
->unique
, text
+2);
5000 case TOK_MMACRO_PARAM
:
5011 if (strchr(text
, ':')) {
5013 expand_mmac_params_range(mac
, t
, &tail
);
5020 * We have to make a substitution of one of the
5021 * forms %1, %-1, %+1, %%foo, %0, %00.
5026 text
= nasm_asprintf("%d", mac
->nparam
);
5029 if (text
[2] != '0' || text
[3])
5031 /* a possible captured label == mac->params[0] */
5038 n
= strtoul(text
+ 1, &ep
, 10);
5042 if (n
<= mac
->nparam
) {
5043 n
= mmac_rotate(mac
, n
);
5044 dup_tlistn(mac
->params
[n
], mac
->paramlen
[n
], &tail
);
5056 n
= strtoul(tok_text(t
) + 2, &ep
, 10);
5060 if (n
&& n
<= mac
->nparam
) {
5061 n
= mmac_rotate(mac
, n
);
5062 tt
= mac
->params
[n
];
5066 nasm_nonfatal("macro parameter `%s' is not a condition code",
5073 if (text
[1] == '-') {
5074 int ncc
= inverse_ccs
[cc
];
5075 if (unlikely(ncc
== -1)) {
5076 nasm_nonfatal("condition code `%s' is not invertible",
5082 text
= nasm_strdup(conditions
[cc
]);
5087 nasm_nonfatal("invalid macro parameter: `%s'", text
);
5097 text
= nasm_strdup(mac
->iname
);
5104 case TOK_PREPROC_QQ
:
5107 text
= nasm_strdup(mac
->name
);
5118 tt
= tokenize(tok_text(t
));
5119 tt
= expand_mmac_params(tt
);
5120 tt
= expand_smacro(tt
);
5121 /* Why dup_tlist() here? We should own tt... */
5122 dup_tlist(tt
, &tail
);
5134 nasm_nonfatal("`%s': not in a macro call", text
);
5145 set_text(t
, text
, tok_strlen(text
));
5158 const struct tokseq_match t
[] = {
5160 PP_CONCAT_MASK(TOK_ID
) |
5161 PP_CONCAT_MASK(TOK_FLOAT
), /* head */
5162 PP_CONCAT_MASK(TOK_ID
) |
5163 PP_CONCAT_MASK(TOK_NUMBER
) |
5164 PP_CONCAT_MASK(TOK_FLOAT
) |
5165 PP_CONCAT_MASK(TOK_OTHER
) /* tail */
5168 PP_CONCAT_MASK(TOK_NUMBER
), /* head */
5169 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
5172 paste_tokens(&thead
, t
, ARRAY_SIZE(t
), false);
5178 static Token
*expand_smacro_noreset(Token
* tline
);
5181 * Expand *one* single-line macro instance. If the first token is not
5182 * a macro at all, it is simply copied to the output and the pointer
5183 * advanced. tpp should be a pointer to a pointer (usually the next
5184 * pointer of the previous token) to the first token. **tpp is updated
5185 * to point to the first token of the expansion, and *tpp updated to
5186 * point to the next pointer of the last token of the expansion.
5188 * If the expansion is empty, *tpp will be unchanged but **tpp will
5189 * be advanced past the macro call.
5191 * Return the macro expanded, or NULL if no expansion took place.
5193 static SMacro
*expand_one_smacro(Token
***tpp
)
5195 Token
**params
= NULL
;
5197 Token
*mstart
= **tpp
;
5198 Token
*tline
= mstart
;
5201 Token
*t
, *tup
, *tafter
;
5206 return false; /* Empty line, nothing to do */
5208 mname
= tok_text(mstart
);
5210 smacro_deadman
.total
--;
5211 smacro_deadman
.levels
--;
5213 if (unlikely(smacro_deadman
.total
< 0 || smacro_deadman
.levels
< 0)) {
5214 if (unlikely(!smacro_deadman
.triggered
)) {
5215 nasm_nonfatal("interminable macro recursion");
5216 smacro_deadman
.triggered
= true;
5219 } else if (tline
->type
== TOK_ID
|| tline
->type
== TOK_PREPROC_ID
) {
5220 head
= (SMacro
*)hash_findix(&smacros
, mname
);
5221 } else if (tline
->type
== TOK_LOCAL_MACRO
) {
5222 Context
*ctx
= get_ctx(mname
, &mname
);
5223 head
= ctx
? (SMacro
*)hash_findix(&ctx
->localmac
, mname
) : NULL
;
5229 * We've hit an identifier of some sort. First check whether the
5230 * identifier is a single-line macro at all, then think about
5231 * checking for parameters if necessary.
5233 list_for_each(m
, head
) {
5234 if (unlikely(m
->alias
&& ppopt
.noaliases
))
5236 if (!mstrcmp(m
->name
, mname
, m
->casesense
))
5244 /* Parse parameters, if applicable */
5249 if (m
->nparam
== 0) {
5251 * Simple case: the macro is parameterless.
5252 * Nothing to parse; the expansion code will
5253 * drop the macro name token.
5257 * Complicated case: at least one macro with this name
5258 * exists and takes parameters. We must find the
5259 * parameters in the call, count them, find the SMacro
5260 * that corresponds to that form of the macro call, and
5261 * substitute for the parameters when we expand. What a
5265 int paren
, brackets
;
5267 tline
= tline
->next
;
5268 tline
= skip_white(tline
);
5269 if (!tok_is(tline
, '(')) {
5271 * This macro wasn't called with parameters: ignore
5272 * the call. (Behaviour borrowed from gnu cpp.)
5280 t
= tline
; /* tline points to leading ( */
5286 nasm_nonfatal("macro call expects terminating `)'");
5290 if (t
->type
!= TOK_OTHER
|| t
->len
!= 1)
5293 switch (t
->text
.a
[0]) {
5295 if (!brackets
&& paren
== 1)
5319 break; /* Normal token */
5324 * Look for a macro matching in both name and parameter count.
5325 * We already know any matches cannot be anywhere before the
5326 * current position of "m", so there is no reason to
5332 *!macro-params-single [on] single-line macro calls with wrong parameter count
5333 *! warns about \i{single-line macros} being invoked
5334 *! with the wrong number of parameters.
5336 nasm_warn(WARN_MACRO_PARAMS_SINGLE
|ERR_HOLD
,
5337 "single-line macro `%s' exists, "
5338 "but not taking %d parameter%s",
5339 mname
, nparam
, (nparam
== 1) ? "" : "s");
5343 if (!mstrcmp(m
->name
, mname
, m
->casesense
)) {
5344 if (nparam
== m
->nparam
)
5345 break; /* It's good */
5346 if (m
->greedy
&& nparam
>= m
->nparam
-1)
5347 break; /* Also good */
5356 /* Expand the macro */
5357 m
->in_progress
= true;
5360 /* Extract parameters */
5361 Token
**phead
, **pep
;
5365 bool bracketed
= false;
5366 bool bad_bracket
= false;
5367 enum sparmflags flags
;
5371 nasm_newn(params
, nparam
);
5373 flags
= m
->params
[i
].flags
;
5374 phead
= pep
= ¶ms
[i
];
5381 tline
= tline
->next
;
5384 nasm_nonfatal("macro call expects terminating `)'");
5390 switch (tline
->type
) {
5392 if (tline
->len
== 1)
5393 ch
= tline
->text
.a
[0];
5396 case TOK_WHITESPACE
:
5397 if (!(flags
& SPARM_NOSTRIP
)) {
5398 if (brackets
|| *phead
)
5399 white
++; /* Keep interior whitespace */
5410 if (!brackets
&& paren
== 1 && !(flags
& SPARM_GREEDY
)) {
5412 nasm_assert(i
< nparam
);
5413 phead
= pep
= ¶ms
[i
];
5417 flags
= m
->params
[i
].flags
;
5423 bracketed
= !*phead
&& !(flags
& SPARM_NOSTRIP
);
5446 i
++; /* Found last argument */
5452 break; /* Normal token */
5458 bad_bracket
|= bracketed
&& !brackets
;
5461 *pep
= t
= new_White(NULL
);
5465 *pep
= t
= dup_Token(NULL
, tline
);
5471 * Possible further processing of parameters. Note that the
5472 * ordering matters here.
5474 for (i
= 0; i
< nparam
; i
++) {
5475 enum sparmflags flags
= m
->params
[i
].flags
;
5477 if (flags
& SPARM_EVAL
) {
5478 /* Evaluate this parameter as a number */
5480 struct tokenval tokval
;
5484 pps
.tptr
= eval_param
= expand_smacro_noreset(params
[i
]);
5486 tokval
.t_type
= TOKEN_INVALID
;
5487 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
5489 free_tlist(eval_param
);
5493 /* Nothing meaningful to do */
5494 } else if (tokval
.t_type
) {
5495 nasm_nonfatal("invalid expression in parameter %d of macro `%s'", i
, m
->name
);
5496 } else if (!is_simple(evalresult
)) {
5497 nasm_nonfatal("non-constant expression in parameter %d of macro `%s'", i
, m
->name
);
5499 params
[i
] = make_tok_num(NULL
, reloc_value(evalresult
));
5503 if (flags
& SPARM_STR
) {
5504 /* Convert expansion to a quoted string */
5508 qs
= expand_smacro_noreset(params
[i
]);
5509 arg
= detoken(qs
, false);
5511 params
[i
] = make_tok_qstr(NULL
, arg
);
5517 /* Note: we own the expansion this returns. */
5518 t
= m
->expand(m
, params
, nparam
);
5520 tafter
= tline
->next
; /* Skip past the macro call */
5521 tline
->next
= NULL
; /* Truncate list at the macro call end */
5528 enum pp_token_type type
= t
->type
;
5529 Token
*tnext
= t
->next
;
5534 t
= dup_Token(tline
, mstart
);
5537 case TOK_PREPROC_QQ
:
5539 size_t mlen
= strlen(m
->name
);
5543 t
->type
= mstart
->type
;
5544 if (t
->type
== TOK_LOCAL_MACRO
) {
5545 const char *psp
; /* prefix start pointer */
5546 const char *pep
; /* prefix end pointer */
5549 psp
= tok_text(mstart
);
5554 p
= nasm_malloc(len
+ 1);
5555 p
= mempcpy(p
, psp
, plen
);
5558 p
= nasm_malloc(len
+ 1);
5560 p
= mempcpy(p
, m
->name
, mlen
);
5562 set_text_free(t
, p
, len
);
5568 case TOK_COND_COMMA
:
5570 t
= cond_comma
? make_tok_char(tline
, ',') : NULL
;
5574 case TOK_PREPROC_ID
:
5575 case TOK_LOCAL_MACRO
:
5578 * Chain this into the target line *before* expanding,
5579 * that way we pick up any arguments to the new macro call,
5584 expand_one_smacro(&tp
);
5585 tline
= *tp
; /* First token left after any macro call */
5589 if (is_smac_param(t
->type
)) {
5590 int param
= smac_nparam(t
->type
);
5591 nasm_assert(!tup
&& param
< nparam
);
5595 tnext
= dup_tlist_reverse(params
[param
], NULL
);
5603 Token
*endt
= tline
;
5606 while (!cond_comma
&& t
&& t
!= endt
) {
5607 cond_comma
= t
->type
!= TOK_WHITESPACE
;
5621 for (t
= tline
; t
&& t
!= tafter
; t
= t
->next
)
5624 m
->in_progress
= false;
5626 /* Don't do this until after expansion or we will clobber mname */
5631 * No macro expansion needed; roll back to mstart (if necessary)
5632 * and then advance to the next input token. Note that this is
5633 * by far the common case!
5636 *tpp
= &mstart
->next
;
5639 smacro_deadman
.levels
++;
5640 if (unlikely(params
))
5641 free_tlist_array(params
, nparam
);
5646 * Expand all single-line macro calls made in the given line.
5647 * Return the expanded version of the line. The original is deemed
5648 * to be destroyed in the process. (In reality we'll just move
5649 * Tokens from input to output a lot of the time, rather than
5650 * actually bothering to destroy and replicate.)
5652 static Token
*expand_smacro(Token
*tline
)
5654 smacro_deadman
.total
= nasm_limit
[LIMIT_MACRO_TOKENS
];
5655 smacro_deadman
.levels
= nasm_limit
[LIMIT_MACRO_LEVELS
];
5656 smacro_deadman
.triggered
= false;
5657 return expand_smacro_noreset(tline
);
5660 static Token
*expand_smacro_noreset(Token
*org_tline
)
5664 errhold errhold
; /* Hold warning/errors during expansion */
5667 return NULL
; /* Empty input */
5670 * Trick: we should avoid changing the start token pointer since it can
5671 * be contained in "next" field of other token. Because of this
5672 * we allocate a copy of first token and work with it; at the end of
5673 * routine we copy it back
5675 tline
= dup_Token(org_tline
->next
, org_tline
);
5678 * Pretend that we always end up doing expansion on the first pass;
5679 * that way %+ get processed. However, if we process %+ before the
5680 * first pass, we end up with things like MACRO %+ TAIL trying to
5681 * look up the macro "MACROTAIL", which we don't want.
5686 static const struct tokseq_match tmatch
[] = {
5688 PP_CONCAT_MASK(TOK_ID
) |
5689 PP_CONCAT_MASK(TOK_LOCAL_MACRO
) |
5690 PP_CONCAT_MASK(TOK_ENVIRON
) |
5691 PP_CONCAT_MASK(TOK_PREPROC_ID
), /* head */
5692 PP_CONCAT_MASK(TOK_ID
) |
5693 PP_CONCAT_MASK(TOK_LOCAL_MACRO
) |
5694 PP_CONCAT_MASK(TOK_ENVIRON
) |
5695 PP_CONCAT_MASK(TOK_PREPROC_ID
) |
5696 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
5699 Token
**tail
= &tline
;
5702 * We hold warnings/errors until we are done this this loop. It is
5703 * possible for nuisance warnings to appear that disappear on later
5706 errhold
= nasm_error_hold_push();
5708 while (*tail
) /* main token loop */
5709 expanded
|= !!expand_one_smacro(&tail
);
5715 * Now scan the entire line and look for successive TOK_IDs
5716 * that resulted after expansion (they can't be produced by
5717 * tokenize()). The successive TOK_IDs should be concatenated.
5718 * Also we look for %+ tokens and concatenate the tokens
5719 * before and after them (without white spaces in between).
5721 if (!paste_tokens(&tline
, tmatch
, ARRAY_SIZE(tmatch
), true))
5722 break; /* Done again! */
5724 nasm_error_hold_pop(errhold
, false);
5727 nasm_error_hold_pop(errhold
, true);
5731 * The expression expanded to empty line;
5732 * we can't return NULL because of the "trick" above.
5733 * Just set the line to a single WHITESPACE token.
5736 tline
= new_White(NULL
);
5739 steal_Token(org_tline
, tline
);
5740 org_tline
->next
= tline
->next
;
5741 delete_Token(tline
);
5747 * Similar to expand_smacro but used exclusively with macro identifiers
5748 * right before they are fetched in. The reason is that there can be
5749 * identifiers consisting of several subparts. We consider that if there
5750 * are more than one element forming the name, user wants a expansion,
5751 * otherwise it will be left as-is. Example:
5755 * the identifier %$abc will be left as-is so that the handler for %define
5756 * will suck it and define the corresponding value. Other case:
5758 * %define _%$abc cde
5760 * In this case user wants name to be expanded *before* %define starts
5761 * working, so we'll expand %$abc into something (if it has a value;
5762 * otherwise it will be left as-is) then concatenate all successive
5765 static Token
*expand_id(Token
* tline
)
5767 Token
*cur
, *oldnext
= NULL
;
5769 if (!tline
|| !tline
->next
)
5774 (cur
->next
->type
== TOK_ID
|| cur
->next
->type
== TOK_PREPROC_ID
||
5775 cur
->next
->type
== TOK_LOCAL_MACRO
|| cur
->next
->type
== TOK_NUMBER
))
5778 /* If identifier consists of just one token, don't expand */
5783 oldnext
= cur
->next
; /* Detach the tail past identifier */
5784 cur
->next
= NULL
; /* so that expand_smacro stops here */
5787 tline
= expand_smacro(tline
);
5790 /* expand_smacro possibly changhed tline; re-scan for EOL */
5792 while (cur
&& cur
->next
)
5795 cur
->next
= oldnext
;
5802 * This is called from find_mmacro_in_list() after finding a suitable macro.
5804 static MMacro
*use_mmacro(MMacro
*m
, int *nparamp
, Token
***paramsp
)
5806 int nparam
= *nparamp
;
5807 Token
**params
= *paramsp
;
5810 * This one is right. Just check if cycle removal
5811 * prohibits us using it before we actually celebrate...
5813 if (m
->in_progress
> m
->max_depth
) {
5814 if (m
->max_depth
> 0) {
5815 nasm_warn(WARN_OTHER
, "reached maximum recursion depth of %i",
5825 * It's right, and we can use it. Add its default
5826 * parameters to the end of our list if necessary.
5828 if (m
->defaults
&& nparam
< m
->nparam_min
+ m
->ndefs
) {
5829 int newnparam
= m
->nparam_min
+ m
->ndefs
;
5830 params
= nasm_realloc(params
, sizeof(*params
) * (newnparam
+2));
5831 memcpy(¶ms
[nparam
+1], &m
->defaults
[nparam
+1-m
->nparam_min
],
5832 (newnparam
- nparam
) * sizeof(*params
));
5836 * If we've gone over the maximum parameter count (and
5837 * we're in Plus mode), ignore parameters beyond
5840 if (m
->plus
&& nparam
> m
->nparam_max
)
5841 nparam
= m
->nparam_max
;
5844 * If nparam was adjusted above, make sure the list is still
5847 params
[nparam
+1] = NULL
;
5856 * Search a macro list and try to find a match. If matching, call
5857 * use_mmacro() to set up the macro call. m points to the list of
5858 * search, which is_mmacro() sets to the first *possible* match.
5861 find_mmacro_in_list(MMacro
*m
, const char *finding
,
5862 int *nparamp
, Token
***paramsp
)
5864 int nparam
= *nparamp
;
5867 if (m
->nparam_min
<= nparam
5868 && (m
->plus
|| nparam
<= m
->nparam_max
)) {
5870 * This one matches, use it.
5872 return use_mmacro(m
, nparamp
, paramsp
);
5876 * Otherwise search for the next one with a name match.
5878 list_for_each(m
, m
->next
) {
5879 if (!mstrcmp(m
->name
, finding
, m
->casesense
))
5888 * Determine whether the given line constitutes a multi-line macro
5889 * call, and return the MMacro structure called if so. Doesn't have
5890 * to check for an initial label - that's taken care of in
5891 * expand_mmacro - but must check numbers of parameters. Guaranteed
5892 * to be called with tline->type == TOK_ID, so the putative macro
5893 * name is easy to find.
5895 static MMacro
*is_mmacro(Token
* tline
, int *nparamp
, Token
***paramsp
)
5897 MMacro
*head
, *m
, *found
;
5898 Token
**params
, **comma
;
5899 int raw_nparam
, nparam
;
5900 const char *finding
= tok_text(tline
);
5901 bool empty_args
= !tline
->next
;
5906 head
= (MMacro
*) hash_findix(&mmacros
, finding
);
5909 * Efficiency: first we see if any macro exists with the given
5910 * name which isn't already excluded by macro cycle removal.
5911 * (The cycle removal test here helps optimize the case of wrapping
5912 * instructions, and is cheap to do here.)
5914 * If not, we can return NULL immediately. _Then_ we
5915 * count the parameters, and then we look further along the
5916 * list if necessary to find the proper MMacro.
5918 list_for_each(m
, head
) {
5919 if (!mstrcmp(m
->name
, finding
, m
->casesense
) &&
5920 (m
->in_progress
!= 1 || m
->max_depth
> 0))
5921 break; /* Found something that needs consideration */
5927 * OK, we have a potential macro. Count and demarcate the
5930 comma
= count_mmac_params(tline
->next
, nparamp
, paramsp
);
5931 raw_nparam
= *nparamp
;
5934 * Search for an exact match. This cannot come *before* the m
5935 * found in the list search before, so we can start there.
5937 * If found is NULL and *paramsp has been cleared, then we
5938 * encountered an error for which we have already issued a
5939 * diagnostic, so we should not proceed.
5941 found
= find_mmacro_in_list(m
, finding
, nparamp
, paramsp
);
5949 * Special weirdness: in NASM < 2.15, an expansion of
5950 * *only* whitespace, as can happen during macro expansion under
5951 * certain circumstances, is counted as zero arguments for the
5952 * purpose of %0, but one argument for the purpose of macro
5953 * matching! In particular, this affects:
5957 * ... with %1 being empty; this would call the one-argument
5958 * version of "foobar" with an empty argument, equivalent to
5962 * ... except that %0 would be set to 0 inside foobar, even if
5963 * foobar is declared with "%macro foobar 1" or equivalent!
5965 * The proper way to do that is to define "%macro foobar 0-1".
5967 * To be compatible without doing something too stupid, try to
5968 * match a zero-argument macro first, but if that fails, try
5969 * for a one-argument macro with the above behavior.
5971 * Furthermore, NASM < 2.15 will match stripping a tailing empty
5972 * argument, but in that case %0 *does* reflect that this argument
5973 * have been stripped; this is handled in count_mmac_params().
5975 * To disable these insane legacy behaviors, use:
5977 * %pragma preproc sane_empty_expansion yes
5979 *!macro-params-legacy [on] improperly calling multi-line macro for legacy support
5980 *! warns about \i{multi-line macros} being invoked
5981 *! with the wrong number of parameters, but for bug-compatibility
5982 *! with NASM versions older than 2.15, NASM tried to fix up the
5983 *! parameters to match the legacy behavior and call the macro anyway.
5984 *! This can happen in certain cases where there are empty arguments
5985 *! without braces, sometimes as a result of macro expansion.
5987 *! The legacy behavior is quite strange and highly context-dependent,
5988 *! and can be disabled with:
5990 *! \c %pragma preproc sane_empty_expansion true
5992 *! It is highly recommended to use this option in new code.
5994 if (!ppopt
.sane_empty_expansion
) {
5996 if (raw_nparam
== 0 && !empty_args
) {
5998 * A single all-whitespace parameter as the only thing?
5999 * Look for a one-argument macro, but don't adjust
6002 int bogus_nparam
= 1;
6004 found
= find_mmacro_in_list(m
, finding
, &bogus_nparam
, paramsp
);
6005 } else if (raw_nparam
> 1 && comma
) {
6006 Token
*comma_tail
= *comma
;
6009 * Drop the terminal argument and try again.
6010 * If we fail, we need to restore the comma to
6014 *nparamp
= raw_nparam
- 1;
6015 found
= find_mmacro_in_list(m
, finding
, nparamp
, paramsp
);
6017 free_tlist(comma_tail
);
6019 *comma
= comma_tail
;
6027 if (raw_nparam
> found
->nparam_min
&&
6028 raw_nparam
<= found
->nparam_min
+ found
->ndefs
) {
6029 /* Replace empty argument with default parameter */
6030 params
[raw_nparam
] =
6031 found
->defaults
[raw_nparam
- found
->nparam_min
];
6032 } else if (raw_nparam
> found
->nparam_max
&& found
->plus
) {
6033 /* Just drop the comma, don't adjust argument count */
6035 /* Drop argument. This may cause nparam < nparam_min. */
6036 params
[raw_nparam
] = NULL
;
6037 *nparamp
= nparam
= raw_nparam
- 1;
6042 if (raw_nparam
< found
->nparam_min
||
6043 (raw_nparam
> found
->nparam_max
&& !found
->plus
)) {
6044 nasm_warn(WARN_MACRO_PARAMS_LEGACY
,
6045 "improperly calling multi-line macro `%s' with %d parameters",
6046 found
->name
, raw_nparam
);
6048 nasm_warn(WARN_MACRO_PARAMS_LEGACY
,
6049 "dropping trailing empty parameter in call to multi-line macro `%s'", found
->name
);
6055 * After all that, we didn't find one with the right number of
6056 * parameters. Issue a warning, and fail to expand the macro.
6058 *!macro-params-multi [on] multi-line macro calls with wrong parameter count
6059 *! warns about \i{multi-line macros} being invoked
6060 *! with the wrong number of parameters. See \k{mlmacover} for an
6061 *! example of why you might want to disable this warning.
6066 nasm_warn(WARN_MACRO_PARAMS_MULTI
,
6067 "multi-line macro `%s' exists, but not taking %d parameter%s",
6068 finding
, nparam
, (nparam
== 1) ? "" : "s");
6069 nasm_free(*paramsp
);
6077 * Save MMacro invocation specific fields in
6078 * preparation for a recursive macro expansion
6080 static void push_mmacro(MMacro
*m
)
6082 MMacroInvocation
*i
;
6084 i
= nasm_malloc(sizeof(MMacroInvocation
));
6086 i
->params
= m
->params
;
6087 i
->iline
= m
->iline
;
6088 i
->nparam
= m
->nparam
;
6089 i
->rotate
= m
->rotate
;
6090 i
->paramlen
= m
->paramlen
;
6091 i
->unique
= m
->unique
;
6092 i
->condcnt
= m
->condcnt
;
6098 * Restore MMacro invocation specific fields that were
6099 * saved during a previous recursive macro expansion
6101 static void pop_mmacro(MMacro
*m
)
6103 MMacroInvocation
*i
;
6108 m
->params
= i
->params
;
6109 m
->iline
= i
->iline
;
6110 m
->nparam
= i
->nparam
;
6111 m
->rotate
= i
->rotate
;
6112 m
->paramlen
= i
->paramlen
;
6113 m
->unique
= i
->unique
;
6114 m
->condcnt
= i
->condcnt
;
6122 * List an mmacro call with arguments (-Lm option)
6124 static void list_mmacro_call(const MMacro
*m
)
6126 const char prefix
[] = " ;;; [macro] ";
6127 size_t namelen
, size
;
6132 namelen
= strlen(m
->iname
);
6133 size
= namelen
+ sizeof(prefix
); /* Includes final null (from prefix) */
6135 for (i
= 1; i
<= m
->nparam
; i
++) {
6137 size
+= 3; /* Braces and space/comma */
6138 list_for_each(t
, m
->params
[i
]) {
6139 if (j
++ >= m
->paramlen
[i
])
6141 size
+= (t
->type
== TOK_WHITESPACE
) ? 1 : t
->len
;
6145 buf
= p
= nasm_malloc(size
);
6146 p
= mempcpy(p
, prefix
, sizeof(prefix
) - 1);
6147 p
= mempcpy(p
, m
->iname
, namelen
);
6150 for (i
= 1; i
<= m
->nparam
; i
++) {
6153 list_for_each(t
, m
->params
[i
]) {
6154 if (j
++ >= m
->paramlen
[i
])
6156 p
= mempcpy(p
, tok_text(t
), t
->len
);
6162 *--p
= '\0'; /* Replace last delimeter with null */
6163 lfmt
->line(LIST_MACRO
, -1, buf
);
6168 * Expand the multi-line macro call made by the given line, if
6169 * there is one to be expanded. If there is, push the expansion on
6170 * istk->expansion and return 1. Otherwise return 0.
6172 static int expand_mmacro(Token
* tline
)
6174 Token
*startline
= tline
;
6175 Token
*label
= NULL
;
6176 bool dont_prepend
= false;
6177 Token
**params
, *t
, *tt
;
6186 /* if (!tok_type(t, TOK_ID)) Lino 02/25/02 */
6187 if (!tok_type(t
, TOK_ID
) && !tok_type(t
, TOK_LOCAL_MACRO
))
6189 m
= is_mmacro(t
, &nparam
, ¶ms
);
6191 mname
= tok_text(t
);
6195 * We have an id which isn't a macro call. We'll assume
6196 * it might be a label; we'll also check to see if a
6197 * colon follows it. Then, if there's another id after
6198 * that lot, we'll check it again for macro-hood.
6203 last
= t
, t
= t
->next
;
6204 if (tok_is(t
, ':')) {
6205 dont_prepend
= true;
6206 last
= t
, t
= t
->next
;
6208 last
= t
, t
= t
->next
;
6210 if (!tok_type(t
, TOK_ID
) || !(m
= is_mmacro(t
, &nparam
, ¶ms
)))
6213 mname
= tok_text(t
);
6217 if (unlikely(mmacro_deadman
.total
>= nasm_limit
[LIMIT_MMACROS
] ||
6218 mmacro_deadman
.levels
>= nasm_limit
[LIMIT_MACRO_LEVELS
])) {
6219 if (!mmacro_deadman
.triggered
) {
6220 nasm_nonfatal("interminable multiline macro recursion");
6221 mmacro_deadman
.triggered
= true;
6226 mmacro_deadman
.total
++;
6227 mmacro_deadman
.levels
++;
6230 * Fix up the parameters: this involves stripping leading and
6231 * trailing whitespace and stripping braces if they are present.
6233 nasm_newn(paramlen
, nparam
+1);
6235 for (i
= 1; (t
= params
[i
]); i
++) {
6236 bool braced
= false;
6239 bool comma
= !m
->plus
|| i
< nparam
;
6242 if (tok_is(t
, '{')) {
6250 for (; t
; t
= t
->next
) {
6256 if (t
->type
== TOK_OTHER
&& t
->len
== 1) {
6257 switch (t
->text
.a
[0]) {
6259 if (comma
&& !brace
)
6269 if (braced
&& !brace
) {
6270 paramlen
[i
] += white
;
6280 paramlen
[i
] += white
+ 1;
6288 * OK, we have a MMacro structure together with a set of
6289 * parameters. We must now go through the expansion and push
6290 * copies of each Line on to istk->expansion. Substitution of
6291 * parameter tokens and macro-local tokens doesn't get done
6292 * until the single-line macro substitution process; this is
6293 * because delaying them allows us to change the semantics
6294 * later through %rotate and give the right semantics for
6297 * First, push an end marker on to istk->expansion, mark this
6298 * macro as in progress, and set up its invocation-specific
6302 ll
->next
= istk
->expansion
;
6304 ll
->where
= istk
->where
;
6305 istk
->expansion
= ll
;
6308 * Save the previous MMacro expansion in the case of
6312 if (m
->max_depth
&& m
->in_progress
)
6319 m
->iname
= nasm_strdup(mname
);
6322 m
->paramlen
= paramlen
;
6323 m
->unique
= unique
++;
6326 m
->mstk
= istk
->mstk
;
6327 istk
->mstk
.mstk
= istk
->mstk
.mmac
= m
;
6329 list_for_each(l
, m
->expansion
) {
6331 ll
->next
= istk
->expansion
;
6332 istk
->expansion
= ll
;
6333 ll
->first
= dup_tlist(l
->first
, NULL
);
6334 ll
->where
= l
->where
;
6338 * If we had a label, and this macro definition does not include
6339 * a %00, push it on as the first line of, ot
6340 * the macro expansion.
6344 * We had a label. If this macro contains an %00 parameter,
6345 * save the value as a special parameter (which is what it
6346 * is), otherwise push it as the first line of the macro
6349 if (m
->capture_label
) {
6350 params
[0] = dup_Token(NULL
, label
);
6352 free_tlist(startline
);
6355 ll
->finishes
= NULL
;
6356 ll
->next
= istk
->expansion
;
6357 istk
->expansion
= ll
;
6358 ll
->first
= startline
;
6359 ll
->where
= istk
->where
;
6360 if (!dont_prepend
) {
6362 label
= label
->next
;
6363 label
->next
= tt
= make_tok_char(NULL
, ':');
6368 istk
->nolist
+= !!(m
->nolist
& NL_LIST
);
6369 istk
->noline
+= !!(m
->nolist
& NL_LINE
);
6371 if (!istk
->nolist
) {
6372 lfmt
->uplevel(LIST_MACRO
, 0);
6374 if (list_option('m'))
6375 list_mmacro_call(m
);
6379 src_macro_push(m
, istk
->where
);
6385 * This function decides if an error message should be suppressed.
6386 * It will never be called with a severity level of ERR_FATAL or
6389 static bool pp_suppress_error(errflags severity
)
6392 * If we're in a dead branch of IF or something like it, ignore the error.
6393 * However, because %else etc are evaluated in the state context
6394 * of the previous branch, errors might get lost:
6395 * %if 0 ... %else trailing garbage ... %endif
6396 * So %else etc should set the ERR_PP_PRECOND flag.
6398 if (istk
&& istk
->conds
&&
6399 ((severity
& ERR_PP_PRECOND
) ?
6400 istk
->conds
->state
== COND_NEVER
:
6401 !emitting(istk
->conds
->state
)))
6408 stdmac_file(const SMacro
*s
, Token
**params
, int nparams
)
6414 return make_tok_qstr(NULL
, src_get_fname());
6418 stdmac_line(const SMacro
*s
, Token
**params
, int nparams
)
6424 return make_tok_num(NULL
, src_get_linnum());
6428 stdmac_bits(const SMacro
*s
, Token
**params
, int nparams
)
6434 return make_tok_num(NULL
, globalbits
);
6438 stdmac_ptr(const SMacro
*s
, Token
**params
, int nparams
)
6444 switch (globalbits
) {
6446 return new_Token(NULL
, TOK_ID
, "word", 4);
6448 return new_Token(NULL
, TOK_ID
, "dword", 5);
6450 return new_Token(NULL
, TOK_ID
, "qword", 5);
6456 /* Add magic standard macros */
6457 struct magic_macros
{
6462 static const struct magic_macros magic_macros
[] =
6464 { "__?FILE?__", 0, stdmac_file
},
6465 { "__?LINE?__", 0, stdmac_line
},
6466 { "__?BITS?__", 0, stdmac_bits
},
6467 { "__?PTR?__", 0, stdmac_ptr
},
6471 static void pp_add_magic_stdmac(void)
6473 const struct magic_macros
*m
;
6478 for (m
= magic_macros
; m
->name
; m
++) {
6479 tmpl
.nparam
= m
->nparam
;
6480 tmpl
.expand
= m
->func
;
6481 define_smacro(m
->name
, true, NULL
, &tmpl
);
6486 pp_reset(const char *file
, enum preproc_mode mode
, struct strlist
*dep_list
)
6489 struct Include
*inc
;
6493 nested_mac_count
= 0;
6494 nested_rep_count
= 0;
6500 /* Reset options to default */
6504 use_loaded
= nasm_malloc(use_package_count
* sizeof(bool));
6505 memset(use_loaded
, 0, use_package_count
* sizeof(bool));
6507 /* First set up the top level input file */
6509 istk
->fp
= nasm_open_read(file
, NF_TEXT
);
6511 nasm_fatalf(ERR_NOFILE
, "unable to open input file `%s'%s%s",
6512 file
, errno
? " " : "", errno
? strerror(errno
) : "");
6515 istk
->where
= src_where();
6518 strlist_add(deplist
, file
);
6521 * Set up the stdmac packages as a virtual include file,
6522 * indicated by a null file pointer.
6527 inc
->where
= src_where();
6528 inc
->nolist
= !list_option('b');
6530 lfmt
->uplevel(LIST_INCLUDE
, 0);
6532 pp_add_magic_stdmac();
6534 if (tasm_compatible_mode
)
6535 pp_add_stdmac(nasm_stdmac_tasm
);
6537 pp_add_stdmac(nasm_stdmac_nasm
);
6538 pp_add_stdmac(nasm_stdmac_version
);
6541 pp_add_stdmac(extrastdmac
);
6543 stdmacpos
= stdmacros
[0];
6544 stdmacnext
= &stdmacros
[1];
6549 * Define the __?PASS?__ macro. This is defined here unlike all the
6550 * other builtins, because it is special -- it varies between
6551 * passes -- but there is really no particular reason to make it
6554 * 0 = dependencies only
6555 * 1 = preparatory passes
6557 * 3 = preproces only
6561 apass
= pass_final() ? 2 : 1;
6573 define_smacro("__?PASS?__", true, make_tok_num(NULL
, apass
), NULL
);
6576 static void pp_init(void)
6581 * Get a line of tokens. If we popped the macro expansion/include stack,
6582 * we return a pointer to the dummy token tok_pop; at that point if
6583 * istk is NULL then we have reached end of input;
6585 static Token tok_pop
; /* Dummy token placeholder */
6587 static Token
*pp_tokline(void)
6590 Line
*l
= istk
->expansion
;
6591 Token
*tline
= NULL
;
6595 * Fetch a tokenized line, either from the macro-expansion
6596 * buffer or from the input file.
6599 while (l
&& l
->finishes
) {
6600 MMacro
*fm
= l
->finishes
;
6602 nasm_assert(fm
== istk
->mstk
.mstk
);
6604 if (!fm
->name
&& fm
->in_progress
> 1) {
6606 * This is a macro-end marker for a macro with no
6607 * name, which means it's not really a macro at all
6608 * but a %rep block, and the `in_progress' field is
6609 * more than 1, meaning that we still need to
6610 * repeat. (1 means the natural last repetition; 0
6611 * means termination by %exitrep.) We have
6612 * therefore expanded up to the %endrep, and must
6613 * push the whole block on to the expansion buffer
6614 * again. We don't bother to remove the macro-end
6615 * marker: we'd only have to generate another one
6619 list_for_each(l
, fm
->expansion
) {
6623 ll
->next
= istk
->expansion
;
6624 ll
->first
= dup_tlist(l
->first
, NULL
);
6625 ll
->where
= l
->where
;
6626 istk
->expansion
= ll
;
6630 MMacro
*m
= istk
->mstk
.mstk
;
6633 * Check whether a `%rep' was started and not ended
6634 * within this macro expansion. This can happen and
6635 * should be detected. It's a fatal error because
6636 * I'm too confused to work out how to recover
6641 nasm_panic("defining with name in expansion");
6643 nasm_fatal("`%%rep' without `%%endrep' within"
6644 " expansion of macro `%s'", m
->name
);
6648 * FIXME: investigate the relationship at this point between
6649 * istk->mstk.mstk and fm
6651 istk
->mstk
= m
->mstk
;
6654 * This was a real macro call, not a %rep, and
6655 * therefore the parameter information needs to
6656 * be freed and the iteration count/nesting
6660 if (!--mmacro_deadman
.levels
) {
6662 * If all mmacro processing done,
6663 * clear all counters and the deadman
6666 nasm_zero(mmacro_deadman
); /* Clear all counters */
6676 nasm_free(m
->params
);
6677 free_tlist(m
->iline
);
6678 nasm_free(m
->paramlen
);
6679 fm
->in_progress
= 0;
6683 if (fm
->nolist
& NL_LIST
) {
6685 } else if (!istk
->nolist
) {
6686 lfmt
->downlevel(LIST_MACRO
);
6689 if (fm
->nolist
& NL_LINE
) {
6691 } else if (!istk
->noline
) {
6692 if (fm
== src_macro_current())
6694 src_update(l
->where
);
6697 istk
->where
= l
->where
;
6700 * FIXME It is incorrect to always free_mmacro here.
6701 * It leads to usage-after-free.
6703 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
6710 istk
->expansion
= l
->next
;
6716 do { /* until we get a line we can use */
6719 if (istk
->expansion
) { /* from a macro expansion */
6720 Line
*l
= istk
->expansion
;
6722 istk
->expansion
= l
->next
;
6723 istk
->where
= l
->where
;
6728 src_update(istk
->where
);
6730 if (!istk
->nolist
) {
6731 line
= detoken(tline
, false);
6732 lfmt
->line(LIST_MACRO
, istk
->where
.lineno
, line
);
6735 } else if ((line
= read_line())) {
6736 line
= prepreproc(line
);
6737 tline
= tokenize(line
);
6741 * The current file has ended; work down the istk
6749 /* nasm_fatal can't be conditionally suppressed */
6750 nasm_fatal("expected `%%endif' before end of file");
6753 list_for_each(is
, i
->next
) {
6755 lfmt
->downlevel(LIST_INCLUDE
);
6756 src_update(is
->where
);
6767 * We must expand MMacro parameters and MMacro-local labels
6768 * _before_ we plunge into directive processing, to cope
6769 * with things like `%define something %1' such as STRUC
6770 * uses. Unless we're _defining_ a MMacro, in which case
6771 * those tokens should be left alone to go into the
6772 * definition; and unless we're in a non-emitting
6773 * condition, in which case we don't want to meddle with
6777 !(istk
->conds
&& !emitting(istk
->conds
->state
)) &&
6778 !(istk
->mstk
.mmac
&& !istk
->mstk
.mmac
->in_progress
)) {
6779 tline
= expand_mmac_params(tline
);
6783 * Check the line to see if it's a preprocessor directive.
6785 if (do_directive(tline
, &dtline
) == DIRECTIVE_FOUND
) {
6788 } else if (defining
) {
6790 * We're defining a multi-line macro. We emit nothing
6792 * shove the tokenized line on to the macro definition.
6794 MMacro
*mmac
= defining
->dstk
.mmac
;
6798 l
->next
= defining
->expansion
;
6801 l
->where
= istk
->where
;
6802 defining
->expansion
= l
;
6805 * Remember if this mmacro expansion contains %00:
6806 * if it does, we will have to handle leading labels
6811 list_for_each(t
, tline
) {
6812 if (!memcmp(t
->text
.a
, "%00", 4))
6813 mmac
->capture_label
= true;
6816 } else if (istk
->conds
&& !emitting(istk
->conds
->state
)) {
6818 * We're in a non-emitting branch of a condition block.
6819 * Emit nothing at all, not even a blank line: when we
6820 * emerge from the condition we'll give a line-number
6821 * directive so we keep our place correctly.
6824 } else if (istk
->mstk
.mstk
&& !istk
->mstk
.mstk
->in_progress
) {
6826 * We're in a %rep block which has been terminated, so
6827 * we're walking through to the %endrep without
6828 * emitting anything. Emit nothing at all, not even a
6829 * blank line: when we emerge from the %rep block we'll
6830 * give a line-number directive so we keep our place
6835 tline
= expand_smacro(tline
);
6836 if (!expand_mmacro(tline
))
6842 static char *pp_getline(void)
6848 tline
= pp_tokline();
6849 if (tline
== &tok_pop
) {
6851 * We popped the macro/include stack. If istk is empty,
6852 * we are at end of input, otherwise just loop back.
6858 * De-tokenize the line and emit it.
6860 line
= detoken(tline
, true);
6866 if (list_option('e') && istk
&& !istk
->nolist
&& line
&& line
[0]) {
6867 char *buf
= nasm_strcat(" ;;; ", line
);
6868 lfmt
->line(LIST_MACRO
, -1, buf
);
6875 static void pp_cleanup_pass(void)
6878 if (defining
->name
) {
6879 nasm_nonfatal("end of file while still defining macro `%s'",
6882 nasm_nonfatal("end of file while still in %%rep");
6885 free_mmacro(defining
);
6900 src_set_fname(NULL
);
6903 static void pp_cleanup_session(void)
6905 nasm_free(use_loaded
);
6912 static void pp_include_path(struct strlist
*list
)
6917 static void pp_pre_include(char *fname
)
6919 Token
*inc
, *space
, *name
;
6922 name
= new_Token(NULL
, TOK_INTERNAL_STRING
, fname
, 0);
6923 space
= new_White(name
);
6924 inc
= new_Token(space
, TOK_PREPROC_ID
, "%include", 0);
6926 l
= nasm_malloc(sizeof(Line
));
6933 static void pp_pre_define(char *definition
)
6939 equals
= strchr(definition
, '=');
6940 space
= new_White(NULL
);
6941 def
= new_Token(space
, TOK_PREPROC_ID
, "%define", 0);
6944 space
->next
= tokenize(definition
);
6948 /* We can't predefine a TOK_LOCAL_MACRO for obvious reasons... */
6949 if (space
->next
->type
!= TOK_PREPROC_ID
&&
6950 space
->next
->type
!= TOK_ID
)
6951 nasm_warn(WARN_OTHER
, "pre-defining non ID `%s\'\n", definition
);
6953 l
= nasm_malloc(sizeof(Line
));
6960 static void pp_pre_undefine(char *definition
)
6965 space
= new_White(NULL
);
6966 def
= new_Token(space
, TOK_PREPROC_ID
, "%undef", 0);
6967 space
->next
= tokenize(definition
);
6969 l
= nasm_malloc(sizeof(Line
));
6976 /* Insert an early preprocessor command that doesn't need special handling */
6977 static void pp_pre_command(const char *what
, char *string
)
6983 def
= tokenize(string
);
6985 space
= new_White(def
);
6986 cmd
= nasm_strcat(what
[0] == '%' ? "" : "%", what
);
6987 def
= new_Token(space
, TOK_PREPROC_ID
, cmd
, nasm_last_string_len());
6991 l
= nasm_malloc(sizeof(Line
));
6998 static void pp_add_stdmac(macros_t
*macros
)
7002 /* Find the end of the list and avoid duplicates */
7003 for (mp
= stdmacros
; *mp
; mp
++) {
7005 return; /* Nothing to do */
7008 nasm_assert(mp
< &stdmacros
[ARRAY_SIZE(stdmacros
)-1]);
7013 static void pp_extra_stdmac(macros_t
*macros
)
7015 extrastdmac
= macros
;
7018 /* Create a numeric token */
7019 static Token
*make_tok_num(Token
*next
, int64_t val
)
7022 int len
= snprintf(numbuf
, sizeof(numbuf
), "%"PRId64
"", val
);
7023 return new_Token(next
, TOK_NUMBER
, numbuf
, len
);
7026 /* Create a quoted string token */
7027 static Token
*make_tok_qstr_len(Token
*next
, const char *str
, size_t len
)
7029 char *p
= nasm_quote(str
, &len
);
7030 return new_Token_free(next
, TOK_STRING
, p
, len
);
7032 static Token
*make_tok_qstr(Token
*next
, const char *str
)
7034 return make_tok_qstr_len(next
, str
, strlen(str
));
7037 /* Create a single-character operator token */
7038 static Token
*make_tok_char(Token
*next
, char op
)
7040 Token
*t
= new_Token(next
, TOK_OTHER
, NULL
, 1);
7046 * Descent the macro hierarchy and display the expansion after
7047 * encountering an error message.
7049 static void pp_error_list_macros(errflags severity
)
7053 severity
|= ERR_PP_LISTMACRO
| ERR_NO_SEVERITY
| ERR_HERE
;
7055 while ((m
= src_error_down())) {
7056 nasm_error(severity
, "... from macro `%s' defined", m
->name
);
7062 const struct preproc_ops nasmpp
= {
7074 pp_error_list_macros
,