EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

member.htm
Class
MEMBER
Encodings
MemberEnc
Procedures
MemberAdd
MemberCreate
MemberUpdate

Class MEMBER describes a named structure member. When a structure is declared (by STRUC/ENDSTRUC block), each its D* statement with a label creates MEMBER record added to its Sss.SssOrdBuffer. Local names of those members are kept in Sss.PgmPool until the end of program.
Structure members themselves create a plain-numeric symbols. Address symbols will be created from them whenever the structure is expanded (structured memory variable created with DS).

Declaring the structure creates one symbol from each its member, no matter if the structure will be ever expanded in data|bss section or not. Fully qualified name of such member symbol is created from the structure name appended with local member name. Their type is 'N'.

When the structure is expanded (using DS statement), another set of symbols is created, their names are constructed from DS label appended with local member name.


Example
Inner STRUC ; Structure Inner is added on Pgm.SssList. D W ; Unnamed data do not create structure member nor a symbol. .Inn1 D W ; Member .Inn1 is added to Sss.SssOrdBuffer. ENDSTRUC Inner ; Scalar symbol Inner.Inn1 is created. Outer STRUC ; Struc Outer is added on Pgm.SssList. .Out1 D W ; Member .Out1 is added to Sss.SssOrdBuffer. .Out2 D Inner ; Members .Out2 and .Out2.Inn1 are added to Sss.SssOrdBuffer. ENDSTRUC Outer ; Scalar symbols Outer.Out1, Outer.Out2, Outer.Out2.Inn1 are created. Var D Outer ; Definition of a structured memory variable. ; This creates address symbols Var, Var.Out1, Var.Out2, Var.Out2.Inn1.
       EUROASM NOWARN=2101
member 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.
ea.htm,      \
eaopt.htm,   \
exp.htm,     \
msg.htm,     \
pgm.htm,     \
pgmopt.htm,  \
reloc.htm,   \
sss.htm,     \
stm.htm,     \
sym.htm,     \
syswin.htm,  \
;;

member HEAD  ; Start of module interface.
↑ MEMBER
represents one member of a structure or library.
MEMBER   STRUC ; Description of named data (D* statements) inside the structure.
.NamePtr   D D ; Pointer to local member name.
.NameSize  D D ; Number of bytes in member name.
.Offset    D D ; Aligned offset of this member relative to start of the structure.
.Size      D D ; Size of member value in bytes.
.Status    D D ; DataType in LSB ('B','U','W','D','Q','T')
            ENDSTRUC MEMBER
↑ MemberEnc
Encoding of flags used in MEMBER.Status.
memberType           = 0x0000_00FF ; DataType of the structure member ('B','U','W','D','Q','T').
 ; Flags memberDelocal* are used in SymDelocalName only.
memberDelocalNone    = 0x0000_0000 ; Do not delocalize symbol name beginning with ..
memberDelocal        = 0x0000_0100 ; Do prefix symbol name beginning with . with the current namespace.
memberDelocalParent  = 0x0000_0200 ; Do prefix symbol name beginning with . with the parent namespace (skip 1 current namespace).
  ENDHEAD member ; End of module interface.
