EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

pf.htm
Enumerations
%PfList
%PfPgmoptList
Macro
PfQueryChar
Procedures
PfDetect
PfDrectveCreate
PfDrectveDestroy
PfLoad
PfOutput
PfSuboperate

This is a common source for generating EuroAssembler output file in a chosen program format. Its interface and procedures are used in actual format modules (pfbin.htm, pfcom.htm etc).

Program formats modules
FormatPlatformModule file
allLinker for all €ASM format output filespf.htm
BINBinary output filepfbin.htm
BOOTBoot sector filepfboot.htm
COFF16|32|64bit Common Object Format modulepfcoff.htm
COM16bit DOS executablepfcom.htm
DLL32|64bit Dynamically Linked Librarypfdll.htm
ELF32|64bit linkable modulepfelf.htm
ELFSO32|64bit Linux shared objectpfelfso.htm
ELFX32|64bit Linux executablepfelfx.htm
LIBCOFLibrary of COFF modulespflibcof.htm
LIBOMFLibrary of OMF modulespflibomf.htm
MZ16bit DOS executablepfmz.htm
OMF16|32bit Object Module Formatpfomf.htm
PE32|64bit Windows Portable Executablepfpe.htm
RSRCCompiled Windows resource (input only)pfrsrc.htm

Most important procedure PfOutput is invoked after the final assembly pass and it provides all functions of linker:

  1. Sections of the just assembled main program are joined to their base segment,
  2. external programs (modules and libraries) requested in source text by pseudoinstruction LINK are loaded from disk, converted to internal PGM format and saved on main program's .ModulePgmList,
  3. segments of all loaded programs are combined to the main program,
  4. order of segments is set,
  5. segments are linked into executable image,
  6. headers and other auxilliary structures are updated,
  7. data in requested output file format are stored to output STREAM and then to a disk file.
Linker object model
PseudoENDPROGRAM ; Last statement of program reached. PgmLinkSections ; Concatenate sections of each segment, if any. PassInspect ; Final pass detected. PgmListLiterals ; Write literal symbols to listing, if requested. PassDestroy ; The final assembly pass is ending. PgmDestroy ; The base program assembly is ending. ChunkTotalLines ; Some statistics, unimportant.. PgmCheckDirty ; Check if anything was emitted to at least one segment. PfOutput ; The €ASM linker. PgmoptSetLinkProp ; Mark the output as linkable, executable etc. PfLoad ; Read modules specified by LINK statements. SysOpenFileMap PfDetect ; Autodetect the format of linked module. PgmoptSetLinkProp ; Mark the loaded module properties. PfFormatLoadPgm ; Convert linked module to €ASM internal format (PGM class). PfomfLoadModule PgmoptSetLinkProp PfDrectveDestroy PgmDetectImportModule PfcoffLoadModule PgmoptSetLinkProp PfDrectveDestroy PgmSelectModules ; Select referenced modules (smart linking). PgmCombine ; Combine segments and symbols of selected modules to the base PGM. SssCombine RelocCombine PfFormatCompile ; Convert PGM to the output format and store to a stream. SssCreateImplicit PfmzDefaultStack RelocPurge PfpeImportCreate PfpeExportCreate PfpeBaserelocCreate PfrsrcLoadIconFile PgmOrderSegments PfDrectveCreate PfcoffFileHeader PfpeOptionalHeader PfpeImportFixup PfpeExportFixup PfpeBaserelocFixup PfcoffSegmRawData PgmEvalEntry PfSuboperate ; Resolve suboperation if requested for OUTFILE=. SysCreateFile SysWriteFile ; Flush the memory stream to a disk file. PgmListMap ; Display map of linked groups and segments in listing. PgmListGlobals ; Display global symbols in listing. CtxDiscard ; Exit the linked program context.

Linkers have to cope with three basic kinds of symbols and their relation to segments:

  1. Standard private and public address symbols are associated with the segment they were defined in. Symbol (stored in the symbol table of object file) contains ordinal number of its segment.
  2. Segment of external symbols are not know yet at the beginning of link-time. Their segment identifier (ordinal number) is NULL, it will be resolved later and replaced with identifier of segment where the symbol is linked to.
  3. Scalar numeric symbols assign special negative value to segment identifier instead of its ordinal (SYM_ABSOLUTE=-1 in COFF, SHN_ABS=-15 in ELF).
    Some tools create a special pseudosegment for numeric constants, often named as .scalars, ABSOLUTE etc.

EuroAssembler uses a slightly different approach: absolute numeric symbols, which do not belong to any segment, have their segment identifier NULL (empty).
When a symbol is declared as external, it is associated with a special external pseudosegment which €ASM creates in parallel with symbol declaration and with identical name. This pseudosegment will be replaced by a real segment later at link time.

|[.text] | |00000123: | |[.text]:00000123 |StdSym: EQU $ ; Associated with the current segment [.text]. |[]:00000456 |NumSym: EQU 456h ; Not associated with any segment, presented as empty []. | |ExtSym: EXTERN ; Temporarily associated with pseudosegment [ExtSym].
In order to introduce a new output program format:
  1. Choose a unique format shortcut and add it on PfList.
  2. Create source file pfshortcut.htm with the corresponding formatting procedure PfshortcutCompile and loading procedure PfshortcutLoadPgm.
  3. Update procedure PfDetect.
  4. Update procedure PgmoptSetDefaults.
  5. Update procedure PgmoptSetLinkProp.
  6. Update procedure PgmListMap.
  7. Update PROGRAM FORMAT= documentation in manual.
  8. Create test file(s) for the new format.
  9. Rebuild EuroAssembler.
   EUROASM NOWARN=2101
pf 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.
dict.htm,    \
ea.htm,      \
eaopt.htm,   \
exp.htm,     \
msg.htm,     \
pfcoff.htm,  \
pfelf.htm,   \
pfmz.htm,    \
pfomf.htm,   \
pfpe.htm,    \
pgm.htm,     \
pgmopt.htm,  \
sym.htm,     \
sss.htm,     \
stm.htm,     \
syswin.htm,  \
;;
 pf HEAD ; Start module interface.
↑ %PfList
This enumeration declares output program formats which EuroAssembler supports.
For each supported format it also defines a corresponding numeric option in PgmoptEncoding:
pgmoptBIN EQU 1
pgmoptBOOT EQU 2
pgmoptCOM EQU 3
etc. Names of those values are enumerated in %PfPgmoptList.
%PfList        %SET BIN,BOOT,COM,OMF,LIBOMF,MZ,COFF,LIBCOF,DLL,PE,RSRC,ELF,ELFX,ELFSO

%value %SETA 1     ; Numeric value of PGMOPT.Status pgmoptBIN, pgmoptCOM etc.
%PfPgmoptList %SET ; Initialize the enumeration to emptiness.
pf %FOR %PfList
     pgmopt%pf     EQU %value ; The actual option definition.
     %PfPgmoptList %SET pgmopt%pf,%PfPgmoptList ; Prepend the option name.
     %value        %SETA %value+1 ; Increment value for the next format.
   %ENDFOR pf
