EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

exp.htm
Class
EXP
Enumerations
ExpOperationList
Encodings
ExpEnc
Macros
ExpClassify
Procedures
ExpAlign
ExpCheckBounds
ExpConvertToNumber
ExpCountItems
ExpEval
ExpEvalBoolean
ExpEvalBoolOp1
ExpEvalCharConst
ExpEvalData
ExpEvalIdentifier
ExpGetNextPrime
ExpEvalNum
ExpParseAlignment
ExpParseChar
ExpParseData
ExpParseDatatype
ExpParseFP
ExpParseIdentifier
ExpParseKeyName
ExpParseKeyValue
ExpParseLiteral
ExpParseNumber
ExpParseOperator
ExpParseRange
ExpParseString
ExpParseSuboperation
ExpReportError
ExpStoreInstr
ExpStoreString
ExpStoreUString
ExpWidth
ExpWidthBitwise
ExpWidthOfDataType
ExpWidthSigned

Class EXP describes a parseable expression element, such as number, string, operator, address, register, which can be used in expression.
The same class also represents evaluated expression.

Interpretation of structure members depends on its type , which is kept in the least significant byte of EXP.Status in the form of an uppercase mnemonic letter A,B,D,F,G,M,N,O,P,R,S,#.

Interpretation of EXP members according to their type stored in EXP.Status LSB
ElementExampletypeEXP.SegEXP.LowEXP.HighEXP.Sym
Number1234'N'0 number value 12340
Numeric symbolNumSym'N'0 Value of NumSym^SYM2 of NumSym
Immediate segment:offset0040h:0062h'F'16bit Segm.value3 0040h Offset 0062h0
AddressLabel:'A'^SSS1(section) of Label: Offset of Label:^SYM2 of Label:
Current Address$'A'^SSS1(section) of $ Offset of $0
Extern symbolExtSym::'A'^SSS1(ext.pseudosegment) of ExtSym 0^SYM2 of ExtSym::
Paragraph addressPARA#Label:'P'^SSS1(group) of Label: 0^SYM2 of Label:
Paragraph address of externPARA#ExtSym::'P'^SSS1(ext.pseudosegment) of ExtSym 0^SYM2 of ExtSym::
Untyped Memory[4*EBX+1234]'M'0 Displacement 12340
Typed Memory[4*EBX+Sym]'M'^SSS1(section) of Sym Displacement (offset of Sym)^SYM2 of Sym
SSS object[DATA]'S'^SSS1(group) 00
StructureSTRU'S'^SSS1(structure) of STRU 00
String or char.constant"abcd"'G'0 Pointer to left quoteBrutto4 size 60
Operator&'O'Handler of & ExpEval.BitwiseAnd DictOperators.DataPriority 7Oper.ordinal 26
Attribute operatorSIZE#'O'Handler of SIZE# ExpEval.Size: DictOperators.DataPriority 15Oper.ordinal 2
RegisterEAX'R'0 DictRegisters.Data00
Data2*DWORD STRU.Sym'D'^SSS1 of STRU or 0 Ptr to data valueEvaluated duplicator 2^SYM2 of STRU.Sym
ErrorESP*4'#'MsgIdcontents of !1S!2O
Comments:
1 ^SSS is a pointer to SSS object (section, segment, group or structure).
2 ^SYM is a pointer to SYM object (private or external symbol).
3 Segment value is the virtual address divided by 16 (contents of the segment register in real CPU mode).
4 Brutto size includes string border quotes and selfescaping quotes.
Interpretation of EXP.Status bits
EXP.Status for type M (memory operand in [braces] )
aassGggg_iiiibbbb_SIBvvddd_Vttttttt ││││││││ ││││││││ ││││││││ │└┴┴┴┴┴┴─t:EXP type: uppercase letter 'M'. ││││││││ ││││││││ ││││││││ └────────V:expVbit4 of vector-index, it completes expIndex (*MM16..31). ││││││││ ││││││││ │││││└┴┴──────────d:expDwidth: disp.width: 0,3,4,5,6,7 = none,zero,8,16,32,64 bits ││││││││ ││││││││ │││└┴─────────────v:expVSIBfam vector-index: 0,1,2,3 = VSIB not used,XMM,YMM,ZMM. ││││││││ ││││││││ ││└───────────────B:expBasePres: base register is present in address expression. ││││││││ ││││││││ │└────────────────I:expIndexPres: index register is present in address expression. ││││││││ ││││││││ └─────────────────S:expScalePres: scale is present in address expression. ││││││││ ││││└┴┴┴───────────────────b:expBase: base register ordinal number, if present. ││││││││ └┴┴┴───────────────────────i:expIndex: index register ordinal number, if present. │││││└┴┴────────────────────────────g:expSegm: segment register ordinal number, if present. ││││└───────────────────────────────G:expSegmPres: segment register is present in address expression. ││└┴────────────────────────────────s:expScale: 0,1,2,3 = 1*,2*,4*,8* if present. └┴──────────────────────────────────a:expAwidth: address width: 0,1,2,3 = unspecified,16,32,64 bits.
EXP.Status for types F, N, A, P (immediate operand)
000000pf_00000000_000ooddd_0ttttttt ││ │││││ └┴┴┴┴┴┴┴─t:EXP type: uppercase letter 'F','N','A','P'. ││ ││└┴┴──────────d:expWidth: number width 3,4,5,6,7 = zero,8,16,32,64 bits ││ └┴─────────────o:expOwidth: operand width: 0,1,2,3 = unspecified or 8,16,32,64 bits. ││ expOwidth is only valid with type 'A' representing DB,DW,DD,DQ. │└────────────────────────────f:expFar: symbol (type='A') is a procedure defined with DIST=FAR. └─────────────────────────────p:expPara: segment-register value is required (PARA#Symbol).
EXP.Status for type D (data definition)
0000G000_00000000_dddddddd_0ttttttt │ ││││││││ └┴┴┴┴┴┴┴─t:EXP type: uppercase letter 'D'. │ └┴┴┴┴┴┴┴──────────d:datatype short upcase letter 'B','U','W','D','Q','T','O','Y','Z','S' or 0. └───────────────────────────────G:expString: no explicit datatype but the value is a quoted string.
EXP.Status for types R, G, S, O (register, string, SSS, operator)
0000G000_00000000_00000000_0ttttttt │ └┴┴┴┴┴┴┴─t:EXP type: uppercase letter which specifies the type ('R','G','S','O'). └───────────────────────────────G:expString: the value is a quoted string.
EXP.Status for type # (evaluation error detected)
00000000_00000000_cccccccc_0ttttttt ││││││││ └┴┴┴┴┴┴┴─t:EXP type: character '#' └┴┴┴┴┴┴┴──────────c:Msg 3rd parameter: unexpected char/reg !3Z/!3R etc.
exp PROGRAM FORMAT=COFF,MODEL=FLAT,WIDTH=32,MaxPasses=32
  INCLUDEHEAD "euroasm.htm" ; Interface (structures, symbols and macros) of other modules.
exp HEAD ; Start of module interface.
↑ EXP
Object of this class represents element of expression or the evaluated expression itself.
Contents of EXP members is described in tables above.
EXP  STRUC
.Status D D ; See the table EXPstatus above.
.Seg    D D ; See the table EXPtype above.
.Low    D D ; See the table EXPtype above.
.High   D D ; See the table EXPtype above.
.Sym    D D ; See the table EXPtype above.
   ENDSTRUC EXP
↑ ExpEnc
Encoding of flags used in EXP.Status and in character classification.
expWidth   = 0000000700h ; Values under expWidth mask, as returned from procedure ExpWidth.
expWidth0  = 000b ; Displacement not present in address expression. [EBX]
expWidth0B = 011b ; Displacement is present and equals to zero.     [EBX+0]
expWidth1B = 100b ; Number in .High:.Low can be encoded in 1 byte.  [EBX+127]
expWidth2B = 101b ; Number in .High:.Low can be encoded in 2 bytes. [EBX+32511]
expWidth4B = 110b ; Number in .High:.Low can be encoded in 4 bytes.
expWidth8B = 111b ; Number in .High:.Low can be encoded in 8 bytes.
; Only two least-significant bits of expWidth are used in EXP.Status to encode expOwidth and expAwidth.
;
expDwidth    = 00000000_00000000_00000111_00000000b ; Displacement width. Set by ExpEvaluate.
expVbit4     = 00000000_00000000_00000000_10000000b ; 4.bit of vector indexregister (when *MM16..31 used as VSIB index).
expVSIBfam   = 00000000_00000000_00011000_00000000b ; none/XMM/YMM/ZMM is used as indexregister (VSIB addressing).
expBasePres  = 00000000_00000000_00100000_00000000b ; Base register is present.
expIndexPres = 00000000_00000000_01000000_00000000b ; Index register is present.
expScalePres = 00000000_00000000_10000000_00000000b ; Scaling is present.
expBase      = 00000000_00001111_00000000_00000000b ; Base register ordinal.
expIndex     = 00000000_11110000_00000000_00000000b ; Index register ordinal.
expFar       = 00000001_00000000_00000000_00000000b ; Expression evaluated as a far procedure.
expPara      = 00000010_00000000_00000000_00000000b ; Segment-register value is required by relocation.
expSegm      = 00000111_00000000_00000000_00000000b ; Segment register ordinal.
expSegmPres  = 00001000_00000000_00000000_00000000b ; Segment register is present. Union bit with expString.
expString    = 00001000_00000000_00000000_00000000b ; This data expression is a quoted string without explicit datatype spec.
expScale     = 00110000_00000000_00000000_00000000b ; Scale value.
expAwidth    = 11000000_00000000_00000000_00000000b ; Address width. Set by ExpEvaluate from reg in addr.expression.

; Character parsing class identifiers:
expSeparator  EQU 0x00 ; Special case.
expEol        EQU 0x01 ; LineFeed.
expWhiteSpace EQU 0x02 ; Space, Delete, Controls except for LF.
expQuote      EQU 0x04 ; Double quote, Apostrophe.
expOperator   EQU 0x08 ; +-*/\&|^~!<=>#
expDigit      EQU 0x10 ; 0..9
expLetter     EQU 0x20 ; a..z, A..Z, $@_`, 128..255
expColon      EQU 0x40 ; :
expFullstop   EQU 0x80 ; .

; CPU flag symbolic definitions:
flagC = 0x0001
flagP = 0x0004
flagA = 0x0010
flagZ = 0x0040
flagS = 0x0080
flagT = 0x0100
flagI = 0x0200
flagD = 0x0400
flagO = 0x0800
↑ ExpOperationList
is enumeration of all named operations defined in €ASM.
I order to install a new operation in €ASM it must be introduced
  1. here in %ExpOperationList enumeration,
  2. as a subPROC in ExpEval,
  3. in operators dictionary DictOperators,
  4. in manual.
%ExpOperationList %SET Membership,                          \ Void operation, evaluated by parser.
  Size, Type, RegType, Scope,                               \ General attribute operations.
  Offset, Section, Segment, Group, Para,                    \ Symbol attribute operations.
  FileSize, FileTime,                                       \ File attribute operations.
  Minus, Plus, BitwiseNot, LogicalNot,                      \ Other unary operations.
  Addition, Subtraction, NumericEqual, Above, Below,        \ Binary operations.
  SignedDivision,Division, SignedModulo, Modulo,            \
  SignedMultiplication, Multiplication, Scaling, BitwiseAnd,\
  BitwiseOr, BitwiseXor, NumericNonEqual, NumericNonEqual2, \
  InsensEqual, AboveOrEqual, BelowOrEqual, ShiftLogicalLeft,\
  ShiftLogicalRight, Greater, Lower, LogicalAnd, LogicalOr, \
  LogicalXor, LowerOrEqual, GreaterOrEqual,                 \
  ShiftArithmeticLeft, ShiftArithmeticRight, InsensNonEqual,\
  SensEqual, SensNonEqual, SegmentSeparation

%ExpOperationListLength %SETL %ExpOperationList
↑ ExpClassify Character
Macro ExpClassify tests which semantic class does the character belong to.
Input
Character 8bit character specified as immediate, register or memory, e.g. AL
Output
AL= character
AH= character class in ExpEncoding, e.g. expLetter
Example
ExpClassify [ESI] TEST AH,expLetter|expDigit
ExpClassify %MACRO Character
      MOVZXB EAX,%Character
      MOV AH,[EAX+ExpClassifySet::]
     %ENDMACRO ExpClassify
  ENDHEAD exp ; End of module interface.
 [.data]
ExpClassifySet:: ; This 256 byte table defines classification of ASCII characters used in macro ExpClassify.
 D 10*B expWhiteSpace        ; control 0..9
 D  1*B expEol               ; LineFeed
 D 22*B expWhiteSpace        ; control 11..32
 D  1*B expOperator          ; !
 D  1*B expQuote             ; "
 D  1*B expOperator          ; #
 D  1*B expLetter            ; $
 D  1*B expSeparator         ; %
 D  1*B expOperator          ; &
 D  1*B expQuote             ; '
 D  1*B expSeparator         ; (
 D  1*B expSeparator         ; )
 D  1*B expOperator          ; *
 D  1*B expOperator          ; +
 D  1*B expSeparator         ; ,
 D  1*B expOperator          ; -
 D  1*B expFullstop          ; .
 D  1*B expOperator          ; /
 D 10*B expDigit             ; 0..9
 D  1*B expColon             ; : 
 D  1*B expSeparator         ; ;
 D  1*B expOperator          ; <
 D  1*B expOperator          ; =
 D  1*B expOperator          ; >
 D  1*B expLetter            ; ?
 D  1*B expLetter            ; @
 D 26*B expLetter            ; A..Z
 D  1*B expSeparator         ; [
 D  1*B expOperator          ; \
 D  1*B expSeparator         ; ]
 D  1*B expOperator          ; ^
 D  1*B expLetter            ; _
 D  1*B expLetter            ; `
 D 26*B expLetter            ; a..z
 D  1*B expSeparator         ; {
 D  1*B expOperator          ; |
 D  1*B expSeparator         ; }
 D  1*B expOperator          ; ~
 D  1*B expWhiteSpace        ; Delete
 D 128*B expLetter           ; 128..255
 %IF $-ExpClassifySet <> 256
   %Error "Wrong ExpClassifySet"
 %ENDIF
[.text]
↑ ExpAlign Org, Alignment, Misalignment
ExpAlign will calculate the number of bytes of alignment stuff.
Input
Org Origin number or VA which is being aligned.
Alignment Requested alignment value, one of 0,1,2,4,8,16,32,64,128,256,512 etc.
Misalignment Misalignment value. It should be in range 0..Alignment-1.
Output
ECX= Number of alignment bytes.
Error
-
Example
Invoke ExpAlign, [ESI+SSS.OrgLow],4,0
Invoked by
EaBufferAlign EaStreamAlign IiAssemble PfcoffSegmRawData PfpeCompile PgmLinkImage PseudoALIGN PseudoData PseudoPROC PseudoPROC1 SssCombine SssLinkSection SymCreateLiteral
ExpAlign Procedure Org, Alignment, Misalignment
      SUB EDX,EDX
      ADD EDX,[%Alignment]
      JZ .20: ; Treat ALIGN 0 as ALIGN 1.
.10:  BSR ECX,EDX
      BSF EAX,EDX
      CMP EAX,ECX ; Check if power of two.
      JE .30:
.20:  MOV EDX,1 ; Wrong alignment obtained, silently repaired to 1.
.30:  MOV EDI,[%Org]
      DEC EDX ; 0,1,3,7,15,31...
      LEA EAX,[EDI+EDX]
      NOT EDX ; FF,FE,FC,F8,F0,E0...
      AND EAX,EDX
      ADD EAX,[%Misalignment]
      NEG EDX ; 1,2,4,8,16,32
      MOV EBX,EAX
      SUB EAX,EDX
      JB .80:
      SUB EAX,EDI
      JAE .90:
.80:  MOV EAX,EBX
      SUB EAX,EDI
.90:  MOV [%ReturnECX],EAX
     EndProcedure ExpAlign
↑ ExpCheckBounds Min, Max
ExpCheckBounds indicates if the input numeric value is outside specified bounderies Min,Max.
Input
EDX:EAX input value as 64bit signed integer.
Min minimal acceptable value as 32bit signed integer.
Max maximal acceptable value as 32bit signed integer.
Output
ZF=1 if the input value did not exceed bounderies.
SF != OF if the input value underflowed Min.
SF = OF if the input value overflowed Max.
Error
-
Example
Invoke ExpCheckBounds 0, 3999 JL Underflowed JG Overflowed
Invoked by
EaoptAssemble
ExpCheckBounds Procedure Min, Max
     MOV EBX,EDX
     MOV ECX,EAX
     MOV EAX,[%Min]
     CDQ
     CMP EBX,EDX
     JL .99:
     JG .50: ; If not lower than Min.
     CMP ECX,EAX
     JL .99:
 .50:MOV EAX,[%Max]
     CDQ
     CMP EBX,EDX
     JG .99:
     JL .OK:
     CMP ECX,EAX
     JG .99:
.OK: CMP EAX,EAX ; Set ZF=1.
.99:EndProcedure ExpCheckBounds
↑ ExpConvertToNumber Exp
Character constants (type 'G') are converted to number (type 'N'), if possible.
Then ExpConvertToNumber checks whether the expression is plain number (type 'N').
Input
Exp is pointer to EXP object.
Output
CF=0 if EXP.Status is numeric (type 'N').
CF=1 if EXP is other than 'N'.
Error
Errors are not reported.
Invokes
ExpEvalCharConst ExpWidth
Invoked by
ChunkSuboperate ExpEvalNum ExpParseAlignment IiAssemble PfSuboperate PseudoEQU PseudopcSETA PseudopcSETC VarSuboperate
ExpConvertToNumber Procedure Exp
     MOV EBX,[%Exp]
     MOV ECX,[EBX+EXP.Status]
     CMP CL,'N'
     JE .90:
     CMP CL,'G'
     STC
     JNE .90:
     MOV ESI,[EBX+EXP.Low]
     MOV EDX,[EBX+EXP.High]
     ADD EDX,ESI
     Invoke ExpEvalCharConst,ESI,EDX
     JC .90:
     MOV [EBX+EXP.Low],EAX
     MOV [EBX+EXP.High],EDX
     Invoke ExpWidth
     SHL ECX,8
     MOV CL,'N'
     MOV [EBX+EXP.Status],ECX
.90:EndProcedure ExpConvertToNumber
↑ ExpCountItems TxtPtr, TxtSize
ExpCountItems will count items in the text. Items are separated with unquoted , (comma). This procedure returns ordinal number of highest nonempty item. Superfluous commas at the end of text are ignored. Empty text returns 0.
Input
TxtPtr Pointer to a comma separated list.
TxtSize Number of characters in the list.
Output
EAX= Number of items.
Example
one, two,,four, ,, returns 4. ,,,four returns 4. one returns 1. ,,, returns 0.
Invoked by
PseudopcSETL VarSuboperate
ExpCountItems Procedure TxtPtr, TxtSize
     MOV EDI,[%TxtPtr]
     MOV ECX,[%TxtSize]
     SUB EBX,EBX ; Length counter.
     LEA ESI,[EDI+ECX-1] ; Parsing backward, starting with the last character.
     STD
.10: CMP ESI,EDI
     JB .90:
     LODSB
     ExpClassify AL
     TEST AH,expWhiteSpace
     JNZ .10:
     CMP AL,','
     JE .10: ; Skip superfluous trailing spaces and commas.
     INC EBX
     JMP .30:
.20: CMP ESI,EDI
     JB .90:
     LODSB
.30: ExpClassify AL
     TEST AH,expQuote
     JZ .50:
     MOV AH,AL ; In quotes or apostrophes.
.40: CMP ESI,EDI
     JB .90:
     LODSB
     CMP AL,AH
     JNE .40:
     JMP .20:
.50: CMP AL,','
     JNE .20:
     INC EBX
     JMP .20:
.90: MOV [%ReturnEAX],EBX
     CLD
   EndProcedure ExpCountItems
↑ ExpEvalBoolean ValPtr, ValSize
ExpEvalBoolean evaluates the input value as a Boolean. The value may be
Input
ValPtr pointer to the evaluated value.
ValSize number of bytes in the value.
Output
CF=0 ZF=0 Evaluated as TRUE.
CF=0 ZF=1 Evaluated as FALSE.
Error
CF=1 Errors are reported with macro Msg.
See also
 
Invokes
DictLookup ExpEval ExpParseString ExpReportError
Invoked by
EaoptAssemble ExpEvalBoolOp1 PseudopcSETB StmGetIiModifiers
ExpEvalBoolean Procedure ValPtr, ValSize
ExpBool LocalVar Size=SIZE#EXP
     ClearLocalVar
     MOV ESI,[%ValPtr]
     MOV ECX,[%ValSize]
     LEA EDI,[%ExpBool]
     JECXZ .N: ; Empty value returns FALSE.
     Invoke DictLookup::, DictBoolean::, ESI,ECX ; Accept enumerated boolean constants YES/NO/TRUE/FALSE etc.
     MOV [EDI+EXP.Low],EAX ; 0 or -1.
     JNC .N: ; If such constant was used, return FALSE or TRUE.
     Invoke ExpEval,EDI,ESI,ECX,[Src::+SRC.CurrentStm]
     Invoke ExpReportError,EDI
     MOV EAX,[EDI+EXP.Status]
     Dispatch AL,'N','G'
     Msg PgmStatus=pgmLastPass,'7338',EAX ; Boolean value expected instead of type "!1Z".
     STC
     JMP .90:
.G:  MOV ESI,[EDI+EXP.Low] ; Ptr to the string's left quote.
     MOV ECX,[EDI+EXP.High] ; Brutto size of the string.
     LEA EDX,[ESI+ECX]
     Invoke ExpParseString, ESI,EDX ; Empty string is evaluated as FALSE.
     LEA EBX,[EDI+EXP.Low]
     Msg cc=C,EAX,EBX ; Syntax error in the string !1S.
     JC .90:
     TEST EAX ; String netto size is in EAX. Return FALSE or TRUE.
     JMP .90:
 .N: MOV ECX,[EDI+EXP.Low]
     OR ECX,[EDI+EXP.High]
.90:EndProcedure ExpEvalBoolean
↑ ExpEvalBoolOp1 StmPtr
ExpEvalBoolOp1 evaluates the first ordinal operand of statement as a Boolean value. The 1st operand ot the statement may be
Input
StmPtr pointer to parsed STM.
Output
CF=0 ZF=0 Evaluated as TRUE.
CF=0 ZF=1 Evaluated as FALSE.
Error
CF=1 Errors are reported with macro Msg.
See also
  ExpEvalBoolean
Invokes
ExpEvalBoolean
Invoked by
PseudopcENDREPEAT PseudopcIF PseudopcWHILE
ExpEvalBoolOp1 Procedure StmPtr
ExpOp1 LocalVar Size=SIZE#EXP
     MOV EBX,[%StmPtr]
     BufferRetrieve [EBX+STM.OrdBuffer]
     TEST ECX
     JZ .90: ; False.
     LEA EDI,[%ExpOp1]
     Invoke ExpEvalBoolean,[ESI+0],[ESI+4]
.90:EndProcedure ExpEvalBoolOp1
↑ ExpEvalCharConst StringPtr, StringEnd
ExpEvalCharConst computes the numeric value of character constant. The input string must have been already validated, at least one character following the terminating quote must be available for read. Netto size must not exceed 8 bytes.
Percent sign inside the string is not expanded as %variable. Quotes inside the string must be doubled.
Input
StringPtr pointer to the opening quote of character constant (" or ')
StringEnd pointer where parsing must stop.
Output
CF=0
EDX:EAX= Numeric value of the character constant.
Error
CF=1
EAX='6131' Character constant !1_ is too big for 64 bits (if more than 8 characters)
or EAX='6161' Syntax error in the char.constant !1S (if does not start with a quote)
EDX=undefined
Example
"abc" = 63_62_61h = 6_513_249 "x""y""" = 'x"y"' = 78_22_79_22h = 2_015_525_154.
Invoked by
ExpConvertToNumber ExpEval ExpEvalData
ExpEvalCharConst Procedure StringPtr, StringEnd
      SUB EAX,EAX
      MOV ESI,[%StringPtr]
      MOV EDX,[%StringEnd]
      MOV [%ReturnEAX],EAX
      MOV [%ReturnEDX],EAX
      LODSB
      CMP AL,'"'
      JE .10:
      CMP AL,"'"
      JE .10:
.E6161:MOVD [%ReturnEAX],'6161'
      STC
      JMP .90:
 .10: MOV AH,AL
      MOV ECX,4
      LEA EDI,[%ReturnEAX]
 .20: CMP ESI,EDX
      JNB .E6161:
      LODSB
      CMP AL,AH
      JNE .30:
      CMP ESI,EDX
      JNB .80:
      LODSB
      CMP AL,AH
      JNE .80: ; End of string.
 .30: STOSB
      LOOP .20:
      MOV CL,4
      LEA EDI,[%ReturnEDX]
 .40: CMP ESI,EDX
      JNB .E6161:
      LODSB
      CMP AL,AH
      JNE .50:
      CMP ESI,EDX
      JNB .80:
      LODSB
      CMP AL,AH
      JNE .80: ; End of string.
 .50: STOSB
      LOOP .40:
      CMP ESI,EDX
      JNB .E6161:
      LODSB
      CMP AL,AH
      JNE .70:
      LODSB
      CMP AL,AH
      JNE .80:
 .70: MOVD [%ReturnEAX],'6131' ; String too long.
      STC
      JMPS .90:
 .80: CLC
 .90:EndProcedure ExpEvalCharConst
↑ ExpEvalData EmitBuffer, RelocBuffer, DataPtr, DataSize, DataType, DataStm
ExpEvalData will assemble source data (the contents of one operand of pseudoinstruction D or a literal data) in format

In this format duplicator is an expression evaluating to non-negative scalar integer number.
Field datatype is short B U W D Q T O Y Z I S or long BYTE UNICHAR WORD DWORD QWORD TBYTE OWORD YWORD ZWORD INSTR datatype name or structure name.
The initializing datavalue can be a string or numeric expression or it may be omitted.

Assembled data are emitted to EmitBuffer, relocations to RelocBuffer.
Default DataType is used when source Data does not specify explicit datatype. If DataType=0, data value may be a quoted string which is emitted as BYTE or UNICHAR, depending on %^UNICODE option.

Even when the datavalue is empty (uninitialized data is being reserved), byte(s) 0x00 are emitted to EmitBuffer. Any nonempty data value will set DataStm.Flags:stmtNotBSS flag. However, when this flag remains reset after all statement's ordinals have been processed, the data go to BSS segment by default and the zero contents of EmitBuffer will be discarded in this case.

Input
EmitBuffer Pointer to BUFFER , reserved by caller for emitted data.
RelocBuffer Pointer to BUFFER , reserved by caller for relocation records RELOC of emitted address(es).
DataPtr Start of source data definition.
DataSize Number of bytes in source data definition.
DataType LSB of this parameter specifies the default datatype ( 'B','U','W','D','Q','T','O','Y','Z','I','S') or 0 .
DataStm is pointer to a STM with Data to evaluate. It may be NULL, no forward referenced symbols will be created in this case.
Output
CF=0, EAX='B','U','W','D','Q','T','O','Y','Z','I','S' - actually used datatype in LSB, combined with flag expString when the data is a quoted string.
EmitBuffer is filled with emitted data value, RelocBuffer with RELOC record(s).
Error
CF=1 EAX=0 Errors are reported with macro Msg.
Example
; DataPtr ; |<--DataSize-->| DataType='B' is ignored, because explicit WORD prevails. 3 * WORD 65_534 ; Returned AL='W'. EmitBuffer will contain 6 bytes FE_FF_FE_FF_FE_FF. ; DataPtr ; |<-DataSize->| DataType='Q' 256 + 256 + 0 ; Returned AL='Q'. EmitBuffer will contain 8 bytes 00_02_00_00_00_00_00_00. ; DataPtr ; |<--DataSize-->| DataType=0 "Quoted string" ; Returned AL='B' or 'U' + expString. EmitBuffer will contain 13 bytes or unichars. ; DataPtr ; |<-DataSize->| DataType='W' is ignored, because explicit D prevails. 2 * D aSymbol ; Returned AL='D'. EmitBuffer will contain 2 doublewords with offset of aSymbol. ; RelocBuffer will contain 2 records with origins 0 and 4.
See also
  ExpParseData
Invokes
EaBufferRelease EaBufferReserve ExpEval ExpEvalCharConst ExpParseData ExpParseFP ExpReportError ExpStoreInstr ExpStoreString ExpStoreUString ExpWidth ExpWidthOfDataType
Invoked by
MemberUpdate PseudoData SymCreateLiteral
Tested by
t1410 t1420 t1430 t1440 t1642 t1711
ExpEvalData Procedure EmitBuffer, RelocBuffer, DataPtr, DataSize, DataType, DataStm
EvDataExp   LocalVar Size=SIZE#EXP; Evaluation of Data expression.
EvDValExp   LocalVar Size=SIZE#EXP; Evaluation of Data value.
EvDFP       LocalVar Size=12   ; Extended/double/float number value.
EvDErr      LocalVar Size=8    ; Error parameter !1S.
EvDRelOrg   LocalVar           ; Relative relocation origin. 
EvDEmitBuf  LocalVar           ; Temporary emit buffer.
EvDRelocBuf LocalVar           ; Temporary relocations buffer.
EvDReloc    LocalVar Size=SIZE#RELOC ; Temporary room for creating relocation.
     Invoke EaBufferReserve::,ExpEvalData
     MOV [%EvDEmitBuf],EAX
     Invoke EaBufferReserve::,ExpEvalData
     MOV [%EvDRelocBuf],EAX
     LEA EDX,[%EvDReloc]
     Clear EDX,Size=SIZE#RELOC
     XOR EAX,EAX
     MOV [%ReturnEAX],EAX
     LEA EBX,[%EvDataExp]
     Invoke ExpParseData,EBX,[%DataPtr],[%DataSize]
     JC .90:
     MOV EAX,[EBX+EXP.Status] ; AL='D', AH=explicit datatype or 0.
     SHR EAX,8
     AND EAX,0x0000_00FF
     TEST AL
     JNZ .20:
     ADD AL,[%DataType] ; If the type is not specified in DataPtr, use default DataType from D-suffix.
     JNZ .20:
     ; Datatype still not specified. If the value is "string", datatype will be 'B' or 'U',
     ; otherwise E6724.
     JSt [EBX+EXP.Status],expString,.10:
     LEA EDX,[%DataPtr]
     Msg '6724',EDX,PgmStatus=pgmLastPass ; Type of data "!1S" is not specified.
     XOR EAX,EAX
     MOV [%ReturnEAX],EAX
     STC
     JMP .90:
 .10:MOV AL,'U'
     JSt [Ea.Eaopt::+EAOPT.Status],eaoptUNICODE,.20:
     MOV AL,'B'
 .20:MOV [%DataType],EAX ; Now DataType is not zero.
     SetSt EAX,expString
     MOV [%ReturnEAX],EAX
     MOV ESI,[EBX+EXP.Low] ; Data value ptr.
     MOV ECX,[%DataPtr] ; Data expression ptr.
     ADD ECX,[%DataSize]
     SUB ECX,ESI ; Data value size.
     StripSpaces ESI,ECX ; Netto data value.
     TEST ECX
     JNZ .40:
  ; Emitting of (duplicated) uninitialized data.   
  ; Data value is empty, e.g.  D 4*W. It may go to BSS, DATA, STACK segment,
  ; in all cases zeroes are emitted to EmitBuffer, thou they might not be emitted in the end.
  ; No relocations to bother with.
     MOV ESI,=8*Q(0) ; Maximal possible data variable is 64 bytes long.
     Invoke ExpWidthOfDataType,[%DataType] ; Returns size of datatype ECX=1..64.
 .30:CMPD [EBX+EXP.High],0 ; Duplicator, may be zero.
     JZ .90:
     DECD [EBX+EXP.High]
     BufferStore [%EmitBuffer],ESI,ECX ; Store zeroed data value duplicator times.
     JMP .30:
 .40: ; Emitting of (duplicated) initialized data. ESI,ECX is the unevaluated data value.
     LEA EDX,[%EvDErr]
     MOV [EDX+0],ESI
     MOV [EDX+4],ECX ; Prepare parameter !1S for the case of error.
     LEA EDX,[ESI+ECX]
     MOV EAX,[%DataStm]
     TEST EAX
     JZ .50:
     SetSt [EAX+STM.Flags],stmtNotBSS ; There is an initialized  static value in data expression.
 .50:MOV EAX,[%DataType]
     CMP AL,'D'  ; If AL=D,Q,T, ESI..EDX may be a FP number.
     JE .55:
     CMP AL,'Q'
     JE .55:
     CMP AL,'T'
     JNE .70:
 .55:MOV EBX,EDX ; Temporary save end of operand to EBX.
     Invoke ExpParseFP,ESI,EDX,EAX
     LEA EDI,[%EvDFP] ; Assume FP value returned in CX:EDX:EAX was valid and store it.
     STOSD
     MOV EAX,EDX
     STOSD
     MOV EAX,ECX
     STOSD
     MOV EDX,EBX ; Restore end of operand to EDX.
     JC .70:
     PUSHFD
     POP EDI ; Temporary save Eflags to EDI.
     CMP ESI,EDX ; Compare parsed FP end with operand end.
     JE .60: ; If the whole data value is a valid FP number.
     ; Data value is an expression or invalid FP number.
     CMPB [%DataType],'T'
     JNE .70: ; If not FP number in DT statement, evaluate the value as an integer expression.
     Msg '6725' ; Datatype TBYTE expects plain floating-point number.
     STC
     JMP .90:
 .60: ; Data value is a floating-point number.
     PUSH EDI
     POPFD ; Restore possible warning flags.
     MOV EAX,[%DataType]
     Msg cc=P,'2211',EAX  ; Precision lost in conversion to float type D!1Z.
     JNO .65:
     Msg cc=NZ,'2215',EAX ;  Overflow in conversion to float type D!1Z.
     Msg  cc=Z,'2216',EAX ; Underflow in conversion to float type D!1Z.
 .65:Invoke ExpWidthOfDataType,EAX ; Set ECX to size 4,8,10.
     LEA ESI,[%EvDFP] ; Computed FP binary value.
     JMP .80: ; Go to store (duplicated) FP value in ESI,ECX.
 .70:LEA EBX,[%EvDataExp]
     MOV ESI,[EBX+EXP.Low] ; Data value ESI..EDX will be evaluated as integer expression.
     MOV ECX,EDX
     SUB ECX,ESI
     LEA EDI,[%EvDValExp]
     Invoke ExpEval,EDI,ESI,ECX,[%DataStm]
     Msg cc=PE,'2210' ; Precision lost in calculation with FP number rounded to integer.
     Invoke ExpReportError,EDI
     JC .90:
     LEA ECX,[%EvDErr] ; Prepare wrong value pointer for the case of error.
     MOV EAX,[EDI+EXP.Status]
     ; Data value might have been evaluated to integer number, address or string.
     Dispatch AL,'N','A','G','P' ; Anything else is wrong.
     Msg '6722',EAX,ECX ; Invalid value type !1Z in data expression "!2S".
     STC
     JMP .90:
; Dispatched values of type .G:, .A:, .N:, .P:
; AL='G' or 'A' or 'N' or 'P'.  AH=expWidth 3..7 required by the value. ECX=!1S data value
; EBX=^EXP with whole data expression. EDI=^EXP with evaluated data value.
 .G: ; Data value was evaluated as a quoted string.
     ; It might be INSTR or char.constant if numeric datatype.
     MOV EAX,[%DataType]
     CMP AL,'B'
     JNE .G2:
 .G1:CMPD [EBX+EXP.High],0 ; Duplicator.
     JZ .90:
     ; Data value is a byte string, e.g. DB "string".
     DECD [EBX+EXP.High]
     Invoke ExpStoreString,[EDI+EXP.Low],[EDI+EXP.High],[%EmitBuffer],0
     Msg cc=C,'6160',ECX ; Syntax error in string !1S.
     JC .90:
     JMP .G1:
 .G2:CMP AL,'U'
     JNE .G4:
     ; Data value is a unichar string, e.g. DU "string".
 .G3:CMPD [EBX+EXP.High],0 ; Duplicator.
     JZ .90:
     DECD [EBX+EXP.High]
     Invoke ExpStoreUString,[EDI+EXP.Low],[EDI+EXP.High],[%EmitBuffer]
     Msg cc=C,'6160',ECX ; Syntax error in string !1S.
     JC .90:
     Msg cc=NZ,'3160' ; Invalid UTF-8 character in UNICHAR string.
     JMP .G3:
 .G4:CMP AL,'I'
     JNE .G9:
     ; Data value is a machine instruction, e.g. DI "RETF"
     MOVD [%EvDRelOrg],0
 .G5:CMPD [EBX+EXP.High],0 ; Duplicator.
     JZ .90:
     DECD [EBX+EXP.High]
     BufferClear [%EvDEmitBuf]
     BufferClear [%EvDRelocBuf]
     Invoke ExpStoreInstr,[EDI+EXP.Low],[EDI+EXP.High],[%EvDEmitBuf],[%EvDRelocBuf],[%DataStm]
     JC .90:
     BufferRetrieve [%EvDEmitBuf]
     BufferStore [%EmitBuffer],ESI,ECX
     MOV EDX,ECX ; Emitted data size.
     BufferRetrieve [%EvDRelocBuf] 
     ; Machine instruction may need many relocations, e.g. D 2*I"PUSH L1,L2,L3".
     ; Offset of each reloc will be increased by emitted data size in EDX.
     JECXZ .G5:
 .G6:MOV EAX,[%EvDRelOrg]
     ADD [ESI+RELOC.OrgLow],EAX
     ADCD [ESI+RELOC.OrgHigh],0
     ADD EAX,EDX
     BufferStore [%RelocBuffer],ESI,SIZE#RELOC
     ADD ESI,SIZE#RELOC
     SUB ECX,SIZE#RELOC
     JNZ .G6:
     ADD [%EvDRelOrg],EDX
     JMP .G5:
 .G9:; Datatype of string is not explicitly specified as INSTR, BYTE or UNICHAR.
     ; Therefore it must be a number (character constant), e.g. DW "ab".
     MOV EAX,[EDI+EXP.High] ; String brutto size.
     ADD EAX,[EDI+EXP.Low]  ; String offset.
     Invoke ExpEvalCharConst,[EDI+EXP.Low],EAX
     Msg cc=C,EAX,ECX ; Wrong character constant !1S.
     JC .90:
     MOV [EDI+EXP.Low],EAX ; Char.constant was evaluated to EDX:EAX.
     MOV [EDI+EXP.High],EDX
     Invoke ExpWidth
     MOV DL,CL ; ECX=expWidth 3..7
     JMP .N2: ; Continue with char constant as if it were a plain number.
 .P: ; Data value is a paragraph address.
     LEA EDX,[%EvDReloc]
     MOVD [EDX+RELOC.Status],relocPara+relocWidth16
     MOV ECX,[EDI+EXP.Seg] ; ECX is now pointer to segment of the symbol.
     JECXZ .N: ; If Segment=0, it is a plain number.
     MOV ECX,[ECX+SSS.SegmPtr]
     MOV [EDX+RELOC.Target],ECX
     JECXZ .N:
     MOV ECX,[ECX+SSS.GroupPtr]
     MOV [EDX+RELOC.Frame],ECX
     MOV DL,expWidth2B
     JMP .N2:
 .A: ; Data value is an address (or external scalar).
     LEA EDX,[%EvDReloc]
     MOV ECX,[EDI+EXP.Seg] ; ECX is now pointer to segment of the symbol or pointer to structure.
     MOV [EDX+RELOC.Target],ECX
     TEST ECX
     JZ .N: ; If Segment=0, it is a plain number.
     JSt [ECX+SSS.Status],sssStructure,.N: ; Address of a structure member is always a plain number.
     ; Data value of this ordinal is a relocable address. Its segment is ECX.
     JSt [ECX+SSS.Status],sssWidthMask, .A1: ; If symbol's segment width is specified.
     ; External symbol does not have segment width specified in its pseudosegment ECX.
     ; Therefore assume it will match current segment width.
     MOV ECX,[%DataStm]
     JECXZ .A2:
     MOV ECX,[ECX+STM.Section]
     JECXZ .A2:
 .A1:MOV EAX,sssWidthMask
     AND EAX,[ECX+SSS.Status]
 .A2:XCHG EAX,ECX
     XOR EAX,EAX
     Dispatch ECX,sssWidth16,sssWidth64
     ; If segment width still could not be determined, default to width=32.
.sssWidth32:
     MOV EAX,relocAbsVA+relocWidth32
     JMP .A3:
.sssWidth64:
     MOV EAX,relocAbsVA+relocWidth64
     JMP .A3:
.sssWidth16:
     MOV EAX,relocAbsVA+relocWidth16
.A3: MOV ECX,[EDX+RELOC.Target]
     MOV ECX,[ECX+SSS.Status]
     JNSt ECX,sssExtern,.A6:
     AND ECX,sssExtAttr
     OR EAX,ECX ; Set postponed attribute operation to the relocation EDX.
     CMP ECX,dictAttrPARA << 16                                                 ;>>
     JNE .A4:
     JNSt EAX,relocAbsVA,.A4:
     RstSt EAX,relocAbsVA
     SetSt EAX,relocPara
.A4: MOV ECX,[EDX+RELOC.Target]
     RstSt [ECX+SSS.Status],sssExtAttr ; Clear extern attribute request when it's been handled.
.A6: MOV [EDX+RELOC.Status],EAX
    ; Although the allocated width specified with [%Datatype] might succeed to acomodate
    ; the address when offset is not too high, it must exactly match the segment width in AL (16,32,64),
    ; so 'W','D','Q' is required.
     MOV EDX,relocWidthMask
     AND EDX,EAX 
     SHR EDX,16  ; EDX is now symbol width 16,32,64.
     SHR EAX,20 ; AL=1,2,4.
     AND EAX,7
     MOV ECX,=B"WD?Q"
     DEC EAX   ; AL=0,1,3.
     MOV AL,[ECX+EAX] ; AL='W','D','Q'.
     CMP AL,[%DataType]
     Msg cc=NE,PgmStatus=pgmLastPass,'3529',EDX,[%DataType] ; !1Dbit symbol does not match datatype "!2Z".
     MOV DL,expWidth2B
     CMP AL,'W'
     JE .N2:
     INC DL ; expWidth4B.
     CMP AL,'D'
     JE .N2:
     INC DL ; expWidth8B.
     JMP .N2: ; Continue anyway.
 .N: ; Data value evaluated as a number.
     MOV DL,AH ; expWidth=3..7 required by the number magnitude.
 .N2:Invoke ExpWidthOfDataType,[%DataType] ; expWidth to EAX, size (1,2,4,8,10,16,32,64) to ECX.
     CMP CL,10
     JNA .N4:
     Msg '6553',[%DataType] ; !1Zword data cannot be statically initialized.
     STC
     JMP .90:
 .N4:LEA ESI,[EDI+EXP.Low] ; ESI is now ptr to evaluated signed 64bit integer data value.
     CMP DL,AL ; Compare allocated expWidth (AL) with expWidth required by data (DL).
     JNA .80: ; If it fits.
     LEA ECX,[%EvDErr]
     Msg '6729',ECX,[%DataType],PgmStatus=pgmLastPass ; Data value "!1S" is too big for datatype "!2Z".
     STC
     JMP .90:
.80: ; Initialized binary data value ESI,ECX will be emitted duplication times. %EvDReloc is prepared.
     LEA EBX,[%EvDataExp]
     CMPD [EBX+EXP.High],0 ; Duplicator, may be zero.
     JZ .90:
     DECD [EBX+EXP.High]
     BufferStore [%EmitBuffer],ESI,ECX ; Byte, word, dword or qword of initialized integer data.
     LEA EDX,[%EvDReloc]
     CMPD [EDX+RELOC.Target],0
     JZ .80:
     ; Data value is not scalar. Relocation is required (duplicator times).
     BufferStore [%RelocBuffer],EDX,SIZE#RELOC
     ADD [EDX+RELOC.OrgLow],ECX ; Prepare reloc.Org for the next duplicated record, if any.
     ADCD [EDX+RELOC.OrgHigh],0
     JMP .80:
 .90:PUSHFD 
       Invoke EaBufferRelease::,[%EvDRelocBuf]
       Invoke EaBufferRelease::,[%EvDEmitBuf]
     POPFD  
     EndProcedure ExpEvalData
↑ ExpEvalNum ExpPtr, ExpSize
ExpEvalNum evaluates numeric expression.
Input
ExpPtr Pointer to expression.
ExpSize Size of expression.
Output
CF=0, EDX:EAX=numeric value of expression.
Error
CF=1 Errors are reported with macro Msg.
See also
ExpEvalBoolOp1.
Invokes
ExpConvertToNumber ExpEval ExpReportError
Invoked by
CtxForNext EaoptAssemble ExpParseData PseudoSEGMENT PseudopcERROR PseudopcFOR PseudopcSHIFT StmGetIiModifiers
ExpEvalNum Procedure ExpPtr, ExpSize
ExpEn LocalVar Size=SIZE#EXP
     MOV ESI,[%ExpPtr]
     MOV ECX,[%ExpSize]
     LEA EDI,[%ExpEn]
     Invoke ExpEval,EDI,ESI,ECX,[Src::+SRC.CurrentStm]
     Invoke ExpReportError,EDI
     Invoke ExpConvertToNumber,EDI
     Msg cc=C,'7332', PgmStatus=pgmLastPass ; Plain numeric value or expression expected.
     MOV EAX,[EDI+EXP.Low]
     MOV EDX,[EDI+EXP.High]
     MOV [%ReturnEAX],EAX
     MOV [%ReturnEDX],EDX
    EndProcedure ExpEvalNum
↑ ExpParseAlignment ValuePtr, ValueSize, SectionPtr
ExpParseAlignment will assemble alignment value, which is either enumerated token (B,W,D,Q,T,O,Y,Z,BYTE,WORD,DWORD,QWORD,TBYTE,OWORD,YWORD,ZWORD) or arithmetic expression which evaluates to a power of two (1,2,4,8,16,32,64,128,256,512).
TBYTE is aligned as QWORD (8).
Input
ValuePtr Pointer to alignment value, e.g. "DWORD", "O" or numeric expression.
ValueSize Size of alignment value in bytes.
SectionPtr pointer to the SSS whose alignment should be higher, otherwise W3410 is reported.
If SectionPtr=0, evaluated alignment value is not checked against section alignment.
If SectionPtr=-1, value is only checked on power-of-two.
Output
CF=0, EAX= alignment value 1,2,4,8,16,32,64,128,256 or 512.
Error
CF=1, EAX=0, E6521 reported by macro Msg . W3410 or E6522 is reported only if SectionPtr is nonzero.
Invokes
DictLookup ExpConvertToNumber ExpEval ExpWidth
Invoked by
PseudoALIGN PseudoSEGMENT StmGetIiModifiers
ExpParseAlignment Procedure ValuePtr, ValueSize, SectionPtr
ExpPA  LocalVar Size=SIZE#EXP ; Expression with evaluated alignment value.
       ClearLocalVar
       MOV ESI,[%ValuePtr]
       MOV ECX,[%ValueSize]
       LEA EDI,[%ExpPA]
       Invoke DictLookup::, DictAlignValue::,ESI,ECX
       JC .10:
       MOV [EDI+EXP.Low],EAX
       MOVB [EDI+EXP.Status],'N'
       JMP .20:
 .10:  Invoke ExpEval,EDI,ESI,ECX,EAX
       Invoke ExpConvertToNumber,EDI
       JNC .20:
.E6521:LEA ESI,[%ValuePtr]
       Msg '6521',ESI,DictAlignValue:: ; Invalid alignment "!1S". Expected one of !2L.
       JMP .Err:
 .20:  MOV EDX,[EDI+EXP.High]
       MOV EAX,[EDI+EXP.Low]
       Invoke ExpWidth
       MOV [EDI+EXP.Status+1],CL
       MOV ECX,[%SectionPtr]
       TEST EDX
       JZ .30:
.E6522:JECXZ .Err:
       LEA ESI,[%ValuePtr]
       Msg '6522',ESI ; Alignment value "!1S" must be power of two (1,2,4,8..512).
.Err:  SUB EAX,EAX
       MOV [%ReturnEAX],EAX
       STC
       JMP .90:
 .30:  MOV [%ReturnEAX],EAX
       JECXZ .90: ; Skip check if %SectionPtr=0.
       ; Test if alignment in EAX is power of 2 <=512.                            ;>
       CMP EAX,512
       JA .E6521:
       BSF EBX,EAX
       JZ .E6521:
       BSR EDX,EAX
       CMP EBX,EDX
       JNE .E6522:
       MOV EBX,ECX
       INC EBX
       JZ .90: ; Skip section check when %SectionPtr=-1.
       ; Test if alignment EAX exceeds section ECX's alignment.
       MOV EBX,[ECX+SSS.Alignment] ; Bug in 20180508 (missing this statement).
       CMP EAX,EBX
       Msg cc=A,'3410',EAX,EBX,ECX ; Requested alignment !1D is greater then alignment !2D of section [!3S].
       CLC
 .90:EndProcedure ExpParseAlignment
↑ ExpParseDatatype DatatypePtr, DatatypeEnd
ExpParseDatatype will inspect if the input text begins with a valid datatype name, which may be a short B U W D Q T O Y Z I S or long BYTE UNICHAR WORD DWORD QWORD TBYTE OWORD YWORD ZWORD INSTR datatype name, or structure name which may start with . when it is local.
Input
DatatypePtr is pointer to the parsed text.
DatatypeEnd is the end of text.
Output if structure
CF=0
EAX= is pointer to the structure (^SSS).
ECX='S'.
ESI= points behind the structure name.
Output if base datatype
CF=0
EAX=0.
ECX= short datatype name 'B','W','U','D','Q','O','Y','Z','I'.
ESI= points behind the datatype name.
Output if no datatype recognized
CF=1
EAX=0.
ECX=0.
ESI= points to the start of parsed text (DatatypePtr).
Invoked by
ExpParseData ExpParseLiteral
Invokes
DictLookup EaBufferRelease EaBufferReserve SssFind SymDelocalName
ExpParseDatatype Procedure DatatypePtr, DatatypeEnd
     MOV ESI,[%DatatypePtr]
     MOV EDX,[%DatatypeEnd]
     MOV [%ReturnESI],ESI
 .10:CMP ESI,EDX
     JNB .NotDataType:
     LODSB
     ExpClassify AL
     TEST AH,expWhiteSpace
     JNZ .10:
     DEC ESI
     MOV EDI,ESI ; Start of possible local datatype name.
     TEST AH,expLetter|expFullstop
     JZ .NotDataType:
 .20:CMP ESI,EDX
     JNB .30:
     LODSB
     ExpClassify AL
     TEST AH,expLetter|expDigit|expFullstop
     JNZ .20:
     CMP AL,':'
     JE .NotDataType: ; Datatype may not terminate with colon.
     DEC ESI
 .30:MOV EDX,ESI ; Behind the last letter of potential datatype name.
     SUB ESI,EDI
     JZ .NotDataType:
     MOV ECX,ESI
     MOV ESI,EDI
     ; ESI,ECX alias ESI..EDX is possible datatype or local structure.
     CMPB [ESI],'.'
     JNE .40:
     Invoke EaBufferReserve::,ExpParseDatatype
     Invoke SymDelocalName::,ESI,ECX,EAX,symDelocal
     BufferRetrieve EAX
     Invoke EaBufferRelease::,EAX
 .40: ; ESI,ECX is delocalized potential datatype (struct) name.
     Invoke SssFind::,sssStructure,0,ESI,ECX,0 ; Return EAX=^SSS or 0.
     JNC .FoundStruc:
     Invoke DictLookup::,DictDatatypes::,ESI,ECX ; Short or long base datatypes.
     JNC .FoundBase:
.NotDataType:
     XOR EAX,EAX
     MOV [%ReturnEAX],EAX
     MOV [%ReturnECX],EAX
     STC
     JMP .90:
.FoundStruc:
     MOVD [%ReturnECX],'S'
     JMP .80:
.FoundBase:
     MOV [%ReturnECX],EAX
     XOR EAX,EAX
.80: MOV [%ReturnESI],EDX
     MOV [%ReturnEAX],EAX
.90:EndProcedure ExpParseDatatype
↑ ExpParseData ExpD, DataExpPtr, DataExpSize
ExpParseData will inspect data expression as they are used in
1) ordinal operand of pseudoinstruction D (explicit data definition or data reservation), or
2) literal data definition, following the literal marker =.
Expected data expression may have format
A) datavalue or
B) datatype datavalue or
C) duplicator * datatype datavalue
where datatype is short B U W D Q T O Y Z I S or long BYTE UNICHAR WORD DWORD QWORD TBYTE OWORD YWORD ZWORD INSTR datatype name, or structure name which may start with . when it is local. Datatype may not be omitted in literal definition 2).
Duplicator, if used, must evaluate to a non-negative scalar number.
Datavalue may be empty (uninitialized data reservation), however syntax 1A) does not reserve data and syntax 2A) is not legal.
Input
ExpD is pointer to EXP output structure, allocated by caller.
DataExpPtr is pointer to the source data expression which is being parsed.
DataExpSize Number of characters in source data expression.
Output
ExpD is filled with parsed data.
ExpD.Status is 'BD', 'UD', 'WD' etc or just 'D' if no explicit datatype is used. ExpD.Status:expString will be set if the data value is a quoted string.
ExpD.High is evaluated duplicator. When duplication is not used, it is set to 1 (default).
ExpD.Low points to data value, just behind datatype name. When datatype name is not specified in data expression, ExpD.Low will be identical with DataExpPtr and the entire input is treated as datavalue. ExpD.Status is just 'D' in this case.
ExpD.Seg is nonzero only when structure name was found. ExpD.Status='SD' in this case.
Source data value is just parsed but not evaluated here.
Error
CF=1 Errors are reported with macro Msg.
Example
; DataExpPtr ; |<--DataExpSize--->| Label D 3 * W 255 + 256*255, 0
See also
  ExpEvalData.
