; ;This is the main module for both the CCP and CMDRUN. ; ;Assemble CCPHDR.MAC to produce the CCP, and LRUNHDR.MAC to ; produce the library processor. ; ;Version 1.02A 10/03/85 - Fixed bugs relating to loading of .SUB ; files from COMMAND.LBR ; ;Version 1.02B 11/04/85 - Fixed bug which caused bad drive/user parse to ; return with indication of a good drive or user parse (eg: ; CUG: would return with a good drive C: parse). Also, CCP ; now checks for a valid drive/user spec whenever a file is ; to be run (ie: COMfiles, SUBfiles and PRLfiles). Also added ; EXPAND,PRINT0 and WHLLBR equates and equates for user's own ; MAXUSR, WHEEL, and MAXUSR boot values (see CCPHDR.MAC for ; details). ; - Stuart Rose ; ;Version 1.03 11/06/85 - Removed PRINT0 equate, changed EXPAND and ; WHLLBR equate to flag options. Fixed more bugs relating ; to library command processor. CMDRUN now properly scans ; more than one command library along the drive search chain. ; ;Version 1.04 03/08/85 - Added EXDRV and EXUSR variables for CMDRUN ; ; 04/14/86 - Fixed bug that prevents nested multiple command ; lines from being run properly. That is, if a multiple command ; is issued, and one of the commands issues a chain command ; with a multiple command, the initial multiple command line ; would be lost, leaving an active RSX, which will not go ; away. Added a name to RSX containing next command. ; (NEXTCMND) ; ; 07/13/86 - Added option to display time-on-system of current ; caller in an RCPM running under BYE509 or newer. If TIMEON ; is YES, and both TIME and BYECHK are YES, then if BYE is ; active displays time-on-system rather than time-of-day. ; Set CCPPLUS to YES in BYE to use this option. ; (Thanks to Stuart Rose) ; ; 07/14/86 - Changed from using a flag byte to equates in ; CCPHDR.MAC and LRUNHDR.MAC. It is now necessary to ; reassemble the source to change options. With the new ; fixes and options in version 1.04, the CCP will be larger ; than 25 sectors, and may require special loading or BIOS ; modifications to accept a larger CCP. ; ; ;Version 1.05 9/1986 - Added history mechanism,print0, and makecolon fix ; ; Added history mechanism that is similar to ; Unix (tm of AT&T) csh's. This includes the internal ; 'h' command that displays the history. This option ; is probably only acceptable with the "temp-disk" being ; a RAMDISK or possibly a fast Harddisk. This ; feature also gives a mechanism for additional extension. ; ; Added print0 back again. ; ; Added makecolon so when running "make", where ; commands generated can have leading colons, an error ; set by one of the commands will terminate the entire ; rest of the (nested) submit file(s). ; ; -Mike Kersenbrock bdos EQU 5 ;Bdos entry point USRDSK EQU 4 ;User/disk (for CP/M 1.4,2.2 compatibility) FCB EQU 5CH ;default FCB FCB2 EQU 6CH ;default 2nd FCB FCBCR EQU 7CH ;CR field of FCB LOADDRV EQU 50H ;.COM file load drive PASS1ADR EQU 51H ;password 1 address PASS1LEN EQU 53H ;password 1 length PASS2ADR EQU 54H ;password 2 address PASS2LEN EQU 56H ;password 2 length SIZECMDLINE EQU 0E7H ;command line max length ; V. 1.05 if ccp ;--------------------------------------------------------------- ;Loader save area and entry points SCBBASE EQU 11bH ;address of System Control Block MEMBASE EQU 11dH ;location of common memory base CHKRSX EQU 11eH ;loader check RSX entry point RELOC EQU 121H ;loader relocate entry point SETLOAD EQU 124H ;loader set load entry point SETNEXT EQU 127H ;loader set next RSX pointer entry point SETRSX EQU 12aH ;loader set RSX pointers entry point xbdos equ 12dh ;save IX and call bdos entry point endif ;CCP ; ;-------------------------------------------------------------- maxdrv EQU 3dh ;ZCPR maxdrive wheel EQU 3eh ;ZCPR wheel maxusr EQU 3fh ;ZCPR maxuser ;........ ; ;Main entry point. The BIOS loads the CCP into the tpa. ;The loader module has a JMP START at 100H to bring us here. ; START: LD SP,STACK ;set up local stack LD HL,CCPRET ; PUSH HL ;push CCP return onto stack LD DE,SCBPB LD C,49 ;RETURN BASE PAGE OF SYSTEM CONTROL BLOCK CALL BDOS ld l,80h ;set up for IX register LD (SCBBASE),HL ;Save address of SCB push hl pop ix ;IX points to SCB (xx80H) if ccp LD a,(ix+7aH) ;0FAH = COMMON MEMORY BASE PAGE LD (MEMBASE),A ;Save common mem base page LD a,(ix+19H) ;99H = BASE PAGE OF BDOS SYSTEM LD (BDOSBASE),A ;Save Base page of BDOS system ; ;CHECK TO SEE IF ANY RSX'S AND/OR LOADER PRESENT ; LD A,(BDOS+2) ;Get top of TPA page SUB (ix+19H) ;compare with BDOS page jr NZ,NOLOAD ;jump if loader already in place ; ;need to relocate the loader into high ram ; LD BC,(LOADLEN) ;PREPARE FOR RELOCATION CALL SETLOAD ;Set up relocation paramaters LD H,E LD L,E CALL RELOC ;relocate the loader LD HL,(BDOS+1) LD L,E LD C,6 CALL MOVEC ;move the serial number into place LD E,0BH CALL SETNEXT ;Set up next address in loader RSX header NOLOAD: if byechk LD DE,rsxpb ;point to call RSX pb CALL rsx ;check for bye present LD (byeact),A ;save BYE active flag endif ; byechk LD C,98 ;FREE BLOCKS CALL xbdos ;free blocks LD (ix+53H),'$' ;0B6H = String delimiter LD (ix+66H),1 ;0E6H = MULTI-SECTOR COUNT LD (ix+67H),0 ;Init BDOS error mode LD (ix+4FH),3 ;0CFH = CONSOLE MODE LOW BYTE LD (ix+50H),0 ;Init Console mode high byte ld a,(ix+2bh) ;get submit drive ld (subfcb),a ;save it bit 5,(ix+34H) ;0B4H = SYSTEM FLAGS (b5=reset disk system) ld c,13 CALL NZ,xbdos ;Reset disk system if set bit 1,(ix+33H) ;0B3H = SYSTEM FLAGS (b1=RSX flag) CALL Z,CHKRSX ;Delete inactive RSXs if clear res 1,(ix+33H) ;Clear RSX flag endif ;CCP LD c,25 CALL xbdos ;get current drive LD (disknum),A ;save it LD BC,USERNUM ;Point to our user number save if ccp LD A,(ix+60h) ;Get BDOS user number else ;if not CCP ld a,(ix+30h) ;get CCP user number endif ;not CCP LD (BC),A ;Save it for us if ccp LD A,(ix+30H) ;Get CCP user number bit 6,(ix+33h) ;Bit 6 = change default u/d to last program jr NZ,OLDUSR ;Jump if to set to last program user number LD (BC),A ;Save CCP user number OLDUSR: LD (ix+60h),A ;Set the BDOS user number INC BC ;Point to our drive save LD A,(BC) ;Get BDOS disk jr NZ,OLDDSK ;Jump if to set to last program disk number LD A,0FFH ;Flag that we must login drive OLDDSK: res 6,(ix+33h) ;reset default u/d bit LD (BC),A ;Save disk number for us INC BC ;POINT TO CURDSK LD A,(ix+2fH) ;Get CCP disk LD (BC),A ;Save it for us CALL seldsk ;select drive LD DE,rsx66 ;point to RSX function 66 CALL rsx ;see if directory names loaded OR a jr NZ,noroot ;jump if no directory names LD (diradr),HL ;save directory name table address noroot: bit 7,(ix+33H) ;Bit 7 of B3H = chain flag jr Z,NOCHAIN ;jump if normal CCP command LD HL,80H ;Point to location of chain command else ;if not CCP ld hl,81h ;point to location of command endif ;not CCP ; ;MOVE THE COMMAND LINE FOR PROCESSING ; MOVCMD: LD DE,CMDLINE ;Point to internal command line buffer LD BC,7FH ;Length of move LD A,C LD (DE),A ;Save command line max length INC DE ldir ;Move command line into place if ccp jp DOCMD ;And go process it. NOCHAIN: ;Here if no chain function call bit 1,(ix+35H) ;0B5H = SYSTEM FLAGS (b1=cold start) jr nz,nocold ;jump if normal warm start if makecolon ; V1.05 xor a ;get a zero ; V1.05 LD (ix+2cH),a ;Zero program return code ; V1.05 LD (ix+2dH),a ; V1.05 endif ; makecolon ; V1.05 set 1,(ix+35h) ;SET COLD START FLAG ld a,1 LD (msgflag),A ;Save copy for us ld c,13 CALL xbdos ;reset disk system on cold boot ld hl,maxdrv ;point to ZCPR maxdrv ld (hl),mydrv ;Init ZCPR MAXDRV ; V1.02B inc hl ld (hl),mywhl ;Init ZCPR WHEEL ; V1.02B inc hl ld (hl),myusr ;Init ZCPR MAXUSR ; V1.02B LD HL,PROFSUB ;point to 'PROFILE.SUB' command jr MOVCMD ;execute PROFILE.SUB on cold start PROFSUB: DEFB 'PROFILE.S',0 ;Cold start command ; ; ; NOCOLD: CALL SETFLG ;SETFLG sets Bits 7 & 5 in offset B4H CALL CRLF ;Turn up a new line bit 6,(ix+24h) ;test for erase of $$$.SUB file ld c,19 call nz,dosubfcb ;erase any $$$.SUB file res 6,(ix+24h) ;reset erase $$$.SUB file ;......... ; ;Internal commands and errors return here ; CCPRET: LD sp,STACK-2 ;Set up the stack LD HL,CCPRET PUSH HL ;Push return onto stack CALL SETFLG ;Set bits 7 & 5 in offset B4H ; ;DISPLAY THE SYSTEM PROMPT ( A> ) ; call prompt ; V 1.05 (code change, but same logic) jp prmpt2 prompt: if time LD E,'[' CALL co ;display "[" if timeon and byechk ld a,(byeact) ;get BYE active flag or a ;is BYE running? jr nz,shwtim ;nope, just show time ld c,79 call xbdos ;get time on from BYE call prtnum ;display time on ld de,minmsg ; display " min." ld c,9 call xbdos jr st1 ;clean up shwtim: endif ; timeon and byechk LD DE,datpb LD c,105 CALL xbdos ;return time LD HL,datpb+3 LD a,(HL) ;get minutes PUSH AF ;Save for later DEC HL ;Point to hours LD A,(HL) CALL hexprt ;display hours LD E,':' ;separater CALL co POP AF ;get minutes CALL hexprt ;display minutes st1: LD E,']' CALL co LD E,' ' CALL co endif ; time CALL PCURDSK ;Display the current drive LD A,(USERNUM) ;get user number if not print0 ; V 1.05 or a ; V 1.05 jr z,noprtusr ;No user number if it is zero ; V 1.05 endif ; not print0 call PRTNUM ;Display user number ; V 1.02B noprtusr: ; V 1.05 bit 7,(ix+24h) ;test for directory name display jr Z,nodirnm ;jump if no directory name display LD HL,(diradr) ;get directory name address LD a,h OR l jr Z,norfile ;jump if null EX DE,HL LD HL,rootdrv ;point to drive returned by rootget rootloop: CALL rootget ;get an entry jr Z,norfile ;jump if at end LD A,(curdsk) ;get current drive CP (HL) ;same as table entry? jr NZ,rootloop INC HL ;point to user number from rootget LD A,(usernum) ;get current user CP (HL) ;same as table entry? jr Z,rootok DEC HL jr rootloop rootok: LD a,':' CALL cono ;display a colon LD HL,rootname ;point to directory name LD c,' ' ;it terminates with a blank CALL prtname ;print the directory name norfile: LD DE,rootrsx ;point to RSX function 65 CALL rsx ;Any LBR RSX's will print their names nodirnm: LD A,'>' JP CONO ;Display the system prompt prmpt2: LD DE,0B1BAH CALL MOVSCB ;Move offsets B1,B2 to BA,BB in SCB OR A ;Test for address of second command line PUSH AF ;save flags on stack jr z,notmulti res 7,(ix+34h) ;Clear Multiple command line flag notmulti: CALL GETLINE ;Get command CALL CRFLGA ;clear bits 7 & 5 in B4H POP AF ;Restore 2nd command flag CALL NZ,CHK2ND ;Check 2nd command line ;........ ; ;Here to process command line ; DOCMD: endif ;CCP xor a ld (ix+25h),a ;Init user number for load overlay function if ccp ld (subflag),a ;init submit flag ld a,(ix+24h) ;get submit user number and 0e0h ;set it to default ld (ix+24h),a ;and save it endif ;CCP bit 6,(ix+34h) ;test default page mode jr nz,oldpmode ld a,(ix+49h) ;get default page mode ld (ix+48h),a ;reset default page mode oldpmode: CALL SCANLINE ;get first item in command line RET Z ;Return to CCPRET if nothing there LD DE,CMDFCB ;Point to command FCB CALL CHKDRV ;Check for drive spec and parse command line LD A,(FILETYPE) ;Get Filetype first byte CP ' ' ;Do we have a filetype? if CCP jr NZ,FTYPE ;jump if filetype present LD HL,CMDFCB ;Point to command FCB LD A,(HL) ;Get user number INC HL ; Point to drive in FCB OR (HL) ;Test for user or drive spec INC HL ;Point to filename LD A,(HL) ;get first byte of filename jr NZ,DRVSPEC ;Jump if drive or user number specified LD HL,(diradr) ;get directory name address LD a,h OR l jr Z,nocmd ;jump if not loaded EX DE,HL LD HL,filename ;point to filename retuned by rootget rootcloop: CALL rootget ;get an entry jr Z,nocmd ;jump if at end CALL scomp ;is directory name=command? jr NZ,rootcloop CALL chkpass ;verify if passworded directory LD HL,rootdrv ;point to directory drive LD a,(HL) INC a LD (filedisk),A ;save it in command drive INC HL ;point to directory user LD a,(HL) jp newuser ;process drive/user change else ;if not ccp ld a,1 jr nz,setftype xor a setftype: ld (typeflag),a ;save filetype flag ld a,(ix+6ch) ;get temp file drive ld (ix+2bh),a ;set submit file drive ld (subfcb),a ;save it ld hl,(cmdfcb) ;get user/drive spec ld (lbrfcb),hl ;put it in LBR FCB ld (usrsav),hl ;and save it ;V 1.03 ld hl,0e704h ;set up search offset, length ;V 1.03 ld (searoff),hl ;V 1.03 ld a,(disknum) ;get default drive ;V 1.03 inc a ;V 1.03 ld h,a ;V 1.03 ld l,1 ;V 1.03 ld (searflg),hl ;V 1.03 docmpf: ;V 1.03 ld a,(usernum) ;V 1.03 ld (ix+60h),a ;set the user number ;V 1.03 ld hl,0 ld (cmdfcb),hl ;zero user/drive for member ld hl,(usrsav) ;get user/drive ;V 1.03 ld (lbrfcb),hl ;put it in LBR FCB ;V 1.03 call cmpftype ;attempt to open COMMAND.LBR using CPM's ;drive search chain. call lbrread ;read first library sector jr z,lbrok ;V 1.03 badlbr: ;V 1.03 call ilprt ;V 1.03 db 'Invalid COMMAND.LBR',13,10,0 ;V 1.03 jr lbrdone ;V 1.03 lbrok: ;V 1.03 ld hl,buff ld de,lbrcmp ld b,14 call comp ;test for valid library jr nz,badlbr ;V 1.03 ld hl,(buff+14) ;get dir length ld (lbrsec),hl ;save dir length ld hl,buff+32 ;point to first member ld b,3 ; 3 members left jr lbr2 lbr1: ld hl,(lbrsec) dec hl ld (lbrsec),hl ;decr sector count ld a,h or l jr z,lbrdone ;V 1.03 call lbrread ;read a directory sector jr nz,badlbr ;V 1.03 ld hl,buff ld b,4 ;4 members per sector lbr2: push bc ld a,(hl) or a ;active member? jr nz,lbr3 inc hl ld (memaddr),hl ;save member address ld a,(typeflag) or a jr nz,ftype ;jump if file type present endif ;not CCP NOCMD: ld a,(ix+34h) and 18h ;Test bits 3,4 of B4H (file type search order) jr Z,FTYPE ;Jump if search .COM only LD B,8 ;init B for later SUB B ;Test for .COM, then .SUB jr Z,NOCMD1 ;Jump if .COM, then .SUB LD B,0 ;Here if order is .SUB, then .COM NOCMD1: PUSH BC ;Save search order indicator for 2nd filetype CALL MOVETYPE ;Move first filetype into FCB (indicator in A) CALL CMPRFTYPE ;Try First filetype POP AF ;retrieve second filetype indicator CALL MOVETYPE ;Move 2nd filetype into FCB FTYPE: CALL CMPRFTYPE ;Attempt to execute the command if ccp if yeslbr ld hl,crname ;Point to CMDRUN fcb if whllbr ld A,(wheel) ; get the wheel byte ; V1.02B and A ; check for wheel byte set (non-zero); V1.02B call nz,setcmd ;set up CMDRUN fcb and attempt else ; if not whllbr call setcmd ;set up CMDRUN fcb and attempt endif ; not whllbr endif ; yeslbr jp ERRXIT ;If we returned, then its an error else ;if not CCP ld hl,(memaddr) ;get member address dec hl lbr3: pop bc inc (hl) ;test for 0ffh jr z,lbrdone ;V 1.03 ld de,32 add hl,de ;next member djnz lbr2 jr lbr1 lbrdone: ;V 1.03 ld a,(duspec) ;drive/user specified? ;V 1.03 or a ;V 1.03 jp z,docmpf ;try again if no drive/user ;V 1.03 jp errxit ;V 1.03 endif ;not CCP if ccp ; ;......... ; ;Here if Drive spec or user number in command line ; DRVSPEC: CP ' ' ;Test for filename in FCB jr NZ,NOCMD ;Jump if Drive spec & filename CALL CHKBLANK ;Check for embedded blanks LD HL,cmdfcb ;point to command user LD a,(HL) DEC a JP P,sisusr ;jump if user # specified LD A,(usernum) ;else get current user # sisusr: INC a LD (HL),a ;put user number in command user INC HL ;point to command drive LD a,(HL) DEC a JP P,sisdrv ;jump if new drive LD A,(curdsk) ;else get current drive sisdrv: INC a LD (HL),a ;put drive in command drive LD A,(cmdfcb) ;get command user DEC a NEWUSER: LD (USERNUM),A ;Save new user number ld (ix+30h),a ;Set CCP user number ld (ix+60h),a ;Set BDOS user number SAMEUSER: LD A,(FILEDISK) ;Get drive from FCB DEC A ;Test it RET M ;Back to CCPRET if no drive spec PUSH AF ;Save new drive on stack CALL SELDSK ;Select new drive POP AF ;restore new drive LD (CURDSK),A ;Save it for us ld (ix+2fh),a ;Set CCP drive, and return to CCPRET ret ;.......... ; ;PRINT DISK IN [A] IF > 0 OR CURRENT DISK ; PRTDISK: DEC A ;Drive specified in FCB? JP P,PRTDSK ;Jump if specified ; ;PRINT CURRENT DISK ; PCURDSK: LD A,(CURDSK) ;Get current drive ; ;PRINT DISK IN [A] ; PRTDSK: ADD A,'A' ;convert to ASCII jp CONOUT ;and print it ;........... ; ;SUBMIT FILE FCB ; SUBNAME: DEFB 0,0,'SUBMIT COM' ;............. ; ;CONSTRUCT SUBMIT COMMAND LINE ; SUBMIT: LD A,(DE) ;Save submit drive LD (ix+2BH),a ;Save submit drive in SCB inc a ;non-zero ld (subflag),a ;set submit flag LD HL,SUBNAME ;Point to submit file name setcmd: ld de,cmdfcb ld bc,13 ;13 bytes long ldir ;move it ld hl,cmdline ;point to command line ld (hl),' ' ;start with a blank inc hl ;point to second byte ld (pfcb),hl ;Store its address for Parse jr cmprftype else ;if not CCP ;........... ; ;Submit file handler for CMDRUN. The .SUB file is ;read from the Library, and saved as $$$.SUB in the current ;CCP drive/user location, and a Chain command is executed ;to let the CCP handle the submit function. ; submit: ld (ix+25h),0 ;reset Loader user number call setlbr ;set up things to read member ld c,19 call dosubfcb ;erase any $$$.SUB file ld c,22 call dosubfcb ;make new $$$.SUB file jr z,smakeok call ilprt db 'No directory space for $$$.SUB',0 rst 0 smakeok: ld hl,(lbrfcb+36) ;get member length inc h dec h jr nz,longsub ;.SUB file member must be < 16k ld a,l cp 129 jr c,slenok longsub: call ilprt db 'SUB member > 16k',0 rst 0 slenok: ld (ix+66h),a ;set multi-sector count ld de,stack call setdma ;set up dma for mass transfer call setlusr ;set library user if no default ld c,20 call xbdos ;read in the .SUB member or a jr z,sreadok call ilprt db 'Cannot read SUB member',0 rst 0 sreadok: ld c,21 call dosubfcb ;write the $$$.SUB file jr z,swriteok call ilprt db 'Out of disk space writing $$$.SUB',0 rst 0 swriteok: ld c,16 call dosubfcb ;close the $$$.SUB file jr z,scloseok call ilprt db 'Cannot close $$$.SUB',0 rst 0 scloseok: ld (ix+66h),1 ;reset multi-sector count call sdefdma ;reset dma set 6,(ix+24h) ;flag $$$.SUB file present ld a,(subfcb) ;get submit drive ld de,80h ;point to target of move or a ;submit drive? jr z,nosubdrv add a,'A'-1 ;make drive ASCII ld (de),a inc de ld a,':' ld (de),a ;put colon into place inc de nosubdrv: ld hl,subname ld bc,5 ldir ;move $$$.S into place ld hl,(pfcb) dec hl ;point to command tail ex de,hl call movetil0 ;move command tail into place ld c,47 ld e,0 jp bdos ;chain to submit handler in CCP subname: db '$$$.S' endif ;not CCP dosubfcb: xor a ;submit fcb always user 0 ld (ix+60h),a ;set submit user number ld de,subfcb ;point to submit FCB call xbdos ;do the function if not ccp or a ;set flag endif ;not CCP ld a,(usernum) ;get our user # ld (ix+60h),a ;set BDOS user number ret subfcb: db 0,'$$$ SUB',0,0,0,0 ds 16 db 0 ;cr field ;............ ; ;COMPARE AND PROCESS FILE TYPE IN COMMAND ; CMPRFTYPE: LD DE,FILETYPE ;point to filetype in FCB LD HL,TYPNAME ;Point to filetype table CALL COMPARE ;Is it .COM, .SUB or .PRL? RET NZ ;Return if no match if ccp LD DE,CMDFCB ;point to command FCB else ;if not CCP push bc ;save filetype code ld de,filename ;point to filename ld hl,(memaddr) ;get member address ld b,11 ;11 bytes to compare call comp ;have we found the member? pop bc ret nz ;return if not found push bc dec de ;point to drive code jp noprtfile ;.......... ; ;Entry point for locating COMMAND.LBR using CP/M's search chain. ; cmpftype: ld de,lbrfcb or 0ffh ;V 1.03 ld (duspec),a ;set to show is drive/user spec ;V 1.03 endif ;not CCP CALL setdusr ;Set FCB user number if specified LD A,(DE) ;get drive code LD C,A ; into C if ccp PUSH BC ;Save filetype code endif ;not CCP LD C,0 OR A ;Test for default drive jr NZ,NOTDEFDSK ;Jump if drive specified DEC DE ;Point to user code LD A,(DE) ;get user INC DE ;back to drive code OR A ;test user code jr NZ,notdefdsk ;Jump if user specified if ccp LD BC,0E704H ;[B] = DRIVE SEARCH OFFSET-1, (E7H) ;[C] = LENGTH OF TABLE (4 bytes) LD A,(CURDSK) ;Get current drive INC A ;Adjust drive LD H,A ;H = current drive + 1 LD L,1 ;flag to prevent duplicate search on same drive else ;if not CCP ld bc,(searoff) ;get search offset and count ;V 1.03 ld hl,(searflg) ;get flags ;V 1.03 xor a ;V 1.03 ld (duspec),a ;flag no drive/user spec ;V 1.03 endif ;not CCP ;.......... ; ;Loop to inspect drive search chain as specified in offsets E8H to EBH ;in the SCB ; CPRFT1: INC B ;Bump search offset DEC C ;Decrement length left LD A,C ;Length left in A PUSH HL ;save HL CALL P,GETSCB ;Test this drive entry if length left > 0 POP HL ;restore HL OR A ;test for end of table JP M,SRCHEND ;Jump if at end of table jr Z,DEFSPEC ;Jump if default drive CP H ;Is the drive the current disk? jr NZ,NOTCURDSK ;Jump if not current disk DEFSPEC: LD A,H ;Get current drive DEC L ;adjust duplicate search flag JP M,CPRFT1 ;Jump if we already scanned this drive NOTCURDSK: LD (DE),A ;Put drive spec into FCB NOTDEFDSK: PUSH BC ;Save these PUSH HL ; registers if not ccp call checkex ;Check for Exclude d/u CALL nz,OPENFILE ;Attempt to open the file else ;if CCP CALL OPENFILE ;Attempt to open the file endif ;CCP jr NZ,fileok ;Jump if open ok POP HL ;restore these POP BC ; registers DEC DE ;point to user code LD A,(DE) ;get user code INC DE ;point to drive code OR A ;test user code jp NZ,srchend ;jump if user number specified LD A,(usernum) ;get current user number OR A ;is it zero? jr Z,cprft1 ;jump if current user is zero XOR A PUSH BC ;save these PUSH HL ; registers ld (ix+60h),a ;set user number to zero if not ccp call checkex ;Check for exclude d/u CALL nz,OPENFILE ;Attempt to open the file (user 0) else ;if CCP CALL OPENFILE ;Attempt to open the file (user 0) endif ;CCP LD A,(usernum) ;get current user number ld (ix+60h),a ;restore current user number jr NZ,filok1 ;jump if ok POP HL ;restore these POP BC ; registers jr cprft1 ;and loop for next drive ;............ ; ;Here if file open is ok at user 0 ; filok1: DEC DE ;point to user number in FCB LD A,1 ;set it to zero (1-1) LD (DE),A ;Save user number in FCB INC DE ;back to drive code ;........... ; ;Here if file open is ok at current user ; fileok: POP HL ;restore these POP BC ; registers if not ccp ;V 1.03 ld (searoff),bc ;save search offset and length ;V 1.03 ld (searflg),hl ;save search flags ;V 1.03 endif ;not CCP ;V 1.03 DEC DE ;point to user number if ccp ld a,(subflag) ;get submit flag or a jr z,notsubset ;jump if we haven't been here before LD a,(ix+25h) ;A5H = user number for loader ld b,a ld a,(ix+24h) ;get submit user or b ;or in user number ld (ix+24h),a ;save it for submit notsubset: endif ;CCP LD A,(DE) ;get FCB user number if not ccp or 80h ;set library load flag for loader endif ;not CCP ld (ix+25h),a ;Set the user number for loader if ccp XOR A LD (DE),A ;set FCB user number to default endif ; CCP INC DE ;point to drive code if ccp LD a,(ix+34h) and 3 ;Test bits 0,1 of B4H (Display command flag) jr Z,NOPRTFILE ;Jump if no dayfile logging LD A,(DE) ;get FCB drive spec CALL PRTDISK ;print drive code LD A,':' ;print colon CALL CONOUT PUSH DE CALL PRTFNAME ;print the file name POP DE PUSH DE LD HL,8 ADD HL,DE ;point to sys flag LD A,(HL) AND 80H ;isolate sys flag LD DE,USER0MSG ;point to (User 0) msg CALL NZ,PRNSTR ;print this msg if sys file CALL CRLF ;turn up new line POP DE else ;if not CCP ret ;all ok endif ;not CCP NOPRTFILE: POP AF ;get file type code LD HL,TYPADDR ;point to vector table if yesprl cp 2 ;is it PRL? jr nz,notprl set 6,(ix+25h) ;set prl flag for loader notprl: endif ; yesprl ADD A,A ;DOUBLE COMMAND # FOR WORD OFFSET CALL ADDHLA ;form table entry address PUSH DE ;save fcb address LD E,(HL) ;Load command routine address into [DE] INC HL LD D,(HL) EX DE,HL ;routine address in [HL] POP DE ;restore FCB address JP (HL) ;Jump to file type handler ;............. ; ;VALID COMMAND FILE TYPES ; TYPNAME: DEFB 'COM ' DEFB 'SUB ' if yesprl DEFB 'PRL ' endif ; yesprl DEFB 0 ;............... ; ;SUBROUTINE ADDRESS FOR FILE TYPES ; TYPADDR: DEFW LOADGO ;COM handler DEFW SUBMIT ;Submit handler if yesprl DEFW LOADGO ;PRL handler (same as COM) endif ; yesprl ;.............. ; ;HERE IF AT END OF DRIVE SEARCH CHAIN ; SRCHEND: if ccp POP BC ;restore filetype code LD A,C ;get drive spec LD (DE),A ;put drive spec into FCB RET ;and return else ;if not CCP jp errxit ;.............. ; ;Routine to check for Exclude drive/user ; checkex: ld a,(wheel) or a ret nz ;ignore if wheel set ld a,(exdrv) or a ;do we check for excluded d/u? jr nz,checkex1 or 0ffh ;set nz ret checkex1: ld a,(de) ;get drive spec or a ;default? jr nz,fcbdiskok ld a,(disknum) ;get current drive inc a fcbdiskok: ld b,a ld a,(exdrv) cp b ;same as EXDRV? ret nz ld a,(exusr) ;get exclude user cp (ix+60h) ;same as current user? ret ;Z flag properly set endif ;not CCP ;............. ; ;MOVE FILE TYPE INTO FCB ; MOVETYPE: RRCA ;Divide by 2 LD HL,TYPNAME ;point to file type list CALL ADDHLA ;compute entry address LD DE,FILETYPE ;point to filetype in FCB LD C,3 ;3 bytes to move jp MOVEC ;move file type if not ccp ;.......... ; ;Read a library directory sector ; lbrread: ld de,buff ;point to buffer call setdma ;set the dma call setlusr ld c,20 call xbdos ;read a sector or a ret ;........... ; ;Inline print routine ; ilprt: pop hl ld a,(hl) inc hl push hl or a ret z call cono jr ilprt ;........... ; ;Compare two strings , ignore parity bit ; comp: push de push hl inc b comp1: dec b jr z,comp2 ld a,(de) and 7fh ld c,a ld a,(hl) and 7fh cp c inc hl inc de jr z,comp1 comp2: pop hl pop de ret ;.............. ; ;Set up stuff to load the Library member ; setlbr: ld hl,(memaddr) ;get member address ld de,11 add hl,de ;point to member start record ld e,(hl) inc hl ld d,(hl) ld (lbrfcb+34),de ;put it in RR field inc hl ld e,(hl) inc hl ld d,(hl) ;get member length push de ;save on stack ld de,buff call setdma ;set the dma call setlusr ld c,33 call xbdos ;random read first member sector (sets ; up for loader sequential read) or a jp z,lbrreadok call ilprt db 'Error reading COMMAND.LBR',13,10,0 jp errxit lbrreadok: pop hl ;get member length ld (lbrfcb+36),hl ;save it for loader ret endif ;not CCP ;........... ; ;.COM and .PRL command type handler ;SET UP PAGE ZERO AND CALL LOADER ; LOADGO: if not ccp call setlbr ;set up for lbr member read endif ;not CCP LD HL,TPA ;load address if ccp LD (LOADADDR),HL ;Save load address LD HL,(BOFFSET) ;Get BDOS base page in H DEC H ;Less one LD L,0C0H ;HL points to free area in loader RSX PUSH HL ;Save on stack else ;if not CCP ld (lbrfcb+34),hl ;save load address ld d,(ix+19h) ;get bdos base page dec d ;less one ld e,0c0h ;DE points to free area in loader RSX push de ;save on stack ld hl,lbrfcb+1 ;source ld a,(hl) ;get load drive endif ;not CCP if ccp LD A,(DE) ;get load drive endif ;CCP LD (LOADDRV),A ;save load drive if ccp EX DE,HL ;swap for move LD C,35 ;35 bytes to move CALL MOVEC ;Move FCB into loader RSX else ;not CCP ld bc,37 ;37 bytes to move ldir ;move it endif ;not CCP ld hl,msgflag ;point to message flag inc (hl) ;bump it LD HL,(PFCB) ;get command tail pointer DEC HL LD DE,81H ;target of command tail EX DE,HL LD (PFCB),HL ;save new command tail pointer CALL MOVETIL0 ;move command tail into place LD (80H),A ;save command tail length CALL SETDFFCB ;set up default FCB at 5CH LD (PASS1ADR),HL ;Save password 1 address LD A,B LD (PASS1LEN),A ;Save password 1 length LD DE,FCB2 ;Point to FCB2 CALL SETFCB ;Set up FCB2 LD (PASS2ADR),HL ;Save password 2 address LD A,B LD (PASS2LEN),A ;Save password 2 length if ccp LD A,(curdsk) ;get ccp drive else ;if not CCP ld a,(disknum) endif ;not CCP CALL SELDSK ;Select drive if ccp ld a,(disknum) ;get old drive flag or a call p,seldsk ;select old drive if to be kept endif ;CCP LD A,(USERNUM) ;get user number ld (ix+60h),a ;set the user number ADD A,A ;Shift user number over to high nybble ADD A,A ADD A,A ADD A,A or (ix+5AH) ;or in BDOS drive LD (USRDSK),A ;Save at location 4 for previous CP/M compatibility call sdefdma ;set default dma POP DE ;restore FCB address if ccp LD HL,(BOFFSET) ;Get BDOS base page in H else ;if not CCP ld h,(ix+19h) ;get bdos base page endif ;not CCP XOR A LD L,A LD SP,HL ;Set up stack just below the BDOS LD H,A ;HL = 0 PUSH HL ;Push return to 0 at top of stack INC H ;HL = 100H PUSH HL ;Push return address for loader ;goes to loaded program LD (FCBCR),A ;zero the record count if ccp if byechk ld a,(byeact) ;get BYE active flag or a ;is BTE active? jr nz,noqs endif ; byechk if byechk or noxoff ld a,2 ;disable flow control if bye present endif ; byechk or noxoff if byechk jr setcon noqs: XOR A ;enable stop/start scroll setcon: endif ; byechk LD (ix+4FH),a ;Set low byte console mode XOR A LD (ix+10H),a ;Zero offsets 90H - 93H in SCB LD (ix+11H),A LD (ix+12H),A LD (ix+13H),A bit 7,(ix+33H) ;Test chain flag jr NZ,CHAINSET ;Jump if chain flag set if makecolon ; V 1.05 ld a,(ix+2ch) ;get error code lsb ; V 1.05 cp 0feh ;CTL-C error? ; V 1.05 jr nz,CHAINSET ;nope, so nothing gets reset ; V 1.05 ld a,(ix+2dh) ;get error code msb ; V 1.05 inc a ;CTL-C error? ; V 1.05 jr nz,CHAINSET ;nope, so no reset again ; V 1.05 ;yep, we reset ONLY CTL-C generated errors endif ; makecolon ; V 1.05 LD (ix+2cH),a ;Zero program return code LD (ix+2dH),a CHAINSET: res 7,(ix+33h) ;Zero chain flag endif ;CCP LD C,59 ;load overlay function JP bdos ;jump to loader to complete load function if ccp and byechk ; rsxpb: DEFB 4 ;rsx function for bye present test byeact: DEFB 0 ;BYE active flag endif ;CCP and byechk ;............... ; ;OUTPUT CHAR IN [A] ; OUTCHAR: cono: LD E,A ;BDOS likes char in E ; ;OUTPUT CHAR IN [E] ; CO: LD C,2 ;console output function jp xbdos ; ;PRINT STRING AT [DE] ; PRNSTR: LD C,9 ;print string function jp xbdos if ccp ; ;GET LINE OF INPUT FROM CONSOLE ; GETLINE: LD HL,CMDLINE-1 ;point to command line length LD (HL),SIZECMDLINE ;set the command line max length ; V. 1.05 EX DE,HL ;BDOS likes the address in DE LD C,10 ;getline function CALL xbdos LD HL,CMDLINE ;point to length LD A,(HL) ;get length INC HL ;point to command string CALL ADDHLA ;point to end of command string LD (HL),0 ;put terminator at end if ccphistory if ccp call CCPEXT ; first try for CCP extension program call z,HISTORY ; then do internal history mechanism, ; optionally turned off by the CCPEXT endif ; ccp endif ; ccphistory jp CRLF ;and turn up a new line ; ;CHECK FOR CONSOLE INPUT ; STATINP: LD C,11 ;console status function CALL CBDOS RET Z ;return if nothing there LD C,1 ;console input function jp CBDOS endif ;CCP ; ;SET DEFAULT DMA ADDRESS ; SDEFDMA: LD DE,80H ;default DMA address ; ;SET DMA ADDRESS IN [DE] ; SETDMA: LD C,26 ;set DMA function jp xbdos ; ;SELECT DISK IN [A] ; SELDSK: LD E,A ;BDOS likes it in E LD C,14 ;select disk function jp xbdos if not ccp ; ;Point to Library FCB and Set user ; setlusr: ld de,lbrfcb endif ;not CCP ; ;Set FCB user number ; setdusr: ld a,(de) ;get FCB user number inc de ;point to drive code or a ret z ;return if default DEC A ;adjust to true user number ld (ix+60h),a ;set the user number RET ; ;SET UP FCB AND OPEN DISK FILE ; OPENFILE: LD BC,0ff0fh ;B = Error mode to set, C = function if ccp LD DE,FILEDISK ;point to drive code else ;if not CCP ld de,lbrfcb+1 ;point to drive code endif LD HL,32 ADD HL,DE ;point to CR in FCB LD (HL),0 ;zero CR field if not ccp ld hl,12 add hl,de ;point to extent ld (hl),0 inc hl ld (hl),0 inc hl ld (hl),0 endif ;not CCP PUSH BC PUSH DE LD DE,PASSWORD ;point to password field CALL SETDMA ;Set the DMA to password field POP DE POP BC PUSH DE openf2: LD (ix+67H),B ;set the error mode CALL xbdos ;execute the function in C LD (ix+67h),0 ;set error mode to zero INC L ;test for physical error jr NZ,noerr ;jump if not physical error LD A,H ;get physical error code OR A jr Z,noerr ;if zero, not a physical error CP 7 ;invalid password? jr NZ,notpwd ;jump if not invalid password CALL getpass LD BC,15 ;B = 0 (error mode), C = 15 (open file) if ccp LD DE,filedisk ;point to FCB drive code else ;if not CCP ld de,lbrfcb+1 ;point to FCB drive code endif ;not CCP jr openf2 ;and attempt another open with new password ;....... ; ;Here if not a password error. determine physical error and print it ; notpwd: LD DE,iomsg CP 1 jr Z,prtmsg LD DE,drvmsg CP 4 jr Z,prtmsg LD DE,qmsg prtmsg: CALL prnstr ;print error message if ccp jp nocold ;and restart CCP else ;if not CCP rst 0 endif ;.......... ; ;Here if open sucessful ; noerr: DEC L ;test return code from open if ccp LD A,(CURDSK) ;get current drive else ;if not CCP ld a,(disknum) endif ;not CCP PUSH HL ;save return code call seldsk ;select the disk CALL SDEFDMA ;Set the DMA to 80H POP HL ;restore return code INC L ;Set return code flag from open POP DE ;align stack RET if ccp ;.......... ; ;Print BCD number in A ; hexprt: PUSH AF ;save it REPT 4 RRA ;Shift high nibble into place ENDM CALL hexpr1 ;print high nibble POP AF ;restore number hexpr1: AND 0fh ;isolate low nibble ADD A,'0' ;convert to ASCII jp outchar ;and print it. endif ;CCP ;............ ; ;Physical error messages ; pwdmsg: DEFB 'Password: $' iomsg: DEFB 'Disk I/O Error$' drvmsg: DEFB 'Invalid drive$' qmsg: DEFB '"?" in command$' if timeon minmsg: defb ' min.$' endif ; timeon if ccp scomp: PUSH HL PUSH DE LD DE,rootname scomp1: LD A,(DE) CP (HL) jr NZ,scompret CP ' ' jr Z,scompret INC HL INC DE jr scomp1 scompret: POP DE POP HL RET rootget: PUSH HL PUSH DE LD HL,rootname LD DE,rootname+1 LD c,17 LD (HL),' ' CALL movec POP DE LD HL,rootname LD b,8 rootnmove: LD A,(DE) OR a jr Z,rgetdone INC DE CP ';' jr Z,getp LD (HL),a INC HL djnz rootnmove LD A,(DE) INC DE CP ';' jr Z,getp XOR a jr rgetdone getp: LD HL,rootpass LD b,8 rootpmove: LD A,(DE) INC DE OR a jr Z,rgetdu LD (HL),a INC HL djnz rootpmove LD A,(DE) INC DE OR a jr Z,rgetdu XOR a jr rgetdone rgetdu: LD A,(DE) INC DE LD b,a LD HL,rootdrv AND 0fh LD (HL),a INC HL LD a,b AND 0f0h RRA RRA RRA RRA LD (HL),a INC a rgetdone: POP HL RET endif ;CCp getpass: LD DE,pwdmsg ;point to password message CALL prnstr ;print "Password:" LD B,8 ;password is 8 bytes max LD HL,password ;point to password field pwdlop: PUSH HL PUSH BC LD E,0fdh ;get console input without echo LD C,6 CALL xbdos POP BC POP HL CALL ucase ;convert to upper case CP 13 ;is it CR? jr Z,pwdon ;jump if done LD (HL),A ;save password char INC HL djnz pwdlop ;and loop for more password chars jr pwdon1 pwdon: LD (HL),' ' ;blank out the rest of the password field INC HL djnz pwdon pwdon1: CALL crlf ;turn up new line RET if ccp chkpass: LD A,(wheel) INC a RET Z LD A,(rootpass) CP ' ' jr Z,norootp LD HL,rootdrv LD A,(maxdrv) DEC a CP (HL) jr C,needpass LD A,(maxusr) DEC a INC HL CP (HL) RET NC needpass: LD A,(password) CP ' ' CALL Z,getpass LD HL,rootpass LD DE,password LD b,8 rpasslop: LD A,(DE) CP (HL) jr NZ,badpass CP ' ' jr Z,norootp INC DE INC HL djnz rpasslop norootp: if expand LD HL,rootdrv LD A,(maxdrv) CP (HL) jr NC,testusr LD a,(HL) LD (maxdrv),A testusr: INC HL LD A,(maxusr) DEC a CP (HL) RET NC LD a,(HL) INC a LD (maxusr),A endif RET badpass: POP HL LD DE,badpmsg JP prnstr badpmsg: DEFB 'Password Error',13,10,'$' endif ;CCP ;............ ; ;CALL BDOS and return with Z flag status of function ; CBDOS: CALL xbdos ;Do the function OR A ;Set/clear the Z flag RET ;................ ; ;SCAN THE COMMAND LINE ; SCANLINE: if ccp CALL CRFLGA ;Clear bits 7 & 5 if offset B4 of SCB endif ;CCP LD HL,CMDLINE+1 ;Point to command line start CALL SIPBLNK ;Skip over initial blanks CP ';' ;Is it a comment line? RET Z ;Ignore comment lines if ccp CP '!' ;Command delimiter? jr Z,DELIM ;Jump if command delimiter CP ':' ;Conditional Execution (begins with colon)? jr NZ,NOCOLON ;Jump if not a colon if makecolon ; needs to be non-destructive ;If the error code is ff00-fffd or ffff ;the command is "punted" -mdk ld a,(ix+2cH) ;Test program return code for non-zero INC a INC a jr Z,DELIM ;If low byte is zero, then jump ld a,(ix+2dH) ;Test high byte for 0FFH INC a RET Z ;Return if we are not to execute this endif ; makecolon if not makecolon INC (ix+2cH) ;Test program return code for non-zero INC (ix+2cH) jr Z,DELIM ;If low byte is zero, then jump INC (ix+2dH) ;Test high byte for 0FFH RET Z ;Return if we are not to execute this ;command because of return code endif ; not makecolon DELIM: INC hl ;skip over delimiter NOCOLON: endif ;CCP LD (PFCB),HL ;Save address of command ;.......... ; ;Loop to convert to upper case and check for second command ; NEXTCHAR: LD A,(HL) ;get char CALL ucase ;convert to upper case LD (HL),A ;put it back if ccp CP '!' ;Is it command delimiter? CALL Z,CHKEXCM ;save 2nd command if present endif ;CCP INC HL ;bump pointer OR A ;End of command line? jr NZ,NEXTCHAR ;loop for more ;............. ; ;Skip over initial blanks ; SKIPBLA: LD HL,(PFCB) ;Get command address SIPBLNK: LD (PFCB),HL ;Save new command address LD (NXTNMA),HL ;and Next command address LD A,(HL) ;Get char OR A ;End of command line? RET Z ;return if done CP ' ' ;Is it a blank? jr Z,SKPBLNK CP 9 ;Test for tab char too. RET NZ SKPBLNK: INC HL ;Bump pointer jr SIPBLNK ;And loop for more if ccp ;................ ; ;Save 2nd command in line by creating a dummy RSX of one page ;to protect the 2nd command after exclamation point ; CHKEXCM: LD E,L LD D,H ;DE = HL INC DE ;DE points to next char after exclamation LD A,(DE) ;Get it CP '!' ;Is it another exclamation? PUSH AF ;save flags PUSH HL ;and char pointer CALL Z,MOVETIL0 ;move command line down one notch to kill ;2nd exclamation immediately after exclamation POP HL ;restore char pointer POP AF ;and flags RET Z ;ignore double exclamations LD (HL),0 ;replace exclamation with null EX DE,HL ;char pointer in DE LD HL,(BDOS+1) ;get top of TPA DEC H ;Reserve 1 page for 2nd command LD L,1ah ;2nd command begins at offset 1bH in RSX;V1.03a PUSH HL ;save start of 2nd command addr ;............... ; ;MOVE 2ND COMMAND LINE INTO PROTECTED PAGE ; MOV2ND: INC HL ;Bump these INC DE ; pointers LD A,(DE) ;get source char LD (HL),A ;put in dest CP '!' ;Test for exclamation Jr NZ,NOTEXCM ;Jump if not exclamation LD (HL),0DH ;Replace all exclamations with CR NOTEXCM: OR A ;End of command? Jr NZ,MOV2ND ;loop for more LD (HL),0DH ;Put a CR at end of command INC HL LD (HL),A ;And a null after the CR LD L,6 LD (HL),0C3H ;Put a JMP inst at offset 6 in RSX INC HL LD (HL),9 ;Target of JMP is offset 9 ;(Next in RSX header) INC HL LD (HL),H ;Complete JMP inst INC HL LD (HL),0C3H ;Put a JMP at location 9 in RSX LD L,0EH ;point to remove flag LD (HL),A ;clear remove flag ld l,10h ;where name goes ;1.03a ld de,next_cmnd ;point to RSX name ;1.03a EX DE,HL ;Setrsx likes it in DE ld bc,8 ;length ;1.03a ldir ;move it into place ;1.03a LD E,A ;point to base of RSX CALL SETRSX ;Set up this RSX POP DE ;recover address of command line ld e,19h ;point to address of next command line ;1.03a ld a,(ix+31h) ;1.03a ld (de),a ;1.03a inc de ;1.03a ld a,(ix+32h) ;1.03a ld (de),a ;save next 2nd command line addr ;1.03a inc de ;start of 2nd command ;1.03a LD (ix+31H),E ;Save command address for next time ;CCP is executed LD (ix+32H),D LD (ix+2eH),D ;Save the base page XOR A ;flag no errors RET next_cmnd: db 'NEXTCMND' ;RSX name for next command ;1.03a endif ;CCP ;................... ; ;CONVERT TO UPPER CASE ; UCASE: AND 7fh CP 61H RET C CP 7BH RET NC SUB ' ' ;Convert to upper case RET if ccp ;...................... ; ;CHECK FOR SECOND COMMAND LINE ; CHK2ND: LD DE,0BAB1H CALL MOVSCB ;Move offsets BA,BB to B1,B2 in SCB OR A ;Is address in offset BB valid? LD DE,0BCB1H CALL Z,MOVSCB ;Move offsets BC,BD to B1,B2 if prev invalid CALL STATINP ;test for console break jr NZ,NO2ND ;Jump if console break ; ;GET ADDRESS AT B1,B2 INTO [DE] (2ND COMMAND LINE) ; LD D,(ix+32H) INC d ;Is address valid? DEC d Jr Z,NO2ND ;Jump if no valid address (no 2nd command) LD E,(ix+31H) LD A,(DE) ;Get first char from 2nd command OR A ;test for null RET NZ ;return if something there NO2ND: ;Here if no 2nd command LD H,(ix+2eh) ;get base page LD L,0EH ;point to remove flag DEC (HL) ;set remove flag for removal ld l,19h ;point to addr of next 2nd command ;1.03a ld a,(hl) ;1.03a ld (ix+31h),a ;1.03a inc hl ;1.03a ld a,(hl) ;1.03a ld (ix+32h),a ;save next 2nd command ;1.03a ld (ix+2eh),a ;save base page of next 2nd command ;1.03a JP CHKRSX ;and remove the dummy RSX endif ;CCP ;.................. ; ;SET UP DEFAULT FCB ; SETDFFCB: LD DE,FCB ; ;SET UP FCB AT [DE] ; SETFCB: CALL SKIPBLA ;Go over leading blanks and tabs PUSH AF ;save flags CALL PARSEFCB ;Parse the item into FCB POP AF ;restore flags RET ; ;PARSE THE COMMAND LINE INTO FCB ; PARSEFCB: LD (PFCB),HL ;Save item pointer LD (NXTNMA),HL ;and next item pointer PUSH DE ;save DE LD DE,PFCB ;point to parse file control block LD C,152 ;parse FCB function CALL xbdos ;parse the FCB POP DE ;restore DE LD A,H ;Test for zero return OR L LD B,(HL) ;get next char after parse into B INC HL ;go over delimiter or trailing blank Jr NZ,NOTPEND ;Jump if not end of command line LD HL,NULCMD ;Point to null command NOTPEND: LD A,H ;Test for error return (0FFFFH) OR L Jr NZ,NOPERR ;Jump if no error LD HL,NULCMD ;Point to null command CALL ERRXIT ;and process error NOPERR: LD A,B ;get next char CP '.' ;is it dot (.)? Jr NZ,NOPDOT ;Jump if not dot DEC HL ;Adjust if dot NOPDOT: LD (PFCB),HL ;Save new item pointer LD C,16 ;16 bytes to move LD HL,PRSEFCB ;source PUSH DE ;save dest CALL MOVEC ;Move first 16 bytes into place LD DE,PASSWORD ;point to password field LD C,10 ;10 bytes to move CALL MOVEC ;move the password into place POP DE ;restore DE LD A,(HL) ;get password length (PRSEFCB+26) LD HL,0 ;init HL NULCMD EQU $-1 OR A ;test for no password LD B,A ;password length in B Jr Z,NOPASS ;Jump if no password LD HL,(NXTNMA) ;get next item pointer FINDSEMI: LD A,(HL) ;get first char CP ';' ;is it password delimiter? INC HL ;bump pointer Jr NZ,FINDSEMI ;loop until ";" found NOPASS: RET ;............... ; ;CHECK FOR DRIVE SPEC IN COMMAND LINE ; CHKDRV: PUSH DE ;save DE XOR A ;Just a zero LD (DE),A ;clear to default user INC DE LD (DE),A ;clear to default drive INC DE ;point to file name CALL SKIPBLA ;skip over leading blanks and tabs LD HL,(PFCB) ;get item address POP DE ;restore DE PUSH DE LD B,4 ;Colon (:) must be found with first 4 bytes FNDCOLON: LD A,(HL) ;Get char CP ':' ;Is it colon? Jr Z,COLONFND ;Jump if colon OR A ;test for end of command line Jr Z,ENDCOLON ;jump if at end CP ' ' ;is it a blank ? Jr Z,endcolon CP 9 ;is it a tab ? Jr Z,endcolon INC HL ;adjust pointer djNZ FNDCOLON ;loop for more ENDCOLON: ;Here if colon not found within first 4 bytes POP DE ;restore DE XOR A ;Just a zero LD (DE),A ;flag no user spec inc DE ;point to drive code ; V1.02B ld (DE),A ;flag no drive spec ; V1.02B dec DE ;point to user code ; V1.02B LD HL,(PFCB) ;get item pointer PASTCOLON: INC DE ;point to drive code LD A,(DE) ;get it PUSH AF ;save on stack CALL PARSEFCB ;parse first item into FCB POP AF ;restore drive spec LD (DE),A ;and restore it. RET COLONFND: ;Here if possible drive/user spec in command line LD HL,(PFCB) ;get item pointer LD A,(HL) ;get the char NUMCHECK: CP '0' ;Numeric range check Jr C,NOTNUM CP ':' ;Numeric range check Jr NC,NOTNUM CALL CVDEC ;convert to User number in binary POP DE ;restore DE PUSH DE LD A,(DE) ;get old user number OR A ;is there one already? Jr NZ,ENDCOLON ;invalid if user number specified twice LD A,B ;get the user number INC A ;adjust LD (DE),A ;Save the user number spec Jr CKDRV1 ;and go and check drive spec ;....... ; ;check for possible drive spec ; NOTNUM: CP 'A' ;Drive range check Jr C,ENDCOLON CP 'Q' ;Drive range check Jr NC,ENDCOLON POP DE ;restore DE PUSH DE INC DE ;point to drive spec LD A,(DE) ;get drive spec OR A ;test for drive spec Jr NZ,ENDCOLON ;jump if this is second drive spec LD A,(HL) ;Get new drive char SUB 40H ;adjust LD (DE),A ;Save drive spec INC HL ;go over drive char CKDRV1: LD A,(HL) ;get next char CP ':' ;Is it a colon? Jr NZ,NUMCHECK ;Loop until colon found INC HL ;go over colon POP DE ;restore DE if ccp call CHKDU ;check the drive/user ; V1.02B endif ;CCP Jr PASTCOLON ;And continue with rest of command line if ccp CHKDU: LD A,(wheel) ;get wheel byte ; V1.02B inc a ;is it set? ; V1.02B ret Z ;yep, then no DU: check ; V1.02B ex de,hl ;point to command user ; V1.02B LD A,(maxusr) ;get max user # allowed ; V1.02B CP (HL) ;within range? ; V1.02B jr C,invalid ;return with CARRY set if not ; V1.02B INC HL ;point to command drive ; V1.02B LD A,(maxdrv) ;get max drive ; V1.02B INC a ;adjust ; V1.02B CP (HL) ;within range? ; V1.02B dec hl ; V1.02B ex de,hl ; V1.02B ret NC ;ret with CARRY in proper state ; V1.02B invalid: LD DE,baddu ;point to Invalid drive/user msg call prnstr ;print msg jp ccpret baddu: DEFB 'Invalid Drive/User',13,10,'$' ;................. ; ;MOVE 2 BYTES OF SCB FROM [D] TO [E] ; MOVSCB: LD HL,(SCBBASE) ;get SCB address LD L,D ;set source offset LD D,H ;set dest offset LD C,2 ;2 bytes to move endif ;CCP ;................ ; ;MOVE [HL] TO [DE] FOR LENGTH IN [C] ; MOVEC: push bc ld b,0 ldir pop bc dec hl ld a,(hl) inc hl ret ;.................... ; ;MOVE [DE] TO [HL] UNTIL NULL ; MOVETIL0: LD C,0 ;Set move terminator MOVE1: LD A,(DE) LD (HL),A OR A LD A,C ;Return length of move in A RET Z ;Return if at end INC HL INC DE INC BC jr MOVE1 if ccp ;................ ; ;SET BITS 7,5 IN OFFSET 0B4H in SCB ; SETFLG: set 7,(ix+34h) set 5,(ix+34h) ret ;............... ; ;CLEAR BITS 7,5 IN OFFSET 0B4H ; CRFLGA: res 7,(ix+34h) res 5,(ix+34h) ret endif ;CCP ;.............. ; ;GET SCB BYTE AT OFFset IN [B] ; GETSCB: LD HL,(SCBBASE) ;get SCB pointer LD L,B ;set the offset LD A,(HL) ;get the byte RET ;.............. ; ;PRINT CR,LF ; CRLF: LD A,0DH CALL CONOUT LD A,0AH jp CONOUT if ccp ;............ ; ;Call RSX ; rsx: ld c,60 jp xbdos ;............... ; ;PRINT NUMBER IN [A] ; PRTNUM: ld h,0 ld l,a decout: push hl push de push bc push af ld bc,-10 ld de,-1 decou1: add hl,bc inc de jr c,decou1 sbc hl,bc ex de,hl ld a,h or l call nz,decout ld a,e add a,'0' call cono pop af pop bc pop de pop hl ret else ;if not CCP xbdos: push ix call bdos pop ix ret endif ;not CCP ;................ ; ;PRINT STRING AT [HL] TERMINATED BY NULL OR CHAR IN [C] ; PRTNAME: LD A,(HL) ;get char OR A ;is it null? RET Z CP C ;is it same as char in C? RET Z CALL CONOUT ;print it INC HL ;bump pointer jr PRTNAME ;and loop ;............. ; ;TEST FOR BLANKS AND ABORT IF BLANKS PRESENT ; CHKBLANK: CALL SKIPBLA ;skip over blanks RET Z ;return if non-blank found ;............... ; ;ERROR EXIT SUBROUTINE ; ERRXIT: if not ccp ccpret: endif ;not CCP LD HL,msgflag ;point to error count dec (hl) ;is it zero? inc (hl) LD (HL),0 ;reset it to zero RET NZ ;return if non-zero LD HL,(nxtnma) ;get command address LD C,' ' ;print until blank or null CALL prtname ;print the first item in command line LD DE,notfnm ;point to "command not found" message CALL prnstr ;print command not found if ccp jp NOCOLD ;and restart the CCP else ;if not CCP rst 0 endif ;not CCP notfnm: DEFB ' command not found.$' ;............... ; ;CONVERT ITEM IN COMMAND LINE TO BINARY ; CVNUM: CALL SKIPBLA ;skip over blanks LD HL,(PFCB) ;get item pointer LD (NXTNMA),HL ;save it RET Z ;return if nothing there LD A,(HL) ;get first char CP '0' ;numeric range check jr C,ERRXIT CP ':' ;numeric range check jr NC,ERRXIT CALL CVDEC ;convert to binary LD (PFCB),HL ;save new item pointer OR 1 ;set NZ return LD A,B ;return number in A RET ;............... ; ;CONVERT ITEM TO BINARY NUMBER ; CVDEC: LD B,0 ;start with 0 CVDECLP: LD A,(HL) ;get char SUB '0' ;convert from ASCII to binary RET C ;return if out of range CP 10 ;numeric range check RET NC ;return if out of range PUSH AF ;save it LD A,B ;prepare to multiply B * 10 ADD A,A ;*2 ADD A,A ;*4 ADD A,B ;*5 ADD A,A ;*10 LD B,A POP AF ;restore number INC HL ;bump pointer ADD A,B ;add in current digit LD B,A CP 16 ;must be less than 16 jr C,CVDECLP ;loop if ok. jr ERRXIT ;otherwise an error if ccp ;................. ; ;PRINT FILENAME IN FCB POINTED TO BY [DE] ; PRTFNAME: INC DE ;point to filename LD H,8 ;filename is 8 bytes CALL PRTDESTR ;print the filename CALL PRTBLANK ;print a blank LD H,3 ;filetype is 3 bytes ;............... ; ;PRINT STRING AT [DE] FOR LENGTH OF [H] BYTES ; PRTDESTR: LD A,(DE) ;get a char AND 7FH ;strip parity CALL CONOUT ;print it INC DE ;bump pointer DEC H ;adjust count jr NZ,PRTDESTR ;loop for more RET ;............. ; ;PRINT A BLANK ; PRTBLANK: LD A,' ' endif ;CCP ;............. ; ;CONSOLE OUTPUT WITH REGISTERS SAVED ; CONOUT: PUSH BC PUSH DE PUSH HL CALL CONO POP HL POP DE POP BC RET ;.................. ; ;[HL] = [HL] + [A] ; ADDHLA: ADD A,L LD L,A RET NC INC H RET ;................ ; ;COMPARE STRINGS [DE] TO [HL] ; COMPARE: LD BC,0FFH ;B = 0 , C = -1 CMPARE1: PUSH DE ;Save the PUSH HL ; pointers CMPRLOOP: LD A,(DE) ;get a byte AND 7FH ;strip parity CP 21h ;is it non-blank and graphic? jr C,COPARE2 ;jump if blank or non-graphic CP (HL) ;compare with target char jr NZ,NOMATCH ;jump if no match COPARE2: INC DE ;bump source pointer INC C ;bump counter LD A,' ' CP (HL) ;at end of target string (terminated by blank)? INC HL ;bump target pointer jr NZ,CMPRLOOP ;jump if more to compare POP HL ;restore these POP DE ; pointers CALL MOVEC ;move target string to source.. match found LD A,B ;A = string number RET NOMATCH: ;Here if no match found LD A,' ' COMARE4: ;Find end of target string CP (HL) ;are we at end? INC HL ;bump pointer jr NZ,COMARE4 POP DE ;align stack POP DE ;recover DE INC B ;bump string number LD C,0FFH ;init length LD A,(HL) ;get first char of next string SUB 1 ;end of list? jr NC,CMPARE1 ;jump if more strings to compare RET if ccphistory ; ; >>>>>>-- COMMAND LINE HISTORY PROCESSING FOR CP/M PLUS --<<<<<< ; ; (C) Copyright 1986 by Michael D. Kersenbrock, 18625 S.W. Hennig ; Court, Aloha, Oregon 97006 All rights Reserved. ; ; Personal non-commercial use and distribution of this software ; is permitted so long as the above Copyright notice is maintained ; with this and subsequent copies. ; ; History (no pun intended, but noted): ; ; Version 1.0 - September 1986 Original release ; ; ; This was written first in psuedo HLL code, then hand coded into assembly ; language. That psuedo-HLL code is included below as comment lines. ; ;Note: No matter how efficiently written, this isn't really practical without ; a ramdisk or a fast hard disk. No strong effort is done to minimize ; the file size (and thus disk speed) because it isn't likely to ; acceptably fast with a floppy (regardless). I use a FAST 720K ramdisk. ; Actually, I have tried it with my floppy, and it isn't too bad at all ; but then, the floppy IS cache'd. I did my own cacheing over and above ; CP/M 3.0's (didn't like theirs), so I don't know how it works with ; DRI's version of cache. I have 178K of floppy-file cacheing. ; ; This history implements "!!", "!pattern", "!number" for command ; substitution, and implements the command 'h' to give a list of ; previous commands and their numbers. ; ; These examples use '!' as the history command character, this is ; the same as Berkeley-UNIX's (tm of AT&T) CSH shell. This CP/M ; implementation uses '|' interchangeably. The functions implemented ; are: ; ; !! Repeat last command, similar to ^W ; ; ! Repeat last command that starts with ; the given pattern. ; ; ! Repeat command numbered ; ; EACH OF THE ABOVE THREE: append the rest of ; "this line" to the substituted line. Example: ; ; If command #40 were: "COMPILE -O -C", then ; "!40 ROUTINE.C" would result in: ; "COMPILE -O -C ROUTINE.C" ; ; h Command that gives numbered command history ; list to be used with the above command. ; ; When a history-substitution is made for a command, the new ; command line is presented to the console for editing in a ; similar fashion to the banked-^W command (unlike csh). ; ; With the substitutions, the rest of the calling command line ; (if any) is added onto the substitution-replacement line. ; ; If you don't want submit files to store their internal-commands ; into the history record, put a space in front of those commands. ; ; If the file ": CCP.EXT" exists, then that program is ; loaded into memory at address 6000H, then executed with HBUFFER ; and CMDLINE address-pointers passed on the stack "above" the ; return address. CMDLINE's pointer is "just" above the return address. ; ; ; Data structure "buffer" has 42 CMDSIZE-byte records numbered 0-41. ; ; defns: when file is read in, ; record 1: contains the last command number ; record 2: contains the last command ; then... ; record 0: is where last command nr is moved to ; record 1: is where "translated" current command ; is built. ; ; ;History file format: ; ; One command line per RECSIZE byte logical record. ; ; First sector contains the current command number (1-byte) ; ; Second sector contains the last command ; Third sector contains the command before last ; (etc.) ; ; If the first byte of a sector is a null, we have ; "reached the end" of the history (null-commands are ; not stored). ; ; The file saves the last 40 command lines. ; ; A "command-line" has the first byte being the byte count, ; and a null-terminator just after the last "real" byte. ; ; If a substituted command line is modified by the line ; editor (when given the opportunity), then this new changed ; version will be put into the history along with the one ; "fetched" from history. ; ; Pattern: String of non-space and non-control characters ; ; ; ; This history routine is called with a newly gotten command in the ; CMDLINE buffer. This routine will play games with the buffer (possibly ; modifying its contents), then return. ; HBUFFER EQU 2000H ; Put buffer past CCP/STACK ADRCCPEXT EQU 6000H ; Give buffer 16K of room NRCMDS EQU 40 ; Number of commands in history NRRECS EQU NRCMDS + 2 ; Number of records in history buffer RECSIZE EQU SIZECMDLINE + 4 ; Size of each record in history buffer HBUFFSIZE EQU NRRECS * RECSIZE ; The buffer's size NRSECTORS EQU (HBUFFSIZE/128)+1 ; sector count of file HIST1 EQU '!' ; Unix csh compatible history char HIST2 EQU '|' ; Alternate easier to hit RCORD0 EQU HBUFFER ; Address of record-0 RCORD1 EQU HBUFFER+RECSIZE ; Address of record-1 RCORD2 EQU HBUFFER+2*RECSIZE ; Address of record-2 HISTORY: ; if (Command length == 0 || cmd starts w/' ' or ':') { ld a,(CMDLINE) ; get command's length or a ; zero length? ; return(); ret z ; yep, punt ld a,(CMDLINE + 1); cp ' ' ; space? ret z cp ':' ret z ; } ; buffer is cleared to nulls ld de,HBUFFER ; Point to history buffer ld bc,HBUFFSIZE ; Indicate size call CLRBUF ; Clear it to zeros ; Check to see if "temp:Historyx.dat" exists ; ; if (exists) { ; readfile into data buffer starting at record-1 point ; } ; call GETHIST ; load history buffer ; read command number from record-1, and write it to record-0 ld a,(RCORD1) ; fetch the last command's number ld (RCORD0),a ; put it into place at record-0 ; reset substitution and error flags; xor a ; get a zero ld (FLAGSUB),a ; reset substitution-happened flag ld (HERROR),a ; reset error flag ; if (first-char == '!') { ld hl,CMDLINE+1 ; point to first character ld a,(HL) ; get that character call ISHISTCHAR ; one of the history-triggering characters? jp nz,HST1 ; nope, go... ; if (2nd char == '!') { inc hl ; point to second character ld a,(HL) ; get it call ISHISTCHAR ; is it a history-triggering character? jr nz,HST2 ; nope, go... ; copy line at record-2 to record-1; ld hl,RCORD2 ; put record-2's address into source register ld de,RCORD1 ; put record-1's address into dest register ld bc,RECSIZE ; load size of a record ldir ; do the copy ; copy rest of cmdline onto end of the record-1 line; ld hl,CMDLINE+3 ; point to rest of command line ld de,RCORD1 ; point at line to put it at call CMDCAT ; concatinate the command lines ; set substitution flag; ld a,1 ld (FLAGSUB),a ; set substitution-happened flag jp HST3 ; } ; else if (rest up to a terminator is numeric) { HST2: call ISNUMERIC ; numeric? jp nc,HST4 ; nope HST21: inc hl ; yep, so it MIGHT be a numeric substitution ld a,(hl) ; get next character call ISNUMERIC ; numeric? jr c,HST21 ; yep, look at next character cp ' '+1 ; a "proper" terminator? jp nc,HST4 ; nope ; yep ; translate number to binary; push hl ; save pointer to "rest-of-command-line". call ATOI ; value is now in DE, rest of cmd is at (HL) ; if ( command number wanted is NOT in our list ) { ld a,(RCORD0) ; get command number for entry at record-2 ld d,a ld a,e sub d ; calculate difference reqnr - cmdnr dec a ; correct boundary condition and 63 ; make modulo-64 loop-around HST7: cp 64-NRCMDS ; range within history database size? jr c,HST5 ; nope, go do error dance ld d,a ld a,65 sub d ; calculate record number for our data call RECADDR ; calculate address of that record into HL ld a,(hl) ; get count of that record or a ; set flags, is this an active record? jr nz,HST6 ; yes, so number is effectively valid ; no HST5: pop hl ; clean stack ; clear cmd line ld hl,0 ; get a double-zero ld (CMDLINE),hl ; zero command line count, and nul terminate it ; print "not found" ld hl,HERR1 ; point to error message ld c,0 ; indicate null-termination call PRTNAME call CRLF ; set errorflag; ld a,1 ld (HERROR),a ; break out from first level 'if' jp HST8 ; } ; else { HST6: ; copy record[(cmdnr-number+1)] to record-1; ; ; we enter with the substitution record already pointed to by HL ; ld de,RCORD1 ; load destination address ld bc,RECSIZE ; load size of record ldir ; do the copy ; copy rest of cmdline onto end of the record-1 line; pop hl ; get back pointer to rest-of-command-line ld de,RCORD1 ; point at line to put it at call CMDCAT ; concatinate the command lines ; set substitution flag; ld a,1 ld (FLAGSUB),a ; } jp HST3 ; } ; else { HST4: ; search (bottom-up) for a string match (no white space) ld b,1 ; initialize record counter HST44: inc b ; point to next record ld a,b ; get record number cp NRRECS ; already checked "last" one? jr nc,HST10 ; yep, none matched call RECADDR ; get pointer to next record to check inc hl ; point to first character in string push hl ; save database string pointer ex de,hl ; put record pointer into DE ld hl,CMDLINE+2 ; point at first character after !/| call CMPSTRG ; string match? pop de ; get database string pointer back jr nc,HST44 ; nope, try next one ; yep, we found it ; if (found) { ; copy that line to record-1; ; ; We enter with the substitution record already pointed to by DE, ; and the "rest of the commandline" pointed to by HL. ; push hl ; save "rest of commandline" ex de,hl ; put found matching-line-pointer into src pntr dec hl ; point back to byte count part of record ld de,RCORD1 ; load destination address ld bc,RECSIZE ; load size of record ldir ; do the copy ; copy rest of cmd line onto end of record-1 line pop hl ; get pointer to "rest of commandline" ld de,RCORD1 ; point to the line we just fetched above call CMDCAT ; concatinate the lines ; set substitution flag; ld a,1 ld (FLAGSUB),a jp HST11 ; } ; else { HST10: ; clear cmd line ; print "not found" ; set errorflag; ; break out from first level 'if' jp HST5 ; does same as needed here, so we'll save a byte or two ; } HST11: ; } HST3: ; copy record-1 to cmdline; ld hl,RCORD1 ; load source pointer ld de,CMDLINE ; load destination ld bc,SIZECMDLINE ; max size ldir ; do the copying jp HST8 ; ; } ; else if (1st char == 'h' && 2rd char == terminator) { HST1: ld hl,CMDLINE+1 ; point to first character ld a,(hl) ; get it cp 'h' ; an 'h'? jp nz,HST9 ; nope inc hl ; point to second character ld a,(hl) ; get that one also cp ' '+1 ; a terminator? jp nc,HST9 ; nope, so go handle "regular" command ; reset substitution flag, and set err flag xor a ; get a zero ld (FLAGSUB),a ; reset substitution flag inc a ; get nonzero ld (HERROR),a ; set error flag ; print cmd lines w/numbers to screen call CRLF ; start on fresh line ld a,(RCORD0) ; get cmd number of record at record-2 sub NRCMDS-1 ; calculate number of last record and 63 ; modulo 64 ld b,a ; put into record counter location dec b ; pre-decrement for proper start ld c,NRRECS ; load record counter HST111: ld a,b ; get command number inc a ; increment to next command number and 63 ; do modulo 64 ld b,a ; put counter back dec c ; count to next record number ld a,c ; get it cp 2 ; Done with all of them? jp c,HST8 ; yep call RECADDR ; nope, so go get pointer to record ld a,(hl) ; get byte count of that record or a ; a null-line? jr z,HST111 ; yes, don't display those inc hl ; no, so point to the line's data push bc ; save counters push hl ; save that data pointer for a second ld a,b ; get command number cp 10 ; single digit? call c,PRTBLANK ; yes, align display columns ld a,b ; get command number call PRTNUM ; print it call PRTBLANK ; print a space call PRTBLANK ; print a space pop hl ; get data pointer to historical cmd line ld c,0 ; indicate null-termination call PRTNAME ; print the string call CRLF ; and complete the line pop bc ; get our counters back jp HST111 ; do next command line in history ; } ; else { HST9: ; copy cmdline to record-1 ld hl,CMDLINE ld de,RCORD1 ld bc,RECSIZE ldir ; } HST8: ; if (not ERRORFLAG) { ld a,(HERROR) ;get error flag or a ;errors? jr nz,HST13 ;yep, so don't change the history database ; increment command number at 0 ; ld a,(RCORD0) ;get the command number inc a ;increment it and 63 ;modulo 64 ld (RCORD0),a ;put it back ; if (first-char-of-cmd is printable, and not ' ' or ':') { ld a,(RCORD1+1) ; get first byte of new command string cp ' '+1 ; ctl char or space? jr c,HST88 ; yep, so don't save line in history cp ':' ; colon? jr z,HST88 ; yep, so don't save line in history ; write buffer starting at record0 (bumps last one out) call PUTHIST ;save history back to file in ramdisk ; } HST88: jr HST99 ; } ; else { ; reset command line; HST13: ld hl,0 ; get a zero ld (CMDLINE),hl ; reset command line jr hst14 ; } HST99: ; ; if (substitution flag set) { ld a,(FLAGSUB) ;get substitution flag or a ;was the command line modified? jr z,HST14 ;nope, so just process normally ;yes ; calculate checksum of cmdline; ld hl,CMDLINE-1 ; point to full command line buffer call CMDSUM ; calculate it's checksum ld (HCMDSUM),de ; save it ; set DMA address to cmdline; ld de,CMDLINE-1 ; put buffer's address into DE call SETDMA ; set the dma address ; set DE to zero and call function 10 (edit substitution line); call CRLF call prompt ; print a prompt ld de,0 ; indicate that the buffer is loaded ld c,10 ; function number 10 call xbdos ; allow line be be edited call SDEFDMA ; put Dma back to default value ld hl,CMDLINE ; point to new command line ld a,(hl) ; fetch count inc hl ; point to first char call addhla ; calculate where just-past-end-is xor a ; get a zero ld (hl),a ; terminate string ; if (new checksum != old checksum) { ld hl,CMDLINE-1 ;point to command line buffer again call CMDSUM ;calulate checksum again ld hl,(HCMDSUM) ;get previous checksum or a ;reset carry sbc hl,de ;checksum the same (no change by user)? ; go through self again; jp nz,HISTORY ;do again if it was changed ;incase it was modified for substitution ;again (silly operator). Also we will put ;this new version into the history. ; } HST15: ; } HST14: ; ; command line now contains command line, ready for "normal" processing. ret ; ; Clear buffer pointed to by DE that is of size BC ; CLRBUF: push hl ; save whatever ld l,e ; load hl with ld h,d ; de ld (hl),0 ; load first location in block inc de ; point the "to" pointer at second location dec bc ; count the one we did "manually" ldir ; block move the rest pop hl ; get whatever back ret ; all pau ; ; Calculate and return address of record number in 'a' ; Return value in HL ; RECADDR: push bc ; save whatever ld hl,0 ; zero accumulator ld bc,RECSIZE ; load size of ONE record CALCADR: sub 1 ; set carry (borrow) flag jr c,RECEXIT ; calculated offset? add hl,bc ; nope, add in another record size jr CALCADR ; test it again RECEXIT: ld bc,HBUFFER ; load start address of the buffer itself add hl,bc ; add in the calculated offset pop bc ; restore whatever ret ; ; Opens History file and loads buffer at record-1. Hbuffer is assumed ; to be already cleared upon entry. ; GETHIST: call OPENHIST ; open history file jr nz,CLOSEHIST ; close if only now created ld e,NRSECTORS ; Get size of file (16K max) ld c,2ch ; get bdos nr for setting multi-sectors call xbdos ; set that many sectors ld de,RCORD1 ; get record-1's address into DE call SETDMA ; set the dma address call GETBLK ; read that many sectors all at once jr CLOSEHIST ; close file GETBLK: ld de,HFCB ; point DE at history's FCB ld c,14h ; get bdos number for read sequential call xbdos ; read file into buffer push af ; save return value ld e,1 ; set multi-sector count back to one ld c,2ch ; get bdos nr for setting multi-sectors call xbdos ; set that many sectors pop af ; get read status back ret ; ; Writes out History file from buffer at record-0. ; Also closes the file. ; PUTHIST: call OPENHIST ; Open history file ld e,NRSECTORS ; Get size of file (16K max) ld c,2ch ; get bdos nr for setting multi-sectors call xbdos ; set that many sectors ld de,RCORD0 ; get record-0's address into DE call SETDMA ; set the dma address xor a ; get a zero ld (HFCBCR),a ; zero "cr" field of the FCB ld de,HFCB ; point DE at history's FCB ld c,15h ; get bdos number for write sequential call xbdos ; write file from buffer ld e,1 ; set multi-sector count back to one ld c,2ch ; get bdos nr for setting multi-sectors call xbdos ; set that many sectors CLOSEHIST: ld de,HFCB ; point at history's FCB again ld c,10h ; get bdos number for file closing call xbdos ; close file, then return jp SDEFDMA ; reset DMA address back to default ; ; Find and open/create history file on the "TEMP" disk. ; ; Returns: ZeroFlag SET if file existed ; RESET if file just created ; OPENHIST: ld hl,HNAME ; load source of extension file's name ld de,HFCB+1 ; load addr of FCB Name-field ld bc,11 ; load size of CPM name ldir ; move it ld a,(usernum) ; get user number add a,'A' ; make unique and printable ld (HFCBUSER),a ; make history file unique to user number ld a,(ix+6ch) ; get temp file drive ld (HFCB),a ; put into FCB xor a ; get a zero ld (HFCBCR),a ; zero "cr" field of the FCB ; ; Opens file at HFCB, the name is assumed ; to be already loaded, and it is assumed to be on the temp drive. ; ; OPENTEMP: call OPENEXIST ; Open existing file ret z ; return with existing file opened ld c,16h ; didn't exist, so get make-file bdos number ld de,HFCB ; make sure still pointed at FCB call xbdos ; create file ld a,1 ; un-set zero flag or a ret ; ; Opens file at FCB if it already exists. ; Returns: Zero flag SET with Success ; Zero flag RESET if file doesn't already exist OPENEXIST: ld a,(ix+6ch) ; get temp file drive ld (HFCB),a ; put into FCB ld de,HFCB2 ; point just past name ld bc,26 ; size of FCB past name call CLRBUF ; clear out FCB ld de,HFCB ; point to History file FCB ld c,0fh ; open file bdos code call xbdos ; open the file or a ; set flags, did file exist? ret ; zero flag set if it did exist ; ; Translate numeric string at (HL) into binary, and return ; value in DE, and HL pointing just after the number (which is ; where it entered at). ; ; It is assumed that the input stream has already been checked ; for at least a single numeric character and that only the ; two LSB's count anyway. ATOI: push hl ;save pointer to "just after the number" ld d,0 ;init our accumulator dec hl ;point to LSB character ld a,(hl) ;get character call ATOB ;convert to binary ld e,a ;finish accumulator initialization dec hl ;point to next-LSB character ld a,(hl) ;get next character call ISNUMERIC ;We have a second digit? jr nc,ATOIEXIT ;nope, so exit already call ATOB ;convert to binary ex de,hl ;put accumulator into hl ld de,10 ;tens digit ATOI4: sub 1 jr c,ATOI5 add hl,de ;add a ten jr ATOI4 ATOI5: ex de,hl ;put accumlator back ATOIEXIT: pop hl ;get the "just after" pointer ret ; ; Convert ascii numeral in 'a' to binary ; return: CARRY FLAG SET indicates ERROR ; ATOB: sub '0' ; subtract ascii offset ret c ; punt if ascii was not numeric (too low) cp 10 ; test to see if it was (too high) numeric ccf ; make same sense as first test ret ; ; Calculates checksum of command line string pointed to by HL, ; returning that 16-bit checksum in DE ; ; The format of the command line string is assumed to be ; that as returned by a BDOS-10 call. ; CMDSUM: inc hl ;point at byte count ld b,(hl) ;get number of bytes ld de,0 ;initialize checksum SUMLOOP: inc hl ;point at next character ld a,(hl) ;get it add a,e ;add partially to checksum jr nc,SUMLP2 ;carry into checksum MSB? inc d ;yep, do the carry SUMLP2: ld e,a ;reassemble checksum djnz SUMLOOP ;do for entire string ret ;and done. ; ; Compares string at (HL) with string at (DE) returning ; CARRY FLAG: SET if equal ; CARRY FLAG: RESET if different ; ; Returns with both DE and HL pointers pointing just one past ; the matching-string (when it matches). ; ; Controlling string is at (HL). This string, up to it's first ; non-alphanumeric, is tested for equality to that at (DE). ; Comparison is not case sensitive. ; CMPSTRG: push bc CMPAGN: ld a,(hl) ;get controlling string cp '!' ;alpha numeric (printable)? jr c,CMPST2 ;nope, HL ended first, so strings matched call UCASE ;make sure upper case ld b,a ;save for a sec. ld a,(de) ;get other string's char call UCASE ;make sure upper case cp b ;strings match? inc hl ; (update inc de ; pointers to next in strings) jr z,CMPAGN ;yup they match, do next character or a ;reset carry flag CMPST2: pop bc ret ;return a no-match ; ; This checks to see if the ascii character in register ; 'a' is the history-mechanism's invocation character ; (or it's alternate). ; ; Modifies nothing but flags ; ; Returns: ZERO FLAG SET if it is one of those characters ; ZERO FLAG RESET if NOT one ISHISTCHAR: cp HIST1 ret z cp HIST2 ret ; ; This checks to see if the ascii character in register ; 'a' is numeric. ; ; Modifies nothing but flags ; ; Returns: CARRY FLAG SET if it is numeric ; CARRY FLAG RESET if NOT numeric ISNUMERIC: cp '0' ccf ret nc cp '9'+1 ret ; ; Concatinate the null-terminated string pointed to by HL to ; the "command-format" string pointed to by DE. The DE string ; has only the string-length and a null-terminated string. ; CMDCAT: push de ; save pointer to string length ld a,(de) ; get current string length ld b,a ; install into our length counter inc de ; point at the string's first character push hl ; save source string for a second ex de,hl ; calculate where the command's null is at call ADDHLA ex de,hl ; put destination pointer into DE pop hl ; put source string pointer into HL CMDCT2: ld a,(hl) ; get source character or a ; null terminator? jr z,CMDCT3 ; yep, go clean up ld (de),a ; nope, load it to the destination inc hl ; update.. inc de ; .. both src/dest pointers to next char inc b ; count the added character ld a,b ; get that count cp SIZECMDLINE ; combined length too long? jr c,CMDCT2 ; nope, go do another character ; yep, so it's exit time prematurely CMDCT3: xor a ; get a null ld (de),a ; null-terminate destination string pop hl ; get back pointer to destination's byte count ld (hl),b ; update it to the new length ret ; ; Looks for file "tempdisk: CCP.EXT". If it exists, it is loaded ; at address ADRCCPEXT, and passed HBUFFER (two above) and ; CMDLINE (just above) the return address on the stack. ; ; Upon CCP.EXT's Return: "Return value" is to be returned in register ; HL and it normally should be a zero. If it is non-zero, then ; the internal history mechanism will be bypassed. ; ; The basic idea here is that additional "shell" concepts could ; be implemented in a HLL ("C" being thought of in particular). ; Like this history mechanism, this probably is only practical ; with systems with bank-switched RAMDISK. My system executes ; this history mechanism with no noticeable pause. My "temp-disk" ; is a 720K DMA-driven bank-switching RAMDISK. My floppies are ; 8" DSDD 1.2MB each. I have no hard disk to try it out on. ; My Z80 runs at 5Mhz with no waitstates. ; ; CCPEXT: ld hl,HEXTNAME ; load source of extension file's name ld de,HFCB+1 ; load addr of FCB Name-field ld bc,11 ; load size of CPM name ldir ; move it call OPENEXIST ; try to open the file jr nz,CCPEX2 ; exit if not successful xor a ; get a zero ld (HFCBCR),a ; zero "cr" field of the FCB ld hl,ADRCCPEXT ; get starting address ld de,0 CCPEX1: add hl,de ; calculate next address push hl ; save it ex de,hl ; put into de call SETDMA ; point DMA there call GETBLK ; read a block pop hl ; get dma pointer back ld de,128 ; sector size or a ; last sector? jr z,CCPEX1 ; nope, so read another call CLOSEHIST ld hl,HBUFFER ; get pointer to history buffer push hl ; ld hl,CMDLINE ; get pointer to incoming command line push hl call ADRCCPEXT ; call loaded program ld a,h ; get.. or l ; ....hl value pop hl pop hl ; clean stack ret CCPEX2: xor a ; set zero flag ret ; HEXTNAME: defb 'CCP EXT' HNAME: defb 'HISTORY DAT' HERR1: defb 0dh,0ah,'Substitution not found',0 HFCB: defb 0,'HISTORY' HFCBUSER: defb ' ' defb 'DAT' HFCB2: defw 0,0,0,0,0,0,0,0,0,0 HFCBCR: defb 0,0,0,0,0,0,0,0,0 FLAGSUB: defb 0 HERROR: defb 0 HCMDSUM: defw 0 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;;; END OF HISTORY MODULE ;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; endif ;ccphistory ;.................. ; ;MESSAGES ; msgflag: DEFB 0 SCBPB: DEFB 3ah,0 PFCB: DEFW 0 DEFW PRSEFCB if not ccp lbrcmp: defb 0,' ',0,0 lbrfcb: defb 0,0,'COMMAND LBR',0,0,0,0 defs 21 else ;if CCP USER0MSG: DEFB ' (User 0)$' rootrsx: DEFB 65 rsx66: DEFB 66 diradr: DEFW 0 rootname: DEFS 9 rootpass: DEFS 9 rootdrv: DEFS 1 rootusr: DEFS 1 datpb: DEFS 4 endif subflag: defs 1 USERNUM: DEFs 1 DISKNUM: DEFs 1 CURDSK: DEFs 1 NXTNMA: DEFS 2 CMDPTR: DEFS 2 BOFFSET: DEFS 1 BDOSBASE: DEFS 1 if not ccp searoff: ds 2 searflg: ds 2 duspec: ds 1 usrsav: ds 2 buff: defs 128 scbbase: defs 2 memaddr: defs 2 lbrsec: defs 2 typeflag: defs 1 endif PASSWORD: DEFS 10 CMDFCB: DEFS 1 FILEDISK: DEFS 1 FILENAME: DEFS 8 FILETYPE: DEFS 24 LOADADDR: DEFS 2 PRSEFCB: DEFS 37 CMDLINE: DEFS 138H if not ccphistory STACK EQU $ endif ; not ccphistory if ccphistory STACK EQU 1300H endif ; ccphistory END