home *** CD-ROM | disk | FTP | other *** search
- PAGE 58,132
- TITLE RAMDSK18.ASM 180K RAM DISK
-
- ;****************************************************************************
- ; VIRTUAL.ASM
- ; AN INSTALLABLE DEVICE DRIVER FOR AN IN STORAGE DISKETTE
- ; (virtual) WITH AN 180K CAPACITY
- ;***************************************************************************
- CSEG SEGMENT PARA PUBLIC 'CODE'
- ;
- ; MACROS
- ;
- STATUS MACRO STATE,ERR,RC
- IFIDN <STATE>,<DONE>
- OR ES:WORD PTR SRH_STA_FLD[BX],0100H
- ENDIF
- IFIDN <STATE>,<BUSY>
- OR ES:WORD PTR SRH_STA_FLD[BX],0200H
- ENDIF
- IFIDN <ERR>,<ERROR>
- OR ES:WORD PTR SRH_STA_FLD[BX],1000H
- ENDIF
- IFNB <RC>
- OR ES:WORD PTR SRH_STA_FLD[BX],RC
- ENDIF
- ENDM
- ;
- ; EQUATES
- ;
- ; This first group of equates allow changing parameters to define other size
- ; disks than the 180K defined here.
- SCTRS_ALLOC EQU 1 ;Sectors per allocation unit;see DOS
- ;2.0 manual C-2
- DIR_ENTRIES EQU 64 ;No.of Directory entries,Same as above
- TOT_SECTORS EQU 360 ;Total No. of Sectors,same as above
- MED_DESCRPT EQU 0FCH ;Media descriptor,14-22 of DOS manual
- ADD_PARAS EQU 2D00H ;paragraphs to add,depends on size
- NO_OF_FATS EQU 2 ;No. of File Alloc.Tables.see C-2
- NO_FAT_SCTRS EQU 2 ;No. of sectors occupied by FAT,C-2
- ;
- ; READ/WRITE
- ;
- SRH EQU 0 ;Static request header start
- SRH_LEN EQU 13 ; " " " length
- SRH_LEN_FLD EQU SRH ; " " " " field
- SRH_UCD_FLD EQU SRH+1 ; " " " Unit code
- SRH_CCD_FLD EQU SRH+2 ; " " " command code fld
- SRH_STA_FLD EQU SRH+3 ; " " " status field
- SRH_RES_FLD EQU SRH+5 ; " " "reserved area field
- ;
- MD EQU SRH+SRH_LEN ;Media description byte
- MD_LEN EQU 1 ; " " " length
- DTA EQU MD+MD_LEN ;disk transfer address
- DTA_LEN EQU 4 ;dta length
- COUNT EQU DTA+DTA_LEN ;byte/sector count
- COUNT_LEN EQU 2 ; " " " length
- SSN EQU COUNT+COUNT_LEN ;starting sector number
- SSN_LEN EQU 2 ; " " " length
- ;
- ; MEDIA CHECK
- ;
- RET_BYTE EQU MD+MD_LEN ;byte returned from driver
- ;
-
- ; BUILD B(ios)P(arameter)B(lock)
- ;
- BPBA_PTR EQU DTA+DTA_LEN ;Pointer to BPB
- BPBA_PTR_LEN EQU 4 ; " " " length
- ;
- ; INIT
- ;
- UNITS EQU SRH+SRH_LEN
- UNITS_LEN EQU 1
- BR_ADDR_0 EQU UNITS+UNITS_LEN
- BR_ADDR_1 EQU BR_ADDR_0+2
- BR_ADDR_LEN EQU 4
- BPB_PTR_OFF EQU BR_ADDR_0+BR_ADDR_LEN
- BPB_PTR_SEG EQU BPB_PTR_OFF+2
- ;
- ;
- VDSK PROC FAR ;Start Virtual disk procedure
- ASSUME CS:CSEG,ES:CSEG,DS:CSEG
- BEGIN:
- START EQU $
- ; SPECIAL DEVICE HEADER
- NEXT_DEV DD -1 ;Pointer to next device
- ATTRIBUTE DW 2000H ;Block device(non-IBM format)
- STRATEGY DW DEV_STRATEGY ;pointer to DeviceStrategy
- INTERRUPT DW DEV_INT ;pointer to device interrupt handler
- DEV_NAME DB 1 ;Number of block devices
- DB 7 DUP(?) ;7 Bytes of filler
- ;
- ;
- RH_OFF DW ? ;Request Header offset
- RH_SEG DW ? ;Request Header segment
- ;
- ; BIOS PARAMETER BLOCK
- ;
- BPB EQU $ ;Current location counter
- DW 512 ;Sector size
- DB SCTRS_ALLOC ;Sectors/allocation unit
- DW 1 ;Number of reserved sectors
- DB NO_OF_FATS ;Number of FATS
- DW DIR_ENTRIES ;Number of directory entries
- DW TOT_SECTORS ;Total number of sectors
- DB MED_DESCRPT ;Media descriptor
- DW NO_FAT_SCTRS ;No.sectors occupied by FAT
- ;
- BPB_PTR DW BPB ;BPB pointer array(1 entry)
- ; CURRENT VIRTUAL DISK INFORMATION
- TOTAL DW ? ;Total sectors to transfer
- VERIFY DB 0 ;Verify 1=Yes, 0 = No
- START_SEC DW 0 ;Starting sector number
- VDISK_PTR DW 0 ;Starting segment of virtual disk
- USER_DTA DD ? ;Ptr to callers disk transfer address
- BOOT_REC EQU $ ;Dummy DOS boot record
- DB 3 DUP(0) ;3 Byte jump>boot code(not bootable)
- ;
- DB 'IBM 2.0' ;Vendor ID(2-spaces betweenM&2crucial)
- DW 512 ;Number of bytes in sector
- DB SCTRS_ALLOC ;1 sector per allocation unit
- DW 1 ;1 reserved sector
- DB NO_OF_FATS ;2 fats
- DW DIR_ENTRIES ;Number of directory entries
- DW TOT_SECTORS ;360 total sectors in image
- DB MED_DESCRPT ;Tells DOS it is 1-side 9 sector disk
- DW NO_FAT_SCTRS ;Number of sectors in FAT
- ;
- ; FUNCTION TABLE
- ;
- FUNTAB LABEL BYTE
- DW INIT ;initialization
- DW MEDIA_CHECK ;Media check ( block only)
- DW BUILD_BPB ;Build BPB
- DW IOCTL_IN ;IOCTL input
- DW INPUT ;Input(read)
- DW NO_INPUT ;non/dest.input,no wait(chr only)
- DW IN_STAT ;Input status
- DW IN_FLUSH ;Input flush
- DW OUTPUT ;Output(write)
- DW OUT_VERIFY ;Output(write)with verify
- DW OUT_STAT ;Output status
- DW OUT_FLUSH ;Output flush
- DW IOCTL_OUT ;IOCTL output
- ;
- ; LOCAL PROCEDURES
- ;
- IN_SAVE PROC NEAR
- MOV AX,ES:WORD PTR DTA[BX] ;Save callers DTA
- MOV CS:USER_DTA,AX
- MOV AX,ES:WORD PTR DTA+2[BX]
- MOV CS:USER_DTA+2,AX
- MOV AX,ES:WORD PTR COUNT[BX];get number of sectors to read
- XOR AH,AH
- MOV CS:TOTAL,AX ;move number of sectors to total
- RET
- IN_SAVE ENDP
- ;
- CALC_ADDR PROC NEAR
- MOV AX,CS:START_SEC ;Get starting sector number
- MOV CX,20H ;move 512 to cx segment style
- MUL CX ;multiply to get actual sector
- MOV DX,CS:VDISK_PTR ;get segment of virtual disk
- ADD DX,AX ;add that segment to initial segment
- MOV DS,DX ;save that as actual segment
- XOR SI,SI ;its on paragraph boundary
- MOV AX,CS:TOTAL ;total number of sectors to read
- MOV CX,512 ;bytes per sector
- MUL CX ;multiply to get copy length
- OR AX,AX ;check for greater than 64k
- JNZ MOVE_IT
- MOV AX,0FFFFH ;move in for 64k
- MOVE_IT:
- XCHG CX,AX ;move length to cx
- RET
- CALC_ADDR ENDP
- ;
- SECTOR_READ PROC NEAR
- CALL CALC_ADDR ;calculate starting"sector"
- MOV ES,CS:USER_DTA+2 ;set destination)ES:DI)to point
- MOV DI,CS:USER_DTA ; to callers dta
- ;
- ; CHECK FOR DTA WRAP IN CASE WE CAME THROUGH VIA VERIFY
- ;
- MOV AX,DI ;get offset of dta
- ADD AX,CX ;add copy length to it
- JNC READ_COPY ;carry flag=0,no wrap
- MOV AX,0FFFFH ;maximum length
- SUB AX,DI ;subtract dta offset from max
- MOV CX,AX ;issue that as copy length to not wrap
- READ_COPY:
- REP MOVSB ;do the "read"
- RET
- SECTOR_READ ENDP
- ;
- SECTOR_WRITE PROC NEAR
- CALL CALC_ADDR ;Calculate starting sector
- PUSH DS
- POP ES ;Establish addressability
- MOV DI,SI ;ES:DI point to disk
- MOV DS,CS:USER_DTA+2 ;DS:DI point to callers dta
- MOV SI,CS:USER_DTA
- ;
- ; CHECK FOR DTA WRAP
- ;
- MOV AX,SI ;Move dta offset to ax
- ADD AX,CX ;add copy length to offset
- JNC WRITE_COPY ;carry flag=0,no segment wrap
- MOV AX,0FFFFH ;move in max copy length
- SUB AX,SI ;subtract dta offset from max
- MOV CX,AX ;use as new copy length to avoid wrap
- WRITE_COPY:
- REP MOVSB ;do the write
- RET
- SECTOR_WRITE ENDP
- ;
- ; DEVICE STRATEGY
- ;
- DEV_STRATEGY:
- MOV CS:RH_SEG,ES ;save segment of request header ptr
- MOV CS:RH_OFF,BX ;save offset of " " "
- RET
- ;
- ; DEVICE INTERRUPT HANDLER
- ;
- DEV_INT:
- ; PRESERVE MACHINE STATE ON ENTRY
- CLD
- PUSH DS
- PUSH ES
- PUSH AX
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH DI
- PUSH SI
- ;
- ; DO THE BRANCH ACCORDING TO THE FUNCTION PASSED
- ;
- MOV AL,ES:[BX]+2 ;Get function byte
- ROL AL,1 ;Get offset into table
- LEA DI,FUNTAB ;get address funtab
- XOR AH,AH
- ADD DI,AX
- JMP WORD PTR[DI]
- ;
- ; INIT
- ;
- INIT:
- PUSH CS
- POP DX ;current cs to dx
- LEA AX,CS:VDISK ;get address of virtual disk
- MOV CL,4
- ROR AX,CL ;divide by 16(paragraph form)
- ADD DX,AX ;add to current cs value
- MOV CS:VDISK_PTR,DX ;save as start segment of virtual disk
- MOV AX,ADD_PARAS ;add 2D00H paragraphs to starting
- ADD DX,AX ; segment of virtual disk
- MOV ES:WORD PTR BR_ADDR_0[BX],0
- MOV ES:BR_ADDR_1[BX],DX ;make that the break address
- MOV ES:BYTE PTR UNITS[BX],1 ;number of diskette units
- LEA DX,BPB_PTR ;get address of bpb pointer array
- MOV ES:BPB_PTR_OFF[BX],DX ;save offset in data packet
- MOV ES:BPB_PTR_SEG[BX],CS ;save segment in data packet
- MOV ES,CS:VDISK_PTR ;get starting address of virtual disk
- XOR DI,DI ;zero out di(boot record)
- LEA SI,BOOT_REC ;address of boot record
- MOV CX,24
- REP MOVSB ;copy 24 bytes of boot record
- MOV CS:WORD PTR START_SEC,1
- MOV CS:WORD PTR TOTAL,2
- CALL CALC_ADDR ;calculate address of logical secor 1
- PUSH DS
- POP ES
- MOV DI,SI ;move that address to ES:DI
- XOR AL,AL
- REP STOSB ;zero out FAT area
- MOV DS:BYTE PTR [SI],0FCH ;set first FAT entry
- MOV DS:BYTE PTR 1[SI],0FFH
- MOV DS:BYTE PTR 2[SI],0FFH
- PUSH DS ;save pointer to FAt on stack
- PUSH SI
- MOV CS:WORD PTR START_SEC,3
- MOV CS:WORD PTR TOTAL,2
- CALL CALC_ADDR ;calculate address logical sector 3
- PUSH DS
- POP ES
- MOV DI,SI ;move that address to ES:DI
- POP SI
- POP DS ;restore address to first FAT
- REP MOVSB ;copy first FAT to second FAT
- MOV CS:WORD PTR START_SEC,5
- MOV CS:WORD PTR TOTAL,4
- CALL CALC_ADDR ;calc.address ofL.S.5(start of dir)
- XOR AL,AL
- PUSH DS
- POP ES ;set up ES:DI to point to it
- XOR DI,DI
- REP STOSB ;zero out directory
- MOV ES,CS:RH_SEG ;restore ES:BX to request header
- MOV BX,CS:RH_OFF
- STATUS DONE,NOERROR,0 ;set status word(done,noerror,0)Macro
- JMP EXIT
- ;
- ; MEDIA CHECK
- MEDIA_CHECK: ;Media check(block only)
- ;
- ; SET MEDIA NOT CHANGED
- MOV ES:BYTE PTR RET_BYTE[BX],1 ;store in return byte
- STATUS DONE,NOERROR,0 ;turn on done bit(macro)
- JMP EXIT
- ;
- ; BUILD BIOS PARAMETER BLOCK
- ;
- BUILD_BPB:
- PUSH ES ;save srh segment
- PUSH BX ;save rh_offset
- MOV CS:WORD PTR START_SEC,0
- MOV CS:WORD PTR TOTAL,1
- CALL CALC_ADDR ;calculate address of first sector
- PUSH CS
- POP ES
- LEA DI,BPB ;address of BIOS paramter block
- ADD SI,11 ;add 11 to si
- MOV CX,13 ;length of bpb
- REP MOVSB
- POP BX ;restore offset of srh
- POP ES ;restore segment of srh
- LEA DX,BPB ;get BPB array pointer
- MOV ES:BPBA_PTR[BX],DX ;save pointer to BPB table
- MOV ES:BPBA_PTR+2[BX],CS
- MOV ES:DTA[BX],DX ;offset of sector buffer
- MOV ES:DTA+2[BX],CS
- STATUS DONE,NOERROR,0 ;macro call
- JMP EXIT
- ;
- ; FOLLOWING ENTRIES ARE NOT SUPPORTED BY THIS DEVICE
- ;
- IOCTL_IN:
- IOCTL_OUT:
- NO_INPUT:
- IN_STAT:
- IN_FLUSH:
- OUT_STAT:
- OUT_FLUSH:
- ;
- ; DISK READ
- ;
- INPUT:
- CALL IN_SAVE ;call initial save routine
- MOV AX,ES:WORD PTR SSN[BX] ;get starting sector number
- MOV CS:START_SEC,AX ;save starting sector number
- MOV AX,ES:WORD PTR COUNT[BX]
- MOV CS:TOTAL,AX ;save total sectors to transfer
- CALL SECTOR_READ ;readin that many sectors
- MOV BX,CS:RH_OFF ;restore ES:BX as request hdr ptr
- MOV ES,CS:RH_SEG
- STATUS DONE,NOERROR,0
- JMP EXIT
- ;
- ; DISK WRITE
- ;
- OUTPUT: ;output(write)
- CALL IN_SAVE
- MOV AX,ES:WORD PTR SSN[BX] ;get starting sector number
- MOV CS:START_SEC,AX ;set " " "
- MOV AX,ES:WORD PTR COUNT[BX]
- MOV CS:TOTAL,AX ;save total sectors to write
- CALL SECTOR_WRITE ;write out those sectors
- MOV BX,CS:RH_OFF ;restore ES:BX as request hdr ptr
- MOV ES,CS:RH_SEG
- CMP CS:BYTE PTR VERIFY,0 ;write verify set
- JZ NO_VERIFY ;no, no write verify
- MOV CS:BYTE PTR VERIFY,0 ;reset verify indicator
- JMP INPUT
- NO_VERIFY:
- STATUS DONE,NOERROR,0 ;set done,noerror in statusword
- JMP EXIT
- OUT_VERIFY: ;output(write)with verify
- MOV CS:BYTE PTR VERIFY,1 ;set the verify flag
- JMP OUTPUT ;branch to output routine
- ;
- ; COMMON EXIT
- EXIT:
- ;
- POP SI ;restore all registers
- POP DI
- POP DX
- POP CX
- POP BX
- POP AX
- POP ES
- POP DS
- RET
- E_O_P:
- ; MACRO TO ALIGN VIRTUAL DISK ON A PARAGRAPH BOUNDARY
- IF ($-START) MOD 16
- ORG ($-START)+16-(($-START)MOD 16)
- ENDIF
- VDISK EQU $
- VDSK ENDP
- CSEG ENDS
- END BEGIN
- ;
- ; THE END
-
-
-