title Write Hand Man - RSX name ('WHMTRSX') ; This is the DASMed version of the Write Hand Man RSX OS equ 0000h BDOS equ 0005h CCP equ 0080h TPA equ 0100h ROLLER equ 0b600h XBIOS equ 0fc5ah .Conin equ 1 .Conout equ 2 .DirCon equ 6 .String equ 9 .RdCon equ 10 .SelDsk equ 14 .Open equ 15 .Close equ 16 .RdSeq equ 20 .RetDsk equ 25 .SetDMA equ 26 .UsrCod equ 32 .RdRnd equ 33 .WrRnd equ 34 .MulSec equ 44 .SCB equ 49 .RSX equ 60 @WBOOT equ 1 @CONST equ 2 @CONIN equ 3 @CONOUT equ 4 @SELMEM equ 27 _get equ -1 _DMA equ 3ch _TEASK equ 00bfh _KTGET equ 00dah _KTPUT equ 00ddh _SCRRUN equ 00e9h ; ; Special key numbers ; _EXIT equ 8 _SHFT equ 21 _SHFLK equ 70 _ALT equ 80 _UNK equ 84 MyRSX equ 122 FCBlen equ 36 _DRV equ 1 _NAM equ 8 _EXT equ 3 _EX equ 12 _RRN equ 33 RRN.Len equ 3 RecLng equ 128 SavLng equ 128 ScrRec equ 56 BitLen equ 8 AreaLen equ 48 BlnkLen equ 10 ConsLen equ 127 MacLen equ 16 MacCnt equ 8 RELlen equ 0900h ; Max length of application _STRT equ 06h _NEXT equ 09h _NAME equ 10h _LOADER equ 18h _TPA equ 1 _PAG.OF equ 02dbh _GET.ST equ 02efh _GET.IN equ 02f1h _LD.PAG equ 0ebh bs equ 08h lf equ 0ah cr equ 0dh esc equ 1bh eot equ '$' ; ; Frame characters ; $D.LL equ 83h ; Double lower left $D.LR equ 89h ; Double lower right $D.UL equ 86h ; Double upper left $D.UR equ 8ch ; Double upper right $D.H equ 8ah ; Double horizontal $D.V equ 85h ; Double vertical ChrMask equ 00000111b LoMask equ 00001111b HiMask equ 11110000b UPPMask equ 01011111b _CSEG equ 01b .NAME equ 2 .DATSIZ equ 10 .LOCCTR equ 11 .PRGSIZ equ 13 .MODEND equ 14 _JP equ 0c3h ; ; >>>>> RSX starts <<<<< ; ds 6 ; xx00: Serial number jp RSXgo ; xx06: Jump to RSX Next: jp BDOS+1 ; xx09: Jump to next RSX dw BDOS+2 ; xx0C: Address of previous Remove: db -1 ; xx0E: Permanent flag db 0 ; xx0F: Bank flag db 'WHMT ' ; xx10: Name of RSX db 0 ; xx18: Loader flag db 0,0 ; xx19: Reserved ; ; >>>>> RSX ends <<<<< ; Version: db 5*16+1 LOAD.Next: dw 0 ; Pointer to LOADER next field RSXgo: ld a,c cp .RSX ; Test RSX request jp nz,NoRSX ld a,(de) cp MyRSX ; Test this RSX jp nz,Next inc de ; Skip to type inc de ld a,(de) and a jp z,Test cp 1 jp z,Install cp 2 jp z,Delete jp NotOur ; ; ***** The get_version task ***** ; Test: ld a,(Remove) ; Test remove flag or a jp nz,NotOur ; .. not permanent ld a,(Version) ; Return version ld l,a ret NoRSX: cp .MulSec ; Test multi sector count jp nz,Next ; .. nope, skip ld a,(BootFlg) ; Test flag or a jp nz,Next ; .. skip if set ld a,e ld (MulSec),a ; Save count jp Next ; .. set by OS MulSec: db 1 Install: ld a,(Remove) ; Test remove flag active or a jp nz,DoInst ; .. yeap, so install jr NotOur Delete: ld a,(Remove) ; Test to be removed or a jr z,DoDel ; .. yeap NotOur: dec de ; Fix pointer dec de jp Next ; .. and do normal BDOS ; ; ***** The remover task ***** ; DoDel: ld bc,3*(@WBOOT-1) ld hl,($WBOOT$) ex de,hl call SetBIOS@ ; Restore all BIOS vectors ld bc,3*(@CONST-1) ld hl,($CONST$+1) ex de,hl call SetBIOS@ ld bc,3*(@CONIN-1) ld hl,($CONIN$+1) ex de,hl call SetBIOS@ ld bc,3*(@CONOUT-1) ld hl,($CONOUT$+1) ex de,hl call SetBIOS@ ld bc,3*(@SELMEM-1) ld hl,($SELMEM$+1) ex de,hl call SetBIOS@ ld a,-1 ld (Remove),a ; Set remove ret ; ; Set address of BIOS ; ENTRY Reg BC holds offset within BIOS jump table ; Reg DE holds new address ; SetBIOS@: ld hl,(OS+1) ; Get base address add hl,bc ; .. add offset inc hl ; .. skip JP ld (hl),e ; Store new address inc hl ld (hl),d ret ; ; Got trigger - Process WHM ; ProcWHM: call SavSYS ; Save system parameters call GetCurUsr ; .. current user call GetCurDMA ; .. current disk buffer ld c,.RetDsk call Next ; .. logged drive ld (CurDriv),a ld e,1 ld c,.MulSec call Next ; Set default record count call GetScrEnv ; Get viewpoint coordinates push hl ld hl,WinSav ld (hl),b ; .. save prameters inc hl ld (hl),c inc hl ld (hl),d inc hl ld (hl),e inc hl pop de ld (hl),d inc hl ld (hl),e ld de,$CURS.OFF ld c,.String call BDOS ; Turn off cursor ld hl,$W.FCB ld de,B.FCB ld bc,$W.LEN ldir ; Set up work file xor a ld b,FCBlen-$W.LEN-RRN.Len ClrWrk: ld (de),a ; .. clear remainder inc de djnz ClrWrk ld de,B.DMA ld c,.SetDMA call BDOS ; Set disk buffer ld de,B.FCB ld c,.Open call BDOS ; Open file ld c,0 ; Init line ld b,ScrRec ; .. and record count SavScrLoop: push bc ld a,c ld (LinCnt),a ; Set line count ld l,a xor a ld h,a ld (B.FCB+_RRN),hl ; .. into random position ld (B.FCB+_RRN+2),a ld bc,GetSCRline ; Get screen line call SCR_RUN ; .. get one line ld c,.WrRnd ld de,B.FCB call BDOS ; Write to disk pop bc inc c djnz SavScrLoop ld c,.Close ld de,B.FCB call BDOS ; Close file ld de,$CURS.ON ld c,.String call BDOS ; Turn on cursor jp WHM.go ; .. enter menue ; LinCnt: dw 0 $CURS.OFF: db esc,'f',eot $CURS.ON: db esc,'e',eot ; ; Get one line from screen into disk buffer ; GetSCRline: ld hl,(LinCnt) ; Fetch current line ld de,3 ld a,0 SavFinLin: and a sbc hl,de ; Fix for line jp c,SavLinFnd inc a jp SavFinLin SavLinFnd: add hl,de push hl ld l,a ld h,0 add hl,hl add hl,hl add hl,hl add hl,hl ld de,ROLLER add hl,de ; Get address to roller RAM pop de ex de,hl ld b,7 SavLinFix: add hl,hl djnz SavLinFix ; Shift line ex de,hl ld a,(hl) ; Get roller entry inc hl ld h,(hl) ld l,a add hl,hl ; .. * 2 ld a,l and HiMask ; Get bits ld b,a ld a,l and LoMask srl a or b ld l,a add hl,de ; .. get real address ld bc,RecLng ld de,B.DMA ldir ; .. copy line to buffer ret ; ; Execute routine in system environment ; ENTRY Reg BC holds address to be executed ; SCR_RUN: call XBIOS dw _SCRRUN ; .. execute ret ; $W.FCB: db 'M'-'@','WHMXWS DAT',0 $W.LEN equ $-$W.FCB db 0 ; ; Fetch current cursor position ; EXIT Reg B holds top row of the viewpoint ; Reg C holds left column of the viewpoint ; Reg D holds bottom of the screen ; Reg E holds right column of the screen ; Reg H holds cursor row ; Reg L holds cursor column ; GetScrEnv: ld hl,XBIOS call Reg dw _TEASK ret ; ; Jump via register ; ENTRY Reg HL holds address ; Reg: jp (hl) ; ; >>> ENTER WRITE HAND'S MAN MENU <<< ; >>> +++++++++++++++++++++++++++ <<< ; WHM.go: ld sp,WHMstk ; Get local stack call SetWHMusr ; Set user ld a,(CurDriv) ld e,a ld c,.SelDsk call BDOS ; Select disk call WindowOut ; Put window WtKey: call XBIOS ; Get key number dw _KTGET jr nc,WtKey ; .. wait for any ld a,c cp _SHFT ; Filter special ones jr z,WtKey cp _ALT jr z,WtKey cp _UNK jr z,WtKey cp _SHFLK jr z,WtKey res 3,b ; Clear repeat bit cp _EXIT jp z,ExitWHM ld a,c call XBIOS ; Put token dw _KTPUT ld c,.DirCon WtBIOSkey: ld e,_get call BDOS ; Get state of console or a jr z,WtBIOSkey ; .. none jp nz,IntrptKey ; Go interpret ; ; Got EXIT key, so exit ; ExitWHM: call RestScr ; Restore screen call SetCalUsr ; .. user call ResDMA ; .. disk buffer ld a,(MulSec) ld e,a ld c,.MulSec call Next ; .. record count call ResSYS ; .. system parameters jp ResCall ; .. fall in final reset ; ; Load window from file ; WindowOut: call Home ; Bring cursor home ld de,$OPTION ld c,.String call BDOS ; Give option window call Home ; .. reset cursor ld c,.String ld de,$CHOICE jp BDOS ; Tell we wanna choice ; ; Home the cursor ; Home: ld de,$HOME ld c,.String jp BDOS ; Set cursor to home position ; ; Blank lines on screen ; BlankLine: call Home ; Bring cursor home ld b,BlnkLen ; Set count ld c,.String ld de,$BLANK BlnkLoop: push bc push de call BDOS ; Blank line pop de pop bc djnz BlnkLoop ; .. loop jr Home ; Home cursor ; ; *** WHY ??? *** ; ;;l0335: jp BlankLine ; .. blank lines ; ; Restore screen ; RestScr: ld de,$CURS.OFF ld c,.String call BDOS ; Turn off cursor ld hl,$W.FCB ld de,B.FCB ld bc,$W.LEN ldir ; Set up work file xor a ld b,FCBlen-$W.LEN-RRN.Len .ClrWrk: ld (de),a ; Clear reast of file inc de djnz .ClrWrk ld de,B.DMA ld c,.SetDMA call BDOS ; Set disk buffer ld de,B.FCB ld c,.Open ; Open file call BDOS ld c,0 ; Clear line count ld b,ScrRec ; .. set record count ResScrLoop: push bc ld a,c ld (LinCnt),a ; Set line ld l,a xor a ld h,a ld (B.FCB+_RRN),hl ; .. as record ld (B.FCB+_RRN+2),a ld c,.RdRnd ld de,B.FCB call BDOS ; Read record ld bc,PutSCRline call SCR_RUN ; Put it to screen pop bc inc c djnz ResScrLoop ld c,.Close ld de,B.FCB call BDOS ; Close file ld c,.Conout ld e,esc ; .. give window prefix call BDOS ld e,'X' ld c,.Conout call BDOS ld hl,WinSav ; Point to old viewpoint ld c,.Conout ld b,' ' ld a,(hl) ; .. add offset add a,b ld e,a push hl push bc call BDOS ; Reset window pop bc pop hl inc hl ld a,(hl) add a,b ld e,a push hl push bc call BDOS pop bc pop hl inc hl ld a,(hl) add a,b ld e,a push hl push bc call BDOS pop bc pop hl inc hl ld a,(hl) add a,b ld e,a push hl push bc call BDOS pop bc pop hl inc hl push hl push bc ld e,esc call BDOS ; Position cursor ld e,'Y' ld c,.Conout call BDOS pop bc pop hl ld a,(hl) add a,b ld e,a push hl push bc call BDOS ; Reset cursor pop bc pop hl inc hl ld a,(hl) add a,b ld e,a call BDOS ld de,$CURS.ON ld c,.String call BDOS ; Turn on cursor ret ; ; Put line to screen ; PutSCRline: ld hl,(LinCnt) ; Get line ld de,3 ld a,0 ResFinLin: and a sbc hl,de ; .. fix index jp c,ResLinFnd inc a jp ResFinLin ResLinFnd: add hl,de ; Calculate roller address push hl ld l,a ld h,0 add hl,hl add hl,hl add hl,hl add hl,hl ld de,ROLLER add hl,de ; .. get address pop de ex de,hl ld b,7 ResLinFix: add hl,hl ; Shift value left djnz ResLinFix ex de,hl ld a,(hl) ; Get address inc hl ld h,(hl) ld l,a add hl,hl ld a,l and HiMask ; Extract for index ld b,a ld a,l and Lomask srl a or b ld l,a add hl,de ; Get real address ex de,hl ld bc,RecLng ld hl,B.DMA ldir ; .. fill line ret ; ds 10 ; ; Got a character - interpret it ; ENTRY Accu holds character ; IntrptKey: and UPPMask ; Get as UPPER case ld hl,$NOTEPAD cp 'A' ; Find standard applications jp z,OptFnd ld hl,$PHONEBOOK cp 'B' jp z,OptFnd ld hl,$CALENDAR cp 'C' jp z,OptFnd ld hl,$DIR cp 'D' jp z,OptFnd ld hl,$VIEW cp 'E' jp z,OptFnd ld hl,$CALCULATE cp 'F' jp z,OptFnd ld hl,$KEYS cp 'G' jp z,OptFnd cp 'R' ld hl,$RESTORE jp z,OptFnd cp 'O' ; Try extension jp nz,WHM.go ; .. nope, so be passive ld de,$ASK ld c,.String call BDOS ; Tell what we want ld e,' ' ld hl,B.FCB+_DRV ld bc,_NAM call FillChar ; Clear name ld a,_NAM ld (B.FCB-1),a ld de,B.FCB-1 ld c,.RdCon call BDOS ; Read file name ld c,.String ld de,$RIGHT call BDOS ; Move cursor right ld hl,B.FCB+1 jp OptFnd ; .. find file ; $RIGHT: db esc,'C',eot ; ; Process file read error ; FileReadErr: ld hl,$LOAD.ERR jp ProcFilErr ; .. process it ; ; Current file not found - retry on drive A: ; File@A: ld a,(B.FCB) cp 'A'-'@' ; Test drive A: already jp z,RelFilErr ; .. should not be ld a,'A'-'@' ld (B.FCB),a ; .. reset to drive A: ld e,0 ld c,.UsrCod call BDOS ; Set user 0 jp LoadRELfil ; Try again ; ; Process file error ; RelFilErr: ld hl,$NOT.FND ProcFilErr: push hl ; Save message call FCBtoStr ; Convert FCB to string pop hl ld de,$EM.buff ld bc,ErrLen call StrCpy ; .. append message call BlankLine ; Blank line call Home ; Home cursor ld de,$ERR.MESS ld c,.String ; Give combined message call BDOS ld c,.Conin call BDOS ; Get quit jp WHM.go ; .. reenter WHM ; ; Convert standard FCB to string ; FCBtoStr: ld hl,B.FCB+1 ld de,$EM.nam ld bc,_NAM call StrCpy ; Copy name ld hl,B.FCB+_DRV+_NAM ld de,$EM.ext ld bc,_EXT call StrCpy ; .. and extension ld a,(WHMusr) add a,'0' ; Make user area printable ld ($EM.usr),a ld a,(CalDrv) ; Get callers drive add a,'A'-1 ; .. as ASCII ld ($ERR.MESS),a ret ; ; Got an option ; ENTRY Reg HL points to option string ; OptFnd: push hl ld de,B.DMA ld c,.SetDMA call BDOS ; Set disk buffer ld hl,B.FCB+_EX ld bc,FCBlen-_EX ld e,0 call FillChar ; Clear remainder ld a,(CalDrv) ; Get program drive ld (B.FCB),a pop hl ld de,B.FCB+_DRV ld bc,_NAM call StrCpy ; Unpack name ld hl,$REL ld bc,_EXT ld de,B.FCB+_DRV+_NAM call StrCpy ; Set extension .REL LoadRELfil: ld c,.Open ld de,B.FCB call BDOS ; Open file inc a jp z,File@A ; .. not there ld a,RecLng ld (BytCnt),a ; Init byte pointer xor a ld (BitCnt),a ; Clear resulting bit pattern ld bc,BASE ; Init offset ld de,0 ; .. and load adress RELloop: ld a,1 call GetBits ; Get bit or a jr nz,RelCtrl ; .. control ld a,8 call GetBits ; Get constant ld (de),a ; .. save inc de jp RELloop RelCtrl: ld a,2 call GetBits ; Get next two bits or a jp z,SpecLink ; .. special link item cp _CSEG ; Verify CSEG jp nz,FileReadErr call GetWrd ; Get address add hl,bc ; .. add offset ld a,l ld (de),a ; Store word inc de ld a,h ld (de),a inc de jp RELloop SpecLink: ld a,4 call GetBits ; Get next four bits cp .NAME ; Check valid ones jp z,PrgNam cp .DATSIZ jp z,RelSiz cp .LOCCTR jp z,LocSet cp .PRGSIZ jp z,RelSiz cp .MODEND jp z,RelEOF jp FileReadErr ; ; Link item 2 : Program name ; PrgNam: ld a,3 call GetBits ; Get length of name call RelNam ; .. then skip it jp RELloop ; ; Link item 10 : Define data size ; Link item 13 : Define program size ; RelSiz: ld a,2 call GetBits ; Get address bits push af call GetWrd ; Get size pop af or a jp z,RELloop ; .. ignore ABSOLUTE ld a,(MaxREL+1) cp h ; Test against max length jp c,FileReadErr jp nz,RELloop ld a,(MaxREL) cp l jp c,FileReadErr jp RELloop ; ; Link item 11 : Set location counter ; LocSet: ld a,2 call GetBits ; .. get address mode call GetWrd ; .. get address add hl,bc ; Make absolute ex de,hl jp RELloop ; ; Link item 14 : End module ; RelEOF: ld c,.Close ld de,B.FCB call BDOS ; Close file ld hl,$DAT ld de,B.FCB+_DRV+_NAM ld bc,_EXT call StrCpy ; ..set extension ld a,_JP ld (BASE),a ; Init jumps ld (B.BDOS),a ld (B.HOME),a ld (B.CHN),a ld hl,WHM.go ld (BASE+1),hl ; Set base to WHM ld hl,(BDOS+1) ld (B.BDOS+1),hl ; .. BDOS ld hl,Home ld (B.HOME+1),hl ; .. cursor home routine ld hl,Chain ld (B.CHN+1),hl ; .. chain routine ld hl,MacroTrg ld (B.TRIG),hl ; .. trigger character address ld hl,KeyMacro ld (B.MACRO),hl ; .. keyboard macro address ld hl,MemArea ld (B.MEM),hl ; .. memory scratchpad call BASE+TPA ; Execute application jp WHM.go ; Enter WHM ; ; Chain hook for application ; Chain: ld hl,B.FCB+1 ; .. point to FCB jp OptFnd ; .. execute command ; ; Skip name of REL module ; ENTRY Accu holds length ; RelNam: ld h,a ; Save length NamSkip: ld a,8 call GetBits ; .. read name for trash dec h jr nz,NamSkip ret ; ; Fetch 16 bit from REL file ; EXIT Reg HL holds 16 bit ; GetWrd: ld a,8 call GetBits ; Get low ld l,a ld a,8 call GetBits ; .. and high ld h,a ret ; ; Load bits from REL file ; ENTRY Accu holds bit count ; EXIT Accu holds value ; GetBits: push bc push de push hl ld d,a ; Save count ld e,0 ; Clear result BitLoop: push de call GetBit ; Get a bit pop de ld a,e rlca ; .. shift old one place or b ; .. insert new bit ld e,a dec d jp nz,BitLoop ld a,e pop hl pop de pop bc ret ; ; Read one bit from REL file ; EXIT Reg B holds 0 or 1 ; GetBit: ld a,(BitCnt) ; Test bits in buffer or a jp nz,BitAvail ; .. yeap call GetByte ; Get byte ld (ReadByt),a ; .. save ld a,BitLen ld (BitCnt),a ; Reset bit length BitAvail: ld a,(ReadByt) ; Get old bits rla ; .. shift ld (ReadByt),a ld a,0 rla ; Insert bit into LSB ld b,a ld a,(BitCnt) dec a ; Bump down the count ld (BitCnt),a ret ; ; Read byte from REL file ; EXIT Accu holds byte read ; GetByte: ld a,(BytCnt) ; Test bytes in buffer cp RecLng jp nz,ByteAval ; .. yeap ld c,.RdSeq ld de,B.FCB call BDOS ; Read record or a jp nz,FileReadErr ; .. should not be the end ByteAval: ld e,a ; Build pointer ld d,0 inc a ld (BytCnt),a ; .. fix ld hl,B.DMA add hl,de ; Point to byte ld a,(hl) ; .. get it ret ; ReadByt: db 0 BitCnt: db 0 BytCnt: db 0 ; ; Get current user ; GetCurUsr: ld c,.UsrCod ld e,_get call Next ; Get current user ld (CurUsr),a ; .. save ; ; Set WHM user ; SetWHMusr: ld a,(WHMusr) ; Get WHM user SetUsr: ld e,a ld c,.UsrCod jp Next ; .. set new user ; ; Restore callers user area ; SetCalUsr: ld a,(CurUsr) ; Get users area jr SetUsr ; ; Restore callers disk buffer ; ResDMA: ld hl,($DMA$) ; Fetch address ex de,hl ld c,.SetDMA jp BDOS ; .. set it ; ; Get current disk buffer address ; GetCurDMA: ld c,.SCB ld de,SCB.PB call Next ; Get current disk buffer ld ($DMA$),hl ret ; SCB.PB: db _DMA,0,0 ; ; Save system parameters ; SavSYS: pop hl ld (SYS.PC),hl ; Save caller ld de,$SYSMEM$ ld hl,PrgTab ld a,(LOADflg) ; Test loader or a jp nz,SkpSavLD ; .. nope ld hl,LoadTab SkpSavLD: push hl push de ld c,(hl) ; Fetch count inc hl ld b,(hl) ; .. flag inc hl ld e,(hl) ; .. offset inc hl ld d,(hl) ld hl,(LOAD.Next) ; Get base add hl,de ; .. get address pop de call SavSYSpar ; Save these parameters pop hl ld bc,SYSlen add hl,bc ; Fix address ld a,(hl) ; Test end or a jp nz,SkpSavLD ld hl,(SYS.PC) ; Get back caller jp (hl) ; .. get back ; ; Reset system parameters ; ResSYS: pop hl ld (SYS.PC),hl ; Save caller ld de,$SYSMEM$ ld hl,PrgTab ld a,(LOADflg) ; Test loader or a jp nz,SkpResLD ; .. nope ld hl,LoadTab SkpResLD: push hl push de ld c,(hl) ; Get count inc hl ld b,(hl) ; .. flag inc hl ld e,(hl) ; .. offset inc hl ld d,(hl) ld hl,(LOAD.Next) ; Get basse add hl,de ; .. get address pop de call ResSYSpar ; Restore these parameters pop hl ld bc,SYSlen add hl,bc ; Fix address ld a,(hl) ; Test end or a jp nz,SkpResLD ld hl,(SYS.PC) ; Get back caller jp (hl) ; .. get back ; ; Save bunch of parameters ; ENTRY Reg DE points to save area ; Reg HL points to system location ; Reg C holds length ; Reg B holds flag ; SavSYSpar: ld a,b ; Test flag or a jp z,LDIR.8 ; .. it's from TPA bank ld a,(PagGap) ; Get page gap add a,h ld h,a ; .. fix address LSP.loop: call LdSYS ; Load from system bank ld (de),a ; .. save inc hl inc de dec c jp nz,LSP.loop ret ; ; Reset bunch of parameters ; ENTRY Reg HL points to save area ; Reg DE points to system location ; Reg C holds length ; Reg B holds flag ; ResSYSpar: ld a,b ; Test flag or a jp nz,RSP.sys ; .. attache system bank ex de,hl call LDIR.8 ; .. get from TPA bank ex de,hl ret RSP.sys: ld a,(PagGap) ; Get page gap add a,h ld h,a ; .. fix address RSP.loop: ld a,(de) ; Get byte call StSYS ; Store into system bank inc hl inc de dec c jp nz,RSP.loop ret ; ; Fill memory with constant byte ; ENTRY Reg HL points to memory to be filled ; Reg BC holds length ; Reg E holds byte ; FillChar: ld (hl),e ; .. store inc hl dec bc ld a,b or c ; Test end jp nz,FillChar ret ; ; Copy string as UPPER case ; ENTRY Reg HL points to source ; Reg DE points to destination ; Reg BC holds length ; StrCpy: ld a,(hl) ; Get character cp 'a' ; Test case jp c,IsUPP ; .. it's not lower and UPPMask ; .. convert IsUPP: ld (de),a ; Unpack inc hl inc de dec bc ld a,b or c ; Test end jp nz,StrCpy ret ; ; Emulate LDIR for byte count ; LDIR.8: push bc ld b,0 ; .. Force 16 bit ldir pop bc ret ; ; Process MACRO key ; EXIT Accu holds key ; Zero set if trigger character found ; ProcMACRO: call $CONIN$ ; .. get character ld hl,MacroTrg ; Test trigger cp (hl) ret z ; .. yeap dec a ; .. fix index and ChrMask rlca ; * 16 rlca rlca rlca ld c,a ld b,0 ld hl,KeyMacro add hl,bc ; Build address ld (MacroPtr),hl ; .. save it ld a,(hl) ld (MacroChr),a ; .. save 1st character xor a inc a ret ; ; Get next macro character ; GetNextMACRO: ld a,(MacroChr) ; Get macro character cp '%' ; Test input from console jp z,GetFromCons ; .. yeap ..GetNextMACRO: ld b,a call GetMACROchar ; Get next macro character ld a,b ret ; ; Get next macro character from current macro ; GetMACROchar: ld hl,(MacroPtr) ; Get pointer inc hl ; .. bump ld (MacroPtr),hl ld a,(hl) ; Get character ld (MacroChr),a ret ; ; Got macro key % : Get macro character from keyboard ; GetFromCons: call $CONIN$ ; Get character cp cr ; Test end of input ret nz ; .. nope call GetMACROchar ; Skip % jp ..GetNextMACRO ; .. get next ; dw -1,-1 WinSav: ds 6 ; ds 10 db 'D.W.Clements 1986' KeyMacro: ds MacLen*MacCnt db 0 MemArea: ds AreaLen $OPTION: db esc,'p' db $D.UL ds 16,$D.H db $D.UR db cr,lf db $D.V,' Write-Hand-Man ',$D.V db cr,lf db $D.V,' Enter Choice[ ]',$D.V db cr,lf db $D.V,' A - ' $NOTEPAD: db 'Notepad ',$D.V db cr,lf db $D.V,' B - ' $PHONEBOOK: db 'Phonebook ',$D.V db cr,lf db $D.V,' C - ' $CALENDAR: db 'Calendar ',$D.V db cr,lf db $D.V,' D - ' $DIR: db 'Dir ',$D.V db cr,lf db $D.V,' E - ' $VIEW: db 'View ',$D.V db cr,lf db $D.V,' F - ' $CALCULATE: db 'Calculate ',$D.V db cr,lf db $D.V,' G - ' $KEYS: db 'Keys ',$D.V db cr,lf db $D.V,' R - ' $RESTORE: db 'Restore ',$D.V db cr,lf db $D.V,' O - OTHER ',$D.V db cr,lf db $D.LL ds 16,$D.H db $D.LR db esc,'q',eot $CHOICE: db lf,lf db esc,'p',$D.V,' Enter Choice[ ]' db bs,bs,esc,'q',eot $BLANK: db ' ',lf,cr,eot $ASK: db cr,esc,'p',$D.V,esc,'q' db ' Name >' db ' ' ds 9,bs db eot ; $ERR.MESS: db 'a' $EM.usr: db '0:' $EM.nam: db 'xxxxxxxx.' $EM.ext: db 'yyy',cr,lf,lf $EM.buff: db ' ' db cr,lf,lf db ' continue >' db eot ; $NOT.FND: db 'file not found ' $LOAD.ERR: db ' load error ' ErrLen equ $-$LOAD.ERR ; $DAT: db 'DAT' $REL: db 'REL' $DMA$: dw CCP MaxREL: dw RELlen CurUsr: db 0 WHMusr: db 0 CalDrv: db 0 CurDriv: db 0 $HOME: db esc,'H',eot db 0 LOADflg: db 0 PagGap: db 0 SYS.PC: dw 0 UsrStkSav: dw 0 $SYSMEM$: ds 180 ; ; Offset table for normal BDOS ; Each record consist of four bytes (Last one only two bytes) ; Byte 1 Number of bytes to be attached ; Byte 2 Memory flag ; Bytes 3,4 Offset in BDOS ; PrgTab: db 2,0 dw 0428h SYSlen equ $-PrgTab db 2,0 dw 0566h db 32,0 dw 0546h db 88,0 dw 059ch db 1,1 dw 289eh db 2,1 dw 0d9fh db 2,1 dw 0332h db 20,1 dw 0abch db 9,1 dw 0d26h db 0,0 ; ; Offset table for LOADER RSX ; Byte definition as above ; LoadTab: db 1,0 dw 1cc3h db 1,0 dw 077ah db 2,0 dw 02cbh db 32,0 dw 0cch db 100,0 dw 1e9ch db 0,0 ; ; !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; !!!!! START OF APPLICATION AREA !!!!! ; !!!!! LENGTH ARE 9 PAGES !!!!! ; !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; BASE equ $ B.BDOS equ BASE+05h B.HOME equ BASE+10h B.CHN equ BASE+13h B.TRIG equ BASE+16h B.MACRO equ BASE+18h B.MEM equ BASE+1ah B.FCB equ BASE+5ch B.DMA equ BASE+80h ; ; ***** The installer task ***** ; db 0 DoInst: inc de inc de ld a,(de) ; Fetch callers drive ld (CalDrv),a inc de inc de ld a,(de) ; Fetch pointer ld l,a inc de ld a,(de) ld h,a ld a,(hl) ; Get trigger ld (Trigg2),a ; .. save ld (Trigg1),a inc de ld a,(de) ; Get pointer to top ld l,a inc de ld a,(de) ld h,a inc de push de ld a,(hl) ; Get character ld (MacroTrg),a inc hl ld de,KeyMacro ld bc,SavLng ldir ; Unpack data from caller pop de ld hl,(Next+1) FindRSX: ld bc,_NEXT-_STRT+1 add hl,bc ; Point to next RSX ld e,(hl) inc hl ld d,(hl) ld l,_NAME ; Point to name ld a,(hl) cp 'G' ; Test system RSX 'GET' jp nz,NotGET inc hl ld a,(hl) cp 'E' jp nz,NotGET inc hl ld a,(hl) cp 'T' jp nz,NotGET inc hl ld a,(hl) cp ' ' jp nz,NotGET ld l,0 ld (GET.RSX),hl ; Save address of GET RSX NotGET: ld l,_LOADER ld a,(hl) cp -1 ; Test loader jp z,LastRSX ; .. yeap ex de,hl jp FindRSX ; Try next GET.RSX: dw 0 LastRSX: ex de,hl ld (LOAD.Next),hl ; Save LOADER pointer ld bc,3*(@WBOOT-1) call GetBIOS@ ; Get warm boot address ld ($WBOOT$),hl ; ..save ld a,(GET.RSX+1) ; Test GET RSX found or a jp z,InstMyRSX ; .. nope so take mine ld hl,(GET.RSX) ld bc,_GET.ST add hl,bc ; Point to GET status ld e,(hl) inc hl ld d,(hl) ex de,hl ld ($CONST$+1),hl ; .. set it up ld hl,(GET.RSX) ld bc,_GET.IN add hl,bc ; Same for GET input ld e,(hl) inc hl ld d,(hl) ex de,hl ld ($CONIN$+1),hl jp SkpMyCON InstMyRSX: ld bc,3*(@CONST-1) call GetBIOS@ ; Get BIOS console vectors ld ($CONST$+1),hl ld bc,3*(@CONIN-1) call GetBIOS@ ld ($CONIN$+1),hl SkpMyCON: ld bc,3*(@CONOUT-1) call GetBIOS@ ; Get BIOS vectors ld ($CONOUT$+1),hl ld bc,3*(@SELMEM-1) call GetBIOS@ ld ($SELMEM$+1),hl ld de,.WBOOT. ld bc,3*(@WBOOT-1) call SetBIOS@ ; Set new warm boot ld a,(GET.RSX+1) ; Test GET RSX or a jp z,SkpSwapRSX ; .. nope ld de,.CONST. ld hl,(GET.RSX) ld bc,_GET.ST add hl,bc ld (hl),e ; Save addresses into GET RSX inc hl ld (hl),d ld de,.CONIN. ld hl,(GET.RSX) ld bc,_GET.IN add hl,bc ld (hl),e inc hl ld (hl),d jp SkpSetVec SkpSwapRSX: ld bc,3*(@CONST-1) ld de,.CONST. call SetBIOS@ ; Set console vectors ld bc,3*(@CONIN-1) ld de,.CONIN. call SetBIOS@ SkpSetVec: ld bc,3*(@CONOUT-1) ld de,$CONOUT$ call SetBIOS@ ; Set other vectors ld bc,3*(@SELMEM-1) ld de,.SELMEM. call SetBIOS@ xor a ld (Remove),a ; Force RSX permanent xor a ld (LOADflg),a ; Clear loader flag ld hl,(LOAD.Next) ld a,(hl) ; Get page ld l,0 ld (LOAD.Next),hl ; .. save page boundary cp _LD.PAG ; Test loader ret z ; .. yeap ld a,1 ld (LOADflg),a ; .. reset flag ld de,_PAG.OF add hl,de ld a,(hl) ; Get pages ld hl,(LOAD.Next) sub h ; .. get gap ld (PagGap),a ret ; ; Get address of BIOS ; ENTRY Reg BC holds offset within BIOS jump table ; EXIT Reg HL holds address ; GetBIOS@: ld hl,(OS+1) ; Fetch base add hl,bc ; .. add offset inc hl ; .. and skip JP ld a,(hl) ; Fetch address inc hl ld h,(hl) ld l,a ret ; SHAR equ $-BASE ds RELlen-SHAR ; ; !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; !!!!! END OF APPLICATION AREA !!!!! ; !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; BootFlg: db 0 TrgFlg: db 0 YourBank: db 0 MyBank: db 0 TstCon: db 0 SavChar: db 0 ; ; New warm boot entry ; .WBOOT.: ld a,(BootFlg) ; Test flag or a jp nz,WHM.go ; .. enter menu jp $-$ ; .. or enter OS $WBOOT$ equ $-2 ; ; New select memory ; .SELMEM.: push af ld a,(BootFlg) ; Test flag or a jp nz,SelMenBank ; Do internal pop af ld (YourBank),a ; .. save jp $SELMEM$ ; .. set bank SelMenBank: pop af ld (MyBank),a ; Save bank $SELMEM$: jp $-$ ; ; New console status ; .CONST.: ld a,(MacroChr) ; Test macro character pending or a jp nz,WHMcon ; .. yeap ld a,(TstCon) ; Test character here or a ret nz ; .. yeap, exit call $CONST$ ; Get state or a ret z ; .. nothing here call $CONIN$ ; Get character ld (SavChar),a ; .. save ld hl,MacroTrg cp (hl) ; Test macro trigger jp nz,NotTrgg ; .. nope call DoMACRO ; .. do the job ret nz NotTrgg: ld a,(BootFlg) ; Test flag or a jp nz,WHMnotc ; .. skip ld a,(SavChar) ; Get character cp $-$ ; Test trigger Trigg1 equ $-1 jp z,Invoke ; .. yeap, set flag WHMnotc: ld a,-1 ld (TstCon),a ; Set character available jp .CONST. ; .. re-enter ; ; Got pending character from console ; WHMcon: ld hl,ConCnt ld a,(hl) ; Get count inc a ; .. bump ld (hl),a and ConsLen+1 ; Test max ret z ; .. nope xor a ld (hl),a ; .. clear inc a ret ConCnt: db 0 ; ; Indicate trigger found ; Invoke: ld a,-1 ld (TrgFlg),a ; Set invocation flag jp Invoked ; .. and process WHM ; ; New console input ; .CONIN.: ld a,(MacroChr) ; Get pending macro or a jp nz,ProcNxtMACRO ; .. there's one ld a,(TstCon) ; Test character here or a jp z,ProcNone ; .. nope xor a ld (TstCon),a ; Clear flag ld a,(SavChar) ; .. get character ret ; ; BIOS redirected vectors ; $CONIN$: jp $-$ $CONST$: jp $-$ $CONOUT$: jp $-$ ; ; Got MACRO trigger - do the job ; DoMACRO: ld (StkSav),sp ; Save stack ld sp,UsrStack ; Load local stack call TPA.Bank ; Set TPA bank call ProcMACRO ; Do the macro push af ; .. save it call Prg.Bank ; Reset bank pop af ; Get back key ld sp,(StkSav) ; .. and stack ret ; ; Got MACRO trigger - do the job ; ..DoMACRO: call ProcMACRO ; Do the macro jp z,EndMACRO ; .. got another trigger jp .CONIN. ; .. get key ; ; Got pending MACRO character - process it ; ProcNxtMACRO: ld (StkSav),sp ; Save stack ld sp,UsrStack ; .. get local call TPA.Bank ; Set TPA bank call GetNextMACRO ; Get next macro character push af call Prg.Bank ; Reset bank pop af ; Get back key ld sp,(StkSav) ; .. and stack jp EndMACRO ; .. process end ; ; Nothing pending - get character ; ProcNone: call $CONIN$ ; Get character ld hl,MacroTrg cp (hl) ; Test MACRO jp z,..DoMACRO ; .. yeap EndMACRO: ld b,a ld a,(BootFlg) ; Test me calling or a ld a,b ret nz ; .. yeap cp $-$ ; Test trigger Trigg2 equ $-1 ret nz ; ; Got trigger - process call ; Invoked: ld a,1 ld (BootFlg),a ; Set WHM activated ld hl,0 add hl,sp ld (UsrStkSav),hl ; Save stack ld sp,WHMstk ; .. get local call TPA.Bank ; Set TPA bank jp ProcWHM ; .. process WHM ; ; Final user reset ; ResCall: xor a ld (BootFlg),a ; Reset WHM active call Prg.Bank ; Reset bank ld sp,(UsrStkSav) ; Get back stack ld a,(TrgFlg) ; Test trigger or a jp z,.CONIN. ; .. nope xor a ld (TrgFlg),a ; Clear it jp .CONST. ; .. fall into state ; ; Set TPA bank ; TPA.Bank: ld a,_TPA push bc call $SELMEM$ ; .. select it pop bc ret ; ; Reset program bank ; Prg.Bank: ld a,(BootFlg) ; Test WHM active or a jp nz,resMyBank ; .. yeap ld a,(YourBank) ; Get external bank jp SetBank ; .. set it resMyBank: ld a,(MyBank) ; Get internal bank SetBank: push bc call $SELMEM$ ; .. set bank pop bc ret ; ; Load byte from system bank ; ENTRY Reg HL holds address ; EXIT Accu holds byte from bank 0 ; LdSYS: push bc push de push hl xor a call $SELMEM$ ; Select system bank pop hl ld a,(hl) ; Load byte push hl push af ld a,_TPA call $SELMEM$ ; Reset to TPA bank pop af pop hl pop de pop bc ret ; ; Store byte into system bank ; ENTRY Reg HL holds address ; Accu holds byte stored into bank 0 ; StSYS: push bc push de push hl push af xor a call $SELMEM$ ; Select system bank pop af pop hl ld (hl),a ; .. store push hl ld a,_TPA call $SELMEM$ ; Reset to TPA bank pop hl pop de pop bc ret ; StkSav: ds 2 ; ds 2*16 UsrStack: ; ds 2*24 WHMstk: ; MacroChr: ds 1 MacroPtr: ds 2 MacroTrg: db -1 end