EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

sym.htm
Class
SYM
Encodings
SymEnc
Macro
SymMemberUpdate
Procedures
SymCreate
SymCreateLiteral
SymDelocalName
SymDynamicLink
SymFindByName
SymFindByInterName
SymFixup
SymFrameAddress
SymResolveImage
SymResolveObject
SymStoreForwarderName

Object SYM represents a program symbol.
All defined symbols of the program (including literals) are kept on PGM.SymList.
A record on PGM.SymList is created

  1. when a symbol is defined as a label of instruction,
  2. when a literal symbol is referred,
  3. when a symbol scope is declared with GLOBAL, PUBLIC, EXTERN, EXPORT, IMPORT statement,
  4. when the symbol is referred in operand field of a statement and it was not defined yet.

Symbol is not created when its attribute is queried.

Actions performed with all symbols in PseudoENDPROGRAM
ProcedureConditionActionComment
PassCreate SetSt symFixed At the start of each pass all symbols created in previous passes are marked symFixed.
RstSt symDefInPass
PassInspect All symbols are fixedSetSt pgmLastPassIf one or more symbols is not fixed, the next pass cannot be the last.
!symFixedRstSt pgmLastPass
PassDestroy symGlobal && symDefInPassSetSt symPublic At the end of each pass the flag symGlobal|symGlobalRef is expanded either to symPublic or symExtern.
symGlobal && !symDefInPassSetSt symExtern
pgmLastPass && !symExtern && !symDefInPass && !symQueriedE6601
pgmLastPass && !symUsed && !symIncluded && !symPublic && !symExportW2101

Querying symbol's attributes does not throw error even if the symbol is not defined.

Referencing a symbol which was not defined yet does not throw an error unless pgmLastPass is set. Instead it is created with temporary estimated attribute values:

Initial estimated attributes of forward-referenced private symbol
AttributeValueRemark
TYPE#'?'Unknown in the first pass(es).
SIZE#0Assuming it represents a non-dimensional point.
SCOPE#'S'Assuming standard private scope.
OFFSET#OFFSET#$+64Assuming it will be defined later withing short jump reach.
SECTION#SECTION#$Assuming it will be defined in the same section.
SEGMENT#SEGMENT#$Assuming it will be defined in the same segment.
GROUP#GROUP#$Assuming it will be defined in the same group.
PARA#GROUP#$>>4Assuming it will be defined in the same group.
Initial estimated attributes of forward-referenced external or imported symbol
AttributeValueRemark
TYPE#'A'Assuming it will stay external (undefined in program).
SIZE#0
SCOPE#'E'Assuming it will stay external (undefined in program).
OFFSET#0Runtime offset will be resolved by pseudosegment relocation.
SECTION#[Symbol]A new extern pseudosegment is created together with the symbol.
Pseudosegment name is identical with external/imported symbol name.
SEGMENT#
GROUP#
PARA #

sym PROGRAM FORMAT=COFF,MODEL=FLAT,WIDTH=32
 INCLUDEHEAD "euroasm.htm" ; Interface (structures, symbols and macros) of other modules.
 sym HEAD ; Start of module interface.
↑ SYM
SYM STRUC          ; +00h.
.NamePtr       D D ; Full name (leading dot resolved, colons removed).
.NameSize      D D ; Number of bytes in symbol name {without colons).
.Section       D D ; Ptr to SSS (sssSection or sssExtern) where it was declared in, or 0 for constants.
.Status        D D ; Other symbol properties, see SymEnc below.
                   ; +10h.
.InterNamePtr  D D ; Pointer to imported symbol internal name or to forwarded export name.
.InterNameSize D D ; Number of bytes in .InterName.
.DllNamePtr    D D ; Pointer to file name of DLL from which the symbol is imported or forwarded DLL name.
.DllNameSize   D D ; Number of bytes in .InterName.
                   ; +20h.
.OffsetLow     D D ; bits 0..31 offset from begining of segment (not from section bottom).
.OffsetHigh    D D ; bits 32..63
.Size          D D ; Number of bytes emitted or reserved by the declaring statement.
.Align         D D ; Explicit alignment 0=default,1,2,4,8,16,...
                   ; +30h.
.LinePtr       D D ; Ptr to source text where the symbol was declared.
.NameIndex     D D ; Ordinal number (0..) in Coff.SymbolTable. Paragraph FA of module in LIBOMF.
.OrdinalNr     D D ; Imported ordinal number value. Valid when .Status:symImportedByOrd is set.
ENDSTRUC SYM
↑ SymEnc - symbol encodings
Some of the SYM.Status flags defined here are adopted from the refering statement: symTypeMask + symPropMask are kept synchronized with stmTypeMask + stmPropMask in statement encoding StmEnc.
All symbols are granted with symFixed in PassCreate (when a new pass starts) and the flag is reset if symbol properties had changed in a pass.
; Symbol TYPE#
symTypeMask       = 0x0000_00FF ; Uppercase letter BUWDQTOYZISNA?. Synchronized with stmTypeMask.
; Symbol SCOPE#.
symPublic         = 0x0000_0100 ; Explicitly declared as PUBLIC. Scope='P'.
symExport         = 0x0000_0200 ; Explicitly declared as EXPORT. Scope='X'.
symExtern         = 0x0000_0400 ; Explicitly declared as EXTERN. Scope='E'.
symImport         = 0x0000_0800 ; Explicitly declared as IMPORT. Scope='I'.
symGlobal         = 0x0000_1000 ; Explicitly declared as GLOBAL. Scope='G'.
symExplScopeMask  = symPublic|symExport|symExtern|symImport|symGlobal
symGlobalRef      = 0x0000_2000 ; Implicitly referred as global (it ends with two colons).
symScopeMask      = symExplScopeMask | symGlobalRef
symLiteral        = 0x0000_4000 ; Symbol is literal, scope='S' (standard private).
symEntry          = 0x0000_8000 ; Symbol is program Entry, scope='P'. Don't E6601 if undefined in main program.
; Symbol properties.  Synchronized with stmPropMask
symIncluded       = 0x0001_0000 ; Symbol was defined in included source chunk. Do not warn if not used.
symProc           = 0x0002_0000 ; Symbol is defined as PROC or PROC1.
symNear           = 0x0004_0000 ; Symbol symProc has DIST=NEAR.
symFar            = 0x0008_0000 ; Symbol symProc has DIST=FAR.
symPropMask       = symIncluded|symProc|symNear|symFar
 ; Referencing symbol flags.