Invokes
ExpEvalNum ExpParseDatatype
Invoked by
ExpEvalData PseudoData
ExpParseData Procedure ExpD, DataExpPtr, DataExpSize
DupEnd  LocalVar ; Ptr to duplication operator * - end of duplicator expression.
     ; Initialization of output EXP.
     MOV EBX,[%ExpD]
     MOV ESI,[%DataExpPtr]
     MOV ECX,[%DataExpSize]
     StripSpaces ESI,ECX
     XOR EAX,EAX
     MOV [%DupEnd],EAX     ; Assume no duplication.
     MOV [EBX+EXP.Seg],EAX ; Assume no ptr to SSS structure.
     MOV [EBX+EXP.Sym],EAX ; Assume no ptr to symbol.
     MOV [EBX+EXP.Low],ESI ; Ptr to source data value.
     INC EAX
     MOV [EBX+EXP.High],EAX; Default duplicator is initialized to 1.
     MOV AL,'D'
     MOV [EBX+EXP.Status],EAX
  ; Output structure EXP is now initialized.
     LEA EDX,[ESI+ECX] ; DataExp end.
 ; Assume format B) - Data expression starts with datatype.
     Invoke ExpParseDatatype,ESI,EDX
     JNC .40:
 ; Assume format C) - Search for duplication operator, which is unquoted * followed by a valid datatype.
 .10:CMP ESI,EDX
     JNB .50:
     LODSB
     CMP AL,'*'
     JE .30:
     CMP AL,'"'
     JE .15:
     CMP AL,"'"
     JNE .10:
 .15:MOV AH,AL ; Inside quoted string.
 .20:CMP ESI,EDX
     JNB .E6721: ; Invalid data expression, missing end quote.
     LODSB
     CMP AL,AH
     JNE .20:
     JMP .10:
 .30:LEA EAX,[ESI-1]
     MOV [%DupEnd],EAX ; Ptr to possible duplication operator * (if datatype/struc follows in ESI..EDX).
    ; CALL .DataType:
     Invoke ExpParseDatatype,ESI,EDX ; Returns EAX=^SSS or 0, CL=short datatype, ESI=parsed position.
     JNC .40:
     MOV [%DupEnd],EAX ; Reset to 0 when no datatype follows *.
     JMP .10: ; Continue searching for next *, e.g. in  2*2*B 0.
 .E6711:Msg '6711' ; Duplicator cannot be empty.
     STC
     JMP .90:
 .E6712:Msg '6712' ; Duplicator out of range 0..2147483647.
     STC
     JMP .90:
 .E6721:LEA EDX,[%DataExpPtr]
     Msg '6721',EDX ; Invalid data expression "!1S".
     STC
     JMP .90:
 .40:MOV [EBX+EXP.Status+1],CL
     MOV [EBX+EXP.Seg],EAX
     MOV [EBX+EXP.Low],ESI
     MOV ECX,[%DupEnd]
     JECXZ .50: ; No duplication.
     MOV ESI,[%DataExpPtr]
     SUB ECX,ESI
     StripSpaces ESI,ECX
     JECXZ .E6711: ; Duplicator cannot be empty.
     PUSH EDX
       Invoke ExpEvalNum,ESI,ECX ; Calculate duplication.
       JC .45:
       TEST EDX
 .45:POP EDX
     JC .50:
     JNZ .E6712: ; Duplicator out of range 0..2147483647.
     MOV [EBX+EXP.High],EAX ; Duplicator value.
 .50:; Assume format A) - value only.
     ; If data value is a quoted string, expString will be flagged.
     MOV ESI,[EBX+EXP.Low] ; Restore pointer to the start of value.
     SUB EAX,EAX
 .60:CMP ESI,EDX
     JNB .80:
     LODSB ; At potential start of string.
     CMP AL,'"'
     JE .65:
     CMP AL,"'"
     JNE .85:
 .65:MOV AH,AL
 .70:CMP ESI,EDX
     JNB .85: ; Not a valid quoted string.
     LODSB
     CMP AL,AH
     JNE .70:
     JMP .60:
 .80:TEST AH
     JZ .85: ; Did not start with a quote.
     SetSt [EBX+EXP.Status],expString
 .85:CLC
 .90:EndProcedure ExpParseData
↑ ExpParseFP TxtPtr, TxtEnd, FPtype

ExpParseFP will parse and evaluate a floating-point number in scientific decimal notation and evaluate it as [IEEE754] extended/double/single precision FP number. The number is internally converted to quadruple precision (96 bits) and then rounded to the precision required by FPtype.
Instead of standard FP number scientific notation the input text may also contain one of signed enumerated floating-point special constants #ZERO, #INF, #PINF, #NAN, #PNAN, #QNAN, #SNAN , optionally immediately prefixed by sign + or -, see FP special values.

