;
;  PROGRAM:  LDR
;  AUTHOR:  RICHARD CONN
;  VERSION:  1.0
;  DATE:  27 FEB 84
;  PREVIOUS VERSIONS:  0.1 (3 Feb 84), 0.2 (22 Feb 84), 1.1 (28 Sep 84)
;
;VERSION        EQU     10

;VERSION        EQU     11      ; Version 1.1 by Joe Wright  28 Sept 84

                       ; This version modified to allow loading the .ENV
                       ;  file the first time, when there is no environment
                       ;  descriptor in memory.  The program now takes
                       ;  the environment address from the .ENV file so
                       ;  that subsequent files are also loaded correctly.
                       ;  ie. LDR SYS.ENV,SYS.RCP,etc.  Note that .ENV must
                       ;  be the first declared file until LDR is installed
                       ;  to your environment.  jww

VERSION EQU     12      ; Version 1.2 by Dave Lucky  31 Dec 84

                       ; This version modified to correct exit regs from
                       ;  SDLOAD subroutine.  The Source and Destination
                       ;  registers on entry were HL and DE, respectively.
                       ;  On exit, they were DE and HL.  The calling routine
                       ;  (SETDATA) went amuck when calculating number of NDR
                       ;  records using bogus DE.  Also, corrected the SETDATA
                       ;  routine from using the incorrect address of the NDR
                       ;  entry size field as well as its contents acquired
                       ;  from the GETNDR routine.

EXTENV  EQU     1       ; 1 for External Environ, 0 for Internal Environ

;
;       LDR is a general-purpose package loader for ZCPR3.  It is
; invoked by the following form:
;
;               LDR <list of packages>
;
; For example:
;               LDR DEFAULT.RCP,SYSIO.IOP
;
;       No default file types are assumed on the list of packages, and
; each package specified must be unambigous and have a type of RCP or IOP
; (for Resident Command Package or Input/Output Package).  LDR
; checks to make sure that the files are valid packages and then loads
; them into memory at the correct locations, checking for package boundary
; overflow.
;
;

;
;  ZCPR3 Header
;
       MACLIB  Z3BASE.LIB

;
;  System Equates
;
bdos    equ     5
fcb     equ     5ch
tbuff   equ     80h
rcpflg  equ     1       ; package type is RCP
iopflg  equ     2       ; package type is IOP
fcpflg  equ     3       ; package type is FCP
ndrflg  equ     4       ; package type is NDR
envflg  equ     5       ; package type is ENV
tcapflg equ     6       ; package type is Z3T
cr      equ     0dh
lf      equ     0ah

       ext     z3init,envptr
       ext     retud,getud,putud,logud
       ext     getrcp,getfcp,getiop,getndr
       ext     f$open,f$close,f$read
       ext     print,pfn2
       ext     hmovb,moveb,fillb
       ext     cline,sksp,zfname

;
;  Environments
;
origin:
;
       if      extenv          ; if external environment ...
;
;  External Environment Definition
;
       jmp     z3ldr
       db      'Z3ENV'         ; this is an environment
       db      1               ; class 1 environment (external)
envloc:
       dw      z3env           ; ptr to environment
z3ldr:
       lhld    envloc          ; HL pts to environment

       else                    ; if internal environment ...
;
;  Internal Environment Definition
;
       MACLIB  SYSENV.LIB
envloc:
       jmp     z3ldr
       SYSENV                  ; define environment
z3ldr:
       lxi     h,envloc        ; HL pts to environment

       endif

;
;  Beginning of LDR
;
       call    z3init  ; initialize environment pointer
       call    banner  ; print banner
       lxi     h,tbuff ; pt to command line
       call    cline   ; save command line as string
       call    sksp    ; skip over spaces
       mov     a,m     ; get offending char
       cpi     '/'     ; help?
       jz      help
       ora     a       ; help?
       jz      help
;
;  Main Loop - HL pts to next file name in list
;
z3ldr1:
       lxi     d,fcb   ; pt to fcb
       call    zfname  ; extract file name and data
       inx     d       ; pt to file name
       call    print
       db      cr,lf,' Loading ',0
       call    pfn2    ; print file name
       push    h       ; save ptr
       call    pkload  ; load file
       pop     h       ; get ptr
       mov     a,m     ; get char
       inx     h       ; pt to next char
       cpi     ','     ; another file in list?
       jz      z3ldr1
       ret