symDefined        = 0x0010_0000 ; Symbol was defined at least once in any pass.
symReferenced     = 0x0020_0000 ; Symbol was referenced. It should have been defined, otherwise E6601.
symQueried        = 0x0040_0000 ; Symbol's attribute was queried. Don't E6601 if not defined and not referred.
symUsed           = 0x0080_0000 ; Symbol was referenced or queried at least once in any pass (symDirty).
symDefInPass      = 0x0100_0000 ; Symbol was already defined in this pass. Reset in PassDestroy.
symFixed          = 0x0200_0000 ; Offset and other properties are definitely computed and fixed.
symEstimated      = 0x0400_0000 ; Offset and other properties are only estimated in this pass.
symImportedByOrd  = 0x0800_8000 ; Symbol is imported by ordinal, not by name. Valid with symImport only.
symForwarded      = 0x1000_0000 ; Exporting of the symbol is provided by other DLL. Valid with symExport only.
 ; Flags symDelocal* are not properties of a symbol, they are used in SymDelocalName only.
symDelocalNone    = 0x0000_0000 ; Do not delocalize symbol name beginning with ..
symDelocal        = 0x2000_0000 ; Do prefix symbol name beginning with . with current namespace.
symDelocalParent  = 0x4000_0000 ; Do prefix symbol name beginning with . with parent namespace (skip 1 current namespace).
symResolved       = 0x8000_0000 ; Extern/import symbol was matched to a public symbol.
  ENDHEAD sym ; End of module interface.
↑ SymMemberUpdate Member
Macro SymMemberUpdate will copy contents of one class member from statement to symbol and clear ECX when they were different.
Input
Member is one of homonymous members of STM and SYM: OffsetLow, OffsetHigh, Section, Size, LinePtr.
EBX= pointer to STM (source).
EDI= pointer to SYM (destination).
Output
EAX=[EBX+STM.%Member]
ECX= 0 if the members were different, otherwise ECX is unchanged.
Error
-
Example
SymMemberUpdate Section
Expanded by
SymCreate
SymMemberUpdate %MACRO Member
    MOV EAX,[EBX+STM.%Member]
    CMP EAX,[EDI+SYM.%Member]
    JE .Fixed%Member%.:
    MOV [EDI+SYM.%Member],EAX
    XOR ECX,ECX ; Set flag Fixed to FALSE.
.Fixed%Member%.:
    %ENDMACRO SymMemberUpdate
↑ SymFindByName SymScope, NamePtr, NameSize, ProgPtr
SymFindByName searches for symbol of given scope by its .Name on ProgPgm.SymList.
Input
SymScope is one of the SymEnc flags symExtern, symPublic, symImport, symExport, or 0, which will accept symbol of any scope.
NamePtr is pointer to the name of searched symbol.
NameSize is size of the symbol name.
ProgPtr Pointer to PGM . It may be NULL, current program is searched in this case.
Output
CF=0
EAX= Pointer to SYM structure of the symbol.
Error
CF=1
EAX= 0 - symbol not found.
Example
Invoke SymFindByName::, symExtern|symImport,ESI,ECX,0
See also
SymFindByInterName.
Invoked by
ExpEvalIdentifier PfDrectveDestroy PfomfLoadModule PgmCombine PseudoPROC1 SssCreate SymCreate SymCreateLiteral SymResolveImage SymResolveObject
Invokes
PgmGetCurrent
SymFindByName Procedure SymScope, NamePtr, NameSize, ProgPtr
       MOV ESI,[%ProgPtr]
       TEST ESI
       JNZ .10:
       Invoke PgmGetCurrent::
       JC .NotFound:
       MOV ESI,EAX ; ^PGM.
 .10:  MOV EDX,[%NameSize]
       MOV EBX,[%NamePtr]
       TEST EDX
       JZ .NotFound:
       ListGetFirst [ESI+PGM.SymList]
       JZ .NotFound:
 .20:  MOV ECX,[%SymScope]
       JECXZ .40:  ; Skip symbol status check if %SymScope=0 (any scope will fit).
       JNSt [EAX+SYM.Status],ECX,.70:
 .40:  CMP EDX,[EAX+SYM.NameSize]
       JNE .70:
       MOV ESI,[EAX+SYM.NamePtr]
       MOV ECX,EDX
       MOV EDI,EBX
       REPE CMPSB
       JE .Found
 .70:  ListGetNext EAX
       JNZ .20:
.NotFound:
       SUB EAX,EAX
       STC
.Found:MOV [%ReturnEAX],EAX
     EndProcedure SymFindByName
↑ SymFindByInterName SymScope, NamePtr, NameSize, ProgPtr
SymFindByInterName searches for symbol of given scope by .InterName on ProgPgm.SymList. SYM.InterName differs from ordinary (public) SYM.Name only in imported symbols.
Input
SymScope is one of the SymEnc flags symExtern, symPublic, symImport, symExport, or 0, which will accept symbol of any scope.
NamePtr Name of the searched symbol.
NameSize Size of symbol internal name.
ProgPtr Pointer to PGM . It may be NULL, current program is searched in this case.
Output
CF=0
EAX= Pointer to SYM structure of the symbol.
Error
CF=1
EAX= 0 - symbol not found.
Example
Invoke SymFindByInterName::,symImport,ESI,ECX,0
See also
SymFindByName.
Invoked by
PfomfLoadModule
Invokes
PgmGetCurrent
SymFindByInterName Procedure SymScope, NamePtr, NameSize, ProgPtr
       MOV ESI,[%ProgPtr]
       TEST ESI
       JNZ .05:
       Invoke PgmGetCurrent::
       JC .NotFound:
       MOV ESI,EAX ; ^PGM.
 .05:  MOV EDX,[%NameSize]
       MOV EBX,[%NamePtr]
       TEST EDX
       JZ .NotFound:
       ListGetFirst [ESI+PGM.SymList]
       JZ .NotFound:
 .10:  MOV ECX,[%SymScope]
       JECXZ .20:  ; Skip symbol status check if %SymScope=0.
       JNSt [EAX+SYM.Status],ECX,.70:
 .20:  CMP EDX,[EAX+SYM.InterNameSize]
       JNE .70:
       MOV ESI,[EAX+SYM.InterNamePtr]
       MOV ECX,EDX
       MOV EDI,EBX
       REPE CMPSB
       JE .Found
 .70:  ListGetNext EAX
       JNZ .10:
.NotFound:
       SUB EAX,EAX
       STC
.Found:MOV [%ReturnEAX],EAX
     EndProcedure SymFindByInterName
↑ SymDelocalName NamePtr, NameSize, NameBuffer, Delocalize
Identifier Name is checked, delocalized and then stored to NameBuffer. If symDelocal is set, Name will be prefixed with current namespace if it is .local.
Input
NamePtr Pointer to the identifier of symbol or structure. It may start with dot ., but no trailing colons or [ ] are allowed.
NameSize Number of bytes in the name.
NameBuffer Pointer to output BUFFER where the checked name will be stored. It should be empty on input.
Delocalize is one of the flags symDelocal, symDelocalParent or symDelocalNone.Regardless of Delocalize, the name is tested for permitted characters.
Output
CF=0, NameBuffer contains valid (delocalized) symbol name.
Error
CF=1 Errors E6110 reported with macro Msg . Output NameBuffer returns as much of input name as possible.
Invokes
CtxPeek
Invoked by
CtxCreate CtxFind ExpEvalIdentifier ExpParseDatatype PseudoPROC1 PseudoSTRUC SssCreate SymCreate
SymDelocalName Procedure NamePtr, NameSize, NameBuffer, Delocalize
      MOV ECX,[%NameSize]
      MOV ESI,[%NamePtr]
      MOV EBX,[%NameBuffer]
      MOV EDX,[%Delocalize]
      JECXZ .20: ; Empty name will pass.
      JNSt EDX, symDelocal | symDelocalParent, .20: ; If symDelocalNone.
      CMPB [ESI],'.' ; Is Name local?
      JNE .20:
      ; Local name will be prefixed with current or parent namespace in NameBuffer.
      SUB EAX,EAX
      JNSt [%Delocalize],symDelocalParent,.10:
      Invoke CtxPeek::, ctxNamespace,0 ; Get and forget the current namespace context to EAX.
 .10: Invoke CtxPeek::, ctxNamespace,EAX
      JC .20: ; If there's no namespace on context stack.
      BufferStore EBX,[EAX+CTX.NamePtr],[EAX+CTX.NameSize] ; Store namespace name first.
 .20: BufferStore EBX,ESI,ECX ; Store (local) Name.
      BufferRetrieve EBX
      JECXZ .90:
      LODSB ; Check the first character used in name.
      DEC ECX
      ExpClassify AL
      TEST AH, expLetter | expFullstop
      JZ .E6110:  ; Invalid symbol name "!1S".
 .30: JECXZ .90:
      LODSB
      DEC ECX
      ExpClassify AL
      TEST AH, expLetter | expDigit | expFullstop
      JNZ .30:
.E6110:LEA EDI,[%NamePtr]
      Msg '6110',EDI,PgmStatus=pgmLastPass ;  Invalid symbol name "!1S".
      STC
 .90:EndProcedure SymDelocalName
↑ SymCreate Reason, NamePtr, NameSize, Statement

SymCreate returns a program symbol specified by Name. It will create a new symbol if it didn't exist in Program.SymList. The symbol is then updated by Statement properties.
SymCreate is invoked on theese circumstances:

Type and some other properties of created symbol are provided by STM:.Section, .Offset, .Size, LinePtr, stmTypeMask,stmPropMask.
Due to optimisation passes the final offset of the created symbol may be different from the value estimated at symbol creation. Statement offset and other properties are updated here.

Input
Reason is a combination of flags in symbol encoding, see above.
NamePtr is pointer to symbol name. It can be volatile, untrimmed, colon(s) terminated and local (start with .), it will be completed with namespace and permanently stored on Pgm.Pool. It may not be $.
NameSize is number of characters in symbol name.
Statement is pointer to STM - parsed statement concerns the symbol.
It may be NULL when Reason=symReferenced, in this case new symbol will not be created if it didn't exist yet.
Output
CF=0, EAX= pointer to an updated existing or just created SYM object.
CF=0, EAX=0 if the reason was symQueried and symbol is undefined.
Error
CF=1 Errors are reported with macro Msg.
EAX=0
Depends on
SymMemberUpdate
Invoked by
ExpEvalIdentifier IiAssemble IiAssembleMultiop MemberCreate PgmGlobalEntry PseudoData PseudoENDPROC PseudoENDPROC1 PseudoEQU PseudoNoOperation PseudoPROC PseudoPROC1 PseudoScope PseudopcMACRO
Tested by
t1646 t2381 t2382
Invokes
EaBufferRelease EaBufferReserve PgmGetCurrent SssCreateExtern SymDelocalName SymFindByName
SymCreate Procedure Reason, NamePtr, NameSize, Statement
PgmPtr     LocalVar ; ^Current program.
PgmStatus  LocalVar ; Local copy of program status.
Fixed      LocalVar ; Value of SYM.Status:symFixed during SymMemberUpdate.
    ClearLocalVar
    MOV EBX,[%Statement]
    ; Check if Program and Statement is provided.
    TEST EBX
    JZ .05: ; Internal error: creating symbol "!1S".
    MOV EDX,[EBX+STM.Program]
    MOV [%PgmPtr],EDX
    TEST EDX
    JZ .05:
    MOV EAX,[EDX+PGM.Status]
    MOV [%PgmStatus],EAX
    MOVD [%Fixed],symFixed
    JMP .10:
.05:JSt [%Reason],symReferenced,.10:
.F9960:LEA ESI,[%NamePtr]
    Msg '9960',ESI ; Internal error: creating symbol "!1S" outside a statement.
.Error:
    XOR EAX,EAX
    MOV [%ReturnEAX],EAX
    STC
    JMP .90:
.E6601: Msg '6601',EDI,[EDI+SYM.LinePtr] ; Symbol "!1S" mentioned at !2@ was not found.
    JMP .Error:
.E6610:Msg '6610',EDI,[EDI+SYM.LinePtr] ; Symbol "!1S" was already defined at "!2@"
    JMP .Error:
.E6621:Msg '6621',EDI,[EDI+SYM.LinePtr] ; External symbol "!1S" defined at "!2@" cannot be made public.
    JMP .Error:
.E6622:Msg '6622',EDI,[EDI+SYM.LinePtr] ; Public symbol "!1S" defined at "!2@" cannot be made external.
    JMP .Error:
.E6624:Msg '6624',EDI,[EDI+SYM.LinePtr] ; Symbol "!1S" was declared as external at !2@.
    JMP .Error:
.E6637:Msg '6637' ; Special symbol "$" can be defined with EQU only.
    JMP .Error:
.E6638:Msg '6638' ; Special symbol "$" cannot be declared global.
    JMP .Error:
.10:TEST EDX
    JNZ .12:
    Invoke PgmGetCurrent::
    MOV EDX,EAX
.12:TEST EBX
    JNZ .13:
    MOV EBX,[EDX+PGM.CurrentStm]
    TEST EBX
    JZ .F9960:
.13:; Check symbol name.
    MOV ESI,[%NamePtr]
    MOV ECX,[%NameSize]
    StripSpaces ESI,ECX
    StripColons ESI,ECX
    JECXZ .Error: ; Silently do not create symbol with empty name.
    CMP ECX,1
    JNE .15:
    CMPB [ESI],'$'
    JNE .15:
    JSt [%Reason],symScopeMask,.E6638: ; Special symbol "$" cannot be declared global.
    JMP .E6637: ; Special symbol "$" can be defined with EQU only.
.15:; Convert local name ESI,ECX to standard scope.
    CMPB [ESI],'.'
    JNE .18: ; If the name is not local.
    Invoke EaBufferReserve::,SymCreate
    Invoke SymDelocalName,ESI,ECX,EAX,symDelocal
    BufferRetrieve EAX
    Invoke EaBufferRelease::, EAX
.18:; ESI,ECX is now nonlocal nonempty trimmed symbol name. Check if it already exists on Program.SymList.
    Invoke SymFindByName,0,ESI,ECX,EDX
    MOV [%ReturnEAX],EAX ; Pointer to symbol, if found, otherwise 0.
    MOV EDI,EAX
    JNC .35: ; Skip definition when the symbol already exists.

    ; Symbol does not exist yet. A new symbol will be defined/declared/referenced/queried.
    JSt [%Reason],symQueried,.90: ; Return no symbol (EAX=0), CF=0.
    ListNew [EDX+PGM.SymList],Zeroed=yes
    MOV EDI,EAX ; Pointer to a new empty symbol.
    MOV [%ReturnEAX],EAX
    PoolStore [EDX+PGM.Pool],ESI,ECX
    MOV ESI,EAX ; ESI,ECX is now nonvolatile nonlocal symbol name in Pgm.Pool.
    MOV [EDI+SYM.NamePtr],ESI
    MOV [EDI+SYM.NameSize],ECX
    MOV ECX,[%Fixed]
    SymMemberUpdate LinePtr ; Where was the symbol defined.
    MOV [%Fixed],ECX
    MOV EAX,[%Reason]
    SetSt [EDI+SYM.Status],EAX
    JNSt EAX,symDefined,.20:
    ; New symbol is being defined. Copy its type and properties from the statement.
    MOV ECX,stmTypeMask+stmPropMask+stmLabelIsPublic ; Masks aliases to symbol properties.
    AND ECX,[EBX+STM.Status]
    OR ECX,symDefined+symDefInPass
    SetSt [EDI+SYM.Status],ECX ; Inherit type, properties and symGlobalRef from the statement.
    RstSt [EDI+SYM.Status],symEstimated
    JMP .45:
.20:JNSt EAX,symExplScopeMask, .25:
    ; New symbol EDI will be declared by explicit scope pseudoinstruction.
    JSt EAX,symPublic|symExport,.30: ; Go to estimate its properties.
    ; New symbol is declared symExtern or symImport.
    Invoke SssCreateExtern::,EDI,[%PgmPtr]
    JMP .90:
.25:JNSt EAX,symReferenced,.90:
    ; New symbol EDI is forward referenced. Its properties will be estimated.
    SetSt EAX,symUsed+symReferenced+symEstimated
    MOV AL,'?'
    MOV [EDI+SYM.Status],EAX
.30:MOV ECX,[%Fixed]
    SymMemberUpdate Section    ; Assume SECTION# $.
    SymMemberUpdate OffsetLow
    SymMemberUpdate OffsetHigh
    MOV [%Fixed],ECX
    ADDD [EDI+SYM.OffsetLow],64 ; AssumeOFFSET# $ + 64.
    ADCD [EDI+SYM.OffsetHigh],0
    JMP .80:
.35: ; Symbol EDI already exists. It is redefined/redeclared/referenced.
    JNSt [%Reason],symDefined,.60:
    ; Existing symbol EDI is (re)defined. It will be updated from the statement EBX.
    MOV EDX,[EDI+SYM.Status] ; Old properties.
    JSt EDX,symDefInPass, .E6610: ; Symbol "!1S" was already defined at "!2@".
    JSt EDX,symExtern|symImport, .E6624: ; Symbol "!1S" was declared as external at !2@.
    MOV EAX,[EBX+STM.Status] ; New properties.
    MOV ECX,stmTypeMask+stmPropMask+stmLabelIsPublic ; Synchronized with symTypeMask+symPropMask+symGlobalRef.
    JNSt EDX,symEntry,.38:
    OR EAX,stmLabelIsPublic ; When the ENTRY is defined in source, pretend it is implicitely global::.
.38:; Update symbol type and miscellaneous properties.
    JNSt EDX,symGlobalRef,.39:
    SetSt EAX,symGlobalRef
.39:AND EAX,ECX
    AND EDX,ECX
    CMP EAX,EDX
    JE .40:
    RstSt [EDI+SYM.Status],symFixed ; If any of symbol properties had changed, a new pass will be required.
.40:OR EAX,symDefined+symDefInPass
    NOT ECX
    ANDD [EDI+SYM.Status],ECX ; Erase old symbol type and properties.
    SetSt [EDI+SYM.Status],EAX ; Replace them with the new ones.
.45:; Update other properties from the statement.
    MOV ECX,[%Fixed]
    SymMemberUpdate Section
    JNSt [EDI+SYM.Status],symExplScopeMask,.47:
    MOV ECX,[%Fixed] ; Do not reset symFixed due to SYM.Section change when the symbol is defined and exported.