This procedure is used by ExpEvalData when pseudoinstruction DD, DQ or DT specifies static FP number.
It is also employed in ExpEvaluate to recognize FP number format, however FP numbers used in expression are converted to 64bit integers before calculation.

Input
TxtPtr is pointer to the beginning of the number string.
TxtEnd is pointer where the parsing stops.
FPtype specifies output format. LSB of this parameter must be 'T' or 'Q' or 'D'.
FPType 'T' returns extended 80bit format in CX:EDX:EAX (LSB in AL, higher word of ECX zeroed}
FPType 'Q' returns double 64bit format in EDX:EAX (LSB in AL, ECX=0)
FPType 'D' returns float 32bit format in EAX (LSB in AL, EDX=ECX=0)
Output
CF=0
ZF=result is 0 or underflowed
OF= overflow or underflow
SF= result is negative
PF= precision lost during conversion
ECX:EDX:EAX= floating-point binary value
ESI= pointer to the character following the parsed number. Always between TxtPtr..TxtEnd.
Error
CF=1 on syntax error, invalid FP notation.
ECX:EDX:EAX= #NAN
Example
TxtPtr TxtEnd | | +123.45E+6+7 FPtype='T' | ESI CF=ZF=SF=OF=PF=0 ECX=0x00004019 EDX=0xEB765200 EAX=0x00000000 TxtPtr TxtEnd | | -9E-87 FPtype='T' | ESI CF=ZF=OF=PF=0 SF=1 ECX=0x0000BEE1 EDX:0x8F3AA5C7 EAX=0x6938DBCA TxtPtr TxtEnd | | +#INF FPtype='D' | ESI CF=ZF=OF=PF=SF=0 ECX=0x00000000 EDX:0x7FF80000 EAX=0x00000000
See also
ExpParseNumber
Invokes
DictLookup
Tested by
t1450 t1451 t1452 t1453
Invoked by
ExpEvalData ExpParseNumber
ExpParseFP Procedure TxtPtr, TxtEnd, FPtype
EfpMan      LocalVar Size=12 ; Mantissa as 96bit unsigned integer. Binary point is between 94. and 95.bit.
EfpExp2     LocalVar Size=4  ; Binary  exponent as 32bit signed integer. Initialized to -95.
EfpExp10    LocalVar Size=4  ; Decadic exponent as 32bit signed integer, used during adopting of mantissa digits.
EfpExpE     LocalVar Size=4  ; Decadic exponent as 32bit signed integer specified with modifier E.
EfpExpSign  LocalVar Size=4  ; Exponent signum. Exponend is negative if %EfpExpSign is nonzero.
     ClearLocalVar
     PUSHFD
      MOVD [%EfpExp2],+95 ; Normalized %EfpMan binary point correction.
      RstSt [ESP],flagP+flagZ+flagS+flagO ;  Reset returning flags.
      SetSt [ESP],flagC ; Preset CF as the marker that the number is not valid yet.
      SUB EAX,EAX
      MOV [%ReturnEDX],EAX
      MOV [%ReturnECX],EAX
      MOV ESI,[%TxtPtr]
      MOV ECX,[%TxtEnd]
      SUB ECX,ESI
      StripSpaces ESI,ECX
      MOV [%ReturnESI],ESI
      LEA EDX,[ESI+ECX]
      TEST ECX
      JZ .ParseEnd:
      LODSB ; Expected sign, first digit or #.
      CMP AL,'+'
      JE .10:
      CMP AL,'-'
      JNE .15:
      SetSt [ESP],flagS ; Keep FPnumber signum in flag on machine stack.
 .10: CMP ESI,EDX
      JNB .ParseEnd:
      LODSB ; First digit or '#' must immediately follow the signum. Separator is non accepted here.
      CMP AL,'_'
      JE .ParseBack: ; Invalid FP notation, it may be reevaluated later as integer expression.
 .15: CMP AL,'#'
      JNE .20:
      MOV ECX,3 ; Expected 3 or 4 letters of special FpConstant #INF,#QNaN etc.
      ExpClassify [ESI+ECX] ; Test 4th character of potential special FpConstant.
      TEST AH,expLetter
      JZ .16:
      INC ECX
 .16: Invoke DictLookup::,DictFpConstants:: ,ESI,ECX
      JC .ParseBack: ; Point to '#' as to invalid character.
      ADD ESI,ECX ; Parsed behind the special FpConstant.
      RstSt [ESP],flagC ; No error when special FpConstant detected.
      MOV [%ReturnESI],ESI
 .FpConstant: ; Convert EAX=Dict_FpConstant%Name.Data to required output format.
      SUB ESI,ESI ; ESI is used to keep signum of the constant.
      JNSt [ESP],flagS,.18:
      OR ESI,0x80000000 ; FP signum.
 .18: TEST EAX 
      JNZ .19: ; If not #ZERO.
      SetSt [ESP],flagZ
 .19: MOV EDX,[%FPtype]
      Dispatch DL,0x51,0x54 ; 'D','Q','T'
 ; .0x44: ; Single precision DD format FpConstant.
      MOV EDX,EAX
      AND EAX,0xFF0000FF
      AND EDX,0x0000FF00
      SHL EDX,8
      OR EAX,EDX
      OR EAX,ESI
 .RA: MOV [%ReturnEAX],EAX
      JMP .90:
 .0x51: ; Double precision DQ format FpConstant.
      MOV EDX,EAX
      MOV ECX,EAX
      AND EAX,0x000000FF
      AND EDX,0xFFF00000
      SHL ECX,1
      AND ECX,0x0000FE00
      OR EDX,ECX
      OR EDX,ESI
 .RD: MOV [%ReturnEDX],EDX
      JMP .RA:
 .0x54: ; Extended precision DT format FpConstant.
      MOV ECX,EAX
      MOV EDX,EAX
      AND ECX,0xFFFF0000
      AND EDX,0x0000FF00
      AND EAX,0x000000FF
      OR ECX,ESI
      SHL EDX,16
      SHR ECX,16
      MOV [%ReturnECX],ECX
      JMP .RD:
 .20:  ; Parsing FP notation after signum, no special FpConstant.
      LEA EDI,[%EfpMan] ; Digits of mantissa will be adopted to 96bit integer [%EfpMan].
      CMP AL,'0' ; Separator is not acceptable before 1st digit.
      JB .ParseBack:
      CMP AL,'9'
      JA .ParseBack:
      JMPS .30:
 .25: CMP ESI,EDX ; More decimal digits, separator, point . or modifier E expected.
      JNB .ParseEnd:
      LODSB
      CMP AL,'_'
      JE .25:   ; Ignore separator.
      CMP AL,'0'
      JB .35:
      CMP AL,'9'
      JA .35:
 .30: CALL .AdoptMan:
      JNC .25:
      SetSt [ESP],flagP ; Signalize loss of precision and continue.
      JMP .25:
 .35: CMP AL,'.'
      JNE .45:
      RstSt [ESP],flagC ; From now this is valid FP notation.
 .40: CMP ESI,EDX ; Continue parsing fraction part of FP number, if any.
      JNB .ParseEnd:
      LODSB
      CMP AL,'_'
      JE .40:
      CMP AL,'0'
      JB .45:
      CMP AL,'9'
      JA .45:
      DECD [%EfpExp10]
      CALL .AdoptMan:
      JNC .40:
      SetSt [ESP],flagP ; Signalize loss of precision and continue.
      JMP .40:
 .45: CMP AL,'e'
      JE .50:
      CMP AL,'E'
      JNE .ParseBack: ; If fraction part terminated and modifier does not follow.
 .50: MOV [%ReturnESI],ESI ; Mark temporary end of parsing for the case of invalid exponent, e.g. 1E+_X.
      RstSt [ESP],flagC ; From now this is valid FP notation.
  .E1:CMP ESI,EDX ; Parsing the exponent part.
      JNB .ParseEnd: ; If nothing follows modifier E.
      LODSB ; Expected sign, digit or separator.
      CMP AL,'_'
      JE .E1:
      CMP AL,'+'
      JE .E2:
      CMP AL,'-'
      JNE .E3:
      DECD [%EfpExpSign] ; Remember that exponent is negative.
  .E2:CMP ESI,EDX  
      JNB .ParseAbort:
      LODSB   ; Only digit or separator is expected after signum.
      CMP AL,'_'
      JE .E2:
      CMP AL,'0'
      JB .ParseAbort: ; At least one digit must follow exponent signum, else abort exponent.
      CMP AL,'9'
      JA .ParseAbort:
  .E3:CALL .AdoptExp:
      JC .Overflow:
  .E4:CMP ESI,EDX ; At least one exponent digit adopted, exponent is valid.
      JNB .ParseEnd:
      LODSB ; Expected separator or digit. Any other char terminates the number.
      CMP AL,'_'
      JE .E4:
      CMP AL,'0'
      JB .ParseBack:
      CMP AL,'9'
      JA .ParseBack:
      JMP .E3:
.ParseAbort: ; Characters behind modifier E are not valid, ignore.
      MOVD [%EfpExpE],0
      MOV ESI,[%ReturnESI] ; Saved pointer right behind modifier.
      JMPS .ParseEnd:
.ParseBack: ; Character just loaded from ESI does not belong to FP syntax.
      DEC ESI
.ParseEnd:
      MOV [%ReturnESI],ESI ; Pointer to the end of valid FP notation.
      MOV EAX,[Dict_FpConstantNAN:: + DICT.Data] ; Prepare Not-a-number for the case of syntax error.
      JSt [ESP],flagC,.FpConstant: ; If syntax error, return CF=1, EAX=#NaN.
      ; Evaluate parsed FP number. Scientific notation is now adopted to %EfpMan, %EfpExpE and %EfpExp10.
      MOV EAX,[EDI]  ; Detect zero mantissa.
      OR EAX,[EDI+4]
      OR EAX,[EDI+8]
      JZ .FpConstant: ; Special case of mantisse 0.0000 return as #ZERO.
      MOV EAX,[%EfpExpE]
      CMPD [%EfpExpSign],0
      JZ .55:
      NEG EAX
 .55: ADD [%EfpExp10],EAX
 .56: ; Get rid of decimal exponent in favor of binary exponent.
      CMPD [%EfpExp10],0
      JLE .60: ; If decimal exponent is negative or zero.
      CALL .Denormalize: ; SHR mantissa in order to make room for nonoverflowing multiplication of mantissa.
      CALL .MulBy10:
      DECD [%EfpExp10]
      JMP .56:
 .60: CMPD [%EfpExp10],0
      JGE .65: ; If decimal exponent is zero.
      CALL .Normalize: ; SHL significant bits in mantissa in order to make division precise.
      CALL .DivBy10:
      INCD [%EfpExp10]
      JMP .60:
 .65: CALL .Normalize:
      MOV ECX,[%EfpExp2]
 ; EDI=%EfpMan is now normalized 96bit mantissa (MSbit=1), ECX=%EfpExp2 is corresponding unbiased binary exponent.
      SUB ESI,ESI
      JNSt [ESP],flagS,.70:
      OR ESI,0x80000000 ; FP signum.
 .70: MOV EAX,[%FPtype]
      Dispatch AL,'D','Q','T'
.Overflow:
      MOV EAX,[Dict_FpConstantINF:: + DICT.Data]
      SetSt [ESP],flagO
      JMP .FpConstant: ; On overflow return CF=0, OF=1, ZF=0, EAX=#INF.
.Underflow:
      MOV EAX,[Dict_FpConstantZERO:: + DICT.Data]
      SetSt [ESP],flagO+flagZ
      JMP .FpConstant: ; On underflow return CF=0, OF=1, ZF=1, EAX=#ZERO.

.MulBy10:PROC ; Multiply by 10 the contents of 96bit mantissa [%EfpMan] addressed with EDI.  Destroys EAX,EDX.
              ; Four most significant bits of mantissa must be 0 (denormalized).
        MOV EAX,10
        MULD [EDI+8] ; Most significant dword of mantissa. Never overflows 32 bits.
        MOV [EDI+8],EAX
        MOV EAX,10
        MULD [EDI+4]
        MOV [EDI+4],EAX
        ADD [EDI+8],EDX
        MOV EAX,10
        MULD [EDI+0] ; Least significant DWORD.
        MOV [EDI+0],EAX
        ADD [EDI+4],EDX
        ADCD [EDI+8],0
        RET
       ENDP .MulBy10:

.DivBy10:PROC ; Divide by 10 the contents of 96bit mantissa [%EfpMan] addressed with EDI.  Destroys EAX,ECX,EDX.
       MOV ECX,10
       SUB EDX,EDX
       MOV EAX,[EDI+8] ; Most significant dword of mantissa. 
       DIV ECX
       MOV [EDI+8],EAX
       MOV EAX,[EDI+4]
       DIV ECX
       MOV [EDI+4],EAX
       MOV EAX,[EDI+0] ; Least significant dword of mantissa.
       DIV ECX
       MOV [EDI+0],EAX
       CMP DL,5 ; Round down or up?
       JBE .90:
       SUB EDX,EDX
       ADDD [EDI+0],1 ; Round up.
       ADC [EDI+4],EDX
       ADC [EDI+8],EDX
 .90:  RET
       ENDP .DivBy10:
       
.DivBy2:PROC ; Divide by 2 the contents of mantissa [%EfpMan] addressed with EDI. Destroys EAX. Returns ZF on underflow.
      SHRD [EDI+8],1
      RCRD [EDI+4],1
      RCRD [EDI+0],1
      MOV EAX,[EDI+0]
      OR  EAX,[EDI+4]
      OR  EAX,[EDI+8]
      RET
     ENDP .DivBy2:

.AdoptExp:PROC ; Multiply by 10 [%EfpExpE] and then add digit from AL.
        ; Input: AL=decimal digit '0'..'9'.
        ; Output: EAX,EBX changed. CF=1 on exponent overflow.
      PUSH EDX
       MOV EBX,0Fh
       MOV EDX,10
       AND EBX,EAX
       MOV EAX,[%EfpExpE]
       MUL EDX
       JC .AE9:
       ADD EAX,EBX
       MOV [%EfpExpE],EAX
 .AE9:POP EDX
      RET
      ENDP .AdoptExp:

.AdoptMan:PROC ; Multiply by 10 [%EfpMan] addressed with EDI and then add digit from AL.
        ; Only increment [%EfpExp10] and set CF if not enough room for the nonzero digit.
        ; Input: AL=decimal digit '0'..'9'.  EDI=^%EfpMan. 
        ; Output: EAX=destroyed, CF=precision lost.
       TESTB [EDI+11],0xF0 ; Mantisa too big?
       JZ .A1:
       INCD [%EfpExp10] ; Too many significant digits in FP notation, adopt only virtually and ignore.
       CMP AL,'1' ; Set CF if nonzero digit. Unsignificant zeros do not signalize precision loss.
       CMC
       RET
  .A1: PUSH EDX,EAX
          CALL ExpParseFP.MulBy10
        POP EAX
        SUB EDX,EDX
        AND EAX,0x0000000F ; Convert decimal digit to binary 0..9.
        ADD [EDI+0],EAX
        ADC [EDI+4],EDX
        ADC [EDI+8],EDX
        TEST EAX ; Nonsignificant zero?
        JZ .A9:
        CMPB [%FPtype],'T'
        JNE .A4:
        OR EDX,[EDI+8]
        JZ .A9:
        JNZ .A8:
 .A4:   CMPB [%FPtype],'Q'
        JNE .A5:
        OR EDX,[EDI+8]
        JNZ .A8:
        TESTD [EDI+4],0xFFE00000
        JZ .A9:
        JNZ .A8:
 .A5: ;  CMPB [%FPtype],'D'
        OR EDX,[EDI+8]
        JNZ .A8:
        OR EDX,[EDI+4]
        JNZ .A8:
        TESTD [EDI+0],0xFF000000
        JZ .A9:
 .A8:   STC ; Signalize precision lost.
 .A9: POP EDX
      RET
      ENDP .AdoptMan:

.Normalize:PROC ; Repeat multiply by 2 [%EfpMan] addressed with EDI until MSbit=1.  Destroys EAX,ECX.
      MOV ECX,96 ; Limit number of shifts when %EfpMan=0.
 .N1: TESTB [EDI+11],0x80
      JNZ .N9: ; Jump if normalized (MSbit=1).
      DECD [%EfpExp2]
      SALD [EDI+0],1
      RCLD [EDI+4],1
      RCLD [EDI+8],1
      LOOP .N1:
 .N9: RET
      ENDP .Normalize:

.Denormalize:PROC ; Divide by 2 the contents of 96bit mantissa [%EfpMan] addressed with EDI until 4 MSbits=0.
 .D1: TESTB [EDI+11],0xF0
      JZ .D9:
      INCD [%EfpExp2]
      SHRD [EDI+8],1
      RCRD [EDI+4],1
      RCRD [EDI+0],1
      JMP .D1:
 .D9: RET
      ENDP .Denormalize:

; Dispatched %FPtype 'D','Q','T'.  EDI=%EfpMan, ECX=[%EfpExp2], ESI=signum in MSbit.
.D:   CMP ECX,128
      JG .Overflow:
 .D1: CMP ECX,-127
      JNL .D2:
      ; Exponent underflow sometimes can be healed with denormalization.
      INC ECX
      CALL .DivBy2:
      JZ .Underflow:
      JMP .D1:
 .D2: JNE .D3:
      ; Biased exponent will be 0 - the number is denormal and real exponent is -126 in this case.
      CALL .DivBy2:
      JZ .Underflow:
 .D3: ; Round mantissa from 96 to 24 bits.
      MOV EAX,[EDI+8]
      SHR EAX,8
      TESTB [EDI+8],0x80
      JZ .D5:
      INC EAX
      TEST EAX,0x02000000
      JZ .D5:
      ; Mantissa after SHR was 0x00FFFFFF and overflowed due to rounding.
      MOV EAX,0x00800000
      INC ECX
 .D5: AND EAX,0x007FFFFF ; Mask off integer bit of mantissa.
      ADD ECX,127 ; Exponent bias.
      SHL ECX,23
      OR EAX,ECX ; Exponent.
      OR EAX,ESI ; Signum bit.
      MOV [%ReturnEAX],EAX
      TEST EAX
      JZ .Underflow:
      JMP .90:
.Q:   CMP ECX,1024
      JG .Overflow:
 .Q1: CMP ECX,-1023
      JNL .Q2:
      ; Exponent underflow sometimes can be healed with denormalization.
      INC ECX
      CALL .DivBy2:
      JZ .Underflow:
      JMP .Q1:
 .Q2: JNE .Q3:
 ; Biased exponent will be 0 - the number is denormal and real exponent is -1022 in this case.
      CALL .DivBy2:
      JZ .Underflow:
 .Q3: ; Round mantissa from 96 to 53 bits.
      MOV EAX,[EDI+4]
      MOV EDX,[EDI+8]
      MOV EBX,ECX
      MOV ECX,11 ; 11+32 bits ignored.
 .Q4: SHR EDX,1
      RCR EAX,1
      LOOP .Q4:
      JNC .Q5:
      ADD EAX,1
      ADC EDX,0
      TEST EDX,0x00200000
      JZ .Q5:
      ; Mantissa after SHR was 0x001FFFFF_FFFFFFFF and overflowed due to rounding.
      MOV EDX,0x00100000
      SUB EAX,EAX
      INC EBX
 .Q5: AND EDX,0x000FFFFF ; Mask off integer bit of mantissa.
      ADD EBX,1023 ; Exponent bias.
      SHL EBX,20
      OR EDX,EBX ; Exponent.
      OR EDX,ESI ; Signum bit.
      MOV [%ReturnEAX],EAX
      MOV [%ReturnEDX],EDX
      OR EAX,EDX
      JZ .Underflow:
      JMP .90:
.T:   CMP ECX,16384
      JG .Overflow:
 .T1: CMP ECX,-16383
      JNL .T2:
      ; Exponent underflow sometimes can be healed with denormalization.
      INC ECX
      CALL .DivBy2:
      JZ .Underflow:
      JMP .T1:
 .T2: JNE .T3:
      ; Biased exponent will be 0 - the number is denormal and real exponent is -16382 in this case.
      CALL .DivBy2:
      JZ .Underflow:
 .T3: ; Round mantissa from 96 to 64 bits.
      MOV EBX,[EDI+0]
      MOV EAX,[EDI+4]
      MOV EDX,[EDI+8]
      TEST EBX,0x80000000
      JZ .T5:
      ADD EAX,1
      ADC EDX,0
      JNC .T5:
      ; Mantissa was 0xFFFFFFFF_FFFFFFFF_8* and overflowed due to rounding.
      MOV EDX,0x80000000
      SUB EAX,EAX
      INC ECX
 .T5: ADD ECX,16383 ; Exponent bias.
      SHR ESI,16 ; Signum in MSbit.
      OR ECX,ESI
      MOV [%ReturnECX],ECX
      MOV [%ReturnEAX],EAX
      MOV [%ReturnEDX],EDX
      OR EAX,EDX
      OR EAX,ECX
      JZ .Underflow:
.90:POPFD
    EndProcedure ExpParseFP
↑ ExpParseIdentifier IdTxtPtr, IdTxtEnd, Fullstops
ExpParseIdentifier identifies a valid plain identifier in the input text. Identifier is a sequence of letters and digits starting with a letter. Fullstops . are allowed only when the 3rd argument is nonzero. Terminating colon(s) : are not parsed here.
Input
IdTxtPtr is pointer to the first character of identifier (letter or fullstop).
TxtEnd where the parsing must stop.
Fullstops is boolean value which specifies if . is allowed in identifier name.
Output
CF=0, EAX= size of identifier in bytes (1..TxtEnd-TxtPtr).
Error
CF=1, EAX=0 if the first character pointed to by TxtPtr was not a letter or fullstop.
See also
ExpEvalIdentifier
Example
IdTxtPtr IdTxtEnd | | [EAX+SomeLongLabel:] |<--EAX=13-->| CF=0
Invokes
 
Invoked by
ExpEvalIdentifier PgmGlobalEntry PseudopcMACRO StmParse
ExpParseIdentifier Procedure IdTxtPtr, IdTxtEnd, Fullstops
      MOV ESI,[%TxtPtr]
      MOV EDX,[%TxtEnd]
      MOV ECX,[%Fullstops]
      CMP ESI,EDX
      JNB .10:
      LODSB
      ExpClassify AL
      TEST AH,expLetter
      JNZ .20:
      JECXZ .10: ; If fullstops not allowed.
      CMP AL,'.'
      JE .20:
      DEC ESI
 .10: SUB ESI,ESI ; Error.
      STC
      JMP .90:
 .20: CMP ESI,EDX
      JNB .80:
      LODSB
      ExpClassify AL
      TEST AH, expLetter | expDigit
      JNZ .20:
      JECXZ .30:
      CMP AL,'.'
      JE .20:
 .30: DEC ESI
 .80: SUB ESI,[%TxtPtr]
 .90: MOV [%ReturnEAX],ESI
     EndProcedure ExpParseIdentifier
↑ ExpParseKeyName KeyPtr, KeyEnd
ExpParseKeyName checks if the input text is a keyword, i.e. identifier immediately followed with =.
Input
KeyPtr Pointer to input text. I must not be empty.
KeyEnd pointer where the parsing must stop.
Output
CF=0
CF=0 EAX= pointer right behind the equal sign. Always between KeyPtr and KeyEnd.
Error
CF=1 EAX= pointer to nonalphanumeric character which terminated the identifier, and which is not =.
Example
KeyPtr KeyEnd | | List= off ; Do not list. | EAX, CF=0
Invoked by
EaIniAssemble EaMain
ExpParseKeyName Procedure KeyPtr, KeyEnd
      MOV ESI,[%KeyPtr]
      MOV EDX,[%KeyEnd]
 .10: CMP ESI,EDX
      JNB .Error:
      LODSB
      MOV [%ReturnEAX],ESI
      ExpClassify AL
      TEST AH,expLetter|expDigit
      JNZ .10:
      CMP AL,'='
      JE .90:
      DEC ESI
.Error:MOV [%ReturnEAX],ESI
      STC
 .90:EndProcedure ExpParseKeyName
↑ ExpParseKeyValue ValPtr, ValEnd
ExpParseKeyValue returns trimmed value specified with ValPtr and ValEnd. The value is terminated with unquoted comma , semicolon ; or EOL.
Input
ValPtr Pointer to the parsed text.
ValEnd pointer where the parsing must stop.
Output
CF=0
ESI= pointer to the start of value. May point to leading " if the value is quoted.
ECX= size of the value. Leading and trailing white spaces are stripped off.
Error
CF=1. ESI,ECX specifies the whole input text (open quote etc).
Example
ValPtr ValEnd | | ErrNr= "5000" + 3 ; Comment. |<--ECX-->| ESI
Invoked by
EaIniAssemble EaMain
ExpParseKeyValue Procedure ValPtr, ValEnd
     MOV EDX,[%ValEnd]
     MOV ESI,[%ValPtr]
     MOV ECX,EDX
     MOV EDI,ESI
     SUB ECX,ESI
     MOV [%ReturnESI],ESI
     MOV [%ReturnECX],ECX
 .10:CMP ESI,EDX
     JNB .80:
     LODSB
     CMP AL,','
     JE .70:
     CMP AL,';'
     JE .70:
     CMP AL,'"'
     JE .20:
     CMP AL,"'"
     JNE .10:
 .20:MOV AH,AL
 .30:CMP ESI,EDX
     CMC
     JC  .90:
     LODSB
     CMP AL,AH
     JNE .30:
     JMP .10:
 .70:DEC ESI
 .80:SUB ESI,EDI
     StripSpaces EDI,ESI
     MOV [%ReturnESI],EDI
     MOV [%ReturnECX],ESI
.90:EndProcedure ExpParseKeyValue
↑ ExpParseLiteral TxtPtr, TxtEnd
ExpParseLiteral checks if the text can be a literal symbol, i.e. it begins with = followed with optional duplication and then with short or long datatype name B,U,W,D,Q,T,O,Y,Z,I,S,BYTE,UNICHAR,WORD,DWORD,QWORD,TBYTE,OWORD,YWORD,ZWORD,INSTR or structure name or followed with a quoted string.
Text behind the datatype (literal value) is not evaluated, only simplified parsing is used until unbalanced unquoted ) or TextEnd is reached.
Input
TxtPtr Pointer to the leading equal sign =.
TxtEnd where the parsing must stop.
Output
CF=0
EAX= behind the parsed literal. Never above TxtEnd.
Error
CF=1 if the text is not a valid literal.
EAX=0
Example
TxtPtr TxtEnd | | MOV ESI,(=D (15*60)+5)+4 | EAX, CF=0 More valid literals: =B"text" =4*T#ZERO ="ANSI or WIDE characters"
See also
SymCreateLiteral
Invokes
ExpParseDatatype
Invoked by
ExpEval
ExpParseLiteral Procedure TxtPtr, TxtEnd
     MOV ESI,[%TxtPtr]
     MOV EDX,[%TxtEnd]
 .10:CMP ESI,EDX
     JNB .NotFound:
     LODSB
     ExpClassify AL
     TEST AH,expWhiteSpace
     JNZ .10:
     CMP AL,'=' ; Literal marker =.
     JNE .NotFound:
.expWhiteSpace:
     CMP ESI,EDX
     JNB .NotFound:
     LODSB
     ExpClassify AL
     Dispatch AH,expWhiteSpace,expQuote
     DEC ESI
     Invoke ExpParseDatatype,ESI,EDX ; Possible literal without duplication.
     JNC .50:
     ; Possible literal with duplication, e.g. =2*2*BYTE 2*2. Search for unquoted *.
.20: CMP ESI,EDX
     JNB .NotFound:
     LODSB
.25: Dispatch AL,0x2A,0x22,0x27 ; Asterix, quote, apostroph.
     JMP .20:
.expQuote: ; Possible string literal without datatype.
     MOV AH,AL
.30: CMP ESI,EDX
     JNB .NotFound:
     LODSB
     CMP AL,AH ; Ending quote?
     JNE .30:
     CMP ESI,EDX
     JE .Found:
     JA .NotFound:
     LODSB
     CMP AL,AH
     JE .30:  ; Selfescaped quote detected.
     JMP .FoundMinus1: ; Recognized literal = "string" or ='O''Hara'.
.0x22: ; Double quote.
.0x27: ; Single quote (apostoph).
     MOV AH,AL
.35: CMP ESI,EDX
     JNB .NotFound:
     LODSB
     CMP AL,AH
     JNE .35:
     CMP ESI,EDX
     JNB .NotFound:
     LODSB
     CMP AL,AH
     JE .35:
     JMP .25:
.0x2A: ; Asterix, possible duplication operator.
     Invoke ExpParseDatatype,ESI,EDX
     JC .20:
.50: ; Literal recognized with possible value. ESI points behind the datatype.
     ; Value ends at EDX=TxtEnd or at unmatched unquoted right parenthesis.
     SUB ECX,ECX ; Parenthesis nesting level.
     MOV BX,'()'
.60: CMP ESI,EDX
     JNB .Found:
     LODSB
     Dispatch AL,BH,BL,0n34,0n39 ; Left, right parenthesis, quote, apostrophe.
     JMP .60:
.0n34: ; Double quote.
.0n39: ; Single quote (apostroph).
     MOV AH,AL