;
;  Print Help Message
;
help:
       call    print
       db      cr,lf,' LDR Syntax:'
       db      cr,lf,' LDR <list of packages/data files>'
       db      cr,lf,' where entries in the list may be any of these types:'
       db      cr,lf
       db      cr,lf,' FCP - Flow Cmnd Package         ENV - Z3 Environ'
       db      cr,lf,' IOP - Input/Output Package      NDR - Z3 Named Dir'
       db      cr,lf,' RCP - Resident Cmnd Package     Z3T - Z3TCAP Entry'
       db      cr,lf,lf,' The ENV file must be first if LDR is not installed.'
       db      cr,lf,0
       ret
;
;  Load package named in FCB
;
pkload:
       call    setdata ; load data buffers from environment in case of change
       call    cktype  ; check for valid file type
       jz      typerr  ; abort if error
       call    open    ; open file, read in first block, check for valid
       jz      getud   ; abort if error

; Check if ENV.  If so, get Z3ENV and call z3init

       push    h               ; save package pointer from cktype
       lxi     d,fcb+9         ; fcb type
       lxi     h,envtyp        ; ENV?
       call    comptyp         ; compare types
       pop     h               ; get package pointer
       jnz     pkld            ; not ENV, proceed normally
;
; File type is ENV.  Get Z3ENV address from file and re-initialize
;
       lxi     h,tbuff         ; first sector in tbuff
       lxi     d,1bh           ; offset to Z3ENV
       dad     d               ; point hl to it
       mov     e,m             ; get Z3ENV
       inx     h
       mov     d,m             ; got it
       xchg                    ; in hl
       call    z3init          ; set new environment

pkld:   call    load    ; load package into memory at correct location
       call    close   ; close up process
       call    getud   ; return home
;
;  Check for IOP and return if not
;
       lda     pktype  ; init package if IOP
       cpi     iopflg
       rnz
;
;  Init IOP
;
       lhld    packadr ; get address
       lxi     d,9     ; 4th JMP into it
       dad     d
       push    h       ; address on stack
       ret             ; "CALL" routine and return to OS
;
;  Load Data Buffers from Environment
;
setdata:
       lhld    envptr  ; get environment descriptor address
       shld    envadr
       lxi     d,80H   ; pt to Z3TCAP
       dad     d
       shld    tcapadr
       call    getrcp  ; get RCP data
       lxi     d,rcpdata       ; load
       call    sdload
       call    getiop  ; get IOP data
       lxi     d,iopdata       ; load
       call    sdload
       call    getfcp  ; get FCP data
       lxi     d,fcpdata       ; load
       call    sdload
       lxi     h,ndridat       ; init NDR data in case no entry
       lxi     d,ndrdata
       mvi     b,9     ; 9 bytes (1-jmp, 5-ID, 2-adr, 1-size)
       call    moveb
       call    getndr  ; get NDR data
       mov     b,a     ; save entry count                              ;1284DL
       mov     a,h     ; no NDR data?
       ora     l
       rz
       mov     a,b     ; restore entry count                           ;1284DL
       call    sdload  ; with DE -> ndrdata                            ;1284DL
       push    d       ; save ptr to entry count                       ;1284DL
       mvi     h,0     ; HL = value
       mov     l,a     ; A  = entry count
       dad     h       ; *2
       mov     d,h     ; DE = value * 2
       mov     e,l
       dad     h       ; *4
       dad     h       ; *8
       dad     h       ; *16
       dad     d       ; *18
       mov     a,h     ; /128
       rlc
       ani     0feh
       mov     h,a
       mov     a,l
       rlc
       ani     1
       ora     h       ; A = value * 18 / 128
       inr     a       ; +1
       pop     d       ; get ptr
       stax    d       ; save value
       ret
;
;  Load 3 bytes pted to by HL into memory pted to by DE+6
;
;       Input Regs:                                                     ;1284DL
;               HL = Source                                             ;1284DL
;               DE = Destination                                        ;1284DL
;                                                                       ;1284DL
;       Output Regs:                                                    ;1284DL
;               HL = Source                                             ;1284DL
;               DE = Destination+8                                      ;1284DL
;                                                                       ;1284DL
sdload:
       push    h       ; save ptr to data
       lxi     h,6     ; add 6 to DE to pt to proper buffer
       dad     d       ; HL pts to buffer
       pop     d       ; DE contains address
       mov     m,e     ; store address
       inx     h
       mov     m,d
       inx     h
       mov     m,a     ; store size data
       xchg            ; swap Source / Destination regs                ;1284DL
       ret
