EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

msg.htm
Tuning
MsgTune
Encoding
MsgEncoding
Macros
Msg
MsgUnexpected
Procedures
MsgProc
Definitions
MsgTexts
Informative messages
Debugging messages
Warning messages
User-generated messages
Error messages
Fatal messages

This module defines texts of all €ASM messages, which are published on standard output and most of them is written into listing file too.

Message written to listing is prefixed with search-marker |# |## |###.

Message written to output is suffixed with position indicator in the source, for instance "file.asm"{12}, where "file.asm" is the (included) source file name without path, and {12} specifies the physical line number where the issue occured.

If the error was detected in macro expansion, multiple position indicators are appended, one for each level of macro nesting.

See also the chapter Messages in manual.


msg PROGRAM FORMAT=COFF,MODEL=FLAT,WIDTH=32
 INCLUDEHEAD "euroasm.htm" ; Interface (structures, symbols and macros) of other modules.
 
msg HEAD ; Start of module interface.
↑ MsgEncoding
Enumerated Boolean flags which are used to control error reporting in some procedures.
msgSuppress  = 0               ; Do not report warnings and errors.
msgReport    = ! msgSuppress   ; Report detected warnings and errors.
↑ Msg cc=, PgmStatus=, MsgId, Par1, Par2,,,,
Macro Msg writes a text message to the console (standard output), and to STM.MsgBuffer (the message buffer of current statement). The message buffer contents will be written into listing in the final pass.
Input
cc= is the condition code which specifies when the message is valid. Message is output unconditionally if this keyword is omitted (default).
PgmStatus= can be one of PGM.Status flag which must be set, otherwise the message is not published. Most often only pgmLastPass is employed here. Default is empty (publish the message in each pass).
Regardless of PgmStatus, any message will be supressed if current Pgm.Status:pgmNoMsg is set. This flag is used in fake statement parsing, e.g. in HEAD block detection in ChunkSubHead.
MsgId is 32bit GP register or immediate message identifier which contains string of four decimal digits.
ParX are zero to nine message parameters which will be expanded in the message text.
Output
Macro Msg keeps all CPU registers and flags unchanged.
The message is written to standard output and to statement MsgBuffer.
Errorlevel is modified in the current program and in its parent objects by the most significant digit of MsgId.
When the message is supressed with cc= or PgmStatus= or with EUROASM option NOWARN=, errorlevel is not modified.
Errors
Fatal error F9999 is issued when the provided MsgId is not found among defined messages.
Examples
Msg '1234',256 Msg cc=C,'3456',EBX Msg PgmStatus=pgmLastPass, EAX,EBX
Invoked from
almost all €ASM procedures.
See also
MsgProc, MsgUnexpected, MsgTexts.
Msg %MACRO cc=, PgmStatus=, MsgId, params
     %IF "%cc" !=== ""
      J%!cc .Msg%.
     %ENDIF
     %IF "%PgmStatus" !=== ""
       MOVB [MsgPgmStatus::],%PgmStatus
     %ENDIF
     %IF %#>1
  p   %FOR %#..2
       PUSHD %*{%p} ; Push message parameters, if any, start from the last.
      %ENDFOR p
     %ENDIF
     PUSHD %MsgId  ; Message identification number.
     PUSHD %#-1 ; Number of message parameters.
     CALL MsgProc::
.Msg%.
    %ENDMACRO Msg
↑ MsgUnexpected cc=, target=
Macro MsgUnexpected throws fatal error F9998 when condition cc occured where it never should happen. The message is completed with EuroAssembler source position.
Input
cc= Condition code constraint specifying when the message is valid. Message is output unconditionally if this keyword is omitted.
target= label where to jump after F9998 was issued. This is used to abort curent procedure when unexpected condition occured. No jumping if omitted.
Output
Macro MsgUnexpected keeps all CPU registers and flags unchanged.
Example
MsgUnexpected cc=C
MsgUnexpected %MACRO cc=, target
    %IF "%cc" !=== ""
:     J%!cc .MsgUnexp%.:
    %ENDIF
    PUSHD %^PROC
    PUSHD %^SOURCELINE
    PUSHD =B"%^SOURCEFILE"
    PUSHD '9998'
    PUSHD 2
    CALL MsgProc::
   ;   Msg '9998',=B"%^SOURCEFILE",%^SOURCELINE ; Unexpected EuroAssembler behaviour of procedure !3$ in "!1$"{!2D}.
    %IF "%target" !=== ""
      JMP %target
    %ENDIF 
 .MsgUnexp%.:
   %ENDMACRO MsgUnexpected
    
    ENDHEAD msg ; End of module interface.
↑ MsgTune
Parameters for tuning of messages appearance.
MsgMaxSize    EQU 256
MsgParMaxSize EQU 28 ; Longer params in MsgText are trunc~~ated from the middle.
MsgPar_Size   EQU 12 ; Max. size of !1_ parameter, suffixed with ~~
MsgSrcPosSize EQU 72 ; Max.size of source position records "file.asm"{lineNr}.
↑ MsgProc
PROC MsgProc is called from macro Msg or MsgUnexpected using special calling convention with variable number of parameters pushed on stack. The last pushed parameter is the number of parameters, the last but one is message identifier '0000'..'9999'.
The procedure interprets message text and replaces parameters with their values.
Expanded by
Msg
Invokes
CtxPeek PgmGetCurrent SrcPosition
[.text]
    PUBLIC MsgProc
MsgProc PROC 
    PUSHAD
    PUSHFD
    MOV EBP,ESP
%MsgPar   %SET EBP+48 ; The first of provided parameters, if [%MsgParNr] > 0.
%MsgId    %SET EBP+44 ; Message identifier.
%MsgParNr %SET EBP+40 ; Number of pushed parameters.
          SUB ESP,MsgMaxSize+MsgSrcPosSize+8 ; Make room for local variables.
%MsgWrongId    %SET EBP-4 ; Used when Msg is invoked with unknown Id.
%MsgTextConPtr %SET EBP-8 ; Pointer inside %MsgText used for console output.
%MsgText       %SET EBP-(MsgMaxSize+MsgSrcPosSize+8) ; Here will be the message string completed.
    ; Examine current program status (flag pgmNoMsg).
    Invoke PgmGetCurrent::
    JC .05: ; Do not suppress messages when no program is created yet.
    MOV EBX,EAX
    JSt [EBX+PGM.Status],pgmNoMsg,.90: ; If messages are not allowed.
    MOVZX ECX,[MsgPgmStatus] ; Static memory variable for communication with macro Msg.
    MOVB [MsgPgmStatus],0 ; Reset after use.
    JECXZ .05: ; Do not suppress messages when not requested with MsgPgmStatus.
    JNSt [EBX+PGM.Status],ECX,.90: ; If MsgPgmStatus doesn't match, supress the message.
; Check if the Msg is suppressed with EUROASM NOWARN=.
 .05:LEA ESI,[%MsgId] ; Pointer to four decimal digits.
    LEA EDI,[ESI+4]
    LodD ESI,Size=4
    JC .10: ; Wrong Id - no suppress.
    CMP ESI,EDI ; Four digits loaded?
    JNE .10:
    CMP EAX,4000 ; Maximal suppressible MsgId.
    JAE .10:
    MOV EBX,EAX ; Decadic Id value 0..9999.
    MOV ECX,EBX
    SHR EBX,3
    AND ECX,7
    BT [Ea.Eaopt.NoWarn:: + EBX],ECX
    JC .90: ; If NoWarn bit is set, supress the message.
   ; Message is not supressed.
.10:MOV EBX,[%MsgId]
    MOV EDI,MsgText ; Static text definitions of all messages.
    MOV ECX,MsgTextEnd-MsgText
    SUB EAX,EAX
    MOV [%MsgWrongId],EAX
    CMP BL,'5' ; User-generated error?
    JNE .15:
    MOV EDI,Msg5000:  ; DB '5000 !1S
    MOV [EDI],EBX
    JMPS .30:
.15:REPNE SCASB ; Find end of previous MsgText line.
    JECXZ .25:
    CMP EBX,[EDI] ; Is it the MsgId at the beginning of line?
    JNE .15:      ; If not, search the next line.
    JMPS .30:
.25:MOV EDI,MsgUnspec:
    MOV [MsgUnspecNr],EBX
    MOV EBX,'9999'
.30: ; Msg text found. EDI now points to MsgText starting with 4digit MsgId.
    LEA ESI,[%MsgText]
    XCHG ESI,EDI
    ; The text from MsgText specified with ESI will be safe-copied to EDI,
    ; trimmed if necessarry, formated for listing, !parameters expanded.
    LEA EDX,[EDI+MsgMaxSize-2] ; End of reserved space.
    ; Search marker.
    MOV AX,"|#" ; Informative messages start with |# I0123
    STOSW
    AND EBX,0Fh ; Severity level 0..9
    MOV AL,AH ; "#"
    CMP BL,1
    JNA .40:
    STOSB ; Warnings start with |## W2345
    CMP BL,4
    JNA .40:
    STOSB ; Errors start with |### E6789
.40:MOV AL," "
    STOSB
    MOV [%MsgTextConPtr],EDI ; Search marker "|###" is not sent to StdOut, skip it.
 ; Prefix message numeric identifier with severity letter.
    MOV AL,[MsgPrefixCharTab+EBX] ; 'I','D','W','U','E','F'.
    STOSB
 ; Propagate errorlevel to parent objects (PGM, Src, Ea).
    Invoke PgmGetCurrent::
    JC .45:
    CMP EBX,[EAX+PGM.Errorlevel]
    JBE .45:
    MOV [EAX+PGM.Errorlevel],EBX
.45:CMP EBX,[Src.Errorlevel::]
    JBE .50:
    MOV [Src.Errorlevel::],EBX
.50:CMP EBX,[Ea.Errorlevel::]
    JBE .55:
    MOV [Ea.Errorlevel::],EBX
  ; Safe-copy message text.
.55:LODSB
    CMP AL,0
    JE .80:    ; End of line.
    CMP AL,32
    JNB .60:
    MOV AL,32 ; Control characters replace with spaces.
.60:CMP AL,'!' ; This may mark an expandable parameter in message text.
    JE .70:
    CMP AL,'|' ; This character must not appear in output, as it would terminate machine comment.
    JNE .65:
    MOV AL,'!' ; Replace '|' with visually similar '!'.
.65:CMP EDI,EDX
    JNB .80:
    STOSB ; Safe copy AL to %Msgtext.
    JMP .55:
.70: ; Expand !parameter.
    LODSB ; Ordinal number of parameter '1'..'9'.
    CMP AL,'!'
    JE .65: ; Double exclamation mark interpret as a single '!'.
    AND EAX,0Fh
    CMP EAX,[%MsgParNr]
    JA .55: ; If parameter not provided by %Msg, skip.
    LEA EBX,[%MsgPar-4+4*EAX]
    MOV EBX,[EBX] ; EBX now contains the 32bit value of pushed parameter.
    LODSB ; Presentation mode ('D', 'K', 'H',,,)
    PUSH EDX,ESI
      CALL .ExpandPar:
    POP ESI,EDX
    JMP .55:
.80:CMPB [EDI-1]," "
    JNE .81:
    DEC EDI       ; Trim the trailing white spaces.
.81:MOV AX,0x0A0D ; End of msg line.
    STOSW
    SUB EAX,EAX
    MOV ECX,EDI
    STOSB
    LEA ESI,[%MsgText]
    SUB ECX,ESI ; ESI,ECX is now formated for listing.
    ; Decide if the message goes to listing file, too.
    MOV EBX,[Src.CurrentStm::]
    MOV EAX,[ESI+4] ; MsgId.
    AND EAX,0x00FFFFFF
    CMP EAX,'056'
    JE .83: ; Informative messages about linking I056* are listed.
.82:CMPD [ESI],'|# I' ; Other informative messages are not listed.
    JE .85:
.83:TEST EBX
    JZ .85:
    BufferStore [EBX+STM.MsgBuffer],ESI,ECX ; Write message to the listing.
.85: ; Append source position before sending the message to StdOutput.
    LEA EDI,[ESI+ECX-2] ; Rewrite CR+LF+NULL at the end of %MsgText.
    ADD EDX,MsgSrcPosSize ; Prolong the room in %MsgText.
    CALL .AppendSrcPos:
    SysOutConsole [%MsgTextConPtr] ; Display Msg to console.
.90:MOV ESP,EBP
    POPFD
    MOV EBX,[%MsgParNr] ; EBX is now 0..9 (how many parameters was MsgProc invoked with).
    LEA EAX,[.Return+4*EBX] ; Select stack frame return code depending on number of parameters.
    JMP EAX
.Return:
p  %FOR 0..36, STEP=4 ; Emit ten variants of return code (0..9 Msg arguments).
      POPAD
      RET %p+8, IMM=WORD
    %ENDFOR p

.AppendSrcPos:: PROC ; Write src position in the form of "file.asm"{line}, context aware.
; Input: EDI=pointer in %MsgText buffer where the src position should be written.
;        EDX=pointer to end of buffer which must not be exceeded.
;        EBX=^STM (may be 0).
;        EBP=caller stack frame.
     TEST EBX
     JZ .90:
     LEA EAX,[EDI+MsgParMaxSize+14]
     CMP EAX,EDX
     JA .90: ; Not enough room for LinePtr, omit.
     MOV EBX,[EBX+STM.LinePtr]
     PUSH EDX
       MOV AL," "
       STOSB
       CALL MsgProc.StoreSrcPos:
     POP EDX
     SUB EAX,EAX
 .20:Invoke CtxPeek::,ctxMACRO,EAX ; Find other src positions, if a macro is being expanded.
     JC .80:
     JNSt [EAX+CTX.Status],ctxExpansion,.20: 
     PUSH EAX,EDX
       LEA ECX,[EDI+MsgParMaxSize+14]
       CMP ECX,EDX
       JA .30:
       MOV EBX,[EAX+CTX.LineNext]
       DEC EBX ; LinePtr of macro invocation.
       MOV AL," " ; Separate src position(s) with one space.
       STOSB
       CALL MsgProc.StoreSrcPos:
 .30:POP EDX,EAX
     JMP .20:
 .80:CMPB [EDI-1]," "
     JNE .81:
     DEC EDI
 .81:MOV AL,13 ; CR+LF at the end of msg line.
     STOSB
     MOV AL,10
     STOSB
     SUB EAX,EAX 
     STOSB ; Zero terminate string.
 .90:RET
     ENDP .AppendSrcPos:

.StoreSrcPos: PROC ; Store one SrcPos in the form of "file.asm"(lineNr} to EDI.
; Input:EBX=LinePtr is pointer to physical line in memory-mapped source or memory-mapped "euroasm.ini".
;      EDI=pointer where to store position. Enough room for MsgParMaxSize bytes is guaranteed.
       PUSH EDI
         Invoke SrcPosition::,EBX ; Returns EDI=^filename, EAX=physical line number
         MOV ESI,EDI
       POP EDI  
       JC .90: ; Store nothing to EDI if file not found.
       ; ESI points to ASCIIZ file name, EAX=line number.
       PUSH EAX
         MOV AL,'"' ; File name is stored in double quotes.
         STOSB
         SUB EAX,EAX
         MOV ECX,MAX_PATH_SIZE
         PUSH EDI
           MOV EDI,ESI
           REPNE SCASB
           LEA ECX,[EDI-1]
         POP EDI
         SUB ECX,ESI ; Filename.ext size.
         CMP ECX,MsgParMaxSize-14
         JBE .50:
         PUSH ECX,ESI ; Filename ESI,ECX too long.
          MOV ECX,MsgParMaxSize/2-8
          REP MOVSB ; Store the first part of long filename.
         POP ESI,ECX
         MOV AL,'~'
         STOSB  ; Store ~~ marker.
         STOSB
         LEA ESI,[ESI+ECX-(MsgParMaxSize/2-8)]
         MOV ECX,MsgParMaxSize/2-8
 .50:    REP MOVSB ; Store the (trailing part of long) filename.
         MOV AL,'"'
         STOSB
         MOV AL,'{'
         STOSB
        POP EAX ; Line number. 
        StoD EDI ; Store decadic line number.
        MOV AL,'}'
        STOSB
 .90:  RET
      ENDP .StoreSrcPos:
    