.70: CMP ESI,EDX
     JNB .NotFound:
     LODSB
     CMP AL,AH
     JNE .70:
     JMP .60:
.BL: INC ECX ; Left parenthesis will increase nesting level.
     JMP .60:
.BH: JECXZ .FoundMinus1: ; Right parenthesis will stop parser, if not nested.
     DEC ECX  ; Right parenthesis will increase nesting level.
     JMP .60:
.NotFound:SUB EAX,EAX
     MOV [%ReturnEAX],EAX
     STC
     JMP .90:
.FoundMinus1:
     DEC ESI
.Found:
     MOV [%ReturnEAX],ESI
     CLC
 .90:EndProcedure ExpParseLiteral
↑ ExpParseNumber NumPtr, NumEnd
ExpParseNumber will parse and recognize format of a number in binary, octal, decimal, hexadecimal and floating-point notation and evaluate it as a signed 64bit integer.
Floating-point number is converted here to 64bit integer, too. Special FP values #ZERO evaluates to 0, #INF and #NAN will set CF.
Input
NumPtr Pointer to the first character of the number. This must be a decimal digit 0..9.
NumEnd where the parsing stops.
Output
CF= evaluated number overflowed 64 bits.
SF= result is negative.
ZF= result is 0 or underflowed.
OF= Overflow (ZF=0) or underflow (ZF=1) occured during float-to-integer conversion.
PF= precision lost during float-to-integer conversion.
EDX:EAX= value of the parsed number as a signed integer.
ESI= pointer to the character following the parsed number. Always between TxtPtr..TxtEnd.
Error
Only that many characters are parsed which are valid number.
Example
NumPtr NumEnd | | 0010_1011b+5678 | ESI CF=ZF=SF=OF=PF=0 EDX=0 EAX=2Bh NumPtr NumEnd | | 0xFE25015Axyz | ESI CF=ZF=SF=OF=PF=0 EDX=0 EAX=FE25015Ah
Invokes
ExpParseFP
Invoked by
ExpEval
Tested by
t1410 t1420 t1430 t1440 t1445 t1450
ExpParseNumber Procedure NumPtr, NumEnd
.flagPrefix EQU 2 ; This unused EFlag bit is employed as presence marker of prefix 0x,0y,0n,0o.
     PUSHFD
     RstSt [ESP],flagO+flagS+flagZ+flagP+flagA+flagC+.flagPrefix ; Initialize flags to 0.
     MOV ESI,[%NumPtr]
     MOV EDX,[%NumEnd]
     MOV [%ReturnESI],ESI ; Initialize parsed position.
     XOR EAX,EAX
     MOV [%ReturnEAX],EAX ; Initialize returned integer.
     MOV [%ReturnEDX],EAX
     LEA EAX,[ESI+2]
     CMP EAX,EDX
     JA .0x: ; If number prefix not present. 
     LODSW
     OR AH,'x'^'X' ; Convert possible prefix modifier to lowercase.
     SetSt [ESP],.flagPrefix
     Dispatch AX,'0x','0o','0y','0n'
     RstSt [ESP],.flagPrefix
     DEC ESI,ESI ; Reset parser pointer back when no prefix used.
.0x: ; Assume hexadecimal format. Suffix 'H' is required if no prefix.
     XOR EBX,EBX ; Number will be temporary adopted to EDI:EBX.
     XOR EDI,EDI
.0x1:CMP ESI,EDX
     JNB .0x8:
     LODSB
     CMP AL,'_'
     JE .0x1:
     CMP AL,'0'
     JB .0x2:
     CMP AL,'9'
     JBE .0x3:
.0x2:OR AL,'h'^'H' ; Convert AL to lowercase.
     CMP AL,'a'
     JB .0x7:
     CMP AL,'f'
     JA .0x7:
     SUB AL,'a'-10
.0x3:; Adopt AL as hexadecimal digit to EDI:EBX.
     AND EAX,0x0000_000F
     MOV ECX,4
.0x4:SHL EBX
     RCL EDI
     JNC .0x5:
     SetSt [ESP],flagA ; Hexadecimal format overflowed but keep parsing on.
.0x5:LOOP .0x4:
     ADD EBX,EAX
     JMP .0x1:
.0x7:CMP AL,'h'
     JE .0x9: ; If postfix 'H' present, number is hexadecimal.
     DEC ESI
.0x8:JNSt [ESP],.flagPrefix,.0e: ; Not hexadecimal, try the next format.
.0x9:JSt [ESP],flagA,.Overflow:
     JMP .Done:
.0e: ; No prefix, no suffix, hence no hexa. Try floating-point format.
     Invoke ExpParseFP,[%NumPtr],[%NumEnd],'T'
     JC .0o: ; If syntax error, try octal format.
     PUSHFD
     POP EDI
     OR [ESP],EDI ; Propagate flags returned from ExpParseFP to this procedure.
     JSt EDI,flagZ, .Done: 
     MOV EDI,ECX ; Save FP signum (bit 15).
     ; Convert returned FP number CX:EDX:EAX to 64bit integer.
     BTR ECX,15 ; Reset FP number sign.
     NEG ECX
     ADD ECX,16383+63 ; Number of bits to right-shift mantissa to get 64bit integer.
     JS .Overflow:
     CMP ECX,63
     JNA .0e2:
     SetSt [ESP],flagO+flagZ ; Signalize underflow on fp-integer conversion.
     JMP .Done: ; Return zero.
.0e2:SHR EDX
     RCR EAX
     JNC .0e3:
     SetSt [ESP],flagP ; Signalize precision lost.
.0e3:LOOP .0e2:
     TEST EDX
     JS .Overflow:
     ; EDX:EAX is now positive 64bit signed integer. 
     BT EDI,15 ; Saved sign of FP number.
     JNC .0e5: ; If not minus, skip the negation.
     NOT EAX
     NOT EDX
     ADD EAX,1
     ADC EDX,0 
.0e5:XCHG EBX,EAX
     XCHG EDI,EDX
     JMP .Done:
.0o: ; Assume octal format. Suffix 'Q' is required if no prefix.
     RstSt [ESP],flagA
     XOR EBX,EBX ; Number will be temporary adopted to EDI:EBX.
     XOR EDI,EDI
     MOV EDX,[%NumEnd]
     MOV ESI,[%NumPtr]  ; Reset parsing position.
     JNSt [ESP],.flagPrefix,.0o1:
     INC ESI,ESI
.0o1:CMP ESI,EDX
     JNB .0o8:
     LODSB
     CMP AL,'_'
     JE .0o1:
     CMP AL,'0'
     JB .0o7:
     CMP AL,'7'
     JA .0o7:
     AND EAX,0x0000_0007 ; Adopt AL as octal digit to EDI:EBX.
     MOV ECX,3
.0o3:SHL EBX
     RCL EDI
     JNC .0o4:
     SetSt [ESP],flagA  ; Octal format overflowed but keep parsing on.
.0o4:LOOP .0o3:
     ADD EBX,EAX
     JMP .0o1:
.0o7:OR AL,'q'^'Q' ; Convert AL to lowercase.
     CMP AL,'q'
     JE .0o9: ; If postfix 'Q' present, number is octal.
     DEC ESI
.0o8:JNSt [ESP],.flagPrefix, .0y:
.0o9:JSt [ESP],flagA,.Overflow:
     JMP .Done:

.0y: ; Assume binary format. Suffix 'B' is required if no prefix.
     RstSt [ESP],flagA
     XOR EBX,EBX ; Number will be temporary adopted to EDI:EBX.
     XOR EDI,EDI
     MOV ESI,[%NumPtr]  ; Reset parsing position.
     JNSt [ESP],.flagPrefix,.0y1:
     INC ESI,ESI
.0y1:CMP ESI,EDX
     JNB .0y8:
     LODSB
     CMP AL,'_'
     JE .0y1:
     CMP AL,'0'
     JB .0y7:
     CMP AL,'1'
     JA .0y7:
     AND EAX,0x0000_0001 ; Adopt AL as binary digit to EDI:EBX.
     SHL EBX
     RCL EDI
     JNC .0y5:
     SetSt [ESP],flagA
.0y5:ADD EBX,EAX
     JMP .0y1:
.0y7:OR AL,'b'^'B' ; Convert AL to lowercase.
     CMP AL,'b'
     JE .0y9:
     DEC ESI
.0y8:JNSt [ESP],.flagPrefix, .0n:
.0y9:JSt [ESP],flagA,.Overflow:
     JMP .Done:

.0n: ; Assume decadic format. Suffix 'D','K','M','G','T','P' is optional.
     RstSt [ESP],flagA
     XOR EBX,EBX ; Number will be temporary adopted to EDI:EBX.
     XOR EDI,EDI
     MOV ESI,[%NumPtr]  ; Reset parsing position.
     JNSt [ESP],.flagPrefix,.0n1:
     INC ESI,ESI
.0n1:CMP ESI,EDX
     JNB .0n9:
     LODSB
     CMP AL,'_'
     JE .0n1:
     CMP AL,'0'
     JB .0n7:
     CMP AL,'9'
     JA .0n7:
     AND EAX,0x0000_000F ; Adopt AL as decimal digit to EDI:EBX.
     MOV ECX,10 ; Multiply previous contents of EDI:EBX by ten.
     XCHG EDX,ECX ; Temporary save parsing limit to ECX.
     XCHG EAX,EDI ; Multiply higher dword first.
     MUL EDX
     JNC .0n2:
     SetSt [ESP],flagA
.0n2:XCHG EDI,EAX ; EDI=high*10.
     MOV EDX,10
     XCHG EAX,EBX ; Multiply lower dword.
     MUL EDX
     ADD EDI,EDX
     JNC .0n3:
     SetSt [ESP],flagA
.0n3:XCHG EBX,EAX ; EBX=low*10.
     ADD EBX,EAX ; Adopt the saved digit.
     ADC EDI,0
     JNC .0n4:
     SetSt [ESP],flagA
.0n4:XCHG EDX,ECX ; Restore saved parsing limit.
     JMP .0n1:
.0n7:OR AL,'d'^'D' ; Convert AL to lowercase.
     SUB ECX,ECX
     Dispatch AL,'k','m','g','t','p','d'
     DEC ESI ; No postfix.
     JMP .0n9:
.Overflow:
     SetSt [ESP],flagC+flagO
     RstSt [ESP],flagZ+flagS+flagA
     MOV EBX,-1
     MOV EDI,0x7FFF_FFFF
     JMP .Done:
.p:  ADD CL,10     
.t:  ADD CL,10
.g:  ADD CL,10
.m:  ADD CL,10
.k:  ADD CL,10
.d:  JECXZ .Done:
.0n8:SAL EBX
     RCL EDI
     JC .Overflow:
     LOOP .0n8:
.0n9:JSt [ESP],flagA,.Overflow:
.Done:
     MOV [%ReturnEAX],EBX
     MOV [%ReturnEDX],EDI
     MOV [%ReturnESI],ESI
     RstSt [ESP],.flagPrefix
     TEST EDI
     JNS .D2:
     SetSt [ESP],flagS
.D2: OR EBX,EDI
     JNZ .D3:
     SetSt [ESP],flagZ
.D3: POPFD
    EndProcedure ExpParseNumber
↑ ExpParseOperator TxtPtr, TxtEnd, Arity
ExpParseOperator will parse input text and look for the operator with longest possible notation.
Input
TxtPtr Pointer to the first char of the operator. Must classify as expOperator.
TxtEnd Where the parsing stops.
Arity Expected type of operator, either dictBinary or dictUnary.
Output
CF=0
EAX= DictOperators.Data contents.
ESI= Behind the last parsed character.
Error
CF=1 No such operator found in dictionary of operators.
AL= unexpected character
ESI=TxtPtr
Example
; TxtPtr TxtEnd ; | | ParsedText DB "3+-5" ; | ; On output ESI Invoke ExpParseOperator, ParsedText+1, ParsedText+SIZE#ParsedText, dictBinary ; will return EAX=6<<16 + 9 ; Priority of Addition=9, ordinal of Addition=6
Invoked by
ExpEval
ExpParseOperator Procedure TxtPtr, TxtEnd, Arity
Operator LocalVar Size=4 ; Local copy. Max.size of operator is 4.
      LEA EDI,[%Operator]
      MOV ESI,[%TxtPtr]
      MOV ECX,[%TxtEnd]
      MOV [%ReturnESI],ESI
      SUB ECX,ESI
      CMP ECX,4
      JNA .10:
      MOV ECX,4
 .10: MOV [EDI],ECX ; Clear higher bytes.
      REP MOVSB
      MOV AL,[ESI] ; Unexpected character on error.
      MOV EBX,DictBinaryOperators:: - SIZE#DICT
      TESTD [%Arity],dictUnary
      JZ .50:
      MOV EBX,DictUnaryOperators:: - SIZE#DICT
 .50: ADD EBX,SIZE#DICT
      LEA EDI,[%Operator]
      MOV ECX,[EBX+DICT.Size]
      MOV ESI,[EBX+DICT.Ptr]
      STC
      JECXZ .80: ; End of dictionary. CF=1
      MOV EDX,ECX
      REPE CMPSB
      JNE .50:
      MOV EAX,[EBX+DICT.Data] ; Operator found.
      ADD [%ReturnESI],EDX ; CF=0
.80:  MOV [%ReturnEAX],EAX
.90: EndProcedure ExpParseOperator
↑ ExpParseRange TxtPtr, TxtEnd
A range is represented with two arithmetic expressions separated with range operator. ExpParseRange looks for the range operator .. (two adjacent unquoted fullstops) in input text.
Input
TxtPtr Pointer to the first character of the left expression.
TxtEnd Pointer behind the last character of the right expression.
Output
CF=0 if range operator exists.
EAX= Pointer behind the range operator in input text.
CF=1 if the text does not contain range operator.
EAX= Pointer to the end of left expression, identical with TxtEnd.
Example
TxtPtr TxtEnd | | 2+3.. 17 | EAX CF=0 TxtPtr TxtEnd | | OrdNumber-1 | EAX CF=1
Invoked by
ChunkSuboperate CtxForNext EaoptAssemble PfSuboperate VarSuboperate
ExpParseRange Procedure TxtPtr, TxtEnd
     MOV ESI,[%TxtPtr]
     MOV EDX,[%TxtEnd]
.10: CMP ESI,EDX
     JNB .70:
     LODSB
     CMP AL,'.'
     JE .60:
.20: CMP AL,'"'
     JNE .40:
.30: CMP ESI,EDX
     JNB .70:
     LODSB
     CMP AL,'"'
     JNE .30:
     JMP .10:
.40: CMP AL,"'"
     JNE .10:
.50: CMP ESI,EDX
     JNB .70:
     LODSB
     CMP AL,"'"
     JNE .50:
     JMP .10:
.70: STC
     JMP .90:
.60: CMP ESI,EDX
     JNB .70:
     LODSB
     CMP AL,'.'
     JNE .20:
.90: MOV [%ReturnEAX],ESI
    EndProcedure ExpParseRange
↑ ExpParseString TxtPtr, TxtEnd
ExpParseString will parse quoted string or character constant. The string must have all %variable expanded. Any character except LineFeed may occur inside the string. Demarcation quotes inside the string must be doubled, e.g. 'It''s five o''clock.'
Input
TxtPtr pointer to the leading single or double quote.
TxtEnd where the parsing stops.
Output
CF=0
EAX= netto size of the string in bytes.
ESI= points to the character following the closing quote.
Error
CF=1
EAX=0 ; This should report E6160 Syntax error in the string !1S.'
ESI= pointer behind the last parsed character.
Example
TxtPtr TxtEnd | | 'It''s five o''clock ','she said.' | CF=0 EAX=18 ESI
Invoked by
ExpEval ExpEvalBoolean
ExpParseString Procedure TxtPtr, TxtEnd
      MOV ESI,[%TxtPtr]
      MOV EDX,[%TxtEnd]
      SUB ECX,ECX ; Netto size counter.
      CMP ESI,EDX
      JNB .Error:
      LODSB
      MOV AH,AL ; Opening quote.
 .20: CMP ESI,EDX
      JNB .Error:
      LODSB
      INC ECX
      CMP AL,AH
      JNE .20:
      DEC ECX
      CMP ESI,EDX
      JNB .End:
      LODSB
      INC ECX
      CMP AL,AH
      JE .20: ; If selfescaped quote.
      DEC ECX
      DEC ESI
      CLC
      JMP .End:
.Error:SUB ECX,ECX
      STC   
.End: MOV [%ReturnEAX],ECX
      MOV [%ReturnESI],ESI
     EndProcedure ExpParseString
↑ ExpParseSuboperation TxtPtr, TxtEnd
Text should start with opening brace [ or {, otherwise ExpParseSuboperation returns error. It will find the corresponding unquoted closing brace ] or }.
Input
TxtPtr pointer to the opening suboperation bracket.
TxtEnd where the parsing stops.
Output
CF=0
ESI= pointer behind the corresponding closing suboperation bracket ] or }, never above TxtEnd.
Error
CF=1 if opening or closing bracket was not found.
ESI= TxtEnd
Example
TxtPtr TxtEnd | | [%AsciiTab[91.."]"]..%&]{1} | ESI CF=0
Invoked by
ChunkSuboperate PfSuboperate VarSuboperate
ExpParseSuboperation Procedure TxtPtr, TxtEnd
     MOV ESI,[%TxtPtr]
     MOV EDX,[%TxtEnd]
     SUB ECX,ECX ; Nesting level.
     CMP ESI,EDX
     JNB .Error:
     LODSB ; Opening bracket.
     CMP AL,'['
     JE .10:
     CMP AL,'{'
     JNE .ErrB:
.10: INC ECX
     MOV BL,AL ; Opening bracket in BL.
     MOV BH,AL
     ADD BH,2  ; Closing bracket in BH.
.20: CMP ESI,EDX ; Not in quotes.
     JNB .Error:
     LODSB
     CMP AL,BH
     JNE .30:
     DEC ECX
     JZ .90:
     JMP .20:
.30: CMP AL,BL
     JNE .40:
     INC ECX
     JMP .20:
.40: CMP AL,'"'
     JE .50:
     CMP AL,"'"
     JNE .20:
.50: ; Opening quote in AL.
     MOV AH,AL
.60: CMP ESI,EDX ; In quotes.
     JNB .Error:
     LODSB
     CMP AL,AH
     JNE .60:
     JMP .20:
.ErrB:DEC ESI
.Error:STC
.90: MOV [%ReturnESI],ESI
    EndProcedure ExpParseSuboperation
↑ ExpStoreString StringPtr, StringSize, Buffer, Uppercase
ExpStoreString will store contents of the string in quoted source notation to a buffer. Preprocessing %variables must have been already expanded but quotes inside the string remain doubled.
Input
StringPtr Pointer to string notation (opening apostrophe or double quote).
StringSize brutto size of the string.
Buffer Pointer to a buffer where the result will be stored.
Uppercase if nonzero, characters a..z will be converted to A..Z.
Output
CF=0
EAX= netto size of the string on buffer.
Error
CF=1
EAX= '6160' - Syntax error in the string !1S.
Example
Input string: 'It''s 100 % true.', brutto size=19. Output string:It's 100 % true., netto size=16.
See also
  ExpStoreUString.
Invoked by
ExpEval ExpEvalData ExpStoreInstr
Tested by
t1345 t1360 t2280
ExpStoreString Procedure StringPtr, StringSize, Buffer, Uppercase
     MOV ESI,[%StringPtr]
     MOV ECX,[%StringSize]
     MOV EBX,[%Uppercase]
     LEA EDX,[ESI+ECX]
     SUB ECX,ECX ; Netto size.
     LODSB
     CMP AL,0x22 ; Double quote.
     JE .20:
     CMP AL,0x27 ; Single apostrophe.
     JNE .E6160:
 .20:MOV AH,AL
 .30:CMP ESI,EDX
     JNB .E6160:
     LODSB
     CMP AL,AH
     JNE .60:
     CMP ESI,EDX
     JNB .80:
     LODSB
     CMP AL,AH
     CLC
     JNE .80:
 .60:TEST EBX ; Uppercase?
     JZ .70:
     CMP AL,'a'
     JB .70:
     CMP AL,'z'
     JA .70:
     XOR AL,'a'-'A' ; Convert to uppercase.
 .70:PUSH EAX
      MOV EDI,ESP ; pointer to the converted character.
      BufferStore [%Buffer],EDI,1
     POP EAX
     INC ECX
     JMP .30:
.E6160:MOV ECX,'6160'
     STC
 .80:MOV [%ReturnEAX],ECX
.99:EndProcedure ExpStoreString
↑ ExpStoreUString StringPtr, StringSize, Buffer

ExpStoreUString will convert the byte string to wide Unicode characters and store them to output buffer. Input string is in source notation (in single or double quotes). Those quotes withing the string must be doubled and all preprocessing %variables expanded. Current Ea.Eaopt.Codepage decides how are the bytes translated.

If the source String is in CODEPAGE=UTF-8, characters are translated by macro DecodeUTF8 . Invalid characters are replaced and stored as U+FFFD.

In non-UTF8 codepage are the characters translated by Ea.CodeTable . This conversion table is constructed on the fly whenever the desired Ea.Eaopt.Codepage is different from the cached codepage identified by Ea.CodePage . Otherwise the conversion table is reused in this procedure.

Input
StringPtr Pointer to the source string (left-border apostrophe or double quote).
StringSize Brutto size of the string (including both quotes).
Buffer Pointer to a buffer where the result will be stored.
Output
EAX= netto size in bytes of the converted UNICHAR string stored in output buffer.
CF=0, ZF=1
Error
W3165 Could not load codepage !1D reported by macro Msg. Other errors are not reported but indicated by flags:
ZF=0 if at least one character was invalid and replaced with U+FFFD . Warning W3160 should be reported.
CF=1 if syntax error was detected in the string. E6160 should be reported.
See also
  ExpStoreString, SysANSI2Wide.
Invoked by
ExpEvalData
Tested by
t1346 t1348 t1360 t2280
[.text]
ExpStoreUString Procedure StringPtr, StringSize, Buffer
QuoteChar      LocalVar             ; Single or double border quote in LSB. Bit 31 used as flag.
ReplacementCnt LocalVar             ; Counter how many replacement characters were used.
ANSItable     LocalVar Size=128    ; Template table of 8bit ANSI characters 0x80..0xFF.
      MOV EDX,[Ea.Eaopt.CodePage::] ; Requested codepage.
      SUB EAX,EAX
      MOV [%ReplacementCnt],EAX
      MOV [%ReturnEAX],EAX
      CMP EDX,65001                 ; CP 65001 is UTF-8.
      JE .20:                       ; Other CP are translated using Ea.CodeTable.
      CMP EDX,[Ea.CodePage::]       ; Is the conversion table already constructed?
      JE .20:                       ; If Ea.CodeTable: already contains translation table, skip.
      ; Construction of translate table for codepage EDX.
      MOV [Ea.CodePage::],EDX
      LEA EDI,[%ANSItable]
      MOV ECX,128
      MOV EAX,ECX
      MOV ESI,EDI
 .10: STOSB                 ; Create template ANSI table with characters 0x80..0xFF.
      INC AL
      JNZ .10:
      SysANSI2Wide EDX,ESI,ECX,Ea.CodeTable::,ECX ; Translate ANSI table to WIDE table, using OS.
      Msg cc=Z,'3165',EDX   ; Could not load codepage !1D.
 .20: MOV ECX,[%StringSize] ; Check the string quotes.
      MOV ESI,[%StringPtr]  ; ESI,ECX must be claimed with quotes.
      CMP ECX,2
      JB .E6160:            ; Syntax error in the string !1S.
      DEC ECX
      MOVZXB EAX,[ESI+ECX]  ; AL is now the closing quote.
      MOV [%QuoteChar],EAX
      LODSB                 ; AL is now the opening quote.
      CMP EAX,[%QuoteChar]
      JNE .E6160:           ; Quotes don't match.
      DEC ECX
      JZ .90:               ; If empty string, done.
      CMP EDX,65001
      JE  .60:              ; If CODEPAGE=UTF-8.
      MOV EBX,Ea.CodeTable::; Translate string ESI,ECX in non-UTF8 codepage by the table EBX.
 .30: SUB EAX,EAX
      LODSB
      CMP AL,[%QuoteChar]   ; Is it a quote inside the string?
      JNE .40:
      DEC ECX
      JZ .E6160:
      LODSB                 ; Quote inside the string must be doubled.
      CMP AL,[%QuoteChar]
      JNE .E6160:           ; If unescaped quote detected.
 .40: CMP AL,128            ; If AL is 7bit ASCII,
      JB .50:               ;   it is zero-extended to Unichar and stored,
      MOV AX,[EBX+2*EAX-256];   otherwise translated by the table EBX.
 .50: BufferStoreWord [%Buffer],EAX
      ADDD [%ReturnEAX],2
      DEC ECX
      JNZ .30:
      JMP .90:
.E6160:STC    ; 6160 Syntax error in the string !1S.
      JMP .99:
 .60: ; UTF-8 conversion to 16bit Unicode uses an algorithm in macro DecodeUTF8.
      DecodeUTF8 ESI, Size=ECX, .StoreUTF16:
.StoreUTF16:PROC1 ; Callback to store decoded Unichar from AX.
              CMP AX,0xFFFD
              JNE .Chk:
              INCD [%ReplacementCnt]
        .Chk: MOV EBX,[%QuoteChar] ; Bit 31 is quote-escape pending flag.
              CMP AX,BX    ; Is the decoded unichar AX identical with quote BX?
              JNE .Out:    ; Just store ordinary character if not.
              BTS EBX,31   ; Check if the quote was escaped and then raise pending flag.
              JNC .End:    ; Do not store the first occurence of quote.
        .Out: BufferStoreWord [%Buffer],EAX ; Store unichar in AX.
              ADDD [%ReturnEAX],2
              BTR EBX,31   ; Clear pending flag, if set.
        .End: MOV [%QuoteChar],EBX
              CLC
              RET
             ENDPROC1 .StoreUTF16:
 .90: CMPD [%ReplacementCnt],0 ; NZ if bad UTF-8 characters.
 .99:EndProcedure ExpStoreUString
↑ ExpWidth
Procedure ExpWidth calculates bytes required to accomodate input integer number.
Input
EDX:EAX= Input integer number.
Output
ECX=expWidth constant (3..7)
Error
-
See also
ExpWidthSigned, ExpWidthBitwise
Invoked by
ExpConvertToNumber ExpEval ExpEvalData ExpEvalIdentifier ExpParseAlignment PseudoEQU
ExpWidth Procedure
     MOV ECX,expWidth8B ; Assume 64bits.
     TEST EDX
     JNZ .50:
     ; EDX=0, 64bit not necessary.
     MOV CL,expWidth0B
     TEST EAX
     JZ .90:
     INC ECX ; expWidth1B
     TEST EAX,0xFFFFFF00
     JZ .90:
     INC ECX ; expWidth2B
     TEST EAX,0xFFFF0000
     JZ .90:
     INC ECX ; expWidth4B
     JMP .90:
 .50:INC EDX
     JNZ .90:
     ; EDX was 0xFFFFFFFF, 64bit might be not necessary.
     NOT EAX
     MOV CL,expWidth1B
     TEST EAX,0xFFFFFF80
     JZ .90:
     INC ECX ; expWidth2B
     TEST EAX,0xFFFF8000
     JZ .90:
     INC ECX ; expWidth4B
     TEST EAX,0x80000000
     JZ .90:
     INC ECX ; expWidth8B
.90: MOV [%ReturnECX],ECX
     EndProcedure ExpWidth
↑ ExpWidthBitwise
ExpWidthBitwise calculates bytes required to accomodate input unsigned integer number.
Input
EDX:EAX= Input unsigned integer number.
Output
ECX=expWidth constant (3..7)
Error
-
Invoked from
IiImmSize
See also
ExpWidth, ExpWidthSigned
Invoked by
IiFlush
ExpWidthBitwise Procedure
     MOV ECX,expWidth8B ; Assume 64bits.
     TEST EDX
     JZ .50: ; If EDX=0, 64bit not necessary.
     INC EDX
     JNZ .90:
     ; EDX was 0xFFFFFFFF, 64bit is not necessary.
     NOT EAX
 .50:BSR EBX,EAX
     MOV CL,expWidth0B
     JZ .90: ; If EAX=0.
     INC ECX ; expWidth1B
     CMP BL,8
     JB .90:
     INC ECX ; expWidth2B
     CMP BL,16
     JB .90:
     INC ECX ; expWidth4B
.90: MOV [%ReturnECX],ECX
     EndProcedure ExpWidthBitwise
↑ ExpWidthSigned
ExpWidth calculates bytes required to accomodate input signed integer number.
Input
EDX:EAX= Input integer number.
Output
ECX=expWidth constant (3..7)
Error
-
See also
 ExpWidth, ExpWidthBitwise
Invoked by
IiCompressDisp8 IiRelocSizeRIP RelocResolveImage RelocResolveObject
ExpWidthSigned Procedure
     MOV ECX,expWidth8B ; Assume 64bits.
     TEST EDX
     JNZ .50:
     MOV CL,expWidth0B
     TEST EAX
     JZ .90:
     JMPS .60:
 .50:INC EDX
     JNZ .90: ;
     ; EDX was 0xFFFFFFFF, 64bit might be not necessary.
     NOT EAX
 .60:MOV CL,expWidth1B
     TEST EAX,0xFFFFFF80
     JZ .90:
     INC ECX ; expWidth2B
     TEST EAX,0xFFFF8000
     JZ .90:
     INC ECX ; expWidth4B
     TEST EAX,0x80000000
     JZ .90:
     INC ECX ; expWidth8B
