[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference noted::hackers_v1

Title:-={ H A C K E R S }=-
Notice:Write locked - see NOTED::HACKERS
Moderator:DIEHRD::MORRIS
Created:Thu Feb 20 1986
Last Modified:Mon Aug 03 1992
Last Successful Update:Fri Jun 06 1997
Number of topics:680
Total number of notes:5456

250.0. "VMS memory disk driver revisited" by BARAKA::LASTOVICA (Norm Lastovica) Fri May 30 1986 21:25

This hack started as a need (as many do I'm sure) and then was documented.
    I think that the procedure is rather spiffy, but I can take no credit
    for the original driver.  Ken Blaylock also deserves credit for
    help writing and debugging.
    
    								30-May-1986


		This is the "kit" for FDDRIVER.


	FDDRIVER impliments a memory based pseudo disk for VAX/VMS
systems.  It has been shown to run on VMS V4.4 although any version
of VMS after 4.0 should be able to run FDDRIVER with no problems.
The primary advantage of a memory based disk is that there are no
disk latency times involved and all transfers happen at CPU speed.
Files that are often accessed can benifit greatly from this driver
due to the performance gains over a physical disk.

	Backround on the driver as it exists can be found by looking
in  SYS$UPDATE:STABACKIT.COM distributed with 4.4.  Basically, a
chunk (user specified size) of nonpaged pool is allocated by the
driver (with a QIO format command to the driver).  Then, the "disk"
can be initialized, mounted, and accessed as a real disk device.  The
original PDDRIVER (that this code is stolen from) used a loop in IOC$
routines to perform byte transfers to and from the user's buffer at
fork IPL.  Needless to say, there is significant overhead in doing
things this way.

	And, as can be guessed, the new version does MOVC3 transfers
of up to one page at a time.  One page at a time is the current limit
because a single mapping register is used to map the user's buffer
into system space.  Special case is the first page where the buffer
may start at a non page boundry and could be less than one page long.

	Following are three pieces of code.  First program is called
FD_SETSIZE.MAR and is used to tell the driver how much pool to 
allocate (remember, 1 page is 512 bytes of nonpaged pool).  This
program would be run once after the driver is loaded.  The next piece
of code is the driver proper.  It is assembled and linked and then
loaded with SYSGEN.  Finally, FDDRIVER_STARTUP.COM can be called
from SYSTARTUP.COM to load the driver, configure the device and mount
it.  The three programs are separated with form feeds (I took out the
form feeds from the driver to make this easier).  As far as I know this
code is safe.  But, I'd make initial tests on a little used machin
after hours...

	Notes of safety:  Don't run FD_SETSIZE while the device is
mounted, this can cause all sorts of problems; Keep FD_SETSIZE where
people will not run it, it can resize without special privs.

	Please let me know if you find changes to be made (ie. make
them and let me know).  Good luck!

	30-may-1986
	Norm Lastovica
	Customer Support Center/Colorado Springs - TSSG
	CX03 1/M12

	.TITLE	fDDRIVER - fAST PSEUDO DISK DRIVER
	.IDENT	'X-0'
;
;****************************************************************************
;*									    *
;*  COPYRIGHT (c) 1984, 1985, 1986 BY					    *
;*  DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASSACHUSETTS.		    *
;*  ALL RIGHTS RESERVED.						    *
;* 									    *
;*  THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND COPIED   *
;*  ONLY IN  ACCORDANCE WITH  THE  TERMS  OF  SUCH  LICENSE  AND WITH THE   *
;*  INCLUSION OF THE ABOVE COPYRIGHT NOTICE. THIS SOFTWARE OR  ANY  OTHER   *
;*  COPIES THEREOF MAY NOT BE PROVIDED OR OTHERWISE MADE AVAILABLE TO ANY   *
;*  OTHER PERSON.  NO TITLE TO AND OWNERSHIP OF  THE  SOFTWARE IS  HEREBY   *
;*  TRANSFERRED.							    *
;* 									    *
;*  THE INFORMATION IN THIS SOFTWARE IS  SUBJECT TO CHANGE WITHOUT NOTICE   *
;*  AND  SHOULD  NOT  BE  CONSTRUED AS  A COMMITMENT BY DIGITAL EQUIPMENT   *
;*  CORPORATION.							    *
;* 									    *
;*  DIGITAL ASSUMES NO RESPONSIBILITY FOR THE USE  OR  RELIABILITY OF ITS   *
;*  SOFTWARE ON EQUIPMENT WHICH IS NOT SUPPLIED BY DIGITAL.		    *
;* 									    *
;*									    *
;****************************************************************************
; 
;++
;		*************************
;		* For Internal Use Only *
;		*************************
; 
; FACILITY:
; 
; 	VAX/VMS fAST Pseudo-disk Device Driver
; 
; ABSTRACT:
; 
;	This version is a hack from the original PDDRIVER supplied with
;	VMS 4.4.  Major advantage of this version is the move by page
;	I/O (sic) to memory.
;
;	the driver allocates pages from nonpaged pool to use for the disk.
;	the program fd_setsize tells the driver how much memory (in pages)
;	to allocate for the disk.
;
; 	This module contains the tables and routines necessary to
; 	emulate device driver processing of a real disk drive using
;	memory resident data instead. For compatability with utilties
;	which wish to know disk geometry information, the pseudo-disk
;	appears to have one sector per track and as many tracks as
;	there are blocks on the disk.
;
;	assembly and link instructions:
;
;		$macro/list fddriver+sys$share:lib/lib
;		$link/map fddriver+sys$system:sys.stb/sel+sys$Input:/opt
;		base=0
;		$exit
;		$mc sysgen conn fda0/noada
;		$run fd_setsize
;		2500			! number of pages needed.  adjust this
;					! as required
;		
; AUTHOR:
;
;	Jay Olson,	Creation Date:	26-Oct-1984
; 
; MODIFIED BY:
;
;	29-May-1986	norm lastovica, ken blaylock
;			use movc3 to move one page at a time rather than
;			one byte at a time.  replaces IOC$MOVFRUSER
;			and IOC$MOVTOUSER calls with fd$... version of the
;			routines.  
;
;	29-may-1986	njl/kgb
;			check for last byte moved prior to calling ioc$filspt.
;			corrects system crashing problem due to accessing
;			invalid pte's.
;
;--

	.SBTTL	EXTERNAL AND LOCAL DEFINITIONS
; 
; EXTERNAL SYMBOLS
; 
	$CRBDEF				;Define channel request block
	$DCDEF				;Define device classes
	$DDBDEF				;Define device data block
	$DEVDEF				;Define device characteristics
	$DPTDEF				;Define driver prologue table
	$DYNDEF				;Define dynamic data structures
	$IDBDEF				;Define interrupt data block
	$IODEF				;Define i/o function codes
	$IPLDEF				;Define interrupt priority levels
	$IRPDEF				;Define i/o request packet
	$SSDEF				;Define system status codes
	$UCBDEF				;Define unit control block
	$VECDEF				;Define interrupt vector block
	$PRDEF				;DEFINE PROCESSOR REGISTERS
	$PTEDEF				;PAGE TABLE ENTRY DEFINITIONS
	$UCBDEF				;DEFINE UCB OFFSETS

; 
; LOCAL SYMBOLS
; 
fD_FIPL		=8			;Fork IPL
fD_BLKSIZ	=512			;Size of a disk block

; 
; UCB OFFSETS WHICH FOLLOW THE STANDARD UCB FIELDS
; 
	$DEFINI	UCB			;Start of UCB definitions

.=UCB$K_LCL_DISK_LENGTH			;Begin definitions at end of UCB

$DEF	UCB$L_MEMBUF	.BLKL	1	;Address of in-memory buffer

UCB$K_fD_LEN=.				;Length of UCB

	$DEFEND	UCB			;End of UCB definitons

	.SBTTL	STANDARD TABLES
; 
; DRIVER PROLOGUE TABLE
; 
; 	The DPT describes driver parameters and I/O database fields
; 	that are to be initialized during driver loading and reloading.
; 

	DPTAB	-			;DPT creation macro
		END=fD_END,-		;Label at end of driver
		ADAPTER=NULL,-		;No real device
		MAXUNITS=1,-		;Only one unit allowed
		UNLOAD=fD_UNLOAD,-	;Clean-up routine when unloading
		FLAGS=<DPT$M_SVP>-	;System page table entry required
		UCBSIZE=UCB$K_fD_LEN,-	;Length of UCB
		NAME=fDDRIVER		;Driver name

	DPT_STORE INIT			;Start control block init values
	DPT_STORE DDB,DDB$L_ACPD,L,-	;Default ACP name
		<^A\F11\>  
	DPT_STORE DDB,DDB$L_ACPD+3,B,-	;ACP class
		<DDB$K_SLOW>
	DPT_STORE UCB,UCB$B_FIPL,B,-	;Fork IPL
		<fD_FIPL>
	DPT_STORE UCB,UCB$L_DEVCHAR,L,-	;Device characteristics
		<DEV$M_FOD-		; Files oriented
		!DEV$M_DIR-		; Directory structured
		!DEV$M_AVL-		; Available
		!DEV$M_SHR-		; Shareable
		!DEV$M_IDV-		; Input device
		!DEV$M_ODV-		; Output device
		!DEV$M_RND>		; Random access
	DPT_STORE UCB,UCB$L_DEVCHAR2,L,-;More device characteristics
		<DEV$M_NNM>		; Prefix name with "node$"
	DPT_STORE UCB,UCB$B_DEVCLASS,B,-;Device class - disk
		<DC$_DISK>
	DPT_STORE UCB,UCB$B_DEVTYPE,B,-	;Device type - RX01
		<DT$_RX01>
	DPT_STORE UCB,UCB$W_DEVBUFSIZ,W,- ;Default buffer size
		<fD_BLKSIZ>
	DPT_STORE UCB,UCB$B_TRACKS,B,1	;Number of sides
	DPT_STORE UCB,UCB$B_SECTORS,B,1	;Number of sectors per track
	DPT_STORE UCB,UCB$B_DIPL,B,21	;Device IPL (not used)
	DPT_STORE UCB,UCB$W_DEVSTS,W,-	;Inhibit log to phy conv in FDT
		<UCB$M_NOCNVRT>

	DPT_STORE REINIT		;Start control block re-init values
	DPT_STORE CRB,CRB$L_INTD+VEC$L_INITIAL,-  ;Controller init address
		      D,fD_CTRL_INIT
	DPT_STORE CRB,CRB$L_INTD+VEC$L_UNITINIT,- ;Unit init address
		      D,fD_UNIT_INIT
	DPT_STORE DDB,DDB$L_DDT,D,fD$DDT	  ;DDT address

	DPT_STORE END			;End of initialization table

; 
; DRIVER DISPATCH TABLE
; 
; 	The DDT lists entry points for driver subroutines which are
; 	called by the operating system.
; 

	DDTAB	-			;DDT creation macro
		DEVNAM=fD,-		;Name of device
		START=fD_STARTIO,-	;Start I/O routine
		UNSOLIC=0,-		;Unsolicited interrupt
		FUNCTB=fD_FUNCTABLE,-	;Function decision table
		CANCEL=0,-		;Cancel=NO-OP for files device
		REGDMP=0,-		;Can't dump any registers
		DIAGBF=0,-		;No diagnostic buffer
		ERLGBF=0		;No error logging

; 
; FUNCTION DECISION TABLE
; 
; 	The FDT lists valid function codes, specifies which
; 	codes are buffered, and designates subroutines to
; 	perform preprocessing for particular functions.
; 

fD_FUNCTABLE:
	FUNCTAB	,-			;List legal functions
		<UNLOAD,-		; Unload
		PACKACK,-		; Pack acknowledge
		AVAILABLE,-		; Available
		SENSECHAR,-		; Sense characteristics
		SENSEMODE,-		; Sense mode
		FORMAT,-		; Format (set size)
		READLBLK,-		; Read logical block
		WRITELBLK,-		; Write logical block
		READPBLK,-		; Read physical block
		WRITEPBLK,-		; Write physical block
		READVBLK,-		; Read virtual block
		WRITEVBLK,-		; Write virtual block
		ACCESS,-		; Access file / find directory entry
		ACPCONTROL,-		; ACP control function
		CREATE,-		; Create file and/or directory entry
		DEACCESS,-		; Deaccess file
		DELETE,-		; Delete file and/or directory entry
		MODIFY,-		; Modify file attributes
		MOUNT-			; Mount volume
		>
	FUNCTAB	,-			;Buffered functions
		<UNLOAD,-		; Unload
		PACKACK,-		; Pack acknowledge
		AVAILABLE,-		; Available
		SENSECHAR,-		; Sense characteristics
		SENSEMODE,-		; Sense mode
		FORMAT,-		; Format (set size)
		ACCESS,-		; Access file / find directory entry
		ACPCONTROL,-		; ACP control function
		CREATE,-		; Create file and/or directory entry
		DEACCESS,-		; Deaccess file
		DELETE,-		; Delete file and/or directory entry
		MODIFY,-		; Modify file attributes
		MOUNT-			; Mount volume
		>
	FUNCTAB	+ACP$READBLK,-		;Read functions
		<READLBLK,-		; Read logical block
		READPBLK,-		; Read physical block
		READVBLK-		; Read virtual block
		>
	FUNCTAB	+ACP$WRITEBLK,-		;Write functions
		<WRITELBLK,-		; Write logical block
		WRITEPBLK,-		; Write physical block
		WRITEVBLK-		; Write virtual block
		>
	FUNCTAB	+ACP$ACCESS,-		;Access functions
		<ACCESS,-		; Acceess file / find directory entry
		CREATE-			; Create file and/or directory entry
		>
	FUNCTAB	+ACP$DEACCESS,-		;Deaccess function
		<DEACCESS-		; Deaccess file
		>
	FUNCTAB	+ACP$MODIFY,-		;Modify functions
		<ACPCONTROL,-		; ACP control function
		DELETE,-		; Delete file and/or directory entry
		MODIFY-			; Modify file attributes
		>
	FUNCTAB	+ACP$MOUNT,-		;Mount function
		<MOUNT-			; Mount volume
		>
	FUNCTAB	+EXE$LCLDSKVALID,-	;Local disk valid functions
		<UNLOAD,-		;Unload volume
		 AVAILABLE,-		;Unit available
		 PACKACK-		;Pack acknowledge
		>
	FUNCTAB	+EXE$ZEROPARM,-		;Zero parameter functions
		<UNLOAD,-		; Unload
		PACKACK,-		; Pack acknowledge
		AVAILABLE,-		; Available
		>
	FUNCTAB	+EXE$ONEPARM,-		;One parameter function
		<FORMAT-		; Format (set size)
		>
	FUNCTAB	+EXE$SENSEMODE,-	;Sense functions
		<SENSECHAR,-		; Sense characteristics
		SENSEMODE-		; Sense mode
		>

	.SBTTL	DRIVER UNLOADING ROUTINE

; ++
; 
; fD_UNLOAD - DRIVER UNLOADING ROUTINE
; 
; FUNCTIONAL DESCRIPTION:
; 
; 	This routine is provided for compatibiltiy with other device
; 	drivers but does nothing.
; 
; 	The operating system calls this routine when unloading the
; 	driver.
; 
; INPUTS:
; 
; 	R4	- CSR address (controller status register)
; 	R5	- IDB address (interrupt data block)
; 
; OUTPUTS:
; 
; 	All general registers (R0 - R15) are preserved.
; 	
;--

fD_UNLOAD:
	RSB				;Return, driver cannot be unloaded

	.SBTTL	CONTROLLER INITIALIZATION ROUTINE
; ++
; 
; fD_CTRL_INIT - CONTROLLER INITIALIZATION ROUTINE
; 
; FUNCTIONAL DESCRIPTION:
; 
; 	This routine is provided for compatibiltiy with other device
; 	drivers but does nothing.
; 
; 	The operating system calls this routine:
; 		- During driver loading or reloading
; 		- During recovery from power failure
; 
; INPUTS:
; 
; 	R4	- CSR address (controller status register)
; 	R5	- IDB address (interrupt data block)
; 
; OUTPUTS:
; 
; 	All general registers (R0 - R15) are preserved.
; 	
;--

fD_CTRL_INIT:
	CLRL	IDB$L_CSR(R5)		;We don't have a csr
	RSB				;Return

	.SBTTL	UNIT INITIALIZATION ROUTINE
;++
; 
; fD_UNIT_INIT - UNIT INITIALIZATION ROUTINE
; 
; FUNCTIONAL DESCRIPTION:
; 
; 	This routine sets the pseudo disk unit online by setting
;	the online bit in the status word of the UCB. If this
;	device is the system disk, the size and address of the
;	in-memory buffer have been stored by SYSBOOT in the last
;	two longwords of the driver and these values are moved into
;	the UCB.
;
; 	The operating system calls this routine:
; 		- During driver loading (but not reloading)
; 		- During recovery from power failure
; 
; INPUTS:
; 
; 	R3	- 0 (Normally primary CSR)
; 	R4	- 0 (Normally secondary CSR)
; 	R5	- UCB address (unit control block)
;
; OUTPUTS:
; 
; 	The unit is set online.
; 	All general registers (R0-R15) are preserved.
; 
;--

fD_UNIT_INIT:
	BISW	#UCB$M_ONLINE,UCB$W_STS(R5)	;Set UCB status online
	CMPL	G^EXE$GL_SYSUCB,R5		;System disk?
	BNEQ	10$				;Branch if not
	MOVAL	fD_END,R1		;SYSBOOT put some stuff at the end
	ADDL	#^XF,R1			;Quadword align it
	BICL	#^XF,R1
	SUBL	#8,R1			;Point to last two longwords
	MOVL	(R1)+,UCB$L_MEMBUF(R5)	;Set up address of buffer
	DIVL3	#fD_BLKSIZ,(R1),-	;Set up size of buffer
		UCB$L_MAXBLOCK(R5)
10$:	RSB					;Return 

	.SBTTL	START I/O ROUTINE
;++
; 
; fD_STARTIO - START I/O ROUTINE
; 
; FUNCTIONAL DESCRIPTION:
;	Start I/O operation. Since no real device in involved, the
;	pseudo I/O operation is done completely in this routine.
;	unfortunately, that may involve substantial periods of time
;	spent at high (fork) IPL.
;
; INPUTS:
; 
; 	R3		- IRP address (i/o request packet)
; 	R5		- UCB address (unit control block)
; 	IRP$L_MEDIA	- Parameter longword (logical block number)
; 
; OUTPUTS:
; 
; 	R0	- First I/O status longword: status code & bytes xfered
; 	R1	- Second I/O status longword: 0 for disks
; 
; 	The I/O function is executed.
; 
; 	All registers except R0-R4 are preserved.
; 
;--

fD_STARTIO:				;Start I/O operation
; 
; 	Preprocess UCB fields
; 
	MOVW	IRP$W_FUNC(R3),UCB$W_FUNC(R5)  ;Save function code
	EXTZV	#IRP$V_FCODE,-		;Extract I/O function code
		#IRP$S_FCODE,IRP$W_FUNC(R3),R1
	MOVB	R1,UCB$B_FEX(R5)	;Store function dispatch index
; 
; 	Branch to function execution
; 

	BBS	#IRP$V_PHYSIO,-		;If set - physical I/O function
		IRP$W_STS(R3),10$
	BBS	#UCB$V_VALID,-		;If set - volume software valid
		UCB$W_STS(R5),10$
	MOVZWL	#SS$_VOLINV,R0		;Set volume invalid status
	BRB	FUNCXT			;And exit
10$:	CMPB	#IO$_UNLOAD, R1		;Unload function?
	BEQL	UNLOAD			;Branch if yes.
	CMPB	#IO$_AVAILABLE,R1	;Available function?
	BEQL	AVAILABLE		;Branch if yes.
	CMPB	#IO$_PACKACK,R1		;Packack function?
	BEQL	PACKACK			;Branch if yes.
	CMPB	#IO$_FORMAT,R1		;Format function?
	BEQL	FORMAT			;Branch if yes.
	BRW	XFER			;Otherwise, must be read or write

	.SBTTL	PACK ACKNOWLEDGE FUNCTION
; 
; PACK ACKNOWLEDGE FUNCTION EXECUTION
; 
; INPUTS:
; 
; 	R3		- IRP address (I/O request packet)
; 	R5		- UCB address (unit control block)
; 
; FUNCTIONAL DESCRIPTION:
; 
; 	Mark the volume valid by setting UCB$V_VALID in UCB$W_STS.
; 	IO$_PACKACK must be the first function issued to the pseudo
; 	disk after the driver has been loaded.
; 

PACKACK:				;Pack acknowledge
	BISW	#UCB$M_VALID,-
		 UCB$W_STS(R5)  	;Set software volume valid bit.
	BRB	NORMAL

	.SBTTL	UNLOAD AND AVAILABLE FUNCTIONS
;
;  UNLOAD AND AVAILABLE FUNCTIONS
;
; INPUTS:
; 
; 	R3		- IRP address (I/O request packet)
; 	R5		- UCB address (unit control block)
; 
; FUNCTIONAL DESCRIPTION:
; 
;	Mark the volume invalid by clearing UCB$V_VALID in UCB$W_STS.
;	since the disk can't be spun down, these two functions are
;	identical.
;
UNLOAD:
AVAILABLE:
	BICW	#UCB$M_VALID, -		;Clear software volume valid bit.
		UCB$W_STS(R5)
;	BRB	NORMAL			;Then complete the operation.

; 
; 	Operaton completion
; 
NORMAL:					;Successful operation complete
	MOVZWL	#SS$_NORMAL,-(SP)	;Assume normal completion status
	MOVW	IRP$W_BCNT(R3),2(SP)	;...merge in the byte count
	POPL	R0
FUNCXT:
	CLRL	R1
	REQCOM				;Complete request

	.SBTTL	SET SIZE OF PSEUDO DISK
;
;  FORMAT FUNCTION (SET SIZE)
;
; INPUTS:
; 
; 	R3		- IRP address (I/O request packet)
; 	R5		- UCB address (unit control block)
; 	IRP$L_MEDIA	- Parameter longword (new size of disk)
; 
; FUNCTIONAL DESCRIPTION:
; 
;	Deallocate memory associated with current pseudo disk (all
;	data is lost), allocate enough memory for the new size and
;	set relevant parameters.
;
FORMAT:
	MOVL	UCB$L_MEMBUF(R5),R0	;Any data currently in use?
	BEQL	10$			;Branch if nothing to deallocate
	MOVL	UCB$L_MAXBLOCK(R5),R1	;Number of blocks to deallocate
	BEQL	10$			;Branch if nothing to deallocate
	MULL	#fD_BLKSIZ,R1		;Convert blocks to bytes
	PUSHL	R3			;Save R3 across call
	ASSUME	fD_FIPL EQ IPL$_SYNCH	;At proper IPL?
	JSB	G^EXE$DEANONPGDSIZ	;Deallocate pool
	POPL	R3			;Restore ptr to IRP
10$:	MULL3	#fD_BLKSIZ,IRP$L_MEDIA(R3),R1	;Count of bytes to allocate
	BEQL	20$			;Branch if nothing to allocate
	JSB	G^EXE$ALONONPAGED	;Allocate memory
	BLBC	R0,20$			;Exit if error
	MOVL	R2,UCB$L_MEMBUF(R5)	;Save pointer to buffer
	DIVL3	#fD_BLKSIZ,R1,UCB$L_MAXBLOCK(R5) ;Convert blocks to bytes
	CVTLW	UCB$L_MAXBLOCK(R5),-	;Adjust disk size parameters too
		UCB$W_CYLINDERS(R5)
	BRB	NORMAL			;Successfull completion

20$:	CLRL	UCB$L_MEMBUF(R5)	;Mark as not used
	CLRL	UCB$L_MAXBLOCK(R5)	;Set size to zero
	BRB	FUNCXT			;Abnormal exit

; 
; Because the ACP FDT routines call QIODRVPKT, it is necessary
; for the actual transfer of data from the in-memory pseudo disk
; to/from the user's buffer to be done here rather than in FDT
; routines. Since we are no longer in process context, the data
; is transfered by IOC$MOVFRUSER or IOC$MOVTOUSER, which double
; map the user buffer using information in UCB$L_SVAPTE.
; 
; FUNCTIONS INCLUDE:
; 
;	Write data, and
;	Read data
; 
; INPUTS:
; 
; 	R3	- IRP address
; 	R5	- UCB address
;	IRP$L_MEDIA - LBN if log I/O, sector and cylinder if phy I/O
;
; FUNCTIONAL DESCRIPTION:
; 
;	If physical I/O, the specified cylinder, track, and sector
;	are converted to a byte offset from the start of the in-memory
;	buffer. (Note: unlike many real disks, no skew and interleave
;	factors are involved). For logical I/O, the byte offset is also
;	calculated, albeit in a different manner. Having obtained the
;	byte offset by some means, the data is moved from/to the user's
;	buffer.
; 

XFER:					;Transfer function execution
	BBC	#IRP$V_PHYSIO,-		;If clear - logical I/O
		IRP$W_STS(R3),10$
; 
; Convert cylinder, track, and sector to byte offset
; 
; 	Byte offset = Sector size * ( (Sectors per track)*Track + Sector )
; 
	MOVZBL	UCB$B_SECTORS(R5),R1	;Put sectors/track in R1
	MULW2	IRP$L_MEDIA+2(R3),R1	;Mult by track number
	ADDW2	IRP$L_MEDIA(R3),R1	;Add in sector
	DECL	R1			;Make zero based
	MULL2	#fD_BLKSIZ,R1		;Convert virtual sector to byte offset
	BRB	20$
10$:	MULL3	#fD_BLKSIZ,IRP$L_MEDIA(R3),R1  ;A simple conversion
20$:	ADDL2	UCB$L_MEMBUF(R5),R1	;Add to base of in-memory buffer
	MOVL	IRP$L_BCNT(R3),R2	;Get number of bytes to move
	BBC	#IRP$V_FUNC,IRP$W_STS(R3),30$ ;Read function?
	bsbw	fd$MOVTOUSER		;Move to user buffer (read)
	BRW	NORMAL
30$:	bsbw	fd$MOVFRUSER		;Move from user buffer (write)
	BRW	NORMAL

PWRFAIL:				;Power failure
	BICW	#UCB$M_POWER,UCB$W_STS(R5)  ;Clear power failure bit
	RSB				;Nothing is lost by power fail
					;So just continue

	.SBTTL	MOVE FROM USER BUFFER
;+
; fd$MOVFRUSER - MOVE FROM USER BUFFER
;
; THIS ROUTINE IS CALLED BY AN I/O DRIVER TO MOVE A STRING FROM A USER
; BUFFER TO AN INTERNAL BUFFER.
;
; INPUTS:
;
;	R0 = ADDRESS OF USER'S BUFFER.
;	R1 = ADDRESS OF INTERNAL BUFFER.
;	R2 = NUMBER OF BYTES TO BE MOVED.
;	R5 = UCB ADDRESS OF DEVICE UNIT.
;
; OUTPUTS:
;
;	***TBS***
;-
 
	.ENABLE	LSB
fd$MOVFRUSER::				;MOVE FROM USER BUFFER
	JSB	g^IOC$INITBUFWIND	;SETUP WINDOW INTO BUFFER
	pushl	r10			; store R10
	bicl3	#^C511,r0,r10		; find end of first page
	subl3	r10,#512,r10		; determine number to move
	cmpl	r10,r2			; is number of bytes left in this page
					; more than the transfer size?
	bleq	20$			; no, we are ok
	movl	r2,r10			; yes, make the transfer size the 
					; number to move!
	brb	20$			; jump into loop

5$:
	addl	r10,r0			; move input pointer
	addl	r10,r1			; move output pointer
	ADDL	#4,UCB$L_SVAPTE(R5)	;UPDATE ADDRESS OF USER PTE
	JSB	g^IOC$FILSPT		;FILL SYSTEM PTE WITH PROPER RELOCATION
	movl	r2,r10			; save count remaining in move count
	cmpl	r10,#512		; is move count > 512?
	blequ	20$			; no, move that # of bytes
	movl	#512,r10		; yes, move just 1 page
20$:
	pushr	#^m<r0,r1,r2,r3,r4,r5>	; save registers
	movc3	r10,(r0),(r1)		; move one page
	popr	#^m<r0,r1,r2,r3,r4,r5>	; restore registers

	subl	r10,r2			; decrement count of remaining bytes
	bgtr	5$			; if not zero, go back for more
30$:
	popl	r10			; restore r10
	RSB				;

	.DSABL	LSB
	.PAGE
	.SBTTL	MOVE TO USER BUFFER
;+
; fd$MOVTOUSER - MOVE TO USER BUFFER
;
; THIS ROUTINE IS CALLED BY AN I/O DRIVER TO MOVE A STRING FROM AN INTERNAL
; BUFFER TO A USER BUFFER.  differs from IOC$ routine by using movc3 rather
; than moving one byte at a time.
;
; INPUTS:
;
;	R1 = ADDRESS OF INTERNAL BUFFER.
;	R2 = NUMBER OF BYTES TO BE MOVED.
;	R5 = UCB ADDRESS OF DEVICE UNIT.
;
; OUTPUTS:
;
; ***TBS***
;-
 
	.ENABLE	LSB
fd$MOVTOUSER::				;MOVE TO USER BUFFER
	JSB	g^IOC$INITBUFWIND	;SETUP WINDOW INTO BUFFER
	pushl	r10			; save r10
	bicl3	#^C511,r0,r10		; find end of first page
	subl3	r10,#512,r10		; determine number of bytes to move
					; that are on first page
	cmpl	r10,r2			; is number of bytes left in this page
					; more than the transfer size?
	bleq	20$			; no, we are ok
	movl	r2,r10			; yes, make the transfer size the total
	brb	20$			; jump into loop

5$:
	addl	r10,r0			; move input pointer 
	addl	r10,r1			; move output pointer
	ADDL	#4,UCB$L_SVAPTE(R5)	;UPDATE ADDRESS OF USER PTE
	JSB	g^IOC$FILSPT		;FILL SYSTEM PTE WITH PROPER RELOCATION
	movl	r2,r10			; save count remaining in move count
	cmpl	r10,#512		; is count remaining > 512?
	blequ	20$			; no, move just the count then
	movl	#512,r10		; yes, move just 1 page
20$:
	pushr	#^m<r0,r1,r2,r3,r4,r5>	; save registers
	movc3	r10,(r1),(r0)		; move one page
	popr	#^m<r0,r1,r2,r3,r4,r5>	; restore registers

	subl	r10,r2			; decrement count of remaining bytes
	bgtr	5$			; if non zero, move more data

	popl	r10			; restore r10
	RSB				; and return

	.BLKL	2			; Filled in by SYSBOOT
fD_END:					; Last location in driver
	.end

	.TITLE	SETSIZE
;
; 	F D _ S E T S I Z E . M A R
;
; Abstract:
;	this program sets the size of the fda0 memory disk.  supply the
;	number of blocks for the device.  Note that the memory is taken
;	from nonpaged pool.  code stolen from STABACKIT.COM VMS 4.4.
;
; assembly and link instructions:
;	$macro fd_setsize
;	$link fd_setsize
;
	$IODEF

	.PSECT	$DATA,WRT,NOEXE,LONG

PD_DESCR:
	.ASCID	"fDA0:"
PD_CHAN:
	.BLKL	1
PD_IOSB:
	.BLKQ	1
QIO_ARGS:
	$QIO	IOSB=PD_IOSB
CMD_DESCR:
	.LONG	4
	.ADDRESS SIZ_ASC
SIZ_ASC:
	.BLKB	6
PROMPT:
	.ASCID	"Device Size in blocks: "
PD_SIZE:
	.BLKL	1

	.PSECT	$CODE,EXE,NOWRT

	.ENTRY	SETSIZE,^M<>

	$ASSIGN_S DEVNAM=PD_DESCR,CHAN=PD_CHAN	; assign a channel to the device
	BLBC	R0,DONE				; test status
	MOVZWL	PD_CHAN,QIO_ARGS+QIO$_CHAN	; set up QIO list

	PUSHAL	CMD_DESCR			; return string length
	PUSHAQ	PROMPT				; prompt string
	PUSHAQ	CMD_DESCR			; return string descriptor
	CALLS	#3,G^LIB$GET_FOREIGN		; get the device size requested

	PUSHAL	PD_SIZE
	PUSHAL	CMD_DESCR
	CALLS	#2,G^OTS$CVT_TI_L		; turn this to binary

	MOVZBL	#IO$_PACKACK,QIO_ARGS+QIO$_FUNC
	$QIOW_G	QIO_ARGS			; enable the device
	BSBW	ERRCHK

	MOVZBL	#IO$_FORMAT,QIO_ARGS+QIO$_FUNC
	MOVL	PD_SIZE,QIO_ARGS+QIO$_P1
	$QIOW_G	QIO_ARGS			; allocate pool for device
	BSBW	ERRCHK
DONE:	RET					; that's it folks!

ERRCHK:
	BLBC	R0,20$
	BLBC	PD_IOSB,10$
	RSB
10$:	MOVZWL	PD_IOSB,R0
20$:	RET
	.END	SETSIZE

$!
$!		F D D R I V E R _ S T A R T U P . C O M
$!
$! load the fddriver pseudo disk and initialize and mount it.  
$! include a call to this procedure from systartup.com.
$!
$	mc sysgen
conn fda0/noada
$!
$	setsize = "$fd_setsize
$	setsize 500			! adjust as needed!
$!
$	init/system/cluster=1/nohigh	fda0 fast_disk
$	mount/system/nomount_ver	fda0 fast_disk fast$
$!
    
T.RTitleUserPersonal
Name
DateLines
250.1Please submit to the TOOLSHEDMETOO::LAMIAMon Jun 02 1986 09:444
    Please consider submitting this to the TOOLSHED.
    
    Refer to METOO::TOOLS$LIBRARY:SW_TOOLS_CATALOG for instructions
    (in the first few notes) on how to submit tools.
250.2Performance vs. PDDRIVER?11740::KAISERSun Jun 08 1986 13:474
It would be interesting to see the performance figures for this driver compared
to PDDRIVER.

---Pete
250.3yup, sure wouldBARAKA::LASTOVICANorm LastovicaMon Jun 09 1986 12:531
    
250.4Is it a fully implimented DSA disk ?PYRITE::HAFEZAmr A. Hafez &#039;On the EVE of Destruction&#039;Mon Jun 09 1986 16:5715
    I did not read the driver code , but can the psuedo disk be made
    availlable to the cluster ? A normal DSA disk can be. This may be
    an interesting way to share memory through the CI without using
    multiport memory. When we get our systems clustered, I will pull
    your code over and try it unless you can save me time by telling
    me if it will work. 
    	Also since it is a file structured device, we should be able
    to map global sections  on it, of course that does not use qio's.
    This would be a full circle implimentation to make memory look like
    disk that looks like memory, but can be shared across the cluster.
    
    
    			nice work tho
    			Amr Hafez
    
250.5Not yetBARAKA::LASTOVICANorm LastovicaMon Jun 09 1986 20:506
    well no, currently it is not cluster available.  It is not an MSCP
    class driver and can thus not take advantage of MSCP.  In the future
    that would be a very nice (and not unreasonably difficult) task.
    Remember, treat this disk as (for example) an RX01.  Access it through
    the driver as another device.  Since it talks as the driver, anything
    that you can do on said RX01 will work here.
250.6PASTIS::MONAHANTue Jun 10 1986 04:2213
    	It doesn't have to be a class/port driver to be MSCP served.
    The only disk *not* supported by the MSCP server is the RX02, and
    that is because the server protocol cannot handle the :-
    
    $ init /density=double
    
    qualifier for the RX02. So provided you do not support a command
    to change the density of your non-paged pool you should have no
    problems making it cluster available.
    
    		Dave
    (now wouldn't a command to change the density of your memory really
    be useful :-)  )
250.7MSCP and meBARAKA::LASTOVICANorm LastovicaThu Jun 12 1986 01:5411
    Humm, I've not looked into it at all.  So what will I have to change?
     Anything?  Well obviously something I guess.  It is "invalid for
    requested operation at this point".  I'll look into it when I have
    the chance.
    
    As far as memory, "I know everything, but I can only recall a bit
    of it at any given time".
    
    For anyone interested, I've got a new version that Frank Droste
    patched that prevents the device from being formatted while it is
    mounted.  Thanks Frank!
250.8And guess what else...BARAKA::LASTOVICANorm LastovicaThu Jun 12 1986 02:499
    I did some more poking about in the last few minutes.  I found that
    the SET DEVICE/SERVED code does the checking for what can and can
    not be set served.  The code excludes any non disk, or RX01, RX02 and
    RX04 (don't ask me).  FDA0 was claiming to be an RX01.  Soooo, I
    had to chose another device.  My first reaction was ML11 ("MEMORY LADEN
    11" sounds about right huh? ) but I settled on FD8 (foreign disk #8)
    to keep things correct.  So that should let it be served.  Problem is my
    cluster that I can test crashy sorts of things is only 1 node big.
    
250.9MSCP'able, handles bunches of memory and more!BARAKA::LASTOVICANorm LastovicaSun Aug 31 1986 20:358
    Since the original set of notes on the topic, the FDDRIVER is now
    MSCP servable.  Several people deserve credit here.  I'll include
    the latest document on the subject as the next reply.  As in the
    past, send me mail if you need a copy.  I know, I know, "Submit
    it to the toolshed".  Once I make a few more stabs at changes
    (performance oriented I hope), I will.
    
    	norm
250.10FDDRIVER.MEM (never tech-edited or reviewed!)BARAKA::LASTOVICANorm LastovicaSun Aug 31 1986 20:36224





                                  FDDRIVER.MEM

                                  20-Aug-1986







               NOTE:  This tool  is  an  in  house,  experimental

               program   for   your   use  on  Digital  Equipment

               Corporation internal machines.









          This document is an interim user's guide for the FDDRIVER "kit".









          FDDRIVER implements a memory based pseudo disk device for VAX/VMS

     systems.   The  primary  advantages  of a memory resident disk is that

     there are no disk latency  times  involved,  there  is  no  controller

     contention  and  all  transfers  happen at CPU (via CPU busses) speed.

     Files that are often accessed and those that are read only can benefit

     greatly from this driver due to performance gains over a physical disk

     device.  Development of this tool was based as a learning exercise  as

     well   as  an  attempt  to  solve  performance  problems  of  existing

     applications.



          The driver is designed to implement  a  device  that  is  totally

     transparent  to  the  system and application in terms of functionality

     and operation.  The only  difference  between  the  FD  device  and  a

     physical  disk should be a noticeable performance improvement with the

     former.  The FD device is able to be MSCP served  as  any  local  disk

     would  be  (note  that the memory disk is in no way dual pathed, and a

     host failure is terminal to the device).   The  current  FDDRIVER  has

     been  shown  locally  to run on VMS versions 4.5 Field Test, V4.4 V4.3

     and V4.2 although any 4.x  version  of  VMS  should  be  able  to  run

     FDDRIVER  with  no  problems.  At this time no testing of any kind has

     been done with versions prior to V4.2, and it is  expected  that  this

     code  will NOT work on V3 systems (though it would be possible to make

     it work, assuming that it does not).



          In most cases, applications would be better off being  redesigned

     than  'fixed'  by using the FDDRIVER.  However, in cases where this is

     impractical (or for files that are commonly  accessed),  FDDRIVER  can

     often  help  performance  significantly  with no code changes (often a

     logical name redefinition is all that is needed).   Applications  that

     are  I/O  bound  are  obviously  helped  the  most.  It seems that DCL

     procedures executed from a memory disk are noticeably  faster  as  are

     common  program  development  functions (edit, compile, edit, compile,

     link, run, edit...).



          As the device is resident in memory, a system failure will result

     in  the  lose of all data in/on the device (as well as access to other

     systems via the MSCP server).  This makes frequent backups to physical

     disk  necessary  in  applications  where  important  (or  difficult to


                                                                     Page 2





     replace) data is  modified.   Directing  editor  journal  files  to  a

     physical  is  an option for protection in certain cases.  Some uses of

     the device will allow loading read-only data into the device at system

     startup  and  then  defining  a  logical  to  point to the memory disk

     instead of the usual physical disk device.  Directory search lists are

     often  helpful here in that the application directory would be totally

     unchanged and copies of some files would be copied to the memory disk.

     In  this  way,  the  applications  are  unaware of any change, and the

     system can be later  changed  back  to  using  a  physical  device  by

     redefining the logical back to its original state.



          Background on the driver as it exists can be found by  inspecting

     SYS$UPDATE:STABACKIT.COM  as  distributed with VMS V4.4.  Basically, a

     portion (user specified size) of nonpaged pool  is  allocated  by  the

     driver  for  use  as  the  device  space.   Then,  the  "disk"  can be

     initialized, mounted, and accessed as would a 'real' disk device.  The

     memory  is  accessed as a series of pages representing a physical disk

     with disk blocks.  The original PDDRIVER (that this  code  is  largely

     lifted  from)  distributed  with  Micro  VMS for use in the standalone

     backup process used a loop in IOC$ routines to perform byte at a  time

     transfers to and from the user's buffer at fork IPL.  Needless to say,

     there is significant overhead in doing things this way.



          And, as  can  be  guessed,  this  new  version  does  MOVC3  (VAX

     instruction for moving a block of data) transfers of up to one page at

     a time.  This one page at a time is the current limit because a single

     mapping  register  is used to map the user's buffer into system space.

     The data transfer happens at elevated IPL, so this type of mapping  is

     required.   Remember  that  even in the FDDRIVER, all transfers to and

     from the user's buffer happen at fork IPL.  The primary  advantage  of

     FDDRIVER  is  less overhead due to moving blocks of data with a single

     instruction rather than one move for each byte.



          The FDDRIVER utility is made up of two pieces of VAX MACRO  code.

     The  first  program  is  called FD_SETSIZE.MAR and is used to tell the

     driver (or device depending on how you look at it) how  much  pool  to

     allocate  (remember,  1  page  is  512  bytes of NONPAGED pool).  This

     program typically would be run once, after the driver is loaded.   The

     other  piece  of  code  is  the  driver  proper (FDDRIVER.MAR).  It is

     assembled and linked and then loaded with SYSGEN.  The driver includes

     all  common  disk  driver  functions,  including a 'format' command to

     allocate memory (this function is used by FD_SETSIZE).



          FDDRIVER_STARTUP.COM (supplied as an example) can be called  from

     SYSTARTUP.COM  to  load  the driver, configure the device and mount it

     each   time   the   system   boots.    Another   command    procedure,

     BUILD_FDDRIVER.COM,  is  supplied  to assemble and link the driver and

     support program.



          Operation would usually proceed as follows:  Once the  driver  is

     loaded,  the  set  size  program is run.  The user is prompted for the

     needed device size in pages.  Assuming sufficient nonpaged  memory  is

     available for the requested number of pages, the pool is allocated and

     the program returns to DCL.  If memory is not  available,  the  driver

     returns  an  error  and  the  device is left with no pages.  After the


                                                                     Page 3





     device is sized, it may be accessed as any  other  disk  device.   The

     user  will then initialize the disk (as any 'real' disk would require)

     and then mount it.  If needed, the  device  may  be  set  MSCP  served

     before it is mounted.



          As far as I know this code is safe.  It has not  crashed  any  of

     our  systems  in  testing in quite a while of active (and semi-active)

     use.  Several other internal sites are  using  the  driver  with  very

     favorable results.  But, given the choice, I'd make initial tests on a

     little used machine or after hours...



          Until I get around to submitting  this  to  the  toolshed  and/or

     creating  a proper VMSINSTALable kit, the assembly is by hand with the

     aid of a command procedure.  To assemble and link the driver,  execute

     the  command  procedure  FDDRIVER_BUILD.COM.   This  will  create  the

     executables FDDRIVER.EXE and FD_SETSIZE.EXE.  You will  then  need  to

     copy  FDDRIVER.EXE to SYS$SYSTEM.  FD_SETSIZE may be left where it is,

     or copied to SYS$SYSTEM (or the usual site location for these sorts of

     utility  programs).   Also,  it may be necessary to rebuild the driver

     for new releases of VMS (probably only at 'even' numbered releases  if

     at all).  To do so, simply execute FDDRIVER_BUILD again.



          You may want to edit FDDRIVER_STARTUP.COM to set  the  device  to

     the  proper  size and possibly enable MSCP serving of the device (on a

     cluster) by removing the commented code  in  the  procedure.   Execute

     this  procedure  to  load the driver, set the size, and initialize and

     mount the device.  You may want to execute  FDDRIVER_STARTUP.COM  from

     your   site   specific  system  startup  procedure  (SYSTARTUP.COM  in

     SYS$MANAGER) to have the device loaded each time the system boots.



          You will most likely need to  raise  the  values  of  the  SYSGEN

     system parameters NPAGEDYN and NPAGEVIR an appropriate amount in order

     to support the size of the pseudo device.  This can be done by  adding

     lines   to  MODPARAMS.DAT  specifying  new  values  for  NPAGEVIR  and

     NPAGEDYN, and then running AUTOGEN.  If the device size for FDA0  will

     remain  a  known  constant  and  if  FDA0  is always created at system

     startup, add this value (in bytes) to both NPAGEDYN and NPAGEVIR.   If

     the  size  is  unknown,  or  if the driver is not always used, add the

     expected maximum size of the driver (again in bytes) to  NPAGEVIR  and

     leave  NPAGEDYN  alone.   This will leave the amount of memory that is

     reserved for the non paged pool at a reasonable size when  the  driver

     is not in use.



          Release notes:



          11-Jun-1986:  This version implements two changes:



          First, the device may not be formatted with  the  format  command

     while  it  is  mounted.   This  helps  prevent system crashes when the

     device is resized while mounted.  Second, the device type  is  changed

     from  RX01  to  FD8  (foreign  disk  type  8).  This change allows the

     device to be set MSCP served.  The  SET  DEVICE/SERVED  code  excludes

     RX01's, RX02's and RX04's (don't as me).


                                                                     Page 4





          27-Jun-1986:  This version is thanks to Rick Murphy:



          The driver was not able to be MSCP  served  with  any  amount  of

     success.   Rick fixed an undocumented field in the driver prologue and

     it now is MSCP working (it  appears).   Note  that  I  have  had  some

     trouble  making  the  'remote' system handle all access cases with the

     driver.  Nothing conclusive yet.



          17-Jul-1986:  This revision was prompted due to a request by Mike

     Greenfield (running on a machine with a tremendous amount of memory):



          The previous version limited the device size to 9999 blocks  (due

     to  4  bytes of input used from the terminal).  This version increases

     the limit to six bytes (999999  blocks!).   If  this  is  not  enough,

     perhaps  8 bytes will be!  And, FDDRIVER_STARTUP.COM now will not load

     the driver if it is there.  The  FD_SETSIZE  call  will  fail  if  the

     device  is mounted when the procedure is run.  This change prevents an

     access violation from SYSGEN if the driver is loaded again.   Finally,

     FDDRIVER_STARTUP.COM  includes an example line to make the FDA0 device

     cluster available via the MSCP server.



          20-Aug-1986:  This revision also  due  to  a  request  from  Mike

     Greenfield (still with lots of memory!):



          In the past, the cylinder count was the number of blocks  on  the

     device (SECTORS=TRACKS=BLOCKS).  Since the cylinder cound is stored in

     a 16 bit word, it had problems going over  65k  cylinders.   Now,  the

     cylinder  count is half the block count because there are 2 blocks per

     track.  This will all the device to have more than 65k blocks.  Later,

     the  sectors  per  track may be a dynamic calculation.  For now, it is

     fixed at 2 sectors per track.









          Please let me know if you find changes to be made (ie.  make them

     and let me know).  Good luck!







             Norman Lastovica

             Customer Support Center / Colorado Springs - TSSG

             Easynet:        DUNE::LASTOVICA

             DTN:            523-4382

             Location:       CX03 1/M12

    
250.11Just thought you might like to know..MDVAX3::COARA wretched hive of bugs and flamers.Sat Nov 21 1987 18:2127
    One of our (Digital's) customers has taken PDDRIVER and made some
    changes to it.  Among other things, he set it up to use MOVC3
    instructions (as does FDDRIVER), and also to run in process context
    at IPL$_ASTDEL, so as not to block higher-level interrupts.  He
    claim it is at least twice as fast (I/Os per second) as the original
    PDDRIVER, with an average rate of 132 operations per second on a
    VAX 11/785.  (These figures are from memory [mine, not the RAM
    disk's!].)
    
    The customer has pointed out that running at IPL$_ASTDEL would allow
    the RAM disk to live in PAGED pool rather than NONPAGED pool, and
    therefore be backed by the primary pagefile.  However, since such
    a scenario would require tweaking some system parameters, he has
    not done anything with it.
    
    I believe he is currently thinking of a P1-space per-process RAM
    disk for processes with huge working sets.  He says this was suggested
    to him for RSX TKB development on the VAX.  ;-)
    
    He has done quite a bit of work on it, and will probably be submitting
    it to the DECUS VAX SIG tapes in Anaheim, December 1987.  (Please
    do not flame at ME about the legality of such a move; he is concerned
    about it himself.  He suspects that the sheer amount of changes
    he has had to make justifies his driver's existence as a `new work'
    rather than `modifications.')
    
    #ken	:-)}
250.12UFP::MURPHYRick - WA1SPT/4Sat Nov 21 1987 21:239
    "In process context"? That's a good trick.. do you do it all in the FDT
    routines - that is, no start I/O at all? I can't think of any other way
    to do this; if you call EXE$QIODRVPKT you've lost process context by
    the time the start I/O routine happens.
    
    Putting it in paged pool does not sound like a very hot idea; you'll be
    trading page fault I/O for "normal" I/O - I'd rather see the memory put
    into ACP caches and RMS buffers.
    	-Rick
250.13MARVIN::WARWICKDNA puts life into your networkMon Nov 23 1987 09:457
    
    If you have an Altstart routine, and send stuff to it with 
    EXE$ALTQUEPKT, you end up in the Altstart routine with all the process
    context (mind you, that's pretty similar to doing it all in the
    FDT routines anyway).
    
    Trev
250.14Neat idea!DUCATI::LASTOVICAain&#039;t juggling till there&#039;s 3 upMon Nov 23 1987 20:4313
    It seems to me that the customer is doing it in a real clever way. By
    putting the disk area in paged pool, some portion of the disk (the most
    often used part) can be memory resident while the rest can be out on a
    real disk, sitting unused.  The largest drawback in the current
    FDDRIVER is that it keeps the entire disk resident at all times.  This
    is bad in that if only 10% of the disk is hit most of the time, 90% of
    the disk space in memory is wasted.  My next suggestion would be to
    make a shared global section that is paged to a backing store of some
    large size.  This will also easily keep all the changes made to the
    disk if it is periodically flushed. 
    
    Getting those large improvements (or greater gains) in performance over
    the PDDRIVER by using MOVC is not surprising.