'QB45BIN.BAS - written by qarnos
'Used by permission: http://www.[abandoned, outdated and now likely malicious qb64 dot net website - don’t go there]/forum/index.php?topic=1771.msg16215#msg16215
'Command line interface adapted by FellippeHeitor
'----------------------------------------------------------------------------
' Used for sorting alphabetically.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Internal constants used by parse rule decoder
'----------------------------------------------------------------------------
CONST TagType.Recursive
= 1 CONST TagType.TokenData
= 2 CONST TagType.StackABS
= 3 CONST TagType.StackREL
= 4
'----------------------------------------------------------------------------
' Constants returned by the Meta field of QBBinReadLine. I will probably
' use the high 16-bits for flags, so best to mask them out for now.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Not yet used since it only supports QB45 atm.
'----------------------------------------------------------------------------
CONST QBBinFileMode.QB45
= 1
'----------------------------------------------------------------------------
' Option variable declarations
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Option variable initialisation
'----------------------------------------------------------------------------
QBBinOption.OmitIncludedLines = -1
QBBinOption.SortProceduresAZ = -1
'----------------------------------------------------------------------------
' Errors only half-implemented so far.
'----------------------------------------------------------------------------
CONST QBErrBadFormat
= 255 CONST QBErrBadToken
= 254
'----------------------------------------------------------------------------
' You may use QBBinEOF, for now, to determine when EOF has been reached.
' QBBinDefType contains the current DEFxxx setting for each letter of the
' alphabet (1 = INT, 2 = LNG, 3 = SNG, 4 = DBL, 5 = STR).
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' A hash table is used for symbols defined in the parse rules. There aren't
' many of them, so a small table will do.
'----------------------------------------------------------------------------
CONST SymbolHashBuckets
= 43
'----------------------------------------------------------------------------
' Not worth commenting on... oops.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' We don't need a very big stack. I haven't seen it go beyond 8 or 9 entries
' so 255 is plenty. Also, STACK(0) is a special entry. IF SP = 0 then there
' is nothing on the stack.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Define global symbol table, code space and instruction pointer
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' PCODE always contains the ID of the current token (the low 10 bits of the
' input word.
'
' HPARAM contains the high 6 bits of the input word and is used by some
' tokens. IE: Identifiers use it for the type suffix and integers
' smaller than 10 are encoded this way.
'
' TOKEN is a string containing the binary data for the current token (PCODE
' and HPARAM in the first word, the rest of the data follows). All the
' FetchXXX functions work on this variable
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' LastProcType is just a hack to keep track of the current SUB or FUNCTION
' status since END SUB and END FUNCTION share the same token.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' These variables contain the current prodecure name and type the parser
' is decoding.
'
' QBBinProcedureType = MAIN | SUB | FUNCTON | DEF
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Variables used to store common token codes referenced in the code. Faster
' than doing GetHashedSymbol("tokenname") every time, and flexible since the
' QB40 token codes are different from QB45.
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Initialisation will eventually be automatic in QBBinOpenFile
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' Get file names, etc.
'----------------------------------------------------------------------------
'ON ERROR GOTO ErrorHandler
GetInputFileName:
PRINT "Conversion utility from QuickBASIC 4.5 binary to plain text." PRINT " Syntax: QB45BIN <source.bas> [-o output.bas]" PRINT "If no output is specified, a backup file is saved and the original" PRINT "file is overwritten."
IF INSTR(InputFile$
, ".") = 0 THEN InputFile$
= InputFile$
+ ".BAS"
path$
= LEFT$(InputFile$
, i
) InputFile$
= MID$(InputFile$
, i
+ 1) OutputFile$ = path$ + InputFile$ + ".converted.bas"
PRINT "Loading parse rules... ";
LoadParseRules
QBBinOpenFile path$ + InputFile$
'---------------------------------------------------------------------------
' The main loop is pretty straight-forward these days.
'---------------------------------------------------------------------------
ProgramLine$ = QBBinReadLine$(Meta&)
'-----------------------------------------------------------------------
' Just an example of meta-data usage. Pretty limited at the moment,
' but could be helpful to QB64 IDE when building SUB/FUNCTION list.
'-----------------------------------------------------------------------
'IF Meta& = QBBinMeta.SUB THEN PRINT "----- SUBROUTINE -----"
'IF Meta& = QBBinMeta.FUNCTION THEN PRINT "----- FUNCTION -----"
'-----------------------------------------------------------------------
' AOutput has become a pretty-print function. All program lines are now
' retrieved by calling QBBinReadLine.
'-----------------------------------------------------------------------
AOutput ProgramLine$
'Quit after a number of seconds - likely an invalid file causing an endless loop
IF StartProcessing!
> TIMER THEN StartProcessing!
= StartProcessing!
- 86400
'If we've made it this far, output the resulting file:
PUT #QBTxtFile
, 1, OutputContents$
TSPECS:
QB45TOKENS:
'
' Most of the tokens for QB45 are defined here, along with the length of the
' token (or '*' for variable length) and some parse rules.
'
' The first column determined the PCODE (the low 10 bits of the token)
' which the rule responds to. This is followed by the length of the token
' *data*, which may be omitted if the token has no data, or an asterisk to
' indicate a variable length token. Variable length tokens are always
' followed by a word indicating the length of the token.
'
' The final column is the parse rule itself. A token may have multiple
' parse rules. Multiple parse rules may be specified on a seperate line
' (without a PCODE or LENGTH field), or seperated by a pipe ('|') symbol.
'
' There is one important difference between the two methods. Some rules
' define a symbol which can be used to reference the rule, such as:
'
' declmod::=SHARED
'
' If a pipe symbol is used, the next rule will inherit the "declmod" (or
' whatever symbol), unless it exlicitly defines it's own. Rules defined
' on seperate lines use the default symbol which, initially, is nothing, but
' may be overridden using the ".default" directive. This is only really used
' in the second half of the rule list, where almost every token is an
' expression ('expr').
'
' Rules are matched on a first-come first-served basis. The first rule which
' can be successfully applied (see below) is accepted.
'
' The rules can have {tags} embedded in them. There are basically two types
' of tags - stack and data/format tags. I will discuss them briefly here:
'
' STACK tags can take these basic forms:
'
' {1}
' {*:1}
' {rulename:1}
' {$+1}
' {$-1}
' {rulename:$+1}
'
' The first type will be substituded for the text located 1 item from the
' top of the parse stack. If the stack isn't that deep, it will be replaced
' with the null string.
'
' The second type is just like the first, except the rule will be rejected
' if the stack item doesn't exist.
'
' The third type will only accept a rule if the stack item at the specified
' offset is of the correct rule type. So {declmod:1} will reject the rule
' if the stack entry at offset 1 is not a "declemod". There is also a special
' rule name, "self", which always refers to the current rule.
'
' The final three forms, use the '$' symbol. This symbol refers to a
' "relative" stack offset - an offset from the deepest stack item referenced
' in a normal tag. This is really a bit of a hack, due to me trying to avoid
' writing a full LALR(1) parser! This feature is rarely used.
'
' DATA/FORMAT tags
'
' Data and format tags being with a '#', such as {#id:2}. These tags are used
' either to interpret data from the token or to generate a dynamic parse
' rule (another hack).
'
' In the case of data tokens, the number refers to the offset into the token
' data on which the tag is to work.
'
' Format tokens usually have two '#' symbols, such as {##id(decl)}. The
' extra '#' causes the parser to re-scan the tag for other tags once it
' has been subsituted, allowing these tags to generate stack tags which can
' then be parsed.
'
' See the function GetTaggedItem for a list of tag names which can be used.
'
'
'
REM -------+-------+-------
DATA 0x000
,"newline::=.{#newline}{#tabh}" DATA 0x001
,2,"newline::=.{#newline}{#tabi}" DATA 0x002
,2,"newline::=.{#newline-include}" DATA 0x003
,4,"newline::=.{#newline-include}{#indent:2} " DATA 0x004
,4,".{#newline}{#thaddr:0}{#label:2}" DATA 0x005
,6,".{#newline}{#thaddr:0}{#label:2} {#indent:4}"
'----------------------------------------------------------------------------
' 0x008 = End of procedure/module code (watch list follows)
' 0x009 = End of watch list
'----------------------------------------------------------------------------
DATA 0x00b
,2,"expr::={#id+}" DATA 0x00c
,2,"consts::={const:1} {#id+} = {0}" DATA "consts::={consts:1}, {#id+} = {0}" DATA 0x00d
,2,"decls::={decls:1}, {#id+:0} {astype:0}" DATA "decls::={decls:0}, {#id+:0}" DATA "decls::={decl:1} {#id+:0} {astype:0}" DATA "decls::={decl:0} {#id+:0}" DATA "{#id+:0} {astype:0}" DATA 0x00e
,4,"expr::={##id(expr)}" DATA 0x00f
,4,"{##id(expr)} = {$+0}" DATA 0x010
,4,"decls::={##id(decl)}" DATA 0x011
,2,"expr::={0}.{#id}" DATA 0x012
,2,"{0}.{#id} = {1}"
' 0x015 = AS USERTYPE
' 0x016 = AS BUILTINTYPE?
DATA 0x015
,4,"astype::={#tabi:2}AS {#type:0}" DATA 0x016
,4,"astype::={#tabi:2}AS {#type:0}"
' 0x017 - used for unkown type assignments?
'----------------------------------------------------------------------------
' 0x019 = user-type field declaration.
'----------------------------------------------------------------------------
DATA 0x01a
,"declmod::=SHARED" DATA 0x01b
,6,"deftype::={#thaddr:0}{#DEFxxx}" DATA 0x01c
,"{self:1}, {0}|REDIM {declmod:1} {0}|REDIM {0}" DATA 0x01e
,2,"decl::=SHARED" DATA 0x01f
,2,"decl::=STATIC" DATA 0x020
,4,"TYPE {#id:2}" DATA 0x021
,*,"$STATIC{#raw}" DATA 0x022
,*,"$DYNAMIC{#raw}" DATA 0x023
,"const::=CONST"
'----------------------------------------------------------------------------
' 0x024 = IDE breakpoint
'----------------------------------------------------------------------------
DATA 0x026
,*,"{deffn:1} = {0}" DATA 0x028
,2,"ON {0} GOSUB {#id}"
'----------------------------------------------------------------------------
' Labels used in $INCLUDEd lines
'----------------------------------------------------------------------------
DATA 0x034
,4,"newline::={#thaddr:0}{#label:2} " DATA 0x035
,6,"newline::={#thaddr:0}{#label:2} {#indent:4}"
DATA 0x037
,4,"CALL {#id:2}{##call()}" DATA 0x038
,4,"{#id:2}{##call}" DATA 0x039
,4,"CALLS {#id:2}{##call()}" DATA 0x03b
,"case::={case:1}, {0}|CASE {0}" DATA 0x03c
,"case::={case:2}, {1} TO {0}|CASE {1} TO {0}" DATA 0x03d
,"case::={case:1}, IS = {0}|CASE IS = {0}" DATA 0x03e
,"case::={case:1}, IS < {0}|CASE IS < {0}" DATA 0x03f
,"case::={case:1}, IS > {0}|CASE IS > {0}" DATA 0x040
,"case::={case:1}, IS <= {0}|CASE IS <= {0}" DATA 0x041
,"case::={case:1}, IS >= {0}|CASE IS >= {0}" DATA 0x042
,"case::={case:1}, IS <> {0}|CASE IS <> {0}"
DATA 0x044
,*,"DECLARE {#procdecl()}" DATA 0x045
,*,"deffn::={#procdecl:2}" DATA 0x047
,"DO UNTIL {0}" DATA 0x048
,2,"DO WHILE {0}" DATA 0x049
,2,"{newline:0}ELSE| ELSE "
' 0x04a = implicit GOTO linenumber used in 0x04c ELSE
DATA 0x04d
,2,"ELSEIF {0} THEN" DATA 0x051
,"END {#proctype}" DATA 0x055
,2,"EXIT {#proctype}" DATA 0x056
,4,"FOR {2} = {1} TO {0}" DATA 0x057
,4,"FOR {3} = {2} TO {1} STEP {0}" DATA 0x058
,*,"funcdef::={#procdecl}" DATA 0x059
,2,"GOSUB {#id}" ' 0x05a 2, "GOSUB {#id}"
DATA 0x05b
,2,"GOTO {#id}" ' 0x05c 2, "GOTO {#id}"
DATA 0x05d
,2,"IF {0} THEN " DATA 0x05e
,2,"IF {0} THEN {#id}" ' 0x05f, 2, "IF {0} THEN "
DATA 0x060
,2,"IF {0} GOTO {#id}" DATA 0x061
,2,"IF {0} THEN" DATA 0x063
,2,"LOOP UNTIL {0}" DATA 0x064
,2,"LOOP WHILE {0}" DATA 0x066
,4,"{self:1}, {0}|NEXT {0}" DATA 0x067
,2,"ON ERROR GOTO {#id}" DATA 0x068
,*,"ON {0} GOSUB {#id-list}" DATA 0x069
,*,"ON {0} GOTO {#id-list}" DATA 0x06b
,2,"RESTORE {#id}" DATA 0x06d
,2,"RESUME {#id}" DATA 0x070
,2,"RETURN {#id}" DATA 0x074
,2,"SELECT CASE {0}" DATA 0x076
,*,"subdef::={#procdecl}" DATA 0x077
,"WAIT {1}, {0}" DATA 0x078
,"WAIT {2}, {1}, {0}"
'----------------------------------------------------------------------------
' 0x07b used in IDE watch mode. Probably 0x07c, too.
'----------------------------------------------------------------------------
DATA 0x07d
,"prnmod::={prnmod:1} {0},|PRINT {0},"
'----------------------------------------------------------------------------
' 3 dummy tokens used in LINE statements
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' graphics co-ordinates
'----------------------------------------------------------------------------
DATA 0x081
,"1st-coord::=({1}, {0})" DATA 0x082
,"1st-coord::=STEP({1}, {0})" DATA 0x083
,"{1st-coord:2}-({1}, {0})|({1}, {0})" DATA 0x084
,"{1st-coord:2}-STEP({1}, {0})|-STEP({1}, {0})"
DATA 0x086
,", {1} AS {0}" DATA 0x087
,"finput::=INPUT {0}," DATA 0x088
,"{input:1} {inputs:0}" DATA 0x089
,*,"input::=INPUT {##input-args}"
'----------------------------------------------------------------------------
' These two consume data, but I have no idea what they do. I haven't seen
' one in the wild.
'----------------------------------------------------------------------------
' 0x08d, 4, ""
'----------------------------------------------------------------------------
' Most of the PRINT stuff is here. The rules are pretty finicky. These
' sequences also apply to LPRINT and WRITE.
'----------------------------------------------------------------------------
DATA 0x08f
,"prnsmc::={self|prncma|prnsrl:1} SPC({0});" DATA "prnsmc::=SPC({0});" DATA 0x090
,"prnsmc::={self|prncma|prnsrl:1} TAB({0});" DATA "prnsmc::=TAB({0});"
DATA 0x091
,"prncma::={self|prnsmc|prnsrl:0} ,|,"
DATA 0x092
,"prnsmc::={self:0}|{prncma|prnsrl:0} ;|;"
DATA 0x093
,"{prnmod:2} {prnuse:1} {prnsrl|prnsmc|prncma:0}" DATA "{prnmod:1} {prnsrl|prnsmc|prncma:0}" DATA "{prnmod:1} {prnuse:0}" DATA "PRINT {prnuse:1} {prnsrl|prnsmc|prncma:0}" DATA "PRINT {prnsrl|prnsmc|prncma:0}"
DATA 0x094
,"prnsrl::={prncma|prnsmc|self:1} {expr:0},|{expr:0}," DATA 0x095
,"prnsrl::={prncma|prnsmc|self:1} {expr:0};|{expr:0};"
DATA 0x096
,"{prnmod:3} {prnuse:2} {prnsmc|prncma|prnsrl:1} {expr:0}" DATA "{prnmod:2} {prnsmc|prncma|prnsrl:1} {expr:0}" DATA "{prnmod:1} {prnsmc|prncma|prnsrl|expr:0}" DATA "PRINT {prnuse:2} {prnsmc|prncma|prnsrl:1} {expr:0}" DATA "PRINT {prnsmc|prncma|prnsrl:1} {expr:0}" DATA "PRINT {prnsmc|prncma|prnsrl|expr:0}"
DATA 0x097
,*,"{#tabi:0}'{#raw:2}" ' 0x098 nothing?
DATA 0x099
,*,"$INCLUDE: '{#raw:0}" DATA 0x09c
,"BLOAD {1}, {0}" DATA 0x09d
,"BSAVE {2}, {1}, {0}" DATA 0x09f
,"CIRCLE {##circle-args}" DATA 0x0a0
,"CIRCLE {##circle-args}" DATA 0x0a1
,2,"CLEAR{##varargs}" DATA 0x0a2
,2,"CLOSE{##varargs}" DATA 0x0a3
,"CLS {expr:0}|CLS" DATA 0x0a4
,2,"COLOR{##varargs}"
DATA 0x0a5
,4,"decl::=COMMON {declmod:0}{#blockname:2}" DATA "decl::=COMMON{#blockname:2}"
DATA 0x0a6
,*,"DATA{#cstr:2}" DATA 0x0a9
,"DEF SEG = {0}"
DATA 0x0ac
,2,"ERASE{##varargs}"
DATA 0x0b1
,"GET {1}, {0}" DATA 0x0b2
,2,"GET {1}, , {0}" DATA 0x0b3
,2,"GET {2}, {1}, {0}" DATA 0x0b4
,"GET {1}, {0}" DATA 0x0b5
,2,"PUT {1}, {0}, {#action-verb}"
DATA 0x0b6
,"inputs::={inputs:1}, {0}|{0}" DATA 0x0b7
,"IOCTL {1}, {0}" DATA 0x0b8
,2,"KEY {#keymode}" DATA 0x0b9
,"KEY {1}, {0}" DATA 0x0bb
,2,"LINE {##line-args}" DATA 0x0bc
,2,"LINE {##line-args}" DATA 0x0bd
,2,"LINE {##line-args}" DATA 0x0be
,2,"LINE {##line-args}"
DATA 0x0c0
,2,"input::=LINE {finput:1} {0}" DATA "input::=LINE INPUT {##input-args} {0}"
DATA 0x0c1
,2,"LOCATE{##varargs}" DATA 0x0c2
,2,"LOCK {##lock-args}" DATA 0x0c3
,"prnmod::=LPRINT" DATA 0x0c4
,"LSET {0} = {1}" DATA 0x0c5
,"MID$({0}, {2}) = {1}" DATA 0x0c6
,"MID$({0}, {3}, {2}) = {1}" DATA 0x0c8
,"NAME {1} AS {0}"
DATA 0x0c9
,2,"OPEN {1} {#open-args} AS {0}" DATA 0x0ca
,2,"OPEN {2} {#open-args} AS {1} LEN = {0}" DATA 0x0cb
,"OPEN {2}, {1}, {0}" DATA 0x0cc
,"OPEN {3}, {2}, {1}, {0}" DATA 0x0cd
,"OPTION BASE 0" DATA 0x0ce
,"OPTION BASE 1" DATA 0x0cf
,"OUT {1}, {0}"
DATA 0x0d0
,"PAINT {2}{nularg:1}{nularg:0}" DATA "PAINT {2}, {nularg:1}, {0}" DATA "PAINT {2}, {1}{nularg:0}" DATA "PAINT {2}, {1}, {0}" DATA 0x0d1
,"PAINT {3}, {2}, {1}, {0}" DATA 0x0d3
,"PALETTE {1}, {0}" DATA 0x0d5
,"PCOPY {1}, {0}"
DATA 0x0d7
,"POKE {1}, {0}" DATA 0x0d9
,"PRESET {0}, {1}" DATA 0x0db
,"PSET {1}, {0}" DATA 0x0dd
,"PUT {1}, {0}" DATA 0x0de
,2,"PUT {1}, , {0}" DATA 0x0df
,2,"PUT {2}, {1}, {0}"
DATA 0x0e1
,"RANDOMIZE {0}" DATA 0x0e2
,"{self:1}, {0}|READ {0}" DATA 0x0e6
,"RSET {0} = {1}"
DATA 0x0e7
,2,"SCREEN{##varargs}" DATA 0x0e8
,"SEEK {1}, {0}" DATA 0x0ec
,"SOUND {1}, {0}" DATA 0x0ed
,2,"SWAP {1}, {0}" DATA 0x0f2
,2,"UNLOCK {##lock-args}" DATA 0x0f3
,"VIEW ({5}, {4})-({3}, {2}){nularg:1}{nularg:0}" DATA "VIEW ({5}, {4})-({3}, {2}), {nularg:1}, {0}" DATA "VIEW ({5}, {4})-({3}, {2}), {1}{nularg:0}" DATA "VIEW ({5}, {4})-({3}, {2})"
DATA 0x0f6
,"VIEW PRINT {1} TO {0}"
DATA 0x0f7
,"VIEW SCREEN ({5}, {4})-({3}, {2}){nularg:1}{nularg:0}" DATA "VIEW SCREEN ({5}, {4})-({3}, {2}), {nularg:1}, {0}" DATA "VIEW SCREEN ({5}, {4})-({3}, {2}), {1}{nularg:0}" DATA "VIEW SCREEN ({5}, {4})-({3}, {2})" DATA 0x0f8
,"WIDTH {1}{nularg:0}|WIDTH {1}, {0}" DATA 0x0f9
,"WIDTH LPRINT {0}" DATA 0x0fa
,"WIDTH {1}, {0}" DATA 0x0fb
,"WINDOW ({3}, {2})-({1}, {0})" DATA 0x0fd
,"WINDOW SCREEN ({3}, {2})-({1}, {0})" DATA 0x0fe
,"prnmod::=WRITE" DATA 0x0ff
,"prnuse::=USING {0};"
DATA 0x108
,"C{#type-abbr}({0})" DATA 0x114
,"ENVIRON$({0})" DATA 0x11b
,"FILEATTR({1}, {0})" DATA 0x123
,"INPUT$({1}, {0})" DATA 0x124
,"INSTR({1}, {0})" DATA 0x125
,"INSTR({2}, {1}, {0})" DATA 0x129
,"LBOUND({1}, {0})" DATA 0x12c
,"LEFT$({1}, {0})" DATA 0x132
,"MID$({1}, {0})" DATA 0x133
,"MID$({2}, {1}, {0})" DATA 0x135
,"MKDMBF$({0})" DATA 0x13e
,"PMAP({1}, {0})" DATA 0x140
,"POINT({1}, {0})" DATA 0x142
,"RIGHT$({1}, {0})" DATA 0x147
,"SCREEN({1}, {0})" DATA 0x148
,"SCREEN({2}, {1}, {0})" DATA 0x153
,"STRING$({1}, {0})" DATA 0x158
,"UBOUND({1}, {0})" DATA 0x15c
,2,"VARPTR$({0})" DATA 0x173
,"nularg::={#nul}"
DATA 0x17c
,6,"astype::={#tabi:4}AS STRING * {#int:2}" DATA 0x17d
,2,"decl::=DIM {declmod:0}|DIM"
'
' This subroutine is called whenever a program line has been decoded.
'
OutputLines = OutputLines + 1
OutputContents$
= OutputContents$
+ CHR$(10) + ProgramLine
OutputContents$ = ProgramLine
Txt$ = Txt2$
TagTxtLen
= CVI(MID$(Txt$
, Marker
+ 4, 2)) TagParam
= CVI(MID$(Txt$
, Marker
+ 6, 2)) TagTxt$
= MID$(Txt$
, Marker
+ 8, TagTxtLen
)
TagParam$ = ITOA(TagParam)
IF TagParam
> 0 THEN TagParam$
= "+" + TagParam$
TagParam$ = "$" + TagParam$
IF TagTxt$
<> "" THEN TagParam$
= TagTxt$
+ ":" + TagParam$
Txt$
= LEFT$(Txt$
, Marker
- 1) + "{" + TagParam$
+ "}" + MID$(Txt$
, Marker
+ 8 + TagTxtLen
)
Txt$
= LEFT$(Txt$
, Marker
- 1) + "®newline¯" + MID$(Txt$
, Marker
+ 2) Txt$
= LEFT$(Txt$
, Marker
- 1) + "®indent¯" + MID$(Txt$
, Marker
+ 4) Txt$
= LEFT$(Txt$
, Marker
- 1) + "®rle¯" + MID$(Txt$
, Marker
+ 3)
DbgPlainText$ = Txt$
'
' Iterates through the various rules for a token contained in the ParseRules
' array and stops when one of them works.
'
ParseRule = ParseRules(PCODE)
DbgOutput ""
DbgOutput
"PCODE = 0x" + HEX$(PCODE
) DbgOutput
"HPARAM = 0x" + HEX$(HPARAM
) DbgOutput ""
'DumpStack
RuleLn
= CVI(MID$(ParseRule
, RuleBegin
+ 0, 2)) RuleID
= CVI(MID$(ParseRule
, RuleBegin
+ 2, 2))
RuleTxt$
= MID$(ParseRule
, RuleBegin
+ 4, RuleLn
)
RuleBegin = RuleBegin + RuleLn
'
' Returns the string of the first rule in a compound|parse|rule, and removes
' it from the input string.
'
' If the rule does not have a rule id (ident::=), DefaultRuleID is assigned.
'
'----------------------------------------------------------------------------
' Locate the first instance of the rule delimiter "|" that does not occur
' inside a rule {tag}
'----------------------------------------------------------------------------
RuleOffset = 1
RuleEnd
= LEN(ParseRule
) + 1
BraceOffset
= INSTR(RuleOffset
, ParseRule
, "{") IF BraceOffset
= 0 THEN BraceOffset
= RuleEnd
PipeOffset
= INSTR(RuleOffset
, ParseRule
, "|")
RuleOffset
= INSTR(BraceOffset
, ParseRule
, "}") IF RuleOffset
= 0 THEN RuleOffset
= RuleEnd
IF PipeOffset
= 0 THEN PipeOffset
= RuleEnd
'----------------------------------------------------------------------------
' Extract the first rule and return if there is nothing left.
'----------------------------------------------------------------------------
FirstRule
= LEFT$(ParseRule
, PipeOffset
- 1) ParseRule
= MID$(ParseRule
, PipeOffset
+ 1)
'----------------------------------------------------------------------------
' If the first rule has a symbol on the left-hand side and the next rule
' does not, the next rule inherits the symbol.
'----------------------------------------------------------------------------
RuleLHS$ = GetParseRuleLHS(FirstRule)
IF RuleLHS$
= "" AND DefaultRuleID
<> "" THEN RuleLHS$ = DefaultRuleID
FirstRule = DefaultRuleID + "::=" + FirstRule
DelimitParseRule = FirstRule
IF RuleLHS$
<> "" AND GetParseRuleLHS
(ParseRule
) = "" THEN ParseRule = RuleLHS$ + "::=" + ParseRule
'
' For debugging only
'
PRINT #5, "The stack has"; SP;
"entries"
Txt$
= LEFT$(Txt$
, Marker
- 1) + "®newline¯" + MID$(Txt$
, Marker
+ 2) Txt$
= LEFT$(Txt$
, Marker
- 1) + "®indent¯" + MID$(Txt$
, Marker
+ 4) Txt$
= LEFT$(Txt$
, Marker
- 1) + "®rle¯" + MID$(Txt$
, Marker
+ 3)
TRIM
= 76 - POS(0) - LEN(Txt$
) '80-60-19=1
RuleOffset = 1
'
' NOTE: Since the stack is flushed immediately upon seeing a leading period,
' rules should not have non-flushing alternatives.
'
FlushStack
RuleOffset = 2
InitialSP = SP
FinalSP = SP
RuleTxt = ParseRule
DbgOutput "Trying rule: " + Quote(ParseRule)
DbgOutput "Rule: " + ParseRule
DbgOutput "Output: " + OutTxt
TagBegin
= INSTR(RuleOffset
, RuleTxt
, "{") IF TagBegin
= 0 THEN TagBegin
= LEN(RuleTxt
) + 1
TagEnd
= INSTR(TagBegin
, RuleTxt
, "}") + 1
OutTxt
= OutTxt
+ MID$(RuleTxt
, RuleOffset
, TagBegin
- RuleOffset
)
TagTxt
= MID$(RuleTxt
, TagBegin
+ 1, TagEnd
- TagBegin
- 2)
'------------------------------------------------------------------------
' If a relative stack tag is used, we will need to wait until all the
' absolute tags have been processed before we can calculate the tag
' offset, so we insert a marker into OutTxt.
'------------------------------------------------------------------------
RuleOffset = TagEnd
IF NOT ValidateStackTag
(RuleID
, TagTxt
, TagParam
) THEN ExecuteParseRule = 0
DbgOutput "Rule REJECTED!"
IF OffsetSP
< SP
THEN OutTxt
= OutTxt
+ MID$(STACK
(SP
- TagParam
), 3) IF SP
- TagParam
- 1 < FinalSP
THEN FinalSP
= SP
- TagParam
- 1
RuleOffset = TagEnd
RuleTxt
= LEFT$(RuleTxt
, TagBegin
- 1) + GetTaggedItem
(TagTxt
, TagParam
) + MID$(RuleTxt
, TagEnd
) RuleOffset = TagBegin
OutTxt = OutTxt + GetTaggedItem(TagTxt, TagParam)
RuleOffset = TagEnd
DbgOutput "Rule: " + ParseRule
DbgOutput "Output: " + OutTxt
SP = FinalSP
TagTxtLen
= CVI(MID$(OutTxt
, Marker
+ 4, 2)) TagParam
= CVI(MID$(OutTxt
, Marker
+ 6, 2)) TagTxt
= MID$(OutTxt
, Marker
+ 8, TagTxtLen
)
IF NOT (ValidateStackTag
(RuleID
, TagTxt
, TagParam
)) THEN SP = InitialSP
ExecuteParseRule = 0
DbgOutput "Rule REJECTED!"
OutTxt
= LEFT$(OutTxt
, Marker
- 1) + MID$(STACK
(SP
- TagParam
), 3) + MID$(OutTxt
, Marker
+ 8 + TagTxtLen
) IF SP
- TagParam
- 1 < FinalSP
THEN FinalSP
= SP
- TagParam
- 1
FOR SP
= InitialSP
TO FinalSP
+ 1 STEP -1: STACK
(SP
) = "":
NEXT SP
SP = FinalSP
PUSH RuleID, OutTxt
ExecuteParseRule = -1
DbgOutput "Rule ACCEPTED!"
'PCODE = RuleID
'
' Generates a /blockname/ as used in COMMON statements, using the ID at
' CODE(DP)
'
ID = FetchINT(DP)
IF ID
<> -1 THEN x$
= " /" + GetID
(ID
) + "/" ELSE x$
= ""
'
' Reads a null-terminate string. These are only found in DATA statements
' and the null always seems to be at the end of the string anyway, but we
' will process it properly to be sure.
'
CSTR$ = FetchRAW(DP)
FetchCSTR$ = CSTR$
'
' Fetches an identifier from the current TOKEN data by performing a symbol
' table lookup on the word at the specified offset.
'
FetchID$ = ""
FetchID$
= GetID
(CVI(MID$(TOKEN
, Offset
+ 3, 2)))
ID$
= GetID
(CVI(MID$(TOKEN
, i
, 2)))
IF IdList$
<> "" THEN IdList$
= IdList$
+ ", " IdList$ = IdList$ + ID$
FetchIDList = IdList$
'
' Returns the integer at the specified zero-based offset from the start
' of the token data.
'
FetchINT = -1
FetchINT
= CVI(MID$(TOKEN
, Offset
+ 3, 2))
'
' Returns the integer at the specified zero-based offset from the start
' of the token data as a LONG value.
'
FetchINTASLONG = -1
FetchINTASLONG
= CVI(MID$(TOKEN
, Offset
+ 3, 2)) AND &HFFFF&
'
' Reads a literal 64-bit float from the p-code and returns its string
' representation. Using the "{dbl}" tag in the SHIFT procedure is a more
' convienient method to extract literals.
'
' The IP is passed by reference, and will be incremented to the code
' following the literal. There is no radix option for floating point values.
'
FetchLiteralDBL$ = "0#"
Value#
= CVD(MID$(TOKEN
, DP
+ 3, 8))
' If the single and double precision representations are equal, we will
' insert a # to indicate double precision.
FetchLiteralDBL$ = Txt$
'
' Reads a literal 16-bit integer from the code and returns its string
' representation. Using the "{int}" tag in ExecuteParseRule is a more
' convienient method to extract literals.
'
' The Radix parameter may be 8, 10 or 16 to produce
' the desired number format, or use the "{int&o}" and "{int&h}" tags.
'
FetchLiteralINT$ = "0"
Value
= CVI(MID$(TOKEN
, Offset
+ 3, 2))
CASE 10: Txt$
= ITOA$
(Value
)
FetchLiteralINT$ = Txt$
'
' Reads a literal 32-bit integer from the code and returns its string
' representation. Using the "{lng}" tag in ExecuteParseRule is a more
' convienient method to extract literals.
'
' The Radix parameter may be 8, 10 or 16 to produce the desired number
' format, or use the "{lng&o}" and "{lng&h}" tags.
'
FetchLiteralLNG$ = "0"
Value
= CVL(MID$(TOKEN
, Offset
+ 3, 4))
CASE 10: Txt$
= LTOA$
(Value
)
IF Value
< 65536 THEN Txt$
= Txt$
+ "&"
FetchLiteralLNG$ = Txt$
'
' Reads a literal 32-bit float from the p-code and returns its string
' representation. Using the "{sng}" tag in the SHIFT procedure is a more
' convienient method to extract literals.
'
' The IP is passed by reference, and will be incremented to the code
' following the literal. There is no radix option for floating point values.
'
FetchLiteralSNG$ = "0"
Value!
= CVS(MID$(TOKEN
, DP
+ 3, 4))
FetchLiteralSNG$ = Txt$
FetchLNG = -1
FetchLNG
= CVL(MID$(TOKEN
, Offset
+ 3, 4))
FetchRAW$
= MID$(TOKEN
, 3 + Offset
)
RuleOffset = 1
RuleEnd
= LEN(ParseRule
) + 1
BraceOffset
= INSTR(RuleOffset
, ParseRule
, "{") PipeOffset
= INSTR(RuleOffset
, ParseRule
, "|")
RuleOffset
= INSTR(BraceOffset
+ 1, ParseRule
, "}")
FindRuleDelimiter = PipeOffset
'
' Flushes all stack entries to STACK(0), ready for final processing into
' a program line.
'
STACK
(0) = STACK
(0) + MID$(STACK
(i
), 3) STACK(i) = ""
SP = 0
'
' Returns an integer identifier for a parse rule symbol
'
'----------------------------------------------------------------------------
' Parse rule symbols my be literal integers
'----------------------------------------------------------------------------
IF StringToINT
(SymbolID$
, SymbolID%
) THEN GetHashedSymbol% = SymbolID%
Hash = HashPJW(SymbolID$)
LookupSymbol = "[" + SymbolID$ + "]"
SymbolOffset
= INSTR(SymbolHashTable
(Hash
), LookupSymbol
)
SymbolID% = SymbolHashEntries
SymbolID%
= SymbolID%
+ UBOUND(ParseRules
) + 1 SymbolID$
= RIGHT$(SymbolHashTable
(Hash
), 2) IF SymbolID$
<> "" THEN SymbolID%
= CVI(SymbolID$
) + 1
SymbolID$
= MKI$(SymbolID%
)
SymbolHashTable(Hash) = SymbolHashTable(Hash) + LookupSymbol + SymbolID$
SymbolHashEntries = SymbolHashEntries + 1
SymbolOffset
= SymbolOffset
+ LEN(LookupSymbol
)
SymbolID$
= MID$(SymbolHashTable
(Hash
), SymbolOffset
, 2) SymbolID%
= CVI(SymbolID$
)
GetHashedSymbol% = SymbolID% '+ UBOUND(ParseRules) + 1
'
' Reads an identifier from the symbol table data stored in the SYMTBL
' array.
'
'----------------------------------------------------------------------------
' Convert offset to LONG to we can read above 32767
'----------------------------------------------------------------------------
SymTblOfs&
= SymTblOffset
AND &HFFFF&
'----------------------------------------------------------------------------
' offset FFFF is used as a shortcut for "0" in statements such as
' ON ERROR GOTO 0
'----------------------------------------------------------------------------
GetID$ = "0"
'----------------------------------------------------------------------------
' Make sure we can at least read the first 4 bytes
'----------------------------------------------------------------------------
GetID$ = "®QB45BIN:SymbolTableError¯"
Symbol&
= (Offset
AND &HFFFF&
) + SymTblOfs&
SymbolFlags
= PEEK(Symbol&
+ 2)
' Short line numbers are stored as integers.
NumericID&
= PEEK(Symbol&
+ 4) OR PEEK(Symbol&
+ 5) * &H100&
' Identifier is a text string - extract it. Note the string may be
' a line number.
Length
= PEEK(Symbol&
+ 3)
GetID$ = "SymbolTableError"
GetID$ = ID$
'
' Removes the parse rule id::= from a string and returns its numeric ID.
'
'----------------------------------------------------------------------------
' The default rule ID is always the PCODE
'----------------------------------------------------------------------------
GetParseRuleID
= SetHashedSymbol
(LEFT$(ParseRule
, i
- 1), TokenID
) ParseRule
= MID$(ParseRule
, i
+ 3)
GetParseRuleID = -1
GetParseRuleLHS
= LEFT$(ParseRule
, i
- 1)
CASE "blockname": SubstTxt
= FetchBlockName
(DP
) CASE "circle-args": SubstTxt
= SubstTagCIRCLE
CASE "input-args": SubstTxt
= SubstTagINPUT
CASE "line-args": SubstTxt
= SubstTagLINE
CASE "lock-args": SubstTxt
= SubstTagLOCK
CASE "open-args": SubstTxt
= SubstTagOPEN
CASE "action-verb": SubstTxt
= SubstTagVERB
CASE "keymode": SubstTxt
= SubstTagKEY
CASE "type-abbr": SubstTxt
= GetTypeAbbr
(HPARAM
)
CASE "call": SubstTxt
= ParseCALL
(0) CASE "call()": SubstTxt
= ParseCALL
(-1)
CASE "defxxx": SubstTxt
= SubstTagDEFxxx
(QBBinDefType
())
CASE "newline-include": SubstTxt
= MKI$(&H20D)
CASE "type": SubstTxt
= GetTypeName$
(FetchINT
(DP
)) CASE "id": SubstTxt
= GetID
(FetchINT
(DP
)) CASE "id+": SubstTxt
= GetID
(FetchINT
(DP
)) + GetTypeSuffix
(HPARAM
) CASE "id-list": SubstTxt
= FetchIDList
(DP
) CASE "id(decl)": SubstTxt
= ParseArrayDecl
CASE "id(expr)": SubstTxt
= ParseArrayExpr
CASE "hprm": SubstTxt
= ITOA$
(HPARAM
) CASE "int": SubstTxt
= FetchLiteralINT
(DP
, 10) CASE "int&h": SubstTxt
= FetchLiteralINT
(DP
, 16) CASE "int&o": SubstTxt
= FetchLiteralINT
(DP
, 8) CASE "label": SubstTxt
= FetchID
(DP
):
IF NOT IsLineNumber
(SubstTxt
) THEN SubstTxt
= SubstTxt
+ ":"
CASE "lng": SubstTxt
= FetchLiteralLNG
(DP
, 10) CASE "lng&h": SubstTxt
= FetchLiteralLNG
(DP
, 16) CASE "lng&o": SubstTxt
= FetchLiteralLNG
(DP
, 8) CASE "nul": SubstTxt
= "" CASE "sng": SubstTxt
= FetchLiteralSNG
(DP
) CASE "dbl": SubstTxt
= FetchLiteralDBL
(DP
) CASE "qstr": SubstTxt
= Quote
(FetchRAW
(DP
)) CASE "cstr": SubstTxt
= FetchCSTR
(DP
) CASE "raw": SubstTxt
= FetchRAW
(DP
) CASE "varargs": SubstTxt
= ParseVarArgs
CASE "procdecl": SubstTxt
= ParseProcDecl$
(DP
, 0) CASE "procdecl()": SubstTxt
= ParseProcDecl$
(DP
, -1) CASE "proctype": SubstTxt
= QBBinProcedureType
CASE "thaddr": SanityCheck DP
SubstTxt = "®QB45BIN:bad tag¯"
GetTaggedItem$ = SubstTxt
TotalLines = 0
IncludeLines = 0
FTell&
= LOC(QBBinFile
) + 1
GET #QBBinFile
, 27, SymTblLen%
ModuleLOC&
= LOC(QBBinFile
) + (SymTblLen%
AND &HFFFF&
) + 1
SEEK #QBBinFile
, ModuleLOC&
GET #QBBinFile
, , ModuleLen%
SEEK #QBBinFile
, LOC(QBBinFile
) + (ModuleLen%
AND &HFFFF&
) + 9
GET #QBBinFile
, , NumTotLines%
GET #QBBinFile
, , NumIncLines%
TotalLines
= TotalLines
+ (NumTotLines%
AND &HFFFF&
) IncludeLines
= IncludeLines
+ (NumIncLines%
AND &HFFFF&
)
SEEK #QBBinFile
, LOC(QBBinFile
) + 5
ProcedureCOUNT = ProcedureCOUNT + 1
GET #QBBinFile
, , NameLen%
SEEK #QBBinFile
, LOC(QBBinFile
) + (NameLen%
AND &HFFFF&
) + 4
SEEK #QBBinFile
, ModuleLOC&
FOR i
= 1 TO ProcedureCOUNT
GET #QBBinFile
, , ModuleLen%
ProcedureLOC
(i
) = LOC(QBBinFile
) + (ModuleLen%
AND &HFFFF&
) + 17 SEEK #QBBinFile
, ProcedureLOC
(i
) + 1
GET #QBBinFile
, , ProcedureNameLEN%
ProcedureNAME
(i
) = STRING$(ProcedureNameLEN%
, 0) GET #QBBinFile
, , ProcedureNAME
(i
) ProcedureNAME
(i
) = UCASE$(ProcedureNAME
(i
))
'------------------------------------------------------------------------
' Incremental bubble sort of procedure names
'------------------------------------------------------------------------
IF QBBinOption.SortProceduresAZ
THEN SWAP ProcedureNAME
(j
+ 1), ProcedureNAME
(j
) SWAP ProcedureLOC
(j
+ 1), ProcedureLOC
(j
)
SEEK #QBBinFile
, LOC(QBBinFile
) + 4
FOR i
= 1 TO ProcedureCOUNT
'PRINT ProcedureNAME(i)
QBBinProcedureIndex
= QBBinProcedureIndex
+ MKL$(ProcedureLOC
(i
))
ERASE ProcedureNAME
, ProcedureLOC
IF QBBinOption.OmitIncludedLines
THEN GetTotalLines = TotalLines - IncludedLines
GetTotalLines = TotalLines
'
' Returns the abbreviated name for a built-in type (ie: LNG or DBL).
'
GetTypeAbbr$ = TypeSpecifiers(LIMIT(TypeID, 0, 5), 2)
LTypeID&
= TypeID
AND &HFFFF&
GetTypeName$ = GetID$(TypeID) ' User-define type
GetTypeName$ = TypeSpecifiers(LTypeID&, 1)
GetTypeSuffix$ = TypeSpecifiers(LIMIT(TypeID, 0, 5), 3)
'
' Implementation of PJW hash, written to avoid 32-bit overflow.
'
h = h + (k \ 16)
g
= (h
AND &HF000000) \
2 ^ 20
h
= (h
AND &HFFFFFF) * 16 + (k
AND 15)
HashPJW%
= h
MOD SymbolHashBuckets
LIMIT = xMin
LIMIT = xMax
LIMIT = x
'----------------------------------------------------------------------------
' Read module size and convert to long to lose sign bit. Note that modules
' should always be a multiple of two in size since all the tokens are 16
' bits.
'----------------------------------------------------------------------------
GET #QBBinFile
, , szModule%
szModule&
= (szModule%
AND &HFFFF&
) szModule% = (szModule& + 1) \ 2
ReadToArrayINT QBBinFile, CODE(), szModule&
'----------------------------------------------------------------------------
' There is always 16 bytes of data after a code block
'----------------------------------------------------------------------------
QBBinCloseFile
LoadMainModule = -1
IF QBBinProcedureIndex
= "" THEN QBBinCloseFile
ProcedureLOC&
= CVL(LEFT$(QBBinProcedureIndex
, 4)) QBBinProcedureIndex
= MID$(QBBinProcedureIndex
, 5) SEEK #QBBinFile
, ProcedureLOC&
QBBinCloseFile
GET #QBBinFile
, , ProcNameLen%
QBBinProcedureName
= STRING$(ProcNameLen%
AND &HFFFF&
, 0) GET #QBBinFile
, , QBBinProcedureName
GET #QBBinFile
, , ProcCodeLen%
ReadToArrayINT QBBinFile
, CODE
(), ProcCodeLen%
AND &HFFFF&
LoadNextProcedure = -1
TokenLBound = &H7FFF
TokenUBound = 0
TokenLength = 0
'----------------------------------------------------------------------------
' Clear the symbol hash table
'----------------------------------------------------------------------------
FOR i
= 0 TO SymbolHashBuckets
- 1: SymbolHashTable
(i
) = "":
NEXT i
SymbolHashEntries = 0
'----------------------------------------------------------------------------
' PASS 1: Enumerate all tokens
'----------------------------------------------------------------------------
RestoreParseRules
DO WHILE ReadParseRule
(TokenPCODE
, TokenLength
, ParseRule
)
TokenLBound = MIN(TokenPCODE, TokenLBound)
TokenUBound = MAX(TokenPCODE, TokenLBound)
'----------------------------------------------------------------------------
' PASS 2: Generate token strings
'----------------------------------------------------------------------------
RestoreParseRules
DO WHILE ReadParseRule
(TokenPCODE
, TokenLength
, ParseRule
)
'------------------------------------------------------------------------
' If this is the first rule for this PCODE, then we'll write the
' length of the token data as the first word.
'------------------------------------------------------------------------
IF ParseRules
(TokenPCODE
) = "" THEN ParseRules
(TokenPCODE
) = MKI$(TokenLength
)
RuleID = GetParseRuleID(ParseRule, TokenPCODE)
IF RuleID
= -1 THEN RuleID
= TokenPCODE
ParseRule
= MKI$(LEN(ParseRule
)) + MKI$(RuleID
) + ParseRule
ParseRules(TokenPCODE) = ParseRules(TokenPCODE) + ParseRule
QBBinTok.SUBDEF = GetHashedSymbol("subdef")
QBBinTok.FUNCDEF = GetHashedSymbol("funcdef")
QBBinTok.DEFTYPE = GetHashedSymbol("deftype")
'
' Returns the token id of the next unprocessed token without modifying IP.
' Neccessary for REDIM, which causes an array expression to behave like
' an array declaration, for reasons best known to the QB45 dev team.
'
LookAhead = -1
LookAhead
= CODE
(IP
) AND &H3FF
RuleAsTypeID = GetHashedSymbol("astype")
RuleDeclID = GetHashedSymbol("decl")
RuleDeclsID = GetHashedSymbol("decls")
nElmts = FetchINT(0)
ID$ = FetchID(2) + GetTypeSuffix(HPARAM)
IF StackPeek
(0) = RuleAsTypeID
THEN ArgC = 1
AsType$ = "{0}"
nElmts = nElmts - 1
Indices$ = STAG(ArgC) + Indices$
ArgC = ArgC + 1
IF StackPeek
(ArgC
) <> &H18 THEN Indices$
= " TO " + Indices$
IF nElmts
THEN Indices$
= ", " + Indices$
IF Indices$
<> "" THEN Indices$
= "(" + Indices$
+ ")"
IF StackPeek
(ArgC
) = RuleDeclsID
THEN ParseArrayDecl$ = STAG(ArgC) + ", " + ID$ + Indices$ + AsType$
ParseArrayDecl$ = STAG(ArgC) + " " + ID$ + Indices$ + AsType$
ParseArrayDecl$ = ID$ + Indices$ + AsType$
'
' Generates a parse rule for an array expression.
'
ParseArrayExpr = ParseArrayDecl
'IF PCODE = 15 THEN ArgC = 1
nElmts = FetchINT(0)
ID$ = FetchID(2) + GetTypeSuffix(HPARAM)
Indices$ = ", " + STAG(ArgC) + Indices$
Indices$ = STAG(ArgC) + Indices$
ArgC = ArgC + 1
Indices$ = "(" + Indices$ + ")"
ParseArrayExpr = ID$ + Indices$
'
' Generates parse rule fragment for a procedure call
'
ArgC = FetchINT(0)
ArgV$ = STAG(ArgI) + ", " + ArgV$
ArgV$ = STAG(ArgI) + ArgV$
IF Parenthesis
THEN ArgV$
= "(" + ArgV$
+ ")" ELSE ArgV$
= " " + ArgV$
ParseCALL$ = ArgV$
'
' This helper function parses a SUB or FUNCTION declaration, or a
' SUB/FUNCTION/DEF FN definition.
'
ID$ = GetID(FetchINT(DP + 0))
Flags = FetchINTASLONG(DP + 2)
ArgC = FetchINTASLONG(DP + 4)
LenALIAS
= Flags \
&H400 AND &H1F
Arguments$ = ""
ProcType
= (Flags
AND &H300) \
256
CASE 1: ID$
= "SUB " + ID$
+ TS$: QBBinProcedureType
= "SUB" CASE 2: ID$
= "FUNCTION " + ID$
+ TS$: QBBinProcedureType
= "FUNCTION" CASE 3: ID$
= "DEF " + ID$
+ TS$: QBBinProcedureType
= "DEF"
'
' Process arguments list
'
ArgName$ = GetID(FetchINT(DP + ArgI * 6 + 0))
ArgFlags = FetchINT(DP + ArgI * 6 + 2)
ArgType = FetchINT(DP + ArgI * 6 + 4)
'------------------------------------------------------------------------
' Process special argument flags. Not all of these can be combined,
' but we'll just assume the file contains a valid combination.
'------------------------------------------------------------------------
IF ArgFlags
AND &H200 THEN ArgName$
= ArgName$
+ GetTypeSuffix
(ArgType
) IF ArgFlags
AND &H400 THEN ArgName$
= ArgName$
+ "()" IF ArgFlags
AND &H800 THEN ArgName$
= "SEG " + ArgName$
IF ArgFlags
AND &H1000 THEN ArgName$
= "BYVAL " + ArgName$
IF ArgFlags
AND &H2000 THEN ArgName$
= ArgName$
+ " AS " + GetTypeName
(ArgType
)
Arguments$ = ArgName$
Arguments$ = Arguments$ + ", " + ArgName$
IF Parenthesis
OR Arguments$
<> "" THEN Arguments$
= " (" + Arguments$
+ ")"
'
' Process CDECL and ALIAS modifiers
'
IF Flags
AND fCDECL
THEN ID$
= ID$
+ " CDECL"
AliasName$
= LEFT$(FetchRAW
(DP
+ ArgI
* 6), LenALIAS
) IF LenALIAS
THEN ID$
= ID$
+ " ALIAS " + AliasName$
ParseProcDecl$ = ID$ + Arguments$
'
'
'
ArgC = FetchINT(0)
IF NULARG
= 0 THEN NULARG
= GetHashedSymbol
("nularg")
IF StackPeek
(ArgI
) <> NULARG
THEN ArgV$
= ", " + ArgV$
ArgV$ = STAG(ArgI) + ArgV$
'----------------------------------------------------------------------------
' Trim trailing commas
'----------------------------------------------------------------------------
IF ArgV$
<> "" THEN ArgV$
= " " + ArgV$
ParseVarArgs$ = ArgV$
POP$
= MID$(STACK
(SP
), 3) SP = SP - 1
'
' The following special codes may be embedded in a string:
'
' 0xccnn0D - RLE encoding (used by QB45 comments)
' 0xnnnn000D - Indentation marker
' 0x101D - NEWLINE marker 1
' 0x201D - NEWLINE marker 2
'
TextBegin = 1
'------------------------------------------------------------------------
' Look for special symbol marker
'------------------------------------------------------------------------
Marker
= INSTR(TextBegin
, STACK
(0), CHR$(&HD)) IF Marker
= 0 THEN Marker
= LEN(STACK
(0)) + 1
'------------------------------------------------------------------------
' Copy leading text to output string
'------------------------------------------------------------------------
OutTxt
= OutTxt
+ MID$(STACK
(0), TextBegin
, Marker
- TextBegin
) TextBegin = Marker
OffsetFromNewline = OffsetFromNewline + Marker - TextBegin
'----------------------------------------------------------------
' Indentation
'----------------------------------------------------------------
RunLn&
= CVI(MID$(STACK
(0), Marker
+ 2)) AND &HFFFF&
RunLn&
= RunLn&
- CLNG(OffsetFromNewline
)
IF (RunLn&
< 0) THEN RunLn&
= 1
OffsetFromNewline = OffsetFromNewline + RunLn&
OutTxt
= OutTxt
+ SPACE$(RunLn&
) TextBegin = Marker + 4
'----------------------------------------------------------------
' Newline
'----------------------------------------------------------------
DiscardLine = 0
FlushToOutput = -1
OffsetFromNewline = 0
TextBegin = Marker + 2
'----------------------------------------------------------------
' Newline - $INCLUDEd file
'----------------------------------------------------------------
DiscardLine = QBBinOption.OmitIncludedLines
FlushToOutput = -1
OffsetFromNewline = 0
TextBegin = Marker + 2
'----------------------------------------------------------------
' RLE encoded comment
'----------------------------------------------------------------
RunLn&
= ASC(MID$(STACK
(0), Marker
+ 1)) RunCh$
= MID$(STACK
(0), Marker
+ 2)
OutTxt
= OutTxt
+ STRING$(RunLn&
, RunCh$
)
OffsetFromNewline = OffsetFromNewline + RunLn&
TextBegin = Marker + 3
QBBinProgramLine = OutTxt
QBBinLineReady
= NOT DiscardLine
OutTxt = ""
STACK
(0) = OutTxt
+ MID$(STACK
(0), Marker
)
' Procedure DEFTYPE defaults to SINGLE
IF LookAhead
<> QBBinTok.DEFTYPE
THEN IP = IP - 1
UnwantedReturnValue$ = SubstTagDEFxxx(ProcDefType())
'FOR i = 1 TO 26: PRINT GetTypeSuffix(ProcDefType(i)); : NEXT i: PRINT
'PRINT QBBinProcedureName
'IF i = 3 THEN i = i + 1
AnythingOutput = 0
InitialLetter = 0
OutTxt = ""
BITSET = 0
BITSET = ProcDefType(j) = i
BITSET
= BITSET
AND QBBinDefType
(j
) <> i
InitialLetter = j + 64
IF AnythingOutput
THEN OutTxt
= OutTxt
+ ", "
OutTxt
= OutTxt
+ CHR$(InitialLetter
)
Range = j + 64 - InitialLetter
IF Range
> 1 THEN OutTxt
= OutTxt
+ "-" + CHR$(j
+ 63)
AnythingOutput = -1
InitialLetter = 0
PUSH QBBinTok.DEFTYPE, "DEF" + GetTypeAbbr(i) + " " + OutTxt
FlushStack
FOR i
= 1 TO 26: QBBinDefType
(i
) = ProcDefType
(i
):
NEXT i
ProcessToken = 0
ProcessToken = -1
DefaultParseRule
SP = SP + 1
STACK
(SP
) = MKI$(ID
) + Txt
QBBinFile = 0
QBBinEOF = -1
'
QBBinEOF = 0
GET #QBBinFile
, , Version%
'----------------------------------------------------------------------------
' Only QB45 is currently supported
'----------------------------------------------------------------------------
IF (Magic%
<> &HFC) OR (Version%
<> 1) THEN PRINT "ERROR: The file you provided does not have a valid QB45 header."
' Don't delete this - alpha sorter needs it!
x = GetTotalLines
'----------------------------------------------------------------------------
' Read symbol table size and convert to long to lose sign bit
'----------------------------------------------------------------------------
GET #QBBinFile
, 27, szSymTbl%
szSymTbl&
= szSymTbl%
AND &HFFFF&
'----------------------------------------------------------------------------
' Load symbol table to memory and return file number
'----------------------------------------------------------------------------
ReadToArrayINT QBBinFile, SYMTBL(), szSymTbl&
'----------------------------------------------------------------------------
' If main module is empty, look for non-empty procedure
'----------------------------------------------------------------------------
Meta = 0
PostProcess
QBBinReadLine = QBBinProgramLine
QBBinLineReady = 0
QBBinProgramLine = ""
QBBinCloseFile
DefaultParseRule
'------------------------------------------------------------------------
' Trap some special tokens
'------------------------------------------------------------------------
'------------------------------------------------------------------------
' Token 0x008 appears at the end of the code (before the watch list)
'------------------------------------------------------------------------
NoMoreTokens = -1
PUSH
0, MKI$(&H10D) ' Force blank line before SUB/FUNCTION ProcessProcDefType
NewProc = -1
'ProcessProcDefType
'END SELECT
'SELECT CASE StackPeek(0)
CASE QBBinTok.SUBDEF: Meta
= QBBinMeta.
SUB
PostProcess
QBBinReadLine = QBBinProgramLine
QBBinLineReady = 0
QBBinProgramLine = ""
'------------------------------------------------------------------------
' Ugh... static. I'm being lazy.
'------------------------------------------------------------------------
'------------------------------------------------------------------------
' If RuleItem isn't empty, extract the next rule.
'------------------------------------------------------------------------
ParseRule = DelimitParseRule(RuleItem, DefaultRuleID)
ReadParseRule = -1
ReadParseRule = 0
'------------------------------------------------------------------------
' Loop until we have something which isn't the .default directive
'------------------------------------------------------------------------
'------------------------------------------------------------------------
' The rule list is terminated by a period.
'------------------------------------------------------------------------
RuleItem = ""
DefaultRuleID = ""
'------------------------------------------------------------------------
' If RuleItem is a number, then assume it is the start of a new token.
' Otherwise, we assume it is an additional rule of the previous token.
'------------------------------------------------------------------------
IF (StringToINT
(RuleItem
, TokenID
)) THEN
'--------------------------------------------------------------------
' If the token length is not omitted, then we need to read again
' to fetch the token parse rule. Also, an asterisk may be used to
' represent a variable length token, so we need to check for that.
'--------------------------------------------------------------------
IF StringToINT
(RuleItem
, OpLen
) THEN
OpLen = -1
OpLen = 0
'------------------------------------------------------------------------
' Extract rule and return
'------------------------------------------------------------------------
ParseRule = DelimitParseRule(RuleItem, DefaultRuleID)
ReadParseRule = -1
CONST BlockReadSize
= 1024 ' must be a multiple of 2
'----------------------------------------------------------------------------
' REDIM the array if necessary, but keep the lower bound in place
'----------------------------------------------------------------------------
FOR i
= 0 TO ByteCount
- 1 STEP BlockReadSize
BytesToRead = ByteCount - i
IF BytesToRead
> BlockReadSize
THEN BytesToRead
= BlockReadSize
GET FileNumber
, , Buffer$
'------------------------------------------------------------------------
' Copy data from string to integer array (even number of bytes only)
'------------------------------------------------------------------------
Index
= LBOUND(Array
) + i \
2 + j \
2 Array
(Index
) = CVI(MID$(Buffer$
, j
, 2))
'------------------------------------------------------------------------
' The final block may have had an odd number of bytes
'------------------------------------------------------------------------
Index
= LBOUND(Array
) + i \
2 + j \
2
'
' Reads a token into the globals PCODE and HPARAM. IP is updated to point
' To the next token, and DP points to the start of the token data.
'
ReadToken = 0
'----------------------------------------------------------------------------
' Fetch basic token information
'----------------------------------------------------------------------------
PCODE
= CODE
(IP
) AND &H3FF HPARAM
= (CODE
(IP
) AND &HFC00&
) \
1024 ReadToken = -1
'----------------------------------------------------------------------------
' If the token is outside the known token range, we have a problem.
'----------------------------------------------------------------------------
IP = IP + 1
PRINT "Bad token found.":
SYSTEM 1 'ERROR QBErrBadToken PCODE
= 0: HPARAM
= 0: TOKEN
= MKI$(0)
'----------------------------------------------------------------------------
' If the token has no information in the parse rules, then we clearly don't
' understand what it does, so increment IP and return. We will try to
' soldier on and parse the rest of the file
'----------------------------------------------------------------------------
IF ParseRules
(PCODE
) = "" THEN AOutput
"REM ®QB45BIN¯ Unkown token - " + HEX$(PCODE
) IP = IP + 1
'----------------------------------------------------------------------------
' Fetch the token data length from the parse rules to determine if the token
' is fixed or variable length
'----------------------------------------------------------------------------
'----------------------------------------------------------------------------
' If the token is variable length it will be followed by the size word, so
' read it now.
'----------------------------------------------------------------------------
IP = IP + 1
TokLen
= CODE
(IP
) AND &HFFFF&
'----------------------------------------------------------------------------
' Read the token data into the TOKEN string. Note that due to a bug in QB64,
' we can not use IP as the control variable.
'----------------------------------------------------------------------------
FOR DP
= IP
+ 1 TO IP
+ (TokLen
+ 1) \
2 TOKEN
= TOKEN
+ MKI$(CODE
(DP
)) IP = DP
TOKEN
= LEFT$(TOKEN
, TokLen
+ 2)
'
' This is so I can change parse rules later if I add QB40 support.
'
ThAddr = FetchINTASLONG(DP)
ThAddr = ThAddr \ 2 - 1
'ERROR QBBinErrInsane
'----------------------------------------------------------------------------
' Parse rule symbols my be literal integers
'----------------------------------------------------------------------------
Hash = HashPJW(SymbolName$)
LookupSymbol = "[" + SymbolName$ + "]"
SymbolOffset
= INSTR(SymbolHashTable
(Hash
), LookupSymbol
)
SymbolHashTable
(Hash
) = SymbolHashTable
(Hash
) + LookupSymbol
+ MKI$(SymbolID
)
SetHashedSymbol = SymbolID
SymbolOffset
= SymbolOffset
+ LEN(LookupSymbol
)
ID$
= MID$(SymbolHashTable
(Hash
), SymbolOffset
, 2) SetHashedSymbol
= CVI(ID$
)
'GetHashedSymbol% = SymbolID% + UBOUND(ParseRules) + 1
'
' Peeks at the ID of a stack item
'
StackPeek = -1
StackPeek
= CVI(LEFT$(STACK
(SP
- OffsetSP
), 2))
'
' STAG is a shortcut function for creating numeric stack tags dynamically
' such as {1}.
'
'
' Parses a STRING into an INTEGER, returning 0 if the string contained
' any invalid characters (not including leading and trailing whitespace).
' Only positive integers are recognised (no negative numbers!).
'
' The actual numeric value is returned in OutVal
'
SignCharacter$
= LEFT$(x$
, 1) SignMultiplier = 1
IF (SignCharacter$
= "+" OR SignCharacter$
= "-") THEN SignMultiplier
= 45 - ASC(SignCharacter$
)
FoundBadDigit
= LEN(x$
) = 0
CASE "&H", "0X": nBase
= 16: FirstDigitPos
= 3 CASE "&O": nBase
= 8: FirstDigitPos
= 3 CASE ELSE: nBase
= 10: FirstDigitPos
= 1
IF Digit
> 16 THEN Digit
= Digit
- 7 IF Digit
< 0 OR Digit
>= nBase
THEN FoundBadDigit
= -1
Value = Value * nBase
Value = Value + Digit
StringToINT
= NOT FoundBadDigit
IF NOT FoundBadDigit
THEN OutVal
= Value
* SignMultiplier
ParseRule = "{?}, {?}, {?}, {?}, {?}, {?}"
ArgC = 0
ArgI = 0
'
' The last 3 arguments are optional.
'
IF StackPeek
(ArgC
) = &H7E + i
THEN
IF ArgI
= 0 THEN ArgI
= 28 - i
* 5
MID$(ParseRule
, 27 - i
* 5, 1) = CHR$(ArgC
+ 48) ArgC = ArgC + 1
' PCODE 0x09f means no colour argument
MID$(ParseRule
, 12, 1) = CHR$(ArgC
+ 48) ArgC = ArgC + 1
' The last 3 arguments are required
MID$(ParseRule
, 7, 1) = CHR$(ArgC
+ 48): ArgC
= ArgC
+ 1 MID$(ParseRule
, 2, 1) = CHR$(ArgC
+ 48): ArgC
= ArgC
+ 1
' Remove unused arguments
ParseRule
= LEFT$(ParseRule
, ArgI
)
ArgI
= INSTR(ParseRule
, "?") ParseRule
= LEFT$(ParseRule
, ArgI
- 2) + MID$(ParseRule
, ArgI
+ 2)
SubstTagCIRCLE = ParseRule
'
' 0x01B : DEF(INT|LNG|SNG|DBL|STR) letterrange
'
' The DEFxxx token is followed by 6 bytes of data. The first two bytes give
' the absolute offset in the p-code to the correspdoning bytes of the next
' DEFxxx statement (!), or 0xFFFF if there are no more DEFxxx statements.
'
' Naturally, we can ignore these two bytes.
'
' The next 4 bytes form a 32-bit integer. The low 3 bits give the data-type
' for the DEFxxx. The upper 26 bits represent each letter or the alphabet,
' with A occupying the highest bit, and Z the lowest.
'
AlphaMask = FetchLNG(2)
DefType
= LIMIT
(AlphaMask
AND 7, 0, 5) OutTxt = "DEF" + GetTypeAbbr(DefType) + " "
' Shift the mask right once to avoid overflow problems.
AlphaMask = AlphaMask \ 2
InitialLetter = 0
AnythingOutput = 0
' We will loop one extra time to avoid code redendancy after the loop to
' clean up the Z. To ensure everything works out, we just need to make
' sure the bit after the Z is clear. We also need to clear the high 2 bits
' every time to avoid overflow ploblems.
' Get the next bit and shift the mask
BITSET
= (AlphaMask
AND &H40000000) <> 0 AlphaMask
= AlphaMask
AND &H3FFFFFE0 AlphaMask = AlphaMask * 2
'------------------------------------------------------------------------
' Update current DEFtype state
'------------------------------------------------------------------------
IF i
< 26 AND BITSET
THEN DefTypeArray
(i
+ 1) = DefType
InitialLetter = i + 65
IF AnythingOutput
THEN OutTxt
= OutTxt
+ ", "
OutTxt
= OutTxt
+ CHR$(InitialLetter
)
Range = i + 65 - InitialLetter
IF Range
> 1 THEN OutTxt
= OutTxt
+ "-" + CHR$(i
+ 64)
AnythingOutput = -1
InitialLetter = 0
SubstTagDEFxxx$ = OutTxt
Tail
= 59 - (((Flags
AND fComma
) = 1) AND 15) OutTxt$
= OutTxt$
+ "{$+0}" + CHR$(Tail
)
SubstTagINPUT = OutTxt$
CASE 1: SubstTagKEY$
= "ON" CASE 2: SubstTagKEY$
= "LIST"
LineForm = PCODE - &HBB
' 0x0bb : LINE x-x, ,[b[f]]
' 0x0bc : LINE x-x,n,[b[f]]
' 0x0bd : LINE x-x,n,[b[f]],n
' 0x0be : LINE x-x, ,[b[f]],n
CASE 0: Rule$
= "{0}, , " + BF$
CASE 1: Rule$
= "{1}, {0}, " + BF$
CASE 2: Rule$
= "{2}, {1}, " + BF$
+ ", {0}" CASE 3: Rule$
= "{1}, , " + BF$
+ ", {0}"
CASE 1: Rule$
= "{1}, {0}" CASE 2: Rule$
= "{2}, {1}, , {0}" CASE 3: Rule$
= "{1}, , , {0}"
SubstTagLINE = Rule$
Flags
= FetchINTASLONG
(0) AND &HFFFF&
SubstTagLOCK$ = "{0}"
' check high 2 bits
CASE 0: SubstTagLOCK$
= "{2}, {1} TO {0}" CASE 1: SubstTagLOCK$
= "{2}, TO {0}" CASE 2: SubstTagLOCK$
= "{1}, {0}"
ModeFlags
= FetchINT
(0) AND &HFFFF&
CASE &H1: ForMode
= "FOR INPUT" CASE &H2: ForMode
= "FOR OUTPUT" CASE &H4: ForMode
= "FOR RANDOM" CASE &H8: ForMode
= "FOR APPEND" CASE &H20: ForMode
= "FOR BINARY"
CASE 1: AccessMode
= "ACCESS READ" CASE 2: AccessMode
= "ACCESS WRITE" CASE 3: AccessMode
= "ACCESS READ WRITE"
CASE 1: LockMode
= "LOCK READ WRITE" CASE 2: LockMode
= "LOCK WRITE" CASE 3: LockMode
= "LOCK READ" CASE 4: LockMode
= "SHARED"
OutTxt = ForMode
IF (OutTxt
<> "" AND AccessMode
<> "") THEN OutTxt
= OutTxt
+ " " OutTxt = OutTxt + AccessMode
IF (OutTxt
<> "" AND LockMode
<> "") THEN OutTxt
= OutTxt
+ " " OutTxt = OutTxt + LockMode
SubstTagOPEN = OutTxt
Verbs$ = "0OR|1AND|2PRESET|3PSET|4XOR|"
VerbBegin
= INSTR(Verbs$
, CHR$(48 + LIMIT
(FetchINT
(0), 0, 4))) + 1 VerbEnd
= INSTR(VerbBegin
, Verbs$
, "|")
SubstTagVERB$
= MID$(Verbs$
, VerbBegin
, VerbEnd
- VerbBegin
)
'
' Splits a {ruletag} into it's constituent components.
'
Delimiter
= INSTR(TagTxt
, ":")
TokenizeTag = TagType.StackREL
Delimiter
= LEN(TagTxt
) + 1 TagParam = 0
TokenizeTag = TagType.StackABS
Delimiter
= LEN(TagTxt
) + 1 TagParam = 0
IF Delimiter
THEN Delimiter
= Delimiter
- 1
TokenizeTag = TagType.Recursive
TokenizeTag = TagType.TokenData
'------------------------------------------------------------------------
' If the specified stack offset is invalid, only the null tag will do.
'------------------------------------------------------------------------
IF (OffsetSP
< 0 OR OffsetSP
>= SP
) THEN ValidateStackTag = (TagTxt = "")
TagOffset = 1
Delimiter
= INSTR(TagOffset
, TagTxt
, "|") IF Delimiter
= 0 THEN Delimiter
= TagLen
+ 1
RuleSymbol
= MID$(TagTxt
, TagOffset
, Delimiter
- TagOffset
)
IF NOT StringToINT
(RuleSymbol
, RuleSymbolID
) THEN RuleSymbolID = GetHashedSymbol(RuleSymbol)
IF RuleSymbol
= "self" THEN RuleSymbolID
= RuleID
TagOffset = Delimiter + 1
ValidateStackTag
= NOT (TagLen
AND TagOffset
> TagLen
)
ValidateStackTag = 0
ValidateStackTag = -1