.90: MOV [%ReturnECX],ECX
     EndProcedure ExpWidthSigned
↑ ExpWidthOfDataType Datatype
ExpWidthOfDataType returns the amount of bytes necessary to accomodate Datatype.
Input
Datatype Short datatype in LSB: 'B','U','W','D','Q','T','O','Y','Z'.
Output
EAX= expWidth (3..7), one of expWidth0B,expWidth1B,expWidth2B,expWidth4B or expWidth8B in EXP encoding.
ECX=size of the datatype in bytes (0..64).
Error
EAX=ECX=0 for other input Datatype.
See also
ExpWidth.
Invoked by
ExpEvalData SssCreate@LT
ExpWidthOfDataType Procedure Datatype
     MOV EDX,[%Datatype]
     SUB ECX,ECX
     AND DL,~('b'^'B') ; Convert to uppercase.
     MOV EAX,expWidth8B ; Width returned for QWORD and wider datatypes.
     Dispatch DL,'B','U','W','D','Q','T','O','Y','Z'
     MOV EAX,expWidth0B ;
     JMP .90:
 .Z: MOV CL,64
     JMP .90:
 .Y: MOV CL,32
     JMP .90:
 .O: MOV CL,16
     JMP .90:
 .T: MOV CL,10
     JMP .90:
 .Q: MOV CL,8
     JMP .90:
 .D: MOV EAX,expWidth4B
     MOV CL,4
     JMP .90:
 .U:
 .W: MOV EAX,expWidth2B
     MOV CL,2
     JMP .90:
 .B: MOV EAX,expWidth1B
     MOV CL,1
    ;JMP .90:
 .90:MOV [%ReturnECX],ECX
     MOV [%ReturnEAX],EAX
   EndProcedure ExpWidthOfDataType
↑ ExpStoreInstr InstrPtr, InstrSize, EmitBuf, RelocBuf, ParentStm
ExpStoreInstr will assemble one machine instruction provided as string operand of pseudoinstruction DI.
DI "INC ESI,EDI" will be assembled as DB 0x46,0x47
Input
InstrPtr pointer to string witch machine instruction (the opening quote).
InstrSize brutto size of the string, including both quotes.
EmitBuf Pointer to a buffer where the operation code will be stored.
RelocBuf Pointer to a buffer where the relocations requested by the machine instruction will be stored.
ParentStm is pointer to a STM with Data to evaluate. Used to let Instr create symbol from label.
Output
CF=0
EAX= netto size of the string on buffer.
Error
CF=1 Errors are reported with macro Msg.
Invokes
EaBufferRelease EaBufferReserve ExpStoreString IiAssemble IiAssembleMultiop StmCreate StmDestroy StmMultiop? StmParse
Invoked by
ExpEvalData
Tested by
t2515
ExpStoreInstr Procedure InstrPtr, InstrSize, EmitBuf, RelocBuf, ParentStm
EsiInstrBuf  LocalVar ; Temporary buffer for recursed assembly process.
EsiChunkLeaf LocalVar Size=4+4+SIZE#CHUNK ; Solo leaf of LIST.
EsiStm  LocalVar Size=SIZE#STM ; Fake statement with machine Instr.
     EaStackCheck ; Protect from SO.
     Invoke EaBufferReserve::,ExpStoreInstr
     MOV [%EsiInstrBuf],EAX
     ; Check the instruction string.     
     Invoke ExpStoreString,[%InstrPtr],[%InstrSize],EAX,0 ; Get rid of quotes in Instr.
     JNC .20:
.E6163:LEA EAX,[%InstrPtr]
     Msg '6163',EAX ; Invalid data-definition of machine instruction !1S.
     STC
     JMP .80:
.E6164:Msg '6164',EBX ;  Unexpected "!1S". Label in data definition INSTR is not suported.
     STC
     JMP .80:
 .20:BufferStoreByte [%EsiInstrBuf],10 ; Terminate instruction with LF.
     BufferRetrieve [%EsiInstrBuf] ; ESI,ECX is now fake statement line.
; Prepare environment for parsing and executing the machine instruction.
     LEA EDI,[%EsiChunkLeaf]
     XOR EAX,EAX
     ADD ECX,ESI
     STOSD ; LIST.Next. Simulate solo leaf with just one chunk for SrcFetchLine.
     STOSD ; LIST.Prev.
     MOV [EDI+CHUNK.Bottom],ESI
     MOV [EDI+CHUNK.Top],ECX
     MOV EAX,chunkSource
     MOV ECX,[%ParentStm]
     JECXZ .30:
     MOV ECX,[ECX+STM.ChunkPtr] ; Inherite chunk properties from parent statement.
     JECXZ .30:
     MOV EAX,[ECX+CHUNK.Status]
     MOV ECX,[ECX+CHUNK.FilePtr]
 .30:MOVD [EDI+CHUNK.FilePtr],ECX
     MOVD [EDI+CHUNK.Status],EAX
     LEA EBX,[%EsiStm]
     Invoke StmCreate::,EBX
     MOV [EBX+STM.ChunkPtr],EDI
     MOV ECX,[%ParentStm]
     JECXZ .35:
     ; Copy some properties from parent statement ECX to fake statement EBX.
     MOV EAX,[ECX+STM.OffsetLow]
     MOV EDX,[ECX+STM.OffsetHigh]
     MOV [EBX+STM.OffsetLow],EAX
     MOV [EBX+STM.OffsetHigh],EDX
     MOV EAX,[ECX+STM.Section]
     MOV EDX,[ECX+STM.Program]
     MOV [EBX+STM.Section],EAX
     MOV [EBX+STM.Program],EDX
     PUSH ESI
       MOV EAX,ECX
       BufferRetrieve [EBX+STM.EmitBuffer]
       MOV [EAX+STM.Size],ECX
       ADD [EAX+STM.OffsetLow],ECX
       ADCD [EAX+STM.OffsetHigh],0
     POP ESI
 .35:Invoke StmParse::,EBX,ESI,EDI
     JC .E6163:
     JSt  [EBX+STM.Status],stmLabelPresent,.E6164:
     JNSt [EBX+STM.Status],stmIntelOperation,.E6163:
     INCD [Ea.StmCount::] ; Counter of total assembled statements.
     CMPD [EBX+STM.NrOfOrdinals],1
     JNA .40:
     Invoke StmMultiop?::,EBX
     JNZ .40:
     Invoke IiAssembleMultiop::,EBX
     JMPS .50:
 .40:Invoke IiAssemble::,EBX 
 .50:BufferRetrieve [EBX+STM.EmitBuffer]
     BufferStore [%EmitBuf],ESI,ECX
     BufferRetrieve [EBX+STM.RelocBuffer]
     BufferStore [%RelocBuf],ESI,ECX
     MOV EDX,[EBX+STM.Status]
     Invoke StmDestroy::,EBX
     AND EDX,stmOperationPresent
     JNZ .80:
     STC ; Flag stmOperationPresent was reset in instruction handler due to error.
 .80:PUSHFD
       Invoke EaBufferRelease::,[%EsiInstrBuf]
     POPFD  
    EndProcedure ExpStoreInstr
↑ ExpParseChar Char, TextPtr, TextEnd
ExpParseChar searches for the occurence of unquoted %Char in the input text.
Input
Char contains the searched character in LSB, e.g. ')', ']'.
TextPtr pointer to the start of text.
TextEnd pointer behind the input text.
Output
CF=0 if the character found.
EAX= pointer to the searched character.
Error
CF=1 if the character not found.
EAX= %TextEnd
Example
TextPtr TextEnd Char=')' | | TYPE#(=2*Q 10) = 'D' | EAX CF=0 TextPtr TextEnd Char=']' | | TYPE#[(4*EAX+ESI+']']= 'D' | EAX CF=0
Invoked by
ExpEval
ExpParseChar Procedure Char, TextPtr, TextEnd
    MOV ESI,[%TextPtr]
    MOV EDX,[%TextEnd]
    MOV EBX,[%Char]
.10:CMP ESI,EDX
    JNB .NotFound:
    LODSB
    CMP AL,BL
    JE .Found:
    ExpClassify AL
    TEST AH, expQuote
    JZ .10:
    MOV AH,AL
.20:CMP ESI,EDX ; Skip up to the next quote.
    JNB .NotFound:
    LODSB
    CMP AL,AH
    JNE .20:
    JMP .10:
.NotFound:
    STC
    JMP .80:
.Found:
    DEC ESI
    CLC
.80:MOV [%ReturnEAX],ESI
  EndProcedure ExpParseChar
↑ ExpReportError Exp

Procedure ExpReportError is used to report errors detected during expression evaluation by ExpEval*

Input
Exp is pointer to an evaluated EXP object.
Output
CF=0, ZF=0 if the expression evaluated without error.
CF=0, ZF=1 if the expression is empty.
Error
CF=1 if Exp.Status type is '#'. Error message identified by Exp.Seg is reported with macro Msg.
Invoked by
ExpEvalBoolean ExpEvalData ExpEvalNum IiAssemble PfcomCompile PfomfStoreModule PgmEvalEntry PseudopcSETA PseudopcSETC
ExpReportError Procedure Exp
    MOV EBX,[%Exp]
    MOV ECX,[EBX+EXP.Status]
    CMP CL,0 ; Empty expression?
    JE .90:
    CMP CL,'#'
    CLC
    JNE .90: ; Do nothing when the Exp is not in error state.
    MOV EDX,[EBX+EXP.Seg] ; MsgId.
    TEST EDX
    JZ .80: ; Do not report error when MsgId=0.
    LEA ESI,[EBX+EXP.Low] ; !1S.
    MOV EDI,[EBX+EXP.Sym] ; !2O.
    SHR ECX,8             ; !3Z.
    ; Some errors can heal themselves in next passes, therefore they are reported in final pass only.
    CMP EDX,'6206'
    JE .50:
    CMP EDX,'6207'
    JE .50:
    CMP EDX,'6301'
    JE .50:
    Msg EDX,ESI,EDI,ECX
    JMPS .80:
.50:Msg EDX,ESI,EDI,ECX,PgmStatus=pgmLastPass
.80:STC
.90:EndProcedure ExpReportError
↑ ExpEval Exp, TxtPtr, TxtSize, Stm

Procedure ExpEval evaluates text containing numeric, logical or memory-addressing expression and puts the result into EXP structure. The evaluated text may also be immediate segment:offset pair, register of any family, memory-addressing expression with segment, base and scalled index register enclosed in braces [].
The text must have %variables expanded.

In phase one the text is parsed to elementary terms, such as number, register, operator, (EXP structure instances) which are temporarily stored in %ExpBuffer.
In phase two the array of EXP records on %ExpBuffer is repeatedly walked thru and operations are calculated. Each evaluation pass searches for the operation with highest priority from the left. Each level of parenthesis increased the operation priority by 100h.
Unary operation will merge the operator term with its operand term.
Binary operation will merge two operands with the operator into one result term.
The evaluation is completed when there is only one operand term left on %ExpBuffer.

Example: Evaluation of expression 3*(-1+5)

%ExpBuffer after phase one:

EXP valueEXP.StatusPriority
3'N' 
*'O' (binary)12
-'O' (unary)100h+14 (highest)
1'N' 
+'O' (binary)100h+10
5'N' 

After 1. evaluation pass:

EXP valueEXP.StatusPriority
3'N' 
*'O' (binary)12
-1'N' 
+'O' (binary)100h+10 (highest)
5'N' 

After 2. evaluation pass:

EXP valueEXP.StatusPriority
3'N' 
*'O' (binary)12 (highest)
4'N' 

After 3. evaluation pass:

EXP valueEXP.StatusPriority
12'N' 
Input
Exp Pointer to the target EXP object (allocated by the caller).
TxtPtr Pointer to the evaluated text.
TxtSize Number of bytes in evaluated text.
Stm Pointer to the current statement. Used when the expression contains fwd referrenced symbols. May be 0 if fwd referenced symbol are not expected.
Output
CF=ZF=PF=0 Exp now contains evaluated expression. Registers unchanged.
On empty text
CF=PF=0 ZF=1 Returned Exp has type 'N' and value 0.
On warning
CF=ZF=0 PF=1 Warning 2210 Loss of precision in calculation with FP number
Error
CF=1 Exp is set to type '#'. Errors should be reported with ExpReportError.
Invokes
DictLookup EaBufferRelease EaBufferReserve ExpEval ExpEvalCharConst ExpEvalIdentifier ExpParseChar ExpParseLiteral ExpParseNumber ExpParseOperator ExpParseString ExpStoreString ExpWidth IiGetRegFamily RelocUniq SssFind SymCreateLiteral
Invoked by
ChunkSuboperate ExpEval ExpEvalBoolean ExpEvalData ExpEvalNum ExpParseAlignment IiAssemble PfSuboperate PgmEvalEntry PgmoptAssemble PseudoEQU PseudopcSETA PseudopcSETC VarSuboperate
Tested by
t1590 t1643 t1648 t1690 t1695 t1891 t5170
ExpEval Procedure Exp, TxtPtr, TxtSize, Stm
ExpBuffer    LocalVar ; ^BUFFER ; Holds parsed elements (EXP objects) before calculations.
BufBottom    LocalVar ; Bottom of ExpBuffer - pointer to the leftmost element ^EXP.
BufTop       LocalVar ; Top of ExpBuffer - pointer behind the last stored EXP).
ParenthesisLevel LocalVar ; Grows by 0x100 by enterring each () pair.
TempStatus   LocalVar ; Temporary result EXP.Status if type='M'.
SymStatus    LocalVar ; SYM.Status which appeared in expression.
ThisExp      LocalVar Size=SIZE#EXP ; Temporary room before storing to ExpBuffer.
QuotientHigh LocalVar ; Temporary variables for 64bit division.
QuotientLow  LocalVar
Walking1High LocalVar
Walking1Low  LocalVar
    ClearLocalVar
    PUSHFD ; Output CPU flags are manipulated as [ESP].
     RstSt [ESP],flagO+flagS+flagZ+flagP+flagC  ;  ~0x8C5 ; Reset returned OF,SF,ZF,PF,CF.
     EaStackCheck ; Protect from SO.
     Invoke EaBufferReserve::, ExpEval
     MOV [%ExpBuffer],EAX
     MOV ESI,[%TxtPtr]
     MOV ECX,[%TxtSize]
     LEA EDI,[%ThisExp]
     StripSpaces ESI,ECX
     TEST ECX
     JZ .Empty:
     LEA EBX,[ESI+ECX]
     CMPB [ESI],'[' ; Test if the whole expression is a memory-addressing operand (Exp.Status='M'). 
     JNE .AfterBegin: ; If ordinary expression.
     CMPB [EBX-1],']'
     JNE .AfterBegin: ; Not a memory-address, e.g. in TYPE#[DI+Symbol] = 'W'.
     ; Whole operand is in square brackets [ ], so it is a memory variable 'M'.
 .30:INC ESI ; Skip the leading [.
     DEC EBX ; Omit the trailing ].
     MOVB [%TempStatus],'M' ; This signalizes special case when memory-addressing expression is evaluated.
   ;  JMP .AfterBegin: ; Start parsing the expression ESI..EBX.

; All noncallable .After* subprocedures  dispatch to .Store* procedure 
; according to the classification of the 1st character.
; This spaghetized code provides syntax of expression 
; as specified in manual.
; Input: ESI=current parsing position.
;        EBX=end of parsed text.
;        EDI=%ThisExp for recursive invocation of ExpEval*.
; Output:ESI=advanced only on white spaces, otherwise not changed.
;        EBX=not changed.

.AfterBegin: PROC ; At the beginning of expression ESI..EBX.
     ; Expected: operand or left parenthesis or unary operator.
     DEC ESI
 .expWhiteSpace:
     INC ESI ; Skip white space.
     CMP ESI,EBX
     JNB ExpEval.E6100: ; Operand cannot be empty.
     ExpClassify [ESI]
     Dispatch AH,expLetter,expDigit,expFullstop,expQuote,expOperator,expSeparator,expWhiteSpace
 .expSeparator:CMP AL,'('
               JE ExpEval.StoreLeftParenthesis:
               CMP AL,'['
               JE ExpEval.StoreMemory:
               JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
 .expDigit:    JMP ExpEval.StoreNumber:
 .expQuote:    JMP ExpEval.StoreString:
 .expFullstop:
 .expLetter:   JMP ExpEval.StoreIdentifier:
 .expOperator: CMP AL,'='
               JE  ExpEval.StoreLiteral:
               JMP ExpEval.StoreUnary:
ENDP .AfterBegin:

.AfterOperand: PROC ; Expected: right parenthesis or binary operator or end.
     DEC ESI
 .expWhiteSpace:
     INC ESI ; Skip white space.
     CMP ESI,EBX
     JNB ExpEval.EndPhaseOne:
     ExpClassify [ESI]
     Dispatch AH,expWhiteSpace,expOperator,expColon
     CMP AL,')'
     JE ExpEval.StoreRightParenthesis:
     ; When expLetter or expDigit follows previous operand, this might not be a syntax error
     ; if the previous operand was segment register terminated with colon [ES: BX]
     PUSH EAX,ESI
 .10: DEC ESI
      ExpClassify [ESI]
      CMP AH,expWhiteSpace
      JE .10:
      CMP AL,':'
      JNE .90:
      BufferRetrieve [%ExpBuffer]
      CMPB [ESI+ECX-SIZE#EXP+EXP.Status],'R'
      JNE .90:                                        ; Previous element was not a register.
      JNSt [ESI+ECX-SIZE#EXP+EXP.Low],iiRegSeg, .90: ;    or it was not a segment register.
      CMP EAX,EAX ; Set ZF=1.
 .90:POP ESI,EAX ; ZF=1 if detected segment separation. It will be actually handled in .EndPhaseOne
     JE ExpEval.AfterBinary: ; Treat segment separation as a binary operation.
     JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
 .expColon:
 .expOperator:JMP ExpEval.StoreBinary:
ENDP .AfterOperand:

.AfterUnary: PROC ; Expected: operand or left parenthesis. 
     DEC ESI
 .expWhiteSpace:
     INC ESI ; Skip white space.
     CMP ESI,EBX
     JNB ExpEval.E6109: ; Premature end of expression "!1S".
     ExpClassify [ESI]
     Dispatch AH,expWhiteSpace,expLetter,expDigit,expFullstop,expQuote,expOperator
     CMP AL,'('
     JE ExpEval.StoreLeftParenthesis:
     CMP AL,'['
     JE ExpEval.StoreMemory:
     JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
  .expDigit:   JMP ExpEval.StoreNumber:
  .expQuote:   JMP ExpEval.StoreString:
  .expFullstop:
  .expLetter:  JMP ExpEval.StoreIdentifier:
  .expOperator:CMP AL,'='
     JE ExpEval.StoreLiteral:
     JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
ENDP .AfterUnary:
 
.AfterBinary: PROC ; Expected: operand or left parenthesis or unary operator.
     DEC ESI
 .expWhiteSpace:
     INC ESI ; Skip white space.
     CMP ESI,EBX
     JNB ExpEval.E6109: ; Premature end of expression "!1S".',0
     ExpClassify [ESI]
     Dispatch AH,expWhiteSpace,expOperator,expLetter,expDigit,expFullstop,expQuote
     CMP AL,'('
     JE ExpEval.StoreLeftParenthesis:
     JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
 .expOperator:
     CMP AL,'='
     JE ExpEval.StoreLiteral:
     JMP ExpEval.StoreUnary: ; Unary operator is permitted after binary, e.g. 123 + -23.
 .expDigit:    JMP ExpEval.StoreNumber:
 .expQuote:    JMP ExpEval.StoreString:
 .expFullstop:
 .expLetter:   JMP ExpEval.StoreIdentifier:
  ENDP .AfterBinary:

.AfterLeftParenthesis: PROC ; Expected operand or left parenthesis of unary operator.
     DEC ESI
 .expWhiteSpace:
     INC ESI ; Skip white space.
     CMP ESI,EBX
     JNB ExpEval.E6109: ; Premature end of expression "!1S".',0
     ExpClassify [ESI]
     Dispatch AH,expWhiteSpace,expOperator,expLetter,expDigit,expFullstop,expQuote
     CMP AL,')'
     JE ExpEval.StoreRightParenthesis:
     CMP AL,'('
     JE  ExpEval.StoreLeftParenthesis:
     CMP AL,'['
     JE ExpEval.StoreMemory:
     JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
  .expOperator: CMP AL,'='
                JE ExpEval.StoreLiteral:
                JMP ExpEval.StoreUnary:
  .expDigit:    JMP ExpEval.StoreNumber:
  .expQuote:    JMP ExpEval.StoreString:
  .expFullstop:
  .expLetter:   JMP ExpEval.StoreIdentifier:
  ENDP .AfterLeftParenthesis:

.AfterRightParenthesis: PROC ; Expected binary operator or right parenthesis or end.
    DEC ESI
 .expWhiteSpace:
    INC ESI ; Skip white space.
    CMP ESI,EBX
    JNB ExpEval.EndPhaseOne:
    ExpClassify [ESI]
    Dispatch AH,expWhiteSpace,expOperator,expColon
    CMP AL,')'
    JE ExpEval.StoreRightParenthesis:
    JMP ExpEval.E6101: ; Unexpected character "!2Z" following "!1S".
 .expColon:
 .expOperator: JMP ExpEval.StoreBinary:
 ENDP .AfterRightParenthesis:

; Noncallable .Store* snippets parse an element of source and then store %ThisExp on %ExpBuffer.
; Input:  ESI=pointer to 1st character of source element. 
;         EBX=^end of parsable text.
;         EDI=^%ThisExp where the element will be parsed and stored to.
; Output: ESI is advanced behind the parsed element in input text.
;         EBX unchanged.
.StoreMemory: ; Eval and store SSS or memory-addressing expression in [ ].
     Invoke ExpParseChar,']',ESI,EBX
     JC .E6103: ; Missing "]" in expression "!1S".
     ; Inspect if the expression ESI..EAX is [section_name] SSS.
     INC ESI              ; Skip the [.
     MOV ECX,EAX
     SUB ECX,ESI
     StripSpaces ESI,ECX
     PUSH EAX ; Pointer to the closing ].
       Invoke SssFind::,sssGroup|sssSegment|sssSection,0,ESI,ECX,0
       JC .StoreMemory4: ; Jump if no such section_name exists (stack will be rebalanced there).
     POP ESI
     ; Found group|segment|section name in brackets. Exp type will be 'S'.
     INC ESI ; Behind the closing bracket ].
     Clear EDI,Size=SIZE#EXP
     MOV [EDI+EXP.Seg],EAX     ; ^SSS.
     MOVB [EDI+EXP.Status],'S'
     BufferStore [%ExpBuffer],EDI,SIZE#EXP
     JMP .AfterOperand:
.StoreMemory4: ; Expect memory-addressing subexpression, e.g. in TYPE#[ESI+Symbol]='D'.
     POP EAX ; Pointer to the closing ].
     DEC ESI ; Back at the leading [.
     INC EAX ; Behind the closing bracket ].
     MOV ECX,EAX ; Temporary save parsed position.
     SUB EAX,ESI
     Invoke ExpEval,EDI,ESI,EAX,[%Stm] ; Recursive invocation to evaluate [memory].
     ; Ignore possible errors in memory-addressing expression.
     MOV ESI,ECX ; Continue from the saved parse position.
     BufferStore [%ExpBuffer],EDI,SIZE#EXP
     JMP .AfterOperand:
.StoreString: ; Store element in quotes. It may be reclassified later as a character constant when submitted to numeric operation.
    MOV ECX,ESI ; Save start of string.
    Invoke ExpParseString,ESI,EBX
    JC .E6160: ; Syntax error in the string !1S.
    MOV EAX,ESI
    MOV [EDI+EXP.Low],ECX ; Pointer to opening quote.
    SUB EAX,ECX
    MOV [EDI+EXP.High],EAX
    XOR EAX,EAX
    MOV [EDI+EXP.Seg],EAX
    MOV [EDI+EXP.Sym],EAX
    MOV AL,'G'
    MOV [EDI+EXP.Status],EAX
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    JMP .AfterOperand:
.StoreNumber: ; Store element which begins with a decimal digit.
    Invoke ExpParseNumber::,ESI,EBX
    JC .E6130: ; The number "!1S" is too big for 64 bits.
    JPO .StoreNumber2: ; PE is set when the number was rounded from floating-point.
    SetSt [ESP],flagP ; Signalize PF=PrecisionLost.
 .StoreNumber2:
    MOV [EDI+EXP.Low],EAX
    MOV [EDI+EXP.High],EDX
    XOR EAX,EAX
    MOV [EDI+EXP.Seg],EAX
    MOV [EDI+EXP.Sym],EAX
    MOV AL,'N'
    MOV [EDI+EXP.Status],EAX
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    JMP .AfterOperand:
.StoreBinary: ; Store element which looks like an operator when a binary one is anticipated.
    Invoke ExpParseOperator,ESI,EBX,dictBinary
    JC .E6182: ; Binary operator instead of "!2Z" expected in expression "!1S".
    MOV EDX,.AfterBinary:
    JMP .StoreOperator:
.StoreUnary: ; Store element which looks like an operator when an unary one is anticipated..
    Invoke ExpParseOperator,ESI,EBX,dictUnary
    JC .E6181: ; Unary operator instead of "!2Z" expected in expression "!1S".
    MOV EDX,.AfterUnary:
.StoreOperator: ; EDI=^EXP, EAX=DictOperators.Data, EDX=.After* where to continue.
    MOV ECX,0x0F ; Mask priority from operator's DICT.Data.
    AND ECX,EAX
    ADD ECX,[%ParenthesisLevel]
    MOV [EDI+EXP.Low],EAX  ; DictOperator.Data.
    MOV [EDI+EXP.High],ECX ; Priority.
    SHR EAX,16 ; EAX is now ordinal number of operation, see ExpOperationList.
    MOV [EDI+EXP.Sym],EAX ; Operation ordinal number.
    MOV ECX,[.HandlersTable-4 + 4*EAX] ; Table of pointers dispatching to operation handler.
    MOV [EDI+EXP.Seg],ECX ; Operation handler, e.g. .Addition:.
    MOVD [EDI+EXP.Status],'O'
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    JMP EDX ; .AfterBinary: or .AfterUnary:.
.StoreIdentifier:
    Invoke ExpEvalIdentifier,EDI,ESI,EBX,[%Stm]
    JNC .Di:
    MOVD [EDI+EXP.Seg],0  ; Error in ExpEvalIdentifier was already reported,
    ;   set MsgId=0 to prevent repeating of error message.
    JMP .Export:
.Di:MOV EAX,[EDI+EXP.Status]
    ;           'A', 'N', 'R', 'S', 'O','?'
    Dispatch AL,0x41,0x4E,0x52,0x53,0x4F,0x3F
    JMP .E6120: ; Symbol "!1S" not found.
.0x3F: ; '?' Undefined symbol recognized in expression.
.0x41: ; 'A' Address recognized in expression.
.0x4E: ; 'N' Plain number  recognized in expression.
.0x52: ; 'R' Register name recognized in expression.
.0x53: ; 'S' Structure name recognized in expression.
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    JMP .AfterOperand:
.0x4F: ; 'O' Unary attribute operator recognized in ExpEvalIdentifier needs some adjustment:
    MOV EAX,[%ParenthesisLevel]
    ADD [EDI+EXP.High],EAX ; Adjust the operation priority.
    MOV ECX,[EDI+EXP.Sym] ; ExpEvalIdentifier put operation's ordinal number here rather than handler.
    MOV EAX,[.HandlersTable-4 + 4*ECX]
    MOV [EDI+EXP.Seg],EAX ; Operation handler, e.g. .Offset:.
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    CMP EAX, .Type:
    JE .o4:
    CMP EAX, .RegType:
    JE .o4:
    CMP EAX, .Scope:
    JNE .AfterUnary:
    ; Attributes TYPE#, REGTYPE# and SCOPE# may be applied to undefined symbol without warning.
    ; Other attributes# will create symbol by reference (and report E6120 if undefined).
.o4:PUSH EBX
      MOV EBX,[%Stm]
      TEST EBX
      JZ .o6:
      ; Signalize pending attribute operation for the following ExpEvalIdentifier,
      ; so it will not create queried symbol by reference.
      SetSt [EBX+STM.Status],stmQueried 
.o6:POP EBX
    JMP .AfterUnary:
    
.StoreLiteral:
    MOV EDX,ESI ; Start of literal (=).
    Invoke ExpParseLiteral,ESI,EBX
    JC .E6671: ;  Invalid syntax of literal symbol !1S".
    MOV ESI,EAX ; Advance ESI behind the parsed literal.
    SUB EAX,EDX
    Invoke SymCreateLiteral::,EDX,EAX,[%Stm]
    JC .E6671: ;  Invalid syntax of literal symbol !1S".
    MOV [EDI+EXP.Sym],EAX
    MOV ECX,[EAX+SYM.Section]
    MOV [EDI+EXP.Seg],ECX
    MOV ECX,[ECX+SSS.RelocBuffer]
    JECXZ .Sl:
    Invoke RelocUniq::,ECX