.ExpandPar: PROC ; Write the value of Msg parameter to MsgText.
; Input: AL=presentation mode ('D','K','H',...)
;        EBX=parameter value as it was pushed on stack in macro Msg invocation.
;        EDI=output position in %MsgText buffer.
;        EBP=caller's stack frame.
; Output:EDI advanced, EBP preserved, other GPR undefined.
    Dispatch AL,'D','K','H','W','B','C','Z','$','_','S','L','@','R','O','Q'
    JMP .90: ; None dispatched: wrong format marker.
.D: MOV EAX,EBX  ; Format D: decimal.
    StoD EDI
    RET
.K: MOV EAX,1K-1 ; Format K: Kilo/Mega/Decimal if EBX is the power of 210.
    TEST EBX
    JZ .D:
    TEST EBX,EAX
    JNZ .D:
    SAR EBX,10
    MOV DL,'K'
    TEST EBX,EAX
    JNZ .K5:
    SAR EBX,10
    MOV DL,'M'
.K5:CALL .D:
    MOV EAX,EDX
    STOSB
    RET
.Q: MOV EAX,[EBX+0]; Format Q: pointer to QWORD integer.
    CDQ
    CMP EDX,[EBX+4]
    JE .H1:        ; If the signed QWORD fits to 32 signiticant bits, display it as 8 hexa digits.
    MOV EDX,[EBX+4]
    StoQH EDI, Size=16 ; Otherwise display the full 16 hexa digits.
    RET
.H: MOV EAX,EBX    ; Format H: hexa 32 bits.
.H1:StoH EDI, Size=8
    RET
.W: MOV EAX,EBX    ; Format W: hexa 16 bits.
    AND EAX,0xFFFF
    StoH EDI, Size=4
    RET
.B: MOV EAX,EBX    ; Format B: hexa 8 bits.
    AND EAX,0xFF
    StoH EDI,Size=2
    RET
.Z: MOV EAX,EBX    ; Format Z: safe store one character.
    CMP AL," "
    JAE .Z6:
    MOV AL," "     ; Replace control character with space.
.Z6:CMP AL,'|'
    JNE .Z8:
    MOV AL,'!'     ; Replace end-of-machine-comment with exclamation.
.Z8:STOSB
    RET
.C: MOV EAX,EBX    ; Format C: character constant.
    MOV ECX,4
.C2:CMP AL," "
    JAE .C3:
    MOV AL," "
.C3:CMP AL,'|'
    JNE .C5:
    MOV AL,'!'
.C5:STOSB
    SHR EAX,8
    LOOP .C2:
    RET
.$: TEST EBX       ; Format $: ASCIIZ string.
    JZ .$9:
    MOV EDX,EDI    ; Temporary save EDI.
    MOV EDI,EBX
    MOV ECX,-1
    SUB EAX,EAX
    REPNE SCASB
    LEA ECX,[EDI-1]
    MOV ESI,EBX
    SUB ECX,EBX
    MOV EDI,EDX
.$2:; ESI,ECX is parameter string.
    JECXZ .$9:
    CMPB [%MsgId+0],'5' ; For messages U5xxx do not shorten parameter value.
    JE .$6:
    CMPW [%MsgId+0],'10'
    JNE .$3:
    CMPD [%MsgId+0],'1010'
    JNE .$6:  ; For messages D10xx (but not D1010) do not shorten parameter value.
.$3:CMP ECX,MsgParMaxSize
    JNA .$6:
    MOV EDX,ECX
    MOV ECX,MsgParMaxSize/2-1 ; Replace the middle of long par value with ~~.
    CALL .$6:
    MOV AL,"~"
    STOSB
    STOSB
    LEA ESI,[ESI+EDX-MsgParMaxSize+2]
    MOV ECX,MsgParMaxSize/2-1
.$6:LODSB
    CMP AL,'|'
    JNE .$7:
    MOV AL,'!'
.$7:CMP AL," "
    JAE .$8:
    MOV AL," "
.$8:STOSB
    LOOP .$6:
.$9:RET

.R:     ; Format R: register name.
    MOV EDX,DictRegisters:: - SIZE#DICT
.R1:ADD EDX,SIZE#DICT
    MOV ECX,[EDX+DICT.Size]
    MOV ESI,[EDX+DICT.Ptr]
    JECXZ .R9:
    CMP BL,[EDX+DICT.Data] ; Compare register family and ordinal number.
    JNE .R1:
    REP MOVSB
.R9:RET

.O:     ; Format O: operation name.
    MOV ESI,[ExpEval.OperationNamesTable::-4 + 4*EBX] ; Operation names are zero-terminated.
.O1:LODSB
    CMP AL,0
    JE .R9:
    STOSB
    JMP .O1:
._: ;   MsgPar_Size   EQU 12 ; Max. size of !1_ parameter, suffixed with ~~
    MOV ECX,MsgPar_Size
._1:MOV AL,[EBX]
    INC EBX
    CMP AL,'|'
    JE ._9:
    CMP AL,' '
    JBE ._9: ; End of string.
    STOSB
    LOOP ._1:
    MOV AL,'~'
    STOSB
    STOSB
._9:RET
.S: TEST EBX ; Format S: string specified as DWORD NamePtr+DWORD NameSize.
    JZ ._9:
    CMP EBX,-1
    JE ._9:
    MOV ESI,[EBX]   ; Pointer to string.
    MOV ECX,[EBX+4] ; Size of the string.
    TEST ESI
    JZ ._9:
    CMP ESI,-1
    JE ._9:
    JMP .$2:
.L:           ; Format L: dictionary list.
    LEA EDX,[EDI+MsgParMaxSize-2]
.L1:MOV ECX,[EBX+DICT.Size]
    MOV ESI,[EBX+DICT.Ptr]
    JECXZ .L8: ; Dict End  reached.
    CMP EDI,EDX
    JNB .L3: ; Truncate long list.
    CALL .$2:
    MOV AL,','
    STOSB
    ADD EBX,SIZE#DICT
    JMP .L1:
.L3:MOV AL,'~'
    STOSB
    STOSB
    JMPS .L9:
.L8:DEC EDI ; Pop the last separating comma.
.L9:RET
    
.@: ; Format @: line pointer presented as "file.asm"{lineNr}.
    ; EBX is LinePtr. First find which file it belongs to.
    CALL MsgProc.StoreSrcPos:
.90:RET
     ENDP .ExpandPar:
    ENDP MsgProc::
↑ MsgTexts
Each message definition is zero-terminated. The first four characters are hexadecimal digits representing the identifier of the message. Nondecimal digits are avoided.
Message text may contain up to nine symbolic parameters whose values are provided by the calling macro Msg. The symbolic parameter consists of three characters:
  1. exclamation mark !
  2. ordinal number of the parameter1..9
  3. presentation mode marker

If the expanded parameter value is longer than MsgParMaxSize, it is truncated from the middle. Truncation is indicated with tildas ~~.

