home *** CD-ROM | disk | FTP | other *** search
- ;********************************************************
- ;* *
- ;* CODE TO IMPLEMENT THE *
- ;* ESSENTIAL CDOS CALLS *
- ;* WHICH WILL ALLOW MOST *
- ;* CROMEMCO SOFTWARE TO *
- ;* RUN UNDER CP/M *
- ;* *
- ;********************************************************
- ;
- ; From Dr. Dobbs, January 1980
- ;
- ; by J. Warner, coded by Bill Bolton
- ;
- ; FILTER2 version by Chuck Weingart:
- ; 1 added code to save and restore all
- ; registers
- ; 2 correct small bug in program as pointed
- ; out by Liegh F. Fiddes in October 1980
- ; DDJ.
- ; 3 added code for 8D function (get CDOS version)
- ; 4 more comments supplied from original article
- ;
- ; This program is uaed by making it part of the
- ;memory image of a Cromemco program. When it gets control
- ;it boosts the function code filter into place at the top
- ;of the TPA and then moves the original program down to
- ;100H and jumps to it.
- ;
- BDOS EQU 0005H
- DUMMY EQU 0000H
- IGOR EQU DUMMY
- ;
- ; Measure the CP/M TPA size. Adjust the addresses in
- ;the function code of the function code filter for
- ;installation at the top of the TPA. Then change the jumps
- ;at 5,6 & 7 to route BDOS calls through the filter. Block
- ;move the filter to the top of the TPA.
- ;
- ;
- ORG 100H
- LD HL,(6) ;GET BDOS ENTRY
- LD (CPM1+1),HL ;INSTALL
- LD (CPM2+1),HL
- DEC H ;MAKE ROOM FOR FILTER
- LD L,0
- LD (6),HL ;INSTALL FILTER ADDRESS
- EX DE,HL
- LD HL,(1) ;GET WARM BOOT ADDRESS,
- INC HL ;IN BIOS JUMP TABLE
- INC HL
- INC HL ;CSTAT ADDRESS
- LD (CSTAT+1),HL ;INSTALL
- INC HL ;BUMP 3 TIMES TO FIND,
- INC HL ;CONIN
- INC HL
- LD (GBYTE+1),HL ;INSTALL
- LD HL,NAME-FILTER ;CALCULATE RELATIVE,
- ADD HL,DE ;SUBROUTINE ADDRESS
- LD (NAM1+1),HL
- LD (NAM2+1),HL
- LD HL,FILTER
- LD BC,END-FILTER
- LDIR ;INSTAL FILTER
- ;
- ; Part 2
- ;
- ; The filter just installed contains a one use
- ;routine to move the *.COM file on top of this stuff
- ;and into position. First put the stack between CP/M
- ;and the filter
- ;
- ;
- LD DE,(6) ;GET FILTER ADDRESS
- LD IX,MOVE-FILTER
- ADD IX,DE ; MOVE relocated addr
- LD HL,MOVE-FILTER+80H
- ADD HL,DE ; for the
- LD SP,HL ; stack
- LD DE,MESG
- LD C,9
- CALL BDOS ; send filter logo
- JP (IX) ; jump to relocated MOVE routine
- ;
- MESG: DEFW 0D0AH
- DEFM 'CDOS FILTER LOADED'
- DEFW 0D0AH
- DEFW 0D0AH
- DEFB '$'
- ;
- ; PART 3
- ;
- ; The following CPM/CDOS codes are affected:
- ; 2 write character to console: the A-reg
- ; must be saved and restored
- ; 11 check console status: this request is
- ; passed directly to the BIOS
- ; 128 read console (no echo): this request is
- ; passed directly to the BIOS
- ; 134 format string to File Control Block. It
- ; does not implement "*" wild cards.
- ; 141 get CDOS version. this is implemented by
- ; simply ignoring the call entirely.
- ;
- ; Note: it is a characteristic of CDOS that all
- ; registers are saved and restored, even in the
- ; "BIOS" portion of the code. Thus, a program that
- ; runs under CDOS might not run under CP/M, even
- ; if no specific CDOS calls are used.
- ;
- FILTER: PUSH AF
- LD A,C
- CP 02H ;write fcn code??
- JR NZ,NOTWR
- POP AF ;going to re-save A-reg later
- PUSH DE
- RES 7,E ;turn off high-order bit in E-reg
- PUSH BC
- PUSH HL ;must save all registers
- ;
- PUSH AF
- CPM1: CALL DUMMY ; >>> Addr supplied by Part 1 <<<
- POP AF
- ;
- GOBAK: POP HL
- POP BC ;restore all registers
- POP DE
- RET ;and return
- ;
- GOCPM: PUSH DE ;save all regs
- PUSH BC
- PUSH HL
- CPM2: CALL DUMMY ; >>> Addr supplied by Part 1 <<<
- JR GOBAK
- ;
- NOTWR: POP AF ;get A-reg back now
- LD A,C
- CP 0BH ;constat fcn code ??
- CSTAT: JP Z,DUMMY ; >>> Addr supplied by Part 1 <<<
- ADD A,A
- JR NC,GOCPM ;not a special fcn code
- ;
- GBYTE: JP Z,DUMMY ;CY=1 & Z=1 --> FCN CODE=80H
- LD A,8DH
- CP C ;get CDOS version fcn code ??
- JR Z,GOBAK
- LD A,86H
- CP C ;format string to fcb fcn code ??
- JP NZ,IGOR
- ;
- ; FORMAT STRING TO FCB - 86H
- ;
- PUSH DE
- LD B,(HL) ;might be disk designator
- INC HL
- LD A,(HL) ;if this is ":" then B-reg
- CP ':' ; contains drive #
- JR NZ,NOCOL
- INC HL ;pointer past colon
- LD A,7
- AND B ;mask
- JR FIRST
- NOCOL: DEC HL
- XOR A ;set for default disk drive
- FIRST:
- LD (DE),A ;first byte of FCB
- INC DE
- LD B,8 ;max # of chars in name
- NAM1: CALL DUMMY ; >>> Addr supplied by Part 1 <<<
- LD A,'.'
- CP (HL) ;check for "."
- JR NZ,EXT
- INC HL
- EXT: LD B,3 ;max # of chars in extension
- NAM2: CALL DUMMY ; >>> Addr supplied by Part 1 <<<
- XOR A ;zero file extent
- LD (DE),A
- ;
- ; next 5 lines from Leigh F. Fiddes
- ;
- PUSH HL ;save HL reg pair
- LD HL,20 ;offset from extent to next rec.
- ADD HL,DE ;HL points to next record field
- LD (HL),A ;zero next record
- POP HL ;restore HL reg pair
- POP DE
- RET
- ;
- ; internal routine to move ASCII string, with blank fill
- ;
- NAME: LD A,(HL) ;get next char from string
- CP 21H ;termination character ??
- JR C,FILL
- INC HL
- CP '.' ;none of these in FCB's
- JR Z,FILL
- CP 60H ;lower case "A"-1
- JR C,NAME1 ;JMP if not lower case
- SUB 20H ;convert lower case to upper
- NAME1: LD (DE),A
- INC DE ;put character in FCB
- DJNZ NAME
- RET ;all done
- ;
- FILL: LD A,20H ;ASCII space
- LD (DE),A
- INC DE ;fill rest of FCB with blanks
- DJNZ FILL
- RET
- ;
- ; this routine does actual move of program back to 100H
- ;
- MOVE: LD HL,200H ;bottom of program
- LD BC,(6) ;top of TPA
- DEC B ;amount to move down
- LD DE,100H ;origin for COM files
- LDIR
- JP 100H ;now, go to it
- END: EQU $
- END
-