.Sl:MOV EDX,[EAX+SYM.OffsetHigh]
    MOV EAX,[EAX+SYM.OffsetLow]    
    MOV [EDI+EXP.High],EDX
    MOV [EDI+EXP.Low],EAX
    Invoke ExpWidth 
    SHL ECX,8
    MOV CL,'A'
    MOV [EDI+EXP.Status],ECX
    BufferStore [%ExpBuffer],EDI,SIZE#EXP
    JMP .AfterOperand:
.StoreLeftParenthesis: ; Handling left parenthesis (.
    ADDD [%ParenthesisLevel],0x100
    INC ESI ; Skip '('.
    JMP .AfterLeftParenthesis:
.StoreRightParenthesis: ; Handling right parenthesis ).
    MOV ECX,[%ParenthesisLevel]
    SUB ECX,0x100
    JB .E6220: ; Unbalanced parenth ")" without "(" in expr."!1S".
    MOV [%ParenthesisLevel],ECX
    INC ESI ; Skip ')'.
    JMP .AfterRightParenthesis:

.EndPhaseOne: ; Phase one termination. 
; Elements parsed to EXP objects are stored on [%ExpBuffer] and waiting for calculation.
; Solve a special case when segment register is followed by other operand
; without Indexing operator (+), in expression like [ES:Symbol] or [DI + CS BX].
    BufferRetrieve [%ExpBuffer]
    LEA EDI,[ESI+ECX] ; Behind the last element.
    SUB ESI,SIZE#EXP