Msg parameter presentation modes
NotationDescriptionExample
!1DPar1 is numeric value presented as signed decimal number.1234
!1KPar1 is numeric value presented as multiple of K or M, if possible.64K
!1QPar1 is pointer to 64bit signed integer presented as 16 or 8 hexadecimal digits.FEDCBA98
!1HPar1 is numeric value presented as 8digit hexadecimal number.0012ABCD
!1WPar1 is numeric value presented as 4digit hexadecimal number.B012
!1BPar1 is numeric value presented as 2digit hexadecimal number.B0
!1CPar1 is numeric value presented as a character constant.abcd
!1ZPar1 contains one character in its LSB.X
!1SPar1 is pointer to two DWORDs which contain pointer and size of presented string. Any text.
!1$Par1 is pointer to zero-terminated string.Some text.
!1_Par1 is pointer to a string, truncated to MsgPar_Size if not zero-terminated sooner. Shorten~~
!1OPar1 contains in its LSB ordinal number of operation specified in %ExpOperationList, which is presented as an operation name. BitwiseAnd
!1RPar1 contains in its LSB register family and ordinal in Register encoding , which is presented as a register name.MM7
!1LPar1 is pointer to Dict* presented as a list of all enumerated names in this dictionary.B,W,D,~~Y,Z
!1@Par1 is pointer to physical line in the source presented as Nr.of line. "Filename.htm"{12}
!!Double exclamation !! in the message text is presented as a single mark.!
See also
MsgProc
[.data] ; Miscellaneous static data used by MsgProc
MsgUnspec: DB '9999 Unspecified EuroAssembler internal error #' ; If macro Msg expanded with unknown MsgId.
MsgUnspecNr:      DB 'xxxx.',0
MsgPrefixCharTab: DB "IDWWWUEEEF" ; MsgId prefix corresponds 
    ; with errorlevel 0123456789 
MsgPgmStatus::    DB 0 ; pgmLastPass flag may be set here to constrain message on last pass only.
MsgText           DB 0 ; Searching for message text by MsgId starts here.
↑ Informative messages 0000..0999
   ; 00?? EuroAssembler start.
 DB '0010 EuroAssembler version !1S started.',0
 DB '0020 Current directory is "!1$".',0
 DB '0050 Global option file "!1$" was created.',0
 DB '0060 Global option file "!1$" could not be created.',0 ; Euroasm.exe launched from read-only disk.
 DB '0070 Assembling global option file "!1$".',0
   ; 01?? Source start.
 DB '0160 Local option file "!1$" was not found.',0
 DB '0170 Assembling local option file "!1$".',0
 DB '0180 Assembling source file "!1$"!2S.',0
   ; 02?? Source envelope start.
 DB '0270 Assembling source "!1S".',0
   ; 03?? Source assembly.
 DB '0310 Assembling source pass !1D.',0
 DB '0320 Assembling source pass !1D - fixing.',0
 DB '0330 Assembling source pass !1D - final.',0
   ; 04?? Program start.
 DB '0470 Assembling program "!1S".',0
   ; 05?? Program assembly.
 DB '0510 Assembling program pass !1D.',0
 DB '0520 Assembling program pass !1D - fixing.',0
 DB '0530 Assembling program pass !1D - final.',0
 DB '0560 Linking !1S module "!2$".',0
 DB '0563 Accepting link directive ''/!1S:!2S''.',0
 DB '0570 Importing !1S library "!2$".',0
   ; 06?? Program end.
 DB '0650 Program "!1S" assembled in !2D passes with errorlevel !3D.',0   
 DB '0660 !1Dbit !2S !3S file "!4$" created, size=!5D.',0
   ; 07?? Source envelope end.
 DB '0750 Source "!1S" (!2D lines) assembled in !3D passes with errorlevel !4D.',0
 DB '0760 !1Dbit !2S !3S file "!4$" created from source, size=!5D.',0
  ; 08?? Source end.
 DB '0860 Listing file "!1$" created, size=!2D.',0
  ; 09?? EuroAssembler end.
 DB '0980 Memory allocation !1D KB. !2D statements assembled in !3D s.',0
 DB '0990 EuroAssembler terminated with errorlevel !1D.',0  
↑ Debugging | diagnostic messages 1000..1999
 DB '1000 ',0 ; Empty line separator.

 ; 10?? Debugging statement structure if EUROASM DisplayStm=enabled.
 DB '1010 **** DISPLAYSTM "!1S"',0
 DB '1020 label="!1S"',0
 DB '1030 prefix!1D="!2S"',0
 DB '1040 !1$ operation="!2S"',0
 DB '1050 ordinal operand number=!1D,value="!2S"',0
 DB '1060 keyword operand,name="!1S",value="!2S"',0

 ; 10?? Debugging instruction encoding  if EUROASM DisplayEnc=enabled.
 DB '1080 Emitted size=!1D,!2S.',0

 ; 1100..1799 Debugging EuroAssembler objects with pseudoinstruction %DISPLAY.
 DB '1100 **** %%DISPLAY All=!1S*',0
 DB '1150 **** %%DISPLAY Files',0
 DB '1160 "!1$",size=!2K,src=!3$',0
 DB '1170 "!1$",size=!2K,src=main',0
 DB '1180 "!1$",size=!2K,src=included in !3@',0
 DB '1200 **** %%DISPLAY Chunks',0
 DB '1210 "!1$"!2S,src=!3$,type=!4$,size=!5D,contents=''!6S''',0
 DB '1250 **** %%DISPLAY Groups, Segments, Sections',0
 DB '1260 [!1S],group!2S,src=!3@',0
 DB '1270  [!1S],purpose=!2$,width=!3D,align=!4K,combine=!5S,class="!6S",src=!7@',0
 DB '1280    [!1S],address=!2Hh,size=!3Hh=!3K,align=!4D,ref=!5Z,src=!6@',0
 DB '1300 **** %%DISPLAY Structures=!1S*',0
 DB '1310 !1S,size=!2K,align=!3K,purpose=!4$,ref=!5Z,src=!6@',0
 DB '1350 **** %%DISPLAY Context',0
 DB '1360 !1S !2S,src=!3$,emit=!4Z,%%.=!5D',0
 DB '1400 **** %%DISPLAY Symbols=!1S*',0
 DB '1410 **** %%DISPLAY UnfixedSymbols=!1S*',0
 DB '1420 **** %%DISPLAY FixedSymbols=!1S*',0
 DB '1430 **** %%DISPLAY UnreferencedSymbols=!1S*',0
 DB '1440 **** %%DISPLAY ReferencedSymbols=!1S*',0
 DB '1450 !1S,[!2S]:!3Hh,type=''!4Z'',size=!5K,scope=''!6$,ref=''!7Z'',fix=!8Z,src=!9@',0
 DB '1500 **** %%DISPLAY LiteralSymbols=!1S*',0
 DB '1550 **** %%DISPLAY Relocations',0
 DB '1560 [!1S]:!2Hh,target=[!3S]:!4Hh,frame=[!5S],width=!6D,type=!7$!8$',0
 DB '1600 **** %%DISPLAY Macros=!1S*',0
 DB '1610 !1S,entry=!2$,src=!3@',0
 DB '1700 **** %%DISPLAY Variables=%%!1S*',0
 DB '1710 **** %%DISPLAY AutomaticVariables',0
 DB '1720 name="%%!1$",value="!2S",size=!3D',0
 DB '1730 name="%%!1D",value="!2S",size=!3D',0
 DB '1740 **** %%DISPLAY FormalVariables=%%!1S*',0
 DB '1750 **** %%DISPLAY UserVariables=%%!1S*',0
 DB '1760 **** %%DISPLAY SystemVariables=%%^!1S*',0
 DB '1770 name="!1S",value="!2S",size=!3D',0
 DB '1780 name="!1S",value="!2S",size=!3D,volatile',0 ; %^TIME,%^DATE,%^VERSION,%^EUROASMOS,%^TIMESTAMP.
 DB '1790 **** End of %%DISPLAY',0

%IF %^PROFILE
 ; 1800..1899 Profiling messages.
 DB '1800 **** PROFILE',0
%ENDIF

