.Title BIGFILES .ENABLE DBG .IDENT /X01.06/ ;BIGFILES.MAR - Programme to list the largest files on a device ; Layout of File Header Block FH.EAD =^O40446 ; Valid Header looks like this F.HEAD =0 ; Header Offset F.NUM =^O10 ; File # Offset F.SEQ =^O12 ; Seq. # Offset F.VOL =^O14 ; Vol. # Offset P.ROG =^O74 ; Prog # Offset P.ROJ =^O76 ; Proj # Offset F.DID =^O102 ; Directory ID F.NAM =^O114 ; FILNAM Offset F.END =^O140 ; End # Offset ; Layout of Node in Tree L.LAST =.-. ; Left Pointer L.NEXT =L.LAST+4 ; Right Pointer L.DATA =L.NEXT+4 ; Start of Data ; Define Job/Process Offsets $JPIDEF ; Define Buffer Sizes NBIG = 50 ; # of biggest files to look for BUFLEN =^O1000 ; Length of Header Block LINLEN =100 ; Length of Line Buffer B_FSPEC =59 ;Length of fspec portion of Line Buffer NX_FID =^X00010001 ; INDEXF.SYS file ID .MACRO PRINT X MOVL X,R0 TSTB (R0)+ BNEQ .-3 SUBL X,R0 MOVL X,OTRAB+RAB$L_RBF MOVW R0,OTRAB+RAB$W_RSZ $PUT RAB=OTRAB .ENDM .MACRO STORE X MOVL X,-(SP) CALLS #1,STORE .ENDM .PSECT CODE NOWRT,EXE .ENTRY BEGIN,^M JSB GETCMD ; Get User's Command JSB GETDSK ; Get Disk to Scan JSB GETPPN ; Get UIC JSB GETLST ; Get Listing Device JSB INIT_SIZE ; Initialize largest size tables JSB OPENS ; Open [0,0]INDEXF.SYS serial JSB SEARCHS ; Scan [0,0]INDEXF.SYS for Files JSB CLOSES ; Close [0,0]INDEX.SYS serial JSB OPENR ; Open [0,0]INDEXF.SYS random JSB SEARCHR ; Convert FID of biggest files to filespec JSB CLOSER ; Close [0,0]INDEXF.SYS random JSB OTOPEN ; Open the Listing Device MOVAL ROOT,-(SP) ; Print the Tree CALLS #1,PRINT ; (Recursive) JSB PSUMMARY ; Print summary line JSB OTCLOSE ; Close the listing device $EXIT_S ; ;---- GETCMD: Retrieve the input command line ; GETCMD: PUSHAL INLEN ; PUSHAL PROMPT ; PUSHAL LINDES CALLS #3,G^LIB$GET_FOREIGN ; J=GET_FOREIGN(LINBUF,PROMPT,INLEN) BLBC R0,10$ MOVAL LINBUF,R2 ; R2 --> Next (First) character in LINBUF RSB 10$: JMP BOMB GETDSK: MOVAL INNAME,R1 ; R1 --> Filename Buffer TSTW INLEN ; Null String? BEQL 5$ CMPB #^A%[%,(R2) ; [P,PN] Delimiter? BEQL 5$ CMPB #^A%/%,(R2) ; Option Delimiter? BEQL 5$ BRW 10$ 5$: MOVAL DNS0,R0 ; Yes, then default Disk BRW 18$ 10$: CMPB #^A%[%,(R2) ; Done? BEQL 15$ CMPB #^A%/%,(R2) BEQL 15$ TSTL INLEN ; Scanned Everything? BEQL 99$ ; Yes -- then Syntax Error MOVB (R2)+,(R1)+ ; No - copy Byte of File Descriptor DECW INLEN CMPB #^A%:%,-1(R2) ; Colon is delimiter BEQL 15$ BRW 10$ 15$: MOVAL DNS1,R0 ; R0 --> File Name String 18$: MOVB (R0)+,(R1)+ BNEQ 18$ SUBL #INNAME,R1 MOVB R1,INFAB+FAB$B_FNS ; Install File Name Size in INFAB MOVB R1,RANFAB+FAB$B_FNS ; Install File Name Size in RANFAB RSB 99$: MOVL #SS$_BADPARAM,R0 JMP BOMB GETPPN: DECW INLEN BLSS 10$ ; Null String CMPB #^A%[%,(R2)+ ; First Character must be [ BNEQ 5$ JSB GETNUM ; Get Project Number MOVL R1,PROJ ; Install It DECW INLEN CMPB #^A%,%,(R2)+ ; Delimiter must be , BNEQ 99$ JSB GETNUM ; Get Programmer Number MOVL R1,PROG ; Install it DECW INLEN CMPB #^A%]%,(R2)+ ; Delimiter must be ] BNEQ 99$ RSB 5$: INCW INLEN CMPB #^A%/%,-(R2) ; Option Designator? BNEQ 99$ 10$: $GETJPI_S ITMLST=ITMLST RSB 99$: MOVL #SS$_BADPARAM,R0 JMP BOMB GETNUM: CLRL R1 ; Initialize Number 5$: SUBB #48,(R2) ; Convert Digit to Number BLSS 10$ ; (Invalid) CMPB #7,(R2) BLSS 10$ ; (Invalid) MULL #8,R1 ; Shift previous number DECW INLEN ADDB (R2)+,R1 ; Add in this Digit BRW 5$ 10$: ADDB #48,(R2) ; Restore Line Buffer RSB ; Exit with R2 --> Delimiter GETLST: CMPB #32,(R2) ; Scan for Spaces BNEQ 5$ ; (Not a Space) DECW INLEN TSTB (R2)+ ; Skip over this Space BRW GETLST 5$: TSTW INLEN ; Option Specified? BLEQ 20$ ; (No) MOVAL OPTL,R1 ; R1 --> Option String 10$: DECW INLEN CMPB (R1)+,(R2)+ ; Search until Delimiter BEQL 10$ CMPB #^A%:%,-1(R2) ; Found Colon Delimiter? BEQL 12$ CMPB #^A%=%,-1(R2) ; Found Equals Delimiter? BEQL 12$ BRW 99$ ; No Delimiter Found 12$: MOVAL OTNAME,OTFAB+FAB$L_FNA ; Insert Listing Filename MOVB INLEN,OTFAB+FAB$B_FNS ; ...and File Name Length BEQL 99$ ; Syntax Error MOVZWL INLEN,R0 ; R0 = Bytes to Copy MOVAL OTNAME,R1 ; R1 --> Filename Buffer 15$: MOVB (R2)+,(R1)+ ; Copy Filename SOBGTR R0,15$ 20$: RSB 99$: MOVL #SS$_BADPARAM,R0 ; Syntax Error JMP BOMB ; ;---- INIT_SIZE: Initialize the largest size tables ; INIT_SIZE: CLRL R0 10$: CLRQ FID_TABLE[R0] ; FID's matching largest sizes CLRL SIZE_TABLE[R0] ; Largest sizes CLRW PROJ_TABLE[R0] ; UIC CLRW PROG_TABLE[R0] ; UIC AOBLSS #NBIG,R0,10$ JSB FIND_SMALL RSB ; ;---- OPENS: Open INDEX.SYS for serial access ; OPENS: $OPEN FAB=INFAB ; Open DEVICE:[0,0]INDEXF.SYS BLBC R0,10$ $CONNECT RAB=INRAB BLBC R0,10$ CLRL TOTBLK ; Clear Total Blocks CLRL TOTFIL ; and Total Files RSB 10$: JMP BOMB ; ;---- OPENR: Open INDEX.SYS for random access ; OPENR: $OPEN FAB=RANFAB ; Open DEVICE:[0,0]INDEXF.SYS BLBC R0,10$ $CONNECT RAB=RANRAB BLBC R0,10$ RSB 10$: JMP BOMB ; ;---- SEARCHS: Search thru all the file headers in INDEXF.SYS ; SEARCHS: ; ;---- Scan to the second occurrance of the INDEXF.SYS file header ;---- in order to determine the offset between file IDs and the ;---- INDEXF VBN such that: file header VBN = offset + file ID ; CLRL OFFSET CLRL NX_CNT ; Index file header counter 5$: JSB FETCH ; Read in block from Index file BLBC R0,20$ INCL OFFSET MOVAL BUFFER,R1 ; R1 points to block from Index file CMPW #FH.EAD,F.HEAD(R1) BNEQ 5$ ; Ignore blocks which are not headers CMPL #NX_FID,F.NUM(R1) BNEQ 5$ ; Scan to the INDEXF.SYS file header INCL NX_CNT CMPL #2,NX_CNT BNEQ 5$ ; Scan to the second INDEXF.SYS header DECL OFFSET BRW 15$ ; Go process the second INDEXF header 10$: JSB FETCH ; Read in block from Index File BLBC R0,20$ 15$: JSB FILTER ; Scan for Header, right [P,PN] BLBC R0,10$ JSB GETSIZ ; Open file to get size JSB CHECK_LARGE ; Check for large file BRW 10$ 20$: RSB ; ;---- FETCH: Get the next file header and check for end of file ; FETCH: $GET RAB=INRAB ; Read in Block BLBS R0,10$ CMPL #RMS$_EOF,R0 ; Error - EOF? BEQL 10$ JMP BOMB ; No -- Complain 10$: RSB ; ;---- FILTER: Validate file header ; FILTER: MOVL #SS$_ACCONFLICT,R0 ; Assume Error MOVAL BUFFER,R1 ; R1 -- File Header CMPW #FH.EAD,F.HEAD(R1) BNEQ 10$ ; Not Header Block ; ;---- Process all files independent of UIC ; MOVW P.ROJ(R1),PROJ ; Get UIC MOVW P.ROG(R1),PROG TSTW F.NUM(R1) BEQL 10$ ; File is Deleted MOVL #SS$_NORMAL,R0 ; File Header is OK INCL TOTFIL ; Found Valid File 10$: RSB ; ;---- GETSIZ: Open file to get size ; GETSIZ: MOVAL BUFFER,R1 ; R1 points to header MOVQ INNAM+NAM$T_DVI,ZZNAM+NAM$T_DVI ; Install Device Identifier MOVQ INNAM+NAM$T_DVI+8,ZZNAM+NAM$T_DVI+8 MOVW F.NUM(R1),ZZNAM+NAM$W_FID ; Install File Identifier MOVW F.SEQ(R1),ZZNAM+NAM$W_FID+2 MOVW F.VOL(R1),ZZNAM+NAM$W_FID+4 $OPEN FAB=ZZFAB ; Open File by File ID BLBC R0,20$ ; (Couldn't) MOVL ZZXAB+XAB$L_HBK,ZZALQ ; Return File Size TSTL TOTBLK ; Total Blocks invalid? BLSS 15$ ADDL ZZXAB+XAB$L_HBK,TOTBLK ; No - Update Total Blocks INCL TOTBLK ; Include File Header in Total 15$: $CLOSE FAB=ZZFAB BRW 30$ 20$: MOVL #-1,ZZALQ ; Invalidate File Size MOVL #-1,TOTBLK ; Invalidate Total Blocks 30$: RSB ; ;---- CHECK_LARGE: If this file is larger than the smallest one in ;---- the list, then save it. ; CHECK_LARGE: TSTL ZZALQ BLSS 10$ ; Skip if invalid file size MOVL SMALL_NDX,R0 ; R0 points to current smallest file CMPL SIZE_TABLE[R0],ZZALQ BGEQU 10$ MOVL ZZALQ,SIZE_TABLE[R0] ; This file is larger, save it MOVQ ZZNAM+NAM$W_FID,FID_TABLE[R0] MOVW PROJ,PROJ_TABLE[R0] MOVW PROG,PROG_TABLE[R0] JSB FIND_SMALL ; Find the new smallest 10$: RSB ; ;---- FIND_SMALL: Find the index of the smallest file in the SIZE_TABLE ; FIND_SMALL: CLRL R1 ;R1 points to smallest CLRL R0 ;R0 advances thru SIZE_TABLE 10$: CMPL SIZE_TABLE[R0],SIZE_TABLE[R1] BGEQU 20$ MOVL R0,R1 ;Update smallest pointer 20$: AOBLSS #NBIG,R0,10$ ;Search whole table MOVL R1,SMALL_NDX ;Save index of smallest RSB ; ;---- SEARCHR: Process all of the files whose ID's are in FID_TABLE ; SEARCHR: MOVL #-1,R6 ;R6 points to FID_TABLE and SIZE_TABLE 10$: JSB FETCHR ;Get the next FID BLBC R0,90$ ;Skip if FID_TABLE is exhausted JSB FILTERR BLBC R0,10$ ;Skip if FID = initial value = 0 JSB READR ;Read the file header corresponding to this FID JSB FORM_LINE ;Format, sort and stack the ASCII print line BRB 10$ 90$: RSB ; ;---- FETCHR: Retrieve the next FID from FID_TABLE ; FETCHR: CLRL R0 AOBLSS #NBIG,R6,10$ ;Update _TABLE pointer BRB 20$ ;Skip if _TABLE exhausted 10$: MOVQ FID_TABLE[R6],R4 ;R4,R5 contain FID MOVL #SS$_NORMAL,R0 20$: RSB ; ;---- FILTERR: Skip _TABLE entries with FID = 0 ; FILTERR: CLRL R0 TSTL R4 ;Test FID BEQL 10$ MOVL #SS$_NORMAL,R0 10$: RSB ; ;---- READR: Read the file header corresponding to the FID ; READR: ADDW3 OFFSET,R4,IREC ;Offset + FID = record # of header $GET RAB=RANRAB BLBS R0,10$ JMP BOMB 10$: RSB ; ;---- FORM_LINE: Format file items into ASCII line buffer ; FORM_LINE: MOVAL LINBUF,R2 ;R2 points to line buffer JSB FORM_SIZE ;Convert the size to ASCII JSB FORM_UIC ;Convert the UIC to ASCII JSB FORM_FSPEC ;Get the filespec for this FID JSB STACK_LINE ;Sort the print line onto the print stack RSB ; ;---- FORM_SIZE: Convert the file size to ASCII ; FORM_SIZE: MOVL SIZE_TABLE[R6],R0 ;Get file size from table JSB MAPD ;Convert to ASCII MOVW #^A' ',(R2)+ RSB ; ;---- FORM_UIC: Convert UIC to ASCII ; FORM_UIC: MOVB #^A'[',(R2)+ MOVW PROJ_TABLE[R6],R0 ;Project (group) JSB MAP MOVB #^A',',(R2)+ MOVW PROG_TABLE[R6],R0 ;Programmer (member) JSB MAP MOVB #^A']',(R2)+ MOVW #^A' ',(R2)+ RSB ; ;---- FORM_FSPEC: Retrieve file spec starting with file header ; FORM_FSPEC: MOVAL (R2),D_LINBUF+4 ; Filespec address in descriptor CALLG FSPEC_ARG,G^FSPEC ; Get filespec starting with header RSB ; ;---- STACK_LINE: Delimit end of line and store line on line stack ; STACK_LINE: ADDL D_LINBUF,R2 ;Point to end of line buffer 10$: CMPB #^A' ',-(R2) ;Remove trailing blanks BEQLU 10$ TSTB (R2)+ MOVB #^O15,(R2)+ MOVB #^O12,(R2)+ CLRB (R2)+ ; End of Record STORE #LINBUF ; Pack it away in Buffer RSB ; ;---- MAP: Convert (R0) to octal and store ASCII digits at (R2) ; MAP: PUSHR #^M ADDL #3,R2 MOVL #3,R3 10$: MOVL R0,R1 BICL #^C^O7,R1 ADDL #48,R1 ; Convert to Octal Digit MOVB R1,-(R2) ; Pack it away ASHL #-3,R0,R0 ; Shift in next digit SOBGTR R3,10$ ADDL #3,R2 ; Point at next free in Buffer POPR #^M RSB ; ;---- MAPD: Convert (R0) to decimal and store ASCII digits at (R2) ; MAPD: TSTL R0 ; Invalid number? BLSS 35$ PUSHR #^M ; Save Registers CLRL R5 ; Clear Leading Zero flag MOVAL LIST,R4 ; R4 --> Divisor table 10$: CLRL R3 ; R3 = Digit 15$: INCL R3 SUBL (R4),R0 ; Subtract Divisor BGEQ 15$ ADDL (R4)+,R0 ; Compensate for DECL R3 ; extra subtract BISL R3,R5 ; Update Leading Zero flag BNEQ 20$ MOVB #32,(R2)+ ; Leading Zero -- suppress it BRW 25$ 20$: ADDB3 #48,R3,(R2)+ ; Output Digit 25$: TSTL (R4) ; End of Divisor Table? BNEQ 10$ TSTL R5 ; Was at least one digit printed? BNEQ 30$ MOVB #48,-1(R2) ; No -- force Zero output 30$: POPR #^M ; Restore Registers MOVB #^A%.%,(R2)+ ; Indicate decimal RSB 35$: MOVQ #^A% ****%,(R2)+ ; Invalid Number RSB .ENTRY STORE,^M MOVL ROOT,R2 ; R2 --> Node BNEQ 10$ JSB GETNOD ; No such node - handle Root as special case MOVL R0,R2 BRW 30$ ; Initialize the new Node 10$: MOVL 4(AP),R3 ; Compare (AP) with (R2) MOVAL L.DATA(R2),R4 12$: CMPB (R3)+,(R4)+ ; Match? BEQL 12$ ; ...if so, try again BGEQ 20$ ; BLSS/BGEQ for ascending/descending TSTL L.NEXT(R2) ; (AP) > (R2) BLEQ 15$ MOVL L.NEXT(R2),R2 ; Update R2 BRW 10$ 15$: JSB GETNOD ; Get new Node MOVL R0,L.NEXT(R2) ; Insert new Node MOVL L.NEXT(R2),R2 ; R2 --> New Node BRW 30$ ; Initialize the new Node 20$: TSTL L.LAST(R2) ; (AP) < (R2) BLEQ 25$ MOVL L.LAST(R2),R2 ; Update R2 BRW 10$ 25$: JSB GETNOD ; Get new Node MOVL R0,L.LAST(R2) ; Insert New Node MOVL L.LAST(R2),R2 ; R2 --> New Node BRW 30$ 30$: CLRL L.LAST(R2) ; New Node, no L.LAST field CLRL L.NEXT(R2) ; ... or L.NEXT field MOVL 4(AP),R0 MOVAL L.DATA(R2),R2 35$: MOVB (R0)+,(R2)+ ; Copy Record into new Node BNEQ 35$ RET GETNOD: MOVL CURADR,R0 ; R0 --> New Node address ADDL #LINLEN,CURADR ; Update Current Address CMPL CURADR,TOPADR ; Extend Task? BLSS 10$ MOVL R0,-(SP) ; Save R0 $EXPREG_S PAGCNT=#1,RETADR=RETADR BLBC R0,99$ MOVL (SP)+,R0 ; Restore R0 TSTL ROOT ; First call? BNEQ 10$ MOVL RETADR,ROOT ; Yes -- Initialize ROOT MOVL RETADR,R0 ; ...and fix up R0 ADDL RETADR,CURADR ; ...and CURADR 10$: MOVL RETADR+4,TOPADR ; Update TOPADR RSB 99$: JMP BOMB ; Error Extending Task OTOPEN: $CREATE FAB=OTFAB ; Create Listing File BLBS R0,10$ 99$: JMP BOMB ; Can't create file 10$: $CONNECT RAB=OTRAB BLBC R0,99$ PRINT #HEADR ; Print Header for List MOVAL INNAME,R0 ; R0 --> Input Filename MOVAL H0,R2 ; R2 --> Device Specifier 15$: MOVB (R0)+,(R2)+ ; Copy Device Name CMPB #^A%:%,-1(R2) ; Colon terminates BNEQ 15$ CLRB (R2)+ ; Indicate End of Buffer PRINT #H0 ; Print Disk PRINT #H1 ; blanks ; MOVL PROJ,R0 ; Install Project Number ; MOVAL H2,R2 ; JSB MAP ; PRINT #H2+3 ; Skip 3 Leading Zeroes ; MOVL PROG,R0 ; ...then Prog. Number ; MOVAL H3,R2 ; JSB MAP ; PRINT #H3+3 ; Skip 3 Leading Zeroes $ASCTIM_S TIMBUF=H4A PRINT #H4 ; Print Remainder of String RSB .ENTRY PRINT,^M<> TSTL @4(AP) ; Test Argument BEQL 10$ ; (Null Tree) ADDL3 @4(AP),#L.LAST,-(SP) CALLS #1,PRINT ; Call Print(L.LAST) ADDL3 @4(AP),#L.DATA,R1 PRINT R1 ; *** PRINT *** ADDL3 @4(AP),#L.NEXT,-(SP) CALLS #1,PRINT ; Call Print(L.NEXT) 10$: RET ; ;---- PSUMMARY: Print the summary line ; PSUMMARY: MOVL TOTBLK,R0 ; Summarize... MOVAL SBLK,R2 JSB MAPD ; Total of XXXXXXX. Blocks in MOVL TOTFIL,R0 MOVAL SFIL,R2 JSB MAPD ; XXXXXXX. Files PRINT #SUMARY RSB OTCLOSE: $CLOSE FAB=OTFAB ; Close Output File RSB CLOSES: $CLOSE FAB=INFAB ; Close Input File RSB CLOSER: $CLOSE FAB=RANFAB ; Close Input File RSB BOMB: MOVL R0,ERRTYP $PUTMSG_S MSGVEC=ERRVEC,FACNAM=SCNAME $EXIT_S .PSECT DATA,LONG SMALL_NDX: .LONG 0 SIZE_TABLE: .BLKL NBIG FID_TABLE: .BLKQ NBIG PROJ_TABLE: .BLKW NBIG PROG_TABLE: .BLKW NBIG INFAB: $FAB FNA=INNAME,FOP=NAM,RFM=FIX,MRS=BUFLEN,NAM=INNAM INNAM: $NAM INRAB: $RAB FAB=INFAB,MBC=16,UBF=BUFFER,USZ=BUFLEN RANFAB: $FAB FNA=INNAME,FOP=NAM,RFM=FIX,MRS=BUFLEN,NAM=RANNAM RANNAM: $NAM RANRAB: $RAB FAB=RANFAB,UBF=RANBUF,USZ=BUFLEN,RAC=KEY,- KBF=IREC,KSZ=4 OTFAB: $FAB FNM= OTRAB: $RAB FAB=OTFAB ZZFAB: $FAB FOP=NAM,NAM=ZZNAM,XAB=ZZXAB ZZNAM: $NAM ZZXAB: $XABFHC ERRVEC: .LONG 2 ; Two Arguments ERRTYP: .LONG 0 ; Error goes here .LONG 0 ; Room for STV PROJ: .LONG 0 ; Project Number PROG: .LONG 0 ; Programmer Number RETADR: .BLKL 2 ; Returned Addresses for Extend Task ROOT: .LONG 0 ; Bottom of Record Buffer CURADR: .LONG 0 ; --> Current Record TOPADR: .LONG 0 ; Top of Record Buffer TOTBLK: .LONG 0 ; Block Total for [P,PN] TOTFIL: .LONG 0 ; File Total for [P,PN] ZZALQ: .LONG 0 ; Allocated Size of File IREC: .LONG 0 ; INDEXF record number(key) RANBUF: .BLKB BUFLEN ; Buffer for file header for directory search BUFFER: .BLKB BUFLEN ; Buffer for File Header DNS0: .ASCII /DRA1:/ DNS1: .ASCIZ /[0,0]INDEXF.SYS/ HEADR: .ASCII <^O15><^O12><^O15><^O12> .ASCIZ / Scan of / H0: .BLKB 20 ; Room for Device Specifier H1: .ASCIZ / / H2: .ASCIZ /xxxxxx,/ H3: .ASCIZ /xxxxxx] on / H4A: .LONG 20 ; String Descriptor for ASCTIM .LONG H4 H4: .BLKB 20 ; Space for Date and Time .ASCII <^O15><^O12><^O15><^O12> .ASCII / SIZE UIC FILE SPECIFICATION/ .ASCIZ <^O15><^O12><^O15><^O12> INNAME: .BLKB LINLEN ; File Name goes here... INLEN: .LONG 0 ; Line Length ITMLST: .WORD 4 ; Return Quadword .WORD JPI$_GRP ; Project Number .LONG PROJ .LONG 0 .WORD 4 ; Return Quadword .WORD JPI$_MEM ; Programmer Number .LONG PROG .LONG 0 .LONG 0 LINDES: .LONG LINLEN ; Length of Line .LONG LINBUF ; Address of Line LINBUF: .BLKB LINLEN ; Line Buffer LIST: .LONG 1000000 ; Table of Divisors for MAPD .LONG 0100000 .LONG 0010000 .LONG 0001000 .LONG 0000100 .LONG 0000010 .LONG 0000001 .LONG 0000000 ; End of Table OPTL: .ASCII %/OUTPUT% ; Option Designator String OTNAME: .BLKB LINLEN ; Listing Filename goes here PROMPT: .ASCID /BIGFILES>/ SCNAME: .ASCID /SCAN/ SUMARY: .ASCII <^O15><^O12>/ Total of/ SBLK: .ASCII /XXXXXXX. Blocks in/ SFIL: .ASCIZ /XXXXXXX. File(s)/<^O15><^O12> FSPEC_ARG: .LONG 6 .ADDRESS RANBUF ; File header buffer .ADDRESS RANRAB ; RAB for random access to INDEXF .ADDRESS D_LINBUF ; Descriptor of fspec part of LINBUF .ADDRESS RANBUF ; Random access buffer .ADDRESS IREC ; Random access record # .ADDRESS OFFSET ; OFFSET+FID=VBN of file header OFFSET: .LONG .-. NX_CNT: .LONG .-. D_LINBUF: .LONG B_FSPEC .ADDRESS .-. .END BEGIN