↑ MemberAdd SssPtr, StmPtr, DstrucPtr
MemberAdd is called when D* data are defined inside STRUC/ENDSTRUC block.
It creates a new MEMBER record in Sss.SssOrdBuffer from D* statement, which is parsed and executed in Stm.
When Stm contains DS statement (structured data variable defined inside outer structure), all members from inner structure are concatenated with Stm local label and added on Sss.SssOrdBuffer, too.
Input
SssPtr ^SSS structure which to add the member to.
StmPtr Parsed D* STM with member information.
DstrucPtr ^SSS (inner) structure of DS data, otherwise 0.
Output
-
Error
-
Example
Inner STRUC .Inn1 DD D ; MemberAdd called here creates the member .Inn1 of Inner structure. ENDSTRUC Inner Outer STRUC .Out1 DD D ; MemberAdd called here creates member .Out1 of Outer structure. .Out2 DS Inner ; MemberAdd called here creates members .Out2 and .Out2.Inn1 of Outer structure. ENDSTRUC Outer Var DS Outer ; Definition of structured memory variable.
See also
MemberCreate. MemberUpdate.
Invokes
EaBufferRelease EaBufferReserve
Invoked by
PseudoData
MemberAdd Procedure SssPtr, StmPtr, DstrucPtr
OutMember  LocalVar Size=SIZE#MEMBER
InnMember  LocalVar Size=SIZE#MEMBER
      MOV EBX,[%StmPtr]
      MOV EDI,[%SssPtr]
      MOV ESI,[EBX+STM.LabelPtr]
      MOV ECX,[EBX+STM.LabelSize]
      PoolStore [EDI+SSS.PgmPool],ESI,ECX
      LEA EDI,[%OutMember]
      MOV [EDI+MEMBER.NamePtr],EAX
      MOV [EDI+MEMBER.NameSize],ECX
      MOV EAX,[EBX+STM.Status]
      MOV EDX,[EBX+STM.Size]
      MOV [EDI+MEMBER.Status],EAX
      MOV [EDI+MEMBER.Size],EDX
      MOV ESI,[%SssPtr]
      MOV EAX,[ESI+SSS.OrgLow]
      ADD EAX,[EBX+STM.AlignBytes]
      MOV [EDI+MEMBER.Offset],EAX
      BufferStore [ESI+SSS.SssOrdBuffer],EDI,SIZE#MEMBER
      Msg cc=C,'9314',MemberAdd
      MOV EDX,[%DstrucPtr]                       ; If the added member (.Out2) is structured, its submembers will be stored, too.
      TEST EDX
      JZ .90:
      JNSt [EDX+SSS.Status],sssStructure,.90:
      MOV EBX,ESI
 ; EDI=^MEMBER just added (".Out2").
 ; EBX=^SSS struc which the member was just added to (Outer)
 ; EDX=^SSS belonging to the added member (Inner).
 ; Local name of each member from structure EDX (".Inn1") will be prefixed with 
 ; member name (".Out2"), saved on [EBX+SSS.PgmPool] and added to [EBX+SSS.SssOrdBuffer].
      BufferRetrieve [EDX+SSS.SssOrdBuffer]
      TEST ECX
      JZ .90:
 .20: PUSH ECX                                   ; ESI=^MEMBER from inner structure (.Inn1)
        LEA EDX,[%InnMember]
        MOV EAX,[ESI+MEMBER.Status]
        MOV ECX,[ESI+MEMBER.Size]
        MOV [EDX+MEMBER.Status],EAX
        MOV [EDX+MEMBER.Size],ECX
        MOV EAX,[EDI+MEMBER.Offset]
        ADD EAX,[ESI+MEMBER.Offset]
        MOV [EDX+MEMBER.Offset],EAX
        Invoke EaBufferReserve::,MemberAdd       ; Temporary buffer for names concatenation.
        BufferStore EAX,[EDI+MEMBER.NamePtr],[EDI+MEMBER.NameSize]
        JC .F9314:
        BufferStore EAX,[ESI+MEMBER.NamePtr],[ESI+MEMBER.NameSize]
        JC .F9314:
        PUSH ESI
          BufferRetrieve EAX
          Invoke EaBufferRelease::,EAX  
          PoolStore [EBX+SSS.PgmPool],ESI,ECX
          MOV [EDX+MEMBER.NamePtr],EAX
          MOV [EDX+MEMBER.NameSize],ECX
        POP ESI
        BufferStore [EBX+SSS.SssOrdBuffer],EDX,SIZE#MEMBER
        JNC .80:
 .F9314:Msg cc=C,'9314',MemberAdd
        POP ECX
        JMPS .90:        
 .80: POP ECX
      ADD ESI,SIZE#MEMBER
      SUB ECX,SIZE#MEMBER
      JA .20:        
 .90:EndProcedure MemberAdd