↑ PfQueryChar Char
Macro PfQueryChar searches for a %Char in string ESI,EDX.
Input
Char is a character to find.
ESI is pointer to the searched string.
EDX is size of the searched string.
Output
ZF=1 if the string contains Char.
EAX,EDI,ECX changed.
PfQueryChar %MACRO Char ; Ad hoc macro to find a Char in string ESI,EDX.
       MOV AL,%Char
       MOV EDI,ESI
       MOV ECX,EDX
       REPNE SCASB
     %ENDMACRO PfQueryChar
%EuroasmDefaultDllName     %SET kernel32.dll            ; Used when IMPORT lacks the LIB= specification.
%EuroasmDefaultDllNameSize %SETS %EuroasmDefaultDllName ; Number of characters in Dll name.
 ENDHEAD pf  ; End of module interface.
↑ PfOutput Pgm
EuroAssembler linker. Its main procedure PfOutput creates output program file with name specified by Pgm.Pgmopt.OutFile in the format specified by Pgm.Pgmopt.Status:pgmoptFormatMask.
PfOutput is dispatcher to actual format creators PfFormat Compile, which write the output to an intermediary memory stream . The stream is finally flushed to a disk file.
Input
Pgm Pointer to a completely assembled PGM object. It may have PGM.LinkFile modules (not loaded yet).
Output
Output file is written to disk.
Error
CF=1 Errors are reported with macro Msg.
Invokes
DictSearchByData PfLoad PfSuboperate PgmCombine PgmRelocResolve PgmSelectModules PgmSymResolve PgmoptSetLinkProp RelocPurge
Invoked by
PgmDestroy
PfOutput Procedure Pgm
OutputStream LocalVar ; Pointer to a STREAM which will accumulate data before they are dumped to the output file.
OutputFile   LocalVar Size=SIZE#FILE ; Structure FILE for the output file.
    MOV EBX,[%Pgm]
    Invoke PgmoptSetLinkProp::,[EBX+PGM.Pgmopt.Status]
    ; Load and select all external modules which were requested by pseudoinstruction LINK
    ;  and store them on Pgm.ModulePgmLst as objects of PGM class.
    MOV ECX,[EBX+PGM.LinkFilesNr]
    JECXZ .20:                                     ; If no link requested.
    MOV ESI,[EBX+PGM.LinkFileNamesTable]
    MOV EDI,[EBX+PGM.LinkLinePtrTable]
.10:LODSD
    Invoke PfLoad,EBX,EAX,[EDI]
    ADD EDI,4
    LOOP .10:
.20:Invoke PgmSelectModules::,EBX
    ; Combine segments and symbols from loaded programs to the base program EBX.
    JSt [EBX+PGM.Pgmopt.Status],pgmoptLibrary,.30: ; If the target program is a library LIBOMF or LIBCOF, loaded not selected modules are not combined.
    Invoke PgmCombine::,EBX                        ; Copy or merge selected modules to the base program EBX.
    Invoke PgmSymResolve::,EBX                     ; Resolve public and external symbols in static linking.
    Invoke PgmRelocResolve::,EBX
    Invoke RelocPurge::,EBX                        ; Omit RELOC records resolved so far.
.30:; Prepare memory stream for output file.
     StreamCreate [EBX+PGM.Pool],BufSize=32K
     MOV [%OutputStream],EAX
     JC .90:

     ; Get the name of procedure for output file formating: PfbinCompile, PfcomCompile etc.
     ; Due to file-naming conventions, the format name (BIN,COM, OMF...)
     ;    needs to be coverted to lower case at asm-time.
     MOV ECX,[EBX+PGM.Pgmopt.Status]
     AND ECX,pgmoptFormatMask
  PF %FOR %PfList
       CMP ECX,pgmopt%PF
       JNE .Not%PF:                                ; Convert program-format shortcut %PF to lowercase %pf, e.g. OMF to omf.
  %PFn %SETS %PF                                   ; Set number of characters in the shortcut to %PFn.
  %pf  %SET                                        ; Initialize the lowcase shortcut to emptiness.
     i %FOR 1..%PFn
         %lc %SETC "%PF[%i]" | 0x20                ; Convert %i-th character to lowercase
         %pf %SET %pf%lc                           ;  and append it to %pf.
       %ENDFOR i                                   ; The conversion takes place at asm-time.
       Invoke Pf%pf{}Compile::,EAX,EBX             ; Invoke the actual formating, e.g. PfomfCompile, PfpeCompile etc.
       JMP .35:
      .Not%PF:
     %ENDFOR PF
     JMP .90:
 .35:; Apply suboperation(s) on the output file.
     Invoke PfSuboperate,EBX,[%OutputStream]
     MOV [%OutputStream],EAX
     ; Warn when the output file already exists on Src.PfList.
     MOV ESI,[EBX+PGM.Pgmopt.OutFilePtr]
     MOV ECX,[EBX+PGM.Pgmopt.OutFileSize]
     ListGetFirst [Src.PfList::]
     JZ .65:
 .40:CMP ECX,[EAX+4]
     JNE .60:                                      ; If filename sizes do not match.
     MOV EDI,[EAX+0]                               ; EDI is now pointer to the first character of filename.
     PUSH EAX,ECX,ESI
 .45:  MOV AL,[ESI]
       MOV AH,[EDI]
       INC ESI
       INC EDI
       CMPB [Ea.EuroasmOS::],'W'
       JNE .50:                                    ; Skip if running on case-sensitive filesystem.
       OR AX,0x2020                                ; Simplified conversion to lowercase.
 .50:  CMP AL,AH
       JNE .55:
       LOOP .45:
 .55:POP ESI,ECX,EAX
     JNE .60:
     Msg '3990',EAX                                ; Overwriting previously generated output file "!1S".
     JMP .70:
 .60:ListGetNext EAX
     JNZ .40:
 .65:ListNew [Src.PfList::]                        ; Add the filename to Src.PfList .
     MOV [EAX+0],ESI                               ; Store filename ESI,ECX to the new leaf EAX.
     MOV [EAX+4],ECX
 .70:; Flush the OutputStream contents to OutputFile on disk.
     LEA EDI,[%OutputFile]
     Clear EDI,Size=SIZE# FILE
     SysCreateFile EDI,ESI                         ; Assign OutputFile EDI with filename ESI and open it for writing.
     JC .E7951:                                    ; Report error EAX if the file is not writable.
     StreamDump [%OutputStream], .WriteBlock:      ; Write the entire stream contents to OutputFile.
 .80:; The file is written, now prepare I0660 with information about output file.
     LEA EBX,[EDI+FILE.Name]
     PUSH [EDI+FILE.Size]
      SysCloseFile EDI
      MOV EAX,[%Pgm]
      LEA EDX,[EAX+PGM.Pgmopt]
      MOV EAX,[EDX+PGMOPT.Status]
      AND EAX,pgmoptModelMask
      Invoke DictSearchByData::,DictProgramModels::,EAX
      MOV EDI,ESI ; !2S
      MOV EAX,[EDX+PGMOPT.Status]
      AND EAX,pgmoptFormatMask
      Invoke DictSearchByData::,DictProgramFormats::,EAX ; ESI=!3S
      MOV ECX,pgmoptWidthMask
      AND ECX,[EDX+PGMOPT.Status]
      SAR ECX,20                                   ; Program width ECX=!1D.
     POP EAX                                       ; Output file size !5D.
     MOV EDX,[%Pgm]
     JSt [EDX+PGM.Status],pgmEnvelope,.I0760:
     Msg '0660',ECX,EDI,ESI,EBX,EAX                ; !1Dbit !2S !3S file "!4$" created, size=!5D.
     JMP .90:
.E7951:CALL .WriteBlock.E7951:                     ; Though the file EDI is not writtable,
     JMP .80:                                      ;    report I0660 (it will have size=0).

PfOutput.WriteBlock:PROC1                                  ; Callback for writing the stream-contents-block ESI,ECX to [%OutputFile].
     LEA EDI,[%OutputFile]
     SysWriteFile EDI,ESI,ECX
     JNC .OK:
.E7951:LEA ECX,[EDI+FILE.Name]                     ; Expects EDI=^FILE, EAX=error code, CF=1.
     Msg '7951',EAX,ECX                            ; Error 0x!1H writing to output file "!2$".
 .OK:RET
    ENDP1 PfOutput.WriteBlock:

.I0760:Msg '0760',ECX,EDI,ESI,EBX,EAX              ; !1Dbit !2S !3S file "!4$" created from source, size=!5D.
.90:EndProcedure PfOutput
↑ PfLoad Pgm, Filemask, LinePtr
PfLoad will resolve linked object module name(s) specified by (possibly wildcarded) Filemask, check their format, and convert each linked file to a PGM structure created on Pgm.Pool. The new created PGM then will be added to Pgm.ModulePgmList.
Input
Pgm is pointer to a completely assembled PGM object to which it is linked (base program).
Filemask is pointer to zero-terminated linked file name. It may contain path and wildcards.
LinePtr points to the source line with LINK statement which requested the file. It is used in error messages.
Output
Requested program(s) are loaded and stored to Pgm.ModulePgmList (but not combined and linked yet).
Error
CF=1 Errors are reported with macro Msg.
See also
PgmCombine.
Invoked by
PfOutput
Invokes
EaoptGetOnePath PfDetect PgmoptSetLinkProp
PfLoad Procedure Pgm, FilemaskPtr, LinePtr
LinkFile      LocalVar Size=SIZE#FILE ; Linked file.
FilemaskEnd   LocalVar
SubopPtr      LocalVar
SubopEnd      LocalVar
PathNr        LocalVar
Status        LocalVar ; Resolving status, see the flags below.
%AtLeast1     %SETA 1  ; One or more files were resolved from wildcards.
%Wildcarded   %SETA 2  ; Filemask contains * or ?.
%WithPath     %SETA 4  ; Filemask contains slash or colon.
    ClearLocalVar
    MOV ESI,[%FilemaskPtr]                       ; Parse the name of linked file.
    GetLength$ ESI
    StripSpaces ESI,ECX
    LEA EDX,[ESI+ECX]                            ; First suppose no quotes and no suboperations, e.g. file*.obj.
    MOV [%FilemaskEnd],EDX
    MOV [%SubopPtr],EDX
    MOV [%SubopEnd],EDX                          ; Suppose no suboperation.
    MOV EDI,ESI
    LODSB
    CMP AL,'"'
    JNE .10:
    MOV EDI,ESI                                  ; Filemask is in quotes.
    DEC ECX
    MOV [%FilemaskPtr],EDI
    REPNE SCASB                                  ; Search for the terminating double quote.
    Msg cc=NE,'6951',ESI                         ; Wrong linked file name !1$.',0
    JNE .90:
    MOV [%SubopPtr],EDI
    DEC EDI
    MOV [%FilemaskEnd],EDI
.10:; [%FilemaskPtr]..[%FilemaskEnd] now specifies unquoted filename, perhaps with path and wildcards, without suboperations.
     MOV ESI,[%FilemaskPtr]
     MOV EDX,[%FilemaskEnd]
     SUB EDX,ESI
     RstSt [%Status],%Wildcarded + %AtLeast1     ; Query if wildcarded (contains asterix or question mark).
     PfQueryChar '*'
     JE .20:
     PfQueryChar '?'
     JNE .30:
.20: SetSt [%Status],%Wildcarded
.30: SetSt [%Status],%WithPath                   ; Query if Filemask was specified with path (if it contains slash or colon).
     PfQueryChar '\'
     JE .55:
     PfQueryChar '/'
     JE .55:
     PfQueryChar ':'
     JE .55:
     RstSt [%Status],%WithPath
     ; If no path was specified in LINK statement, we must try all pathes from %^LINKPATH.
.40: Invoke EaoptGetOnePath::,[Ea.Eaopt.LinkPathPtr::],[Ea.Eaopt.LinkPathSize::],[%PathNr] ; Get the path to ESI,ECX.
     JC .80:                                     ; If there are no more path specified in LINKPATH=.
     INCD [%PathNr]                              ; Prepare for the next path.
     MOV EDX,[%FilemaskEnd]
     SUB EDX,[%FilemaskPtr]                      ; EDX is now size of filemask without path.
     LEA EAX,[EDX+ECX]                           ; ESI,ECX is one include path.
     CMP EAX,MAX_PATH_SIZE
     Msg cc=A,'6953',ESI                         ; Size of LinkPath "!1_" + size of filename exceeded 256 characters.
     JA .90:
     LEA EDI,[%LinkFile+FILE.Name]               ; Assign path+filemask to LinkFile.
     REP MOVSB
     MOV AX,'\/'
     CMPB [Ea.EuroasmOS::],'W'                   ; Choose slash or backslash.
     JE .50:
     XCHG AL,AH                                  ; Backslash if euroasm.exe runs on Windows, otherwise use slash /.
.50: CMP AL,[EDI-1]
     JE .60:
     CMP AH,[EDI-1]
     JE .60:
     STOSB                                       ; If the path was not terminated with slash or backslash, append it.
     JMP .60:
.55: LEA EDI,[%LinkFile+FILE.Name]
.60: MOV ESI,[%FilemaskPtr]
     MOV ECX,EDX
     REP MOVSB
     SUB EAX,EAX                                 ; Zero terminate filemask.
     STOSB                                       ; LinkFile is now assigned with path and filemask.
     LEA EDI,[%LinkFile]
     SysEachFile EDI, .File                      ; Perform callback .File with each wildcard-resolved filename.
     JSt [%Status],%WithPath,.80:
     JSt [%Status],%Wildcarded,.40:              ; Continue search with the next link path.
     JNSt [%Status],%AtLeast1,.40:               ; If non-wildcarded file not found, continue search.
     JMP .90:
.E6954:LEA EAX,[EDI+FILE.Name]
     Msg '6954',EAX                              ; Linked file "!1$" not found.
     JMP .90:

.File:PROC1 ; Callback from SysEachFile. Input:
        ; EBX=^FILE with assigned FILE.Name.
        ; EDX=find-handle from OS.
        ; ESI=^FILE.Name
        ; EDI=WIN32_FIND_DATAW
     SetSt [%Status],%AtLeast1
     LEA EDX,[EBX+FILE.Name]
     SysOpenFileMap EBX,EDX
     Msg cc=C,'8530',EDX                         ; Error reading linked file "!1$".
     JC .F8:
     MOV ECX,EAX                                 ; The contents of linked file EBX is now mapped in memory ESI,ECX.
     ; Detect format of linked file.
     Invoke PfDetect, ESI,ECX                    ; Returns one of DictProgramFormats in EAX.
     Msg cc=Z,'8539',EDX                         ; Format of file "!1$" was not recognized.
     JZ .F8:
     MOV EDI,EAX                                 ; Pointer to Dict_Format.
     Invoke PgmoptSetLinkProp::,[EDI+DICT.Data]  ; Set properties corresponding to the format.
     TEST EAX,pgmoptLinkable | pgmoptImportable
     Msg cc=Z,'8534',EDI,EDX                     ; Format !1S of file "!2$" is not linkable.
     JZ .F8:
     TEST EAX,pgmoptLibrary|pgmoptExportable
     MOV EAX,'0560'                              ; Linking !1S module "!2$".
     JZ .85:
     MOV EAX,'0561'                              ; Linking !1S library "!2$".
.85: Msg EAX,EDI,EDX
     CMP [EDI+DICT.Data],pgmoptELFSO
     JNE .86:
     MOV EAX,[%Pgm]
     SetSt [EAX+PGM.Status],pgmLoadsELFSO
.86:; Procedures for input file loading are PfomfLoadPgm, PfcoffLoadPgm, PfdllLoadPgm etc.
   ; Due to naming conventions we need lowercase format shortcut.
     MOV EAX,[EDI+DICT.Data]
     AND EAX,pgmoptFormatMask
  PF %FOR %PfList
       CMP AL,pgmopt%PF
       JNE .Not%PF:
       ; Convert program-format shortcut %PF to lowercase %pf, e.g. OMF to omf.
  %PFn %SETS %PF                                 ; Set number of characters in shortcut to %PFn.
  %pf  %SET                                      ; Initialize lowcase shortcut to emptiness.
     i %FOR 1..%PFn
         %lc %SETC "%PF[%i]" | 0x20              ; Convert %i-th character to lowercase
         %pf %SET %pf%lc                         ;  and append to the loading-procedure name.
       %ENDFOR i
       Invoke Pf%pf{}LoadPgm::,[%Pgm],ESI,ECX,EDX ; Perform the actual loading, e.g. PfcoffLoadPgm.
       JMP .F8:
      .Not%PF:
     %ENDFOR PF
 .F8:SysCloseFile EBX                            ; Release the memory-mapped file.
 .F9:RET
     ENDP1 .File:

.80: JSt [%Status],%Wildcarded,.90:              ; Do not report "E6954 not found" when specified with wildcards.
     JNSt [%Status],%AtLeast1,.E6954:            ; Linked file "!1$" not found.
.90:EndProcedure PfLoad
↑ PfDetect InputObjPtr, InputObjSize
PfDetect will inspect and recognize the format of input file submitted to linker.
Input
InputObjPtr is pointer to the file contents mapped in memory, loaded by the caller.
InputObjSize is number of bytes in the file.
Output
ZF=0, EAX= is pointer to DICT dictionary item of recognized DictProgramFormats, e.g. Dict_FormatCOFF.
ZF=1, EAX=0 when none of known program linkable formats was recognized.
Error
-
See also
PgmDetectImportModule
Invoked by
PfLoad
Invokes
PfomfLoadRecord PfrsrcStoreRecord
PfDetect Procedure InputObjPtr, InputObjSize
       MOV EBX,[%InputObjPtr]
       MOV ECX,[%InputObjSize]
       LEA EDX,[EBX+ECX] ; InputObjEnd.
        ; Try format RSRC. It consists of PFRSRC_RES_HEADER records+data.
       MOV EAX,EBX
.RSRC1:Invoke PfrsrcStoreRecord::,EAX,EDX,0,0 ; Silently verify one resource header and raw data.
       JC .NoRSRC:
       JNZ .RSRC1: ; Test the next resource record at EAX.
       MOV EAX,Dict_FormatRSRC:: ; Valid format RSRC detected.
       JMP .Detected:
.NoRSRC:
       ; Try format LIBCOF. It starts with signature !<arch>.
       CMP ECX,8
       JB .NoLIBCOF:
       MOV EAX,0x72613C21 ; '!<ar'
       CMP [EBX],EAX
       JNE .NoLIBCOF:
       MOV EAX,0x0A3E6863 ; 'ch>',0x0A
       CMP [EBX+4],EAX
       JNE .NoLIBCOF
       MOV EAX,Dict_FormatLIBCOF::
       JMP .Detected:
.NoLIBCOF:
       ; Try format LIBOMF. It consists of valid OMF records,
       ; the first one is LIBHDR.
       CMP ECX,27
       JB .NoLIBOMF: ; If too short.
       MOV ESI,EBX
       CMPB [ESI],LIBHDR
       JNE .NoLIBOMF:
       MOVZXW EDI,[ESI+1]
       ADD EDI,3 ; EDI is now library page size. Legal sizes are 16,32,64,..32K.
       TEST EDI,0x0000_000F
       JNZ .NoLIBOMF: ; If invalid page size.
       PUSH ECX
        BSF EAX,EDI
        BSR ECX,EDI
        CMP EAX,ECX
       POP ECX
       JNE .NoLIBOMF: ; If invalid page size (not power of two).
       CMP EAX,4
       JB .NoLIBOMF: ; If invalid page size.
       CMP EAX,15
       JA .NoLIBOMF: ; If invalid page size.
       DEC EDI ; Page size is OK. EDI is now the align mask for modules in library.
       MOV EDX,[ESI+3] ; File address of library dictionary.
       ADD EDX,ESI ; EDX now points to the dictionary, i.e. end of library records.
.LIBOMF1:Invoke PfomfLoadRecord::,ESI,EBX,EDX,0 ; Silently verify one OMF record.
       JC .NoLIBOMF:
       MOV AL,[ESI]
       AND AL,~1 ; Reset LSbit (when MODEND32 is used).
       CMP AL,MODEND
       JNE .LIBOMF3:
       ; Some linkers rather than blowing up the length of MODEND prefer to keep MODEND short
       ; and page-align the room between MODEND and the following THEADR/LHEADR.
       LEA EAX,[ESI+ECX]
       SUB EAX,EBX ; EAX is now FA of the end of MODEND.
       NEG EAX
       AND EAX,EDI ; 0..PageSize-1.
       ADD ESI,EAX ; Align ESI to the next page.
.LIBOMF3:ADD ESI,ECX ; ESI now points to the next OMF record.
       TEST ECX
       JNZ .LIBOMF1: ; Check the next OMF record.
       MOV EAX,Dict_FormatLIBOMF::
       JMP .Detected:
.NoLIBOMF:
       ; Try format OMF. If consists of valid OMF records.
       CMP ECX,10
       JB .NoOMF: ; If too short.
       MOV ESI,EBX
       MOV AL,[ESI]
       CMP AL,THEADR ; The first OMF record must be THEADR or LHEADR.
       JE .OMF1:
       CMP AL,LHEADR
       JNE .NoOMF:
