.MCALL .MODULE .MODULE BUPINI,VERSION=19,IDENT=NO,COMMENT= ; Copyright (c) 1998 by Mentec, Inc., Nashua, NH. ; All rights reserved ; ; This software is furnished under a license for use only on a ; single computer system and may be copied only 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 except for use on such ; system and to one who agrees to these license terms. Title ; to and ownership of the software shall at all times remain ; in Mentec, Inc. ; ; The information in this document is subject to change without ; notice and should not be construed as a commitment by Digital ; Equipment Corporation, or Mentec, Inc. ; ; Digital and Mentec assume no responsibility for the use or ; reliability of its software on equipment which is not supplied ; by Digital or Mentec, and listed in the Software Product ; Description. .SBTTL BUPINI - Initialize Backup Disk Volumes ; 12-Jan-89 RHH V5.5 Work .SBTTL Local Macros .MACRO ...... .ENDM .SBTTL Global Data References .NLIST BEX .GLOBL INITED ; Defined in BUPIMA .SBTTL INIDAT - Homeblock and Directory Segment Data .PSECT INIDAT,D IDBUP: .ASCII /BUQ / ; "BUQ" followed by 9 spaces. .EVEN ; ------------------------- Order dependent ----------------------------- PROTHB: .WORD 1 ; Pack cluster size .WORD 6 ; Starting block of first segment VERS: .RAD50 /V05/ ; Version ID: .ASCII /RT11A / ; Volume id OWNER: .ASCII / / ; Owner DECRT: .ASCII /DECRT11A / ; System id PROSIZ== .-PROTHB ; Size in bytes of homeblock .EVEN ; ---------------------------------------------------------------------- ; Prototype directory segment with EMPTY entry. ; ------------------------- Order dependent ----------------------------- PROTO:: .WORD 1 ; ONE segment in use .WORD 0 ; Link to next segment .WORD 1 ; Highest segment open .WORD 0 ; Number of extra bytes RESBLK: .WORD 10 ; Starting block for files .WORD 1000 ; File status, empty entry .RAD50 / EMPTYFIL/ ; File name PEMPLN: .WORD 0 ; File length .WORD 0 ; Job number, channel number .WORD 0 ; File creation date .WORD 4000 ; End of file marker PROTOL== .-PROTO ; Length in byte of segment ; ---------------------------------------------------------------------- INISIZ: .WORD 0 ; Device size for BB Scan WASVOL: .WORD 0 ; Disk's previous volume no. FUDGE: .WORD 0 ; RK06/7 buffer adrs compensation .SBTTL Main code ;+ ; INITIALIZE ; This routine is in charge of handling the initialization of backup ; volumes. It provides three entry points, one which processes explicit ; initialize commands and two which implicitly initialize non-backup ; volumes during the execution of image copy commands. ;- .MCALL .READW, .WRITW, .SPFUN .MCALL .BR, SOB .PSECT INITD,D RTHMB: .BYTE 0 ; RT-11 homeblock indicator BPHMB: .BYTE 0 ; BUP-inited homeblock OLDBUP: .BYTE 0 ; Old bup homeblock DRSVAL: .BYTE 0 ; VALID_DIRECTORY indicator HASFLS: .BYTE 0 ; VOLUME_CONTAINS_FILES indicator HASPRO: .BYTE 0 ; VOLUME_CONTAINS_PROTECTED_FILES NEEDIN: .BYTE 0 ; Volume needs initialization INICMD: .BYTE 0 ; INIT command (vs. BACKUP command) .EVEN .PSECT INITLZ,I .ENABL LSB INITIO::MOV INFIL,OUTFIL ; correct CSI's reverse perspective MOV OUTFIL,DEVSPC ; Point to OUTPUT device name MOV #1,OUTCHA ; (use OUTPUT's channel) MOV #INIDEV,R4 ; Get address to store dev CALL SETINA ; Put device name in message MOV #DEVICE,R4 ; Get address to store dev CALL SETINA ; Put device name in message MOV NHDRAD,R1 ; At first available address, CALL FETHAN ; fetch handler. MOV R0,NHDRAD ; save next avail hdlr address MOV R0,BUFADD ; Save address for buffers CALL XMBUFR ; Try for XM high mem buffer MOV OUTCHA,R2 ; On output channel, MOV #DEVSPC,R3 ; and INPUT device, CALL LOOKD ; Lookup device. BCC INITD1 ; If no errors, proceed. RTN1: RETURN ...... .DSABL LSB .SBTTL INITD1 - Initialize Code .ENABL LSB ; Enter here from INIT code above INITD1: MOVB #1,INICMD ; Declare INIT command MOVB #1,NEEDIN ; Declare need for initializing MOV #1,VOLNUM ; Set VOLUME_NUMBER = 1 BR 20$ ; Initialize. ...... ; Enter here from BACKUP code, at the beginning of a volume INITD2::CLRB NEEDIN ; No assumptions about needing init BR 10$ ...... ; Enter here to force an initialization. The volume number has been ; predetermined by the BUPIMA code. INITD3::MOVB #1,NEEDIN ; Need INIT from BACKUP 10$: CLRB INICMD ; NOT INIT command (BACKUP command) 20$: CLR INITED ; Indicate NOT_YET_INITIALIZED CALL CHKRTD ; Check for RT-11 structure BCC 24$ ; proceed if no read error CALL PROM2 ; prompt for output volume BR 20$ ; and try again. ...... 24$: TSTB DRSVAL ; valid directory? BEQ 30$ ; Branch if not RT-11 disk CLR R1 ; Default to no-special-message TSTB BPHMB ; Check for BUP initialized BEQ 40$ ; Branch if not TSTB GIV.Z ; Disk has BUP signature; /INITIALIZE? BMI 70$ ; Branch if so. TSTB NEEDIN ; non-vol-1 BACKUP? BNE 70$ ; do initialize disk. TSTB OLDBUP ; Is it an old BUP disk? BNE 50$ ; if so, check for "Files exist" MOV WASVOL,VOLNUM ; preserve its volume number RETURN ; otherwise return - already BUP disk. ...... 30$: MOV #NRT,R1 ; "Volume not RT-11 initialized" CMPB DEV1,#DEV.DM ; Initializing RK06/7? BEQ 35$ CMPB DEV1,#DEV.DL ; or RL01/2? BNE 70$ 35$: CALL ERRR ; BUP can't do that from scratch. BR 130$ ...... 40$: MOV #BAK,R1 ; "Not a BACKUP volume" BR 70$ ...... 50$: TSTB HASFLS ; Check for existing files BEQ 70$ ; Branch if none MOV #VCF,R1 ; "Volume contains files" ; Decide what messages to print to the terminal 70$: TSTB NEEDIN ; FORCED init? BNE 80$ ; Branch if so - VOLNUM known. ; This is part of a BACKUP sequence. It has been determined that the ; first volume needs BUP initializing in order to proceed. If /INIT ; was NOT specified, ignore /NOQUERY and force a prompt. MOV #1,VOLNUM ; Otherwise, this is 1st volume. TSTB GIV.Z ; /INITIALIZE specified? BPL 90$ ; If not, /NOQUERY is ignored. 80$: TSTB GIV.Y ; /NOQUERY? BMI DOINIT ; Go directly to INIT if so. ; Print special warning, if there is one, and request permission to INITIALIZE 90$: TSTB INICMD ; INIT command? BEQ 100$ ; branch if not. TST R1 ; any special message? BEQ 120$ ; if not, just do simple prompt. CMP R1,#NRT ; don't care about NOT RT INITED BEQ 120$ CMP R1,#BAK ; or NOT A BACKUP VOLUME BEQ 120$ 100$: TST R1 ; is there a special message? BEQ DOINIT ; If not, go initialize. 110$: .ERR #ERRARE,R1,LEVEL=WARNING,RETURN=YES,FILE=#DEVSPC 120$: CALL INIPRM ; Ask "Initialize; Are you sure? " BNE DOINIT ; On "YES" proceed to INIT and BACKUP 130$: SEC ; Indicate INIT_NOT_DONE RETURN ; On "NO" return to caller. ...... .DSABL LSB .SBTTL DOBBS - Do BADBLOCK SCAN and INITIALIZE ;+ ; Do BAD_BLOCK scan, write BOOT block, HOME block, and blank directory. ;- .ENABL LSB DOINIT: MOV OUTCHA,R5 ; Use normal output channel MOV BUFADD,R1 ; Start of buffer CALL READHB ; read existing homeblock BCS BAD1 ; if BBR not right, quit now. CALL DOBBSB ; Do badblock scan and Create BOOT BCS BAD1 ; Branch if error CALL HBDATA ; Do new HOMEBLOCK BCS BAD1 ; Branch if error CALL FILSEG ; Go create RT DIRECTORY segment BCS BAD1 ; if error return now. INC INITED ; Indicate INITIALIZED RETURN ...... BAD1: SEC ; Set carry RETURN ; Return to caller ...... .DSABL LSB .SBTTL DOBBSB - Do bad-block scan and write BOOT block .ENABL LSB DOBBSB: CALL GSIZE1 ; Get size of device to scan BCS BAD1 ; Bad exit MOV R1,INISIZ ; Get size into location for later TSTB GIV.G ; /G? ("Don't do BBS?") BMI 95$ ; If so, go on to create boot block. CALL BADBLK ; Call badblock scan BCS 100$ ; Branch if error TSTB GIV.W ; /NOLOG in effect? BMI 95$ MOV #NBB,R1 CALL INFORM ; <-I-NO BAD BLOCKS DETECTED> 95$: CALL CREBOO ; Go create boot block ; (returns success/error in C) 100$: RETURN ...... .DSABL LSB ;+ .SBTTL CHKRTD - Check for RT-11 Directory Structure ;- .ENABL LSB CHKRTD: CLRB RTHMB ; Assume not RT-11 homeblock CLRB BPHMB ; Assume not BUP homeblock CLRB OLDBUP ; Assume not OLD BUP homeblock CLRB DRSVAL ; Assume invalid directory CLRB HASFLS ; Assume volume has no files CLRB HASPRO ; and no protected files MOV BUFADD,R1 ; Get buffer address MOV R1,BUFAD2 ; Start of second buffer ADD #512.,BUFAD2 ; Allocate for home block ; Read homeblock, and make sure that volume is truly an RT-11 initialized ; volume. If it's not, and the device is an RL or RK06/7, the BBRT may ; really have things fouled up. (For example, FILES-11 disks contain ; 0,1 in the first two words of the homeblock, which the RT-11 handler ; interprets to mean, "replace block 0 with block 1".) .READW #EMTARE,OUTCHA,R1,#256.,#HMBLK BCS 120$ ADD #DK.VTO,R1 ; Point to where "DECRT11A" should be MOV #DECRT,R0 ; Point to "DECRT11A" MOV #12.,R2 ; match this many characters 10$: CMPB (R0)+,(R1)+ ; do they match? BNE 110$ ; Return, indicating NOT-RT DEC R2 BGT 10$ INCB RTHMB ; Ok. Assume DUP or BUP made this. MOV BUFADD,R1 ; point to buffer again CMP DK.TAG(R1),IDBUP ; BUP identifier in HB? BNE 30$ ; branch if not. CMPB DK.TAG+2(R1),#'P ; OLD BUP initialized? BNE 20$ INCB OLDBUP ; Flag it "OLD BUP disk" CMPB DK.TAG+3(R1),#40 ; Any files there? BEQ 20$ INCB HASFLS ; "with files" 20$: INCB BPHMB ; otherwise, set a flag TSTB NEEDIN ; If not initing, BNE 30$ MOV DK.VOL(R1),WASVOL ; get its volume number ;+ ; Disk seems to be initialized, either by BUP or by DUP. Read directory ; segment of the output disk. Check to see if the directory header ; makes sense. If so, check whether it contains any permanent files. ;- 30$: MOV #6,R2 ; Directory block 40$: MOV BUFADD,R1 ; re-point to buffer TST R2 ; block no. = zero? BEQ 110$ ; return if no more dir blocks .READW #EMTARE,OUTCHA,R1,#512.,R2 ; Read directory segment BCC 60$ ; Branch if no error 50$: CALL RE1MSG BR BAD1 ...... 60$: TSTB DRSVAL ; Directory validated yet? BNE 70$ ; If so, skip header check. TST @R1 ; Look at total # of segments BLE NOTRT ; If neg or zero, it's NOT RT-11 vol CALL SEGVAL ; Check for directory seg validity BCS NOTRT ; Branch if not. INCB DRSVAL ; Declare directory valid. TST D.LENG(R1) ; 1st entry status word zero? BEQ NOTRT ; Branch if so. Bad entry. 70$: MOV R1,R0 ; calculate ADD #2000,R0 ; high limit of buffer address MOV D.NEXT(R1),R2 ; Calculate next segment BEQ 80$ ; branch if none DEC R2 ASL R2 ADD #6,R2 ; calculate blk no of next segment 80$: ADD #D.LENG,R1 ; Point to 1st directory entry 90$: CMP R1,R0 BHIS NOTRT ; running off end? Declare invalid. BIT #E.EOS,@R1 ; end of segment? BNE 40$ ; get next segment BIT #E.PERM,@R1 ; permanent entry? BEQ 100$ ; branch if not MOVB #1,HASFLS ; otherwise set the HAS_FILES flag. BIT #E.PROT,@R1 ; Is file protected? BEQ 100$ ; branch if not MOVB #1,HASPRO ; set the HAS_PROTECTED_FILES flag. 100$: ADD #E.ELEN,R1 ; point to next entry BR 90$ ; and continue ...... NOTRT: CLRB DRSVAL ; Declare invalid directory 110$: CLC ; but no READ_ERROR problems 120$: RETURN ...... .DSABL LSB .SBTTL DBOOT - Prototype Boot Block ; DEFINITIONS CR = 15 LF = 12 TTPS = 177564 TTPB = 177566 CONTYP = 13 ; MSCP CONTROLLER CODE ; Data Area DBOOT: NOP ; TYPE 1 BOOT BLOCK RESET ; DATA VOLUME BR 3$ ; GO TO EXECUTABLE CODE .=DBOOT+ ; START OF ID AREA .BYTE 20 ; PDP-11 INSTRUCTION SET .BYTE 103 ; CONTROLLER TYPE (NON-MSCP) .BYTE 20 ; RT-11 FILE STRUCTURE .BYTE 0 ; CHECKSUM 3$: BR 4$ ; CALL PRINT ROUTINE 4$: JSR R0,1$ ; DO IT .ASCII <0><0><0><0>\?BOOT-U-No boot on volume\<200> .EVEN 1$: TSTB @#TTPS ; IS PRINTER READY? BPL 1$ ; NO, BRANCH BACK MOVB (R0)+,@#TTPB ; OUTPUT A CHARACTER BPL 1$ ; REPEAT TILL ALL 2$: BR 2$ ; ADIOS DBOOTS=<.-DBOOT>/2 .SBTTL CREBOO - Create Boot Block ;+ ; CREBOO - This routine will create the boot block indicating a ; data volume (non-bootable). This will secure the operation ; of IND .structure ;- .ENABL LSB CREBOO: MOV OUTCHA,R5 BR 5$ ...... CREBO1::MOV TMPCHA,R5 ; Entry for TEMP file boot block 5$: MOV #,R4 ; POINT TO CONTROLLER TYPE ;*ACTION* CHECK IF MSCP CONTROLLER DEC R4 ; POINT TO INFORMATION AREA CLR R1 ; R1 = ACCUMULATOR CLR R2 ; USE FOR LATER MOVB (R4)+,R2 ; GET N*2 BYTE ADD R2,R1 ; ADD TO ACCUMULATOR MOVB (R4)+,R2 ; GET N*2+1 BYTE ADD R2,R1 ; ADD TO ACCUMULATOR MOVB (R4)+,R2 ; GET N*2+2 BYTE ADD R2,R1 ; ADD TO ACCUMULATOR COM R1 ; COMPLEMENT RESULT MOVB R1,(R4) ; PUT CHECKSUM IN BOOT MOV #DBOOT,R4 ; POINT TO BOOT TEMPLATE .WRITW #EMTARE,R5,R4,#DBOOTS,#0 ; WRITE BOOT BLOCK BCC 10$ ; BRANCH IF NO ERROR CALL WR1MSG ;<-F-DIRECTORY OUTPUT ERROR> SEC 10$: RETURN ...... .DSABL LSB .SBTTL Create blank RT-11 directory segment ;+ ; This routine creates an RT-11 directory segment on the volume opened. ; ; CALL FILSEG ; ; C-BIT = 0 SUCCESS ; = 1 ERROR ; ; R1,R2,R3 - MODIFIED ;- .ENABL LSB FILSEG: MOV BUFAD2,R1 ; Get address of buffer CALL CLRBUF ; Clear it ADD #512.,R1 ; Get address of 2nd block buffer CALL CLRBUF ; Clear that too. MOV INISIZ,R1 ; Get output device size SUB RESBLK,R1 ; Account for directory/homeblock MOV R1,PEMPLN ; Store in prototype directory MOV BUFAD2,R1 ; Get address of buffer MOV #PROTO,R2 ; Get address of prototype seg MOV #PROTOL,R3 ; Length of prototype 2$: MOVB (R2)+,(R1)+ ; Store DEC R3 ; Decrement count BNE 2$ ; Repeat till finish ; Write two blocks (one and only directory segment) .WRITW #EMTARE,OUTCHA,BUFAD2,#512.,#6 BCC 4$ ; Return if no error CALL WR1MSG ; <-F-DIRECTORY OUTPUT ERROR> ; SEC 4$: RETURN .DSABL LSB .SBTTL Create RT11 homeblock ;+ ; Write the RT-11 homeblock structure on the volume. ; If the volume was previously determined to be RT-11 initialized, ; preserve any existing BBRT information. Otherwise, clear the BBRT. ; ; CALL HBDATA ; Write a BUP homeblock ; ; to channel OUTCHA ; or ; CALL CREHB1 ; This entry writes a NORMAL ; ; homeblock to channel TMPCHA ; on return: ; ; C-BIT = 0 SUCCESS ; = 1 ERROR ; R0,R1,R2 - ARE MODIFIED ; ;- .ENABL LSB CREHB1::MOV TMPCHA,R5 ; Use TEMPORARY file MOV BUFADD,R1 ; Start of buffer CALL CLRBUF ; Clear buffer, point to it MOV #170000,2(R1) ; initialize BBRT area MOV #007777,4(R1) BR 40$ ; join common code ...... HBDATA: MOV OUTCHA,R5 ; Use normal output channel MOV BUFADD,R1 ; Start of buffer CALL READHB ; read existing homeblock BCC 10$ ; Branch if no error CALL RE1MSG ; <-F-Directory input error> BR BAD2 ; Bad exit ...... 10$: TSTB RTHMB ; Is the homeblock RT-11 style? BNE 20$ ; Branch if so. CALL CLRBUF ; If not, Clear it out, MOV #170000,2(R1) ; initialize BBRT area MOV #007777,4(R1) 20$: MOV VOLNUM,DK.VOL(R1) ; Store VOLUME NUMBER in DK.VOL CLR DK.TOT(R1) ; Set DK.TOT = 0 CLR DK.SIZ(R1) ; Set DK.SIZ = 0 CLR DK.TSZ(R1) ; Set DK.TSZ = 0 ADD #DK.TAG,R1 ; Point to BUP ID area MOV #IDBUP,R0 MOV #12.,R2 ; Store BUP ID in homeblock buffer 30$: MOVB (R0)+,(R1)+ DEC R2 BNE 30$ 40$: MOV BUFADD,R1 ; Point to start of buffer ADD #PCLUST,R1 ; Point to cluster size item MOV #PROTHB,R0 ; Point to prototype homeblock MOV #PROSIZ,R2 ; Size of homeblock data 50$: MOVB (R0)+,(R1)+ ; Move data to buffer DEC R2 BNE 50$ ; Calculate Homeblock Checksum MOV R3,-(SP) CLR R0 ; clear accumulator MOV BUFADD,R1 ; Point to homeblock data MOV #255.,R2 ; add up this many words 60$: ADD (R1)+,R0 DEC R2 BGT 60$ MOV R0,@R1 ; store it in homeblock MOV (SP)+,R3 ; Write the homeblock .WRITW #EMTARE,R5,BUFADD,#256.,#HMBLK BCC 70$ ; Branch if no error CALL WR1MSG ; <-F-DIRECTORY OUTPUT ERROR> BAD2: SEC 70$: RETURN ; Return ...... .DSABL LSB .SBTTL Error message routines ;+ ; Print an -E-level message and return. The message pointer is passed ; in R1. ;- ERRR: .ERR #ERRARE,R1,LEVEL=ERROR,RETURN=YES,FILE=#DEVSPC RETURN ...... ;+ ; Display "?BUP-F-Directory input error" and return. ;- RE1MSG: MOV #RE1,R1 ; Do DIRECTORY INPUT error message BR ERMSG ...... ;+ ; Display "?BUP-F-Directory I/O error" and return. ;- WR1MSG: MOV #WR1,R1 ; Do DIRECTORY OUTPUT error message .BR ERMSG ;+ ; Print a fatal error message and return ;- ERMSG: MOV OUTFIL,DEVSPC .ERR #ERRARE,R1,LEVEL=FATAL,RETURN=YES,FILE=#DEVSPC BR BAD2 ...... .SBTTL BADBLK - Bad block scan ;+ ; The volume to be initialized is scanned for bad blocks. The ; buffer area available for the read request is calculated by ; the external subroutine 'dynbuf'; when the volumes' blocks ; left to read are less than the blocks chunks being read then ; the wordcount is adjusted to that of the blocks left to read. ; The size of the volume scanned is calculated from external routine ; GSIZE. ; ; CALL BADBLK ; ; C-BIT = 0 SUCCESS ; = 1 ERROR (BAD BLOCKS) ; ; R0-R5 - ARE MODIFIED ; ; EXTERNAL LINKAGE ; ; DYNBUF - ALLOCATE MEMORY DYNAMICALLY FOR BUFFER SPACE ; ;- .ENABL LSB BADBLK::TSTB GIV.W ; /NOLOG in effect? BMI 10$ MOV #BBS,R1 CALL INFORM ; <-I-BAD BLOCK SCAN STARTED...> 10$: MOV INISIZ,R4 ; Get device size CALL DYNBUF ; Calculate available memory MOV BUFADD,R2 ; Get buffer address CLR R3 ; Start at block zero SCAN: MOV R4,R0 ; Blocks to read BEQ GOOD ; Branch if finish MOV R5,R1 ; Word count for buffer SWAB R1 ; Blocks to read CMP R0,R1 ; Are there left less than to be read BHIS 20$ ; No go read SWAB R0 ; Make blocks left new wordcount MOV R0,R5 ; Next word count 20$: .READW #EMTARE,OUTCHA,R2,R5,R3 ; Check if the read works BCC 30$ ; Branch if no error CMPB @#ERRBYT,#1 ; Is it hard error BNE BAD ; No, skip BBLMSG: MOV #BBD,R1 CALL INFORM ; <-I-Bad blocks detected; Use another volume> BR BAD ; Bad exit ...... 30$: SWAB R0 ; Make wordcount blocks ADD R0,R3 ; Update input block SUB R0,R4 ; Update blocks to read BNE SCAN ; Repeat if nto finish GOOD: TST (PC)+ ; Clear crry BAD: SEC ; Set carry RETURN ; Return ...... .DSABL LSB .SBTTL CLRBUF - Clear the 256 word buffer area ;+ ; ; R1 = Address of buffer to clear ; ;- .ENABL LSB CLRBUF: MOV R1,-(SP) ; Save working registers MOV R2,-(SP) MOV #256.,R2 10$: CLR (R1)+ ; Clear the area DEC R2 BNE 10$ MOV (SP)+,R2 ; restore registers MOV (SP)+,R1 RETURN ...... .SBTTL INIPRM - Initialize prompt ; Ask "Initialize ddn; Are you sure?" INIPRM: 30$: MOV #INIDEV,R1 ; "Initialize; Are you sure?" CALL ANSWRP ; Get answer. YES or NO? BMI 30$ ; Neither; try again. RETURN ; Return with answer code in R0 ...... .DSABL LSB .SBTTL READHB - Read existing homeblock ;+ ; Read existing home block ; ; R5 = channel ; R1 = buffer address ;- .ENABL LSB READHB: MOV R2,-(SP) ; make R2 available CLR FUDGE MOV #EMTARE,R0 ; point to EMT arg block MOV R0,R2 INC R2 ; point to EMT subcode MOV R5,(R0)+ ; put channel in low byte MOV #HMBLK,(R0)+ ; blk MOV R1,(R0)+ ; buf MOV #256.,(R0)+ ; wcnt CLR @R0 ; assume .READW CMPB DEV1,#DEV.DM ; Is device RK06 or RK07? BNE 10$ ; branch if not. INC FUDGE ; if so, set flag BR 20$ 10$: CMPB DEV1,#DEV.DL ; Is it an RL01 or RL02? BNE 30$ ; branch if not. 20$: MOV #<377*400+377>,(R0)+ ; SPFUN READ code in EMTARE CLR @R0 ; specify WAIT mode MOVB #32,@R2 ; put SPFUN code in EMTARE BR 40$ 30$: MOVB #10,@R2 ; put READ code in EMTARE 40$: MOV #EMTARE,R0 ; point to EMTARE, EMT 375 ; do READ or SPFUN BCS 70$ ; return immediately on error ; If device supports BBR in homeblock, check to make sure that it's ; RT-11 initialized. If it's an RK06/7, move data down one word. CMPB @R2,#10 ; did we do .READW? BEQ 70$ ; return if so with C-Clear. TST FUDGE ; RK06/7? BEQ 60$ ; branch if not. MOV R1,R0 ; buf MOV R1,-(SP) MOV #256.,R2 ; counter TST (R0)+ ; R0 -> 2nd word of buf 50$: MOV (R0)+,(R1)+ ; move buffer down one word DEC R2 BNE 50$ MOV (SP)+,R1 ; restore buf pointer ; Check to make sure that homeblock itself is not BBR'ed (like FILES-11 ; disks appear to be) 60$: CMP @R1,#HMBLK ; BBR entry involves blk 0 or 1? BHI 70$ ; (CMP sets C-bit if so) MOV #NRT,R1 CALL ERRR ; -E-Volume not RT-11 initialized SEC 70$: MOV (SP)+,R2 ;*C* restore R2 RETURN ...... .DSABL LSB .END