↑ MemberCreate SssPtr, StmPtr
MemberCreate creates a symbol for each named structure member. It is used when DS statement is executed both inside a section or inside a structure.
MemberCreate is invoked in ctxSTRUC+ctxExpansion context, local member names will be combined with context namespace.
Input
SssPtr Pointer to an existing structure whose members from Sss.SssOrdBuffer are created.
StmPtr DS statement which provides default properties of created symbols.
Output
CF=0
Error
CF=1 Errors are reported with macro Msg.
Example
Inner STRUC .Inn1 DD D ; Member of Inner structure. DD D ; Unnamed data do not create structure member. ENDSTRUC Inner Outer STRUC .Out1 DD D; Member of Outer structure. .Out2 DS Inner ; Structured member of Outer structure. ENDSTRUC Outer Var DS Outer ; Definition of structured memory variable. ; Previous statement will create symbols Var, Var.Out1, Var.Out2, Var.Out2.Inn1
See also
MemberAdd, MemberUpdate.
Invokes
SymCreate
Invoked by
PseudoData
MemberCreate Procedure SssPtr, StmPtr
McStm  LocalVar Size=SIZE#STM                    ; Temporary fake statement which provides info for creating a symbol.
     LEA EBX,[%McStm]
     CopyTo EBX,[%StmPtr],Size=SIZE#STM          ; Initialize temporary fake statement.
 .10:MOV EDX,[%SssPtr]                           ; ^SSS structure.
     MOV EDI,[EBX+STM.OffsetLow]
     TEST EDX
     STC
     JZ .90:
     BufferRetrieve [EDX+SSS.SssOrdBuffer]
     TEST ECX
     JZ .90:                                     ; Do nothing if there are no named members in SssOrdBuffer.
 .50:PUSH ECX,ESI,EDI                            ; ESI=^MEMBER, EBX=^STM temporary fake statement.
       MOV ECX,[ESI+MEMBER.NameSize]
       MOV EDX,[ESI+MEMBER.Size]
       ADD EDI,[ESI+MEMBER.Offset]
       MOV EAX,[ESI+MEMBER.Status]
       MOV ESI,[ESI+MEMBER.NamePtr]
       MOV [EBX+STM.Size],EDX
       MOV [EBX+STM.OffsetLow],EDI
       MOV [EBX+STM.Status],AL
       MOV EAX,stmLabelIsPublic                  ; Alias symGlobalRef.
       AND EAX,[EBX+STM.Status]
       OR  EAX,symDefined
       Invoke SymCreate::,EAX,ESI,ECX,EBX
       TEST EAX
       JZ .80:
       SetSt [EAX+SYM.Status],symReferenced      ; Member of a structure shouldn't report W2101.
.80: POP EDI,ESI,ECX
     ADD ESI,SIZE#MEMBER
     SUB ECX,SIZE#MEMBER
     JA .50:                                     ; The next member.
 .90:EndProcedure MemberCreate