%IF %^DEBUG
 ; 1900..1939 Internal debugging.
  DB '1911 Dispatching format "!1S".',0 ; See also E7511.
  DB '1912 Allocated memory pool at source line {!1D}:',0
  DB '1913 Pool=!1H, Gran=!2K, Total=!3H=!3K, Size=!4H=!4K',0
  DB '1914 Pool.Prev=!1H, Last=!2H, Ptr=!3H, Top=!4H.',0
  DB '1915   Poolblock=!1H, Prev=!2H, bottom=!3H, top=!4H.',0
  DB '1920 PGM^!1H:St=!2H,program !3S ******** EaDisplayPgm at "!4$"{!5D}',0
  DB '1921 PGM^!1H:St=!2H,module !3S',0
  DB '1922  SYM^!2H:Sc''!1Z'',St!3H,Se!4H,[!5S]:!6H,!7S,Ni!8D',0
  DB '1923  SSS^!2H:''!1Z'',St!3W,!4$Sg!5H Gr!6H Sm!7H,[!8S],Ni!9D',0
  DB '1925   RELOC^!1H:St!2H,Org!3H:!4H,Fr!5H,Tg!6H:!7H',0
  DB '1927 Creating pool at 0x!1H, size=!2K',0
  DB '1928 Total size of pool 0x!1H=!2K',0
  DB '1929 Destroying pool block 0x!1H, freed size=!2K',0
  DB '1930 GetLastError returned 0x!1H',0
  DB '1931 Increasing pool block !1Hh by !2K, total=!3K',0
  DB '1932 !2C.Pool 0x2Hh total comitted !3K.',0
%ENDIF

↑ Warning messages 20000..4999
 DB '2101 Symbol "!1S" was defined but never used.',0
 ; Warnings W2101, W2102 are not generated when the object was defined in an included file.
 DB '2102 Structure "!1S" was defined but never used.',0
 DB '2210 Precision lost in calculation with FP number rounded to integer.',0
 DB '2211 Precision lost in conversion to float type D!1Z.',0
 DB '2215 Overflow in conversion to float type D!1Z.',0
 DB '2216 Underflow in conversion to float type D!1Z.',0
 DB '2340 This instruction requires option "EUROASM !1S".',0
 DB '2350 Conflict in segment override prefixes.',0

 ; Warning numbers 2356..2371 correspond with bit-nr of prefix in prefix encoding.
 DB '2356 Prefix LOCK: is not expected in this instruction.',0
 DB '2358 Prefix REPE: is not expected in this instruction.',0
 DB '2359 Prefix REPNE: is not expected in this instruction.',0
 DB '2360 Prefix SEGES: is not expected in this instruction.',0
 DB '2361 Prefix SEGCS: is not expected in this instruction.',0
 DB '2362 Prefix SEGSS: is not expected in this instruction.',0
 DB '2363 Prefix SEGDS: is not expected in this instruction.',0
 DB '2364 Prefix SEGFS: is not expected in this instruction.',0
 DB '2365 Prefix SEGGS: is not expected in this instruction.',0
 DB '2366 Prefix XACQUIRE: is not expected in this instruction.',0
 DB '2367 Prefix XRELEASE: is not expected in this instruction.',0
 DB '2368 Prefix SELDOM: is not expected in this instruction.',0
 DB '2369 Prefix OFTEN: is not expected in this instruction.',0
 DB '2370 Prefix OTOGGLE: is not expected in this instruction.',0
 DB '2371 Prefix ATOGGLE: is not expected in this instruction.',0
 DB '2377 Segment override is ignored in 64bit mode.',0
 DB '2381 XLAT operand may only specify segment override and BX/EBX/RBX.',0
 DB '2400 Modifier "!1S" is not applicable in this instruction.',0
 DB '2401 Modifier "!1S" could not be obeyed in this instruction.',0
 DB '2450 The value OPER=!1D is not supported in this MVEX/EVEX instruction.',0
          ; Instruction handler macro IiEmitModRM Disp8?VEX= has value 'F' in the nibble
          ; corresponding to OPER, or the keyword Disp8?VEX is omitted (it defaults to 0xFFFF_FFFF).
 DB '2452 Register swizzle (EH=0,OPER=!1D) is not supported in this MVEX instruction.',0
 DB '2461 Immediate value (!1D) should not exceed !2D.',0
 DB '2510 Formal variable "!1S" will not be overwritten.',0
 DB '2512 Overwriting macro "!1S" previously defined at !2@.',0
 DB '2515 Macro "!1S" was not found, it cannot be dropped.',0
 DB '2520 Environment variable "!1S" is undefined or empty.',0
 DB '2575 Deallocation of virtual memory !1C.Pool !2Hh failed.',0
      ; !2H is pointer of the failed POOL object.
 DB '2610 Parameter "!1S=" was not specified in macro prototype at !2@. Ignored.',0
 DB '2612 "!1S" is not member of structure "!2S". Ignored.',0
 DB '2613 Value "!1S" does not fit to structure member "!2S.!3S". Truncated.',0
 DB '2711 Special dynamic symbol $ cannot be made global.',0
 DB '2820 Illegal combination of prefixes from the same group.',0
 DB '2910 Section [!1S] could not be fixed in the fixing pass.',0
 DB '2911 Section [!1S] could not be fixed in the final pass.',0
 DB '2913 Symbol "!1S" could not be fixed.',0
 DB '2921 Nonrelocable entry point "!1S" is not supported by linker.',0
 DB '2931 Updating group [!1S] previously declared in !2@.',0
 DB '3160 Invalid UTF-8 character in string definition.',0
 DB '3165 Could not load codepage !1D.',0
 DB '3201 No segment with PURPOSE=!1S found.',0
 DB '3203 Segment [!1S] was member of group [!2S] defined in !3@.',0
 DB '3205 Emitting data to section [!1S] with PURPOSE=BSS.',0
 DB '3206 Emitting code to section [!1S] with PURPOSE=BSS.',0
 DB '3209 Membership of segment [!1S] in group [!2S] is not possible in this memory model.',0
 DB '3312 No mask specified, this instruction requires MASK=K1..K7.',0
 DB '3313 Zeroing is not allowed in this instruction.',0
 DB '3315 Destination, vector index register and mask register should be distinct.',0 
 DB '3410 Requested alignment !1D is greater then alignment !2D of section [!3S].',0
 DB '3412 Value of the 2nd operand (!2D) should be below the 1st operand (!1D). Ignored.',0
 DB '3413 Pseudoinstruction ALIGN expects one or two operands.',0
 DB '3432 Displacement above 4 GB is not directly encodable. Use indirect addressing.',0
 DB '3470 No valid HEAD..ENDHEAD block found in the file "!1S".',0
 DB '3510 Whole value "!1S" does not fit into structure member !2S.',0
 DB '3529 !1Dbit symbol does not match datatype "!2Z".',0
 DB '3541 Segment name "!1S" is too long, truncated in output file.',0
 DB '3610 File inclusion in repeating block "!1S" is not supported.',0
 DB '3653 Case insensitivity of linked and imported symbols is not supported.',0
 DB '3654 Name of library module "!1S" exceeds 255 characters. Truncated.',0
 DB '3656 Module started with record type !1Bh at "!2$"[!3Hh] is not terminated with MODEND. Ignored.',0
 
 ; 37??  euroasmi.ini syntax errors.
 DB '3705 Unexpected text "!1S" in "euroasm.ini" file.',0
 DB '3706 Value of !1S=!2S does not fit into  8 bits. Ignored.',0
 DB '3707 Value of !1S=!2S does not fit into 16 bits. Ignored.',0
 DB '3708 Value of !1S=!2S does not fit into 32 bits. Ignored.',0
 DB '3712 !1S=!2D is out of limit !3D..!4D. Ignored.',0
 DB '3713 !1S=!2D is out of limit !3D..!4D. Set to !5D.',0
 DB '3710 Option "!1S" is in undefined [section] of "euroasm.ini" file. Ignored.',0
 DB '3715 Invalid [EUROASM] option "!1S=!2S". Ignored.',0
 DB '3716 Invalid [PROGRAM] option "!1S=!2S". Ignored.',0
 DB '3720 "!1S" is illegal option in [EUROASM] section. Ignored.',0
 DB '3721 Scalar value expected instead of !1S=!2S',0
 DB '3726 Unknown CPU option "!1S", expected !2L.',0
 DB '3730 "!1S" is illegal option in [PROGRAM] section. Ignored.',0
 DB '3731 Self-relative relocation to an absolute VA at [!1S]:!2Hh is not linkable.',0
 DB '3732 Far relocation to an absolute VA at [!1S]:!2Hh is not linkable.',0
 DB '3733 Illegal memory model "!1S". Expected !2L',0
 DB '3736 Illegal program width "!1D", must be 16,32,64. Ignored.',0
 DB '3738 Value !1D should be a power of 2. Ignored.',0
 DB '3740 Unknown instruction modifier "!1S=". Ignored.',0
 DB '3741 Instruction modifier !1S= is not expected in this statement. Ignored.',0
 DB '3742 Illegal !1S= value "!2S". Expected !3L.',0
 DB '3743 Value !1S=!2S is not acceptable in this statement. Ignored.',0
 DB '3744 Value !1S=!2S=!3D is not acceptable, 0..7 expected.',0
 DB '3751 Ignored illegal %%DISPLAY option "!1S". Expected !2L',0
 DB '3811 Unbalanced option stack. EUROASM POP missing.',0
 DB '3812 EUROASM POP without EUROASM PUSH. Ignored.',0
 DB '3860 Ignored illegal %%FOR option "!1S=". Expected STEP=.',0
 DB '3866 Ignored illegal option "!1S=".',0
 DB '3870 Ignored illegal %%ERROR option "!1S=". Expected ID=.',0
 DB '3872 Wrong %%ERROR ID=!1D, expected 0..999 or 5000..5999.',0
 DB '3922 Missing segment with PURPOSE=STACK.',0
 DB '3924 Missing program entry.',0
 DB '3926 Segment [!1S] had to be regrouped from [!2S] to [!3S].',0
 DB '3990 Overwriting previously generated output file "!1S".',0