.10:ADD ESI,SIZE#EXP
    CMP ESI,EDI
    JNB .PhaseTwo:
    CMPB [ESI+EXP.Status],'R'
    JNE .10:
    JNSt [ESI+EXP.Low],iiRegSeg, .10:
    ADD ESI,SIZE#EXP
    CMP ESI,EDI
    JNB .PhaseTwo:
    CMPB [ESI+EXP.Status],'O'
    JE .10:
    ; Special case - SegmReg: not followed with operator. [FS:ESI]
    ; Fake Indexing operator will be inserted.
    BufferNew [%ExpBuffer],SIZE#EXP
    MOV ECX,EAX
    SUB ECX,ESI
    SHR ECX,2
    ADD EDI,SIZE#EXP-4
    LEA ESI,[EDI-SIZE#EXP]
    STD
    REP MOVSD
    CLD
    SUB EDI,SIZE#EXP-4
    MOVD [EDI+EXP.Status],'O' ; Fake operator element.
    MOV EAX,[DictOperationAddition:: + DICT.Data]
    MOVD [EDI+EXP.High],9 ; Addition/Indexing priority.
    MOV [EDI+EXP.Low],EAX
    MOVD [EDI+EXP.Seg],ExpEval.Addition:
.PhaseTwo: ; Phase two starts to calculate elements and operations in [%ExpBuffer].
    BufferRetrieve [%ExpBuffer]
    LEA EDI,[ESI+ECX] ; Behind the last element.
    MOV [%BufBottom],ESI
    MOV [%BufTop],EDI
    CMP ECX,SIZE#EXP
    JE .Calculated: ; All operations calculated, only one element left on %ExpBuffer.
    JB .Empty:
   ; More than one element, €ASM will find operation with the highest priority, starting from left.
    SUB EDX,EDX ; Highest priority so far.
    SUB EBX,EBX ; Pointer to the corresponding EXP operation whith highest priority.
.NextElement:
    SUB EDI,SIZE#EXP
    CMP EDI,ESI
    JB .Calculate:
    CMPB [EDI+EXP.Status],'O'
    JNE .NextElement: ; If the element EDI is not an operator.
    CMP EDX,[EDI+EXP.High] ; Priority.
    JA .NextElement:
    MOV EDX,[EDI+EXP.High] ; Highest priority so far.
    MOV EBX,EDI            ; ^EXP with highest priority so far.
    JMP .NextElement:
.Calculate:
    TEST EBX ; EBX is ^EXP of operation with the highest priority.
    JZ .E6200 ; Syntax error in expression "!1S".
    JMP [EBX+EXP.Seg] ; Dispatch to current operation handler - .Minus:, .Addition: etc.

; Left-side operand (if operator at EBX is binary) is EBX-SIZE#EXP aliased as %LeftOperand,
; right-side operand is EBX+EXP@SIZE aliased as %RightOperand.
; Other important pointers on handler entry are [%BufBottom],[%BufTop] - edges of parsed expression.

%LeftOperand  %SET EBX-SIZE#EXP
%RightOperand %SET EBX+SIZE#EXP

    
; Miscellaneous auxiliary subprocedures follow.
 
.CheckLeftOpNumber: PROC ; The element at EBX - SIZE#EXP should be a number or address.
; String operand will be reclassified as character constant. i.e. number, if possible.
; Input: EBX=^EXP with binary operation.
; Output:   CF=0 if operand is number or address. EAX=undefined.
; On error: CF=1 if not a valid number or address.
;              EAX='6131' Character constant !1S is too big for 64 bits
;              EAX='6161' Syntax error in the char.constant !1S.
;              EAX='6206' In expression "!1S" !2O can be applied to plain numbers only.
    PUSH EDX,ESI
     LEA ESI,[%LeftOperand] ; Left operand.
 .CheckOperandNumber: ; Common continuation with .CheckRightOpNumber. ESI=^EXP with operand.
     MOV EAX,[ESI+EXP.Status]
     Dispatch AL,'N','A','G'
     MOV EAX,'6206' ; !2O can be applied to plain numbers only in expression "!1S".
     STC
     JMP .N:
.G:  MOV EAX,[ESI+EXP.High] ; Pointer to left quote of the string.
     ADD EAX,[ESI+EXP.Low]  ; Add brutto string size.
     Invoke ExpEvalCharConst,[ESI+EXP.Low],EAX ; On error returns EAX='6131' or '6161'.
     JC .N:
     MOV [ESI+EXP.Low],EAX
     MOV [ESI+EXP.High],EDX
     MOVB [ESI+EXP.Status],'N'
.A:
.N: POP ESI,EDX
    RET
   ENDP .CheckLeftOpNumber:

.CheckRightOpNumber: PROC ; The element at EBX + SIZE#EXP should be a number or address.
; String operand will be reclassified as character constant. i.e. number, if possible.
; Input: EBX=^EXP with binary operation.
; Output:   CF=0 if operand is number or address. EAX=undefined.
; On error: CF=1 if not a valid number or address.
;              EAX='6131' Character constant !1S is too big for 64 bits.
;              EAX='6161' Syntax error in the char.constant !1S.
;              EAX='6206' In expression "!1S" !2O can be applied to plain numbers only.
    PUSH EDX,ESI
     LEA ESI,[%RightOperand] ; Right operand.
     JMP ExpEval.CheckLeftOpNumber.CheckOperandNumber:
  ENDP .CheckRightOpNumber:

.NegLeftOperand: PROC ; Negate numeric element at [EBX-SIZE#EXP]. Destroys EAX,EDX,ESI.
     LEA ESI,[%LeftOperand]
  .NegOperand: ; at ESI.
     MOV EAX,[ESI+EXP.Low]
     MOV EDX,[ESI+EXP.High]
     NOT EAX
     NOT EDX
     ADD EAX,1
     ADC EDX,0
     MOV [ESI+EXP.Low],EAX
     MOV [ESI+EXP.High],EDX
     RET
     ENDP .NegLeftOperand:

.NegRightOperand: PROC ; Negate numeric element at [EBX+SIZE#EXP]. Destroys EAX,EDX,ESI.
     LEA ESI,[%RightOperand]
     JMPS ExpEval.NegLeftOperand.NegOperand:
     ENDP .NegRightOperand:

.SwapOperands: PROC ; Callable subprocedure to exchange both operands of binary operation.
; Output: EDX:EAX=.High:.Low value of the operand which is on the left after swap.
;         ESI,EDI=pointers to the left,right operand.
   LEA ESI,[%LeftOperand] ; The left operand.
   LEA EDI,[%RightOperand] ; The right operand.
   MOV EAX,[ESI+EXP.Sym]
   XCHG EAX,[EDI+EXP.Sym]
   MOV [ESI+EXP.Sym],EAX
   MOV EAX,[ESI+EXP.Status]
   MOV EDX,[ESI+EXP.Seg]
   XCHG EAX,[EDI+EXP.Status]
   XCHG EDX,[EDI+EXP.Seg]
   MOV [ESI+EXP.Status],EAX
   MOV [ESI+EXP.Seg],EDX
   MOV EAX,[ESI+EXP.Low]
   MOV EDX,[ESI+EXP.High]
   XCHG EAX,[EDI+EXP.Low]
   XCHG EDX,[EDI+EXP.High]
   MOV [ESI+EXP.Low],EAX
   MOV [ESI+EXP.High],EDX
   RET
  ENDP .SwapOperands:

.CheckAwidth:PROC ; Check consistency of addressing mode. Detect error in [EBX+SI] etc.
; Address width expAwidth in [%TempStatus] must be 0 or it must match the width of GP register in ECX.
; Vector-index register will always pass, it does not involve the address-size.
; Input: ECX=DictRegisters.Data
; Output:CF=0 All OK, register width matches [%TempStatus]. EAX changed, ECX preserved.
; Error: CF=1 EBX='6277', AL=reg, ECX preserved. Unexpected !2R, invalid register combination in address expression "!1S".
    PUSH ECX
     JSt ECX,iiReg_Fam32,.90: ; XMM,YMM,ZMM used as vector indexregister.
     SHR ECX,25 ; Register byte size, see DictRegisters.Data.
     AND ECX,0x00000007 ; Reg size 001b,010b,100b for 2,4,8 bytes
     CMP CL,4
     JB  .20:
     DEC ECX ; Reg size  01b,10b,11b for 2,4,8 bytes
 .20:MOV EAX,expAwidth ; 0xC000_0000
     SHL ECX,30 ; Match expAwidth mask.
     AND EAX,[%TempStatus]
     JZ .30: ; Status.expAwidth was not set yet, so any width will fit.
     CMP EAX,ECX
     JE .30:
     MOV EBX,'6277' ; Unexpected !2R, invalid register combination in address expression "!1S".
     MOV EAX,ECX
     STC
     JMP .90: ; Return with error.
 .30:OR [%TempStatus],ECX ; Otherwise set expAwidth mask.
 .90:POP ECX
    RET
    ENDP .CheckAwidth:

.CheckBinaryNumeric: PROC ; Callable proc to check if types of both [%LeftOperand] and [%RightOperand] are 'N'.
; Input: EBX=^EXP with binary operation on [%ExpBuffer].
; Output: CF=0, both operands are numeric, EDX:EAX=Left operand .High:.Low.
; Error: CF=1, EAX=MsgId.  EDX=unspecified.
;              EAX='6131' Character constant !1S is too big for 64 bits.
;              EAX='6161' Syntax error in the char.constant !1S.
;              EAX='6206' In expression "!1S" !2O can be applied to plain numbers only.
    CALL ExpEval.CheckLeftOpNumber: ; Convert String to Number, check if number or address.
    JC .90: ; If left operand was not numeric or address.
    CALL ExpEval.CheckRightOpNumber:
    JC .90: ; If right operand was not numeric or address.
    MOV EAX,[%LeftOperand+EXP.Seg]
    OR EAX,[%RightOperand+EXP.Seg] ; Both operand should be sectionless.
    MOV EAX,'6206'
    STC
    JNZ .90:
    MOV EAX,[%LeftOperand+EXP.Low]
    MOV EDX,[%LeftOperand+EXP.High]
    CLC
.90:RET
    ENDP .CheckBinaryNumeric:

.CheckBinaryNumericAddr: PROC ; Callable proc to check if types of both [%LeftOperand] and [%RightOperand]
; are both 'N' or they are both 'A' with the same segment. Used in numeric compare operations.
; Input: EBX=^EXP with binary operation on [%ExpBuffer].
; Output: CF=0, both operands are numeric, EDX:EAX=Left operand .High:.Low.
; Error: CF=1, EAX=MsgId.  EDX=unspecified.
;              EAX='6131' Character constant !1S is too big for 64 bits.
;              EAX='6161' Syntax error in the char.constant !1S.
;              EAX='6207' In expression "!1S" !2O requires both addresses from the same segment.
    CALL ExpEval.CheckLeftOpNumber: ; Convert String to Number, check if number or address.
    JC .90: ; If left operand was not numeric or address.
    CALL ExpEval.CheckRightOpNumber:
    JC .90: ; If right operand was not numeric or address.
    MOV EAX,[%LeftOperand+EXP.Status]
    MOV EDX,[%RightOperand+EXP.Status]
    MOV AH,DL
    Dispatch AX,'NN','AA'
.E6207:
    MOV EAX,'6207'
    STC
    JMP .90:
.AA:MOV EAX,[%LeftOperand+EXP.Seg]
    MOV EDX,[%RightOperand+EXP.Seg]
    MOV EAX,[EAX+SSS.SegmPtr]
    CMP EAX,[EDX+SSS.SegmPtr]
    JNE .E6207:
.NN:MOV EAX,[%LeftOperand+EXP.Low]
    MOV EDX,[%LeftOperand+EXP.High]
    CLC
.90:RET
    ENDP .CheckBinaryNumericAddr:

.AdoptIndexing: PROC ; Callable subprocedure for adopting an register in address expression.
; Input:    ECX=DictRegisters.Data    [%TempStatus]=Address expression status.
; Output:   CF=0, [%TempStatus] modified, EAX destroyed, ECX preserved.
; On error: CF=1, EBX=MsgId,'6274''6278' ,AL=reg, ECX preserved.
     Invoke IiGetRegFamily::,ECX
     Dispatch AL,iiReg_R16,iiReg_R32,iiReg_R64,iiReg_SEG,iiReg_ZMM,iiReg_YMM,iiReg_XMM
.E6278:MOV EBX,'6278' ; Illegal register !2R used in address expression "!1S".
 .Er:MOV EAX,ECX
     STC
     RET
.iiReg_SEG:
     MOV EAX,iiReg_Ord8 ; Mask for segment-register ordinal number.
     AND EAX,ECX
     JNSt [%TempStatus],expSegmPres,.10:
     MOV EBX,'6272' ; Unexpected !3R, only one segm.reg. is allowed in expression "!1S".
     JMP .Er:
.E6271:MOV EBX,'6271' ; Illegal register !3R used in 16bit addressing in expression "!1S".
     JMP .Er:
.E6273:MOV EBX,'6273' ; Unexpected !3R, only one base register is allowed in expression "!1S".
     JMP .Er:
.E6274:MOV EBX,'6274' ; Unexpected !3R, only one indexreg. is allowed in expression "!1S".
     JMP .Er:
 .10:; Adopt as a segment register.
     SHL EAX,24 ; Convert iiReg_Ord8 to expSegm.
     OR EAX,expSegmPres
     OR [%TempStatus],EAX
     JMP .90:
.iiReg_R16:
.iiReg_R32:
.iiReg_R64:
     MOV EAX,iiReg_Ord16 ; Mask for general-purpose register ordinal number.
     AND EAX,ECX
     JSt [%TempStatus],expBasePres,.30: ; If one basereg is already adopted, adopt as index.
     JNSt ECX,iiRegBase,.30:
     ; Adopt as a base register.
     SHL EAX,16 ; Convert iiReg_Ord16 to expBase.
     OR EAX,expBasePres
     OR [%TempStatus],EAX
     CALL ExpEval.CheckAwidth:
     JMP .90:
.iiReg_XMM:
.iiReg_YMM:
.iiReg_ZMM:
     MOV EAX,0110_0000b
     AND EAX,ECX       ; AL is now 0000_0000b,0010_0000b,0100_0000b for XMM,YMM,ZMM.
     ADD AL,0010_0000b ; AL is now 0010_0000b,0100_0000b,0110_0000b for XMM,YMM,ZMM.
     SHL EAX,6 ; Convert vector family to expVSIBfam.
     OR [%TempStatus],EAX
     MOV EAX,iiReg_Ord32 ; Mask for vector-index register ordinal number.
     AND EAX,ECX
     BTR EAX,4
     JNC .30:
     ORD [%TempStatus],expVbit4
 .30:JSt [%TempStatus],expIndexPres, .E6274:
     JNSt ECX,iiRegIndex, .50:
     ; Adopt as an index register.
     SHL EAX,20 ; Convert iiReg_Ord16 to expIndex.
     OR EAX,expIndexPres
     OR [%TempStatus],EAX
     CALL ExpEval.CheckAwidth:
     JMP .90:
 .50:Invoke IiGetRegFamily::, ECX
     CMP AL,iiReg_R32
     JE .60:
     CMP AL,iiReg_R64
     JE .60:
     JNSt ECX,iiRegBase|iiRegIndex,.E6271: ; Illegal register !2R used in 16bit addressing in expression "!1S".
     JMP .E6273: ; Unexpected !2R, only one base register is allowed in expression "!1S".
 .60:; Special case in 32bit addressing: expBasePres is already occupied but curently adopting register
 ; cannot be adopted as an index. E.g. ESP in [EBX+ESP].
 ; Solve this by readopting EBX as an index and adopting the current reg ESP as a base.
     MOV EAX,expBase
     AND EAX,[%TempStatus]
     SHL EAX,4
     OR [%TempStatus],EAX
     MOV EAX,~expBase
     AND [%TempStatus],EAX
     JNSt ECX,iiRegBase, .E6278: ; Illegal register !2R used in address expression "!1S".
     MOV EAX,0x0F ; Mask for register ordinal number
     AND EAX,ECX
     SHL EAX,16
     OR EAX,expBasePres+expIndexPres
     OR [%TempStatus],EAX
     MOV EAX,expBase+expIndex+expBasePres+expIndexPres
     AND EAX,[%TempStatus]
     CMP EAX,0x00440000 + expBasePres+expIndexPres ; [ESP+ESP] or [RSP+RSP].
     JE .E6273: ; Unexpected !2R, only one base register is allowed in expression "!1S".
     CALL ExpEval.CheckAwidth:
 .90:RET
    ENDP .AdoptIndexing:

.AdoptScaling: PROC  ; Callable subprocedure for scaled address expression.
; Input:    ECX=DictRegisters.Data    [%TempStatus]=Address expression status.
;           EDX=scaling factor (-1,0,1,2,3 for 0*,1*,2*,4*,8*)
; Output:   CF=0, [%TempStatus] modified, EAX,EDX destroyed, EBX,ECX preserved.
; On error: CF=1, EBX='6272','6275','6276' or '6277', AL=!2R, ECX preserved.
     MOV EAX,ECX
     JSt [%TempStatus],expScalePres|expIndexPres,.E6276: ; Unexpected !2R - more than one register not allowed in expression "!1S".
     JNSt ECX,iiRegIndex, .E6275: ; Scaled reg !2R cannot be used as indexreg in expresion "!1S".
     CALL ExpEval.CheckAwidth: ; Returns EBX='6277', AL=!2R on error.
     JC .Err:
     TEST EDX
     JNS .30:
     INC EDX ; EDX=0.
     JMP .50: ; If 0*IndexReg, expIndex will be set but expIndexPres+expScalePres not.
 .30:SetSt [%TempStatus],expIndexPres+expScalePres
     SHL EDX,28 ; Convert scaling factor to expScale.
     TEST CL,iiReg_Fam32
     JZ .50:
     MOV EAX,0110_0000b
     AND EAX,ECX       ; AL is now 0000_0000b,0010_0000b,0100_0000b for XMM,YMM,ZMM.
     ADD AL,0010_0000b ; AL is now 0010_0000b,0100_0000b,0110_0000b for XMM,YMM,ZMM.
     SHL EAX,6 ; Convert vector family to expVSIBfam.
     OR EDX,EAX
     MOV EAX,iiReg_Ord32 ; Vector indexregister ordinal number.
     AND EAX,ECX
     BTR EAX,4
     JNC .50:
     OR EDX,expVbit4
 .50:MOV EAX,iiReg_Ord16 ; General-purpose indexregister ordinal number.
     AND EAX,ECX
     RstSt [%TempStatus],expIndex ; Clear eventual expIndex remaining from prevous 0* scaling.
     SHL EAX,20 ; Convert iiReg_Ord16 to expIndex.
     OR EDX,EAX
     OR [%TempStatus],EDX
     JMPS .90:
.E6275:MOV EBX,'6275' ; Scaled reg !3R cannot be used as indexreg in expresion "!1S".
     JMPS .Err:
.E6276:MOV EBX,'6276' ; Unexpected !3R - more than one register not allowed in expression "!1S".
 .Err:STC
 .90:RET
    ENDP .AdoptScaling:

.ReturnBool: ; Input: EAX=EXP.Value (0 or -1); ECX=EXP.Status
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EAX
    MOVD [%LeftOperand+EXP.Seg],0
    MOV [%LeftOperand+EXP.Status],ECX
    JMP ExpEval.DoneBinary:

.ReturnFalse:PROC ; Uncallable. Set left operand to boolean False. Output:EAX=0
    XOR EAX,EAX
    MOV ECX,'N'+(3<<8) ;                                                                      >>
    JMP ExpEval.ReturnBool:
    ENDP .ReturnFalse:

.ReturnTrue:PROC ;  Uncallable. Set left operand to boolean True. Output:EAX=-1
    XOR EAX,EAX
    MOV ECX,'N'+(4<<8) ;                                                                      >>
    DEC EAX
    JMP ExpEval.ReturnBool:
    ENDP .ReturnTrue:

;  Operation handlers for all operations defined in ExpOperationList.
; Elements have been parsed into the EXP format and stored in [%ExpBuffer].
; Handler is provided with EBX=pointer to EXP with the operation, neighbouring its operands.
; Handler must not change EBX and EBP. It ends with .DoneUnary or .DoneBinary.

.Membership: ; Dummy handler, membership is not processed here.

.SegmentSeparation: PROC ; Something like 1234:5678 or [ES : BX].
    CMPB [%TempStatus],'M'
    JNE .50:
    CMPB [%LeftOperand+EXP.Status],'R' ; Left operand must be a segment register.
    JNE ExpEval.E6240: ; Immediate far pointer "!1S" must not be in braces [].
    MOV ECX,[%LeftOperand+EXP.Low] ; DictRegisters.Data.
    JNSt ECX,iiRegSeg,ExpEval.E6240:
    CALL ExpEval.AdoptIndexing
    MOV EDX,EAX
    MOV EAX,EBX
    JC ExpEval.ErrorEAX:
    CALL ExpEval.SwapOperands:
    JMP ExpEval.DoneBinary:
.50:; Segment-separated expression is not in braces [], therefore it only may be immediate segment:offset in JMPF/CALLF.
    ; %LeftOperand and %RightOperand will be evaluated here and %LeftOperand reclassified as 'F'.
    CALL ExpEval.CheckLeftOpNumber: ; Convert String to Number.
    JC ExpEval.E6241: ; Segment part of imm.far pointer "!1S" must be a plain 16bit number.
    MOV EDX,[%LeftOperand+EXP.High]
    MOV EAX,[%LeftOperand+EXP.Low]
    TEST EDX
    JNZ ExpEval.E6241:
    MOV [%LeftOperand+EXP.Seg],EAX
    CALL ExpEval.CheckRightOpNumber: ; Convert String to Number, if possible.
    MOVB [%LeftOperand+EXP.Status],'F'
    CMPB [%RightOperand+EXP.Status],'N'
    JE .70:
    CMPB [%RightOperand+EXP.Status],'A'
    JNE ExpEval.E6242: ; Invalid offset part of immediate far pointer "!1S".
 .70:MOV EAX,[%RightOperand+EXP.Low]
    MOV EDX,[%RightOperand+EXP.High]
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
   ENDP .SegmentSeparation:

.Minus: PROC
    CALL ExpEval.CheckRightOpNumber:
    JC ExpEval.ErrorEAX:
    CMPB [%RightOperand+EXP.Status],'A'
    JE ExpEval.E6208: ; Unary minus is not applicable to an address in expression "!1S".
    CALL ExpEval.NegRightOperand:
    JMP ExpEval.DoneUnary:
    ENDP .Minus:

.Plus: PROC
   ; CALL ExpEval.CheckRightOpNumber:
   ; JC ExpEval.ErrorEAX:
    JMP ExpEval.DoneUnary:
    ENDP .Plus:

.BitwiseNot: PROC
    CALL ExpEval.CheckRightOpNumber:
    JC ExpEval.ErrorEAX:
    NOTD [%RightOperand+EXP.Low]
    NOTD [%RightOperand+EXP.High]
    JMP ExpEval.DoneUnary:
    ENDP .BitwiseNot:

.LogicalNot: PROC
    CALL ExpEval.CheckRightOpNumber:
    JC ExpEval.ErrorEAX:
    MOV EAX,[%RightOperand+EXP.Low]
    OR EAX,[%RightOperand+EXP.High]
    MOV EAX,-1
    JZ .5:
    SUB EAX,EAX
 .5:MOV [%RightOperand+EXP.Low],EAX
    MOV [%RightOperand+EXP.High],EAX
    JMP ExpEval.DoneUnary:
    ENDP .LogicalNot:

.Addition: PROC ; Also .Indexing with Register.
    CALL ExpEval.CheckLeftOpNumber: ; Convert String to Number,
    CALL ExpEval.CheckRightOpNumber: ; ignore if not possible.
    MOV AL,[%RightOperand+EXP.Status] ; Right operand type.
    MOV AH,[%LeftOperand+EXP.Status] ; Left operand type.
    Dispatch AX,'NN','NA','AN','RN','NR','RA','AR','RR'
    JMP ExpEval.E6301: ; !2O applied to illegal operand in "!1S".
.NN:MOV EAX,[%RightOperand+EXP.Low] ; [Scalar+scalar].
    MOV EDX,[%RightOperand+EXP.High]
    ADD [%LeftOperand+EXP.Low],EAX ; The actual Addition.
    ADC [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
.AN:CALL ExpEval.SwapOperands:      ; [Scalar+address].
.NA:MOV EAX,[%RightOperand+EXP.Low] ;  [Address+scalar].
    MOV EDX,[%RightOperand+EXP.High]
    ADD [%LeftOperand+EXP.Low],EAX  ; Add scalar to address symbol.
    ADC [%LeftOperand+EXP.High],EDX ; Ignore overflow in displ.calculations.
    JMP ExpEval.DoneBinary:
    ; Operation with regs is possible only in address expr.(type 'M').
.AR: ; [Reg+address].
.NR: ; [Reg+scalar].
.RR: ; [Reg+reg].
     CALL ExpEval.SwapOperands: ; Left operand will be adopted sooner, therefore it will be the base.
.RA: ; [Address+reg].
.RN: ; [Scalar+reg].
    MOV ECX,[%RightOperand+EXP.Low] ; DictRegisters.Data
    CALL ExpEval.AdoptIndexing:
    JC ExpEval.Error: ; Report error in adopting a register in ECX.
    JMP ExpEval.DoneBinary:
   ENDP .Addition:

.Subtraction: PROC
    CALL ExpEval.CheckLeftOpNumber: ; Convert String to Number,
    CALL ExpEval.CheckRightOpNumber: ; ignore if not possible.
    MOV AL,[%RightOperand+EXP.Status] ; Right operand
    MOV AH,[%LeftOperand+EXP.Status] ; Left operand
    Dispatch AX,'NN','NA','NR','AA'
    JMP ExpEval.E6301: ; !2O applied to illegal operand in "!1S".',0
.AA: ; [Address-address].
    MOV EAX,[%RightOperand+EXP.Seg] ; Right operand section.
    MOV EAX,[EAX+SSS.SegmPtr]       ; Right operand segment.
    MOV EDX,[%LeftOperand+EXP.Seg]  ; Left operand section.
    MOV EDX,[EDX+SSS.SegmPtr]       ; Left operand segment.
    SUB EAX,EDX
    JNE ExpEval.E6331: ; Subtraction of addresses from different segments in expression "!1S".
    MOV [%LeftOperand+EXP.Seg],EAX ; Convert address to a plain number.
    MOV [%LeftOperand+EXP.Sym],EAX
    MOVB [%LeftOperand+EXP.Status],'N'
.NN:MOV EAX,[%RightOperand+EXP.Low] ; [Scalar-scalar].
    MOV EDX,[%RightOperand+EXP.High]
    SUB [%LeftOperand+EXP.Low],EAX ; The actual Subtraction.
    SBB [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
.NA:MOV EAX,[%RightOperand+EXP.Low] ; [Address-scalar].
    MOV EDX,[%RightOperand+EXP.High]
    SUB [%LeftOperand+EXP.Low],EAX  ; Subtract scalar from address.
    SBB [%LeftOperand+EXP.High],EDX ; Ignore overflow in displacement calculations.
    JMP ExpEval.DoneBinary:
.NR:MOV ECX,[%LeftOperand+EXP.Low] ; [Reg-scalar].
    CALL ExpEval.AdoptIndexing:
    JC ExpEval.Error: ; Report error in adopting a register in ECX.
    CALL ExpEval.SwapOperands:
    MOV EAX,[%LeftOperand+EXP.Low]
    MOV EDX,[%LeftOperand+EXP.High]
    NOT EAX ; Negate the number.
    NOT EDX
    ADD EAX,1
    ADC EDX,0
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
   ENDP .Subtraction:

.Scaling: PROC
    CALL ExpEval.CheckLeftOpNumber:  ; Convert String to Number,
    CALL ExpEval.CheckRightOpNumber: ; ignore if not possible.
    MOV AL,[%RightOperand+EXP.Status] ; Right operand
    MOV AH,[%LeftOperand+EXP.Status] ; Left operand
    Dispatch AX,'NR','RN'
    JMP ExpEval.E6301: ; !2O applied to illegal operand in "!1S".',0
.NR: ; [Reg*scalar].
    CALL ExpEval.SwapOperands:
.RN: ; [Scalar*reg].
    MOV EDX,[%LeftOperand+EXP.High]
    MOV EAX,[%LeftOperand+EXP.Low]
    TEST EDX ; Scaling factor.High
    JNZ ExpEval.E6279: ; Invalid scaling factor in expression "!1S".
    DEC EDX ; Prepare EDX=-1 for the case when scale=0.
    BSR ECX,EAX
    JNZ .20:
    MOV ECX,[%RightOperand+EXP.Low] ; Indexregister data.
    CALL ExpEval.AdoptScaling: ; EDX=scaling (-1,0,1,2,3 for 0*,1*,2*,4*,8*)
    JC ExpEval.Error: ; Error in adopting a register. EBX=MsgId, AL=!2R.
    JMP ExpEval.DoneBinary
.20:CMP CL,3
    JA ExpEval.E6279: ; Invalid scaling factor in expression "!1S".
    BSF EDX,EAX
    CMP ECX,EDX
    JNE ExpEval.E6279: ; Invalid scaling factor in expression "!1S".
    ; Scaling factor EAX is 1,2,4 or 8.
    MOV ECX,[%RightOperand+EXP.Low] ; Indexregister data.
    CALL ExpEval.AdoptScaling: ; EDX=scaling (-1,0,1,2,3 for 0*,1*,2*,4*,8*)
    JC ExpEval.Error: ; Error in adopting a register in ECX (E6272 or E6277).
    SUB EAX,EAX
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EAX
    JMP ExpEval.DoneBinary:
    ENDP .Scaling:

.Multiplication: PROC ; If any operand is register, the operation will reclassify to Scaling.
    CMPB [%RightOperand+EXP.Status],'R'
    JE .10:
    CMPB [%LeftOperand+EXP.Status],'R'
    JNE .20:
 .10: ; Convert multiplication to scaling.
    MOV EAX,[DictOperationScaling:: + DICT.Data]
    DECD [EBX+EXP.High] ; Change priority from Multiplication (11) to Scaling (10).
    MOV [EBX+EXP.Low],EAX
    MOV EAX,ExpEval.Scaling:
    MOV [EBX+EXP.Seg],EAX
    JMP ExpEval.PhaseTwo: ; Whole expression in %ExpBuffer must be reevaluated due to priority change.
 .20: ; Ordinary multiplication.
    CALL ExpEval.CheckBinaryNumeric: ; Convert String/Char constant to Number.
    JC ExpEval.ErrorEAX:
    MOV EAX,[%RightOperand+EXP.Low]
    MOV ESI,[%LeftOperand+EXP.Low]
    MOV EDI,[%LeftOperand+EXP.High]
    MUL ESI ; Right.Low * Left.Low.
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    MOV EAX,[%RightOperand+EXP.Low]
    MUL EDI ; Right.Low * Left.High
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    ADD [%LeftOperand+EXP.High],EAX
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    MOV EAX,[%RightOperand+EXP.High]
    MUL ESI ; Right.High * Left.Low
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    ADD [%LeftOperand+EXP.High],EAX
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    MOV EAX,[%RightOperand+EXP.High]
    MUL EDI ; Left.High * Right.High
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    TEST EAX
    JNZ ExpEval.E6311: ; Multiplication 64bit overflow
 .90:JMP ExpEval.DoneBinary:
    ENDP .Multiplication:

.SignedMultiplication: PROC
    CALL ExpEval.CheckBinaryNumeric: ; Convert String/Char constant to Number.
    JC ExpEval.ErrorEAX:
    MOV CX,0x8000 ; CH=Signum mask, CL=result signum.
    TEST [%LeftOperand+EXP.High+3],CH
    JZ .30:
    CALL ExpEval.NegLeftOperand:
    XOR CL,1
 .30:TEST [%RightOperand+EXP.High+3],CH
    JZ .40:
    CALL ExpEval.NegRightOperand:
    XOR CL,1
 .40: ; Both operands are now positive. CL is signum of the result (0 or 1).
    MOV EAX,[%RightOperand+EXP.Low]
    MOV ESI,[%LeftOperand+EXP.Low]
    MOV EDI,[%LeftOperand+EXP.High]
    MUL ESI
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    MOV EAX,[%RightOperand+EXP.Low]
    MUL EDI
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    ADD [%LeftOperand+EXP.High],EAX
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    MOV EAX,[%RightOperand+EXP.High]
    MUL ESI
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    ADD [%LeftOperand+EXP.High],EAX
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    MOV EAX,[%RightOperand+EXP.High]
    MUL EDI
    JO ExpEval.E6311: ; Multiplication 64bit overflow
    TEST EAX
    JNZ ExpEval.E6311: ; Multiplication 64bit overflow
    MOV EAX,[%LeftOperand+EXP.High]
    TEST EAX
    JS  ExpEval.E6311: ; Multiplication 64bit overflow
    TEST CL
    JZ .90:
    CALL ExpEval.NegLeftOperand:
 .90:JMP ExpEval.DoneBinary:
    ENDP .SignedMultiplication:

.Divide64: PROC ; Callable subprocedure to divide unsigned [%LeftOperand] by [%RightOperand].
 ; Returns Quotient in EDX:EAX. Changes ESI,EDI.  Called from .Division and .Modulo operations.
     XOR EAX,EAX
     STC
     MOV [%Walking1Low],EAX
     MOV [%QuotientLow],EAX
     MOV [%QuotientHigh],EAX
     RCR EAX,1
     MOV [%Walking1High],EAX ; Walking1 and Quotient initialized.
     MOV EAX,[%QuotientLow]
     MOV EDX,[%QuotientHigh]
 .40:OR  EAX,[%Walking1Low]
     OR  EDX,[%Walking1High]
     MOV [%QuotientLow],EAX
     MOV [%QuotientHigh],EDX
    ; Try if quotient(EDX:EAX) multiplied with divisor(%RightOperand) is not bigger than divident(%LeftOperand)
     MOV EAX,[%QuotientHigh]
     MULD [%RightOperand+EXP.High]
     JC .60:
     TEST EAX
     STC
     JNZ .60:
     MOV ESI,EAX
     MOV EDI,EDX
     MOV EAX,[%QuotientHigh]
     MULD [%RightOperand+EXP.Low]
     JC .60:
     ADD EDI,EAX
     JC .60:
     MOV EAX,[%QuotientLow]
     MULD [%RightOperand+EXP.High]
     JC .60:
     ADD EDI,EAX
     JC .60:
     MOV EAX,[%QuotientLow]
     MULD [%RightOperand+EXP.Low]
     ADD ESI,EAX
     ADC EDI,EDX
     JC .60:
     CMP [%LeftOperand+EXP.High],EDI
     JNE .60:
     CMP [%LeftOperand+EXP.Low],ESI
 .60:MOV EAX,[%QuotientLow]
     MOV EDX,[%QuotientHigh]
     JC  .70: ; CF=1      product is above (reset the Walking1 in Quotient).
     JNE .80: ; CF=0 ZF=0 product is below (keep  the Walking1 in Quotient).
     JE  .90: ; CF=0 ZF=1 product is equal (division done).
 .70:XOR EAX,[%Walking1Low]  ; Product too big, reset the current walking bit.
     XOR EDX,[%Walking1High]
     MOV [%QuotientLow],EAX
     MOV [%QuotientHigh],EDX
 .80:SHRD [%Walking1High]
     RCRD [%Walking1Low]
     JNC .40: ; Repeat for all 64 bits.
 .90:RET
    ENDP .Divide64:

.Division: PROC  ; In the expression a / b = c, a is called the dividend,
                 ; b is the divisor and c is called the quotient.
     CALL ExpEval.CheckBinaryNumeric: ; EDX:EAX=Dividient
     JC ExpEval.ErrorEAX:
     MOV EDI,[%RightOperand+EXP.High]
     MOV ESI,[%RightOperand+EXP.Low]
     MOV ECX,EDI
     OR  ECX,ESI
     JZ ExpEval.E6310: ; !2O by zero in "!1S".
     TEST EDI
     JNZ .Division64:
     ; 32bit division can be calculated with one DIV.
     CMP EDX,ESI
     JAE .Division64:
     DIV ESI
     SUB EDX,EDX
     JMP .70:
.Division64:
     CALL ExpEval.Divide64:
 .70:; EDX:EAX is quotient.
     MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
     JMP ExpEval.DoneBinary:
    ENDP .Division:

.SignedModulo: PROC
     CALL ExpEval.CheckBinaryNumeric: ; Convert String/Char constant to Number.
     JC ExpEval.ErrorEAX:
     MOV CX,0x8000 ; CH=Signum mask, CL=result signum.
     TEST [%LeftOperand+EXP.High+3],CH
     JZ .10:
     CALL ExpEval.NegLeftOperand:
     OR CL,1
 .10:TEST [%RightOperand+EXP.High+3],CH
     JZ .20:
     CALL ExpEval.NegRightOperand:
 .20: ; Both operands are now positive. CL is signum of the divident=signum of the remainder.
     MOV EDI,[%RightOperand+EXP.High]
     MOV ESI,[%RightOperand+EXP.Low]
     OR  EDI,ESI
     MOV EDI,[%RightOperand+EXP.High]
     JZ ExpEval.E6310: ; !2O by zero in "!1S".
     TEST EDI
     JNZ .Division64:
     ; 32bit modulo can be calculated with one DIV.
     MOV EDX,[%LeftOperand+EXP.High]
     MOV EAX,[%LeftOperand+EXP.Low]
     CMP EDX,ESI
     JAE .Division64:
     DIV ESI ; 32bit modulo.
     MOV EAX,EDX ; 32bit unsigned remainder.
     SUB EDX,EDX
     MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
     JMP .70:
 .Division64:
     CALL ExpEval.Divide64:
    ; EDX:EAX is unsigned quotient. CL is signum of quotient.
     MULD [%RightOperand+EXP.Low]
     MOV ESI,EAX
     MOV EDI,EDX
     MOV EAX,[%QuotientLow]
     MULD [%RightOperand+EXP.High]
     ADD EDI,EAX
     MOV EAX,[%QuotientHigh]
     MULD [%RightOperand+EXP.Low]
     ADD EDI,EAX
     SUB [%LeftOperand+EXP.Low],ESI
     SBB [%LeftOperand+EXP.High],EDI
 .70:TEST CL
     JZ .80:
     CALL ExpEval.NegLeftOperand:
 .80:JMP ExpEval.DoneBinary:
    ENDP .SignedModulo:

.Modulo: PROC  ; Unsigned modulo.
     CALL ExpEval.CheckBinaryNumeric: ; EDX:EAX=Dividient
     JC ExpEval.ErrorEAX:
     MOV EDI,[%RightOperand+EXP.High]
     MOV ESI,[%RightOperand+EXP.Low]
     MOV ECX,EDI
     OR  ECX,ESI
     JZ ExpEval.E6310: ; !2O by zero in "!1S".
     TEST EDI
     JNZ .Division64:
     ; 32bit modulo can be calculated with one DIV.
     CMP EDX,ESI
     JAE .Division64:
     DIV ESI
     MOV [%LeftOperand+EXP.Low],EDX
     MOVD [%LeftOperand+EXP.High],0
     JMP .90:
.Division64:
     CALL ExpEval.Divide64:
     ; EDX:EAX = [%Quotient].
     MULD [%RightOperand+EXP.Low]
     MOV ESI,EAX
     MOV EDI,EDX
     MOV EAX,[%QuotientLow]
     MULD [%RightOperand+EXP.High]
     ADD EDI,EAX
     MOV EAX,[%QuotientHigh]
     MULD [%RightOperand+EXP.Low]
     ADD EDI,EAX
     SUB [%LeftOperand+EXP.Low],ESI
     SBB [%LeftOperand+EXP.High],EDI
 .90:JMP ExpEval.DoneBinary:
    ENDP .Modulo:

.SignedDivision: PROC
     CALL ExpEval.CheckBinaryNumeric: ; Convert String/Char constant to Number.
     JC ExpEval.ErrorEAX:
     MOV CX,0x8000 ; CH=Signum mask, CL=result signum.
     TEST [%LeftOperand+EXP.High+3],CH
     JZ .10:
     CALL ExpEval.NegLeftOperand:
     XOR CL,1
 .10:TEST [%RightOperand+EXP.High+3],CH
     JZ .20:
     CALL ExpEval.NegRightOperand:
     XOR CL,1
 .20: ; Both operands are now positive. CL is signum of the result.
     MOV EDI,[%RightOperand+EXP.High]
     MOV ESI,[%RightOperand+EXP.Low]
     OR  EDI,ESI
     MOV EDI,[%RightOperand+EXP.High]
     JZ ExpEval.E6310: ; !2O by zero in "!1S".
     TEST EDI
     JNZ .Division64:
     ; 32bit division can be calculated with one DIV.
     MOV EDX,[%LeftOperand+EXP.High]
     MOV EAX,[%LeftOperand+EXP.Low]
     CMP EDX,ESI
     JAE .Division64:
     DIV ESI ; 32bit integer division.
     SUB EDX,EDX
     JMP .70:
.Division64:
     CALL ExpEval.Divide64:
 .70:; EDX:EAX is quotient. CL is signum.
     MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
     TEST CL
     JZ .80:
     CALL ExpEval.NegLeftOperand:
 .80:JMP ExpEval.DoneBinary:
    ENDP .SignedDivision:

.NumericEqual: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EAX,[%RightOperand+EXP.Low]
    JNE ExpEval.ReturnFalse:
    CMP EDX,[%RightOperand+EXP.High]
    JNE ExpEval.ReturnFalse:
    JMP ExpEval.ReturnTrue:
   ENDP .NumericEqual:

.NumericNonEqual2:
.NumericNonEqual: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EAX,[%RightOperand+EXP.Low]
    JNE ExpEval.ReturnTrue:
    CMP EDX,[%RightOperand+EXP.High]
    JNE ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .NumericNonEqual:

.Above: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JA  ExpEval.ReturnTrue:
    JB  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JA  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .Above:

.Below: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JB  ExpEval.ReturnTrue:
    JA  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JB  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .Below:

.AboveOrEqual: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JA  ExpEval.ReturnTrue:
    JB  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JAE ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .AboveOrEqual:

.BelowOrEqual: PROC
    CALL ExpEval.CheckBinaryNumericAddr:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JA  ExpEval.ReturnFalse:
    JB  ExpEval.ReturnTrue:
    CMP EAX,[%RightOperand+EXP.Low]
    JBE ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .BelowOrEqual:

.Greater: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JG  ExpEval.ReturnTrue:
    JL  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JG  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .Greater:

.Lower: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JL  ExpEval.ReturnTrue:
    JG  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JL  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .Lower:

.LowerOrEqual:PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JL  ExpEval.ReturnTrue:
    JG  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JLE ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .LowerOrEqual:

.GreaterOrEqual: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    CMP EDX,[%RightOperand+EXP.High]
    JG  ExpEval.ReturnTrue:
    JL  ExpEval.ReturnFalse:
    CMP EAX,[%RightOperand+EXP.Low]
    JGE ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .GreaterOrEqual:

.LogicalAnd: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    OR EAX,EDX
    JZ ExpEval.ReturnFalse:
    MOV EAX,[%RightOperand+EXP.Low]
    OR  EAX,[%RightOperand+EXP.High]
    JZ  ExpEval.ReturnFalse:
    JMP ExpEval.ReturnTrue:
   ENDP .LogicalAnd:

.LogicalOr: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    OR EAX,EDX
    JNZ ExpEval.ReturnTrue:
    MOV EAX,[%RightOperand+EXP.Low]
    OR  EAX,[%RightOperand+EXP.High]
    JNZ  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .LogicalOr:

.LogicalXor: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    OR EAX,EDX
    MOV ECX,[%RightOperand+EXP.Low]
    OR  ECX,[%RightOperand+EXP.High]
    JZ .20:
    TEST EAX
    JZ  ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
 .20:TEST EAX
    JNZ ExpEval.ReturnTrue:
    JMP ExpEval.ReturnFalse:
   ENDP .LogicalXor:

.BitwiseAnd: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    AND EAX,[%RightOperand+EXP.Low]
    AND EDX,[%RightOperand+EXP.High]
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
   ENDP .BitwiseAnd:

.BitwiseOr: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    OR  EAX,[%RightOperand+EXP.Low]
    OR  EDX,[%RightOperand+EXP.High]
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
   ENDP .BitwiseOr:

.BitwiseXor: PROC
    CALL ExpEval.CheckBinaryNumeric:
    JC ExpEval.ErrorEAX:
    XOR EAX,[%RightOperand+EXP.Low]
    XOR EDX,[%RightOperand+EXP.High]
    MOV [%LeftOperand+EXP.Low],EAX
    MOV [%LeftOperand+EXP.High],EDX
    JMP ExpEval.DoneBinary:
   ENDP .BitwiseXor:

.ShiftLogicalLeft: PROC
     CALL ExpEval.CheckBinaryNumeric:
     JC ExpEval.ErrorEAX:
     MOV ESI,[%RightOperand+EXP.High]
     MOV ECX,[%RightOperand+EXP.Low] ; Number of shifts.
     TEST ESI
     JS .Reverse:
     JZ .10:
     MOV ECX,64
 .10:TEST ECX
     JZ .90:
 .20:SHL EAX,1
     RCL EDX,1
     LOOP .20:
     MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
 .90:JMP ExpEval.DoneBinary:
 .Reverse:
    CALL ExpEval.NegRightOperand:
    JMP  ExpEval.ShiftLogicalRight:
   ENDP .ShiftLogicalLeft:

.ShiftLogicalRight: PROC
     CALL ExpEval.CheckBinaryNumeric:
     JC ExpEval.ErrorEAX:
     MOV ESI,[%RightOperand+EXP.High]
     MOV ECX,[%RightOperand+EXP.Low] ; Number of shifts.
     TEST ESI
     JS .Reverse:
     JZ .10:
     MOV ECX,64
 .10:JECXZ .90:
 .20:SHR EDX,1
     RCR EAX,1
     LOOP .20:
     MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
 .90:JMP ExpEval.DoneBinary:
 .Reverse:
     CALL ExpEval.NegRightOperand:
     JMP ExpEval.ShiftLogicalLeft:
   ENDP .ShiftLogicalRight:

.ShiftArithmeticLeft: PROC
     CALL ExpEval.CheckBinaryNumeric:
     JC ExpEval.ErrorEAX:
     MOV ESI,[%RightOperand+EXP.High]
     MOV ECX,[%RightOperand+EXP.Low] ; ESI:ECX=Number of shifts.
     TEST ESI
     JS .Reverse:
     JZ .10:
     MOV ECX,64
 .10:JECXZ .90:
 .20:SAL EAX,1 ; SAL of positive number. CF=overflow.
     RCL EDX,1
     JO ExpEval.E6311:
     LOOP .20:
 .80:MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
 .90:JMP ExpEval.DoneBinary:
 .Reverse:
     CALL ExpEval.NegRightOperand:
     JMP ExpEval.ShiftArithmeticRight:
   ENDP .ShiftArithmeticLeft:

.ShiftArithmeticRight: PROC
     CALL ExpEval.CheckBinaryNumeric:
     JC ExpEval.ErrorEAX:
     MOV ESI,[%RightOperand+EXP.High]
     MOV ECX,[%RightOperand+EXP.Low] ; Number of shifts.
     TEST ESI
     JS .Reverse:
     JZ .10:
     MOV ECX,64
 .10:JECXZ .90:
 .20:SAR EDX,1
     RCR EAX,1
     LOOP .20:
 .80:MOV [%LeftOperand+EXP.Low],EAX
     MOV [%LeftOperand+EXP.High],EDX
 .90:JMP ExpEval.DoneBinary:
 .Reverse:
     CALL ExpEval.NegRightOperand:
     JMP ExpEval.ShiftArithmeticLeft:
   ENDP .ShiftArithmeticRight:

.StringCmp: PROC ; Common code for strings compare operations.
; Input: ECX=0 for case insensitive, -1 otherwise. EBX=^EXP with StringCmp operation.
; Output:CF=0, ZF=strings are equal. EAX,ECX,EDX,ESI,EDI destroyed.
; Error: CF=1, EBX='6321' or '6160'.     ECX,EDX,ESI,EDI destroyed.
     CMPB [%LeftOperand+EXP.Status],'G'
     JE .10:
.E6321: ; String compare !2O with non-string operand in expression "!1S".
     MOV EDX,[EBX+EXP.Sym] ; Operation ordinal.
     MOV EBX,'6321'  ; String compare !2O with non-string operand in expression "!1S".
     STC
     JMP .90:
 .10:CMPB [%RightOperand+EXP.Status],'G'
     JNE .E6321: ; String compare !2O with non-string operand in expression "!1S".
     Invoke EaBufferReserve::, ExpEval.StringCmp
     MOV EDX,EAX ; Left string buffer handle.
     Invoke ExpStoreString, [%LeftOperand+EXP.Low],[%LeftOperand+EXP.High],EDX,ECX
     JNC .20:
.E6160:MOV EBX,'6160' ; Syntax error in the string !1S.
     STC
     JMP .90:
 .20:Invoke EaBufferReserve::, ExpEval.StringCmp
     MOV EDI,EAX ; Right string buffer handle.
     Invoke ExpStoreString, [%RightOperand+EXP.Low],[%RightOperand+EXP.High],EDI,ECX
     JC .E6160: ; Syntax error in the string !1S.
     PUSH EDX,EDI ; Buffer handles.
       BufferRetrieve EDI
       MOV EDI,ESI ; Right string pointer.
       MOV EAX,ECX ; Netto size.
       BufferRetrieve EDX
       CMP EAX,ECX
       JNE .50: ; Different sizes.
       REPE CMPSB
 .50:POP EDI,EDX
     PUSHFD ; Save Zero flag.
       Invoke EaBufferRelease::, EDI
       Invoke EaBufferRelease::, EDX
     POPFD
     CLC
 .90:RET
    ENDP .StringCmp:

.SensEqual: PROC
     SUB ECX,ECX
     CALL ExpEval.StringCmp:
     JC ExpEval.Error:
     JNE ExpEval.ReturnFalse:
     JMP ExpEval.ReturnTrue:
    ENDP .SensEqual:

.SensNonEqual: PROC
     SUB ECX,ECX
     CALL ExpEval.StringCmp:
     JC ExpEval.Error:
     JE ExpEval.ReturnFalse:
     JMP ExpEval.ReturnTrue:
    ENDP .SensNonEqual:

.InsensEqual: PROC
     SUB ECX,ECX
     DEC ECX
     CALL ExpEval.StringCmp:
     JC ExpEval.Error:
     JNE ExpEval.ReturnFalse:
     JMP ExpEval.ReturnTrue:
    ENDP .InsensEqual:

.InsensNonEqual: PROC
     SUB ECX,ECX
     DEC ECX
     CALL ExpEval.StringCmp:
     JC ExpEval.Error:
     JE  ExpEval.ReturnFalse:
     JMP ExpEval.ReturnTrue:
    ENDP .InsensNonEqual:

; Attribute unary operations. %RightOperand will be replaced with its evaluated attribute.
; When the %RightOperand.Seg is sssExtern, its SSS.Status will be modified here, so its sssExtAttr
; specifies postponed attribute operation, which should be resolved at link time.
; Attribute operation with nonextern symbol is performed here.

.Size:: PROC ; Handler of attribute SIZE#.
   MOV EAX,[%RightOperand+EXP.Status]
   AND AL,0x7F ; Remove EXP.Status bit 7 used as expVbit4 in vector-index expressions.
   Dispatch AL,'A','N','M','S','R','O'
   JMP ExpEval.DoneAttribute0:
.R:MOV EAX,[%RightOperand+EXP.Low] ; SIZE# was applied on register.
   SHR EAX,24 ; DictRegisters.Data contains register size in bytes.
   JMP ExpEval.DoneAttributeN:
.S:MOV ESI,[%RightOperand+EXP.Seg] ; SIZE# was applied on SSS object.
   MOV EAX,[ESI+SSS.TopLow]
   MOV EDX,[ESI+SSS.TopHigh]
   SUB EAX,[ESI+SSS.BottomLow]
   SBB EDX,[ESI+SSS.BottomHigh]
   JMP ExpEval.DoneAttributeN64:
.O:JMP ExpEval.DoneAttributeScalar0: ; SIZE# was applied on operator.
.M:
.N:
.A:MOV ECX,[%RightOperand+EXP.Sym]
   CMP ECX,%ExpOperationListLength ; EXP.Sym can be 0 or operation-ordinal or ^SYM.
   JBE .O:
   MOV EAX,[ECX+SYM.Size]
   JMP ExpEval.DoneAttributeN:
 ENDP .Size:
 
.Type::    PROC ; Handler of attribute TYPE#.
   MOV ECX,[%RightOperand+EXP.Sym]
   MOV EAX,[%RightOperand+EXP.Status] ; If no typed symbol in ECX, use expression type.
   CMP ECX,%ExpOperationListLength
   JBE .N:
   MOV EAX,[ECX+SYM.Status]   ; ECX is ^SYM, use its type.
.N:AND EAX,0x7F
   JMP ExpEval.DoneAttributeN:
 ENDP .Type:

[.data]
ExpRegTypeTable: \ Conversion of shifted register family to REGTYPE# attribute (32 values).
 DB '?SFMETCCBBWWDDQQXXXXYYYYZZZZK?N?'
[.text]
.RegType:: PROC ; Handler of attribute REGTYPE#.
   MOV ECX,[%RightOperand+EXP.Status]
   MOV EAX,'?'
   CMP CL,'R' ; Is REGTYPE# applied to a register?
   JNE ExpEval.DoneAttributeN: ; Return '?' if argument of REGTYPE# is not a register.
   MOV EAX,[%RightOperand+EXP.Low] ; EAX is now register encoding.
   AND EAX,iiRegIdMask
   SHR EAX,3
   MOV AL,[ExpRegTypeTable+EAX] ; Translate shifted register family to one-letter attribute REGTYPE#.
   JMP ExpEval.DoneAttributeN:
 ENDP .RegType:

.Scope::   PROC  ; Handler of attribute SCOPE#.
   MOV EAX,[%RightOperand+EXP.Status]
   Dispatch AL,'O'
   MOV ECX,[%RightOperand+EXP.Sym]
   CMP ECX,%ExpOperationListLength
   JNA .S:
   MOV AL,'I'
   JSt [ECX+SYM.Status],symImport,.G:
   MOV AL,'E'
   JSt [ECX+SYM.Status],symExtern,.G:
   MOV AL,'X'
   JSt [ECX+SYM.Status],symExport,.G:
   MOV AL,'P'
   JSt [ECX+SYM.Status],symPublic,.G:
   MOV AL,'G'
   JSt [ECX+SYM.Status],symGlobal|symGlobalRef,.G:
.O:XOR ECX,ECX
   MOV [%RightOperand+EXP.Sym],ECX
.S:MOV AL,'S' ; Standard private scope is default.
.G:AND EAX,0x7F
   JMP ExpEval.DoneAttributeN:
 ENDP .Scope:
   
.Offset::  PROC ; Handler of attribute OFFSET#.
   MOV EAX,[%RightOperand+EXP.Status]
   Dispatch AL,'A','N','F','S'
   JMP ExpEval.DoneAttributeScalar0: ; Other expression types return offset=0.
.S:MOV ESI,[%RightOperand+EXP.Seg]
   TEST ESI
   JZ ExpEval.DoneAttributeScalar0:
   JNSt [ESI+SSS.Status],sssSection, ExpEval.DoneAttributeScalar0:
.N:
.F:MOV EAX,[%RightOperand+EXP.Low]
   MOV EDX,[%RightOperand+EXP.High]
   JMP ExpEval.DoneAttributeN64:
.A:MOV ESI,[%RightOperand+EXP.Seg]
   TEST ESI
   JZ .N:
   RstSt [ESI+SSS.Status],sssExtAttr
   OR [ESI+SSS.Status],dictAttrOFFSET<<16                                     ;>>
   JNSt [ESI+SSS.Status],sssExtern,.N:
   SUB EAX,EAX
   SUB EDX,EDX
   JMP ExpEval.DoneAttribute:
 ENDP .Offset:
 
.Section:: PROC ; Handler of attribute SECTION#.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'A','N','M','S'
    JMP ExpEval.DoneAttributeScalar0: ; Other types of expression return scalar 0.
.A:
.N:
.M:
.S:
    MOV ECX,[%RightOperand+EXP.Sym]
    MOV ESI,[%RightOperand+EXP.Seg]
    JECXZ .S5:
    MOV ESI,[ECX+SYM.Section]
    XOR ECX,ECX
    MOV [%RightOperand+EXP.Sym],ECX
.S5:TEST ESI
    JZ ExpEval.DoneAttributeScalar0:
    JSt [ESI+SSS.Status],sssStructure, ExpEval.DoneAttributeScalar0: ; Section# of struc member is plain 0.
    RstSt [ESI+SSS.Status],sssExtAttr
    JSt [ESI+SSS.Status],sssExtern,ExpEval.Segment: ; Section in external modules is identical to segment.
    MOV EAX,[ESI+SSS.BottomLow]
    MOV EDX,[ESI+SSS.BottomHigh]
    JMP ExpEval.DoneAttribute:
.O: XOR ECX,ECX
    MOV [%RightOperand+EXP.Sym],ECX
    JMP ExpEval.DoneAttribute:
 ENDP .Section:
 
.Segment:: PROC  ; Handler of attribute SEGMENT#.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'A','N','M','S'
    JMP ExpEval.DoneAttributeScalar0: ; Other types of expression return scalar 0.
.A:
.N:
.M:
.S:
    MOV ECX,[%RightOperand+EXP.Sym]
    MOV ESI,[%RightOperand+EXP.Seg]
    JECXZ .S5:
    MOV ESI,[ECX+SYM.Section]
    XOR ECX,ECX
    MOV [%RightOperand+EXP.Sym],ECX
.S5:TEST ESI
    JZ ExpEval.DoneAttribute0:
    JSt [ESI+SSS.Status],sssStructure, ExpEval.DoneAttribute0: ; Segment# of struc member is plain 0.
    RstSt [ESI+SSS.Status],sssExtAttr
    JNSt [ESI+SSS.Status],sssExtern,.S7:
    ; Operation SEGMENT# applied to extern symbol will be postponed to link time.
    OR [ESI+SSS.Status],dictAttrSEGMENT<<16                                     ; >>
.S7:MOV ESI,[ESI+SSS.SegmPtr]
    XOR EAX,EAX
    XOR EDX,EDX
    JMP ExpEval.DoneAttribute:
 ENDP .Segment:

.Group:: PROC  ; Handler of attribute GROUP#.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'A','N','M','S'
    JMP ExpEval.DoneAttributeScalar0: ; Other types of expression return scalar 0.
.A:
.N:
.M:
.S:
    MOV ECX,[%RightOperand+EXP.Sym]
    MOV ESI,[%RightOperand+EXP.Seg]
    JECXZ .G5:
    MOV ESI,[ECX+SYM.Section]
    XOR ECX,ECX
    MOV [%RightOperand+EXP.Sym],ECX
.G5:TEST ESI
    JZ ExpEval.DoneAttributeScalar0:
    JSt [ESI+SSS.Status],sssStructure, ExpEval.DoneAttributeScalar0: ; Group# of struc member is plain 0.
    MOV EAX,ESI
    MOV ESI,[EAX+SSS.GroupPtr]
    TEST ESI
    JNZ .G7:
    MOV ESI,[EAX+SSS.SegmPtr] ; If not in group, return segment address.
.G7:RstSt [ESI+SSS.Status],sssExtAttr
    JNSt [ESI+SSS.Status],sssExtern,.G8:
    ; Operation GROUP# applied to extern symbol will be postponed to link time.
    OR [ESI+SSS.Status],dictAttrGROUP<<16                                        ; >>
.G8:XOR EAX,EAX
    XOR EDX,EDX
    JMP ExpEval.DoneAttribute:
 ENDP .Group::

.Para:: PROC ; Handler of attribute PARA#. Similar to .Group:: but sets expPara.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'A','S'
    JNE ExpEval.DoneAttributeScalar0: ; Other types of expression return scalar 0.
.S:
.A: MOV ECX,[%RightOperand+EXP.Sym]
    MOV ESI,[%RightOperand+EXP.Seg]
    JECXZ .P5:
    MOV ESI,[ECX+SYM.Section]
.P5:TEST ESI
    JZ .P8:
    JSt [ESI+SSS.Status],sssStructure, ExpEval.DoneAttribute0: ; Para# of struc member is plain 0.
    MOV EAX,ESI
    MOV ESI,[EAX+SSS.GroupPtr]
    TEST ESI
    JNZ .P8:
    MOV ESI,[EAX+SSS.SegmPtr] ; If not in group, return segment address.
.P7:RstSt [ESI+SSS.Status],sssExtAttr
    JNSt [ESI+SSS.Status],sssExtern,.P8:
    ; Operation PARA# applied to extern symbol will be postponed to link time.
    OR [ESI+SSS.Status],dictAttrPARA<<16                                        ; >>
.P8:XOR EAX,EAX
    XOR EDX,EDX
    MOV ECX,'P'+expPara ; Base segment register value will be requested by relocation.
    JMP ExpEval.Scalar:
 ENDP .Para::

.FileSize:: PROC ; Handler of attribute FILESIZE#.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'G'
.Abort:JMP ExpEval.DoneAttributeScalar0: ; Other types of expression than filename string return 0.
.G: MOV ESI,[%RightOperand+EXP.Low]
    MOV ECX,[%RightOperand+EXP.High] ; ESI,ECX is quoted filename, not zero terminated.
    LODSB
    CMP AL,'"'
    JNE .Abort:
    CMP [ESI+ECX-2],AL
    JNE .Abort:
    SUB EAX,EAX
    MOV [ESI+ECX-2],AL
    SysGetFileSize ESI
    MOVB [ESI+ECX-2],'"'
    JMP ExpEval.DoneAttributeN64: ; Return 64bit filesize.
  ENDP .FileSize::

.FileTime:: PROC ; Handler of attribute FILETIME.
    MOV EAX,[%RightOperand+EXP.Status]
    Dispatch AL,'G'
.Abort:JMP ExpEval.DoneAttributeScalar0: ; Other types of expression than filename string return 0.
.G: MOV ESI,[%RightOperand+EXP.Low]
    MOV ECX,[%RightOperand+EXP.High] ; ESI,ECX is quoted filename, not zero terminated.
    LODSB
    CMP AL,'"'
    JNE .Abort:
    CMP [ESI+ECX-2],AL
    JNE .Abort:
    SUB EAX,EAX
    MOV [ESI+ECX-2],AL
    SysGetFileTime ESI
    MOVB [ESI+ECX-2],'"'
    JMP ExpEval.DoneAttributeN: ; Return 32bit timestamp of the file.
  ENDP .FileTime::

; Attribute handlers epilogue.
.DoneAttributeScalar0:
    XOR ESI,ESI
    MOV [%RightOperand+EXP.Sym],ESI
.DoneAttribute0:   ; Return scalar 0.
    XOR EAX,EAX
.DoneAttributeN:   ; Return 32bit scalar EAX.
    XOR EDX,EDX
.DoneAttributeN64: ; Return 64bit scalar EDX:EAX.
    XOR ESI,ESI
.DoneAttribute:    ; Return address. Expects EDX:EAX=offset, ESI=^SSS or 0.
    Invoke ExpWidth
    SHL ECX,8
    MOV CL,'N'
    TEST ESI
    JZ .Scalar:
    MOV CL,'A'
.Scalar:
    CMPB [%RightOperand+EXP.Status],'#' ; If the questioned expression was in error,
    JE .DoneUnary:                      ;  return this error instead of attribute value.
.NoError: 
    MOV [%RightOperand+EXP.Status],ECX
    MOV [%RightOperand+EXP.Low],EAX
    MOV [%RightOperand+EXP.High],EDX
    MOV [%RightOperand+EXP.Seg],ESI
    MOV ECX,[%RightOperand+EXP.Sym] ; ECX is either ^SYM or ordinal Nr of operation.
    CMP ECX,%ExpOperationListLength
    JBE .DoneUnary:
    SetSt [ECX+SYM.Status],symQueried+symUsed ; Prevent E6101 to raise due to referring attribute of undefined symbol.
    CMPB [%RightOperand+EXP.Status],'N'
    JNE .DoneUnary:
    MOVD [%RightOperand+EXP.Sym],0
   ;JMP .DoneUnary:
 
.DoneUnary: ; Unary operation EBX epilogue.
            ; Swallow EXP at EBX (unary operator). Keep %RightOperand as the result.
   BufferClear [%ExpBuffer] ; Mark as empty but do not erase data.
   MOV EAX,EBX
   MOV ESI,[%BufBottom]
   SUB EAX,ESI
   BufferStore [%ExpBuffer],ESI,EAX
   ADD EBX,SIZE#EXP ; Skip the calculated operation.
   MOV ECX,[%BufTop]
   SUB ECX,EBX
   BufferStore [%ExpBuffer],EBX,ECX
   JMP .PhaseTwo: ; Continue calculating the next operation.

.DoneBinary: ; Binary operation EBX epilogue.
             ; Swallow two EXPs at EBX (operation and right operand). Keep %LeftOperand as result.
   BufferClear [%ExpBuffer] ; Mark as empty but do not erase data.
   MOV EAX,EBX
   MOV ESI,[%BufBottom]
   SUB EAX,ESI
   BufferStore [%ExpBuffer],ESI,EAX
   ADD EBX,2*SIZE#EXP ; Skip the calculated operation and the right operand.
   MOV ECX,[%BufTop]
   SUB ECX,EBX
   BufferStore [%ExpBuffer],EBX,ECX
   JMP .PhaseTwo: ; Continue calculating the next operation.

.Calculated: ; .PhaseTwo just ended. ESI=^EXP with result.
    CMPD [%ParenthesisLevel],0
    JNE .E6221: ; Unbalanced parenth.: "(" without ")" in expression "!1S".
    MOV EAX,[ESI+EXP.Status]
    MOV EBX,[%TempStatus]
    MOV AH,BL ; 0 or 'M' if in [braces], BL bit 7 may be set (=expVbit4).
    AND AX,0x7F7F ; Remove expVbit4 for dispatching purpose.
    Dispatch AX,'NM','AM','RM','R','N','A','F','G','P','?' ; Other types are illegal.
    MOV EBX,'6200' ;  Syntax error in expression "!1S".
    JMP .Error:
.N: ; E.g. 1234
.?: ; E.g. UndefinedSymbol
.P: ; E.g. PARA# DataSym
.A: ; E.g. $+5 or FarProc
    JSt [ESI+EXP.Status],expPara,.export:
    MOV ECX,[ESI+EXP.Sym]
    JECXZ .F:
    JNSt [ECX+SYM.Status],symFar, .F:
    SetSt [ESI+EXP.Status],expFar
.F: ; E.g. 1234:5678
    MOV EAX,[ESI+EXP.Low]
    MOV EDX,[ESI+EXP.High]
    Invoke ExpWidth
    MOV [ESI+EXP.Status+1],CL
.G: ; E.g. "string"
.R: ; E.g. XMM0
  ; [%TempStatus] is not 'M', i.e. operand not in [].
.export: ; Presence of registers and/or scale is illegal.
    MOV ECX,[%TempStatus]
    JECXZ .ExpExport: ; OK, no base/index/scale adopted.
    MOV EBX,'6270' ; Address expression "!1S" must be in [].
    JMP .Error:
.NM: ; E.g. [1234]
.AM: ; E.g. [Symbol]
    MOV EAX,[ESI+EXP.Low]
    MOV EDX,[ESI+EXP.High]
    Invoke ExpWidth
    SHL ECX,8
    OR [%TempStatus],ECX
    JMPS .?M:
.RM: ; E.g. [EBX] or [XMM31].
    ; [%TempStatus] is 'M', it will replace [ESI+EXP.Status]
    MOV ECX,[ESI+EXP.Low] ; Register properties as in Dict.Register.Data.
    CALL .AdoptIndexing:
    JC ExpEval.Error: ; If adopting error.
    SUB ECX,ECX
    MOV [ESI+EXP.Low],ECX ; Remove register from address expression.
.?M:LEA ECX,[%SymStatus] ; This might contain type of symbol which appeared in expression.
    Invoke DictLookup::,DictDatatypesShort::,ECX,1
    MOV EAX,[%TempStatus]
    JC .M2: ; If not the case.
    MOV ECX,expVbit4
    AND ECX,EAX ; CL now has bit 7 set if adopted VSIB index was above 16.
    MOV AL,[%SymStatus] ; Replace 'M' with specific symbol type 'B','U','W','D','Q','T','O','Y','Z'.
    OR  EAX,ECX ; Keep expVbit4 in specific symbol, too.
.M2:MOV [ESI+EXP.Status],EAX
 ; Check for conflict in displacement size and register width in address expression.
    MOV ECX,EAX
    AND EAX,expAwidth
    JZ .ExpExport: ; If expAwidth was not specified (no registers), any expDwidth fits.
    AND ECX,expDwidth ; CH is now 0..7.
    CMP EAX,0x40000000
    JNE .M4:
    ; Address size was set by registers to 16 bit.
    CMP CH,5
    JA .E6281: ; Displacement in "!1S" is too big for address size 16 bit.
.M4:CMP EAX,0x80000000
    JNE .ExpExport:
    ; Address size was set by registers to 32 bit.
    CMP CH,6
    JA .E6282: ; Displacement in "!1S" is too big for address size 32 bit.
    ; JMP .ExpExport:
.B:
.U:
.W:
.D:
.Q:
.O:
.Y:
.Z:
.ExpExport:
    MOV EDI,[%Exp]
    MOV ECX,SIZE#EXP / 4
    REP MOVSD
    JMP .End:

[.data]
   ALIGN DWORD
.HandlersTable: ; Pointers to operation handlers declared in ExpOperationList.
operation %FOR %ExpOperationList
    DD .%operation
   %ENDFOR operation
.OperationNamesTable:: ; Pointers to names of operations declared in ExpOperationList.
operation %FOR %ExpOperationList ; Operation name is used in MsgProc 
    DD =B"%operation"            ;  in expansion of parameter !1O.
   %ENDFOR operation
[.text]

.Empty:SetSt [ESP],flagZ ; ZF=parsed expression was empty, which returns number 0.
      MOV EDI,[%Exp]
      Clear EDI,Size=SIZE#EXP
      MOVB [EDI+EXP.Status],'N'
      JMP .End:

.Export: ; [%ThisExp] is directly used as output %Exp.
       LEA ESI,[%ThisExp]
       MOV EDI,[%Exp]
       MOV ECX,SIZE#EXP / 4
       CMPB [ESI+EXP.Status],'#'
       JNE .Exp5:
       SetSt [ESP],flagC
 .Exp5:REP MOVSD
       JMP .End:
; Error handlers.

.ErrorEAX: ; Error from arithmetic operations.
    MOV EDX,[EBX+EXP.Sym] ; Operation ordinal number.
    MOV EBX,EAX ; MsgId.
    MOV EAX,EDX
    JMP .Error:
.E6100:MOV EBX,'6100' ; Operand cannot be empty.
    JMP .Error:
.E6101:MOV EBX,'6101' ; Expression "!1S" is followed by unexpected character "!3Z".
    JMP .ErrorP:
.E6103:MOV EBX,'6103' ; Missing "]" in expression "!1S".
    JMP .Error:
.E6109:MOV EBX,'6109' ; Premature end of expression "!1S".
    JMP .Error:    
.E6120:MOV EBX,'6120' ; Symbol "!1S" not found.
    JMP .Error:
.E6130:MOV EBX,'6130' ; The number "!1S" is too big for 64 bits.
    JMP .Error:
.E6160:MOV EBX,'6160' ; Syntax error in the string !1S.'
    JMP .Error:
.E6181:MOV EBX,'6181' ;  Unary operator instead of "!3Z" expected in expression "!1S"
    JMP .Error:    
.E6182:MOV EBX,'6182' ; Binary operator instead of "!3Z" expected in expression "!1S".
    JMP .Error:
.E6200:MOV EBX,'6200' ; Syntax error in expression "!1S".
    JMP .Error:    
.E6208:MOV EBX,'6208' ; Unary minus is not applicable to an address in expression "!1S".
    JMP .Error:
.E6220:MOV EBX,'6220' ; Unbalanced parenthesis: ")" without "(" in expression "!1S".
    JMP .ErrorP:
.E6221:MOV EBX,'6221' ; Unbalanced parenthesis: "(" without ")" in expression "!1S".
    JMP .Error:
.E6240:MOV EBX,'6240' ; Immediate far pointer "!1S" must not be in braces [].
    JMP .Error:
.E6241:MOV EBX,'6241' ; Segment part of imm.far pointer "!1S" must be a plain 16bit number.
    JMP .Error:
.E6242:MOV EBX,'6242' ; Invalid offset part of immediate far pointer "!1S".
    JMP .Error:
.E6279:MOV EBX,'6279' ; Invalid scaling factor in expression "!1S".
    JMP .Error:
.E6281:MOV EBX,'6281' ; Displacement in "!1S" is too big for address size 16 bit.
    JMP .Error:
.E6282:MOV EBX,'6282' ; Displacement in "!1S" is too big for address size 32 bit.
    JMP .Error:
.E6301:MOV EDX,[EBX+EXP.Sym]
    MOV EBX,'6301' ; !2O applied to illegal operand in "!1S".
    JMP .Error:
.E6310:MOV EDX,[EBX+EXP.Sym]
    MOV EBX,'6310' ; !2O by zero in "!1S".
    JMP .Error:
.E6311:MOV EDX,[EBX+EXP.Sym]
    MOV EBX,'6311' ; !2O 64bit overflow in "!1S".',0
    JMP .Error:
.E6331:MOV EBX,'6331' ; Subtraction of addr. from different segments in expression "!1S".
    JMP .ErrorP:
.E6671:MOV EBX,'6671' ; Invalid syntax of literal symbol !1S".    
    JMP .Error:
 .ErrorP; !1S will be [%TxtPtr]..ESI.
       ; Input: EBX=MsgId, AL=content of !3, EDX=!2O, ESI=parser position.
       MOV ECX,ESI
       SUB ECX,[%TxtPtr]
       JLE .Error: ; If ESI wasn't valid parser position.
       CMP ECX,[%TxtSize]
       JNGE .Err:
.Error:; Construction of error record in output EXP. !1S will be [%TxtPtr],[%TxtSize].
       MOV ECX,[%TxtSize]
 .Err: ; EBX=MsgId, EDX=!2O, AL=!3.
       MOV ESI,[%TxtPtr]
       MOV EDI,[%Exp]
       MOV [EDI+EXP.Seg],EBX ;   MsgId.
       MOV [EDI+EXP.Sym],EDX ;    !2O.
       SHL EAX,8
       MOV AL,'#'
       MOV [EDI+EXP.Status],EAX ; !3R.
       MOV [EDI+EXP.Low],ESI    ; !1S ptr.
       MOV [EDI+EXP.High],ECX   ; !1S size.
       SetSt [ESP],flagC
.End:  Invoke EaBufferRelease::, [%ExpBuffer]
      POPFD
 EndProcedure ExpEval
↑ ExpEvalIdentifier IdExp, IdPtr, IdEnd, StmPtr
ExpEvalIdentifier will parse, recognize and evaluate

If the first character is fullstop . (local label), the current namespace from context stack will be prefixed to the local name.
Symbol name may be terminated with one or more colons :. The terminating colon tells €ASM that the identifier is a symbol, even when it collides with nonsegment register or instruction name.

If the referrenced symbol was not defined yet, ExpEvalIdentifier does not define it, but it will create the record on Program.SymList by reference and return its estimated attributes. Creating of the symbol can be suppressed by Stm.Status:stmQueried, which happens when the symbol name is queried by attribute TYPE# or SIZE#.

Input
IdExp is pointer to a target EXP object, allocated by caller.
IdPtr is pointer to the first letter or fullstop of identifier.
IdEnd where the parsing of name stops.
StmPtr is pointer to the statement. Used when expression contains fwd referrenced symbols. If this parameter is NULL (when processing euroasm.ini etc), no symbol will be recognized.
Output
CF=0, IdExp is filled with expression corresponding to type 'S' (structure), 'R' (register), 'O' (attribute operator), 'N' or 'A' (symbol).
ESI= points to the character following the symbol notation (including the terminating colon, if any).
Error
CF=1, IdExp is filled with type '#', E6120 Symbol "!1S" not found.
ESI= points to the last parsed character which inflicted the error.
Example
%IdPtr %IdEnd | | MySymbol:: + 24 | ESI CF=0 IdExp.Status='A' %IdPtr %IdEnd | | EXP.Seg+EDI] | ESI CF=0 IdExp.Status='N' %IdPtr %IdEnd | | [ES:EDI+1234] | ESI CF=0 IdExp.Status='R' %IdPtr %IdEnd | | SIZE#SOMESTRUC | ESI CF=0 IdExp.Status='O' %IdPtr %IdEnd | | SIZE#SOMESTRUC | ESI CF=0 IdExp.Status='S'
Invokes
DictLookup EaBufferRelease EaBufferReserve ExpParseIdentifier ExpWidth PgmGetCurrent SssFind SymCreate SymDelocalName SymFindByName
Invoked by
ExpEval
ExpEvalIdentifier Procedure IdExp, IdPtr, IdEnd, StmPtr
EiBuffer    LocalVar ; Buffer for symbol name.
EiSize      LocalVar ; Identifier size.
EiStatus    LocalVar ; Parsing flags.
eiColon     EQU 1 ; Symbol name terminated with at least one colon.
eiExtern    EQU 2 ; Symbol name terminated with two or more colons.
      ClearLocalVar
      MOV ESI,[%IdPtr]
      MOV EDX,[%IdEnd]
      MOV EDI,[%IdExp]
      XOR EAX,EAX
      MOV ECX,SIZE#EXP / 4
      REP STOSD ; Preinitialize output EXP.
      MOV EDI,[%IdExp]
      Invoke EaBufferReserve::,ExpEvalIdentifier
      MOV [%EiBuffer],EAX ; Temporary buffer.
      Invoke ExpParseIdentifier,ESI,EDX,expFullstop
      MOV [%EiSize],EAX
      JC .E6120: ; Symbol "!1S" not found.
      ADD ESI,EAX ; Add parsed size.
      CMP ESI,EDX
      JNB .30:
      LODSB
      CMP AL,'#'
      JNE .10:
      MOV EAX,[%IdPtr]
      MOV ECX,ESI
      SUB ECX,EAX
      Invoke DictLookup::,DictUnaryOperators::,EAX,ECX
      JC .25: ; Skip if # follows but it's not valid attribute operator, e.g. SomeSymbol#<OtherSymb.
      ; Attribute operator recognized. EAX is DictUnaryOperators.Data.
      MOV [%ReturnESI],ESI
      MOV EDX,0x0F ; Mask priority from operator's DICT.Data.
      MOV ECX,EAX
      AND EDX,EAX
      SHR ECX,16 ; ECX=ordinal number of operation, starting with 1.
      ; Attribute-operation handler cannot be put to EXP.Seg yet,
      ; it will be specified later in ExpEval.StoreIdentifier.
      ; Similar adjustment will be needed for EXP.High (operation priority).
      MOV [EDI+EXP.Sym],ECX 
      ; ADD EDX,[%ParenthesisLevel] ; Neither the priority can be adjusted yet because ParenthesisLevel is not available.
      MOV [EDI+EXP.Low],EAX  ; DictOperators.Data.
      MOV [EDI+EXP.High],EDX ; Priority.
      MOV EAX,'O'
      MOV [EDI+EXP.Seg],ECX  ; Operation handler is temporarily populated with operation ordinal.
      MOV [EDI+EXP.Status],EAX
      JMP .90:
 .10: ; Identifier ESI,[%EiSize] is not terminated with #. It may be a symbol or structure or register.
      CMP AL,':' ; Terminator.
      JNE .25:
      ; Identifier is a symbol or segment register.
      SetSt [%EiStatus],eiColon
 .20: CMP ESI,EDX
      JNB .30:
      LODSB
      CMP AL,':'
      JNE .25:
      SetSt [%EiStatus],eiExtern
      JMP .20: ; Swallow all terminating colons.
 .25: DEC ESI
 .30: MOV [%ReturnESI],ESI
      Invoke SymDelocalName::,[%IdPtr],[%EiSize],[%EiBuffer],symDelocal
      BufferRetrieve [%EiBuffer]
      ; ESI,ECX is now delocalized identifier name, without any terminating colons.
      Invoke DictLookup::, DictRegisters::,ESI,ECX
      JC .35: ; If not a register.
      JSt EAX,iiRegSeg,.32:
      JSt [%EiStatus],eiColon,.40: ; Colon terminated identifier cannot be a structure name or non-segment register.
 .32: ; Register recognized. EAX=DictRegister.Data. 
      MOV [EDI+EXP.Low],EAX
      MOV EAX,'R'
      MOV [EDI+EXP.Status],EAX
      JMP .90:
 .35: Invoke SssFind::,sssStructure,0,ESI,ECX,0
      JC .40: 
      ; Structure name recognized. EAX=^SSS.
      MOV [EDI+EXP.Seg],EAX
      MOV EAX,'S'
      MOV [EDI+EXP.Status],EAX
      JMP .90:
 .40:  ; ESI,ECX is treated like a symbol. It may be external, forward-referenced, $.
      MOV EBX,[%StmPtr]
      TEST EBX
      JNZ .42:
      Invoke PgmGetCurrent::
      JC .E6120: ; Symbol "!1S" not found.
      MOV EDX,EAX ; Current program.
      JMPS .43:
 .42: MOV EDX,[EBX+STM.Program]
      TEST EDX
      JZ .E6120: ; Symbol "!1S" not found.
 .43: ; Test if special symbol $.
      CMP ECX,1
      JNE .60:
      CMPB [ESI],'$'
      JNE .60:
      ; Special symbol $ recognized. EBX=^STM, EDX=^PGM.
      JNSt [%EiStatus],eiExtern,.45:
      Msg '2711' ; Special dynamic symbol $ cannot be made global.
 .45: MOV ECX,[EDX+PGM.CurrentSect]
      XOR EAX,EAX
      XOR EDX,EDX
      JECXZ .50:
      MOV EAX,[ECX+SSS.OrgLow]
      MOV EDX,[ECX+SSS.OrgHigh]
 .50: MOV [EDI+EXP.Low],EAX
      MOV [EDI+EXP.High],EDX
      MOV [EDI+EXP.Seg],ECX ; Current section.
      XOR EAX,EAX
      MOV AL,'A'
      MOV [EDI+EXP.Status],EAX
      JMP .90:
.E6120:MOV EAX,'6120' ; Symbol "!1S" not found.
      MOV [EDI+EXP.Seg],EAX
      MOV ESI,[%IdPtr]
      MOV ECX,[%IdEnd]
      SUB ECX,ESI
      MOV [EDI+EXP.Low],ESI
      MOV [EDI+EXP.High],ECX
 .55: MOVB [EDI+EXP.Status],'#'
      Invoke EaBufferRelease::,[%EiBuffer]
      STC
      JMP .99:
 .60: ; ESI,ECX is an ordinary symbol. It may be external, forward-referenced, queried.
      MOV EAX,symReferenced
      TEST EBX ; ^STM.
      JZ .65:
      JNSt [EBX+STM.Status],stmQueried,.64:
      ; Attribute query is pending.
      RstSt [EBX+STM.Status],stmQueried
      Invoke SymFindByName::,0,ESI,ECX,0
      JNC .66:
      MOV BL,'?'
      JMP .88: ; Undefined symbol is queried.
 .64: JNSt [%EiStatus],eiExtern,.65:
      OR EAX,symGlobalRef
 .65: Invoke SymCreate::,EAX,ESI,ECX,EBX
 .66: MOV [EDI+EXP.Sym],EAX
      TEST EAX
      JZ .E6120: ; Symbol "!1S" not found.
 .70: MOV EBX,'N' ; Assume numeric symbol.
      MOV ECX,[EAX+SYM.Section]
      JECXZ .80:
      JNSt [ECX+SSS.Status],sssStructure,.75:
      XOR ECX,ECX ; Members of structure are scalar numbers.
      JMPS .80:
 .75: MOV BL,'A'
 .80: MOV [EDI+EXP.Seg],ECX
      MOV EDX,[EAX+SYM.OffsetHigh]
      MOV EAX,[EAX+SYM.OffsetLow]
      Invoke ExpWidth
      MOV BH,CL
      MOV [EDI+EXP.Low],EAX
      MOV [EDI+EXP.High],EDX
.88:  MOV [EDI+EXP.Status],EBX
.90:  Invoke EaBufferRelease::,[%EiBuffer]
      CLC
.99:EndProcedure ExpEvalIdentifier
↑ ExpGetNextPrime Number
ExpGetNextPrime returns a nearest prime number greater than the given Number, using [Primality] trial division algorithm.
Input numberReturned number
0..12
23
3..45
5..67
7..1011
11..1213
etc
Input
Number Unsigned input integer number.
Output
CF=0, EAX= the next prime greater than the input Number.
Error
CF=1 EAX=-1 on overflow.
Invoked by
PflibomfCompile
ExpGetNextPrime Procedure Number
     MOV EBX,[%Number]
     MOVD [%ReturnEAX],-1
 .10:INC EBX ; Try the next greater number.
     CMP EBX,3
     JBE .80:
     TEST BL,1
     JZ .10: ; If EBX is even.
     MOV EAX,EBX
     SUB EDX,EDX
     MOV ECX,3
     DIV ECX
     TEST EDX
     JZ .10: ; If EBX is divisible by 3.
     STC
     SBB ECX,ECX
 .20:ADD ECX,6 ; ECX will be 5 (,11,17,23,29...).
     MOV EAX,ECX
     MUL ECX
     JC .90:
     CMP EAX,EBX
     JA .80: ; EBX is prime.
     MOV EAX,EBX
     SUB EDX,EDX
     DIV ECX
     TEST EDX
     JZ .10: ; If EBX is divisible by 5 (,11,17,23,29...).
     LEA ESI,[ECX+2]
     MOV EAX,EBX
     SUB EDX,EDX
     DIV ESI
     TEST EDX
     JZ .10: ; If EBX is divisible by 7 (,13,19,25,31...).
     JMP .20
.80: MOV [%ReturnEAX],EBX ; Prime number found.
     CLC
.90:EndProcedure ExpGetNextPrime
  ENDPROGRAM exp

▲Back to the top▲