EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

pfcoff.htm
Structures
PFCOFF_FILE_HEADER
PFCOFF_RELOCATION
PFCOFF_SECTION_HEADER
PFCOFF_SYMBOL
Encodings
PFCOFF_encodings
Data
PfcoffStub
Procedures
PfcoffCompile
PfcoffFileHeader
PfcoffLoadModule
PfcoffLoadPgm
PfcoffRelocation2Reloc
PfcoffSegmCreate
PfcoffSegmRawData
PfcoffSectHeaders
PfcoffStreamReloc
PfcoffSymFile
PfcoffSymSegment
PfcoffSymSymbol
PfcoffSymTable

This source PF generates EuroAssembler output object file in program format COFF, as specified in [MS_PECOFF].


       EUROASM NOWARN=2101,NOWARN=2102
pfcoff 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,     \
pf.htm,      \
pfpe.htm,    \
pgm.htm,     \
pgmopt.htm,  \
reloc.htm,   \
sss.htm,     \
stm.htm,     \
sym.htm,     \
syswin.htm,  \
;;
 pfcoff HEAD ; Start module interface.
↑ PFCOFF_FILE_HEADER
COFF file header used in both object and image file.
PFCOFF_FILE_HEADER STRUC
.Machine              D WORD  ; See PFCOFF_encodings below.
.NumberOfSections     D WORD  ; How many PFCOFF_SECTION_HEADER objects follow the file header.
.TimeDateStamp        D DWORD ; Seconds since 1.1.1970 UTC till the link time.
.PointerToSymbolTable D DWORD ; File offset of COFF symbol table, or 0 if the table is omitted.
.NumberOfSymbols      D DWORD ; How many PFCOFF_SYMBOL objects there are in symbol table.
.SizeOfOptionalHeader D WORD  ; Size of PFPE_OPTIONAL_HEADER32 object including .DataDirectory.
.Characteristics      D WORD  ; See PFCOFF_encodings below.
 ENDSTRUC PFCOFF_FILE_HEADER  ; SIZE# PFCOFF_FILE_HEADER=14h=20
↑ PFCOFF_SECTION_HEADER
COFF section header.
PFCOFF_SECTION_HEADER STRUC
.Name                 D 8*BYTE  ; Section name, NULL padded but not always NULL terminated. Or /123 (offset in string table).
.VirtualSize          D DWORD   ; Aligned section size (PE|DLL]. 0 in object files (COFF).
.VirtualAddress       D DWORD   ; RVA of section relative to ImageBase when loaded in memory. 0 in object files.
.SizeOfRawData        D DWORD   ; Rounded up by FileAlignment in PE|DLL. 0 in BSS sections.
.PointerToRawData     D DWORD   ; File pointer to section data. Rounded up to FileAlignment in executables. 0 in BSS.
.PointerToRelocations D DWORD   ; File pointer to relocation entries for this section. 0 if no relocations.
.PointerToLinenumbers D DWORD   ; File pointer to line-number entries for this section. 0 if no line numbers.
.NumberOfRelocations  D WORD    ; Number of relocation entries for this section.
.NumberOfLinenumbers  D WORD    ; Number of line-number entries for this section. Not supported by €ASM.
.Characteristics      D DWORD   ; See PFCOFF_encodings below.
 ENDSTRUC PFCOFF_SECTION_HEADER ; SIZE# PFCOFF_SECTION_HEADER=28h=40
↑ PFCOFF_RELOCATION

PFCOFF_RELOCATION is a 10 byte structure of objects which are stored in the table immediately following raw data in each section of COFF object file, independed of module width.

Assignment of the .Type member of PFCOFF_RELOCATION depends on the architecture, which is selected in €ASM by PFCOFF_FILE_HEADER.Machine, which is selected by the width of COFF module file:

.Type when .Machine = 0x014C (I386 16|32bit)
.Type valueMS SDK nomenclatureRemark€ASM RELOC.Type
0x0000IMAGE_REL_I386_ABSOLUTE Reference is absolute, no relocation is necessaryrelocResolved
0x0001IMAGE_REL_I386_DIR16 Direct 16-bit reference to the symbols virtual addressrelocAbsVA + relocWidth16
0x0002IMAGE_REL_I386_REL16 IP-relative 16-bit reference to the symbols virtual addressrelocRel + relocWidth16
0x0006IMAGE_REL_I386_DIR32 Direct 32-bit reference to the symbols virtual address relocAbsVA + relocWidth32
0x0007IMAGE_REL_I386_DIR32NB Direct 32-bit reference to the symbols virtual address, base not included relocAbsRVA + relocWidth32
0x0009IMAGE_REL_I386_SEG12 Direct 16-bit reference to the segment-selector bits of a 32-bit virtual addressrelocPara + relocWidth16
0x000AIMAGE_REL_I386_SECTION The 16-bit section index of the section that contains the target. This is used to support debugging information.not supported
0x000BIMAGE_REL_I386_SECREL The 32-bit offset of the target from the beginning of its section. This is used to support debugging information and static thread local storage. not supported
0x000CIMAGE_REL_I386_TOKEN CLR tokennot supported
0x000DIMAGE_REL_I386_SECREL7 7 bit offset from base of section containing targetnot supported
0x0014IMAGE_REL_I386_REL32 EIP-relative 32-bit reference to the symbols virtual address relocRel + relocWidth32
.Type when .Machine = 0x8664 (AMD64 64bit)
.Type valueMS SDK nomenclatureRemark€ASM RELOC.Type
0x0000IMAGE_REL_AMD64_ABSOLUTEReference is absolute, no relocation is necessaryrelocResolved
0x0001IMAGE_REL_AMD64_ADDR64 The 64-bit VA of the relocation target. relocAbsVA + relocWidth64
0x0002IMAGE_REL_AMD64_ADDR32 The 32-bit VA of the relocation target. relocAbsVA + relocWidth32
0x0003IMAGE_REL_AMD64_ADDR32NBThe 32-bit address without an image base (RVA). relocAbsRVA + relocWidth32
0x0004IMAGE_REL_AMD64_REL32 The 32-bit relative address from the byte following the relocation. relocRel + relocWidth32
0x0005IMAGE_REL_AMD64_REL32_1 The 32-bit address RIP-relative to byte distance 1 from the relocation. relocRel + relocWidth32 + 1<<12
0x0006IMAGE_REL_AMD64_REL32_2 The 32-bit address RIP-relative to byte distance 2 from the relocation. relocRel + relocWidth32 + 2<<12
0x0007IMAGE_REL_AMD64_REL32_3 The 32-bit address RIP-relative to byte distance 3 from the relocation. relocRel + relocWidth32 + 3<<12
0x0008IMAGE_REL_AMD64_REL32_4 The 32-bit address RIP-relative to byte distance 4 from the relocation. relocRel + relocWidth32 + 4<<12
0x0009IMAGE_REL_AMD64_REL32_5 The 32-bit address RIP-relative to byte distance 5 from the relocation. relocRel + relocWidth32 + 5<<12
0x000AIMAGE_REL_AMD64_SECTION The 16-bit section index of the section that contains the target. This is used to support debugging information.not supported
0x000BIMAGE_REL_AMD64_SECREL The 32-bit offset of the target from the beginning of its section. This is used to support debugging information and static thread local storage.not supported
0x000CIMAGE_REL_AMD64_SECREL7 A 7-bit unsigned offset from the base of the section that contains the target.not supported
0x000DIMAGE_REL_AMD64_TOKEN CLR tokens. not supported
0x000EIMAGE_REL_AMD64_SREL32 A 32-bit signed span-dependent value emitted into the object.not supported
0x000FIMAGE_REL_AMD64_PAIR A pair that must immediately follow every span-dependent value.not supported
0x0010IMAGE_REL_AMD64_SSPAN32 A 32-bit signed span-dependent value that is applied at link time.not supported

Documentation
[COFFRelocTypes]
See also
RELOC used internally by €ASM, and PFPE_BASERELOC used for base relocations in PE and DLL executables.
PFCOFF_RELOCATION STRUC
.VirtualAddress   D DWORD   ; RVA of relocated word/dword/qword in emitted code.
.SymbolTableIndex D DWORD   ; Zero-based index of PFCOFF_SYMBOL in the symbol table.
.Type             D  WORD   ; See the table above.
 ENDSTRUC PFCOFF_RELOCATION ; SIZE# PFCOFF_RELOCATION=0Ah=10
↑ PFCOFF_LINENUMBER
COFF structure describing the relationship between RVA and source physical line. Deprecated.
PFCOFF_LINENUMBER STRUC
.VirtualAddress   D 0*DWORD ; RVA related to the .LineNumber if .LineNumber > 0. Unioned with .SymbolTableIndex.
.SymbolTableIndex D DWORD   ; Zero-based index of PFCOFF_SYMBOL in the symbol table.
.Linenumber       D  WORD   ; Physical line number if nonzero, otherwise .SymbolTableIndex is used.
 ENDSTRUC PFCOFF_LINENUMBER ; SIZE# PFCOFF_LINENUMBER=6
↑ PFCOFF_SYMBOL
COFF symbol structure.
PFCOFF_SYMBOL STRUC
.Name               D 8*BYTE; Alias DD 0,OffsetIntoStringTable if the namesize is longer than 8.
.Value              D DWORD ; Relocatable address or scalar value of the symbol.
.SectionNumber      D WORD  ; 1-based index to the table of IMAGE_SECTION_HEADERs or spec.constant in PFCOFF_encodings.
.Type               D WORD  ; See PFCOFF_encodings below.
.StorageClass       D BYTE  ; See PFCOFF_encodings below.
.NumberOfAuxSymbols D BYTE  ; Number of auxiliary symbol table entries that follow this record.
 ENDSTRUC PFCOFF_SYMBOL     ; SIZE# PFCOFF_SYMBOL=12h=18
↑ PFCOFF_encodings
Following symbolic encodings was adopted from Win32 SDK WINNT.h.
; PFCOFF_SECTION_HEADER.Characteristics:
pfcoffSCN_CNT_CODE                =  0x0000_0020  ; Section contains code.
pfcoffSCN_CNT_INITIALIZED_DATA    =  0x0000_0040  ; Section contains initialized data.
pfcoffSCN_CNT_UNINITIALIZED_DATA  =  0x0000_0080  ; Section contains uninitialized data.
pfcoffSCN_PurposeMask             =  0x0000_00E0
pfcoffSCN_LNK_INFO                =  0x0000_0200  ; Section contains comments or some other type of information.
pfcoffSCN_LNK_REMOVE              =  0x0000_0800  ; Section contents will not become part of image.
pfcoffSCN_LNK_COMDAT              =  0x0000_1000  ; Section contents COMDAT data.
pfcoffSCN_GPREL                   =  0x0000_8000  ; Section content can be accessed relative to global pointer.
pfcoffSCN_MEM_PURGEABLE           =  0x0002_0000  ; Reserved.
pfcoffSCN_ALIGN_1BYTES            =  0x0010_0000  ; Section alignment is BYTE.  Valid only for object files.
pfcoffSCN_ALIGN_2BYTES            =  0x0020_0000  ; Section alignment is WORD.  Valid only for object files.
pfcoffSCN_ALIGN_4BYTES            =  0x0030_0000  ; Section alignment is DWORD. Valid only for object files.
pfcoffSCN_ALIGN_8BYTES            =  0x0040_0000  ; Section alignment is QWORD. Valid only for object files.
pfcoffSCN_ALIGN_16BYTES           =  0x0050_0000  ; Section alignment is OWORD. Valid only for object files. Default.
pfcoffSCN_ALIGN_32BYTES           =  0x0060_0000  ; Section alignment is YWORD. Valid only for object files.
pfcoffSCN_ALIGN_64BYTES           =  0x0070_0000  ; Section alignment is ZWORD. Valid only for object files.
pfcoffSCN_ALIGN_128BYTES          =  0x0080_0000  ; Section alignment is 128.   Valid only for object files.
pfcoffSCN_ALIGN_256BYTES          =  0x0090_0000  ; Section alignment is 256.   Valid only for object files.
pfcoffSCN_ALIGN_512BYTES          =  0x00A0_0000  ; Section alignment is 512.   Valid only for object files.
pfcoffSCN_ALIGN_1024BYTES         =  0x00B0_0000  ; Section alignment is 1K.    Valid only for object files.
pfcoffSCN_ALIGN_2048BYTES         =  0x00C0_0000  ; Section alignment is 2K.    Valid only for object files.
pfcoffSCN_ALIGN_4096BYTES         =  0x00D0_0000  ; Section alignment is 4K.    Valid only for object files.
pfcoffSCN_ALIGN_8192BYTES         =  0x00E0_0000  ; Section alignment is 8K.    Valid only for object files.
pfcoffSCN_ALIGN_MASK              =  0x00F0_0000  ; Mask for section alignment.
pfcoffSCN_LNK_NRELOC_OVFL         =  0x0100_0000  ; Section contains extended relocations.
pfcoffSCN_MEM_DISCARDABLE         =  0x0200_0000  ; Section can be discarded.
pfcoffSCN_MEM_NOT_CACHED          =  0x0400_0000  ; Section is not cacheable.
pfcoffSCN_MEM_NOT_PAGED           =  0x0800_0000  ; Section is not pageable.
pfcoffSCN_MEM_SHARED              =  0x1000_0000  ; Section is shareable.
pfcoffSCN_MEM_EXECUTE             =  0x2000_0000  ; Section is executable.
pfcoffSCN_MEM_READ                =  0x4000_0000  ; Section is readable.
pfcoffSCN_MEM_WRITE               =  0x8000_0000  ; Section is writeable.
pfcoffSCN_AccessMask              =  0xE000_0000