.47:SymMemberUpdate Size
    MOV [%Fixed],ECX
    ; Update offset.
    MOV EAX,[EDI+SYM.OffsetLow]
    MOV EDX,[EDI+SYM.OffsetHigh]
    SUB EAX,[EBX+STM.OffsetLow]
    SBB EDX,[EBX+STM.OffsetHigh] ; EDX:EAX is negative if symbol offset grows in this pass.
    JS .50: ; Growing is acceptable in any pass, including the fixing one.
    JNSt [%PgmStatus],pgmFixingPass|pgmLastPass,.50:
    ; Do not decrease symbol offset in fixing pass. Stuff the emitted code with NOPs instead.
    ADD [EBX+STM.AlignBytes],EAX
    JMP .80:
.50:SUB [EDI+SYM.OffsetLow],EAX  ; Update offset in ordinary passes.
    SBB [EDI+SYM.OffsetHigh],EDX
    OR EAX,EDX
    JZ .55:
    RstSt [%Fixed],symFixed ; Signalize that offset has changed.
.55: ; Update flag symFixed.
    JSt [%Fixed],symFixed,.60:
    RstSt [EDI+SYM.Status],symFixed
.60:MOV EAX,[%Reason]
    JNSt EAX,symExplScopeMask,.80:
    ; Existing symbol EDI is (re)declared. Check for conflicts.
    JNSt EAX,symPublic|symExport,.70:
    JSt EAX,symForwarded|symExport,.70:
    JSt [EDI+SYM.Status],symExtern|symImport,.E6621: ; External symbol "!1S" defined at "!2@" cannot be made public.
.70:JNSt EAX,symExtern|symImport,.75:
    JSt [EDI+SYM.Status],symDefined,.E6622: ; Public symbol "!1S" defined at "!2@" cannot be made external.
.75:SetSt [EDI+SYM.Status],EAX ; Update scope.
.80:MOV EAX,[%Reason]
    JNSt EAX,symReferenced,.85:
    ; Existing symbol is referenced.
    SetSt EAX,symUsed
    PUSH EAX,EDI; If symbol EDI is member of a structured symbol, mark the parent symbol symReferenced, too.
      MOV EBX,EDI
      MOV EDI,[EBX+SYM.NamePtr]
      MOV ECX,[EBX+SYM.NameSize]
      MOV EDX,EDI
      MOV AL,'.'
      REPNE SCASB
      JNE .84:    ; If there's no membership in symbol name.
      DEC EDI
      MOV ECX,[%Statement]
      JECXZ .84:
      MOV ECX,[ECX+STM.Program]
      SUB EDI,EDX ; EDX,EDI is now potentional parent's name.
      Invoke SymFindByName,0,EDX,EDI,ECX
      JC .84:     ; If no parent exists.
      SetSt [EAX+SYM.Status],symUsed+symReferenced
.84:POP EDI,EAX
    SetSt [EDI+SYM.Status],EAX
    JSt [EDI+SYM.Status],symDefined,.85:
    JNSt [EDI+SYM.Status],symEstimated,.85:
    RstSt [EDI+SYM.Status],symEstimated
    XOR EAX,EAX
    MOV [EDI+SYM.OffsetLow],EAX ; In the next passes is the original estimated offset $+64 changed to 0.
    MOV [EDI+SYM.OffsetHigh],EAX
.85:JNSt [%PgmStatus],pgmLastPass,.90:
    ; Final pass check of symbol.
    JSt [EDI+SYM.Status],symDefined,.88:
    JSt [EDI+SYM.Status],symExtern|symImport|symForwarded|symEntry,.90:
    JMP .E6601: ; Symbol "!1S" mentioned at !2@ was not found.
.88:JSt  [EDI+SYM.Status],symIncluded|symScopeMask|symReferenced|symQueried,.90:
    MOV ECX,[EDI+SYM.Section]
    JECXZ .89:
    JSt [ECX+SSS.Status],sssStructure,.90:
.89:Msg '2101',EDI ; Symbol !1S was defined but never used.
.90:EndProcedure SymCreate
↑ SymFixup Symbol
SymFixup elevates symbol offset if the symbol is defined in a segment whose bottom was elevated during combine process.
Input
Symbol Pointer to the fixed-up SYM.
Output
Symbol .Section and .Offset may be changed.
Invoked by
PgmCombine
SymFixup Procedure Symbol
    MOV EBX,[%Symbol]
    MOV ECX,[EBX+SYM.Section]
    JECXZ .90: ; If the symbol is scalar.
    ; Symbol EBX may belong to base program and then its .Section
    ;  may refer to a sssSection rather than to a sssSegment.
    ; However, its offset is already related to the segment bottom.
    JNSt [ECX+SSS.Status],sssSection,.30:
    MOV ECX,[ECX+SSS.SegmPtr]
    JECXZ .90:
    RstSt [ECX+SSS.Status],sssSection
.30:MOV EAX,[ECX+SSS.BottomLow]
    MOV EDX,[ECX+SSS.BottomHigh]  ; Elevated bottom of symbol's previous segment.
    MOV ESI,[ECX+SSS.SegmPtr] ; Base segment of the new symbol's segment.
    TEST ESI
    JZ .90:
    SUB EAX,[ESI+SSS.BottomLow]
    SBB EDX,[ESI+SSS.BottomHigh]
    ADD [EBX+SYM.OffsetLow],EAX   ; Fixup the symbol offset.
    ADC [EBX+SYM.OffsetHigh],EDX
    MOV [EBX+SYM.Section],ESI     ; Fixup the symbol new segment.
.90:EndProcedure SymFixup
↑ SymResolveImage Pgm
SymResolveImage inspects external and imported symbols in executable Pgm, tries to find a homonymous public symbol and update its properties. Succesfully matched external symbol is then marked as symResolved.
Virtual addresses of all segments and groups must be already set by PgmLinkImage.
Input
Pgm is pointer to program whose global symbols are matched.
Output
-
Error
Errors are reported with macro Msg.
See also
SymResolveObject
Invokes
DictSearchByData SymFindByName
Invoked by
PgmLinkImage
SymResolveImage Procedure Pgm
DictFormat LocalVar ; ^DICT with current program format name (used in error messages).
    MOV EBX,[%Pgm]
    MOV ECX,pgmoptFormatMask
    AND ECX,[EBX+PGM.Pgmopt.Status]
    Invoke DictSearchByData::,DictProgramFormats::,ECX
    MOV [%DictFormat],ESI ; String pointer to format name, e.g."COM". Used as !1S in Msg.
    ListGetFirst [EBX+PGM.SymList]
    JZ .90: ; If there are no symbols in the program, done.
