.TITLE ASNSD - VAX/VMS VIRT DISK DRIVER ASSIGN/DEASSIGN .IDENT 'V00-01A' ; Copyright 1994 Glenn C. Everhart ; All rights reserved ; ; FACILITY: ; ; ASSIGN/DEASSIGN VIRTUAL DISK TASK THAT WORKS WITH VDDRIVER ; ESTABLISHES CONNECTION (OR BREAKS IT) BETWEEN A LUN OF ; SD: AND A CONTIGUOUS FILE. ; This assign program is the image which assigns up to two files ; at a time to SDdriver (striping disk driver) to allow striping. ; It also sets up reserved space, chunk (granule) size, and so on. ; Up to 6 containers are allowed; the first reserved block if any ; contains description info about the disks composing the save ; areas. SDdriver allocates IRPs as needed, but does not attempt ; to merge multiple parts of a long i/o to one disk into a single ; IRP as DEC's driver does, but rather keeps them separate so it ; never needs to copy data into pool. Data copying is viewed as ; a greater evil than an extra IRP or two now and then. ; ; The stripe driver SDDRIVER will use the first reserved block ; to hold info about the stripeset if possible. ; The block will contain number of parts, working number parts ; (used as we fill in), size of reserved area, size of each ; part, total size of disk, and chunk size. Each piece will be ; represented by devicename, unit number, start LBN, and size ; for up to 6 pieces (determined by UCB space). ; This will detect most (but NOT all) potential errors in ; assigning storage. The error detection is intended to be helpful, ; but not absolutely bulletproof, which I deem infeasible. ; Command format: ; ASNSD/switches SDn: file1 file2 ; where a .CLD file is expected so that this can all be parsed by ; the CLI. ; ; Note: define VMS$V5 to build for Version 5.x of VMS. VMS$V5=1 ; ; ; AUTHOR: ; ; G. EVERHART ; ; 04-Aug-1989 D. HITTNER Cleaned up definitions, added messages ; 29-Aug-1989 G. Everhart Added more flexible device geometry selection ; 03-jan-1994 G. Everhart Striping driver stuff ;-- .PAGE .SBTTL EXTERNAL AND LOCAL DEFINITIONS .LIBRARY /SYS$SHARE:LIB/ ; ; EXTERNAL SYMBOLS ; $ADPDEF ;DEFINE ADAPTER CONTROL BLOCK $ATRDEF $CRBDEF ;DEFINE CHANNEL REQUEST BLOCK $DCDEF ;DEFINE DEVICE CLASS $DDBDEF ;DEFINE DEVICE DATA BLOCK $DEVDEF ;DEFINE DEVICE CHARACTERISTICS $DPTDEF ;DEFINE DRIVER PROLOGUE TABLE $DVIDEF ;Symbols for $GETDVI service. $EMBDEF ;DEFINE ERROR MESSAGE BUFFER $FABDEF $FATDEF $FIBDEF ;Symbols for file information block. $IDBDEF ;DEFINE INTERRUPT DATA BLOCK $IODEF ;DEFINE I/O FUNCTION CODES $IRPDEF ;DEFINE I/O REQUEST PACKET $NAMDEF $PRDEF ;DEFINE PROCESSOR REGISTERS $RMSDEF $SBDEF $SCSDEF $SSDEF ;DEFINE SYSTEM STATUS CODES $STSDEF ;Symbols for returned status. $TPADEF ;Symbols for LIB$TPARSE calls. $UCBDEF ;DEFINE UNIT CONTROL BLOCK $VECDEF ;DEFINE INTERRUPT VECTOR BLOCK $XABDEF ; ; UCB OFFSETS WHICH FOLLOW THE STANDARD UCB FIELDS ; DEFINE THESE SO WE KNOW WHERE IN THE UCB TO ACCESS. WE MUST ; SET THE ONLINE BIT OR CLEAR IT, AND ALSO SET ; UCB$HUCB (HOST UCB ADDRESS), UCB$HFSZ (HOST FILE SIZE), ; AND UCB$HLBN (HOST LOGICAL BLOCK NUMBER OF FILE START) ; ; Note: These MUST match the definitions in SDDRIVER. Don't ; change one without changing the other to match it!!! ; G. Everhart 10/10/1989 ; ; UCB OFFSETS WHICH FOLLOW THE STANDARD UCB FIELDS ; $DEFINI UCB ;START OF UCB DEFINITIONS ;.=UCB$W_BCR+2 ;BEGIN DEFINITIONS AT END OF UCB .=UCB$K_LCL_DISK_LENGTH ;v4 def end of ucb ; USE THESE FIELDS TO HOLD OUR LOCAL DATA FOR VIRT DISK. ; Add our stuff at the end to ensure we don't mess some fields up that some ; areas of VMS may want. $DEF UCB$PPID .BLKL 1 ;PID OF ORIGINAL PROCESS FROM IRQ BLK ; host descriptor areas cntof: $DEF UCB$HUCB .BLKL 1 ;ADDRESS OF HOST UCB $DEF UCB$HLBN .BLKL 1 ;LBN OF HOST FILE $DEF UCB$HFSZ .BLKL 1 ;SIZE OF HOST FILE, BLKS ucbcntsz=.-cntof $def ucb$hucb2 .blkl 1 ;host UCB of file 2 $def ucb$hlbn2 .blkl 1 ;LBN of file 2 $def ucb$hfsz2 .blkl 1 ; One label block has 6 longs for fixed info plus 7 longs per ; container. This is enough for 17 containers. I dislike pushing ; things so allow up to 16 here. .blkl 30 ; Space for 10 more info sets .blkl 12 ;and 4 more (total 16 now) .blkl 3 ;safety ; NOTE: It is important to ENSURE that we never clobber IRP$L_PID twice! ; therefore, adopt convention that UCB$PPID is cleared whenever we put ; back the old PID value in the IRP. Only clobber the PID where ; UCB$PPID is zero!!! $DEF UCB$stats .BLKL 1 ;STATUS CODE SAVE AREA $DEF UCB$OBCT .BLKL 1 ;STORE FOR IRP$L_OBCNT too $def ucb$totfsz .blkl 2 ;Total size of virt dsk $def ucb$lmedia .blkl 1 ;storage for IRP$L_MEDIA $def ucb$owind .blkl 1 ; store irp$l_wind... $def ucb$osegv .blkl 1 ; and irp$l_segvbn $def ucb$l_SD_host_descr .blkl 2 ; char string descr ; $def ucb$vdcontfil .blkb 148 ; ; striping extra fields $def ucb$grnsiz .blkl 1 ;size of a stripe chunk in blocks $def ucb$irpcnt .blkl 1 ;count of IRPs for this i/o $def ucb$ncont .blkl 1 ;number container files $def ucb$bcntwk .blkl 1 ;work storage for byte count used $def ucb$sublbn .blkl 1 ;lbn of current sub-irp $def ucb$grnbas .blkl 1 ;number of reserved blocks this seg $def ucb$subsva .blkl 1 ;system virt addr for current IRP ; $def ucb$l_rclok .blkl 1 ;Flag that keeps us from finishing I/O till ;all IRPs are sent. $def ucb$q_SD_svaptetmp .blkl 2 $def ucb$l_SD_flag .blkl 1 ;sanity flag to ensure we have right driver ; next 2 left over from vqdriver $def ucb$shmd .blkl 1 ;shadow mode. 0=use file 1 only $def ucb$rwlk .blkl 1 ; read/write interlock. Initialize to 1 $def ucb$rwlbn .blkl 1 ; LBN of first block in special read/logical $def ucb$rwsz .blkl 1 ; size of special transfer $def ucb$llbn1 .blkl 1 ; last LBN of file 1 $def ucb$llbn2 .blkl 1 ; last LBN of file 2 $def ucb$ucbos .blkl 1 ; offset to ucb/lbn/fsz in ucb to use at fin-io $def ucb$rwdir .blkl 1 ;read (0) or write (1) I/O $def ucb$ercd1 .blkl 1 ; store for error code of 1st write of 2 ; $DEF UCB$K_SD_LEN .BLKW 1 ;LENGTH OF UCB ;UCB$K_SD_LEN=. ;LENGTH OF UCB $DEFEND UCB ;END OF UCB DEFINITONS ; TO SET ONLINE: ; BISW #UCB$M_ONLINE,UCB$W_STS(R5) ;SET UCB STATUS ONLINE ; Macro to check return status of system calls. ; .MACRO ON_ERR THERE,?HERE BLBS R0,HERE BRW THERE HERE: .ENDM ON_ERR .macro bgeqw guess,?where blss where brw guess where: .endm ; ; ; .PSECT ADVDD_DATA,RD,WRT,NOEXE,quad DEFAULT_DEVICE: .ASCID /SYS$DISK/ .ALIGN LONG DFAB_BLK: $FAB FNM=,XAB=FNXAB,FAC=,DNM= ; FNXAB: $XABFHC ; XAB STUFF TO GET LBN, SIZE .BLKL 20 ;SAFETY IOSTATUS: .BLKQ 1 DEV_BUF: ; Buffer to hold device name. .BLKB 40 DEV_BUF_SIZ = . - DEV_BUF DEV_BUF_DESC: ; Descriptor pointing to device name. .LONG DEV_BUF_SIZ .ADDRESS DEV_BUF ; SECOND FILE CONTROL BLOCKS .ALIGN LONG EFAB_BLK: $FAB FNM=,XAB=EFNXAB,FAC=,DNM= ; EFNXAB: $XABFHC ; XAB STUFF TO GET LBN, SIZE .BLKL 20 ;SAFETY EIOSTATUS: .BLKQ 1 EDEV_BUF: ; Buffer to hold device name. .BLKB 40 EDEV_BUF_SIZ = . - EDEV_BUF EDEV_BUF_DESC: ; Descriptor pointing to device name. .LONG EDEV_BUF_SIZ .ADDRESS EDEV_BUF PID: ; Owner of device (if any). .BLKL 1 EPID: .BLKL 1 DEV_ITEM_LIST: ; Device list for $GETDVI. .WORD DEV_BUF_SIZ ; Make sure we a have a physical device name. .WORD DVI$_DEVNAM .ADDRESS DEV_BUF .ADDRESS DEV_BUF_DESC .WORD 4 ; See if someone has this device allocated. .WORD DVI$_PID .ADDRESS PID .LONG 0 .WORD 4 .WORD DVI$_DEVCLASS ; Check for a terminal. .ADDRESS DEV_CLASS .LONG 0 .LONG 0 ; End if item list. ; DUPLICATE ITEM LIST FOR 2ND FILE. EEV_FLAG: .LONG 0 EEV_ITEM_LIST: ; Device list for $GETDVI. .WORD EDEV_BUF_SIZ ; Make sure we a have a physical device name. .WORD DVI$_DEVNAM .ADDRESS EDEV_BUF .ADDRESS EDEV_BUF_DESC .WORD 4 ; See if someone has this device allocated. .WORD DVI$_PID .ADDRESS EPID .LONG 0 .WORD 4 .WORD DVI$_DEVCLASS ; Check for a terminal. .ADDRESS DEV_CLASS .LONG 0 .LONG 0 ; End if item list. DEV_CLASS: .LONG 1 ;** VDV_BUF: ; Buffer to hold VDVice name. .BLKB 40 VDV_BUF_SIZ = . - VDV_BUF VDV_BUF_DESC: ; Descriptor pointing to VDVice name. .LONG VDV_BUF_SIZ .ADDRESS VDV_BUF VPID: ; Owner of VDVice (if any). .BLKL 1 VDV_ITEM_LIST: ; VDVice list for $GETDVI. .WORD VDV_BUF_SIZ ; Make sure we a have a physical device name. .WORD DVI$_DEVNAM .ADDRESS VDV_BUF .ADDRESS VDV_BUF_DESC .WORD 4 ; See if someone has this device allocated. .WORD DVI$_PID .ADDRESS VPID .LONG 0 .WORD 4 .WORD DVI$_DEVCLASS ; Check for a terminal. .ADDRESS VDV_CLASS .LONG 0 .LONG 0 ; End if item list. VDV_CLASS: .LONG 1 ;** DEFNAM: WRK: .BLKL 1 ;SCRATCH INTEGER WRK2: .BLKL 1 .align long wrkstr: .word 20 ;length .byte dsc$k_dtype_t ;text .byte 1 ;static .address wrkdat wrkdat: .blkb 20 .byte 0,0,0,0 ;safety ; DESCRIPTOR FOR VDn: "FILENAME" .ALIGN LONG VDFNM: .WORD 255. ;LENGTH VDFTP: .BYTE DSC$K_DTYPE_T ;TEXT TYPE .BYTE 1 ; STATIC STRING .ADDRESS VDFNMD VDFNMD: .BLKB 256. ; DATA AREA ; ; DESCRIPTOR FOR DVn:DSKFIL "FILENAME" .ALIGN LONG DDFNM: .WORD 255. ;LENGTH DDFTP: .BYTE DSC$K_DTYPE_T ;TEXT TYPE .BYTE 1 ; STATIC STRING DDFNA: .ADDRESS DDFNMD DDFNMD: .BLKB 256. ; DATA AREA DDCHN: .LONG 0 VDCHN: .LONG 0 ;CHANNEL HOLDERS ; second file desc. .ALIGN LONG EDFNM: .WORD 255. ;LENGTH EDFTP: .BYTE DSC$K_DTYPE_T ;TEXT TYPE .BYTE 1 ; STATIC STRING EDFNA: .ADDRESS EDFNMD EDFNMD: .BLKB 256. ; DATA AREA EDCHN: .LONG 0 ; ; ; KERNEL ARG LIST for BashUCB K_ARG: .LONG 3 ;2 ARGS: HOST-DVC NAME, VD DVC NAME .ADDRESS DEV_BUF_DESC .ADDRESS VDV_BUF_DESC .ADDRESS EDEV_BUF_DESC ;2ND FILE (IF PRESENT) ; ; We don't allocate the file here; user can readily do this ; himself. A copy/contig/alloc=nnnnn command followed by a ; set file/end will, for instance, do nicely. ; repdsc: .ascid /REPORT/ ;report associated file .align long repflg: .long 0 ;1 if reporting, 0 otherwise reptxt: .word 80 ;80 byte long .byte dsc$k_dtype_t ;static, fixed length string of text .byte 1 .address repwrk ;data pointer is repwrk's address repwrk: .blkb 80 ;copy of filespec s64dsc: .ascid /SEC64/ ;flag this if 64 sectors/trk geometry needed s32dsc: .ascid /SEC32/ ;md: type 32 sector forcer ASDSC: .ASCID /ASSIGN/ DASDSC: .ASCID /DEASSIGN/ P1DSC: .ASCID /UNIT/ P2DSC: .ASCID /FNAM/ P3DSC: .ASCID /FNAM2/ enadsc: .ascid /ENABLE/ ;flags this is the end of containers newdsc: .ASCID /NEW/ ;flags that history is invalid, set up a new one appdsc: .ascid /APPEND/ ;append more container files to stripeset chkdsc: .ascid /CHUNKSIZE/ ;size of a chunk of storage on stripeset ;(also called "granule" in some places.) LBNDSC: .ASCID /LBN/ LENDSC: .ASCID /LENGTH/ slbnds: .ascid /SLBN/ ;secondary LBN flag slends: .ascid /SLENGTH/ ;secondary size file grndsc: .ascid /GRANULE/ resdsc: .ascid /RESERVED/ ;number blocks to reserve, default 1, for stripe desc .EVEN cupf: .long 0 ;catchup flag cupsz: .long 0 ;device size for catchup cupcur: .long 0 ;current block for catch-up appflg: shd2: .long 0 ;flag we start with r/w both newflg: .long 1 enaflg: .long 0 ;/enable flag, set if we have all storage now SHDF: .LONG 1 ;second file there if nonzero SHMD: .LONG 0 ;SD: USAGE MODE 0=VD: COMPAT, 1=2 FILES THERE ASDAS: .LONG 0 ;DEFAULT DEASSIGN secflg: .long 0 ;flag that a second filename was entered if nonzero rsrvd: .long 1 ;number blocks reserved at start of each container chunk: .long 0 ;size of stripe chunk of blocks on a disk vSec64: .long 0 ;1 if using /sec64 geometry vsec32: .long 0 ;1 if using /sec32 geometry LBNn: .long 0 ;temp storage for /lbn=number LENn: .long 0 ;temp storage for /len=number slbnn: .long 0 ;/slbn temp slenn: .long 0 ;/slen temo ; ; ucb data area HSTUCB: .LONG 0 ;HOST UCB ADDRESS HSTLBN: .LONG 0 ;LBN OF 1ST BLK OF HOST FILE HSTFSZ: .LONG 0 ;LENGTH IN BLOCKS OF HOST FILE HSTUC2: .LONG 0 ;HOST UCB ADDRESS FILE 2 HSTLB2: .LONG 0 ;LBN FILE 2 HSTFS2: .LONG 0 ;LENGTH OF SECOND FILE (IF ANY) ; debug words vducb: .long 0 vdsts: .long 0 vdsts2: .long 0 vdsts3: .long 0 vdcyl: .long 0 vdprog: .long 0 ;counts where we've been ; lblblk: .long 0 ;# saveset pieces nparts: .long 0 ;number parts in stripeset rsvsiz: .long 1 ;reserved size partsz: .long 0 ;size of piece totsiz: .long 0 ;accum. size of total stripeset "disk" chksiz: .long 1 ;chunk size ;each segment of storage contains device name, unit, start LBN, size ; so that these can be compared with what user assigns to ensure he ; gets it right if reusing old stripeset. (We won't save allocation ; class or nodename here...too complex and won't save from many errors ; anyhow...we'll catch most of it here.) .blkb 492 ;rest of lbl blk lblisb: .blkl 2 ;iosb for label read/write ; ; ERROR: .LONG 2 MESS: .LONG SS$_ABORT .LONG 0 ; Device geometry ; Use this table for "large" devices so that container files of ; sizes matching known geometry devices are made to appear to ; have exactly the known geometry. This will avoid a LOT of special ; case testing and allow insertion of more device geometries as we ; like .macro Geotbl losz,hisz,blks,cyl,trk,sect .Long losz ;low limit file size this geom .Long hisz ;high limit file size this geom .long blks ;Number of blks on device .word cyl ;number cylinders .byte trk ;number tracks/cyl .byte sect ;number sectors/track .endm ; Geoms MUST be in increasing order of size. Geoms: ; losiz hisiz blks cyl trk sect id Geotbl 4800, 4810, 4800, 200, 2, 12 ;RK05 Geotbl 10240, 10250, 10240, 256, 2, 40 ;RL01 (sect=256 bytes) Geotbl 20480, 20500, 20480, 512, 2, 40 ;RL02 (Sect=256 bytes) Geotbl 27126, 27150, 27126, 411, 3, 22 ;RK06 GeoTbl 53790, 53830, 53790, 815, 3, 22 ;RK07 GeoTbl 131680, 131700, 131680, 823, 5, 32 ;RM03 GeoTbl 138672, 138690, 138672, 1024, 8, 17 ;RD53 GeoTbl 171798, 171850, 171798, 411, 19, 22 ;RP04 GeoTbl 242606, 242650, 242606, 559, 14, 31 ;RM80 (or RB80) GeoTbl 340670, 340720, 340670, 815, 19, 22 ;RP06 GeoTbl 500384, 500420, 500384, 823, 19, 32 ;RM05 GeoTbl 891072, 891110, 891072, 1248, 14, 51 ;RA81 GeoTbl 1008000,1008500,1008000,630, 32, 50 ;RP07 GeoTbl 1216665,1216700,1216665,1423, 15, 57 ;RA82 GeoTbl 1218000,1218020,1218000,50750, 4, 6 ;rrd42 GeoTbl 1954050,1954200,1954050,1835, 15, 71 ;RZ57 .Long 0,0,0,0 ;list terminator ; ; ; .PSECT ADVDD_CODE,RD,NOWRT,EXE,quad .ENTRY ADVDD,^M clrl repflg ;say not reporting initially movl #1,rsrvd ;say 1 reserved block clrl enaflg clrl hstfsz clrl hstfs2 movl #1,newflg ;flag /new movab repwrk,r0 ;clear work string initially movl #80,r1 1$: clrb (r0)+ sobgtr r1,1$ ;zero the array out pushab enadsc ;/enable flag being issued here? calls #1,g^cli$present ;see if we find that cmpl r0,#cli$_present bneq 12$ ;if neq no /enable incl enaflg ;enable online 12$: MOVL #1,ASDAS ;SET ASSIGN PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH PUSHAB VDFNM ;ADDRESS OF DESCRIPTOR TO RETURN PUSHAB P1DSC ; GET P1 (VDn: UNIT) CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF NAME TO VDFNM ON_ERR ADVDD_EXIT clrl vsec64 ;zero s64 flag clrl vsec32 ;ditto s32 flag pushab s64dsc calls #1,g^cli$present ;see if /sec64 specified cmpl r0,#cli$_present bneq 503$ ;if neq not there incl vsec64 503$: pushab s32dsc calls #1,g^cli$present ;see if /sec32 specified cmpl r0,#cli$_present bneq 1503$ ;if neq not there incl vsec32 1503$: pushab appdsc ;was /APPEND seen? clrl appflg ;(assume no) calls #1,g^cli$present cmpl r0,#cli$_present bneq 6031$ ;if neql no /aPPEND seen incl appflg ;if eql we saw /APPEND 6031$: pushab newdsc ;was /NEW seen? clrl newflg ;(assume no) calls #1,g^cli$present cmpl r0,#cli$_present bneq 603$ ;if neql no /new seen incl newflg ;if eql we saw /new 603$: pushab repdsc calls #1,g^cli$present ;/report used? cmpl r0,#cli$_present bneq 103$ ;if not there, skip... movl #1,repflg jmp das1 ;if there, no need for 2nd file either ; ; IF "DEASSIGN" WE DON'T NEED 2ND ARG... SEE... ; 103$: PUSHAB DASDSC ; 'DEASSIGN' CALLS #1,G^CLI$PRESENT ; IS /DEASSIGN USED? CMPL R0,#CLI$_PRESENT ; IF EQ YES BEQL DAS1 CLRL SHMD ; INITIALLY SET SHARE MODE 0 FOR ONE FILE MODE PUSHAB WRK ; GET 2ND FILE (REAL FILE) PUSHAB DDFNM ; & ITS DESCRIPTOR PUSHAB P2DSC ; & PARAMETER NAME 'P2' CALLS #3,G^CLI$GET_VALUE ; GET FNM ON_ERR ADVDD_EXIT ; tstl shdf ; see /shadow? ; beql das2 ;if eql no, skip getting 2nd file clrl shdf clrl secflg ;no 2nd filename yet pushab wrk2 pushab EDFNM ;get 2nd filename (if any) pushab p3dsc calls #3,g^cli$get_value ;get filename blbc r0,105$ ;if error leave secflg=0 incl shdf incl secflg ;got a 2nd filename 105$: BRB DAS2 DAS1: CLRL ASDAS ; FLAG /DEAS DAS2: TSTL ASDAS ; IF 0, DEASSIGNING SO NO CHNL FOR HOST ; FILE bneq 50$ 52$: brw 1290$ 50$: ; BEQL l290$ movl #16,chunk ;default chunk is 16 blocks pushab grndsc ;/granule:n same as chunk:n calls #1,g^cli$present cmpl r0,#cli$_present bneq 1117$ pushab wrk pushab wrkstr pushab grndsc brb 1116$ 1117$: pushab chkdsc ;/chunk:nnnn chunksize setup calls #1,g^cli$present ; was /chunk there? cmpl r0,#cli$_present ;see the /chunk? bneq 250$ ;if neq no, skip around ; get the value and store PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB chkdsc ; GET chunk 1116$: CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF LBN ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab chunk ;where to store chunk size pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ; chunk now contains chunksize. 250$: movl #1,rsrvd ;default 1 reserved block pushab resdsc ;/reserved=nnnn reserved block desc calls #1,g^cli$present ; was /reserved there? cmpl r0,#cli$_present bneq 289$ ;if neq no, skip around ; get the value and store PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB resdsc ; GET reserved size CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF LBN ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab rsrvd ;where to store reserved size pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ; rsrvd now contains number of reserved blocks (for stripeset label) 289$: tstl repflg beql 3350$ brw 1290$ 3350$: ;/report doesn't need file either $ASSIGN_S - ; Get a channel to the DEVNAM=DDFNM,- ; device for host file CHAN=DDCHN ON_ERR ADVDD_EXIT ; LET ERRORS BY FOR THIS SINCE WE GET OUR INFO VIA OPEN ANYWAY SO ; CHANNEL REALLY DOESN'T HAVE TO BE THERE. ; Get the physical device name, and see if this device has an owner. ; (We must do this so we can get the host UCB address) $GETDVI_S - CHAN=ddchn,- ; Command line has device name. ITMLST=DEV_ITEM_LIST BLBS R0,40$ BRW advdd_EXIT 40$: tstl shdf ; see second filename? beql 1290$ ; if not, no info needed $assign_s devnam=EDFNM,chan=EDCHN on_err advdd_Exit $getdvi_s chan=EDCHN,ITMLST=EEV_ITEM_LIST on_err advdd_exit 1290$: ; MUST HAVE ASSIGNMENT TO VD: UNIT IN ANY CASE. $ASSIGN_S - DEVNAM=VDFNM,- ; GET CHANNEL FOR VDn: CHAN=VDCHN ON_ERR ADVDD_EXIT ; SKIP OUT IF ERROR $GETDVI_S - CHAN=vdchn,- ; Command line has device name. ITMLST=VDV_ITEM_LIST BLBS R0,140$ BRW advdd_EXIT 140$: ; ; NOW LOCATE THE FILE AND VERIFY IT'S REALLY CONTIGUOUS, AND FIND ; OUT HOW BIG IT IS. STORE RESULTS IN HSTLBN AND HSTFSZ AND ; CALL KERNEL ROUTINE TO BASH THE VDn: UCB APPROPRIATELY. ; ; DON'T NEED TO DO THIS FOR DEASSIGN SO CHECK THAT FIRST... brb 230$ 231$: brw 296$ 230$: ; bneq 296$ ;/catchup mode doesn't need to open files TSTL ASDAS ; IF ZERO WE DEASSIGN BEQL 231$ tstl repflg bneq 231$ ;forget file open if /report only clrl lbnn clrl lenn ;zero lbn and length flags. brb 1401$ 1400$: brw 1501$ 1401$: PUSHAB LBNDSC ; 'lbn=' CALLS #1,G^CLI$PRESENT ; IS /DEASSIGN USED? CMPL R0,#CLI$_PRESENT ; IF EQ YES Bneq 1400$ ; if neq no pushab lendsc ; /len=nnnn calls #1,g^cli$present ;see it too? (must have both) cmpl r0,#cli$_present Bneq 1400$ ; have both /len and /lbn specified. Get values for them. If they ; look OK, bypass file open and replace logic. PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB lbndsc ; GET lbn CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF LBN ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab lbnn ;where to store pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ; lbnn now is start logical blk PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB lendsc ; GET length CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF Length ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab lenn ;where to store pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ;len must be positive! tstl lenn ;so IS it positive? blss 1501$ ;if lss then no, it's negative so try and probably ; fail to open file. movl lbnn,hstlbn ;looks ok so save host LBN movl lenn,hstfsz ;and start blk brw 1785$ ;then merge common path in again. 1501$: ; ; OPEN THE FILE, CHECK ITS INITIAL LBN ; IF ERROR OR NOT CONTIG, EXIT... ; DO VIA OPENING FILE AND READING ITS' STATBLOCK VIA ; QIO... ; SET UP FOR FILENAME WE REALLY FOUND IN FAB... MOVL DDFNA,DFAB_BLK+FAB$L_FNA ;SET UP FILENAME ADDR MOVB DDFNM,DFAB_BLK+FAB$B_FNS ;AND LENGTH $OPEN FAB=DFAB_BLK blbs r0,235$ 236$: brw 300$ 235$: ; BLBC R0,300$ ; FAILURE IF FILE WON'T OPEN ; FNXAB HAS INFO ON LBN, SIZE MOVL FNXAB+XAB$L_SBN,HSTLBN ; GET HOST'S LBN bneq 237$ 238$: brw 301$ 237$: ; BEQL 301$ ;;; RESTRICTION FOR NOW ... ;;; IF ZERO, FILE NONCONTIG ;;; SO FORGET IT... MOVL FNXAB+XAB$L_HBK,HSTFSZ ; GET FILE SIZE. (CHECK THAT BELOW) 1785$: ; Note that /lbn and /len switches pply to 1st file only, so far. tstl shdf ;doing /shadow? bneq 3603$ brw 1603$ ; if eql no 3603$: ;;;;; brb 2401$ 2400$: brw 2501$ 2401$: PUSHAB SLBNDS ; 'slbn=' CALLS #1,G^CLI$PRESENT ; IS /DEASSIGN USED? CMPL R0,#CLI$_PRESENT ; IF EQ YES Bneq 2400$ ; if neq no pushab slends ; /slen=nnnn calls #1,g^cli$present ;see it too? (must have both) cmpl r0,#cli$_present Bneq 2400$ ; have both /slen and /slbn specified. Get values for them. If they ; look OK, bypass file open and replace logic. PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB slbnds ; GET slbn CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF LBN ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab slbnn ;where to store pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ; lbnn now is start logical blk PUSHAB WRK ;PUSH LONGWORD ADDR FOR RETLENGTH pushab wrkstr ;scratch string PUSHAB slends ; GET length CALLS #3,G^CLI$GET_VALUE ;GET VALUE OF Length ON_ERR ADVDD_EXIT ; string in wrkdat pushl #17 ;mask...ignore blanks pushl #4 ;4 bytes pushab slenn ;where to store pushab wrkstr ;string descriptor calls #4,g^ots$cvt_tu_l ;convert to binary on_err advdd_exit ;len must be positive! tstl slenn ;so IS it positive? blss 2501$ ;if lss then no, it's negative so try and probably ; fail to open file. movl slbnn,hstlb2 ;looks ok so save host LBN movl slenn,hstfs2 ;and start blk brw 2785$ ;then merge common path in again. 2501$: ;;;;; MOVL EDFNA,EFAB_BLK+FAB$L_FNA ;SET UP FILENAME ADDR MOVB EDFNM,EFAB_BLK+FAB$B_FNS ;AND LENGTH $OPEN FAB=EFAB_BLK blbs r0,3501$ brw 236$ ; failure if file won't open 3501$: ; FNXAB HAS INFO ON LBN, SIZE MOVL EFNXAB+XAB$L_SBN,HSTLB2 ; GET HOST'S LBN bneq 3502$ brw 238$ 3502$: ; ;;; RESTRICTION FOR NOW ... ;;; IF ZERO, FILE NONCONTIG ;;; SO FORGET IT... MOVL EFNXAB+XAB$L_HBK,HSTFS2 ; GET FILE SIZE. (CHECK THAT BELOW) ;NOW set hstfsz to min of the two sizes ;(we check others later but the map algorithm [from sigtapes] assumes ; all parts of stripeset are the same size.) 2785$: cmpl hstfsz,hstfs2 ;file 1 bigger bleq 1603$ ;if file 1 smaller or equal use that size movl hstfs2,hstfsz ;else use file 2 size here 1603$: TSTL HSTFSZ ; HOST SIZE POSITIVE bgtr 7603$ 3604$: brw 301$ 7603$: ; IF <0 OR =0 THEN ILLEGAL; BUG OUT ; ELSE ISSUE THE REQUESTS TO GET THE ; DEVICES... ; Now grab a copy of the label block provided that one exists. ; Label fmt described earlier. ; After first part of label we have: ; dvc name, 4 longs counted ; unit, 1 long ; start LBN on host ; size tstl rsrvd ; any blocks reserved at start? bneq 3606$ ; if none, we forget it. 3607$: brw 296$ 3606$: $qiow_s efn=#1,chan=ddchn,func=#io$_readlblk,- iosb=lblisb,p1=lblblk,p2=#512,p3=hstlbn ;read label block in blbs r0,3608$ 3609$: brw 302$ ; on error skip out 3608$: movl lblisb,r0 blbc r0,3609$ ; report error if one occurs ; if /new was seen, just init the lbl block. tstl newflg ; /new seen? bneq 299$ ; if so, set up initial conds ; Now see if it looks like the right sections are being combined ; together, exiting if not. cmpl hstfsz,partsz ; file size ok? blss 3604$ ; too small, branch cmpl rsrvd,rsvsiz ; Reserve what was reserved initially? beql 3302$ 3301$: brw 301$ ; if no, can't do it 3302$: cmpl chunk,chksiz ; same chunk size as saved? beql 3674$ brw 3604$ ;if not abort 3674$: cmpl nparts,#16 ; if 16 parts already,... bgeq 3301$ ; we can't add another tstl secflg ; trying to add 2 more here? beql 296$ ; if not, all OK so far cmpl nparts,#15 ; otherwise unless LESS than 15 we lose bgeq 3301$ ; there's space enough in the UCB for more files. ; Force it on after 6th file though. brb 296$ 299$: ; new stripeset fill-in here pushr #^m ;movc5 trashes r0-r5 movab lblblk,r6 ; area to clear movc5 #0,(r6),#0,#512,(r6) ;zero the entire buffer first popr #^m movl rsrvd,rsvsiz ; master reserved space amount movl hstfsz,partsz ; master storage area size movl chunk,chksiz ; label blk master size 296$: ; now set up or check the rest in knl mode. Need knl mode to ; get device names from DDB and so on. $CMKRNL_S - ROUTIN=BASHUCB,ARGLST=K_ARG CMPL R0,#SS$_NORMAL ;Any errors? bneq 3300$ brw 300$ 3300$: MOVL R0,MESS ;Move error to message ; ERROR RETURN ... CLOSE FAB & LEAVE $PUTMSG_S MSGVEC=ERROR ;Pump out error message $CLOSE FAB=DFAB_BLK $DASSGN_S CHAN=VDCHN $DASSGN_S CHAN=DDCHN ;CLEAN UP I/O CHANNELS $dassgn_s chan=edchn movl mess,r0 ret ; BEQL 300$ ;No, skip error routine 302$: MOVL R0,MESS ;Move error to message 301$: ; ERROR RETURN ... CLOSE FAB & LEAVE $PUTMSG_S MSGVEC=ERROR ;Pump out error message $CLOSE FAB=DFAB_BLK brb 303$ 300$: ; BE SURE WE DON'T LEAVE THE CHANNELS ASSIGNED TO THE DEVICES ; EITHER... ; write the label block out if bashucb said all well tstl rsrvd ;provided there IS a label block, bleq 303$ $qiow_s efn=#1,chan=ddchn,func=#io$_writelblk,- iosb=lblisb,p1=lblblk,p2=#512,p3=hstlbn ;write the new ; label block if all looks ok. 303$: $DASSGN_S CHAN=VDCHN tstl repflg bneq 550$ TSTL ASDAS ; IF ZERO WE DEASSIGN beql 540$ ; if zero, no file chnl to deass $DASSGN_S CHAN=DDCHN ;CLEAN UP I/O CHANNELS tstl shdf beql 540$ $dassgn_s chan=edchn 540$: ; skip deassign file chnl on advd/deassign ; to avoid final error msg RET 550$: ; print out the filespec tstb repwrk ;got any file assigned? beql 552$ ;if not, don't emit name pushab reptxt ;text descr. of filename calls #1,g^lib$put_output ;emit same 552$: ret advdd_exit: RET ; BASHUCB - AREA TO MESS UP UCB WITH OUR FILE DATA ; BEWARE BEWARE BEWARE ; runs in KERNEL mode ... HAS to be right. .ENTRY BASHUCB,^M ; TAKEN LOOSELY FROM ZERO.MAR .if ndf,vms$v5 MOVL G^SCH$GL_CURPCB,R4 ;;; NEED OUR PCB .iff MOVL G^CTL$GL_PCB,R4 ;;; NEED OUR PCB (VMS V5) .endc JSB G^SCH$IOLOCKW ;;; LOCK I/O DATABASE CLRL HSTUCB ;;; ZERO "HOST" UCB tstl repflg bneq 90$ ;;;no host lookup on /report TSTL ASDAS ;;; IF DEASSIGN, ZERO BEQL 90$ ;;; SO IF EQUAL SKIP LOCATE HOST UCB tstl secflg ;see a second file desc? beql 58$ ;if not skip movl 12(AP),r1 ;get file 2 desc jsb g^ioc$searchdev blbc r0,59$ ;if we fail, scram movl r1,hstuc2 ;if we succeed save host UCB address for file 2 58$: MOVL 4(AP),R1 ;;; ADDRESS DVC NAME DESCRIPTORS JSB G^IOC$SEARCHDEV ;;; GET UCB ADDRESS INTO R1 BLBS R0,60$ 59$: BRW BSH_XIT 60$: ; TSTL UCB$L_PID(R1) ;;; ENSURE DVC NOT ALLOCATED ; BEQL 80$ ; MOVL #SS$_DEVALLOC,R0 ; BRW BSH_XIT ; ALLOCATED OK SINCE IT COULD JUST BE PRIVATE MOUNT... ; 80$: MOVL R1,HSTUCB ;;; SAVE HOST UCB ADDRESS BEQL 167$ ;;; ... BUT ZERO UCB ADDRESS LOOKS BAAAAD 90$: MOVL 8(AP),R1 ;;; ADDRESS VDn NAME DESCRIPTORS JSB G^IOC$SEARCHDEV ;;; GET UCB ADDRESS INTO R1 BLBS R0,160$ BRW BSH_XIT 160$: movl r1,vducb ;;; store vd ucb ;ensure this really is SD driver before we clobber anything cmpl ucb$l_SD_flag(r1),#^A/GCYS/ ;check our magic number bneq 169$ ;if not there, scram movl ucb$l_maxblock(r1),cupsz ;;;save device size tstl repflg bneq 168$ ;;;on /report don't mess ucb up TSTL UCB$L_PID(R1) ;;; ENSURE DVC NOT ALLOCATED BEQL 180$ 165$: MOVL #SS$_DEVALLOC,R0 167$: BRW BSH_XIT 168$: brw 455$ 169$: movl #ss$_badparam,r0 ;if not a SD device generate bad param err brb 167$ 180$: ; BUGGER THE UCB ; ASSUMES FILE LBN AND SIZE ALREADY RECORDED ; ALSO ASSUMES THAT ZERO LBN OR SIZE MEANS THIS ENTRY NEVER CALLED. ; (REALLY ONLY WORRY ABOUT ZERO SIZE; IF WE OVERMAP A REAL DEVICE ; THEN ZERO INITIAL LBN COULD BE OK.) ; ; CHECK REF COUNT FIRST... ONLY CAN GET AWAY WITH THIS ON DEVICE ; NOBODY'S USING... ; .. fake this since device may have count messed by advd somehow ; but will be allocated if mounted. ; ... for now ... 554$: 1893$: movzwl ucb$w_refc(r1),vdsts2 ;;; save status for debug CMPW UCB$W_REFC(R1),#1 ;;; CHECK COUNT VS 1 FOR THIS BGTRU 165$ ; TSTW UCB$W_REFC(R1) ;;; IF MOUNTED DON'T TOUCH ; BNEQ 165$ ;;; IF NEQ IT'S ACCESSED... MOVL HSTUCB,UCB$HUCB(R1) ;;; SAVE HOST UCB OR 0 BNEQ 184$ ;;; IF NE, OK NOW ;;; ZERO -- DEASSIGNING. FLAG VOLUME INVALID BICW #UCB$M_ONLINE,UCB$W_STS(R1) ;;; FLAG OFFLINE BICW #UCB$M_VALID,UCB$W_STS(R1) ;;; AND INVALID clrl ucb$vdcontfil(r1) ;;;clr container file name ; zero size and so on too in case volume gets reassigned later clrl ucb$totfsz(r1) clrl ucb$ncont(r1) ;no containers till now clrl ucb$l_maxblock(r1) ;set size=0 again too BRW 200$ 184$: movl totsiz,ucb$l_maxblock(r1) ;get size now movl nparts,ucb$ncont(r1) ; get number of container slots now tstl appflg ; appending to old assign? beql 884$ ;if eql no tstl newflg ;new asn? beql 584$ ;if eql no ; if no append or new stripeset, zero count. ; (no append -> first call for setup this disk.) 884$: clrl ucb$ncont(r1) ;else clear count of container files clrl nparts ;clr count in label blk of parts so far clrl ucb$l_maxblock(r1) ;& other junk 584$: pushr #^m movl r1,r2 ; fill data into correct ucb slot movl ucb$ncont(r1),r0 ;# containers mull2 #ucbcntsz,r0 ;size of one in ucb (3 longs) addl2 r1,r0 ;point at this container area MOVL HSTLBN,UCB$HLBN(R0) ;;; SAVE HOST'S LBN MOVL HSTFSZ,UCB$HFSZ(R0) ;;; AND FILE SIZE cmpl hstfsz,partsz ; filesize bigger than common? bneq 1584$ ; if not equal must be bigger movl partsz,ucb$hfsz(r0) ; store common size 1584$: ADDL2 ucb$hfsz(r0),UCB$L_MAXBLOCK(R1) ;;; Update disk size in geom area subl2 rsrvd,ucb$l_maxblock(r1) ;subtract off reserved bits movl ucb$l_maxblock(r1),totsiz ;store in label pushr #^m ; Fill in device name/unit/lbn/size stuff here too in label blk movl nparts,r4 ;cell number mull2 #28,r4 ;size of slot = 7 longs addl2 #24,r4 ;6 longs in first part movab lblblk,r5 ;now get base addr of lblblk addl2 r5,r4 ;point at hdr area now movl ucb$hucb(r0),r8 ;pointer host ucb bgeqw 508$ movl ucb$l_ddb(r8),r7 ;now get DDB movab ddb$t_name(r7),r6 ;get dvc name at r6 movl #ss$_normal,r0 ;assume success cmpl lblblk,nparts ;See if the assign is new bgtr 501$ ;if gtr, need to chk names ; new assign...put names in for 1st time ; (Yes,this is not completely unique...alloclass is ignored, for example... ; but it will serve to eliminate most errors.) movl (r6),(r4) movl 4(r6),4(r4) ;fill in name. Just use 4 movl's movl 8(r6),8(r4) ;& forget length test. movl 12(r6),12(r4) 501$: movzbl (r6),r7 ;length to compare ; ??count must be same too pushl r4 503$: cmpb (r4)+,(r6)+ ;stupidly compare dvc name (cmpc?) bneq 504$ ;no? flag error sobgtr r7,503$ ;check all popl r4 addl2 #16,r4 ;pass name movl ucb$ncont(r1),r7 ;# containers mull2 #ucbcntsz,r7 ;size of one addl2 r1,r7 ;point at this cont. info movl ucb$hucb(r7),r7 cmpl lblblk,nparts ;Need to test existing flds? bgtr 507$ ;if gtr, need chk movzwl ucb$w_unit(r7),(r4) ;else just store new unit no. movl hstlbn,4(r4) ; start lbn movl hstfsz,8(r4) ; size brb 507$ 504$: movl #ss$_drverr,r0 ; Make compare fail look real bad brb 508$ ; scram on error 507$: cmpw ucb$w_unit(r7),(r4) ; unbit # match? bneq 504$ ; if not, leave cmpl hstlbn,4(r4) ; same start lbn? bneq 504$ ; if not fail ; ??might need to check vs common size if bigger cmpl hstfsz,8(r4) ; same size? bneq 504$ ; if not fail too 508$: popr #^m ; If we had error from anyplace, r0 will show it blbc r0,509$ incl nparts ;if it looks ok, bump container count 509$: clrl ucb$ppid(r1) ;;;zero original PID blbs r0,506$ popr #^m movl #ss$_drverr,r0 ; send this err to caller brw bsh_xit ; as bad compare flag. 506$: popr #^m movl r4,-(sp) movl hstucb,r4 ;;;get host UCB beql 189$ ;;;forget it if none ;;;must make maxbcnt and fipl match!!! movb ucb$b_fipl(r4),ucb$b_fipl(r1) ;;;ensure fork levels match cmpl ucb$l_maxbcnt(r4),ucb$l_maxbcnt(r1) bgtru 189$ ;if host maxbcnt bigger than ours ;leave ours alone. movl ucb$l_maxbcnt(r4),ucb$l_maxbcnt(r1) ;;;store max bytes as a word 189$: movl (sp)+,r4 ;;; AND QIO CHECKS, AND OUR SAFETY ;;; ONES) clrl ucb$shmd(r1) ;;;shadow mode 0 - no shadowing initial tstl shdf ;;;second file spec'd? bneq 2191$ 2192$: brw 191$ ;;;if eql no 2191$: movl ucb$ncont(r1),r0 ;# containers mull2 #ucbcntsz,r0 ;size of one addl2 r1,r0 ;pointer this container info movl hstuc2,ucb$hucb2(r0) ;;;store host ucb file 2 beql 2192$ ;;;zero is not valid... movl hstfs2,ucb$hfsz2(r0) ;;;store file size cmpl hstfs2,partsz ;bigger than common? bneq 2584$ ; if not equal, must be bigger movl partsz,ucb$hfsz2(r0) ; store common if so 2584$: movl hstlb2,ucb$hlbn2(r0) ;;;and start LBN addl2 ucb$hfsz2(r0),ucb$l_maxblock(r1) ;add to running tot size subl2 rsrvd,ucb$l_maxblock(r1) ;subtract reserved blks movl #2,ucb$shmd(r1) ;;;set stripe mode ok pushr #^m ; fill in device name/unit/lbn/size movl nparts,r4 ; slot number we're working on mull2 #28,r4 ; 7 longs/slot addl2 #24,r4 ; 6 longs at start movab lblblk,r5 ; point at 2nd slot addl2 r5,r4 movl ucb$hucb2(r0),r8 movl ucb$l_ddb(r8),r7 ;get ddb movab ddb$t_name(r7),r6 ;device name string movl #ss$_normal,r0 ; assume success cmpl lblblk,nparts ; existing assignments? bgtr 1501$ ;if >, old, check device info ; New assignment needs to have names put in movl (r6),(r4) ; copy device name etc. movl 4(r6),4(r4) movl 8(r6),8(r4) movl 12(r6),12(r4) 1501$: movzbl (r6),r7 ; size of name pushl r4 1503$: cmpb (r4)+,(r6)+ ; compare this dvc name bneq 1504$ ; Error if diff sobgtr r7,1503$ popl r4 addl2 #16,r4 ; pass name movl ucb$ncont(r1),r7 ; # containers mull2 #ucbcntsz,r7 ; size of one addl2 r1,r7 movl ucb$hucb2(r7),r7 cmpl lblblk,nparts ;check other fields against saved ones? bgtr 1507$ ;if gtr, check... movzwl ucb$w_unit(r7),(r4) ;if new store unit # movl hstlb2,4(r4) ;... lbn movl hstfs2,8(r4) ;... & size brb 1507$ 1504$: movl #ss$_drverr,r0 ; This error to user brb 1508$ ; We leave if anything fails 1507$: cmpl hstfs2,8(r4) ; same size? bneq 1504$ ; if not we lose cmpw ucb$w_unit(r7),(r4) ; same unit no? bneq 1504$ cmpl hstlb2,4(r4) ; same lbn? bneq 1504$ 1508$: popr #^m blbc r0,1509$ incl nparts ; Count another area if all's ok 1509$: clrl ucb$ppid(r1) ;;;zero original PID 191$: movl nparts,ucb$ncont(r1) ; save number of container slots full cmpl nparts,lblblk ; Filled in all slots? bleq 1191$ movl nparts,lblblk ; save # areas available now 1191$: movl ucb$l_maxblock(r1),totsiz ;get size to here ; mainline writes label block back after we return ; now figure out device geometry MOVL ucb$l_maxblock(r1),R0 ;;; GET HOST SIZE movl r0,ucb$totfsz(r1) ; save as dsk size ASHL #-6,R0,R0 ;;; GET # CYLINDERS IN SIZE NOW ;Set default geometry as 1 track/cylinder, 64 sectors/track, and ; as many cylinders as needed for device size. We use this if the ; /SEC64 switch is given. Otherwise we check to see if the container ; file is size same as some known disk and adopt its' geometry, or ; if that fails use either a 1 sector/trk 1 trk/cyl n cylinder ; geometry for small disks (under 65000 blocks), or a 32 sect/trk ; 32 trk/cyl n cylinder geometry for large disks. ; ; *** Where one gets over 2 billion blocks and sets the sign bit ; *** in the blocks count, this code will break due to not ; *** ensuring sign extension is avoided. Since this corresponds ; *** to a single disk of 1 terabyte, it seems unlikely to cause ; *** difficulties for a while. The 64 sector geometry breaks down ; *** at 64*65536 blocks (2 GB) and the 32*32*n geometry breaks ; *** down at 1024 * 65536 blocks. These seem high enough not to ; *** worry about for now. If they become a problem, play with ; *** geometry!!! ; MOVW R0,UCB$W_CYLINDERS(R1) ;;; SAVE IN UCB FOR REST OF VMS movl r0,vdcyl ;;; store cylinders for debug movb #64,ucb$b_sectors(r1) ;;;init sectors to 64 always movb #1,ucb$b_tracks(r1) ;number of tracks/cyl=1 tstl vsec64 ;;;did user say he needs 64 sector geometry? beql 6843$ ;;;if eql no, do tests cmpl ucb$l_maxblock(r1),#<64*65536> ;ensure geom is ok bgtru 687$ ; if disk this big, use 32x32xn brw 6841$ ;;;if neql leave geometry alone... 6843$: tstl vsec32 ;;;did he ask for 32 sect/32 trk geom? bneq 687$ ;;; if sect32 asked for, do default md: ;;; geometry, 1 by 1 by n for small disks, 32 by 32 ;;; by n for big ones. ; bneq 685$ ;;;if so (neq) skip geom table. movl r2,-(sp) ;;;Need a register to point to geoms movab geoms,r2 ;;;so we can test sizes ; Check for file sizes of known disks and set geometry of those ; disks IF we match. 686$: tstl (r2) ;;;end of table? beql 687$ ;;;if eql yes, skip out cmpl ucb$l_maxblock(r1),(r2) ;;;above min size this disk type? blss 688$ ;;;if too small, we're done so exit the loop cmpl ucb$l_maxblock(r1),4(r2) ;;;see if too big bgtr 688$ ;;;if too big, look at next ; got a match. Now fill in geometry ; (r2) = lo size (must be at LEAST as large as device) ; 4(r4) = hi size lim ; 8(r2) = # blks on device ; 12(r2) = cyl ; 14(r2) = trk ; 15(r2) = cyl movl 8(r2),ucb$l_maxblock(r1) ;Set up maximum block movw 12(r2),ucb$w_cylinders(r1) ;number of cylinders movb 14(r2),ucb$b_tracks(r1) ;number of tracks/cyl movb 15(r2),ucb$b_sectors(r1) ;number sectors/track movl (sp)+,r2 ;restore our register brb 684$ ;exit, we got our device ; Notice we must pass the "small device" test since some devices have ; less than 65000 blocks. We won't emulate device TYPE exactly, but will ; emulate device GEOMETRY with this logic. 688$: addl2 #16,r2 ;pass to next entry of geoms table brb 686$ ;go check for next device or end 687$: movl (sp)+,r2 ;;;restore reg ; test for small files cmpl ucb$l_maxblock(r1),#65530 ;"small" disks? bgtr 685$ movw ucb$l_maxblock(r1),ucb$w_cylinders(r1) ;yep...save size in cyl movb #1,ucb$b_sectors(r1) ;and set 1 sector/trk movb #1,ucb$b_tracks(r1) ;and 1 track/cyl (should be ok already) brw 684$ ;done with geometry 685$: ; Add other checks here ; Make geometry like mdan: disks, that is, 32 sectors and 32 tracks/cyl. ; unless /sec64 switch was set. This facilitates random use as a switch ; over from md: type disks. Note 32 * 32 = 1024 MOVL ucb$l_maxblock(r1),R0 ;;; GET HOST SIZE ASHL #-10,R0,R0 ;;; GET # CYLINDERS IN SIZE NOW as #/1024 MOVW R0,UCB$W_CYLINDERS(R1) ;;; SAVE IN UCB FOR REST OF VMS bicl2 #1023,ucb$l_maxblock(r1) ;ensure even number of cylinders movb #32,ucb$b_sectors(r1) ;set 32 sectors/track movb #32,ucb$b_tracks(r1) ;and 32 tracks/cylinder brb 684$ ;This is the "large disk" default ; ;unless /sec64 sets 64 sect geom. 6841$: ; If here, we are using the 64 sector/track geometry bicl2 #63,ucb$l_maxblock(r1) ;make disk size a multiple of sect/trk 684$: pushl r0 pushl r1 pushl r2 ; Fill in filename as 1st 79 chars of what user sent us movab ddfnmd,r0 ;data address movl #79,r2 ;copy 79 bytes addl #ucb$vdcontfil,r1 ;point at ucb offset 457$: movb (r0)+,(r1)+ sobgtr r2,457$ ;copy the data clrb (r0)+ ;null terminate popl r2 popl r1 popl r0 movl rsrvd,ucb$grnbas(r1) ;store reserved loc movl chunk,ucb$grnsiz(r1) ;store chunk cmpl nparts,#16 ; This max # save areas? beql 558$ ; if so enable now tstl enaflg ; put it online yet? beql 557$ ; skip if not 558$: cmpl nparts,lblblk ;see if # parts matches beql 559$ ;if so OK movl #ss$_parity,r0 ;else flag an error brb bsh_xit 559$: BISW #UCB$M_ONLINE,UCB$W_STS(R1) ;;; FLAG ONLINE NOW BISW #UCB$M_VALID,UCB$W_STS(R1) ;;; AND VOL VALID 557$: movzwl ucb$w_sts(r1),vdsts ;;; save VD status ;;; THAT'S IT... SHOULD BE OK NOW. brb 200$ 455$: ; copy vd: stored name into prog area pushl r1 pushl r2 movab repwrk,r0 ;;;get report area movl #80,r2 ;;;80 bytes max addl2 #ucb$vdcontfil,r1 ;;;point at in area 456$: movb (r1)+,(r0)+ beql 458$ ;;;on null terminator stop copy ;;;(keeps old name junk from reappearing) sobgtr r2,456$ ;;;copy the data 458$: popl r2 popl r1 200$: MOVL #SS$_NORMAL,R0 brb bsh_xit 1892$: tstl ucb$hucb2(r1) ;;;ensure 2nd ucb exists beql 1894$ ;;;if eql clear cupf brb 200$ ;;;set valid code and return 1894$: movl #46,r0 ;;;set error code BSH_XIT: PUSHL R0 JSB G^SCH$IOUNLOCK ;;; UNLOCK I/O DATABASE (DROP IPL) POPL R0 ;;; REMEMBER R0 RET ;;; BACK TO USER MODE NOW .END ADVDD