;
;  Print Banner
;
banner:
       call    print
       db      cr,lf,'ZCPR3 LDR, Version '
       db      (VERSION/10)+'0','.',(VERSION MOD 10)+'0',0
       ret
;
;  Check for Valid Package File Type
;       Return with Zero Flag Set if error
;       If validated, PKTYPE contains package type and HL pts to data
;
cktype:
       lxi     d,fcb+9 ; pt to file type
       lxi     h,rcptyp        ; see if RCP
       mvi     b,rcpflg        ; RCP code
       call    comptyp ; compare
       jz      cktok   ; OK if match
       lxi     h,ioptyp        ; see if IOP
       mvi     b,iopflg        ; IOP code
       call    comptyp ; compare
       jz      cktok   ; OK if match
       lxi     h,fcptyp        ; see if FCP
       mvi     b,fcpflg        ; FCP code
       call    comptyp ; compare
       jz      cktok   ; OK if match
       lxi     h,ndrtyp        ; see if NDR
       mvi     b,ndrflg        ; NDR code
       call    comptyp ; compare
       jz      cktok   ; OK if match
       lxi     h,envtyp        ; see if ENV
       mvi     b,envflg        ; ENV code
       call    comptyp ; compare
       jz      cktok   ; OK if match
       lxi     h,tcaptyp       ; see if Z3TCAP
       mvi     b,tcapflg       ; Z3T code
       call    comptyp ; compare
       jz      cktok
       mvi     b,0     ; invalid type
cktok:
       mov     a,b     ; set package type
       sta     pktype
       ora     a       ; set NZ if no error
       ret
comptyp:
       push    d       ; save regs
       push    b
       mvi     b,3     ; 3 bytes
compt1:
       ldax    d       ; get FCB char
       ani     7fh     ; mask
       cmp     m       ; compare
       jnz     compt2
       inx     h       ; pt to next
       inx     d
       dcr     b       ; count down
       jnz     compt1
compt2:
       pop     b       ; restore regs
       pop     d
       ret
typerr:
       call    prf     ; print file name and string
       db      ' is not a Valid Type',0
       ret
;
;  Open File and Load First Block into TBUFF
;       Validate Package Structure and Return with Zero Flag Set if Error
;       On input, HL pts to data buffer
;       If no error, HL points to load address and B is number of 128-byte
;               pages allowed in buffer
;
open:
       call    putud   ; save location
       call    retud   ; get UD in BC
       lda     fcb     ; get disk
       ora     a       ; default?
       jz      open0
       mov     b,a     ; disk in B (A=1)
       dcr     b       ; adjust to A=0
open0:
       lda     fcb+13  ; get user
       mov     c,a     ; user in C
       call    logud   ; log into UD
       xra     a       ; clear disk
       sta     fcb

;
;  Disallow Ambiguous File Name
;
       call    ambchk  ; check for ambiguous file name
       jz      amberr  ; abort if any ambiguity
;
;  Open File
;
       lxi     d,fcb   ; pt to FCB
       call    f$open  ; open file
       jnz     fnferr  ; abort if file not found
;
;  Read First 128-byte Block
;
       call    f$read  ; read in first block
       jnz     fempty  ; abort if file empty
;
;  Validate Package
;       Package Data Area is structured as follows:
;               DB      numjmps ; number of jumps at beginning of package
;               DB      'Z3xxx' ; package ID (always 5 chars)
;               DW      address ; address of memory buffer
;               DB      size    ; number of 128-byte blocks in memory buffer
;
       xchg            ; DE pts to package data
       ldax    d       ; get number of jumps
       inx     d       ; pt to package ID
       mov     b,a     ; jump count in B
;
;  Validate Package - MUST have proper number of JMPs
;
       lxi     h,tbuff ; check jumps
open1:
       mov     a,b     ; at limit of jumps?
       ora     a
       jz      open2
       dcr     b       ; count down
       mov     a,m     ; check for JMP
       cpi     0C3H    ; JMP?
       jnz     strerr  ; structure error
       inx     h       ; pt to next
       inx     h
       inx     h
       jmp     open1
;
;  Check Package ID - must match
;
open2:
       mvi     b,5     ; check package ID
open3:
       ldax    d       ; get byte
       cpi     ' '     ; no ID if space
       jz      open4
       cmp     m       ; check
       jnz     strerr  ; structure error
open4:
       inx     d       ; pt to next
       inx     h
       dcr     b       ; count down
       jnz     open3
;
;  Extract Package Address
;
       ldax    d       ; get low-order address
       mov     l,a     ; put in HL
       inx     d
       ldax    d       ; get high-order address
       mov     h,a
       inx     d