↑ User generated messages 5000..5999
Msg5000: DB '5000 !1S',0
↑ Error messages 6000..8999
 ; 61?? Elementary term syntax errors.
 DB '6100 Operand cannot be empty.',0
 DB '6101 Expression "!1S" is followed by unexpected character "!3Z".',0
 DB '6103 Missing "]" in expression "!1S".',0
 DB '6109 Premature end of expression "!1S".',0
 DB '6110 Invalid symbol name "!1S".',0
 DB '6120 Symbol "!1S" not found.',0
 DB '6122 Structure "!1S" not found.',0
 DB '6130 The number "!1S" is too big for 64 bits.',0
 DB '6131 Character constant !1S is too big for 64 bits.',0
 DB '6133 Wrong number format, unexpected "!1S"',0
 DB '6160 Syntax error in the string !1S.',0
 DB '6161 Syntax error in the character constant !1S.',0
 DB '6163 Data definition INSTR !1S is not a valid machine instruction.',0
 DB '6164 Unexpected "!1S". Label in data definition INSTR is not suported.',0
 DB '6171 Only attribute @SIZE or @TYPE may be applied to a structure name !1S.',0
 DB '6181 Unary operator instead of "!3Z" expected in expression "!1S".',0
 DB '6182 Binary operator instead of "!3Z" expected in expression "!1S".',0
 
 ; 62?? Expression syntax errors.
 DB '6200 Syntax error in expression "!1S".',0
 DB '6205 Invalid operation !1S.',0
 DB '6206 In expression "!1S" operation ''!2O'' can be applied to plain numbers only.',0
 DB '6207 In expression "!1S" operation ''!2O'' requires both addresses from the same segment.',0
 DB '6208 Unary minus is not applicable to an address in expression "!1S".',0
 DB '6220 Unbalanced parenthesis: ")" without "(" in expression "!1S".',0
 DB '6221 Unbalanced parenthesis: "(" without ")" in expression "!1S".',0
 DB '6240 Immediate far pointer "!1S" must not be in braces [].',0
 DB '6241 Segment part of immediate far pointer "!1S" must be a plain 16bit number.',0
 DB '6242 Invalid offset part of immediate far pointer "!1S".',0

 ; 627? Address expression syntax errors.
 DB '6270 Address expression "!1S" must be in [].',0
 DB '6271 Illegal register !3R used in 16bit addressing in expression "!1S".',0
 DB '6272 Unexpected !3R, only one segment register is allowed in expression "!1S".',0
 DB '6273 Unexpected !3R, only one base register is allowed in expression "!1S".',0
 DB '6274 Unexpected !3R, only one indexregister is allowed in expression "!1S".',0
 DB '6275 Scaled register !3R cannot be used as indexregister in expresion "!1S".',0
 DB '6276 Unexpected !3R - more than one register scaling is not allowed in expression "!1S".',0
 DB '6277 Unexpected !3R, invalid register combination in address expression "!1S".',0
 DB '6278 Illegal register !3R used in address expression "!1S".',0
 DB '6279 Invalid scaling factor in expression "!1S".',0
 DB '6281 Displacement in "!1S" is too big for address size 16 bit.',0
 DB '6282 Displacement in "!1S" is too big for address size 32 bit.',0
 DB '6284 This instruction does not accept vector indexregister.',0
 DB '6285 This instruction requires vector indexregister !1ZMM.',0
 
 ; 630? Arithmetic errors.
 DB '6301 !2O applied to illegal operand type in "!1S".',0
 DB '6310 !2O by zero in "!1S".',0
 DB '6311 !2O 64bit overflow in "!1S".',0
 DB '6321 String compare !2O with non-string operand in expression "!1S".',0
 DB '6331 Subtraction of addresses from different segments in expression "!1S".',0 

 ; 65?? Wrong values.
 DB '6521 Invalid alignment "!1S". Expected one of !2L.',0
 DB '6522 Alignment value "!1S" must be power of two (1,2,4,8..512).',0
 DB '6525 Invalid width !1D, must be 16 or 32 or 64.',0
 DB '6528 Illegal program format "!1S". Expected !2$.',0
 DB '6531 1st operand of HINT_NOP may not exceed 63 (00q..77q).',0
 DB '6537 MOV CS / POP CS is an invalid operation.',0
 DB '6555 Offset out of section limits.',0
 DB '6530 Please specify SEGMENT PURPOSE= (combination of DATA|CODE|BSS).',0
 DB '6531 Illegal character "!1Z" in purpose specification. Expected "PURPOSE=DATA+CODE+BSS".',0
 DB '6553 !1Zword memory variable cannot be statically initialized.',0 
 
 ; 66?? Symbol errors.
 DB '6601 Symbol "!1S" mentioned at !2@ was not found.',0
 DB '6610 Symbol "!1S" was already defined at !2@.',0
 DB '6611 Symbol "!1S" exported from "!2$" was already declared at !3@.',0
 DB '6612 Cannot declare structure "!1S" when such symbol was declared at !2@.',0
 DB '6620 External symbol "!1S" cannot be used as 8bit value.',0
 DB '6621 External/imported symbol "!1S" defined at !2@ cannot be published/exported.',0
 DB '6622 Public symbol "!1S" was defined at !2@, it cannot be external.',0
 DB '6623 Symbol "!1S" is defined at !2@, it cannot be external.',0
 DB '6624 Symbol "!1S" was declared as external at !2@.',0
 DB '6631 Number or address expected.',0
 DB '6634 Origin offset "$" may be equated only within the current section or structure.',0
 DB '6635 Origin offset "$" cannot be equated more than 4 GB away.',0
 DB '6637 Special dynamic symbol "$" can be defined with EQU only.',0
 DB '6638 Special dynamic symbol "$" cannot be declared global.',0
 DB '6671 Invalid syntax of literal symbol !1S.',0
 DB '6675 Missing datatype in literal !1S.',0
 DB '6676 Wrong literal datatype "!1Z".',0

 ; 67?? Data expression errors.
 DB '6711 Duplicator cannot be empty.',0
 DB '6712 Duplicator out of range 0..2147483647.',0
 DB '6721 Invalid data expression "!1S".',0
 DB '6722 Invalid value type ''!1Z'' in data expression "!2S".',0
 DB '6724 Type of data "!1S" is not specified.',0
 DB '6725 Datatype TBYTE expects plain floating-point number.',0
 DB '6726 Relocatable address does not fit to 8bit register.',0
 DB '6727 Immediate value !1D is too big.',0
 DB '6728 Immediate value is too big for !1D byte(s).',0
 DB '6729 Data value "!1S" is too big for datatype "!2Z".',0
 DB '6730 Operand size could not be determined, please use DATA= modifier.',0
 DB '6731 Required address width 64 can be used in 64bit segment only.',0
 DB '6732 Required operand width 64 can be used in 64bit segment only.',0
 DB '6733 Required address width 16 cannot be used in 64bit segment.',0
 DB '6735 Required operand width 16 of this instruction cannot be used in 64bit mode.',0
 DB '6736 Required operand width 32 of this instruction cannot be used in 64bit mode.',0
 DB '6737 Required operand width 16 cannot be used as relocable in 32bit segment.',0
 DB '6738 Required operand width 32 cannot be used as relocable in 16bit segment.',0
 DB '6739 This instruction is not supported in 64bit mode.',0
 DB '6740 Impracticable operand-size requested with mnemonic suffix.',0
 DB '6741 Displacement !1K is too big for 16bit addressing mode.',0
 DB '6742 Displacement !1K is too big for 32/64bit addressing mode.',0
 DB '6743 NEAR mask jump cannot be used in 16bit addressing mode.',0
 DB '6744 This VSIB instruction cannot be used in 16bit addressing mode.',0
 DB '6746 Secondary immediate operand should be a plain number.',0
 DB '6747 Secondary immediate operand is too big for 1 byte.',0
 DB '6749 This instruction is supported in 64bit mode only.',0
 DB '6752 Segment registers ES,CS,SS,DS cannot be pushed/popped in 64bit mode.',0
 DB '6753 8bit register or memory operand cannot be pushed/popped.',0
 DB '6755 Unexpected !1R. Only accumulator register AL/AX/EAX/RAX is accepted here.',0
 DB '6756 Only register CX, ECX or RCX can be used as a counter.',0
 DB '6757 Wrong string source specified. Only [rS:rSI] is acceptable.',0
 DB '6758 Wrong string destination specified. Only [ES:rDI] is acceptable.',0
 DB '6759 Address width of both operands must be the same.',0
 DB '6760 Impracticable distance requested with mnemonic suffix.',0
 DB '6761 Offset is too big for 16bit relocation.',0
 DB '6762 Relocation [!1S]:!2H out of range.',0
 DB '6763 Only AL/AX/EAX can be used in I/O instruction.',0
 DB '6764 Operand-size 64 bits can be used in 64bit mode only.',0
 DB '6765 Operand-size 64 bits is required in 64bit mode.',0
 DB '6767 Only SSE register 0..7 may be used as 4th operand.',0
 DB '6768 Only SSE register 0..15 may be used as 4th operand.',0
 DB '6771 Immediate segment value !1Hh is too big for 16 bits.',0
 DB '6774 Short jump is out of byte range.',0
 DB '6775 Near 16bit jump is out of word range.',0
 DB '6784 Operand requires prefix REX which is supported in 64bit segment only.',0
 DB '6785 Registers AH,BH,CH,DH cannot be used when instruction requires prefix REX/VEX.',0
 DB '6788 Register !1R can be used in in 64bit segment only.',0
 DB '6792 Please specify memory operand size with DATA=DWORD or DATA=QWORD.',0
 DB '6793 Please specify memory operand size with DATA=OWORD or DATA=YWORD.',0

 ; 68?? Statement structure errors.
 DB '6810 Label is not expected in this statement.',0
 DB '6811 This statement requires a label.',0
 DB '6812 Trying to define 2nd label "!2S" when label "!1S" was already defined in this statement.',0
 DB '6820 Instruction prefix is not expected in this statement.',0
 DB '6824 More than 4 prefixes are not allowed in one statement.',0
 DB '6830 Ordinal operands are not expected in this statement.',0
 DB '6831 This statement requires just one operand.',0
 DB '6832 This statement requires just two operands.',0
 DB '6833 This statement requires just three operands.',0
 DB '6837 More than one operand is not expected.',0
 DB '6838 More than four operands are not expected.',0
 DB '6839 Operand(s) missing.',0
 DB '6840 Keyword operands are not expected in this statement.',0
 DB '6850 Unexpected line continuation.',0
 DB '6860 Unrecognized operation "!1S", ignored.',0
 DB '6909 Unspecified include error at "!1_".',0
 DB '6910 Wrong filename !1S.',0
 DB '6911 Wrong file suboperation "!1S".',0
 DB '6912 Unexpected text "!1S" following the file name.',0
 DB '6913 Size of IncludePath "!1S" + size of filename exceeded 256 characters.',0
 DB '6914 File "!1S" not found.',0
 DB '6915 Error reading file "!1S".',0
 DB '6916 "!1S" - number of included files exceeded MaxInclusions.',0
 DB '6917 Wrong nesting, ENDHEAD without HEAD in file "!1S".',0
 DB '6918 Wrong nesting, missing ENDHEAD in file "!1S".',0
 DB '6919 Mismatched HEAD..ENDHEAD identifier in file "!1S".',0
 DB '6951 Wrong linked file name !1$.',0
 DB '6952 Wrong import !1S in library "!2$".',0
 DB '6953 Size of LinkPath "!1_" + size of filename exceeded 256 characters.',0
 DB '6954 Linked file "!1$" not found.',0
 DB '6961 Unresolved external/imported symbol "!1S".',0

 ; 71?? Block structure errors.
 DB '7110 Wrong nesting, expected "!1S !2S".',0
 DB '7120 Wrong nesting, unexpected !1S.',0
 DB '7122 %ELSE was already used in this %IF..%ENDIF block. Ignored.',0
 DB '7125 This instruction is not allowed in STRUC definition.',0
 DB '7130 Wrong nesting, statement out of PROGRAM..ENDPROGRAM block.',0
 DB '7140 Number of expansions exceeded MAXEXPANSIONS=!1D.',0
 DB '7150 Program !1S cannot be embedded in another program with the same name.',0
 
 ; 73?? Preprocessing %variable errors.
 DB '7310 Wrong preprocessing %%variable name "!1S".',0
 DB '7311 Suboperation length %%& cannot be used outside brackets [] or {}.',0  
 DB '7312 System or macro %%variable "!1S" cannot be explicitly assigned.',0
 DB '7313 Macro %%variable "!1S" cannot be used outside %%MACRO..%%ENDMACRO block.',0
 DB '7315 Wrong %%variable "!1S". Macro cannot have that many ordinals.',0
 DB '7316 Invertable macro %%variable "!1S" not specified in %MACRO prototype.".',0
 DB '7317 Macro %%variable "!1S" must contain invertable condition code.',0 
 DB '7319 Invalid character in the macro name.',0
 DB '7320 Wrong suboperation "!1S", expecting "!2Z".',0
 DB '7330 Plain 32bit numeric range value expected instead of expr.type "!1Z".',0
 DB '7331 Plain logical value or expression expected.',0
 DB '7332 Plain numeric value or expression expected.',0
 DB '7333 Value !1D does not fit as 8bit character.',0
 DB '7334 Value !1D does not fit as 16bit Unicode character.',0
 DB '7338 Boolean value expected instead of type "!1Z".',0

