1 /****************************************************************************
2 *
3 *                            Open Watcom Project
4 *
5 *    Portions Copyright (c) 1983-2002 Sybase, Inc. All Rights Reserved.
6 *
7 *  ========================================================================
8 *
9 *    This file contains Original Code and/or Modifications of Original
10 *    Code as defined in and that are subject to the Sybase Open Watcom
11 *    Public License version 1.0 (the 'License'). You may not use this file
12 *    except in compliance with the License. BY USING THIS FILE YOU AGREE TO
13 *    ALL TERMS AND CONDITIONS OF THE LICENSE. A copy of the License is
14 *    provided with the Original Code and Modifications, and is also
15 *    available at www.sybase.com/developer/opensource.
16 *
17 *    The Original Code and all software distributed under the License are
18 *    distributed on an 'AS IS' basis, WITHOUT WARRANTY OF ANY KIND, EITHER
19 *    EXPRESS OR IMPLIED, AND SYBASE AND ALL CONTRIBUTORS HEREBY DISCLAIM
20 *    ALL SUCH WARRANTIES, INCLUDING WITHOUT LIMITATION, ANY WARRANTIES OF
21 *    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE, QUIET ENJOYMENT OR
22 *    NON-INFRINGEMENT. Please see the License for the specific language
23 *    governing rights and limitations under the License.
24 *
25 *  ========================================================================
26 *
27 * Description:  expression evaluator.
28 *
29 ****************************************************************************/
30 
31 #include <stddef.h>
32 #include <ctype.h>
33 
34 #include "globals.h"
35 #include "parser.h"
36 #include "reswords.h"
37 #include "expreval.h"
38 #include "segment.h"
39 #include "proc.h"
40 #include "assume.h"
41 #include "tokenize.h"
42 #include "types.h"
43 #include "label.h"
44 #include "atofloat.h"
45 #include "myassert.h"
46 
47 #define ALIAS_IN_EXPR 1 /* allow alias names in expression */
48 
49 #define UNARY_PLUSMINUS 0
50 #define BINARY_PLUSMINUS 1
51 
52 /* activate if a detailed error location is needed and -dt cant be used */
53 #if 0
54 #define ERRLOC( i ) printf("Error at %s.%u: %u >%s< >%s<\n", __FILE__, __LINE__, i, ModuleInfo.tokenarray[i].string_ptr, ModuleInfo.tokenarray[0].tokpos )
55 //#undef DebugMsg1
56 //#define DebugMsg1( x ) printf x
57 #else
58 #define ERRLOC( i )
59 #endif
60 
61 #if STACKBASESUPP==0
62 extern enum special_token basereg[];
63 #else
64 extern uint_32          StackAdj;
65 #endif
66 
67 #ifdef DEBUG_OUT
68 static int evallvl = 0;
69 #endif
70 
71 /* the following static variables should be moved to ModuleInfo. */
72 static struct asym *thissym; /* helper symbol for THIS operator */
73 static struct asym *nullstruct; /* used for T_DOT if second op is a forward ref */
74 static struct asym *nullmbr; /* used for T_DOT if "current" struct is a forward ref */
75 static int (* fnEmitErr)( int, ... );
76 static int noEmitErr( int msg, ... );
77 
78 /* code label type values - returned by SIZE and TYPE operators */
79 enum labelsize {
80     LS_SHORT  = 0xFF01, /* it's documented, but can a label be "short"? */
81     //LS_NEAR16 = 0xFF02, /* v2.09: the near values are calculated */
82     //LS_NEAR32 = 0xFF04,
83     //LS_NEAR64 = 0xFF08,
84     LS_FAR16  = 0xFF05,
85     LS_FAR32  = 0xFF06,
86 };
87 
init_expr(struct expr * opnd)88 static void init_expr( struct expr *opnd )
89 /****************************************/
90 {
91     opnd->value    = 0;
92     opnd->hvalue   = 0;
93     opnd->hlvalue  = 0;
94     opnd->quoted_string   = NULL;
95     opnd->base_reg = NULL;
96     opnd->idx_reg  = NULL;
97     opnd->label_tok = NULL;
98     opnd->override = NULL;
99     opnd->instr    = EMPTY;
100     opnd->kind     = EXPR_EMPTY;
101     opnd->mem_type = MT_EMPTY;
102     opnd->scale    = 0;
103     opnd->Ofssize  = USE_EMPTY;
104     opnd->flags1   = 0;
105     opnd->sym      = NULL;
106     opnd->mbr      = NULL;
107     opnd->type     = NULL;
108 }
109 
TokenAssign(struct expr * opnd1,const struct expr * opnd2)110 static void TokenAssign( struct expr *opnd1, const struct expr *opnd2 )
111 /*********************************************************************/
112 {
113 #if 1
114     /* note that offsetof() is used. This means, don't change position
115      of field <type> in expr! */
116     memcpy( opnd1, opnd2, offsetof( struct expr, type ) );
117 #else
118     opnd1->llvalue  = opnd2->llvalue;
119     opnd1->hlvalue  = opnd2->hlvalue;
120     opnd1->quoted_string   = opnd2->quoted_string; /* probably useless */
121     opnd1->base_reg = opnd2->base_reg;
122     opnd1->idx_reg  = opnd2->idx_reg;
123     opnd1->label_tok = opnd2->label_tok;
124     opnd1->override = opnd2->override;
125     opnd1->instr    = opnd2->instr;
126     opnd1->kind     = opnd2->kind;
127     opnd1->mem_type = opnd2->mem_type;
128     opnd1->scale    = opnd2->scale;
129     opnd1->Ofssize  = opnd2->Ofssize;
130     opnd1->flags1   = opnd2->flags1;
131     opnd1->sym      = opnd2->sym;
132     opnd1->mbr      = opnd2->mbr;
133 //  opnd1->type     = opnd2->type;
134 #endif
135 }
136 
137 //#define BRACKET_PRECEDENCE 1
138 //#define PTR_PRECEDENCE     4
139 //#define PLUS_PRECEDENCE    9
140 #define CMP_PRECEDENCE    10
141 
get_precedence(const struct asm_tok * item)142 static int get_precedence( const struct asm_tok *item )
143 /*****************************************************/
144 {
145     /* The following table is taken verbatim from MASM 6.1 Programmer's Guide,
146      * page 14, Table 1.3.
147 
148      * 1            (), []
149      * 2            LENGTH, SIZE, WIDTH, MASK, LENGTHOF, SIZEOF
150      * 3            . (structure-field-name operator)
151      * 4            : (segment override operator), PTR
152      * 5            LROFFSET, OFFSET, SEG, THIS, TYPE
153      * 6            HIGH, HIGHWORD, LOW, LOWWORD
154      * 7            +, - (unary)
155      * 8            *, /, MOD, SHL, SHR
156      * 9            +, - (binary)
157      * 10           EQ, NE, LT, LE, GT, GE
158      * 11           NOT
159      * 12           AND
160      * 13           OR, XOR
161      * 14           OPATTR, SHORT, .TYPE
162 
163      * The following table appears in QuickHelp online documentation for
164      * both MASM 6.0 and 6.1. It's slightly different!
165 
166      * 1            LENGTH, SIZE, WIDTH, MASK
167      * 2            (), []
168      * 3            . (structure-field-name operator)
169      * 4            : (segment override operator), PTR
170      * 5            THIS, OFFSET, SEG, TYPE
171      * 6            HIGH, LOW
172      * 7            +, - (unary)
173      * 8            *, /, MOD, SHL, SHR
174      * 9            +, - (binary)
175      * 10           EQ, NE, LT, LE, GT, GE
176      * 11           NOT
177      * 12           AND
178      * 13           OR, XOR
179      * 14           SHORT, OPATTR, .TYPE, ADDR
180 
181      * japheth: the first table is the prefered one. Reasons:
182      * - () and [] must be first.
183      * - it contains operators SIZEOF, LENGTHOF, HIGHWORD, LOWWORD, LROFFSET
184      * - ADDR is no operator for expressions. It's exclusively used inside
185      *   INVOKE directive.
186 
187      * However, what's wrong in both tables is the precedence of
188      * the dot operator: Actually for both JWasm and Wasm the dot precedence
189      * is 2 and LENGTH, SIZE, ... have precedence 3 instead.
190 
191      * Precedence of operator TYPE was 5 in original Wasm source. It has
192      * been changed to 4, as described in the Masm docs. This allows syntax
193      * "TYPE DWORD ptr xxx"
194 
195      * v2.02: another case which is problematic:
196      *     mov al,BYTE PTR CS:[]
197      * Since PTR and ':' have the very same priority, the evaluator will
198      * first calculate 'BYTE PTR CS'. This is invalid, but didn't matter
199      * prior to v2.02 because register coercion was never checked for
200      * plausibility. Solution: priority of ':' is changed from 4 to 3.
201      */
202 
203     switch( item->token ) {
204     case T_UNARY_OPERATOR:
205     case T_BINARY_OPERATOR:
206         return( item->precedence );
207     case T_OP_BRACKET:
208     case T_OP_SQ_BRACKET:
209         /* v2.08: with -Zm, the priority of [] and (), if
210          * used as binary operator, is 9 (like binary +/-).
211          * test cases: mov ax,+5[bx]
212          *             mov ax,-5[bx]
213          */
214         //return( 1 );
215         return( ModuleInfo.m510 ? 9 : 1 );
216     case T_DOT:
217         return( 2 );
218     case T_COLON:
219         //return( 4 );
220         return( 3 ); /* changed for v2.02 */
221     case '*':
222     case '/':
223         return( 8 );
224     case '+':
225     case '-':
226         return( item->specval ? 9 : 7 );
227     }
228     /* shouldn't happen! */
229     DebugMsg(("get_precedence: unexpected operator=%s\n", item->string_ptr));
230     fnEmitErr( SYNTAX_ERROR_EX, item->string_ptr );
231     return( ERROR );
232 }
233 
234 #if 0
235 static bool is_operator( enum tok_type tt )
236 /*****************************************/
237 /* determine if token is an operator */
238 {
239     /* T_OP_BRACKET and above: "(,[,],},:,.,+,-,*,/" */
240     /* rest: T_REG, T_STYPE, T_RES_ID, T_ID, T_STRING,
241      * T_NUM, T_FLOAT, T_BAD_NUM, T_DBL_COLON, T_PERCENT
242      */
243     return( tt >= T_OP_BRACKET || tt == T_UNARY_OPERATOR || tt == T_BINARY_OPERATOR );
244 }
245 
246 static bool is_unary_op( enum tok_type tt )
247 /*****************************************/
248 /* determine if token is an unary operator */
249 {
250     return( tt == T_OP_BRACKET || tt == T_OP_SQ_BRACKET || tt ==  '+' || tt == '-' || tt == T_UNARY_OPERATOR );
251 }
252 
253 #else
254 #define is_operator( tt ) ( tt >= T_OP_BRACKET || tt == T_UNARY_OPERATOR || tt == T_BINARY_OPERATOR )
255 #define is_unary_op( tt ) ( tt == T_OP_BRACKET || tt == T_OP_SQ_BRACKET || tt ==  '+' || tt == '-' || tt == T_UNARY_OPERATOR )
256 #endif
257 
258 /* get value for simple types
259  * NEAR, FAR and PROC are handled slightly differently:
260  * the HIBYTE is set to 0xFF, and PROC depends on the memory model
261  */
GetTypeSize(enum memtype mem_type,int Ofssize)262 static unsigned int GetTypeSize( enum memtype mem_type, int Ofssize )
263 /*******************************************************************/
264 {
265     if ( (mem_type & MT_SPECIAL) == 0 )
266         return( ( mem_type & MT_SIZE_MASK ) + 1 );
267     if ( Ofssize == USE_EMPTY )
268         Ofssize = ModuleInfo.Ofssize;
269     switch ( mem_type ) {
270     case MT_NEAR: return ( 0xFF00 | ( 2 << Ofssize ) ) ;
271     case MT_FAR:  return ( ( Ofssize == USE16 ) ? LS_FAR16 : 0xFF00 | ( ( 2 << Ofssize ) + 2 ) );
272     }
273     /* shouldn't happen */
274     return( 0 );
275 }
276 
277 #if AMD64_SUPPORT
GetRecordMask(struct dsym * record)278 static uint_64 GetRecordMask( struct dsym *record )
279 #else
280 static uint_32 GetRecordMask( struct dsym *record )
281 #endif
282 /*************************************************/
283 {
284 #if AMD64_SUPPORT
285     uint_64 mask = 0;
286 #else
287     uint_32 mask = 0;
288 #endif
289     int i;
290     struct sfield *fl;
291 
292     for ( fl = record->e.structinfo->head; fl; fl = fl->next ) {
293         struct asym *sym = &fl->sym;
294         for ( i = sym->offset ;i < sym->offset + sym->total_size; i++ )
295             mask |= 1 << i;
296     }
297     return( mask );
298 }
299 
300 /* v2.06: the value of number strings is now evaluated here.
301  * Prior to v2.06, it was evaluated in the tokenizer and the
302  * value was stored in the token string buffer. Since the content
303  * of the token buffer is no longer destroyed when macros or
304  * generated code is run, the old strategy needed too much space.
305  */
306 
myatoi128(const char * src,uint_64 dst[],int base,int size)307 void myatoi128( const char *src, uint_64 dst[], int base, int size )
308 /******************************************************************/
309 {
310     uint_32             val;
311     unsigned            len;
312     const char          *end = src + size;
313     uint_16             *px;
314 
315     dst[0] = 0;
316     dst[1] = 0;
317     do {
318         val = ( *src <= '9' ? *src - '0' : ( *src | 0x20 ) - 'a' + 10 );
319         px = (uint_16 *)dst;
320         for ( len = ( 2 * sizeof( uint_64 ) ) >> 1; len; len-- ) {
321             val += (uint_32)*px * base;
322             *(px++) = val;
323             val >>= 16;
324         };
325         //myassert( val == 0 ); /* if number doesn't fit in 128 bits */
326         src++;
327     } while( src < end );
328     return;
329 }
330 
331 /* get an operand. operands are:
332  * - integer constant      : EXPR_CONST
333  * - quoted string         : EXPR_CONST
334  * - register              : EXPR_REG (indirect = 1/0)
335  * - user identifier (T_ID): EXPR_ADDR | EXPR_CONST
336  * - reserved ID (T_RES_ID): EXPR_CONST ( EXPR_ADDR if id=FLAT )
337  * - float constant        : EXPR_FLOAT
338  *
339  * valid user identifiers are
340  * - TYPE ( struct/union, typedef, record )
341  * - STRUCT FIELD (also bitfield)
342  * - variable (internal, external, stack ) or constant (EQU, '=')
343  * valid reserved IDs are types (BYTE, WORD, ... ) and FLAT
344  */
get_operand(struct expr * opnd,int * idx,struct asm_tok tokenarray[],const uint_8 flags)345 static ret_code get_operand( struct expr *opnd, int *idx, struct asm_tok tokenarray[], const uint_8 flags )
346 /*********************************************************************************************************/
347 {
348     char        *tmp;
349     struct asym *sym;
350     int         i = *idx;
351     int         j;
352     char        labelbuff[16];/* for anonymous labels */
353 
354     DebugMsg1(("%u get_operand(idx=%u >%s<, flgs=%Xh) enter [memtype=%Xh]\n", evallvl, i, tokenarray[i].tokpos, flags, opnd->mem_type ));
355     switch( tokenarray[i].token ) {
356     case T_NUM:
357         DebugMsg1(("%u get_operand: T_NUM, %s, base=%u, len=%u\n", evallvl, tokenarray[i].string_ptr, tokenarray[i].numbase, tokenarray[i].itemlen ));
358         opnd->kind = EXPR_CONST;
359         myatoi128( tokenarray[i].string_ptr, &opnd->llvalue, tokenarray[i].numbase, tokenarray[i].itemlen );
360         //opnd->llvalue = tokenarray[i].value64;
361         //opnd->hlvalue = ( tokenarray[i].numflg == NF_NULL ? 0 : *(uint_64 *)( tokenarray[i].string_ptr - sizeof(uint_64) ) );
362         break;
363     case T_STRING:
364         DebugMsg1(("%u get_operand: T_STRING, %s, size=%u\n", evallvl, tokenarray[i].string_ptr, tokenarray[i].stringlen ));
365         /* string enclosed in <> or {} are rejected since v1.94! */
366         if ( tokenarray[i].string_delim != '"' && tokenarray[i].string_delim != '\'') {
367             if ( opnd->is_opattr ) /* OPATTR operator accepts anything! */
368                 break;
369                 /* v2.0: display a comprehensible error msg if a quote is missing */
370             if ( tokenarray[i].string_delim == NULLC &&
371                 ( *tokenarray[i].string_ptr == '"' || *tokenarray[i].string_ptr == '\'' ))
372                 fnEmitErr( MISSING_QUOTATION_MARK_IN_STRING );
373             else
374                 fnEmitErr( UNEXPECTED_LITERAL_FOUND_IN_EXPRESSION, tokenarray[i].tokpos );
375             return( ERROR );
376         }
377         opnd->kind = EXPR_CONST;
378         opnd->quoted_string = &tokenarray[i];
379         //opnd->value = 0;
380         tmp = tokenarray[i].string_ptr + 1; /* skip the quote */
381 
382         /* v2.06: use max. 16 bytes to create the "value".
383          * Prior to 2.06, max 8 bytes were used for 64-bit and
384          * max 4 bytes were used for 16-/32-bit.
385          */
386         j = ( tokenarray[i].stringlen > sizeof( opnd->chararray ) ? sizeof( opnd->chararray ) : tokenarray[i].stringlen );
387         for( ; j; j-- )
388             opnd->chararray[j-1] = *tmp++;
389         break;
390     case T_REG:
391         DebugMsg1(( "%u get_operand: T_REG, string=%s, tokval=%u, regno=%u\n", evallvl, tokenarray[i].string_ptr, tokenarray[i].tokval, tokenarray[i].bytval ));
392         opnd->kind = EXPR_REG;
393         opnd->base_reg = &tokenarray[i];
394         j = tokenarray[i].tokval;
395 
396         /* check if cpu is sufficient for register */
397         if( ( ( GetCpuSp( j ) & P_EXT_MASK ) &&
398              (( GetCpuSp( j ) & ModuleInfo.curr_cpu & P_EXT_MASK) == 0) ||
399              ( ModuleInfo.curr_cpu & P_CPU_MASK ) < ( GetCpuSp( j ) & P_CPU_MASK ) ) ) {
400             /* v2.11: do not exit in indirect mode; avoids additional syntax error caused by ']' */
401             if ( flags & EXPF_IN_SQBR ) {
402                 opnd->kind = EXPR_ERROR;
403                 fnEmitErr( INSTRUCTION_OR_REGISTER_NOT_ACCEPTED_IN_CURRENT_CPU_MODE );
404             } else
405                 return( fnEmitErr( INSTRUCTION_OR_REGISTER_NOT_ACCEPTED_IN_CURRENT_CPU_MODE ) );
406         }
407 
408         if( flags & EXPF_IN_SQBR ) {
409             /* a valid index register? */
410             if ( GetSflagsSp( j ) & SFR_IREG ) {
411                 opnd->indirect = TRUE;
412                 opnd->assumecheck = TRUE;
413             } else if ( GetValueSp( j ) & OP_SR ) {
414                 /* a segment register inside square brackets is only
415                  * accepted by Masm if it is the segment part of an
416                  * address (mov ax,[bx+cs:label])!
417                  */
418                 /* v2.10: check moved here avain. regression v2.08-2.09, where
419                  * it was in colon_op(). see regression test OVERRID3.ASC.
420                  */
421                 //if( tokenarray[i+1].token != T_COLON ) {
422                 if( tokenarray[i+1].token != T_COLON ||
423                    ( Options.strict_masm_compat && tokenarray[i+2].token == T_REG ) ) {
424                     return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
425                 }
426             } else {
427                 if ( opnd->is_opattr ) /* v2.11: just set error for opattr */
428                     opnd->kind = EXPR_ERROR;
429                 else
430                     return( fnEmitErr( MUST_BE_INDEX_OR_BASE_REGISTER ) );
431             }
432         }
433         break;
434     case T_ID:
435         tmp = tokenarray[i].string_ptr;
436         //if ( opnd->type ) { /* v2.11 */
437         if ( opnd->is_dot ) {
438             DebugMsg1(("%u get_operand: T_ID, is_dot=1, id=%s, opnd.type=%s\n", evallvl, tokenarray[i].string_ptr, opnd->type ? opnd->type->name : "NULL" ));
439             opnd->value = 0;
440             sym = ( opnd->type ? SearchNameInStruct( opnd->type, tmp, &opnd->uvalue, 0 ) : NULL );
441             DebugMsg1(("get_operand(%s): is_dot, sym=%s, offset=%" I32_SPEC "Xh\n",
442                        tmp, sym ? sym->name : "NULL", opnd->uvalue ));
443             if ( sym == NULL ) {
444                 sym = SymSearch( tmp );
445                 if ( sym ) {
446                     /*
447                      * skip a type specifier matching the data item's type
448                      * that's something like "<item>.<type>.<member>"
449                      */
450                     if ( sym->state == SYM_TYPE ) {
451                         /*
452                          * v2.07: "if" added.
453                          * Masm accepts a different type spec if the "assumed"
454                          * type is undefined
455                          * v2.09: the change in v2.07 is a regression. if it's a type,
456                          * then "usually" assume a type coercion and "switch" to the
457                          * new type - but not for register assume. This isn't fixed
458                          * yet, because there's no way to find out if a register assume
459                          * did set field 'type'.
460                          * v2.09: oldstructs condition added, see regression test dotop4.asm.
461                          * v2.11: fixme? opnd->type may be NULL here?
462                          * v2.12: for opnd->type==NULL test case, see expr5.aso.
463                          */
464                         //if ( sym == opnd->type || opnd->type->isdefined == FALSE )
465                         //if ( sym == opnd->type || opnd->type->isdefined == FALSE || ModuleInfo.oldstructs )
466                         if ( sym == opnd->type || ( opnd->type && opnd->type->isdefined == FALSE ) || ModuleInfo.oldstructs )
467                             ; //opnd->sym = sym;
468                         else {
469                             sym = NULL;
470                         }
471                     } else if ( ModuleInfo.oldstructs &&
472                                ( sym->state == SYM_STRUCT_FIELD ||
473                                 sym->state == SYM_EXTERNAL || /* v2.01: added */
474                                 /* v2.05: changed */
475                                 //( sym->state == SYM_INTERNAL && sym->mem_type == MT_ABS ) ) )
476                                 sym->state == SYM_INTERNAL ) )
477                         //opnd->sym = sym;
478                         ;
479                     else {
480                         /* fixme: clear sym?
481                          * if the symbol is not a type, it's an error which can
482                          * be detected in pass 1 already. dot_op() will emit
483                          * 'struct field expected' if sym isn't cleared.
484                          * v2.11: always clear sym.
485                          */
486                         //if ( opnd->type != nullstruct )
487                         sym = NULL;
488                     }
489                 }
490             }
491         } else {
492             DebugMsg1(("%u get_operand: T_ID, id=%s\n", evallvl, tokenarray[i].string_ptr ));
493             /* ensure anonym labels are uppercase */
494             /* v2.06: changed. Previously member 'string_ptr' was used to
495              * store the anonymous label, but one cannot safely assume that
496              * there's enough free space for a larger symbol name! It (partly)
497              * worked by accident, because @F/@B usually are the last tokens
498              * in a line [ but see: .if ( eax == @F && ecx == 2 ) ].
499              */
500             if ( *tmp == '@' && *(tmp+2 ) == NULLC ) {
501                 if ( *(tmp+1) == 'b' || *(tmp+1 ) == 'B' )
502                     tmp = GetAnonymousLabel( labelbuff, 0 );
503                 else if (*(tmp+1) == 'f' || *(tmp+1 ) == 'F' )
504                     tmp = GetAnonymousLabel( labelbuff, 1 );
505             }
506             sym = SymSearch( tmp );
507         }
508         if ( sym == NULL ||
509             sym->state == SYM_UNDEFINED ||
510             ( sym->state == SYM_TYPE && sym->typekind == TYPE_NONE ) ||  /* v2.10: added */
511 #if ALIAS_IN_EXPR == 0
512             sym->state == SYM_ALIAS || /* v2.04: added */
513 #endif
514             sym->state == SYM_MACRO ||
515             sym->state == SYM_TMACRO ) {
516 
517             /* for OPATTR, anything is ok */
518             if ( opnd->is_opattr ) {
519                 DebugMsg1(( "get_operand(%s): OPATTR, symbol invalid\n", tokenarray[i].string_ptr ));
520                 opnd->kind = EXPR_ERROR;
521                 break;
522             }
523 #if 0 /* v2.10: obsolete, since fnEmitErr() won't display anything in "EQU" mode */
524             /* if it is EQU, don't display an error, but return ERROR */
525             if ( flags & EXPF_NOERRMSG ) {
526                 DebugMsg1(("get_operand(%s): EQU, symbol invalid\n", tokenarray[i].string_ptr));
527                 return( ERROR );
528             }
529 #endif
530             if ( sym && ( sym->state == SYM_MACRO ||
531 #if ALIAS_IN_EXPR == 0
532                          sym->state == SYM_ALIAS || /* v2.04: added */
533 #endif
534                          sym->state == SYM_TMACRO ) ) {
535                 DebugMsg1(("get_operand(%s): symbol is macro/textmacro/alias!\n", tokenarray[i].string_ptr));
536                 fnEmitErr( INVALID_SYMBOL_TYPE_IN_EXPRESSION, sym->name );
537                 return( ERROR );
538             }
539             /* v2.11: flag EXPF_NOUNDEF won't accept undefined symbols anymore.
540              * previously, it did just avoid to create a label with state SYM_UNDEFINED -
541              * hence the old name, EXPF_NOLCREATE
542              */
543             //if( Parse_Pass == PASS_1 ) {
544             if( Parse_Pass == PASS_1 && !( flags & EXPF_NOUNDEF ) ) {
545                 /* if symbol wasn't found, assume it is a forward ref! */
546                 if ( sym == NULL ) {
547                     /* v2.11: flag EXPF_NOLCREATE has got another meaning */
548                     //if ( opnd->type == NULL && !( flags & EXPF_NOLCREATE ) ) { /* added v1.95 */
549                     if ( opnd->type == NULL ) {
550                         sym = SymLookup( tmp );
551                         sym->state = SYM_UNDEFINED;
552                         sym_add_table( &SymTables[TAB_UNDEF], (struct dsym *)sym ); /* add UNDEFINED */
553                         DebugMsg1(("get_operand(%s): symbol not (yet) defined, CurrProc=%s\n", tmp, CurrProc ? CurrProc->sym.name : "NULL" ));
554 
555                     // } else if ( opnd->type == NULL || opnd->type != nullstruct ) { /* v2.08: if changed */
556                     // } else if ( opnd->type == NULL || opnd->type->typekind != TYPE_NONE ) { /* v2.11: if changed */
557                     } else if ( opnd->type->typekind != TYPE_NONE ) {
558                         /* no struct or struct is known and defined */
559                         DebugMsg(("get_operand(%s): symbol error (type=%s typekind=%u)\n", tmp, opnd->type ? opnd->type->name : "NULL", opnd->type ? opnd->type->typekind : 0 ));
560                         if ( *opnd->type->name )
561                             fnEmitErr( MEMBER_NOT_DEFINED, opnd->type->name, tmp );
562                         else
563                             fnEmitErr( SYMBOL_NOT_DEFINED, tmp );
564                         return( ERROR );
565                     } else {
566                         /* forward reference to a struct.
567                          * In these cases, assume everything is ok.
568                          */
569                         if ( !nullmbr ) {
570                             nullmbr = SymAlloc( "" );
571                         }
572                         DebugMsg(("get_operand(%s): forward reference to a struct (using nullmbr)\n", tmp ));
573                         /* "break" because nullmbr has state SYM_UNDEFINED */
574                         opnd->mbr = nullmbr;
575                         opnd->kind = EXPR_CONST;
576                         break;
577                     }
578                 }
579             } else {
580                 DebugMsg1(("get_operand(%s): symbol %s not defined, pass > 1, curr proc=>%s<, \n", tokenarray[i].string_ptr, tmp, CurrProc ? CurrProc->sym.name : "NULL" ));
581                 if ( opnd->type && *opnd->type->name ) {
582                     fnEmitErr( MEMBER_NOT_DEFINED, opnd->type->name, tmp );
583                 } else {
584                     fnEmitErr( SYMBOL_NOT_DEFINED, *(tmp+1) == '&' ? "@@" : tmp );
585                 }
586                 return( ERROR );
587             }
588 #if ALIAS_IN_EXPR /* v2.04b: added */
589         } else if ( sym->state == SYM_ALIAS ) {
590             /* ALIAS symbols are not really useable in expressions.
591              * The alias' substitute symbol is, however.
592              */
593             sym = sym->substitute; /* can't be NULL */
594 #endif
595         }
596         /* set default values */
597         sym->used = TRUE;
598         DebugMsg1(("get_operand(%s): sym->state=%u type=>%s< ofs=%X memtype=%Xh total_size=%u defined=%u\n",
599                 tokenarray[i].string_ptr, sym->state, sym->type ? sym->type->name : "NULL", sym->offset, sym->mem_type, sym->total_size, sym->isdefined ));
600         switch ( sym->state ) {
601         case SYM_TYPE: /* STRUCT, UNION, RECORD, TYPEDEF */
602             /* v2.09: no structinfo data for typedefs */
603             if ( sym->typekind != TYPE_TYPEDEF && ((struct dsym *)sym)->e.structinfo->isOpen ) {
604                 DebugMsg1(("get_operand(%s): struct/union definition isn't closed!\n", sym->name ));
605                 opnd->kind = EXPR_ERROR;
606                 break;
607             }
608             /* skip "alias" types */
609             for ( ; sym->type; sym = sym->type );
610             opnd->kind = EXPR_CONST;
611             opnd->mem_type = sym->mem_type;
612             opnd->is_type = TRUE;
613             opnd->type = sym;
614             DebugMsg1(("get_operand(%s): symbol.typekind=%u (STRUCT/UNION/TYPEDEF/RECORD)\n", sym->name, sym->typekind ));
615 
616             /* v2.08: if() removed. This was an old hack. */
617             //if ( tokenarray[i-1].token != T_DOT && tokenarray[i+1].token != T_DOT )
618             /* v2.06: the default value for RECORD types is the mask value */
619             if ( sym->typekind == TYPE_RECORD ) {
620 #if AMD64_SUPPORT
621                 opnd->llvalue = GetRecordMask( (struct dsym *)sym );
622 #else
623                 opnd->value = GetRecordMask( (struct dsym *)sym );
624 #endif
625             } else if ( ( sym->mem_type & MT_SPECIAL_MASK ) == MT_ADDRESS ) { /* v2.09: added */
626                 if ( sym->mem_type == MT_PROC ) {
627                     opnd->value = sym->total_size;
628                     opnd->Ofssize = sym->Ofssize;
629                 } else
630                     opnd->value = GetTypeSize( sym->mem_type, sym->Ofssize );
631             } else
632                 opnd->value = sym->total_size;
633 
634             break;
635         case SYM_STRUCT_FIELD:
636             DebugMsg1(("get_operand(%s): structure field, ofs=%Xh\n", sym->name, sym->offset ));
637 
638             /* opnd->value might have been set by SearchNameInStruct() already! */
639             opnd->value += sym->offset;
640             opnd->kind = EXPR_CONST;
641             opnd->mbr = sym;
642             /* skip "alias" types (probably obsolete by now!) */
643             for ( ; sym->type; sym = sym->type );
644             opnd->mem_type = sym->mem_type;
645             /*
646              * check if the member field is a type (struct or union).
647              * If yes, set the <type> member!
648              * this cannot be done in PrepareOp()
649              */
650             opnd->type = ( sym->state == SYM_TYPE && sym->typekind != TYPE_TYPEDEF ) ? sym : NULL;
651             DebugMsg1(("get_operand: mem_type=%Xh type=%s\n", opnd->mem_type, opnd->type ? opnd->type->name : "NULL" ));
652             break;
653         default: /* SYM_INTERNAL, SYM_EXTERNAL, SYM_SEG, SYM_GRP, SYM_STACK */
654             opnd->kind = EXPR_ADDR;
655             /* call internal function (@Line, ... ) */
656             if ( sym->predefined && sym->sfunc_ptr )
657                 sym->sfunc_ptr( sym, NULL );
658             //if( opnd->sym->mem_type == MT_ABS ) {
659             if( sym->state == SYM_INTERNAL && sym->segment == NULL ) {
660                 opnd->kind = EXPR_CONST;
661                 opnd->uvalue = sym->uvalue;
662                 opnd->hvalue = sym->value3264;
663                 DebugMsg1(("get_operand(%s): equate hval=%Xh, lval=%Xh\n", sym->name, opnd->hvalue, opnd->uvalue ));
664                 opnd->mem_type = sym->mem_type;
665                 /* don't set the symbol reference, it isn't a label */
666             } else if( sym->state == SYM_EXTERNAL &&
667                       sym->mem_type == MT_EMPTY &&
668                       sym->iscomm == FALSE ) {
669                 /* type remains EXPR_ADDR, to force fixup creation */
670                 //opnd->mem_type = sym->mem_type; /* v2.10: unnecessary, init value IS MT_EMPTY */
671                 opnd->is_abs = TRUE;
672                 opnd->sym = sym;
673             } else {
674                 opnd->label_tok = &tokenarray[i];
675 
676                 /* a variable with arbitrary type? */
677                 /* v2.05: added check for MT_EMPTY */
678                 //if( opnd->sym->type ) {
679                 if( sym->type && sym->type->mem_type != MT_EMPTY ) {
680                     /* skip "alias" types */
681                     /* v2.05: obsolete */
682                     //for ( sym2 = opnd->sym; sym2->type; sym2 = sym2->type );
683                     //opnd->mem_type = sym2->mem_type;
684                     opnd->mem_type = sym->type->mem_type;
685                 } else {
686                     opnd->mem_type = sym->mem_type;
687                 }
688                 /* since there is no fixup for auto variables, the "offset"
689                  must be stored in the <value> field */
690                 if ( sym->state == SYM_STACK ) {
691 #if STACKBASESUPP
692                     /* v2.13: fixes github #6 */
693                     //opnd->llvalue = sym->offset + StackAdj;
694                     opnd->llvalue = (int_64)sym->offset + StackAdj;
695 #else
696                     //opnd->llvalue = sym->offset;
697                     opnd->llvalue = (int_64)sym->offset;
698 #endif
699                     opnd->indirect = TRUE;
700                     /* v2.10: base register values now set here */
701                     opnd->base_reg = &tokenarray[i];
702 #if STACKBASESUPP
703                     tokenarray[i].tokval = CurrProc->e.procinfo->basereg;
704 #else
705                     tokenarray[i].tokval = basereg[ModuleInfo.Ofssize];
706 #endif
707                     tokenarray[i].bytval = GetRegNo( tokenarray[i].tokval );
708                 }
709                 opnd->sym = sym;
710                 /* v2.09: added (also see change in PrepareOp() )
711                  * and see case SYM_STRUCT_FIELD.
712                  */
713                 for ( ; sym->type; sym = sym->type );
714                 opnd->type = ( sym->state == SYM_TYPE && sym->typekind != TYPE_TYPEDEF ) ? sym : NULL;
715             }
716             break;
717         }
718         break;
719     case T_STYPE:
720         DebugMsg1(("%u get_operand: T_STYPE (>%s<, value=%X)\n", evallvl, tokenarray[i].string_ptr, tokenarray[i].tokval));
721         opnd->kind = EXPR_CONST;
722         /* for types, return the size as numeric constant */
723         /* fixme: mem_type should be set only when used as first arg of PTR op! */
724         opnd->mem_type = GetMemtypeSp( tokenarray[i].tokval );
725         opnd->Ofssize = GetSflagsSp( tokenarray[i].tokval );
726         opnd->value = GetTypeSize( opnd->mem_type, opnd->Ofssize );
727         opnd->is_type = TRUE;
728         opnd->type = NULL; /* v2.08: added */
729         break;
730     case T_RES_ID:
731         DebugMsg1(("%u get_operand: T_RES_ID (>%s<, value=%X)\n", evallvl, tokenarray[i].string_ptr, tokenarray[i].tokval));
732         if ( tokenarray[i].tokval == T_FLAT ) {
733             /* v2.09: query NOUNDEF flag */
734             //if ( error_msg ) { /* don't define FLAT group in EQU expression! */
735             if ( ( flags & EXPF_NOUNDEF ) == 0 ) {
736                 /* v2.08 cpu check added */
737                 if( ( ModuleInfo.curr_cpu & P_CPU_MASK ) < P_386 ) {
738                     fnEmitErr( INSTRUCTION_OR_REGISTER_NOT_ACCEPTED_IN_CURRENT_CPU_MODE );
739                     return( ERROR );
740                 }
741                 DefineFlatGroup();
742             }
743             if ( !( opnd->sym = &ModuleInfo.flat_grp->sym ) )
744                 return( ERROR );
745 
746             opnd->label_tok = &tokenarray[i];
747             opnd->kind = EXPR_ADDR;
748 
749         } else {
750             return( fnEmitErr( SYNTAX_ERROR_EX, tokenarray[i].string_ptr ) );
751         }
752         break;
753     case T_FLOAT: /* v2.05 */
754         DebugMsg1(("%u get_operand: T_FLOAT (>%s<)\n", evallvl, tokenarray[i].string_ptr ));
755         opnd->kind = EXPR_FLOAT;
756         opnd->float_tok = &tokenarray[i];
757         //opnd->ftype = ( tokenarray[i].floattype != 0 );
758         break;
759     //case T_CL_BRACKET:
760     //case T_CL_SQ_BRACKET:
761     default:
762         DebugMsg1(("%u get_operand: default (token=%u, string=%s)\n", evallvl, tokenarray[i].token, tokenarray[i].string_ptr));
763         if ( opnd->is_opattr ) {    /* for OPATTR, allow any operand */
764             if ( tokenarray[i].token == T_FINAL ||
765                 tokenarray[i].token == T_CL_BRACKET ||
766                 tokenarray[i].token == T_CL_SQ_BRACKET ) /* don't go beyond T_FINAL, ) or ] ! */
767                 return( NOT_ERROR );
768             break;
769         }
770         if ( tokenarray[i].token == T_BAD_NUM )
771             /* Masm complains even if in EQU-mode */
772             fnEmitErr( NONDIGIT_IN_NUMBER, tokenarray[i].string_ptr );
773         else if ( tokenarray[i].token == T_COLON )
774             fnEmitErr( SYNTAX_ERROR_UNEXPECTED_COLON );
775         else if ( isalpha( *tokenarray[i].string_ptr ) )
776             fnEmitErr( EXPRESSION_EXPECTED, tokenarray[i].tokpos ); /* better error msg */
777         else
778             fnEmitErr( SYNTAX_ERROR_EX, tokenarray[i].tokpos );
779         return( ERROR );
780     }
781     (*idx)++;
782     DebugMsg1(("%u get_operand exit, ok, kind=%d value=%" I64_SPEC "X hvalue=%" I64_SPEC "X mem_type=%Xh abs=%u string=%s is_type=%u type=>%s< sym=%s mbr=%s\n",
783                evallvl, opnd->kind, opnd->llvalue, opnd->hlvalue, opnd->mem_type, opnd->is_abs,
784                opnd->quoted_string ? opnd->quoted_string->string_ptr : "NULL",
785                opnd->is_type, opnd->type ? opnd->type->name : "NULL",
786                opnd->sym ? opnd->sym->name : "NULL",
787                opnd->mbr ? opnd->mbr->name : "NULL" ));
788     return( NOT_ERROR );
789 }
790 
791 #if 0
792 static bool check_same( struct expr *opnd1, struct expr *opnd2, enum exprtype kind )
793 /**********************************************************************************/
794 /* Check if both tok_1 and tok_2 equal type */
795 {
796     return( ( opnd1->kind == kind && opnd2->kind == kind ) ? TRUE : FALSE );
797 }
798 #else
799 #define check_same( first, second, KIND ) ( first->kind == KIND && second->kind == KIND )
800 #endif
801 
check_both(const struct expr * opnd1,const struct expr * opnd2,enum exprtype type1,enum exprtype type2)802 static bool check_both( const struct expr *opnd1, const struct expr *opnd2, enum exprtype type1, enum exprtype type2 )
803 /********************************************************************************************************************/
804 /* Check if tok_1 == type1 and tok_2 == type2 or vice versa */
805 {
806     if( opnd1->kind == type1 && opnd2->kind == type2 )
807         return( TRUE );
808     if( opnd1->kind == type2 && opnd2->kind == type1 )
809         return( TRUE );
810     return( FALSE );
811 }
812 
index_connect(struct expr * opnd1,const struct expr * opnd2)813 static ret_code index_connect( struct expr *opnd1, const struct expr *opnd2 )
814 /***************************************************************************/
815 /* Connects the register lists. called by plus_op() and dot_op() */
816 {
817     /* move opnd2.base to either opnd1.base or opnd1.idx */
818     if ( opnd2->base_reg != NULL ) {
819         if ( opnd1->base_reg == NULL )
820             opnd1->base_reg = opnd2->base_reg;
821         else if ( opnd1->idx_reg == NULL ) {
822             /* v2.10: exchange base and index register.
823              * was previously in parser.c, and only done
824              * if -Zg was active.
825              */
826             if ( opnd1->base_reg->bytval != 4 ) {   /* if base isn't [E|R]SP, exchange regs */
827                 opnd1->idx_reg = opnd1->base_reg;
828                 opnd1->base_reg = opnd2->base_reg;
829             } else {
830                 opnd1->idx_reg = opnd2->base_reg;
831             }
832         } else {
833             return( fnEmitErr( MULTIPLE_INDEX_REGISTERS_NOT_ALLOWED ) );
834         }
835         opnd1->indirect = TRUE;
836     }
837     /* move opnd2.idx to opnd1.index - if it is free */
838     if( opnd2->idx_reg != NULL ) {
839         //if ( opnd2->scale == 0 && opnd1->base_reg == NULL ) {
840         //    opnd1->base_reg = opnd2->idx_reg;
841         //} else if ( opnd1->idx_reg == NULL ) {
842         if ( opnd1->idx_reg == NULL ) {
843             opnd1->idx_reg = opnd2->idx_reg;
844             opnd1->scale = opnd2->scale;
845         } else {
846             return( fnEmitErr( MULTIPLE_INDEX_REGISTERS_NOT_ALLOWED ) );
847         }
848         opnd1->indirect = TRUE;
849     }
850     return( NOT_ERROR );
851 }
852 
853 /* convert an address operand to a const operand if possible.
854  * called for '*', '/', '+', '-' and binary (EQ,NE, ... SHL, SHR, ... OR,AND,XOR) operators.
855  * the main purpose is: if a forward reference is included,
856  * assume it is referencing a constant, not a label.
857  */
858 
MakeConst(struct expr * opnd)859 static void MakeConst( struct expr *opnd )
860 /****************************************/
861 {
862     if( ( opnd->kind != EXPR_ADDR ) || opnd->indirect ) /* v2.09: check for indirect added */
863         return;
864 
865     if( opnd->sym ) {
866         if ( Parse_Pass > PASS_1 )
867             return;
868         /* added for v1.94: if the evaluator assumed an address because
869          * the label wasn't defined yet, then negate this. Also, an
870          * EXTERNDEF:ABS is to be accepted.
871          * v2.07: if the "not yet defined" label was an argument of
872          * an (OFFSET) operator, do NOT change the type!
873          */
874         if ( ( opnd->sym->state == SYM_UNDEFINED && opnd->instr == EMPTY ) ||
875             ( opnd->sym->state == SYM_EXTERNAL && opnd->sym->weak == TRUE && opnd->is_abs == TRUE ) )
876             ;
877         else
878             return;
879         /* assume a value != 0 to avoid problems with div */
880         opnd->value = 1;
881     }
882 
883     opnd->label_tok = NULL;
884     if( opnd->mbr != NULL ) {
885         if( opnd->mbr->state == SYM_STRUCT_FIELD ) {
886 #if 0 /* v2.09: mbr can only be SYM_STRUCT_FIELD or SYM_UNDEFINED (if nullmbr) */
887         } else if( opnd->mbr->state == SYM_TYPE ) {
888             opnd->value += opnd->mbr->total_size;
889             opnd->mbr = NULL;
890 #endif
891         } else {
892             return;
893         }
894     }
895 #if 0 /* v2.09: obsolete */
896     if( opnd->base_reg != NULL )
897         return;
898     if( opnd->idx_reg  != NULL )
899         return;
900 #endif
901     if( opnd->override != NULL )
902         return;
903     opnd->instr = EMPTY;
904     opnd->kind = EXPR_CONST;
905     //opnd->indirect = FALSE; /* not needed */
906     opnd->explicit = FALSE;
907     opnd->mem_type = MT_EMPTY;
908 }
909 
910 /* used by EQ, NE, GT, GE, LE, LT if item is a direct address
911  */
912 
MakeConst2(struct expr * opnd1,struct expr * opnd2)913 static ret_code MakeConst2( struct expr *opnd1, struct expr *opnd2 )
914 /******************************************************************/
915 {
916 
917     if ( opnd1->sym->state == SYM_EXTERNAL ) {
918         return( fnEmitErr( INVALID_USE_OF_EXTERNAL_SYMBOL, opnd1->sym->name ) );
919     } else if ( ( opnd1->sym->segment != opnd2->sym->segment &&
920                  /* v2.07: ignore segments if at least one label is a fwd ref */
921                  opnd1->sym->state != SYM_UNDEFINED &&
922                  opnd2->sym->state != SYM_UNDEFINED ) ||
923                opnd2->sym->state == SYM_EXTERNAL ) {
924         return( fnEmitErr( OPERANDS_MUST_BE_IN_SAME_SEGMENT ) );
925     }
926     opnd1->kind = EXPR_CONST;
927     opnd1->value += opnd1->sym->offset;
928     opnd2->kind = EXPR_CONST;
929     opnd2->value += opnd2->sym->offset;
930     return( NOT_ERROR );
931 }
932 
ConstError(struct expr * opnd1,struct expr * opnd2)933 static ret_code ConstError( struct expr *opnd1, struct expr *opnd2 )
934 /******************************************************************/
935 {
936     if ( opnd1->is_opattr )
937         return( NOT_ERROR );
938     if ( opnd1->kind == EXPR_FLOAT || opnd2->kind == EXPR_FLOAT )
939         fnEmitErr( REAL_OR_BCD_NUMBER_NOT_ALLOWED );
940     else
941         fnEmitErr( CONSTANT_EXPECTED );
942     return( ERROR );
943 }
944 
945 /* used by + and - binary operators */
946 
fix_struct_value(struct expr * opnd)947 static void fix_struct_value( struct expr *opnd )
948 /***********************************************/
949 {
950     if( opnd->mbr && ( opnd->mbr->state == SYM_TYPE ) ) {
951         opnd->value += opnd->mbr->total_size;
952         opnd->mbr = NULL;
953     }
954 }
955 
check_direct_reg(const struct expr * opnd1,const struct expr * opnd2)956 static int check_direct_reg( const struct expr *opnd1, const struct expr *opnd2 )
957 /*******************************************************************************/
958 {
959     if( ( opnd1->kind == EXPR_REG ) && ( opnd1->indirect == FALSE )
960         || ( opnd2->kind == EXPR_REG ) && ( opnd2->indirect == FALSE ) ) {
961         return( ERROR );
962     }
963     return( NOT_ERROR );
964 }
965 
GetSizeValue(struct asym * sym)966 static unsigned GetSizeValue( struct asym *sym )
967 /**********************************************/
968 {
969     if ( sym->mem_type == MT_PTR )
970         return( SizeFromMemtype( sym->isfar ? MT_FAR : MT_NEAR, sym->Ofssize, sym->type ) );
971     return( SizeFromMemtype( sym->mem_type, sym->Ofssize, sym->type ) );
972 }
973 
IsOffset(struct expr * opnd)974 static unsigned IsOffset( struct expr *opnd )
975 /*******************************************/
976 {
977     if ( opnd->mem_type == MT_EMPTY )
978         if ( opnd->instr == T_OFFSET ||
979 #if IMAGERELSUPP
980             opnd->instr == T_IMAGEREL ||
981 #endif
982 #if SECTIONRELSUPP
983             opnd->instr == T_SECTIONREL ||
984 #endif
985             opnd->instr == T_LROFFSET )
986             return( 1 );
987     return( 0 );
988 }
989 
invalid_operand(struct expr * opnd,char * oprtr,char * operand)990 static ret_code invalid_operand( struct expr *opnd, char *oprtr, char *operand )
991 /******************************************************************************/
992 {
993     if ( !opnd->is_opattr )
994         fnEmitErr( INVALID_OPERAND_FOR_OPERATOR, _strupr( oprtr), operand );
995     return( ERROR );
996 }
997 
998 /* operators
999  * LENGTH:    number of items of first initializer's first dimension
1000  * SIZE:      size in bytes of first initializer's first dimension
1001  * LENGTHOF:  number of elements in an array
1002  * SIZEOF:    size in bytes of item (array/struct)
1003  *
1004  * these operators accept structure fields, stack variables and data labels.
1005  * the old SIZE and LENGTH ops also accept code labels (memtype NEAR/FAR).
1006  * in Masm, symbolic constants (defined with EQU or =) are
1007  * also accepted, but no plain numbers!?
1008  */
1009 
sizlen_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1010 static ret_code sizlen_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1011 /*********************************************************************************************************/
1012 {
1013     opnd1->kind = EXPR_CONST;
1014 
1015     DebugMsg1(("sizlen_op(%s): sym=%X, mbr=%X, type=>%s<\n", GetResWName( oper, NULL ),
1016                opnd2->sym, opnd2->mbr, opnd2->type ? opnd2->type->name : "NULL" ));
1017 
1018     if ( sym ) {
1019         if ( sym->state == SYM_STRUCT_FIELD || sym->state == SYM_STACK )
1020             ;
1021         else if ( sym->state == SYM_UNDEFINED ) {
1022             /* v2.10: forward references should have attributes EXPR_ADDR + sym.state=SYM_UNDEFINED */
1023             opnd1->kind = EXPR_ADDR;
1024             opnd1->sym = sym;
1025         } else if ( ( sym->state == SYM_EXTERNAL ||
1026                  sym->state == SYM_INTERNAL) &&
1027                  //sym->mem_type != MT_ABS &&
1028                  sym->mem_type != MT_EMPTY &&
1029                  //sym->mem_type != MT_PROC && /* MT_PROC probably obsolete */
1030                  sym->mem_type != MT_FAR &&
1031                  sym->mem_type != MT_NEAR )
1032             ;
1033         else if ( sym->state == SYM_GRP || sym->state == SYM_SEG ) {
1034             return( fnEmitErr( EXPECTED_DATA_LABEL ) );
1035         } else if ( oper == T_SIZE || oper == T_LENGTH )
1036             ;
1037         else {
1038             return( fnEmitErr( EXPECTED_DATA_LABEL ) );
1039         }
1040     }
1041 
1042     switch( oper ) {
1043     case T_LENGTH:
1044         /* data items and struct fields have a "first" count.
1045          * for procedure locals (+arguments) and code labels, always 1 is returned.
1046          */
1047         /* v2.09: first_length is valid if isdata is set */
1048         //opnd1->value = ( sym->state != SYM_STACK && sym->isarray ) ? sym->first_length : 1;
1049         opnd1->value = sym->isdata ? sym->first_length : 1;
1050         break;
1051     case T_LENGTHOF:
1052         /* LENGTHOF needs either a data label or a structure field */
1053         /* a TYPE (structure, typedef) is invalid */
1054         if( opnd2->kind == EXPR_CONST ) {
1055             opnd1->value = opnd2->mbr->total_length;
1056 #if 0 /* v2.09: unnecessary */
1057         } else if( sym->state == SYM_UNDEFINED && Parse_Pass == PASS_1 ) {
1058             opnd1->value = sym->total_length;
1059 #endif
1060         } else if ( sym->state == SYM_EXTERNAL && sym->iscomm == FALSE ) {
1061             /* for externals other than COMM, total_length field is used otherwise */
1062             opnd1->value = 1;
1063         } else {
1064             opnd1->value = sym->total_length;
1065         }
1066         break;
1067     case T_SIZE:
1068         /* v2.04: first_size is no longer set for SYM_STACK. */
1069         if( sym == NULL ) {
1070             /* v2.09: check memtype */
1071             if ( ( opnd2->mem_type & MT_SPECIAL_MASK ) == MT_ADDRESS )
1072                 opnd1->value = 0xFF00 | opnd2->value;
1073             else
1074                 opnd1->value = opnd2->value;
1075         } else if ( sym->isdata ) {
1076             opnd1->value = sym->first_size;
1077 #if 0 /* v2.09: can't happen, since for a type, sym is NULL */
1078         } else if( sym->state == SYM_TYPE ) {
1079             opnd1->value = sym->total_size;
1080 #endif
1081         } else if( sym->state == SYM_STACK ) {
1082             opnd1->value = GetSizeValue( sym );
1083         } else if( sym->mem_type == MT_NEAR ) {
1084             /* v2.09: also handle 64-bit */
1085             //opnd1->value = GetSymOfssize( sym ) ? LS_NEAR32 : LS_NEAR16;
1086             opnd1->value = 0xFF00 | ( 2 << GetSymOfssize( sym ) );
1087         } else if( sym->mem_type == MT_FAR ) {
1088             opnd1->value = GetSymOfssize( sym ) ? LS_FAR32 : LS_FAR16;
1089         } else {
1090             opnd1->value = GetSizeValue( sym );
1091         }
1092         DebugMsg1(("sizlen_op(SIZE): result=%u [symbol %s, first_size=%u]\n", opnd1->value, sym ? sym->name : "NULL", sym ? sym->first_size : 0 ));
1093         break;
1094     case T_SIZEOF:
1095 #ifdef DEBUG_OUT
1096         if (sym)
1097             DebugMsg1(("sizlen_op(sizeof): symbol %s, state=%u, size=%u\n", sym->name, sym->state, sym->total_size ));
1098         else if ( opnd2->is_type && opnd2->type )
1099             DebugMsg1(("sizlen_op(sizeof): symbol %s (TYPE), opnd2.value=%u\n", opnd2->type->name, opnd2->value ));
1100         else
1101             DebugMsg1(("sizlen_op(sizeof): symbol NULL, opnd2.value=%u\n", opnd2->value ));
1102 #endif
1103         /* if sym is NULL, then operand is a type constant */
1104         if ( sym == NULL ) {
1105             /* v2.06: default value of RECORD types is the mask! */
1106             if ( opnd2->is_type && opnd2->type && opnd2->type->typekind == TYPE_RECORD )
1107                 opnd1->value = opnd2->type->total_size;
1108             else
1109                 opnd1->value = opnd2->value;
1110 #if 1 /* v2.05: don't use total_size for externals anymore! */
1111         } else if ( sym->state == SYM_EXTERNAL && sym->iscomm == FALSE ) {
1112             opnd1->value = GetSizeValue( sym );
1113             //if ( sym->iscomm == TRUE )
1114             //    opnd1->value *= sym->total_length;
1115 #endif
1116         } else
1117             opnd1->value = sym->total_size;
1118         break;
1119     }
1120     return( NOT_ERROR );
1121 }
1122 
1123 /* TYPE operator */
1124 
type_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1125 static ret_code type_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1126 /*******************************************************************************************************/
1127 {
1128     DebugMsg1(("type_op: opnd2 kind=%d memtype=%X sym=%s type=%s instr=%d istype=%u explicit=%u indirect=%u\n",
1129                opnd2->kind,
1130                opnd2->mem_type,
1131                sym ? sym->name : "NULL",
1132                opnd2->type ? opnd2->type->name : "NULL",
1133                opnd2->instr, opnd2->is_type, opnd2->explicit,  opnd2->indirect ));
1134     opnd1->kind = EXPR_CONST;
1135     /* TYPE accepts arrays/structs/unions/registers */
1136     /* v2.11: if memtype isn't empty, ignore any unary operator
1137      * test cases:
1138      * - type qword ptr sym.
1139      * - type qword ptr offset sym
1140      * operators LOW, HIGH, LOWWORD, HIGHWORD, LOW32, HIGH32,
1141      * OFFSET, IMAGEREL, SECTIONREL and LROFFSET
1142      * will set opnd.memtype to MT_EMPTY.
1143      */
1144     if( opnd2->instr != EMPTY && opnd2->mem_type != MT_EMPTY ) {
1145         opnd2->instr = EMPTY;
1146         sym = NULL;
1147     }
1148     if( opnd2->instr != EMPTY ) {
1149         if ( opnd2->sym ) {
1150             switch ( opnd2->instr ) {
1151             case T_LOW:
1152             case T_HIGH:
1153                 opnd1->value = 1;
1154                 break;
1155             case T_LOWWORD:
1156             case T_HIGHWORD:
1157                 //case T_SEG: /* masm returns 0 for TYPE SEG <label>! */
1158                 opnd1->value = 2;
1159                 break;
1160 #if LOHI32
1161             case T_LOW32:
1162             case T_HIGH32:
1163                 opnd1->value = 4;
1164                 break;
1165 #endif
1166             case T_OFFSET:
1167             case T_LROFFSET:
1168 #if SECTIONRELSUPP
1169             case T_SECTIONREL: /* masm returns 0 for TYPE SECTIONREL <label>! */
1170 #endif
1171 #if IMAGERELSUPP
1172             case T_IMAGEREL: /* masm returns 0 for TYPE IMAGEREL <label>! */
1173 #endif
1174                 opnd1->value = 2 << GetSymOfssize( opnd2->sym );
1175                 opnd1->is_type = TRUE; /* v2.03: added */
1176                 break;
1177             }
1178         }
1179     } else if ( sym == NULL ) {
1180         //printf( "sym=NULL kind=%d mem_type=%X indirect=%u is_type=%u type=%s\n", opnd2->kind, opnd2->mem_type, opnd2->indirect, opnd2->is_type, opnd2->type ? opnd2->type->name : "NULL" );
1181         /* for types, return total_size */
1182         if ( opnd2->is_type == TRUE ) {
1183             /* v2.06: default value of RECORD types is the mask! */
1184             if ( opnd2->type && opnd2->type->typekind == TYPE_RECORD )
1185                 opnd2->value = opnd2->type->total_size;
1186             //opnd1->value = opnd2->value;
1187             TokenAssign( opnd1, opnd2 );
1188             /* v2.05: added, (type procptr) ptr <reg>
1189              * the type probably should be set generally,
1190              * but this variant is the one used by INVOKE, other
1191              * usages are virtually irrelevant.
1192              * v2.10: opnd1->type now always set. Example:
1193              *   ( type x ) eq ( type y )
1194              * also see new function cmp_types()
1195              */
1196             //if ( opnd2->mem_type == MT_PROC )
1197             opnd1->type = opnd2->type;
1198 
1199         } else if ( opnd2->kind == EXPR_REG && opnd2->indirect == FALSE ) {
1200             opnd1->value = SizeFromRegister( opnd2->base_reg->tokval );
1201             opnd1->is_type = TRUE; /* v2.03: added */
1202             /* v2.10: check for assumes if it's a full size GPR */
1203             if ( opnd1->value == CurrWordSize &&
1204                 opnd1->mem_type == MT_EMPTY &&
1205                 ( GetValueSp( opnd2->base_reg->tokval ) & OP_RGT8 ) &&
1206                 ( sym = GetStdAssumeEx( opnd2->base_reg->bytval ) ) ) {
1207                 DebugMsg1(("type_op: assume type=%X [name=>%s< memtype=%X]\n", sym, sym->name, sym->mem_type ));
1208                 opnd1->type = sym;
1209                 opnd1->mem_type = sym->mem_type;
1210                 opnd1->value = sym->total_size;
1211             } else {
1212                 opnd1->mem_type = opnd2->mem_type; /* v2.10: added */
1213                 opnd1->type = opnd2->type; /* v2.10: added */
1214                 if ( opnd1->mem_type == MT_EMPTY )
1215                     MemtypeFromSize( opnd1->value, &opnd1->mem_type ); /* v2.03: added */
1216             }
1217 
1218 #if 0 /* Masm returns 0 for TYPE <segment_register> */
1219             /* if it is a segment register, use default word size */
1220             if ( opnd1->value == 0 )
1221                 opnd1->value = Use32 ? 4 : 2;
1222 #endif
1223         //} else if ( opnd2->explicit ) { /* v2.05: changed */
1224         //} else if ( opnd2->mem_type != MT_EMPTY ) { /* v2.10: changed */
1225         } else if ( opnd2->mem_type != MT_EMPTY || opnd2->explicit ) {
1226             if ( opnd2->mem_type != MT_EMPTY ) {
1227                 opnd1->value = SizeFromMemtype( opnd2->mem_type, opnd2->Ofssize, opnd2->type );
1228                 opnd1->mem_type = opnd2->mem_type; /* v2.04: added */
1229             } else {
1230                 if ( opnd2->type ) {
1231                     opnd1->value = opnd2->type->total_size;
1232                     opnd1->mem_type = opnd2->type->mem_type;
1233                 }
1234             }
1235             opnd1->is_type = TRUE; /* v2.04: added */
1236             opnd1->type = opnd2->type; /* v2.09: added */
1237         } else /* it is a number or EXPR_REG + indirect */
1238             opnd1->value = 0;
1239 #if 0
1240     } else if ( sym->state == SYM_TYPE ) {
1241         TokenAssign( opnd1, opnd2 );
1242         opnd1->type = sym;
1243 #endif
1244     } else if ( sym->state == SYM_UNDEFINED ) { /* v2.10: added */
1245         opnd1->kind = EXPR_ADDR;
1246         opnd1->sym = sym;
1247         /* is_type must be set, to avoid the forward referenced symbol be changed
1248          * to a type if the type expression is the left operand of PTR
1249          */
1250         opnd1->is_type = TRUE;
1251         //} else if( sym->mem_type == MT_TYPE ) { /* v2.04: check for explicit */
1252     } else if( sym->mem_type == MT_TYPE && opnd2->explicit == FALSE ) {
1253         opnd1->value = sym->type->total_size;
1254         opnd1->is_type = TRUE; /* v2.03: added */
1255         //if ( opnd1->mem_type == MT_EMPTY ) /* v2.09 */
1256         opnd1->mem_type = sym->type->mem_type; /* v2.09 */
1257         opnd1->type = sym->type; /* v2.09 */
1258         //printf( "sym=%s MT_TYPE type=%s type->memt=%X\n", sym->name, sym->type->name, sym->type->mem_type );
1259     } else {
1260 #if 1 /* v2.03: added */
1261         opnd1->is_type = TRUE;
1262         if ( opnd1->mem_type == MT_EMPTY )
1263             opnd1->mem_type = opnd2->mem_type;
1264 #endif
1265         //if ( opnd2->type ) { /* v2.10a: see types14.asm */
1266         if ( opnd2->type && opnd2->mbr == NULL ) {
1267             opnd1->type_tok = opnd2->type_tok;
1268             opnd1->type = opnd2->type;
1269             opnd1->value = opnd1->type->total_size;
1270         } else if ( sym->mem_type == MT_PTR ) {
1271             //printf( "sym=%s MT_PTR target_memt=%X target=%s\n", sym->name, sym->ptr_memtype, sym->target_type ? sym->target_type->name : "NULL" );
1272             opnd1->type_tok = opnd2->type_tok; /* v2.10: added */
1273             opnd1->value = SizeFromMemtype( sym->isfar ? MT_FAR : MT_NEAR, sym->Ofssize, NULL );
1274         } else if( sym->mem_type == MT_NEAR ) {
1275             /* v2.09: also handle 64-bit */
1276             //opnd1->value = GetSymOfssize( sym ) ? LS_NEAR32 : LS_NEAR16;
1277             opnd1->value = 0xFF00 | ( 2 << GetSymOfssize( sym ) );
1278         } else if( sym->mem_type == MT_FAR ) {
1279             opnd1->value = GetSymOfssize( sym ) ? LS_FAR32 : LS_FAR16;
1280         } else
1281             opnd1->value = SizeFromMemtype( opnd2->mem_type, GetSymOfssize( sym ), sym->type );
1282     }
1283     DebugMsg1(("type_op: result value=%u is_type=%u type=%s\n", opnd1->value, opnd1->is_type, opnd1->type ? opnd1->type->name : "NULL" ));
1284     return( NOT_ERROR );
1285 }
1286 
1287 /* v2.08: changed plain hex numbers to enum */
1288 enum opattr_bits {
1289     OPATTR_CODELABEL = 0x01,
1290     OPATTR_DATALABEL = 0x02,  /* memory variable, has relocatable data label */
1291     OPATTR_IMMEDIATE = 0x04,  /* immediate value */
1292     OPATTR_DIRECTMEM = 0x08,  /* uses direct memory addressing */
1293     OPATTR_REGISTER  = 0x10,  /* is a register value */
1294     OPATTR_DEFINED   = 0x20,  /* no reference to undefined label */
1295     OPATTR_SSREL     = 0x40,  /* is relative to SS */
1296     OPATTR_EXTRNREF  = 0x80,  /* references external label */
1297     OPATTR_LANG_MASK = 0x700,
1298 };
1299 
1300 /*
1301  * T_DOT_TYPE: implement .TYPE as an alias for OPATTR
1302  * T_OPATTR:
1303  */
opattr_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1304 static ret_code opattr_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1305 /*********************************************************************************************************/
1306 {
1307 
1308     DebugMsg1(("opattr_op: arg kind=%d memtype=%X sym=%s\n",
1309                opnd2->kind, opnd2->mem_type,
1310                opnd2->sym ? opnd2->sym->name : "NULL" ));
1311     opnd1->kind = EXPR_CONST;
1312     opnd1->sym = NULL;  /* clear symbol in case it is undef */
1313     opnd1->value = 0;
1314     opnd1->mem_type = MT_EMPTY;
1315     opnd1->is_opattr = FALSE; /* v2: added */
1316 
1317     if ( opnd2->kind == EXPR_EMPTY )
1318         return( NOT_ERROR );
1319 
1320     /* bit 0: code label (near|far)? */
1321     if ( opnd2->kind == EXPR_ADDR ) {
1322         if ( opnd2->sym && opnd2->sym->state != SYM_STACK &&
1323             ( opnd2->mem_type & MT_SPECIAL_MASK ) == MT_ADDRESS )
1324             opnd1->value |= OPATTR_CODELABEL;
1325 
1326         if ( IsOffset( opnd2 ) &&
1327             opnd2->sym &&
1328             ( opnd2->sym->mem_type & MT_SPECIAL_MASK ) == MT_ADDRESS )
1329             opnd1->value |= OPATTR_CODELABEL;
1330 
1331         /* bit 1: memory variable, relocatable data label? */
1332         if ( opnd2->sym &&
1333             (( opnd2->sym->mem_type == MT_TYPE ||
1334               ( opnd2->mem_type & MT_SPECIAL ) == 0 ) ||
1335              ( opnd2->mem_type == MT_EMPTY &&
1336               ( opnd2->sym->mem_type & MT_SPECIAL ) == 0 )))
1337             opnd1->value |= OPATTR_DATALABEL;
1338     }
1339     /* kind==EXPR_ADDR is not reliably set for indirect register addressing! */
1340     /* v2.12: check if operand is valid */
1341     //if ( opnd2->indirect )
1342     if ( opnd2->kind != EXPR_ERROR && opnd2->indirect )
1343         opnd1->value |= OPATTR_DATALABEL;
1344 
1345 
1346     /* bit 2: immediate value? */
1347     if ( opnd2->kind == EXPR_CONST ||
1348         ( opnd2->kind == EXPR_ADDR &&
1349          opnd2->indirect == FALSE &&
1350          (( opnd2->mem_type == MT_EMPTY && IsOffset(opnd2) ) ||
1351           //( opnd2->mem_type == MT_ABS ) ||  /* v2.06: added (abs. external) */
1352           ( opnd2->mem_type == MT_EMPTY ) ||  /* v2.06: added (abs. external) */
1353           (( opnd2->mem_type & MT_SPECIAL_MASK ) == MT_ADDRESS )) &&
1354          ( opnd2->sym->state == SYM_INTERNAL ||
1355           opnd2->sym->state == SYM_EXTERNAL ) ) )
1356         opnd1->value |= OPATTR_IMMEDIATE;
1357 
1358     /* bit 3: uses direct memory addressing?
1359      */
1360     if ( opnd2->kind == EXPR_ADDR &&
1361         opnd2->indirect == FALSE &&
1362         //opnd2->base_reg == NULL &&
1363         (( opnd2->mem_type == MT_EMPTY && opnd2->instr == EMPTY ) ||
1364          ( opnd2->mem_type == MT_TYPE ) || /* v2.05: added */
1365          (( opnd2->mem_type & MT_SPECIAL ) == 0 ) ||
1366          opnd2->mem_type == MT_PTR ) &&
1367         (opnd2->sym == NULL ||
1368          opnd2->sym->state == SYM_INTERNAL ||
1369          opnd2->sym->state == SYM_EXTERNAL ) )
1370         opnd1->value |= OPATTR_DIRECTMEM;
1371 
1372     if ( opnd2->kind == EXPR_REG && opnd2->indirect == FALSE )
1373         opnd1->value |= OPATTR_REGISTER;
1374 
1375     //if ( opnd2->kind != EXPR_ERROR && ( opnd2->sym == 0 || opnd2->sym->isdefined == TRUE ) )
1376     if ( opnd2->kind != EXPR_ERROR && opnd2->kind != EXPR_FLOAT && ( opnd2->sym == NULL || opnd2->sym->isdefined == TRUE ) )
1377         opnd1->value |= OPATTR_DEFINED;
1378 
1379     if ( ( opnd2->sym && opnd2->sym->state == SYM_STACK ) ||
1380         ( opnd2->indirect && opnd2->base_reg &&
1381          /* v2.11: use new flag SFR_SSBASED */
1382          //( opnd2->base_reg->tokval == T_ESP || opnd2->base_reg->tokval == T_EBP || opnd2->base_reg->tokval == T_BP ) ) )
1383          ( GetSflagsSp( opnd2->base_reg->tokval ) & SFR_SSBASED ) ) )
1384         opnd1->value |= OPATTR_SSREL;
1385 
1386     if ( opnd2->sym && opnd2->sym->state == SYM_EXTERNAL )
1387         opnd1->value |= OPATTR_EXTRNREF;
1388 
1389     if ( oper == T_OPATTR )
1390         /* v2.12: no language if symbol isn't defined properly */
1391         //if ( opnd2->sym )
1392         if ( opnd2->sym && opnd2->kind != EXPR_ERROR )
1393             opnd1->value |= opnd2->sym->langtype << 8;
1394 
1395     DebugMsg1(("opattr_op returns %Xh\n", opnd1->value));
1396     return( NOT_ERROR );
1397 }
1398 
short_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1399 static ret_code short_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1400 /********************************************************************************************************/
1401 {
1402     if ( opnd2->kind != EXPR_ADDR ||
1403         ( opnd2->mem_type != MT_EMPTY &&
1404          opnd2->mem_type != MT_NEAR &&
1405          opnd2->mem_type != MT_FAR ) ) {
1406         return( fnEmitErr( EXPRESSION_MUST_BE_A_CODE_ADDRESS ) );
1407     }
1408     TokenAssign( opnd1, opnd2 );
1409     opnd1->instr = oper;
1410     return( NOT_ERROR );
1411 }
1412 
seg_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1413 static ret_code seg_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1414 /******************************************************************************************************/
1415 {
1416     /* v2.10: check for sym==NULL ( seg ds:[0] ) added */
1417     if ( opnd2->sym == NULL || opnd2->sym->state == SYM_STACK || opnd2->is_abs ) {
1418         return( fnEmitErr( OPERAND_MUST_BE_RELOCATABLE ) );
1419     }
1420     TokenAssign( opnd1, opnd2 );
1421     opnd1->instr = oper;
1422     if ( opnd1->mbr ) /* v2.08: set value more selectively */
1423         opnd1->value = 0;    /* v2.07: added ( SEG <member> ) */
1424     opnd1->mem_type = MT_EMPTY; /* v2.04a */
1425     return( NOT_ERROR );
1426 }
1427 
1428 /* handles offset operators:
1429  * OFFSET, LROFFSEG, IMAGEREL, SECTIONREL
1430  */
1431 
offset_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1432 static ret_code offset_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1433 /*********************************************************************************************************/
1434 {
1435     if ( oper == T_OFFSET ) {
1436         /* if operand is a constant value, skip OFFSET operator */
1437         if ( opnd2->kind == EXPR_CONST ) {
1438             TokenAssign( opnd1, opnd2 );
1439             return( NOT_ERROR );
1440         }
1441     }
1442     if ( (sym && sym->state == SYM_GRP) || opnd2->instr == T_SEG ) {
1443         return( invalid_operand( opnd2, GetResWName( oper, NULL ), name ) );
1444     }
1445     /* offset operator accepts types, but returns always 0 */
1446     if ( opnd2->is_type )
1447         opnd2->value = 0;
1448 
1449     TokenAssign( opnd1, opnd2 );
1450     opnd1->instr = oper;
1451 
1452     if ( opnd2->indirect ) {
1453         /* Masm v5.1 allows indirect operands, but Masm v6 with -Zm
1454          * won't accept it.
1455          */
1456         return( invalid_operand( opnd2, GetResWName( oper, NULL ), name ) );
1457     }
1458     /* skip memory type of operand, just address is needed */
1459     //opnd1->mem_type = MT_NEAR;
1460     opnd1->mem_type = MT_EMPTY;
1461     /* clear overrides ("offset SEG:xxx") */
1462     /* v2.01: override information is important for fixup creation!
1463      * the reason why it was cleared probably was to avoid creation
1464      * of a segment prefix. This case is now handled in the parser.
1465      */
1466     // opnd1->override = NULL;
1467     return( NOT_ERROR );
1468 }
1469 
lowword_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1470 static ret_code lowword_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1471 /**********************************************************************************************************/
1472 {
1473     TokenAssign( opnd1, opnd2 );
1474     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1475         opnd1->instr = T_LOWWORD;
1476         //opnd1->mem_type = MT_WORD; /* v2.05 */
1477         opnd1->mem_type = MT_EMPTY;
1478     }
1479     opnd1->llvalue &= 0xffff;
1480     return( NOT_ERROR );
1481 }
1482 
highword_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1483 static ret_code highword_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1484 /***********************************************************************************************************/
1485 {
1486     TokenAssign( opnd1, opnd2 );
1487     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1488         opnd1->instr = T_HIGHWORD;
1489         //opnd1->mem_type = MT_WORD; /* v2.05 */
1490         opnd1->mem_type = MT_EMPTY;
1491     }
1492     //opnd1->value = opnd1->value >> 16;
1493     opnd1->llvalue = ( opnd1->llvalue >> 16 ) & 0xffff;/* v2.12: fix for bug #298 in SF */
1494     return( NOT_ERROR );
1495 }
1496 
low_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1497 static ret_code low_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1498 /******************************************************************************************************/
1499 {
1500     TokenAssign( opnd1, opnd2 );
1501     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1502 #if 0
1503         /* LOW works for OMF/BIN only */
1504         /* v2.07: don't check any format-specific rules in the
1505          * expression evaluator!
1506          */
1507         if ( Options.output_format != OFORMAT_OMF &&
1508             Options.output_format != OFORMAT_BIN && opnd2->sym ) {
1509             return( fnEmitErr( SYMBOL_TYPE_CONFLICT, opnd2->sym->name ) );
1510         }
1511 #endif
1512         opnd1->instr = T_LOW;
1513         opnd1->mem_type = MT_EMPTY;
1514     }
1515     opnd1->llvalue &= 0xff;
1516     return( NOT_ERROR );
1517 }
1518 
high_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1519 static ret_code high_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1520 /*******************************************************************************************************/
1521 {
1522     TokenAssign( opnd1, opnd2 );
1523     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1524         /* v2.07: don't check any format-specific rules in the
1525          * expression evaluator!
1526          */
1527 #if 0
1528         if ( Options.output_format != OFORMAT_OMF &&
1529             Options.output_format != OFORMAT_BIN && opnd2->sym ) {
1530             return( fnEmitErr( SYMBOL_TYPE_CONFLICT, opnd2->sym->name ) );
1531         }
1532 #endif
1533         opnd1->instr = T_HIGH;
1534         opnd1->mem_type = MT_EMPTY;
1535     }
1536     opnd1->value = opnd1->value >> 8;
1537     opnd1->llvalue &= 0xff;
1538     return( NOT_ERROR );
1539 }
1540 
1541 #if LOHI32
1542 
low32_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1543 static ret_code low32_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1544 /********************************************************************************************************/
1545 {
1546     /* v2.06: added support for double constants */
1547     if ( opnd2->kind == EXPR_FLOAT ) {
1548         if ( Options.strict_masm_compat )
1549             return( ConstError( opnd1, opnd2 ) );
1550         atofloat( &opnd2->llvalue, opnd2->float_tok->string_ptr, sizeof( opnd2->llvalue), opnd2->negative, opnd2->float_tok->floattype );
1551         opnd2->kind = EXPR_CONST;
1552         opnd2->float_tok = NULL;
1553     }
1554     TokenAssign( opnd1, opnd2 );
1555     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1556         opnd1->instr = T_LOW32;
1557         //opnd1->mem_type = MT_DWORD; /* v2.10: changed - also see change in parser.c, idata_fixup() */
1558         opnd1->mem_type = MT_EMPTY;
1559     }
1560     opnd1->llvalue &= 0xffffffff;
1561     return( NOT_ERROR );
1562 }
1563 
high32_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1564 static ret_code high32_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1565 /*********************************************************************************************************/
1566 {
1567     /* v2.06: added support for double constants */
1568     if ( opnd2->kind == EXPR_FLOAT ) {
1569         if ( Options.strict_masm_compat )
1570             return( ConstError( opnd1, opnd2 ) );
1571         atofloat( &opnd2->llvalue, opnd2->float_tok->string_ptr, sizeof( opnd2->llvalue), opnd2->negative, opnd2->float_tok->floattype );
1572         opnd2->kind = EXPR_CONST;
1573         opnd2->float_tok = NULL;
1574     }
1575     TokenAssign( opnd1, opnd2 );
1576     if ( opnd2->kind == EXPR_ADDR && opnd2->instr != T_SEG ) {
1577         opnd1->instr = T_HIGH32;
1578         //opnd1->mem_type = MT_DWORD; /* v2.10: changed - also see change in parser.c, idata_fixup() */
1579         opnd1->mem_type = MT_EMPTY;
1580     }
1581     opnd1->llvalue = opnd1->llvalue >> 32;
1582     return( NOT_ERROR );
1583 }
1584 
1585 #endif
1586 
this_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1587 static ret_code this_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1588 /*******************************************************************************************************/
1589 {
1590     if ( opnd2->is_type == FALSE ) {
1591         return( fnEmitErr( INVALID_TYPE_EXPRESSION ) );
1592     }
1593     /* v2.06: won't work inside structs */
1594     if ( CurrStruct ) {
1595         return( fnEmitErr( MUST_BE_IN_SEGMENT_BLOCK ) );
1596     }
1597     /* v2.06: won't work outside segments */
1598     if ( CurrSeg == NULL ) {
1599         return( EmitErr( MUST_BE_IN_SEGMENT_BLOCK ) ); /* error displayed even in EQU, hence EmitErr()! */
1600     }
1601 
1602     if ( thissym == NULL ) {
1603         thissym = SymAlloc( "" );
1604         /* fixme: set thissym->variable? */
1605         thissym->state = SYM_INTERNAL;
1606         thissym->isdefined = TRUE;
1607     }
1608 
1609     DebugMsg1(("this_op: memtype=%Xh type=%s\n", opnd2->mem_type, opnd2->type ? opnd2->type->name : "NULL" ));
1610     opnd1->kind = EXPR_ADDR;
1611 
1612     /* v2.09: a label is not a valid argument */
1613     //if ( opnd2->sym && opnd2->sym->mem_type == MT_TYPE )
1614     //    thissym->type = opnd2->sym->type;
1615     /* v2.09: set structured type */
1616     thissym->type = opnd2->type;
1617     if ( opnd2->type ) {
1618         thissym->mem_type = MT_TYPE;
1619     } else
1620         thissym->mem_type = opnd2->mem_type;
1621 
1622     opnd1->sym  = thissym;
1623     SetSymSegOfs( thissym );
1624     opnd1->mem_type = thissym->mem_type;
1625     return( NOT_ERROR );
1626 }
1627 
1628 /* WIDTH and MASK operators */
1629 
wimask_op(int oper,struct expr * opnd1,struct expr * opnd2,struct asym * sym,char * name)1630 static ret_code wimask_op( int oper, struct expr *opnd1, struct expr *opnd2, struct asym *sym, char *name )
1631 /*********************************************************************************************************/
1632 {
1633     /* additional check needed if operand is a type */
1634     if ( opnd2->is_type ) {
1635         sym = opnd2->type;
1636         if (sym->typekind != TYPE_RECORD ) {
1637             return( fnEmitErr( OPERAND_MUST_BE_RECORD ) );
1638         }
1639     } else if ( opnd2->kind == EXPR_CONST ) {
1640         sym = opnd2->mbr;
1641     } else {
1642         sym = opnd2->sym;
1643     }
1644     if ( oper == T_MASK ) {
1645         int i;
1646         opnd1->value = 0;
1647         if ( opnd2->is_type ) { /* get mask of the RECORD? */
1648 #if AMD64_SUPPORT
1649             opnd1->llvalue = GetRecordMask( (struct dsym *)sym );
1650 #else
1651             opnd1->value = GetRecordMask( (struct dsym *)sym );
1652 #endif
1653         } else { /* get mask of the bitfield */
1654             for ( i = sym->offset ;i < sym->offset + sym->total_size; i++ )
1655 #if AMD64_SUPPORT
1656 #if defined(LLONG_MAX) || defined(__GNUC__) || defined(__TINYC__)
1657                 opnd1->llvalue |= 1ULL << i;
1658 #else
1659                 opnd1->llvalue |= 1i64 << i;
1660 #endif
1661 #else
1662                 opnd1->value |= 1 << i;
1663 #endif
1664         }
1665     } else {
1666         if ( opnd2->is_type ) { /* get width of the RECORD? */
1667             struct dsym *dir = (struct dsym *)sym;
1668             struct sfield *fl;
1669             for ( fl = dir->e.structinfo->head; fl; fl = fl->next )
1670                 opnd1->value += fl->sym.total_size;
1671         } else
1672             opnd1->value = sym->total_size;
1673     }
1674     opnd1->kind = EXPR_CONST;
1675     return( NOT_ERROR );
1676 }
1677 
1678 #define  res(token, function) function ,
1679 static ret_code (* const unaryop[])( int, struct expr *, struct expr *, struct asym *, char * ) = {
1680 #include "unaryop.h"
1681 };
1682 #undef res
1683 
1684 /* plus_op() is called by [], () and + operator handlers */
1685 
plus_op(struct expr * opnd1,struct expr * opnd2)1686 static ret_code plus_op( struct expr *opnd1, struct expr *opnd2 )
1687 /***************************************************************/
1688 {
1689     DebugMsg1(("plus_op: kind=%d/%d memtype=%Xh-%Xh value=%d-%d sym=%s-%s mbr=%s-%s type=%s-%s\n",
1690                opnd1->kind, opnd2->kind,
1691                opnd1->mem_type, opnd2->mem_type,
1692                opnd1->value, opnd2->value,
1693                opnd1->sym ? opnd1->sym->name : "NULL",
1694                opnd2->sym ? opnd2->sym->name : "NULL",
1695                opnd1->mbr ? opnd1->mbr->name : "NULL",
1696                opnd2->mbr ? opnd2->mbr->name : "NULL",
1697                opnd1->type ? opnd1->type->name : "NULL",
1698                opnd2->type ? opnd2->type->name : "NULL" ));
1699     /*
1700      * The formats allowed are (registers inside [] only!):
1701      *        constant + constant  CONST-CONST
1702      *        constant + address   CONST-ADDR
1703      *        register + constant  ADDR-CONST
1704      *        address + register   ADDR-ADDR
1705      *        register + register  ADDR-ADDR
1706      *        address  + address   ADDR-ADDR
1707      */
1708 
1709     if( check_direct_reg( opnd1, opnd2 ) == ERROR ) {
1710         DebugMsg(("plus_op: error direct register\n" ));
1711         return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
1712     }
1713     /* v2.08: remove EXPR_REG variants */
1714     if ( opnd1->kind == EXPR_REG )
1715         opnd1->kind = EXPR_ADDR;
1716     if ( opnd2->kind == EXPR_REG )
1717         opnd2->kind = EXPR_ADDR;
1718 
1719     /* v2.07: don't allow multiple overrides */
1720     if ( opnd2->override ) {
1721         if ( opnd1->override ) {
1722             /* v2.07a: both T_REG or both T_ID is rejected */
1723             if ( opnd1->override->token == opnd2->override->token ) {
1724                 DebugMsg(("plus_op: multiple overrides\n" ));
1725                 return( fnEmitErr( MULTIPLE_OVERRIDES ) );
1726             }
1727         }
1728         opnd1->override = opnd2->override;
1729     }
1730 
1731     if( check_same( opnd1, opnd2, EXPR_CONST ) ) {
1732 
1733         DebugMsg1(("plus_op: CONST - CONST\n" ));
1734         opnd1->llvalue += opnd2->llvalue;
1735 
1736     } else if( check_same( opnd1, opnd2, EXPR_ADDR ) ) {
1737 
1738         DebugMsg1(("plus_op: ADDR - ADDR\n" ));
1739         fix_struct_value( opnd1 );
1740         fix_struct_value( opnd2 );
1741         if ( index_connect( opnd1, opnd2 ) == ERROR )
1742             return( ERROR );
1743         if( opnd2->sym != NULL ) {
1744             /* two relocatable labels not allowed */
1745             /* v2.05: changed */
1746             //if ( ( opnd1->sym != NULL ) && ( Parse_Pass > PASS_1 || error_msg == FALSE ) ) {
1747             if ( opnd1->sym != NULL &&
1748                 opnd1->sym->state != SYM_UNDEFINED &&
1749                 opnd2->sym->state != SYM_UNDEFINED ) {
1750                 DebugMsg(("plus_op: two relocatable labels: %s - %s \n", opnd1->sym->name, opnd2->sym->name ));
1751                 return( fnEmitErr( CANNOT_ADD_TWO_RELOCATABLE_LABELS ) );
1752             }
1753             opnd1->label_tok = opnd2->label_tok;
1754             opnd1->sym = opnd2->sym;
1755             /* v2.05: added */
1756             if ( opnd1->mem_type == MT_EMPTY )
1757                 opnd1->mem_type = opnd2->mem_type;
1758             /* v2.10: copy qualifier ( [<reg>+imagerel xxx] */
1759             if ( opnd2->instr != EMPTY )
1760                 opnd1->instr = opnd2->instr;
1761         }
1762         opnd1->llvalue += opnd2->llvalue;
1763         /* v2.08: added, test case [ecx+ebx.<struc>].<mbr> */
1764         if ( opnd2->type )
1765             opnd1->type = opnd2->type;
1766 
1767     } else if( check_both( opnd1, opnd2, EXPR_CONST, EXPR_ADDR ) ) {
1768 
1769         if( opnd1->kind == EXPR_CONST ) {
1770             DebugMsg1(("plus_op: CONST - ADDR\n" ));
1771             opnd2->llvalue += opnd1->llvalue;
1772             opnd2->indirect |= opnd1->indirect;
1773 
1774             if( opnd1->explicit == TRUE ) {
1775                 opnd2->explicit = TRUE;
1776                 opnd2->mem_type = opnd1->mem_type;
1777             } else if ( opnd2->mem_type == MT_EMPTY )
1778                 opnd2->mem_type = opnd1->mem_type;
1779 
1780             /* v2.05: added. See dotop2.asm, "mov eax, v2.f1[ebx*2]" */
1781             if ( opnd2->mbr == NULL )
1782                 opnd2->mbr = opnd1->mbr;
1783 
1784             /* v2.08: added, test case [4+ebx.<struc>].<mbr> */
1785             if ( opnd2->type )
1786                 opnd1->type = opnd2->type; /* set <type> in op1! */
1787 
1788             TokenAssign( opnd1, opnd2 );
1789 
1790         } else {
1791             DebugMsg1(("plus_op: ADDR - CONST\n" ));
1792             opnd1->llvalue += opnd2->llvalue;
1793             /* v2.04: added. to make this case behave like
1794              * the CONST - REG case (see below).
1795              */
1796             /* v2.08: changed, test case [reg+struct] */
1797             //if ( opnd1->mem_type == MT_EMPTY )
1798             if ( opnd2->mbr ) { /* v2.10: added; regression test dotop5.asm */
1799                 opnd1->mbr = opnd2->mbr;
1800                 opnd1->mem_type = opnd2->mem_type;
1801             } else
1802             if ( opnd1->mem_type == MT_EMPTY && opnd2->is_type == FALSE )
1803                 opnd1->mem_type = opnd2->mem_type;
1804         }
1805         fix_struct_value( opnd1 );
1806     } else {
1807         DebugMsg(("plus_op: error, unexpected format: %u - %u\n", opnd1->kind, opnd2->kind ));
1808         return( ConstError( opnd1, opnd2 ) );
1809     }
1810     return( NOT_ERROR );
1811 }
1812 
minus_op(struct expr * opnd1,struct expr * opnd2)1813 static ret_code minus_op( struct expr *opnd1, struct expr *opnd2 )
1814 /****************************************************************/
1815 {
1816     struct asym      *sym;
1817     /*
1818      * The only formats allowed are:
1819      *        constant - constant
1820      *         address - constant       ( only in this order )
1821      *         address - address
1822      *        register - constant       ( only inside [] and in this
1823      *                                    order )
1824      */
1825 
1826     DebugMsg1(("minus_op: kind tok1=%u, tok2=%u\n", opnd1->kind, opnd2->kind ));
1827 
1828     if( check_direct_reg( opnd1, opnd2 ) == ERROR ) {
1829         DebugMsg(("minus_op: error direct register\n"));
1830         return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
1831     }
1832 
1833     /* added for v1.94. It's related to the change done in MakeConst()!
1834      * todo: find out why flag no_error_msg was checked in v1.94-2.09.
1835      */
1836     if ( opnd1->kind == EXPR_ADDR &&
1837         opnd2->kind == EXPR_ADDR &&
1838         opnd2->sym &&
1839         opnd2->sym->state == SYM_UNDEFINED /* && !no_error_msg */ )
1840         ; /* don't convert token2 to a constant! */
1841     else
1842         MakeConst( opnd2 );
1843 
1844     if( check_same( opnd1, opnd2, EXPR_CONST ) ) {
1845 
1846         DebugMsg1(("minus_op: CONST-CONST\n" ));
1847         opnd1->llvalue -= opnd2->llvalue;
1848 
1849     } else if( opnd1->kind == EXPR_ADDR &&
1850               opnd2->kind == EXPR_CONST ) {
1851 
1852         DebugMsg1(("minus_op: ADDR-CONST\n" ));
1853         opnd1->llvalue -= opnd2->llvalue;
1854         fix_struct_value( opnd1 );
1855 
1856     } else if( check_same( opnd1, opnd2, EXPR_ADDR ) ){
1857 
1858         DebugMsg1(("minus_op: ADDR-ADDR\n" ));
1859         fix_struct_value( opnd1 );
1860         fix_struct_value( opnd2 );
1861         //if( opnd2->base_reg != NULL || opnd2->idx_reg != NULL ) { /* v2.09: just check 'indirect' */
1862         if( opnd2->indirect ) {
1863             DebugMsg(("minus_op error, opnd2->indirect==TRUE\n"));
1864             return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
1865         }
1866         if( opnd2->label_tok == NULL ) {
1867             /* v2.06c: do 64-bit arithmetic (more rigid test in data.c) */
1868             //opnd1->value -= opnd2->value;
1869             opnd1->value64 -= opnd2->value64;
1870             opnd1->indirect |= opnd2->indirect;
1871         } else {
1872             if( opnd1->label_tok == NULL || opnd1->sym == NULL || opnd2->sym == NULL ) {
1873                 DebugMsg(("minus_op error, label_tok=%X opnd1.sym=%X opnd2.sym=%X\n", opnd1->label_tok, opnd1->sym, opnd2->sym ));
1874                 /* v2.05: error msg changed */
1875                 //fnEmitErr( SYNTAX_ERROR );
1876                 return( fnEmitErr( OPERAND_MUST_BE_RELOCATABLE ) );
1877             }
1878             /* handle first operand */
1879             sym = opnd1->sym;
1880             opnd1->value += sym->offset;
1881 
1882             /* handle second operand */
1883             sym = opnd2->sym;
1884             if( Parse_Pass > PASS_1 ) {
1885                 /* if symbol is external, error - unless it's the same symbol */
1886                 if ( ( sym->state == SYM_EXTERNAL ||
1887                      opnd1->sym->state == SYM_EXTERNAL) &&
1888                     sym != opnd1->sym ) {
1889                     DebugMsg(("minus_op error 6\n"));
1890                     return( fnEmitErr(INVALID_USE_OF_EXTERNAL_SYMBOL, opnd1->sym->name ) );
1891                 }
1892                 /* check if the 2 offsets belong to the same segment */
1893                 if ( sym->segment != opnd1->sym->segment ) {
1894                     DebugMsg(("minus_op error, sym.segm=%X opnd1->sym.segm=%X\n", sym->segment, opnd1->sym->segment ));
1895                     return( fnEmitErr( OPERANDS_MUST_BE_IN_SAME_SEGMENT ) );
1896                 }
1897             }
1898 
1899             /* the type changes from address to constant.
1900              * but only if both labels are defined and no indirect addressing.
1901              */
1902             opnd1->kind = EXPR_CONST;
1903 
1904             /* v2.05: if at least one label is undefined, assume result=1 */
1905             if ( opnd1->sym->state == SYM_UNDEFINED ||
1906                 opnd2->sym->state == SYM_UNDEFINED ) {
1907                 opnd1->value = 1;
1908                 /* 2.09: make sure an undefined label is returned in opnd.sym.
1909                  * expression type has to be ADDR then; see equate22.aso.
1910                  * 2.11: returning EXPR_ADDR may cause problems -
1911                  * it may make the code longer than necessary, thus
1912                  * triggering an unnecessary jump extension.
1913                  * so it is returned only if the expression is used to define an equate.
1914                  */
1915                 if ( opnd1->sym->state != SYM_UNDEFINED ) {
1916                     opnd1->sym = opnd2->sym;
1917                     opnd1->label_tok = opnd2->label_tok;
1918                 }
1919                 opnd1->kind = EXPR_ADDR;
1920             } else {
1921                 /* v2.06c: do 64-bit arithmetic (more rigid test in data.c) */
1922                 //opnd1->value -= sym->offset;
1923                 //opnd1->value -= opnd2->value;
1924                 opnd1->value64 -= sym->offset;
1925                 opnd1->value64 -= opnd2->value64;
1926                 opnd1->label_tok = NULL;
1927                 opnd1->sym = NULL;
1928             }
1929             //if( opnd1->base_reg == NULL && opnd1->idx_reg == NULL ) { /* v2.09: just check 'indirect' */
1930             if( opnd1->indirect == FALSE ) {
1931                 if( opnd1->instr == T_OFFSET && opnd2->instr == T_OFFSET )
1932                     opnd1->instr = EMPTY;
1933                 //opnd1->indirect = FALSE; /* v2.09: not needed */
1934             } else {
1935                 DebugMsg1(("minus_op, exit, ADDR, base=%X, idx=%X\n", opnd1->base_reg, opnd1->idx_reg ));
1936                 opnd1->kind = EXPR_ADDR;
1937                 //opnd1->indirect |= opnd2->indirect;  /* v2.09: op1->indirect is always 1, op2->indirect is always 0 */
1938             }
1939             opnd1->explicit = FALSE;
1940             opnd1->mem_type = MT_EMPTY;
1941         }
1942 
1943     } else if( opnd1->kind == EXPR_REG &&
1944               opnd2->kind == EXPR_CONST ) {
1945 
1946         opnd1->llvalue = -1 * opnd2->llvalue;
1947         opnd1->indirect |= opnd2->indirect;
1948         opnd1->kind = EXPR_ADDR;
1949 
1950     } else {
1951         DebugMsg(("minus_op, exit, error: kinds tok1=%u, tok2=%u\n", opnd1->kind, opnd2->kind ));
1952         return( ConstError( opnd1, opnd2 ) );
1953     }
1954     return( NOT_ERROR );
1955 }
1956 
1957 /* v2.10: don't emit "struct field expected" error if item is an operand of OPATTR */
1958 
struct_field_error(struct expr * opnd)1959 static ret_code struct_field_error( struct expr *opnd )
1960 /*****************************************************/
1961 {
1962     if ( opnd->is_opattr ) {
1963         opnd->kind = EXPR_ERROR;
1964         return( NOT_ERROR );
1965     }
1966     return( fnEmitErr( STRUCTURE_FIELD_EXPECTED ) );
1967 }
1968 
dot_op(struct expr * opnd1,struct expr * opnd2)1969 static ret_code dot_op( struct expr *opnd1, struct expr *opnd2 )
1970 /**************************************************************/
1971 {
1972     /* this code needs cleanup! some stuff is obsolete. */
1973 
1974     DebugMsg1(("dot_op: op1-op2 kind=%d/%d value=%u/%u sym=%s-%s type=%s-%s mbr=%s-%s\n",
1975                opnd1->kind, opnd2->kind,
1976                opnd1->value, opnd2->value,
1977                opnd1->sym  ? opnd1->sym->name  : "NULL",
1978                opnd2->sym  ? opnd2->sym->name  : "NULL",
1979                opnd1->type ? opnd1->type->name : "NULL",
1980                opnd2->type ? opnd2->type->name : "NULL",
1981                opnd1->mbr  ? opnd1->mbr->name  : "NULL",
1982                opnd2->mbr  ? opnd2->mbr->name  : "NULL" ));
1983 
1984     /*
1985      * The formats allowed are:
1986      *        [register]      . (type) constant
1987      *        label           . (type) constant
1988      *        (type) constant . (type) constant
1989      *
1990      * with OPTION OLDSTRUCTS:
1991      *        [register]      . address
1992      *        address         . address
1993      */
1994 
1995     if( check_direct_reg( opnd1, opnd2 ) == ERROR ) {
1996         DebugMsg(("dot_op: error direct register\n"));
1997         return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
1998     }
1999 
2000     /* v2.08: remove EXPR_REG variants */
2001     if ( opnd1->kind == EXPR_REG )
2002         opnd1->kind = EXPR_ADDR;
2003     if ( opnd2->kind == EXPR_REG )
2004         opnd2->kind = EXPR_ADDR;
2005 
2006     /* forward ref to a struct: [reg].<struct> */
2007     if ( opnd2->sym && opnd2->sym->state == SYM_UNDEFINED && Parse_Pass == PASS_1 ) {
2008         DebugMsg(("dot_op: forward reference %s, replaced by null struct type\n", opnd2->sym->name ));
2009         if ( !nullstruct )
2010             nullstruct = CreateTypeSymbol( NULL, "", FALSE );
2011         opnd2->type = nullstruct;
2012         opnd2->is_type = TRUE; /* v2.10: added */
2013         opnd2->sym = NULL;
2014         opnd2->kind = EXPR_CONST;
2015     }
2016 
2017     if( check_same( opnd1, opnd2, EXPR_ADDR ) ) {
2018 
2019         DebugMsg1(("dot_op, ADDR - ADDR, t1-t2 memtype=%X-%X sym=%s-%s\n",
2020                    opnd1->mem_type, opnd2->mem_type,
2021                    opnd1->sym  ? opnd1->sym->name  : "NULL",
2022                    opnd2->sym  ? opnd2->sym->name  : "NULL" ));
2023 
2024 #if 1 /* v2.05: error */
2025         if ( opnd2->mbr == NULL && !ModuleInfo.oldstructs ) {
2026             DebugMsg(("dot_op: error, mbr 2 is NULL\n"));
2027             return( struct_field_error( opnd1 ) );
2028         }
2029 #endif
2030         if ( index_connect( opnd1, opnd2 ) == ERROR )
2031             return( ERROR );
2032 
2033         if( opnd2->sym != NULL ) {
2034             if( opnd1->sym != NULL &&
2035                 opnd1->sym->state != SYM_UNDEFINED &&
2036                 opnd2->sym->state != SYM_UNDEFINED ) {
2037                 DebugMsg(("dot_op: error, two relocatable labels: %s - %s \n", opnd1->sym->name, opnd2->sym->name ));
2038                 return( fnEmitErr( CANNOT_ADD_TWO_RELOCATABLE_LABELS ) );
2039             }
2040             opnd1->label_tok = opnd2->label_tok;
2041             opnd1->sym = opnd2->sym;
2042         }
2043         if( opnd2->mbr != NULL ) {
2044             opnd1->mbr = opnd2->mbr;
2045         }
2046         opnd1->value += opnd2->value;
2047         if( opnd1->explicit == FALSE ) {
2048             opnd1->mem_type = opnd2->mem_type;
2049         }
2050         if ( opnd2->type )
2051             opnd1->type = opnd2->type;
2052 
2053     } else if( ( opnd1->kind == EXPR_CONST ) && ( opnd2->kind == EXPR_ADDR ) ) {
2054 
2055         DebugMsg1(("dot_op, CONST - ADDR: t1-t2 memtype=%Xh-%Xh istype=%u-%u\n",
2056                    opnd1->mem_type, opnd2->mem_type, opnd1->is_type, opnd2->is_type ));
2057         /* v2.08 added (copied from branch EXPR_ADDR-EXPR_REG )*/
2058         if ( opnd1->is_type && opnd1->type ) {
2059             opnd2->assumecheck = FALSE;
2060             opnd1->llvalue = 0;  /* v2.08: this was previously done in get_operand() */
2061         }
2062 #if 1 /* v2.05: error */
2063         /* <structname>.<member>[<index_reg>] is ALWAYS ok! */
2064         if ( ( !ModuleInfo.oldstructs ) && ( opnd1->is_type == FALSE && opnd1->mbr == NULL ) )
2065             return( struct_field_error( opnd1 ) );
2066 #endif
2067         /* for TYPE.xxx, return offset instead of size */
2068         if ( opnd1->mbr && opnd1->mbr->state == SYM_TYPE )
2069             opnd1->llvalue = opnd1->mbr->offset;
2070         opnd2->indirect |= opnd1->indirect;
2071         opnd2->llvalue += opnd1->llvalue;
2072         DebugMsg1(("dot_op, CONST - ADDR, t1.type=%X (%s), t2.type=%X (%s)\n",
2073                    opnd1->type,
2074                    opnd1->type ? opnd1->type->name : "",
2075                    opnd2->type,
2076                    opnd2->type ? opnd2->type->name : "" ));
2077         /* v2.06: added. test case: INVOKE struct.mbr[edx] ( mbr has a type ) */
2078         if ( opnd2->mbr )
2079             opnd1->type = opnd2->type;
2080         TokenAssign( opnd1, opnd2 );
2081 
2082     } else if( ( opnd1->kind == EXPR_ADDR ) && ( opnd2->kind == EXPR_CONST ) ) {
2083 
2084         DebugMsg1(("dot_op, ADDR - CONST: t1-t2 memtype=%Xh-%Xh t1.explicit=%u\n",
2085                    opnd1->mem_type, opnd2->mem_type, opnd1->explicit ));
2086 
2087         /* v2.08: changed to catch [ebx].<num> or [ebx].<simple type> */
2088         //if ( (!ModuleInfo.oldstructs) && opnd2->type == NULL && opnd2->mbr == NULL ) {
2089         if ( (!ModuleInfo.oldstructs) && ( opnd2->type == NULL || opnd2->is_type == FALSE ) && opnd2->mbr == NULL ) {
2090             DebugMsg(("dot_op: error, constant or simple type after dot\n"));
2091             return( struct_field_error( opnd1 ) );
2092         }
2093 
2094         /* v2.08 added (copied from branch EXPR_ADDR-EXPR_REG )*/
2095         if ( opnd2->is_type && opnd2->type ) {
2096             opnd1->assumecheck = FALSE;
2097             /* v2.12: problem: see dotop6.asm */
2098             //opnd2->llvalue = 0;  /* v2.08: this was previously done in get_operand() */
2099             opnd2->llvalue -= opnd2->type->total_size;  /* v2.12: adjust for type's size only */
2100             DebugMsg1(("dot_op, ADDR - CONST, t2.type.total_size=%u, new t2->value=%u\n", opnd2->type->total_size, opnd2->value ));
2101         }
2102         /* for [var].TYPE | STRUCT_FIELD, use offset instead of size */
2103         if ( opnd2->mbr && opnd2->mbr->state == SYM_TYPE )
2104             opnd2->llvalue = opnd2->mbr->offset;
2105         opnd1->llvalue += opnd2->llvalue;
2106         opnd1->mem_type = opnd2->mem_type; /* v2.08: now always done */
2107         if( opnd2->mbr != NULL ) {
2108             opnd1->mbr = opnd2->mbr;
2109 #if 0 /* v2.07 */
2110             /* temp. disabled in v1.95, test case:
2111              * mov eax,(<struct> ptr [ebx]).F1
2112              * however: mov ax, word ptr var[bx].F1 ???
2113              * the condition can't be disabled. Instead the PTR
2114              * operator must NOT set the explicit flag if the
2115              * first operand is a structure.
2116              */
2117             if( opnd1->explicit == FALSE )
2118 #endif
2119                 //opnd1->mem_type = opnd2->mem_type; /* v2.08: obsolete */
2120         }
2121 
2122         DebugMsg1(("dot_op, ADDR - CONST, t1.type=%X (%s), t2.type=%X (%s)\n",
2123                    opnd1->type,
2124                    opnd1->type ? opnd1->type->name : "",
2125                    opnd2->type,
2126                    opnd2->type ? opnd2->type->name : "" ));
2127 #if 0 /* v1.96 */
2128         if ( opnd2->type )
2129 #endif
2130             opnd1->type = opnd2->type;
2131 
2132     } else if ( opnd1->kind == EXPR_CONST && opnd2->kind == EXPR_CONST ) {
2133 
2134         DebugMsg1(("dot_op, CONST - CONST, t1-t2 value=%u-%u, memtype=%Xh-%Xh istype=%u-%u\n",
2135                    opnd1->value, opnd2->value, opnd1->mem_type, opnd2->mem_type, opnd1->is_type, opnd2->is_type));
2136         if ( opnd2->mbr == NULL && !ModuleInfo.oldstructs ) {
2137             DebugMsg(("dot_op: error, opnd2.mbr=NULL\n" ));
2138             return( struct_field_error( opnd1 ) );
2139         }
2140         if ( opnd1->type != NULL ) {
2141             /*
2142              * v2.06: the token1 value must NOT be ignored if the token is a
2143              * struct member: mov ax, [offset] <struct>.<mbr>.<mbr>
2144              */
2145             if ( opnd1->mbr != NULL )
2146                 opnd1->llvalue += opnd2->llvalue;
2147             else {
2148                 /* old token is a type - the value (=size) is ignored then. */
2149                 opnd1->llvalue = opnd2->llvalue;
2150             }
2151             opnd1->mbr = opnd2->mbr;
2152             /* v2.0: copy mem_type (test case: mov ds:[<struct>.<mbr>], 123) */
2153             opnd1->mem_type = opnd2->mem_type;
2154             /* v2.05: removed, it's still a type constant */
2155             //opnd1->is_type = FALSE;
2156             opnd1->is_type = opnd2->is_type;
2157             /* either clear <type> or use the renewed one */
2158             if ( opnd1->type != opnd2->type )
2159                 opnd1->type = opnd2->type;
2160             else
2161                 opnd1->type = NULL;
2162         } else {
2163             /* old token is NOT a type */
2164             /* most likely a number or an MT_ABS symbol! */
2165             /* so the TOTAL of both constants is required */
2166             opnd1->llvalue += opnd2->llvalue;
2167             opnd1->mbr = opnd2->mbr;
2168             opnd1->mem_type = opnd2->mem_type;
2169         }
2170     } else {
2171         DebugMsg(("dot_op: error, unknown kind combination, opnd1->kind=%d, opnd2->kind=%d\n", opnd1->kind, opnd2->kind ));
2172         return( struct_field_error( opnd1 ) );
2173     }
2174     return( NOT_ERROR );
2175 }
2176 
colon_op(struct expr * opnd1,struct expr * opnd2)2177 static ret_code colon_op( struct expr *opnd1, struct expr *opnd2 )
2178 /****************************************************************/
2179 {
2180     int_32              temp;
2181     struct asym         *sym;
2182     /*
2183      * The only formats allowed are:
2184      *     seg_reg : const
2185      *     seg_reg : address
2186      *     seg_label : const
2187      *     seg_label : address
2188      *     ( seg_label = segment or group symbol )
2189      *     inside square brackets, seg_reg : register is not accepted
2190      *     if Masm-syntax is on.
2191      */
2192     DebugMsg1(("colon_op: t1-t2 kind=%d/%d type=%s-%s is_type=%u-%u\n",
2193                opnd1->kind, opnd2->kind,
2194                opnd1->type ? opnd1->type->name : "NULL",
2195                opnd2->type ? opnd2->type->name : "NULL",
2196                opnd1->is_type, opnd2->is_type ));
2197     if( opnd2->override != NULL ) {
2198         /* v2.07a: was too rigid */
2199         if ( ( opnd1->kind == EXPR_REG && opnd2->override->token == T_REG ) ||
2200             ( opnd1->kind == EXPR_ADDR && opnd2->override->token == T_ID ) ) {
2201             DebugMsg(("colon_op: multiple override=%s\n", opnd2->override->string_ptr ));
2202             return( fnEmitErr( MULTIPLE_OVERRIDES ) );
2203         }
2204     }
2205     switch ( opnd2->kind ) {
2206     case EXPR_REG:
2207         /* v2.05: register as second operand must be enclosed in [] */
2208         if ( opnd2->indirect == FALSE ) {
2209             DebugMsg(("colon_op: register after : not enclosed in []\n" ));
2210             return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2211         }
2212         break;
2213     case EXPR_FLOAT:
2214         return( fnEmitErr( REAL_OR_BCD_NUMBER_NOT_ALLOWED ) );
2215     }
2216 
2217     if( opnd1->kind == EXPR_REG ) {
2218 
2219         /* the item before the ':' must be a single register */
2220         if( opnd1->idx_reg != NULL ) {
2221             DebugMsg(("colon_op: register before ':' has idx_reg set!?\n"));
2222             return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2223         }
2224         /* segment override inside bracket not allowed with -Zne.
2225          * [ds:0] is ok, but [ds:ebx] is rejected.
2226          */
2227         /* v2.08: test moved here from get_operand() */
2228         /* v2.10: regression in v2.08-2.09: check was way too simple.
2229          * problem: indirect-flag isn't set for segment regs (anymore?).
2230          * error check moved back to get_operand().
2231          */
2232 #if 0
2233         if ( Options.strict_masm_compat ) {
2234             return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2235         }
2236 #endif
2237         /* make sure first operand is a segment register */
2238         temp = opnd1->base_reg->tokval;
2239         if ( ( GetValueSp( temp ) & OP_SR ) == 0 ) {
2240             return( fnEmitErr( SEGMENT_GROUP_OR_SEGREG_EXPECTED ) );
2241         }
2242 
2243         opnd2->override = opnd1->base_reg;
2244         opnd2->indirect |= opnd1->indirect;
2245 
2246         if ( opnd2->kind == EXPR_CONST ) {
2247             opnd2->kind = EXPR_ADDR;
2248             /* v2.05: type flag cleared HERE, not in dot_op()
2249              * v2.05rc17 problem: mov es:byte ptr <var>,0
2250              * so the flag isn't cleared at all now.
2251              */
2252             //opnd2->is_type = FALSE;
2253         }
2254 
2255         if( opnd1->explicit ) {
2256             opnd2->explicit = opnd1->explicit;
2257             opnd2->mem_type = opnd1->mem_type;
2258             opnd2->Ofssize  = opnd1->Ofssize;
2259         }
2260         TokenAssign( opnd1, opnd2 );
2261 
2262         /*
2263          * currently the <type> token isn't copied by
2264          * TokenAssign (which is probably just for historical reasons).
2265          * So copy it manually!
2266          * v1.95: only copy if it is != NULL!
2267          * Testcase: (<type> ptr DS:[0]).<struct_field> ...
2268          * In this case the DS:[] will clear the <type>, as a result
2269          * the dot operator won't have a valid assume and the code fails.
2270          */
2271         if ( opnd2->type )
2272             opnd1->type = opnd2->type;
2273 
2274     } else if( opnd1->kind == EXPR_ADDR &&
2275               /* opnd2->kind == EXPR_ADDR && */
2276               opnd1->override == NULL &&
2277               opnd1->instr == EMPTY &&
2278               opnd1->value == 0 &&
2279               opnd1->sym &&
2280               opnd1->base_reg == NULL &&
2281               opnd1->idx_reg == NULL ) {
2282 
2283         sym = opnd1->sym;
2284 
2285         if( sym->state == SYM_GRP || sym->state == SYM_SEG ) {
2286             opnd2->kind = EXPR_ADDR;
2287             opnd2->override = opnd1->label_tok;
2288             opnd2->indirect |= opnd1->indirect;
2289             if( opnd1->explicit ) {
2290                 opnd2->explicit = opnd1->explicit;
2291                 opnd2->mem_type = opnd1->mem_type;
2292                 opnd2->Ofssize  = opnd1->Ofssize;
2293             }
2294             TokenAssign( opnd1, opnd2 );
2295             opnd1->type = opnd2->type;
2296 
2297         } else if( Parse_Pass > PASS_1 || sym->state != SYM_UNDEFINED ) {
2298             DebugMsg(("colon_op error 4\n"));
2299             return( fnEmitErr( SEGMENT_GROUP_OR_SEGREG_EXPECTED ) );
2300         }
2301     } else {
2302         DebugMsg(("colon_op error 5\n"));
2303         return( fnEmitErr( SEGMENT_GROUP_OR_SEGREG_EXPECTED ) );
2304     }
2305     return( NOT_ERROR );
2306 }
2307 
positive_op(struct expr * opnd1,struct expr * opnd2)2308 static ret_code positive_op( struct expr *opnd1, struct expr *opnd2 )
2309 /*******************************************************************/
2310 {
2311     DebugMsg1(("positive_op: value=%" I64_SPEC "X high=%" I64_SPEC "X\n", opnd2->llvalue, opnd2->hlvalue ));
2312     /*
2313      * The formats allowed are:
2314      *        + constant
2315      *        + float
2316      * v2.06: unlike the other operators unary + will
2317      * handle 128-bit values (needed for TBYTE integers)
2318      */
2319 
2320     MakeConst( opnd2 );
2321     if( opnd2->kind == EXPR_CONST ) {
2322         opnd1->kind = EXPR_CONST;
2323         opnd1->llvalue = opnd2->llvalue;
2324         opnd1->hlvalue = opnd2->hlvalue; /* v2.06: added */
2325     } else if( opnd2->kind == EXPR_FLOAT ) {
2326         opnd1->kind = EXPR_FLOAT;
2327         opnd1->float_tok = opnd2->float_tok;
2328         opnd1->negative = opnd2->negative;
2329     } else {
2330         DebugMsg(("positive_op: error 1\n"));
2331         return( fnEmitErr( CONSTANT_EXPECTED ) );
2332     }
2333     return( NOT_ERROR );
2334 }
2335 
negative_op(struct expr * opnd1,struct expr * opnd2)2336 static ret_code negative_op( struct expr *opnd1, struct expr *opnd2 )
2337 /*******************************************************************/
2338 {
2339     DebugMsg1(("negative_op: value=%" I64_SPEC "X high=%" I64_SPEC "X\n", opnd2->llvalue, opnd2->hlvalue ));
2340     /*
2341      * The formats allowed are:
2342      *        - constant
2343      *        - float
2344      */
2345 
2346     MakeConst( opnd2 );
2347     if( opnd2->kind == EXPR_CONST ) {
2348         opnd1->kind = EXPR_CONST;
2349         opnd1->llvalue = -opnd2->llvalue;
2350         /* v2.06: the unary '-' operator is to work with
2351          * magnitudes > 64-bit. Current implementation is
2352          * a bit hackish.
2353          */
2354         if ( opnd2->hlvalue )
2355             opnd1->hlvalue = -opnd2->hlvalue - 1;
2356         opnd1->negative = 1 - opnd2->negative; /* ??? supposed to be used for EXPR_FLOAT only! */
2357     } else if( opnd2->kind == EXPR_FLOAT ) {
2358         opnd1->kind = EXPR_FLOAT;
2359         opnd1->float_tok = opnd2->float_tok;
2360         opnd1->negative = 1 - opnd2->negative;
2361     } else {
2362         DebugMsg(("negative_op: unexpected opnd2.kind=%d\n", opnd2->kind ));
2363         return( fnEmitErr( CONSTANT_EXPECTED ) );
2364     }
2365     return( NOT_ERROR );
2366 }
2367 
2368 /* v2.07: moved out from get_operand, case T_REG
2369  * this function is now called from calculate() only.
2370  */
CheckAssume(struct expr * opnd)2371 static void CheckAssume( struct expr *opnd )
2372 /******************************************/
2373 {
2374     struct asym *sym = NULL;
2375 
2376     DebugMsg1(( "CheckAssume: enter\n" ));
2377 #if 1 /* v2.10: see regression test ptr2.asm */
2378     if ( opnd->explicit ) { /* perhaps check mem_type instead of explicit */
2379         if ( opnd->type && opnd->type->mem_type == MT_PTR ) {
2380             DebugMsg1(( "CheckAssume(%s, MT_PTR type=>%s< )\n", opnd->type->name ));
2381             if ( opnd->type->is_ptr == 1 ) { /* dereference only if indirection is 1 */
2382                 opnd->mem_type = opnd->type->ptr_memtype;
2383                 opnd->type = opnd->type->target_type;
2384                 return; /* ignore assumes in this case */
2385             }
2386         }
2387     }
2388 #endif
2389     /* in jwasm < v2.10, the idx_reg had higher priority than base_reg.
2390      * However, the base reg is supposed to have a higher priority.
2391      * This wasn't fully clear, because in Masm 6, if no register has
2392      * a scaling factor, the second one becomes base - something that
2393      * JWasm didn't do, unless -Zg was set.
2394      * Since v2.10, JWasm behaves like Masm v6+: base and index registers
2395      * are swapped, and assume for base has higher priority than assume for
2396      * index.
2397      */
2398     if ( opnd->base_reg ) {
2399         sym = GetStdAssumeEx( opnd->base_reg->bytval );
2400     }
2401     if (!sym && opnd->idx_reg ) {
2402         sym = GetStdAssumeEx( opnd->idx_reg->bytval );
2403     }
2404     if ( sym ) {
2405         DebugMsg1(( "CheckAssume(%s, type=>%s<, mbr=>%s<): assume=%s [memtype=%X isptr=%u type=%s target_type=%s ptr_memt=%X]\n",
2406                    GetResWName( ( opnd->idx_reg ? opnd->idx_reg->tokval : opnd->base_reg->tokval ), NULL ),
2407                    opnd->type ? opnd->type->name : "NULL",
2408                    opnd->mbr ? opnd->mbr->name : "NULL",
2409                    sym->name, sym->mem_type, sym->is_ptr,
2410                    sym->type ? sym->type->name : "NULL",
2411                    sym->target_type ? sym->target_type->name : "NULL",
2412                    sym->ptr_memtype ));
2413         /* v2.08: skip ASSUMEd type if type or mbr is set */
2414         //if ( opnd->type || opnd->mbr )
2415         //    return;
2416         /* skip "alias" types */
2417         /* v2.05: obsolete */
2418         //for ( ; sym->type; sym = sym->type );
2419         /* v2.05: new */
2420         if ( sym->mem_type == MT_TYPE )
2421             opnd->type = sym->type;
2422         else if ( sym->is_ptr == 1 ) { /* v2.10: only dereference if indirection is 1 */
2423             opnd->type = sym->target_type;
2424             if ( sym->target_type )
2425                 opnd->mem_type = sym->target_type->mem_type;
2426             else
2427                 opnd->mem_type = sym->ptr_memtype;
2428         }
2429     }
2430 }
2431 
2432 /* get floating-point register index */
2433 
check_streg(struct expr * opnd1,struct expr * opnd2)2434 static ret_code check_streg( struct expr *opnd1, struct expr *opnd2 )
2435 /*******************************************************************/
2436 {
2437     if ( opnd1->scale > 0 ) {
2438         return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2439     }
2440     opnd1->scale++; /* make sure there's only ONE bracket pair */
2441     if ( opnd2->kind != EXPR_CONST ) {
2442         return( fnEmitErr( INVALID_COPROCESSOR_REGISTER ) );
2443     }
2444     opnd1->st_idx = opnd2->value;
2445     return( NOT_ERROR );
2446 }
2447 
2448 /* v2.10: comparison of type operands moved from calculate() to this function. */
2449 
cmp_types(struct expr * opnd1,struct expr * opnd2,int trueval)2450 static void cmp_types( struct expr *opnd1, struct expr *opnd2, int trueval )
2451 /**************************************************************************/
2452 {
2453     struct asym *type1;
2454     struct asym *type2;
2455 
2456     /* v2.10: special handling of pointer types. */
2457     //if ( opnd1->mem_type == MT_PTR && opnd2->mem_type == MT_PTR && opnd1->type && opnd2->type ) {
2458     if ( opnd1->mem_type == MT_PTR && opnd2->mem_type == MT_PTR ) {
2459         /**/myassert( ( opnd1->type || opnd1->type_tok ) && ( opnd2->type || opnd2->type_tok ) );
2460         type1 = ( opnd1->type ? opnd1->type : SymSearch( opnd1->type_tok->string_ptr ) );
2461         type2 = ( opnd2->type ? opnd2->type : SymSearch( opnd2->type_tok->string_ptr ) );
2462         //opnd1->value64 = ( ( type1->is_ptr == type2->is_ptr &&
2463         opnd1->value64 = ( ( type1->is_ptr == type2->is_ptr &&
2464                             type1->ptr_memtype == type2->ptr_memtype &&
2465                             type1->target_type == type2->target_type ) ? trueval : ~trueval );
2466         DebugMsg1(("cmp_types: MT_PTR-MT_PTR is_ptr=%u-%u ptr_memtype=%X-%X target_type=%X-%X\n",
2467                    type1->is_ptr, type2->is_ptr,
2468                    type1->ptr_memtype, type2->ptr_memtype,
2469                    type1->target_type, type2->target_type ));
2470     } else {
2471         DebugMsg1(("cmp_types: memtype=%X-%X type=%X-%X\n",
2472                    opnd1->mem_type, opnd2->mem_type, opnd1->type, opnd2->type ));
2473         /* v2.09: include type member in comparison, but ignore typedef types */
2474         if ( opnd1->type && opnd1->type->typekind == TYPE_TYPEDEF && opnd1->type->is_ptr == 0 )
2475             opnd1->type = NULL;
2476         if ( opnd2->type && opnd2->type->typekind == TYPE_TYPEDEF && opnd2->type->is_ptr == 0 )
2477             opnd2->type = NULL;
2478         opnd1->value64 = ( ( opnd1->mem_type == opnd2->mem_type &&
2479                             opnd1->type == opnd2->type ) ? trueval : ~trueval );
2480     }
2481 }
2482 
calculate(struct expr * opnd1,struct expr * opnd2,const struct asm_tok * oper)2483 static ret_code calculate( struct expr *opnd1, struct expr *opnd2, const struct asm_tok *oper )
2484 /*********************************************************************************************/
2485 /* Performs operation <oper> with operands <opnd1> and <opnd2>.
2486  * the result will be returned in <opnd1>.
2487  * <oper> points to the item in tokenarray[] that contains the operator.
2488  * possible operators:
2489  *  T_OP_BRACKET       is (virtually) an alias for '+'
2490  *  T_OP_SQ_BRACKET    is (virtually) an alias for '+'
2491  *  '+' (unary + binary )
2492  *  '-' (unary + binary )
2493  *  '*'
2494  *  '/'
2495  *  T_DOT
2496  *  T_COLON
2497  *  T_BINARY_OPERATOR ( PTR, MOD, GE, GT, LE, GT, EQ, NE, also AND, OR, XOR, SHL, SHR )
2498  *  T_UNARY_OPERATOR ( OFFSET, SHORT, ... , also NOT )
2499  *
2500  * to be done: the code can be simplified because currently
2501  *             expression type is set to EXPR_REG when a
2502  *             register was found - even if it is inside [].
2503  *             A reg inside [] should ALWAYS give EXPR_ADDR!
2504  */
2505 {
2506     int_32              temp;
2507     struct asym         *sym;
2508     char                *name;
2509 
2510     /* avoid to use the <string> member once it's part of an expression!
2511      * the <value> member is the one to be used then.
2512      * test case: db "a"+80h
2513      * v2.08: first: this is too early; second: the current operand is opnd2.
2514      * third: the space is also used by float_tok member, which cannot be cleared.
2515      * probably the best solution - at calculate()'s end:
2516      * if ( opnd1->kind == EXPR_CONST ) opnd1->quoted_string = NULL;
2517      */
2518     opnd1->quoted_string = NULL;
2519 
2520     /* v2.11: added check to ensure constant fits in 64-bits */
2521     if ( opnd2->hlvalue ) {
2522         /* opattr and unary +/- are ok, they can handle 128-bits */
2523         if ( opnd2->is_opattr || ( ( oper->token == '+' || oper->token == '-' ) && oper->specval == UNARY_PLUSMINUS ) )
2524             ;
2525         else {
2526             DebugMsg(("%u calculate(%s): value too large\n", evallvl, oper->string_ptr ));
2527             return( fnEmitErr( CONSTANT_VALUE_TOO_LARGE_EX, opnd2->hlvalue, opnd2->value64 ) );
2528         }
2529     }
2530 
2531     switch( oper->token ) {
2532     case T_OP_SQ_BRACKET:
2533         /* v2.07: the ASSUMEs are now checked only when operator [] is done.
2534          * this is compatible with Masm:
2535          *   assume ebx:ptr <struct>
2536          *   mov eax, [ebx.<member>]             ;is to fail
2537          *   mov eax, [ebx.<struct>.<member>]    ;is to be ok
2538          * previously both variants were accepted by jwasm.
2539          */
2540         if ( opnd2->assumecheck == TRUE ) {
2541             opnd2->assumecheck = FALSE;   /* check ONE time only! */
2542             if ( opnd1->sym == NULL ) /* v2.10: added; see assume10.asm */
2543                 CheckAssume( opnd2 );
2544         }
2545 
2546         if ( opnd1->kind == EXPR_EMPTY ) {
2547             DebugMsg1(("%u calculate(%s): single item\n", evallvl, oper->string_ptr ));
2548             TokenAssign( opnd1, opnd2 );
2549             opnd1->type = opnd2->type;
2550             if ( opnd1->is_type && opnd1->kind == EXPR_CONST )
2551                 opnd1->is_type = 0;
2552             break;
2553         }
2554 
2555         /* v2.03: make JWasm reject syntax variants
2556          * "mov eax, DWORD [EBX]"
2557          * "mov eax, DWORD [var_name]"
2558          * variants still valid:
2559          * "mov eax, DWORD [WORD]"
2560          * "mov eax, DWORD [4]"
2561          * "mov eax, [DWORD][EBX]"
2562          */
2563         /* v2.08: structure/union names are ok: mov eax, S1[ebx] */
2564         //if ( opnd1->is_type == TRUE &&
2565         if ( opnd1->is_type == TRUE && opnd1->type == NULL &&
2566             (opnd2->kind == EXPR_ADDR || opnd2->kind == EXPR_REG ) ) {
2567             DebugMsg(("calculate(%s): incompatible usage of (simple) type\n", oper->string_ptr ));
2568             return( fnEmitErr( SYNTAX_ERROR_IN_EXPRESSION ) );
2569         }
2570 
2571         /* v2.08: moved here from get_operand() */
2572         if ( opnd1->base_reg && opnd1->base_reg->tokval == T_ST )
2573             return( check_streg( opnd1, opnd2 ) );
2574 
2575 #ifdef DEBUG_OUT
2576         if ( plus_op( opnd1, opnd2 ) == ERROR )
2577             return( ERROR );
2578         break;
2579 #else
2580         return( plus_op( opnd1, opnd2 ) );
2581 #endif
2582     case T_OP_BRACKET:
2583 
2584         if ( opnd1->kind == EXPR_EMPTY ) {
2585             DebugMsg1(("%u calculate(%s): single item\n", evallvl, oper->string_ptr ));
2586             TokenAssign( opnd1, opnd2 );
2587             opnd1->type = opnd2->type;
2588             break;
2589         }
2590         /* v2.03: make JWasm reject syntax variants
2591          * "mov eax, DWORD (<label>)"
2592          */
2593         if ( opnd1->is_type == TRUE && opnd2->kind == EXPR_ADDR ) {
2594             DebugMsg(("calculate(%s): incompatible usage of (simple) type\n", oper->string_ptr ));
2595             return( fnEmitErr( SYNTAX_ERROR_IN_EXPRESSION ) );
2596         }
2597 
2598         /* v2.08: moved here from get_operand() */
2599         if ( opnd1->base_reg && opnd1->base_reg->tokval == T_ST )
2600             return( check_streg( opnd1, opnd2 ) );
2601 
2602         DebugMsg1(("calculate(%s): calling plus_op()\n", oper->string_ptr ));
2603 #ifdef DEBUG_OUT
2604         if ( plus_op( opnd1, opnd2 ) == ERROR )
2605             return( ERROR );
2606         break;
2607 #else
2608         return( plus_op( opnd1, opnd2 ) );
2609 #endif
2610     case '+':
2611         if ( oper->specval == UNARY_PLUSMINUS ) /* unary op? */
2612             return( positive_op( opnd1, opnd2 ) );
2613 #ifdef DEBUG_OUT
2614         if ( plus_op( opnd1, opnd2 ) == ERROR )
2615             return( ERROR );
2616         break;
2617 #else
2618         return( plus_op( opnd1, opnd2 ) );
2619 #endif
2620     case '-':
2621         if ( oper->specval == UNARY_PLUSMINUS ) /* unary op? */
2622             return( negative_op( opnd1, opnd2 ) );
2623 #ifdef DEBUG_OUT
2624         if ( minus_op( opnd1, opnd2 ) == ERROR )
2625             return( ERROR );
2626         break;
2627 #else
2628         return( minus_op( opnd1, opnd2 ) );
2629 #endif
2630     case T_DOT:
2631 #ifdef DEBUG_OUT
2632         if ( dot_op( opnd1, opnd2 ) == ERROR )
2633             return( ERROR );
2634         break;
2635 #else
2636         return( dot_op( opnd1, opnd2 ) );
2637 #endif
2638     case T_COLON:
2639 #ifdef DEBUG_OUT
2640         if ( colon_op( opnd1, opnd2 ) == ERROR )
2641             return( ERROR );
2642         break;
2643 #else
2644         return( colon_op( opnd1, opnd2 ) );
2645 #endif
2646     case '*':
2647         /*
2648          * The only formats allowed are:
2649          *        constant * constant
2650          *        register * scaling factor ( 1, 2, 4 or 8 )
2651          *                   386 only
2652          */
2653         DebugMsg1(("calculate(*): kind=%d/%d value=%" I64_SPEC "d-%" I64_SPEC "d mbr=%X-%X\n",
2654                    opnd1->kind,    opnd2->kind,
2655                    opnd1->value64, opnd2->value64,
2656                    opnd1->mbr,     opnd2->mbr ));
2657 
2658         MakeConst( opnd1 );
2659         MakeConst( opnd2 );
2660 
2661         if( check_same( opnd1, opnd2, EXPR_CONST ) ) {
2662             opnd1->llvalue *= opnd2->llvalue;
2663         } else if( check_both( opnd1, opnd2, EXPR_REG, EXPR_CONST ) ) {
2664             if( check_direct_reg( opnd1, opnd2 ) == ERROR ) {
2665                 DebugMsg(("calculate(*) error direct register\n"));
2666                 return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2667             }
2668             /* scaling factor */
2669             if( opnd2->kind == EXPR_REG ) {
2670                 /* scale * reg */
2671                 opnd1->idx_reg = opnd2->base_reg;
2672                 opnd1->scale = opnd1->value;
2673                 opnd1->value = 0;
2674                 //opnd2->base_reg = NULL;
2675             } else {
2676                 /* reg * scale */
2677                 opnd1->idx_reg = opnd1->base_reg;
2678                 opnd1->scale = opnd2->value;
2679             }
2680             /* v2.08: check 0 (the default value) here */
2681             if ( opnd1->scale == 0 ) {
2682                 return( fnEmitErr( SCALE_FACTOR_MUST_BE_1_2_4_OR_8 ) );
2683             }
2684 
2685             opnd1->base_reg = NULL;
2686             opnd1->indirect = TRUE;
2687             opnd1->kind = EXPR_ADDR;
2688         } else {
2689             DebugMsg(("calculate(*) error 2\n"));
2690             return( ConstError( opnd1, opnd2 ) );
2691         }
2692         break;
2693     case '/':
2694         /*
2695          * The only formats allowed are:
2696          *        constant / constant
2697          */
2698         DebugMsg1(("calculate(/): t1-t2 kind %u-%u values %" I64_SPEC "d-%" I64_SPEC "d\n",
2699                    opnd1->kind,    opnd2->kind,
2700                    opnd1->value64, opnd2->value64 ));
2701         MakeConst( opnd1 );
2702         MakeConst( opnd2 );
2703 
2704         if( check_same( opnd1, opnd2, EXPR_CONST ) == FALSE ) {
2705             DebugMsg(("calculate(/) error 1\n"));
2706             return( ConstError( opnd1, opnd2 ) );
2707         }
2708 
2709         if ( opnd2->llvalue == 0 ) {
2710             DebugMsg(("calculate(/) error 2\n"));
2711             return( fnEmitErr( DIVIDE_BY_ZERO_IN_EXPR ) );
2712         }
2713 
2714         opnd1->value64 /= opnd2->value64;
2715         break;
2716     case T_BINARY_OPERATOR:
2717         DebugMsg1(("calculate(%s [T_BINARY_OPERATOR] ): t1-t2 kind %d/%d memtype %X-%X sym %s-%s type %s-%s\n",
2718                    oper->string_ptr,
2719                    opnd1->kind, opnd2->kind,
2720                    opnd1->mem_type, opnd2->mem_type,
2721                    opnd1->sym  ? opnd1->sym->name  : "NULL",
2722                    opnd2->sym  ? opnd2->sym->name  : "NULL",
2723                    opnd1->type ? opnd1->type->name : "NULL",
2724                    opnd2->type ? opnd2->type->name : "NULL" ));
2725 
2726         if ( oper->tokval == T_PTR ) {
2727             if ( opnd1->is_type == FALSE ) {
2728                 if ( opnd1->sym && opnd1->sym->state == SYM_UNDEFINED ) {
2729                     CreateTypeSymbol( opnd1->sym, NULL, TRUE );
2730                     opnd1->type = opnd1->sym;
2731                     opnd1->sym = NULL;
2732                     opnd1->is_type = TRUE;
2733                 } else {
2734                     DebugMsg(("calculate(PTR), error 1: t1 is_type == FALSE\n"));
2735                     return( fnEmitErr( INVALID_TYPE_EXPRESSION ) );
2736                 }
2737             }
2738             opnd2->explicit = TRUE;
2739             /* v2.02: if operand is a register, make sure
2740              * that invalid combinations ("DWORD PTR AX") are flagged.
2741              *
2742              * v2.10: must also be checked inside []. However, it's
2743              * a problem to properly handle this case, since opnd->indirect
2744              * is just a flag.
2745              * Curr. hackish fix: to query state of assumecheck if indirect==TRUE.
2746              * Proposed "good" fix: change EXPR_REG to EXPR_ADDR in
2747              * CheckAssume(), that is, when the terminating  ']' was found.
2748              */
2749             //if ( opnd2->kind == EXPR_REG && opnd2->indirect == FALSE ) {
2750             if ( opnd2->kind == EXPR_REG && ( opnd2->indirect == FALSE || opnd2->assumecheck == TRUE ) ) {
2751                 temp = opnd2->base_reg->tokval;
2752                 /* for segment registers, both size 2 and 4 is ok.*/
2753                 if ( GetValueSp( temp ) & OP_SR ) {
2754                     if ( opnd1->value != 2 && opnd1->value != 4 ) {
2755                         DebugMsg(("calculate(PTR): segment register size (=2/4) doesn't match type size (=%u)\n", opnd1->value ));
2756                         return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2757                     }
2758                 } else if ( opnd1->value != SizeFromRegister( temp ) ) {
2759                     DebugMsg(("calculate(PTR): register size doesn't match type size; %u != %u\n", SizeFromRegister( temp ), opnd1->value ));
2760                     return( fnEmitErr( INVALID_USE_OF_REGISTER ) );
2761                 }
2762             } else if ( opnd2->kind == EXPR_FLOAT ) {
2763                 if ( !( opnd1->mem_type & MT_FLOAT ) ) {
2764                     DebugMsg(("calculate(PTR): type memtype=%Xh ( MT_FLOAT not set, although right op is FLOAT )\n", opnd1->mem_type ));
2765                     return( fnEmitErr( REAL_OR_BCD_NUMBER_NOT_ALLOWED ) );
2766                 }
2767             }
2768             opnd2->mem_type = opnd1->mem_type;
2769             opnd2->Ofssize  = opnd1->Ofssize;
2770             /* v2.04: added */
2771             if ( opnd2->is_type )
2772                 opnd2->value  = opnd1->value;
2773 
2774             /* todo: describe which case is handled here. How is the left
2775              * operand of PTR supposed to get an override? And why is
2776              * it necessary to change kind to EXPR_ADDR here? */
2777             if ( opnd1->override != NULL ) {
2778                 if ( opnd2->override == NULL )
2779                     opnd2->override = opnd1->override;
2780                 opnd2->kind = EXPR_ADDR;
2781             }
2782             //if ( opnd1->mbr )
2783             //    opnd2->mbr = opnd1->mbr;
2784             //if ( opnd1->sym )
2785             //    opnd2->sym = opnd1->sym;
2786             //opnd2->instr = opnd1->instr;
2787 
2788             /* note: member type isn't copied, IOW: value of opnd1->type is kept. */
2789             TokenAssign( opnd1, opnd2 );
2790             break;
2791         }
2792 
2793         MakeConst( opnd1 );
2794         MakeConst( opnd2 );
2795 
2796         if ( check_same( opnd1, opnd2, EXPR_CONST ) )
2797             ;
2798         /* if it's EQ, NE, LE [, ...], operands may be either constants
2799          or relocatable labels */
2800         else if ( oper->precedence == CMP_PRECEDENCE &&
2801                  opnd1->kind != EXPR_CONST ) {
2802             if ( opnd1->kind == EXPR_ADDR && opnd1->indirect == FALSE && opnd1->sym )
2803                 if ( opnd2->kind == EXPR_ADDR && opnd2->indirect == FALSE && opnd2->sym ) {
2804                     if ( MakeConst2( opnd1, opnd2 ) == ERROR ) {
2805                         DebugMsg(("calculate(%s) error 1\n", oper->string_ptr ));
2806                         return( ERROR );
2807                     }
2808                 } else {
2809                     DebugMsg(("calculate(%s) error 2, token2.kind=%d indirect=%u sym=%s\n",
2810                               oper->string_ptr, opnd2->kind, opnd2->indirect,
2811                               opnd2->sym ? opnd2->sym->name : "NULL" ));
2812                     return( fnEmitErr( OPERAND_MUST_BE_RELOCATABLE ) );
2813                 }
2814             else {
2815                 DebugMsg(("calculate(%s) error 3\n", oper->string_ptr ));
2816                 return( fnEmitErr( CONSTANT_OR_RELOCATABLE_LABEL_EXPECTED ) );
2817             }
2818         } else {
2819             DebugMsg(("calculate(%s) error 4\n", oper->string_ptr ));
2820             return( ConstError( opnd1, opnd2 ) );
2821         }
2822 
2823         DebugMsg1(("calculate(%s): values=%" I64_SPEC "d/%" I64_SPEC "d is_type=%u/%u memtypes=%X/%X\n", oper->string_ptr,
2824                    opnd1->value64, opnd2->value64, opnd1->is_type, opnd2->is_type, opnd1->mem_type, opnd2->mem_type  ));
2825         switch( oper->tokval ) {
2826         case T_EQ:
2827 #if 1 /* v2.03: added */
2828             /* if both operands are types, do a more comprehensive comparison! */
2829             if ( opnd1->is_type && opnd2->is_type ) {
2830                 cmp_types( opnd1, opnd2, -1 );
2831             } else
2832 #endif
2833             opnd1->value64 = ( opnd1->value64 == opnd2->value64 ? -1:0 );
2834             break;
2835         case T_NE:
2836 #if 1 /* v2.03: added */
2837             /* if both operands are types, do a more comprehensive comparison! */
2838             if ( opnd1->is_type && opnd2->is_type ) {
2839                 cmp_types( opnd1, opnd2, 0 );
2840             } else
2841 #endif
2842             opnd1->value64 = ( opnd1->value64 != opnd2->value64 ? -1:0 );
2843             break;
2844         case T_LT:
2845             opnd1->value64 = ( opnd1->value64 <  opnd2->value64 ? -1:0 );
2846             break;
2847         case T_LE:
2848             opnd1->value64 = ( opnd1->value64 <= opnd2->value64 ? -1:0 );
2849             break;
2850         case T_GT:
2851             opnd1->value64 = ( opnd1->value64 >  opnd2->value64 ? -1:0 );
2852             break;
2853         case T_GE:
2854             opnd1->value64 = ( opnd1->value64 >= opnd2->value64 ? -1:0 );
2855             break;
2856         case T_MOD:
2857             if ( opnd2->llvalue == 0 ) {
2858                 return( fnEmitErr( DIVIDE_BY_ZERO_IN_EXPR ) );
2859             } else
2860                 opnd1->llvalue %= opnd2->llvalue;
2861             break;
2862         case T_SHL:
2863             /* v2.04: check for shift count < 0 */
2864             DebugMsg1(("calculate(SHL): value=%" I64_SPEC "X << %" I32_SPEC "u (max=%u)\n", opnd1->llvalue, opnd2->value, 8 * sizeof( opnd1->llvalue ) ));
2865             if ( opnd2->value < 0 )
2866                 fnEmitErr( COUNT_MUST_BE_POSITIVE_OR_ZERO );
2867             else if ( opnd2->value >= ( 8 * sizeof( opnd1->llvalue ) ) )
2868                 opnd1->llvalue = 0;
2869             else
2870                 opnd1->llvalue = opnd1->llvalue << opnd2->value;
2871             /* v2.01: result is 64-bit only if mode is USE64 */
2872             /* v2.06: for -Zm only. This is not entirely correct,
2873              * since Masm v6x also does 32-bit shifts, but since v2.06
2874              * JWasm intends to behave like Masm v8+.
2875              * Might be better to implement OPTION EXPR16|32|64.
2876              */
2877             //if ( ModuleInfo.Ofssize <= USE32 ) {
2878             if ( ModuleInfo.m510 ) {
2879                 opnd1->hvalue = 0;
2880                 opnd1->hlvalue = 0;
2881             }
2882             break;
2883         case T_SHR:
2884             /* Masm v8 works with unsigned 64-bit,
2885              * Masm v6 masks shift count with 0x3F.
2886              * v2.04: does behave like Masm v8+.
2887              * there is a problem with some compilers if shift
2888              * count is >= 64. So in this case the result is zeroed manually
2889              */
2890 #if 0
2891             if ( opnd1->hvalue == -1 ) {
2892                 opnd1->hvalue = 0;
2893                 opnd1->hlvalue = 0;
2894             }
2895 #endif
2896             /* v2.04: check for shift count < 0 */
2897             if ( opnd2->value < 0 )
2898                 fnEmitErr( COUNT_MUST_BE_POSITIVE_OR_ZERO );
2899             else if ( opnd2->value >= ( 8 * sizeof( opnd1->llvalue ) ) )
2900                 opnd1->llvalue = 0;
2901             else
2902                 opnd1->llvalue = opnd1->llvalue >> opnd2->value;
2903             break;
2904         case T_AND:
2905             opnd1->llvalue &= opnd2->llvalue;
2906             break;
2907         case T_OR:
2908             opnd1->llvalue |= opnd2->llvalue;
2909             break;
2910         case T_XOR:
2911             opnd1->llvalue ^= opnd2->llvalue;
2912             break;
2913         }
2914         break; /* end case T_BINARY_OPERATOR */
2915     case T_UNARY_OPERATOR:
2916         DebugMsg1(("calculate(%s [T_UNARY_OPERATOR]): opnd2 kind=%d sym=%s mbr=%s type=%s memtype=%X is_type=%u indirect=%u\n",
2917                    oper->string_ptr,
2918                    opnd2->kind,
2919                    opnd2->sym ? opnd2->sym->name : "NULL",
2920                    opnd2->mbr ? opnd2->mbr->name : "NULL",
2921                    opnd2->type ? opnd2->type->name : "NULL",
2922                    opnd2->mem_type, opnd2->is_type, opnd2->indirect ));
2923         /* NOT is an instruction and hence has no valid
2924          * value to be returned by GetValueSp() or GetSflagsSp()!
2925          */
2926         if( oper->tokval == T_NOT ) {
2927             MakeConst( opnd2 );
2928             if( opnd2->kind != EXPR_CONST ) {
2929                 DebugMsg(("calculate(%s) error 1\n", oper->string_ptr ));
2930                 return( fnEmitErr( CONSTANT_OPERAND_EXPECTED ) );
2931             }
2932             TokenAssign( opnd1, opnd2 );
2933             opnd1->llvalue = ~(opnd2->llvalue);
2934             break;
2935         }
2936 
2937         /* operator         accepts
2938          ----------------------------------------------
2939          SIZEOF/SIZE        label, type, struct field
2940          LENGTHOF/LENGTH    label, struct field
2941          TYPE               label, type, struct field, register, number
2942          LOW                constant, label (OMF+BIN only)
2943          HIGH               constant, label (OMF+BIN only)
2944          LOWWORD            constant, label
2945          HIGHWORD           constant
2946          LOW32              constant, label, float
2947          HIGH32             constant, float
2948          THIS               type
2949          OPATTR/.TYPE       label, type, struct field, register, number
2950          SHORT              label
2951          SEG                label
2952          OFFSET/LROFFSET    label, struct field, number
2953          IMAGEREL           label
2954          SECTIONREL         label
2955          WIDTH/MASK         bitfields or RECORD type
2956          */
2957 
2958         temp = GetValueSp( oper->tokval );
2959 
2960         sym = opnd2->sym;
2961         if( opnd2->mbr != NULL )
2962             sym = opnd2->mbr;
2963 
2964         /* for error displays, get the position of the operand that
2965          * caused the trouble.
2966          */
2967         if ( opnd2->instr != EMPTY )
2968             name = oper->tokpos + strlen( oper->string_ptr ) + 1;
2969         else if ( sym )
2970             name = sym->name;
2971         else if ( opnd2->base_reg != NULL && opnd2->indirect == FALSE )
2972             name = opnd2->base_reg->string_ptr;
2973         else
2974             name = oper->tokpos + strlen( oper->string_ptr ) + 1;
2975 
2976         switch ( opnd2->kind ) {
2977         case EXPR_CONST:
2978             /* v2.05: conditions "struct-field" and "istype" exchanged */
2979             /* is item a struct field? */
2980             /* v2.10: fixme: EXPR_CONST & mbr!=NULL - what's that supposed to be? */
2981             if ( opnd2->mbr != NULL && opnd2->mbr->state != SYM_TYPE ) {
2982                 if ( opnd2->mbr->mem_type == MT_BITS ) { /* bitfield? */
2983                     if ( ( temp & AT_BF ) == 0 ) {
2984                         return( invalid_operand( opnd2, oper->string_ptr, name ) );
2985                     }
2986                 } else {
2987                     if ( ( temp & AT_FIELD ) == 0 ) {
2988                         return( invalid_operand( opnd2, oper->string_ptr, name ) );
2989                     }
2990                 }
2991             } else if ( opnd2->is_type ) { /* is item a type? */
2992                 if ( ( temp & AT_TYPE ) == 0 ) {
2993                     return( invalid_operand( opnd2, oper->string_ptr, name ) );
2994                 }
2995             } else { /*  or is it a number? */
2996                 if ( ( temp & AT_NUM ) == 0 ) {
2997                     return( invalid_operand( opnd2, oper->string_ptr, name ) );
2998                 }
2999             }
3000             break;
3001         case EXPR_ADDR:
3002             /* an indirect memory operand? (not an auto variable) */
3003             if ( opnd2->indirect == TRUE && opnd2->sym == NULL ) {
3004                 if ( ( temp & AT_IND ) == 0 ) {
3005                     return( invalid_operand( opnd2, oper->string_ptr, name ) );
3006                 }
3007             } else {
3008                 if ( ( temp & AT_LABEL ) == 0 ) {
3009                     return( invalid_operand( opnd2, oper->string_ptr, name ) );
3010                 }
3011             }
3012 #if 0 /* v2.08: this if() obsolete? */
3013             if( opnd2->instr != EMPTY ) {
3014                 /* if instr is set, it's not a full address */
3015                 switch ( oper->tokval ) {
3016                 case T_LOW:
3017                 case T_HIGH:
3018                 case T_LOWWORD:
3019                 case T_HIGHWORD:
3020 #if LOHI32
3021                 case T_LOW32:
3022                 case T_HIGH32:
3023 #endif
3024                 case T_TYPE:
3025                 case T_OPATTR:
3026                 case T_DOT_TYPE:
3027                 case T_OFFSET: /* v2.08: added, to allow OFFSET OFFSET <addr> */
3028                     break;
3029                 default:
3030                     /* remaining: OFFSET, LROFFSET, IMAGEREL, SECTIONREL, SEG,
3031                      * SHORT
3032                      * THIS (won't set opnd.instr)
3033                      * (SIZE, SIZEOF, LENGTH, LENGHTOF, MASK, WIDTH) -> EXPR_CONST
3034                      *
3035                      */
3036                     DebugMsg(("calculate %s error 2\n", oper->string_ptr ));
3037                     return( fnEmitErr( LABEL_EXPECTED ) );
3038                 }
3039             }
3040 #endif
3041             break;
3042         case EXPR_REG:
3043             if ( ( temp & AT_REG ) == 0 ) {
3044                 return( invalid_operand( opnd2, oper->string_ptr, name ) );
3045             }
3046             break;
3047         case EXPR_FLOAT: /* v2.05: added */
3048             if ( ( temp & AT_FLOAT ) == 0 ) {
3049                 DebugMsg(("calculate %s 'float' error\n", oper->string_ptr ));
3050                 return( fnEmitErr( REAL_OR_BCD_NUMBER_NOT_ALLOWED ) );
3051             }
3052             break;
3053         }
3054 #ifdef DEBUG_OUT
3055         if ( unaryop[ GetSflagsSp( oper->tokval ) ]( oper->tokval, opnd1, opnd2, sym, name ) == ERROR )
3056             return( ERROR );
3057         break;
3058 #else
3059         return( unaryop[ GetSflagsSp( oper->tokval ) ]( oper->tokval, opnd1, opnd2, sym, name ) );
3060 #endif
3061     //case T_RES_ID:
3062     default: /* shouldn't happen */
3063         DebugMsg(("calculate(%s): unknown operator\n", oper->string_ptr ));
3064         return( fnEmitErr( SYNTAX_ERROR_EX, oper->string_ptr ) );
3065     } /* end switch( oper->token ) */
3066 
3067 #ifdef DEBUG_OUT
3068     if ( opnd1->hlvalue ) {
3069         DebugMsg1(("%u calculate(%s) exit, ok kind=%d value=0x%" I64_SPEC "X_%016" I64_SPEC "X memtype=0x%X indirect=%u type=>%s<\n",
3070                    evallvl,
3071                    oper->string_ptr,
3072                    opnd1->kind,
3073                    opnd1->hlvalue, opnd1->llvalue,
3074                    opnd1->mem_type,
3075                    opnd1->indirect, opnd1->type ? opnd1->type->name : "NULL" ));
3076     } else if ( opnd1->hvalue ) {
3077         DebugMsg1(("%u calculate(%s) exit, ok kind=%d value=%" I64_SPEC"d(0x%" I64_SPEC "X) memtype=0x%X indirect=%u type=>%s<\n",
3078                    evallvl,
3079                    oper->string_ptr,
3080                    opnd1->kind,
3081                    opnd1->llvalue, opnd1->llvalue,
3082                    opnd1->mem_type,
3083                    opnd1->indirect, opnd1->type ? opnd1->type->name : "NULL" ));
3084     } else {
3085         DebugMsg1(("%u calculate(%s) exit, ok kind=%d value=%d(0x%X) memtype=0x%X ind=%u exp=%u type=%s mbr=%s\n",
3086                    evallvl,
3087                    oper->string_ptr,
3088                    opnd1->kind,
3089                    opnd1->value, opnd1->value,
3090                    opnd1->mem_type,
3091                    opnd1->indirect, opnd1->explicit,
3092                    opnd1->type ? opnd1->type->name : "NULL",
3093                    opnd1->mbr ? opnd1->mbr->name : "NULL" ));
3094     }
3095 #endif
3096     return( NOT_ERROR );
3097 }
3098 
3099 /* this code runs BEFORE the - right - operand of an operator is read */
3100 
PrepareOp(struct expr * opnd,const struct expr * old,const struct asm_tok * oper)3101 static void PrepareOp( struct expr *opnd, const struct expr *old, const struct asm_tok *oper )
3102 /********************************************************************************************/
3103 {
3104     opnd->is_opattr = old->is_opattr;
3105 
3106     switch ( oper->token ) {
3107     case T_DOT:
3108         DebugMsg(("PrepareOp: DOT operator found, old.sym=%X, old.type=%s, expr=%s\n", old->sym, (old->type ? old->type->name : "NULL" ), oper->tokpos + strlen( oper->string_ptr ) ));
3109         if ( old->type ) {
3110             DebugMsg1(("PrepareOp: implicit type: %s\n", old->type->name));
3111             opnd->type = old->type;
3112             opnd->is_dot = TRUE;
3113 #if 0
3114         /* v2.09 (type field is now set in get_operand();
3115          * it's problematic to use old->sym here, because this field
3116          * is not necessarily set by the operand just before the dot.
3117          */
3118         //} else if ( old->sym && old->sym->mem_type == MT_TYPE ) {
3119         } else if ( old->sym && old->sym->mem_type == MT_TYPE && old->instr == EMPTY ) {
3120             DebugMsg1(("PrepareOp: label %s, implicit type: %s\n", old->sym->name, old->sym->type->name));
3121             for ( opnd->type = old->sym->type; opnd->type->type; opnd->type = opnd->type->type );
3122 #endif
3123         /* v2.07: changed */
3124         //} else if ( !ModuleInfo.oldstructs ) {
3125         /* v2.08: reverted, replaced by changes in dot_op() and get_operand(), case T_STYPE */
3126         //} else if ( old->sym && old->sym->mem_type == MT_EMPTY && !ModuleInfo.oldstructs ) {
3127         /* v2.11: nullstruct not used here. Set type to NULL and is_dot==TRUE */
3128         //} else if ( !ModuleInfo.oldstructs ) {
3129         } else if ( !ModuleInfo.oldstructs && old->sym && old->sym->state == SYM_UNDEFINED ) {
3130             DebugMsg1(("PrepareOp: forward ref to %s, type will be NULL\n", old->sym->name ));
3131             opnd->type = NULL;
3132             opnd->is_dot = TRUE;
3133         }
3134         break;
3135     case T_UNARY_OPERATOR:
3136         switch ( oper->tokval ) {
3137         case T_OPATTR:
3138         case T_DOT_TYPE:
3139             DebugMsg(("PrepareOp: OPATTR operator found, old.sym=%X, old.type=%s, expr=%s\n",
3140                       old->sym, (old->type ? old->type->name : "NULL" ), oper->tokpos + strlen( oper->string_ptr ) ));
3141             opnd->is_opattr = TRUE;
3142             break;
3143         }
3144         break;
3145     }
3146 }
3147 
OperErr(int i,struct asm_tok tokenarray[])3148 static void OperErr( int i, struct asm_tok tokenarray[] )
3149 /*******************************************************/
3150 {
3151     if ( tokenarray[i].token <= T_BAD_NUM ) {
3152         fnEmitErr( MISSING_OPERATOR_IN_EXPRESSION ); ERRLOC(i);
3153     } else
3154         fnEmitErr( SYNTAX_ERROR_EX, tokenarray[i].string_ptr );
3155 
3156     return;
3157 }
3158 
3159 #define IsCurrToken( tok )  ( tokenarray[*i].token == tok )
3160 
evaluate(struct expr * opnd1,int * i,struct asm_tok tokenarray[],const int end,const uint_8 flags)3161 static ret_code evaluate( struct expr *opnd1, int *i, struct asm_tok tokenarray[], const int end, const uint_8 flags )
3162 /********************************************************************************************************************/
3163 {
3164     ret_code rc = NOT_ERROR;
3165 
3166     DebugMsg1(("%u evaluate(i=%d, end=%d, flags=%X) enter [opnd1: kind=%d type=%s]\n",
3167                ++evallvl, *i, end, flags, opnd1->kind, opnd1->type ? opnd1->type->name : "NULL" ));
3168 
3169     /* v2.07: this function has been "simplified".
3170      * it's ensured now that if any operator is involved
3171      * - including () and [] - then calculate() will be called.
3172      * v2.10: removed the 'return( ERROR )' branches, to make
3173      * OPATTR work better.
3174      * v2.10: loop changed from 'do {} while' to 'while () {}'.
3175      * v2.10: 'flags' argument contains "inside []" information.
3176      */
3177 
3178     /*
3179      * First token may be either an unary operator or an operand
3180      */
3181     if ( opnd1->kind == EXPR_EMPTY &&  !is_unary_op( tokenarray[*i].token ) ) {
3182         rc = get_operand( opnd1, i, tokenarray, flags );
3183     }
3184 
3185     /* now handle operators. */
3186     while ( rc == NOT_ERROR && *i < end && !IsCurrToken( T_CL_BRACKET ) && !IsCurrToken( T_CL_SQ_BRACKET ) ) {
3187 
3188         int curr_operator;
3189         struct expr opnd2;
3190 
3191         curr_operator = *i;
3192         DebugMsg1(("%u evaluate loop, operator=>%s< opnd1->sym=%p, type=%s\n",
3193                    evallvl, tokenarray[curr_operator].string_ptr, opnd1->sym, (opnd1->type ? opnd1->type->name : "NULL") ));
3194 
3195         if ( opnd1->kind != EXPR_EMPTY ) {
3196             /* check operator behind operand. Must be binary or open bracket */
3197             if ( tokenarray[curr_operator].token == '+' || tokenarray[curr_operator].token == '-' )
3198                 tokenarray[curr_operator].specval = BINARY_PLUSMINUS;
3199             else if( !is_operator( tokenarray[curr_operator].token ) || tokenarray[curr_operator].token == T_UNARY_OPERATOR ) {
3200                 DebugMsg(("%u evaluate: unexpected token at idx=%u, token=%X >%s<\n", evallvl, curr_operator, tokenarray[curr_operator].token, tokenarray[curr_operator].tokpos ));
3201                 rc = ERROR;
3202                 //if ( !opnd2.is_opattr )  /* v2.11: opnd2 was accessed before initialization */
3203                 if ( !opnd1->is_opattr )
3204                     OperErr( curr_operator, tokenarray );
3205                 break;
3206             }
3207         }
3208 
3209         (*i)++;
3210 
3211         init_expr( &opnd2 );
3212         PrepareOp( &opnd2, opnd1, &tokenarray[curr_operator] );
3213 
3214         /* read the (next) operand. */
3215 
3216         if( tokenarray[curr_operator].token == T_OP_BRACKET ||
3217            tokenarray[curr_operator].token == T_OP_SQ_BRACKET ) {
3218             int exp_token = T_CL_BRACKET;
3219             if( tokenarray[curr_operator].token == T_OP_SQ_BRACKET ) {
3220                 exp_token = T_CL_SQ_BRACKET;
3221 #if 1 /* v2.10: slightly hackish; see regression test dotop5.asm */
3222             } else if ( opnd1->is_dot ) {
3223                 opnd2.type = opnd1->type;
3224                 opnd2.is_dot = TRUE;
3225 #endif
3226             }
3227 
3228             rc = evaluate( &opnd2, i, tokenarray, end, ( flags | ( exp_token == T_CL_SQ_BRACKET ? EXPF_IN_SQBR : 0 ) ) & ~EXPF_ONEOPND );
3229 
3230             if( !IsCurrToken( exp_token ) ) {
3231                 DebugMsg(("%u evaluate: error, missing '%c', i=%u\n", evallvl, exp_token, *i ));
3232                 if ( rc != ERROR ) {
3233                     fnEmitErr( MISSING_RIGHT_PARENTHESIS_IN_EXPRESSION );
3234                     /* v2.12: if curr token is a comma, the intention might be to call a macro function
3235                      * - using an undefined ( or not yet defined ) macro. The problem is that the name
3236                      * of this undefined macro isn't displayed in pass one, making it hard to see the
3237                      * reason for the error msg. However, if a comma is found, then it's surely no valid
3238                      * expression - in this case an "undefined symbol" err msg may be helpful.
3239                      */
3240                     if ( IsCurrToken( T_COMMA ) && opnd1->sym && opnd1->sym->state == SYM_UNDEFINED )
3241                         fnEmitErr( SYMBOL_NOT_DEFINED, opnd1->sym->name );
3242                 }
3243                 rc = ERROR;
3244             } else {
3245                 (*i)++;
3246             }
3247 
3248         } else if( is_unary_op( tokenarray[*i].token ) ) { /* brackets, +, -, T_UNARY_OPERATOR? */
3249             /* v2.13: see types16.asm */
3250             //rc = evaluate( &opnd2, i, tokenarray, end, flags | EXPF_ONEOPND );
3251             rc = evaluate( &opnd2, i, tokenarray, end, ( flags | EXPF_ONEOPND ) & ~EXPF_IN_SQBR );
3252         } else {
3253             /* get either:
3254              * - operand of unary operator OR
3255              * - 2. operand of binary operator
3256              */
3257             /* v2.13: remove "inside brackets" for unary ops */
3258             //rc = get_operand( &opnd2, i, tokenarray, flags );
3259             rc = get_operand( &opnd2, i, tokenarray, ( tokenarray[curr_operator].token == T_UNARY_OPERATOR ) ? ( flags & ~EXPF_IN_SQBR): flags );
3260         }
3261 
3262         /*
3263          * parse expression until either the end or an operator with a higher priority is found.
3264          */
3265 
3266         while( rc != ERROR && *i < end && !IsCurrToken( T_CL_BRACKET ) && !IsCurrToken( T_CL_SQ_BRACKET ) ) {
3267 
3268             if ( tokenarray[*i].token == '+' || tokenarray[*i].token == '-' )
3269                 tokenarray[*i].specval = BINARY_PLUSMINUS;
3270             else if( !is_operator( tokenarray[*i].token ) || tokenarray[*i].token == T_UNARY_OPERATOR ) {
3271                 DebugMsg(("%u evaluate: unexpected token at %u, token=%X >%s<\n", evallvl, *i, tokenarray[*i].token, tokenarray[*i].tokpos ));
3272                 rc = ERROR;
3273                 if ( !opnd2.is_opattr ) /* don't emit error if expression is OPATTR operand */
3274                     OperErr( *i, tokenarray );
3275                 break;
3276             }
3277 
3278             if( get_precedence( &tokenarray[*i] ) >= get_precedence( &tokenarray[curr_operator] ) )
3279                 break;
3280 
3281             DebugMsg1(("evaluate: inner loop, calling evaluate(), i=%u\n", *i ));
3282             rc = evaluate( &opnd2, i, tokenarray, end, flags | EXPF_ONEOPND );
3283         }
3284 
3285         /* v2.10: OPATTR special handling */
3286         if ( rc == ERROR && opnd2.is_opattr ) {
3287             /* skip tokens until the end */
3288             while( *i < end && !IsCurrToken( T_CL_BRACKET ) && !IsCurrToken( T_CL_SQ_BRACKET ) ) {
3289                 (*i)++;
3290             }
3291             opnd2.kind = EXPR_EMPTY;
3292             rc = NOT_ERROR;
3293         }
3294         if( rc != ERROR ) {
3295             rc = calculate( opnd1, &opnd2, &tokenarray[curr_operator] );
3296         }
3297 
3298         if( flags & EXPF_ONEOPND ) /* stop after one operand? */
3299             break;
3300     }
3301 
3302 #ifdef DEBUG_OUT
3303     if ( opnd1->hvalue != -1 && opnd1->hvalue != 0 ) {
3304         DebugMsg1(("%u evaluate exit, rc=%d, kind=%d value=%" I64_SPEC "d(0x%" I64_SPEC "X) memtype=%Xh string=%s indirect=%u type=>%s<\n",
3305                    evallvl--, rc, opnd1->kind, opnd1->llvalue, opnd1->llvalue, opnd1->mem_type,
3306                    opnd1->quoted_string ? opnd1->quoted_string->string_ptr : "NULL",
3307                    opnd1->indirect,
3308                    opnd1->type ? opnd1->type->name : "NULL" ));
3309     } else {
3310         DebugMsg1(("%u evaluate exit, rc=%d, kind=%d value=%" I32_SPEC "d(0x%" I32_SPEC "X) memtype=%Xh string=%s ind=%u exp=%u ofssiz=%d instr=%s type=>%s<\n",
3311                    evallvl--, rc, opnd1->kind, opnd1->value, opnd1->value, opnd1->mem_type,
3312                    opnd1->quoted_string ? opnd1->quoted_string->string_ptr : "NULL",
3313                    opnd1->indirect, opnd1->explicit, opnd1->Ofssize,
3314                    opnd1->instr == EMPTY ? "" : GetResWName( opnd1->instr, NULL ),
3315                    opnd1->type ? opnd1->type->name : "NULL" ));
3316     }
3317 #endif
3318     return( rc );
3319 }
3320 
is_expr_item(struct asm_tok * item)3321 static bool is_expr_item( struct asm_tok *item )
3322 /**********************************************/
3323 /* Check if a token is a valid part of an expression.
3324  * chars + - * / . : [] and () are operators.
3325  * also done here:
3326  * T_INSTRUCTION  SHL, SHR, AND, OR, XOR changed to T_BINARY_OPERATOR
3327  * T_INSTRUCTION  NOT                    changed to T_UNARY_OPERATOR
3328  * T_DIRECTIVE    PROC                   changed to T_STYPE
3329  * for the new operators the precedence is set.
3330  * DUP, comma or other instructions or directives terminate the expression.
3331  */
3332 {
3333     switch( item->token ) {
3334     case T_INSTRUCTION:
3335         switch( item->tokval ) {
3336         case T_SHL:
3337         case T_SHR:
3338             item->token = T_BINARY_OPERATOR;
3339             item->precedence = 8;
3340             return( TRUE );
3341         case T_NOT:
3342             item->token = T_UNARY_OPERATOR;
3343             item->precedence = 11;
3344             return( TRUE );
3345         case T_AND:
3346             item->token = T_BINARY_OPERATOR;
3347             item->precedence = 12;
3348             return( TRUE );
3349         case T_OR:
3350         case T_XOR:
3351             item->token = T_BINARY_OPERATOR;
3352             item->precedence = 13;
3353             return( TRUE );
3354         }
3355         return( FALSE );
3356     case T_RES_ID:
3357         if ( item->tokval == T_DUP ) /* DUP must terminate the expression */
3358             return( FALSE );
3359         break;
3360     case T_DIRECTIVE:
3361         /* PROC is converted to a type */
3362         if ( item->tokval == T_PROC ) {
3363             item->token = T_STYPE;
3364             /* v2.06: avoid to use ST_PROC */
3365             //item->bytval = ST_PROC;
3366             item->tokval = ( ( SIZE_CODEPTR & ( 1 << ModuleInfo.model ) ) ? T_FAR : T_NEAR );
3367             return( TRUE );
3368         }
3369         /* fall through. Other directives will end the expression */
3370     case T_COMMA:
3371     //case T_FLOAT: /* v2.05: floats are now handled */
3372     //case T_QUESTION_MARK: /* v2.08: no need to be handled here */
3373         return( FALSE );
3374     }
3375     return( TRUE );
3376 }
3377 
noEmitErr(int msg,...)3378 static int noEmitErr( int msg, ... )
3379 /**********************************/
3380 {
3381     return( ERROR );
3382 }
3383 
3384 /* evaluate an operand
3385  * start_tok: index of first token of expression
3386  * end_tok:   index of last  token of expression
3387  */
EvalOperand(int * start_tok,struct asm_tok tokenarray[],int end_tok,struct expr * result,uint_8 flags)3388 ret_code EvalOperand( int *start_tok, struct asm_tok tokenarray[], int end_tok, struct expr *result, uint_8 flags )
3389 /*****************************************************************************************************************/
3390 {
3391     int         i;
3392 
3393     DebugMsg1(("EvalOperand(start=%u, end=%u, flags=%X) enter: >%s<\n", *start_tok, end_tok, flags, tokenarray[*start_tok].tokpos ));
3394 
3395     init_expr( result );
3396 
3397     for( i = *start_tok; ( i < end_tok ) && is_expr_item( &tokenarray[i] ); i++ );
3398     if ( i == *start_tok )
3399         return( NOT_ERROR );
3400 
3401     /* v2.10: global flag 'error_msg' replaced by 'fnEmitErr()' */
3402     fnEmitErr = ( ( flags & EXPF_NOERRMSG ) ? noEmitErr : EmitErr );
3403     return ( evaluate( result, start_tok, tokenarray, i, flags ) );
3404 }
3405 
EmitConstError(const struct expr * opnd)3406 ret_code EmitConstError( const struct expr *opnd )
3407 /************************************************/
3408 {
3409     if ( opnd->hlvalue != 0 )
3410         EmitErr( CONSTANT_VALUE_TOO_LARGE_EX, opnd->hlvalue, opnd->value64 );
3411     else
3412         EmitErr( CONSTANT_VALUE_TOO_LARGE, opnd->value64 );
3413     return( ERROR );
3414 }
3415 
3416 /* global init (called once for each module) */
3417 
ExprEvalInit(void)3418 void ExprEvalInit( void )
3419 /***********************/
3420 {
3421     thissym = NULL;
3422     nullstruct = NULL;
3423     nullmbr = NULL;
3424 }
3425