• IBM vdisk.asm (2/3)

    From T. Ment@21:1/5 to All on Tue Jun 23 03:10:55 2020
    [continued from previous message]

    DB 'Licensed Material - Program Property of IBM. '
    DB 'Author: Dick Dievendorff, '
    DB 'Rod Springhetti, & '
    DB 'David M. Sewell'

    MAXSEC_TRF DW 0 ;maximum number of sectors to transfer when
    ;in extended memory

    BUFF_SIZE DW 0 ;desired VDISK buffer size in kilobytes

    MIN_MEMORY_LEFT DW 64 ;minimum amount of system memory (kilobytes)
    ;that must remain after VDISK is installed

    FIRST_EM_SW DB ? ;0FFH if this is the first device driver
    ;to be installed in extended memory
    ;00H if another VDISK extended memory driver
    ;has been installed

    FIRST_VDISK DW ? ;segment address of 1st VDISK device driver PARA_PER_KB DW 1024/PARA_SIZE ;paragraphs in one kilobyte
    C1024 DW 1024 ;bytes in one kilobyte
    DIRE_SIZE DW DIR_ENTRY_SIZE ;bytes in one directory entry
    DIR_SECTORS DW ? ;number of sectors of directory

    ERR_FLAG DB 0 ;error indicators to condition messages ERR_BSIZE EQU 80H ;buffer size adjusted
    ERR_SSZ EQU 40H ;sector size adjusted
    ERR_DIRN EQU 20H ;number of directory entries adjusted
    ERR_PASS EQU 10H ;some adjustment made that requires
    ;recomputation of values previously computed ERR_SSZB EQU ERR_SSZ+ERR_PASS ;sector size altered this pass ERR_SYSSZ EQU 08H ;system storage too small for VDISK
    ERR_SWTCH EQU 04H ;invalid switch character
    ERR_EXTSW EQU 02H ;extender card switches don't match memory size ERR_ESIZE EQU 01H ;Transfer size adjusted

    ; additional errors added - kwc

    major_version equ 4 ;Major DOS version
    minor_version equ 00 ;Minor DOS Version

    expected_version equ (MINOR_VERSION SHL 8)+MAJOR_VERSION

    err_flag2 db 0
    err_baddos equ 01h ; Invalid DOS Version

    SUBTTL Initialization, Part one
    PAGE ;-----------------------------------------------------------------------;
    ; Command Code 0 - Initialization ;
    ; At entry, DS:BX point to request header, AX = 0 ; ;-----------------------------------------------------------------------; ;Initialization is divided into two parts.
    ;This part, executed first, is later overlaid by the VDISK buffer.

    INIT_P1 PROC ;first part of initialization
    MOV DX,SS ;save stack segment register
    MOV CX,SP ;save stack pointer register
    CLI ;inhibit interrupts while changing SS:SP
    MOV AX,CS ;move CS to SS through AX
    MOV SS,AX
    MOV SP,OFFSET MSGEND ;end of VDISKMSG
    ADD SP,STACK_SIZE ;+ length of our stack
    STI ;allow interrupts
    PUSH DX ;save old SS register on new stack
    PUSH CX ;save old SP register on new stack

    push bx ;secure registers before DOS int
    push cx ;secure registers before DOS int

    ; add version check - kwc

    mov ah,030h
    int 21h
    pop cx ;restore pointer values
    pop bx ;restore pointer values
    cmp ax,expected_version
    je okdos

    or cs:err_flag2,err_baddos

    okdos:
    CALL GET_PARMS ;get parameters from CONFIG.SYS line

    PUSH CS
    POP DS ;set DS = CS
    ASSUME DS:CSEG

    CALL APPLY_DEFAULTS ;supply any values not specified
    CALL DETERMINE_START ;compute start address of VDISK buffer
    CALL VALIDATE ;validate parameters
    CALL COPY_BPB ;Copy BIOS Parameter Block to boot record

    CALL VERIFY_EXTENDER ;Verify that extender card switches are right

    TEST ERR_FLAG,ERR_EXTSW ;are switches wrong?
    JNZ INIT_P1_A ;if so, exit with messages

    test CS:err_flag2,err_baddos
    jnz init_p1_a

    CMP EM_SW,0 ;extended memory requested?
    JE INIT_P1_A ;jump if not

    TEST ERR_FLAG,ERR_SYSSZ ;is system too small for VDISK?
    JNZ INIT_P1_A ;if so, don't do extended memory init

    CALL UPDATE_AVAIL ;update AVAIL_HI and AVAIL_LO to reflect
    ;addition of extended memory VDISK
    CALL FORMAT_VDISK ;construct a boot record, FATs and
    ;directory in storage immediately
    ;following this device driver
    CALL MOVE_VDISK ;move formatted boot record, FATs,
    ;and directory to extended memory
    CALL UPDATE_BOOT ;place the end address of ALL VDISKs
    ;in the boot record of the first VDISK
    CMP FIRST_EM_SW,0 ;is this the first extended memory VDISK?
    JE INIT_P1_A ;no, exit

    CALL STEAL_INT19 ;point INT 19H to this VDISK
    INIT_P1_A:
    CALL FILL_RH ;fill in INIT request header
    CALL WRITE_MESSAGES ;display all messages
    POP CX ;get old SP from stack
    POP DX ;get old SS from stack
    CLI ;disable interrupts while changing SS:SP
    MOV SS,DX ;restore stack segment register
    MOV SP,CX ;restore stack pointer register
    STI ;enable interrupts ;-----------------------------------------------------------------------;
    ; INIT_P2 must be short enough to fit into the boot sector ;
    ; (minimum size of boot sector is 128 bytes), so we set up ;
    ; as many pointers as we can to help keep INIT_P2 short. ;
    ; ;
    ; ES:DI = storage address of first FAT sector ;
    ; BL = media control byte ;
    ; CX = number of FAT copies ;
    ; DX = number of bytes in one FAT, less 3 ;
    ; SI = offset of VOL label field ; ;-----------------------------------------------------------------------;
    MOV ES,START_BUFFER_PARA ;start paragraph of VDISK buffer

    MOV AX,BPB_RES ;number of reserved sectors
    MUL BPB_SSZ ;* sector size
    MOV DI,AX ;ES:DI point to FAT start

    MOV BL,BPB_MCB ;media control byte

    MOV CL,BPB_FATN ;number of FAT copies
    XOR CH,CH

    MOV AX,BPB_FATSZ ;FAT size in sectors
    MUL BPB_SSZ ;* sector size = total FAT bytes

    SUB AX,3 ;-3 (FEFFFF stored by code)
    MOV DX,AX

    MOV SI,OFFSET VOL_LABEL ;point to VOL label directory entry
    JMP INIT_P2 ;jump to second part of initialization
    ;this is redundant if the VDISK is in
    ;extended memory, but is executed anyway

    SUBTTL GET_PARMS Parameter Line Scan
    PAGE ;-----------------------------------------------------------------------; ;GET_PARMS gets the parameters from the CONFIG.SYS statement ;
    ; ; ;Register usage: ;
    ; DS:SI indexes parameter string ;
    ; AL contains character from parameter string ;
    ; CX value from GET_NUMBER ; ;-----------------------------------------------------------------------;
    ASSUME DS:NOTHING ;DS:BX point to Request Header
    GET_PARMS PROC ;get parameters from CONFIG.SYS line
    PUSH DS ;save DS
    LDS SI,RH.RH0_BPBA ;DS:SI point to all after DEVICE=
    ;in CONFIG.SYS line
    XOR AL,AL ;not at end of line

    ;Skip until first delimiter is found. There may be digits in the path string.

    ;DS:SI points to \pathstring\VDISK.SYS nn nn nn
    ;The character following VDISK.SYS may have been changed to a null (00H).
    ;All letters have been changed to uppercase.

    GET_PARMS_A: ;skip to DOS delimiter character
    CALL GET_PCHAR ;get parameter character into AL
    JZ GET_PARMS_X ;get out if end of line encountered
    OR AL,AL ;test for null
    JZ GET_PARMS_C ;
    CMP AL,' '
    JE GET_PARMS_C ;
    CMP AL,','
    JE GET_PARMS_C ;
    CMP AL,';'
    JE GET_PARMS_C ;
    CMP AL,'+'
    JE GET_PARMS_C ;
    CMP AL,'='
    JE GET_PARMS_C ;
    CMP AL,TAB
    JNE GET_PARMS_A ;skip until delimiter or CR



    GET_PARMS_C:
    PUSH SI ;save to rescan
    MOV CS:EM_SW,0 ;indicate no /E found
    JMP GET_SLASH ;see if current character is an slash

    GET_PARMS_D: ;scan for /
    CALL GET_PCHAR
    JZ GET_PARMS_B ;exit if end of line

    GET_SLASH: ;check for slash
    CMP AL,'/' ;found slash?
    JNE GET_PARMS_D ;no, continue scan

    CALL GET_PCHAR ;get char following slash
    CMP AL,'E' ;don't have to test for lower case E,
    ;letters have been changed to upper case
    JNE GET_PARMS_E ;not 'E'
    MOV CS:EM_SW,AL ;indicate /E found

    CALL GET_PCHAR ;get char following E
    CMP AL,':' ;is it a delimeter ?
    JNE GET_PARMS_D ;not a ':'


    CALL GET_MAXSIZE ;get maximum sector size


    JMP GET_PARMS_D ;continue forward scan

    GET_PARMS_E: ;/ found, not 'E'
    OR CS:ERR_FLAG,ERR_SWTCH ;indicate invalid switch character
    JMP GET_PARMS_D ;continue scan



    GET_PARMS_B: ;now pointing to first delimiter
    POP SI ;get pointer, used to rescan for /E
    XOR AL,AL ;not at EOL now
    CALL GET_PCHAR ;get first character
    CALL SKIP_TO_DIGIT ;skip to first digit
    JZ GET_PARMS_X ;found EOL, no digits remain

    CALL GET_NUMBER ;extract digits, convert to binary
    MOV CS:BUFF_SIZE,CX ;store buffer size

    CALL SKIP_TO_DIGIT ;skip to next digit
    JZ GET_PARMS_X ;found EOL, no digits remain

    CALL GET_NUMBER ;extract digits, convert to binary
    MOV CS:BPB_SSZ,CX ;store sector size

    CALL SKIP_TO_DIGIT ;skip to next digit
    JZ GET_PARMS_X ;found EOL, no digits remain

    CALL GET_NUMBER ;extract digits, convert to binary
    MOV CS:BPB_DIRN,CX ;store number of directory entries



    GET_PARMS_X: ;premature end of line
    POP DS ;restore DS
    RET



    GET_MAXSIZE PROC ;get maximum sector size

    CALL GET_PCHAR ;get next character
    CALL CHECK_NUM ;is it a number ?
    JZ GET_NEXTNUM ;yes, go get next number
    OR CS:ERR_FLAG,ERR_ESIZE ;indicate invalid sector size
    RET ;
    GET_NEXTNUM: ;get next number
    CALL GET_NUMBER ;extract digits and convert to binary
    MOV CS:MAXSEC_TRF,CX ;save maximum sector size to transfer
    RET
    GET_MAXSIZE ENDP



    GET_PCHAR PROC ;internal proc to get next character into AL
    CMP AL,CR ;carriage return already encountered?
    JE GET_PCHAR_X ;don't read past end of line
    CMP AL,LF ;line feed already encountered?
    JE GET_PCHAR_X ;don't read past end of line
    LODSB ;get char from DS:SI, increment SI
    CMP AL,CR ;is the char a carriage return?
    JE GET_PCHAR_X ;yes, set Z flag at end of line
    CMP AL,LF ;no, is it a line feed?
    GET_PCHAR_X: ;attempted read past end of line
    RET
    GET_PCHAR ENDP ;returns char in AL


    CHECK_NUM PROC ;check AL for ASCII digit
    CMP AL,'0' ;< '0'?
    JB CHECK_NUM_X ;exit if it is

    CMP AL,'9' ;> '9'?
    JA CHECK_NUM_X ;exit if it is

    CMP AL,AL ;set Z flag to indicate numeric
    CHECK_NUM_X:
    RET ;Z set if numeric, NZ if not numeric
    CHECK_NUM ENDP


    SKIP_TO_DIGIT PROC ;skip to first numeric character
    CALL CHECK_NUM ;is current char a digit?
    JZ SKIP_TO_DIGIT_X ;if so, skip is complete

    CALL GET_PCHAR ;get next character from line
    JNZ SKIP_TO_DIGIT ;loop until first digit or CR or LF
    RET ;character is CR or LF

    SKIP_TO_DIGIT_X:
    CMP AL,0 ;digit found, force NZ
    RET
    SKIP_TO_DIGIT ENDP

    C10 DW 10
    GN_ERR DB ? ;zero if no overflow in accumulation

    GET_NUMBER PROC ;convert string of digits to binary value
    XOR CX,CX ;accumulate number in CX
    MOV CS:GN_ERR,CL ;no overflow yet
    GET_NUMBER_A: ;accumulate next digit
    SUB AL,'0' ;convert ASCII to binary
    CBW ;clear AH
    XCHG AX,CX ;previous accumulation in AX, new digit in CL
    MUL CS:C10 ;DX:AX := AX*10
    OR CS:GN_ERR,DL ;set GN_ERR <> 0 if overflow
    ADD AX,CX ;add new digit from
    XCHG AX,CX ;number now in CX
    DEC SI ;back up to prior entry
    MOV AL,' ' ;blank out prior entry
    MOV [SI],AL ;
    INC SI ;set to current entry
    CALL GET_PCHAR ;get next character
    CALL CHECK_NUM ;see if it was numeric
    JZ GET_NUMBER_A ;continue accumulating
    CMP CS:GN_ERR,0 ;did we overflow?
    JE GET_NUMBER_B ;if not, we're done
    XOR CX,CX ;return zero (always invalid) if overflow GET_NUMBER_B:
    RET ;number in CX, next char in AL
    GET_NUMBER ENDP

    GET_PARMS ENDP

    SUBTTL APPLY_DEFAULTS
    PAGE ;-----------------------------------------------------------------------;
    ; APPLY_DEFAULTS supplies any parameter values that the user ;
    ; failed to specify ; ;-----------------------------------------------------------------------;
    ASSUME DS:CSEG
    APPLY_DEFAULTS PROC
    XOR AX,AX
    CMP BUFF_SIZE,AX ;is buffer size zero?
    JNE APPLY_DEFAULTS_A ;no, user specified something

    MOV BUFF_SIZE,DFLT_BSIZE ;supply default buffer size
    OR ERR_FLAG,ERR_BSIZE ;indicate buffersize adjusted

    APPLY_DEFAULTS_A:
    CMP BPB_SSZ,AX ;is sector size zero?
    JNE APPLY_DEFAULTS_B ;no, user specified something

    MOV BPB_SSZ,DFLT_SSZ ;supply default sector size
    OR ERR_FLAG,ERR_SSZ ;indicate sector size adjusted

    APPLY_DEFAULTS_B:
    CMP BPB_DIRN,AX ;are directory entries zero?
    JNE APPLY_DEFAULTS_C ;no, user specified something

    MOV BPB_DIRN,DFLT_DIRN ;supply default directory entries
    OR ERR_FLAG,ERR_DIRN ;indicate directory entries adjusted

    APPLY_DEFAULTS_C: ;
    CMP EM_SW,0 ;extended memory ?
    JE APPLY_DEFAULTS_D ;no, jump around
    CMP MAXSEC_TRF,AX ;is maximum sectors zero?
    JNE APPLY_DEFAULTS_D ;no, user specified something

    MOV MAXSEC_TRF,DFLT_ESS ;supply default maximum number of
    ;sector to transfer
    OR ERR_FLAG,ERR_ESIZE ;indicate transfer size adjusted APPLY_DEFAULTS_D:
    RET
    APPLY_DEFAULTS ENDP

    SUBTTL DETERMINE_START address of VDISK buffer
    PAGE ;-----------------------------------------------------------------------;
    ; DETERMINE_START figures out the starting address of the VDISK ;
    ; buffer ; ;-----------------------------------------------------------------------;
    ASSUME DS:CSEG
    DETERMINE_START PROC

    ;If extended memory is NOT being used, the VDISK buffer immediately
    ;follows the resident code.

    ;If extended memory IS being used, START_BUFFER_PARA becomes the
    ;end of device driver address passed back to DOS.

    MOV AX,CS ;start para of VDISK code
    ADD AX,VDISKP ;+ length of resident code
    MOV START_BUFFER_PARA,AX ;save as buffer start para

    CMP EM_SW,0 ;is extended memory requested?
    JE DETERMINE_START_X ;if not, we're done here

    ;If this is the first extended memory VDISK device driver to be installed,
    ;the start address for I/O is 1 megabyte.

    ;If one or more extended memory VDISK device drivers have been installed,
    ;the start address for I/O for THIS device driver is acquired from the
    ;fields AVAIL_LO and AVAIL_HI in the FIRST VDISK device driver.

    ;The first extended memory VDISK device driver is located by INT 19H's vector.

    MOV FIRST_EM_SW,0FFH ;indicate first VDISK device driver
    MOV FIRST_VDISK,CS ;segment addr of first VDISK

    PUSH DS ;preserve DS
    XOR AX,AX
    MOV DS,AX ;set DS = 0
    ASSUME DS:INT_VEC

    MOV AX,DS:BOOT_VECS ;get segment addr of INT 19H routine
    MOV DS,AX ;to DS
    ASSUME DS:NOTHING

    PUSH CS
    POP ES ;set ES = CS
    MOV SI,OFFSET VOL_LABEL ;DS:SI point to VOL label field
    ;in first VDISK (if present)
    MOV DI,SI ;ES:DI point to VOL label field of
    ;this VDISK

    MOV CX,VOL_LABEL_LEN ;length of volume label
    REP CMPSB ;does INT 19H vector point to a VDISK
    ;device driver?
    JNE DETERMINE_START_A ;jump if this is the first VDISK

    ;Another extended memory VDISK device driver has been installed.
    ;Its AVAIL_LO and AVAIL_HI are the first free byte of extended memory.

    MOV CS:FIRST_EM_SW,0 ;indicate not first device driver
    MOV CS:FIRST_VDISK,DS ;save pointer to 1st device driver

    ;Copy AVAIL_LO and AVAIL_HI from first VDISK to this VDISK

    MOV SI,OFFSET AVAIL_LO ;DS:SI point to AVAIL_LO in first VDISK
    MOV DI,SI ;ES:DI point to AVAIL_LO in this VDISK
    MOVSW ;copy AVAIL_LO from first to this VDISK
    MOVSB ;copy AVAIL_HI

    DETERMINE_START_A: ;copy AVAIL_LO and AVAIL_HI to START_EM
    POP DS ;set DS = CS

    MOV SI,OFFSET AVAIL_LO ;source offset
    MOV DI,OFFSET START_EM_LO ;destination offset

    MOVSW ;move AVAIL_LO to START_EM_LO
    MOVSB ;move AVAIL_HI to START_EM_HI DETERMINE_START_X:
    RET
    DETERMINE_START ENDP

    SUBTTL VALIDATE parameters
    PAGE ;-----------------------------------------------------------------------;
    ; VALIDATE adjusts parameters as necessary ; ;-----------------------------------------------------------------------; VAL_SSZ_TBL LABEL WORD ;table of valid sector sizes
    VAL_SSZ_S DW 128 ;smallest valid sector size
    DW 256
    VAL_SSZ_L DW 512 ;largest valid sector size
    VAL_SSZ_N EQU ($-VAL_SSZ_TBL)/2 ;number of table entries

    ASSUME DS:CSEG
    VALIDATE PROC ;validate parameters
    MOV BPB_AUSZ,1 ;initial allocation unit is 1 sector

    CALL VAL_BSIZE ;validate buffer size

    CALL VAL_SSZ ;validate (adjust if necessary) BPB_SSZ

    VALIDATE_A:
    AND ERR_FLAG,255-ERR_PASS ;indicate nothing changed this pass

    MOV AX,BPB_SSZ ;sector size
    CWD ;clear DX for division
    DIV WPARA_SIZE ;sector size/para size
    MOV PARAS_PER_SECTOR,AX ;number of paragraphs/sector

    MOV AX,BUFF_SIZE ;requested buffersize in KB
    MUL C1024 ;DX:AX = buffer size in bytes
    DIV BPB_SSZ ;/sector size = # sectors
    MOV BPB_SECN,AX ;store number of sectors

    CALL VAL_DIRN ;validate number of directory entries

    TEST ERR_FLAG,ERR_PASS ;may have reset sector size
    JNZ VALIDATE_A ;recompute directory & FAT sizes

    CALL VAL_FAT ;compute FAT entries, validity test

    TEST ERR_FLAG,ERR_PASS ;if cluster size altered this pass
    JNZ VALIDATE_A ;recompute directory & FAT sizes

    ;Make certain buffer size is large enough to contain:
    ; boot sector(s)
    ; FAT sector(s)
    ; directory sector(s)
    ; at least 1 data cluster

    MOV AL,BPB_FATN ;number of FAT copies
    CBW ;clear AH
    MUL BPB_FATSZ ;* sectors for 1 FAT = FAT sectors
    ADD AX,BPB_RES ;+ reserved sectors
    ADD AX,DIR_SECTORS ;+ directory sectors
    MOV CL,BPB_AUSZ ;get sectors/cluster
    XOR CH,CH ;CX = sectors in one cluster
    ADD AX,CX ;+ one data cluster
    CMP BPB_SECN,AX ;compare with sectors available
    JAE VALIDATE_X ;jump if enough sectors

    CMP DIR_SECTORS,1 ;down to 1 directory sector?
    JBE VALIDATE_C ;can't let it go below 1

    MOV AX,BPB_SSZ ;sector size
    CWD ;clear DX for division
    DIV DIRE_SIZE ;sectorsize/dir entry size = entries/sector
    SUB BPB_DIRN,AX ;reduce directory entries by 1 sector

    OR ERR_FLAG,ERR_DIRN ;indicate directory entries adjusted
    JMP VALIDATE_A ;retry with new directory entries number

    VALIDATE_C: ;not enough space for any VDISK
    OR ERR_FLAG,ERR_SYSSZ
    VALIDATE_X:
    RET

    SUBTTL VAL_BSIZE Validate buffer size
    PAGE ;-----------------------------------------------------------------------;
    ; VAL_BSIZE adjusts the buffer size as necessary ; ;-----------------------------------------------------------------------; VAL_BSIZE PROC
    CALL GET_MSIZE ;determine memory available to VDISK
    ;returns available KB in AX
    OR AX,AX ;is any memory available at all?
    JNZ VAL_BSIZE_B ;yes, continue

    OR ERR_FLAG,ERR_SYSSZ ;indicate system too small for VDISK
    MOV BUFF_SIZE,1 ;set up minimal values to continue init
    MOV AX,VAL_SSZ_S ;smallest possible sector size
    MOV BPB_SSZ,AX
    MOV BPB_DIRN,4 ;4 directory entries
    RET

    VAL_BSIZE_B: ;some memory is available
    CMP AX,BUFF_SIZE ;is available memory >= requested?
    JAE VAL_BSIZE_C ;if so, we're done

    MOV BUFF_SIZE,AX ;give all available memory
    OR ERR_FLAG,ERR_BSIZE ;indicate buffersize adjusted VAL_BSIZE_C:
    RET


    GET_MSIZE PROC ;determine memory available to VDISK
    ;returns KB available in AX
    CMP EM_SW,0 ;extended memory?
    JE GET_MSIZE_2 ;use non-extended memory routine

    MOV AH,EM_MEMSIZE ;function code to AH
    INT EM_INT ;get extended memory size in AX
    JC GET_MSIZE_Z ;if error, no extended memory installed

    MUL C1024 ;DX,AX = bytes of extended memory
    ADD DX,10H ;DX,AX = high addr of extended memory+1
    SUB AX,AVAIL_LO ;- address of first available byte
    SBB DL,AVAIL_HI ;is number of free bytes
    DIV C1024 ;AX = number of whole free kilobytes
    RET

    GET_MSIZE_2: ;non-extended memory size determination

    ;Compute AX = total system size, - (VDISK end address + 64KB)

    MOV AX,START_BUFFER_PARA ;paragraph end of VDISK code
    XOR DX,DX ;clear for division
    DIV PARA_PER_KB ;KB address of load point
    ADD DX,0FFFFH ;round upward to KB boundary
    ADC AX,MIN_MEMORY_LEFT ;pick up CY and the 64KB we should leave
    PUSH AX ;save across interrupt
    INT MEM_SIZE ;get total system size
    POP DX ;amount of total that we can't use
    SUB AX,DX ;available space to VDISK
    JNC GET_MSIZE_X ;exit if positive

    GET_MSIZE_Z:
    XOR AX,AX ;indicate no memory available GET_MSIZE_X: ;exit from memory size determination
    RET
    GET_MSIZE ENDP

    VAL_BSIZE ENDP

    SUBTTL VAL_SSZ Validate Sector Size
    PAGE ;-----------------------------------------------------------------------;
    ; VAL_SSZ validates sector size, adjusting if necessary ; ;-----------------------------------------------------------------------; VAL_SSZ PROC ;validate sector size
    CMP CS:EM_SW,0 ;extended memory ?
    JE VAL_SSZ_ST ;no,go check sector size
    MOV BX,MAXSEC_TRF ;move number of sectors to transfer
    CMP BX,1 ;> or equal to 1 ?
    JB DFLT_TRF ;set default if it is
    CMP BX,8 ;> than 8 ?
    JA DFLT_TRF ;set default if it is
    JMP VAL_SSZ_ST ;continue processing

    DFLT_TRF: ;set default
    MOV MAXSEC_TRF,DFLT_ESS ;
    MOV BX,MAXSEC_TRF ;
    OR CS:ERR_FLAG,ERR_ESIZE ;indicate transfer size adjusted

    VAL_SSZ_ST: ;validate sector size
    MOV MAX_CNT,BX ;initialize maximum number of sectors
    ;to transfer for extended memory case
    MOV BX,BPB_SSZ ;requested sector size
    MOV CX,VAL_SSZ_N ;number of table entries
    MOV SI,OFFSET VAL_SSZ_TBL ;DS:SI point to table start
    VAL_SSZ_A:
    LODSW ;get table entry, step table pointer
    CMP AX,BX ;is value in table?
    JE VAL_SSZ_X ;exit if value found
    LOOP VAL_SSZ_A ;loop until table end

    MOV BX,DFLT_SSZ ;get default sector size
    MOV BPB_SSZ,BX ;set sector size to default value
    OR ERR_FLAG,ERR_SSZ ;indicate sector size adjusted VAL_SSZ_X:

    ;Compute the maximum number of sectors that can be moved in 64KB (less one) ;Restricting moves to this amount avoids 64KB boundary problems.

    CMP CS:EM_SW,0 ;extended memory ?
    JNE SIZE_DONE ;yes, we are done
    XOR DX,DX
    MOV AX,0FFFFH ;64KB - 1
    DIV BX ;/sector size
    MOV MAX_CNT,AX ;max sectors in one move
    SIZE_DONE:
    RET
    VAL_SSZ ENDP

    SUBTTL VAL_DIRN Validate number of directory entries
    PAGE ;-----------------------------------------------------------------------;
    ; VAL_DIRN validates and adjusts the number of directory entries. ;
    ; ;
    ; Minimum is MIN_DIRN, maximum is MAX_DIRN. If outside these ;
    ; limits, DFLT_DIRN is used. ;
    ; ;
    ; The number of directory entries is rounded upward to fill ;
    ; a sector ; ;-----------------------------------------------------------------------; VAL_DIRN PROC
    MOV AX,BPB_DIRN ;requested directory entries
    CMP AX,MIN_DIRN ;if less than minimum
    JB VAL_DIRN_A ;use default instead

    CMP AX,MAX_DIRN ;if <= maximum
    JBE VAL_DIRN_B ;accept value as provided

    VAL_DIRN_A:
    MOV AX,DFLT_DIRN ;use default directory entries
    OR ERR_FLAG,ERR_DIRN ;indicate directory entries adjusted VAL_DIRN_B: ;AX is number of directory entries
    MUL DIRE_SIZE ;* 32 = bytes of directory requested
    DIV BPB_SSZ ;/ sector size = # of directory sectors
    OR DX,DX ;test remainder for zero
    JZ VAL_DIRN_C ;jump if exact fit

    INC AX ;increment directory sectors
    OR ERR_FLAG,ERR_DIRN ;indicate directory entries adjusted VAL_DIRN_C: ;make sure enough sectors available
    MOV DX,BPB_SECN ;total sectors on media
    SUB DX,BPB_RES ;less reserved sectors
    SUB DX,2 ;less minimum FAT and 1 data sector
    CMP AX,DX ;if directory sectors <= available
    JLE VAL_DIRN_D ;use requested amount

    MOV AX,1 ;use only one directory sector
    OR ERR_FLAG,ERR_DIRN ;indicate directory entries adjusted VAL_DIRN_D:
    MOV DIR_SECTORS,AX ;save number of directory sectors
    MUL BPB_SSZ ;dir sectors * sector size = dir bytes
    DIV DIRE_SIZE ;dir bytes / entry size = entries
    MOV BPB_DIRN,AX ;store adjusted directory entries
    RET
    VAL_DIRN ENDP

    SUBTTL VAL_FAT Validate File Allocation Table (FAT)
    PAGE ;-----------------------------------------------------------------------; ;VAL_FAT computes: ; ;BPB_FATSZ, the number of sectors required per FAT copy ;
    ; ;
    ;Each FAT entry is 12 bits long, for a maximum of 4095 FAT entries. ;
    ;(A few FAT entries are reserved, so the highest number of FAT entries ;
    ;we permit is 0FE0H.) With large buffer sizes and small sector sizes, ;
    ;we have more allocation units to describe than a 12-bit entry will ; ;describe. If the number of FAT entries is too large, the sector size ;
    ;is increased (up to a maximum of 512 bytes), and then the allocation ;
    ;unit (cluster) size is doubled, until we have few enough allocation ; ;units to be properly described in 12 bits. ;
    ; ;
    ;This computation is slightly conservative in that the FAT entries ; ;necessary to describe the FAT sectors are included in the computation. ; ;-----------------------------------------------------------------------; VAL_FAT PROC
    MOV AX,BPB_SECN ;total number of sectors
    SUB AX,BPB_RES ;don't count boot sector(s)
    SUB AX,DIR_SECTORS ;don't count directory sectors
    JG VAL_FAT_A ;jump if some remaining
    MOV BPB_SSZ,DFLT_SSZ ;force default sector size
    OR ERR_FLAG,ERR_SSZ+ERR_PASS ;indicate sector size adjusted
    JMP SHORT VAL_FAT_X ;recompute all values
    VAL_FAT_A:
    XOR DX,DX ;clear DX for division
    MOV CL,BPB_AUSZ ;CX = sectors/cluster
    XOR CH,CH
    DIV CX ;whole number of clusters in AX
    ADD DX,0FFFFH ;set carry if remainder
    ADC AX,0 ;increment AX if remainder
    CMP AX,MAX_FATE ;number of FAT entries too large?
    JBE VAL_FAT_C ;no, continue

    MOV AX,BPB_SSZ ;pick up current sector size
    CMP AX,VAL_SSZ_L ;already at largest permitted?
    JE VAL_FAT_B ;yes, can't make it any larger

    SHL BPB_SSZ,1 ;double sector size
    OR ERR_FLAG,ERR_SSZB ;indicate sector size adjusted
    JMP SHORT VAL_FAT_X ;recompute all sizes with new BPBSSZ

    VAL_FAT_B: ;sector size is at maximum
    SHL BPB_AUSZ,1 ;double allocation unit size
    OR ERR_FLAG,ERR_PASS ;indicate another pass required
    JMP SHORT VAL_FAT_X ;recompute values

    VAL_FAT_C: ;FAT size = 1.5 * number of clusters
    MOV CX,AX ;number of clusters
    SHL AX,1 ;* 2
    ADD AX,CX ;* 3
    SHR AX,1 ;* 1.5
    ADC AX,3 ;add 3 bytes for first 2 FAT entries
    ;(media descriptor and FFFFH), and CY
    XOR DX,DX ;clear DX for division
    DIV BPB_SSZ ;FAT size/sector size
    ADD DX,0FFFFH ;set carry if remainder
    ADC AX,0 ;round upward
    MOV BPB_FATSZ,AX ;number of sectors for 1 FAT copy VAL_FAT_X:
    RET
    VAL_FAT ENDP


    VALIDATE ENDP

    SUBTTL COPY_BPB Copy BPB to Boot Record
    PAGE ;-----------------------------------------------------------------------;
    ; COPY_BPB copies the BIOS Parameter Block (BPB) ;
    ; to the VDISK Boot Record ; ;-----------------------------------------------------------------------;
    ASSUME DS:CSEG
    COPY_BPB PROC ;Copy BBP to Boot Record
    PUSH DS
    POP ES ;set ES = DS

    MOV CX,BPB_LEN ;length of BPB
    MOV SI,OFFSET BPB ;source offset
    MOV DI,OFFSET BOOT_BPB ;target offset
    REP MOVSB ;copy BPB to boot record
    RET
    COPY_BPB ENDP

    SUBTTL VERIFY_EXTENDER
    PAGE ;-----------------------------------------------------------------------;
    ; VERIFY_EXTENDER makes sure that if an Expansion Unit is ;
    ; installed, the memory size switches on the Extender Card ;
    ; are correctly set. ; ;-----------------------------------------------------------------------;


    ASSUME DS:CSEG
    EXT_P210 EQU 0210H ;write to latch expansion bus data
    ;read to verify expansion bus data
    EXT_P213 EQU 0213H ;Expansion Unit status

    VERIFY_EXTENDER PROC

    NOP

    MOV DX,EXT_P210 ;Expansion bus data port address

    MOV AX,5555H ;set data pattern
    OUT DX,AL ;write 55H to control port
    PUSH DX
    POP DX

    JMP SHORT $+2 ;Let the I/O circuits catch up
    IN AL,020h ;Clear the CMOS bus drivers!

    IN AL,DX ;recover data
    CMP AH,AL ;did we recover the same data?
    JNE VERIFY_EXTENDER_X ;if not, no extender card

    NOT AX ;set AX = 0AAAAH
    OUT DX,AL ;write 0AAH to control port
    PUSH DX ;load data line
    POP DX ;load data line

    JMP SHORT $+2 ;Let the I/O circuits catch up
    IN AL,020h ;Clear the CMOS bus drivers!

    IN AL,DX ;recover data
    CMP AH,AL ;did we recover the same data?
    JNE VERIFY_EXTENDER_X ;if not, no extender card

    ;Expansion Unit is present.

    ;Determine what the switch settings should be on the Extender Card

    INT MEM_SIZE ;get system memory size in KB in AX
    ADD AX,63D ;memory size + 63K
    MOV CL,6 ;2^6 = 64
    SHR AX,CL ;divide by 64
    ;AX is highest segment address
    MOV AH,AL ;save number of segments

    ;Read Expander card switch settings

    MOV DX,EXT_P213 ;expansion unit status
    IN AL,DX ;read status
    ;bits 7-4 (hi nibble) are switches
    MOV CL,4 ;shift count
    SHR AL,CL ;shift switches to bits 3-0 of AL

    CMP AH,AL ;do switches match memory size?
    JE VERIFY_EXTENDER_X ;yes, exit normally

    OR ERR_FLAG,ERR_EXTSW ;indicate switch settings are wrong

    VERIFY_EXTENDER_X:
    RET
    VERIFY_EXTENDER ENDP

    SUBTTL UPDATE_AVAIL
    PAGE ;-----------------------------------------------------------------------;
    ; UPDATE_AVAIL updates the address of the first byte in extended ;
    ; memory not used by any VDISK buffer ; ;-----------------------------------------------------------------------; UPDATE_AVAIL PROC ;update AVAIL_LO and AVAIL_HI of first VDISK
    MOV AX,BUFF_SIZE ;number of KB of VDISK buffer
    MUL C1024 ;DX,AX = number of bytes of VDISK buffer

    PUSH DS
    MOV DS,FIRST_VDISK ;set DS to first VDISK
    ADD DS:AVAIL_LO,AX ;update first available byte location
    ADC DS:AVAIL_HI,DL
    POP DS
    RET
    UPDATE_AVAIL ENDP

    SUBTTL FORMAT_VDISK
    PAGE ;-----------------------------------------------------------------------;
    ; This Request Header is used by MOVE_VDISK to move the ;
    ; first few sectors of the virtual disk (boot, FAT, and ;
    ; Directory) into extended memory. ; ;-----------------------------------------------------------------------;

    MOVE_RH DB MOVE_RH_L ;length of request header
    DB 0 ;sub unit
    DB 8 ;output operation
    DW 0 ;status
    DQ ? ;reserved for DOS
    DB ? ;media descriptor byte
    MOVE_RHO DW ? ;offset of data transfer address MOVE_RHS DW ? ;segment of data transfer address MOVE_RHCNT DW ? ;count of sectors to transfer
    DW 0 ;starting sector number
    MOVE_RH_L EQU $-MOVE_RH ;length of request header

    ;-----------------------------------------------------------------------;
    ; FORMAT_VDISK formats the boot sector, FAT, and directory of an ;
    ; extended memory VDISK in storage immediately following ;
    ; VDISK code, in preparation for moving to extended memory. ; ;-----------------------------------------------------------------------; FORMAT_VDISK PROC ;format boot record, FATs and directory

    MOV AX,CS ;compute 20-bit address
    MUL WPARA_SIZE ;16 * segment
    ADD AX,OFFSET MSGEND ;+ offset
    ADC DL,0 ;pick up carry
    ADD AX,STACK_SIZE ;plus stack size
    ADC DL,0 ;pick up carry

    DIV WPARA_SIZE ;split into segment(AX)&offset(DX)
    MOV MOVE_RHS,AX ;save in Request Header for move
    MOV MOVE_RHO,DX

    MOV DI,DX ;offset to DI
    MOV ES,AX ;segment to ES

    ;copy the boot record

    MOV SI,OFFSET BOOT_RECORD ;point to source field
    MOV AX,BPB_RES ;number of reserved sectors
    MUL BPB_SSZ ;* sector size = length of boot records
    MOV CX,AX ;length to CX for move
    REP MOVSB ;move boot record(s)

    ;format the FAT(s)

    MOV CL,BPB_FATN ;number of FATs
    XOR CH,CH
    FORMAT_VDISK_A: ;set up one FAT
    PUSH CX ;save loop counter on stack
    MOV AL,BPB_MCB ;media control byte
    STOSB ;store media control byte, increment DI
    MOV AX,0FFFFH ;bytes 2 and 3 of FAT are 0FFH
    STOSW
    MOV AX,BPB_FATSZ ;number of sectors per FAT
    MUL BPB_SSZ ;* sector size = length of FAT in bytes
    SUB AX,3 ;less the 3 bytes we've stored
    MOV CX,AX ;count to CX
    XOR AX,AX
    REP STOSB ;clear remainder of FAT
    POP CX ;get loop counter off stack
    LOOP FORMAT_VDISK_A ;loop for all copies of the FAT

    ;Format the directory

    MOV SI,OFFSET VOL_LABEL ;point to volume label
    MOV CX,VOL_LABEL_LEN ;length of volume directory entry
    REP MOVSB ;move volume id to directory
    MOV AX,DIR_ENTRY_SIZE ;length of 1 directory entry
    MUL BPB_DIRN ;* number entries = bytes of directory
    SUB AX,VOL_LABEL_LEN ;less length of volume label
    MOV CX,AX ;CX = length of rest of directory
    XOR AX,AX
    REP STOSB ;clear directory to nulls
    RET
    FORMAT_VDISK ENDP

    SUBTTL MOVE_VDISK
    PAGE ;-----------------------------------------------------------------------;
    ; MOVE_VDISK moves the formatted boot sector, FAT, and directory ;
    ; into extended memory. ; ;-----------------------------------------------------------------------;

    MOVE_VDISK PROC
    MOV AL,BPB_FATN ;number of FAT copies
    CBW ;clear AH
    MUL BPB_FATSZ ;number of FAT sectors
    ADD AX,BPB_RES ;+ reserved sectors
    ADD AX,DIR_SECTORS ;+ directory sectors
    MOV MOVE_RHCNT,AX ;store as I/O length

    MOV BX,OFFSET MOVE_RH ;DS:BX point to request header
    PUSH DS ;make sure DS gets preserved
    CALL INOUT ;move to extended memory
    POP DS
    RET

    [continued in next message]

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)