↑ MemberUpdate SssPtr, StmPtr, OutEmitBuffer, OutRelocBuffer
MemberUpdate copies data from Sss.EmitBuffer to OutEmitBuffer , updating matching members by keywords in Stm.KeyBuffer.
It is used in structured data declaration (pseudoinstruction DS) with initialized members. Initialized contents of any member will also set the flag Stm.Flags:stmtNotBSS.
Input
SssPtr Pointer to structure which is instantionized (SSS).
StmPtr is the parsed statement which defines the structured memory variable. It may have keywords whose value updates members of the structure.
OutEmitBuffer reserved empty BUFFER , allocated by caller.
OutRelocBuffer reserved empty BUFFER , allocated by caller.
Output
OutEmitBuffer is filled with structure data, updated with statement's keyword values. Occupied size equals to Sss.EmitBuffer.
OutRelocBuffer is filled with relocations of static data used in this structured memory variable. Their origins are related to the beginning of emitted structure.
Error
reported with macro Msg.
See also
MemberAdd, MemberCreate.
Invokes
EaBufferRelease EaBufferReserve ExpEvalData
Invoked by
PseudoData
MemberUpdate Procedure SssPtr, StmPtr, OutEmitBuffer, OutRelocBuffer
MuEmitBuffer  LocalVar                           ; Temporary buffer used in keyword value evaluation.
MuRelocBuffer LocalVar                           ; Temporary buffer used in keyword value evaluation.
      Invoke EaBufferReserve::,MemberUpdate
      MOV [%MuEmitBuffer],EAX
      Invoke EaBufferReserve::,MemberUpdate
      MOV [%MuRelocBuffer],EAX
      MOV EDI,[%SssPtr]                          ; Instantionized structure.
      MOV EBX,[%StmPtr]                          ; Definition statement with keywords.
      TEST EDI
      STC
      JZ .99:
      BufferRetrieve [EDI+SSS.EmitBuffer]        ; Template data of the structure, including its static defaults.
      BufferStore [%OutEmitBuffer],ESI,ECX
      Msg cc=C,'9314',MemberUpdate
 ; OutEmitBuffer is initialized with STRUC defaults. Now its members will be updated by Stm keywords.
 ; Outer loop .10: .. .80: walks through statement keywords, and for each keyword 
 ;                             and inner loop .20: .. .30: searches for the member.
      BufferRetrieve [EBX+STM.KeyBuffer]
      LEA EDX,[ESI+ECX]                          ; ESI..EDX are keyword records (4*DD).
 .10: CMP ESI,EDX
      JNB .90:
      PUSH EDX,ESI
        MOV EDI,[%SssPtr]
        MOV EBX,ESI                              ; EBX is now keyword record (4*DD).
        BufferRetrieve [EDI+SSS.SssOrdBuffer]
        LEA EDX,[ESI+ECX]                        ; ESI..EDX are MEMBER records.
  .20:  CMP ESI,EDX
        JNB .30:
        Compare [EBX+0],[EBX+4],[ESI+MEMBER.NamePtr],[ESI+MEMBER.NameSize]
        JE .40:
        ADD ESI,SIZE#MEMBER
        JMP .20:
  .30: ; Keyword is not in memberlist.
        Msg '2612',EBX,EDI,PgmStatus=pgmLastPass ;  "!1S" is not member of structure !2S. Ignored.
        JMP .80:                                 ; Continue with the next keyword.
  .40: ; Matching member found. Keyword value at [EBX+8],[EBX+12] will safely rewrite
       ; corresponding contents of OutEmitBuffer at [ESI+MEMBER.Offset].
        BufferClear [%MuEmitBuffer]
        BufferClear [%MuRelocBuffer]
        Invoke ExpEvalData::,[%MuEmitBuffer],[%MuRelocBuffer],[EBX+8],[EBX+12],[ESI+MEMBER.Status],[%StmPtr] ; Also set stmtNotBSS.
        JC .80:
        MOV EAX,[ESI+MEMBER.Offset]              ; Relative offset inside the structure contents (0..value size).
        MOV EDX,[ESI+MEMBER.Size]                ; Maximal size that may be rewritten.
        BufferRetrieve [%MuEmitBuffer]           ; ESI,ECX is proposed new value.
        CMP ECX,EDX
        JBE .50:
        LEA ECX,[EBX+8]
        Msg '2613',ECX,[%SssPtr],EBX             ; Value "!1S" does not fit to structure member !2S.!3S. Truncated.
        MOV ECX,EDX
  .50:  MOV EDI,ESI
        MOV EDX,ECX                              ; EDI,EDX is now truncated new value.
        BufferRetrieve [%OutEmitBuffer]
        ADD ESI,EAX                              ; Add member offset.
        CopyTo ESI,EDI,Size=EDX                  ; Rewrite (truncated) data in OutEmitBuffer.
        BufferRetrieve [%MuRelocBuffer]
        JECXZ .80:
  .60:  ; Each relocation in keyword value will be patched with member offset in EAX.
        ADD [ESI+RELOC.OrgLow],EAX
        ADCD [ESI+RELOC.OrgHigh],0
        BufferStore [%OutRelocBuffer],ESI,SIZE#RELOC
        Msg cc=C,'9314',MemberUpdate
        ADD ESI,SIZE#RELOC
        SUB ECX,SIZE#RELOC
        JA .60:
  .80:POP ESI,EDX
      ADD ESI,16                                 ; The next keyword.
      JMP .10:
[.data]
           ALIGN DWORD
.TempReloc DS RELOC                              ; Swap area for .SortByOrg.
[.text]
 .90: ; %OutRelocBuffer was filled with relocations from updating keywords.
    ; However, not updated members of the structure may have its own relocations,
    ; they will be appended to %OutRelocBuffer unless a relocation already exists
    ; on the same origin.
      MOV EDI,[%SssPtr]
      BufferRetrieve [EDI+SSS.RelocBuffer]
      JECXZ .98:
 .92: PUSH ECX,ESI
       MOV EBX,ESI                               ; Relocation from the structure.
       MOV EDX,[EBX+RELOC.OrgLow]
       BufferRetrieve [%OutRelocBuffer]
       JECXZ .95:
 .94:  CMP EDX,[ESI+RELOC.OrgLow]                ; Compare with relocation from keywords.
       JE .96:                                   ; Relocation with this origin was already stored in OutRelocBuffer, skip.
       ADD ESI,SIZE#RELOC
       SUB ECX,SIZE#RELOC
       JA .94:
 .95:  ; None from relocations already stored in %OutRelocBuffer has the same origin EDX as EBX.
       BufferStore [%OutRelocBuffer],EBX,SIZE#RELOC
       Msg cc=C,'9314',MemberUpdate
 .96: POP ESI,ECX
      ADD ESI,SIZE#RELOC
      SUB ECX,SIZE#RELOC
      JA .92:
 .98: Invoke EaBufferRelease::,[%MuRelocBuffer]
      Invoke EaBufferRelease::,[%MuEmitBuffer]
      ; Contents of OutRelocBuffer must be sorted by origin.
      BufferRetrieve [%OutRelocBuffer]
      JECXZ .99:
      MOV EDI,SIZE#RELOC
      MOV EAX,ECX
      CDQ
      DIV EDI
      ShellSort ESI,EAX,EDI,SortByOrg
SortByOrg:: PROC1 ; ShellSort callback used to sort relocations by RELOC.Org.
       ; Input: ESI and EDI point to RELOC objects being compared.
       ; Output: when they are in wrong order, this procedure performs their swap and returns CF=1. EAX,EDX are clobbered.
       ; Called back by Member update and by PfOutput.
       MOV EDX,[EDI+RELOC.OrgHigh]
       CMP EDX,[ESI+RELOC.OrgHigh]
       JA .OK:                                   ; Return with CF=0.
       JB .Swap:
       MOV EAX,[EDI+RELOC.OrgLow]
       CMP EAX,[ESI+RELOC.OrgLow]
       JAE .OK:                                  ; Return with CF=0.
 .Swap:MOV EDX,MemberUpdate.TempReloc
       CopyTo EDX,ESI,Size=SIZE#RELOC
       CopyTo ESI,EDI,Size=SIZE#RELOC
       CopyTo EDI,EDX,Size=SIZE#RELOC
       STC                                       ; Return with CF=1.
 .OK:  RET
      ENDP1 SortByOrg::
.99: EndProcedure MemberUpdate
 ENDPROGRAM member

▲Back to the top▲