; 75?? Machine instruction errors.

 DB '7500 This instruction does not expect any operands.',0
 DB '7501 This instruction does not expect one operand.',0
 DB '7502 This instruction does not expect two operands.',0
 DB '7503 This instruction does not expect three operands.',0
 DB '7504 This instruction does not expect four operands.',0
 DB '7510 Invalid operand type "!1Z".',0
 DB '7511 Unexpected operand combination "!1S".',0
 DB '7512 This operand combination requires mnemonic suffix D.',0
 DB '7513 This operand combination requires mnemonic suffix D or Q.',0
 DB '7514 This operand combination requires mnemonic suffix D.',0
 DB '7515 This operand combination requires mnemonic suffix Q.',0
 DB '7517 Instruction "!1S" is not encodable with this operand combination.',0
 DB '7521 Operand Nr.!1D is too big.',0
 DB '7541 XLAT accepts operand in the form [SegmentReg:rBX] only.',0

 DB '7600 First operand may be ST0 only.',0
 DB '7602 At least one operand must be FP register ST0.',0
 DB '7610 Only register !2$ is expected as operand !1D.',0
  
 ; 77?? Linkage and relocation errors.
 DB '7710 Missing program entry point.',0
 DB '7711 Invalid program entry point "!1S".',0
 DB '7713 Unresolved external entry point "!1S". Ignored.',0
 DB '7716 Number of linked files exceeded MaxLinks=!1D.',0
 DB '7718 Cannot link segments [!1S] which have different width.',0
 DB '7723 Program format COM requires fixed entry point at [!1S]:100h.',0
 DB '7724 Program format COM requires fixed Imagebase=0.',0
 DB '7727 Unresolved extern relocation at [!1S]:!2Hh.',0
 DB '7734 Relocation type 0x!1W in [!2S] is not resolvable in this program format.',0
 DB '7735 Relocation width !1D is not linkable in this program format.',0
 DB '7736 Relocation symbol index !1D in [!2S] is out of range !3D.',0
 DB '7737 Invalid base relocation at [!1S]:!2H.',0
 DB '7739 Relocation of frame symbol indexed as !1D in module "!2S" not found.',0
 DB '7741 StubFile="!1$" was no found.',0
 DB '7742 StubFile="!1$" was not found in LinkPath="!2S".',0
 DB '7743 Invalid format of StubFile="!1$".',0
 DB '7751 IconFile="!1$" was no found.',0
 DB '7752 IconFile="!1$" was not found in LinkPath="!2S".',0
 DB '7753 Invalid format of IconFile="!1$".',0
 DB '7765 Invalid format of COFF object module "!1S".',0
 DB '7766 Invalid format of COFF object file "!1$".',0
 DB '7768 Invalid format of COFF library "!1$"[!2Hh].',0

 ; 78?? Pseudoinstruction errors.
 DB '7800 Unknown !1S keyword "!2S". Expected one of !3L.',0
 DB '7805 Unknown !1S value "!2S". Expected one of !3L.',0
 DB '7810 Unknown EUROASM ordinal "!1S". Expected one of !2L.',0
 DB '7821 Unknown PROGRAM keyword "!1S". Expected one of !2L.',0
 DB '7827 EuroAssembler does not compile format RSRC, use resource compiler instead.',0
 DB '7830 Object [!1S] defined in !2@ is not a segment.',0
 DB '7831 Group, segment or section name "!1S" must be in braces [].',0
 DB '7833 Group, segment, section or structure [!1S] was already declared in !2@.',0
 DB '7834 Structure "!1S" was already declared in !2@.',0
 DB '7835 Implicit segment [!1S] cannot be redeclared, it is not empty.',0
 DB '7836 Segment [!1S] was already defined in !2@.',0
 DB '7838 [!1S] is not 16bit segment, it cannot be member of a group.',0
 DB '7841 %%SETS and %%SETL expect %%variable name as the only operand.',0

 ; 79?? Other errors.
 DB '7920 Invalid fixup at [!1S]:!2Hh.',0
 DB '7921 Fixup increment out of 64KB range at [!1S]:!2Hh.',0
 DB '7922 Fixup increment out of 4GB range at [!1S]:!2Hh.',0
 DB '7923 Number of relocations (!1D) exceeded 65_535.',0
 DB '7924 Invalid relocation [!1S]:!2Hh.',0
 DB '7926 Relocation offset out of 64KB range at [!1S]:!2Hh.',0
 DB '7927 Relocation offset out of 4GB range at [!1S]:!2Hh.',0
 DB '7928 Unaligned segment of relocation [!1S]:!2Hh.',0
 DB '7951 Error 0x!1H writing to output file "!2$".',0
 DB '7982 Error writing to listing file "!1$".',0
 
 ; 80?? Wrong input source file.
 DB '8000 Input source file was not specified.',0
 DB '8010 Source file "!1S" was not found.',0
 DB '8020 Filename "!1$" is too long.',0
 DB '8030 Error reading source file "!1$".',0
 
 ; 85?? Wrong linked file.
 DB '8512 Length of linked file name "!1$" exceeds 254 characters.',0
 DB '8513 Segment/symbol name "!1S" exceeds 254 characters. Truncated in OMF.',0
 DB '8515 Segment [!1S] over 4 GB.',0
 DB '8519 Number of indexed references in OMF exceeded 32767. Truncated.',0
 DB '8523 OMF 16bit segment [!1S] size !2K exceeded 64KB. Truncated.',0
 DB '8524 Size of segment [!1S] exceeded 4 GB. Truncated.',0
 DB '8525 Size of segment [!1S] exceeded 4 GB.',0
 DB '8527 Offset of public symbol "!1S" exceeded 4 GB, not suported in OMF.',0
 DB '8530 Error reading linked file "!1$".',0
 DB '8531 Error reading imported file "!1$".',0
 DB '8532 Wrong checksum of OMF record type !1Bh at "!2$"[!3Hh].',0
 DB '8533 Invalid OMF record type !1Bh at "!2$"[!3Hh].',0
 DB '8534 Format !1S of file "!2$" is not linkable.',0
 DB '8535 Format of file "!1$" is not importable.',0
 DB '8539 Format of file "!1$" was not recognized.',0
 DB '8540 Public symbol "!1S" was already defined at !2@.',0
 DB '8543 Duplicated imported symbol "!1S" in "!2$".',0
 DB '8544 Entry specified in program "!1S" collides with entry in "!2S".',0
 DB '8572 Invalid suboperation of PROGRAM OUTFILE="!1S. Ignored.',0
 DB '8613 Loader of !1S program will not bind dynamically imported symbol "!2".',0
 
