VAR represents an user-defined preprocessing %variable . Objects VAR are kept on Pass.VarList.
User-defined %variable is created/updated in %SET* pseudoinstruction on current program's Pass.VarList.
Other than user-defined %variables are not kept on lists, they are dynamically expanded on demand from the information kept in €ASM objects.
In the beginning of each pass its VarList is initialized from parent Pgm.VarList. When the last pass ends, its VarList is merged to Pgm.Varlist.
If the %variable name matches formal parameter of any ctxMACRO or ctxFOR between ctxPGM and the top of context stack, a warning W2510 is issued that formal parameter cannot be changed in %FOR or %MACRO block and normal (nonformal) %variable is created instead.
When a %variable is retrieved, it is searched for in the whole context stack. It can be found in ctxPGM, ctxFOR, ctxMACRO in the stack order.
Scope of preprocessing %variables is the whole source file.
EUROASM NOWARN=2101 var PROGRAM FORMAT=COFF,MODEL=FLAT,WIDTH=32 INCLUDEHEAD "euroasm.htm" ; Interface (structures, symbols and macros) of other modules. INCLUDEHEAD \ ; Include headers of another modules used in this module. ctx.htm, \ dict.htm, \ ea.htm, \ eaopt.htm, \ exp.htm, \ ii.htm, \ lst.htm, \ msg.htm, \ pass.htm, \ pgm.htm, \ pgmopt.htm, \ reloc.htm, \ sss.htm, \ stm.htm, \ sym.htm, \ syswin.htm, \ ;;
var HEAD ; Start of module interface.
VAR STRUC .NamePtr D DWORD ; Pointer to %variable name. .NameSize D DWORD ; Number of characters in %variable name including the % sign. .ValuePtr D DWORD ; Pointer to %variable contens. .ValueSize D DWORD ; Number of bytes in %variable value. .ValueAlloc D DWORD ; Size of memory allocated for the value. Usually dword aligned .ValueSize or greater. ENDSTRUC VAR
Type of preprocessing %variable is recognized by characters in its name and returned by VarParseName.
The mask under varTypeSysEnum
keeps ordinal number of system %^variable in the corresponding enumeration:
varTypeSysEasm
it is %EaoptEasmList,varTypeSysPgmOpt
it is %PgmoptList,varTypeSysEaopt
it is %EaoptMiscList,
%EaoptStatusList or
%EaoptFeaList.Flags varTypeSysEaoptS
and varTypeSysEaoptF
specify that the option belongs to
%EaoptStatusList or
%EaoptFeaList.
Ordinal varTypeSysEnum
is not valid in this case, and
DictLookup should be used to retrieve the corresponding flag from
DictEaoptStatus or
DictEaoptFea.
varTypeMask = 0x0000_FFFF ; Result of parsing any text which begins with %: varTypeNone = 0x0000_0000 ; %% varTypeLen = 0x0000_0001 ; %& varTypeExp = 0x0000_0002 ; %. varTypePseudo = 0x0000_0004 ; One of pseudoinstruction whose name begins with % (%SET, %SHIFT, %MACRO,..) varTypeId = 0x0000_0008 ; %abc User-defined %variable. Might be a %MACRO/%FOR formal %variable, too. varTypeSysEasm = 0x0000_0010 ; €ASM %^System %variable (%^DATE, %^LINE, %^PROGRAM, ...) varTypeSysPgmopt = 0x0000_0020 ; PROGRAM %^System %variable (%^FORMAT, %^MODEL, %SUBSYSTEM, ...) varTypeSysEaopt = 0x0000_0040 ; EUROASM %^System %variable (%^AMD, %^AUTOALIGN, %^WARN, ...) varTypeLabel = 0x0000_0080 ; %: varTypeOrd = 0x0000_0100 ; %123 varTypeOrdList = 0x0000_0200 ; %* varTypeOrdLen = 0x0000_0400 ; %# varTypeKeyList = 0x0000_0800 ; %=* varTypeKeyLen = 0x0000_1000 ; %=# varTypeInvId = 0x0000_2000 ; %!abc varTypeInvOrd = 0x0000_4000 ; %!123 varTypeSysEnum = 0x003F_0000 ; Ordinal of EUROASM system %^variable, valid with varTypeSys* only. varTypeLabelExt = 0x0100_0000 ; Label of macro was defined as external (terminated with double colon). varTypeSysKind = 0x7000_0000 ; Kind of EUROASM system %^variable, valid with varTypeSysEaopt only: varTypeSysEaoptM = 0x1000_0000 ; Ordinal number in varTypeSysEnum is from %EaoptMiscList. varTypeSysEaoptF = 0x2000_0000 ; Ordinal number in varTypeSysEnum is from %EaoptFeaList. varTypeSysEaoptS = 0x4000_0000 ; Ordinal number in varTypeSysEnum is from %EaoptStatusList.
ENDHEAD var ; End of module interface.
VarAssign Procedure StmPtr, Buffer MOV EBX,[%StmPtr] MOV EDI,[EBX+STM.Program] MOV ESI,[EBX+STM.LabelPtr] ; e.g. %Identifier MOV ECX,[EBX+STM.LabelSize] TEST EDI JZ .F9310: MOV EDX,[EDI+PGM.PassPtr] TEST EDX JZ .F9310: JECXZ .F9310: Invoke VarListSearch,[EDX+PASS.VarList],ESI,ECX JC .Create: MOV EBX,EAX ; Pointer to a VAR with this %name. BufferRetrieve [%Buffer] ; %Variable already exists, it will be overwritten. CMP ECX,[EBX+VAR.ValueAlloc] JBE .Reuse: PoolStore [EDX+PASS.Pool],ESI,ECX ; Old value is to short, a new room must be allocated from Pass.Pool. JC .F9310: MOV [EBX+VAR.ValueAlloc],ECX MOV [EBX+VAR.ValueSize],ECX MOV [EBX+VAR.ValuePtr],EAX JMP .Done: .F9310:Msg '9310',EBX ; Allocation error assigning value to %%!1S. .Error:STC JMP .End: .Reuse: MOV EDI,[EBX+VAR.ValuePtr] ; Old %Variable had a longer value, it may be reused. MOV [EBX+VAR.ValueSize],ECX REP MOVSB JMP .Done: .Create: ListNew [EDX+PASS.VarList] ; %Variable with the name ESI,ECX is not on the list. A new one will be appended. JC .F9310: MOV EBX,EAX PoolStore [EDX+PASS.Pool],ESI,ECX JC .F9310: MOV [EBX+VAR.NamePtr],EAX MOV [EBX+VAR.NameSize],ECX BufferRetrieve [%Buffer] MOV [EBX+VAR.ValueSize],ECX MOV EDI,12 CMP ECX,EDI JB .C2: MOV EDI,ECX .C2:MOV [EBX+VAR.ValueAlloc],EDI ; Allocated size is at least 12. PoolNew [EDX+PASS.Pool],EDI JC .F9310: MOV [EBX+VAR.ValuePtr],EAX MOV EDI,EAX REP MOVSB .Done:CLC .End:EndProcedure VarAssign
VarCheckFormal Procedure NamePtr, NameSize MOV EDX,[%NameSize] MOV EDI,[%NamePtr] TEST EDX STC JZ .99: INC EDI ; Get rid of the leading %. DEC EDX SUB EBX,EBX .20: Invoke CtxPeek::, ctxFOR | ctxMACRO, EBX JC .99: MOV EBX,EAX BufferRetrieve [EBX+CTX.FrmBuffer] JC .20: JECXZ .20: ; ESI,ECX is 1 or more formal parameters (NamePtr,NameSize,ValPtr,ValSize). .30: Compare [ESI+0],[ESI+4],EDI,EDX CLC JE .99: ; Formal variable found. ADD ESI,16 SUB ECX,16 JA .30: JMP .20: .99:EndProcedure VarCheckFormal
VarCheckId Procedure NamePtr, NameSize MOV ESI,[%NamePtr] MOV ECX,[%NameSize] LEA EDX,[ESI+ECX] Invoke VarParseName,ESI,EDX LEA EDI,[%NamePtr] CMP EAX,varTypeId Msg cc=NE,'7312',EDI ; "!1S" cannot be explicitly assigned. STC JNE .99: MOV ESI,[%NamePtr] Invoke VarCheckFormal,ESI,ECX Msg cc=NC,'2510',EDI ; Formal variable "!1S" will not be overwritten.',0 CLC .99:EndProcedure VarCheckId
%name{1..3}
|
ESI CF=0 EAX=varTypeId
%^TIME[1..2]
|
ESI CF=0 EAX=varTypeSysEasm + 10<<16 (ordinal of TIME in %EaoptEasmList=10)
%% copied.
|
ESI CF=0 EAX=varTypeNone
%+ wrong variable
|
ESI CF=1 EAX=varTypeNoneVarParseName Procedure TxtPtr, TxtEnd MOV ESI,[%TxtPtr] MOV EDX,[%TxtEnd] CMP ESI,EDX JNB .Error: LODSB CMP AL,'%%' JNE .ErrorB: CMP ESI,EDX JNB .End: LODSB ExpClassify AL Dispatch AH,expLetter,expDigit ; ! # % & * . : = ^ Dispatch AL,0x21,0x23,0x25,0x26,0x2A,0x2E,0x3A,0x3D,0x5E JMP .ErrorB: .0x21: ; %!abc or %!123 CMP ESI,EDX JNB .Error: LODSB ExpClassify AL CMP AH,expLetter JE .InvId: CMP AH,expDigit JE .InvOrd: JMP .ErrorB: .InvId:MOV EBX,varTypeInvId .InvI1:CMP ESI,EDX JNB .End: LODSB ExpClassify AL CMP AH,expLetter JE .InvI1: CMP AH,expDigit JE .InvI1: DEC ESI JMP .End: .InvOrd:MOV EBX,varTypeInvOrd .InvO1:CMP ESI,EDX JNB .End: LODSB ExpClassify AL CMP AH,expDigit JE .InvO1: DEC ESI JMP .End: .0x23: ; %# MOV EBX,varTypeOrdLen JMP .End: .0x25: ; %% MOV EBX,varTypeNone JMP .End: .0x26: ; %& MOV EBX,varTypeLen JMP .End: .0x2A: ; %* MOV EBX,varTypeOrdList JMP .End: .0x2E: ; %. MOV EBX,varTypeExp JMP .End: .0x3A: ; %: MOV EBX,varTypeLabel JMP .End: .0x3D: ; %=* or %=# CMP ESI,EDX JNB .Error: LODSB CMP AL,'*' MOV EBX,varTypeKeyList JE .End: CMP AL,'#' MOV EBX,varTypeKeyLen JE .End: JMP .ErrorB: .0x5E: ; %^id CMP ESI,EDX JNB .Error: .Sys1: CMP ESI,EDX JNB .Sys3: LODSB ExpClassify AL CMP AH,expLetter JE .Sys1: CMP AH,expDigit JE .Sys1: .Sys2: DEC ESI .Sys3: MOV EDI,[%TxtPtr] MOV ECX,ESI ADD EDI,2 ; Skip %^ SUB ECX,EDI MOV EBX,varTypeSysEasm Invoke DictLookup::, DictEasmSysVar::, EDI,ECX MOV EBX,EAX JNC .End: Invoke DictLookup::, DictPgmopt::, EDI,ECX MOV EBX,EAX JNC .End: Invoke DictLookup::, DictEaoptMisc::, EDI,ECX MOV EBX,EAX JNC .End: Invoke DictLookup::, DictEaoptStatus::, EDI,ECX MOV EBX,EAX JNC .End: Invoke DictLookup::, DictEaoptFea::, EDI,ECX MOV EBX,EAX JNC .End: JMP .Error: .expDigit:MOV EBX,varTypeOrd .expO1:CMP ESI,EDX JNB .End: LODSB ExpClassify AL CMP AH,expDigit JE .expO1: DEC ESI JMP .End: .expLetter: ; %identifier or %pseudoinstruction. CMP ESI,EDX JNB .expL2: LODSB ExpClassify AL CMP AH,expLetter JE .expLetter: CMP AH,expDigit JE .expLetter: DEC ESI .expL2:MOV EDI,[%TxtPtr] MOV ECX,ESI SUB ECX,EDI MOV EBX,varTypePseudo Invoke DictLookup::, DictPcPseudo::, EDI,ECX JNC .End: MOV EBX,varTypeId JMP .End: .ErrorB:DEC ESI .Error:SUB EBX,EBX ; varTypeNone STC JMPS .90: .End: CLC .90: MOV [%ReturnEAX],EBX MOV [%ReturnESI],ESI EndProcedure VarParseName
Input text begins with %variable name, which may be suboperated. VarExpand will parse and expand the %variable, including its chained&nested suboperations, to the output buffer and return pointer behind the parsed text. It is invoked recursively from StmExpandField and VarExpandField.
Expansion rules:
%%
expands to a single %.
%&
expands to Length. Error
E7311 is reported if the 4th parameter is -1.
%Reserved name is copied verbatim (e.g. %IF, %Comment
..).
%Identifier
(formal and user-defined %variable) is searched for in ctxMACROexp, ctxFOR, ctxPROGRAM
in the context stack order.
Automatic %macro_variables (%!identifier, %number, %!number, %*, %#, %=*, %=#, %:
)
are searched for in the topmost ctxMACROexp only.
Expansion unique number %.
is searched for in
ctxMACROexp, ctxFOR, ctxWHILE, ctxREPEAT in the context stack order.
Src.Lst.Status:lstNothingExp
is reset if a %variable is expanded,
except for varTypeNone|varTypePseudo
.
VarExpand Procedure TxtPtr, TxtEnd, OutBuffer, Length
VarExpStatus LocalVar ; varTypeLabelExt flag.
VarExErrPar LocalVar Size=8 ; Room for Msg parameter !1S in case of error.
VarExNumber LocalVar Size=20 ; Room for the expanded number.
VarDaysInMonths LocalVar Size=12 ; 31,28,31,30,...
EaStackCheck ; Check for stack overflow.
XOR EAX,EAX
MOV EDI,[%TxtPtr]
MOV [%VarExpStatus],EAX
Invoke VarParseName,EDI,[%TxtEnd] ; Examine %variable type and name.
MOV [%ReturnEAX],ESI ; End of %variable name without suboperations.
JC .E7310: ; Wrong preprocessing %%variable name "!1S"
CMP EAX,varTypeNone
JE .10:
JSt EAX,varTypePseudo,.10:
RstSt [Src.Lst.Status::],lstNothingExp ; %Variables of all other types require expansion.
.10: MOV ECX,ESI ; End of parsed name, it might point to suboperation.
MOV ESI,EDI
SUB ECX,EDI
JC .E7310: ; Wrong preprocessing %%variable name "!1S"
PUSH .StoreVarContents: ; Prepare return address from callable %variable-handler.
Dispatch AX, varTypeNone,varTypeLen,varTypeExp,varTypePseudo,varTypeId, \
varTypeSysEasm,varTypeSysEaopt,varTypeSysPgmopt,varTypeLabel,varTypeOrd, \
varTypeOrdList,varTypeOrdLen,varTypeKeyList,varTypeKeyLen,varTypeInvId,varTypeInvOrd
; Callable %variable handlers. After their RET they continue at .StoreVarContents:.
; Input: ESI,ECX variable name, e.g. "%Id", "%=#", "%1" etc.
; EAX= variable type in %Variable types encoding.
; Output:ESI,ECX variable contents to be stored into OutBuffer.
.varTypeNone: ; %%
MOV ECX,1
RET
.varTypeLen: ; %&.
MOV EAX,[%Length] ; -1 if not inside suboperation brackets.
CDQ
MOV ECX,EAX
INC ECX
JNZ .expandInteger:
Msg '7311' ; Suboperation length %& cannot be used outside brackets [] or {}.
RET ; Do not expand.
.expandInteger: ; EDX:EAX=integer to expand as an unsigned decimal number.
LEA EDI,[%VarExNumber]
MOV ESI,EDI
StoQD EDI,Align=left,Signed=no
MOV ECX,EDI
SUB ECX,ESI
RET
.expandFalse:
MOV ESI,=B"0"
MOV ECX,1
RET
.expandTrue:
MOV ESI,=B"-1"
MOV ECX,2
RET
.expandEmpty:
SUB ECX,ECX
RET
.varTypePseudo: ; One of pseudoinstruction whose name begins with % (%SET, %MACRO,..)
RET ; Copy %VAR name verbatim (unexpanded).
.varTypeSysEasm: ; €ASM %^System %variable (%^DATE, %^LINE, ...)
MOV EDX,.EaoptEasmTable
JMP .varTypeSys:
.varTypeSysEaopt: ; EUROASM %^System %variable (%^AMD, %^AUTOALIGN, ...)
LEA EBX,[Ea.Eaopt::] ; EBX=pointer to EAOPT in charge.
MOV EDX,.EaoptMiscTable
JSt EAX,varTypeSysEaoptM, .varTypeSys:
JNSt EAX,varTypeSysEaoptS, .vtF:
AND EAX,varTypeSysEnum
SHR EAX,16
MOV EAX,[.EaoptStatusEnc-4+4*EAX] ; EAX is now eaoptAUTOALIGN, eaoptDUMP etc.
TEST [EBX+EAOPT.Status],EAX
JNZ .expandTrue:
JMP .expandFalse:
.vtF:JNSt EAX,varTypeSysEaoptF, .F9983:
AND EAX,varTypeSysEnum
SHR EAX,16
MOV EAX,[.EaoptFeaEnc-4+4*EAX] ; EAX is now iiFea_AMD, iiFea_UNDOC etc.
TEST [EBX+EAOPT.Features],EAX
JNZ .expandTrue:
JMP .expandFalse:
.F9983:Msg '9983' ; Missing varTypeSysKind in VarExpand.varTypeSysEaopt.
JMP .expandEmpty:
.varTypeSysPgmopt: ; PROGRAM %^System %variable (%^FORMAT, %^MODEL, ...)
MOV EDX,.PgmoptTable
PUSH EAX
Invoke PgmGetCurrent::
JNC .vtp: ; If no program exists yet (when assembling global euroasm.ini options).
LEA EBX,[Ea.Pgmopt::] ; EBX=pointer to the factory-default PGMOPT.
JMPS .vt0:
.vtp: LEA EBX,[EAX+PGM.Pgmopt] ; EBX=pointer to PGMOPT in charge.
.vt0: POP EAX
; JMPS .varTypeSys: ; EBX=pointer to PGMOPT in charge.
.varTypeSys: ; Expand %^variables. EDX is a dispatch table for %^var names.
AND EAX,varTypeSysEnum
SHR EAX,16 ; EAX=table index in %*List (1..%*ListLength)
Msg cc=Z,'9984' ; Wrong index of %%^SystemVariable in VarExpand.vatTypeSys.
JMP [4*EAX+EDX-4] ; One of SysVar retrievers - .DATE:, .EUROASMOS:, .. .WIN32VERSIONVALUE:
; EasmSysVar handlers.
.PASS: Invoke PgmGetCurrent::
MOV ECX,EAX
JC .Ret:
JECXZ .Ret:
MOV EAX,[ECX+PGM.PassNr]
XOR EDX,EDX
JMP .expandInteger:
.PROC: Invoke CtxPeek::, ctxPROC | ctxPROC1,0
.Pro1:MOV ECX,EAX
JC .Ret:
MOV ESI,[EAX+CTX.NamePtr]
MOV ECX,[EAX+CTX.NameSize]
.Ret:RET
.PROGRAM:Invoke CtxPeek::, ctxPROGRAM,0
JMP .Pro1:
.SECTION:Invoke PgmGetCurrent::
JC .Ret:
MOV ECX,EAX
JECXZ .Ret:
MOV ECX,[EAX+PGM.CurrentSect]
JECXZ .Ret:
.Se9: MOV ESI,[ECX+SSS.NamePtr]
MOV ECX,[ECX+SSS.NameSize]
RET
.SEGMENT:Invoke PgmGetCurrent::
MOV ECX,EAX
JC .Ret:
MOV ECX,[EAX+PGM.CurrentSect]
JECXZ .Ret:
MOV ECX,[ECX+SSS.SegmPtr]
JMP .Se9:
.SOURCEFILE: ; File "name.ext" (base source or included file) of the file
; where the expanding statement lies. See also .SOURCELINE.
CALL .SourcePos:
MOV ECX,0
JC .Ret:
LEA ESI,[EDX+FILE.Name]
.size:MOV EDI,ESI
MOV ECX,MAX_PATH_SIZE
SUB EAX,EAX
REPNE SCASB
LEA ECX,[EDI-1] ; End of filename.
SUB ECX,ESI
RET
.SOURCEEXT: ; File extension of the base source file.
CALL .SourcePos:
MOV ECX,0
JC .Ret:
LEA ESI,[EDX+FILE.Name]
ADD ESI,[EDX+FILE.ExtOffs]
JMP .size:
.SOURCENAME: ; Name of the base source file without path and extension.
CALL .SourcePos:
MOV ESI,EDI ; ^FILE.Name+.NameOffs
MOV ECX,0
JC .Ret:
MOV ECX,[EDX+FILE.ExtOffs]
SUB ECX,[EDX+FILE.NameOffs]
RET
.SOURCELINE: ; Physical line number in the file (base source or included file)
; where the expanding statement lies. See also .SOURCEFILE.
CALL .SourcePos:
SUB EDX,EDX
JMP .expandInteger: ; EAX=line number.
.SourcePos: ; Called from handlers of %^Source*.
; Returns EAX=srcLine, EDX=^FILE, EDI=^%srcName. EBX=?,ECX=?
; On error returns EAX=1,EDX=Ea.SrcFile, EDI=Ea.SrcFile.Name, EBX=0.
MOV EDX,Ea.SrcFile::
LEA EDI,[EDX+FILE.Name]
SUB ECX,ECX
Invoke CtxPeek::,ctxMACRO,0
JC .nomac:
JSt [EAX+CTX.Status],ctxNoEmit,.nomac:
JNSt [EAX+CTX.Status],ctxExpansion,.nomac:
; When %^Source* is mentioned in macro-expansion context,
; it will return source position of macro invokation
; instead of position of macro definition.
MOV EAX,[EAX+CTX.LineNext] ; End of source line with macro invokation.
DEC ECX
JMP .pos:
.nomac:MOV EBX,[Src.CurrentStm::]
TEST EBX
JZ .Ret:
MOV EAX,[EBX+STM.LinePtr]
.pos: Invoke SrcPosition::,EAX ; Returns EAX=srcLineNr, EDX=^FILE or NUL, EDI=^%srcName.
LEA EAX,[EAX+ECX] ; Decrement EAX when found in macro context next line.
RET ; CF=not found.
.TIME: MOV EAX,[Ea.Eaopt.TimeStamp::]
LEA EDI,[%VarExNumber] ; Room for the expanded 'HHMMSS" string.
SUB EDX,EDX
MOV ESI,EDI
MOV ECX,24*60*60
DIV ECX
MOV EAX,EDX ; Number of seconds since midnight UTC.
SUB EDX,EDX
MOV ECX,60*60
DIV ECX
StoD EDI,Size=2,Align=right,LeadingZeroes=yes ; Hour 00..23.
MOV EAX,EDX
SUB EDX,EDX
MOV ECX,60
DIV ECX
StoD EDI,Size=2,Align=right,LeadingZeroes=yes ; Minute 00..59.
MOV EAX,EDX
StoD EDI,Size=2,Align=right,LeadingZeroes=yes ; Second 00..59.
MOV ECX,6
RET
.DATE: LEA EDI,[%VarDaysInMonths]
MOV ECX,12
MOV AL,31
MOV EBX,EDI
REP STOSB
DEC AL
MOVB [EBX+1],28 ; February.
MOV [EBX+3],AL ; April.
MOV [EBX+5],AL ; June.
MOV [EBX+8],AL ; September.
MOV [EBX+10],AL ; November.
MOV EAX,[Ea.Eaopt.TimeStamp::]
LEA EDI,[%VarExNumber] ; Room for the expanded "YYYYMMDD" string.
MOV ECX,24*60*60 ; Seconds in a day.
SUB EDX,EDX
DIV ECX ; EAX is now the number of whole days since 1.1.1970.
MOV EBX,1970
.D1: MOV ECX,365
TEST BL,3
JNZ .D2:
INC ECX ; The year EBX is leap.
.D2: INC EBX
SUB EAX,ECX
JNB .D1:
ADD EAX,ECX
DEC EBX
XCHG EAX,EBX ; EAX is now the current year; EBX is now days in this year.
StoD EDI,Size=4,Align=right,LeadingZeroes=yes
LEA ESI,[%VarDaysInMonths-1]
TEST AL,3
JNZ .D4:
MOVB [ESI+2],29 ; Leap year.
.D4: SUB EAX,EAX
SUB ECX,ECX
.D5: INC EAX
MOV CL,[ESI+EAX] ; CL is now days in month EAX (28..31).
SUB EBX,ECX
JNB .D5:
ADD EBX,ECX
StoD EDI,Size=2,Align=right,LeadingZeroes=yes ; Month 01..12.
XCHG EAX,EBX
INC EAX
StoD EDI,Size=2,Align=right,LeadingZeroes=yes ; Day 01..31.
LEA ESI,[%VarExNumber]
MOV ECX,8
RET
.EUROASMOS:
LEA ESI,[Ea.EuroasmOS::]
GetLength$ ESI
RET
.VERSION:LEA ESI,[Ea.Version::]
MOV CL,8
.Ret3:RET
; EaoptSysVar handlers. EBX=^EAOPT
.CPU: MOV EAX,[EBX+EAOPT.Machine]
cpu %FOR %IiCpuList
MOV ESI,=B"%cpu"
%cpuS %SETS %cpu
MOV ECX,%cpuS
JSt EAX,iiCPU_%cpu, .Ret3:
%ENDFOR cpu
JMP .expandEmpty:
.SIMD: MOV EAX,[EBX+EAOPT.Machine]
simd %FOR %IiSimdList
MOV ESI,=B"%simd"
%simdS %SETS %simd
MOV ECX,%simdS
JSt EAX,iiCPU_%simd, .Ret3:
%ENDFOR simd
JMP .expandFalse:
.TIMESTAMP: MOV EAX,[EBX+EAOPT.TimeStamp]
SUB EDX,EDX
JMP .expandInteger:
.CODEPAGE: MOV EAX,[EBX+EAOPT.CodePage]
SUB EDX,EDX
JMP .expandInteger:
.DUMPWIDTH: MOV EAX,[EBX+EAOPT.DumpWidth]
SUB EDX,EDX
JMP .expandInteger:
.INCLUDEPATH:MOV ESI,[EBX+EAOPT.IncludePathPtr]
MOV ECX,[EBX+EAOPT.IncludePathSize]
RET
.LINKPATH: MOV ESI,[EBX+EAOPT.LinkPathPtr]
MOV ECX,[EBX+EAOPT.LinkPathSize]
RET
.RUNPATH: MOV ESI,[EBX+EAOPT.RunPathPtr]
MOV ECX,[EBX+EAOPT.RunPathSize]
RET
.INTERPRETER:MOV ESI,[EBX+EAOPT.InterpreterPtr]
MOV ECX,[EBX+EAOPT.InterpreterSize]
RET
.LISTFILE: Invoke LstGetFileName::
RET
.MAXINCLUSIONS:MOV EAX,[EBX+EAOPT.MaxInclusions]
SUB EDX,EDX
JMP .expandInteger:
.MAXLINKS: MOV EAX,[EBX+EAOPT.MaxLinks]
SUB EDX,EDX
JMP .expandInteger:
.WARN: MOV DH,1
JMPS .W0:
.NOWARN: SUB EDX,EDX
.W0: MOV ECX,SIZE#EAOPT.NoWarn
LEA EDI,[EBX+EAOPT.NoWarn]
LEA ESI,[%VarExNumber]
.W1: MOV BL,1
MOV DL,[EDI]
.W2: MOV AL,1
AND EAX,EDX
XOR AL,DH
ADD AL,'0'
MOV [ESI],AL
BufferStore [%OutBuffer],ESI,1
JC .F9314:
SHR DL,1
SHL BL,1
JNC .W2:
INC EDI
LOOP .W1:
; %OutBuffer is now filled with 4000 characters '0' or '1'.
; The 1st character, which corresponds to unused message I0000,
; will be excluded by direct buffer contents modification.
; Thus, %^WARN[1]
will yield the 1st (and not the 0th) digit.
MOV EBX,[%OutBuffer]
INCD [EBX+BUFFER.Bottom]
; Unlike other handlers, WARN/NOWARN will not RET to .StoreVarContents with value in ESI,ECX,
; because [%OutBuffer] is already written.
POP EAX ; Discard the return address to .StoreVarContents:
JMP .Suboperations:
; PgmoptSysVar handlers. EBX=^PGMOPT
.expandPGMOPTstatus: ; EAX=PGMOPT.Status flag
JSt [EBX+PGMOPT.Status],EAX,.expandTrue:
JMP .expandFalse:
.DLLCHARACTERISTICS:
MOV EAX,[EBX+PGMOPT.DllCharacteristics]
SUB EDX,EDX
JMP .expandInteger:
.ENTRY: MOV ESI,[EBX+PGMOPT.EntryPtr]
MOV ECX,[EBX+PGMOPT.EntrySize]
RET
.FILEALIGN: MOV EAX,[EBX+PGMOPT.FileAlign]
SUB EDX,EDX
JMP .expandInteger:
.FORMAT: MOV EAX,[EBX+PGMOPT.Status]
AND EAX,pgmoptFormatMask
Invoke DictSearchByData::,DictProgramFormats::,EAX
JC .expandEmpty:
MOV ECX,[ESI+DICT.Size]
MOV ESI,[ESI+DICT.Ptr]
RET
.ICONFILE: MOV ESI,[EBX+PGMOPT.IconFilePtr]
MOV ECX,[EBX+PGMOPT.IconFileSize]
RET
.IMAGEBASE: MOV EAX,[EBX+PGMOPT.ImageBaseLow]
MOV EDX,[EBX+PGMOPT.ImageBaseHigh]
JMP .expandInteger:
.LISTMAP: MOV EAX,pgmoptLISTMAP
JMP .expandPGMOPTstatus:
.LISTGLOBALS:MOV EAX,pgmoptLISTGLOBALS
JMP .expandPGMOPTstatus:
.LISTLITERALS:MOV EAX,pgmoptLISTLITERALS
JMP .expandPGMOPTstatus:
.MAJOROSVERSION:MOV EAX,[EBX+PGMOPT.MajorOsVersion]
SUB EDX,EDX
JMP .expandInteger:
.MAJORSUBSYSTEMVERSION:MOV EAX,[EBX+PGMOPT.MajorSubsystemVersion]
SUB EDX,EDX
JMP .expandInteger:
.MAXEXPANSIONS:MOV EAX,[EBX+PGMOPT.MaxExpansions]
SUB EDX,EDX
JMP .expandInteger:
.MAXPASSES: MOV EAX,[EBX+PGMOPT.MaxPasses]
SUB EDX,EDX
JMP .expandInteger:
.MINOROSVERSION:MOV EAX,[EBX+PGMOPT.MinorOsVersion]
SUB EDX,EDX
JMP .expandInteger:
.MINORSUBSYSTEMVERSION:MOV EAX,[EBX+PGMOPT.MinorSubsystemVersion]
SUB EDX,EDX
JMP .expandInteger:
.MAJORIMAGEVERSION:MOV EAX,[EBX+PGMOPT.MajorImageVersion]
SUB EDX,EDX
JMP .expandInteger:
.MINORIMAGEVERSION:MOV EAX,[EBX+PGMOPT.MinorImageVersion]
SUB EDX,EDX
JMP .expandInteger:
.MAJORLINKERVERSION:MOV EAX,[EBX+PGMOPT.MajorLinkerVersion]
SUB EDX,EDX
JMP .expandInteger:
.MINORLINKERVERSION:MOV EAX,[EBX+PGMOPT.MinorLinkerVersion]
SUB EDX,EDX
JMP .expandInteger:
.MODEL: MOV EAX,[EBX+PGMOPT.Status]
AND EAX,pgmoptModelMask
Invoke DictSearchByData::,DictProgramModels::,EAX
JC .expandEmpty:
MOV ECX,[ESI+DICT.Size]
MOV ESI,[ESI+DICT.Ptr]
RET
.OUTFILE: MOV ESI,[EBX+PGMOPT.OutFilePtr]
MOV ECX,[EBX+PGMOPT.OutFileSize]
RET
.SECTIONALIGN:MOV EAX,[EBX+PGMOPT.SectionAlign]
SUB EDX,EDX
JMP .expandInteger:
.SIZEOFHEAPCOMMIT:MOV EAX,[EBX+PGMOPT.SizeOfHeapCommitLow]
MOV EDX,[EBX+PGMOPT.SizeOfHeapCommitHigh]
JMP .expandInteger:
.SIZEOFHEAPRESERVE:MOV EAX,[EBX+PGMOPT.SizeOfHeapReserveLow]
MOV EDX,[EBX+PGMOPT.SizeOfHeapReserveHigh]
JMP .expandInteger:
.SIZEOFSTACKCOMMIT:MOV EAX,[EBX+PGMOPT.SizeOfStackCommitLow]
MOV EDX,[EBX+PGMOPT.SizeOfStackCommitHigh]
JMP .expandInteger:
.SIZEOFSTACKRESERVE:MOV EAX,[EBX+PGMOPT.SizeOfStackReserveLow]
MOV EDX,[EBX+PGMOPT.SizeOfStackReserveHigh]
JMP .expandInteger:
.STUBFILE: MOV ESI,[EBX+PGMOPT.StubFilePtr]
MOV ECX,[EBX+PGMOPT.StubFileSize]
RET
.SUBSYSTEM: MOV EAX,[EBX+PGMOPT.Subsystem]
SUB EDX,EDX
JMP .expandInteger:
.WIDTH: SUB EDX,EDX
MOV EAX,64
JSt [EBX+PGMOPT.Status],pgmoptWidth64,.expandInteger
MOV AL,32
JSt [EBX+PGMOPT.Status],pgmoptWidth32,.expandInteger
MOV AL,16
JSt [EBX+PGMOPT.Status],pgmoptWidth16,.expandInteger
JMP .expandEmpty:
.WIN32VERSIONVALUE:MOV EAX,[EBX+PGMOPT.Win32VersionValue]
SUB EDX,EDX
JMP .expandInteger:
.varTypeId: ; ESI,ECX=%id User-defined %variable. It might be a %MACRO/%FOR formal %variable.
SUB EBX,EBX ; Context ptr.
.NextCtx:
Invoke CtxPeek::, ctxPROGRAM | ctxFOR | ctxMACRO, EBX
JC .expandEmpty:
MOV EBX,EAX ; Ptr to context which might contain the expanded formal or user-defined %variable.
MOV EDX,[EBX+CTX.Status]
AND EDX,ctxPROGRAM | ctxFOR | ctxMACRO
Dispatch EDX,ctxPROGRAM,ctxFOR,ctxMACRO
JMP .NextCtx:
.ctxPROGRAM: ; Search for user-defined %variable ESI,ECX.
MOV EAX,[EBX+CTX.ObjPtr] ; ^PGM
TEST EAX
JZ .NextCtx:
MOV EDX,[EAX+PGM.PassPtr]
TEST EDX
JZ .NextCtx:
Invoke VarListSearch, [EDX+PASS.VarList], ESI,ECX
JC .NextCtx:
; EAX = %variable found.
MOV ESI,[EAX+VAR.ValuePtr]
MOV ECX,[EAX+VAR.ValueSize]
.IdEnd:
RET
.ctxMACRO: ; Search for formal variable ESI,ECX in FrmBuffer of context EBX.
.ctxFOR:
LEA EDI,[ESI+1] ; Skip % in the name of formal variable.
LEA EDX,[ECX-1] ; Search for the formal variable EDI,EDX.
PUSH ECX,ESI
BufferRetrieve [EBX+CTX.FrmBuffer] ; ESI,ECX now contains 0 or more 4*DD.
CMP ECX,16 ; ECX=0,16,32,48..
JB .FrmEnd: ; CF=1 not found
.FrmNext:Compare EDI,EDX,[ESI+0],[ESI+4] ; Returns ZF=1,CF=0 on name match.
MOV EAX,ESI ; Ptr to formal variable in case of match.
JE .FrmEnd: ; CF=0 found
ADD ESI,16
SUB ECX,16
JG .FrmNext:
STC
.FrmEnd:
POP ESI,ECX
JC .NextCtx:
MOV ESI,[EAX+8] ; ZF=1, EAX=4*DD with matching formal variable.
MOV ECX,[EAX+12]
RET
.varTypeLabel: ; %:
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
SetSt [%VarExpStatus],varTypeLabel
BufferRetrieve [EAX+CTX.ObjBuffer]
JNSt [ESI+CTX_MAC.InvokStmStatus],stmLabelIsPublic,.vtL5:
SetSt [%VarExpStatus],varTypeLabelExt
.vtL5:MOV ECX,[ESI+CTX_MAC.LabelSize]
MOV ESI,[ESI+CTX_MAC.LabelPtr]
RET
.varTypeOrd: ; ESI,ECX=%123
LEA EDI,[%VarExErrPar]
MOV [EDI+0],ESI
MOV [EDI+4],ECX ; Number of digits in %variable name.
CMP ECX,20
JA .E7315: ; Wrong %%variable "!1S". Macro cannot have that many ordinals.
INC ESI ; Skip the percent sign.
DEC ECX
LodQD ESI,Size=ECX
TEST EDX
JNZ .E7315:
MOV EBX,EAX ; Ordinal number.
LEA ESI,[%VarExErrPar]
MOV ECX,[ESI+4]
MOV ESI,[ESI]
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
TEST EBX
JZ .MacroName: ; %0=macro name, regardless of MAC.Shift.
ADD EBX,[EAX+CTX.Shift]
BufferRetrieve [EAX+CTX.OrdBuffer]
SAR ECX,3
CMP EBX,1
JB .expandEmpty:
CMP EBX,ECX
JA .expandEmpty:
MOV ECX,[ESI+8*EBX-8+4]
MOV ESI,[ESI+8*EBX-8+0]
RET
.E7315:Msg '7315',EDI ; Wrong %%variable "!1S". Macro cannot have that many ordinals.
JMP .expandEmpty:
.MacroName: ; %0
BufferRetrieve [EAX+CTX.ObjBuffer]
MOV ECX,[ESI+CTX_MAC.MacroNameSize]
MOV ESI,[ESI+CTX_MAC.MacroNamePtr]
RET
.varTypeOrdList: ; %*
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
MOV EDI,EAX ; ^CTX
Invoke EaBufferReserve::,.varTypeOrdList
MOV EDX,EAX ; Temporary buffer for %variable contents.
BufferRetrieve [EDI+CTX.OrdBuffer]
JECXZ .ol3:
.ol1: BufferStore EDX,[ESI],[ESI+4]
JC .F9314:
ADD ESI,8
SUB ECX,8
JNA .ol3:
BufferStore EDX,=B',',1
JC .F9314:
JMP .ol1:
.ol3: BufferRetrieve EDX
Invoke EaBufferRelease::,EDX
RET
.varTypeOrdLen: ; %#
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
BufferRetrieve [EAX+CTX.OrdBuffer]
MOV EAX,ECX
SAR EAX,3
SUB EDX,EDX
JMP .expandInteger:
.varTypeKeyList: ; %=*
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
MOV EDI,EAX ; ^CTX
Invoke EaBufferReserve::,.varTypeKeyList
MOV EDX,EAX ; Temporary buffer for %variable contents.
BufferRetrieve [EDI+CTX.KeyBuffer]
JECXZ .kl3:
.kl1: BufferStore EDX,[ESI],[ESI+4]
JC .F9314:
BufferStore EDX,=B'=',1
JC .F9314:
BufferStore EDX,[ESI+8],[ESI+12]
JC .F9314:
ADD ESI,16
SUB ECX,16
JNG .kl3:
BufferStore EDX,=B',',1
JNC .kl1:
.F9314:Msg '9314',VarExpand ; Allocation error storing to buffer in !1H.
STC
JMP .99:
.kl3: BufferRetrieve EDX
Invoke EaBufferRelease::,EDX
RET
.varTypeKeyLen: ; %=#
CALL .GetMacroCtx:
JC .expandFalse:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
BufferRetrieve [EAX+CTX.KeyBuffer]
MOV EAX,ECX
SAR EAX,4
SUB EDX,EDX
JMP .expandInteger:
.varTypeInvId: ; %!abc
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
LEA EDI,[ESI+2]
LEA EDX,[ECX-2] ; Strip leading %! from variable name.
BufferRetrieve [EAX+CTX.FrmBuffer]
JC .E7316: ; Invertable macro %%variable "!1S" not specified in %MACRO prototype.".
CMP ECX,16
JL .E7316:
.InId2:Compare [ESI+0],[ESI+4],EDI,EDX
JE .InId5:
ADD ESI,16
SUB ECX,16
JG .InId2:
JMP .E7316: ; Invertable macro %%variable "!1S" not specified in %MACRO prototype.".
.InId5:MOV ECX,[ESI+12]
MOV ESI,[ESI+8] ; ESI,ECX is %!variable value (not inverted yet).
.InId7:Invoke DictLookup::,DictCondCodes::,ESI,ECX
JC .E7317: ; Macro %%variable "!1S" must contain invertable condition code instead of "!2S".
LEA EDI,[%VarExNumber] ; EAX has inverted cc in bytes 0..2, zero padded.
STOSB ; Room for the expanded number reused for inverted cc.
SHR EAX,8
CMP AL,1111b ; End of cc.
JBE .InId9:
STOSB
SHR EAX,8
CMP AL,1111b
JBE .InId9:
STOSB
.InId9:LEA ESI,[%VarExNumber]
SUB EDI,ESI
MOV ECX,EDI
RET
.varTypeInvOrd ; %!123
LEA EDI,[%VarExErrPar]
MOV [EDI+0],ESI
MOV [EDI+4],ECX ; Number of digits in %variable name.
CMP ECX,21
JA .E7315: ; Wrong %%variable "!1S". Macro cannot have that many ordinals.
INC ESI ; Skip the percent sign.
DEC ECX
INC ESI ; Skip exclamation sign.
DEC ECX
LodQD ESI,Size=ECX
TEST EDX
JNZ .E7315:
MOV EBX,EAX ; Ordinal number.
LEA ESI,[%VarExErrPar]
MOV ECX,[ESI+4]
MOV ESI,[ESI]
CALL .GetMacroCtx:
JC .expandEmpty:
JNSt [EAX+CTX.Status],ctxExpansion,.expandEmpty:
TEST EBX
JZ .E7317: ; Macro %%variable "!1S" must contain invertable condition code instead of "!2S".
ADD EBX,[EAX+CTX.Shift]
BufferRetrieve [EAX+CTX.OrdBuffer]
SAR ECX,3
CMP EBX,1
JB .E7317:
CMP EBX,ECX
JA .E7317:
MOV ECX,[ESI+8*EBX-8+4]
MOV ESI,[ESI+8*EBX-8+0]
JMP .InId7:
.varTypeExp: ; %.
Invoke CtxPeek::, ctxExpandable, 0
JC .expandFalse: ; %. outside expandable block is expanded to '0'.
MOV EAX,[EAX+CTX.ExpansionNr]
SUB EDX,EDX
JMP .expandInteger:
.GetMacroCtx: ; Called from .varTypeMacro%variables
; Inp:ESI,ECX=macro%variable name (%* %=* %2 %!id ...)
; Out:CF=0 EAX=^CTX
; Error: CF=1 EDI,EAX undefined.
Invoke CtxPeek::,ctxMACRO,0 ; Macro%variables are constructed from the latest ctxMACRO+ctxExpansion only.
JC .E7313: ; Macro %%variable "!1S" cannot be used outside %%MACRO/%%ENDMACRO block.
JSt [EAX+CTX.Status],ctxNoEmit,.93:
JNSt [EAX+CTX.Status],ctxExpansion,.E7313G:
JMPS .93:
.E7313G:
LEA EDI,[%VarExErrPar]
MOV [EDI+0],ESI
MOV [EDI+4],ECX
Msg '7313',EDI ; Macro %%variable "!1S" cannot be used outside %%MACRO/%%ENDMACRO block.
STC
.93:RET
[.data]
ALIGN DWORD
.EaoptMiscTable: ; Retrieve handlers for non-boolean %^CPU, %^SIMD, %^WARN, %^CODEPAGE etc.
Option %FOR %EaoptMiscList ; EaoptMiscList.
DD .%Option:
%ENDFOR Option
.EaoptEasmTable: ; Retrieve handlers for %^DATE, %^VERSION etc.
option %FOR %EaoptEasmList ; EaoptEasmList.
DD .%option:
%ENDFOR option
.PgmoptTable: ; Retrieve handlers for %^FORMAT, %^SUBSYSTEM etc.
option %FOR %PgmoptList ; PgmoptList.
DD .%option:
%ENDFOR option
.EaoptStatusEnc: ; EAOPT.Status flags for boolean %^AUTOALIGN, %^LISTMACRO etc.
value %FOR %EaoptStatusList ; %EaoptStatusList.
DD eaopt%value
%ENDFOR value
.EaoptFeaEnc: ; EAOPT.Features flags for boolean %^CYRIX, %^UNDOC etc.
value %FOR %EaoptFeaList ; %EaoptFeaList.
DD iiFea_%value
%ENDFOR value
[.text]
.E7310: ; Wrong preprocessing %%variable name "!1S"
MOV EAX,'7310'
;JMP .E731:
.E731:MOV ESI,EAX ; MsgNr.
Invoke CtxStatusAll::
TEST EAX,ctxNoEmit
STC
JNZ .99: ; Skip error message when not emitting.
LEA EBX,[%VarExErrPar]
MOV EDI,[%TxtPtr]
MOV ECX,[%ReturnEAX]
MOV [EBX+0],EDI
SUB ECX,EDI
MOV [EBX+4],ECX
Msg ESI,EBX
STC
JMP .99:
.E7313: ; Macro %%variable "!1S" cannot be used outside %%MACRO/%%ENDMACRO block.
MOV EAX,'7313'
JMP .E731:
.E7316: ; Invertable macro %%variable "!1S" not specified in %MACRO prototype.".
MOV EAX,'7316'
JMP .E731:
.E7317: ; Macro %%variable "!1S" must contain invertable condition code.
MOV EAX,'7317' ; ESI is pointer to QWORD with wrong value string (!2S)
JMP .E731:
.StoreVarContents: ; ESI,ECX is %Variable contents without suboperations.
JECXZ .Suboperations:
BufferStore [%OutBuffer],ESI,ECX
JC .F9314:
JNSt [%VarExpStatus],varTypeLabel,.Suboperations:
BufferStore [%OutBuffer],=B":",1
RstSt [%VarExpStatus],varTypeLabel
JNSt [%VarExpStatus],varTypeLabelExt,.Suboperations:
BufferStore [%OutBuffer],=B":",1
RstSt [%VarExpStatus],varTypeLabelExt
.Suboperations:
MOV ESI,[%ReturnEAX]
CMP ESI,[%TxtEnd]
JNB .Done:
Invoke VarSuboperate, [%ReturnEAX],[%TxtEnd],[%OutBuffer]
MOV [%ReturnEAX],EAX
JZ .Suboperations: ; Next chained suboperator might follow.
.Done:CLC
.99:EndProcedure VarExpand
VarListSearch Procedure List, NamePtr, NameSize MOV EBX,[%NamePtr] MOV EDX,[%NameSize] ListGetLast [%List] JZ .80: .10: CMP EDX,[EAX+VAR.NameSize] JNE .70: MOV ECX,EDX MOV ESI,EBX MOV EDI,[EAX+VAR.NamePtr] REPE CMPSB JE .90: .70: ListGetPrev EAX JNZ .10: .80: STC .90: MOV [%ReturnEAX],EAX EndProcedure VarListSearch
VarSuboperate Procedure TxtPtr, TxtEnd, Buffer VarSubBuffer LocalVar ; A temporary buffer for expanded suboperator. VarSubExp LocalVar Size=SIZE#EXP ; Room for the expression evaluating. VarLeft LocalVar ; Left range value. VarRight LocalVar ; Right range value. VarRightPtr LocalVar ; Pointer to the right range text. VarRightEnd LocalVar ; End of the right range text. MOV EDI,[%TxtPtr] MOV EDX,[%TxtEnd] MOV [%ReturnEAX],EDI MOV BL,[EDI] CMP BL,'[' JE .10: CMP BL,'{' CLC JNE .99: .10: MOVD [%VarLeft],1 ; Initialize with default=1 Invoke EaBufferReserve::, VarSuboperate MOV [%VarSubBuffer],EAX BufferRetrieve [%Buffer] MOV [%VarRight],ECX ; Size of %var value, i.e. sublist %& parameter. CMP BL,'[' JE .20: Invoke ExpCountItems::,ESI,ECX ; Sublist, BL='{'. MOV [%VarRight],EAX .20: ; The matching unquoted right brace to the corresponding left brace in BL must be found. Invoke ExpParseSuboperation::,EDI,EDX MOV [%ReturnEAX],ESI JC .E7320: ; Wrong suboperation "!1S", expecting "!2Z". MOV ECX,ESI ; Suboperator end. ; The text EDI..ECX will be expanded to [%VarSubBuffer]. Invoke VarExpandField,EDI,ECX,[%VarSubBuffer],[%VarRight] ; VarSubBuffer now contains expanded text of suboperations, e.g. {1+2..3*4} BufferRetrieve [%VarSubBuffer] SUB ECX,2 ; Strip the brackets [] {} JZ .End: ; An empty suboperation. JB .E7320: INC ESI ; Skip the left bracket. LEA EDX,[ESI+ECX] ; Behind the right bracket. LEA EBX,[%VarSubExp] Invoke ExpParseRange::,ESI,EDX JNC .Range: SUB EDX,ESI ; No range, only one operand ESI..EDX. Invoke ExpEval::,EBX,ESI,EDX,0 JC .Error: JZ .RangeEvaluated: ; Empty left value - use default 1. Invoke ExpConvertToNumber::,EBX MOV ECX,[EBX+EXP.Status] MOV EAX,[EBX+EXP.Low] JC .E7330: CMP CH,expWidth8B JNB .E7330: MOV [%VarLeft],EAX MOV [%VarRight],EAX JMP .RangeEvaluated: .Range: ; Range specified. Left range operand is ESI..EAX-2 MOV [%VarRightPtr],EAX ; Right range operand is EAX..EDX, store it for later. MOV [%VarRightEnd],EDX SUB EAX,2 SUB EAX,ESI Invoke ExpEval::,EBX,ESI,EAX,0 JC .Error: JZ .RR: ; Empty left range, leave it to the default=1. Invoke ExpConvertToNumber::,EBX MOV ECX,[EBX+EXP.Status] MOV EAX,[EBX+EXP.Low] JC .E7330: CMP CH,expWidth8B JNB .E7330: MOV [%VarLeft],EAX MOV EAX,[%VarRightEnd] MOV ECX,[%VarRightPtr] SUB EAX,ECX .RR: Invoke ExpEval::,EBX,ECX,EAX,0 JC .Error: JZ .RangeEvaluated: Invoke ExpConvertToNumber::,EBX MOV ECX,[EBX+EXP.Status] MOV EAX,[EBX+EXP.Low] JC .E7330: CMP CH,expWidth8B JNB .E7330: MOV [%VarRight],EAX .RangeEvaluated: ; The actual suboperation with range %VarLeft..%VarRight takes place here. MOV EDI,[%TxtPtr] BufferRetrieve [%Buffer] BufferClear [%Buffer] LEA EDX,[ESI+ECX] MOV EAX,[%VarLeft] CMPB [EDI],'[' JNE .Sublist: ; Substring. LEA EBX,[ESI+EAX-1] CMP EBX,ESI JAE .S2: MOV EBX,ESI .S2: MOV EAX,[%VarRight] LEA EDI,[ESI+EAX] CMP EDI,EDX JBE .S4: MOV EDI,EDX .S4: SUB EDI,EBX JNA .End: BufferStore [%Buffer],EBX,EDI Msg cc=C,'9314',VarSuboperate ; Allocation error storing to the buffer in !1H. JMP .End: .SkipItem: ; Move ESI forward to the next item but not over EDX. CF=1 if EDX reached. .S1:CMP ESI,EDX JNB .S8: LODSB CMP AL,',' ; Unquoted item separator. JE .S9: MOV AH,AL CMP AL,'"' JE .S5: CMP AL,"'" JNE .S1: .S5:CMP ESI,EDX ; Inside the string. JNB .S8: LODSB CMP AL,AH JNE .S5: JMP .S1: .S8:STC .S9:RET .E7320:LEA ECX,[%VarSubExp+4] ; Reuse EXP structure for error parameter !1S. MOV ESI,[%TxtPtr] MOV EDX,[%TxtEnd] MOV AL,[ESI] SUB EDX,ESI ADD AL,2 ; Convert [{ to ]} MOV [ECX+0],ESI MOV [ECX+4],EDX Msg '7320',ECX,EAX ; Wrong suboperation "!1S", expecting "!2Z". JMP .Error: .E7330: Msg '7330',ECX ; A plain 32bit numeric range value expected instead of expr.type "!1Z".',0 .Error:Invoke EaBufferRelease::, [%VarSubBuffer] STC JMP .99: .Sublist: ; of text between ESI and EDX. MOV EBX,EAX ; %VarLeft. CMP EAX,1 JGE .L2: MOV EBX,1 .L2: ; EBX is the left index, not less than 1. ESI will be positioned to that index. SUB ECX,ECX ; Left index counter during the positioning. .L3: INC ECX CMP ECX,EBX JNB .L4: CALL .SkipItem JC .End: JMP .L3: .L4: MOV EDI,ESI ; EDI now points to the %VarLeft item. .L5: CMP ECX,[%VarRight] JE .L6: JG .End: CALL .SkipItem INC ECX JMP .L5: .L6: ; ESI points at the last item. CALL .SkipItem CMPB [ESI-1],',' JNE .L7: DEC ESI ; Skip the comma behind the last sublisted item. .L7: SUB ESI,EDI JNA .End: BufferStore [%Buffer],EDI,ESI Msg cc=C,'9314',VarSuboperate ; Allocation error storing to a buffer in !1H. .End:Invoke EaBufferRelease::, [%VarSubBuffer] SUB EAX,EAX ; Set ZF=1. .99:EndProcedure VarSuboperate
C:\ASM\%^sourcefile[1..%&-4].lst
,
it will be expanded and suboperated to the output buffer.%&
when the field is inside suboperation, otherwise -1.VarExpandField Procedure FieldPtr, FieldEnd, OutBuffer, Length MOV EDX,[%FieldEnd] MOV EDI,[%FieldPtr] .10: MOV ECX,EDX MOV ESI,EDI SUB ECX,EDI JNA .90: MOV AL,'%%' REPNE SCASB JNE .80: DEC EDI MOV ECX,EDI SUB ECX,ESI BufferStore [%OutBuffer],ESI,ECX Msg cc=C,'9314',VarExpandField ; Allocation error storing to buffer in !1H. Invoke EaBufferReserve::, VarExpandField MOV EBX,EAX ; Temporary buffer. Invoke VarExpand,EDI,EDX,EBX,[%Length] MOV EDI,EAX BufferRetrieve EBX BufferStore [%OutBuffer],ESI,ECX Msg cc=C,'9314',VarExpandField ; Allocation error storing to buffer in !1H. Invoke EaBufferRelease::, EBX JMP .10: .80: SUB EDX,ESI BufferStore [%OutBuffer],ESI,EDX Msg cc=C,'9314',VarExpandField ; Allocation error storing to buffer in !1H. .90:EndProcedure VarExpandField
VarListMerge Procedure ParentPass, ChildPass MOV EBX,[%ParentPass] MOV EDX,[%ChildPass] ListGetFirst [EDX+PASS.VarList] JZ .90: .10:MOV ESI,EAX ; Ptr to VAR. PoolStore [EBX+PASS.Pool],[ESI+VAR.NamePtr],[ESI+VAR.NameSize] MOV [ESI+VAR.NamePtr],EAX MOV ECX,[ESI+VAR.ValueAlloc] PoolStore [EBX+PASS.Pool],[ESI+VAR.ValuePtr],ECX Msg cc=C,'9304',VarListMerge ; Allocation error storing to pool in !1H. MOV [ESI+VAR.ValuePtr],EAX ListStore [EBX+PASS.VarList],ESI Msg cc=C,'9324',VarListMerge ; Allocation error storing to list in !1H. ListGetNext ESI JNZ .10: .90:EndProcedure VarListMerge
ENDPROGRAM var