1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2019 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
79 typedef struct SMacro SMacro
;
80 typedef struct MMacro MMacro
;
81 typedef struct MMacroInvocation MMacroInvocation
;
82 typedef struct Context Context
;
83 typedef struct Token Token
;
84 typedef struct Line Line
;
85 typedef struct Include Include
;
86 typedef struct Cond Cond
;
89 * This is the internal form which we break input lines up into.
90 * Typically stored in linked lists.
92 * Note that `type' serves a double meaning: TOK_SMAC_START_PARAMS is
93 * not necessarily used as-is, but is also used to encode the number
94 * and expansion type of substituted parameter. So in the definition
96 * %define a(x,=y) ( (x) & ~(y) )
98 * the token representing `x' will have its type changed to
99 * tok_smac_param(0) but the one representing `y' will be
100 * tok_smac_param(1); see the accessor functions below.
102 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
103 * which doesn't need quotes around it. Used in the pre-include
104 * mechanism as an alternative to trying to find a sensible type of
105 * quote to use on the filename we were passed.
108 TOK_NONE
= 0, TOK_WHITESPACE
, TOK_COMMENT
,
109 TOK_CORRUPT
, /* Token text modified in an unsafe manner, now bogus */
110 TOK_BLOCK
, /* Storage block pointer, not a real token */
112 TOK_PREPROC_ID
, TOK_MMACRO_PARAM
, TOK_LOCAL_SYMBOL
,
113 TOK_LOCAL_MACRO
, TOK_ENVIRON
, TOK_STRING
,
114 TOK_NUMBER
, TOK_FLOAT
, TOK_OTHER
,
116 TOK_PREPROC_Q
, TOK_PREPROC_QQ
,
118 TOK_COND_COMMA
, /* %, */
119 TOK_INDIRECT
, /* %[...] */
120 TOK_SMAC_START_PARAMS
, /* MUST BE LAST IN THE LIST!!! */
121 TOK_MAX
= INT_MAX
/* Keep compiler from reducing the range */
124 static inline enum pp_token_type
tok_smac_param(int param
)
126 return TOK_SMAC_START_PARAMS
+ param
;
128 static int smac_nparam(enum pp_token_type toktype
)
130 return toktype
- TOK_SMAC_START_PARAMS
;
132 static bool is_smac_param(enum pp_token_type toktype
)
134 return toktype
>= TOK_SMAC_START_PARAMS
;
137 #define PP_CONCAT_MASK(x) (1U << (x))
139 struct tokseq_match
{
145 * This is tuned so struct Token should be 64 bytes on 64-bit
146 * systems and 32 bytes on 32-bit systems. It enables them
147 * to be nicely cache aligned, and the text to still be kept
148 * inline for nearly all tokens.
150 * We prohibit tokens of length > MAX_TEXT even though
151 * length here is an unsigned int; this avoids problems
152 * if the length is passed through an interface with type "int",
153 * and is absurdly large anyway.
155 * For the text mode, in pointer mode the pointer is stored at the end
156 * of the union and the pad field is cleared. This allows short tokens
157 * to be unconditionally tested for by only looking at the first text
158 * bytes and not examining the type or len fields.
160 #define INLINE_TEXT (7*sizeof(char *)-sizeof(enum pp_token_type)-sizeof(unsigned int)-1)
161 #define MAX_TEXT (INT_MAX-2)
165 enum pp_token_type type
;
168 char a
[INLINE_TEXT
+1];
170 char pad
[INLINE_TEXT
+1 - sizeof(char *)];
177 * Note on the storage of both SMacro and MMacros: the hash table
178 * indexes them case-insensitively, and we then have to go through a
179 * linked list of potential case aliases (and, for MMacros, parameter
180 * ranges); this is to preserve the matching semantics of the earlier
181 * code. If the number of case aliases for a specific macro is a
182 * performance issue, you may want to reconsider your coding style.
186 * Function call tp obtain the expansion of an smacro
188 typedef Token
*(*ExpandSMacro
)(const SMacro
*s
, Token
**params
, int nparams
);
191 * Store the definition of a single-line macro.
195 SPARM_EVAL
= 1, /* Evaluate as a numeric expression (=) */
196 SPARM_STR
= 2, /* Convert to quoted string ($) */
197 SPARM_NOSTRIP
= 4, /* Don't strip braces (!) */
198 SPARM_GREEDY
= 8 /* Greedy final parameter (+) */
203 enum sparmflags flags
;
207 SMacro
*next
; /* MUST BE FIRST - see free_smacro() */
212 struct smac_param
*params
;
217 bool alias
; /* This is an alias macro */
221 * Store the definition of a multi-line macro. This is also used to
222 * store the interiors of `%rep...%endrep' blocks, which are
223 * effectively self-re-invoking multi-line macros which simply
224 * don't have a name or bother to appear in the hash tables. %rep
225 * blocks are signified by having a NULL `name' field.
227 * In a MMacro describing a `%rep' block, the `in_progress' field
228 * isn't merely boolean, but gives the number of repeats left to
231 * The `next' field is used for storing MMacros in hash tables; the
232 * `next_active' field is for stacking them on istk entries.
234 * When a MMacro is being expanded, `params', `iline', `nparam',
235 * `paramlen', `rotate' and `unique' are local to the invocation.
239 * Expansion stack. Note that .mmac can point back to the macro itself,
240 * whereas .mstk cannot.
243 MMacro
*mstk
; /* Any expansion, real macro or not */
244 MMacro
*mmac
; /* Highest level actual mmacro */
250 MMacroInvocation
*prev
; /* previous invocation */
253 int nparam_min
, nparam_max
;
255 bool plus
; /* is the last parameter greedy? */
256 bool nolist
; /* is this macro listing-inhibited? */
257 bool capture_label
; /* macro definition has %00; capture label */
258 int32_t in_progress
; /* is this macro currently being expanded? */
259 int32_t max_depth
; /* maximum number of recursive expansions allowed */
260 Token
*dlist
; /* All defaults as one list */
261 Token
**defaults
; /* Parameter default pointers */
262 int ndefs
; /* number of default parameters */
265 struct mstk mstk
; /* Macro expansion stack */
266 struct mstk dstk
; /* Macro definitions stack */
267 Token
**params
; /* actual parameters */
268 Token
*iline
; /* invocation line */
269 unsigned int nparam
, rotate
;
270 char *iname
; /* name invoked as */
273 int lineno
; /* Current line number on expansion */
274 uint64_t condcnt
; /* number of if blocks... */
276 const char *fname
; /* File where defined */
277 int32_t xline
; /* First line in macro */
281 /* Store the definition of a multi-line macro, as defined in a
282 * previous recursive macro expansion.
286 struct MMacroInvocation
{
287 MMacroInvocation
*prev
; /* previous invocation */
288 Token
**params
; /* actual parameters */
289 Token
*iline
; /* invocation line */
290 unsigned int nparam
, rotate
;
299 * The context stack is composed of a linked list of these.
304 struct hash_table localmac
;
310 static inline const char *tok_text(const struct Token
*t
)
312 return (t
->len
<= INLINE_TEXT
) ? t
->text
.a
: t
->text
.p
.ptr
;
316 * Returns a mutable pointer to the text buffer. The text can be changed,
317 * but the length MUST NOT CHANGE, in either direction; nor is it permitted
318 * to pad with null characters to create an artificially shorter string.
320 static inline char *tok_text_buf(struct Token
*t
)
322 return (t
->len
<= INLINE_TEXT
) ? t
->text
.a
: t
->text
.p
.ptr
;
325 static inline unsigned int tok_check_len(size_t len
)
327 if (unlikely(len
> MAX_TEXT
))
328 nasm_fatal("impossibly large token");
333 /* strlen() variant useful for set_text() and its variants */
334 static size_t tok_strlen(const char *str
)
336 return strnlen(str
, MAX_TEXT
+1);
340 * Set the text field to a copy of the given string; the length if
341 * not given should be obtained with tok_strlen().
343 static Token
*set_text(struct Token
*t
, const char *text
, size_t len
)
347 if (t
->len
> INLINE_TEXT
)
348 nasm_free(t
->text
.p
.ptr
);
350 nasm_zero(t
->text
.a
);
352 t
->len
= tok_check_len(len
);
353 textp
= (len
> INLINE_TEXT
)
354 ? (t
->text
.p
.ptr
= nasm_malloc(len
+1)) : t
->text
.a
;
355 memcpy(textp
, text
, len
+1);
360 * Set the text field to the existing pre-allocated string, either
361 * taking over or freeing the allocation in the process.
363 static Token
*set_text_free(struct Token
*t
, char *text
, unsigned int len
)
365 if (t
->len
> INLINE_TEXT
)
366 nasm_free(t
->text
.p
.ptr
);
368 nasm_zero(t
->text
.a
);
370 t
->len
= tok_check_len(len
);
371 if (len
> INLINE_TEXT
) {
372 t
->text
.p
.ptr
= text
;
374 memcpy(t
->text
.a
, text
, len
+1);
382 * Allocate a new buffer containing a copy of the text field
385 static char *dup_text(const struct Token
*t
)
387 size_t size
= t
->len
+ 1;
388 char *p
= nasm_malloc(size
);
390 return memcpy(p
, tok_text(t
), size
);
394 * Multi-line macro definitions are stored as a linked list of
395 * these, which is essentially a container to allow several linked
398 * Note that in this module, linked lists are treated as stacks
399 * wherever possible. For this reason, Lines are _pushed_ on to the
400 * `expansion' field in MMacro structures, so that the linked list,
401 * if walked, would give the macro lines in reverse order; this
402 * means that we can walk the list when expanding a macro, and thus
403 * push the lines on to the `expansion' field in _istk_ in reverse
404 * order (so that when popped back off they are in the right
405 * order). It may seem cockeyed, and it relies on my design having
406 * an even number of steps in, but it works...
408 * Some of these structures, rather than being actual lines, are
409 * markers delimiting the end of the expansion of a given macro.
410 * This is for use in the cycle-tracking and %rep-handling code.
411 * Such structures have `finishes' non-NULL, and `first' NULL. All
412 * others have `finishes' NULL, but `first' may still be NULL if
422 * To handle an arbitrary level of file inclusion, we maintain a
423 * stack (ie linked list) of these things.
437 * File real name hash, so we don't have to re-search the include
438 * path for every pass (and potentially more than that if a file
439 * is used more than once.)
441 struct hash_table FileHash
;
444 * Counters to trap on insane macro recursion or processing.
445 * Note: for smacros these count *down*, for mmacros they count *up*.
448 int64_t total
; /* Total number of macros/tokens */
449 int64_t levels
; /* Descent depth across all macros */
450 bool triggered
; /* Already triggered, no need for error msg */
453 static struct deadman smacro_deadman
, mmacro_deadman
;
456 * Conditional assembly: we maintain a separate stack of these for
457 * each level of file inclusion. (The only reason we keep the
458 * stacks separate is to ensure that a stray `%endif' in a file
459 * included from within the true branch of a `%if' won't terminate
460 * it and cause confusion: instead, rightly, it'll cause an error.)
464 * These states are for use just after %if or %elif: IF_TRUE
465 * means the condition has evaluated to truth so we are
466 * currently emitting, whereas IF_FALSE means we are not
467 * currently emitting but will start doing so if a %else comes
468 * up. In these states, all directives are admissible: %elif,
469 * %else and %endif. (And of course %if.)
471 COND_IF_TRUE
, COND_IF_FALSE
,
473 * These states come up after a %else: ELSE_TRUE means we're
474 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
475 * any %elif or %else will cause an error.
477 COND_ELSE_TRUE
, COND_ELSE_FALSE
,
479 * These states mean that we're not emitting now, and also that
480 * nothing until %endif will be emitted at all. COND_DONE is
481 * used when we've had our moment of emission
482 * and have now started seeing %elifs. COND_NEVER is used when
483 * the condition construct in question is contained within a
484 * non-emitting branch of a larger condition construct,
485 * or if there is an error.
487 COND_DONE
, COND_NEVER
491 enum cond_state state
;
493 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
496 * These defines are used as the possible return values for do_directive
498 #define NO_DIRECTIVE_FOUND 0
499 #define DIRECTIVE_FOUND 1
502 * Condition codes. Note that we use c_ prefix not C_ because C_ is
503 * used in nasm.h for the "real" condition codes. At _this_ level,
504 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
505 * ones, so we need a different enum...
507 static const char * const conditions
[] = {
508 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
509 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
510 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
513 c_A
, c_AE
, c_B
, c_BE
, c_C
, c_CXZ
, c_E
, c_ECXZ
, c_G
, c_GE
, c_L
, c_LE
,
514 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, c_NE
, c_NG
, c_NGE
, c_NL
, c_NLE
, c_NO
,
515 c_NP
, c_NS
, c_NZ
, c_O
, c_P
, c_PE
, c_PO
, c_RCXZ
, c_S
, c_Z
,
518 static const enum pp_conds inverse_ccs
[] = {
519 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, -1, c_NE
, -1, c_NG
, c_NGE
, c_NL
, c_NLE
,
520 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
,
521 c_Z
, c_NO
, c_NP
, c_PO
, c_PE
, -1, c_NS
, c_NZ
527 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
528 static int is_condition(enum preproc_token arg
)
530 return PP_IS_COND(arg
) || (arg
== PP_ELSE
) || (arg
== PP_ENDIF
);
533 /* For TASM compatibility we need to be able to recognise TASM compatible
534 * conditional compilation directives. Using the NASM pre-processor does
535 * not work, so we look for them specifically from the following list and
536 * then jam in the equivalent NASM directive into the input stream.
540 TM_ARG
, TM_ELIF
, TM_ELSE
, TM_ENDIF
, TM_IF
, TM_IFDEF
, TM_IFDIFI
,
541 TM_IFNDEF
, TM_INCLUDE
, TM_LOCAL
544 static const char * const tasm_directives
[] = {
545 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
546 "ifndef", "include", "local"
549 static int StackSize
= 4;
550 static const char *StackPointer
= "ebp";
551 static int ArgOffset
= 8;
552 static int LocalOffset
= 0;
554 static Context
*cstk
;
555 static Include
*istk
;
556 static const struct strlist
*ipath_list
;
557 static bool do_aliases
;
559 static struct strlist
*deplist
;
561 static uint64_t unique
; /* unique identifier numbers */
563 static Line
*predef
= NULL
;
564 static bool do_predef
;
565 static enum preproc_mode pp_mode
;
568 * The current set of multi-line macros we have defined.
570 static struct hash_table mmacros
;
573 * The current set of single-line macros we have defined.
575 static struct hash_table smacros
;
578 * The multi-line macro we are currently defining, or the %rep
579 * block we are currently reading, if any.
581 static MMacro
*defining
;
583 static uint64_t nested_mac_count
;
584 static uint64_t nested_rep_count
;
587 * The number of macro parameters to allocate space for at a time.
589 #define PARAM_DELTA 16
592 * The standard macro set: defined in macros.c in a set of arrays.
593 * This gives our position in any macro set, while we are processing it.
594 * The stdmacset is an array of such macro sets.
596 static macros_t
*stdmacpos
;
597 static macros_t
**stdmacnext
;
598 static macros_t
*stdmacros
[8];
599 static macros_t
*extrastdmac
;
602 * Map of which %use packages have been loaded
604 static bool *use_loaded
;
607 * Forward declarations.
609 static void pp_add_stdmac(macros_t
*macros
);
610 static Token
*expand_mmac_params(Token
* tline
);
611 static Token
*expand_smacro(Token
* tline
);
612 static Token
*expand_id(Token
* tline
);
613 static Context
*get_ctx(const char *name
, const char **namep
);
614 static Token
*make_tok_num(Token
*next
, int64_t val
);
615 static Token
*make_tok_qstr(Token
*next
, const char *str
);
616 static Token
*make_tok_char(Token
*next
, char op
);
617 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
618 const char *text
, size_t txtlen
);
619 static Token
*new_Token_free(Token
* next
, enum pp_token_type type
,
620 char *text
, size_t txtlen
);
621 static Token
*dup_Token(Token
*next
, const Token
*src
);
622 static Token
*new_White(Token
*next
);
623 static Token
*delete_Token(Token
*t
);
624 static Token
*steal_Token(Token
*dst
, Token
*src
);
625 static const struct use_package
*
626 get_use_pkg(Token
*t
, const char *dname
, const char **name
);
628 /* Safe test for token type, false on x == NULL */
629 static inline bool tok_type(const Token
*x
, enum pp_token_type t
)
631 return x
&& x
->type
== t
;
634 /* Whitespace token? */
635 static inline bool tok_white(const Token
*x
)
637 return tok_type(x
, TOK_WHITESPACE
);
640 /* Skip past any whitespace */
641 static inline Token
*skip_white(Token
*x
)
649 /* Delete any whitespace */
650 static Token
*zap_white(Token
*x
)
659 * Single special character tests. The use of & rather than && is intentional; it
660 * tells the compiler that it is safe to access text.a[1] unconditionally; hopefully
661 * a smart compiler should turn it into a 16-bit memory reference.
663 static inline bool tok_is(const Token
*x
, char c
)
665 return x
&& ((x
->text
.a
[0] == c
) & !x
->text
.a
[1]);
668 /* True if any other kind of token that "c", but not NULL */
669 static inline bool tok_isnt(const Token
*x
, char c
)
671 return x
&& !((x
->text
.a
[0] == c
) & !x
->text
.a
[1]);
675 * Unquote a token if it is a string, and set its type to
676 * TOK_INTERNAL_STRING.
678 static const char *unquote_token(Token
*t
)
680 if (t
->type
!= TOK_STRING
)
683 t
->type
= TOK_INTERNAL_STRING
;
685 if (t
->len
> INLINE_TEXT
) {
686 char *p
= t
->text
.p
.ptr
;
688 t
->len
= nasm_unquote(p
, NULL
);
690 if (t
->len
<= INLINE_TEXT
) {
691 nasm_zero(t
->text
.a
);
692 memcpy(t
->text
.a
, p
, t
->len
);
699 t
->len
= nasm_unquote(t
->text
.a
, NULL
);
704 static const char *unquote_token_cstr(Token
*t
)
706 if (t
->type
!= TOK_STRING
)
709 t
->type
= TOK_INTERNAL_STRING
;
711 if (t
->len
> INLINE_TEXT
) {
712 char *p
= t
->text
.p
.ptr
;
714 t
->len
= nasm_unquote_cstr(p
, NULL
);
716 if (t
->len
<= INLINE_TEXT
) {
717 nasm_zero(t
->text
.a
);
718 memcpy(t
->text
.a
, p
, t
->len
);
725 t
->len
= nasm_unquote_cstr(t
->text
.a
, NULL
);
730 static Token
*quote_internal_string_token(Token
*t
)
735 p
= nasm_quote(tok_text(t
), &len
);
736 t
->type
= TOK_STRING
;
737 return set_text_free(t
, p
, len
);
740 static inline Token
*quote_token(Token
*t
)
742 if (likely(!tok_is(t
, TOK_INTERNAL_STRING
)))
745 return quote_internal_string_token(t
);
749 * In-place reverse a list of tokens.
751 static Token
*reverse_tokens(Token
*t
)
767 * getenv() variant operating on an input token
769 static const char *pp_getenv(const Token
*t
, bool warn
)
771 const char *txt
= tok_text(t
);
774 bool is_string
= false;
781 txt
+= 2; /* Skip leading %! */
782 is_string
= nasm_isquote(*txt
);
789 case TOK_INTERNAL_STRING
:
799 buf
= nasm_strdup(txt
);
800 nasm_unquote_cstr(buf
, NULL
);
807 *!environment [on] nonexistent environment variable
808 *! warns if a nonexistent environment variable
809 *! is accessed using the \c{%!} preprocessor
810 *! construct (see \k{getenv}.) Such environment
811 *! variables are treated as empty (with this
812 *! warning issued) starting in NASM 2.15;
813 *! earlier versions of NASM would treat this as
816 nasm_warn(WARN_ENVIRONMENT
, "nonexistent environment variable `%s'", txt
);
827 * Handle TASM specific directives, which do not contain a % in
828 * front of them. We do it here because I could not find any other
829 * place to do it for the moment, and it is a hack (ideally it would
830 * be nice to be able to use the NASM pre-processor to do it).
832 static char *check_tasm_directive(char *line
)
834 int32_t i
, j
, k
, m
, len
;
835 char *p
, *q
, *oldline
, oldchar
;
837 p
= nasm_skip_spaces(line
);
839 /* Binary search for the directive name */
841 j
= ARRAY_SIZE(tasm_directives
);
842 q
= nasm_skip_word(p
);
849 m
= nasm_stricmp(p
, tasm_directives
[k
]);
851 /* We have found a directive, so jam a % in front of it
852 * so that NASM will then recognise it as one if it's own.
857 line
= nasm_malloc(len
+ 2);
859 if (k
== TM_IFDIFI
) {
861 * NASM does not recognise IFDIFI, so we convert
862 * it to %if 0. This is not used in NASM
863 * compatible code, but does need to parse for the
864 * TASM macro package.
866 strcpy(line
+ 1, "if 0");
868 memcpy(line
+ 1, p
, len
+ 1);
883 * The pre-preprocessing stage... This function translates line
884 * number indications as they emerge from GNU cpp (`# lineno "file"
885 * flags') into NASM preprocessor line number indications (`%line
888 static char *prepreproc(char *line
)
891 char *fname
, *oldline
;
893 if (line
[0] == '#' && line
[1] == ' ') {
896 lineno
= atoi(fname
);
897 fname
+= strspn(fname
, "0123456789 ");
900 fnlen
= strcspn(fname
, "\"");
901 line
= nasm_malloc(20 + fnlen
);
902 snprintf(line
, 20 + fnlen
, "%%line %d %.*s", lineno
, fnlen
, fname
);
905 if (tasm_compatible_mode
)
906 return check_tasm_directive(line
);
911 * Free a linked list of tokens.
913 static void free_tlist(Token
* list
)
916 list
= delete_Token(list
);
920 * Free a linked list of lines.
922 static void free_llist(Line
* list
)
925 list_for_each_safe(l
, tmp
, list
) {
926 free_tlist(l
->first
);
932 * Free an array of linked lists of tokens
934 static void free_tlist_array(Token
**array
, size_t nlists
)
936 Token
**listp
= array
;
939 free_tlist(*listp
++);
945 * Duplicate a linked list of tokens.
947 static Token
*dup_tlist(const Token
*list
, Token
***tailp
)
949 Token
*newlist
= NULL
;
950 Token
**tailpp
= &newlist
;
953 list_for_each(t
, list
) {
955 *tailpp
= nt
= dup_Token(NULL
, t
);
968 * Duplicate a linked list of tokens with a maximum count
970 static Token
*dup_tlistn(const Token
*list
, size_t cnt
, Token
***tailp
)
972 Token
*newlist
= NULL
;
973 Token
**tailpp
= &newlist
;
976 list_for_each(t
, list
) {
980 *tailpp
= nt
= dup_Token(NULL
, t
);
994 * Duplicate a linked list of tokens in reverse order
996 static Token
*dup_tlist_reverse(const Token
*list
, Token
*tail
)
1000 list_for_each(t
, list
)
1001 tail
= dup_Token(tail
, t
);
1009 static void free_mmacro(MMacro
* m
)
1012 free_tlist(m
->dlist
);
1013 nasm_free(m
->defaults
);
1014 free_llist(m
->expansion
);
1019 * Clear or free an SMacro
1021 static void free_smacro_members(SMacro
*s
)
1025 for (i
= 0; i
< s
->nparam
; i
++) {
1026 if (s
->params
[i
].name
.len
> INLINE_TEXT
)
1027 nasm_free(s
->params
[i
].name
.text
.p
.ptr
);
1029 nasm_free(s
->params
);
1032 free_tlist(s
->expansion
);
1035 static void clear_smacro(SMacro
*s
)
1037 free_smacro_members(s
);
1038 /* Wipe everything except the next pointer */
1039 memset(&s
->next
+ 1, 0, sizeof *s
- sizeof s
->next
);
1045 static void free_smacro(SMacro
*s
)
1047 free_smacro_members(s
);
1052 * Free all currently defined macros, and free the hash tables
1054 static void free_smacro_table(struct hash_table
*smt
)
1056 struct hash_iterator it
;
1057 const struct hash_node
*np
;
1059 hash_for_each(smt
, it
, np
) {
1061 SMacro
*s
= np
->data
;
1062 nasm_free((void *)np
->key
);
1063 list_for_each_safe(s
, tmp
, s
)
1069 static void free_mmacro_table(struct hash_table
*mmt
)
1071 struct hash_iterator it
;
1072 const struct hash_node
*np
;
1074 hash_for_each(mmt
, it
, np
) {
1076 MMacro
*m
= np
->data
;
1077 nasm_free((void *)np
->key
);
1078 list_for_each_safe(m
, tmp
, m
)
1084 static void free_macros(void)
1086 free_smacro_table(&smacros
);
1087 free_mmacro_table(&mmacros
);
1091 * Initialize the hash tables
1093 static void init_macros(void)
1098 * Pop the context stack.
1100 static void ctx_pop(void)
1105 free_smacro_table(&c
->localmac
);
1106 nasm_free((char *)c
->name
);
1111 * Search for a key in the hash index; adding it if necessary
1112 * (in which case we initialize the data pointer to NULL.)
1115 hash_findi_add(struct hash_table
*hash
, const char *str
)
1117 struct hash_insert hi
;
1120 size_t l
= strlen(str
) + 1;
1122 r
= hash_findib(hash
, str
, l
, &hi
);
1126 strx
= nasm_malloc(l
); /* Use a more efficient allocator here? */
1127 memcpy(strx
, str
, l
);
1128 return hash_add(&hi
, strx
, NULL
);
1132 * Like hash_findi, but returns the data element rather than a pointer
1133 * to it. Used only when not adding a new element, hence no third
1137 hash_findix(struct hash_table
*hash
, const char *str
)
1141 p
= hash_findi(hash
, str
, NULL
);
1142 return p
? *p
: NULL
;
1146 * read line from standart macros set,
1147 * if there no more left -- return NULL
1149 static char *line_from_stdmac(void)
1152 const unsigned char *p
= stdmacpos
;
1160 * 32-126 is ASCII, 127 is end of line, 128-31 are directives
1161 * (allowed to wrap around) corresponding to PP_* tokens 0-159.
1163 while ((c
= *p
++) != 127) {
1164 uint8_t ndir
= c
- 128;
1166 len
+= pp_directives_len
[ndir
] + 1;
1171 line
= nasm_malloc(len
+ 1);
1174 while ((c
= *stdmacpos
++) != 127) {
1175 uint8_t ndir
= c
- 128;
1176 if (ndir
< 256-96) {
1177 memcpy(q
, pp_directives
[ndir
], pp_directives_len
[ndir
]);
1178 q
+= pp_directives_len
[ndir
];
1187 if (*stdmacpos
== 127) {
1188 /* This was the last of this particular macro set */
1191 stdmacpos
= *stdmacnext
++;
1192 } else if (do_predef
) {
1196 * Nasty hack: here we push the contents of
1197 * `predef' on to the top-level expansion stack,
1198 * since this is the most convenient way to
1199 * implement the pre-include and pre-define
1202 list_for_each(pd
, predef
) {
1204 l
->next
= istk
->expansion
;
1205 l
->first
= dup_tlist(pd
->first
, NULL
);
1208 istk
->expansion
= l
;
1218 * Read a line from a file. Return NULL on end of file.
1220 static char *line_from_file(FILE *f
)
1223 unsigned int size
, next
;
1224 const unsigned int delta
= 512;
1225 const unsigned int pad
= 8;
1226 unsigned int nr_cont
= 0;
1232 p
= buffer
= nasm_malloc(size
);
1265 case 032: /* ^Z = legacy MS-DOS end of file mark */
1272 if (next
== '\r' || next
== '\n') {
1280 if (p
>= (buffer
+ size
- pad
)) {
1281 buffer
= nasm_realloc(buffer
, size
+ delta
);
1282 p
= buffer
+ size
- pad
;
1289 lineno
= src_get_linnum() + istk
->lineinc
+
1290 (nr_cont
* istk
->lineinc
);
1291 src_set_linnum(lineno
);
1297 * Common read routine regardless of source
1299 static char *read_line(void)
1305 line
= line_from_file(f
);
1307 line
= line_from_stdmac();
1313 lfmt
->line(LIST_READ
, src_get_linnum(), line
);
1319 * Tokenize a line of text. This is a very simple process since we
1320 * don't need to parse the value out of e.g. numeric tokens: we
1321 * simply split one string into many.
1323 static Token
*tokenize(const char *line
)
1325 enum pp_token_type type
;
1327 Token
*t
, **tail
= &list
;
1330 const char *p
= line
;
1331 const char *ep
= NULL
; /* End of token, for trimming the end */
1333 char firstchar
= *p
; /* Can be used to override the first char */
1337 * Preprocessor construct; find the end of the token.
1338 * Classification is handled later, because %{...} can be
1339 * used to create any preprocessor token.
1342 if (*p
== '+' && !nasm_isdigit(p
[1])) {
1345 } else if (nasm_isdigit(*p
) ||
1346 ((*p
== '-' || *p
== '+') && nasm_isdigit(p
[1]))) {
1350 while (nasm_isdigit(*p
));
1351 } else if (*p
== '{' || *p
== '[') {
1352 /* %{...} or %[...] */
1353 char firstchar
= *p
;
1354 char endchar
= *p
+ 2; /* } or ] */
1356 line
+= (*p
++ == '{'); /* Skip { but not [ (yet) */
1358 if (*p
== firstchar
) {
1360 } else if (*p
== endchar
) {
1362 } else if (nasm_isquote(*p
)) {
1363 p
= nasm_skip_string(p
);
1367 * *p can have been advanced to a null character by
1368 * nasm_skip_string()
1371 nasm_warn(WARN_OTHER
, "unterminated %%%c construct",
1377 ep
= lvl
? p
: p
-1; /* Terminal character not part of token */
1378 } else if (*p
== '?') {
1383 } else if (*p
== '!') {
1384 /* Environment variable reference */
1386 if (nasm_isidchar(*p
)) {
1390 while (nasm_isidchar(*p
));
1391 } else if (nasm_isquote(*p
)) {
1392 p
= nasm_skip_string(p
);
1396 nasm_nonfatalf(ERR_PASS1
, "unterminated %%! string");
1398 /* %! without anything else... */
1400 } else if (*p
== ',') {
1401 /* Conditional comma */
1403 } else if (nasm_isidchar(*p
) ||
1404 ((*p
== '%' || *p
== '$') && nasm_isidchar(p
[1]))) {
1405 /* Identifier or some sort */
1409 while (nasm_isidchar(*p
));
1410 } else if (*p
== '%') {
1419 /* Classify here, to handle %{...} correctly */
1421 type
= TOK_OTHER
; /* % operator */
1427 type
= (toklen
== 2) ? TOK_PASTE
: TOK_MMACRO_PARAM
;
1431 type
= TOK_MMACRO_PARAM
;
1436 type
= TOK_PREPROC_Q
;
1437 else if (toklen
== 3 && line
[2] == '?')
1438 type
= TOK_PREPROC_QQ
;
1440 type
= TOK_PREPROC_ID
;
1444 type
= (toklen
== 2) ? TOK_OTHER
: TOK_ENVIRON
;
1448 type
= (toklen
== 2) ? TOK_OTHER
: TOK_LOCAL_SYMBOL
;
1452 type
= (toklen
== 2) ? TOK_OTHER
: TOK_LOCAL_MACRO
;
1456 line
+= 2; /* Skip %[ */
1457 firstchar
= *line
; /* Don't clobber */
1459 type
= TOK_INDIRECT
;
1463 type
= (toklen
== 2) ? TOK_COND_COMMA
: TOK_PREPROC_ID
;
1470 type
= TOK_PREPROC_ID
;
1474 type
= TOK_MMACRO_PARAM
; /* %{:..} */
1478 if (nasm_isdigit(c0
))
1479 type
= TOK_MMACRO_PARAM
;
1480 else if (nasm_isidchar(c0
) || toklen
> 2)
1481 type
= TOK_PREPROC_ID
;
1487 } else if (nasm_isidstart(*p
) || (*p
== '$' && nasm_isidstart(p
[1]))) {
1489 * An identifier. This includes the ? operator, which is
1490 * treated as a keyword, not as a special character
1494 while (nasm_isidchar(*++p
))
1496 } else if (nasm_isquote(*p
)) {
1501 p
= nasm_skip_string(p
);
1506 nasm_warn(WARN_OTHER
, "unterminated string");
1507 /* Handling unterminated strings by UNV */
1510 } else if (p
[0] == '$' && p
[1] == '$') {
1511 type
= TOK_OTHER
; /* TOKEN_BASE */
1513 } else if (nasm_isnumstart(*p
)) {
1514 bool is_hex
= false;
1515 bool is_float
= false;
1531 if (!is_hex
&& (c
== 'e' || c
== 'E')) {
1533 if (*p
== '+' || *p
== '-') {
1535 * e can only be followed by +/- if it is either a
1536 * prefixed hex number or a floating-point number
1541 } else if (c
== 'H' || c
== 'h' || c
== 'X' || c
== 'x') {
1543 } else if (c
== 'P' || c
== 'p') {
1545 if (*p
== '+' || *p
== '-')
1547 } else if (nasm_isnumchar(c
))
1548 ; /* just advance */
1549 else if (c
== '.') {
1551 * we need to deal with consequences of the legacy
1552 * parser, like "1.nolist" being two tokens
1553 * (TOK_NUMBER, TOK_ID) here; at least give it
1554 * a shot for now. In the future, we probably need
1555 * a flex-based scanner with proper pattern matching
1556 * to do it as well as it can be done. Nothing in
1557 * the world is going to help the person who wants
1558 * 0x123.p16 interpreted as two tokens, though.
1564 if (nasm_isdigit(*r
) || (is_hex
&& nasm_isxdigit(*r
)) ||
1565 (!is_hex
&& (*r
== 'e' || *r
== 'E')) ||
1566 (*r
== 'p' || *r
== 'P')) {
1570 break; /* Terminate the token */
1574 p
--; /* Point to first character beyond number */
1576 if (p
== line
+1 && *line
== '$') {
1577 type
= TOK_OTHER
; /* TOKEN_HERE */
1579 if (has_e
&& !is_hex
) {
1580 /* 1e13 is floating-point, but 1e13h is not */
1584 type
= is_float
? TOK_FLOAT
: TOK_NUMBER
;
1586 } else if (nasm_isspace(*p
)) {
1587 type
= TOK_WHITESPACE
;
1588 p
= nasm_skip_spaces(p
);
1590 * Whitespace just before end-of-line is discarded by
1591 * pretending it's a comment; whitespace just before a
1592 * comment gets lumped into the comment.
1594 if (!*p
|| *p
== ';') {
1599 } else if (*p
== ';') {
1605 * Anything else is an operator of some kind. We check
1606 * for all the double-character operators (>>, <<, //,
1607 * %%, <=, >=, ==, !=, <>, &&, ||, ^^) and the triple-
1608 * character operators (<<<, >>>, <=>) but anything
1609 * else is a single-character operator.
1618 } else if (*p
== '=') {
1628 } else if (*p
== '=') {
1632 } else if (*p
== '>') {
1647 /* These operators can be doubled but nothing else */
1657 if (type
== TOK_WHITESPACE
) {
1658 *tail
= t
= new_White(NULL
);
1660 } else if (type
!= TOK_COMMENT
) {
1663 *tail
= t
= new_Token(NULL
, type
, line
, ep
- line
);
1664 *tok_text_buf(t
) = firstchar
; /* E.g. %{foo} -> {foo -> %foo */
1673 * Tokens are allocated in blocks to improve speed. Set the blocksize
1674 * to 0 to use regular nasm_malloc(); this is useful for debugging.
1676 * alloc_Token() returns a zero-initialized token structure.
1678 #define TOKEN_BLOCKSIZE 4096
1682 static Token
*freeTokens
= NULL
;
1683 static Token
*tokenblocks
= NULL
;
1685 static Token
*alloc_Token(void)
1687 Token
*t
= freeTokens
;
1693 nasm_newn(block
, TOKEN_BLOCKSIZE
);
1696 * The first entry in each array are a linked list of
1697 * block allocations and is not used for data.
1699 block
[0].next
= tokenblocks
;
1700 block
[0].type
= TOK_BLOCK
;
1701 tokenblocks
= block
;
1704 * Add the rest to the free list
1706 for (i
= 2; i
< TOKEN_BLOCKSIZE
- 1; i
++)
1707 block
[i
].next
= &block
[i
+1];
1709 freeTokens
= &block
[2];
1712 * Return the topmost usable token
1717 freeTokens
= t
->next
;
1722 static Token
*delete_Token(Token
*t
)
1724 Token
*next
= t
->next
;
1727 t
->next
= freeTokens
;
1733 static void delete_Blocks(void)
1735 Token
*block
, *blocktmp
;
1737 list_for_each_safe(block
, blocktmp
, tokenblocks
)
1740 freeTokens
= tokenblocks
= NULL
;
1745 static inline Token
*alloc_Token(void)
1752 static Token
*delete_Token(Token
*t
)
1754 Token
*next
= t
->next
;
1759 static inline void delete_Blocks(void)
1767 * this function creates a new Token and passes a pointer to it
1768 * back to the caller. It sets the type, text, and next pointer elements.
1770 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
1771 const char *text
, size_t txtlen
)
1773 Token
*t
= alloc_Token();
1778 if (type
== TOK_WHITESPACE
) {
1782 if (text
&& text
[0] && !txtlen
)
1783 txtlen
= tok_strlen(text
);
1785 t
->len
= tok_check_len(txtlen
);
1788 textp
= (txtlen
> INLINE_TEXT
)
1789 ? (t
->text
.p
.ptr
= nasm_malloc(txtlen
+1)) : t
->text
.a
;
1790 memcpy(textp
, text
, txtlen
);
1791 textp
[txtlen
] = '\0'; /* In case we needed malloc() */
1794 * Allocate a buffer but do not fill it. The caller
1795 * can fill in text, but must not change the length.
1796 * The filled in text must be exactly txtlen once
1797 * the buffer is filled and before the token is added
1798 * to any line lists.
1800 if (txtlen
> INLINE_TEXT
)
1801 t
->text
.p
.ptr
= nasm_zalloc(txtlen
+1);
1808 * Same as new_Token(), but text belongs to the new token and is
1809 * either taken over or freed. This function MUST be called
1810 * with valid txt and txtlen, unlike new_Token().
1812 static Token
*new_Token_free(Token
* next
, enum pp_token_type type
,
1813 char *text
, size_t txtlen
)
1815 Token
*t
= alloc_Token();
1819 t
->len
= tok_check_len(txtlen
);
1821 if (txtlen
<= INLINE_TEXT
) {
1822 memcpy(t
->text
.a
, text
, txtlen
);
1825 t
->text
.p
.ptr
= text
;
1831 static Token
*dup_Token(Token
*next
, const Token
*src
)
1833 Token
*t
= alloc_Token();
1835 memcpy(t
, src
, sizeof *src
);
1838 if (t
->len
> INLINE_TEXT
) {
1839 t
->text
.p
.ptr
= nasm_malloc(t
->len
+ 1);
1840 memcpy(t
->text
.p
.ptr
, src
->text
.p
.ptr
, t
->len
+1);
1846 static Token
*new_White(Token
*next
)
1848 Token
*t
= alloc_Token();
1851 t
->type
= TOK_WHITESPACE
;
1859 * This *transfers* the content from one token to another, leaving the
1860 * next pointer of the latter intact. Unlike dup_Token(), the old
1861 * token is destroyed, except for its next pointer, and the text
1862 * pointer allocation, if any, is simply transferred.
1864 static Token
*steal_Token(Token
*dst
, Token
*src
)
1866 /* Overwrite everything except the next pointers */
1867 memcpy((char *)dst
+ sizeof(Token
*), (char *)src
+ sizeof(Token
*),
1868 sizeof(Token
) - sizeof(Token
*));
1870 /* Clear the donor token */
1871 memset((char *)src
+ sizeof(Token
*), 0, sizeof(Token
) - sizeof(Token
*));
1877 * Convert a line of tokens back into text. This modifies the list
1878 * by expanding environment variables.
1880 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1881 * are also transformed into ..@ctxnum.xxx
1883 static char *detoken(Token
* tlist
, bool expand_locals
)
1889 list_for_each(t
, tlist
) {
1893 const char *v
= pp_getenv(t
, true);
1894 set_text(t
, v
, tok_strlen(v
));
1895 t
->type
= TOK_INTERNAL_STRING
;
1899 case TOK_LOCAL_MACRO
:
1900 case TOK_LOCAL_SYMBOL
:
1901 if (expand_locals
) {
1904 Context
*ctx
= get_ctx(tok_text(t
), &q
);
1906 p
= nasm_asprintf("..@%"PRIu64
".%s", ctx
->number
, q
);
1907 set_text_free(t
, p
, nasm_last_string_len());
1914 break; /* No modifications */
1917 if (debug_level(2)) {
1918 unsigned int t_len
= t
->len
;
1919 unsigned int s_len
= tok_strlen(tok_text(t
));
1920 if (t_len
!= s_len
) {
1921 nasm_panic("assertion failed: token \"%s\" type %u len %u has t->len %u\n",
1922 tok_text(t
), t
->type
, s_len
, t_len
);
1930 p
= line
= nasm_malloc(len
+ 1);
1932 list_for_each(t
, tlist
)
1933 p
= mempcpy(p
, tok_text(t
), t
->len
);
1940 * A scanner, suitable for use by the expression evaluator, which
1941 * operates on a line of Tokens. Expects a pointer to a pointer to
1942 * the first token in the line to be passed in as its private_data
1945 * FIX: This really needs to be unified with stdscan.
1952 static int ppscan(void *private_data
, struct tokenval
*tokval
)
1954 struct ppscan
*pps
= private_data
;
1959 if (pps
->ntokens
&& (tline
= pps
->tptr
)) {
1961 pps
->tptr
= tline
->next
;
1965 return tokval
->t_type
= TOKEN_EOS
;
1967 } while (tline
->type
== TOK_WHITESPACE
|| tline
->type
== TOK_COMMENT
);
1969 txt
= tok_text(tline
);
1970 tokval
->t_charptr
= (char *)txt
; /* Fix this */
1972 if (txt
[0] == '$') {
1974 return tokval
->t_type
= TOKEN_HERE
;
1975 } else if (txt
[1] == '$' && !txt
[2]) {
1976 return tokval
->t_type
= TOKEN_BASE
;
1977 } else if (tline
->type
== TOK_ID
) {
1978 tokval
->t_charptr
++;
1979 return tokval
->t_type
= TOKEN_ID
;
1983 switch (tline
->type
) {
1985 if (tline
->len
== 1)
1986 return tokval
->t_type
= txt
[0];
1989 return nasm_token_hash(txt
, tokval
);
1994 tokval
->t_integer
= readnum(txt
, &rn_error
);
1996 return tokval
->t_type
= TOKEN_ERRNUM
;
1998 return tokval
->t_type
= TOKEN_NUM
;
2002 return tokval
->t_type
= TOKEN_FLOAT
;
2005 tokval
->t_charptr
= (char *)unquote_token(tline
);
2006 tokval
->t_inttwo
= tline
->len
;
2007 return tokval
->t_type
= TOKEN_STR
;
2012 * 1. An expression (true if nonzero 0)
2013 * 2. The keywords true, on, yes for true
2014 * 3. The keywords false, off, no for false
2015 * 4. An empty line, for true
2017 * On error, return defval (usually the previous value)
2019 static bool pp_get_boolean_option(Token
*tline
, bool defval
)
2021 static const char * const noyes
[] = {
2027 struct tokenval tokval
;
2030 tline
= skip_white(tline
);
2034 if (tline
->type
== TOK_ID
) {
2036 const char *txt
= tok_text(tline
);
2038 for (i
= 0; i
< ARRAY_SIZE(noyes
); i
++)
2039 if (!nasm_stricmp(txt
, noyes
[i
]))
2046 tokval
.t_type
= TOKEN_INVALID
;
2047 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
2053 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
2054 if (!is_really_simple(evalresult
)) {
2055 nasm_nonfatal("boolean flag expression must be a constant");
2059 return reloc_value(evalresult
) != 0;
2063 * Compare a string to the name of an existing macro; this is a
2064 * simple wrapper which calls either strcmp or nasm_stricmp
2065 * depending on the value of the `casesense' parameter.
2067 static int mstrcmp(const char *p
, const char *q
, bool casesense
)
2069 return casesense
? strcmp(p
, q
) : nasm_stricmp(p
, q
);
2073 * Compare a string to the name of an existing macro; this is a
2074 * simple wrapper which calls either strcmp or nasm_stricmp
2075 * depending on the value of the `casesense' parameter.
2077 static int mmemcmp(const char *p
, const char *q
, size_t l
, bool casesense
)
2079 return casesense
? memcmp(p
, q
, l
) : nasm_memicmp(p
, q
, l
);
2083 * Return the Context structure associated with a %$ token. Return
2084 * NULL, having _already_ reported an error condition, if the
2085 * context stack isn't deep enough for the supplied number of $
2088 * If "namep" is non-NULL, set it to the pointer to the macro name
2089 * tail, i.e. the part beyond %$...
2091 static Context
*get_ctx(const char *name
, const char **namep
)
2099 if (!name
|| name
[0] != '%' || name
[1] != '$')
2103 nasm_nonfatal("`%s': context stack is empty", name
);
2110 while (ctx
&& *name
== '$') {
2116 nasm_nonfatal("`%s': context stack is only"
2117 " %d level%s deep", name
, i
, (i
== 1 ? "" : "s"));
2128 * Open an include file. This routine must always return a valid
2129 * file pointer if it returns - it's responsible for throwing an
2130 * ERR_FATAL and bombing out completely if not. It should also try
2131 * the include path one by one until it finds the file or reaches
2132 * the end of the path.
2134 * Note: for INC_PROBE the function returns NULL at all times;
2135 * instead look for the
2138 INC_NEEDED
, /* File must exist */
2139 INC_OPTIONAL
, /* Missing is OK */
2140 INC_PROBE
/* Only an existence probe */
2143 /* This is conducts a full pathname search */
2144 static FILE *inc_fopen_search(const char *file
, char **slpath
,
2145 enum incopen_mode omode
, enum file_flags fmode
)
2147 const struct strlist_entry
*ip
= strlist_head(ipath_list
);
2149 const char *prefix
= "";
2154 sp
= nasm_catfile(prefix
, file
);
2155 if (omode
== INC_PROBE
) {
2157 found
= nasm_file_exists(sp
);
2159 fp
= nasm_open_read(sp
, fmode
);
2160 found
= (fp
!= NULL
);
2180 * Open a file, or test for the presence of one (depending on omode),
2181 * considering the include path.
2183 static FILE *inc_fopen(const char *file
,
2184 struct strlist
*dhead
,
2185 const char **found_path
,
2186 enum incopen_mode omode
,
2187 enum file_flags fmode
)
2189 struct hash_insert hi
;
2194 hp
= hash_find(&FileHash
, file
, &hi
);
2197 if (path
|| omode
!= INC_NEEDED
) {
2198 strlist_add(dhead
, path
? path
: file
);
2201 /* Need to do the actual path search */
2202 fp
= inc_fopen_search(file
, &path
, omode
, fmode
);
2204 /* Positive or negative result */
2205 hash_add(&hi
, nasm_strdup(file
), path
);
2208 * Add file to dependency path.
2210 if (path
|| omode
!= INC_NEEDED
)
2211 strlist_add(dhead
, file
);
2215 if (omode
== INC_NEEDED
)
2216 nasm_fatal("unable to open include file `%s'", file
);
2218 if (!fp
&& omode
!= INC_PROBE
)
2219 fp
= nasm_open_read(path
, fmode
);
2229 * Opens an include or input file. Public version, for use by modules
2230 * that get a file:lineno pair and need to look at the file again
2231 * (e.g. the CodeView debug backend). Returns NULL on failure.
2233 FILE *pp_input_fopen(const char *filename
, enum file_flags mode
)
2235 return inc_fopen(filename
, NULL
, NULL
, INC_OPTIONAL
, mode
);
2239 * Determine if we should warn on defining a single-line macro of
2240 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
2241 * return true if _any_ single-line macro of that name is defined.
2242 * Otherwise, will return true if a single-line macro with either
2243 * `nparam' or no parameters is defined.
2245 * If a macro with precisely the right number of parameters is
2246 * defined, or nparam is -1, the address of the definition structure
2247 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
2248 * is NULL, no action will be taken regarding its contents, and no
2251 * Note that this is also called with nparam zero to resolve
2254 * If you already know which context macro belongs to, you can pass
2255 * the context pointer as first parameter; if you won't but name begins
2256 * with %$ the context will be automatically computed. If all_contexts
2257 * is true, macro will be searched in outer contexts as well.
2260 smacro_defined(Context
* ctx
, const char *name
, int nparam
, SMacro
** defn
,
2261 bool nocase
, bool find_alias
)
2263 struct hash_table
*smtbl
;
2267 smtbl
= &ctx
->localmac
;
2268 } else if (name
[0] == '%' && name
[1] == '$') {
2270 ctx
= get_ctx(name
, &name
);
2272 return false; /* got to return _something_ */
2273 smtbl
= &ctx
->localmac
;
2279 m
= (SMacro
*) hash_findix(smtbl
, name
);
2282 if (!mstrcmp(m
->name
, name
, m
->casesense
&& nocase
) &&
2283 (nparam
<= 0 || m
->nparam
== 0 || nparam
== m
->nparam
||
2284 (m
->greedy
&& nparam
>= m
->nparam
-1))) {
2285 if (m
->alias
&& !find_alias
) {
2287 name
= tok_text(m
->expansion
);
2294 *defn
= (nparam
== m
->nparam
|| nparam
== -1) ? m
: NULL
;
2304 /* param should be a natural number [0; INT_MAX] */
2305 static int read_param_count(const char *str
)
2310 result
= readnum(str
, &err
);
2311 if (result
< 0 || result
> INT_MAX
) {
2313 nasm_nonfatal("parameter count `%s' is out of bounds [%d; %d]",
2316 nasm_nonfatal("unable to parse parameter count `%s'", str
);
2321 * Count and mark off the parameters in a multi-line macro call.
2322 * This is called both from within the multi-line macro expansion
2323 * code, and also to mark off the default parameters when provided
2324 * in a %macro definition line.
2326 * Note that we need space in the params array for parameter 0 being
2327 * a possible captured label as well as the final NULL.
2329 static void count_mmac_params(Token
* t
, int *nparamp
, Token
***paramsp
)
2335 paramsize
= PARAM_DELTA
;
2336 params
= nasm_malloc(paramsize
* sizeof(*params
));
2339 while ((t
= skip_white(t
))) {
2340 /* 2 slots for captured label and NULL */
2341 if (nparam
+2 >= paramsize
) {
2342 paramsize
+= PARAM_DELTA
;
2343 params
= nasm_realloc(params
, sizeof(*params
) * paramsize
);
2345 params
[++nparam
] = t
;
2346 if (tok_is(t
, '{')) {
2348 while (brace
&& (t
= t
->next
)) {
2349 brace
+= tok_is(t
, '{');
2350 brace
-= tok_is(t
, '}');
2355 * Now we've found the closing brace, look further
2358 t
= skip_white(t
->next
);
2359 if (tok_isnt(t
, ','))
2360 nasm_nonfatal("braces do not enclose all of macro parameter");
2362 nasm_nonfatal("expecting closing brace in macro parameter");
2366 while (tok_isnt(t
, ','))
2369 if (t
) /* got a comma */
2370 t
= t
->next
; /* eat the comma */
2373 params
[nparam
+1] = NULL
;
2379 * Determine whether one of the various `if' conditions is true or
2382 * We must free the tline we get passed.
2384 static enum cond_state
if_condition(Token
* tline
, enum preproc_token ct
)
2387 Token
*t
, *tt
, *origline
;
2389 struct tokenval tokval
;
2391 enum pp_token_type needtype
;
2392 const char *dname
= pp_directives
[ct
];
2393 bool casesense
= true;
2394 enum preproc_token cond
= PP_COND(ct
);
2400 j
= false; /* have we matched yet? */
2402 tline
= skip_white(tline
);
2405 if (tline
->type
!= TOK_ID
) {
2406 nasm_nonfatal("`%s' expects context identifiers",
2410 if (cstk
&& cstk
->name
&& !nasm_stricmp(tok_text(tline
), cstk
->name
))
2412 tline
= tline
->next
;
2417 j
= false; /* have we matched yet? */
2419 tline
= skip_white(tline
);
2420 if (!tline
|| (tline
->type
!= TOK_ID
&&
2421 tline
->type
!= TOK_LOCAL_MACRO
)) {
2422 nasm_nonfatal("`%s' expects macro identifiers",
2426 if (smacro_defined(NULL
, tok_text(tline
), 0, NULL
, true, false))
2428 tline
= tline
->next
;
2433 tline
= expand_smacro(tline
);
2434 j
= false; /* have we matched yet? */
2436 tline
= skip_white(tline
);
2437 if (!tline
|| (tline
->type
!= TOK_ID
&&
2438 tline
->type
!= TOK_STRING
&&
2439 tline
->type
!= TOK_INTERNAL_STRING
&&
2440 tline
->type
!= TOK_ENVIRON
)) {
2441 nasm_nonfatal("`%s' expects environment variable names",
2446 j
|= !!pp_getenv(tline
, false);
2447 tline
= tline
->next
;
2455 tline
= expand_smacro(tline
);
2457 while (tok_isnt(tt
, ','))
2460 nasm_nonfatal("`%s' expects two comma-separated arguments",
2465 j
= true; /* assume equality unless proved not */
2466 while (tok_isnt(t
, ',') && tt
) {
2467 unsigned int l1
, l2
;
2468 const char *t1
, *t2
;
2470 if (tok_is(tt
, ',')) {
2471 nasm_nonfatal("`%s': more than one comma on line",
2475 if (t
->type
== TOK_WHITESPACE
) {
2479 if (tt
->type
== TOK_WHITESPACE
) {
2483 if (tt
->type
!= t
->type
) {
2484 j
= false; /* found mismatching tokens */
2488 t1
= unquote_token(t
);
2489 t2
= unquote_token(tt
);
2493 if (l1
!= l2
|| mmemcmp(t1
, t2
, l1
, casesense
)) {
2501 if (!tok_is(t
, ',') || tt
)
2502 j
= false; /* trailing gunk on one end or other */
2508 MMacro searching
, *mmac
;
2510 tline
= skip_white(tline
);
2511 tline
= expand_id(tline
);
2512 if (!tok_type(tline
, TOK_ID
)) {
2513 nasm_nonfatal("`%s' expects a macro name", dname
);
2516 nasm_zero(searching
);
2517 searching
.name
= dup_text(tline
);
2518 searching
.casesense
= true;
2519 searching
.nparam_min
= 0;
2520 searching
.nparam_max
= INT_MAX
;
2521 tline
= expand_smacro(tline
->next
);
2522 tline
= skip_white(tline
);
2524 } else if (!tok_type(tline
, TOK_NUMBER
)) {
2525 nasm_nonfatal("`%s' expects a parameter count or nothing",
2528 searching
.nparam_min
= searching
.nparam_max
=
2529 read_param_count(tok_text(tline
));
2531 if (tline
&& tok_is(tline
->next
, '-')) {
2532 tline
= tline
->next
->next
;
2533 if (tok_is(tline
, '*'))
2534 searching
.nparam_max
= INT_MAX
;
2535 else if (!tok_type(tline
, TOK_NUMBER
))
2536 nasm_nonfatal("`%s' expects a parameter count after `-'",
2539 searching
.nparam_max
= read_param_count(tok_text(tline
));
2540 if (searching
.nparam_min
> searching
.nparam_max
) {
2541 nasm_nonfatal("minimum parameter count exceeds maximum");
2542 searching
.nparam_max
= searching
.nparam_min
;
2546 if (tline
&& tok_is(tline
->next
, '+')) {
2547 tline
= tline
->next
;
2548 searching
.plus
= true;
2550 mmac
= (MMacro
*) hash_findix(&mmacros
, searching
.name
);
2552 if (!strcmp(mmac
->name
, searching
.name
) &&
2553 (mmac
->nparam_min
<= searching
.nparam_max
2555 && (searching
.nparam_min
<= mmac
->nparam_max
2562 if (tline
&& tline
->next
)
2563 nasm_warn(WARN_OTHER
, "trailing garbage after %%ifmacro ignored");
2564 nasm_free(searching
.name
);
2573 needtype
= TOK_NUMBER
;
2576 needtype
= TOK_STRING
;
2580 t
= tline
= expand_smacro(tline
);
2582 while (tok_white(t
) ||
2583 (needtype
== TOK_NUMBER
&& (tok_is(t
, '-') | tok_is(t
, '+'))))
2586 j
= tok_type(t
, needtype
);
2590 tline
= expand_smacro(tline
);
2591 t
= skip_white(tline
);
2595 t
= skip_white(t
->next
); /* Skip the actual token + whitespace */
2601 tline
= expand_smacro(tline
);
2602 t
= skip_white(tline
);
2603 j
= !t
; /* Should be empty */
2607 pps
.tptr
= tline
= expand_smacro(tline
);
2609 tokval
.t_type
= TOKEN_INVALID
;
2610 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
2614 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
2615 if (!is_simple(evalresult
)) {
2616 nasm_nonfatal("non-constant value given to `%s'",
2620 j
= reloc_value(evalresult
) != 0;
2626 const struct use_package
*pkg
;
2629 pkg
= get_use_pkg(tline
, dname
, &name
);
2633 j
= pkg
&& ((cond
== PP_IFUSABLE
) | use_loaded
[pkg
->index
]);
2638 nasm_nonfatal("unknown preprocessor directive `%s'", dname
);
2642 free_tlist(origline
);
2643 return (j
^ PP_COND_NEGATIVE(ct
)) ? COND_IF_TRUE
: COND_IF_FALSE
;
2646 free_tlist(origline
);
2651 * Default smacro expansion routine: just returns a copy of the
2655 smacro_expand_default(const SMacro
*s
, Token
**params
, int nparams
)
2660 return dup_tlist(s
->expansion
, NULL
);
2664 * Emit a macro defintion or undef to the listing file, if
2665 * desired. This is similar to detoken(), but it handles the reverse
2666 * expansion list, does not expand %! or local variable tokens, and
2667 * does some special handling for macro parameters.
2670 list_smacro_def(enum preproc_token op
, const Context
*ctx
, const SMacro
*m
)
2673 size_t namelen
, size
;
2675 char *context_prefix
= NULL
;
2678 namelen
= strlen(m
->name
);
2679 size
= namelen
+ 2; /* Include room for space after name + NUL */
2682 int context_depth
= cstk
->depth
- ctx
->depth
+ 1;
2684 nasm_asprintf("[%s::%"PRIu64
"] %%%-*s",
2685 ctx
->name
? ctx
->name
: "",
2686 ctx
->number
, context_depth
, "");
2688 context_len
= nasm_last_string_len();
2689 memset(context_prefix
+ context_len
- context_depth
,
2690 '$', context_depth
);
2691 size
+= context_len
;
2694 list_for_each(t
, m
->expansion
)
2699 * Space for ( and either , or ) around each
2700 * parameter, plus up to 4 flags.
2704 size
+= 1 + 4 * m
->nparam
;
2705 for (i
= 0; i
< m
->nparam
; i
++)
2706 size
+= m
->params
[i
].name
.len
;
2709 def
= nasm_malloc(size
);
2713 list_for_each(t
, m
->expansion
) {
2715 memcpy(p
, tok_text(t
), t
->len
);
2724 for (i
= m
->nparam
-1; i
>= 0; i
--) {
2725 enum sparmflags flags
= m
->params
[i
].flags
;
2726 if (flags
& SPARM_GREEDY
)
2728 p
-= m
->params
[i
].name
.len
;
2729 memcpy(p
, tok_text(&m
->params
[i
].name
), m
->params
[i
].name
.len
);
2731 if (flags
& SPARM_NOSTRIP
)
2733 if (flags
& SPARM_STR
)
2735 if (flags
& SPARM_EVAL
)
2739 *p
= '('; /* First parameter starts with ( not , */
2743 memcpy(p
, m
->name
, namelen
);
2745 if (context_prefix
) {
2747 memcpy(p
, context_prefix
, context_len
);
2748 nasm_free(context_prefix
);
2751 nasm_listmsg("%s %s", pp_directives
[op
], p
);
2756 * Parse smacro arguments, return argument count. If the tmpl argument
2757 * is set, set the nparam, greedy and params field in the template.
2758 * *tpp is updated to point to the pointer to the first token after the
2761 * The text values from any argument tokens are "stolen" and the
2762 * corresponding text fields set to NULL.
2764 static int parse_smacro_template(Token
***tpp
, SMacro
*tmpl
)
2767 enum sparmflags flags
;
2768 struct smac_param
*params
= NULL
;
2770 bool greedy
= false;
2776 * DO NOT skip whitespace here, or we won't be able to distinguish:
2778 * %define foo (a,b) ; no arguments, (a,b) is the expansion
2779 * %define bar(a,b) ; two arguments, empty expansion
2781 * This ambiguity was inherited from C.
2784 if (!tok_is(t
, '('))
2792 /* Count parameters first */
2793 sparam
= parse_smacro_template(&txpp
, NULL
);
2795 goto finish
; /* No parameters, we're done */
2796 nasm_newn(params
, sparam
);
2799 /* Skip leading paren */
2808 if (!t
|| !t
->type
) {
2810 nasm_nonfatal("`)' expected to terminate macro template");
2812 nasm_nonfatal("parameter identifier expected");
2826 switch (t
->text
.a
[0]) {
2828 flags
|= SPARM_EVAL
;
2834 flags
|= SPARM_NOSTRIP
;
2837 flags
|= SPARM_GREEDY
;
2842 nasm_nonfatal("greedy parameter must be last");
2847 steal_Token(¶ms
[nparam
].name
, name
);
2848 params
[nparam
].flags
= flags
;
2853 done
= t
->text
.a
[0] == ')';
2860 case TOK_WHITESPACE
:
2866 nasm_nonfatal("garbage `%s' in macro parameter list", tok_text(t
));
2877 while (t
&& t
->type
== TOK_WHITESPACE
) {
2883 tmpl
->nparam
= nparam
;
2884 tmpl
->greedy
= greedy
;
2885 tmpl
->params
= params
;
2891 * Common code for defining an smacro. The tmpl argument, if not NULL,
2892 * contains any macro parameters that aren't explicit arguments;
2893 * those are the more uncommon macro variants.
2895 static SMacro
*define_smacro(const char *mname
, bool casesense
,
2896 Token
*expansion
, SMacro
*tmpl
)
2898 SMacro
*smac
, **smhead
;
2899 struct hash_table
*smtbl
;
2901 bool defining_alias
= false;
2902 unsigned int nparam
= 0;
2905 defining_alias
= tmpl
->alias
;
2906 nparam
= tmpl
->nparam
;
2910 ctx
= get_ctx(mname
, &mname
);
2912 if (!smacro_defined(ctx
, mname
, nparam
, &smac
, casesense
, true)) {
2913 /* Create a new macro */
2914 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
2915 smhead
= (SMacro
**) hash_findi_add(smtbl
, mname
);
2917 smac
->next
= *smhead
;
2921 nasm_warn(WARN_OTHER
, "single-line macro `%s' defined both with and"
2922 " without parameters", mname
);
2924 * Some instances of the old code considered this a failure,
2925 * some others didn't. What is the right thing to do here?
2928 } else if (!smac
->alias
|| !do_aliases
|| defining_alias
) {
2930 * We're redefining, so we have to take over an
2931 * existing SMacro structure. This means freeing
2932 * what was already in it, but not the structure itself.
2936 } else if (smac
->in_progress
) {
2937 nasm_nonfatal("macro alias loop");
2940 /* It is an alias macro; follow the alias link */
2943 smac
->in_progress
= true;
2944 s
= define_smacro(tok_text(smac
->expansion
), casesense
,
2946 smac
->in_progress
= false;
2951 smac
->name
= nasm_strdup(mname
);
2952 smac
->casesense
= casesense
;
2953 smac
->expansion
= expansion
;
2954 smac
->expand
= smacro_expand_default
;
2956 smac
->nparam
= tmpl
->nparam
;
2957 smac
->params
= tmpl
->params
;
2958 smac
->alias
= tmpl
->alias
;
2959 smac
->greedy
= tmpl
->greedy
;
2961 smac
->expand
= tmpl
->expand
;
2963 if (list_option('s')) {
2964 list_smacro_def((smac
->alias
? PP_DEFALIAS
: PP_DEFINE
)
2965 + !casesense
, ctx
, smac
);
2970 free_tlist(expansion
);
2972 free_smacro_members(tmpl
);
2977 * Undefine an smacro
2979 static void undef_smacro(const char *mname
, bool undefalias
)
2981 SMacro
**smhead
, *s
, **sp
;
2982 struct hash_table
*smtbl
;
2985 ctx
= get_ctx(mname
, &mname
);
2986 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
2987 smhead
= (SMacro
**)hash_findi(smtbl
, mname
, NULL
);
2991 * We now have a macro name... go hunt for it.
2994 while ((s
= *sp
) != NULL
) {
2995 if (!mstrcmp(s
->name
, mname
, s
->casesense
)) {
2996 if (s
->alias
&& !undefalias
) {
2999 if (s
->in_progress
) {
3000 nasm_nonfatal("macro alias loop");
3002 s
->in_progress
= true;
3003 undef_smacro(tok_text(s
->expansion
), false);
3004 s
->in_progress
= false;
3007 if (list_option('d'))
3008 list_smacro_def(s
->alias
? PP_UNDEFALIAS
: PP_UNDEF
,
3021 * Parse a mmacro specification.
3023 static bool parse_mmacro_spec(Token
*tline
, MMacro
*def
, const char *directive
)
3025 tline
= tline
->next
;
3026 tline
= skip_white(tline
);
3027 tline
= expand_id(tline
);
3028 if (!tok_type(tline
, TOK_ID
)) {
3029 nasm_nonfatal("`%s' expects a macro name", directive
);
3036 def
->name
= dup_text(tline
);
3038 def
->nolist
= false;
3039 def
->nparam_min
= 0;
3040 def
->nparam_max
= 0;
3042 tline
= expand_smacro(tline
->next
);
3043 tline
= skip_white(tline
);
3044 if (!tok_type(tline
, TOK_NUMBER
))
3045 nasm_nonfatal("`%s' expects a parameter count", directive
);
3047 def
->nparam_min
= def
->nparam_max
= read_param_count(tok_text(tline
));
3048 if (tline
&& tok_is(tline
->next
, '-')) {
3049 tline
= tline
->next
->next
;
3050 if (tok_is(tline
, '*')) {
3051 def
->nparam_max
= INT_MAX
;
3052 } else if (!tok_type(tline
, TOK_NUMBER
)) {
3053 nasm_nonfatal("`%s' expects a parameter count after `-'", directive
);
3055 def
->nparam_max
= read_param_count(tok_text(tline
));
3056 if (def
->nparam_min
> def
->nparam_max
) {
3057 nasm_nonfatal("minimum parameter count exceeds maximum");
3058 def
->nparam_max
= def
->nparam_min
;
3062 if (tline
&& tok_is(tline
->next
, '+')) {
3063 tline
= tline
->next
;
3066 if (tline
&& tok_type(tline
->next
, TOK_ID
) &&
3067 tline
->next
->len
== 7 &&
3068 !nasm_stricmp(tline
->next
->text
.a
, ".nolist")) {
3069 tline
= tline
->next
;
3070 def
->nolist
= !list_option('f') || istk
->nolist
;
3074 * Handle default parameters.
3076 if (tline
&& tline
->next
) {
3077 def
->dlist
= tline
->next
;
3079 count_mmac_params(def
->dlist
, &def
->ndefs
, &def
->defaults
);
3082 def
->defaults
= NULL
;
3084 def
->expansion
= NULL
;
3086 if (def
->defaults
&& def
->ndefs
> def
->nparam_max
- def
->nparam_min
&&
3089 *!macro-defaults [on] macros with more default than optional parameters
3090 *! warns when a macro has more default parameters than optional parameters.
3091 *! See \k{mlmacdef} for why might want to disable this warning.
3093 nasm_warn(WARN_MACRO_DEFAULTS
,
3094 "too many default macro parameters in macro `%s'", def
->name
);
3102 * Decode a size directive
3104 static int parse_size(const char *str
) {
3105 static const char *size_names
[] =
3106 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
3107 static const int sizes
[] =
3108 { 0, 1, 4, 16, 8, 10, 2, 32 };
3109 return str
? sizes
[bsii(str
, size_names
, ARRAY_SIZE(size_names
))+1] : 0;
3113 * Process a preprocessor %pragma directive. Currently there are none.
3114 * Gets passed the token list starting with the "preproc" token from
3115 * "%pragma preproc".
3117 static void do_pragma_preproc(Token
*tline
)
3119 /* Skip to the real stuff */
3120 tline
= tline
->next
;
3121 tline
= skip_white(tline
);
3125 (void)tline
; /* Nothing else to do at present */
3128 static bool is_macro_id(const Token
*t
)
3130 return tok_type(t
, TOK_ID
) || tok_type(t
, TOK_LOCAL_MACRO
);
3133 static const char *get_id(Token
**tp
, const char *dname
)
3138 t
= t
->next
; /* Skip directive */
3142 if (!is_macro_id(t
)) {
3143 nasm_nonfatal("`%s' expects a macro identifier", dname
);
3153 /* Parse a %use package name and find the package. Set *err on syntax error. */
3154 static const struct use_package
*
3155 get_use_pkg(Token
*t
, const char *dname
, const char **name
)
3160 t
= expand_smacro(t
);
3165 nasm_nonfatal("`%s' expects a package name, got end of line", dname
);
3167 } else if (t
->type
!= TOK_ID
&& t
->type
!= TOK_STRING
) {
3168 nasm_nonfatal("`%s' expects a package name, got `%s'",
3169 dname
, tok_text(t
));
3173 *name
= id
= unquote_token(t
);
3178 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3180 return nasm_find_use_package(id
);
3184 * find and process preprocessor directive in passed line
3185 * Find out if a line contains a preprocessor directive, and deal
3188 * If a directive _is_ found, it is the responsibility of this routine
3189 * (and not the caller) to free_tlist() the line.
3191 * @param tline a pointer to the current tokeninzed line linked list
3192 * @param output if this directive generated output
3193 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
3196 static int do_directive(Token
*tline
, Token
**output
)
3198 enum preproc_token i
;
3208 const char *found_path
;
3214 MMacro
*mmac
, **mmhead
;
3215 Token
*t
= NULL
, *tt
, *macro_start
, *last
, *origline
;
3217 struct tokenval tokval
;
3222 const char *dname
; /* Name of directive, for messages */
3224 *output
= NULL
; /* No output generated */
3227 tline
= skip_white(tline
);
3228 if (!tline
|| !tok_type(tline
, TOK_PREPROC_ID
))
3229 return NO_DIRECTIVE_FOUND
;
3231 dname
= tok_text(tline
);
3232 if (dname
[1] == '%')
3233 return NO_DIRECTIVE_FOUND
;
3235 i
= pp_token_hash(dname
);
3238 if (PP_HAS_CASE(i
) & PP_INSENSITIVE(i
)) {
3244 * If we're in a non-emitting branch of a condition construct,
3245 * or walking to the end of an already terminated %rep block,
3246 * we should ignore all directives except for condition
3249 if (((istk
->conds
&& !emitting(istk
->conds
->state
)) ||
3250 (istk
->mstk
.mstk
&& !istk
->mstk
.mstk
->in_progress
)) &&
3252 return NO_DIRECTIVE_FOUND
;
3256 * If we're defining a macro or reading a %rep block, we should
3257 * ignore all directives except for %macro/%imacro (which nest),
3258 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
3259 * If we're in a %rep block, another %rep nests, so should be let through.
3261 if (defining
&& i
!= PP_MACRO
&& i
!= PP_RMACRO
&&
3262 i
!= PP_ENDMACRO
&& i
!= PP_ENDM
&&
3263 (defining
->name
|| (i
!= PP_ENDREP
&& i
!= PP_REP
))) {
3264 return NO_DIRECTIVE_FOUND
;
3268 if (i
== PP_MACRO
|| i
== PP_RMACRO
) {
3270 return NO_DIRECTIVE_FOUND
;
3271 } else if (nested_mac_count
> 0) {
3272 if (i
== PP_ENDMACRO
) {
3274 return NO_DIRECTIVE_FOUND
;
3277 if (!defining
->name
) {
3280 return NO_DIRECTIVE_FOUND
;
3281 } else if (nested_rep_count
> 0) {
3282 if (i
== PP_ENDREP
) {
3284 return NO_DIRECTIVE_FOUND
;
3292 nasm_nonfatal("unknown preprocessor directive `%s'", dname
);
3293 return NO_DIRECTIVE_FOUND
; /* didn't get it */
3297 * %pragma namespace options...
3299 * The namespace "preproc" is reserved for the preprocessor;
3300 * all other namespaces generate a [pragma] assembly directive.
3302 * Invalid %pragmas are ignored and may have different
3303 * meaning in future versions of NASM.
3306 tline
= tline
->next
;
3308 tline
= zap_white(expand_smacro(tline
));
3309 if (tok_type(tline
, TOK_ID
)) {
3310 if (!nasm_stricmp(tok_text(tline
), "preproc")) {
3311 /* Preprocessor pragma */
3312 do_pragma_preproc(tline
);
3315 /* Build the assembler directive */
3317 /* Append bracket to the end of the output */
3318 for (t
= tline
; t
->next
; t
= t
->next
)
3320 t
->next
= make_tok_char(NULL
, ']');
3322 /* Prepend "[pragma " */
3323 t
= new_White(tline
);
3324 t
= new_Token(t
, TOK_ID
, "pragma", 6);
3325 t
= make_tok_char(t
, '[');
3333 /* Directive to tell NASM what the default stack size is. The
3334 * default is for a 16-bit stack, and this can be overriden with
3337 tline
= skip_white(tline
->next
);
3338 if (!tline
|| tline
->type
!= TOK_ID
) {
3339 nasm_nonfatal("`%s' missing size parameter", dname
);
3341 if (nasm_stricmp(tok_text(tline
), "flat") == 0) {
3342 /* All subsequent ARG directives are for a 32-bit stack */
3344 StackPointer
= "ebp";
3347 } else if (nasm_stricmp(tok_text(tline
), "flat64") == 0) {
3348 /* All subsequent ARG directives are for a 64-bit stack */
3350 StackPointer
= "rbp";
3353 } else if (nasm_stricmp(tok_text(tline
), "large") == 0) {
3354 /* All subsequent ARG directives are for a 16-bit stack,
3355 * far function call.
3358 StackPointer
= "bp";
3361 } else if (nasm_stricmp(tok_text(tline
), "small") == 0) {
3362 /* All subsequent ARG directives are for a 16-bit stack,
3363 * far function call. We don't support near functions.
3366 StackPointer
= "bp";
3370 nasm_nonfatal("`%s' invalid size type", dname
);
3375 /* TASM like ARG directive to define arguments to functions, in
3376 * the following form:
3378 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
3383 char directive
[256];
3384 int size
= StackSize
;
3386 /* Find the argument name */
3387 tline
= skip_white(tline
->next
);
3388 if (!tline
|| tline
->type
!= TOK_ID
) {
3389 nasm_nonfatal("`%s' missing argument parameter", dname
);
3392 arg
= tok_text(tline
);
3394 /* Find the argument size type */
3395 tline
= tline
->next
;
3396 if (!tok_is(tline
, ':')) {
3397 nasm_nonfatal("syntax error processing `%s' directive", dname
);
3400 tline
= tline
->next
;
3401 if (!tok_type(tline
, TOK_ID
)) {
3402 nasm_nonfatal("`%s' missing size type parameter", dname
);
3406 /* Allow macro expansion of type parameter */
3407 tt
= tokenize(tok_text(tline
));
3408 tt
= expand_smacro(tt
);
3409 size
= parse_size(tok_text(tt
));
3411 nasm_nonfatal("invalid size type for `%s' missing directive", dname
);
3417 /* Round up to even stack slots */
3418 size
= ALIGN(size
, StackSize
);
3420 /* Now define the macro for the argument */
3421 snprintf(directive
, sizeof(directive
), "%%define %s (%s+%d)",
3422 arg
, StackPointer
, offset
);
3423 do_directive(tokenize(directive
), output
);
3426 /* Move to the next argument in the list */
3427 tline
= skip_white(tline
->next
);
3428 } while (tok_is(tline
, ','));
3433 /* TASM like LOCAL directive to define local variables for a
3434 * function, in the following form:
3436 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
3438 * The '= LocalSize' at the end is ignored by NASM, but is
3439 * required by TASM to define the local parameter size (and used
3440 * by the TASM macro package).
3442 offset
= LocalOffset
;
3445 char directive
[256];
3446 int size
= StackSize
;
3448 /* Find the argument name */
3449 tline
= skip_white(tline
->next
);
3450 if (!tline
|| tline
->type
!= TOK_ID
) {
3451 nasm_nonfatal("`%s' missing argument parameter", dname
);
3454 local
= tok_text(tline
);
3456 /* Find the argument size type */
3457 tline
= tline
->next
;
3458 if (!tok_is(tline
, ':')) {
3459 nasm_nonfatal("syntax error processing `%s' directive", dname
);
3462 tline
= tline
->next
;
3463 if (!tok_type(tline
, TOK_ID
)) {
3464 nasm_nonfatal("`%s' missing size type parameter", dname
);
3468 /* Allow macro expansion of type parameter */
3469 tt
= tokenize(tok_text(tline
));
3470 tt
= expand_smacro(tt
);
3471 size
= parse_size(tok_text(tt
));
3473 nasm_nonfatal("invalid size type for `%s' missing directive", dname
);
3479 /* Round up to even stack slots */
3480 size
= ALIGN(size
, StackSize
);
3482 offset
+= size
; /* Negative offset, increment before */
3484 /* Now define the macro for the argument */
3485 snprintf(directive
, sizeof(directive
), "%%define %s (%s-%d)",
3486 local
, StackPointer
, offset
);
3487 do_directive(tokenize(directive
), output
);
3489 /* Now define the assign to setup the enter_c macro correctly */
3490 snprintf(directive
, sizeof(directive
),
3491 "%%assign %%$localsize %%$localsize+%d", size
);
3492 do_directive(tokenize(directive
), output
);
3494 /* Move to the next argument in the list */
3495 tline
= skip_white(tline
->next
);
3496 } while (tok_is(tline
, ','));
3497 LocalOffset
= offset
;
3502 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3508 t
= tline
->next
= expand_smacro(tline
->next
);
3510 if (!t
|| (t
->type
!= TOK_STRING
&&
3511 t
->type
!= TOK_INTERNAL_STRING
)) {
3512 nasm_nonfatal("`%s' expects a file name", dname
);
3516 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3518 strlist_add(deplist
, unquote_token_cstr(t
));
3522 t
= tline
->next
= expand_smacro(tline
->next
);
3525 if (!t
|| (t
->type
!= TOK_STRING
&&
3526 t
->type
!= TOK_INTERNAL_STRING
)) {
3527 nasm_nonfatal("`%s' expects a file name", dname
);
3531 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
3532 p
= unquote_token_cstr(t
);
3536 inc
->fp
= inc_fopen(p
, deplist
, &found_path
,
3537 (pp_mode
== PP_DEPS
)
3538 ? INC_OPTIONAL
: INC_NEEDED
, NF_TEXT
);
3540 /* -MG given but file not found */
3543 inc
->fname
= src_set_fname(found_path
? found_path
: p
);
3544 inc
->lineno
= src_set_linnum(0);
3546 inc
->nolist
= istk
->nolist
;
3548 lfmt
->uplevel(LIST_INCLUDE
, 0);
3554 const struct use_package
*pkg
;
3557 pkg
= get_use_pkg(tline
->next
, dname
, &name
);
3561 nasm_nonfatal("unknown `%s' package: `%s'", dname
, name
);
3562 } else if (!use_loaded
[pkg
->index
]) {
3564 * Not already included, go ahead and include it.
3565 * Treat it as an include file for the purpose of
3566 * producing a listing.
3568 use_loaded
[pkg
->index
] = true;
3569 stdmacpos
= pkg
->macros
;
3572 inc
->fname
= src_set_fname(NULL
);
3573 inc
->lineno
= src_set_linnum(0);
3574 inc
->nolist
= !list_option('b') || istk
->nolist
;
3576 lfmt
->uplevel(LIST_INCLUDE
, 0);
3583 tline
= tline
->next
;
3584 tline
= skip_white(tline
);
3585 tline
= expand_id(tline
);
3587 if (!tok_type(tline
, TOK_ID
)) {
3588 nasm_nonfatal("`%s' expects a context identifier",
3593 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored",
3595 p
= tok_text(tline
);
3597 p
= NULL
; /* Anonymous */
3602 ctx
->depth
= cstk
? cstk
->depth
+ 1 : 1;
3604 ctx
->name
= p
? nasm_strdup(p
) : NULL
;
3605 ctx
->number
= unique
++;
3610 nasm_nonfatal("`%s': context stack is empty",
3612 } else if (i
== PP_POP
) {
3613 if (p
&& (!cstk
->name
|| nasm_stricmp(p
, cstk
->name
)))
3614 nasm_nonfatal("`%s' in wrong context: %s, "
3616 dname
, cstk
->name
? cstk
->name
: "anonymous", p
);
3621 nasm_free((char *)cstk
->name
);
3622 cstk
->name
= p
? nasm_strdup(p
) : NULL
;
3628 severity
= ERR_FATAL
;
3631 severity
= ERR_NONFATAL
|ERR_PASS2
;
3635 *!user [on] %warning directives
3636 *! controls output of \c{%warning} directives (see \k{pperror}).
3638 severity
= ERR_WARNING
|WARN_USER
|ERR_PASS2
;
3643 /* Only error out if this is the final pass */
3644 tline
->next
= expand_smacro(tline
->next
);
3645 tline
= tline
->next
;
3646 tline
= skip_white(tline
);
3647 t
= tline
? tline
->next
: NULL
;
3649 if (tok_type(tline
, TOK_STRING
) && !t
) {
3650 /* The line contains only a quoted string */
3651 p
= unquote_token(tline
); /* Ignore NUL character truncation */
3652 nasm_error(severity
, "%s", p
);
3654 /* Not a quoted string, or more than a quoted string */
3655 q
= detoken(tline
, false);
3656 nasm_error(severity
, "%s", q
);
3663 if (istk
->conds
&& !emitting(istk
->conds
->state
))
3666 j
= if_condition(tline
->next
, i
);
3667 tline
->next
= NULL
; /* it got freed */
3669 cond
= nasm_malloc(sizeof(Cond
));
3670 cond
->next
= istk
->conds
;
3674 istk
->mstk
.mstk
->condcnt
++;
3679 nasm_fatal("`%s': no matching `%%if'", dname
);
3680 switch(istk
->conds
->state
) {
3682 istk
->conds
->state
= COND_DONE
;
3689 case COND_ELSE_TRUE
:
3690 case COND_ELSE_FALSE
:
3691 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
3692 "`%%elif' after `%%else' ignored");
3693 istk
->conds
->state
= COND_NEVER
;
3698 * IMPORTANT: In the case of %if, we will already have
3699 * called expand_mmac_params(); however, if we're
3700 * processing an %elif we must have been in a
3701 * non-emitting mode, which would have inhibited
3702 * the normal invocation of expand_mmac_params().
3703 * Therefore, we have to do it explicitly here.
3705 j
= if_condition(expand_mmac_params(tline
->next
), i
);
3706 tline
->next
= NULL
; /* it got freed */
3707 istk
->conds
->state
= j
;
3714 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
3715 "trailing garbage after `%%else' ignored");
3717 nasm_fatal("`%%else: no matching `%%if'");
3718 switch(istk
->conds
->state
) {
3721 istk
->conds
->state
= COND_ELSE_FALSE
;
3728 istk
->conds
->state
= COND_ELSE_TRUE
;
3731 case COND_ELSE_TRUE
:
3732 case COND_ELSE_FALSE
:
3733 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
3734 "`%%else' after `%%else' ignored.");
3735 istk
->conds
->state
= COND_NEVER
;
3742 nasm_warn(WARN_OTHER
|ERR_PP_PRECOND
,
3743 "trailing garbage after `%%endif' ignored");
3745 nasm_fatal("`%%endif': no matching `%%if'");
3747 istk
->conds
= cond
->next
;
3750 istk
->mstk
.mstk
->condcnt
--;
3755 nasm_assert(!defining
);
3757 defining
->casesense
= casesense
;
3758 defining
->dstk
.mmac
= defining
;
3760 defining
->max_depth
= nasm_limit
[LIMIT_MACRO_LEVELS
];
3761 if (!parse_mmacro_spec(tline
, defining
, dname
)) {
3762 nasm_free(defining
);
3766 src_get(&defining
->xline
, &defining
->fname
);
3768 mmac
= (MMacro
*) hash_findix(&mmacros
, defining
->name
);
3770 if (!strcmp(mmac
->name
, defining
->name
) &&
3771 (mmac
->nparam_min
<= defining
->nparam_max
3773 && (defining
->nparam_min
<= mmac
->nparam_max
3775 nasm_warn(WARN_OTHER
, "redefining multi-line macro `%s'",
3785 if (!(defining
&& defining
->name
)) {
3786 nasm_nonfatal("`%s': not defining a macro", tok_text(tline
));
3789 mmhead
= (MMacro
**) hash_findi_add(&mmacros
, defining
->name
);
3790 defining
->next
= *mmhead
;
3797 * We must search along istk->expansion until we hit a
3798 * macro-end marker for a macro with a name. Then we
3799 * bypass all lines between exitmacro and endmacro.
3801 list_for_each(l
, istk
->expansion
)
3802 if (l
->finishes
&& l
->finishes
->name
)
3807 * Remove all conditional entries relative to this
3808 * macro invocation. (safe to do in this context)
3810 for ( ; l
->finishes
->condcnt
> 0; l
->finishes
->condcnt
--) {
3812 istk
->conds
= cond
->next
;
3815 istk
->expansion
= l
;
3817 nasm_nonfatal("`%%exitmacro' not within `%%macro' block");
3830 spec
.casesense
= casesense
;
3831 if (!parse_mmacro_spec(tline
, &spec
, dname
)) {
3834 mmac_p
= (MMacro
**) hash_findi(&mmacros
, spec
.name
, NULL
);
3835 while (mmac_p
&& *mmac_p
) {
3837 if (mmac
->casesense
== spec
.casesense
&&
3838 !mstrcmp(mmac
->name
, spec
.name
, spec
.casesense
) &&
3839 mmac
->nparam_min
== spec
.nparam_min
&&
3840 mmac
->nparam_max
== spec
.nparam_max
&&
3841 mmac
->plus
== spec
.plus
) {
3842 *mmac_p
= mmac
->next
;
3845 mmac_p
= &mmac
->next
;
3848 free_tlist(spec
.dlist
);
3853 while (tok_white(tline
->next
))
3854 tline
= tline
->next
;
3856 free_tlist(origline
);
3857 nasm_nonfatal("`%%rotate' missing rotate count");
3858 return DIRECTIVE_FOUND
;
3860 t
= expand_smacro(tline
->next
);
3862 pps
.tptr
= tline
= t
;
3864 tokval
.t_type
= TOKEN_INVALID
;
3866 evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
3869 return DIRECTIVE_FOUND
;
3871 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
3872 if (!is_simple(evalresult
)) {
3873 nasm_nonfatal("non-constant value given to `%%rotate'");
3874 return DIRECTIVE_FOUND
;
3876 mmac
= istk
->mstk
.mmac
;
3878 nasm_nonfatal("`%%rotate' invoked outside a macro call");
3879 } else if (mmac
->nparam
== 0) {
3880 nasm_nonfatal("`%%rotate' invoked within macro without parameters");
3882 int rotate
= mmac
->rotate
+ reloc_value(evalresult
);
3884 rotate
%= (int)mmac
->nparam
;
3886 rotate
+= mmac
->nparam
;
3888 mmac
->rotate
= rotate
;
3894 MMacro
*tmp_defining
;
3897 tline
= skip_white(tline
->next
);
3898 if (tok_type(tline
, TOK_ID
) && tline
->len
== 7 &&
3899 !nasm_memicmp(tline
->text
.a
, ".nolist", 7)) {
3900 nolist
= !list_option('f') || istk
->nolist
;
3901 tline
= skip_white(tline
->next
);
3905 pps
.tptr
= expand_smacro(tline
);
3907 tokval
.t_type
= TOKEN_INVALID
;
3908 /* XXX: really critical?! */
3910 evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
3914 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
3915 if (!is_simple(evalresult
)) {
3916 nasm_nonfatal("non-constant value given to `%%rep'");
3919 count
= reloc_value(evalresult
);
3920 if (count
> nasm_limit
[LIMIT_REP
]) {
3921 nasm_nonfatal("`%%rep' count %"PRId64
" exceeds limit (currently %"PRId64
")",
3922 count
, nasm_limit
[LIMIT_REP
]);
3924 } else if (count
< 0) {
3926 *!negative-rep [on] regative %rep count
3927 *! warns about negative counts given to the \c{%rep}
3928 *! preprocessor directive.
3930 nasm_warn(ERR_PASS2
|WARN_NEGATIVE_REP
,
3931 "negative `%%rep' count: %"PRId64
, count
);
3937 nasm_nonfatal("`%%rep' expects a repeat count");
3940 tmp_defining
= defining
;
3942 defining
->nolist
= nolist
;
3943 defining
->in_progress
= count
;
3944 defining
->mstk
= istk
->mstk
;
3945 defining
->dstk
.mstk
= tmp_defining
;
3946 defining
->dstk
.mmac
= tmp_defining
? tmp_defining
->dstk
.mmac
: NULL
;
3947 src_get(&defining
->xline
, &defining
->fname
);
3952 if (!defining
|| defining
->name
) {
3953 nasm_nonfatal("`%%endrep': no matching `%%rep'");
3958 * Now we have a "macro" defined - although it has no name
3959 * and we won't be entering it in the hash tables - we must
3960 * push a macro-end marker for it on to istk->expansion.
3961 * After that, it will take care of propagating itself (a
3962 * macro-end marker line for a macro which is really a %rep
3963 * block will cause the macro to be re-expanded, complete
3964 * with another macro-end marker to ensure the process
3965 * continues) until the whole expansion is forcibly removed
3966 * from istk->expansion by a %exitrep.
3969 l
->next
= istk
->expansion
;
3970 l
->finishes
= defining
;
3972 istk
->expansion
= l
;
3974 istk
->mstk
.mstk
= defining
;
3976 lfmt
->uplevel(defining
->nolist
? LIST_MACRO_NOLIST
: LIST_MACRO
, 0);
3977 defining
= defining
->dstk
.mstk
;
3982 * We must search along istk->expansion until we hit a
3983 * macro-end marker for a macro with no name. Then we set
3984 * its `in_progress' flag to 0.
3986 list_for_each(l
, istk
->expansion
)
3987 if (l
->finishes
&& !l
->finishes
->name
)
3991 l
->finishes
->in_progress
= 0;
3993 nasm_nonfatal("`%%exitrep' not within `%%rep' block");
4003 if (!(mname
= get_id(&tline
, dname
)))
4007 lastp
= &tline
->next
;
4008 nparam
= parse_smacro_template(&lastp
, &tmpl
);
4012 if (unlikely(i
== PP_DEFALIAS
)) {
4013 macro_start
= tline
;
4014 if (!is_macro_id(macro_start
)) {
4015 nasm_nonfatal("`%s' expects a macro identifier to alias",
4019 tt
= macro_start
->next
;
4020 macro_start
->next
= NULL
;
4021 tline
= tline
->next
;
4022 tline
= skip_white(tline
);
4023 if (tline
&& tline
->type
) {
4024 nasm_warn(WARN_OTHER
,
4025 "trailing garbage after aliasing identifier ignored");
4030 /* Expand the macro definition now for %xdefine and %ixdefine */
4031 if (i
== PP_XDEFINE
)
4032 tline
= expand_smacro(tline
);
4034 /* Reverse expansion list and mark parameter tokens */
4038 if (t
->type
== TOK_ID
) {
4039 const char *ttext
= tok_text(t
);
4040 size_t tlen
= t
->len
;
4041 for (i
= 0; i
< nparam
; i
++) {
4042 if (tmpl
.params
[i
].name
.len
== t
->len
&&
4043 !memcmp(ttext
, tok_text(&tmpl
.params
[i
].name
), tlen
)) {
4044 t
->type
= tok_smac_param(i
);
4050 t
->next
= macro_start
;
4057 * Good. We now have a macro name, a parameter count, and a
4058 * token list (in reverse order) for an expansion. We ought
4059 * to be OK just to create an SMacro, store it, and let
4060 * free_tlist have the rest of the line (which we have
4061 * carefully re-terminated after chopping off the expansion
4064 define_smacro(mname
, casesense
, macro_start
, &tmpl
);
4070 if (!(mname
= get_id(&tline
, dname
)))
4073 nasm_warn(WARN_OTHER
, "trailing garbage after macro name ignored");
4075 undef_smacro(mname
, i
== PP_UNDEFALIAS
);
4079 if (!(mname
= get_id(&tline
, dname
)))
4083 tline
= expand_smacro(tline
->next
);
4086 tline
= zap_white(tline
);
4087 q
= detoken(tline
, false);
4088 macro_start
= make_tok_qstr(NULL
, q
);
4092 * We now have a macro name, an implicit parameter count of
4093 * zero, and a string token to use as an expansion. Create
4094 * and store an SMacro.
4096 define_smacro(mname
, casesense
, macro_start
, NULL
);
4100 if (!(mname
= get_id(&tline
, dname
)))
4104 tline
= expand_smacro(tline
->next
);
4107 t
= skip_white(tline
);
4108 /* t should now point to the string */
4109 if (!tok_type(t
, TOK_STRING
)) {
4110 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4116 * Convert the string to a token stream. Note that smacros
4117 * are stored with the token stream reversed, so we have to
4118 * reverse the output of tokenize().
4120 macro_start
= reverse_tokens(tokenize(unquote_token_cstr(t
)));
4123 * We now have a macro name, an implicit parameter count of
4124 * zero, and a numeric token to use as an expansion. Create
4125 * and store an SMacro.
4127 define_smacro(mname
, casesense
, macro_start
, NULL
);
4133 const char *found_path
;
4135 if (!(mname
= get_id(&tline
, dname
)))
4139 tline
= expand_smacro(tline
->next
);
4142 t
= skip_white(tline
);
4143 if (!t
|| (t
->type
!= TOK_STRING
&&
4144 t
->type
!= TOK_INTERNAL_STRING
)) {
4145 nasm_nonfatal("`%s' expects a file name", dname
);
4150 nasm_warn(WARN_OTHER
, "trailing garbage after `%s' ignored", dname
);
4152 p
= unquote_token_cstr(t
);
4154 inc_fopen(p
, NULL
, &found_path
, INC_PROBE
, NF_BINARY
);
4157 macro_start
= make_tok_qstr(NULL
, found_path
);
4160 * We now have a macro name, an implicit parameter count of
4161 * zero, and a string token to use as an expansion. Create
4162 * and store an SMacro.
4164 define_smacro(mname
, casesense
, macro_start
, NULL
);
4170 if (!(mname
= get_id(&tline
, dname
)))
4174 tline
= expand_smacro(tline
->next
);
4177 t
= skip_white(tline
);
4178 /* t should now point to the string */
4179 if (!tok_type(t
, TOK_STRING
)) {
4180 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4182 free_tlist(origline
);
4183 return DIRECTIVE_FOUND
;
4187 macro_start
= make_tok_num(NULL
, t
->len
);
4190 * We now have a macro name, an implicit parameter count of
4191 * zero, and a numeric token to use as an expansion. Create
4192 * and store an SMacro.
4194 define_smacro(mname
, casesense
, macro_start
, NULL
);
4196 free_tlist(origline
);
4197 return DIRECTIVE_FOUND
;
4200 if (!(mname
= get_id(&tline
, dname
)))
4204 tline
= expand_smacro(tline
->next
);
4208 list_for_each(t
, tline
) {
4210 case TOK_WHITESPACE
:
4217 if (tok_is(t
, ',')) /* permit comma separators */
4219 /* else fall through */
4221 nasm_nonfatal("non-string passed to `%s': %s", dname
,
4228 q
= qbuf
= nasm_malloc(len
);
4229 list_for_each(t
, tline
) {
4230 if (t
->type
== TOK_INTERNAL_STRING
)
4231 q
= mempcpy(q
, tok_text(t
), t
->len
);
4235 * We now have a macro name, an implicit parameter count of
4236 * zero, and a numeric token to use as an expansion. Create
4237 * and store an SMacro.
4239 macro_start
= make_tok_qstr(NULL
, qbuf
);
4241 define_smacro(mname
, casesense
, macro_start
, NULL
);
4247 int64_t start
, count
;
4251 if (!(mname
= get_id(&tline
, dname
)))
4255 tline
= expand_smacro(tline
->next
);
4258 if (tline
) /* skip expanded id */
4263 /* t should now point to the string */
4264 if (!tok_type(t
, TOK_STRING
)) {
4265 nasm_nonfatal("`%s' requires string as second parameter", dname
);
4272 tokval
.t_type
= TOKEN_INVALID
;
4273 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4277 } else if (!is_simple(evalresult
)) {
4278 nasm_nonfatal("non-constant value given to `%s'", dname
);
4282 start
= evalresult
->value
- 1;
4284 pps
.tptr
= skip_white(pps
.tptr
);
4286 count
= 1; /* Backwards compatibility: one character */
4288 tokval
.t_type
= TOKEN_INVALID
;
4289 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4293 } else if (!is_simple(evalresult
)) {
4294 nasm_nonfatal("non-constant value given to `%s'", dname
);
4298 count
= evalresult
->value
;
4304 /* make start and count being in range */
4308 count
= len
+ count
+ 1 - start
;
4309 if (start
+ count
> (int64_t)len
)
4310 count
= len
- start
;
4311 if (!len
|| count
< 0 || start
>=(int64_t)len
)
4312 start
= -1, count
= 0; /* empty string */
4314 txt
= (start
< 0) ? "" : tok_text(t
) + start
;
4316 macro_start
= make_tok_qstr(NULL
, txt
);
4319 * We now have a macro name, an implicit parameter count of
4320 * zero, and a numeric token to use as an expansion. Create
4321 * and store an SMacro.
4323 define_smacro(mname
, casesense
, macro_start
, NULL
);
4329 if (!(mname
= get_id(&tline
, dname
)))
4333 tline
= expand_smacro(tline
->next
);
4338 tokval
.t_type
= TOKEN_INVALID
;
4339 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
4345 nasm_warn(WARN_OTHER
, "trailing garbage after expression ignored");
4347 if (!is_simple(evalresult
)) {
4348 nasm_nonfatal("non-constant value given to `%s'", dname
);
4349 free_tlist(origline
);
4350 return DIRECTIVE_FOUND
;
4353 macro_start
= make_tok_num(NULL
, reloc_value(evalresult
));
4356 * We now have a macro name, an implicit parameter count of
4357 * zero, and a numeric token to use as an expansion. Create
4358 * and store an SMacro.
4360 define_smacro(mname
, casesense
, macro_start
, NULL
);
4364 tline
= tline
->next
;
4365 tline
= expand_smacro(tline
);
4366 do_aliases
= pp_get_boolean_option(tline
, do_aliases
);
4371 * Syntax is `%line nnn[+mmm] [filename]'
4373 if (unlikely(pp_noline
))
4376 tline
= tline
->next
;
4377 tline
= skip_white(tline
);
4378 if (!tok_type(tline
, TOK_NUMBER
)) {
4379 nasm_nonfatal("`%s' expects line number", dname
);
4382 k
= readnum(tok_text(tline
), &err
);
4384 tline
= tline
->next
;
4385 if (tok_is(tline
, '+')) {
4386 tline
= tline
->next
;
4387 if (!tok_type(tline
, TOK_NUMBER
)) {
4388 nasm_nonfatal("`%s' expects line increment", dname
);
4391 m
= readnum(tok_text(tline
), &err
);
4392 tline
= tline
->next
;
4394 tline
= skip_white(tline
);
4398 char *fname
= detoken(tline
, false);
4399 src_set_fname(fname
);
4406 free_tlist(origline
);
4407 return DIRECTIVE_FOUND
;
4411 * Ensure that a macro parameter contains a condition code and
4412 * nothing else. Return the condition code index if so, or -1
4415 static int find_cc(Token
* t
)
4420 return -1; /* Probably a %+ without a space */
4423 if (!tok_type(t
, TOK_ID
))
4426 tt
= skip_white(tt
);
4427 if (tok_isnt(tt
, ','))
4430 return bsii(tok_text(t
), (const char **)conditions
,
4431 ARRAY_SIZE(conditions
));
4434 static inline bool pp_concat_match(const Token
*t
, unsigned int mask
)
4436 return t
&& (PP_CONCAT_MASK(t
->type
) & mask
);
4440 * This routines walks over tokens strem and handles tokens
4441 * pasting, if @handle_explicit passed then explicit pasting
4442 * term is handled, otherwise -- implicit pastings only.
4443 * The @m array can contain a series of token types which are
4444 * executed as separate passes.
4446 static bool paste_tokens(Token
**head
, const struct tokseq_match
*m
,
4447 size_t mnum
, bool handle_explicit
)
4449 Token
*tok
, *t
, *next
, **prev_next
, **prev_nonspace
;
4450 bool pasted
= false;
4455 * The last token before pasting. We need it
4456 * to be able to connect new handled tokens.
4457 * In other words if there were a tokens stream
4461 * and we've joined tokens B and C, the resulting
4467 prev_next
= prev_nonspace
= head
;
4469 if (tok_white(tok
) || tok_type(tok
, TOK_PASTE
))
4470 prev_nonspace
= NULL
;
4472 while (tok
&& (next
= tok
->next
)) {
4473 bool did_paste
= false;
4475 switch (tok
->type
) {
4476 case TOK_WHITESPACE
:
4477 /* Zap redundant whitespaces */
4478 tok
->next
= next
= zap_white(next
);
4482 /* Explicit pasting */
4483 if (!handle_explicit
)
4486 /* Left pasting token is start of line */
4487 if (!prev_nonspace
) {
4488 nasm_nonfatal("No lvalue found on pasting");
4489 tok
= delete_Token(tok
);
4495 prev_next
= prev_nonspace
;
4498 /* Delete leading whitespace */
4499 next
= zap_white(t
->next
);
4501 /* Delete the %+ token itself */
4502 nasm_assert(next
== tok
);
4503 next
= delete_Token(next
);
4505 /* Delete trailing whitespace */
4506 next
= zap_white(next
);
4509 * No ending token, this might happen in two
4512 * 1) There indeed no right token at all
4513 * 2) There is a bare "%define ID" statement,
4514 * and @ID does expand to whitespace.
4516 * So technically we need to do a grammar analysis
4517 * in another stage of parsing, but for now lets don't
4518 * change the behaviour people used to. Simply allow
4519 * whitespace after paste token.
4522 *prev_nonspace
= tok
= NULL
; /* End of line */
4526 p
= buf
= nasm_malloc(t
->len
+ next
->len
+ 1);
4527 p
= mempcpy(p
, tok_text(t
), t
->len
);
4528 p
= mempcpy(p
, tok_text(next
), next
->len
);
4536 * No output at all? Replace with a single whitespace.
4537 * This should never happen.
4539 t
= new_White(NULL
);
4542 *prev_nonspace
= tok
= t
;
4544 t
= t
->next
; /* Find the last token produced */
4546 /* Delete the second token and attach to the end of the list */
4547 t
->next
= delete_Token(next
);
4549 /* We want to restart from the head of the pasted token */
4554 /* implicit pasting */
4555 for (i
= 0; i
< mnum
; i
++) {
4556 if (pp_concat_match(tok
, m
[i
].mask_head
))
4564 while (pp_concat_match(next
, m
[i
].mask_tail
)) {
4569 /* No match or no text to process */
4570 if (len
== tok
->len
)
4573 p
= buf
= nasm_malloc(len
+ 1);
4574 while (tok
!= next
) {
4575 p
= mempcpy(p
, tok_text(tok
), tok
->len
);
4576 tok
= delete_Token(tok
);
4579 *prev_next
= tok
= t
= tokenize(buf
);
4583 * Connect pasted into original stream,
4584 * ie A -> new-tokens -> B
4589 prev_next
= prev_nonspace
= &t
->next
;
4597 prev_next
= &tok
->next
;
4598 if (next
&& next
->type
!= TOK_WHITESPACE
&& next
->type
!= TOK_PASTE
)
4599 prev_nonspace
= prev_next
;
4609 * Computes the proper rotation of mmacro parameters
4611 static int mmac_rotate(const MMacro
*mac
, unsigned int n
)
4613 if (--n
< mac
->nparam
)
4614 n
= (n
+ mac
->rotate
) % mac
->nparam
;
4620 * expands to a list of tokens from %{x:y}
4622 static Token
*expand_mmac_params_range(MMacro
*mac
, Token
*tline
, Token
***last
)
4624 Token
*t
= tline
, **tt
, *tm
, *head
;
4628 pos
= strchr(tok_text(tline
), ':');
4631 lst
= atoi(pos
+ 1);
4632 fst
= atoi(tok_text(tline
) + 1);
4635 * only macros params are accounted so
4636 * if someone passes %0 -- we reject such
4639 if (lst
== 0 || fst
== 0)
4642 /* the values should be sane */
4643 if ((fst
> (int)mac
->nparam
|| fst
< (-(int)mac
->nparam
)) ||
4644 (lst
> (int)mac
->nparam
|| lst
< (-(int)mac
->nparam
)))
4647 fst
= fst
< 0 ? fst
+ (int)mac
->nparam
+ 1: fst
;
4648 lst
= lst
< 0 ? lst
+ (int)mac
->nparam
+ 1: lst
;
4650 /* count from zero */
4654 * It will be at least one token. Note we
4655 * need to scan params until separator, otherwise
4656 * only first token will be passed.
4658 j
= (fst
+ mac
->rotate
) % mac
->nparam
;
4659 tm
= mac
->params
[j
+1];
4662 head
= dup_Token(NULL
, tm
);
4663 tt
= &head
->next
, tm
= tm
->next
;
4664 while (tok_isnt(tm
, ',')) {
4665 t
= dup_Token(NULL
, tm
);
4666 *tt
= t
, tt
= &t
->next
, tm
= tm
->next
;
4670 for (i
= fst
+ 1; i
<= lst
; i
++) {
4671 t
= make_tok_char(NULL
, ',');
4672 *tt
= t
, tt
= &t
->next
;
4673 j
= (i
+ mac
->rotate
) % mac
->nparam
;
4674 tm
= mac
->params
[j
+1];
4675 while (tok_isnt(tm
, ',')) {
4676 t
= dup_Token(NULL
, tm
);
4677 *tt
= t
, tt
= &t
->next
, tm
= tm
->next
;
4681 for (i
= fst
- 1; i
>= lst
; i
--) {
4682 t
= make_tok_char(NULL
, ',');
4683 *tt
= t
, tt
= &t
->next
;
4684 j
= (i
+ mac
->rotate
) % mac
->nparam
;
4685 tm
= mac
->params
[j
+1];
4686 while (!tok_isnt(tm
, ',')) {
4687 t
= dup_Token(NULL
, tm
);
4688 *tt
= t
, tt
= &t
->next
, tm
= tm
->next
;
4697 nasm_nonfatal("`%%{%s}': macro parameters out of range",
4698 tok_text(tline
) + 1);
4703 * Expand MMacro-local things: parameter references (%0, %n, %+n,
4704 * %-n) and MMacro-local identifiers (%%foo) as well as
4705 * macro indirection (%[...]) and range (%{..:..}).
4707 static Token
*expand_mmac_params(Token
* tline
)
4709 Token
**tail
, *thead
;
4710 bool changed
= false;
4711 MMacro
*mac
= istk
->mstk
.mmac
;
4719 const char *text
= tok_text(t
);
4722 tline
= tline
->next
;
4726 case TOK_LOCAL_SYMBOL
:
4728 text
= nasm_asprintf("..@%"PRIu64
".%s", mac
->unique
, text
+2);
4731 case TOK_MMACRO_PARAM
:
4738 nasm_nonfatal("`%s': not in a macro call", text
);
4743 if (strchr(text
, ':')) {
4745 * seems we have a parameters range here
4747 Token
*head
, **last
;
4748 head
= expand_mmac_params_range(mac
, t
, &last
);
4759 * We have to make a substitution of one of the
4760 * forms %1, %-1, %+1, %%foo, %0, %00.
4765 text
= nasm_asprintf("%d", mac
->nparam
);
4768 if (text
[2] != '0' || text
[3])
4770 /* a possible captured label == mac->params[0] */
4777 n
= strtoul(text
+ 1, &ep
, 10);
4781 if (n
<= mac
->nparam
) {
4782 n
= mmac_rotate(mac
, n
);
4783 dup_tlistn(mac
->params
[n
], mac
->paramlen
[n
], &tail
);
4797 n
= strtoul(tok_text(t
) + 2, &ep
, 10);
4801 if (n
&& n
< mac
->nparam
) {
4802 n
= mmac_rotate(mac
, n
);
4803 tt
= mac
->params
[n
];
4807 nasm_nonfatal("macro parameter `%s' is not a condition code",
4814 if (text
[1] == '-') {
4815 int ncc
= inverse_ccs
[cc
];
4816 if (unlikely(ncc
== -1)) {
4817 nasm_nonfatal("condition code `%s' is not invertible",
4823 text
= nasm_strdup(conditions
[cc
]);
4828 nasm_nonfatal("invalid macro parameter: `%s'", text
);
4838 text
= nasm_strdup(mac
->iname
);
4845 case TOK_PREPROC_QQ
:
4848 text
= nasm_strdup(mac
->name
);
4859 tt
= tokenize(tok_text(t
));
4860 tt
= expand_mmac_params(tt
);
4861 tt
= expand_smacro(tt
);
4862 /* Why dup_tlist() here? We should own tt... */
4863 dup_tlist(tt
, &tail
);
4880 set_text(t
, text
, tok_strlen(text
));
4893 const struct tokseq_match t
[] = {
4895 PP_CONCAT_MASK(TOK_ID
) |
4896 PP_CONCAT_MASK(TOK_FLOAT
), /* head */
4897 PP_CONCAT_MASK(TOK_ID
) |
4898 PP_CONCAT_MASK(TOK_NUMBER
) |
4899 PP_CONCAT_MASK(TOK_FLOAT
) |
4900 PP_CONCAT_MASK(TOK_OTHER
) /* tail */
4903 PP_CONCAT_MASK(TOK_NUMBER
), /* head */
4904 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
4907 paste_tokens(&thead
, t
, ARRAY_SIZE(t
), false);
4913 static Token
*expand_smacro_noreset(Token
* tline
);
4916 * Expand *one* single-line macro instance. If the first token is not
4917 * a macro at all, it is simply copied to the output and the pointer
4918 * advanced. tpp should be a pointer to a pointer (usually the next
4919 * pointer of the previous token) to the first token. **tpp is updated
4920 * to point to the first token of the expansion, and *tpp updated to
4921 * point to the next pointer of the last token of the expansion.
4923 * If the expansion is empty, *tpp will be unchanged but **tpp will
4924 * be advanced past the macro call.
4926 * Return the macro expanded, or NULL if no expansion took place.
4928 static SMacro
*expand_one_smacro(Token
***tpp
)
4930 Token
**params
= NULL
;
4932 Token
*mstart
= **tpp
;
4933 Token
*tline
= mstart
;
4936 Token
*t
, *tup
, *tafter
;
4941 return false; /* Empty line, nothing to do */
4943 mname
= tok_text(mstart
);
4945 smacro_deadman
.total
--;
4946 smacro_deadman
.levels
--;
4948 if (unlikely(smacro_deadman
.total
< 0 || smacro_deadman
.levels
< 0)) {
4949 if (unlikely(!smacro_deadman
.triggered
)) {
4950 nasm_nonfatal("interminable macro recursion");
4951 smacro_deadman
.triggered
= true;
4954 } else if (tline
->type
== TOK_ID
|| tline
->type
== TOK_PREPROC_ID
) {
4955 head
= (SMacro
*)hash_findix(&smacros
, mname
);
4956 } else if (tline
->type
== TOK_LOCAL_MACRO
) {
4957 Context
*ctx
= get_ctx(mname
, &mname
);
4958 head
= ctx
? (SMacro
*)hash_findix(&ctx
->localmac
, mname
) : NULL
;
4964 * We've hit an identifier of some sort. First check whether the
4965 * identifier is a single-line macro at all, then think about
4966 * checking for parameters if necessary.
4968 list_for_each(m
, head
) {
4969 if (unlikely(m
->alias
&& !do_aliases
))
4971 if (!mstrcmp(m
->name
, mname
, m
->casesense
))
4979 /* Parse parameters, if applicable */
4984 if (m
->nparam
== 0) {
4986 * Simple case: the macro is parameterless.
4987 * Nothing to parse; the expansion code will
4988 * drop the macro name token.
4992 * Complicated case: at least one macro with this name
4993 * exists and takes parameters. We must find the
4994 * parameters in the call, count them, find the SMacro
4995 * that corresponds to that form of the macro call, and
4996 * substitute for the parameters when we expand. What a
5000 int paren
, brackets
;
5002 tline
= tline
->next
;
5003 tline
= skip_white(tline
);
5004 if (!tok_is(tline
, '(')) {
5006 * This macro wasn't called with parameters: ignore
5007 * the call. (Behaviour borrowed from gnu cpp.)
5015 t
= tline
; /* tline points to leading ( */
5021 nasm_nonfatal("macro call expects terminating `)'");
5025 if (t
->type
!= TOK_OTHER
|| t
->len
!= 1)
5028 switch (t
->text
.a
[0]) {
5054 break; /* Normal token */
5059 * Look for a macro matching in both name and parameter count.
5060 * We already know any matches cannot be anywhere before the
5061 * current position of "m", so there is no reason to
5067 *!macro-params-single [on] single-line macro calls with wrong parameter count
5068 *! warns about \i{single-line macros} being invoked
5069 *! with the wrong number of parameters.
5071 nasm_warn(WARN_MACRO_PARAMS_SINGLE
,
5072 "single-line macro `%s' exists, "
5073 "but not taking %d parameter%s",
5074 mname
, nparam
, (nparam
== 1) ? "" : "s");
5078 if (!mstrcmp(m
->name
, mname
, m
->casesense
)) {
5079 if (nparam
== m
->nparam
)
5080 break; /* It's good */
5081 if (m
->greedy
&& nparam
>= m
->nparam
-1)
5082 break; /* Also good */
5091 /* Expand the macro */
5092 m
->in_progress
= true;
5095 /* Extract parameters */
5096 Token
**phead
, **pep
;
5100 bool bracketed
= false;
5101 bool bad_bracket
= false;
5102 enum sparmflags flags
;
5106 nasm_newn(params
, nparam
);
5108 flags
= m
->params
[i
].flags
;
5109 phead
= pep
= ¶ms
[i
];
5116 tline
= tline
->next
;
5119 nasm_nonfatal("macro call expects terminating `)'");
5125 switch (tline
->type
) {
5127 if (tline
->len
== 1)
5128 ch
= tline
->text
.a
[0];
5131 case TOK_WHITESPACE
:
5132 if (!(flags
& SPARM_NOSTRIP
)) {
5133 if (brackets
|| *phead
)
5134 white
++; /* Keep interior whitespace */
5145 if (!brackets
&& !(flags
& SPARM_GREEDY
)) {
5147 nasm_assert(i
< nparam
);
5148 phead
= pep
= ¶ms
[i
];
5152 flags
= m
->params
[i
].flags
;
5158 bracketed
= !*phead
&& !(flags
& SPARM_NOSTRIP
);
5181 i
++; /* Found last argument */
5187 break; /* Normal token */
5193 bad_bracket
|= bracketed
&& !brackets
;
5196 *pep
= t
= new_White(NULL
);
5200 *pep
= t
= dup_Token(NULL
, tline
);
5206 * Possible further processing of parameters. Note that the
5207 * ordering matters here.
5209 for (i
= 0; i
< nparam
; i
++) {
5210 enum sparmflags flags
= m
->params
[i
].flags
;
5212 if (flags
& SPARM_EVAL
) {
5213 /* Evaluate this parameter as a number */
5215 struct tokenval tokval
;
5219 pps
.tptr
= eval_param
= expand_smacro_noreset(params
[i
]);
5221 tokval
.t_type
= TOKEN_INVALID
;
5222 evalresult
= evaluate(ppscan
, &pps
, &tokval
, NULL
, true, NULL
);
5224 free_tlist(eval_param
);
5228 /* Nothing meaningful to do */
5229 } else if (tokval
.t_type
) {
5230 nasm_nonfatal("invalid expression in parameter %d of macro `%s'", i
, m
->name
);
5231 } else if (!is_simple(evalresult
)) {
5232 nasm_nonfatal("non-constant expression in parameter %d of macro `%s'", i
, m
->name
);
5234 params
[i
] = make_tok_num(NULL
, reloc_value(evalresult
));
5238 if (flags
& SPARM_STR
) {
5239 /* Convert expansion to a quoted string */
5243 qs
= expand_smacro_noreset(params
[i
]);
5244 arg
= detoken(qs
, false);
5246 params
[i
] = make_tok_qstr(NULL
, arg
);
5252 /* Note: we own the expansion this returns. */
5253 t
= m
->expand(m
, params
, nparam
);
5255 tafter
= tline
->next
; /* Skip past the macro call */
5256 tline
->next
= NULL
; /* Truncate list at the macro call end */
5263 enum pp_token_type type
= t
->type
;
5264 Token
*tnext
= t
->next
;
5269 t
= dup_Token(tline
, mstart
);
5272 case TOK_PREPROC_QQ
:
5274 size_t mlen
= strlen(m
->name
);
5278 t
->type
= mstart
->type
;
5279 if (t
->type
== TOK_LOCAL_MACRO
) {
5280 const char *psp
; /* prefix start pointer */
5281 const char *pep
; /* prefix end pointer */
5284 psp
= tok_text(mstart
);
5289 p
= nasm_malloc(len
+ 1);
5290 p
= mempcpy(p
, psp
, plen
);
5293 p
= nasm_malloc(len
+ 1);
5295 p
= mempcpy(p
, m
->name
, mlen
);
5297 set_text_free(t
, p
, len
);
5303 case TOK_COND_COMMA
:
5305 t
= cond_comma
? make_tok_char(tline
, ',') : NULL
;
5309 case TOK_PREPROC_ID
:
5310 case TOK_LOCAL_MACRO
:
5313 * Chain this into the target line *before* expanding,
5314 * that way we pick up any arguments to the new macro call,
5319 expand_one_smacro(&tp
);
5320 tline
= *tp
; /* First token left after any macro call */
5324 if (is_smac_param(t
->type
)) {
5325 int param
= smac_nparam(t
->type
);
5326 nasm_assert(!tup
&& param
< nparam
);
5330 tnext
= dup_tlist_reverse(params
[param
], NULL
);
5338 Token
*endt
= tline
;
5341 while (!cond_comma
&& t
&& t
!= endt
)
5342 cond_comma
= t
->type
!= TOK_WHITESPACE
;
5354 for (t
= tline
; t
!= tafter
; t
= t
->next
)
5357 m
->in_progress
= false;
5359 /* Don't do this until after expansion or we will clobber mname */
5364 * No macro expansion needed; roll back to mstart (if necessary)
5365 * and then advance to the next input token. Note that this is
5366 * by far the common case!
5369 *tpp
= &mstart
->next
;
5372 smacro_deadman
.levels
++;
5373 if (unlikely(params
))
5374 free_tlist_array(params
, nparam
);
5379 * Expand all single-line macro calls made in the given line.
5380 * Return the expanded version of the line. The original is deemed
5381 * to be destroyed in the process. (In reality we'll just move
5382 * Tokens from input to output a lot of the time, rather than
5383 * actually bothering to destroy and replicate.)
5385 static Token
*expand_smacro(Token
*tline
)
5387 smacro_deadman
.total
= nasm_limit
[LIMIT_MACRO_TOKENS
];
5388 smacro_deadman
.levels
= nasm_limit
[LIMIT_MACRO_LEVELS
];
5389 smacro_deadman
.triggered
= false;
5390 return expand_smacro_noreset(tline
);
5393 static Token
*expand_smacro_noreset(Token
*org_tline
)
5399 return NULL
; /* Empty input */
5402 * Trick: we should avoid changing the start token pointer since it can
5403 * be contained in "next" field of other token. Because of this
5404 * we allocate a copy of first token and work with it; at the end of
5405 * routine we copy it back
5407 tline
= dup_Token(org_tline
->next
, org_tline
);
5410 * Pretend that we always end up doing expansion on the first pass;
5411 * that way %+ get processed. However, if we process %+ before the
5412 * first pass, we end up with things like MACRO %+ TAIL trying to
5413 * look up the macro "MACROTAIL", which we don't want.
5417 static const struct tokseq_match tmatch
[] = {
5419 PP_CONCAT_MASK(TOK_ID
) |
5420 PP_CONCAT_MASK(TOK_LOCAL_MACRO
) |
5421 PP_CONCAT_MASK(TOK_ENVIRON
) |
5422 PP_CONCAT_MASK(TOK_PREPROC_ID
), /* head */
5423 PP_CONCAT_MASK(TOK_ID
) |
5424 PP_CONCAT_MASK(TOK_LOCAL_MACRO
) |
5425 PP_CONCAT_MASK(TOK_ENVIRON
) |
5426 PP_CONCAT_MASK(TOK_PREPROC_ID
) |
5427 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
5430 Token
**tail
= &tline
;
5432 while (*tail
) /* main token loop */
5433 expanded
|= !!expand_one_smacro(&tail
);
5439 * Now scan the entire line and look for successive TOK_IDs
5440 * that resulted after expansion (they can't be produced by
5441 * tokenize()). The successive TOK_IDs should be concatenated.
5442 * Also we look for %+ tokens and concatenate the tokens
5443 * before and after them (without white spaces in between).
5445 if (!paste_tokens(&tline
, tmatch
, ARRAY_SIZE(tmatch
), true))
5446 break; /* Done again! */
5453 * The expression expanded to empty line;
5454 * we can't return NULL because of the "trick" above.
5455 * Just set the line to a single WHITESPACE token.
5458 tline
= new_White(NULL
);
5461 steal_Token(org_tline
, tline
);
5462 org_tline
->next
= tline
->next
;
5463 delete_Token(tline
);
5469 * Similar to expand_smacro but used exclusively with macro identifiers
5470 * right before they are fetched in. The reason is that there can be
5471 * identifiers consisting of several subparts. We consider that if there
5472 * are more than one element forming the name, user wants a expansion,
5473 * otherwise it will be left as-is. Example:
5477 * the identifier %$abc will be left as-is so that the handler for %define
5478 * will suck it and define the corresponding value. Other case:
5480 * %define _%$abc cde
5482 * In this case user wants name to be expanded *before* %define starts
5483 * working, so we'll expand %$abc into something (if it has a value;
5484 * otherwise it will be left as-is) then concatenate all successive
5487 static Token
*expand_id(Token
* tline
)
5489 Token
*cur
, *oldnext
= NULL
;
5491 if (!tline
|| !tline
->next
)
5496 (cur
->next
->type
== TOK_ID
|| cur
->next
->type
== TOK_PREPROC_ID
||
5497 cur
->next
->type
== TOK_LOCAL_MACRO
|| cur
->next
->type
== TOK_NUMBER
))
5500 /* If identifier consists of just one token, don't expand */
5505 oldnext
= cur
->next
; /* Detach the tail past identifier */
5506 cur
->next
= NULL
; /* so that expand_smacro stops here */
5509 tline
= expand_smacro(tline
);
5512 /* expand_smacro possibly changhed tline; re-scan for EOL */
5514 while (cur
&& cur
->next
)
5517 cur
->next
= oldnext
;
5524 * Determine whether the given line constitutes a multi-line macro
5525 * call, and return the MMacro structure called if so. Doesn't have
5526 * to check for an initial label - that's taken care of in
5527 * expand_mmacro - but must check numbers of parameters. Guaranteed
5528 * to be called with tline->type == TOK_ID, so the putative macro
5529 * name is easy to find.
5531 static MMacro
*is_mmacro(Token
* tline
, int *nparamp
, Token
***params_array
)
5536 const char *finding
= tok_text(tline
);
5538 head
= (MMacro
*) hash_findix(&mmacros
, finding
);
5541 * Efficiency: first we see if any macro exists with the given
5542 * name which isn't already excluded by macro cycle removal.
5543 * (The cycle removal test here helps optimize the case of wrapping
5544 * instructions, and is cheap to do here.)
5546 * If not, we can return NULL immediately. _Then_ we
5547 * count the parameters, and then we look further along the
5548 * list if necessary to find the proper MMacro.
5550 list_for_each(m
, head
) {
5551 if (!mstrcmp(m
->name
, finding
, m
->casesense
) &&
5552 (m
->in_progress
!= 1 || m
->max_depth
> 0))
5553 break; /* Found something that needs consideration */
5559 * OK, we have a potential macro. Count and demarcate the
5562 count_mmac_params(tline
->next
, &nparam
, ¶ms
);
5565 * So we know how many parameters we've got. Find the MMacro
5566 * structure that handles this number.
5569 if (m
->nparam_min
<= nparam
5570 && (m
->plus
|| nparam
<= m
->nparam_max
)) {
5572 * This one is right. Just check if cycle removal
5573 * prohibits us using it before we actually celebrate...
5575 if (m
->in_progress
> m
->max_depth
) {
5576 if (m
->max_depth
> 0) {
5577 nasm_warn(WARN_OTHER
, "reached maximum recursion depth of %i",
5584 * It's right, and we can use it. Add its default
5585 * parameters to the end of our list if necessary.
5587 if (m
->defaults
&& nparam
< m
->nparam_min
+ m
->ndefs
) {
5588 int newnparam
= m
->nparam_min
+ m
->ndefs
;
5589 params
= nasm_realloc(params
, sizeof(*params
) * (newnparam
+2));
5590 memcpy(¶ms
[nparam
+1], &m
->defaults
[nparam
+1-m
->nparam_min
],
5591 (newnparam
- nparam
) * sizeof(*params
));
5595 * If we've gone over the maximum parameter count (and
5596 * we're in Plus mode), ignore parameters beyond
5599 if (m
->plus
&& nparam
> m
->nparam_max
)
5600 nparam
= m
->nparam_max
;
5603 * If nparam was adjusted above, make sure the list is still
5606 params
[nparam
+1] = NULL
;
5609 *params_array
= params
;
5614 * This one wasn't right: look for the next one with the
5617 list_for_each(m
, m
->next
)
5618 if (!mstrcmp(m
->name
, tok_text(tline
), m
->casesense
))
5623 * After all that, we didn't find one with the right number of
5624 * parameters. Issue a warning, and fail to expand the macro.
5626 *!macro-params-multi [on] multi-line macro calls with wrong parameter count
5627 *! warns about \i{multi-line macros} being invoked
5628 *! with the wrong number of parameters. See \k{mlmacover} for an
5629 *! example of why you might want to disable this warning.
5631 nasm_warn(WARN_MACRO_PARAMS_MULTI
,
5632 "multi-line macro `%s' exists, but not taking %d parameter%s",
5633 tok_text(tline
), nparam
, (nparam
== 1) ? "" : "s");
5642 * Save MMacro invocation specific fields in
5643 * preparation for a recursive macro expansion
5645 static void push_mmacro(MMacro
*m
)
5647 MMacroInvocation
*i
;
5649 i
= nasm_malloc(sizeof(MMacroInvocation
));
5651 i
->params
= m
->params
;
5652 i
->iline
= m
->iline
;
5653 i
->nparam
= m
->nparam
;
5654 i
->rotate
= m
->rotate
;
5655 i
->paramlen
= m
->paramlen
;
5656 i
->unique
= m
->unique
;
5657 i
->condcnt
= m
->condcnt
;
5663 * Restore MMacro invocation specific fields that were
5664 * saved during a previous recursive macro expansion
5666 static void pop_mmacro(MMacro
*m
)
5668 MMacroInvocation
*i
;
5673 m
->params
= i
->params
;
5674 m
->iline
= i
->iline
;
5675 m
->nparam
= i
->nparam
;
5676 m
->rotate
= i
->rotate
;
5677 m
->paramlen
= i
->paramlen
;
5678 m
->unique
= i
->unique
;
5679 m
->condcnt
= i
->condcnt
;
5687 * List an mmacro call with arguments (-Lm option)
5689 static void list_mmacro_call(const MMacro
*m
)
5691 const char prefix
[] = " ;;; [macro] ";
5692 size_t namelen
, size
;
5697 namelen
= strlen(m
->iname
);
5698 size
= namelen
+ sizeof(prefix
); /* Includes final null (from prefix) */
5700 for (i
= 1; i
<= m
->nparam
; i
++) {
5702 size
+= 3; /* Braces and space/comma */
5703 list_for_each(t
, m
->params
[i
]) {
5704 if (j
++ >= m
->paramlen
[i
])
5706 size
+= (t
->type
== TOK_WHITESPACE
) ? 1 : t
->len
;
5710 buf
= p
= nasm_malloc(size
);
5711 p
= mempcpy(p
, prefix
, sizeof(prefix
) - 1);
5712 p
= mempcpy(p
, m
->iname
, namelen
);
5715 for (i
= 1; i
<= m
->nparam
; i
++) {
5718 list_for_each(t
, m
->params
[i
]) {
5719 if (j
++ >= m
->paramlen
[i
])
5721 p
= mempcpy(p
, tok_text(t
), t
->len
);
5727 *--p
= '\0'; /* Replace last delimeter with null */
5728 lfmt
->line(LIST_MACRO
, -1, buf
);
5733 * Expand the multi-line macro call made by the given line, if
5734 * there is one to be expanded. If there is, push the expansion on
5735 * istk->expansion and return 1. Otherwise return 0.
5737 static int expand_mmacro(Token
* tline
)
5739 Token
*startline
= tline
;
5740 Token
*label
= NULL
;
5741 bool dont_prepend
= false;
5742 Token
**params
, *t
, *tt
;
5751 /* if (!tok_type(t, TOK_ID)) Lino 02/25/02 */
5752 if (!tok_type(t
, TOK_ID
) && !tok_type(t
, TOK_LOCAL_MACRO
))
5754 m
= is_mmacro(t
, &nparam
, ¶ms
);
5756 mname
= tok_text(t
);
5760 * We have an id which isn't a macro call. We'll assume
5761 * it might be a label; we'll also check to see if a
5762 * colon follows it. Then, if there's another id after
5763 * that lot, we'll check it again for macro-hood.
5768 last
= t
, t
= t
->next
;
5769 if (tok_is(t
, ':')) {
5770 dont_prepend
= true;
5771 last
= t
, t
= t
->next
;
5773 last
= t
, t
= t
->next
;
5775 if (!tok_type(t
, TOK_ID
) || !(m
= is_mmacro(t
, &nparam
, ¶ms
)))
5778 mname
= tok_text(t
);
5782 if (unlikely(mmacro_deadman
.total
>= nasm_limit
[LIMIT_MMACROS
] ||
5783 mmacro_deadman
.levels
>= nasm_limit
[LIMIT_MACRO_LEVELS
])) {
5784 if (!mmacro_deadman
.triggered
) {
5785 nasm_nonfatal("interminable multiline macro recursion");
5786 mmacro_deadman
.triggered
= true;
5791 mmacro_deadman
.total
++;
5792 mmacro_deadman
.levels
++;
5795 * Fix up the parameters: this involves stripping leading and
5796 * trailing whitespace, then stripping braces if they are
5799 nasm_newn(paramlen
, nparam
+1);
5801 nasm_assert(params
[nparam
+1] == NULL
);
5803 for (i
= 1; (t
= params
[i
]); i
++) {
5804 bool braced
= false;
5807 bool comma
= !m
->plus
|| i
< nparam
;
5810 if (tok_is(t
, '{')) {
5818 for (; t
; t
= t
->next
) {
5824 if (t
->type
== TOK_OTHER
&& t
->len
== 1) {
5825 switch (t
->text
.a
[0]) {
5827 if (comma
&& !brace
)
5837 if (braced
&& !brace
) {
5838 paramlen
[i
] += white
;
5848 paramlen
[i
] += white
+ 1;
5856 * OK, we have a MMacro structure together with a set of
5857 * parameters. We must now go through the expansion and push
5858 * copies of each Line on to istk->expansion. Substitution of
5859 * parameter tokens and macro-local tokens doesn't get done
5860 * until the single-line macro substitution process; this is
5861 * because delaying them allows us to change the semantics
5862 * later through %rotate and give the right semantics for
5865 * First, push an end marker on to istk->expansion, mark this
5866 * macro as in progress, and set up its invocation-specific
5870 ll
->next
= istk
->expansion
;
5872 istk
->expansion
= ll
;
5875 * Save the previous MMacro expansion in the case of
5879 if (m
->max_depth
&& m
->in_progress
)
5886 m
->iname
= nasm_strdup(mname
);
5889 m
->paramlen
= paramlen
;
5890 m
->unique
= unique
++;
5894 m
->mstk
= istk
->mstk
;
5895 istk
->mstk
.mstk
= istk
->mstk
.mmac
= m
;
5897 list_for_each(l
, m
->expansion
) {
5899 ll
->next
= istk
->expansion
;
5900 istk
->expansion
= ll
;
5901 ll
->first
= dup_tlist(l
->first
, NULL
);
5905 * If we had a label, and this macro definition does not include
5906 * a %00, push it on as the first line of, ot
5907 * the macro expansion.
5911 * We had a label. If this macro contains an %00 parameter,
5912 * save the value as a special parameter (which is what it
5913 * is), otherwise push it as the first line of the macro
5916 if (m
->capture_label
) {
5917 params
[0] = dup_Token(NULL
, label
);
5919 free_tlist(startline
);
5922 ll
->finishes
= NULL
;
5923 ll
->next
= istk
->expansion
;
5924 istk
->expansion
= ll
;
5925 ll
->first
= startline
;
5926 if (!dont_prepend
) {
5928 label
= label
->next
;
5929 label
->next
= tt
= make_tok_char(NULL
, ':');
5934 lfmt
->uplevel(m
->nolist
? LIST_MACRO_NOLIST
: LIST_MACRO
, 0);
5936 if (list_option('m') && !m
->nolist
)
5937 list_mmacro_call(m
);
5943 * This function decides if an error message should be suppressed.
5944 * It will never be called with a severity level of ERR_FATAL or
5947 static bool pp_suppress_error(errflags severity
)
5950 * If we're in a dead branch of IF or something like it, ignore the error.
5951 * However, because %else etc are evaluated in the state context
5952 * of the previous branch, errors might get lost:
5953 * %if 0 ... %else trailing garbage ... %endif
5954 * So %else etc should set the ERR_PP_PRECOND flag.
5956 if (istk
&& istk
->conds
&&
5957 ((severity
& ERR_PP_PRECOND
) ?
5958 istk
->conds
->state
== COND_NEVER
:
5959 !emitting(istk
->conds
->state
)))
5966 stdmac_file(const SMacro
*s
, Token
**params
, int nparams
)
5972 return make_tok_qstr(NULL
, src_get_fname());
5976 stdmac_line(const SMacro
*s
, Token
**params
, int nparams
)
5982 return make_tok_num(NULL
, src_get_linnum());
5986 stdmac_bits(const SMacro
*s
, Token
**params
, int nparams
)
5992 return make_tok_num(NULL
, globalbits
);
5996 stdmac_ptr(const SMacro
*s
, Token
**params
, int nparams
)
6002 switch (globalbits
) {
6004 return new_Token(NULL
, TOK_ID
, "word", 4);
6006 return new_Token(NULL
, TOK_ID
, "dword", 5);
6008 return new_Token(NULL
, TOK_ID
, "qword", 5);
6014 /* Add magic standard macros */
6015 struct magic_macros
{
6020 static const struct magic_macros magic_macros
[] =
6022 { "__?FILE?__", 0, stdmac_file
},
6023 { "__?LINE?__", 0, stdmac_line
},
6024 { "__?BITS?__", 0, stdmac_bits
},
6025 { "__?PTR?__", 0, stdmac_ptr
},
6029 static void pp_add_magic_stdmac(void)
6031 const struct magic_macros
*m
;
6036 for (m
= magic_macros
; m
->name
; m
++) {
6037 tmpl
.nparam
= m
->nparam
;
6038 tmpl
.expand
= m
->func
;
6039 define_smacro(m
->name
, true, NULL
, &tmpl
);
6044 pp_reset(const char *file
, enum preproc_mode mode
, struct strlist
*dep_list
)
6047 struct Include
*inc
;
6051 nested_mac_count
= 0;
6052 nested_rep_count
= 0;
6060 use_loaded
= nasm_malloc(use_package_count
* sizeof(bool));
6061 memset(use_loaded
, 0, use_package_count
* sizeof(bool));
6063 /* First set up the top level input file */
6065 istk
->fp
= nasm_open_read(file
, NF_TEXT
);
6069 nasm_fatalf(ERR_NOFILE
, "unable to open input file `%s'", file
);
6071 strlist_add(deplist
, file
);
6074 * Set up the stdmac packages as a virtual include file,
6075 * indicated by a null file pointer.
6079 inc
->fname
= src_set_fname(NULL
);
6080 inc
->nolist
= !list_option('b');
6082 lfmt
->uplevel(LIST_INCLUDE
, 0);
6084 pp_add_magic_stdmac();
6086 if (tasm_compatible_mode
)
6087 pp_add_stdmac(nasm_stdmac_tasm
);
6089 pp_add_stdmac(nasm_stdmac_nasm
);
6090 pp_add_stdmac(nasm_stdmac_version
);
6093 pp_add_stdmac(extrastdmac
);
6095 stdmacpos
= stdmacros
[0];
6096 stdmacnext
= &stdmacros
[1];
6101 * Define the __?PASS?__ macro. This is defined here unlike all the
6102 * other builtins, because it is special -- it varies between
6103 * passes -- but there is really no particular reason to make it
6106 * 0 = dependencies only
6107 * 1 = preparatory passes
6109 * 3 = preproces only
6113 apass
= pass_final() ? 2 : 1;
6125 define_smacro("__?PASS?__", true, make_tok_num(NULL
, apass
), NULL
);
6128 static void pp_init(void)
6133 * Get a line of tokens. If we popped the macro expansion/include stack,
6134 * we return a pointer to the dummy token tok_pop; at that point if
6135 * istk is NULL then we have reached end of input;
6137 static Token tok_pop
; /* Dummy token placeholder */
6139 static Token
*pp_tokline(void)
6142 Line
*l
= istk
->expansion
;
6143 Token
*tline
= NULL
;
6147 * Fetch a tokenized line, either from the macro-expansion
6148 * buffer or from the input file.
6151 while (l
&& l
->finishes
) {
6152 MMacro
*fm
= l
->finishes
;
6154 if (!fm
->name
&& fm
->in_progress
> 1) {
6156 * This is a macro-end marker for a macro with no
6157 * name, which means it's not really a macro at all
6158 * but a %rep block, and the `in_progress' field is
6159 * more than 1, meaning that we still need to
6160 * repeat. (1 means the natural last repetition; 0
6161 * means termination by %exitrep.) We have
6162 * therefore expanded up to the %endrep, and must
6163 * push the whole block on to the expansion buffer
6164 * again. We don't bother to remove the macro-end
6165 * marker: we'd only have to generate another one
6169 list_for_each(l
, fm
->expansion
) {
6170 Token
*t
, *tt
, **tail
;
6174 ll
->next
= istk
->expansion
;
6177 list_for_each(t
, l
->first
) {
6179 tt
= *tail
= dup_Token(NULL
, t
);
6183 istk
->expansion
= ll
;
6187 MMacro
*m
= istk
->mstk
.mstk
;
6190 * Check whether a `%rep' was started and not ended
6191 * within this macro expansion. This can happen and
6192 * should be detected. It's a fatal error because
6193 * I'm too confused to work out how to recover
6198 nasm_panic("defining with name in expansion");
6200 nasm_fatal("`%%rep' without `%%endrep' within"
6201 " expansion of macro `%s'", m
->name
);
6205 * FIXME: investigate the relationship at this point between
6206 * istk->mstk.mstk and fm
6208 istk
->mstk
= m
->mstk
;
6211 * This was a real macro call, not a %rep, and
6212 * therefore the parameter information needs to
6213 * be freed and the iteration count/nesting
6217 if (!--mmacro_deadman
.levels
) {
6219 * If all mmacro processing done,
6220 * clear all counters and the deadman
6223 nasm_zero(mmacro_deadman
); /* Clear all counters */
6233 nasm_free(m
->params
);
6234 free_tlist(m
->iline
);
6235 nasm_free(m
->paramlen
);
6236 fm
->in_progress
= 0;
6241 * FIXME It is incorrect to always free_mmacro here.
6242 * It leads to usage-after-free.
6244 * https://bugzilla.nasm.us/show_bug.cgi?id=3392414
6251 istk
->expansion
= l
->next
;
6253 lfmt
->downlevel(LIST_MACRO
);
6257 do { /* until we get a line we can use */
6260 if (istk
->expansion
) { /* from a macro expansion */
6261 Line
*l
= istk
->expansion
;
6264 if (istk
->mstk
.mstk
) {
6265 istk
->mstk
.mstk
->lineno
++;
6266 if (istk
->mstk
.mstk
->fname
)
6267 lineno
= istk
->mstk
.mstk
->lineno
+
6268 istk
->mstk
.mstk
->xline
;
6270 lineno
= 0; /* Defined at init time or builtin */
6272 lineno
= src_get_linnum();
6276 istk
->expansion
= l
->next
;
6279 line
= detoken(tline
, false);
6281 lfmt
->line(LIST_MACRO
, lineno
, line
);
6283 } else if ((line
= read_line())) {
6284 line
= prepreproc(line
);
6285 tline
= tokenize(line
);
6289 * The current file has ended; work down the istk
6295 /* nasm_error can't be conditionally suppressed */
6296 nasm_fatal("expected `%%endif' before end of file");
6298 /* only set line and file name if there's a next node */
6300 src_set(i
->lineno
, i
->fname
);
6302 lfmt
->downlevel(LIST_INCLUDE
);
6309 * We must expand MMacro parameters and MMacro-local labels
6310 * _before_ we plunge into directive processing, to cope
6311 * with things like `%define something %1' such as STRUC
6312 * uses. Unless we're _defining_ a MMacro, in which case
6313 * those tokens should be left alone to go into the
6314 * definition; and unless we're in a non-emitting
6315 * condition, in which case we don't want to meddle with
6318 if (!defining
&& !(istk
->conds
&& !emitting(istk
->conds
->state
))
6319 && !(istk
->mstk
.mstk
&& !istk
->mstk
.mstk
->in_progress
)) {
6320 tline
= expand_mmac_params(tline
);
6324 * Check the line to see if it's a preprocessor directive.
6326 if (do_directive(tline
, &dtline
) == DIRECTIVE_FOUND
) {
6329 } else if (defining
) {
6331 * We're defining a multi-line macro. We emit nothing
6333 * shove the tokenized line on to the macro definition.
6335 MMacro
*mmac
= defining
->dstk
.mmac
;
6337 Line
*l
= nasm_malloc(sizeof(Line
));
6338 l
->next
= defining
->expansion
;
6341 defining
->expansion
= l
;
6344 * Remember if this mmacro expansion contains %00:
6345 * if it does, we will have to handle leading labels
6350 list_for_each(t
, tline
) {
6351 if (!memcmp(t
->text
.a
, "%00", 4))
6352 mmac
->capture_label
= true;
6355 } else if (istk
->conds
&& !emitting(istk
->conds
->state
)) {
6357 * We're in a non-emitting branch of a condition block.
6358 * Emit nothing at all, not even a blank line: when we
6359 * emerge from the condition we'll give a line-number
6360 * directive so we keep our place correctly.
6363 } else if (istk
->mstk
.mstk
&& !istk
->mstk
.mstk
->in_progress
) {
6365 * We're in a %rep block which has been terminated, so
6366 * we're walking through to the %endrep without
6367 * emitting anything. Emit nothing at all, not even a
6368 * blank line: when we emerge from the %rep block we'll
6369 * give a line-number directive so we keep our place
6374 tline
= expand_smacro(tline
);
6375 if (!expand_mmacro(tline
))
6381 static char *pp_getline(void)
6387 tline
= pp_tokline();
6388 if (tline
== &tok_pop
) {
6390 * We popped the macro/include stack. If istk is empty,
6391 * we are at end of input, otherwise just loop back.
6397 * De-tokenize the line and emit it.
6399 line
= detoken(tline
, true);
6405 if (list_option('e') && istk
&& !istk
->nolist
&& line
&& line
[0]) {
6406 char *buf
= nasm_strcat(" ;;; ", line
);
6407 lfmt
->line(LIST_MACRO
, -1, buf
);
6414 static void pp_cleanup_pass(void)
6417 if (defining
->name
) {
6418 nasm_nonfatal("end of file while still defining macro `%s'",
6421 nasm_nonfatal("end of file while still in %%rep");
6424 free_mmacro(defining
);
6439 src_set_fname(NULL
);
6442 static void pp_cleanup_session(void)
6444 nasm_free(use_loaded
);
6451 static void pp_include_path(struct strlist
*list
)
6456 static void pp_pre_include(char *fname
)
6458 Token
*inc
, *space
, *name
;
6461 name
= new_Token(NULL
, TOK_INTERNAL_STRING
, fname
, 0);
6462 space
= new_White(name
);
6463 inc
= new_Token(space
, TOK_PREPROC_ID
, "%include", 0);
6465 l
= nasm_malloc(sizeof(Line
));
6472 static void pp_pre_define(char *definition
)
6478 equals
= strchr(definition
, '=');
6479 space
= new_White(NULL
);
6480 def
= new_Token(space
, TOK_PREPROC_ID
, "%define", 0);
6483 space
->next
= tokenize(definition
);
6487 /* We can't predefine a TOK_LOCAL_MACRO for obvious reasons... */
6488 if (space
->next
->type
!= TOK_PREPROC_ID
&&
6489 space
->next
->type
!= TOK_ID
)
6490 nasm_warn(WARN_OTHER
, "pre-defining non ID `%s\'\n", definition
);
6492 l
= nasm_malloc(sizeof(Line
));
6499 static void pp_pre_undefine(char *definition
)
6504 space
= new_White(NULL
);
6505 def
= new_Token(space
, TOK_PREPROC_ID
, "%undef", 0);
6506 space
->next
= tokenize(definition
);
6508 l
= nasm_malloc(sizeof(Line
));
6515 /* Insert an early preprocessor command that doesn't need special handling */
6516 static void pp_pre_command(const char *what
, char *string
)
6522 def
= tokenize(string
);
6524 space
= new_White(def
);
6525 cmd
= nasm_strcat(what
[0] == '%' ? "" : "%", what
);
6526 def
= new_Token(space
, TOK_PREPROC_ID
, cmd
, nasm_last_string_len());
6530 l
= nasm_malloc(sizeof(Line
));
6537 static void pp_add_stdmac(macros_t
*macros
)
6541 /* Find the end of the list and avoid duplicates */
6542 for (mp
= stdmacros
; *mp
; mp
++) {
6544 return; /* Nothing to do */
6547 nasm_assert(mp
< &stdmacros
[ARRAY_SIZE(stdmacros
)-1]);
6552 static void pp_extra_stdmac(macros_t
*macros
)
6554 extrastdmac
= macros
;
6557 /* Create a numeric token */
6558 static Token
*make_tok_num(Token
*next
, int64_t val
)
6561 int len
= snprintf(numbuf
, sizeof(numbuf
), "%"PRId64
"", val
);
6562 return new_Token(next
, TOK_NUMBER
, numbuf
, len
);
6565 /* Create a quoted string token */
6566 static Token
*make_tok_qstr(Token
*next
, const char *str
)
6568 size_t len
= strlen(str
);
6569 char *p
= nasm_quote(str
, &len
);
6570 return new_Token_free(next
, TOK_STRING
, p
, len
);
6573 /* Create a single-character operator token */
6574 static Token
*make_tok_char(Token
*next
, char op
)
6576 Token
*t
= new_Token(next
, TOK_OTHER
, NULL
, 1);
6581 static void pp_list_one_macro(MMacro
*m
, errflags severity
)
6586 /* We need to print the mstk.mmac list in reverse order */
6587 pp_list_one_macro(m
->mstk
.mmac
, severity
);
6589 if (m
->name
&& !m
->nolist
) {
6590 src_set(m
->xline
+ m
->lineno
, m
->fname
);
6591 nasm_error(severity
, "... from macro `%s' defined", m
->name
);
6595 static void pp_error_list_macros(errflags severity
)
6597 struct src_location saved
;
6599 severity
|= ERR_PP_LISTMACRO
| ERR_NO_SEVERITY
| ERR_HERE
;
6600 saved
= src_where();
6603 pp_list_one_macro(istk
->mstk
.mmac
, severity
);
6608 const struct preproc_ops nasmpp
= {
6620 pp_error_list_macros
,