home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
ftp.barnyard.co.uk
/
2015.02.ftp.barnyard.co.uk.tar
/
ftp.barnyard.co.uk
/
cpm
/
walnut-creek-CDROM
/
MBUG
/
MBUG172.ARC
/
BASCONV.LBR
/
BASCONV.MYC
/
BASCONV.MYC
Wrap
Text File
|
1979-12-31
|
24KB
|
1,296 lines
;
; Basic Conversion Program
;
; Converts tokenised BASIC memory dumps to
; ASCII source code
;
; IBM version rjm 15/8/84 (original 6502 version)
; Added more tokens rjm 26/3/88
;
; Z80 version rjm 28/3/88
; TRS80 & C64 added rjm 29/3/88
version equ 20
false equ 0
true equ not false
;Set one and only one of the equates below to true
ibm equ true ;IBM PC BASIC
trs80 equ false ;TRS80 Level II BASIC
c64 equ false ;Commodore 64 BASIC 2.0
if (ibm and trs80) or (ibm and c64) or (trs80 and c64)
One version at a time, please!
endif
;Do not change these equates:
notasc equ ibm or trs80 ;numbers are not in ASCII
tabff equ ibm ;second set of tokens
tabfe equ ibm ;third "
tabfd equ ibm ;fourth "
exttab equ tabff or tabfe or tabfd
.z80
cseg
; SYSLIB routines used:
ext argv,print,ialloc,alloc,getud,logud,putud,retud
ext bbline,crlf,f$exist,f$delete,fi0$open,fo0$open
ext fi0$close,fo0$close,f0$get,f0$put,fname,initfcb
ext pfn2,cout,cin,cst,mhlfdc,ma2hc
if notasc ;only needed for numbers
ext mafdc,mhl4hc
; Routines from FLOAT.REL:
ext ftoa,mtof
endif
eof equ 1ah
ctls equ 13h
cr equ 0dh
lf equ 0ah
ctlc equ 3
bdos equ 5
wmboot equ 0
tbuff equ 80h
if ibm
maxt1 equ 0f4h
maxff equ 0a5h
maxfe equ 0a6h
maxfd equ 086h
byte1 equ 0ffh
endif
if trs80
maxt1 equ 0fbh
byte1 equ 0ffh
endif
if c64
maxt1 equ 0cbh
byte1 equ 01h
endif
start:
ld hl,tbuff+1 ;parse command line
ld de,toktab
ld a,0ffh ;put null at end
call argv
ld a,(numtok) ;get count
or a
jr z,dohelp ;help if none
ld ix,(tok1) ;see if help wanted
ld a,'/'
cp (ix)
jp nz,nohelp
cp (ix+1)
jp nz,nohelp
dohelp:
call print
db cr,lf
if ibm
db 'IBMCONV'
endif
if trs80
db 'TRSCONV'
endif
if c64
db 'C64CONV'
endif
db ' v',(version/10) + '0'
db '.',(version mod 10) + '0',cr,lf
db 'Converts '
if ibm
db 'IBM PC'
endif
if trs80
db 'TRS-80 Level II'
endif
if c64
db 'Commodore 64'
endif
db ' BASIC files to ASCII',cr,lf
db 'Usage: '
if ibm
db 'IBMCONV'
endif
if trs80
db 'TRSCONV'
endif
if c64
db 'C64CONV'
endif
db ' [du:]infile [[du:]outfile]',cr,lf
db 'Default output file is <infile>.ASC',cr,lf,0
ret
nohelp:
xor a ;request 100 byte stack
call ialloc
ld de,100
call alloc
jr nz,memok
call print
db cr,lf,'Insufficient memory.',cr,lf,0
ret
memok:
add hl,de ;get top of it
dec hl ;-1
ld sp,hl ;set stack
call putud ;save original du:
call retud ;get it
ld a,b ;save current
ld (curdrv),a
ld a,c
ld (curusr),a
ld hl,(tok1) ;parse input filename
ld de,infcb
call fname
jr nz,infok
invfn:
call print
db cr,lf,'Invalid disk/user.',cr,lf,0
jp wmboot
infok:
call setdu ;calc source du:
ld (indu),bc
ld a,(numtok) ;if second filename,
cp 2
jr c,no2fn
ld hl,(tok2) ;parse it
ld de,outfcb
call fname
jr z,invfn
call setdu
ld (outdu),bc
ld a,(outfcb+1) ;if no filename,
cp ' ' ;either space or ?
jr z,samefn
cp '?'
jr z,samefn ;filename is same
jr tstifn
no2fn:
ld bc,(indu) ;same drive/user as input
ld (outdu),bc
xor a ;clear drive ind
ld (outfcb),a
samefn:
ld hl,infcb+1 ;filename is same
ld de,outfcb+1
ld bc,8
ldir
ld hl,asctyp ;type is .ASC
ld bc,3
ldir
ld de,outfcb ;initialise it
call initfcb
tstifn:
ld bc,(indu)
call logud
ld de,infcb ;open input file
call fi0$open
jr z,opok
call print
db cr,lf,'Input file not found.',cr,lf,0
jp done2
opok:
ld bc,(outdu) ;see if o/p file exists
call logud
ld de,outfcb
call f$exist
jr z,outok
call print
db 'Output file ',0
ld de,outfcb+1
call pfn2
call print
db ' exists: Delete? ',0
ld a,0ffh ;capitalise
call bbline ;get reply
call crlf
ld a,(hl)
cp 'Y' ;must be Y
jp nz,done1 ;else quit
ld de,outfcb
call f$delete ;erase it
outok:
call fo0$open ;open it
jr z,oopok
call print
db cr,lf,'Error in opening output file.'
db cr,lf,0
jp done1
oopok:
call print
db 'Display result? ',0
ld a,0ffh
call bbline
call crlf
ld a,(hl)
cp 'Y'
ld a,0
jr nz,setdfl
ld a,0ffh ;set flag if Y
setdfl:
ld (disflg),a
;Input and output files open. Start to look at file.
ld bc,(indu) ;log into source
call logud
call f0$get ;get first byte
jp nz,dskerr
cp byte1 ;if not correct byte,
jp nz,notbas ;not a BASIC file
if c64
call f0$get ;ignore c64 load address
jp nz,dskerr
endif
;Main loop here
loop:
call cst ;char at console?
jr nz,cklink
call cin ;yes, get it
cp ctls ;if ctl-s,
jr nz,cklink
call cin ;wait for another
cp ctlc ;if ctl-c,
jp z,done ;finish
cklink:
ld bc,(indu) ;log into source
call logud
call f0$get ;get linkage to next line
jp nz,dskerr
or a ;if zero,
jr nz,glb2
call f0$get ;get another
jp nz,dskerr
or a ;if zero,
jp z,done ;done
jr glnno
glb2:
call f0$get ;get (and ignore) 2nd linkage byte
jp nz,dskerr
glnno:
call f0$get ;get 2-byte line #
jp nz,dskerr
ld l,a
call f0$get
jp nz,dskerr
ld h,a
ld de,numbuf ;convert to decimal
call mhlfdc
xor a ;put 0 at end
ld (de),a
call prnbuf ;print
ld a,' ' ;then space
call chrout
xor a ;clear quote flag
ld (quote),a
line_loop:
ld bc,(indu) ;get next character
call logud
call f0$get
jp nz,dskerr
or a ;if 0,
jr nz,tsttok
ld bc,(outdu)
call logud
ld a,cr ;do cr/lf
call chrout
ld a,lf
call chrout
jp loop ;and process next line
tsttok:
ld e,a ;save char
cp '"' ;toggle quote mode
jr nz,notquote ;if "
ld a,(quote)
xor 0ffh
ld (quote),a
ld a,e
notquote:
ld a,(quote) ;if in quote mode,
or a
ld a,e
jr z,tsttok1
if c64
call cbmconv ;convert CBM --> real ASCII if C64
endif
jr ckctl ;and no tokens allowed
tsttok1:
or a ;test the byte
jp m,proctok ;token if bit 7 set
ckctl:
cp 07fh ;don't print delete
jr c,ckctl1 ;or any above
invchr:
call dunno ;see?
jp line_loop
ckctl1:
cp ' ' ;if printable,
jr c,ctl_chr
ld bc,(outdu) ;do it
call logud
call chrout
jp line_loop
ctl_chr:
if notasc ;if numbers are not in ASCII,
cp 11h ;11 - 1a --> '0'-'9'
jr c,nctldig
cp 1bh
jr nc,nctldig
add a,01fh ;add ASCII
ld bc,(outdu)
call logud
call chrout ;output it
jp line_loop
nctldig:
cp 0bh ;01 - 0a are invalid
jr c,invchr
ld bc,(indu) ;else need more
call logud
cp 0fh ;0f is 1-byte int
jr nz,db2
call f0$get
jp nz,dskerr
ld de,numbuf
call mafdc ;convert
xor a
ld (de),a
call prnbuf ;output
jp line_loop
db2:
cp 1eh ;1b and 1e are illegal
jp z,invchr
cp 1bh
jp z,invchr
cp 1dh ;1d, 1f are floating point
jr z,fpnums
cp 1fh
jr z,fpnumd
push af ;save type
call f0$get ;get 2 bytes in hl
jp nz,dskerr
ld l,a
call f0$get
jp nz,dskerr
ld bc,(outdu)
call logud
ld h,a
pop af ;restore type
cp 0eh ;0e and 1c are decimal
jr z,decnum
cp 1ch
jr z,decnum
cp 0dh ;0d is decimal -1
jr nz,hexoct
inc hl
decnum:
ld de,numbuf ;convert
call mhlfdc
opnum:
xor a
ld (de),a
call prnbuf ;print
jp line_loop
hexoct:
push af ;save
ld a,'&'
call chrout
pop af
cp 0bh ;0b is octal
jr nz,hexnum
ld a,'O'
call chrout
ld de,numbuf
call mhl4oc ;convert
jr opnum
hexnum:
ld a,'H'
call chrout
ld de,numbuf
call mhl4hc ;convert
jr opnum
fpnums:
ld c,4 ;single precision floating point
jr fpnum
fpnumd:
ld c,8 ;double precision
fpnum:
ld b,c ;count to b
ld hl,fpacc ;get accumulator address
getfpn:
call f0$get ;get the number
jp nz,dskerr
ld (hl),a ;store it
inc hl
djnz getfpn
ld a,c ;get size
cp 4
ld a,0
jr z,fpconv
ld a,1 ;a=1 for doubles
fpconv:
push af ;save id
ld hl,fpacc ;convert to our f/p format
call mtof
pop af ;restore id
ld hl,fpacc ;convert to ascii
call ftoa
ld bc,(outdu)
call logud ;select o/p du
call outstr ;hl has address of string
jp line_loop
else
call dunno ;control characters illegal
jp line_loop
endif ;notasc
proctok:
ld (curtok),a ;save it
if tabff
cp 0ffh ;fd, fe & ff
jp z,cktkff
endif
if tabfe
cp 0feh ;have separate tables
jp z,cktkfe
endif
if tabfd
cp 0fdh
jp z,cktkfd
endif
cp maxt1+1 ;if < max,
jp nc,invchr
and 07fh ;remove bit 7
sla a ;*2
ld hl,ttab0 ;add to base
add a,l
ld l,a
ld a,h
adc a,0
ld h,a
ld e,(hl) ;get address
inc hl
ld d,(hl)
ex de,hl ;in hl
ld a,(hl) ;if 0,
or a
jp z,invchr ;invalid
call outstr ;else print it
jp line_loop
if tabff
cktkff:
call f0$get ;get next
jp nz,dskerr
ld (curtok2),a ;save
or a ;test
jp p,err2tok ;must have bit 7 set
cp maxff+1 ;and <max
jr nc,err2tok
ld hl,ttab1
pr2tok:
and 07fh ;mask
sla a
add a,l
ld l,a
ld a,h
adc a,0
ld h,a
ld e,(hl) ;get address
inc hl
ld d,(hl)
ex de,hl ;in hl
ld a,(hl) ;if 0,
or a
jr z,err2tok ;not valid
call outstr ;otherwise print
jp line_loop
err2tok:
ld a,(curtok) ;print tokens
call dunno
ld a,(curtok2)
jp invchr
endif ;tabff
if tabfe
cktkfe:
call f0$get ;get next
jp nz,dskerr
ld (curtok2),a ;save
or a ;test
jp p,err2tok ;must have bit 7 set
cp maxfe+1 ;and <max
jr nc,err2tok
ld hl,ttab2
jp pr2tok
endif ;tabfe
if tabfd
cktkfd:
call f0$get ;get next
jp nz,dskerr
ld (curtok2),a ;save
or a ;test
jp p,err2tok ;must have bit 7 set
cp maxfd+1 ;and <max
jr nc,err2tok
ld hl,ttab3
jp pr2tok
endif ;tabfd
;Incorrect byte 1, so not a BASIC file:
notbas:
call print
db cr,lf,'Not a BASIC file...',cr,lf,0
done:
ld bc,(outdu) ;close i/p & o/p
call logud
call fo0$close
done1:
ld bc,(indu)
call logud
call fi0$close
done2:
call getud ;restore original du:
jp wmboot
;Output null-terminated string in (hl)
outstr:
push af
push bc
ld bc,(outdu)
call logud
outstr1:
ld a,(hl) ;quit if 0
inc hl ;bump here
or a
jr z,outstrx
call chrout ;else output it
jr outstr1
outstrx:
pop bc
pop af
ret
;Unknown character or furphy: print hex value
dunno:
push af
push bc
push de
ld bc,(outdu)
call logud
push af ;save value
ld a,'(' ;print in brackets
call chrout
ld a,'$'
call chrout
pop af ;restore character
ld de,numbuf
call ma2hc ;convert to hex
xor a ;put 0 at end
ld (de),a
call prnbuf ;output it
ld a,')'
call chrout
pop de
pop bc
pop af
ret
if notasc
;Output HL as 6-character octal number to buffer in (de)
mhl4oc:
push hl ;save hl
push bc ;bc
push af ;and af
sla l ;get first bit
rl h
rla
and 1 ;1 bit
or '0'
ld (de),a ;store it
inc de
ld b,5 ;do 5 more
mhl4oc1:
ld c,3 ;3 bits for each
mhl4oc2:
sla l ;rotate left
rl h
rla
dec c ;for each 3 bits
jr nz,mhl4oc2
and 7 ;mask
or '0'
ld (de),a
inc de ;store
djnz mhl4oc1
pop af
pop bc
pop hl
ret
endif ;notasc
;Send character in A to output file/display
chrout:
push bc
ld c,a
call f0$put
jp nz,dskerr
ld a,(disflg) ;to console if required
or a
jr z,chrout1
ld a,c
call cout
chrout1:
pop bc
ret
;Output number in numbuf
prnbuf:
push hl
ld hl,numbuf
call outstr
pop hl
ret
;Disk error
dskerr:
call print
db cr,lf,'Disk error.',cr,lf,0
jp done
;Set up du: in b,c from fname
setdu:
dec b ;get in range
ld a,b ;test disk first
or a ;none specified if -ve
jp p,setduu
ld a,(curdrv) ;so use current
ld b,a
setduu:
ld a,c ;now try user
cp 32 ;only 0-31
ret c
ld a,(curusr) ;else current
ld c,a
ret
if c64
;Convert CBM ASCII (PETASCII) to real ASCII
; if (value >= $40) and (value <= $5f):
; value := value + 32
; if (value >= $c0) and (value <= $df):
; value := value - 128
cbmconv:
cp '@' ;upper case -> lower
ret c
cp '_'+1
jr nc,cbmconv1
or 020h
ret
cbmconv1:
cp '@'+80h
ret c
cp '_'+80h+1
ret nc
and 07fh
ret
endif ;c64
;Tables of addresses for each token
;TTAB1 is tokens prefixed by 'FF'
;TTAB2 is tokens preceded by 'FE'
;TTAB3 is tokens preceded by 'FD'
;***********************************************************************
;
; IBM-PC Token tables
;
;***********************************************************************
if ibm
ttab0: dw t80,t81,t82,t83,t84,t85,t86,t87
dw t88,t89,t8a,t8b,t8c,t8d,t8e,t8f
dw t90,t91,t92,t93,t94,t95,t96,t97
dw t98,t99,t9a,t9b,t9c,t9d,t9e,t9f
dw ta0,ta1,ta2,ta3,ta4,ta5,ta6,ta7
dw ta8,ta9,taa,tab,tac,tad,tae,taf
dw tb0,tb1,tb2,tb3,tb4,tb5,tb6,tb7
dw tb8,tb9,tba,tbb,tbc,tbd,tbe,tbf
dw tc0,tc1,tc2,tc3,tc4,tc5,tc6,tc7
dw tc8,tc9,tca,tcb,tcc,tcd,tce,tcf
dw td0,td1,td2,td3,td4,td5,td6,td7
dw td8,td9,tda,tdb,tdc,tdd,tde,tdf
dw te0,te1,te2,te3,te4,te5,te6,te7
dw te8,te9,tea,teb,tec,ted,tee,tef
dw tf0,tf1,tf2,tf3,tf4,tf5,tf6,tf7
dw tf8,tf9,tfa,tfb,tfc,tfd,tfe
;
ttab1: dw t180,t181,t182,t183,t184,t185,t186,t187
dw t188,t189,t18a,t18b,t18c,t18d,t18e,t18f
dw t190,t191,t192,t193,t194,t195,t196,t197
dw t198,t199,t19a,t19b,t19c,t19d,t19e,t19f
dw t1a0,t1a1,t1a2,t1a3,t1a4,t1a5
;
;The following tokens are not used yet
; dw t1a6,t1a7
; dw t1a8,t1a9,t1aa,t1ab,t1ac,t1ad,t1ae,t1af
; dw t1b0,t1b1,t1b2,t1b3,t1b4,t1b5,t1b6,t1b7
; dw t1b8,t1b9,t1ba,t1bb,t1bc,t1bd,t1be,t1bf
; dw t1c0,t1c1,t1c2,t1c3,t1c4,t1c5,t1c6,t1c7
; dw t1c8,t1c9,t1ca,t1cb,t1cc,t1cd,t1ce,t1cf
; dw t1d0,t1d1,t1d2,t1d3,t1d4,t1d5,t1d6,t1d7
; dw t1d8,t1d9,t1da,t1db,t1dc,t1dd,t1de,t1df
; dw t1e0,t1e1,t1e2,t1e3,t1e4,t1e5,t1e6,t1e7
; dw t1e8,t1e9,t1ea,t1eb,t1ec,t1ed,t1ee,t1ef
; dw t1f0,t1f1,t1f2,t1f3,t1f4,t1f5,t1f6,t1f7
; dw t1f8,t1f9,t1fa,t1fb,t1fc,t1fd,t1fe,t1ff
;
ttab2: dw t280,t281,t282,t283,t284,t285,t286,t287
dw t288,t289,t28a,t28b,t28c,t28d,t28e,t28f
dw t290,t291,t292,t293,t294,t295,t296,t297
dw t298,t299,t29a,t29b,t29c,t29d,t29e,t29f
dw t2a0,t2a1,t2a2,t2a3,t2a4,t2a5,t2a6
ttab3: dw t380,t381,t382,t383,t384,t385,t386
;Names for each token:-
;Unknown or unused tokens have zero as the only value.
t80: db 0
t81: db 'END',0
t82: db 'FOR',0
t83: db 'NEXT',0
t84: db 'DATA',0
t85: db 'INPUT',0
t86: db 'DIM',0
t87: db 'READ',0
t88: db 'LET',0
t89: db 'GOTO',0
t8a: db 'RUN',0
t8b: db 'IF',0
t8c: db 'RESTORE',0
t8d: db 'GOSUB',0
t8e: db 'RETURN',0
t8f: db 'REM',0
t90: db 'STOP',0
t91: db 'PRINT',0
t92: db 'CLEAR',0
t93: db 'LIST',0
t94: db 'NEW',0
t95: db 'ON',0
t96: db 'WAIT',0
t97: db 'DEF',0
t98: db 'POKE',0
t99: db 'CONT',0
t9a: db 0
t9b: db 0
t9c: db 'OUT',0
t9d: db 'LPRINT',0
t9e: db 'LLIST',0
t9f: db 0
ta0: db 'WIDTH',0
ta1: db 'ELSE',0
ta2: db 'TRON',0
ta3: db 'TROFF',0
ta4: db 'SWAP',0
ta5: db 'ERASE',0
ta6: db 'EDIT',0
ta7: db 'ERROR',0
ta8: db 'RESUME',0
ta9: db 'DELETE',0
taa: db 'AUTO',0
tab: db 'RENUM',0
tac: db 'DEFSTR',0
tad: db 'DEFINT',0
tae: db 'DEFSNG',0
taf: db 'DEFDBL',0
tb0: db 'LINE',0
tb1: db 'WHILE',0
tb2: db 'WEND',0
tb3: db 'CALL',0
tb4: db 0
tb5: db 0
tb6: db 0
tb7: db 'WRITE',0
tb8: db 'OPTION',0
tb9: db 'RANDOMIZE',0
tba: db 'OPEN',0
tbb: db 'CLOSE',0
tbc: db 'LOAD',0
tbd: db 'MERGE',0
tbe: db 'SAVE',0
tbf: db 'COLOR',0
tc0: db 'CLS',0
tc1: db 'MOTOR',0
tc2: db 'BSAVE',0
tc3: db 'BLOAD',0
tc4: db 'SOUND',0
tc5: db 'BEEP',0
tc6: db 'PSET',0
tc7: db 'PRESET',0
tc8: db 'SCREEN',0
tc9: db 'KEY',0
tca: db 'LOCATE',0
tcb: db 0
tcc: db 'TO',0
tcd: db 'THEN',0
tce: db 'TAB(',0
tcf: db 'STEP',0
td0: db 'USR',0
td1: db 'FN',0
td2: db 'SPC(',0
td3: db 'NOT',0
td4: db 'ERL',0
td5: db 'ERR',0
td6: db 'STRING$',0
td7: db 'USING',0
td8: db 'INSTR',0
td9: db '''',0
tda: db 'VARPTR',0
tdb: db 'CSRLIN',0
tdc: db 'POINT',0
tdd: db 'OFF',0
tde: db 'INKEY$',0
tdf: db 0
te0: db 0
te1: db 0
te2: db 0
te3: db 0
te4: db 0
te5: db 0
te6: db '>',0
te7: db '=',0
te8: db '<',0
te9: db '+',0
tea: db '-',0
teb: db '*',0
tec: db '/',0
ted: db '^',0
tee: db 'AND',0
tef: db 'OR',0
tf0: db 'XOR',0
tf1: db 'EQV',0
tf2: db 'IMP',0
tf3: db 'MOD',0
tf4: db '\',0
tf5: db 0
tf6: db 0
tf7: db 0
tf8: db 0
tf9: db 0
tfa: db 0
tfb: db 0
tfc: db 0
tfd: db 0
tfe: db 0
;
t180: db 0
t181: db 'LEFT$',0
t182: db 'RIGHT$',0
t183: db 'MID$',0
t184: db 'SGN',0
t185: db 'INT',0
t186: db 'ABS',0
t187: db 'SQR',0
t188: db 'RND',0
t189: db 'SIN',0
t18a: db 'LOG',0
t18b: db 'EXP',0
t18c: db 'COS',0
t18d: db 'TAN',0
t18e: db 'ATN',0
t18f: db 'FRE',0
t190: db 'INP',0
t191: db 'POS',0
t192: db 'LEN',0
t193: db 'STR$',0
t194: db 'VAL',0
t195: db 'ASC',0
t196: db 'CHR$',0
t197: db 'PEEK',0
t198: db 'SPACE$',0
t199: db 'OCT$',0
t19a: db 'HEX$',0
t19b: db 'LPOS',0
t19c: db 'CINT',0
t19d: db 'CSNG',0
t19e: db 'CDBL',0
t19f: db 'FIX',0
t1a0: db 'PEN',0
t1a1: db 'STICK',0
t1a2: db 'STRIG',0
t1a3: db 'EOF',0
t1a4: db 'LOC',0
t1a5: db 'LOF',0
;
t280: db 0
t281: db 'FILES',0
t282: db 'FIELD',0
t283: db 'SYSTEM',0
t284: db 'NAME',0
t285: db 'LSET',0
t286: db 'RSET',0
t287: db 'KILL',0
t288: db 'PUT',0
t289: db 'GET',0
t28a: db 'RESET',0
t28b: db 'COMMON',0
t28c: db 'CHAIN',0
t28d: db 'DATE$',0
t28e: db 'TIME$',0
t28f: db 'PAINT',0
t290: db 'COM',0
t291: db 'CIRCLE',0
t292: db 'DRAW',0
t293: db 'PLAY',0
t294: db 'TIMER',0
t295: db 'IOCTL',0
t296: db 'MKDIR',0
t297: db 'SHELL',0
t298: db 'VIEW',0
t299: db 'PMAP',0
t29a: db 'ERDEV',0
t29b: db 'CHDIR',0
t29c: db 'RMDIR',0
t29d: db 'ENVIRON',0
t29e: db 'WINDOW',0
t29f: db 'PALETTE',0
t2a0: db 0
t2a1: db 0
t2a2: db 0
t2a3: db 0
t2a4: db 'NOISE',0
t2a5: db 'PCOPY',0
t2a6: db 'TERM',0
;
t380: db 0
t381: db 'CVI',0
t382: db 'CVS',0
t383: db 'CVD',0
t384: db 'MKI$',0
t385: db 'MKS$',0
t386: db 'MKD$',0
endif ;ibm
;***********************************************************************
;
; TRS-80 Level II Token tables
;
;***********************************************************************
if trs80
ttab0: dw t80,t81,t82,t83,t84,t85,t86,t87
dw t88,t89,t8a,t8b,t8c,t8d,t8e,t8f
dw t90,t91,t92,t93,t94,t95,t96,t97
dw t98,t99,t9a,t9b,t9c,t9d,t9e,t9f
dw ta0,ta1,ta2,ta3,ta4,ta5,ta6,ta7
dw ta8,ta9,taa,tab,tac,tad,tae,taf
dw tb0,tb1,tb2,tb3,tb4,tb5,tb6,tb7
dw tb8,tb9,tba,tbb,tbc,tbd,tbe,tbf
dw tc0,tc1,tc2,tc3,tc4,tc5,tc6,tc7
dw tc8,tc9,tca,tcb,tcc,tcd,tce,tcf
dw td0,td1,td2,td3,td4,td5,td6,td7
dw td8,td9,tda,tdb,tdc,tdd,tde,tdf
dw te0,te1,te2,te3,te4,te5,te6,te7
dw te8,te9,tea,teb,tec,ted,tee,tef
dw tf0,tf1,tf2,tf3,tf4,tf5,tf6,tf7
dw tf8,tf9,tfa,tfb
;
t80: db ' END ',0
t81: db ' FOR ',0
t82: db ' RESET ',0
t83: db ' SET ',0
t84: db ' CLS ',0
t85: db ' CMD ',0
t86: db ' RANDOM ',0
t87: db ' NEXT ',0
t88: db ' DATA ',0
t89: db ' INPUT ',0
t8a: db ' DIM ',0
t8b: db ' READ ',0
t8c: db ' LET ',0
t8d: db ' GOTO ',0
t8e: db ' RUN ',0
t8f: db ' IF ',0
t90: db ' RESTORE ',0
t91: db ' GOSUB ',0
t92: db ' RETURN ',0
t93: db ' REM ',0
t94: db ' STOP ',0
t95: db ' ELSE ',0
t96: db ' TRON ',0
t97: db ' TROFF ',0
t98: db ' DEFSTR ',0
t99: db ' DEFINT ',0
t9a: db ' DEFSNG ',0
t9b: db ' DEFDBL ',0
t9c: db ' LINE ',0
t9d: db ' EDIT ',0
t9e: db ' ERROR ',0
t9f: db ' RESUME ',0
ta0: db ' OUT ',0
ta1: db ' ON ',0
ta2: db ' OPEN ',0
ta3: db ' FIELD ',0
ta4: db ' GET ',0
ta5: db ' PUT ',0
ta6: db ' CLOSE ',0
ta7: db ' LOAD ',0
ta8: db ' MERGE ',0
ta9: db ' NAME ',0
taa: db ' KILL ',0
tab: db ' LSET ',0
tac: db ' RSET ',0
tad: db ' SAVE ',0
tae: db ' SYSTEM ',0
taf: db ' LPRINT ',0
tb0: db ' DEF ',0
tb1: db ' POKE ',0
tb2: db ' PRINT ',0
tb3: db ' CONT ',0
tb4: db ' LIST ',0
tb5: db ' LLIST ',0
tb6: db ' DELETE ',0
tb7: db ' AUTO ',0
tb8: db ' CLEAR ',0
tb9: db ' CLOAD ',0
tba: db ' CSAVE ',0
tbb: db ' NEW ',0
tbc: db ' TAB( ',0
tbd: db ' TO ',0
tbe: db ' FN ',0
tbf: db ' USING ',0
tc0: db ' VARPTR ',0
tc1: db ' USR ',0
tc2: db ' ERL ',0
tc3: db ' ERR ',0
tc4: db ' STRING$ ',0
tc5: db ' INSTR ',0
tc6: db ' POINT ',0
tc7: db ' TIME$ ',0
tc8: db ' MEM ',0
tc9: db ' INKEY$ ',0
tca: db ' THEN ',0
tcb: db ' NOT ',0
tcc: db ' STEP ',0
tcd: db '+',0
tce: db '-',0
tcf: db '*',0
td0: db '/',0
td1: db '^',0
td2: db ' AND ',0
td3: db ' OR ',0
td4: db '>',0
td5: db '=',0
td6: db '<',0
td7: db ' SGN ',0
td8: db ' INT ',0
td9: db ' ABS ',0
tda: db ' FRE ',0
tdb: db ' INP ',0
tdc: db ' POS ',0
tdd: db ' SQR ',0
tde: db ' RND ',0
tdf: db ' LOG ',0
te0: db ' EXP ',0
te1: db ' COS ',0
te2: db ' SIN ',0
te3: db ' TAN ',0
te4: db ' ATN ',0
te5: db ' PEEK ',0
te6: db ' CVI ',0
te7: db ' CVS ',0
te8: db ' CVD ',0
te9: db ' EOF ',0
tea: db ' LOC ',0
teb: db ' LOF ',0
tec: db ' MKI$ ',0
ted: db ' MKS$ ',0
tee: db ' MKD$ ',0
tef: db ' CINT ',0
tf0: db ' CSNG ',0
tf1: db ' CDBL ',0
tf2: db ' FIX ',0
tf3: db ' LEN ',0
tf4: db ' STR$ ',0
tf5: db ' VAL ',0
tf6: db ' ASC ',0
tf7: db ' CHR$ ',0
tf8: db ' LEFT$ ',0
tf9: db ' RIGHT$ ',0
tfa: db ' MID$ ',0
tfb: db '''',0
endif ;trs80
;***********************************************************************
;
; Commodore 64 Token tables
;
;***********************************************************************
if c64
ttab0: dw t80,t81,t82,t83,t84,t85,t86,t87
dw t88,t89,t8a,t8b,t8c,t8d,t8e,t8f
dw t90,t91,t92,t93,t94,t95,t96,t97
dw t98,t99,t9a,t9b,t9c,t9d,t9e,t9f
dw ta0,ta1,ta2,ta3,ta4,ta5,ta6,ta7
dw ta8,ta9,taa,tab,tac,tad,tae,taf
dw tb0,tb1,tb2,tb3,tb4,tb5,tb6,tb7
dw tb8,tb9,tba,tbb,tbc,tbd,tbe,tbf
dw tc0,tc1,tc2,tc3,tc4,tc5,tc6,tc7
dw tc8,tc9,tca,tcb
;
t80: db 'END',0
t81: db 'FOR',0
t82: db 'NEXT',0
t83: db 'DATA',0
t84: db 'INPUT#',0
t85: db 'INPUT',0
t86: db 'DIM',0
t87: db 'READ',0
t88: db 'LET',0
t89: db 'GOTO',0
t8a: db 'RUN',0
t8b: db 'IF',0
t8c: db 'RESTORE',0
t8d: db 'GOSUB',0
t8e: db 'RETURN',0
t8f: db 'REM',0
t90: db 'STOP',0
t91: db 'ON',0
t92: db 'WAIT',0
t93: db 'LOAD',0
t94: db 'SAVE',0
t95: db 'VERIFY',0
t96: db 'DEF',0
t97: db 'POKE',0
t98: db 'PRINT#',0
t99: db 'PRINT',0
t9a: db 'CONT',0
t9b: db 'LIST',0
t9c: db 'CLR',0
t9d: db 'CMD',0
t9e: db 'SYS',0
t9f: db 'OPEN',0
ta0: db 'CLOSE',0
ta1: db 'GET',0
ta2: db 'NEW',0
ta3: db 'TAB(',0
ta4: db 'TO',0
ta5: db 'FN',0
ta6: db 'SPC(',0
ta7: db 'THEN',0
ta8: db 'NOT',0
ta9: db 'STEP',0
taa: db '+',0
tab: db '-',0
tac: db '*',0
tad: db '/',0
tae: db '^',0
taf: db 'AND',0
tb0: db 'OR',0
tb1: db '>',0
tb2: db '=',0
tb3: db '<',0
tb4: db 'SGN',0
tb5: db 'INT',0
tb6: db 'ABS',0
tb7: db 'USR',0
tb8: db 'FRE',0
tb9: db 'POS',0
tba: db 'SQR',0
tbb: db 'RND',0
tbc: db 'LOG',0
tbd: db 'EXP',0
tbe: db 'COS',0
tbf: db 'SIN',0
tc0: db 'TAN',0
tc1: db 'ATN',0
tc2: db 'PEEK',0
tc3: db 'LEN',0
tc4: db 'STR$',0
tc5: db 'VAL',0
tc6: db 'ASC',0
tc7: db 'CHR$',0
tc8: db 'LEFT$',0
tc9: db 'RIGHT$',0
tca: db 'MID$',0
tcb: db 'GO',0
endif ;c64
;
asctyp: db 'ASC'
indu: ds 2
outdu: ds 2
curdrv: ds 1
curusr: ds 1
disflg: ds 1 ;flag: display result
curtok: ds 1 ;current token
if exttab
curtok2:
ds 1 ;2nd token if any
endif
quote: ds 1 ;quote mode flag
numbuf: ds 7 ;number conversion buffer
;
;Token pointer table for argv
toktab:
db 2 ;2 tokens only
numtok: ds 1
tok1: ds 2
tok2: ds 2
if notasc
fpacc: ds 8 ;temp f/p accumulator
endif
infcb: ds 36
outfcb: ds 36
end start