; PFCOFF_FILE_HEADER. Machine CPU values:
pfcoffFILE_MACHINE_UNKNOWN         =  0x0000  ; Applicable to any machine type.
pfcoffFILE_MACHINE_I386            =  0x014C  ; Intel 386. Default for 16|32bit modules, regardless on CPU=.
pfcoffFILE_MACHINE_I486            =  0x014D  ; Intel 486.
pfcoffFILE_MACHINE_I586            =  0x014E  ; Intel Pentium.
pfcoffFILE_MACHINE_IA64            =  0x0200  ; Intel Itanium (64bit).
pfcoffFILE_MACHINE_AMD64           =  0x8664  ; AMD 64bit. Default for 64bit modules.

; PFCOFF_FILE_HEADER.Characteristics flags:
pfcoffFILE_RELOCS_STRIPPED         =  0x0001  ; Relocation info stripped from file.
pfcoffFILE_EXECUTABLE_IMAGE        =  0x0002  ; File is executable  (i.e. no unresolved external references).
pfcoffFILE_LINE_NUMS_STRIPPED      =  0x0004  ; Line numbers stripped from file.
pfcoffFILE_LOCAL_SYMS_STRIPPED     =  0x0008  ; Local symbols stripped from file.
pfcoffFILE_AGGRESIVE_WS_TRIM       =  0x0010  ; Agressively trim working set (obsolete).
pfcoffFILE_LARGE_ADDRESS_AWARE     =  0x0020  ; Application can handle more than 2GB addresses - 64bit module.
;                                  =  0x0040  ; Reserved.
pfcoffFILE_BYTES_REVERSED_LO       =  0x0080  ; Bytes of machine word are reversed (deprecated).
pfcoffFILE_32BIT_MACHINE           =  0x0100  ; 32 bit architecture. Reset in 16bit COFF.
pfcoffFILE_DEBUG_STRIPPED          =  0x0200  ; Debugging info stripped from image file into .DBG file.
pfcoffFILE_REMOVABLE_RUN_FROM_SWAP =  0x0400  ; If image is on removable media, copy and run from the swap file.
pfcoffFILE_NET_RUN_FROM_SWAP       =  0x0800  ; If image is on network, copy and run from the swap file.
pfcoffFILE_SYSTEM                  =  0x1000  ; Image is a system file rather than user program.
pfcoffFILE_DLL                     =  0x2000  ; File is a DLL.
pfcoffFILE_UP_SYSTEM_ONLY          =  0x4000  ; File should only be run on a uniprocessor machine
pfcoffFILE_BYTES_REVERSED_HI       =  0x8000  ; Bytes of machine word are reversed (deprecated).

; PFCOFF_SYMBOL.SectionNumber special constants:
pfcoffSYM_UNDEFINED =  0 ; Symbol is undefined or it is common.
pfcoffSYM_ABSOLUTE  = -1 ; Symbol is an absolute value (scalar).
pfcoffSYM_DEBUG     = -2 ; Symbol is a special debug item.

; PFCOFF_SYMBOL.StorageClass constants:
pfcoffSYM_CLASS_EXTERNAL   = 2   ; External or public symbol.
pfcoffSYM_CLASS_STATIC     = 3   ; Standard private symbol or segment.
pfcoffSYM_CLASS_FILE       = 103 ; Source filename symbol.
pfcoffSYM_CLASS_SECTION    = 104 ; Definition of section (MSCOFF uses pfcoffSYM_CLASS_STATIC instead).

; PFCOFF_SYMBOL.Type is reduced to EuroAssembler's limited set of fundamental datatypes:
; LSB Type specifies the width and type of the symbol.
pfcoffSYM_TYPE_NULL       = 0x00 ; No type information.
pfcoffSYM_TYPE_VOID       = 0x01 ; No valid type.
pfcoffSYM_TYPE_CHAR       = 0x02 ; BYTE.
pfcoffSYM_TYPE_SHORT      = 0x03 ; WORD.
pfcoffSYM_TYPE_INT        = 0x04 ; DWORD or QWORD (32bit or 64bit program).
pfcoffSYM_TYPE_LONG       = 0x05 ; DWORD.
pfcoffSYM_TYPE_FLOAT      = 0x06 ; DWORD.
pfcoffSYM_TYPE_DOUBLE     = 0x07 ; QWORD.
pfcoffSYM_TYPE_BYTE       = 0x0C ; BYTE.
pfcoffSYM_TYPE_WORD       = 0x0D ; WORD.
pfcoffSYM_TYPE_UINT       = 0x0E ; DWORD or QWORD (32bit or 64bit program).
pfcoffSYM_TYPE_DWORD      = 0x0F ; DWORD.
pfcoffSYM_TYPE_LONGDOUBLE = 0x10 ; TBYTE.
; MSB Type specifies complex type of symbol.
pfcoffSYM_DTYPE_NULL      = 0x00 ; No derived type.
pfcoffSYM_DTYPE_POINTER   = 0x01 ; Pointer to base type.
pfcoffSYM_DTYPE_FUNCTION  = 0x02 ; Procedure or function.
pfcoffSYM_DTYPE_ARRAY     = 0x03 ; Structure.
 ENDHEAD pfcoff  ; End of module interface.
↑ PfcoffSymFile File, SymbolTableBuffer
PfcoffSymFile creates and stores one PFCOFF_SYMBOL record into SymbolTableBuffer with name .file and one or more auxiliary records with the actual filename.
Input
File Pointer to FILE object with assigned name of source file.
SymbolTableBuffer Pointer to output BUFFER , allocated by caller, where PFCOFF_SYMBOL records will be stored.
Output
Symbol records stored to buffer.
Error
CF=1 Errors are reported with macro Msg.
See also
PfcoffSymSymbol, PfcoffSymSegment.
Invoked by
PfcoffSymTable PfpeCompile
PfcoffSymFile Procedure File, SymbolTableBuffer
SymPtr LocalVar
    MOV EBX,[%SymbolTableBuffer]
    BufferNew EBX, SIZE# PFCOFF_SYMBOL, Zeroed=Yes             ; Base record.
    JC .90:
    MOV [%SymPtr],EAX
    MOV EDI,EAX
    MOVB [EDI+PFCOFF_SYMBOL.StorageClass],pfcoffSYM_CLASS_FILE ; 103=0x67
    MOVW [EDI+PFCOFF_SYMBOL.SectionNumber],pfcoffSYM_DEBUG     ; -2=0xFFFE
    MOV EAX,".fil"
    MOV [EDI+PFCOFF_SYMBOL.Name+0],EAX
    MOV AL,"e"
    MOV [EDI+PFCOFF_SYMBOL.Name+4],AL
    MOV ESI,[%File]
    LEA EDX,[ESI+FILE.Name]
.20:BufferNew EBX, SIZE# PFCOFF_SYMBOL, Zeroed=Yes             ; Auxilliary record.
    JC .90:
    MOV ESI,[%SymPtr]                            ; ESI now points to the base record.
    INCB [ESI+PFCOFF_SYMBOL.NumberOfAuxSymbols]
    MOV EDI,EAX                                  ; EDI now points to the auxilliary record.
    MOV ESI,EDX                                  ; ESI now points to the unstored part of file name.
    MOV ECX,SIZE# PFCOFF_SYMBOL
.30:LODSB
    CMP AL,0
    JZ .90:
    STOSB
    LOOP .30:                                    ; Copy file name to auxilliary record(s).
    MOV EDX,ESI
    JMP .20:
.90:EndProcedure PfcoffSymFile
↑ PfcoffSymSegment Symbol, SymbolTableBuffer, StringTableBuffer
PfcoffSymSegment creates and stores one PFCOFF_SYMBOL record into SymbolTableBuffer with StorageClass=SYM_CLASS_STATIC, and one auxiliary record with netto segment size and with the number of relocations.
NameIndex of the symbol associated with Segment is updated.
Input
Symbol Pointer to SYM object type symSe (symbol associated with COFF section).
SymbolTableBuffer Pointer to output BUFFER where to store PFCOFF_SYMBOL records.
StringTableBuffer Pointer to output BUFFER where segment name longer than 8 can be stored.
Output
Two records are stored to SymbolTableBuffer.
Error
CF=1 Errors are reported with macro Msg.
See also
PfcoffSymSymbol, PfcoffSymFile.
Invoked by
PfcoffSymTable PfpeCompile
PfcoffSymSegment Procedure Symbol, SymbolTableBuffer, StringTableBuffer
      ; Update input Symbol.NameIndex.
      BufferRetrieve [%SymbolTableBuffer]
      MOV EAX,ECX                                ; PFCOFF_SYMBOL records used so far = index in COFF symbol table.
      SUB EDX,EDX
      MOV ECX, SIZE# PFCOFF_SYMBOL               ; 18.
      DIV ECX
      MOV EDX,[%Symbol]                          ; EDX=^SYM.
      MOV ECX,[EDX+SYM.Section]
      JNSt [ECX+SSS.Status],sssSegment,.90:      ; If Symbol represents a group, ignore (COFF doesn't support groups).
      MOV [EDX+SYM.NameIndex],EAX
      ; Create new PFCOFF_SYMBOL.
      BufferNew [%SymbolTableBuffer], SIZE# PFCOFF_SYMBOL, Zeroed=Yes
      JC .90:
      MOV EBX,EAX                                ; EBX=^PFCOFF_SYMBOL.
      ; PFCOFF_SYMBOL.Name.
      MOV ECX,[EDX+SYM.NameSize]
      MOV ESI,[EDX+SYM.NamePtr]
      LEA EDI,[EBX+PFCOFF_SYMBOL.Name]
      CMP ECX,8
      JA .10:
      REP MOVSB                                  ; Symbol name is short.
      JMPS .20:
 .10: MOV EAX,[%StringTableBuffer]               ; Symbol name is long.
      PUSH ECX,ESI
        BufferRetrieve EAX
        MOV [EBX+PFCOFF_SYMBOL.Name+4],ECX
      POP ESI,ECX
      BufferStore EAX,ESI,ECX
      BufferStoreByte EAX,0
.20:  ; PFCOFF_SYMBOL.SectionNumber.
      MOV EDX,[EDX+SYM.Section]                  ; EDX=^SSS.
      MOV EAX,[EDX+SSS.SegmIndex]
      MOV [EBX+PFCOFF_SYMBOL.SectionNumber],EAX
      ; PFCOFF_SYMBOL.StorageClass.
      MOVB [EBX+PFCOFF_SYMBOL.StorageClass],pfcoffSYM_CLASS_STATIC ; 3.
      ; PFCOFF_SYMBOL auxilliary record Format 5.
      MOVB [EBX+PFCOFF_SYMBOL.NumberOfAuxSymbols],1
      BufferNew [%SymbolTableBuffer], SIZE# PFCOFF_SYMBOL, Zeroed=Yes
      MOV EBX,EAX
      BufferRetrieve [EDX+SSS.EmitBuffer]
      MOV [EBX+0],ECX
      BufferRetrieve [EDX+SSS.RelocBuffer]
      MOV EAX,ECX
      SUB EDX,EDX
      MOV ECX, SIZE# RELOC
      DIV ECX
      MOV ECX,0xFFFF
      CMP EAX,ECX
      JNA .30:
      XCHG EAX,ECX
.30:  MOV [EBX+4],AX
.90:EndProcedure PfcoffSymSegment
↑ PfcoffSymSymbol Symbol, SymbolTableBuffer, StringTableBuffer
PfcoffSymSymbol creates and stores one PFCOFF_SYMBOL record into SymbolTableBuffer with symbol name.
Its index is stored to input Symbol.NameIndex.
Input
Symbol Pointer to SYM object.
SymbolTableBuffer Pointer to output BUFFER where PFCOFF_SYMBOL record will be stored.
StringTableBuffer Pointer to output BUFFER where symbol name longer than 8 bytes will be stored.
Output
Symbol record stored to buffer, its .NameIndex updated.
Error
CF=1 Errors are reported with macro Msg.
See also
PfcoffSymSegment, PfcoffSymFile.
Invoked by
PfcoffSymTable PfpeCompile
PfcoffSymSymbol Procedure Symbol, SymbolTableBuffer, StringTableBuffer
    ; Update input Symbol.NameIndex.
    BufferRetrieve [%SymbolTableBuffer]
    MOV EAX,ECX                                  ; Number of PFCOFF_SYMBOL records used so far = index in COFF symbol table.
    SUB EDX,EDX
    MOV ECX, SIZE# PFCOFF_SYMBOL                 ; 18.
    DIV ECX
    MOV EDX,[%Symbol]                            ; EDX=^SYM.
    MOV [EDX+SYM.NameIndex],EAX                  ; Update SYM.NameIndex of the input symbol EDX.
    ; Create new PFCOFF_SYMBOL.
    BufferNew [%SymbolTableBuffer],ECX,Zeroed=Yes; Allocate 18 bytes of memory.
    JC .90:
    MOV EBX,EAX                                  ; EBX=^PFCOFF_SYMBOL.
    ; PFCOFF_SYMBOL.Name.
    MOV ECX,[EDX+SYM.NameSize]
    MOV ESI,[EDX+SYM.NamePtr]
    LEA EDI,[EBX+PFCOFF_SYMBOL.Name]
    CMP ECX,8
    JA .10:
    REP MOVSB                                    ; Symbol name is short.
    JMPS .20:
.10:MOV EAX,[%StringTableBuffer]                 ; Symbol name is long.
    PUSH ECX,ESI
      BufferRetrieve EAX
      MOV [EBX+PFCOFF_SYMBOL.Name+4],ECX         ; Relative address of long name.
    POP ESI,ECX
    BufferStore EAX,ESI,ECX                      ; Store long name.
    BufferStoreByte EAX,0                        ; Zero-terminate the name.
.20:; PFCOFF_SYMBOL.Value.
    MOV EAX,[EDX+SYM.OffsetLow]
    MOV [EBX+PFCOFF_SYMBOL.Value],EAX
    ; PFCOFF_SYMBOL.SectionNumber.
    MOV AX,pfcoffSYM_UNDEFINED                   ; AX=0, assume external symbol.
    JSt [EDX+SYM.Status],symExtern | symImport, .30:
    MOV ECX,[EDX+SYM.Section]
    MOV AX,pfcoffSYM_ABSOLUTE                    ; AX=-1, assume scalar symbol.
    JECXZ .30:                                   ; If symbol's segment is empty.
    MOV EAX,[ECX+SSS.SegmIndex]                  ; AX=ordinal number of symbols segment.
.30:MOV [EBX+PFCOFF_SYMBOL.SectionNumber],AX
    ; PFCOFF_SYMBOL.StorageClass.
    MOV AL,pfcoffSYM_CLASS_EXTERNAL              ; AL=2, assume global symbol.
    JSt [EDX+SYM.Status],symExtern | symPublic | symExport | symImport,.40:
    MOV AL,pfcoffSYM_CLASS_STATIC                ; AL=3, otherwise it is standard private local symbol.
.40:MOV [EBX+PFCOFF_SYMBOL.StorageClass],AL
    ; Symbol.Type.
    MOV EAX,[EDX+SYM.Status]
    MOV CX,pfcoffSYM_DTYPE_FUNCTION <<8 + pfcoffSYM_TYPE_VOID      ; >> 0x2001
    JSt EAX,symProc,.50:           ; If the symbol EDX is PROC (procedure/function name).
    Dispatch AL,'A','B','U','W','D','Q','T'
    MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_NULL       ; >> 0x0000 default to unknown type.
    JMPS .50:
.B: MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_BYTE       ; >> 0x000C
    JMPS .50:
.U:
.W: MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_WORD       ; >> 0x000D
    JMPS .50:
.D: MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_DWORD      ; >> 0x000F
    JMPS .50:
.Q: MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_UINT       ; >> 0x000E
    JMPS .50:
.T: MOV CX,pfcoffSYM_DTYPE_NULL    <<8 + pfcoffSYM_TYPE_LONGDOUBLE ; >> 0x0010
    JMPS .50:
.A: MOV CX,pfcoffSYM_DTYPE_POINTER <<8 + pfcoffSYM_TYPE_VOID       ; >> 0x0101
.50:MOV [EBX+PFCOFF_SYMBOL.Type],CX
.90:EndProcedure PfcoffSymSymbol
↑ PfcoffStub
Data between PfcoffStub..PfcoffStubEnd represent compiled 16bit SMALL MZ program, built in euroasm.exe file. It reports a message This program was launched in DOS but it requires Windows.
coffstub.exe was created from the source coffstub.htm , it is used as the default stub when the program option STUBFILE= is empty or when it specifies nonexisting or damaged file.
[.data]
PfcoffStub::
   INCLUDEBIN "../objlib/coffstub.exe"
PfcoffStubEnd::
[.text]
↑ PfcoffFileHeader FileHeader, PgmPtr
PfcoffFileHeader will initizalize COFF file header structure and set those members which can be derived from program specified with PgmPtr at the moment of COFF construction.
Input
FileHeader Pointer to PFCOFF_FILE_HEADER object, allocated by the caller.
PgmPtr Pointer to PGM from which is the COFF file compiled.
Output
Following members of FileHeader are filled: .Machine, .TimeDateStamp, .SizeOfOptionalHeader, .Characteristics . Other members are zeroed.
Error
CF=1 Errors are reported with macro Msg.
Invoked by
PfcoffCompile PfpeCompile
PfcoffFileHeader Procedure FileHeader,PgmPtr
    MOV EDI,[%FileHeader]
    MOV EBX,[%PgmPtr]
    Clear EDI,Size=SIZE#PFCOFF_FILE_HEADER
    MOV EAX,[EBX+PGM.Pgmopt.Status]
    JSt EAX,pgmoptWidthMask,.40:
    ; Program width is not specified.
    ListGetFirst [EBX+PGM.SssList]
    JZ .40:
.20:JNSt [EAX+SSS.Status],sssSegment,.30:
    JNSt [EAX+SSS.Purpose],sssPurposeRegular,.30:
    MOV EAX,[EAX+SSS.Status]
    AND EAX,sssWidthMask                     ; Identical with pgmoptWidthMask.
    JMPS .40:
.30:ListGetNext EAX
    JNZ .20:
.40: ; Assume 64bit.
    MOV ECX,pfcoffFILE_MACHINE_AMD64         ; PFCOFF_FILE_HEADER.Machine.
    MOV ESI,SIZE# PFPE_OPTIONAL_HEADER64     ; PFCOFF_FILE_HEADER.SizeOfOptionalHeader.
    MOV EDX,pfcoffFILE_LARGE_ADDRESS_AWARE   ; PFCOFF_FILE_HEADER.Characteristics.
    JSt EAX,pgmoptWidth64,.70:               ; Otherwise assume 32bit.
    MOV ECX,pfcoffFILE_MACHINE_I386          ; PFCOFF_FILE_HEADER.Machine.
    MOV ESI,SIZE# PFPE_OPTIONAL_HEADER32       ; PFCOFF_FILE_HEADER.SizeOfOptionalHeader.
    XOR EDX,EDX                              ; PFCOFF_FILE_HEADER.Characteristics.
    JSt EAX,pgmoptWidth16,.70:
    MOV EDX,pfcoffFILE_32BIT_MACHINE
.70:MOV [EDI+PFCOFF_FILE_HEADER.Machine],CX
    Dispatch AL,pgmoptPE,pgmoptDLL
    JMPS .80:                                ; SizeOfOptionalHeader in nonexecutables is left at 0.
.pgmoptDLL: OR EDX,pfcoffFILE_EXECUTABLE_IMAGE + pfcoffFILE_DLL
.pgmoptPE:  OR EDX,pfcoffFILE_EXECUTABLE_IMAGE
    MOV [EDI+PFCOFF_FILE_HEADER.SizeOfOptionalHeader],ESI
.80:MOV [EDI+PFCOFF_FILE_HEADER.Characteristics],DX
    MOV ECX,[Ea.Eaopt.TimeStamp::]
    MOV [EDI+PFCOFF_FILE_HEADER.TimeDateStamp],ECX
   EndProcedure PfcoffFileHeader
↑ PfcoffSegmCreate Segment, Program, SectionHeaderBuffer, FileHeader
PfcoffSegmCreate creates an empty SectionHeader in SectionHeaderBuffer.
Input
Segment is pointer to SSS whose data are processed.
Program is pointer to current PGM.
SectionHeaderBuffer is pointer to a BUFFER where the coresponding PFCOFF_SECTION_HEADER record will be stored.
FileHeader is pointer to PFCOFF_FILE_HEADER whose member .NumberOfSections will be incremented. This incremented section ordinal will be also written to SSS.SegmIndex of the Segment.
Output
%Segment.SegmIndex, %FileHeader.NumberOfSections and all buffers are updated.
Error
CF=1 Errors are reported with macro Msg.
Invoked by
PfpeCompile
PfcoffSegmCreate Procedure Segment, Program, SectionHeaderBuffer, FileHeader
    MOV EBX,[%FileHeader]
    MOV ESI,[%Segment]
    MOVZXW EDX,[EBX+PFCOFF_FILE_HEADER.NumberOfSections]
    INC EDX                                      ; One-based section number.
    MOV [ESI+SSS.SegmIndex],EDX
    TEST EDX,0xFFFF_0000
    Msg '7913',cc=NZ                             ; Number of COFF sections (segments) exceeded 65_535.
    MOV [EBX+PFCOFF_FILE_HEADER.NumberOfSections],DX
    BufferNew [%SectionHeaderBuffer],SIZE#PFCOFF_SECTION_HEADER
    MOV EDI,EAX
    SUB EAX,EAX
    MOV ECX,SIZE#PFCOFF_SECTION_HEADER / 4
    REP STOSD                                    ; Clear the new section header.
   EndProcedure PfcoffSegmCreate
↑ PfcoffLoadPgm BasePgm, ObjBegin, ObjSize, FileNamePtr

PfcoffLoadPgm reads the contents of one COFF object file and converts it to structures of a fresh new program, which then will be stored on BasePgm.ModulePgmList.

Input
BasePgm is pointer to an existing PGM to which the object file is being linked/imported.
ObjBegin is pointer to the contents of COFF object mapped in memory by the caller. It must start with PFCOFF_FILE_HEADER
ObjSize is number of bytes in the COFF object.
FileNamePtr is pointer to zero-terminated object file name (used in error reports).
Output
Loaded program is stored on BasePgm.ModulePgmList as a new PGM structure.
Error
Error E7766 reported with macro Msg.
Invoked from
PfLoad
Invokes
EaBufferRelease EaBufferReserve EaFs2Id PfcoffLoadModule
PfcoffLoadPgm Procedure BasePgm, ObjBegin, ObjSize, FileNamePtr
    MOV EDI,[%FileNamePtr]
    GetLength$ EDI
    MOV EDX,ECX                                  ; EDI,ECX is file name string. Remove path.
    LEA ESI,[EDI+ECX-1]
    STD
.20:LODSB                                        ; Read the string backward.
    CMP AL,'\'
    JE .30:
    CMP AL,'/'
    JE .30:
    CMP AL,':'
    LOOPNE .20:
.30:CLD
    LEA ESI,[EDI+ECX]
    SUB EDX,ECX                                  ; ESI,EDX is now file name without path. Remove file extension (usually .obj).
    LEA EDI,[ESI+EDX]
.40:DEC EDI
    CMP EDI,ESI
    JNA .60:
    CMPB [EDI],'.'
    JNE .40:
.50:SUB EDI,ESI
    JNZ .70:
.60:MOV EDI,EDX                                  ; When the file name has no extension, use it as whole.
.70:; ESI,EDI is now file name without path and without extension, it will be used as the module name.
    Invoke EaBufferReserve::,PfcoffLoadPgm
    Invoke EaFs2Id::,ESI,EDI,EAX                 ; Replace nonalphanum with underscores.
    BufferRetrieve EAX
    Invoke EaBufferRelease::,EAX
    Invoke PfcoffLoadModule,[%BasePgm],[%ObjBegin],[%ObjSize],[%FileNamePtr],ESI,ECX,pgmoptCOFF
.90:EndProcedure PfcoffLoadPgm
↑ PfcoffLoadModule BaseProgram, ModBegin, ModSize, FileName$Ptr, ModNamePtr, ModNameSize, Format

PfcoffLoadModule reads the contents of one COFF object module and converts it to structures of a fresh new program, which then will be stored on BasePgm.ModulePgmList.
The object can be the whole contents of a separate file in COFF format, or it can be one member of object library in LIBCOF format.

Input
BaseProgram is pointer to an existing PGM to which the object file is being loaded.
ModBegin is pointer to the contents of COFF object mapped in memory by the caller. It must start with PFCOFF_FILE_HEADER.
ModSize is number of bytes in the module.
FileName$Ptr is pointer to zero-terminated file name (used in error reports).
ModNamePtr is pointer to module name which will be used as loaded program name. It may be volatile.
ModNameSize is number of characters in module name.
Format is either pgmoptCOFF or pgmoptLIBCOF.
Output
Loaded program is stored on BasePgm.ModulePgmList as a new PGM structure.
Error
E7766 reported with macro Msg.
Invoked by
PfcoffLoadPgm PflibcofLoadPgm
Invokes
PfDrectveDestroy PfcoffRelocation2Reloc PgmoptSetLinkProp SssCreateExtern SssCreateSe SssFindByIndex SssGuessPurpose
PfcoffLoadModule Procedure BaseProgram, ModBegin, ModSize, FileName$Ptr,ModNamePtr,ModNameSize,Format
ModEnd        LocalVar ; Pointer to the end of loaded file.
CoffScnBegin  LocalVar ; Pointer to the first section header in memory mapped file.
CoffScnPtr    LocalVar ; Pointer to the current section header in memory mapped file.
CoffScnEnd    LocalVar ; Pointer behind the last section header in memory mapped file.
CoffScnCount  LocalVar ; Number of PFCOFF_SECTION_HEADER records in the file.
CoffScnIndex  LocalVar ; Ordinal number of PFCOFF_SECTION_HEADER in COFF file (1,2,3..).
CoffSymPtr    LocalVar ; Pointer to the current PFCOFF_SYMBOL record in memory mapped file.
CoffSymCount  LocalVar ; Number of PFCOFF_SYMBOL records in the module.
CoffSymIndex  LocalVar ; 0-based ordinal number of PFCOFF_SYMBOL in COFF module (0,1,2,3..).
CoffSymAux    LocalVar ; Number of auxiliary symbols pending in PFCOFF_SYMBOL table.
CoffStrBegin  LocalVar ; Pointer to COFF string table in memory mapped file.
SssAlignment  LocalVar ; SSS.Alignment (power of 2).
LinkStm       LocalVar Size=SIZE#STM ; Temporary fake statement used in SssCreateSe.
    ClearLocalVar
    MOV EBX,[%BaseProgram]
    MOV EDX,[EBX+PGM.Pool]
    MOV EAX,[EBX+PGM.LinePtr]
    LEA EDI,[%LinkStm]
    MOV [EDI+STM.LinePtr],EAX
    ; Create loaded module. Simplified intialization inherits Pool from BaseProgram.
    ListNew [EBX+PGM.ModulePgmList],Zeroed=yes
    JC .90:
    MOV EBX,EAX                                  ; EBX is now the new module program.
    MOV [EDI+STM.Program],EBX
    MOV ESI,[%ModNamePtr]
    MOV ECX,[%ModNameSize]
    MOV [EBX+PGM.Pool],EDX
    PoolStore EDX,ESI,ECX                        ; Make the PGM.Name nonvolatile.
    MOV [EBX+PGM.NamePtr],EAX
    MOV [EBX+PGM.NameSize],ECX
    ListCreate EDX,SIZE# SSS
    MOV [EBX+PGM.SssList],EAX
    ListCreate EDX,SIZE# SYM
    MOV [EBX+PGM.SymList],EAX
    MOV ECX,[%Format]
    Invoke PgmoptSetLinkProp::,ECX               ; Get default properties for the module format (COFF|LIBCOF).
    AND EAX,pgmoptLinkPropMask
    CMP ECX,pgmoptLIBCOF
    JNE .F0:
    SetSt EAX,pgmoptLibMember
.F0:MOV [EBX+PGM.Pgmopt.Status],EAX
    MOV ESI,[%ModBegin]
    MOV ECX,[%ModSize]
    ADD ECX,ESI
    MOV [%ModEnd],ECX
    ; Retrieve information from COFF file header mapped at ESI.
    MOVZXW EDX,[ESI+PFCOFF_FILE_HEADER.Machine]  ; Try to specify the module width from COFF file header characteristics.
    MOVZXW EAX,[ESI+PFCOFF_FILE_HEADER.Characteristics]
    MOV ECX,pgmoptCOFF+pgmoptWidth64             ; Assume 64bit COFF.
    CMP DX,pfcoffFILE_MACHINE_AMD64
    JE .F1:
    CMP DX,pfcoffFILE_MACHINE_IA64
    JE .F1:
    MOV ECX,pgmoptCOFF+pgmoptWidth32             ; Assume 32bit COFF.
    JSt EAX,pfcoffFILE_32BIT_MACHINE,.F1:
    MOV ECX,pgmoptCOFF+pgmoptWidth16             ; Otherwise assume 16bit COFF.
.F1:SetSt [EBX+PGM.Pgmopt.Status],ECX            ; Store format and width of the loaded module. Model is unspecified.
    MOV EDX,[ESI+PFCOFF_FILE_HEADER.PointerToSymbolTable] ; File address.
    MOV ECX,[ESI+PFCOFF_FILE_HEADER.NumberOfSymbols]
    ADD EDX,[%ModBegin]                          ; Convert FA into pointer to symbol table in mapped memory.
    MOV [%CoffSymCount],ECX
    MOV [%CoffSymPtr],EDX
    MOV EAX,SIZE# PFCOFF_SYMBOL
    MUL ECX
    ADD EAX,[%CoffSymPtr]
    MOV [%CoffStrBegin],EAX                      ; Pointer to the string table following the symbol table.
    MOVZXW EDX,[ESI+PFCOFF_FILE_HEADER.SizeOfOptionalHeader]
    MOVZXW ECX,[ESI+PFCOFF_FILE_HEADER.NumberOfSections]
    LEA ESI,[ESI + SIZE# PFCOFF_FILE_HEADER + EDX]
    MOV [%CoffScnBegin],ESI                      ; ESI is pointer to the 1st COFF section header.
    MOV EAX,SIZE# PFCOFF_SECTION_HEADER
    MOV [%CoffScnCount],ECX
    SUB ESI,EAX
    MOV [%CoffScnPtr],ESI                        ; Pointer to the current-1 COFF section header in mapped memory.
    ADD ESI,EAX
    MUL ECX
    ADD EAX,ESI
    MOV [%CoffScnEnd],EAX
    CMP EAX,[%ModEnd]
    JNB .E7766:                                  ; Invalid format of COFF object file "!1S".
.G1:; Convert section headers to program segments in the loop .G1: .. .G9:.
    MOV ESI,[%CoffScnPtr]
    ADD ESI,SIZE# PFCOFF_SECTION_HEADER
    MOV [%CoffScnPtr],ESI                        ; ESI=^PFCOFF_SECTION_HEADER, EBX=^PGM of the loaded module.
    INCD [%CoffScnIndex]
    CMP ESI,[%CoffScnEnd]
    JNB .H1:                                     ; If there are no more section headers left to convert.
    MOV EDX,[ESI+PFCOFF_SECTION_HEADER.Characteristics]
    ; Find segment alignment.
    MOV EAX,1
    MOV ECX,pfcoffSCN_ALIGN_MASK
    AND ECX,EDX
    SHR ECX,20
    JZ .G2:
    DEC ECX
    SHL EAX,CL                                   ; Convert pfcoffSCN alignment to SSS.Alignment.
.G2:MOV [%SssAlignment],EAX
    ; Find segment properties (SSS.Status).
    MOV EDI,pgmoptWidthMask                      ; Width of the loaded segment is specified by module width.
    AND EDI,[EBX+PGM.Pgmopt.Status]              ; Encoding of pgmoptWidthMask is synchronized with sssWidthMask.
    OR EDI,sssSegment+sssPublic                  ; "Section" in MS terminology is "Segment" in €ASM.
    ; Find segment purpose from section characteristics in EDX.
    XOR EAX,EAX
    JNSt EDX,pfcoffSCN_CNT_CODE,.GC:
    JNSt EDX,pfcoffSCN_MEM_EXECUTE,.GC:
    OR EAX,sssPurposeCODE
.GC:JNSt EDX,pfcoffSCN_MEM_READ,.GS:
    JNSt EDX,pfcoffSCN_CNT_INITIALIZED_DATA,.GR:
    JNSt EDX,pfcoffSCN_MEM_WRITE,.GD:
    OR EAX,sssPurposeDATA
.GD:JSt EDX,pfcoffSCN_MEM_WRITE,.GR:
    OR EAX,sssPurposeRODATA
.GR:JNSt EDX,pfcoffSCN_CNT_UNINITIALIZED_DATA,.GS:
    JNSt EDX,pfcoffSCN_MEM_WRITE,.GS:
    OR EAX,sssPurposeBSS
.GS:XCHG EAX,EDX                                 ; EDX=SSS.Purpose.
    ; Find segment name.
    LEA ESI,[ESI+PFCOFF_SECTION_HEADER.Name]
    MOV ECX,8                                    ; At first assume short section name.
    CMPB [ESI],'/'                               ; Longnames are represented as "/123" (123 is offset in the string table).
    JNE .G7:                                     ; If segment name is short, it was stored in section header directly.
    INC ESI                                      ; Otherwise skip the slash.
    LodD ESI,Size=7                              ; Load decimal offset in the string table into EAX.
.G6:MOV ESI,[%CoffStrBegin]                      ; String table in mapped memory. At least 4 bytes long.
    CMP EAX,4
    JNA .E7766:                                  ; Invalid format of COFF object file "!1S".
    CMP EAX,[ESI]                                ; Dword at ESI is the size of string table.
    JNB .E7766:                                  ; Invalid format of COFF object file "!1S".
    ADD ESI,EAX
    GetLength$ ESI                               ; Segment name at ESI is a zero-terminated string. Get its length to ECX.
.G7:StripSpaces ESI,ECX                          ; Get rid of trailing NULL characters, if any.
    ; Create new segment in the loaded module. ESI,ECX=name, EDX=purpose, EDI=status.
    LEA EAX,[%LinkStm]                           ; ^STM.
    Invoke SssCreateSe::,EAX,0,ESI,ECX,EDI,EDX,[%SssAlignment]
    JC .G9:                                      ; Errors were already reported by SssCreateSe.
    MOV EDI,EAX                                  ; EDI=^SSS.
    MOV ECX,[%CoffScnIndex]
    MOV [EDI+SSS.SegmIndex],ECX                  ; Set 1-based ordinal in COFF section headers.
    MOV [EDI+SSS.Purpose],EDX
    Invoke SssGuessPurpose::,EDI                 ; If the purpose EDX wasn't specified by characteristics, guess by name.
    MOV ESI,[%CoffScnPtr]                        ; Restore ESI. Examine if the section has initialized raw data.
    MOV EAX,[ESI+PFCOFF_SECTION_HEADER.SizeOfRawData]    ; Nonzero in BSS.
    MOV ECX,[ESI+PFCOFF_SECTION_HEADER.PointerToRawData] ; Zero in BSS.
    MOV [EDI+SSS.TopLow],EAX
    JECXZ .G9:                                   ; Skip if uninitialized data section.
    SetSt [EDI+SSS.Status],sssNotBSS
    ADD ECX,[%ModBegin]                          ; Convert FA to pointer.
    CMP ECX,[%ModEnd]
    JNB .E7766:                                  ; Invalid format of COFF object file "!1S".
    BufferStore [EDI+SSS.EmitBuffer],ECX,EAX     ; Segment raw data.
.G9:JMP .G1                                      ; Section header ESI is converted, go and get the next one.
.E7766:Msg '7765',EBX                            ; Invalid format of COFF object module "!1S".
    JMP .90:

.H1:; Convert symbols from COFF symbol table to PGM EBX symbols in  the loop .H2: .. .M9:.
    XOR EAX,EAX
    MOV [%CoffSymAux],EAX
    DEC EAX
    MOV [%CoffSymIndex],EAX
    SUBD [%CoffSymPtr],SIZE# PFCOFF_SYMBOL       ; Symbol table pass is initialized.
.H2:MOV ESI,[%CoffSymPtr]
    MOV EAX,[%CoffSymIndex]
    ADD ESI,SIZE# PFCOFF_SYMBOL
    INC EAX
    MOV [%CoffSymPtr],ESI
    MOV [%CoffSymIndex],EAX
    CMP EAX,[%CoffSymCount]
    JAE .Q1:                                     ; When there are no more symbols records left to convert.
    MOV ECX,[%CoffSymAux]                        ; Number of pending Aux records.
    JECXZ .H3:
    DEC ECX                                      ; PFCOFF_SYMBOL ESI has auxilliary records.
    MOV [%CoffSymAux],ECX
    JMP .H2:                                     ; Ignore aux record(s).
.H3:; Symbol name.
    LEA EDX,[ESI+PFCOFF_SYMBOL.Name]
    MOV ECX,[EDX]                                ; If the symbol name is long, LSD=0.
    JECXZ .H4:
    MOV ECX,8                                    ; Symbol name EDX,ECX is short, NULL padded.
    JMP .H5:
.H4:MOV EAX,[EDX+4]                              ; Get the offset of long symbol name in string table.
    MOV EDX,[%CoffStrBegin]                      ; EDX=^string table.
    CMP EAX,[EDX]                                ; The first dword is the table size.
    JNB .E7766:                                  ; Return error if out of string table.
    ADD EDX,EAX                                  ; EDX is now pointer to ASCIIZ string.
    GetLength$ EDX
.H5:StripSpaces,EDX,ECX                          ; Get rid of trailing NULL characters, if any.
    MOVZXB EAX,[ESI+PFCOFF_SYMBOL.NumberOfAuxSymbols] ; ESI=^PFCOFF_SYMBOL, EDX,ECX=name, EBX=^PGM.
    MOV [%CoffSymAux],EAX                        ; Number of pending Aux records which follow symbol ESI.
    TEST EAX
    JZ .M1:                                      ; If it has no auxilliary record, it can't be a section's symbol.
    CMPB [ESI+PFCOFF_SYMBOL.StorageClass],pfcoffSYM_CLASS_FILE
    JE .H2:                                      ; Ignore COFF symbol of type '.file',
    MOVSXW EAX,[ESI+PFCOFF_SYMBOL.SectionNumber] ; Update COFF symbol which represents a COFF section as symSe. It has 1 aux record.
    TEST EAX
    JLE .M1:                                     ; If not positive, it can't be a segment's symbol symSe.
    CMPB [ESI+PFCOFF_SYMBOL.StorageClass],pfcoffSYM_CLASS_STATIC
    JNE .M1:                                     ; If storage class != 3, it can't be a segment's symbol.
    Invoke SssFindByIndex::,EAX,EBX              ; COFF symbol at ESI represents a COFF section with SectionNumber EAX.
    JNC .H7:
.E7941:Msg '7941',EDX,EDI,EBX                    ; Symbol name "!1$" mismatched COFF section "!2S" in module "!3S".
    JMP .H2:                                     ; If the segment was not declared in COFF section header.
.H7:MOV EDI,[EAX+SSS.SymPtr]
    TEST EDI
    JZ .E7766:
    Compare [EDI+SYM.NamePtr],[EDI+SYM.NameSize],EDX,ECX
    JNE .E7941:                                  ; Symbol name "!1$" mismatched COFF section "!2S" in module "!3S".
    MOV EAX,[%CoffSymIndex]                      ; Update symSe EDI which was already created in module EBX by SssCreateSe at .G7.
    MOV [EDI+SYM.NameIndex],EAX
    JMP .H2:                ; Go get the next COFF symbol.
.E7944:Msg '7944',ECX,EDI,EBX                    ; COFF section #!1D of symbol "!2S" in module "!3S" was not found.
    JMP .M9:
.M1: ; COFF symbol at ESI is standard, global or scalar. Its name is EDX,ECX.
    ListNew [EBX+PGM.SymList],Zeroed=yes         ; Create a new symbol in the loaded module.
    MOV EDI,EAX
    PoolStore [EBX+PGM.Pool],EDX,ECX
    MOV [EDI+SYM.NamePtr],EAX
    MOV [EDI+SYM.NameSize],ECX
    MOV EAX,[%CoffSymIndex]
    MOV EDX,[EBX+PGM.LinePtr]
    MOV [EDI+SYM.NameIndex],EAX
    MOV [EDI+SYM.LinePtr],EDX
    MOV EAX,[ESI+PFCOFF_SYMBOL.Value]
    MOV [EDI+SYM.OffsetLow],EAX
    ; Get scope and section assigned to COFF symbol ESI.
    MOVSXW ECX,[ESI+PFCOFF_SYMBOL.SectionNumber] ; -2,-1,0,1,2,3,,,
    TEST ECX
    JZ .M3:                                      ; pfcoffSYM_UNDEFINED is external.
    JS .M5:                                      ; pfcoffSYM_ABSOLUTE|pfcoffSYM_DEBUG is treated as scalar (SYM.Section=0).
    Invoke SssFindByIndex::,ECX,EBX              ; Segment with SSS.SegmIndex=ECX should have been already loaded.
    JC .E7944:                                   ; COFF section #!1D of symbol "!2S" in module "!3S" was not found.
    MOV [EDI+SYM.Section],EAX                    ; Symbol EDI is defined in segment EAX of program EBX.
    MOVZXB EDX,[ESI+PFCOFF_SYMBOL.StorageClass]  ; Symbol is private of public.
    Dispatch DL,pfcoffSYM_CLASS_STATIC,pfcoffSYM_CLASS_EXTERNAL
    Msg  '2733',EDX,EDI,EBX                      ; Unsupported StorageClass !1D of symbol "!2S" in COFF module !3S. Ignored.
    JMP .H2:
.pfcoffSYM_CLASS_EXTERNAL:                       ; Symbol is public.
    SetSt [EDI+SYM.Status],symPublic
.pfcoffSYM_CLASS_STATIC:                         ; Symbol is private (nonglobal).
    JMP .M5:
.M3:SetSt [EDI+SYM.Status],symExtern             ; Symbol is external.
    Invoke SssCreateExtern::,EDI,EBX             ; Assign SYM.Section with extern pseudosegment.
.M5:; Convert COFF symbol type to SYM.Status in EAX.
    MOV EAX,[EDI+SYM.Status]
    SetSt EAX,symUsed
    MOVZXW EDX,[ESI+PFCOFF_SYMBOL.Type]
    MOV AL,'A'
    CMP DH,pfcoffSYM_DTYPE_FUNCTION
    JNE .M7:
    SetSt EAX,symProc
.M7:Dispatch DL,pfcoffSYM_TYPE_CHAR,pfcoffSYM_TYPE_SHORT,pfcoffSYM_TYPE_INT,\
           pfcoffSYM_TYPE_LONG,pfcoffSYM_TYPE_FLOAT,pfcoffSYM_TYPE_DOUBLE, \
           pfcoffSYM_TYPE_BYTE,pfcoffSYM_TYPE_WORD,pfcoffSYM_TYPE_UINT, \
           pfcoffSYM_TYPE_DWORD,pfcoffSYM_TYPE_LONGDOUBLE
    JMP .M9:                                     ; SYM_TYPE_VOID.
.pfcoffSYM_TYPE_INT:
.pfcoffSYM_TYPE_UINT:                            ; DWORD or QWORD, depending on program width.
    MOV AL,'D'
    JNSt [EBX+PGM.Pgmopt.Status],pgmoptWidth64,.M9:
    MOV AL,'Q'
    JMP .M9:
.pfcoffSYM_TYPE_BYTE:
.pfcoffSYM_TYPE_CHAR:
    MOV AL,'B'
    JMP .M9:
.pfcoffSYM_TYPE_WORD:
.pfcoffSYM_TYPE_SHORT:
    MOV AL,'W'
    JMP .M9:
.pfcoffSYM_TYPE_DWORD:
.pfcoffSYM_TYPE_LONG:
.pfcoffSYM_TYPE_FLOAT:
    MOV AL,'D'
    JMP .M9:
.pfcoffSYM_TYPE_DOUBLE:
    MOV AL,'Q'
     JMP .M9:
.pfcoffSYM_TYPE_LONGDOUBLE
    MOV AL,'T'
.M9:MOV [EDI+SYM.Status],EAX
    JMP .H2:                                     ; COFF symbol ESI is converted, go get the next one.

.Q1:Invoke PfDrectveDestroy::,EBX                ; Transform COFF section [.drectve] (if exists) to symbols in module EBX.
.R1: ; Convert COFF relocations to program relocations for each program segment in the loop .R2: .. .90:.
    MOV ESI,[%CoffScnBegin]
    XOR EAX,EAX
    SUB ESI,SIZE# PFCOFF_SECTION_HEADER
    MOV [%CoffScnIndex],EAX
    MOV [%CoffScnPtr],ESI
.R2:MOV ESI,[%CoffScnPtr]
    ADD ESI,SIZE# PFCOFF_SECTION_HEADER
    MOV [%CoffScnPtr],ESI
    INCD [%CoffScnIndex]
    CMP ESI,[%CoffScnEnd]
    JNB .90:
    MOVZXW ECX,[ESI+PFCOFF_SECTION_HEADER.NumberOfRelocations]
    JECXZ .R2:                                   ; The next COFF section.
    Invoke SssFindByIndex::,[%CoffScnIndex],EBX
    JNC .R4:
.E7943:Msg '7943',[%CoffScnIndex],EBX            ; COFF section #!1D in module "!2S" was not found.
    JMP .R2:
.R4:MOV EDX,[ESI+PFCOFF_SECTION_HEADER.PointerToRelocations]
    MOV ESI,EAX
    ADD EDX,[%ModBegin]                          ; EDX=^PFCOFF_RELOCATION, ESI=^SSS, EBX=^PGM
.R5:Invoke PfcoffRelocation2Reloc,EDX,ESI,EBX
    ADD EDX,SIZE# PFCOFF_RELOCATION
    LOOP .R5:                                    ; The next relocation.
    JMP .R2:                                     ; The next COFF section.
.90:EndProcedure PfcoffLoadModule
↑ PfcoffRelocation2Reloc CoffRelocation, SssSegment, ModProgram
PfcoffRelocation2Reloc will convert one COFF relocation record to €ASM RELOC record and store it to SssSegment.RelocBuffer.
Symbols and sections of loaded module must have been already loaded to ModProgram.
Input
CoffRelocation is pointer to the input PFCOFF_RELOCATION.
SssSegment is pointer to SSS segment which contains the relocation.
ModProgram is pointer to PGM - the loaded module.
Output
Relocation is converted.
Error
E7735, E7736.
Invokes
SymFindByIndex
Invoked by
PfcoffLoadModule
PfcoffRelocation2Reloc Procedure CoffRelocation, SssSegment, ModProgram
Reloc LocalVar Size=SIZE# RELOC ; Working room for the program relocation.
    MOV EDX,[%CoffRelocation]
    MOV ESI,[%SssSegment]
    MOV EBX,[%ModProgram]
    BufferNew [ESI+SSS.RelocBuffer],SIZE# RELOC, Zeroed=Yes
    MOV EDI,EAX
    MOV EAX,[EDX+PFCOFF_RELOCATION.VirtualAddress]
    MOV [EDI+RELOC.Section],ESI
    MOV [EDI+RELOC.OrgLow],EAX
    MOV ECX,[EDX+PFCOFF_RELOCATION.SymbolTableIndex]
    Invoke SymFindByIndex::,ECX,EBX
    JC .E7736:                               ; Symbol #!1D in COFF section [!2S] was not found.',0
    MOV [EDI+RELOC.Symbol],EAX
    MOVZXW EAX,[EDX+PFCOFF_RELOCATION.Type]
    XOR ECX,ECX
    JSt [EBX+PGM.Pgmopt.Status],pgmoptWidth64,.AMD64:
.I386: ; Machine=I386 in 16|32bit programs.
    Dispatch AX,0x0006,0x0014,0x0007,0x0001,0x0002 ; Supported types of I386 relocations.
.E7735:Msg '7734',EAX,ESI,[EDI+RELOC.OrgLow] ; Relocation type 0x!1W at [!2S]:!3H is not resolvable in this program format.
    JMP .90:
.E7736:Msg '7736',ECX,ESI                    ; Symbol #!1D in COFF section [!2S] was not found.
    JMP .90:
.0x0001:MOV EAX,relocWidth16+relocAbsVA      ; IMAGE_REL_I386_DIR16.
    JMP .30:
.0x0002:MOV EAX,relocWidth16+relocRel        ; IMAGE_REL_I386_REL16.
    JMP .30:
.0x0006:MOV EAX,relocWidth32+relocAbsVA      ; IMAGE_REL_I386_DIR32.
    JMP .30:
.0x0007:MOV EAX,relocWidth32+relocAbsRVA     ; IMAGE_REL_I386_DIR325NB.
    JMP .30:
.0x0014:MOV EAX,relocWidth32+relocRel        ; IMAGE_REL_I386_REL32.
    JMP .30:
.AMD64:; Machine=AMD64 in 64bit programs.
    Dispatch AX,0004h,0001h,0002h,0003h,0008h,0005h,0006h,0007h,0009h ; Supported types of AMD64 relocations.
    JMP .E7735:  ; Relocation type 0x!1W at [!2S]:!3H is not resolvable in this program format.
.0005h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32_1.
    ADD ECX,1
    JMP .30:
.0006h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32_2.
    ADD ECX,2
    JMP .30:
.0007h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32_3.
    ADD ECX,3
    JMP .30:
.0008h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32_4.
    ADD ECX,4
    JMP .30:
.0009h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32_5.
    ADD ECX,5
    JMP .30:
.0001h:MOV EAX,relocWidth64+relocAbsVA       ; IMAGE_REL_AMD64_ADDR64.
    JMP .30:
.0002h:MOV EAX,relocWidth32+relocAbsVA       ; IMAGE_REL_AMD64_ADDR32.
    JMP .30:
.0003h:MOV EAX,relocWidth32+relocAbsRVA      ; IMAGE_REL_AMD64_ADDR32NB.
    JMP .30:
.0004h:MOV EAX,relocWidth32+relocRel         ; IMAGE_REL_AMD64_REL32.
    ;JMP .30:
.30:OR [EDI+RELOC.Status],EAX
    JNSt EAX,relocRel,.80:
    AND EAX,relocWidthMask
    SHR EAX,19                               ; Convert relocWidthMask to the object size 2|4|8.
    ADD ECX,EAX
.80:MOV EAX,ECX
    CDQ
    SUB [EDI+RELOC.AddendLow],EAX
    SBB [EDI+RELOC.AddendHigh],EDX
.90:EndProcedure PfcoffRelocation2Reloc
↑ PfcoffSymTable Program, SymTableBuffer, StringTableBuffer
PfcoffSymTable populates SymTableBuffer with PFCOFF_SYMBOL records for each of SYM symbols of the %Program.
Input
Program ^PGM. with .SymOrdBuffer filed and sorted.
SymTableBuffer is pointer to an output BUFFER for the COFF symbol table.
StringTableBuffer is pointer to an output BUFFER for the COFF string table.
Output
SymTableBuffer is filled with PFCOFF_SYMBOL records of type file, symSe, symPrivate, symGlobal.
SYM.NameIndex of each %Program symbol is updated.
Error
-
Invoked by
PfcoffCompile
Invokes
PfcoffSymFile PfcoffSymSegment PfcoffSymSymbol
PfcoffSymTable Procedure Program, SymTableBuffer, StringTableBuffer
    MOV EBX,[%SymTableBuffer]
    BufferClear EBX
    Invoke PfcoffSymFile,Ea.SrcFile::,EBX   ; Create '.file' COFF symbol in the buffer EBX.
    MOV EDX,[%Program]
    BufferRetrieve [EDX+PGM.SymOrdBuffer]
    SHR ECX,2                               ; Number of SYM symbols in the %Program.
    JZ .90:
    MOV EDX,[%StringTableBuffer]
.10:LODSD                                   ; EAX=^SYM.
    JNSt [EAX+SYM.Status],symSe,.20:
    MOV EDI,[EAX+SYM.Section]
    JNSt [EDI+SSS.Status],sssSegment|sssGroup,.20:
    Invoke PfcoffSymSegment,EAX,EBX,EDX     ; Create CLASS_STATIC (section type) pair of COFF symbols.
    JMP .80:
.20:Invoke PfcoffSymSymbol,EAX,EBX,EDX      ; Create scalar or local or global COFF symbol.
.80:DEC ECX
    JNZ .10:                                ; The next symbol.
.90:EndProcedure PfcoffSymTable
↑ PfcoffCompile OutputStream, Pgm
PfcoffCompile is constructor of an output object module in Microsoft Common Object File Format as specified in [MS_PECOFF].
Input
OutputStream is pointer to an empty STREAM for the output image contents.
Pgm is pointer to PGM representing completely assembled program.
Output
OutputStream is filled with output file contents.
Error
Errors are reported with macro Msg.
Invoked from
PfOutput
Invokes
EaBufferRelease EaBufferReserve PfDrectveCreate PfcoffFileHeader PfcoffSectHeaders PfcoffSymTable PgmOrderSegments PgmOrderSymbols PgmResizeGroups
Invoked by
PflibcofStoreObjectModule
PfcoffCompile  Procedure OutputStream, Pgm
CoffFileHeader   LocalVar Size=SIZE#PFCOFF_FILE_HEADER ; Room for PFCOFF_FILE_HEADER object.
SectionHeaderBuf LocalVar ; Pointer to BUFFER which keeps PFCOFF_SECTION_HEADER objects, one for each segment.
SymbolTableBuf   LocalVar ; Pointer to BUFFER for PFCOFF_SYMBOL records.
StringTableBuf   LocalVar ; Pointer to BUFFER for longname strings.
Machine          LocalVar ; LSW specifies PFCOFF_FILE_HEADER.Machine.
     ; Initialize temporary data structures.
     Invoke EaBufferReserve::,PfcoffCompile
     MOV [%SectionHeaderBuf],EAX         ; Section headers buffer.
     Invoke EaBufferReserve::,PfcoffCompile
     MOV [%SymbolTableBuf],EAX           ; Symbols buffer.
     Invoke EaBufferReserve::,PfcoffCompile
     MOV [%StringTableBuf],EAX           ; String table buffer.
     MOV EDX,EAX
     BufferStoreDword EDX,4              ; Initialize dword StringTableSize in the buffer EDX.
     MOV EBX,[%Pgm]
     MOV EAX,pgmoptFormatMask
     AND EAX,[EBX+PGM.Pgmopt.Status]
     CMP AL,pgmoptCOFF
     JNE .10:                            ; Do not create [.directve] segment in LIBCOF format.
     Invoke PfDrectveCreate::,EBX
.10: Invoke PgmOrderSegments::,EBX
     Invoke PgmOrderSymbols::,EBX
     LEA EDI,[%CoffFileHeader]
     Invoke PfcoffFileHeader,EDI,EBX      ; Create COFF file header. Optional header is not used in this format.
     MOVZXW EAX,[EDI+PFCOFF_FILE_HEADER.Machine]
     MOV [%Machine],EAX
     MOV ESI,[%SectionHeaderBuf]
     Invoke PfcoffSectHeaders,EBX,ESI,EDX ; Create COFF section headers.
     BufferRetrieve ESI
     MOV EAX,ECX
     SUB EDX,EDX
     MOV ECX,SIZE# PFCOFF_SECTION_HEADER
     DIV ECX
     MOV [EDI+PFCOFF_FILE_HEADER.NumberOfSections],AX
     MOV ESI,[%SymbolTableBuf]
     Invoke PfcoffSymTable,EBX,ESI,[%StringTableBuf] ; Create symbol table.
     BufferRetrieve ESI
     MOV EAX,ECX
     SUB EDX,EDX
     MOV ECX,SIZE# PFCOFF_SYMBOL
     DIV ECX
     MOV [EDI+PFCOFF_FILE_HEADER.NumberOfSymbols],EAX
     CALL .Stream:                        ; Update COFF components in the 1st dummy pass.
     StreamClear [%OutputStream]
     CALL .Stream:                        ; This time store updated COFF components to the %OutputStream.
     Invoke PgmResizeGroups::,EBX
     Invoke EaBufferRelease::,[%SymbolTableBuf]
     Invoke EaBufferRelease::,[%StringTableBuf]
     Invoke EaBufferRelease::,[%SectionHeaderBuf]
   EndProcedure PfcoffCompile

PfcoffCompile.Stream: PROC1                            ; EBX=^PGM (not clobbered).
     MOV EDX,[%OutputStream]
     ; COFF file header.
     LEA EDI,[%CoffFileHeader]
     StreamStore EDX,EDI,SIZE# PFCOFF_FILE_HEADER
     ; COFF section headers.
     BufferRetrieve [%SectionHeaderBuf]
     StreamStore EDX,ESI,ECX
     MOV EDI,ESI                           ; EDI=pointer to the 1st COFF section header.
     BufferRetrieve [EBX+PGM.SegOrdBuffer]
     SHR ECX,2
     JZ .S8:
.S2: LODSD
     PUSH ECX,ESI
       MOV ESI,EAX                         ; ESI=^SSS, EDI=^PFCOFF_SECTION_HEADER.
       JNSt [ESI+SSS.Status],sssSegment,.S7:
       MOV EAX,[ESI+SSS.TopLow]
       MOV EDX,[ESI+SSS.TopHigh]
       SUB EAX,[ESI+SSS.BottomLow]
       SBB EDX,[ESI+SSS.BottomHigh]
       Msg cc=NZ,'8525',ESI                ; Size of segment [!1S] exceeded 4 GB.
       MOV [EDI+PFCOFF_SECTION_HEADER.SizeOfRawData],EAX
       MOV EDX,[%OutputStream]
       JNSt [ESI+SSS.Status],sssNotBSS, .S4:
       Invoke EaStreamAlign::, EDX,[EBX+PGM.Pgmopt.FileAlign],0 ; Default FileAlign is 4 in COFF format.
       StreamGetSize EDX                   ; EAX=aligned file-address of the emitted raw data.
       MOV [EDI+PFCOFF_SECTION_HEADER.PointerToRawData],EAX
       MOV [ESI+SSS.BottomFA],EAX
       PUSH ESI
         BufferRetrieve [ESI+SSS.EmitBuffer]
         StreamStore EDX,ESI,ECX
       POP ESI
       MOV [EDI+PFCOFF_SECTION_HEADER.SizeOfRawData],ECX
       ADD ECX,[ESI+SSS.BottomFA]
       MOV [ESI+SSS.TopFA],ECX
       BufferRetrieve [ESI+SSS.RelocBuffer]; ESI now points to an array of RELOC records.
       JECXZ .S4:                          ; Skip if no relocations.
       Invoke EaStreamAlign::, EDX,2,0     ; COFF relocations are WORD aligned.
       StreamGetSize EDX                   ; EAX=aligned file-address of the COFF relocations.
       MOV [EDI+PFCOFF_SECTION_HEADER.PointerToRelocations],EAX
       ADD ECX,ESI                         ; ECX=^top of the array of RELOC records.
       SUB EAX,EAX                         ; EAX=counter of relocations.
.S3:   Invoke PfcoffStreamReloc,EDX,ESI,[%Machine] ; Convert and stream the RELOC at ESI.
       INC EAX                             ; EAX=counter of relocations.
       ADD ESI,SIZE# RELOC
       CMP ESI,ECX
       JB .S3:
       MOV [EDI+PFCOFF_SECTION_HEADER.NumberOfRelocations],EAX
.S4:   ADD EDI,SIZE# PFCOFF_SECTION_HEADER
.S7: POP ESI,ECX
     DEC ECX
     JNZ .S2:                              ; The next SSS segment.
.S8: ; COFF symbol table.
     Invoke EaStreamAlign::, EDX,2,0       ; COFF symbols are WORD aligned.
     StreamGetSize EDX                     ; EAX=aligned file-address of the COFF symbol table.
     LEA EDI,[%CoffFileHeader]
     MOV [EDI+PFCOFF_FILE_HEADER.PointerToSymbolTable],EAX
     BufferRetrieve [%SymbolTableBuf]
     StreamStore EDX,ESI,ECX
     ; COFF string table.
     BufferRetrieve [%StringTableBuf]
     MOV [ESI],ECX                         ; Update StringTable size.
     StreamStore EDX,ESI,ECX
     RET
    ENDP1 PfcoffCompile.Stream:
↑ PfcoffSectHeaders Program, SectHeadersBuffer, StringTableBuffer
PfcoffSectHeaders initializes SectHeadersBuffer with PFCOFF_SECTION_HEADER for each segment stored on %Program.SegOrdBuffer and updates their members SSS.NameIndex, PFCOFF_SECTION_HEADER.Name, PFCOFF_SECTION_HEADER.Characteristics..
Input
Program ^PGM. with .SegOrdBuffer filed and sorted.
SectHeadersBuffer is pointer to BUFFER for the COFF section headers.
StringTableBuffer is pointer to BUFFER for the string table. It may be 0, long sections names are truncated then.
Output
SectHeadersBuffer is filled.
SSS.SegmIndex of each section in the table is updated.
Error
-
Invoked by
PfcoffCompile
Invokes
SssGetCoffCharacteristics
PfcoffSectHeaders Procedure Program, SectHeadersBuffer, StringTableBuffer
SegmIndex LocalVar
    MOV EBX,[%SectHeadersBuffer]
    BufferClear EBX
    SUB EAX,EAX
    MOV [%SegmIndex],EAX
    MOV EDX,[%Program]
    BufferRetrieve [EDX+PGM.SegOrdBuffer]
    SHR ECX,2                               ; Number of segments in program EDX.
    JZ .90:
.10:LODSD                                   ; EAX=^SSS.
    PUSH ECX,ESI
     JNSt [EAX+SSS.Status],sssSegment,.80:
     MOV ECX,[%SegmIndex]
     INC ECX
     MOV [%SegmIndex],ECX
     MOV [EAX+SSS.SegmIndex],ECX
     MOV ESI,EAX                            ; ESI=^SSS.
     BufferNew EBX,SIZE# PFCOFF_SECTION_HEADER, Zeroed=Yes
     MOV EDX,EAX                            ; EDX=^PFCOFF_SECTION_HEADER.
     MOV EAX,ESI                            ; EAX=^SSS.
     ; PFCOFF_SECTION_HEADER.Name.
     MOV ECX,[EAX+SSS.NameSize]
     MOV ESI,[EAX+SSS.NamePtr]
     LEA EDI,[EDX+PFCOFF_SECTION_HEADER.Name]
     CMP ECX,8
     JBE .30:
.20: PUSHAD ; EAX=^SSS, EBX=%SectHeaderBuffer, ESI,ECX=SSS.Name, EDX=PFCOFF_SECTION_HEADER, EDI=PFCOFF_SECTION_HEADER.Name
       MOV EBX,[%StringTableBuffer]
       TEST EBX
       JNZ .25:                             ; Skip if long section names are supported via string table.
       Msg '3541',EAX                       ; Segment name "!1S" is too long, truncated in output file.
       MOV ECX,8                            ; Executable formats limit segment name size to 8 characters.
       REP MOVSB
       JMP .29:
.25:   PUSH ECX,ESI
         BufferRetrieve EBX
         MOV EDX,ECX                        ; Remember buffer offset of the free space in StringTableBuffer.
       POP ESI,ECX
       BufferStore EBX,ESI,ECX              ; Store long name into the string table.
       BufferStoreByte EBX,0                ; Terminating zero.
       MOV AL,'/'
       STOSB                                ; Instead of long segment name store /ASCII_offset to section header.Name.
       MOV EAX,EDX                          ; Offset within string table.
       StoD EDI,Size=7
.29: POPAD
     JMP .40:
.30: REP MOVSB
.40: MOV EDI,EAX
     ; PFCOFF_SECTION_HEADER.Characteristics. EDI=^SSS, EDX=^PFCOFF_SECTION_HEADER.
     Invoke SssGetCoffCharacteristics::,EDI
     MOV [EDX+PFCOFF_SECTION_HEADER.Characteristics],EAX
.80:POP ESI,ECX
    DEC ECX
    JNZ .10:                                ; The next segment.
.90:EndProcedure PfcoffSectHeaders
↑ PfcoffStreamReloc Stream, Reloc, Machine
PfcoffStreamReloc converts one €ASM relocation to COFF relocation and stores it to the Stream.
Input
Stream is pointer to the output STREAM.
Reloc is pointer to the input RELOC record.
Machine has the value of PFCOFF_FILE_HEADER.Machine in LSW.
Output
PFCOFF_RELOCATION record is stored to the %Stream.
Error
E6762, E7729 or E7731 is reported with macro Msg.
See also
Relocation types.
PfcoffStreamReloc Procedure Stream, Reloc, Machine
EmittedBottom  LocalVar                          ; Pointer to the bottom of emitted data in SSS.EmitBuffer.
EmittedTop     LocalVar                          ; Pointer to the top of emitted data in SSS.EmitBuffer.
CoffRelocation LocalVar Size=SIZE# PFCOFF_RELOCATION
     MOV ESI,[%Reloc]
     JSt [ESI+RELOC.Status],relocIgnore,.90:
     LEA EDI,[%CoffRelocation]
     MOV EAX,[ESI+RELOC.OrgLow]
     MOV [EDI+PFCOFF_RELOCATION.VirtualAddress],EAX ; Offset of the relocated DWORD|QWORD memory unit.
     MOV ECX,[ESI+RELOC.Symbol]
     JECXZ .10:
     MOV ECX,[ECX+SYM.NameIndex]                 ; Target symbol identification.
.10: MOV [EDI+PFCOFF_RELOCATION.SymbolTableIndex],ECX
     ; Get rid of RELOC.Addend: add it to the relocated memory unit in emitted code|data, and then clear the RELOC.Addend.
     MOV ESI,[ESI+RELOC.Section]
     BufferRetrieve [ESI+SSS.EmitBuffer]
     ADD ECX,ESI
     MOV [%EmittedBottom],ESI
     MOV [%EmittedTop],ECX
     MOV ESI,[%Reloc]
     MOV ECX,[ESI+RELOC.Status]
     MOV EBX,relocWidthMask
     AND EBX,ECX
     SHR EBX,19                                  ; Compute size of relocate memory unit (2|4|8).
     MOV EAX,[ESI+RELOC.AddendLow]
     MOV EDX,[ESI+RELOC.AddendHigh]
     JNSt ECX,relocRel,.20:
     ADD EAX,EBX                                 ; COFF_RELOCATION correction.
     ADC EDX,0
.20: MOV ESI,[ESI+RELOC.OrgLow]
     ADD ESI,[%EmittedBottom]
     CMP ESI,[%EmittedTop]
     JNB .E6762:
     MOV EBX,ECX
     AND ECX,relocWidthMask
     Dispatch ECX,relocWidth32,relocWidth64,relocWidth16
     MOV ESI,[%Reloc]
     Msg '7729',[ESI+RELOC.Section],[ESI+RELOC.OrgLow]      ; Unspecified relocation width at [!2S]:!3Hh.
     JMP .90:
.E7731:MOV ESI,[%Reloc]
     Msg  '7731',EDX,[ESI+RELOC.Section],[ESI+RELOC.OrgLow] ; Invalid reloc type 0x!1H at [!2S]:!3Hh.
     JMP .90:
.E6762:MOV ESI,[%Reloc]
     Msg '6762',[ESI+RELOC.Section],[ESI+RELOC.OrgLow]      ; Relocation [!1S]:!2H out of range.
     JMP .90:
.relocWidth64:
     ADD [ESI+0],EAX
     ADC [ESI+4],EDX
     JMP.30:
.relocWidth16:
     ADD [ESI],AX
     JMP .30:
.relocWidth32:
     ADD [ESI],EAX
.30: XOR EAX,EAX
     MOV ESI,[%Reloc]
     MOV [ESI+RELOC.AddendLow],EAX
     MOV [ESI+RELOC.AddendHigh],EAX
     ; Convert RELOC.Status EBX to PFCOFF_RELOCATION.Type.
     JSt EBX,relocWidth32,.Width32:
     JSt EBX,relocWidth64,.Width64:
     JSt EBX,relocWidth16,.Width16:
.Width16:
     MOV AL,1                ; 1: IMAGE_DIR_I386_DIR16.
     JSt EBX,relocAbsVA,.70:
     INC EAX                 ; 2: IMAGE_REL_I386_REL16.
     JSt EBX,relocRel,.70:
     MOV AL,9                ; 9: IMAGE_REL_I386_SEG12.
     JSt EBX,relocPara,.70:
     JMP .E7731:
.Width64:
     MOV AL,1                ; 1: IMAGE_REL_AMD64_ADDR64.
     CMPW [%Machine],pfcoffFILE_MACHINE_AMD64
     JNE .E7731:
     JSt EBX,relocAbsVA,.70:
     JMP .E7731:
.Width32:
     CMPW [%Machine],pfcoffFILE_MACHINE_AMD64
     JNE .40:
     MOV AL,2                ; 2: IMAGE_REL_AMD64_ADDR32.
     JSt EBX,relocAbsVA,.70:
     INC EAX                 ; 3: IMAGE_REL_AMD64_ADDR32NB.
     JSt EBX,relocAbsRVA,.70:
     INC EAX                 ; 4: IMAGE_REL_AMD64_REL32.
     JSt EBX,relocRel,.70:
     JMP .E7731:
.40: MOV AL,6                ; 6: IMAGE+REL_I386_DIR32.
     JSt EBX,relocAbsVA,.70:
     INC EAX                 ; 7: IMAGE+REL_I386_DIR32NB.
     JSt EBX,relocAbsRVA,.70:
     MOV AL,20               ; 20: IMAGE_REL_I386_REL32.
     JNSt EBX,relocRel,.E7731:
.70: MOV [EDI+PFCOFF_RELOCATION.Type],AX
.80: StreamStore [%Stream],EDI,SIZE# PFCOFF_RELOCATION
.90:EndProcedure PfcoffStreamReloc
↑ PfcoffSegmRawData Segment, Program, FileAddress, SectionHeader, RawBuffer, StringTableBuffer
PfcoffSegmRawData will flush segment data and relocations into RawBuffer and update SectionHeader.
Raw emitted data are followed by PFCOFF_RELOCATION records, word aligned.
Input
Segment is pointer to SSS whose data are processed.
Program is pointer to current PGM.
FileAddress is unaligned FA of this raw data within the output object file. It will be aligned by FileAlign= and then emitted data and relocations will be virtually saved to output file at this FA.
SectionHeader is pointer to PFCOFF_SECTION_HEADER initialized object.
RawBuffer is pointer to a BUFFER for emitted data+reloc. It will be stuffed first with zeros to achieve FileAlign= alignment.
StringTableBuffer is pointer to BUFFER for longer symbol names. It may be NULL for executable images.
Output
EAX= New (unaligned) FileAddress, i.e. the input FileAddress increased by the amount of data actually stored to RawBuffer.
SectionHeader, RawBuffer, StringTableBuffer are updated.
Error
CF=1 Errors are reported with macro Msg.
Invoked by
PfpeCompile
Invokes
ExpAlign SssGetCoffCharacteristics
PfcoffSegmRawData Procedure Segment,Program,FileAddress,SectionHeader,RawBuffer,StringTableBuffer
PgmoptStatus    LocalVar ; Local copy of program option Status.
SectionAlign    LocalVar ; Local copy of program option SECTIONALIGN=.
FileAlign       LocalVar ; Local copy of program option FILEALIGN=.
FirstRelocation LocalVar ; Distance of the 1st PFCOFF_RELOCATION record from %RawBuf.Bottom.
CoffRelocation  LocalVar Size=SIZE# PFCOFF_RELOCATION ; Temporary room for one relocation.
    MOV EDX,[%Program]
    MOV ECX,[EDX+PGM.Pgmopt.SectionAlign]
    MOV ESI,[EDX+PGM.Pgmopt.FileAlign]
    MOV EAX,[EDX+PGM.Pgmopt.Status]
    MOV [%SectionAlign],ECX
    MOV [%FileAlign],ESI
    MOV [%PgmoptStatus],EAX
    MOV EAX,[%FileAddress]
    MOV EDI,[%SectionHeader]
    MOV EBX,[%Segment]
    MOV [%ReturnEAX],EAX                         ; Initialize returned output FileAddress.
    ; SectionHeader.Name
    MOV ECX,[EBX+SSS.NameSize]
    MOV ESI,[EBX+SSS.NamePtr]
    LEA EDI,[EDI+PFCOFF_SECTION_HEADER.Name]
    CMP ECX,8
    JA .15:
.10:REP MOVSB                                    ; Short names go directly to section header.
    JMP .25:
.15:MOV EAX,[%StringTableBuffer]                 ; Longer name is stored to string table.
    TEST EAX
    JNZ .20:                                     ; Skip when long section names are supported via string table.
    Msg '3541',EBX                               ; Segment name "!1S" is too long, truncated in output file.
    MOV ECX,8                                    ; Executable formats limit segment name size to 8 characters.
    JMP .10:
.20:PUSH ECX,ESI
      BufferRetrieve EAX                         ; Get current index to string table.
      MOV EDX,ECX                                ; Remember buffer offset of the free space in StringTableBufer.
    POP ESI,ECX
    BufferStore EAX,ESI,ECX                      ; Store long name into the string table.
    BufferStoreByte EAX,0                        ; Terminating zero.
    MOV AL,'/'                                   ; Continue with section header.
    STOSB                                        ; Instead of long segment name store /ASCII_offset to section header.Name.
    MOV EAX,EDX                                  ; Offset within string table.
    StoD EDI,Size=7
.25:MOV EDI,[%SectionHeader]
    ; SectionHeader.VirtualSize and .VirtualAddress.
    JNSt [%PgmoptStatus],pgmoptImage,.30:        ; Leave VS and VA at 0 when COFF object file is created.
    ; Section bottom of executables has already been section-aligned and
    ;   increased by ImageBase in PgmMarshalSegments.
    MOV ESI,[EBX+SSS.BottomLow]
    MOV ECX,[EBX+SSS.BottomHigh]                 ; Section bottom ECX:ESI of linkables is always 0.
    MOV EDX,[%Program]
    PUSH ESI
      SUB ESI,[EDX+PGM.Pgmopt.ImageBaseLow]      ; Convert VA to RVA.
      SBB ECX,[EDX+PGM.Pgmopt.ImageBaseHigh]
      MOV [EDI+PFCOFF_SECTION_HEADER.VirtualAddress],ESI
    POP ESI
    MOV EAX,[EBX+SSS.TopLow]
    MOV EDX,[EBX+SSS.TopHigh]
    SUB EAX,ESI
    SBB EDX,ECX                                  ; EDX:EAX is now the netto data size.
    Invoke ExpAlign::,EAX,[%SectionAlign],0      ; VirtualSize will be section-aligned upward, too.
    ADD EAX,ECX
    MOV [EDI+PFCOFF_SECTION_HEADER.VirtualSize],EAX
.30:MOV ESI,[EBX+SSS.BottomLow]                  ; Set .SizeOfRawData to section header.
    MOV EAX,[EBX+SSS.TopLow]
    MOV EDX,[EBX+SSS.TopHigh]
    SUB EAX,ESI                                  ; EDX:EAX is now netto section size, both for
    SBB EDX,[EBX+SSS.BottomHigh]                 ;  initialized and uninitialized sections.
    MOV ECX,EAX ; RawDataSize.
    JSt [EBX+SSS.Purpose],sssPurposeInitMask,.35:; Skip if initialized.
    JSt [EBX+SSS.Status],sssNotBSS,.35:
    JNSt [%PgmoptStatus],pgmoptExecutable,.35:   ; Skip if COFF linkable format.
    SUB ECX,ECX                                  ; BSS raw size in executable image is 0.
.35:MOV [EDI+PFCOFF_SECTION_HEADER.SizeOfRawData],ECX
    JSt [EBX+SSS.Purpose],sssPurposeBSS,.44:
    JNSt [EBX+SSS.Status],sssNotBSS,.44:         ; BSS section has .PointerToRawData=0.
    ; Set .PointerToRawData into section header. Raw data must be file-aligned first.
    MOV EAX,[%ReturnEAX]                         ; Current unaligned FA.
    Invoke ExpAlign::,EAX,[%FileAlign],0
    ADD EAX,ECX
    MOV [%ReturnEAX],EAX
    MOV [EDI+PFCOFF_SECTION_HEADER.PointerToRawData],EAX
    JECXZ .40:
.37:BufferStoreByte [%RawBuffer],0               ; Alignment stuff.
    SUB ECX,1
    JNZ .37:
.40:BufferRetrieve [EBX+SSS.EmitBuffer]          ; Store emitted raw data to aligned RawBuffer.
    BufferStore [%RawBuffer],ESI,ECX
    ADD [%ReturnEAX],ECX
    MOV EAX,[EDI+PFCOFF_SECTION_HEADER.SizeOfRawData] ; Virtual size of raw data.
    SUB EAX,ECX                                  ; Compare with emitted size.
    JNA .44:
    ADD [%ReturnEAX],EAX
    BufferResize [%RawBuffer],EAX
.44:JNSt [%PgmoptStatus],pgmoptExecutable,.48:   ; COFF object files will have relocations stored.
    JNSt [Ea.Eaopt.Status::],eaoptDEBUG,.85:     ; No relocation records in PE+DLL when DEBUG=OFF.
.48:; SectionHeader Relocations. Relocation records will be word-aligned.
    BufferRetrieve [EBX+SSS.RelocBuffer]
    JECXZ .56:                                   ; If there are no relocations in the segment EBX.
.52:JNSt [ESI+RELOC.Status],relocIgnore,.58:
    ADD ESI,SIZE# RELOC
    SUB ECX,SIZE# RELOC
    JA .52:
.56:JMP .85:                                     ; If there are no unresolved relocations in the segment EBX.
.58:; There is at least one unresolved relocation in segment EBX.
    MOV EAX,[%ReturnEAX]                         ; Current unaligned FA. Align it to WORD.
    TEST AL,1
    JZ .61:
    INC EAX
    MOV [%ReturnEAX],EAX
    BufferStoreByte [%RawBuffer],0
.61:MOV [EDI+PFCOFF_SECTION_HEADER.PointerToRelocations],EAX
    BufferRetrieve [%RawBuffer]
    MOV [%FirstRelocation],ECX
    ; ECX is the distance of 1st PFCOFF_RELOCATION record from %RawBuffer.Bottom,
    ;   whose .VirtualAddress might be rewritten later if the number of relocations exceeds 64K.
    LEA EDI,[%CoffRelocation]                    ; EDI points to output COFF format of relocation.
    BufferRetrieve [EBX+SSS.RelocBuffer]         ; Loop .64: .. .80: through all RELOC records.
.64:JSt [ESI+RELOC.Status],relocIgnore, .75:     ; Check if the RELOC record is valid and if it goes to COFF.
    PUSH ECX,ESI
      MOV EAX,ESI                                ; Pointer to the input RELOC (internal format of relocation).
      MOV ESI,[EAX+RELOC.OrgLow]                 ; Set RVA of the word/dword/qword which is relocated.
      MOV ECX,[EAX+RELOC.OrgHigh]
      MOV EDX,[EAX+RELOC.Section]
      JECXZ .65:
      Msg '7927',EDX,ESI                         ; Relocation offset out of 4GB range at [!1S]:!2Hh.
      JMP .74:                                   ; Ignore invalid relocation.
.65:  MOV [EDI+PFCOFF_RELOCATION.VirtualAddress],ESI
      ; Set the index of COFF section which is the target of relocation.
      MOV ECX,[EAX+RELOC.Symbol]
      MOV ECX,[ECX+SYM.Section]
      SUB EBX,EBX                                ; Default symbol index is 0, which represents no segment.
      JECXZ .67:                                 ; If the symbol was plain number, .SymbolTableIndex=EBX=0.
      MOV EBX,[ECX+SSS.NameIndex]
      MOV ECX,[ECX+SSS.SegmPtr]                  ; Segment of relocation target.
      JECXZ .67:
      MOV EBX,[ECX+SSS.NameIndex]
.67:  MOV [EDI+PFCOFF_RELOCATION.SymbolTableIndex],EBX
      ; Set the type of relocation.
      MOV ECX,[%Program]
      MOV EBX,[EAX+RELOC.Status]
      MOV EDX,[EAX+RELOC.Section]
      JSt [ECX+PGM.Pgmopt.Status],pgmoptWidth64,.AMD64:
.I386:; Machine=I386 in 16|32bit programs.
      JSt EBX,relocWidth16,.W16:
      JSt EBX,relocWidth64,.E7924:               ; Invalid relocation.
      MOV CX,0x0006                              ; IMAGE_REL_I386_DIR32.
      JSt EBX,relocAbsVA,.70:
      MOV CL,0x0014                              ; IMAGE_REL_I386_REL32.
      JSt EBX,relocRel,.70:
      MOV CL,0x0007                              ; IMAGE_REL_I386_DIR32NB.
      JSt EBX,relocAbsRVA,.70:
.E7924:POP ESI                                   ; Restore ^RELOC.
      PUSH ESI
      MOV EDX,[ESI+RELOC.Section]
      Msg '7924',[ESI+RELOC.Section],[ESI+RELOC.OrgLow] ; Invalid relocation [!1S]:!2Hh.
      JMP .74:
.W16: MOV CX,0x0001                              ; IMAGE_REL_I386_DIR16.
      JSt EBX,relocAbsVA,.70:
      MOV CL,0x0002                              ; IMAGE_REL_I386_REL16.
      JSt EBX,relocRel,.70:
.AMD64:; Machine=AMD64 in 64bit programs.
      MOV CX,0x0004                              ; IMAGE_REL_AMD64_REL32.
      JSt EBX,relocWidth16,.E7924:               ; Invalid relocation [!1S]:!2Hh.
      JSt EBX,relocWidth64,.W64:
      MOV EAX,relocRelDist
      AND EAX,EBX
      SHR EAX,24                                 ; Convert relocRelDist to imm+imm2 size 0..5.
      CMP EAX,5
      JA .E7924:                                 ; Invalid relocation [!1S]:!2Hh.
      ADD CL,AL                                  ; Change reloc type from 0x0004 to 0x0004..0x0009.
      JSt EBX,relocRel,.70:
      MOV CL,0x0002                              ; IMAGE_REL_AMD64_ADDR32.
      JSt EBX,relocAbsVA,.70:
      MOV CL,0x0003                              ; IMAGE_REL_AMD64_ADDR32NB.
      JSt EBX,relocAbsRVA,.70:
      JMP .E7924:                                ; Invalid relocation [!1S]:!2Hh.
.W64: MOV CL,0x0001                              ; IMAGE_REL_AMD64_ADDR64.
.70:  MOV [EDI+PFCOFF_RELOCATION.Type],CX
      MOV ECX,SIZE#PFCOFF_RELOCATION
      BufferStore [%RawBuffer],EDI,ECX
      MOV EDX,[%SectionHeader]
      ADD [%ReturnEAX],ECX
      INCD [EDX+PFCOFF_SECTION_HEADER.NumberOfRelocations] ; This 16bit counter temporarily misuses
      ;   it's unemployed 16bit neighbour .NumberOfLinenumbers, so the counter is in fact 32bit.
      ;   Word overflow will be healed at .80:.
.74:POP ESI,ECX
.75:ADD ESI,SIZE#RELOC
    SUB ECX,SIZE#RELOC
    JA .64:                                      ; The next RELOC record.
.80:MOV EDI,[%SectionHeader]
    MOV EAX,[EDI+PFCOFF_SECTION_HEADER.NumberOfRelocations]
    TEST EAX,0xFFFF0000
    JZ .85:
    ; The .NumberOfRelocations exceeded 64K, design patch will be applied.
    BufferRetrieve [%RawBuffer]                  ; Reread the buffer, as it might get reallocated during BufferStore.
    ADD ESI,[%FirstRelocation]                   ; Find position of the 1st PFCOFF_RELOCATION record in RawBuffer.
    ; First copy the 1st record to the end.
    MOV ECX,SIZE#PFCOFF_RELOCATION
    BufferStore [%RawBuffer],ESI,ECX
    ADD [%ReturnEAX],ECX
    INC EAX                                      ; Increment number of relocations, because one more record was added.
    BufferRetrieve [%RawBuffer]                  ; Reread the buffer, as it might get reallocated during BufferStore.
    ADD ESI,[%FirstRelocation]                   ; Find position of the 1st PFCOFF_RELOCATION record.
    MOV [ESI+PFCOFF_RELOCATION.VirtualAddress],EAX ; Real number of relocation, which is above 64K.
    MOV EAX,0x0000FFFF
    MOVD [EDI+PFCOFF_SECTION_HEADER.NumberOfRelocations],EAX ; Simultaneously clear neighbouring .NumberOfLinenumbers.
    SetSt [EDI+PFCOFF_SECTION_HEADER.Characteristics],pfcoffSCN_LNK_NRELOC_OVFL
.85:; Update SectionHeader.Characteristics.
    Invoke SssGetCoffCharacteristics::, [%Segment]
    SetSt [EDI+PFCOFF_SECTION_HEADER.Characteristics],EAX
  EndProcedure PfcoffSegmRawData
    ENDPROGRAM pfcoff

▲Back to the top▲