;
;  Check for Valid Package Address
;
       mov     a,h     ; must not be zero
       ora     l
       jz      adrerr
;
;  Extract 128-byte Block Count
;
       ldax    d       ; get block count
       mov     b,a     ; put in B
       xra     a       ; set flags
       dcr     a       ; NZ
       ret
;
;  Ambiguous File Name Check
;       Returns with Z Set if Ambiguous
;
ambchk:
       lxi     d,fcb+1 ; check for ambiguous file name
       mvi     b,11    ; 11 chars
ambchk1:
       ldax    d       ; get char
       ani     7fh     ; mask
       cpi     '?'
       rz
       inx     d       ; pt to next
       dcr     b       ; count down
       jnz     ambchk1
       dcr     b       ; set NZ flag
       ret

;
;  Error Messages
;
amberr:
       call    prf     ; print file name and message
       db      ' is Ambiguous',0
erret:
       xra     a       ; set error code
       ret
adrerr:
       call    prf     ; print file name and message
       db      ' Not Known to Environ',0
       jmp     erret
fnferr:
       call    prf     ; print file name and message
       db      ' Not Found',0
       jmp     erret
fempty:
       call    prf     ; print file name and message
       db      ' Empty',0
       jmp     erret
strerr:
       call    prf     ; print file name and message
       db      ' Contains a Format Flaw',0
       jmp     erret
prf:
       call    print
       db      cr,lf,' File ',0
       lxi     d,fcb+1
       call    pfn2
       jmp     print

;
;  Close File
;
close:
       lxi     d,fcb   ; pt to FCB
       jmp     f$close ; close file

;
;  Load File Into Buffer
;
load:
       shld    packadr ; save package address in case of error
       xchg            ; DE pts to buffer, B = Max Blocks
load1:
       push    b       ; save count
       lxi     h,tbuff ; pt to buffer
       mvi     b,128
       call    hmovb   ; copy TBUFF into Buffer
       push    d       ; save ptr to next block in buffer
       lxi     d,fcb   ; pt to fcb
       call    f$read  ; read next block
       pop     d       ; get ptr
       pop     b       ; get count
       rnz             ; done if NZ
       dcr     b       ; count down
       jnz     load1
;
;  Buffer Full
;
       call    prf
       db      ' is too Large',0
       lhld    packadr ; clear package
       mvi     b,128   ; NOPs
       xra     a
       call    fillb
       lxi     b,128   ; pt to after last NOP
       dad     b
       mvi     b,3     ; copy 3 bytes
       xchg            ; DE pts to empty space
       lxi     h,ercode        ; store error code
       jmp     moveb
;
;  Error Code to be Stored if Package Load Fails
;
ercode:
       xra     a       ; 3 bytes
       dcr     a       ; A=0FFH and NZ Flag Set
       ret

;
;  Buffers
;
ndridat:
       db      0       ; no JMPs
       db      '     ' ; no ID stored
       dw      0       ; address
       db      0       ; (z3ndirs*18)/128+1 size
rcptyp:
       db      'RCP'   ; file type of RCP file
rcpdata:
       db      0       ; 0 JMPs
       db      'Z3RCP' ; ID
       dw      0       ; address
       db      0       ; size
ioptyp:
       db      'IOP'   ; file type of IOP file
iopdata:
       db      16      ; 16 JMPs
       db      'Z3IOP' ; ID
       dw      0       ; address
       db      0       ; size
fcptyp:
       db      'FCP'   ; file type of FCP file
fcpdata:
       db      0       ; 0 JMPs
       db      'Z3FCP' ; ID
       dw      0       ; address
       db      0       ; size
ndrtyp:
       db      'NDR'   ; file type of NDR file
ndrdata:
       db      0       ; no JMPs
       db      '     ' ; no ID stored
       dw      0       ; address
       db      0       ; (z3ndirs*18)/128+1 size
envtyp:
       db      'ENV'   ; file type of ENV file
envdata:
       db      1       ; 1 JMP
       db      'Z3ENV' ; ID
envadr:
       dw      0       ; address
       db      2       ; 2 128-byte blocks max
tcaptyp:
       db      'Z3T'   ; file type of Z3TCAP file
tcapdata:
       db      0       ; no JMPs
       db      '     ' ; no ID stored
tcapadr:
       dw      0       ; address
       db      1       ; 1 128-byte block max
pktype:
       ds      1       ; package type (0=error)
packadr:
       ds      2       ; package address

       end