.50:MOV ESI,EAX ; Resolve all external and imported symbols in the loop .50: .. .80:.
    JSt [ESI+SYM.Status],symForwarded,.80: ; Leave forward-exported symbols to the loader.
    JNSt [ESI+SYM.Status],symExtern|symImport,.80:
.55:; ESI is an referenced external or imported symbol. Its SYM.Section specifies an external pseudosegment.
    MOV ECX,[ESI+SYM.Section]
    JECXZ .E6961: ; This should never happen, extern symbol is always framed by extern pseudosegment.
    ; The contents of SSS.SymPtr in extern pseudosegment ECX will be replaced
    ;     with pointer to the matching public symbol.
    ; Find public symbol by the name of extern/import symbol ESI
    ;    (symbol ESI name is identical with the name of extern pseudosegment ECX).
    Invoke SymFindByName::,symPublic,[ESI+SYM.NamePtr],[ESI+SYM.NameSize],EBX
    MOV [ECX+SSS.SymPtr],EAX ; The matching public symbol EAX will be put to extern pseudosegment's SSS.SymPtr.
    JNC .60: ; If matching public symbol EAX found.
    JSt [ESI+SYM.Status],symImport,.80: ; Do not report as the symbol ESI might have been linked from import library.
.E6961:Msg '6961',ESI ; Unresolved external/imported symbol "!1S".
    JMP .80:
.60:SetSt [ESI+SYM.Status],symResolved
    MOV EDX,[EAX+SYM.Section] ; Section of the matching public symbol.
    TEST EDX
    JZ .70:
    MOV EDX,[EDX+SSS.SegmPtr]  ; Segment of the matching public symbol.
    MOV [ECX+SSS.SegmPtr],EDX  ; Update segment of extern pseudosegment.
    MOV EDX,[EDX+SSS.GroupPtr] ; Group of the matching public symbol.
    MOV [ECX+SSS.GroupPtr],EDX ; Update group of extern pseudosegment.
.70:JNSt [EAX+SYM.Status],symImport,.80:
    ; Warn if dynamic link was used in COM or MZ output format.
    JSt [EBX+PGM.Pgmopt.Status],pgmoptImports,.80: ; Skip E8613 when the format allows import.
    Msg '8613',[%DictFormat],ESI ; Loader of !1S program will not bind dynamically imported symbol "!2".
.80:ListGetNext ESI ; The next external or imported symbol.
    JNZ .50:
.90:EndProcedure SymResolveImage
↑ SymFrameAddress Symbol, Program
SymFrameAddress returns addressing frame of the Symbol.
Input
Symbol is pointer to SYM object.
Program is pointer to program PGM where the Symbol belongs.
Output
EDX:EAX= offset of the Symbol.
ECX= pointer to the group SSS of the symbol.
Error
-
Invoked by
PgmListGlobals PgmListMap
SymFrameAddress Procedure Symbol, Program
    SUB EAX,EAX
    SUB EDX,EDX
    SUB ECX,ECX
    MOV EBX,[%Symbol]
    TEST EBX
    JZ .80:
    MOV EAX,[EBX+SYM.OffsetLow]
    MOV EDX,[EBX+SYM.OffsetHigh]
    MOV ECX,[EBX+SYM.Section]
    JECXZ .80:
    MOV EDI,[ECX+SSS.GroupPtr]
    TEST EDI
    JNZ .10:
    MOV EDI,ECX
.10:JNSt [ECX+SSS.Status],sssExtern,.20:
    MOV EBX,[ECX+SSS.SymPtr]
    TEST EBX
    JZ .80:
    ADD EAX,[EBX+SYM.OffsetLow]
    ADC EDX,[EBX+SYM.OffsetHigh]
    MOV ECX,[EBX+SYM.Section]
    JECXZ .80:
    MOV ECX,[ECX+SSS.SegmPtr]
    MOV EDI,[ECX+SSS.GroupPtr]
    TEST EDI
    JNZ .20:
    MOV EDI,ECX ; Group EDI equals to segment ECX if the segment is not grouped.
    JMP .30:
.20:MOV EDI,[EDI+SSS.GroupPtr]  ; Group might be linked from external module.
.30:TEST EDI
    JNZ .40:
    MOV EDI,ECX ; Group EDI equals to segment ECX if the segment is not grouped.
.40:; ECX is now symbol's segment and EDI its group, both are nonzero.
    MOV ESI,[%Program]
    JSt [ESI+PGM.Pgmopt.Status],pgmoptFLAT,.50: ; Frame is 0 in FLAT model.
    ADD EAX,[ECX+SSS.BottomLow]
    ADC EDX,[ECX+SSS.BottomHigh]
    SUB EAX,[EDI+SSS.BottomLow]
    SBB EDX,[EDI+SSS.BottomHigh]
.50:MOV ECX,EDI
.80:MOV [%ReturnEAX],EAX
    MOV [%ReturnEDX],EDX
    MOV [%ReturnECX],ECX
EndProcedure SymFrameAddress
↑ SymResolveObject Pgm
SymResolveObject inspects external symbols of linked object module Pgm, tries to find a homonymous public symbol in the same segment and update its properties. Succesfully matched external symbol is then marked as symResolved.
SymResolveObject is invoked when an object file is linked from other object files, segments are not linked yet to image (their bottoms are all 0). Therefore references between homonymous symbols from different segments cannot be resolved here.
Input
Pgm is pointer to program whose global symbols are matched.
Output
-
Error
-
See also
SymResolveImage
Invokes
SymFindByName
Invoked by
PfcoffCompile
SymResolveObject Procedure Pgm
    MOV EBX,[%Pgm]
    ListGetFirst [EBX+PGM.SymList]
    JZ .90: ; If there are no symbols in the program, done.
.10:MOV ESI,EAX
    JNSt [ESI+SYM.Status],symExtern,.80:
    ; Find public symbol by the name of extern symbol ESI.
    Invoke SymFindByName::,symPublic,[ESI+SYM.NamePtr],[ESI+SYM.NameSize],EBX
    JC .80:
    ; EAX is now homonymous public symbol matched with extern ESI.
    MOV ECX,[ESI+SYM.Section]
    JECXZ .60:
    MOV [ECX+SSS.SymPtr],EAX
