home *** CD-ROM | disk | FTP | other *** search
- .Z80
- ;Modified LOADER for CP/M version 3.1
- ;
- ;This Loader is to be combined with the modified CCP before installing
- ;the CCP. It is especially useful in an RCPM
- ;environment. See CCP+.DOC for more details.
- ;
- ;This is the modified dissasembled version of the LOADER.
- ;
- ;Jim Lopushinsky, Edmonton, Alberta, Canada
- ;484-5981 @ 300/1200 bps
-
- bdos EQU 5
-
- ;.............
- ;
- ;RSX header for the loader.
- ;
- ;
- begin:
- ds 4 ; 100H
- dw end-begin ;Length of loader module 104H
- JP LOADER ;Loader entry point
- NEXT: JP 6 ;modified to JMP BDOS
- PREV: DEFW 7 ;modified to point to prev RSX
- DEFB 0 ;remove flag
- DEFB 0 ;non-banked flag
- DEFB 'LOADER ' ;The name of this RSX
- DEFB 0FFH ;Loader flag
- DEFB 0,0 ;reserved
-
- ;.........
- ;
- ;End of RSX header
- ;
- scbbase: ;Address of Base of System Control Block
- DEFW 0 ; 11BH
- membase: ;Address of Base of Common memory
- DEFB 0 ; 11DH
-
- ;...........
- ;
- ;Jump table for service routines that the CCP uses in the non-relocated
- ;version of the loader
- ;
-
- JP chkrsx ;Remove inactive RSXs 11EH
- JP reloc ;Relocate RSX 121H
- JP setload ;compute relocate address 124H
- JP setnext ;set up next RSX pointer 127H
- JP setrsx ;set up RSX chains 12AH
- ;
- ;save IX and call BDOS 12DH
- ;
- xbdos:
- push ix
- call bdos
- pop ix
- ret
-
- ;............
- ;
- ;Loader entry point. All BDOS calls are intercepted here. We only
- ;need to intercept function 59, Load overlay
- ;
-
- LOADER:
- LD A,C ;Get BDOS function
- CP 59 ;is it Load overlay?
- jr NZ,NEXT ;on to BDOS if not
- POP BC ;GET RETURN ADDRESS IN [BC]
- PUSH BC
- LD (STKSAVE),sp
- LD SP,LDRSTACK
- PUSH BC ;Save return address on stack
- ld ix,(scbbase) ;SCB in IX
- EX DE,HL
- LD (LFCBADDR),HL ;Save Load FCB address
- LD A,H ;Test for load address of 0
- OR L
- PUSH AF ;save flags
- CALL Z,CHKRSX ;Delete inactive RSXs if 0
- POP AF ;restore flags
- CALL NZ,LOAD ;if load address non-zero, load the program
- POP DE ;Get return address
- LD HL,100H ;point to start of .COM file
- LD A,(HL) ;Get first byte
- CP 0C9H ;Is it a return inst?
- jr Z,DORSX ;RSXs attached. Go relocate them
- LD A,D ;Test for return address of 100H
- DEC A
- OR E
- jr NZ,NOT100H ;Jump if not loading a .COM or .PRL file
- LD A,(PREV+1) ;Get High byte prev address
- OR A ;is it 0?
- jr NZ,NOT100H ;Nope
- LD HL,(NEXT+1) ;Get next RSX address
- LD (BDOS+1),HL ;Save in JMP BDOS in page 0
- LD (BDOSJMP),HL ;And save it for us
- CALL SETTPA ;Set Top of TPA address in SCB
- NOT100H:
- LD sp,(STKSAVE) ;Restore callers stack
- XOR A ;flag no error
- LD L,A
- LD H,A
- RET
-
- ;...............
- ;
- ;HERE IF BAD LOAD ADDRESS
- ;
- BADADDR:
- LD DE,0FEH ;init error code
- ERRRET:
- LD sp,(STKSAVE) ;restore callers stack
- POP HL ;get return address
- PUSH HL
- DEC H ;test for return to 100H (called from CCP)
- LD A,H
- OR L
- EX DE,HL ;error code in HL
- LD A,L ;propagate error code to A and B
- LD B,H
- RET NZ ;return if called by user program (not CCP)
- BADADRA:
- LD C,9 ;print string function
- LD DE,LOADMSG ;point to load error message
- CALL xbdos ;print the error message
- RST 0 ;and warm boot.
-
- ;.................
- ;
- ;RELOCATE THE RSX
- ;
- MOVERSX:
- INC HL
- LD C,(HL) ;Get length of RSX into BC
- INC HL
- LD B,(HL)
- LD A,(MEMBASE) ;Get common memory base
- OR A ;Test for banked system
- jr Z,NONBNK ;Jump if non-banked system
- INC HL
- INC (HL) ;Test for non-banked only load
- jr Z,LNOLOAD ;jump if non-banked only RSX
- NONBNK:
- PUSH DE ;Save RSX start address
- CALL SETLOAD ;Set up relocation address
- POP HL ;RSX start address in HL
- CALL RELOC ;Relocate the RSX
- CALL SETRSX ;Set up the RSX pointers
- LNOLOAD:
- POP HL ;restore COM header table location
-
- ;...............
- ;
- ;LOAD RSX'S AND ADJUST COM FILE
- ;
- DORSX:
- LD DE,16 ;offset in COM file header to start of
- ;RSX length table
- ADD HL,DE ;form address
- PUSH HL ;save on stack
- LD E,(HL) ;Get start address of RSX in DE
- INC HL
- LD D,(HL)
- LD A,E ;Test for end of RSX table
- OR D
- jr NZ,MOVERSX ;Go do it if not at end
- CALL 0103H ;Call init routine in COM file RSX header
- LD A,(200H) ;Get first byte of .COM file
- CP 0C9H ;Is it return inst?
- jr NZ,NO2NDHDR ;Jump if no second header page
- set 1,(ix+33h) ;Set RSX flag
-
- ;...........
- ;
- ;Here to move the COM file down one page
- ;
- NO2NDHDR:
- LD bc,(0101H) ;Get length of COM file into bc
- LD HL,200H ;source
- LD DE,100H ;destination
- LDIR ;Move COM file down one page
- jr NOT100H ;and process next header
-
- ;............
- ;
- ;SET UP RSX HEADERS. DE = base of RSX
- ;
- SETRSX:
- LD HL,(BDOS+1) ;get top of TPA
- LD L,0 ;align on page boundary
- LD BC,6 ;length of move
- LDIR ;move Serial number into place
- xor a
- LD E,18H ;point to loader flag
- LD (DE),A ;zero the loader flag
- LD E,0DH ;High byte of prev address
- LD (DE),A ;zero prev high byte
- DEC DE ;low byte of prev
- LD A,7
- LD (DE),A ;prev = 0007H
- LD L,E ;point to prev in next RSX
- LD E,0BH ;next field in this RSX
- LD (HL),E ;set prev field of next RSX
- INC HL ;to point to this RSX
- LD (HL),D
-
- ;..............
- ;
- ;SET UP NEXT FIELD IN RSX HEADER
- ;HL = base of next RSX, DE= next field in this RSX
- ;
- SETNEXT:
- EX DE,HL ;HL=next field, DE=next RSX
- LD (HL),D ;save page number
- DEC HL ;point to low byte
- LD (HL),6 ;always 6
- STNEXTA:
- LD L,6 ;adjust
- LD (BDOS+1),HL ;alter JMP BDOS
- LD (BDOSJMP),HL ;and save it for us
-
- ;.............
- ;
- ;SET TOP OF TPA IN SCB
- ;
- SETTPA:
- LD DE,LSCBPB ;point to SCB paramater block
-
- ;.............
- ;
- ;GET/SET SCB AT [DE]
- ;
- LGSSCB:
- LD C,49 ;get/set SCB
- jp xbdos ;Set the Top TPA address in SCB
-
- ;.............
- ;
- ;DELETE ANY INACTIVE RSX'S
- ;
- CHKRSX:
- LD HL,(BDOS+1) ;get top of TPA
- LD B,H ;top of TPA page in B
- RSXRMLOOP:
- LD H,B ;get RSX base page
- LD L,18H ;offset to loader flag
- INC (HL) ;test loader flag
- DEC (HL)
- RET NZ ;return if at loader
- LD L,0BH ;offset to high byte of next field
- LD B,(HL) ;get next RSX page into B
- LD L,0EH ;point to remove flag
- LD A,(HL) ;get remove flag
- OR A ;test remove flag
- jr Z,RSXRMLOOP ;jump if not to remove this RSX
- LD L,0CH ;point to prev field
- LD E,(HL) ;get prev address into DE
- INC HL
- LD D,(HL)
- LD A,B ;get next RSX page
- LD (DE),A ;set prev RSX to bypass this RSX
- DEC DE
- LD A,6 ;always 6
- LD (DE),A
- INC DE ;back to high byte of prev field
- LD H,B ;form address of next RSX
- LD L,0CH ;offset to prev field in next RSX
- LD (HL),E ;set prev address in next RSX
- INC HL ;to bypass this RSX
- LD (HL),D
- LD A,D ;test for page zero prev pointer
- OR A
- PUSH BC ;save RSX page
- CALL Z,STNEXTA ;alter location 6 if we just removed
- ;lowest RSX
- POP BC ;restore RSX page
- jr RSXRMLOOP ;and loop for more RSXs
-
- ;............
- ;
- ;LOAD THE PROGRAM
- ;
- LOAD:
- PUSH HL ;save FCB address
- LD DE,DMASCB ;point to SCB param block for get DMA
- CALL LGSSCB ;Get current DMA address
- EX DE,HL ;DMA into DE
- ex (sp),iy ;restore FCB address, save IY
- bit 7,(ix+25h) ;test library member load
- jr z,notlbr
- ld l,(iy+23h)
- ld h,(iy+24h) ;get member length into HL
- ld (memlen),hl ;save member length
- jr load1
- notlbr:
- ld (iy+20h),0 ;zero record count
- load1:
- ld l,(iy+21h)
- ld h,(iy+22h) ;get load address into HL
- ex (sp),iy ;restore IY, save FCB address
- DEC H ;test for load address < 100H
- INC H
- jp Z,BADADDR ;jump if attempt to load below 100H
- PUSH HL ;save load address
- PUSH DE ;save old DMA address
- PUSH HL ;save load address again
- CALL setusr ;set up multi-sector count, user number
- POP HL ;restore load address
- PUSH AF ;save old mult-sector count on stack
- MOREREAD:
- LD A,(BDOS+2) ;get base page of top of TPA
- DEC A ;less one
- SUB H ;compare with load address
- jp C,TOHIGH ;jump if too high
- jp Z,tohigh
- LD (nextaddr),HL ;save current sector address
- CP 64
- jr C,ok64
- LD a,64
- ok64:
- PUSH HL
- LD d,a
- ADD A,a
- bit 7,(ix+25h) ;test library flag
- jr z,load3
- ld hl,(memlen) ;get member length left
- ld c,a ;sector count in c
- ld b,0
- sbc hl,bc ;calculate new length left
- jr nc,load2 ;jump if no overflow
- ld a,(memlen) ;get length left
- ld hl,0
- load2:
- ld (memlen),hl ;save new length left
- or a ;at end of member?
- jr nz,load3
- pop hl ;restore stack
- inc a ;A = 1
- jr readend
- load3:
- LD e,a
- CALL setmce
- LD e,0
- POP HL
- PUSH HL
- PUSH DE
- CALL LREAD ;read a sector
- POP DE ;restore block length
- POP HL ;restore sector address
- ADD HL,DE ;bump sector address
- jr Z,MOREREAD ;jump if no read errors
- READEND:
- POP BC ;get old multi-sector count
- DEC A ;if EOF, A = zero
- LD E,B ;old multi-sector count in E
- CALL SETMCE ;restore old multi-sector count
- LD C,26 ;set DMA function
- POP DE ;restore old DMA address
- PUSH AF ;save read EOF status
- CALL setous ;set DMA to old value, restore old user number
- POP AF ;restore read EOF status
- LD de,(ERRCODE) ;get read error flags
- jp NZ,ERRRET ;jump if read error (not EOF)
- POP DE ;restore load address into DE
- POP HL ;restore FCB address into HL
-
- ;.............
- ;
- ;CHECK FOR PRL FILE (PAGE RELOCATABLE)
- ;
-
- bit 6,(ix+25h) ;is it PRL?
- ret z
-
- ;.............
- ;
- ;here if .PRL file loaded
- ;
- LD A,E
- OR A ;must be on even page boundary
- jp NZ,BADADDR ;jump if not on page boundary
- LD H,D ;load address into HL
- LD L,E
- INC HL ;point to code length in PRL header
- LD C,(HL) ;get code length into BC
- INC HL
- LD B,(HL)
- LD L,E ;L = 0
-
- ;...............
- ;
- ;RELOCATE THE LOADED MODULE
- ;
- RELOC:
- INC H ;point to start of code
- PUSH DE ;save load address
- PUSH BC ;save length
- LDIR ;move the module to target location
- ;[HL] NOW POINTS TO START OF BIT MAP
- POP BC ;restore length
- POP DE ;restore target address
- PUSH DE
- LD E,D ;target page into E
- DEC E ;adjust relocation offset
- PUSH HL ;save bit map address
- LD H,E ;relocation offset in H
- LD E,0 ;init bit offset
- RELOCLP:
- LD A,B ;test for end
- OR C
- jr Z,RELOCDN ;Jump if done
- DEC BC ;Decrement length left
- LD A,E ;get number of bits left
- AND 7
- jr NZ,NOBUMP ;jump ok
- EX (SP),HL ;get bit map address
- LD A,(HL) ;get next byte from bit map
- INC HL ;bump
- EX (SP),HL ;back to stack
- LD L,A ;bits in L
- NOBUMP:
- RL l ;shift into carry
- jr NC,NOADJUST ;jump if no need to adjust
- LD A,(DE) ;get a byte
- ADD A,H ;adjust it
- LD (DE),A ;put it back
- NOADJUST:
- INC DE ;bump pointer
- jr RELOCLP ;and loop for more
- RELOCDN: ;relocation complete
- POP DE ;adjust stack
- POP DE
- RET
-
- ;................
- ;
- ;HERE IF LOAD ADDRESS IS TOO HIGH
- ;
- TOHIGH:
- CALL SETMSC ;restore things
- LD HL,80H ;point to TBUFF
- CALL LREAD ;read one more sector into TBUFF
- jr NZ,READEND ;jump if read error
- LD HL,0FEH ;set error code
- LD (ERRCODE),HL
- jr READEND ;and jump to read return
-
- ;..............
- ;
- ;SET UP THE LOAD PARAMETERS
- ;
- SETLOAD:
- LD A,(BDOS+2) ;get top of TPA page
- DEC A ;less one
- DEC BC ;decrement load length
- SUB B ;compute target page
- INC BC ;correct load length
- CP 0FH ;load must start at page 15 or higher
- jp C,BADADRA ;jump if too low
- LD HL,(NEXTADDR) ;get target address
- CP H ;compare with load page
- jp C,BADADRA ;jump if target address > load address
- LD D,A ;relocation address into DE
- LD E,0
- RET
-
- ;..............
- ;
- ;RETURN MULTI-SECTOR COUNT IN [A] AND SET IT TO 1
- ;
- SETMSC:
- LD E,1 ;set multi-sector count to 1
-
- ;...............
- ;
- ;RETURN MULTI-SECTOR COUNT IN [A] AND SET IT TO [E]
- ;
- SETMCE:
- LD A,(ix+66H) ;get the old multi-sector count
- LD (ix+66H),E ;set the new multi-sector count
- RET
-
- ;..............
- ;
- ;SET DMA ADDRESS AND READ a sector
- ;
- LREAD:
- EX DE,HL ;DMA address in DE
- LD C,26 ;Set DMA function
- CALL xbdos ;set the DMA address
- LD C,20 ;Read sequential function
- LD HL,(LFCBADDR) ;point to FCB
- EX DE,HL ; into DE
- CALL xbdos ;read a sector
- LD (ERRCODE),HL ;save return code
- OR A ;set read return flag
- RET
-
- ;............
- ;
- ;set up load user number
- ;
- SETUSR:
- LD A,(ix+25H) ;get load user number
- and 1fh ;default user number
- jr Z,setmsc ;go and set multi-sector count if default
- DEC A ;adjust to true user number
- LD E,A ;into E for BDOS
- LD A,(ix+60H) ;get old user number
- LD (curusr),A ;save it
- LD (ix+60H),E ;set new user number
- jr setmsc ;and on to set multi-sector count
-
- ;................
- ;
- ;restore old user number
- ;
- setous:
- LD A,(ix+25H) ;get load user number
- and 1fh ;default?
- Jr Z,setous1 ;on to restore old DMA if default
- LD A,(curusr) ;get old user number
- LD (ix+60H),A ;restore it
- setous1:
- LD (ix+25H),0 ;set load user to default
- jp xbdos
-
- ;..............
- ;
- ;LOAD ERROR MESSAGE
- ;
- LOADMSG: DEFB 0DH,0AH
- DEFB 'Load Error$'
-
- ;............
- ;
- ;SCB FOR GET DMA ADDRESS
- ;
- DMASCB: DEFB 3ch ;offset to DMA address
- DEFB 0 ;return value from SCB
-
- ;...........
- ;
- ;SCB PARAMETER BLOCK TO SET OFFSET 62H (TOP OF TPA)
- ;
- LSCBPB:
- DEFB 62h ;offset to top of TPA address
- DEFB 0FEH ;set word in SCB
-
- end equ $
-
- BDOSJMP equ $ ;Top of TPA address
- NEXTADDR equ $+2 ;next load sector address
- LFCBADDR equ $+4 ;load FCB address
- STKSAVE equ $+6 ;user stack save
- ERRCODE equ $+8 ;read error return code
- ;local stack space
- LDRSTACK EQU $+45
- curusr equ $+10 ;old user number
- memlen equ $+11 ;library member length
-
-
- END