↑ Fatal messages 9000..9999
 DB '9110 Cannot allocate virtual memory.',0
 DB '9113 Process heap damaged at line !1D.',0
 DB '9210 Memory reserved for machine stack is too small for this source file.',0
          ; EuroAssembler is by default created with SizeOfStackReserve=1MB.
 DB '9304 Allocation error storing to pool in !1H.',0
 DB '9310 Allocation error assigning value to %%!1S.',0
 DB '9312 Allocation error expanding macro !1S.',0
 DB '9313 Allocation error reserving buffer for !1H.',0
 DB '9314 Allocation error storing to buffer in !1H.',0
 DB '9316 Allocation error creating image buffer.',0
 DB '9324 Allocation error storing to list in !1H.',0
 DB '9334 Allocation error storing to stack in !1H.',0
 DB '9341 Internal error: invalid COM file size.',0
 DB '9960 Internal error: creating symbol "!1S" outside the statement.',0
 DB '9961 Internal error: unexpected expression type "!1Z" in IiImmSize.',0
 DB '9971 Internal error: unexpected error on macro expansion.',0
 DB '9974 Internal error: unhandled relocation type 0x!1W at [!2S]:!3Hh.',0
 DB '9975 Internal error: record size !1D exceeded 1024 in OMF record type 0x!2H.',0
 DB '9977 Internal error: Segment Nr.!1D overflowed CombineMap in PgmCombine.',0
 DB '9979 Internal error: Missing format handler in PgmCreateImplicitSegments.',0
 DB '9981 Internal error: No AVX prefix is defined for instruction !1S.',0
 DB '9982 Internal error: Invalid token "!1$" in AVX prefix for instruction !2S.',0  
 DB '9983 Internal error: Missing varTypeSysKind in VarExpand.varTypeSysEaopt.',0
 DB '9984 Internal error: Wrong index of %%^SystemVariable in VarExpand.varTypeSys.',0
 DB '9985 Internal error: IiGetRegFamily/Ordinal provided with invalid register encoding.',0
 DB '9987 Internal error: ModRM fields are not specified in handler (missing IiOpEn).',0
 DB '9990 Multiplication to Scaling transformation. Not used as real message.',0
 DB '9995 This part of EuroAssembler is not ready yet.',0
 DB '9997 Internal EuroAssembler error.',0
 DB '9998 Unexpected EuroAssembler behaviour of procedure !3$ in "!1$"{!2D}.',0
 MsgTextEnd:
  ENDPROGRAM msg

▲Back to the top▲