.TITLE UND - Undelete a File .IDENT /V1.1N/ .NLIST BEX,TOC ; UND - Undelete a recently-deleted file ; ; Command line format: "UND DO:=DI:[grp,mem]/SE" ; ; Where DO: is the output device, DI: is the input device ; and the output and input devices are not the same. ; ; If DO: is unspecified, SY: is used. The default is /-SE. ; ; The undeleted file is placed into the current UIC on ; the output device. ; ; The program will accept a command line with input and output disks (which ; must be different) and an optional UIC. It will then scan the input disk's ; index file for all deleted files (owned by that UIC). An error message will ; be printed if a search of the bitmap shows that a data block has been reused. ; All blocks of the old file will be read and written to the new file in ; the current UIC on the output device. ; ; This program will only succeed in recovering a file if the file header ; has not been reused. Optimum results occur when a single user ; accidentally deletes a file and immediately stops all writing to the ; volume, to avoid losing either the file header or any of the other ; blocks belonging to the deleted file. OPLUN = 1 ;Output device IXLUN = 2 ;Index file device BMLUN = 3 ;Bit map device IPLUN = 4 ;Input device TILUN = 5 ;TI: for command line and error messages .MCALL EXIT$S,QIOW$,ALUN$S,DIR$,GLUN$S,QIOW$S .MCALL GCML$,GCMLB$,CSI$,CSI$1,CSI$2,CSI$SW,CSI$ND .MCALL HMBOF$,FHDOF$ .MCALL NMBLK$,FDOP$A,FDRC$A,FDBK$A,OPEN$R,READ$ .MCALL OPEN$W,FINIT$,FDBDF$,FSRSZ$,CLOSE$,WRITE$,WAIT$ HMBOF$ DEF$L ;Locally define home block offsets FHDOF$ DEF$L ;Locally define file header offsets CSI$ ;Define CSI control block offsets CSIBLK: .BLKB C.SIZE ;Allocate the CSI control block SWTBL: CSI$SW SE,1,SWORD,SET,NEG CSI$ND SWORD: .WORD 0 ;1=/SE GCLBLK: GCMLB$ 4,UND,,TILUN ;Allocate and initialize GCML control block FSRSZ$ 1 ;1 file open for GCML PREARG: .WORD MSG ARGBLK: .BLKW 6 ;Argument block for EDMSG BMAPB: .WORD -1 ;Current bit map block in memory QFLAG: .WORD 0 ;1=Quit this session UICFLG: .WORD 0 ;1=UIC specified OWNER: .WORD 0 ;UIC of owner STBK: .BLKW 5 ;FCS statistics block IOSB: .BLKW 2 ;I/O status block HDR: .BLKB 512. ;Index header block buffer DATA: .BLKB 512. ;Deleted file block buffer BMAP: .BLKB 512. ;Bit map block buffer LINE: .BLKB 132. ;Message buffer TEMP: .BLKW 2 ;Buffer for device name RDQIO: QIOW$ IO.RLB,IPLUN,4,,IOSB,, TQIO: QIOW$ IO.WVB,TILUN,5,,,, QIOATR: QIOW$ IO.WAT,OPLUN,4,,IOSB,, RATUFA: .BYTE 13.,35. ;Write date/time attributes .WORD HDR+S.HDHD+I.RVNO ;Point to original header .WORD 0 ;Mark end of attribute list ; ; The output file FDB ; OUTFDB: FDBDF$ FDRC$A FD.RWM ;Block I/O operations FDBK$A DATA,512.,,,IOSB FDOP$A OPLUN,,DFNB,FO.WRT DFNB: NMBLK$ ;Default file name ; ; The input index file FDB ; INXFDB: FDBDF$ FDRC$A FD.RWM ;Block I/O operations FDBK$A HDR,512.,,,IOSB FDOP$A IXLUN,INDX,,FO.RD INDX: .WORD 0,0 ;Dataset descriptor block .WORD INXULN,INXUIC .WORD INXFLN,INXFIL ; ; The bitmap file FDB ; BMPFDB: FDBDF$ FDRC$A FD.RWM ;Block I/O operations FDBK$A BMAP,512.,,,IOSB FDOP$A BMLUN,BITM,,FO.RD BITM: .WORD 0,0 ;Dataset descriptor block .WORD INXULN,INXUIC .WORD BITFLN,BITFIL INXUIC: .ASCII /[0,0]/ INXULN=.-INXUIC INXFIL: .ASCII /INDEXF.SYS/ INXFLN=.-INXFIL BITFIL: .ASCII /BITMAP.SYS/ BITFLN=.-BITFIL BITCHK: .BYTE 1 ;Bit check table for bit map .BYTE 2 .BYTE 4 .BYTE 10 .BYTE 20 .BYTE 40 .BYTE 100 .BYTE 200 MSG: .ASCIZ /UND -- / SYNMSG: .ASCIZ \%N%ISyntax Error, "UND ddn:=ddn:[grp,mem]/SE"\ DEVMSG: .ASCIZ /%N%IDevices must be distinct/ FILMSG: .ASCIZ \%N%IRecover %X [Y/N/G/Q] ?\ FL1MSG: .ASCIZ /%N%IRecovering %X/ OPNMSG: .ASCIZ /%N%I Output file opened as: %X/ WARN: .ASCIZ /%N%I*** Warning %X (VBN %T.) probably corrupted ***/ INPMSG: .ASCIZ /%N%I*** Input File error, %I error code = (%D.) (VBN %T.) ***/ OUTMSG: .ASCIZ /%N%I*** Output File error, %I error code = (%D.) (VBN %T.) ***/ INXMSG: .ASCIZ /%N%I*** Input Index File %I error = (%D.) ***/ BITMSG: .ASCIZ /%N%I*** Input Bitmap File %I error = (%D.) ***/ OASNER: .ASCIZ /%N%I*** ALUN$ failure on output, DIR error code = (%D.) ***/ IASNER: .ASCIZ /%N%I*** ALUN$ failure on input, DIR error code = (%D.) ***/ FCSERR: .ASCIZ /FCS/ DIRERR: .ASCIZ /DIR/ .EVEN .PAGE START: FINIT$ ;Initialize FSR QIOW$S #IO.ATT,#TILUN,#5 ;Attach TI: .SBTTL Command line proccessing ; Get the command line, parse it, and assign luns UNDEL: CLR SWORD ;Initialize to /-SE GCML$ #GCLBLK ;Try to get the command line BCC 10$ ;If CC, get was successful EXIT$S ;If CS, probably EOF so get out 10$: MOV R0,R1 ;R1 = #GCLBLK MOV #CSIBLK,R0 ;Get CSI block address CSI$1 ,G.CMLD+2(R1),G.CMLD(R1) BCS SYNERR ;If CS, syntax error MOVB #CS.OUT,C.TYPR(R0) ;Setup for left side BITB #CS.EQU,C.STAT(R0) ;Were both devices specified? BEQ 12$ ;If EQ, no CSI$2 ,,#SWTBL ;Parse the output spec BCS SYNERR ;If CS, parse error BITB #,C.STAT(R0) ;Any improper specs? BNE SYNERR ;If NE, incorrect output specs BITB #CS.DVF,C.STAT(R0) ;Spec must have device BEQ 12$ ;If EQ, no output device CALL DEVICE ;Get device name from CSI block MOV #CSIBLK,R0 ;Restore CSI block address MOVB #CS.INP,C.TYPR(R0) ;Setup for right side BR 15$ 12$: MOV #"SY,R3 ;Default output device CLR R4 ; and unit 15$: ALUN$S #OPLUN,R3,R4 ;Assign LUN to output device BCS ASNOER ;Branch on error CSI$2 ,,#SWTBL ;Parse the input spec BCS SYNERR ;If CS, parse error BITB #,C.STAT(R0) ;Did input have proper specs? BNE SYNERR ;If NE, incorrect input specs BITB #CS.DVF,C.STAT(R0) ;Spec must have device BEQ SYNERR ;If EQ, no input device CLR UICFLG BITB #CS.DIF,C.STAT(R0) ;Spec may have a UIC BEQ 20$ ;If eq, no UIC specified INC UICFLG MOV #CSIBLK+C.DIRD,R2 ;Input UIC string address MOV #OWNER,R3 ;Directory buffer address CALL .ASCPP ;Convert UIC string 20$: CALL DEVICE ;Input device from CSI block ALUN$S #IXLUN,R3,R4 ;Assign LUN for index file BCS ASNIER ;Branch on error ALUN$S #BMLUN,R3,R4 ;Assign LUN for bitmap BCS ASNIER ;Branch on error ALUN$S #IPLUN,R3,R4 ;Assign LUN for data BCS ASNIER ;Branch on error CALL DEVCHK ;Check if devices are same BCS DEVERR ;If CS, devices are the same JMP INDEX SYNERR: MOV #SYNMSG,R1 BR WRER DEVERR: MOV #DEVMSG,R1 BR WRER ASNOER: MOV #OASNER,R1 ;R1 has address of error message MOV $DSW,ARGBLK ;Put error code in message BR WRER ASNIER: MOV #IASNER,R1 ;R1 has address of error message MOV $DSW,ARGBLK ;Put error code in message WRER: CALL WRITE ;Output error message JMP UNDEL ;Go try for another command line .PAGE ; DEVICE - Get device name for ALUN directive ; ; Inputs: ; Device descriptor in CSI block ; Outputs: ; R3 = Device name (in ASCII) ; R4 = Unit number (in binary) DEVICE: MOV #CSIBLK+C.DEVD,R0 ;Device name descriptor MOV (R0)+,R1 ;Length of device name string MOV (R0),R0 ;Pointer to string MOVB (R0)+,TEMP ;Get low character MOVB (R0)+,TEMP+1 ;Get high character MOV TEMP,R3 ;R3 = device name CLR R4 ;Unit defaults to 0 SUB #2,R1 ;Device takes 2 characters BEQ 20$ ;If EQ, done (we'll let syntax slide) 10$: CMPB (R0),#': ;If :, done BEQ 20$ MOVB (R0)+,R2 ;Get digit SUB #'0,R2 ;Convert from ASCII ASH #3,R4 ;Bump higher digits by 8 (octal) ADD R2,R4 ;Add low digit SOB R1,10$ ;Still characters left 20$: RETURN ; DEVCHK - Check for same device ; ; Outputs: ; CS = devices same DEVCHK: MOV #HDR,R0 ;Use HDR as GLUN buffer GLUN$S #IPLUN,R0 ;Get input info MOV #DATA,R1 ;Use data as other GLUN buffer GLUN$S #OPLUN,R1 ;Get output info CMP G.LUNA(R0),G.LUNA(R1) ;Compare devices BNE 10$ ;If NE, devices are different CMPB G.LUNU(R0),G.LUNU(R1) ;Check units if same type device BNE 10$ ;If NE, units are different SEC ;Set the carry, input = output RETURN 10$: CLC RETURN .PAGE .SBTTL Index file search ; INDEX - Search the index file ; ; Inputs: ; Owner = UIC on input device INDEX: MOV #INXFDB,R0 CALL OPENFL ;Open the index file BCC 10$ MOV #FCSERR,ARGBLK ;Assume FCS error TSTB INXFDB+F.ERR+1 ;Was it? BEQ 1$ ;Yes - branch MOV #DIRERR,ARGBLK ;No, indicate DIR error 1$: MOVB INXFDB+F.ERR,R1 ;R1 has sign extended error code MOV R1,ARGBLK+2 ;Put error code in message MOV #INXMSG,R1 CALL WRITE JMP UNDEL 10$: MOV #BMPFDB,R0 CALL OPENFL ;Open the bitmap file BCC 15$ MOV #FCSERR,ARGBLK ;Assume FCS error TSTB BMPFDB+F.ERR+1 ;Was it? BEQ 11$ ;Yes - branch MOV #DIRERR,ARGBLK ;No, indicate DIR error 11$: MOVB BMPFDB+F.ERR,R1 ;R1 has sign extended error code MOV R1,ARGBLK+2 ;Put error code in message MOV #BITMSG,R1 CALL WRITE BR 60$ ; ; Defaults to sequential reads through index file ; 15$: MOV #INXFDB,R0 ;Get FDB address MOV #2,F.VBN+2(R0) ;Position to home block VBN READ$ R0 ;Read the home block WAIT$ R0 MOV HDR+H.IBSZ,R5 ;Get the index-bit-map size ADD #5,R5 ;First 5 headers are system files ADD R5,F.VBN+2(R0) ;Skip to the first user header CLR QFLAG ;Reset done flag 30$: READ$ #INXFDB ;Read index file header BCS 50$ ;If error, assume EOF WAIT$ R0 BCS 50$ ;If CS, file error, close file CMP HDR+H.IDOF,#27027 ;All header id's set to 27027 when created BNE 40$ ;If NE, block doesn't contain file header TST HDR+H.FNUM ;Test if this file header was deleted BNE 40$ ;If NE, this header is still in use CALL CHKFIL ;Check if proper UIC BCS 40$ ;If CS, not right file TST QFLAG ;Are we finished? BNE 50$ ;If NE, yes CALL COPY ;Try to recover this file BCS 50$ ;If CS, error in copying file 40$: BR 30$ ;Continue until EOF 50$: CLOSE$ #BMPFDB ;Close the bitmap file 60$: CLOSE$ #INXFDB ;Close index file JMP UNDEL ; OPENFL - Open file with statistics block ; ; Inputs: ; R0 = Address of FDB ; Outputs: ; CS = File open error OPENFL: MOV #STBK,F.STBK(R0);Specify statistics block OPEN$R R0 ;Open the file BCS 10$ ;Branch on error MOV STBK+4,F.HIBK(R0) ;Get highest VBN from STBK MOV STBK+6,F.HIBK+2(R0) ;Get low word ADD #1,STBK+6 ;Set EOF VBN to high block + 1 ADC STBK+4 MOV STBK+4,F.EFBK(R0) ;Get EOF VBN MOV STBK+6,F.EFBK+2(R0) ;Get low word 10$: RETURN .PAGE ; CHKFIL - Check if file is to be recovered ; ; Outputs: ; CC = Recover the file ; CS = Wrong file CHKFIL: TST UICFLG ;Was a UIC given? BEQ 10$ ;If EQ, no CMP HDR+H.FOWN,OWNER ;Correct UIC? BEQ 10$ ;If EQ, file has correct UIC 5$: SEC ;Else set carry and return RETURN 10$: MOV #5,R5 ;Length of file spec MOVB HDR+H.IDOF,R0 ;Offset to ID area in words ASL R0 ;Convert to bytes ADD #HDR+I.FNAM,R0 ;Address to file name in radix 50 MOV #ARGBLK,R1 TST (R0) ;Ignore temporary files BEQ 5$ 20$: MOV (R0)+,(R1)+ ;Move file name to ARGBLK SOB R5,20$ TST SWORD ;Are we selectively recovering? BNE 22$ ;If NE, yes MOV #FL1MSG,R1 ;Write filename CALL WRITE BR 30$ 22$: MOV #FILMSG,R1 ;Write filename before recovering CALL WRITE CLR TEMP ;Initialize answer QIOW$S #IO.RVB,#TILUN,#5,,#IOSB,,<#TEMP,#1> TSTB IOSB ;Did we get error? BMI 25$ ;If MI, yes, assume ^Z MOV TEMP,R0 ;Get response character BICB #40,R0 ;Convert to upper case CMPB #'Y,R0 ;Do we want this one? BEQ 30$ ;If EQ, yes CMPB #'G,R0 ;Do we want this and all following files? BEQ 28$ ;If EQ, yes CMPB #'Q,R0 ;Do we want to quit? BNE 5$ ;If NE, no - assume "N" 25$: INC QFLAG ;Yes, set quit flag 28$: CLR SWORD ;Reset switch word to "/-SE" 30$: CLC RETURN ; COPY - Open the output file to copy into ; ; Inputs: ; Acceptable file header has been found ; ; Outputs: ; CC = Successful copy ; CS = Error with output file ; ; File created on output device in users UIC COPY: MOV #HDR,R1 ;Deleted file header on input device MOVB H.IDOF(R1),R2 ;Header offset to ID area MOVB H.MPOF(R1),R3 ;Header offset to mapping area ASL R2 ;Convert offsets from words to bytes ASL R3 ADD R1,R2 ;R2 = Address of ID area ADD R1,R3 ;R3 = Address of mapping MOV #DFNB+N.FNAM,R4 ;R4 = Address for filename in default blk MOV #4,R5 ;Move file name and type only 10$: MOV (R2)+,(R4)+ ;Get the deleted file name SOB R5,10$ CLR (R4)+ ;Use version 0 MOV H.UFAT+F.HIBK+2(R1),R2 ;Get low word of file length BIT #100000,R2 ;Do we have more than 15 bits? BNE 11$ ;If NE, yes TST H.UFAT+F.HIBK(R1) ;Do we have more than 16 bits? BEQ 12$ ;If EQ, no 11$: MOV #77777,R2 ;Allocate maximum initial size 12$: BITB #UC.CON,H.UCHA(R1) ;Is this file contiguous? BNE 13$ ;If NE, yes NEG R2 ;Negative means non-contiguous allocation 13$: MOV #OUTFDB,R0 ;Get output FDB MOV R2,F.CNTG(R0) OPEN$W ;Open the output file for writing BCC 20$ ;If CC, file opened OK 14$: MOV #FCSERR,ARGBLK ;Assume FCS error TSTB OUTFDB+F.ERR+1 ;Was it? BEQ 15$ ;Yes - branch MOV #DIRERR,ARGBLK ;No, indicate DIR error 15$: MOVB OUTFDB+F.ERR,R1 ;R1 has sign extended error code MOV R1,ARGBLK+2 ;Put error code in message MOV #OUTMSG,R1 ;Send error message to terminal CALL WRITE CLOSE$ #OUTFDB ;Close the output file SEC RETURN 20$: MOV #5,R5 ;Move "opened" file name to message MOV #ARGBLK,R1 ADD #F.FNB+N.FNAM,R0 25$: MOV (R0)+,(R1)+ SOB R5,25$ MOV #OPNMSG,R1 CALL WRITE DIR$ #QIOATR ;Write attributes to save creation date BCS 14$ ;If CS, error MOVB IOSB,F.ERR(R0) ;Put error code in normal spot BLT 14$ ;If LT, error CALL COPYBK ;Go copy the file BCS 40$ ;If CS, unrecoverable error in COPYBK MOV #HDR+H.UFAT,R1 ;R1 = Address of user attributes for file MOV #OUTFDB,R0 ;R0 = Destination of attributes MOV #7,R5 ;Move 7 words of attributes 30$: MOV (R1)+,(R0)+ ;Move attributes to output FDB SOB R5,30$ CLOSE$ #OUTFDB ;Close the output file CLC ;Clear carry, indicate success 40$: RETURN .PAGE ; COPYBK - Copy the file blocks pointed to by the map area ; ; Inputs: ; R3 = Address of mapping area in header COPYBK: MOV #-1,BMAPB ;Reset current bit map pointer CLR R5 BISB M.USE(R3),R5 ;Words of retrieval pointers ASL R5 ;Bytes of retrieval pointers ADD #M.RTRV,R3 ;Address of first pointer CLR TEMP ;Reset virtual block count CLR TEMP+2 10$: TST R5 ;Test if done BLE 50$ ;If LE, done with file ; ; Assume size of contiguous block count - 1 = 1 byte (high byte of 1st word) ; and size of LBN field is 3 bytes ; CLR R1 BISB (R3)+,R1 ;R1 = High word of LBN CLR R4 BISB (R3)+,R4 ;R4 = Contiguous block count - 1 INC R4 ;0 ... -> 1 ... MOV (R3)+,R2 ;R2 = Low word of LBN 20$: ADD #1,TEMP+2 ;Increment virtual block number ADC TEMP CALL BLKCHK ;Check if block reused BCS 35$ ;If CS, error in BLKCHK MOV #RDQIO,R0 ;Address of read QIO MOV R1,Q.IOPL+6(R0) ;High word of LBN MOV R2,Q.IOPL+10(R0);Low word of LBN DIR$ R0 ;Read one block of file by LBN BCS 25$ ;If CS, directive error TSTB IOSB ;Check for I/O error BPL 28$ ;If PL, no errors MOV #FCSERR,ARGBLK ;FCS error MOVB IOSB,ARGBLK+2 ;Get error code for message BIS #177400,ARGBLK+2;Extend sign BR 26$ 25$: MOV #DIRERR,ARGBLK ;DIR error MOV $DSW,ARGBLK+2 ;Get error code for message 26$: MOV #TEMP,ARGBLK+4 ;Get VBN MOV #INPMSG,R1 CALL WRITE 28$: WRITE$ #OUTFDB ;Write the block to output device BCS 29$ WAIT$ R0 BCC 40$ 29$: MOV #FCSERR,ARGBLK ;Assume FCS error TSTB OUTFDB+F.ERR+1 ;Was it? BEQ 30$ ;Yes - branch MOV #DIRERR,ARGBLK ;No, indicate DIR error 30$: MOVB OUTFDB+F.ERR,R1 ;R1 has sign extended error code MOV R1,ARGBLK+2 ;Put error code in message MOV #TEMP,ARGBLK+4 ;Get VBN MOV #OUTMSG,R1 CALL WRITE SEC 35$: RETURN 40$: ADD #1,R2 ;Next contiguous block ADCB R1 ; (Note: INC doesn't set carry) DEC R4 ;Any more contiguous blocks BGT 20$ ;If GT, yes SUB #4,R5 ;R5 = New bytes of retreival pointers BR 10$ 50$: CLC RETURN .PAGE ; BLKCHK - Check if the block has been reused ; ; Inputs: ; R1,R2 = Double precision logical block number ; ; Effects: ; Warning written to terminal if block reused BLKCHK: CALL $SAVAL ;Save the registers MOV R2,R3 MOV R1,R2 ;R1,R2 => R2,R3 MOV R3,R1 BIC #177770,R1 ;R1 = Bitmap bit number in byte .REPT 3 ASR R2 ;Double precision divide by 8. ROR R3 ;(Bitmap is 8 blocks per byte) .ENDR ; ; Compute VBN in BITMAP.SYS, (512. * 8.) = Device blocks per bitmap block ; DIV #1000,R2 ;Divide R2,R3 by 1000 ;R2 = VBN of bitmap file ;R3 = byte address into bitmap block ADD #2,R2 ;Map starts at second block CMP R2,BMAPB ;Do we already have this block in memory? BEQ 10$ ;If EQ, yes MOV R2,BMAPB MOV R2,BMPFDB+F.BKVB+2 ;Insert VBN in FDB CLR BMPFDB+F.BKVB READ$ #BMPFDB ;Read block of bitmap BCS 2$ WAIT$ R0 BCC 10$ 2$: MOV #FCSERR,ARGBLK ;Assume FCS error TSTB BMPFDB+F.ERR+1 ;Was it? BEQ 5$ ;Yes - branch MOV #DIRERR,ARGBLK ;No, indicate DIR error 5$: MOVB BMPFDB+F.ERR,R1 ;R1 has sign extended error code MOV R1,ARGBLK+2 ;Put error code in message MOV #BITMSG,R1 CALL WRITE SEC RETURN 10$: BITB BITCHK(R1),BMAP(R3) BNE 20$ ;If NE, block still unused MOV #TEMP,ARGBLK+12 ;Insert virtual block number MOV #WARN,R1 ;Send warning of corruption CALL WRITE 20$: CLC RETURN .PAGE .SBTTL TERMINAL IO ; WRITE - Send message to TI: ; ; Inputs: ; R1 = Input string WRITE: MOV R0,-(SP) MOV R1,-(SP) MOV R2,-(SP) MOV #PREARG,R2 ;Argument block for EDMSG MOV #LINE,R0 ;Output buffer for EDMSG CALL $EDMSG MOV R1,TQIO+Q.IOPL+2 ;Set record length DIR$ #TQIO MOV (SP)+,R2 MOV (SP)+,R1 MOV (SP)+,R0 RETURN .END START