Browse Source

added new /b=options to assign.com - Not complete at this time.

pull/476/head
Mark Pruden 1 year ago
parent
commit
d5c331076c
  1. 1
      Doc/ChangeLog.txt
  2. 483
      Source/Apps/assign/assign.asm

1
Doc/ChangeLog.txt

@ -52,6 +52,7 @@ Version 3.5
- PMS: Support interrupt-driven PS2 Keyboard Interface - PMS: Support interrupt-driven PS2 Keyboard Interface
- D?M: Added NetBoot support for Duodyne - D?M: Added NetBoot support for Duodyne
- WBW: Add options to TUNE/HBIOS to force detection of MSX and RC AY/YM standard PSG ports - WBW: Add options to TUNE/HBIOS to force detection of MSX and RC AY/YM standard PSG ports
- MAP: Added /B=OPTIONS for automated drive assignment to ASSIGN.COM
Version 3.4 Version 3.4
----------- -----------

483
Source/Apps/assign/assign.asm

@ -11,6 +11,8 @@
; ex: ASSIGN (display all active drive assignments) ; ex: ASSIGN (display all active drive assignments)
; ASSIGN /? (display version and usage) ; ASSIGN /? (display version and usage)
; ASSIGN /L (display all possible devices) ; ASSIGN /L (display all possible devices)
; ASSIGN /B=OPTS (perform assignment based on options)
; ASSIGN C: (display assignment for C:)
; ASSIGN C:=D: (swaps C: and D:) ; ASSIGN C:=D: (swaps C: and D:)
; ASSIGN C:=FD0: (assign C: to floppy unit 0) ; ASSIGN C:=FD0: (assign C: to floppy unit 0)
; ASSIGN C:=IDE0:1 (assign C: to IDE unit0, slice 1) ; ASSIGN C:=IDE0:1 (assign C: to IDE unit0, slice 1)
@ -33,6 +35,7 @@
; 2023-06-19 [WBW] Update for revised DIODEVICE API ; 2023-06-19 [WBW] Update for revised DIODEVICE API
; 2023-09-19 [WBW] Added CHUSB & CHSD device support ; 2023-09-19 [WBW] Added CHUSB & CHSD device support
; 2023-10-13 [WBW] Fixed DPH creation to select correct DPB ; 2023-10-13 [WBW] Fixed DPH creation to select correct DPB
; 2024-12-17 [MAP] Added new /B=opt feaure to assign drives
;_______________________________________________________________________________ ;_______________________________________________________________________________
; ;
; ToDo: ; ToDo:
@ -52,6 +55,7 @@ bnksel .equ $FFF3 ; HBIOS bank select vector
stamp .equ $40 ; loc of RomWBW CBIOS zero page stamp stamp .equ $40 ; loc of RomWBW CBIOS zero page stamp
; ;
#include "../../ver.inc" #include "../../ver.inc"
#include "../../HBIOS/hbios.inc"
; ;
;=============================================================================== ;===============================================================================
; Code Section ; Code Section
@ -253,7 +257,7 @@ initcpm3:
; switch to sysbnk ; switch to sysbnk
ld a,($FFE0) ; get current bank ld a,($FFE0) ; get current bank
push af ; save it push af ; save it
ld bc,$F8F2 ; HBIOS Get Bank Info
ld bc,BC_SYSGET_BNKINFO ; HBIOS Get Bank Info
rst 08 ; call HBIOS, E=User Bank rst 08 ; call HBIOS, E=User Bank
ld a,e ; HBIOS User Bank ld a,e ; HBIOS User Bank
call bnksel ; HBIOS BNKSEL call bnksel ; HBIOS BNKSEL
@ -399,6 +403,8 @@ option:
ld a,(hl) ; get it ld a,(hl) ; get it
cp '?' ; is it a '?' as expected? cp '?' ; is it a '?' as expected?
jp z,usage ; yes, display usage jp z,usage ; yes, display usage
cp 'B' ; assign Boot Hard Drive Slices
jp z,bootdr ; yes, assign boot drive slices
cp 'L' ; is it a 'L', display device list? cp 'L' ; is it a 'L', display device list?
jp z,devlist ; yes, display device list jp z,devlist ; yes, display device list
jp errprm ; anything else is an error jp errprm ; anything else is an error
@ -438,8 +444,7 @@ devlist:
or a ; set flags or a ; set flags
jr nz,devlstu ; do UNA mode dev list jr nz,devlstu ; do UNA mode dev list
; ;
ld b,$F8 ; hbios func: sysget
ld c,$10 ; sysget subfunc: diocnt
ld bc,BC_SYSGET_DIOCNT ; hbios func: sysget subfunc: diocnt
rst 08 ; call hbios, E := device count rst 08 ; call hbios, E := device count
ld b,e ; use device count for loop count ld b,e ; use device count for loop count
ld c,0 ; use C for device index ld c,0 ; use C for device index
@ -486,6 +491,423 @@ devlstu1:
djnz devlstu1 ; loop as needed djnz devlstu1 ; loop as needed
ret ; return ret ; return
; ;
; -------------------------------------------------
; /B=XXX - Bootup drive Assignment
;
; Variable used across the entire bootdr: function
; - (mapwrk) working table of assignments
; - (mapadr) pointer to next drive assignment in mapwrk
; - (dstdrv) Drive letter of next assigment 0-15
; - (tmpstr) List of Option letters being processed
;
bootdr:
; command line processing mapping options into (tmpstr)
inc hl ; next char after the /B expect a delimeter
call nonblank ; skip ws
cp '='
inc hl
call nonblank ; skip ws
call getalpha ; options string into (tmpstr)
;
; defaulting loop for normal disk boot starting at A:
ld hl,mapwrk ; DE := working drive map
ld (mapadr),hl ; save pointer o next drive maping
xor a ; next dest drive letter start at A:
ld (dstdrv),a
bootdr1:
; process next letter in the cmd line options
ld a,(tmpstr) ; next letter
res 5,a ; FORCE UPPERCASE (IMPERFECTLY)
; Case Statement
ld hl,bootdr2 ; return address for below JP
push hl ; when RET from below JP, return
cp 'A'
jp z,bootdra ; RAM
cp 'B'
jp z,bootdrb ; BOOT
cp 'F'
jp z,bootdrf ; FLOPPY
cp 'H'
jp z,bootdrh ; HARD DRIVES (improved)
cp 'L'
jp z,bootdrl ; HARD DRIVES (legacy)
cp 'O'
jp z,bootdro ; ROM
cp 'P'
jp z,bootdrp ; PRESERVE/KEEP (SKIP)
cp 'S'
jp z,bootdrs ; SLICES (OFF BOOT DRIVE)
cp 'X'
jp z,bootdrx ; UNASSIGN
cp 'Z'
jp z,bootdrz ; UNASSIGN ALL REMAINING
; no valid option was found just ignore and continue
; potentially signal an error
pop hl ; remove the return address, since no match
bootdr2:
jr c,bootdr4 ; if overflowed, exhaused drives then error
; bump to next letter in tmp str, by shifing string left in buffer
ld hl,tmpstr+1 ; copy from +1 in buffer
ld a,(hl) ; copy next char for Z check
ld de,tmpstr ; copy down to +0 in buffer
ld bc,16 ; buffer is 16 bytes
ldir
or a ; set flags based on next char
jr nz,bootdr1 ; loop if character found
bootdr3:
xor a ; success
ret ; finished
bootdr4:
or $ff ; failure
ret ; finished
;
; -------------------------------------------------
; /B=XXX AGORITHMS START HERE
;
; PRESERVE, SKIP 1, JUST LOOP
bootdrp:
call bootinc ; Skip to next drive letter
ret ; Finished
;
; EXCLUDE / UNASSIGNED / GAP
bootdrx:
ld a,$FF ; $FF (unit) signal a drive not assigned
ld (unit),a ; set unit
xor a ; slice 0
ld (slice),a ; save as slice to assign.
call bootadd ; assign the slice
ret ; Finished, returning error
;
; EXCLUDE / UNASSIGNED - ALL REMAINING
bootdrz:
ld a,$FF ; $FF (unit) signal a drive not assigned
ld (unit),a ; set unit
xor a ; slice 0
ld (slice),a ; save as slice to assign.
bootdrz1:
call bootadd ; assign the slice
jr nc,bootdrz1 ; NC still can continue to allocate
xor a ; success
ret ; Finished
;
; BOOT DRIVE
bootdrb:
ld bc,BC_SYSGET_BOOTINFO ; HBIOS SysGet; BootInfo
rst 08 ; Get boot disk unit/slice in DE
ld a,d ; boot unit id returned in D
ld (unit),a ; save as unit number
ld a,e ; boot slice returned in E
ld (slice),a ; save as slice to assign.
call bootadd ; add the boot drive slice
ret ; Finished, returning error
;
; RAM DRIVE
bootdra:
ld a,$FF ; specific mask to include all BITS
ld (atrmask),a ; mask for device attributes
ld a,%00010101 ; specific mask for RAM DRIVE.
ld (atrcomp),a ; compare to after mask
call bootadds ; do single slice assignment
ret ; Finished, returning error
;
; ROM DRIVE
; Note: if MDFFENABLE is enabled, this wont select the ROM since the
; driver returns MD_AFSH (%00010111), and we cannot generalise this mask
bootdro:
ld a,$FF ; specific mask to include all BITS
ld (atrmask),a ; mask for device attributes
ld a,%00010100 ; specific mask for ROM drive. "MD_AROM"
ld (atrcomp),a ; compare to after mask
call bootadds ; do single slice assignment
; possible workaround below, not elegant. other woraround is to have a specific option for this code
; Better option is change the definitions for device attribute media types to
; 4=ROM, 5=RAM, 6=FLASH, 7=RAMF, (6,7 swapped) so much easir to mask RAM/ROM as only 1 bit difference
; ld a,%00010111 ; specific mask for ROM drive. "MD_AFSH"
; ld (atrcomp),a ; compare to after mask
; call bootadds ; do single slice assignment
ret ; Finished, returning error
;
; FLOPPY DRIVE(S)
bootdrf:
ld a,%11000000 ; device parameters (Removable Floppy)
ld (atrmask),a ; mask for device attributes
ld (atrcomp),a ; compare to after mask
call bootadds ; do single slice assignment
ret ; Finished, returning error
;
; SLICES (From Boot Drive Only)
bootdrs:
; find the boot drive, save unit /slice number
ld a,(mapwrk) ; boot drive unit number
ld (unit),a ; save as unit number to assign
ld a,0 ; starting slice number
bootdrs1:
; A is next slice to assign when entering here
ld (slice),a ; save as slice to assign.
call bootadd ; add the slice, return Z - past the last drive
jr c,bootdrs2 ; drives exhaused, finish up
ld a,(slice) ; get the slice just consumed
inc a ; next slice
JR bootdrs1 ; loop round
bootdrs2:
xor a ; success
ret
;
; HARD DRIVE(S) - Improved from CBIOS - More Drives
bootdrh:
ld a,%00100000 ; device parameters (High Capacity)
ld (atrmask),a ; mask for device attributes
ld (atrcomp),a ; compare to after mask
; count the number of drives matching criteria
call bootcnt ; return Drive count in A
; compute Slices per volume from drv count in A
call bootdrh1 ; return SPV in A
ld (slicec),a ; slice per volume count
; do the drive assignment
call bootaddn ; do the drive assignment
ret ; Finished returning error
;
; Input A contains device count return SPV (slices per volume) in A
bootdrh1:
ld e,a ; divide by by e, the number of devices
ld a,(dstdrv) ; next destination drive to map, 0-15
ld d,a ; put it in d
ld a,16 ; total number of drives
sub d ; less assigned = remaining
ld d,a ; divides d - remaing drives
; The following routine divides d by e and places the quotient in d and the remainder in a
; https://wikiti.brandonw.net/index.php?title=Z80_Routines:Math:Division
xor a
ld b, 8
bootdrh2:
sla d
rla
cp e
jr c, $+4
sub e
inc d
djnz bootdrh2
ld a,d ; end of the division the quotiant in A
ret ; return it
;
; HARD DRIVE(S) - Legacy (from CBIOS)
bootdrl:
ld a,%00100000 ; device parameters (High Capacity)
ld (atrmask),a ; mask for device attributes
ld (atrcomp),a ; compare to after mask
;
; count the number of drives matching criteria
call bootcnt ; return Drive count in A
;
; compute Slices per volume from drv count in A
call bootdrl1 ; return SPV in A
ld (slicec),a ; slice per volume count
;
; do the drive assignment
call bootaddn ; do the drive assignment
xor a ; Success
ret ; Finished
;
; Input A contains device count return SPV (slices per volume) in A
bootdrl1:
ld e,8 ; ASSUME 8 SLICES PER VOLUME
dec a ; DEC ACCUM TO CHECK FOR COUNT = 1
jr z,bootdrl2 ; YES, SKIP AHEAD TO IMPLEMENT 8 HDSPV
ld e,4 ; NOW ASSUME 4 SLICES PER VOLUME
dec a ; DEC ACCUM TO CHECK FOR COUNT = 2
jr z,bootdrl2 ; YES, SKIP AHEAD TO IMPLEMENT 4 HDSPV
ld e,2 ; IN ALL OTHER CASES, WE USE 2 HDSPV
bootdrl2:
ld a,e
ret
;
; -------------------------------------------------
; /B=XXX - General Purpose Functions
;
; Count Number of Devices
; (atrmask) mask the device attribtes
; (atrcomp) compare to set zero flag
; return A number of drives mathing the attributes
bootcnt
; loop thru hbios units looking for device type/unit match
ld bc,BC_SYSGET_DIOCNT ; hbios func: sysget subfunc: diocnt
rst 08 ; call hbios, E := device count
ld b,e ; use device count for loop count
ld c,0 ; use C for device index C = 0
ld l,0 ; will contain the drive count
bootcnt1:
call bootmat ; perform the match on device C, Z if match
jr nz,bootcnt2 ; not matching, skip and continue loop
inc l ; same so incrment the counter
bootcnt2:
inc c ; next drive letter
djnz bootcnt1 ; loop
ld a,l ; return the count in A register
or a ; ensure registers are set correctly
ret ; Finished
;
; Loop though all devices add a single slice based on device attributes
; See method below for documentation. Noting (slice) is defaulted to 1
bootadds
ld a,1
ld (slicec),a
; fall through to bootaddn
;
; Loop though all devices add N slice(s) based on device attributes
; (atrmask) mask the device attribtes
; (atrcomp) compare to set zero flag
; (slicec) number of slices
; return C flag
; C have expended all drives
; NC still can continue to allocate
; Z otherwise successfully completed
bootaddn
; loop thru hbios units looking for device type/unit match
ld bc,BC_SYSGET_DIOCNT ; hbios func: sysget subfunc: diocnt
rst 08 ; call hbios, E := device count
ld b,e ; use device count for loop count
ld c,0 ; use C for device index C = 0
bootaddn1:
call bootmat ; perform the match on device C, Z if match
jr nz,bootaddn4 ; not same skip volume, continue loop
; save the disk unit
ld a,c ; get the unit id back into A
ld (unit),a ; unit to add, if we add it.
; setup inner loop
push bc ; save loop control for outer loop
ld a,(slicec) ; count of slices to assign
ld b,a ; use device count for loop count
ld c,0 ; use C for slice index slice = 0
bootaddn2:
; entering here C contains updated slice
ld a,c ; slice number
ld (slice),a ; slice number
; assign the slice and loop
push bc ; save loop control
call bootadd ; add the slice
pop bc ; restore loop
jr c,bootaddn3 ; if bootadd, ran out of drives to allocate
inc c ; next slice
djnz bootaddn2 ; inner loop
bootaddn3:
; finish inner loop for next disk unit
pop bc ; restore loop control for outer
ret c ; return if no drives left to allocate
bootaddn4:
; continue looping to next unit
inc c ; next device
djnz bootaddn1 ; outer loop
xor a ; success
ret ; Finished
;
; Add a Single Drive.
; based on (unit) and (slice) variables
; This routine will skip if drive already assigned
; return C flag
; C have expended all drives
; NC still can continue to allocate
bootadd:
; check we are not already past last (P:) drive
ld hl,dstdrv ; destination drive
ld a,15
cp (hl) ; C set if >= 16
ret c ; Return with carry, cannot assign.
; do we need to perform duplicate check
ld a,(dstdrv) ; next destination drive to map, could be A: (=0)
or a ; is it A:
jr z,bootadd1 ; nothing to check we are assigning the A: drive
; perform duplicate check before assignment
ld b,a ; B number of entries to check
ld hl,mapwrk ; HL point to working drive map table to compare to
ld de,unit ; DE comparison, unit/slice are ordered (psudo mapwrk entry)
call valid3 ; perform a duplicate check (REUSED)
jr z,bootinc1 ; Z - found a duplicate, exit out
;
bootadd1:
; actually assign it.
ld hl,(mapadr) ; address of next map entry in table
ld a,(unit) ; the unit number
ld (hl), a ; write unit number to Table
inc hl
ld a,(slice) ; the slice
ld (hl), a ; write slice to the table
; show the new assignment
push bc
push de
ld a,(dstdrv) ; destination drive
call showone ; show it's new value
pop de
pop bc
; signal the change has occured
ld hl,modcnt ; point to mod count
inc (hl) ; increment it
; fall through to bootinc and inc target drive
;
; Increment to the next drive (A-P)
; return C flag
; C have expended all drives
; NC still can continue to allocate
bootinc:
; check we are not already past last (P:) drive
ld hl,dstdrv ; destination drive
ld a,15
cp (hl) ; C set if >= 16
ret c ; Return with carry, cannot increment.
; actually increment it
inc (hl) ; increment destination drive (A-P)
ld hl,(mapadr) ; address in working assignment table (mapwrk)
ld bc,4
add hl,bc
ld (mapadr),hl ; move address to next location in map
bootinc1:
ld hl,dstdrv ; destination drive
ld a,15
cp (hl) ; C set if >= 16
ret
;
; Does Disk Unit Meet matching Criteria
; pass in C which is the unit, ret Z if matching:
; * (atrmask) mask the device attribtes
; * (atrcomp) compare to set zero flag
; registers BC DE HL are preserved
bootmat:
push hl
push de
push bc ; preserve
; get the disk unit attributes
ld b,BF_DIODEVICE ; hbios func: diodevice C:= DISK UNIT
rst 08 ; call hbios, C := device attributes
; do the attribute comparison
ld a,(atrmask) ; attribute bit mask
and c ; mask with device attributes from hbios
ld c,a ; move value back to c
ld a,(atrcomp) ; value parameter to compare with
cp c ; do the comparison : Z if matching
jr nz,bootmat3 ; not matching, just return, NZ go no further
; Attributes match - did caller request high capacity device
bit 5,a ; high capacity flag passed in (atrcomp)
jr NZ,bootmat1 ; IF hig capacity, test if hd is onlne
; Attributes match - but NOT high capacity
xor a ; Result = Z
jr bootmat3 ; and return
bootmat1:
; Attributes match - and IS high capacity
pop bc ; get C para back (unit)
push bc
; Sense Media
ld b,BF_DIOMEDIA ; HBIOS FUNC: SENSE MEDIA
ld e,1 ; PERFORM MEDIA DISCOVERY
rst 08 ; DO IT
; returns NZ if error (no media), and Z if no error (media detected)
; can just return this flag
bootmat3:
pop bc
pop de
pop hl ; restore and return
ret
;
; ----------------------------------------------------------------
;
; Install the new drive map into CBIOS ; Install the new drive map into CBIOS
; ;
install: install:
@ -653,7 +1075,7 @@ makdphuna1: ; handle ram/rom
makdphwbw: ; determine appropriate dpb (WBW mode, unit number in A) makdphwbw: ; determine appropriate dpb (WBW mode, unit number in A)
; ;
ld c,a ; unit number to C ld c,a ; unit number to C
ld b,$17 ; HBIOS: Report Device Info
ld b,BF_DIODEVICE ; HBIOS: Report Device Info
rst 08 ; call HBIOS, return w/ device type in D, physical unit in E rst 08 ; call HBIOS, return w/ device type in D, physical unit in E
ld a,d ; device type to A ld a,d ; device type to A
cp $00 ; ram/rom? cp $00 ; ram/rom?
@ -751,7 +1173,7 @@ instcpm3:
; swicth to sysbnk ; swicth to sysbnk
ld a,($FFE0) ; get current bank ld a,($FFE0) ; get current bank
push af ; save it push af ; save it
ld bc,$F8F2 ; HBIOS Get Bank Info
ld bc,BC_SYSGET_BNKINFO ; HBIOS Get Bank Info
rst 08 ; call HBIOS, E=User Bank rst 08 ; call HBIOS, E=User Bank
ld a,e ; HBIOS User Bank ld a,e ; HBIOS User Bank
call $FFF3 ; HBIOS BNKSEL call $FFF3 ; HBIOS BNKSEL
@ -764,7 +1186,6 @@ instcpm3:
ld l,a ; ... ld l,a ; ...
ld (dphadr),hl ; save starting dphadr ld (dphadr),hl ; save starting dphadr
ld hl,(drvtbl) ; get drive table in HL ld hl,(drvtbl) ; get drive table in HL
ld de,mapwrk ; DE := working drive map ld de,mapwrk ; DE := working drive map
ld b,16 ld b,16
@ -905,6 +1326,14 @@ valid2: ; setup for inner loop
call addhl ; point to entry following call addhl ; point to entry following
pop de ; de points to comparison entry pop de ; de points to comparison entry
; ;
; Scan for a match in (mapwrk)
; The following comparison code is called elsewhere, not just from above
; (please respect the contract)
; hl : pointer to start of items to scan check in map
; de is the invarient (fixed) entry in the table to compare against
; b : is the number of items to check
; return Z - Found a duplicate comparison=0
; return NZ - No Matches found (a=$ff)
valid3: ; inner loop valid3: ; inner loop
; bypass unassigned drives (only need to test 1) ; bypass unassigned drives (only need to test 1)
ld a,(hl) ; get first drive unit in A ld a,(hl) ; get first drive unit in A
@ -981,7 +1410,7 @@ drvswap:
ld a,(srcdrv) ; get the source drive ld a,(srcdrv) ; get the source drive
call chkdrv ; valid drive? call chkdrv ; valid drive?
ret nz ; abort if not ret nz ; abort if not
ld hl,(drives) ; load source/dest in DE
ld hl,(drives) ; load source/dest in HL
ld a,h ; put source drive num in a ld a,h ; put source drive num in a
cp l ; compare to the dest drive num cp l ; compare to the dest drive num
jp z,errswp ; Invalid swap request, src == dest jp z,errswp ; Invalid swap request, src == dest
@ -1070,14 +1499,13 @@ drvmap2:
ld (device),a ; save as device id ld (device),a ; save as device id
; ;
; loop thru hbios units looking for device type/unit match ; loop thru hbios units looking for device type/unit match
ld b,$F8 ; hbios func: sysget
ld c,$10 ; sysget subfunc: diocnt
ld bc,BC_SYSGET_DIOCNT ; hbios func: sysget subfunc: diocnt
rst 08 ; call hbios, E := device count rst 08 ; call hbios, E := device count
ld b,e ; use device count for loop count ld b,e ; use device count for loop count
ld c,0 ; use C for device index ld c,0 ; use C for device index
drvmap3: drvmap3:
push bc ; preserve loop control push bc ; preserve loop control
ld b,$17 ; hbios func: diodevice
ld b,BF_DIODEVICE ; hbios func: diodevice
rst 08 ; call hbios, D := device, E := unit rst 08 ; call hbios, D := device, E := unit
pop bc ; restore loop control pop bc ; restore loop control
ld a,(device) ld a,(device)
@ -1206,12 +1634,12 @@ showall:
ld b,16 ; 16 drives possible ld b,16 ; 16 drives possible
ld c,0 ; map index (drive letter) ld c,0 ; map index (drive letter)
; ;
ld a,b ; load count
or $FF ; signal no action
ret z ; bail out if zero
; ld a,b ; load count
; or $FF ; signal no action
; ret z ; bail out if zero
; ;
showall1: ; loop showall1: ; loop
ld a,c ;
; ld a,c ;
push bc ; save loop control push bc ; save loop control
call showass call showass
pop bc ; restore loop control pop bc ; restore loop control
@ -1226,8 +1654,9 @@ showall1: ; loop
showass: showass:
; ;
; setup HL to point to desired entry in table ; setup HL to point to desired entry in table
ld c,a ; save incoming drive in C
; ld c,a ; save incoming drive in C
ld hl,mapwrk ; HL = address of drive map ld hl,mapwrk ; HL = address of drive map
ld a,c
rlca rlca
rlca rlca
call addhl ; HL = address of drive map table entry call addhl ; HL = address of drive map table entry
@ -1301,7 +1730,7 @@ prtdev:
or a ; set flags or a ; set flags
ld a,e ; put device num back ld a,e ; put device num back
jr nz,prtdevu ; print device in UNA mode jr nz,prtdevu ; print device in UNA mode
ld b,$17 ; hbios func: diodevice
ld b,BF_DIODEVICE ; hbios func: diodevice
ld c,a ; unit to C ld c,a ; unit to C
rst 08 ; call hbios, D := device, E := unit rst 08 ; call hbios, D := device, E := unit
push de ; save results push de ; save results
@ -1389,15 +1818,14 @@ chkdrv:
; ;
chkdev: ; HBIOS variant chkdev: ; HBIOS variant
push af ; save incoming unit push af ; save incoming unit
ld b,$F8 ; hbios func: sysget
ld c,$10 ; sysget subfunc: diocnt
ld bc,BC_SYSGET_DIOCNT ; hbios func: sysget subfunc: diocnt
rst 08 ; call hbios, E := device count rst 08 ; call hbios, E := device count
pop af ; restore incoming unit pop af ; restore incoming unit
cp e ; compare to unit count cp e ; compare to unit count
jp nc,errdev ; if too high, error jp nc,errdev ; if too high, error
; ;
; get device/unit info ; get device/unit info
ld b,$17 ; hbios func: diodevice
ld b,BF_DIODEVICE ; hbios func: diodevice
ld c,a ; unit to C ld c,a ; unit to C
rst 08 ; call hbios, C := device attributes rst 08 ; call hbios, C := device attributes
; ;
@ -1871,16 +2299,22 @@ drives:
dstdrv .db 0 ; destination drive dstdrv .db 0 ; destination drive
srcdrv .db 0 ; source drive srcdrv .db 0 ; source drive
device .db 0 ; source device device .db 0 ; source device
; note (unit and slice) need to be kept ordered since they are used
; in code forming a temp table entry (comparison purposes). See bootadd:
unit .db 0 ; source unit unit .db 0 ; source unit
slice .db 0 ; source slice slice .db 0 ; source slice
; ;
atrmask .db 0 ; device attributes mask before compare
atrcomp .db 0 ; device attributes compare to
slicec .db 1 ; number of slices to assign for each volume
;
unamod .db 0 ; $FF indicates UNA UBIOS active unamod .db 0 ; $FF indicates UNA UBIOS active
modcnt .db 0 ; count of drive map modifications modcnt .db 0 ; count of drive map modifications
; ;
srcptr .dw 0 ; source pointer for copy srcptr .dw 0 ; source pointer for copy
dstptr .dw 0 ; destination pointer for copy dstptr .dw 0 ; destination pointer for copy
tmpent .fill 4,0 ; space to save a table entry tmpent .fill 4,0 ; space to save a table entry
tmpstr .fill 9,0 ; temporary string of up to 8 chars, zero term
tmpstr .fill 17,0 ; temporary string of up to 16 chars, zero term
; ;
heaptop .dw 0 ; current address of top of heap memory heaptop .dw 0 ; current address of top of heap memory
heaplim .dw 0 ; heap limit address heaplim .dw 0 ; heap limit address
@ -1893,6 +2327,7 @@ scbop .db $FF ; set a byte
scbval .dw $FF ; value to set scbval .dw $FF ; value to set
; ;
mapwrk .fill (4 * 16),$FF ; working copy of drive map mapwrk .fill (4 * 16),$FF ; working copy of drive map
mapadr .dw mapwrk ; working pointer into mapwrk used by /B=
; ;
devtbl: ; device table devtbl: ; device table
.dw dev00, dev01, dev02, dev03 .dw dev00, dev01, dev02, dev03
@ -1936,17 +2371,19 @@ stack .equ $ ; stack top
; Messages ; Messages
; ;
indent .db " ",0 indent .db " ",0
msgban1 .db "ASSIGN v1.8 for RomWBW CP/M ",0
msgban1 .db "ASSIGN v1.9 for RomWBW CP/M ",0
msg22 .db "2.2",0 msg22 .db "2.2",0
msg3 .db "3",0 msg3 .db "3",0
msbban2 .db ", 13-Oct-2023",0
msbban2 .db ", 9-Dec-2024",0
msghb .db " (HBIOS Mode)",0 msghb .db " (HBIOS Mode)",0
msgub .db " (UBIOS Mode)",0 msgub .db " (UBIOS Mode)",0
msgban3 .db "Copyright 2023, Wayne Warthen, GNU GPL v3",0
msgban3 .db "Copyright 2024, Wayne Warthen, GNU GPL v3",0
msguse .db "Usage: ASSIGN D:[=[{D:|<device>[<unitnum>]:[<slicenum>]}]][,...]",13,10 msguse .db "Usage: ASSIGN D:[=[{D:|<device>[<unitnum>]:[<slicenum>]}]][,...]",13,10
.db " ex. ASSIGN (display all active assignments)",13,10 .db " ex. ASSIGN (display all active assignments)",13,10
.db " ASSIGN /? (display version and usage)",13,10 .db " ASSIGN /? (display version and usage)",13,10
.db " ASSIGN /L (display all possible devices)",13,10 .db " ASSIGN /L (display all possible devices)",13,10
.db " ASSIGN /B=OPTS (perform assignment based on options)",13,10
.db " ASSIGN C: (display assignment for C:)",13,10
.db " ASSIGN C:=D: (swaps C: and D:)",13,10 .db " ASSIGN C:=D: (swaps C: and D:)",13,10
.db " ASSIGN C:=FD0: (assign C: to floppy unit 0)",13,10 .db " ASSIGN C:=FD0: (assign C: to floppy unit 0)",13,10
.db " ASSIGN C:=IDE0:1 (assign C: to IDE unit0, slice 1)",13,10 .db " ASSIGN C:=IDE0:1 (assign C: to IDE unit0, slice 1)",13,10

Loading…
Cancel
Save