1 /* ----------------------------------------------------------------------- *
3 * Copyright 1996-2012 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
84 typedef struct SMacro SMacro
;
85 typedef struct MMacro MMacro
;
86 typedef struct MMacroInvocation MMacroInvocation
;
87 typedef struct Context Context
;
88 typedef struct Token Token
;
89 typedef struct Blocks Blocks
;
90 typedef struct Line Line
;
91 typedef struct Include Include
;
92 typedef struct Cond Cond
;
93 typedef struct IncPath IncPath
;
96 * Note on the storage of both SMacro and MMacros: the hash table
97 * indexes them case-insensitively, and we then have to go through a
98 * linked list of potential case aliases (and, for MMacros, parameter
99 * ranges); this is to preserve the matching semantics of the earlier
100 * code. If the number of case aliases for a specific macro is a
101 * performance issue, you may want to reconsider your coding style.
105 * Store the definition of a single-line macro.
117 * Store the definition of a multi-line macro. This is also used to
118 * store the interiors of `%rep...%endrep' blocks, which are
119 * effectively self-re-invoking multi-line macros which simply
120 * don't have a name or bother to appear in the hash tables. %rep
121 * blocks are signified by having a NULL `name' field.
123 * In a MMacro describing a `%rep' block, the `in_progress' field
124 * isn't merely boolean, but gives the number of repeats left to
127 * The `next' field is used for storing MMacros in hash tables; the
128 * `next_active' field is for stacking them on istk entries.
130 * When a MMacro is being expanded, `params', `iline', `nparam',
131 * `paramlen', `rotate' and `unique' are local to the invocation.
135 MMacroInvocation
*prev
; /* previous invocation */
137 int nparam_min
, nparam_max
;
139 bool plus
; /* is the last parameter greedy? */
140 bool nolist
; /* is this macro listing-inhibited? */
141 int64_t in_progress
; /* is this macro currently being expanded? */
142 int32_t max_depth
; /* maximum number of recursive expansions allowed */
143 Token
*dlist
; /* All defaults as one list */
144 Token
**defaults
; /* Parameter default pointers */
145 int ndefs
; /* number of default parameters */
149 MMacro
*rep_nest
; /* used for nesting %rep */
150 Token
**params
; /* actual parameters */
151 Token
*iline
; /* invocation line */
152 unsigned int nparam
, rotate
;
155 int lineno
; /* Current line number on expansion */
156 uint64_t condcnt
; /* number of if blocks... */
160 /* Store the definition of a multi-line macro, as defined in a
161 * previous recursive macro expansion.
163 struct MMacroInvocation
{
164 MMacroInvocation
*prev
; /* previous invocation */
165 Token
**params
; /* actual parameters */
166 Token
*iline
; /* invocation line */
167 unsigned int nparam
, rotate
;
175 * The context stack is composed of a linked list of these.
180 struct hash_table localmac
;
185 * This is the internal form which we break input lines up into.
186 * Typically stored in linked lists.
188 * Note that `type' serves a double meaning: TOK_SMAC_PARAM is not
189 * necessarily used as-is, but is intended to denote the number of
190 * the substituted parameter. So in the definition
192 * %define a(x,y) ( (x) & ~(y) )
194 * the token representing `x' will have its type changed to
195 * TOK_SMAC_PARAM, but the one representing `y' will be
198 * TOK_INTERNAL_STRING is a dirty hack: it's a single string token
199 * which doesn't need quotes around it. Used in the pre-include
200 * mechanism as an alternative to trying to find a sensible type of
201 * quote to use on the filename we were passed.
204 TOK_NONE
= 0, TOK_WHITESPACE
, TOK_COMMENT
, TOK_ID
,
205 TOK_PREPROC_ID
, TOK_STRING
,
206 TOK_NUMBER
, TOK_FLOAT
, TOK_SMAC_END
, TOK_OTHER
,
208 TOK_PREPROC_Q
, TOK_PREPROC_QQ
,
210 TOK_INDIRECT
, /* %[...] */
211 TOK_SMAC_PARAM
, /* MUST BE LAST IN THE LIST!!! */
212 TOK_MAX
= INT_MAX
/* Keep compiler from reducing the range */
215 #define PP_CONCAT_MASK(x) (1 << (x))
216 #define PP_CONCAT_MATCH(t, mask) (PP_CONCAT_MASK((t)->type) & mask)
218 struct tokseq_match
{
227 SMacro
*mac
; /* associated macro for TOK_SMAC_END */
228 size_t len
; /* scratch length field */
229 } a
; /* Auxiliary data */
230 enum pp_token_type type
;
234 * Multi-line macro definitions are stored as a linked list of
235 * these, which is essentially a container to allow several linked
238 * Note that in this module, linked lists are treated as stacks
239 * wherever possible. For this reason, Lines are _pushed_ on to the
240 * `expansion' field in MMacro structures, so that the linked list,
241 * if walked, would give the macro lines in reverse order; this
242 * means that we can walk the list when expanding a macro, and thus
243 * push the lines on to the `expansion' field in _istk_ in reverse
244 * order (so that when popped back off they are in the right
245 * order). It may seem cockeyed, and it relies on my design having
246 * an even number of steps in, but it works...
248 * Some of these structures, rather than being actual lines, are
249 * markers delimiting the end of the expansion of a given macro.
250 * This is for use in the cycle-tracking and %rep-handling code.
251 * Such structures have `finishes' non-NULL, and `first' NULL. All
252 * others have `finishes' NULL, but `first' may still be NULL if
262 * To handle an arbitrary level of file inclusion, we maintain a
263 * stack (ie linked list) of these things.
272 MMacro
*mstk
; /* stack of active macros/reps */
276 * Include search path. This is simply a list of strings which get
277 * prepended, in turn, to the name of an include file, in an
278 * attempt to find the file if it's not in the current directory.
286 * Conditional assembly: we maintain a separate stack of these for
287 * each level of file inclusion. (The only reason we keep the
288 * stacks separate is to ensure that a stray `%endif' in a file
289 * included from within the true branch of a `%if' won't terminate
290 * it and cause confusion: instead, rightly, it'll cause an error.)
298 * These states are for use just after %if or %elif: IF_TRUE
299 * means the condition has evaluated to truth so we are
300 * currently emitting, whereas IF_FALSE means we are not
301 * currently emitting but will start doing so if a %else comes
302 * up. In these states, all directives are admissible: %elif,
303 * %else and %endif. (And of course %if.)
305 COND_IF_TRUE
, COND_IF_FALSE
,
307 * These states come up after a %else: ELSE_TRUE means we're
308 * emitting, and ELSE_FALSE means we're not. In ELSE_* states,
309 * any %elif or %else will cause an error.
311 COND_ELSE_TRUE
, COND_ELSE_FALSE
,
313 * These states mean that we're not emitting now, and also that
314 * nothing until %endif will be emitted at all. COND_DONE is
315 * used when we've had our moment of emission
316 * and have now started seeing %elifs. COND_NEVER is used when
317 * the condition construct in question is contained within a
318 * non-emitting branch of a larger condition construct,
319 * or if there is an error.
321 COND_DONE
, COND_NEVER
323 #define emitting(x) ( (x) == COND_IF_TRUE || (x) == COND_ELSE_TRUE )
326 * These defines are used as the possible return values for do_directive
328 #define NO_DIRECTIVE_FOUND 0
329 #define DIRECTIVE_FOUND 1
332 * This define sets the upper limit for smacro and recursive mmacro
335 #define DEADMAN_LIMIT (1 << 20)
338 #define REP_LIMIT ((INT64_C(1) << 62))
341 * Condition codes. Note that we use c_ prefix not C_ because C_ is
342 * used in nasm.h for the "real" condition codes. At _this_ level,
343 * we treat CXZ and ECXZ as condition codes, albeit non-invertible
344 * ones, so we need a different enum...
346 static const char * const conditions
[] = {
347 "a", "ae", "b", "be", "c", "cxz", "e", "ecxz", "g", "ge", "l", "le",
348 "na", "nae", "nb", "nbe", "nc", "ne", "ng", "nge", "nl", "nle", "no",
349 "np", "ns", "nz", "o", "p", "pe", "po", "rcxz", "s", "z"
352 c_A
, c_AE
, c_B
, c_BE
, c_C
, c_CXZ
, c_E
, c_ECXZ
, c_G
, c_GE
, c_L
, c_LE
,
353 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, c_NE
, c_NG
, c_NGE
, c_NL
, c_NLE
, c_NO
,
354 c_NP
, c_NS
, c_NZ
, c_O
, c_P
, c_PE
, c_PO
, c_RCXZ
, c_S
, c_Z
,
357 static const enum pp_conds inverse_ccs
[] = {
358 c_NA
, c_NAE
, c_NB
, c_NBE
, c_NC
, -1, c_NE
, -1, c_NG
, c_NGE
, c_NL
, c_NLE
,
359 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
,
360 c_Z
, c_NO
, c_NP
, c_PO
, c_PE
, -1, c_NS
, c_NZ
366 /* If this is a an IF, ELIF, ELSE or ENDIF keyword */
367 static int is_condition(enum preproc_token arg
)
369 return PP_IS_COND(arg
) || (arg
== PP_ELSE
) || (arg
== PP_ENDIF
);
372 /* For TASM compatibility we need to be able to recognise TASM compatible
373 * conditional compilation directives. Using the NASM pre-processor does
374 * not work, so we look for them specifically from the following list and
375 * then jam in the equivalent NASM directive into the input stream.
379 TM_ARG
, TM_ELIF
, TM_ELSE
, TM_ENDIF
, TM_IF
, TM_IFDEF
, TM_IFDIFI
,
380 TM_IFNDEF
, TM_INCLUDE
, TM_LOCAL
383 static const char * const tasm_directives
[] = {
384 "arg", "elif", "else", "endif", "if", "ifdef", "ifdifi",
385 "ifndef", "include", "local"
388 static int StackSize
= 4;
389 static char *StackPointer
= "ebp";
390 static int ArgOffset
= 8;
391 static int LocalOffset
= 0;
393 static Context
*cstk
;
394 static Include
*istk
;
395 static IncPath
*ipath
= NULL
;
397 static int pass
; /* HACK: pass 0 = generate dependencies only */
398 static StrList
**dephead
, **deptail
; /* Dependency list */
400 static uint64_t unique
; /* unique identifier numbers */
402 static Line
*predef
= NULL
;
403 static bool do_predef
;
405 static ListGen
*list
;
408 * The current set of multi-line macros we have defined.
410 static struct hash_table mmacros
;
413 * The current set of single-line macros we have defined.
415 static struct hash_table smacros
;
418 * The multi-line macro we are currently defining, or the %rep
419 * block we are currently reading, if any.
421 static MMacro
*defining
;
423 static uint64_t nested_mac_count
;
424 static uint64_t nested_rep_count
;
427 * The number of macro parameters to allocate space for at a time.
429 #define PARAM_DELTA 16
432 * The standard macro set: defined in macros.c in the array nasm_stdmac.
433 * This gives our position in the macro set, when we're processing it.
435 static macros_t
*stdmacpos
;
438 * The extra standard macros that come from the object format, if
441 static macros_t
*extrastdmac
= NULL
;
442 static bool any_extrastdmac
;
445 * Tokens are allocated in blocks to improve speed
447 #define TOKEN_BLOCKSIZE 4096
448 static Token
*freeTokens
= NULL
;
454 static Blocks blocks
= { NULL
, NULL
};
457 * Forward declarations.
459 static Token
*expand_mmac_params(Token
* tline
);
460 static Token
*expand_smacro(Token
* tline
);
461 static Token
*expand_id(Token
* tline
);
462 static Context
*get_ctx(const char *name
, const char **namep
);
463 static void make_tok_num(Token
* tok
, int64_t val
);
464 static void error(int severity
, const char *fmt
, ...);
465 static void error_precond(int severity
, const char *fmt
, ...);
466 static void *new_Block(size_t size
);
467 static void delete_Blocks(void);
468 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
469 const char *text
, int txtlen
);
470 static Token
*delete_Token(Token
* t
);
473 * Macros for safe checking of token pointers, avoid *(NULL)
475 #define tok_type_(x,t) ((x) && (x)->type == (t))
476 #define skip_white_(x) if (tok_type_((x), TOK_WHITESPACE)) (x)=(x)->next
477 #define tok_is_(x,v) (tok_type_((x), TOK_OTHER) && !strcmp((x)->text,(v)))
478 #define tok_isnt_(x,v) ((x) && ((x)->type!=TOK_OTHER || strcmp((x)->text,(v))))
481 * nasm_unquote with error if the string contains NUL characters.
482 * If the string contains NUL characters, issue an error and return
483 * the C len, i.e. truncate at the NUL.
485 static size_t nasm_unquote_cstr(char *qstr
, enum preproc_token directive
)
487 size_t len
= nasm_unquote(qstr
, NULL
);
488 size_t clen
= strlen(qstr
);
491 error(ERR_NONFATAL
, "NUL character in `%s' directive",
492 pp_directives
[directive
]);
498 * In-place reverse a list of tokens.
500 static Token
*reverse_tokens(Token
*t
)
516 * Handle TASM specific directives, which do not contain a % in
517 * front of them. We do it here because I could not find any other
518 * place to do it for the moment, and it is a hack (ideally it would
519 * be nice to be able to use the NASM pre-processor to do it).
521 static char *check_tasm_directive(char *line
)
523 int32_t i
, j
, k
, m
, len
;
524 char *p
, *q
, *oldline
, oldchar
;
526 p
= nasm_skip_spaces(line
);
528 /* Binary search for the directive name */
530 j
= ARRAY_SIZE(tasm_directives
);
531 q
= nasm_skip_word(p
);
538 m
= nasm_stricmp(p
, tasm_directives
[k
]);
540 /* We have found a directive, so jam a % in front of it
541 * so that NASM will then recognise it as one if it's own.
546 line
= nasm_malloc(len
+ 2);
548 if (k
== TM_IFDIFI
) {
550 * NASM does not recognise IFDIFI, so we convert
551 * it to %if 0. This is not used in NASM
552 * compatible code, but does need to parse for the
553 * TASM macro package.
555 strcpy(line
+ 1, "if 0");
557 memcpy(line
+ 1, p
, len
+ 1);
572 * The pre-preprocessing stage... This function translates line
573 * number indications as they emerge from GNU cpp (`# lineno "file"
574 * flags') into NASM preprocessor line number indications (`%line
577 static char *prepreproc(char *line
)
580 char *fname
, *oldline
;
582 if (line
[0] == '#' && line
[1] == ' ') {
585 lineno
= atoi(fname
);
586 fname
+= strspn(fname
, "0123456789 ");
589 fnlen
= strcspn(fname
, "\"");
590 line
= nasm_malloc(20 + fnlen
);
591 snprintf(line
, 20 + fnlen
, "%%line %d %.*s", lineno
, fnlen
, fname
);
594 if (tasm_compatible_mode
)
595 return check_tasm_directive(line
);
600 * Free a linked list of tokens.
602 static void free_tlist(Token
* list
)
605 list
= delete_Token(list
);
609 * Free a linked list of lines.
611 static void free_llist(Line
* list
)
614 list_for_each_safe(l
, tmp
, list
) {
615 free_tlist(l
->first
);
623 static void free_mmacro(MMacro
* m
)
626 free_tlist(m
->dlist
);
627 nasm_free(m
->defaults
);
628 free_llist(m
->expansion
);
633 * Free all currently defined macros, and free the hash tables
635 static void free_smacro_table(struct hash_table
*smt
)
639 struct hash_tbl_node
*it
= NULL
;
641 while ((s
= hash_iterate(smt
, &it
, &key
)) != NULL
) {
642 nasm_free((void *)key
);
643 list_for_each_safe(s
, tmp
, s
) {
645 free_tlist(s
->expansion
);
652 static void free_mmacro_table(struct hash_table
*mmt
)
656 struct hash_tbl_node
*it
= NULL
;
659 while ((m
= hash_iterate(mmt
, &it
, &key
)) != NULL
) {
660 nasm_free((void *)key
);
661 list_for_each_safe(m
,tmp
, m
)
667 static void free_macros(void)
669 free_smacro_table(&smacros
);
670 free_mmacro_table(&mmacros
);
674 * Initialize the hash tables
676 static void init_macros(void)
678 hash_init(&smacros
, HASH_LARGE
);
679 hash_init(&mmacros
, HASH_LARGE
);
683 * Pop the context stack.
685 static void ctx_pop(void)
690 free_smacro_table(&c
->localmac
);
696 * Search for a key in the hash index; adding it if necessary
697 * (in which case we initialize the data pointer to NULL.)
700 hash_findi_add(struct hash_table
*hash
, const char *str
)
702 struct hash_insert hi
;
706 r
= hash_findi(hash
, str
, &hi
);
710 strx
= nasm_strdup(str
); /* Use a more efficient allocator here? */
711 return hash_add(&hi
, strx
, NULL
);
715 * Like hash_findi, but returns the data element rather than a pointer
716 * to it. Used only when not adding a new element, hence no third
720 hash_findix(struct hash_table
*hash
, const char *str
)
724 p
= hash_findi(hash
, str
, NULL
);
725 return p
? *p
: NULL
;
729 * read line from standart macros set,
730 * if there no more left -- return NULL
732 static char *line_from_stdmac(void)
735 const unsigned char *p
= stdmacpos
;
744 len
+= pp_directives_len
[c
- 0x80] + 1;
749 line
= nasm_malloc(len
+ 1);
751 while ((c
= *stdmacpos
++)) {
753 memcpy(q
, pp_directives
[c
- 0x80], pp_directives_len
[c
- 0x80]);
754 q
+= pp_directives_len
[c
- 0x80];
764 /* This was the last of the standard macro chain... */
766 if (any_extrastdmac
) {
767 stdmacpos
= extrastdmac
;
768 any_extrastdmac
= false;
769 } else if (do_predef
) {
771 Token
*head
, **tail
, *t
;
774 * Nasty hack: here we push the contents of
775 * `predef' on to the top-level expansion stack,
776 * since this is the most convenient way to
777 * implement the pre-include and pre-define
780 list_for_each(pd
, predef
) {
783 list_for_each(t
, pd
->first
) {
784 *tail
= new_Token(NULL
, t
->type
, t
->text
, 0);
785 tail
= &(*tail
)->next
;
788 l
= nasm_malloc(sizeof(Line
));
789 l
->next
= istk
->expansion
;
802 #define BUF_DELTA 512
804 * Read a line from the top file in istk, handling multiple CR/LFs
805 * at the end of the line read, and handling spurious ^Zs. Will
806 * return lines from the standard macro set if this has not already
809 static char *read_line(void)
811 char *buffer
, *p
, *q
;
812 int bufsize
, continued_count
;
815 * standart macros set (predefined) goes first
817 p
= line_from_stdmac();
822 * regular read from a file
825 buffer
= nasm_malloc(BUF_DELTA
);
829 q
= fgets(p
, bufsize
- (p
- buffer
), istk
->fp
);
833 if (p
> buffer
&& p
[-1] == '\n') {
835 * Convert backslash-CRLF line continuation sequences into
836 * nothing at all (for DOS and Windows)
838 if (((p
- 2) > buffer
) && (p
[-3] == '\\') && (p
[-2] == '\r')) {
844 * Also convert backslash-LF line continuation sequences into
845 * nothing at all (for Unix)
847 else if (((p
- 1) > buffer
) && (p
[-2] == '\\')) {
855 if (p
- buffer
> bufsize
- 10) {
856 int32_t offset
= p
- buffer
;
857 bufsize
+= BUF_DELTA
;
858 buffer
= nasm_realloc(buffer
, bufsize
);
859 p
= buffer
+ offset
; /* prevent stale-pointer problems */
863 if (!q
&& p
== buffer
) {
868 src_set_linnum(src_get_linnum() + istk
->lineinc
+
869 (continued_count
* istk
->lineinc
));
872 * Play safe: remove CRs as well as LFs, if any of either are
873 * present at the end of the line.
875 while (--p
>= buffer
&& (*p
== '\n' || *p
== '\r'))
879 * Handle spurious ^Z, which may be inserted into source files
880 * by some file transfer utilities.
882 buffer
[strcspn(buffer
, "\032")] = '\0';
884 list
->line(LIST_READ
, buffer
);
890 * Tokenize a line of text. This is a very simple process since we
891 * don't need to parse the value out of e.g. numeric tokens: we
892 * simply split one string into many.
894 static Token
*tokenize(char *line
)
897 enum pp_token_type type
;
899 Token
*t
, **tail
= &list
;
905 if (*p
== '+' && !nasm_isdigit(p
[1])) {
908 } else if (nasm_isdigit(*p
) ||
909 ((*p
== '-' || *p
== '+') && nasm_isdigit(p
[1]))) {
913 while (nasm_isdigit(*p
));
914 type
= TOK_PREPROC_ID
;
915 } else if (*p
== '{') {
924 error(ERR_WARNING
| ERR_PASS1
, "unterminated %{ construct");
928 type
= TOK_PREPROC_ID
;
929 } else if (*p
== '[') {
931 line
+= 2; /* Skip the leading %[ */
933 while (lvl
&& (c
= *p
++)) {
945 p
= nasm_skip_string(p
- 1) + 1;
955 error(ERR_NONFATAL
, "unterminated %[ construct");
957 } else if (*p
== '?') {
958 type
= TOK_PREPROC_Q
; /* %? */
961 type
= TOK_PREPROC_QQ
; /* %?? */
964 } else if (*p
== '!') {
965 type
= TOK_PREPROC_ID
;
971 while (isidchar(*p
));
972 } else if (*p
== '\'' || *p
== '\"' || *p
== '`') {
973 p
= nasm_skip_string(p
);
977 error(ERR_NONFATAL
|ERR_PASS1
, "unterminated %! string");
979 /* %! without string or identifier */
980 type
= TOK_OTHER
; /* Legacy behavior... */
982 } else if (isidchar(*p
) ||
983 ((*p
== '!' || *p
== '%' || *p
== '$') &&
988 while (isidchar(*p
));
989 type
= TOK_PREPROC_ID
;
995 } else if (isidstart(*p
) || (*p
== '$' && isidstart(p
[1]))) {
998 while (*p
&& isidchar(*p
))
1000 } else if (*p
== '\'' || *p
== '"' || *p
== '`') {
1005 p
= nasm_skip_string(p
);
1010 error(ERR_WARNING
|ERR_PASS1
, "unterminated string");
1011 /* Handling unterminated strings by UNV */
1014 } else if (p
[0] == '$' && p
[1] == '$') {
1015 type
= TOK_OTHER
; /* TOKEN_BASE */
1017 } else if (isnumstart(*p
)) {
1018 bool is_hex
= false;
1019 bool is_float
= false;
1035 if (!is_hex
&& (c
== 'e' || c
== 'E')) {
1037 if (*p
== '+' || *p
== '-') {
1039 * e can only be followed by +/- if it is either a
1040 * prefixed hex number or a floating-point number
1045 } else if (c
== 'H' || c
== 'h' || c
== 'X' || c
== 'x') {
1047 } else if (c
== 'P' || c
== 'p') {
1049 if (*p
== '+' || *p
== '-')
1051 } else if (isnumchar(c
) || c
== '_')
1052 ; /* just advance */
1053 else if (c
== '.') {
1055 * we need to deal with consequences of the legacy
1056 * parser, like "1.nolist" being two tokens
1057 * (TOK_NUMBER, TOK_ID) here; at least give it
1058 * a shot for now. In the future, we probably need
1059 * a flex-based scanner with proper pattern matching
1060 * to do it as well as it can be done. Nothing in
1061 * the world is going to help the person who wants
1062 * 0x123.p16 interpreted as two tokens, though.
1068 if (nasm_isdigit(*r
) || (is_hex
&& nasm_isxdigit(*r
)) ||
1069 (!is_hex
&& (*r
== 'e' || *r
== 'E')) ||
1070 (*r
== 'p' || *r
== 'P')) {
1074 break; /* Terminate the token */
1078 p
--; /* Point to first character beyond number */
1080 if (p
== line
+1 && *line
== '$') {
1081 type
= TOK_OTHER
; /* TOKEN_HERE */
1083 if (has_e
&& !is_hex
) {
1084 /* 1e13 is floating-point, but 1e13h is not */
1088 type
= is_float
? TOK_FLOAT
: TOK_NUMBER
;
1090 } else if (nasm_isspace(*p
)) {
1091 type
= TOK_WHITESPACE
;
1092 p
= nasm_skip_spaces(p
);
1094 * Whitespace just before end-of-line is discarded by
1095 * pretending it's a comment; whitespace just before a
1096 * comment gets lumped into the comment.
1098 if (!*p
|| *p
== ';') {
1103 } else if (*p
== ';') {
1109 * Anything else is an operator of some kind. We check
1110 * for all the double-character operators (>>, <<, //,
1111 * %%, <=, >=, ==, !=, <>, &&, ||, ^^), but anything
1112 * else is a single-character operator.
1115 if ((p
[0] == '>' && p
[1] == '>') ||
1116 (p
[0] == '<' && p
[1] == '<') ||
1117 (p
[0] == '/' && p
[1] == '/') ||
1118 (p
[0] == '<' && p
[1] == '=') ||
1119 (p
[0] == '>' && p
[1] == '=') ||
1120 (p
[0] == '=' && p
[1] == '=') ||
1121 (p
[0] == '!' && p
[1] == '=') ||
1122 (p
[0] == '<' && p
[1] == '>') ||
1123 (p
[0] == '&' && p
[1] == '&') ||
1124 (p
[0] == '|' && p
[1] == '|') ||
1125 (p
[0] == '^' && p
[1] == '^')) {
1131 /* Handling unterminated string by UNV */
1134 *tail = t = new_Token(NULL, TOK_STRING, line, p-line+1);
1135 t->text[p-line] = *line;
1139 if (type
!= TOK_COMMENT
) {
1140 *tail
= t
= new_Token(NULL
, type
, line
, p
- line
);
1149 * this function allocates a new managed block of memory and
1150 * returns a pointer to the block. The managed blocks are
1151 * deleted only all at once by the delete_Blocks function.
1153 static void *new_Block(size_t size
)
1155 Blocks
*b
= &blocks
;
1157 /* first, get to the end of the linked list */
1160 /* now allocate the requested chunk */
1161 b
->chunk
= nasm_malloc(size
);
1163 /* now allocate a new block for the next request */
1164 b
->next
= nasm_malloc(sizeof(Blocks
));
1165 /* and initialize the contents of the new block */
1166 b
->next
->next
= NULL
;
1167 b
->next
->chunk
= NULL
;
1172 * this function deletes all managed blocks of memory
1174 static void delete_Blocks(void)
1176 Blocks
*a
, *b
= &blocks
;
1179 * keep in mind that the first block, pointed to by blocks
1180 * is a static and not dynamically allocated, so we don't
1185 nasm_free(b
->chunk
);
1194 * this function creates a new Token and passes a pointer to it
1195 * back to the caller. It sets the type and text elements, and
1196 * also the a.mac and next elements to NULL.
1198 static Token
*new_Token(Token
* next
, enum pp_token_type type
,
1199 const char *text
, int txtlen
)
1205 freeTokens
= (Token
*) new_Block(TOKEN_BLOCKSIZE
* sizeof(Token
));
1206 for (i
= 0; i
< TOKEN_BLOCKSIZE
- 1; i
++)
1207 freeTokens
[i
].next
= &freeTokens
[i
+ 1];
1208 freeTokens
[i
].next
= NULL
;
1211 freeTokens
= t
->next
;
1215 if (type
== TOK_WHITESPACE
|| !text
) {
1219 txtlen
= strlen(text
);
1220 t
->text
= nasm_malloc(txtlen
+1);
1221 memcpy(t
->text
, text
, txtlen
);
1222 t
->text
[txtlen
] = '\0';
1227 static Token
*delete_Token(Token
* t
)
1229 Token
*next
= t
->next
;
1231 t
->next
= freeTokens
;
1237 * Convert a line of tokens back into text.
1238 * If expand_locals is not zero, identifiers of the form "%$*xxx"
1239 * will be transformed into ..@ctxnum.xxx
1241 static char *detoken(Token
* tlist
, bool expand_locals
)
1248 list_for_each(t
, tlist
) {
1249 if (t
->type
== TOK_PREPROC_ID
&& t
->text
[1] == '!') {
1254 if (*v
== '\'' || *v
== '\"' || *v
== '`') {
1255 size_t len
= nasm_unquote(v
, NULL
);
1256 size_t clen
= strlen(v
);
1259 error(ERR_NONFATAL
| ERR_PASS1
,
1260 "NUL character in %! string");
1266 char *p
= getenv(v
);
1268 error(ERR_NONFATAL
| ERR_PASS1
,
1269 "nonexistent environment variable `%s'", v
);
1272 t
->text
= nasm_strdup(p
);
1277 /* Expand local macros here and not during preprocessing */
1278 if (expand_locals
&&
1279 t
->type
== TOK_PREPROC_ID
&& t
->text
&&
1280 t
->text
[0] == '%' && t
->text
[1] == '$') {
1283 Context
*ctx
= get_ctx(t
->text
, &q
);
1286 snprintf(buffer
, sizeof(buffer
), "..@%"PRIu32
".", ctx
->number
);
1287 p
= nasm_strcat(buffer
, q
);
1292 if (t
->type
== TOK_WHITESPACE
)
1295 len
+= strlen(t
->text
);
1298 p
= line
= nasm_malloc(len
+ 1);
1300 list_for_each(t
, tlist
) {
1301 if (t
->type
== TOK_WHITESPACE
) {
1303 } else if (t
->text
) {
1315 * A scanner, suitable for use by the expression evaluator, which
1316 * operates on a line of Tokens. Expects a pointer to a pointer to
1317 * the first token in the line to be passed in as its private_data
1320 * FIX: This really needs to be unified with stdscan.
1322 static int ppscan(void *private_data
, struct tokenval
*tokval
)
1324 Token
**tlineptr
= private_data
;
1326 char ourcopy
[MAX_KEYWORD
+1], *p
, *r
, *s
;
1330 *tlineptr
= tline
? tline
->next
: NULL
;
1331 } while (tline
&& (tline
->type
== TOK_WHITESPACE
||
1332 tline
->type
== TOK_COMMENT
));
1335 return tokval
->t_type
= TOKEN_EOS
;
1337 tokval
->t_charptr
= tline
->text
;
1339 if (tline
->text
[0] == '$' && !tline
->text
[1])
1340 return tokval
->t_type
= TOKEN_HERE
;
1341 if (tline
->text
[0] == '$' && tline
->text
[1] == '$' && !tline
->text
[2])
1342 return tokval
->t_type
= TOKEN_BASE
;
1344 if (tline
->type
== TOK_ID
) {
1345 p
= tokval
->t_charptr
= tline
->text
;
1347 tokval
->t_charptr
++;
1348 return tokval
->t_type
= TOKEN_ID
;
1351 for (r
= p
, s
= ourcopy
; *r
; r
++) {
1352 if (r
>= p
+MAX_KEYWORD
)
1353 return tokval
->t_type
= TOKEN_ID
; /* Not a keyword */
1354 *s
++ = nasm_tolower(*r
);
1357 /* right, so we have an identifier sitting in temp storage. now,
1358 * is it actually a register or instruction name, or what? */
1359 return nasm_token_hash(ourcopy
, tokval
);
1362 if (tline
->type
== TOK_NUMBER
) {
1364 tokval
->t_integer
= readnum(tline
->text
, &rn_error
);
1365 tokval
->t_charptr
= tline
->text
;
1367 return tokval
->t_type
= TOKEN_ERRNUM
;
1369 return tokval
->t_type
= TOKEN_NUM
;
1372 if (tline
->type
== TOK_FLOAT
) {
1373 return tokval
->t_type
= TOKEN_FLOAT
;
1376 if (tline
->type
== TOK_STRING
) {
1379 bq
= tline
->text
[0];
1380 tokval
->t_charptr
= tline
->text
;
1381 tokval
->t_inttwo
= nasm_unquote(tline
->text
, &ep
);
1383 if (ep
[0] != bq
|| ep
[1] != '\0')
1384 return tokval
->t_type
= TOKEN_ERRSTR
;
1386 return tokval
->t_type
= TOKEN_STR
;
1389 if (tline
->type
== TOK_OTHER
) {
1390 if (!strcmp(tline
->text
, "<<"))
1391 return tokval
->t_type
= TOKEN_SHL
;
1392 if (!strcmp(tline
->text
, ">>"))
1393 return tokval
->t_type
= TOKEN_SHR
;
1394 if (!strcmp(tline
->text
, "//"))
1395 return tokval
->t_type
= TOKEN_SDIV
;
1396 if (!strcmp(tline
->text
, "%%"))
1397 return tokval
->t_type
= TOKEN_SMOD
;
1398 if (!strcmp(tline
->text
, "=="))
1399 return tokval
->t_type
= TOKEN_EQ
;
1400 if (!strcmp(tline
->text
, "<>"))
1401 return tokval
->t_type
= TOKEN_NE
;
1402 if (!strcmp(tline
->text
, "!="))
1403 return tokval
->t_type
= TOKEN_NE
;
1404 if (!strcmp(tline
->text
, "<="))
1405 return tokval
->t_type
= TOKEN_LE
;
1406 if (!strcmp(tline
->text
, ">="))
1407 return tokval
->t_type
= TOKEN_GE
;
1408 if (!strcmp(tline
->text
, "&&"))
1409 return tokval
->t_type
= TOKEN_DBL_AND
;
1410 if (!strcmp(tline
->text
, "^^"))
1411 return tokval
->t_type
= TOKEN_DBL_XOR
;
1412 if (!strcmp(tline
->text
, "||"))
1413 return tokval
->t_type
= TOKEN_DBL_OR
;
1417 * We have no other options: just return the first character of
1420 return tokval
->t_type
= tline
->text
[0];
1424 * Compare a string to the name of an existing macro; this is a
1425 * simple wrapper which calls either strcmp or nasm_stricmp
1426 * depending on the value of the `casesense' parameter.
1428 static int mstrcmp(const char *p
, const char *q
, bool casesense
)
1430 return casesense
? strcmp(p
, q
) : nasm_stricmp(p
, q
);
1434 * Compare a string to the name of an existing macro; this is a
1435 * simple wrapper which calls either strcmp or nasm_stricmp
1436 * depending on the value of the `casesense' parameter.
1438 static int mmemcmp(const char *p
, const char *q
, size_t l
, bool casesense
)
1440 return casesense
? memcmp(p
, q
, l
) : nasm_memicmp(p
, q
, l
);
1444 * Return the Context structure associated with a %$ token. Return
1445 * NULL, having _already_ reported an error condition, if the
1446 * context stack isn't deep enough for the supplied number of $
1449 * If "namep" is non-NULL, set it to the pointer to the macro name
1450 * tail, i.e. the part beyond %$...
1452 static Context
*get_ctx(const char *name
, const char **namep
)
1460 if (!name
|| name
[0] != '%' || name
[1] != '$')
1464 error(ERR_NONFATAL
, "`%s': context stack is empty", name
);
1471 while (ctx
&& *name
== '$') {
1477 error(ERR_NONFATAL
, "`%s': context stack is only"
1478 " %d level%s deep", name
, i
, (i
== 1 ? "" : "s"));
1489 * Check to see if a file is already in a string list
1491 static bool in_list(const StrList
*list
, const char *str
)
1494 if (!strcmp(list
->str
, str
))
1502 * Open an include file. This routine must always return a valid
1503 * file pointer if it returns - it's responsible for throwing an
1504 * ERR_FATAL and bombing out completely if not. It should also try
1505 * the include path one by one until it finds the file or reaches
1506 * the end of the path.
1508 static FILE *inc_fopen(const char *file
, StrList
**dhead
, StrList
***dtail
,
1513 IncPath
*ip
= ipath
;
1514 int len
= strlen(file
);
1515 size_t prefix_len
= 0;
1519 sl
= nasm_malloc(prefix_len
+len
+1+sizeof sl
->next
);
1520 memcpy(sl
->str
, prefix
, prefix_len
);
1521 memcpy(sl
->str
+prefix_len
, file
, len
+1);
1522 fp
= fopen(sl
->str
, "r");
1523 if (fp
&& dhead
&& !in_list(*dhead
, sl
->str
)) {
1541 prefix_len
= strlen(prefix
);
1543 /* -MG given and file not found */
1544 if (dhead
&& !in_list(*dhead
, file
)) {
1545 sl
= nasm_malloc(len
+1+sizeof sl
->next
);
1547 strcpy(sl
->str
, file
);
1555 error(ERR_FATAL
, "unable to open include file `%s'", file
);
1560 * Determine if we should warn on defining a single-line macro of
1561 * name `name', with `nparam' parameters. If nparam is 0 or -1, will
1562 * return true if _any_ single-line macro of that name is defined.
1563 * Otherwise, will return true if a single-line macro with either
1564 * `nparam' or no parameters is defined.
1566 * If a macro with precisely the right number of parameters is
1567 * defined, or nparam is -1, the address of the definition structure
1568 * will be returned in `defn'; otherwise NULL will be returned. If `defn'
1569 * is NULL, no action will be taken regarding its contents, and no
1572 * Note that this is also called with nparam zero to resolve
1575 * If you already know which context macro belongs to, you can pass
1576 * the context pointer as first parameter; if you won't but name begins
1577 * with %$ the context will be automatically computed. If all_contexts
1578 * is true, macro will be searched in outer contexts as well.
1581 smacro_defined(Context
* ctx
, const char *name
, int nparam
, SMacro
** defn
,
1584 struct hash_table
*smtbl
;
1588 smtbl
= &ctx
->localmac
;
1589 } else if (name
[0] == '%' && name
[1] == '$') {
1591 ctx
= get_ctx(name
, &name
);
1593 return false; /* got to return _something_ */
1594 smtbl
= &ctx
->localmac
;
1598 m
= (SMacro
*) hash_findix(smtbl
, name
);
1601 if (!mstrcmp(m
->name
, name
, m
->casesense
&& nocase
) &&
1602 (nparam
<= 0 || m
->nparam
== 0 || nparam
== (int) m
->nparam
)) {
1604 if (nparam
== (int) m
->nparam
|| nparam
== -1)
1618 * Count and mark off the parameters in a multi-line macro call.
1619 * This is called both from within the multi-line macro expansion
1620 * code, and also to mark off the default parameters when provided
1621 * in a %macro definition line.
1623 static void count_mmac_params(Token
* t
, int *nparam
, Token
*** params
)
1625 int paramsize
, brace
;
1627 *nparam
= paramsize
= 0;
1630 /* +1: we need space for the final NULL */
1631 if (*nparam
+1 >= paramsize
) {
1632 paramsize
+= PARAM_DELTA
;
1633 *params
= nasm_realloc(*params
, sizeof(**params
) * paramsize
);
1637 if (tok_is_(t
, "{"))
1639 (*params
)[(*nparam
)++] = t
;
1640 while (tok_isnt_(t
, brace
? "}" : ","))
1642 if (t
) { /* got a comma/brace */
1646 * Now we've found the closing brace, look further
1650 if (tok_isnt_(t
, ",")) {
1652 "braces do not enclose all of macro parameter");
1653 while (tok_isnt_(t
, ","))
1657 t
= t
->next
; /* eat the comma */
1664 * Determine whether one of the various `if' conditions is true or
1667 * We must free the tline we get passed.
1669 static bool if_condition(Token
* tline
, enum preproc_token ct
)
1671 enum pp_conditional i
= PP_COND(ct
);
1673 Token
*t
, *tt
, **tptr
, *origline
;
1674 struct tokenval tokval
;
1676 enum pp_token_type needtype
;
1683 j
= false; /* have we matched yet? */
1688 if (tline
->type
!= TOK_ID
) {
1690 "`%s' expects context identifiers", pp_directives
[ct
]);
1691 free_tlist(origline
);
1694 if (cstk
&& cstk
->name
&& !nasm_stricmp(tline
->text
, cstk
->name
))
1696 tline
= tline
->next
;
1701 j
= false; /* have we matched yet? */
1704 if (!tline
|| (tline
->type
!= TOK_ID
&&
1705 (tline
->type
!= TOK_PREPROC_ID
||
1706 tline
->text
[1] != '$'))) {
1708 "`%s' expects macro identifiers", pp_directives
[ct
]);
1711 if (smacro_defined(NULL
, tline
->text
, 0, NULL
, true))
1713 tline
= tline
->next
;
1718 tline
= expand_smacro(tline
);
1719 j
= false; /* have we matched yet? */
1722 if (!tline
|| (tline
->type
!= TOK_ID
&&
1723 tline
->type
!= TOK_STRING
&&
1724 (tline
->type
!= TOK_PREPROC_ID
||
1725 tline
->text
[1] != '!'))) {
1727 "`%s' expects environment variable names",
1732 if (tline
->type
== TOK_PREPROC_ID
)
1733 p
+= 2; /* Skip leading %! */
1734 if (*p
== '\'' || *p
== '\"' || *p
== '`')
1735 nasm_unquote_cstr(p
, ct
);
1738 tline
= tline
->next
;
1744 tline
= expand_smacro(tline
);
1746 while (tok_isnt_(tt
, ","))
1750 "`%s' expects two comma-separated arguments",
1755 j
= true; /* assume equality unless proved not */
1756 while ((t
->type
!= TOK_OTHER
|| strcmp(t
->text
, ",")) && tt
) {
1757 if (tt
->type
== TOK_OTHER
&& !strcmp(tt
->text
, ",")) {
1758 error(ERR_NONFATAL
, "`%s': more than one comma on line",
1762 if (t
->type
== TOK_WHITESPACE
) {
1766 if (tt
->type
== TOK_WHITESPACE
) {
1770 if (tt
->type
!= t
->type
) {
1771 j
= false; /* found mismatching tokens */
1774 /* When comparing strings, need to unquote them first */
1775 if (t
->type
== TOK_STRING
) {
1776 size_t l1
= nasm_unquote(t
->text
, NULL
);
1777 size_t l2
= nasm_unquote(tt
->text
, NULL
);
1783 if (mmemcmp(t
->text
, tt
->text
, l1
, i
== PPC_IFIDN
)) {
1787 } else if (mstrcmp(tt
->text
, t
->text
, i
== PPC_IFIDN
) != 0) {
1788 j
= false; /* found mismatching tokens */
1795 if ((t
->type
!= TOK_OTHER
|| strcmp(t
->text
, ",")) || tt
)
1796 j
= false; /* trailing gunk on one end or other */
1802 MMacro searching
, *mmac
;
1805 tline
= expand_id(tline
);
1806 if (!tok_type_(tline
, TOK_ID
)) {
1808 "`%s' expects a macro name", pp_directives
[ct
]);
1811 searching
.name
= nasm_strdup(tline
->text
);
1812 searching
.casesense
= true;
1813 searching
.plus
= false;
1814 searching
.nolist
= false;
1815 searching
.in_progress
= 0;
1816 searching
.max_depth
= 0;
1817 searching
.rep_nest
= NULL
;
1818 searching
.nparam_min
= 0;
1819 searching
.nparam_max
= INT_MAX
;
1820 tline
= expand_smacro(tline
->next
);
1823 } else if (!tok_type_(tline
, TOK_NUMBER
)) {
1825 "`%s' expects a parameter count or nothing",
1828 searching
.nparam_min
= searching
.nparam_max
=
1829 readnum(tline
->text
, &j
);
1832 "unable to parse parameter count `%s'",
1835 if (tline
&& tok_is_(tline
->next
, "-")) {
1836 tline
= tline
->next
->next
;
1837 if (tok_is_(tline
, "*"))
1838 searching
.nparam_max
= INT_MAX
;
1839 else if (!tok_type_(tline
, TOK_NUMBER
))
1841 "`%s' expects a parameter count after `-'",
1844 searching
.nparam_max
= readnum(tline
->text
, &j
);
1847 "unable to parse parameter count `%s'",
1849 if (searching
.nparam_min
> searching
.nparam_max
)
1851 "minimum parameter count exceeds maximum");
1854 if (tline
&& tok_is_(tline
->next
, "+")) {
1855 tline
= tline
->next
;
1856 searching
.plus
= true;
1858 mmac
= (MMacro
*) hash_findix(&mmacros
, searching
.name
);
1860 if (!strcmp(mmac
->name
, searching
.name
) &&
1861 (mmac
->nparam_min
<= searching
.nparam_max
1863 && (searching
.nparam_min
<= mmac
->nparam_max
1870 if (tline
&& tline
->next
)
1871 error(ERR_WARNING
|ERR_PASS1
,
1872 "trailing garbage after %%ifmacro ignored");
1873 nasm_free(searching
.name
);
1882 needtype
= TOK_NUMBER
;
1885 needtype
= TOK_STRING
;
1889 t
= tline
= expand_smacro(tline
);
1891 while (tok_type_(t
, TOK_WHITESPACE
) ||
1892 (needtype
== TOK_NUMBER
&&
1893 tok_type_(t
, TOK_OTHER
) &&
1894 (t
->text
[0] == '-' || t
->text
[0] == '+') &&
1898 j
= tok_type_(t
, needtype
);
1902 t
= tline
= expand_smacro(tline
);
1903 while (tok_type_(t
, TOK_WHITESPACE
))
1908 t
= t
->next
; /* Skip the actual token */
1909 while (tok_type_(t
, TOK_WHITESPACE
))
1911 j
= !t
; /* Should be nothing left */
1916 t
= tline
= expand_smacro(tline
);
1917 while (tok_type_(t
, TOK_WHITESPACE
))
1920 j
= !t
; /* Should be empty */
1924 t
= tline
= expand_smacro(tline
);
1926 tokval
.t_type
= TOKEN_INVALID
;
1927 evalresult
= evaluate(ppscan
, tptr
, &tokval
,
1928 NULL
, pass
| CRITICAL
, error
, NULL
);
1932 error(ERR_WARNING
|ERR_PASS1
,
1933 "trailing garbage after expression ignored");
1934 if (!is_simple(evalresult
)) {
1936 "non-constant value given to `%s'", pp_directives
[ct
]);
1939 j
= reloc_value(evalresult
) != 0;
1944 "preprocessor directive `%s' not yet implemented",
1949 free_tlist(origline
);
1950 return j
^ PP_NEGATIVE(ct
);
1953 free_tlist(origline
);
1958 * Common code for defining an smacro
1960 static bool define_smacro(Context
*ctx
, const char *mname
, bool casesense
,
1961 int nparam
, Token
*expansion
)
1963 SMacro
*smac
, **smhead
;
1964 struct hash_table
*smtbl
;
1966 if (smacro_defined(ctx
, mname
, nparam
, &smac
, casesense
)) {
1968 error(ERR_WARNING
|ERR_PASS1
,
1969 "single-line macro `%s' defined both with and"
1970 " without parameters", mname
);
1972 * Some instances of the old code considered this a failure,
1973 * some others didn't. What is the right thing to do here?
1975 free_tlist(expansion
);
1976 return false; /* Failure */
1979 * We're redefining, so we have to take over an
1980 * existing SMacro structure. This means freeing
1981 * what was already in it.
1983 nasm_free(smac
->name
);
1984 free_tlist(smac
->expansion
);
1987 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
1988 smhead
= (SMacro
**) hash_findi_add(smtbl
, mname
);
1989 smac
= nasm_malloc(sizeof(SMacro
));
1990 smac
->next
= *smhead
;
1993 smac
->name
= nasm_strdup(mname
);
1994 smac
->casesense
= casesense
;
1995 smac
->nparam
= nparam
;
1996 smac
->expansion
= expansion
;
1997 smac
->in_progress
= false;
1998 return true; /* Success */
2002 * Undefine an smacro
2004 static void undef_smacro(Context
*ctx
, const char *mname
)
2006 SMacro
**smhead
, *s
, **sp
;
2007 struct hash_table
*smtbl
;
2009 smtbl
= ctx
? &ctx
->localmac
: &smacros
;
2010 smhead
= (SMacro
**)hash_findi(smtbl
, mname
, NULL
);
2014 * We now have a macro name... go hunt for it.
2017 while ((s
= *sp
) != NULL
) {
2018 if (!mstrcmp(s
->name
, mname
, s
->casesense
)) {
2021 free_tlist(s
->expansion
);
2031 * Parse a mmacro specification.
2033 static bool parse_mmacro_spec(Token
*tline
, MMacro
*def
, const char *directive
)
2037 tline
= tline
->next
;
2039 tline
= expand_id(tline
);
2040 if (!tok_type_(tline
, TOK_ID
)) {
2041 error(ERR_NONFATAL
, "`%s' expects a macro name", directive
);
2046 def
->name
= nasm_strdup(tline
->text
);
2048 def
->nolist
= false;
2049 def
->in_progress
= 0;
2050 def
->rep_nest
= NULL
;
2051 def
->nparam_min
= 0;
2052 def
->nparam_max
= 0;
2054 tline
= expand_smacro(tline
->next
);
2056 if (!tok_type_(tline
, TOK_NUMBER
)) {
2057 error(ERR_NONFATAL
, "`%s' expects a parameter count", directive
);
2059 def
->nparam_min
= def
->nparam_max
=
2060 readnum(tline
->text
, &err
);
2063 "unable to parse parameter count `%s'", tline
->text
);
2065 if (tline
&& tok_is_(tline
->next
, "-")) {
2066 tline
= tline
->next
->next
;
2067 if (tok_is_(tline
, "*")) {
2068 def
->nparam_max
= INT_MAX
;
2069 } else if (!tok_type_(tline
, TOK_NUMBER
)) {
2071 "`%s' expects a parameter count after `-'", directive
);
2073 def
->nparam_max
= readnum(tline
->text
, &err
);
2075 error(ERR_NONFATAL
, "unable to parse parameter count `%s'",
2078 if (def
->nparam_min
> def
->nparam_max
) {
2079 error(ERR_NONFATAL
, "minimum parameter count exceeds maximum");
2083 if (tline
&& tok_is_(tline
->next
, "+")) {
2084 tline
= tline
->next
;
2087 if (tline
&& tok_type_(tline
->next
, TOK_ID
) &&
2088 !nasm_stricmp(tline
->next
->text
, ".nolist")) {
2089 tline
= tline
->next
;
2094 * Handle default parameters.
2096 if (tline
&& tline
->next
) {
2097 def
->dlist
= tline
->next
;
2099 count_mmac_params(def
->dlist
, &def
->ndefs
, &def
->defaults
);
2102 def
->defaults
= NULL
;
2104 def
->expansion
= NULL
;
2106 if (def
->defaults
&& def
->ndefs
> def
->nparam_max
- def
->nparam_min
&&
2108 error(ERR_WARNING
|ERR_PASS1
|ERR_WARN_MDP
,
2109 "too many default macro parameters");
2116 * Decode a size directive
2118 static int parse_size(const char *str
) {
2119 static const char *size_names
[] =
2120 { "byte", "dword", "oword", "qword", "tword", "word", "yword" };
2121 static const int sizes
[] =
2122 { 0, 1, 4, 16, 8, 10, 2, 32 };
2124 return sizes
[bsii(str
, size_names
, ARRAY_SIZE(size_names
))+1];
2128 * find and process preprocessor directive in passed line
2129 * Find out if a line contains a preprocessor directive, and deal
2132 * If a directive _is_ found, it is the responsibility of this routine
2133 * (and not the caller) to free_tlist() the line.
2135 * @param tline a pointer to the current tokeninzed line linked list
2136 * @return DIRECTIVE_FOUND or NO_DIRECTIVE_FOUND
2139 static int do_directive(Token
* tline
)
2141 enum preproc_token i
;
2154 MMacro
*mmac
, **mmhead
;
2155 Token
*t
, *tt
, *param_start
, *macro_start
, *last
, **tptr
, *origline
;
2157 struct tokenval tokval
;
2159 MMacro
*tmp_defining
; /* Used when manipulating rep_nest */
2167 if (!tline
|| !tok_type_(tline
, TOK_PREPROC_ID
) ||
2168 (tline
->text
[1] == '%' || tline
->text
[1] == '$'
2169 || tline
->text
[1] == '!'))
2170 return NO_DIRECTIVE_FOUND
;
2172 i
= pp_token_hash(tline
->text
);
2175 * FIXME: We zap execution of PP_RMACRO, PP_IRMACRO, PP_EXITMACRO
2176 * since they are known to be buggy at moment, we need to fix them
2177 * in future release (2.09-2.10)
2179 if (i
== PP_RMACRO
|| i
== PP_RMACRO
|| i
== PP_EXITMACRO
) {
2180 error(ERR_NONFATAL
, "unknown preprocessor directive `%s'",
2182 return NO_DIRECTIVE_FOUND
;
2186 * If we're in a non-emitting branch of a condition construct,
2187 * or walking to the end of an already terminated %rep block,
2188 * we should ignore all directives except for condition
2191 if (((istk
->conds
&& !emitting(istk
->conds
->state
)) ||
2192 (istk
->mstk
&& !istk
->mstk
->in_progress
)) && !is_condition(i
)) {
2193 return NO_DIRECTIVE_FOUND
;
2197 * If we're defining a macro or reading a %rep block, we should
2198 * ignore all directives except for %macro/%imacro (which nest),
2199 * %endm/%endmacro, and (only if we're in a %rep block) %endrep.
2200 * If we're in a %rep block, another %rep nests, so should be let through.
2202 if (defining
&& i
!= PP_MACRO
&& i
!= PP_IMACRO
&&
2203 i
!= PP_RMACRO
&& i
!= PP_IRMACRO
&&
2204 i
!= PP_ENDMACRO
&& i
!= PP_ENDM
&&
2205 (defining
->name
|| (i
!= PP_ENDREP
&& i
!= PP_REP
))) {
2206 return NO_DIRECTIVE_FOUND
;
2210 if (i
== PP_MACRO
|| i
== PP_IMACRO
||
2211 i
== PP_RMACRO
|| i
== PP_IRMACRO
) {
2213 return NO_DIRECTIVE_FOUND
;
2214 } else if (nested_mac_count
> 0) {
2215 if (i
== PP_ENDMACRO
) {
2217 return NO_DIRECTIVE_FOUND
;
2220 if (!defining
->name
) {
2223 return NO_DIRECTIVE_FOUND
;
2224 } else if (nested_rep_count
> 0) {
2225 if (i
== PP_ENDREP
) {
2227 return NO_DIRECTIVE_FOUND
;
2235 error(ERR_NONFATAL
, "unknown preprocessor directive `%s'",
2237 return NO_DIRECTIVE_FOUND
; /* didn't get it */
2240 /* Directive to tell NASM what the default stack size is. The
2241 * default is for a 16-bit stack, and this can be overriden with
2244 tline
= tline
->next
;
2245 if (tline
&& tline
->type
== TOK_WHITESPACE
)
2246 tline
= tline
->next
;
2247 if (!tline
|| tline
->type
!= TOK_ID
) {
2248 error(ERR_NONFATAL
, "`%%stacksize' missing size parameter");
2249 free_tlist(origline
);
2250 return DIRECTIVE_FOUND
;
2252 if (nasm_stricmp(tline
->text
, "flat") == 0) {
2253 /* All subsequent ARG directives are for a 32-bit stack */
2255 StackPointer
= "ebp";
2258 } else if (nasm_stricmp(tline
->text
, "flat64") == 0) {
2259 /* All subsequent ARG directives are for a 64-bit stack */
2261 StackPointer
= "rbp";
2264 } else if (nasm_stricmp(tline
->text
, "large") == 0) {
2265 /* All subsequent ARG directives are for a 16-bit stack,
2266 * far function call.
2269 StackPointer
= "bp";
2272 } else if (nasm_stricmp(tline
->text
, "small") == 0) {
2273 /* All subsequent ARG directives are for a 16-bit stack,
2274 * far function call. We don't support near functions.
2277 StackPointer
= "bp";
2281 error(ERR_NONFATAL
, "`%%stacksize' invalid size type");
2282 free_tlist(origline
);
2283 return DIRECTIVE_FOUND
;
2285 free_tlist(origline
);
2286 return DIRECTIVE_FOUND
;
2289 /* TASM like ARG directive to define arguments to functions, in
2290 * the following form:
2292 * ARG arg1:WORD, arg2:DWORD, arg4:QWORD
2296 char *arg
, directive
[256];
2297 int size
= StackSize
;
2299 /* Find the argument name */
2300 tline
= tline
->next
;
2301 if (tline
&& tline
->type
== TOK_WHITESPACE
)
2302 tline
= tline
->next
;
2303 if (!tline
|| tline
->type
!= TOK_ID
) {
2304 error(ERR_NONFATAL
, "`%%arg' missing argument parameter");
2305 free_tlist(origline
);
2306 return DIRECTIVE_FOUND
;
2310 /* Find the argument size type */
2311 tline
= tline
->next
;
2312 if (!tline
|| tline
->type
!= TOK_OTHER
2313 || tline
->text
[0] != ':') {
2315 "Syntax error processing `%%arg' directive");
2316 free_tlist(origline
);
2317 return DIRECTIVE_FOUND
;
2319 tline
= tline
->next
;
2320 if (!tline
|| tline
->type
!= TOK_ID
) {
2321 error(ERR_NONFATAL
, "`%%arg' missing size type parameter");
2322 free_tlist(origline
);
2323 return DIRECTIVE_FOUND
;
2326 /* Allow macro expansion of type parameter */
2327 tt
= tokenize(tline
->text
);
2328 tt
= expand_smacro(tt
);
2329 size
= parse_size(tt
->text
);
2332 "Invalid size type for `%%arg' missing directive");
2334 free_tlist(origline
);
2335 return DIRECTIVE_FOUND
;
2339 /* Round up to even stack slots */
2340 size
= ALIGN(size
, StackSize
);
2342 /* Now define the macro for the argument */
2343 snprintf(directive
, sizeof(directive
), "%%define %s (%s+%d)",
2344 arg
, StackPointer
, offset
);
2345 do_directive(tokenize(directive
));
2348 /* Move to the next argument in the list */
2349 tline
= tline
->next
;
2350 if (tline
&& tline
->type
== TOK_WHITESPACE
)
2351 tline
= tline
->next
;
2352 } while (tline
&& tline
->type
== TOK_OTHER
&& tline
->text
[0] == ',');
2354 free_tlist(origline
);
2355 return DIRECTIVE_FOUND
;
2358 /* TASM like LOCAL directive to define local variables for a
2359 * function, in the following form:
2361 * LOCAL local1:WORD, local2:DWORD, local4:QWORD = LocalSize
2363 * The '= LocalSize' at the end is ignored by NASM, but is
2364 * required by TASM to define the local parameter size (and used
2365 * by the TASM macro package).
2367 offset
= LocalOffset
;
2369 char *local
, directive
[256];
2370 int size
= StackSize
;
2372 /* Find the argument name */
2373 tline
= tline
->next
;
2374 if (tline
&& tline
->type
== TOK_WHITESPACE
)
2375 tline
= tline
->next
;
2376 if (!tline
|| tline
->type
!= TOK_ID
) {
2378 "`%%local' missing argument parameter");
2379 free_tlist(origline
);
2380 return DIRECTIVE_FOUND
;
2382 local
= tline
->text
;
2384 /* Find the argument size type */
2385 tline
= tline
->next
;
2386 if (!tline
|| tline
->type
!= TOK_OTHER
2387 || tline
->text
[0] != ':') {
2389 "Syntax error processing `%%local' directive");
2390 free_tlist(origline
);
2391 return DIRECTIVE_FOUND
;
2393 tline
= tline
->next
;
2394 if (!tline
|| tline
->type
!= TOK_ID
) {
2396 "`%%local' missing size type parameter");
2397 free_tlist(origline
);
2398 return DIRECTIVE_FOUND
;
2401 /* Allow macro expansion of type parameter */
2402 tt
= tokenize(tline
->text
);
2403 tt
= expand_smacro(tt
);
2404 size
= parse_size(tt
->text
);
2407 "Invalid size type for `%%local' missing directive");
2409 free_tlist(origline
);
2410 return DIRECTIVE_FOUND
;
2414 /* Round up to even stack slots */
2415 size
= ALIGN(size
, StackSize
);
2417 offset
+= size
; /* Negative offset, increment before */
2419 /* Now define the macro for the argument */
2420 snprintf(directive
, sizeof(directive
), "%%define %s (%s-%d)",
2421 local
, StackPointer
, offset
);
2422 do_directive(tokenize(directive
));
2424 /* Now define the assign to setup the enter_c macro correctly */
2425 snprintf(directive
, sizeof(directive
),
2426 "%%assign %%$localsize %%$localsize+%d", size
);
2427 do_directive(tokenize(directive
));
2429 /* Move to the next argument in the list */
2430 tline
= tline
->next
;
2431 if (tline
&& tline
->type
== TOK_WHITESPACE
)
2432 tline
= tline
->next
;
2433 } while (tline
&& tline
->type
== TOK_OTHER
&& tline
->text
[0] == ',');
2434 LocalOffset
= offset
;
2435 free_tlist(origline
);
2436 return DIRECTIVE_FOUND
;
2440 error(ERR_WARNING
|ERR_PASS1
,
2441 "trailing garbage after `%%clear' ignored");
2444 free_tlist(origline
);
2445 return DIRECTIVE_FOUND
;
2448 t
= tline
->next
= expand_smacro(tline
->next
);
2450 if (!t
|| (t
->type
!= TOK_STRING
&&
2451 t
->type
!= TOK_INTERNAL_STRING
)) {
2452 error(ERR_NONFATAL
, "`%%depend' expects a file name");
2453 free_tlist(origline
);
2454 return DIRECTIVE_FOUND
; /* but we did _something_ */
2457 error(ERR_WARNING
|ERR_PASS1
,
2458 "trailing garbage after `%%depend' ignored");
2460 if (t
->type
!= TOK_INTERNAL_STRING
)
2461 nasm_unquote_cstr(p
, i
);
2462 if (dephead
&& !in_list(*dephead
, p
)) {
2463 StrList
*sl
= nasm_malloc(strlen(p
)+1+sizeof sl
->next
);
2467 deptail
= &sl
->next
;
2469 free_tlist(origline
);
2470 return DIRECTIVE_FOUND
;
2473 t
= tline
->next
= expand_smacro(tline
->next
);
2476 if (!t
|| (t
->type
!= TOK_STRING
&&
2477 t
->type
!= TOK_INTERNAL_STRING
)) {
2478 error(ERR_NONFATAL
, "`%%include' expects a file name");
2479 free_tlist(origline
);
2480 return DIRECTIVE_FOUND
; /* but we did _something_ */
2483 error(ERR_WARNING
|ERR_PASS1
,
2484 "trailing garbage after `%%include' ignored");
2486 if (t
->type
!= TOK_INTERNAL_STRING
)
2487 nasm_unquote_cstr(p
, i
);
2488 inc
= nasm_malloc(sizeof(Include
));
2491 inc
->fp
= inc_fopen(p
, dephead
, &deptail
, pass
== 0);
2493 /* -MG given but file not found */
2496 inc
->fname
= src_set_fname(nasm_strdup(p
));
2497 inc
->lineno
= src_set_linnum(0);
2499 inc
->expansion
= NULL
;
2502 list
->uplevel(LIST_INCLUDE
);
2504 free_tlist(origline
);
2505 return DIRECTIVE_FOUND
;
2509 static macros_t
*use_pkg
;
2510 const char *pkg_macro
= NULL
;
2512 tline
= tline
->next
;
2514 tline
= expand_id(tline
);
2516 if (!tline
|| (tline
->type
!= TOK_STRING
&&
2517 tline
->type
!= TOK_INTERNAL_STRING
&&
2518 tline
->type
!= TOK_ID
)) {
2519 error(ERR_NONFATAL
, "`%%use' expects a package name");
2520 free_tlist(origline
);
2521 return DIRECTIVE_FOUND
; /* but we did _something_ */
2524 error(ERR_WARNING
|ERR_PASS1
,
2525 "trailing garbage after `%%use' ignored");
2526 if (tline
->type
== TOK_STRING
)
2527 nasm_unquote_cstr(tline
->text
, i
);
2528 use_pkg
= nasm_stdmac_find_package(tline
->text
);
2530 error(ERR_NONFATAL
, "unknown `%%use' package: %s", tline
->text
);
2532 pkg_macro
= (char *)use_pkg
+ 1; /* The first string will be <%define>__USE_*__ */
2533 if (use_pkg
&& ! smacro_defined(NULL
, pkg_macro
, 0, NULL
, true)) {
2534 /* Not already included, go ahead and include it */
2535 stdmacpos
= use_pkg
;
2537 free_tlist(origline
);
2538 return DIRECTIVE_FOUND
;
2543 tline
= tline
->next
;
2545 tline
= expand_id(tline
);
2547 if (!tok_type_(tline
, TOK_ID
)) {
2548 error(ERR_NONFATAL
, "`%s' expects a context identifier",
2550 free_tlist(origline
);
2551 return DIRECTIVE_FOUND
; /* but we did _something_ */
2554 error(ERR_WARNING
|ERR_PASS1
,
2555 "trailing garbage after `%s' ignored",
2557 p
= nasm_strdup(tline
->text
);
2559 p
= NULL
; /* Anonymous */
2563 ctx
= nasm_malloc(sizeof(Context
));
2565 hash_init(&ctx
->localmac
, HASH_SMALL
);
2567 ctx
->number
= unique
++;
2572 error(ERR_NONFATAL
, "`%s': context stack is empty",
2574 } else if (i
== PP_POP
) {
2575 if (p
&& (!cstk
->name
|| nasm_stricmp(p
, cstk
->name
)))
2576 error(ERR_NONFATAL
, "`%%pop' in wrong context: %s, "
2578 cstk
->name
? cstk
->name
: "anonymous", p
);
2583 nasm_free(cstk
->name
);
2589 free_tlist(origline
);
2590 return DIRECTIVE_FOUND
;
2592 severity
= ERR_FATAL
;
2595 severity
= ERR_NONFATAL
;
2598 severity
= ERR_WARNING
|ERR_WARN_USER
;
2603 /* Only error out if this is the final pass */
2604 if (pass
!= 2 && i
!= PP_FATAL
)
2605 return DIRECTIVE_FOUND
;
2607 tline
->next
= expand_smacro(tline
->next
);
2608 tline
= tline
->next
;
2610 t
= tline
? tline
->next
: NULL
;
2612 if (tok_type_(tline
, TOK_STRING
) && !t
) {
2613 /* The line contains only a quoted string */
2615 nasm_unquote(p
, NULL
); /* Ignore NUL character truncation */
2616 error(severity
, "%s", p
);
2618 /* Not a quoted string, or more than a quoted string */
2619 p
= detoken(tline
, false);
2620 error(severity
, "%s", p
);
2623 free_tlist(origline
);
2624 return DIRECTIVE_FOUND
;
2628 if (istk
->conds
&& !emitting(istk
->conds
->state
))
2631 j
= if_condition(tline
->next
, i
);
2632 tline
->next
= NULL
; /* it got freed */
2633 j
= j
< 0 ? COND_NEVER
: j
? COND_IF_TRUE
: COND_IF_FALSE
;
2635 cond
= nasm_malloc(sizeof(Cond
));
2636 cond
->next
= istk
->conds
;
2640 istk
->mstk
->condcnt
++;
2641 free_tlist(origline
);
2642 return DIRECTIVE_FOUND
;
2646 error(ERR_FATAL
, "`%s': no matching `%%if'", pp_directives
[i
]);
2647 switch(istk
->conds
->state
) {
2649 istk
->conds
->state
= COND_DONE
;
2656 case COND_ELSE_TRUE
:
2657 case COND_ELSE_FALSE
:
2658 error_precond(ERR_WARNING
|ERR_PASS1
,
2659 "`%%elif' after `%%else' ignored");
2660 istk
->conds
->state
= COND_NEVER
;
2665 * IMPORTANT: In the case of %if, we will already have
2666 * called expand_mmac_params(); however, if we're
2667 * processing an %elif we must have been in a
2668 * non-emitting mode, which would have inhibited
2669 * the normal invocation of expand_mmac_params().
2670 * Therefore, we have to do it explicitly here.
2672 j
= if_condition(expand_mmac_params(tline
->next
), i
);
2673 tline
->next
= NULL
; /* it got freed */
2674 istk
->conds
->state
=
2675 j
< 0 ? COND_NEVER
: j
? COND_IF_TRUE
: COND_IF_FALSE
;
2678 free_tlist(origline
);
2679 return DIRECTIVE_FOUND
;
2683 error_precond(ERR_WARNING
|ERR_PASS1
,
2684 "trailing garbage after `%%else' ignored");
2686 error(ERR_FATAL
, "`%%else': no matching `%%if'");
2687 switch(istk
->conds
->state
) {
2690 istk
->conds
->state
= COND_ELSE_FALSE
;
2697 istk
->conds
->state
= COND_ELSE_TRUE
;
2700 case COND_ELSE_TRUE
:
2701 case COND_ELSE_FALSE
:
2702 error_precond(ERR_WARNING
|ERR_PASS1
,
2703 "`%%else' after `%%else' ignored.");
2704 istk
->conds
->state
= COND_NEVER
;
2707 free_tlist(origline
);
2708 return DIRECTIVE_FOUND
;
2712 error_precond(ERR_WARNING
|ERR_PASS1
,
2713 "trailing garbage after `%%endif' ignored");
2715 error(ERR_FATAL
, "`%%endif': no matching `%%if'");
2717 istk
->conds
= cond
->next
;
2720 istk
->mstk
->condcnt
--;
2721 free_tlist(origline
);
2722 return DIRECTIVE_FOUND
;
2729 error(ERR_FATAL
, "`%s': already defining a macro",
2731 return DIRECTIVE_FOUND
;
2733 defining
= nasm_malloc(sizeof(MMacro
));
2734 defining
->max_depth
=
2735 (i
== PP_RMACRO
) || (i
== PP_IRMACRO
) ? DEADMAN_LIMIT
: 0;
2736 defining
->casesense
= (i
== PP_MACRO
) || (i
== PP_RMACRO
);
2737 if (!parse_mmacro_spec(tline
, defining
, pp_directives
[i
])) {
2738 nasm_free(defining
);
2740 return DIRECTIVE_FOUND
;
2743 mmac
= (MMacro
*) hash_findix(&mmacros
, defining
->name
);
2745 if (!strcmp(mmac
->name
, defining
->name
) &&
2746 (mmac
->nparam_min
<= defining
->nparam_max
2748 && (defining
->nparam_min
<= mmac
->nparam_max
2750 error(ERR_WARNING
|ERR_PASS1
,
2751 "redefining multi-line macro `%s'", defining
->name
);
2752 return DIRECTIVE_FOUND
;
2756 free_tlist(origline
);
2757 return DIRECTIVE_FOUND
;
2761 if (! (defining
&& defining
->name
)) {
2762 error(ERR_NONFATAL
, "`%s': not defining a macro", tline
->text
);
2763 return DIRECTIVE_FOUND
;
2765 mmhead
= (MMacro
**) hash_findi_add(&mmacros
, defining
->name
);
2766 defining
->next
= *mmhead
;
2769 free_tlist(origline
);
2770 return DIRECTIVE_FOUND
;
2774 * We must search along istk->expansion until we hit a
2775 * macro-end marker for a macro with a name. Then we
2776 * bypass all lines between exitmacro and endmacro.
2778 list_for_each(l
, istk
->expansion
)
2779 if (l
->finishes
&& l
->finishes
->name
)
2784 * Remove all conditional entries relative to this
2785 * macro invocation. (safe to do in this context)
2787 for ( ; l
->finishes
->condcnt
> 0; l
->finishes
->condcnt
--) {
2789 istk
->conds
= cond
->next
;
2792 istk
->expansion
= l
;
2794 error(ERR_NONFATAL
, "`%%exitmacro' not within `%%macro' block");
2796 free_tlist(origline
);
2797 return DIRECTIVE_FOUND
;
2805 spec
.casesense
= (i
== PP_UNMACRO
);
2806 if (!parse_mmacro_spec(tline
, &spec
, pp_directives
[i
])) {
2807 return DIRECTIVE_FOUND
;
2809 mmac_p
= (MMacro
**) hash_findi(&mmacros
, spec
.name
, NULL
);
2810 while (mmac_p
&& *mmac_p
) {
2812 if (mmac
->casesense
== spec
.casesense
&&
2813 !mstrcmp(mmac
->name
, spec
.name
, spec
.casesense
) &&
2814 mmac
->nparam_min
== spec
.nparam_min
&&
2815 mmac
->nparam_max
== spec
.nparam_max
&&
2816 mmac
->plus
== spec
.plus
) {
2817 *mmac_p
= mmac
->next
;
2820 mmac_p
= &mmac
->next
;
2823 free_tlist(origline
);
2824 free_tlist(spec
.dlist
);
2825 return DIRECTIVE_FOUND
;
2829 if (tline
->next
&& tline
->next
->type
== TOK_WHITESPACE
)
2830 tline
= tline
->next
;
2832 free_tlist(origline
);
2833 error(ERR_NONFATAL
, "`%%rotate' missing rotate count");
2834 return DIRECTIVE_FOUND
;
2836 t
= expand_smacro(tline
->next
);
2838 free_tlist(origline
);
2841 tokval
.t_type
= TOKEN_INVALID
;
2843 evaluate(ppscan
, tptr
, &tokval
, NULL
, pass
, error
, NULL
);
2846 return DIRECTIVE_FOUND
;
2848 error(ERR_WARNING
|ERR_PASS1
,
2849 "trailing garbage after expression ignored");
2850 if (!is_simple(evalresult
)) {
2851 error(ERR_NONFATAL
, "non-constant value given to `%%rotate'");
2852 return DIRECTIVE_FOUND
;
2855 while (mmac
&& !mmac
->name
) /* avoid mistaking %reps for macros */
2856 mmac
= mmac
->next_active
;
2858 error(ERR_NONFATAL
, "`%%rotate' invoked outside a macro call");
2859 } else if (mmac
->nparam
== 0) {
2861 "`%%rotate' invoked within macro without parameters");
2863 int rotate
= mmac
->rotate
+ reloc_value(evalresult
);
2865 rotate
%= (int)mmac
->nparam
;
2867 rotate
+= mmac
->nparam
;
2869 mmac
->rotate
= rotate
;
2871 return DIRECTIVE_FOUND
;
2876 tline
= tline
->next
;
2877 } while (tok_type_(tline
, TOK_WHITESPACE
));
2879 if (tok_type_(tline
, TOK_ID
) &&
2880 nasm_stricmp(tline
->text
, ".nolist") == 0) {
2883 tline
= tline
->next
;
2884 } while (tok_type_(tline
, TOK_WHITESPACE
));
2888 t
= expand_smacro(tline
);
2890 tokval
.t_type
= TOKEN_INVALID
;
2892 evaluate(ppscan
, tptr
, &tokval
, NULL
, pass
, error
, NULL
);
2894 free_tlist(origline
);
2895 return DIRECTIVE_FOUND
;
2898 error(ERR_WARNING
|ERR_PASS1
,
2899 "trailing garbage after expression ignored");
2900 if (!is_simple(evalresult
)) {
2901 error(ERR_NONFATAL
, "non-constant value given to `%%rep'");
2902 return DIRECTIVE_FOUND
;
2904 count
= reloc_value(evalresult
);
2905 if (count
>= REP_LIMIT
) {
2906 error(ERR_NONFATAL
, "`%%rep' value exceeds limit");
2911 error(ERR_NONFATAL
, "`%%rep' expects a repeat count");
2914 free_tlist(origline
);
2916 tmp_defining
= defining
;
2917 defining
= nasm_malloc(sizeof(MMacro
));
2918 defining
->prev
= NULL
;
2919 defining
->name
= NULL
; /* flags this macro as a %rep block */
2920 defining
->casesense
= false;
2921 defining
->plus
= false;
2922 defining
->nolist
= nolist
;
2923 defining
->in_progress
= count
;
2924 defining
->max_depth
= 0;
2925 defining
->nparam_min
= defining
->nparam_max
= 0;
2926 defining
->defaults
= NULL
;
2927 defining
->dlist
= NULL
;
2928 defining
->expansion
= NULL
;
2929 defining
->next_active
= istk
->mstk
;
2930 defining
->rep_nest
= tmp_defining
;
2931 return DIRECTIVE_FOUND
;
2934 if (!defining
|| defining
->name
) {
2935 error(ERR_NONFATAL
, "`%%endrep': no matching `%%rep'");
2936 return DIRECTIVE_FOUND
;
2940 * Now we have a "macro" defined - although it has no name
2941 * and we won't be entering it in the hash tables - we must
2942 * push a macro-end marker for it on to istk->expansion.
2943 * After that, it will take care of propagating itself (a
2944 * macro-end marker line for a macro which is really a %rep
2945 * block will cause the macro to be re-expanded, complete
2946 * with another macro-end marker to ensure the process
2947 * continues) until the whole expansion is forcibly removed
2948 * from istk->expansion by a %exitrep.
2950 l
= nasm_malloc(sizeof(Line
));
2951 l
->next
= istk
->expansion
;
2952 l
->finishes
= defining
;
2954 istk
->expansion
= l
;
2956 istk
->mstk
= defining
;
2958 list
->uplevel(defining
->nolist
? LIST_MACRO_NOLIST
: LIST_MACRO
);
2959 tmp_defining
= defining
;
2960 defining
= defining
->rep_nest
;
2961 free_tlist(origline
);
2962 return DIRECTIVE_FOUND
;
2966 * We must search along istk->expansion until we hit a
2967 * macro-end marker for a macro with no name. Then we set
2968 * its `in_progress' flag to 0.
2970 list_for_each(l
, istk
->expansion
)
2971 if (l
->finishes
&& !l
->finishes
->name
)
2975 l
->finishes
->in_progress
= 1;
2977 error(ERR_NONFATAL
, "`%%exitrep' not within `%%rep' block");
2978 free_tlist(origline
);
2979 return DIRECTIVE_FOUND
;
2985 casesense
= (i
== PP_DEFINE
|| i
== PP_XDEFINE
);
2987 tline
= tline
->next
;
2989 tline
= expand_id(tline
);
2990 if (!tline
|| (tline
->type
!= TOK_ID
&&
2991 (tline
->type
!= TOK_PREPROC_ID
||
2992 tline
->text
[1] != '$'))) {
2993 error(ERR_NONFATAL
, "`%s' expects a macro identifier",
2995 free_tlist(origline
);
2996 return DIRECTIVE_FOUND
;
2999 ctx
= get_ctx(tline
->text
, &mname
);
3001 param_start
= tline
= tline
->next
;
3004 /* Expand the macro definition now for %xdefine and %ixdefine */
3005 if ((i
== PP_XDEFINE
) || (i
== PP_IXDEFINE
))
3006 tline
= expand_smacro(tline
);
3008 if (tok_is_(tline
, "(")) {
3010 * This macro has parameters.
3013 tline
= tline
->next
;
3017 error(ERR_NONFATAL
, "parameter identifier expected");
3018 free_tlist(origline
);
3019 return DIRECTIVE_FOUND
;
3021 if (tline
->type
!= TOK_ID
) {
3023 "`%s': parameter identifier expected",
3025 free_tlist(origline
);
3026 return DIRECTIVE_FOUND
;
3028 tline
->type
= TOK_SMAC_PARAM
+ nparam
++;
3029 tline
= tline
->next
;
3031 if (tok_is_(tline
, ",")) {
3032 tline
= tline
->next
;
3034 if (!tok_is_(tline
, ")")) {
3036 "`)' expected to terminate macro template");
3037 free_tlist(origline
);
3038 return DIRECTIVE_FOUND
;
3044 tline
= tline
->next
;
3046 if (tok_type_(tline
, TOK_WHITESPACE
))
3047 last
= tline
, tline
= tline
->next
;
3052 if (t
->type
== TOK_ID
) {
3053 list_for_each(tt
, param_start
)
3054 if (tt
->type
>= TOK_SMAC_PARAM
&&
3055 !strcmp(tt
->text
, t
->text
))
3059 t
->next
= macro_start
;
3064 * Good. We now have a macro name, a parameter count, and a
3065 * token list (in reverse order) for an expansion. We ought
3066 * to be OK just to create an SMacro, store it, and let
3067 * free_tlist have the rest of the line (which we have
3068 * carefully re-terminated after chopping off the expansion
3071 define_smacro(ctx
, mname
, casesense
, nparam
, macro_start
);
3072 free_tlist(origline
);
3073 return DIRECTIVE_FOUND
;
3076 tline
= tline
->next
;
3078 tline
= expand_id(tline
);
3079 if (!tline
|| (tline
->type
!= TOK_ID
&&
3080 (tline
->type
!= TOK_PREPROC_ID
||
3081 tline
->text
[1] != '$'))) {
3082 error(ERR_NONFATAL
, "`%%undef' expects a macro identifier");
3083 free_tlist(origline
);
3084 return DIRECTIVE_FOUND
;
3087 error(ERR_WARNING
|ERR_PASS1
,
3088 "trailing garbage after macro name ignored");
3091 /* Find the context that symbol belongs to */
3092 ctx
= get_ctx(tline
->text
, &mname
);
3093 undef_smacro(ctx
, mname
);
3094 free_tlist(origline
);
3095 return DIRECTIVE_FOUND
;
3099 casesense
= (i
== PP_DEFSTR
);
3101 tline
= tline
->next
;
3103 tline
= expand_id(tline
);
3104 if (!tline
|| (tline
->type
!= TOK_ID
&&
3105 (tline
->type
!= TOK_PREPROC_ID
||
3106 tline
->text
[1] != '$'))) {
3107 error(ERR_NONFATAL
, "`%s' expects a macro identifier",
3109 free_tlist(origline
);
3110 return DIRECTIVE_FOUND
;
3113 ctx
= get_ctx(tline
->text
, &mname
);
3115 tline
= expand_smacro(tline
->next
);
3118 while (tok_type_(tline
, TOK_WHITESPACE
))
3119 tline
= delete_Token(tline
);
3121 p
= detoken(tline
, false);
3122 macro_start
= nasm_malloc(sizeof(*macro_start
));
3123 macro_start
->next
= NULL
;
3124 macro_start
->text
= nasm_quote(p
, strlen(p
));
3125 macro_start
->type
= TOK_STRING
;
3126 macro_start
->a
.mac
= NULL
;
3130 * We now have a macro name, an implicit parameter count of
3131 * zero, and a string token to use as an expansion. Create
3132 * and store an SMacro.
3134 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3135 free_tlist(origline
);
3136 return DIRECTIVE_FOUND
;
3140 casesense
= (i
== PP_DEFTOK
);
3142 tline
= tline
->next
;
3144 tline
= expand_id(tline
);
3145 if (!tline
|| (tline
->type
!= TOK_ID
&&
3146 (tline
->type
!= TOK_PREPROC_ID
||
3147 tline
->text
[1] != '$'))) {
3149 "`%s' expects a macro identifier as first parameter",
3151 free_tlist(origline
);
3152 return DIRECTIVE_FOUND
;
3154 ctx
= get_ctx(tline
->text
, &mname
);
3156 tline
= expand_smacro(tline
->next
);
3160 while (tok_type_(t
, TOK_WHITESPACE
))
3162 /* t should now point to the string */
3163 if (!tok_type_(t
, TOK_STRING
)) {
3165 "`%s` requires string as second parameter",
3168 free_tlist(origline
);
3169 return DIRECTIVE_FOUND
;
3173 * Convert the string to a token stream. Note that smacros
3174 * are stored with the token stream reversed, so we have to
3175 * reverse the output of tokenize().
3177 nasm_unquote_cstr(t
->text
, i
);
3178 macro_start
= reverse_tokens(tokenize(t
->text
));
3181 * We now have a macro name, an implicit parameter count of
3182 * zero, and a numeric token to use as an expansion. Create
3183 * and store an SMacro.
3185 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3187 free_tlist(origline
);
3188 return DIRECTIVE_FOUND
;
3193 StrList
*xsl
= NULL
;
3194 StrList
**xst
= &xsl
;
3198 tline
= tline
->next
;
3200 tline
= expand_id(tline
);
3201 if (!tline
|| (tline
->type
!= TOK_ID
&&
3202 (tline
->type
!= TOK_PREPROC_ID
||
3203 tline
->text
[1] != '$'))) {
3205 "`%%pathsearch' expects a macro identifier as first parameter");
3206 free_tlist(origline
);
3207 return DIRECTIVE_FOUND
;
3209 ctx
= get_ctx(tline
->text
, &mname
);
3211 tline
= expand_smacro(tline
->next
);
3215 while (tok_type_(t
, TOK_WHITESPACE
))
3218 if (!t
|| (t
->type
!= TOK_STRING
&&
3219 t
->type
!= TOK_INTERNAL_STRING
)) {
3220 error(ERR_NONFATAL
, "`%%pathsearch' expects a file name");
3222 free_tlist(origline
);
3223 return DIRECTIVE_FOUND
; /* but we did _something_ */
3226 error(ERR_WARNING
|ERR_PASS1
,
3227 "trailing garbage after `%%pathsearch' ignored");
3229 if (t
->type
!= TOK_INTERNAL_STRING
)
3230 nasm_unquote(p
, NULL
);
3232 fp
= inc_fopen(p
, &xsl
, &xst
, true);
3235 fclose(fp
); /* Don't actually care about the file */
3237 macro_start
= nasm_malloc(sizeof(*macro_start
));
3238 macro_start
->next
= NULL
;
3239 macro_start
->text
= nasm_quote(p
, strlen(p
));
3240 macro_start
->type
= TOK_STRING
;
3241 macro_start
->a
.mac
= NULL
;
3246 * We now have a macro name, an implicit parameter count of
3247 * zero, and a string token to use as an expansion. Create
3248 * and store an SMacro.
3250 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3252 free_tlist(origline
);
3253 return DIRECTIVE_FOUND
;
3259 tline
= tline
->next
;
3261 tline
= expand_id(tline
);
3262 if (!tline
|| (tline
->type
!= TOK_ID
&&
3263 (tline
->type
!= TOK_PREPROC_ID
||
3264 tline
->text
[1] != '$'))) {
3266 "`%%strlen' expects a macro identifier as first parameter");
3267 free_tlist(origline
);
3268 return DIRECTIVE_FOUND
;
3270 ctx
= get_ctx(tline
->text
, &mname
);
3272 tline
= expand_smacro(tline
->next
);
3276 while (tok_type_(t
, TOK_WHITESPACE
))
3278 /* t should now point to the string */
3279 if (!tok_type_(t
, TOK_STRING
)) {
3281 "`%%strlen` requires string as second parameter");
3283 free_tlist(origline
);
3284 return DIRECTIVE_FOUND
;
3287 macro_start
= nasm_malloc(sizeof(*macro_start
));
3288 macro_start
->next
= NULL
;
3289 make_tok_num(macro_start
, nasm_unquote(t
->text
, NULL
));
3290 macro_start
->a
.mac
= NULL
;
3293 * We now have a macro name, an implicit parameter count of
3294 * zero, and a numeric token to use as an expansion. Create
3295 * and store an SMacro.
3297 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3299 free_tlist(origline
);
3300 return DIRECTIVE_FOUND
;
3305 tline
= tline
->next
;
3307 tline
= expand_id(tline
);
3308 if (!tline
|| (tline
->type
!= TOK_ID
&&
3309 (tline
->type
!= TOK_PREPROC_ID
||
3310 tline
->text
[1] != '$'))) {
3312 "`%%strcat' expects a macro identifier as first parameter");
3313 free_tlist(origline
);
3314 return DIRECTIVE_FOUND
;
3316 ctx
= get_ctx(tline
->text
, &mname
);
3318 tline
= expand_smacro(tline
->next
);
3322 list_for_each(t
, tline
) {
3324 case TOK_WHITESPACE
:
3327 len
+= t
->a
.len
= nasm_unquote(t
->text
, NULL
);
3330 if (!strcmp(t
->text
, ",")) /* permit comma separators */
3332 /* else fall through */
3335 "non-string passed to `%%strcat' (%d)", t
->type
);
3337 free_tlist(origline
);
3338 return DIRECTIVE_FOUND
;
3342 p
= pp
= nasm_malloc(len
);
3343 list_for_each(t
, tline
) {
3344 if (t
->type
== TOK_STRING
) {
3345 memcpy(p
, t
->text
, t
->a
.len
);
3351 * We now have a macro name, an implicit parameter count of
3352 * zero, and a numeric token to use as an expansion. Create
3353 * and store an SMacro.
3355 macro_start
= new_Token(NULL
, TOK_STRING
, NULL
, 0);
3356 macro_start
->text
= nasm_quote(pp
, len
);
3358 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3360 free_tlist(origline
);
3361 return DIRECTIVE_FOUND
;
3365 int64_t start
, count
;
3370 tline
= tline
->next
;
3372 tline
= expand_id(tline
);
3373 if (!tline
|| (tline
->type
!= TOK_ID
&&
3374 (tline
->type
!= TOK_PREPROC_ID
||
3375 tline
->text
[1] != '$'))) {
3377 "`%%substr' expects a macro identifier as first parameter");
3378 free_tlist(origline
);
3379 return DIRECTIVE_FOUND
;
3381 ctx
= get_ctx(tline
->text
, &mname
);
3383 tline
= expand_smacro(tline
->next
);
3386 if (tline
) /* skip expanded id */
3388 while (tok_type_(t
, TOK_WHITESPACE
))
3391 /* t should now point to the string */
3392 if (!tok_type_(t
, TOK_STRING
)) {
3394 "`%%substr` requires string as second parameter");
3396 free_tlist(origline
);
3397 return DIRECTIVE_FOUND
;
3402 tokval
.t_type
= TOKEN_INVALID
;
3403 evalresult
= evaluate(ppscan
, tptr
, &tokval
, NULL
,
3407 free_tlist(origline
);
3408 return DIRECTIVE_FOUND
;
3409 } else if (!is_simple(evalresult
)) {
3410 error(ERR_NONFATAL
, "non-constant value given to `%%substr`");
3412 free_tlist(origline
);
3413 return DIRECTIVE_FOUND
;
3415 start
= evalresult
->value
- 1;
3417 while (tok_type_(tt
, TOK_WHITESPACE
))
3420 count
= 1; /* Backwards compatibility: one character */
3422 tokval
.t_type
= TOKEN_INVALID
;
3423 evalresult
= evaluate(ppscan
, tptr
, &tokval
, NULL
,
3427 free_tlist(origline
);
3428 return DIRECTIVE_FOUND
;
3429 } else if (!is_simple(evalresult
)) {
3430 error(ERR_NONFATAL
, "non-constant value given to `%%substr`");
3432 free_tlist(origline
);
3433 return DIRECTIVE_FOUND
;
3435 count
= evalresult
->value
;
3438 len
= nasm_unquote(t
->text
, NULL
);
3440 /* make start and count being in range */
3444 count
= len
+ count
+ 1 - start
;
3445 if (start
+ count
> (int64_t)len
)
3446 count
= len
- start
;
3447 if (!len
|| count
< 0 || start
>=(int64_t)len
)
3448 start
= -1, count
= 0; /* empty string */
3450 macro_start
= nasm_malloc(sizeof(*macro_start
));
3451 macro_start
->next
= NULL
;
3452 macro_start
->text
= nasm_quote((start
< 0) ? "" : t
->text
+ start
, count
);
3453 macro_start
->type
= TOK_STRING
;
3454 macro_start
->a
.mac
= NULL
;
3457 * We now have a macro name, an implicit parameter count of
3458 * zero, and a numeric token to use as an expansion. Create
3459 * and store an SMacro.
3461 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3463 free_tlist(origline
);
3464 return DIRECTIVE_FOUND
;
3469 casesense
= (i
== PP_ASSIGN
);
3471 tline
= tline
->next
;
3473 tline
= expand_id(tline
);
3474 if (!tline
|| (tline
->type
!= TOK_ID
&&
3475 (tline
->type
!= TOK_PREPROC_ID
||
3476 tline
->text
[1] != '$'))) {
3478 "`%%%sassign' expects a macro identifier",
3479 (i
== PP_IASSIGN
? "i" : ""));
3480 free_tlist(origline
);
3481 return DIRECTIVE_FOUND
;
3483 ctx
= get_ctx(tline
->text
, &mname
);
3485 tline
= expand_smacro(tline
->next
);
3490 tokval
.t_type
= TOKEN_INVALID
;
3492 evaluate(ppscan
, tptr
, &tokval
, NULL
, pass
, error
, NULL
);
3495 free_tlist(origline
);
3496 return DIRECTIVE_FOUND
;
3500 error(ERR_WARNING
|ERR_PASS1
,
3501 "trailing garbage after expression ignored");
3503 if (!is_simple(evalresult
)) {
3505 "non-constant value given to `%%%sassign'",
3506 (i
== PP_IASSIGN
? "i" : ""));
3507 free_tlist(origline
);
3508 return DIRECTIVE_FOUND
;
3511 macro_start
= nasm_malloc(sizeof(*macro_start
));
3512 macro_start
->next
= NULL
;
3513 make_tok_num(macro_start
, reloc_value(evalresult
));
3514 macro_start
->a
.mac
= NULL
;
3517 * We now have a macro name, an implicit parameter count of
3518 * zero, and a numeric token to use as an expansion. Create
3519 * and store an SMacro.
3521 define_smacro(ctx
, mname
, casesense
, 0, macro_start
);
3522 free_tlist(origline
);
3523 return DIRECTIVE_FOUND
;
3527 * Syntax is `%line nnn[+mmm] [filename]'
3529 tline
= tline
->next
;
3531 if (!tok_type_(tline
, TOK_NUMBER
)) {
3532 error(ERR_NONFATAL
, "`%%line' expects line number");
3533 free_tlist(origline
);
3534 return DIRECTIVE_FOUND
;
3536 k
= readnum(tline
->text
, &err
);
3538 tline
= tline
->next
;
3539 if (tok_is_(tline
, "+")) {
3540 tline
= tline
->next
;
3541 if (!tok_type_(tline
, TOK_NUMBER
)) {
3542 error(ERR_NONFATAL
, "`%%line' expects line increment");
3543 free_tlist(origline
);
3544 return DIRECTIVE_FOUND
;
3546 m
= readnum(tline
->text
, &err
);
3547 tline
= tline
->next
;
3553 nasm_free(src_set_fname(detoken(tline
, false)));
3555 free_tlist(origline
);
3556 return DIRECTIVE_FOUND
;
3560 "preprocessor directive `%s' not yet implemented",
3562 return DIRECTIVE_FOUND
;
3567 * Ensure that a macro parameter contains a condition code and
3568 * nothing else. Return the condition code index if so, or -1
3571 static int find_cc(Token
* t
)
3576 return -1; /* Probably a %+ without a space */
3579 if (t
->type
!= TOK_ID
)
3583 if (tt
&& (tt
->type
!= TOK_OTHER
|| strcmp(tt
->text
, ",")))
3586 return bsii(t
->text
, (const char **)conditions
, ARRAY_SIZE(conditions
));
3590 * This routines walks over tokens strem and hadnles tokens
3591 * pasting, if @handle_explicit passed then explicit pasting
3592 * term is handled, otherwise -- implicit pastings only.
3594 static bool paste_tokens(Token
**head
, const struct tokseq_match
*m
,
3595 size_t mnum
, bool handle_explicit
)
3597 Token
*tok
, *next
, **prev_next
, **prev_nonspace
;
3598 bool pasted
= false;
3603 * The last token before pasting. We need it
3604 * to be able to connect new handled tokens.
3605 * In other words if there were a tokens stream
3609 * and we've joined tokens B and C, the resulting
3617 if (!tok_type_(tok
, TOK_WHITESPACE
) && !tok_type_(tok
, TOK_PASTE
))
3618 prev_nonspace
= head
;
3620 prev_nonspace
= NULL
;
3622 while (tok
&& (next
= tok
->next
)) {
3624 switch (tok
->type
) {
3625 case TOK_WHITESPACE
:
3626 /* Zap redundant whitespaces */
3627 while (tok_type_(next
, TOK_WHITESPACE
))
3628 next
= delete_Token(next
);
3633 /* Explicit pasting */
3634 if (!handle_explicit
)
3636 next
= delete_Token(tok
);
3638 while (tok_type_(next
, TOK_WHITESPACE
))
3639 next
= delete_Token(next
);
3644 /* No ending token */
3646 error(ERR_FATAL
, "No rvalue found on pasting");
3648 /* Left pasting token is start of line */
3650 error(ERR_FATAL
, "No lvalue found on pasting");
3652 tok
= *prev_nonspace
;
3653 while (tok_type_(tok
, TOK_WHITESPACE
))
3654 tok
= delete_Token(tok
);
3655 len
= strlen(tok
->text
);
3656 len
+= strlen(next
->text
);
3658 p
= buf
= nasm_malloc(len
+ 1);
3659 strcpy(p
, tok
->text
);
3660 p
= strchr(p
, '\0');
3661 strcpy(p
, next
->text
);
3665 tok
= tokenize(buf
);
3668 *prev_nonspace
= tok
;
3669 while (tok
&& tok
->next
)
3672 tok
->next
= delete_Token(next
);
3674 /* Restart from pasted tokens head */
3675 tok
= *prev_nonspace
;
3679 /* implicit pasting */
3680 for (i
= 0; i
< mnum
; i
++) {
3681 if (!(PP_CONCAT_MATCH(tok
, m
[i
].mask_head
)))
3685 while (next
&& PP_CONCAT_MATCH(next
, m
[i
].mask_tail
)) {
3686 len
+= strlen(next
->text
);
3694 len
+= strlen(tok
->text
);
3695 p
= buf
= nasm_malloc(len
+ 1);
3697 while (tok
!= next
) {
3698 strcpy(p
, tok
->text
);
3699 p
= strchr(p
, '\0');
3700 tok
= delete_Token(tok
);
3703 tok
= tokenize(buf
);
3712 * Connect pasted into original stream,
3713 * ie A -> new-tokens -> B
3715 while (tok
&& tok
->next
)
3722 /* Restart from pasted tokens head */
3723 tok
= prev_next
? *prev_next
: *head
;
3729 prev_next
= &tok
->next
;
3732 !tok_type_(tok
->next
, TOK_WHITESPACE
) &&
3733 !tok_type_(tok
->next
, TOK_PASTE
))
3734 prev_nonspace
= prev_next
;
3743 * expands to a list of tokens from %{x:y}
3745 static Token
*expand_mmac_params_range(MMacro
*mac
, Token
*tline
, Token
***last
)
3747 Token
*t
= tline
, **tt
, *tm
, *head
;
3751 pos
= strchr(tline
->text
, ':');
3754 lst
= atoi(pos
+ 1);
3755 fst
= atoi(tline
->text
+ 1);
3758 * only macros params are accounted so
3759 * if someone passes %0 -- we reject such
3762 if (lst
== 0 || fst
== 0)
3765 /* the values should be sane */
3766 if ((fst
> (int)mac
->nparam
|| fst
< (-(int)mac
->nparam
)) ||
3767 (lst
> (int)mac
->nparam
|| lst
< (-(int)mac
->nparam
)))
3770 fst
= fst
< 0 ? fst
+ (int)mac
->nparam
+ 1: fst
;
3771 lst
= lst
< 0 ? lst
+ (int)mac
->nparam
+ 1: lst
;
3773 /* counted from zero */
3777 * it will be at least one token
3779 tm
= mac
->params
[(fst
+ mac
->rotate
) % mac
->nparam
];
3780 t
= new_Token(NULL
, tm
->type
, tm
->text
, 0);
3781 head
= t
, tt
= &t
->next
;
3783 for (i
= fst
+ 1; i
<= lst
; i
++) {
3784 t
= new_Token(NULL
, TOK_OTHER
, ",", 0);
3785 *tt
= t
, tt
= &t
->next
;
3786 j
= (i
+ mac
->rotate
) % mac
->nparam
;
3787 tm
= mac
->params
[j
];
3788 t
= new_Token(NULL
, tm
->type
, tm
->text
, 0);
3789 *tt
= t
, tt
= &t
->next
;
3792 for (i
= fst
- 1; i
>= lst
; i
--) {
3793 t
= new_Token(NULL
, TOK_OTHER
, ",", 0);
3794 *tt
= t
, tt
= &t
->next
;
3795 j
= (i
+ mac
->rotate
) % mac
->nparam
;
3796 tm
= mac
->params
[j
];
3797 t
= new_Token(NULL
, tm
->type
, tm
->text
, 0);
3798 *tt
= t
, tt
= &t
->next
;
3806 error(ERR_NONFATAL
, "`%%{%s}': macro parameters out of range",
3812 * Expand MMacro-local things: parameter references (%0, %n, %+n,
3813 * %-n) and MMacro-local identifiers (%%foo) as well as
3814 * macro indirection (%[...]) and range (%{..:..}).
3816 static Token
*expand_mmac_params(Token
* tline
)
3818 Token
*t
, *tt
, **tail
, *thead
;
3819 bool changed
= false;
3826 if (tline
->type
== TOK_PREPROC_ID
&&
3827 (((tline
->text
[1] == '+' || tline
->text
[1] == '-') && tline
->text
[2]) ||
3828 (tline
->text
[1] >= '0' && tline
->text
[1] <= '9') ||
3829 tline
->text
[1] == '%')) {
3831 int type
= 0, cc
; /* type = 0 to placate optimisers */
3838 tline
= tline
->next
;
3841 while (mac
&& !mac
->name
) /* avoid mistaking %reps for macros */
3842 mac
= mac
->next_active
;
3844 error(ERR_NONFATAL
, "`%s': not in a macro call", t
->text
);
3846 pos
= strchr(t
->text
, ':');
3848 switch (t
->text
[1]) {
3850 * We have to make a substitution of one of the
3851 * forms %1, %-1, %+1, %%foo, %0.
3855 snprintf(tmpbuf
, sizeof(tmpbuf
), "%d", mac
->nparam
);
3856 text
= nasm_strdup(tmpbuf
);
3860 snprintf(tmpbuf
, sizeof(tmpbuf
), "..@%"PRIu64
".",
3862 text
= nasm_strcat(tmpbuf
, t
->text
+ 2);
3865 n
= atoi(t
->text
+ 2) - 1;
3866 if (n
>= mac
->nparam
)
3869 if (mac
->nparam
> 1)
3870 n
= (n
+ mac
->rotate
) % mac
->nparam
;
3871 tt
= mac
->params
[n
];
3876 "macro parameter %d is not a condition code",
3881 if (inverse_ccs
[cc
] == -1) {
3883 "condition code `%s' is not invertible",
3887 text
= nasm_strdup(conditions
[inverse_ccs
[cc
]]);
3891 n
= atoi(t
->text
+ 2) - 1;
3892 if (n
>= mac
->nparam
)
3895 if (mac
->nparam
> 1)
3896 n
= (n
+ mac
->rotate
) % mac
->nparam
;
3897 tt
= mac
->params
[n
];
3902 "macro parameter %d is not a condition code",
3907 text
= nasm_strdup(conditions
[cc
]);
3911 n
= atoi(t
->text
+ 1) - 1;
3912 if (n
>= mac
->nparam
)
3915 if (mac
->nparam
> 1)
3916 n
= (n
+ mac
->rotate
) % mac
->nparam
;
3917 tt
= mac
->params
[n
];
3920 for (i
= 0; i
< mac
->paramlen
[n
]; i
++) {
3921 *tail
= new_Token(NULL
, tt
->type
, tt
->text
, 0);
3922 tail
= &(*tail
)->next
;
3926 text
= NULL
; /* we've done it here */
3931 * seems we have a parameters range here
3933 Token
*head
, **last
;
3934 head
= expand_mmac_params_range(mac
, t
, &last
);
3955 } else if (tline
->type
== TOK_INDIRECT
) {
3957 tline
= tline
->next
;
3958 tt
= tokenize(t
->text
);
3959 tt
= expand_mmac_params(tt
);
3960 tt
= expand_smacro(tt
);
3963 tt
->a
.mac
= NULL
; /* Necessary? */
3971 tline
= tline
->next
;
3979 const struct tokseq_match t
[] = {
3981 PP_CONCAT_MASK(TOK_ID
) |
3982 PP_CONCAT_MASK(TOK_FLOAT
), /* head */
3983 PP_CONCAT_MASK(TOK_ID
) |
3984 PP_CONCAT_MASK(TOK_NUMBER
) |
3985 PP_CONCAT_MASK(TOK_FLOAT
) |
3986 PP_CONCAT_MASK(TOK_OTHER
) /* tail */
3989 PP_CONCAT_MASK(TOK_NUMBER
), /* head */
3990 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
3993 paste_tokens(&thead
, t
, ARRAY_SIZE(t
), false);
4000 * Expand all single-line macro calls made in the given line.
4001 * Return the expanded version of the line. The original is deemed
4002 * to be destroyed in the process. (In reality we'll just move
4003 * Tokens from input to output a lot of the time, rather than
4004 * actually bothering to destroy and replicate.)
4007 static Token
*expand_smacro(Token
* tline
)
4009 Token
*t
, *tt
, *mstart
, **tail
, *thead
;
4010 SMacro
*head
= NULL
, *m
;
4013 unsigned int nparam
, sparam
;
4015 Token
*org_tline
= tline
;
4018 int deadman
= DEADMAN_LIMIT
;
4022 * Trick: we should avoid changing the start token pointer since it can
4023 * be contained in "next" field of other token. Because of this
4024 * we allocate a copy of first token and work with it; at the end of
4025 * routine we copy it back
4028 tline
= new_Token(org_tline
->next
, org_tline
->type
,
4029 org_tline
->text
, 0);
4030 tline
->a
.mac
= org_tline
->a
.mac
;
4031 nasm_free(org_tline
->text
);
4032 org_tline
->text
= NULL
;
4035 expanded
= true; /* Always expand %+ at least once */
4041 while (tline
) { /* main token loop */
4043 error(ERR_NONFATAL
, "interminable macro recursion");
4047 if ((mname
= tline
->text
)) {
4048 /* if this token is a local macro, look in local context */
4049 if (tline
->type
== TOK_ID
) {
4050 head
= (SMacro
*)hash_findix(&smacros
, mname
);
4051 } else if (tline
->type
== TOK_PREPROC_ID
) {
4052 ctx
= get_ctx(mname
, &mname
);
4053 head
= ctx
? (SMacro
*)hash_findix(&ctx
->localmac
, mname
) : NULL
;
4058 * We've hit an identifier. As in is_mmacro below, we first
4059 * check whether the identifier is a single-line macro at
4060 * all, then think about checking for parameters if
4063 list_for_each(m
, head
)
4064 if (!mstrcmp(m
->name
, mname
, m
->casesense
))
4070 if (m
->nparam
== 0) {
4072 * Simple case: the macro is parameterless. Discard the
4073 * one token that the macro call took, and push the
4074 * expansion back on the to-do stack.
4076 if (!m
->expansion
) {
4077 if (!strcmp("__FILE__", m
->name
)) {
4080 src_get(&num
, &file
);
4081 tline
->text
= nasm_quote(file
, strlen(file
));
4082 tline
->type
= TOK_STRING
;
4086 if (!strcmp("__LINE__", m
->name
)) {
4087 nasm_free(tline
->text
);
4088 make_tok_num(tline
, src_get_linnum());
4091 if (!strcmp("__BITS__", m
->name
)) {
4092 nasm_free(tline
->text
);
4093 make_tok_num(tline
, globalbits
);
4096 tline
= delete_Token(tline
);
4101 * Complicated case: at least one macro with this name
4102 * exists and takes parameters. We must find the
4103 * parameters in the call, count them, find the SMacro
4104 * that corresponds to that form of the macro call, and
4105 * substitute for the parameters when we expand. What a
4108 /*tline = tline->next;
4109 skip_white_(tline); */
4112 while (tok_type_(t
, TOK_SMAC_END
)) {
4113 t
->a
.mac
->in_progress
= false;
4115 t
= tline
->next
= delete_Token(t
);
4118 } while (tok_type_(tline
, TOK_WHITESPACE
));
4119 if (!tok_is_(tline
, "(")) {
4121 * This macro wasn't called with parameters: ignore
4122 * the call. (Behaviour borrowed from gnu cpp.)
4131 sparam
= PARAM_DELTA
;
4132 params
= nasm_malloc(sparam
* sizeof(Token
*));
4133 params
[0] = tline
->next
;
4134 paramsize
= nasm_malloc(sparam
* sizeof(int));
4136 while (true) { /* parameter loop */
4138 * For some unusual expansions
4139 * which concatenates function call
4142 while (tok_type_(t
, TOK_SMAC_END
)) {
4143 t
->a
.mac
->in_progress
= false;
4145 t
= tline
->next
= delete_Token(t
);
4151 "macro call expects terminating `)'");
4154 if (tline
->type
== TOK_WHITESPACE
4156 if (paramsize
[nparam
])
4159 params
[nparam
] = tline
->next
;
4160 continue; /* parameter loop */
4162 if (tline
->type
== TOK_OTHER
4163 && tline
->text
[1] == 0) {
4164 char ch
= tline
->text
[0];
4165 if (ch
== ',' && !paren
&& brackets
<= 0) {
4166 if (++nparam
>= sparam
) {
4167 sparam
+= PARAM_DELTA
;
4168 params
= nasm_realloc(params
,
4169 sparam
* sizeof(Token
*));
4170 paramsize
= nasm_realloc(paramsize
,
4171 sparam
* sizeof(int));
4173 params
[nparam
] = tline
->next
;
4174 paramsize
[nparam
] = 0;
4176 continue; /* parameter loop */
4179 (brackets
> 0 || (brackets
== 0 &&
4180 !paramsize
[nparam
])))
4182 if (!(brackets
++)) {
4183 params
[nparam
] = tline
->next
;
4184 continue; /* parameter loop */
4187 if (ch
== '}' && brackets
> 0)
4188 if (--brackets
== 0) {
4190 continue; /* parameter loop */
4192 if (ch
== '(' && !brackets
)
4194 if (ch
== ')' && brackets
<= 0)
4200 error(ERR_NONFATAL
, "braces do not "
4201 "enclose all of macro parameter");
4203 paramsize
[nparam
] += white
+ 1;
4205 } /* parameter loop */
4207 while (m
&& (m
->nparam
!= nparam
||
4208 mstrcmp(m
->name
, mname
,
4212 error(ERR_WARNING
|ERR_PASS1
|ERR_WARN_MNP
,
4213 "macro `%s' exists, "
4214 "but not taking %d parameters",
4215 mstart
->text
, nparam
);
4218 if (m
&& m
->in_progress
)
4220 if (!m
) { /* in progess or didn't find '(' or wrong nparam */
4222 * Design question: should we handle !tline, which
4223 * indicates missing ')' here, or expand those
4224 * macros anyway, which requires the (t) test a few
4228 nasm_free(paramsize
);
4232 * Expand the macro: we are placed on the last token of the
4233 * call, so that we can easily split the call from the
4234 * following tokens. We also start by pushing an SMAC_END
4235 * token for the cycle removal.
4242 tt
= new_Token(tline
, TOK_SMAC_END
, NULL
, 0);
4244 m
->in_progress
= true;
4246 list_for_each(t
, m
->expansion
) {
4247 if (t
->type
>= TOK_SMAC_PARAM
) {
4248 Token
*pcopy
= tline
, **ptail
= &pcopy
;
4252 ttt
= params
[t
->type
- TOK_SMAC_PARAM
];
4253 i
= paramsize
[t
->type
- TOK_SMAC_PARAM
];
4255 pt
= *ptail
= new_Token(tline
, ttt
->type
,
4261 } else if (t
->type
== TOK_PREPROC_Q
) {
4262 tt
= new_Token(tline
, TOK_ID
, mname
, 0);
4264 } else if (t
->type
== TOK_PREPROC_QQ
) {
4265 tt
= new_Token(tline
, TOK_ID
, m
->name
, 0);
4268 tt
= new_Token(tline
, t
->type
, t
->text
, 0);
4274 * Having done that, get rid of the macro call, and clean
4275 * up the parameters.
4278 nasm_free(paramsize
);
4281 continue; /* main token loop */
4286 if (tline
->type
== TOK_SMAC_END
) {
4287 tline
->a
.mac
->in_progress
= false;
4288 tline
= delete_Token(tline
);
4291 tline
= tline
->next
;
4299 * Now scan the entire line and look for successive TOK_IDs that resulted
4300 * after expansion (they can't be produced by tokenize()). The successive
4301 * TOK_IDs should be concatenated.
4302 * Also we look for %+ tokens and concatenate the tokens before and after
4303 * them (without white spaces in between).
4306 const struct tokseq_match t
[] = {
4308 PP_CONCAT_MASK(TOK_ID
) |
4309 PP_CONCAT_MASK(TOK_PREPROC_ID
), /* head */
4310 PP_CONCAT_MASK(TOK_ID
) |
4311 PP_CONCAT_MASK(TOK_PREPROC_ID
) |
4312 PP_CONCAT_MASK(TOK_NUMBER
) /* tail */
4315 if (paste_tokens(&thead
, t
, ARRAY_SIZE(t
), true)) {
4317 * If we concatenated something, *and* we had previously expanded
4318 * an actual macro, scan the lines again for macros...
4329 *org_tline
= *thead
;
4330 /* since we just gave text to org_line, don't free it */
4332 delete_Token(thead
);
4334 /* the expression expanded to empty line;
4335 we can't return NULL for some reasons
4336 we just set the line to a single WHITESPACE token. */
4337 memset(org_tline
, 0, sizeof(*org_tline
));
4338 org_tline
->text
= NULL
;
4339 org_tline
->type
= TOK_WHITESPACE
;
4348 * Similar to expand_smacro but used exclusively with macro identifiers
4349 * right before they are fetched in. The reason is that there can be
4350 * identifiers consisting of several subparts. We consider that if there
4351 * are more than one element forming the name, user wants a expansion,
4352 * otherwise it will be left as-is. Example:
4356 * the identifier %$abc will be left as-is so that the handler for %define
4357 * will suck it and define the corresponding value. Other case:
4359 * %define _%$abc cde
4361 * In this case user wants name to be expanded *before* %define starts
4362 * working, so we'll expand %$abc into something (if it has a value;
4363 * otherwise it will be left as-is) then concatenate all successive
4366 static Token
*expand_id(Token
* tline
)
4368 Token
*cur
, *oldnext
= NULL
;
4370 if (!tline
|| !tline
->next
)
4375 (cur
->next
->type
== TOK_ID
||
4376 cur
->next
->type
== TOK_PREPROC_ID
4377 || cur
->next
->type
== TOK_NUMBER
))
4380 /* If identifier consists of just one token, don't expand */
4385 oldnext
= cur
->next
; /* Detach the tail past identifier */
4386 cur
->next
= NULL
; /* so that expand_smacro stops here */
4389 tline
= expand_smacro(tline
);
4392 /* expand_smacro possibly changhed tline; re-scan for EOL */
4394 while (cur
&& cur
->next
)
4397 cur
->next
= oldnext
;
4404 * Determine whether the given line constitutes a multi-line macro
4405 * call, and return the MMacro structure called if so. Doesn't have
4406 * to check for an initial label - that's taken care of in
4407 * expand_mmacro - but must check numbers of parameters. Guaranteed
4408 * to be called with tline->type == TOK_ID, so the putative macro
4409 * name is easy to find.
4411 static MMacro
*is_mmacro(Token
* tline
, Token
*** params_array
)
4417 head
= (MMacro
*) hash_findix(&mmacros
, tline
->text
);
4420 * Efficiency: first we see if any macro exists with the given
4421 * name. If not, we can return NULL immediately. _Then_ we
4422 * count the parameters, and then we look further along the
4423 * list if necessary to find the proper MMacro.
4425 list_for_each(m
, head
)
4426 if (!mstrcmp(m
->name
, tline
->text
, m
->casesense
))
4432 * OK, we have a potential macro. Count and demarcate the
4435 count_mmac_params(tline
->next
, &nparam
, ¶ms
);
4438 * So we know how many parameters we've got. Find the MMacro
4439 * structure that handles this number.
4442 if (m
->nparam_min
<= nparam
4443 && (m
->plus
|| nparam
<= m
->nparam_max
)) {
4445 * This one is right. Just check if cycle removal
4446 * prohibits us using it before we actually celebrate...
4448 if (m
->in_progress
> m
->max_depth
) {
4449 if (m
->max_depth
> 0) {
4451 "reached maximum recursion depth of %i",
4458 * It's right, and we can use it. Add its default
4459 * parameters to the end of our list if necessary.
4461 if (m
->defaults
&& nparam
< m
->nparam_min
+ m
->ndefs
) {
4463 nasm_realloc(params
,
4464 ((m
->nparam_min
+ m
->ndefs
+
4465 1) * sizeof(*params
)));
4466 while (nparam
< m
->nparam_min
+ m
->ndefs
) {
4467 params
[nparam
] = m
->defaults
[nparam
- m
->nparam_min
];
4472 * If we've gone over the maximum parameter count (and
4473 * we're in Plus mode), ignore parameters beyond
4476 if (m
->plus
&& nparam
> m
->nparam_max
)
4477 nparam
= m
->nparam_max
;
4479 * Then terminate the parameter list, and leave.
4481 if (!params
) { /* need this special case */
4482 params
= nasm_malloc(sizeof(*params
));
4485 params
[nparam
] = NULL
;
4486 *params_array
= params
;
4490 * This one wasn't right: look for the next one with the
4493 list_for_each(m
, m
->next
)
4494 if (!mstrcmp(m
->name
, tline
->text
, m
->casesense
))
4499 * After all that, we didn't find one with the right number of
4500 * parameters. Issue a warning, and fail to expand the macro.
4502 error(ERR_WARNING
|ERR_PASS1
|ERR_WARN_MNP
,
4503 "macro `%s' exists, but not taking %d parameters",
4504 tline
->text
, nparam
);
4511 * Save MMacro invocation specific fields in
4512 * preparation for a recursive macro expansion
4514 static void push_mmacro(MMacro
*m
)
4516 MMacroInvocation
*i
;
4518 i
= nasm_malloc(sizeof(MMacroInvocation
));
4520 i
->params
= m
->params
;
4521 i
->iline
= m
->iline
;
4522 i
->nparam
= m
->nparam
;
4523 i
->rotate
= m
->rotate
;
4524 i
->paramlen
= m
->paramlen
;
4525 i
->unique
= m
->unique
;
4526 i
->condcnt
= m
->condcnt
;
4532 * Restore MMacro invocation specific fields that were
4533 * saved during a previous recursive macro expansion
4535 static void pop_mmacro(MMacro
*m
)
4537 MMacroInvocation
*i
;
4542 m
->params
= i
->params
;
4543 m
->iline
= i
->iline
;
4544 m
->nparam
= i
->nparam
;
4545 m
->rotate
= i
->rotate
;
4546 m
->paramlen
= i
->paramlen
;
4547 m
->unique
= i
->unique
;
4548 m
->condcnt
= i
->condcnt
;
4555 * Expand the multi-line macro call made by the given line, if
4556 * there is one to be expanded. If there is, push the expansion on
4557 * istk->expansion and return 1. Otherwise return 0.
4559 static int expand_mmacro(Token
* tline
)
4561 Token
*startline
= tline
;
4562 Token
*label
= NULL
;
4563 int dont_prepend
= 0;
4564 Token
**params
, *t
, *tt
;
4567 int i
, nparam
, *paramlen
;
4572 /* if (!tok_type_(t, TOK_ID)) Lino 02/25/02 */
4573 if (!tok_type_(t
, TOK_ID
) && !tok_type_(t
, TOK_PREPROC_ID
))
4575 m
= is_mmacro(t
, ¶ms
);
4581 * We have an id which isn't a macro call. We'll assume
4582 * it might be a label; we'll also check to see if a
4583 * colon follows it. Then, if there's another id after
4584 * that lot, we'll check it again for macro-hood.
4588 if (tok_type_(t
, TOK_WHITESPACE
))
4589 last
= t
, t
= t
->next
;
4590 if (tok_is_(t
, ":")) {
4592 last
= t
, t
= t
->next
;
4593 if (tok_type_(t
, TOK_WHITESPACE
))
4594 last
= t
, t
= t
->next
;
4596 if (!tok_type_(t
, TOK_ID
) || !(m
= is_mmacro(t
, ¶ms
)))
4604 * Fix up the parameters: this involves stripping leading and
4605 * trailing whitespace, then stripping braces if they are
4608 for (nparam
= 0; params
[nparam
]; nparam
++) ;
4609 paramlen
= nparam
? nasm_malloc(nparam
* sizeof(*paramlen
)) : NULL
;
4611 for (i
= 0; params
[i
]; i
++) {
4613 int comma
= (!m
->plus
|| i
< nparam
- 1);
4617 if (tok_is_(t
, "{"))
4618 t
= t
->next
, brace
= true, comma
= false;
4622 if (comma
&& t
->type
== TOK_OTHER
&& !strcmp(t
->text
, ","))
4623 break; /* ... because we have hit a comma */
4624 if (comma
&& t
->type
== TOK_WHITESPACE
4625 && tok_is_(t
->next
, ","))
4626 break; /* ... or a space then a comma */
4627 if (brace
&& t
->type
== TOK_OTHER
&& !strcmp(t
->text
, "}"))
4628 break; /* ... or a brace */
4635 * OK, we have a MMacro structure together with a set of
4636 * parameters. We must now go through the expansion and push
4637 * copies of each Line on to istk->expansion. Substitution of
4638 * parameter tokens and macro-local tokens doesn't get done
4639 * until the single-line macro substitution process; this is
4640 * because delaying them allows us to change the semantics
4641 * later through %rotate.
4643 * First, push an end marker on to istk->expansion, mark this
4644 * macro as in progress, and set up its invocation-specific
4647 ll
= nasm_malloc(sizeof(Line
));
4648 ll
->next
= istk
->expansion
;
4651 istk
->expansion
= ll
;
4654 * Save the previous MMacro expansion in the case of
4657 if (m
->max_depth
&& m
->in_progress
)
4665 m
->paramlen
= paramlen
;
4666 m
->unique
= unique
++;
4670 m
->next_active
= istk
->mstk
;
4673 list_for_each(l
, m
->expansion
) {
4676 ll
= nasm_malloc(sizeof(Line
));
4677 ll
->finishes
= NULL
;
4678 ll
->next
= istk
->expansion
;
4679 istk
->expansion
= ll
;
4682 list_for_each(t
, l
->first
) {
4686 tt
= *tail
= new_Token(NULL
, TOK_ID
, mname
, 0);
4688 case TOK_PREPROC_QQ
:
4689 tt
= *tail
= new_Token(NULL
, TOK_ID
, m
->name
, 0);
4691 case TOK_PREPROC_ID
:
4692 if (t
->text
[1] == '0' && t
->text
[2] == '0') {
4700 tt
= *tail
= new_Token(NULL
, x
->type
, x
->text
, 0);
4709 * If we had a label, push it on as the first line of
4710 * the macro expansion.
4713 if (dont_prepend
< 0)
4714 free_tlist(startline
);
4716 ll
= nasm_malloc(sizeof(Line
));
4717 ll
->finishes
= NULL
;
4718 ll
->next
= istk
->expansion
;
4719 istk
->expansion
= ll
;
4720 ll
->first
= startline
;
4721 if (!dont_prepend
) {
4723 label
= label
->next
;
4724 label
->next
= tt
= new_Token(NULL
, TOK_OTHER
, ":", 0);
4729 list
->uplevel(m
->nolist
? LIST_MACRO_NOLIST
: LIST_MACRO
);
4734 /* The function that actually does the error reporting */
4735 static void verror(int severity
, const char *fmt
, va_list arg
)
4738 MMacro
*mmac
= NULL
;
4741 vsnprintf(buff
, sizeof(buff
), fmt
, arg
);
4743 /* get %macro name */
4744 if (istk
&& istk
->mstk
) {
4746 /* but %rep blocks should be skipped */
4747 while (mmac
&& !mmac
->name
)
4748 mmac
= mmac
->next_active
, delta
++;
4752 nasm_error(severity
, "(%s:%d) %s",
4753 mmac
->name
, mmac
->lineno
- delta
, buff
);
4755 nasm_error(severity
, "%s", buff
);
4759 * Since preprocessor always operate only on the line that didn't
4760 * arrived yet, we should always use ERR_OFFBY1.
4762 static void error(int severity
, const char *fmt
, ...)
4766 /* If we're in a dead branch of IF or something like it, ignore the error */
4767 if (istk
&& istk
->conds
&& !emitting(istk
->conds
->state
))
4771 verror(severity
, fmt
, arg
);
4776 * Because %else etc are evaluated in the state context
4777 * of the previous branch, errors might get lost with error():
4778 * %if 0 ... %else trailing garbage ... %endif
4779 * So %else etc should report errors with this function.
4781 static void error_precond(int severity
, const char *fmt
, ...)
4785 /* Only ignore the error if it's really in a dead branch */
4786 if (istk
&& istk
->conds
&& istk
->conds
->state
== COND_NEVER
)
4790 verror(severity
, fmt
, arg
);
4795 pp_reset(char *file
, int apass
, ListGen
* listgen
, StrList
**deplist
)
4800 istk
= nasm_malloc(sizeof(Include
));
4803 istk
->expansion
= NULL
;
4805 istk
->fp
= fopen(file
, "r");
4807 src_set_fname(nasm_strdup(file
));
4811 error(ERR_FATAL
|ERR_NOFILE
, "unable to open input file `%s'",
4814 nested_mac_count
= 0;
4815 nested_rep_count
= 0;
4818 if (tasm_compatible_mode
) {
4819 stdmacpos
= nasm_stdmac
;
4821 stdmacpos
= nasm_stdmac_after_tasm
;
4823 any_extrastdmac
= extrastdmac
&& *extrastdmac
;
4828 * 0 for dependencies, 1 for preparatory passes, 2 for final pass.
4829 * The caller, however, will also pass in 3 for preprocess-only so
4830 * we can set __PASS__ accordingly.
4832 pass
= apass
> 2 ? 2 : apass
;
4834 dephead
= deptail
= deplist
;
4836 StrList
*sl
= nasm_malloc(strlen(file
)+1+sizeof sl
->next
);
4838 strcpy(sl
->str
, file
);
4840 deptail
= &sl
->next
;
4844 * Define the __PASS__ macro. This is defined here unlike
4845 * all the other builtins, because it is special -- it varies between
4848 t
= nasm_malloc(sizeof(*t
));
4850 make_tok_num(t
, apass
);
4852 define_smacro(NULL
, "__PASS__", true, 0, t
);
4855 static char *pp_getline(void)
4862 * Fetch a tokenized line, either from the macro-expansion
4863 * buffer or from the input file.
4866 while (istk
->expansion
&& istk
->expansion
->finishes
) {
4867 Line
*l
= istk
->expansion
;
4868 if (!l
->finishes
->name
&& l
->finishes
->in_progress
> 1) {
4872 * This is a macro-end marker for a macro with no
4873 * name, which means it's not really a macro at all
4874 * but a %rep block, and the `in_progress' field is
4875 * more than 1, meaning that we still need to
4876 * repeat. (1 means the natural last repetition; 0
4877 * means termination by %exitrep.) We have
4878 * therefore expanded up to the %endrep, and must
4879 * push the whole block on to the expansion buffer
4880 * again. We don't bother to remove the macro-end
4881 * marker: we'd only have to generate another one
4884 l
->finishes
->in_progress
--;
4885 list_for_each(l
, l
->finishes
->expansion
) {
4886 Token
*t
, *tt
, **tail
;
4888 ll
= nasm_malloc(sizeof(Line
));
4889 ll
->next
= istk
->expansion
;
4890 ll
->finishes
= NULL
;
4894 list_for_each(t
, l
->first
) {
4895 if (t
->text
|| t
->type
== TOK_WHITESPACE
) {
4896 tt
= *tail
= new_Token(NULL
, t
->type
, t
->text
, 0);
4901 istk
->expansion
= ll
;
4905 * Check whether a `%rep' was started and not ended
4906 * within this macro expansion. This can happen and
4907 * should be detected. It's a fatal error because
4908 * I'm too confused to work out how to recover
4914 "defining with name in expansion");
4915 else if (istk
->mstk
->name
)
4917 "`%%rep' without `%%endrep' within"
4918 " expansion of macro `%s'",
4923 * FIXME: investigate the relationship at this point between
4924 * istk->mstk and l->finishes
4927 MMacro
*m
= istk
->mstk
;
4928 istk
->mstk
= m
->next_active
;
4931 * This was a real macro call, not a %rep, and
4932 * therefore the parameter information needs to
4937 l
->finishes
->in_progress
--;
4939 nasm_free(m
->params
);
4940 free_tlist(m
->iline
);
4941 nasm_free(m
->paramlen
);
4942 l
->finishes
->in_progress
= 0;
4947 istk
->expansion
= l
->next
;
4949 list
->downlevel(LIST_MACRO
);
4952 while (1) { /* until we get a line we can use */
4954 if (istk
->expansion
) { /* from a macro expansion */
4956 Line
*l
= istk
->expansion
;
4958 istk
->mstk
->lineno
++;
4960 istk
->expansion
= l
->next
;
4962 p
= detoken(tline
, false);
4963 list
->line(LIST_MACRO
, p
);
4968 if (line
) { /* from the current input file */
4969 line
= prepreproc(line
);
4970 tline
= tokenize(line
);
4975 * The current file has ended; work down the istk
4981 /* nasm_error can't be conditionally suppressed */
4982 nasm_error(ERR_FATAL
,
4983 "expected `%%endif' before end of file");
4985 /* only set line and file name if there's a next node */
4987 src_set_linnum(i
->lineno
);
4988 nasm_free(src_set_fname(nasm_strdup(i
->fname
)));
4991 list
->downlevel(LIST_INCLUDE
);
4995 if (istk
->expansion
&& istk
->expansion
->finishes
)
5001 * We must expand MMacro parameters and MMacro-local labels
5002 * _before_ we plunge into directive processing, to cope
5003 * with things like `%define something %1' such as STRUC
5004 * uses. Unless we're _defining_ a MMacro, in which case
5005 * those tokens should be left alone to go into the
5006 * definition; and unless we're in a non-emitting
5007 * condition, in which case we don't want to meddle with
5010 if (!defining
&& !(istk
->conds
&& !emitting(istk
->conds
->state
))
5011 && !(istk
->mstk
&& !istk
->mstk
->in_progress
)) {
5012 tline
= expand_mmac_params(tline
);
5016 * Check the line to see if it's a preprocessor directive.
5018 if (do_directive(tline
) == DIRECTIVE_FOUND
) {
5020 } else if (defining
) {
5022 * We're defining a multi-line macro. We emit nothing
5024 * shove the tokenized line on to the macro definition.
5026 Line
*l
= nasm_malloc(sizeof(Line
));
5027 l
->next
= defining
->expansion
;
5030 defining
->expansion
= l
;
5032 } else if (istk
->conds
&& !emitting(istk
->conds
->state
)) {
5034 * We're in a non-emitting branch of a condition block.
5035 * Emit nothing at all, not even a blank line: when we
5036 * emerge from the condition we'll give a line-number
5037 * directive so we keep our place correctly.
5041 } else if (istk
->mstk
&& !istk
->mstk
->in_progress
) {
5043 * We're in a %rep block which has been terminated, so
5044 * we're walking through to the %endrep without
5045 * emitting anything. Emit nothing at all, not even a
5046 * blank line: when we emerge from the %rep block we'll
5047 * give a line-number directive so we keep our place
5053 tline
= expand_smacro(tline
);
5054 if (!expand_mmacro(tline
)) {
5056 * De-tokenize the line again, and emit it.
5058 line
= detoken(tline
, true);
5062 continue; /* expand_mmacro calls free_tlist */
5070 static void pp_cleanup(int pass
)
5073 if (defining
->name
) {
5075 "end of file while still defining macro `%s'",
5078 error(ERR_NONFATAL
, "end of file while still in %%rep");
5081 free_mmacro(defining
);
5091 nasm_free(i
->fname
);
5096 nasm_free(src_set_fname(NULL
));
5101 while ((i
= ipath
)) {
5110 static void pp_include_path(char *path
)
5114 i
= nasm_malloc(sizeof(IncPath
));
5115 i
->path
= path
? nasm_strdup(path
) : NULL
;
5128 static void pp_pre_include(char *fname
)
5130 Token
*inc
, *space
, *name
;
5133 name
= new_Token(NULL
, TOK_INTERNAL_STRING
, fname
, 0);
5134 space
= new_Token(name
, TOK_WHITESPACE
, NULL
, 0);
5135 inc
= new_Token(space
, TOK_PREPROC_ID
, "%include", 0);
5137 l
= nasm_malloc(sizeof(Line
));
5144 static void pp_pre_define(char *definition
)
5150 equals
= strchr(definition
, '=');
5151 space
= new_Token(NULL
, TOK_WHITESPACE
, NULL
, 0);
5152 def
= new_Token(space
, TOK_PREPROC_ID
, "%define", 0);
5155 space
->next
= tokenize(definition
);
5159 l
= nasm_malloc(sizeof(Line
));
5166 static void pp_pre_undefine(char *definition
)
5171 space
= new_Token(NULL
, TOK_WHITESPACE
, NULL
, 0);
5172 def
= new_Token(space
, TOK_PREPROC_ID
, "%undef", 0);
5173 space
->next
= tokenize(definition
);
5175 l
= nasm_malloc(sizeof(Line
));
5182 static void pp_extra_stdmac(macros_t
*macros
)
5184 extrastdmac
= macros
;
5187 static void make_tok_num(Token
* tok
, int64_t val
)
5190 snprintf(numbuf
, sizeof(numbuf
), "%"PRId64
"", val
);
5191 tok
->text
= nasm_strdup(numbuf
);
5192 tok
->type
= TOK_NUMBER
;
5195 struct preproc_ops nasmpp
= {