.60:SetSt [ESI+SYM.Status],symResolved
.80:ListGetNext ESI ; The next external or imported symbol.
    JNZ .10:
.90:EndProcedure SymResolveObject
SymDynamicLink Procedure Sym,PgmPtr,DllPtr,DllSize,FwdPtr,FwdSize
     MOV EDI,[%Sym]
     MOV EBX,[%PgmPtr]
     TEST EDI
     JZ .90:
     Invoke SssCreateExtern::,EDI,EBX
     JSt [EDI+SYM.Status],symImport,.10:
     JNSt [EDI+SYM.Status],symExport,.90:
     SetSt [EDI+SYM.Status],symGlobal ; Export symbol implies globality.
.10: MOV ECX,[%DllSize]
     MOV ESI,[%DllPtr]
     JECXZ .60: ; If LIB= is not explicitly specified, leave it as is.
     ListGetFirst [EBX+PGM.SymList] ; Reuse identical DllName from any older symbol.
     JZ .40:
.20: JNSt [EAX+SYM.Status],symImport|symExport,.30:
     MOV EDX,[EAX+SYM.DllNamePtr] ; Old nonvolatile DllName.
     Compare EDX,[EAX+SYM.DllNameSize],ESI,ECX
     JE .50: ; If found, reuse previously stored name EDX.
.30: ListGetNext EAX
     JNZ .20:
.40: PoolStore [EBX+PGM.Pool],ESI,ECX ; Make DllName nonvolatile.
     MOV EDX,EAX
.50: MOV ESI,EDX
     MOV [EDI+SYM.DllNamePtr],ESI
     MOV [EDI+SYM.DllNameSize],ECX
.60: JNSt [EDI+SYM.Status],symExport,.90:
     MOV ESI,[%FwdPtr]
     MOV ECX,[%FwdSize]
     JECXZ .90: ; If no forward was specified.
     SetSt [EDI+SYM.Status],symForwarded
     PoolStore [EBX+PGM.Pool],ESI,ECX
     JMP .80:
.70: MOV EAX,[EDI+SYM.NamePtr] ; Default Fwd name is identical with symbol name.
     MOV ECX,[EDI+SYM.NameSize]
.80: MOV [EDI+SYM.InterNamePtr],EAX
     MOV [EDI+SYM.InterNameSize],ECX
.90:EndProcedure SymDynamicLink
↑ SymStoreForwarderName Symb, FwdBuffer
This procedure will store ASCIIZ string which consists of Symb.DllName without path and extension, concatenated with forwarder name from Symb.InterName.
Input
Symb is pointer to SYM symbol with symExport+symForwarded flags set.
FwdBuffer is pointer to BUFFER where the forwarder name will be stored.
Output
Dynamic-linking properties of Sym are set.
Error
-
Invoked by
PfpeExportCreate
SymStoreForwarderName Procedure Symb, FwdBuffer
     MOV EBX,[%Symb]
     JNSt [EBX+SYM.Status],symExport,.90:
     JNSt [EBX+SYM.Status],symForwarded,.90:
     MOV ESI,[EBX+SYM.DllNamePtr]
     MOV ECX,[EBX+SYM.DllNameSize]
     FileNameParse ESI,Size=ECX,Unicode=0
     SUB ECX,EAX ; EAX,ECX is now file name without extension.
     MOV EDX,[%FwdBuffer]
     BufferStore EDX,EAX,ECX
     BufferStoreByte EDX,'.'
     MOV ESI,[EBX+SYM.InterNamePtr]
     MOV ECX,[EBX+SYM.InterNameSize]
     TEST ECX
     JNZ .80:
     MOV ESI,[EBX+SYM.NamePtr]
     MOV ECX,[EBX+SYM.NameSize]
.80: BufferStore EDX,ESI,ECX
     BufferStoreByte EDX,0
.90:EndProcedure SymStoreForwarderName
↑ SymCreateLiteral LitPtr, LitSize, StmPtr
SymCreateLiteral will create a new literal symbol on StmPtr.Program.SymList or reuse existing symbol with identical name.
LIteral strings without type specifier, e.g. ="String" will be in fact created under modified name =B"String" or =U"String".
Input
LitPtr Source text which should be a literal, i.e. equal sign = followed with optional duplication, then with short or long datatype name or structure name, or followed with a quoted string.
LitSize Number of bytes in source literal definition.
StmPtr ^STM which refers/creates the literal symbol.
Output
CF=0
EAX= Pointer to new or reused SYM.
Error
CF=1, "E6671 Invalid syntax of literal symbol !1S" should be reported by the caller.
EAX=0
See also
ExpParseLiteral.
Invokes
EaBufferRelease EaBufferReserve ExpAlign ExpEvalData SssCreate@LT SssCreate@RT SssEmit SymFindByName
Invoked by
ExpEval
Tested by
t1711 t1713 t1717
SymCreateLiteral Procedure LitPtr, LitSize, StmPtr
LitNameBuffer  LocalVar ; Temporary buffer for updated literal name.
LitEmitBuffer  LocalVar ; Temporary buffer for emitted data.
LitRelocBuffer LocalVar ; Temporary buffer for emitted relocations.
LitSection     LocalVar ; ^SSS with [@RT0] or [@LT*].
ExpStatus      LocalVar ; Status of literal evaluated to EXP.
     EaStackCheck ; Protect from SO in case of recursed literal.
     Invoke EaBufferReserve::,SymCreateLiteral
     MOV [%LitNameBuffer],EAX
     Invoke EaBufferReserve::,SymCreateLiteral
     MOV [%LitEmitBuffer],EAX
     Invoke EaBufferReserve::,SymCreateLiteral
     MOV [%LitRelocBuffer],EAX
     MOV EBX,[%StmPtr]
     TEST EBX
     JZ .Error:
     MOV EDX,[EBX+STM.Program]
     TEST EDX
     JNZ .10:
.Error:SUB EAX,EAX
     MOV [%ReturnEAX],EAX
     STC
     JMP .90:
.10: ; Prepare literal name.
     MOV EDI,[%LitNameBuffer]
     MOV ESI,[%LitPtr]
     MOV ECX,[%LitSize]
     StripSpaces ESI,ECX
     BufferStore EDI,ESI,ECX
     LEA EDX,[ESI+ECX]
     LODSB
     CMP AL,'='
     JNE .Error:
.20: CMP ESI,EDX
     JNB .35:
     LODSB
     ExpClassify AL
     TEST AH,expWhiteSpace
     JNZ .20:
     DEC ESI     ; ESI now points to source data expression.
     SUB EDX,ESI ; EDX is size of the value.
     TEST AH,expQuote
     JZ .35:
     ; Literal defines a string without type. B or U will be injected into its name.
     BufferClear EDI
     MOV AX,"=U"
     JSt [Ea.Eaopt.Status::],eaoptUNICODE,.30:
     MOV AX,"=B"
.30: BufferStoreWord EDI,EAX ; Insert either =B or =U.
     BufferStore EDI,ESI,EDX ; Insert the rest (quoted string).
.35: ; Evaluate literal data to %LitEmitBuffer and %LitRelocBuffer.
     BufferRetrieve EDI      ; Literal name, e.g. =U"Text".
     INC ESI
     DEC ECX
     MOV EDX,[%LitEmitBuffer]
     Invoke ExpEvalData::,EDX,[%LitRelocBuffer],ESI,ECX,0,EBX
     MOV [%ExpStatus],EAX
     JC .Error:
     JNSt EAX,expString, .40:
     CMP AL,'B'
     JNE .38:
     BufferStoreByte EDX,0   ; Terminate string literal value with NUL character.
.38: CMP AL,'U'
     JNE .40:
     BufferStoreWord EDX,0
.40: ; Get literal section.
     CMP AL,'I'
     JNE .45:
     Invoke SssCreate@RT::,0,EBX
     JMP .50:
.45: Invoke SssCreate@LT::,EAX,EBX
.50: JC .Error:
     MOV [%LitSection],EAX
     ; Look if verbatim same literal symbol was already created.
     BufferRetrieve [%LitNameBuffer]
     MOV EDX,[EBX+STM.Program]
     Invoke SymFindByName,0,ESI,ECX,EDX
     MOV [%ReturnEAX],EAX
     JNC .55:
     ; Not found. The new literal symbol will be created.
     PoolStore [EDX+PGM.Pool],ESI,ECX
     MOV ESI,EAX ; ESI,ECX is now nonvolatile literal name, e.g. "=B 1+2", with PGM lifetime.
     ListNew [EDX+PGM.SymList], Zeroed=yes ; Allocate room for the new literal symbol.
      ; EAX=^SYM, EBX=^STM, EDX=^PGM, ESI,ECX=literal name.
     MOV [%ReturnEAX],EAX
     MOV [EAX+SYM.NamePtr],ESI
     MOV [EAX+SYM.NameSize],ECX
     MOV ECX,[%ExpStatus]  ; (Re)initialize status of literal symbol EAX.
     MOV EDX,[EBX+STM.LinePtr]
     RstSt ECX,expString
     SetSt ECX,symLiteral+symDefined+symReferenced+symUsed+symDefInPass+symFixed
     MOV [EAX+SYM.LinePtr],EDX ; Source line where it was first referred (=created).
     MOV [EAX+SYM.Status],ECX
.55: ; Look if the value of symbol EAX stored in [%LitEmitBuffer] is already emitted in %LitSection.
     MOV EBX,[%LitSection]
     BufferRetrieve [EBX+SSS.EmitBuffer]
     MOV EDI,ESI
     LEA EDX,[ESI+ECX] ; EDI..EDX is now the already emitted section contents.
.60: BufferRetrieve [%LitEmitBuffer] ; ESI,ECX is now the new literal value. EAX=^SYM.
     LEA EAX,[EDI+ECX]
     CMP EAX,EDX
     JA  .70:    ; Skip if behind the section limit.
     PUSH EDI
       REPE CMPSB
     POP EDI
     JE .65:     ; Reusable literal value was found.
     ADD EDI,[EBX+SSS.Alignment] ; Try the next possible aligned position in section.
     JMP .60:
.65: ; EDI is address of reusable literal value in section's EmitBuffer. ECX=0.
     BufferRetrieve [EBX+SSS.EmitBuffer]
     SUB EDI,ESI
     ADD EDI,[EBX+SSS.BottomLow]
     JMP .80:
.70: MOV EBX,[%LitSection]
     ; Literal value in %LitEmitBuffer is not yet in EBX section's EmitBuffer.
     MOV EDI,[EBX+SSS.OrgLow]
     Invoke ExpAlign::,EDI,[EBX+SSS.Alignment],0 ; Return ECX=required size of alignment stuff.
     ADD EDI,ECX
     MOV ESI,[%StmPtr]
     MOV ESI,[ESI+STM.Program]
     TEST [ESI+PGM.Status],pgmLastPass
     MOV ESI,[%LitRelocBuffer]
     JNZ .75:
     XOR ESI,ESI ; Relocations are flushed in the final pass only.
.75: Invoke SssEmit::,EBX,[%LitEmitBuffer],ESI,ECX
.80: MOV EAX,[%ReturnEAX]
     ; Update properties of literal symbol EAX. EDI is its offset from segment's bottom.
     CMP EDI,[EAX+SYM.OffsetLow]
     JE .83:
.82: MOV [EAX+SYM.OffsetLow],EDI
     RstSt [EAX+SYM.Status],symFixed
.83: CMP EBX,[EAX+SYM.Section]
     JE .86:
     MOV [EAX+SYM.Section],EBX
     RstSt [EAX+SYM.Status],symFixed
.86: MOV ECX,[EBX+SSS.Alignment]
     CMP ECX,[EAX+SYM.Align]
     JE .89:
     MOV [EAX+SYM.Align],ECX
     RstSt [EAX+SYM.Status],symFixed
.89: BufferRetrieve [%LitEmitBuffer]
     CMP ECX,[EAX+SYM.Size]
     JE .90:
     MOV [EAX+SYM.Size],ECX
     RstSt [EAX+SYM.Status],symFixed
.90: PUSHFD ; Keep CF.
      Invoke EaBufferRelease::,[%LitEmitBuffer]
      Invoke EaBufferRelease::,[%LitRelocBuffer]
      Invoke EaBufferRelease::,[%LitNameBuffer]
     POPFD
    EndProcedure SymCreateLiteral
ENDPROGRAM sym

▲Back to the top▲