.OMF1: Invoke PfomfLoadRecord::,ESI,EBX,EDX,0 ; Silently verify one OMF record.
       JC .NoOMF:
       ADD ESI,ECX ; ESI now points to the next OMF record.
       TEST ECX
       JNZ .OMF1: ; Check the next OMF record.
       MOV EAX,Dict_FormatOMF::
       JMP .Detected:
.NoOMF:
       ; Try format COFF. It begins with valid machine type.
       MOV ECX,[%InputObjSize]
       CMP ECX,SIZE# PFCOFF_FILE_HEADER
       JNA .NoCOFF: ; If too short.
       MOV AX,[EBX]
       Dispatch AX,pfcoffFILE_MACHINE_I386, pfcoffFILE_MACHINE_I486, \
                   pfcoffFILE_MACHINE_I586, pfcoffFILE_MACHINE_IA64, \
                   pfcoffFILE_MACHINE_AMD64, pfcoffFILE_MACHINE_UNKNOWN
       JMP .NoCOFF:
.pfcoffFILE_MACHINE_I386:
.pfcoffFILE_MACHINE_I486:
.pfcoffFILE_MACHINE_I586:
.pfcoffFILE_MACHINE_IA64:
.pfcoffFILE_MACHINE_AMD64:
.pfcoffFILE_MACHINE_UNKNOWN: ; Linked file format detected as COFF.
        MOV EAX,Dict_FormatCOFF::
        JMP .Detected:
.NoCOFF:
       ; Try formats PE, DLL, MZ. They begin with MZ signature.
       CMP ECX,SIZE#PFMZ_DOS_HEADER
       JB .NoMZ: ; If too short.
       CMPW [EBX],'MZ'
       JNE .NoMZ:
       MOV EAX,Dict_FormatMZ:: ; It may be MZ format.
       MOV ESI,[EBX+PFMZ_DOS_HEADER.e_lfanew] ; Offset to PE signature.
       ADD ESI,EBX
       CMP ESI,EDX
       JA .Detected: ; Not PE, but MZ.
       CMPD [ESI],'PE'
       JNE .Detected:; Not PE, but MZ.
       ADD ESI,4 ; Skip the PE signature to file header.
       LEA EDI,[ESI+SIZE# PFCOFF_FILE_HEADER + SIZE# PFPE_OPTIONAL_HEADER64]
       CMP EDI,EDX
       JA .Detected: ; Not PE, but MZ.
       MOV EAX,Dict_FormatDLL:: ; File is PE or DLL.
       JSt [ESI+PFCOFF_FILE_HEADER.Characteristics],pfcoffFILE_DLL,.Detected:
       MOV EAX,Dict_FormatPE::
       JMP .Detected:
.NoMZ:
       ; Try formats ELF,XELFX, ELFSO. They begin with ELF signature.
       CMP ECX,SIZE# PFELF_EHDR64
       JB .NONE:
       CMPD [EBX],0x464C457F
       JNE .NONE:
       MOV DL,[EBX+PFELF_EHDR64.e_type]
       MOV EAX,Dict_FormatELF::
       CMP DL,pfelfRel
       JE .Detected:
       MOV EAX,Dict_FormatELFX::
       CMP DL,pfelfExec
       JE .Detected:
       MOV EAX,Dict_FormatELFSO::
       CMP DL,pfelfDyn
       JE .Detected:
.NONE: XOR EAX,EAX ; File format was not recognized.
.Detected:
       MOV [%ReturnEAX],EAX
       TEST EAX ; Set ZF.
    EndProcedure PfDetect
↑ PfDrectveCreate Program

PfDrectveCreate creates new auxilliary section of unspecified width with name [.drectve] and PURPOSE=DRECTVE when a non-executable files is compiled, if a section with that name and purpose does not exist yet. Otherwise it appends to its contents.
The section contains linker directives which will be used when the final executable is created.

See PfDrectveDestroy for the list of supported directives.

The section is not created if Windows dynamic linking is not required, i.e. when no symbol with scope EXPORT or IMPORT was defined in the Program.

Raw contents of [.drectve] segment in COFF module is a plain text string, such as /IMPORT:GetStdHandle:"kernel32.dll" /ENTRY:WinMain.

Raw contents of [.drectve] segment in ELF module is specified in documentation of ELF section type SHT_NOTE.

Input
Program is pointer to PGM.
Output
New segment [.drectve] is created in Program if entry point or at least one imported symbol is declared in Program..
Error
-
See also
PfDrectveDestroy
Invoked by
PfcoffCompile PfelfCompile
Invokes
EaBufferAlign EaBufferRelease EaBufferReserve SssCreateSe SssFindByName
PfDrectveCreate Procedure Program
TextBuf   LocalVar                                       ; Pointer to a BUFFER with section contents.
Statement LocalVar Size=SIZE# STM                        ; Forged statement required by SssCreateSe.
    ClearLocalVar
    MOV EBX,[%Program]
    Invoke EaBufferReserve::,PfDrectveCreate
    MOV [%TextBuf],EAX
    MOV EDX,EAX
    ; Create directive /ENTRY: if this Program specifies entry symbol.
    MOV ECX,[EBX+PGM.Pgmopt.EntrySize]
    JECXZ .10:                                           ; If no ENTRY= was specified.
    MOV ESI,[EBX+PGM.Pgmopt.EntryPtr]
    BufferStore EDX,=B" /ENTRY:",8
    BufferStore EDX,ESI,ECX
.10:; Create directives /EXPORT: and /IMPORT: if such symbols exist.
    ListGetFirst [EBX+PGM.SymList]
    JZ .55:
.20:JNSt [EAX+SYM.Status],symExport,.30:
    BufferStore EDX,=B" /EXPORT:",9
    BufferStore EDX,[EAX+SYM.NamePtr],[EAX+SYM.NameSize] ; Exported symbol name.
.30:JNSt [EAX+SYM.Status],symImport,.50:
    BufferStore EDX,=B" /IMPORT:",9
    BufferStore EDX,[EAX+SYM.NamePtr],[EAX+SYM.NameSize] ; Imported symbol name.
    MOV ECX,[EAX+SYM.DllNameSize]
    MOV ESI,[EAX+SYM.DllNamePtr]
    JECXZ .50:                                           ; Default DLL kernel32.dll assumed.
    CMP ECX,12
    JNE .40:                                             ; Nondefault DLL.
    MOV EDI,0x20202020
    MOV ECX,[ESI+0]
    OR ECX,EDI                                           ; Convert letters to lower case.
    CMP ECX,'kern'
    JNE .40:                                             ; Nondefault DLL.
    MOV ECX,[ESI+4]
    OR ECX,EDI                                           ; Convert letters to lower case.
    CMP ECX,'el32'
    JNE .40:                                             ; Nondefault DLL.
    MOV ECX,[ESI+8]
    OR ECX,EDI                                           ; Convert letters to lower case.
    CMP ECX,'.dll'
    JE .50: ; Skip when symbol EAX is imported from the default library "%EuroasmDefaultDllName", which may be omitted.
.40:; Nondefault DLL is used. Store its colon-separated quoted name.
    BufferStoreWord EDX,':"'
    BufferStore EDX,[EAX+SYM.DllNamePtr],[EAX+SYM.DllNameSize]
    BufferStoreByte EDX,'"'
.50:ListGetNext EAX
    JNZ .20:                                             ; The next symbol.
.55:BufferRetrieve EDX
    JECXZ .80:                                           ; Skip if no directive was stored.
    ; Section [.drectve] will be created.
    LEA EDI,[%Statement]
    MOV [EDI+STM.Program],EBX
    MOV EAX,[EBX+PGM.CurrentStm]
    TEST EAX
    JZ .60:
    MOV EAX,[EAX+STM.LinePtr]
    MOV [EDI+STM.LinePtr],EAX
.60:Invoke SssFindByName::,sssSegment,sssPublic,=B'.drectve',8,EBX
    JNC .70:                                            ; If [.drectve] exists, reuse it.
    PUSH ECX
     MOV ECX,4                                          ; ELF PT_NOTE .drectve section alignment.
     JSt [EBX+PGM.Pgmopt.Status],pgmoptELFbased,.65:
     MOV CL,1                                           ; COFF .drectve section alignment.
.65: Invoke SssCreateSe::,EDI,0,=B'.drectve',8,sssSegment+sssNotBSS+sssPublic,sssPurposeDRECTVE,ECX
    POP ECX                                             ; Restore [.drectve] payload size.
.70:MOV EDI,EAX                                         ; ^SSS [drectv].
    JSt [EBX+PGM.Pgmopt.Status],pgmoptELFbased,.75:
    BufferStore [EDI+SSS.EmitBuffer],ESI,ECX            ; COFF based segment has no header.
    BufferRetrieve [EDI+SSS.EmitBuffer]
    MOV [EDI+SSS.TopLow],ECX
    JMP .80:
.75:Invoke EaBufferAlign::,EDX,8                        ; ELF based formats.
    BufferRetrieve EDX                                  ; ESI,ECX is the .directv strings.
    MOV EDX,[EDI+SSS.EmitBuffer]
    BufferStoreDword EDX,13                             ; namesz "EuroAssembler".
    BufferStoreDword EDX,ECX                            ; descsz [.drectv] strings.
    BufferStoreDword EDX,0x0000_00EA                    ; type 0xEA = €ASM "linker directive".
    BufferStore      EDX,=B"EuroAssembler",14           ; name.
    BufferStoreWord  EDX,0                              ; padding to DWORD.
    BufferStore      EDX,ESI,ECX                        ; desc - the actual .drectv string.
    BufferRetrieve EDX
    MOV [EDI+SSS.TopLow],ECX
.80:Invoke EaBufferRelease::,[%TextBuf]
.90:EndProcedure PfDrectveCreate
↑ PfDrectveDestroy Program

PfDrectveDestroy will find an auxiliary segment [.drectve] with PURPOSE=DRECTVE, read, parse and assemble its emitted contents, and then it will discard the segment.

Segment raw contents is plain text when COFF module is loaded. When the [.drectve] ELF section is loaded, the plain text is encapsulated as ELF PT_NOTE section.
The PT_NOTE header and the actual plain text are DWORD aligned and they may repeat when [.drectv] combines more then one ELF modules.

Typical plain-text directive looks like /name: value. Directive consists of

prefix
slash / or hyphen -
name
(identifier)
suffix
colon : or equal sign = or white space(s)
value
quoted or unquoted string.
Input
Program is a pointer to the just loaded PGM.
Output
Each linker directive creates or updates its symbol in the Program.
Segment [.drectve] was removed from Program.SssList.
Error
CF=1 Errors are reported with macro Msg.
See also
PfDrectveCreate
Invokes
DictLookup SssCreateExtern SssFindByName SymFindByName
Invoked by
PfcoffLoadModule PfelfLoadPgm PfomfLoadModule
PfDrectveDestroy Procedure Program
DrectveSegm LocalVar       ; ^SSS [.drectve].
DrectveTop  LocalVar       ; End of SSS.EmitBuffer.
DllNameSize LocalVar       ; Components parsed from the format /NAME:Value:"DllName".
DllNamePtr  LocalVar
ValueSize   LocalVar
ValuePtr    LocalVar
NameSize    LocalVar
NamePtr     LocalVar
    MOV EBX,[%Program]
    Invoke SssFindByName::,sssSegment,0,=B'.drectve',8,EBX
    JC .99:
    JNSt [EAX+SSS.Purpose],sssPurposeDRECTVE,.99:
    MOV [%DrectveSegm],EAX
    BufferRetrieve [EAX+SSS.EmitBuffer]
    LEA EDX,[ESI+ECX]
    MOV [%DrectveTop],EDX
    JSt [EBX+PGM.Pgmopt.Status],pgmoptELFbased,.ELF:
    CALL .Parse:
    JMP .90:
.ELF:
    LODSD                                        ; namesz DWORD (unaligned).
    Align2Dword EAX
    MOV ECX,EAX
    LODSD                                        ; descsz DWORD (unaligned).
    Align2Dword EAX
    LEA ESI,[ESI+4+ECX]                          ; Skip type and name.
    LEA EDX,[ESI+EAX]                            ; End of desc.
    CALL .Parse:
    CMP EDX,[%DrectveTop]
    JB .ELF:                                     ; When they are more then 1 concatenated PT_NOTE ELF sections.
    JMP .90:

; Directive handlers. They may destroy any GPR but EBP. Return via plain RET.
;  Input: EBX=^PGM,
;         ESI,ECX=Value,
;         EBP=local variables frame.

.E6120:LEA EDX,[%ValuePtr]
    Msg '6120',EDX                               ; Symbol "!1S" not found.
    RET

.ENTRY:: ; Handler of directive /ENTRY:EntrySymbolName. It declares executable entry point.
    PoolStore [EBX+PGM.Pool],ESI,ECX
    MOV [EBX+PGM.Pgmopt.EntryPtr],EAX
    MOV [EBX+PGM.Pgmopt.EntrySize],ECX
    RET

.EXPORT:: ; Handler of directive /EXPORT:ExportedSymbolName. It marks the symbol as symExport.
          ; It is used to declare exportness of a symbol inside the module for dynamic linking.
    Invoke SymFindByName::,0,ESI,ECX,EBX
    JC .E6120:
    SetSt [EAX+SYM.Status],symExport
    RET

.IMPORT:: ; Handler of directive /IMPORT:ImportedSymbolName:"DllName".
          ; It creates/updates the symbol as symImport. DllName is optional.
    TEST ECX
    JZ .I9:
    MOV EDI,ESI                                  ; Beginning of the value.
    LEA EDX,[ESI+ECX]                            ; End of value.
.I1:CMP ESI,EDX
    JNB .I3:
    LODSB
    CMP AL,':'                                   ; Search for : or = which terminates ImportedSymbolName.
    JE .I2:
    CMP AL,'='
    JNE .I1:
.I2:DEC ESI
.I3:MOV ECX,ESI
    SUB ECX,EDI                                  ; EDI,ECX is now ImportedSymbolName.
    Invoke SymFindByName::,0,EDI,ECX,EBX
    JNC .I4:
    ; Create imported symbol named EDI,ECX in program EBX.
    ListNew [EBX+PGM.SymList],Zeroed=yes
    MOV [EAX+SYM.NamePtr],EDI
    MOV [EAX+SYM.NameSize],ECX
    XCHG EAX,EDI                                 ; EAX is now volatile symbol name, EDI=^SYM.
      PoolStore [EBX+PGM.Pool],EAX,ECX
      MOV [EDI+SYM.NamePtr],EAX
    XCHG EDI,EAX
.I4:MOV EDI,EAX                                  ; EDI is now the symbol which should be marked as imported.
    SetSt [EDI+SYM.Status],symImport
    Invoke SssCreateExtern::,EDI,EBX             ; Accompany the imported symbol with its extern pseudosegment.
    CMP ESI,EDX                                  ; At the end of value?
    JNB .I7:                                     ; If no explicit DllName follows.
    ; ImportedSymbolName is followed with colon and DllName in double quotes.
    LODSB                                        ; Skip the : or =.
    CMP ESI,EDX
    JNB .I7:                                     ; No explicit DllName follows.
    LODSB
    MOV AH,AL                                    ; Double quote expected.
    CMP AL,'"'
    JNE .I7:                                     ; Treat invalid DllName as default "kernel32.dll".
    MOV [EDI+SYM.DllNamePtr],ESI
.I5:CMP ESI,EDX
    JNB .I7:                                     ; Treat invalid DllName as default "kernel32.dll".
    LODSB
    CMP AL,AH
    JNE .I5:
    DEC ESI
    SUB ESI,[EDI+SYM.DllNamePtr]
    MOV [EDI+SYM.DllNameSize],ESI
    TEST ESI
    JZ .I7:
    PoolStore [EBX+PGM.Pool],[EDI+SYM.DllNamePtr],ESI,ZeroTerminate=YES
    MOV [EDI+SYM.DllNamePtr],EAX                 ; Make DllName persistent.
    RET
.I7:; No valid DllName provided, assume "kernel32.dll".
    MOV [EDI+SYM.DllNamePtr],=B"%EuroasmDefaultDllName"
    MOV [EDI+SYM.DllNameSize],%EuroasmDefaultDllNameSize
.I9:RET
                                                 ; End of directive handlers.
.Parse: PROC                                     ; Handle string ESI..EDX with directives for program EBX.
    ; Search for the prefix of directive /Name. It starts with / or -.
.10:CMP ESI,EDX
    JNB .80:
    LODSB
    CMP AL,'/'
    JE .20:
    CMP AL,'-'
    JNE .10:
.20:MOV [%NamePtr],ESI
    XOR EAX,EAX
    MOV [%ValuePtr],EAX
    MOV [%ValueSize],EAX
    MOV [%DllNamePtr],EAX
    MOV [%DllNameSize],EAX
    ; Search for the suffix which terminates the /Name (colon, equal or space).
.30:CMP ESI,EDX
    JNB .40:
    LODSB
    ExpClassify AL
    CMP AL,':'
    JE .35:
    CMP AL,'='
    JE .35:
    CMP AH,expWhiteSpace
    JNE .30:
.35:DEC ESI
.40:MOV ECX,ESI
    SUB ECX,[%NamePtr]
    MOV [%NameSize],ECX
    INC ESI                                      ; Skip the suffix.
.45:; Search for the value. It may be in quotes.
    CMP ESI,EDX
    JNB .75:
    LODSB
    ExpClassify AL
    CMP AH,expWhiteSpace
    JE .45:
    CMP AH,expQuote
    JNE .55:
    MOV AH,AL                                    ; Value is in single or double quotes AL=AH.
    MOV [%ValuePtr],ESI
.50:CMP ESI,EDX
    JNB .10:                                     ; Silently abandon the invalid value because it is not properly terminated.
    LODSB
    CMP AL,AH                                    ; Is it the terminating quote?
    JNE .50:
    MOV ECX,ESI
    DEC ECX
    SUB ECX,[%ValuePtr]
    MOV [%ValueSize],ECX                         ; Netto size without quotes.
    JMP .75:
.55:DEC ESI                                      ; Back to the first nonwhite value character.
    MOV [%ValuePtr],ESI                          ; Value is unquoted.
.60:CMP ESI,EDX
    JNB .70:                                     ; End of the value found.
    LODSB
    CMP AL,','                                   ; Unquoted comma terminates the value.
    JE .65:
    ExpClassify AL
    CMP AH,expWhiteSpace
    JNE .60:
.65:DEC ESI                                      ; Unquoted comma or space terminated the value.
.70:MOV ECX,ESI
    SUB ECX,[%ValuePtr]
    MOV [%ValueSize],ECX
.75:; Name and value was succesfully parsed.
    Invoke DictLookup::,DictDrectve::,[%NamePtr],[%NameSize]
    JC .10:                                      ; Silently ignore when the name is not among supported directives.
    PUSHAD                                       ; EAX is now the directive handler, e.g. PfDrectveDestroy.EXPORT::.
      LEA ECX,[%NamePtr]
      LEA EDX,[%ValuePtr]
      Msg '0563',ECX,EDX                         ; Accepting link directive /!1S:!2S.
      MOV ESI,[%ValuePtr]
      MOV ECX,[%ValueSize]
      CALL EAX                                   ; Execute the handler.
    POPAD
    JMP .10:
.80:RET
    ENDP .Parse:

.90:MOV EDX,[%DrectveSegm]
    Invoke SymFindByName::,0,[EDX+SSS.NamePtr],[EDX+SSS.NameSize],EBX
    JC .95:
    ListRemove [EBX+PGM.SymList],EAX             ; Discard the .drectve (symSe) symbol.
.95:ListRemove [EBX+PGM.SssList],EDX             ; Discard the [.drectve] segment.
.99:EndProcedure PfDrectveDestroy
↑ PfSuboperate Program, OutStream
Procedure PfSuboperate resolves suboperations specified in program option, such as PROGRAM OUTFILE="file.bin"[256..]. If no suboperation is requested, or if the OUTFILE= is left empty (default), this procedure does nothing.
Otherwise it will trim the OutStream and also remove suboperators from Program.Pgmopt.OutFile specification.
Input
Program Pointer to a completely assembled PGM object.
OutStream is pointer to STREAM which contains the complete assembled and linked output file.
Output
EAX pointer to an output STREAM with suboperated output file. It will be identical with input %OutStream when no suboperations are required.
Error
Errors are reported with macro Msg.
Invoked by
PfOutput
Tested by
t7121 t7122 t7123
Invokes
EaBufferRelease EaBufferReserve ExpConvertToNumber ExpEval ExpParseRange ExpParseSuboperation VarExpandField
PfSuboperate  Procedure Program, OutStream
PfSopOutFileSize LocalVar ; Filename size with removed suboperations prepared for return.
PfSopOutFileEnd  LocalVar ; ^Behind the last closing bracket.
PfSopStart       LocalVar ; ^Opening bracket of one suboperation.
PfSopEnd         LocalVar ; ^Behind the closing bracket of one suboperation.
PfSopLeftPtr     LocalVar ; ^Left range expression.
PfSopLeftEnd     LocalVar ; ^Behind the left range expression.
PfSopRightPtr    LocalVar ; ^Right range expression.
PfSopRightEnd    LocalVar ; ^Behind the right range expression.
PfSopLeftVal     LocalVar ; Left range value.
PfSopRightVal    LocalVar ; Right range value.
PfSopStatus      LocalVar ; Bit 1 is set if the range covers both left and right value.
PfSopBuffer      LocalVar ; Temporary buffer for range calculation.
PfSopStream      LocalVar ; Temporary substream for suboperation.
PfSopExp         LocalVar Size=SIZE# EXP
    MOV EAX,[%OutStream]
    MOV EBX,[%Program]
    MOV [%ReturnEAX],EAX                   ; Prepare for the case when no suboperation is required.
    Invoke EaBufferReserve::,PfSuboperate
    MOV [%PfSopBuffer],EAX
    MOV EDI,[EBX+PGM.Pgmopt.OutFilePtr]
    MOV ECX,[EBX+PGM.Pgmopt.OutFileSize]
    MOV ESI,EDI
    MOV [%PfSopOutFileSize],ECX
    LEA EDX,[EDI+ECX]                      ; End of suboperated filename (behind the last closing bracket).
    MOV [%PfSopOutFileEnd],EDX
    ; Leading quote of filename was already removed, ESI,ECX may be e.g.file.bin"{5..%&-4}[256..].
    MOV AL,'"'
    REPNE SCASB
    JNE .90:                               ; If no valid suboperation.
    MOV [%PfSopStart],EDI                  ; EDI now should point to the opening bracket following the quote. Otherwise E8572.
    LEA EAX,[EDI-1]
    SUB EAX,ESI
    MOV [%PfSopOutFileSize],EAX            ; Size with removed suboperations prepared for return.
.10: ; EDI..EDX must be a suboperations chain, e.g. {5..%&-4}[256..], or empty.
    CMP EDI,EDX
    JNB .90:                               ; If empty chain, we're done.
    Invoke ExpParseSuboperation::,EDI,EDX  ; Returns ESI at the end of 1st suboperator (closing bracket).
    JC .E8572:                             ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
    ; EDI..ESI is now one valid suboperator, e.g. {5..%&-4}.
    MOV [%PfSopEnd],ESI
    INC EDI
    DEC ESI                                ; Strip off the brackets.
    RstSt [%PfSopStatus],1
    Invoke ExpParseRange::,EDI,ESI         ; Returns EAX behind the range operator.
    MOV [%PfSopLeftPtr],EDI
    MOV [%PfSopRightPtr],EAX
    MOV [%PfSopRightEnd],ESI
    JC .20:                                ; If no range operator .. was found in EDI..ESI. Returned EAX=ESI.
    SetSt [%PfSopStatus],1                 ; EAX points behind the range operator ...
    SUB EAX,2 ; Skip the range operator.
.20:MOV [%PfSopLeftEnd],EAX                ; Both range expressions are parsed now.
    MOVD [%PfSopLeftVal],1                 ; Default.
    StreamReset [%ReturnEAX]
    CMPB [EDI-1],'{'
    JE .30:
    StreamGetSize [%ReturnEAX]
    JMP .32:
.30:StreamGetLines [%ReturnEAX]
.32:MOV [%PfSopRightVal],EAX ; Default.
    LEA EDX,[%PfSopExp]
    BufferClear [%PfSopBuffer]             ; Prepare to evaluate the left range value.
    Invoke VarExpandField::,[%PfSopLeftPtr],[%PfSopLeftEnd],[%PfSopBuffer],EAX ; Expand %&.
    BufferRetrieve [%PfSopBuffer]
    StripSpaces ESI,ECX
    JECXZ .38:                             ; Leave empty left range at default=1.
    Invoke ExpEval::,EDX,ESI,ECX,0
    JC .E8572:                             ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
    Invoke ExpConvertToNumber::,EDX
    JC .E8572:                             ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
    MOV ECX,[EDX+EXP.Low]
    MOV [%PfSopLeftVal],ECX
    JMPS .40:
.38:SetSt [%PfSopStatus],1
.40:BufferClear [%PfSopBuffer]             ; Evaluate the right range value.
    Invoke VarExpandField::,[%PfSopRightPtr],[%PfSopRightEnd],[%PfSopBuffer],EAX
    BufferRetrieve [%PfSopBuffer]
    StripSpaces ESI,ECX
    JECXZ .45:                             ; Leave empty right range at default=%&=[%PfSopRightVal].
    Invoke ExpEval::,EDX,ESI,ECX,0
    JC .E8572:                             ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
    Invoke ExpConvertToNumber::,EDX
    JC .E8572:                             ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
    MOV ECX,[EDX+EXP.Low]
    MOV [%PfSopRightVal],ECX
    JMP .50:
.45:JSt [%PfSopStatus],1,.50:
    MOV ECX,[%PfSopLeftVal]
    MOV [%PfSopRightVal],ECX
.50:StreamCreate [EBX+PGM.Pool]            ; Both range values are calculated now.
    MOV [%PfSopStream],EAX
    StreamReset [%ReturnEAX]               ; Copy suboperated stream [%ReturnEAX] to the new [%PfSopStream].
    SUB EDX,EDX                            ; Line counter.
    MOV ECX,[%PfSopLeftVal]
.60:INC EDX
    CMP EDX,ECX
    JNL .70:
    CMPB [EDI-1],'{'
    JE .65:
    StreamReadByte [%ReturnEAX]            ; Substring - skip 1 byte.
    JMP .60:
.65:StreamReadLn [%ReturnEAX],0            ; Sublist - skip 1 line.
    JMP .60:
.70:CMP EDX,[%PfSopRightVal]
    JG .85:
    CMPB [EDI-1],'{'
    JE .75:
    StreamReadByte [%ReturnEAX]            ; Substring - read 1 byte.
    StreamStoreByte [%PfSopStream],AL
    INC EDX
    JMP .70:
.75:BufferClear [%PfSopBuffer]
    StreamReadLn [%ReturnEAX],[%PfSopBuffer] ; Sublist - read 1 line.
    BufferRetrieve [%PfSopBuffer]
    StreamStore [%PfSopStream],ESI,ECX
    INC EDX
    JMP .70:
.85: ; [%PfSopStream] is suboperated now. It will replace current stream at [%ReturnEAX].
    MOV EAX,[%PfSopStream]
    MOV [%ReturnEAX],EAX
    MOV EDI,[%PfSopEnd]
    MOV EDX,[%PfSopOutFileEnd]
    JMP .10:                               ; Suboperators may chain.
.E8572:LEA EAX,[EBX+PGM.Pgmopt.OutFilePtr]
     Msg '8572',EAX                        ; Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.
.90:Invoke EaBufferRelease::,[%PfSopBuffer]
    MOV EAX,[%PfSopOutFileSize]
    MOV EDI,[EBX+PGM.Pgmopt.OutFilePtr]
    MOV [EBX+PGM.Pgmopt.OutFileSize],EAX   ; Remove suboperations from outfile name.
    MOVB [EDI+EAX],0                       ; Zero terminate the filename.
   EndProcedure PfSuboperate
  ENDPROGRAM pf

▲Back to the top▲