title 'MML: REL Utilities' name ('RELUTIL') ; This tool conbines three .REL related MML utilities: ; (1) Utility to display all names in a .REL file. ; ; Original format: RELMAP ; ; (2) Utility to display the contents of a .REL file with each REL ; statement split into separate bit, hex and text fields. Data ; bytes are however shown as a continuous stream with a '0' ; as the first field. ; ; Original format: RELDUMP ; ; (3) Utility to remove any entry names within a .REL file which ; are not required. Bothe the entry point and the entry list ; will require to be removed for each name to be removed. ; Users should first run RELMAP &/or RELDUMP. ; ; Original format: RELDEL ; For all utilities: Copyright: MML Systems Limited ; 11 Sun Street, London E.C.2. ; 1981 ; November 2015 - Combination of all three tools ; The new format is: ; ; RELUTIL -M : RELMAP ; RELUTIL -S : RELDUMP ; RELUTIL -D : RELDEL entry $memry OS equ 0000h BDOS equ 0005h TPATOP equ BDOS+1 FCB equ 005ch FCB2 equ FCB+_DIR cin equ 1 cout equ 2 cmsg equ 9 cstat equ 11 fopen equ 15 fclose equ 16 fread equ 20 fwrite equ 21 fdma equ 26 OSerr equ 255 .drv equ 1 .nam equ 8 .ext equ 3 _EX equ 12 _DIR equ 16 FCBlen equ 33 reclng equ 128 tab equ 09h lf equ 0ah cr equ 0dh eof equ 1ah eot equ '$' NOMSB equ 01111111b UPPER equ 01011111b ld sp,mysp ; Set up local stack ld hl,($memry) ; .REL file copied to DMA address set to program end ld (dma),hl ld hl,(TPATOP) ; Get top of memory ld bc,-reclng add hl,bc ; Let some room ld (TopMem),hl ; Save available top of memory ; ld ix,FCB+.drv ld a,(ix+0) ; Get name character cp ' ' ; Verify not empty jp z,help1 ; Give some help if so cp '-' ; Verify option jr z,findopt ; Tell error noopt: ld de,illopt ; Tell invalid jp help illfile: ld de,nofile ; Tell missing file jp help findopt: ld a,(ix+1) ; Get option ld hl,RELMAP cp 'M' ; Check options jr z,gotopt ld hl,RELDUMP cp 'S' jr z,gotopt ld hl,RELDEL cp 'D' jr nz,noopt gotopt: ld (optadr),hl ; Save option address ; ld hl,FCB2+.drv ld a,(hl) cp ' ' ; Verify filename jr z,illfile ; Nope, invalid dec hl ld de,FCB ld bc,.drv+.nam+.ext ldir ; Move FCB to right place ; ld de,FCB+.drv+.nam ld a,(de) ; Test extension cp ' ' jr nz,gotext ld hl,$REL ld bc,.ext ldir ; Set default gotext: call init$fcb ; Set up file ld de,FCB call open ; Open file jr nz,pr05 ; Got it ld de,notfound call conmsg ; Tell file not found jp OS ; Exit pr05: call RdFile ; Read file into memory ; ; Display each link command ; display: ld hl,(optadr) ; Get utility address jp (hl) ; Go ; ; Entry of tools ; RELMAP: ld hl,streamMAP ld de,tableMAP ld bc,stmMAP xor a jr RELnxt RELDUMP: ld hl,streamDUMP ld de,tableDUMP ld bc,stmDUMP ld a,01b jr RELnxt RELDEL: ld hl,streamDEL ld de,tableDEL ld bc,stmDEL ld a,11b ; ; Set up memory for tools ; RELnxt: ld (Outena),a ; Dis/Enable console/file output ld (spcLinkTab),bc ; Save table address ld (optadr),hl ; Save new utility address call conmsg ; Print message sub a ld (xpos),a ; Init console values ld (ypos),a ld hl,($memry) ; Get start of heap dec hl ld (rel$byte$ptr),hl ld (wr$byte$ptr),hl sub a ld (rel$bit$ptr),a ld (rd$bit$ptr),a ld (wr$bit$ptr),a ld (link$ptr),a ld (wr$byte),a jr display ; Execute tool ; ; --> MAP ; streamMAP: call OneBit ; Get next bit jr nz,stm$typeMAP ; Got control ld a,8 call skip$bits ; Skip constant byte jr streamMAP stm$typeMAP: call TwoBits ; Get two bits jr z,stm$linkMAP ; Got special link item ld a,16 ; <--- call skip$bits ; Skip word jr streamMAP stm$linkMAP: call FourBits ; Build four bits control jp execAdr ; Do table jump ; ; --> DUMP ; streamDUMP: call OneBit ; Get next bit jr nz,stm$typeDUMP ; Got control call data$disp ; Display constant byte jr streamDUMP stm$typeDUMP: call stm$typeCommon jr nz,streamDUMP stm$linkDUMP: call get$halfx ; Build four bits control jp execAdr ; Do table jump ; ; --> DEL ; streamDEL:: ld a,(link$ptr) ; Get bit count or a ; Test any left call nz,wr$link ; Write link to file sub a ld (link$ptr),a ; Reset count call OneBit ; Get next bit jr nz,stm$typeDEL ; Got control call data$disp ; Display constant byte jr streamDEL stm$typeDEL: call stm$typeCommon jr nz,streamDEL call get$halfx ; Build four bits control jp execAdr ; Do table jump ; ; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ ; ; The Microsoft Link items ; ; ### Name field only ### ; MS-Link 0000: Entry symbol ; MAP0000:: ld a,'e' jr MAP$name ; ; MS-Link 0001: Select common block ; MAP0001: ld a,'C' jr MAP$name ; ; MS-Link 0010: Program name ; MAP0010: ld a,'m' jr MAP$name ; ; MS-Link 0011: Library call ; MAP0011: ld a,'l' jr MAP$name ; ; MS-Link 0100: Extension MS-Link ; MAP0100: ld a,'u' jr MAP$name ; ; ### Value and name field ### ; MS-Link 0101: Define common size ; MAP0101: ld a,'c' jr MAP$val$name ; ; MS-Link 0110: Chain external ; MAP0110: ld a,'X' jr MAP$val$name ; ; MS-Link 0111: Define entry point ; MAP0111: ld a,'E' jr MAP$val$name ; ; ### Value field only ### ; MS-Link 1000: External -offset ; MAP1000: ld a,'u' MAP$val$name: push af call stm$valueMAP pop af MAP$name: ld ($$name+1),a call stm$nameMAP ld de,$$name call dsp$nameMAP ret ; ; On DUMP the value field only links are treated the same way ; ; MS-Link 1001: External +offset ; MAP1001: ; ; MS-Link 1010: Define data size ; MAP1010: ; ; MS-Link 1011: Set location counter ; MAP1011: ; ; MS-Link 1100: Chain address ; MAP1100: ; ; MS-Link 1101: Define program size ; MAP1101: call stm$valueMAP ret ; ; MS-Link 1110: End module ; MAP1110: call stm$valueMAP sub a ld (rel$bit$ptr),a ; align to byte boundary call delimiter ; Indicate end of file ret ; ; MS-Link 1111: End file ; MAP1111: link$eofDUMP: call newline jp OS ; ; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ ; ; On DUMP the name field only links are treated the same way ; DUMP0000: DUMP0001: DUMP0010: DUMP0011: DUMP0100: call skip$val call stm$nameDUMP call dsp$name ret ; ; On DUMP the value and name field links are treated the same way ; DUMP0101: DUMP0110: DUMP0111: call stm$value call dsp$blnk call stm$nameDUMP call dsp$name ret ; ; On DUMP the value field only links are treated the same way ; DUMP1000: DUMP1001: DUMP1010: DUMP1011: DUMP1100: DUMP1101: call stm$value ret ; DUMP1110: call stm$value sub a ld (rel$bit$ptr),a ; align to byte boundary call delimiter ; Indicate end of file ret ; DUMP1111: jp link$eofDUMP ; ; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ ; DEL0000: call stm$nameDEL call dsp$name call ok$del ; Ask for deletion this ENTRY ret ; DEL0001: DEL0010: DEL0011: DEL0100: DEL0101: call stm$nameDEL call dsp$name ret ; DEL0110: DEL1000: call stm$value call dsp$blnk call stm$nameDEL call dsp$name ret ; DEL0111: call stm$value call dsp$blnk call stm$nameDEL call dsp$name call ok$del ; Ask for deletion this ENTRY ret ; DEL1001: DEL1010: DEL1011: DEL1100: DEL1101: call stm$value ret ; DEL1110: call stm$value sub a ld (rd$bit$ptr),a ; align to byte boundary call wr$link ; Write pending link call byte$bound ; Fill to byte boundary sub a ld (link$ptr),a call delimiter ; Indicate end of file ret ; DEL1111: call wr$link ; Write pending link call byte$bound ; Fill to byte boundary ; ; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ ; ; reached link eof command ; call newline call fill$rec ; fill to end of record with nulls ld hl,($memry) ; .REL file copied to DMA address set to program end ld (dma),hl call init$fcb ; Prepare FCB ld de,FCB call open ; Open file jr nz,wr1 ; Got it ld de,notfound call conmsg jp OS ; File not found wr1: call WrFile ; Write file back ld de,FCB call close ; Close file jp OS ; End of deletion ; ; Fill to end of record with ctrl-z ; fill$rec: ld hl,(wr$byte$ptr) inc hl ld de,($memry) ; .REL file copied to DMA address set to program end ld a,l sub e and reclng-1 ; Test record boundary ret z ; Got it ld a,eof ld (wr$byte),a call put$nxt$byte ; Put end of file jr fill$rec ; ; Fill bits to end of byte with zero ; byte$bound: ld a,(wr$bit$ptr) ; Get pointer or a ; Test byte boundary ret z ; Yeap sub a call put$nxt$bit ; Put zero to file jr byte$bound ; ; ok$del ; ok$del: ld de,delete call string ; Ask for deletion the module ok1: call keystat ; Wait for key pressed jr z,ok1 ; Not yet call Conin ; Read key and NOMSB and UPPER cp 'Y' ; Test YES jr z,ok$y cp 'N' ; Must be NO jr nz,ok$del ret ok$y: sub a ld (link$ptr),a ; Clear pointer ret ; ; skip$value ; where the link command does not include a value, ; but does include a name, then blanks pad over ; the displayed value fields ; skip$val: ld b,8 ; Set length no$val: push bc call dsp$blnk ; Display blanks pop bc djnz no$val ret ; ; Process start of control ; stm$typeCommon: ld (last$bit),a ; Save control bit call newline ld a,(last$bit) call dsp$bit ; Display bit call dsp$blnk call TwoBits ; Get two bits call dsp$blnk push af call nz,get$word ; Get word if not special link pop af ret ; ; Check enough memory ; chkmem: inc hl ex de,hl ld hl,(free) ld a,d ; Test in range cp h ret c jr nz,bad$code ; Error if not ld a,e cp l ret c bad$code: ld de,prog$err call conmsg ; Tell error jp OS ; Exit ; ; Initialize FCB ; init$fcb: ld hl,FCB+_EX ; Point to control bytes sub a ld b,FCBlen-_EX init$1: ld (hl),a ; Clear control inc hl djnz init$1 ret ; ; Give delimiter line ; delimiter: ld de,delline ; ; Send message terminated by '$' to console ; Reg in: DE->message ; conmsg: call string ; Send message ; ; Test console interrupt ; tst$abort: call keystat ; Just check for any console input or a ret z call Conin ; YES - Abort run jp OS ; ; Put new line to console ; newline: ld a,cr call conout ld a,lf call conout ld a,(ypos) inc a ; Update row ld (ypos),a sub a ld (xpos),a ; Clear column ret ; ; Display current bit ; dsp$bit: push af push hl and 00000001b ; Extract bit add a,'0' ; Make ASCII ld hl,Outena bit 0,(hl) ; Test console enabled call nz,conout ; Print it if so pop hl pop af ret ; ; Print blank ; dsp$blnk: push af ld a,' ' call conout ; Simple one pop af ret ; ; Fetch next bit as bit 0 in A ; get$nxt$bit:: ld a,(rel$bit$ptr) ; Get bit count dec a cp 0 ; Test bits remaining call m,get$nxt$byte ; Nope, get new byte ld (rel$bit$ptr),a ; Save bit count ld b,a ; Get as count ld a,(rel$byte) inc b inc$bit: dec b ; Test bit position found jr z,fnd$bit ; Yeap rrca ; Shift into right place jr inc$bit fnd$bit: and 00000001b ; Isolate bit push af ld hl,Outena bit 1,(hl) ; Test file enabled call nz,save$bit ; Put bit if so pop af ret ; ; Add next bit to current bit in a after shifting a ; add$nxt$bit: rlca ; Shift old in ld b,a push bc call get$nxt$bit ; Get next bit pop bc or b ; Combine it ret ; ; Fetch next byte ; get$nxt$byte: ld hl,(rel$byte$ptr) call chkmem ; Check enough memory ex de,hl ld (rel$byte$ptr),hl ld a,(hl) ; Get byte ld (rel$byte),a ld a,7 ; Start with bit 7 ret ; ; Skip A bits ; skip$bits: or a ret z push af call get$nxt$bit ; Get bit pop af dec a jr skip$bits ; ; Get & display hex digit(s) ; get$word: ld a,(Outena) push af xor a ld (Outena),a ; Disable console temporary call FourBits ; Get bits ld (temp$digits),a ; Save call FourBits ; Get next ld (temp$digits+1),a pop af ld (Outena),a call get$byte ld a,(temp$digits) call dsp$half ld a,(temp$digits+1) call dsp$half ret ; ; Combine byte ; ; *** NOT REALLY *** ; get$byte: call get$half ; Four bits call get$half ; *NEW* four bits ret ; ; Combine four bits and display them ; get$halfx: call FourBits ; Get four bits and display them call dsp$blnk ret ; ; Combine four bits and display them ; get$half: call get$nxt$bit ; Get bits call add$nxt$bit call add$nxt$bit call add$nxt$bit dsp$half: push af and 00001111b ; Get bits add a,90h ; Make ASCII daa adc a,40h daa call conout pop af ret ; ; Save bit in buffer ; save$bit: push af ld hl,link ld a,(link$ptr) ; Get pointer ld e,a ; Build index ld d,0 add hl,de ; Build buffer address inc a ld (link$ptr),a ; Update index pop af ld (hl),a ; Store bit ret ; ; Write a .REL link to file ; wr$link: ld a,(link$ptr) ; Get length ld hl,link ; Init pointer wr$lnk1: push af ld a,(hl) ; Get value push hl call put$nxt$bit ; Put to file pop hl inc hl pop af dec a jr nz,wr$lnk1 ret ; ; Write bit 0 in A as next bit ; put$nxt$bit: push af and 00000001b ; Get bit rrca ; Shift it ld hl,wr$byte or (hl) ; Combineit rlca ld (hl),a ld a,(wr$bit$ptr) ; Get count inc a cp 8 ; Test byte filled <--- call nc,put$nxt$byte ; Yeap, get next ld (wr$bit$ptr),a pop af ret ; ; Write next byte ; put$nxt$byte: ld hl,(wr$byte$ptr); Get byte pointer call chkmem ; Check enough memory ex de,hl ld (wr$byte$ptr),hl ld a,(wr$byte) ld (hl),a sub a ld (wr$byte),a ; Set byte content to zero ld a,0 ; Reset bit count to zero ret ; ; Display txt$name ; dsp$name: ld de,txt$name call conmsg ret ; ; Display txt$name use prefix defined in (DE) ; dsp$nameMAP: ld a,(xpos) ; Get column cp 80-8-3 ; <--- call nc,newline add a,3 ; <--- ld (xpos),a ; Init column call conmsg call dsp$name call tst$abort ld a,(xpos) add a,8 ; Update column ld (xpos),a ret ; ; value ; frst 2 bits ; 00 absolute ; 01 program relative ; 10 data relative ; 11 common relative ; ; next 16 bits ; address field ; stm$value: call get$nxt$bit ; Get bits call dsp$bit call add$nxt$bit call dsp$bit call dsp$blnk call get$word ; Get word ret ; ; Value ; first 2 bits ; 00 absolute ; 01 program relative ; 10 data relative ; 11 common relative ; ; next 16 bits ; address field ; stm$valueMAP: ld a,2+16 ; <--- call skip$bits ; Skip bits ret ; ; Process name ; 3 bit name count ; count x 8bit ascii characters ; named saved in NAME with trailing blanks ; stm$nameDEL: stm$nameDUMP: call init$name ; Init name, return length of name, 3 bits call dsp$blnk ret z ld hl,txt$name ld b,a ld a,16 ; <--- sub b ; Calculate gap sub b jr z,cr$nameGo cr$blnkDUMP: call dsp$blnk ; Fill gap dec a jp nz,cr$blnkDUMP cr$nameGo: ld a,(Outena) push af xor a ld (Outena),a ; Disable console temporary cr$nameDUMP: push bc push hl call FourBits ; Get high four bits of byte call dsp$half ; Display them add a,a ; Shift into upper place add a,a add a,a add a,a push af call FourBits ; Get low four bits of byte call dsp$half ; Display them ld l,a pop af add a,l ; Combine for character pop hl call is$print ; Test printable pop bc djnz cr$nameDUMP call dsp$blnk pop af ld (Outena),a ; Reset console ret ; ; Process 'name' ; 3 bit name count ; count x 8bit ascii characters ; named saved in NAME with trailing blanks ; stm$nameMAP: call init$name ; Init name, return length of name, 3 bits ret z ; Empty name ld hl,txt$name ld b,a ; Set length cr$nameMAP: push bc push hl call FourBits ; Get high four bits of byte add a,a ; Shift into upper place add a,a add a,a add a,a push af call FourBits ; Get low four bits of byte ld l,a pop af add a,l ; Combine for character pop hl call is$print ; Test valid character pop bc djnz cr$nameMAP ret ; ; Init name buffer ; init$name: ld b,txtlen ld a,' ' ld hl,txt$name name$blank: ld (hl),a ; Blank name inc hl djnz name$blank call ThreeBits ; Get three bits ret ; ; Check if character printable ; is$print: cp ' ' ; Text printable jr c,bad$isprint cp '~'+1 jr c,not$isprint bad$isprint: ld a,'.' ; Map if not not$isprint: ld (hl),a ; Save character inc hl ; Update pointer ret ; ; Execute special link item in Accu ; execAdr: ld hl,display push hl ; Set return address add a,a ; Double for index ld c,a ld b,0 ld hl,(spcLinkTab) ; Get table address add hl,bc ld e,(hl) ; Load address inc hl ld d,(hl) ex de,hl jp (hl) ; Go ; ; Display constant byte ; data$disp: ld hl,last$bit cp (hl) ; Test same previous bit ld (last$bit),a jr nz,new$data.DUMP; Nope ld a,(xpos) ; Get column cp 80-3 ; Test in range ; <--- jr c,cont$data.DUMP new$data.DUMP: call newline ld a,(last$bit) call dsp$bit call dsp$blnk ld a,(xpos) add a,2 ; Update column ld (xpos),a cont$data.DUMP: call get$byte ld a,(xpos) add a,2 ; Update column ld (xpos),a ret ; ; Give some help text ; help: push de ld de,error call conmsg ; Indicate error pop de call conmsg ; Tell entry message help1: ld de,helptxt call conmsg ; Give help jp OS ; ; ##### BIT INTERFACE ##### ; ; Get one bit from REL file - Control bit ; OneBit: call get$nxt$bit ; Get next bit or a ret ; ; Get two bits from REL file - Address mode bits ; TwoBits: call get$nxt$bit ; Get two bits call dsp$bit call add$nxt$bit call dsp$bit ret ; ; Get three bits from REL file - Length bits ; ThreeBits: call get$nxt$bit ; Get three bits call dsp$bit call add$nxt$bit call dsp$bit call add$nxt$bit call dsp$bit ret ; ; Combine four bits ; FourBits: call get$nxt$bit ; Get four bits call dsp$bit call add$nxt$bit call dsp$bit call add$nxt$bit call dsp$bit call add$nxt$bit call dsp$bit ret EightBits:: SixteenBits:: ; ; Read the entire REL file into memory ; RdFile: ld hl,(dma) ; Get DMA address nxtbuf: ; Read next buffer from disk ex de,hl ; Copy DMA into DE ld hl,(TopMem) ; Get available top of memory ld a,d cp h ; Test still room for REL file jr c,mem$ok ; Yeap jr nz,mem$full ld a,e cp l jr c,mem$ok mem$full: ld de,outofmem call conmsg ; Memory overflow jp OS ; Exit mem$ok: call setdma ; Set DMA ld de,FCB call dskrd ; Read record ret nz ; Ready if beyond last record ld hl,(dma) ; Get DMA address ld bc,reclng add hl,bc ; & increment by 128 bytes ld (dma),hl ld (free),hl ; Free points to location beyond .REL file jr nxtbuf ; ; Write the entire REL file back ; WrFile: ld hl,(dma) ; Get DMA address wr2: ; Write next buffer to disk ex de,hl ; Copy DMA into D,E ld hl,(wr$byte$ptr); end of REL inc hl ld a,d cp h ; Test end reached jr c,wr3 ; Nope ret nz ld a,e cp l ret nc wr3: call setdma ; Set DMA ld de,FCB call dskwr ; Write jr nz,wr$error ; Write error ld hl,(dma) ; Get DMA address ld c,reclng ld b,0 add hl,bc ; & increment by 128 bytes ld (dma),hl jr wr2 wr$error: ld de,bad$write call conmsg jp OS ; ; ##### OS INTERFACE ##### ; ; Read character from console ; Conin: ld c,cin call BDOS ; Read key ret ; ; Put character to console ; conout: push hl push de push bc push af ld e,a ; Unpack character ld c,cout call BDOS ; Read it call tst$abort pop af pop bc pop de pop hl ret ; ; Put string to console ; string: ld c,cmsg call BDOS ; Send message ret ; ; Get state of keyboard ; keystat: ld c,cstat call BDOS ; Test key pressed or a ret ; ; Open file ; open: ld c,fopen call BDOS ; Open file cp OSerr ; Test found ret ; ; Close file ; close: ld c,fclose call BDOS ; Do it ret ; ; Read record from file ; dskrd: ld c,fread call BDOS ; Read record or a ; Check if read beyond last record ret ; ; Write record to file ; dskwr: ld c,fwrite call BDOS ; Write or a ; Check if write error ret ; ; Set disk buffer ; setdma: ld c,fdma call BDOS ; Set DMA ret dseg helptxt: db 'Program for working on REL80 library files' db cr,lf,lf db '1.Display base information in a library' db cr,lf,lf db 'Call it:' db cr,lf db tab,'RELUTIL -M ' db cr,lf,lf db '2.Dump a library' db cr,lf,lf db 'Call it:' db cr,lf db tab,'RELUTIL -S ' db cr,lf,lf db '3.Delete modules from a library' db cr,lf,lf db 'Call it:' db cr,lf db tab,'RELUTIL -D ' db cr,lf,eot error: db cr,lf,'### Invocation error: ',eot illopt: db 'Invalid option',cr,lf,lf,eot nofile: db 'Missing file',cr,lf,lf,eot notfound: db 'NEW .REL FILE',cr,lf,eot outofmem: db cr,lf,'out of memory',cr,lf,eot prog$err: db cr,lf,'program error',cr,lf,eot bad$write: db cr,lf,'write error',cr,lf,eot $REL: db 'REL' delline: db cr,lf,'=======================================' db '=======================================',cr,lf,eot tableMAP: db cr,lf,'MML:RELMAP - list of REL symbol names' db cr,lf,'/m/ -> module, /l/ -> library, /e/ -> entry list, /c/ -> common block' db cr,lf,'/E/ -> entry point, /C/ -> common symbol, /X/ -> external symbol' db cr,lf,'---------------------------------------------------------------------' db cr,lf,lf db eot tableDUMP: db cr,lf,'MML:RELDUMP - bit/hex dump of REL link instructions' db cr,lf,'---------------------------------------------------' db cr,lf,lf db eot tableDEL: db cr,lf,'MML:RELDEL - deletion of symbol names in REL' db cr,lf,'(Only entry point names and the entry list)' db cr,lf,'--------------------------------------------' db cr,lf,lf db eot stmMAP: dw MAP0000,MAP0001,MAP0010,MAP0011,MAP0100,MAP0101,MAP0110,MAP0111 dw MAP1000,MAP1001,MAP1010,MAP1011,MAP1100,MAP1101,MAP1110,MAP1111 stmDUMP: dw DUMP0000,DUMP0001,DUMP0010,DUMP0011,DUMP0100,DUMP0101,DUMP0110,DUMP0111 dw DUMP1000,DUMP1001,DUMP1010,DUMP1011,DUMP1100,DUMP1101,DUMP1110,DUMP1111 stmDEL: dw DEL0000,DEL0001,DEL0010,DEL0011,DEL0100,DEL0101,DEL0110,DEL0111 dw DEL1000,DEL1001,DEL1010,DEL1011,DEL1100,DEL1101,DEL1110,DEL1111 txt$name: db '12345678' ; max of 8 byte address txtlen equ $-txt$name db eot p$name: db '/e/',eot c$name: db '/C/',eot m$name: db '/m/',eot l$name: db '/l/',eot u$name: db '/u/',eot cs$name: db '/c/',eot x$name: db '/X/',eot s$name: db '/E/',eot $$name: db '/?/',eot delete: db cr,lf,'Delete Y/N ?',eot $memry: ds 2 TopMem: ds 2 dma: ds 2 optadr: ds 2 spcLinkTab: ds 2 free: ds 2 wr$byte$ptr: ds 2 rd$byte$ptr equ $ rel$byte$ptr: ds 2 ;; (rel$byte),a (rd$byte) wr$byte: ds 1 wr$bit$ptr: ds 1 rd$bit$ptr equ $ rel$bit$ptr: ds 1 link$ptr: ds 1 last$bit: ds 1 rel$byte: ds 1 temp$digits: ds 2 link: ds 128 Outena: ds 1 xpos: ds 1 ypos: ds 1 ; ds 2*64 mysp: end