.MCALL .MODULE .MODULE BUPMT1,VERSION=24,IDENT=NO,GLOBAL=.BPMT1 ; 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 BUPMT1 - Magtape Backup ; 06-Jul-89 RHH V5.5 work .ENABL GBL,LC .NLIST BEX .SBTTL Conditionals DEBUG = 0 ; Enable/Disable debugging code AUTOLB = 1 ; Auto-increment of tape label on subsequent vol .SBTTL MACROS and DEBUG messages .MCALL .ASSUME .BR .CLOSE .DATE .ENTER .FETCH .MCALL .GVAL .HERR .LOOKUP .PRINT .PURGE .READ .MCALL .READW .SERR SOB .SPFUN .WAIT .WRITW .PSECT MT1DAT,D ; PSECT ordering - ensure that .PSECT .LIBC.,I ; MT1 is last because handler .PSECT MT1,I ; is loaded immediately above. .GLOBL $CBDMG ; ULBLIB - Convert Binary to Decimal .MACRO .TYPE1 LOC,MSGADR ; Type a message with a value JSR R5,TYPE1 .WORD MSGADR .WORD LOC .ENDM .MACRO .DBTYP MSG ; Type a message .IF NE DEBUG .PRINT MSG .IFF .ENDC .ENDM .MACRO .DBTP1 LOC,MSGADR ; Type a message with a value .IF NE DEBUG JSR R5,TYPE1 .WORD MSGADR .WORD LOC .ENDC .ENDM .MACRO ...... .ENDM .SBTTL MONTAB - Days per month table .PSECT MT1DAT,D ; MONTAB contains 12 entries, one for each month, each containing the total ; number of days in a non-leap year up till the start of that month. JAN = 0 ;0 DAYS UP TO JANUARY FEB = JAN + 31. MAR = FEB + 28. APR = MAR + 31. MAY = APR + 30. JUN = MAY + 31. JUL = JUN + 30. AUG = JUL + 31. SEP = AUG + 31. OCT = SEP + 30. NOV = OCT + 31. NOEL = NOV + 30. MONTAB: .WORD 0 ;IF NO DATE SPECIFIED, MONTH = 0 .WORD JAN,FEB,MAR,APR,MAY,JUN,JUL,AUG,SEP,OCT,NOV,NOEL .SBTTL Local Variables for BUPMT1 SAVE1: .WORD 0 ; save blocks to copy SAVE2: .WORD 0 ; save input location TEMP1: .WORD 0 ; Used for temporary storage BFA2: .WORD 0 ; 2nd buffer address TDATE: .WORD 0 ; RT-11 DATE WORD ENDTAP: .WORD 0 ; END-OF-TAPE flag TCDONE: .WORD 0 ; COPY-DONE/ERROR flag NXTBLK: .WORD 0 ; next block needed -RHH BLKCNT: .WORD 0 ; VERIFY word count BSEQNO: .WORD 0 ; Block sequence number FSEQNO: .WORD 0 ; File sequence number FSECNO: .WORD 0 ; File section number APENDD: .WORD 0 ; "Appended to THIS tape" flag EOTFLG: .WORD 0 ; END-OF-TAPE flag INBUF: .WORD 0 ; Input buffer pointer for VERIFY OUTBUF: .WORD 0 ; Output buffer pointer for VERIFY DUPNBF: .BLKB 10. ; Duplicate saveset name buffer .EVEN IDBLK: .WORD 4 ; IDATE argument block .WORD MONVAL .WORD DAYVAL .WORD YEARVL .WORD TDATE MONVAL: .WORD 0 ; IDATE variables DAYVAL: .WORD 0 YEARVL: .WORD 0 .IF NE DEBUG MSG1: .ASCIZ /*** Starting TCOPY ***/ ;MSG2: .ASCIZ /*** Starting VERIFY ***/ MSG3: .ASCIZ /*** Returned from VERIFY ***/ MSG4: .ASCIZ /*** Writing TWO TAPE MARKS ***/ MSG5: .ASCII /*** Attempt tape block starting with /<200> MSG6: .ASCIZ /*** Normal finish of TCOPY ***/ MSG8: .ASCII /*** READing at /<200> MSG10: .ASCII /NUMSPF = /<200> MSG11: .ASCII /NXTBLK = /<200> MSG12: .ASCIZ /*** TAPE MARK found during VERIFY ***/ MSG13: .ASCII /*** VERIFYing with BLKCNT=/<200> MSG14: .ASCII /*** Top of VERIFY, BLKCOP=/<200> MSGBA: .ASCII /BUFADD = /<200> MSGSB: .ASCII /SPFBUF = /<200> .EVEN .ENDC OLDBUP: .ASCIZ /?BUP-F-Cannot append to old BUP tape/ .EVEN .SBTTL TBAC - Main code for TAPE BACKUP ;+ ; The tape backup. The magtape device name is loaded into the mount ; and initialize messages by SETNAM. The handler for magtape device ; is loaded. The user is requested to mount the tape. A non-file struc- ; tered lookup is performed to the tape on channel TAPCHA. The status ; of the tape is obtained by CHKSTA, on return if the carry is clear ; it means that we can proceed, else the user decide to abort before ; initialize. The information about the input file or device is obtained ; by CHKINP, this information will be used when initializing the tape ; (TINIT). On return from initialize, the routine CALBUF is called to ; calculate the even number of 2K word records available as buffer space. ; This will be split into two for a read buffer and a write buffer. ; A message signaling the start of the copy operation is printed. On ; return from the copy operation (TCOPY) if the carry is set, it means ; that the backup operation is not completed yet and the user must be ; informed to mount a new volume. This new volume will be checked, init, ; and used for backup as the first one, the copy operation is finished ; when the carry bit is returned clear. ;- .PSECT MT1,I .ENABL LSB TBACO:: MOV #OUTASC,R1 ; device ASCII MOV #DEVICE,R4 ; back device msg CALL SETNAM ; Get device into prompt MOV #OUTASC,R1 ; device ASCII MOV #INIDEV,R4 ; init device msg CALL SETNAM ; Get device into prompt MOV INCHAN,DSKCHA ; disk is input, MOV OUTCHA,TAPCHA ; tape is output. .DATE ; Get todays date MOV R0,TDATE ; Store date ; Fetch magtape (output) device handler MOV OUTFIL,DEVSPC ; Get output dev for nfs look MOV NHDRAD,R1 ; next available handler address CALL FETHAN ; Go fetch handler MOV R0,NHDRAD ; Save address for next handler MOV #1,VOLNUM ; Volume number one TSTB GIV.Y ; NOQUERY Given? BMI 10$ ; If so, don't interrogate. CALL PROM1 ; Ask for output vol mount BCC 10$ ; If answer is YES, proceed RETURN ; Return if no ; Open access to tape using NFS lookup ; Check for BUP initialized 10$: MOV #DEVSPC,R1 ; R1 -> device for nfs MOV #TAPCHA,R2 ; R2 -> channel CALL TLOOK ; Go open magtape channel CALL CHKSTA ; Check status of tape BCS 50$ BIT #A$GRP,OPTACT ; INIT only? BEQ 20$ ; If not, do input stuff. MOV NHDRAD,BUFADD ; Save upper free address ;; CALL XMBUFR ; If XM, try using region. BR 30$ ; Fetch input device handler. ; Initialize stuff pertaining to input. ; Allocate and calculate addresses of buffers. 20$: CALL INLOAD ; Fetch & open input BCS 50$ ; on error, quit. 30$: CALL CALBUF ; Calculate number of buffers ASR R5 ; Required spfuns MOV R5,NUMSPF ; Save number of spfuns CALL GTSFAD ; Calc adrs of 2nd buf SPFBUF .DBTP1 BUFADD,MSGBA .DBTP1 SPFBUF,MSGSB .DBTP1 NUMSPF,MSG10 CLR APENDD ; INIT APPEND flag MOV #1,FSEQNO ; INIT File Sequence number MOV #1,FSECNO ; INIT File Section number, MOV OUTFIL,DEVSPC ; Have proper dev ready for errors ; Initialize the tape, if /INIT (/Z) requested TSTB GIV.Z ; INITIALIZE specified? BPL 40$ ; Branch if not. CALL TINIT ; Do tape initialization BCS 50$ ; Branch if error BIT #A$GRP,OPTACT ; INIT only? BEQ 80$ ; if not, go ahead. ; Finishup INIT_ONLY job CALL TWOTM ; write TM's 2 and 3, CALL REWIND ; rewind tape, CLC ; indicate job well-done. RETURN ; return to BUP main. ; Doing a backup. Find the logical end-of-tape (two tapemarks). 40$: CALL FNDEND ; Find end of current tape - BCC 60$ ; If no error, go do backup. 50$: JMP 150$ ; Branch if stop desired ; Reenter here for multiple files 60$: CMP FSEQNO,#1 ; Is tape volume empty? BEQ 70$ ; Pretend we're creating volume. INC APENDD ; make note of doing append, 70$: CALL FINIT ; Write HDR records and tape mark, 80$: .IF NE DEBUG CLR NXTBLK ; INIT "Next Blk Needed" .ENDC MOV FILSIZ,BLKCOP ; get blocks to backup MOV FILSIZ,REMFIL ; for /DEVICE case ; For the new wildcard capability, subroutine GINBLK (in BUPSUB) ; is used to Get INput BLocKs. Initialize variables related to GINBLK. ; MAKDIR in BUPCMD has hopefully made a directory "container" in ; a temporary file on SY:. This file is treated as the zeroth file. BIT #I$OPT,OPTACT ; /DEVICE operation? BNE NEXTAP ; if so, skip this stuff. CLR RESUME ; Indicate 1st blocks from TMP file MOV CONBLK,REMFIL ; blocks remaining in TMP file ; A new output volume is ready to go NEXTAP: CALL SETSTR ; Enable STREAMING TSTB GIV.W ; /NOLOG in effect? BMI 100$ ; If so, skip messages TST APENDD BEQ 90$ .PRINT #MESAPP ; Print "Appending..." BR 100$ ; Backup one section to tape until either the input is exhausted ; or the tape reaches EOT. 90$: .TYPE1 VOLNUM,MESCON ; Signal start of copy 100$: CALL SAVPOS ; Save current parameters MOVB GIV.W,VERFYG ; Set control for logging CLR EOTFLG ; reset EOT flag CALL TCOPY ; Go backup blocks to tape ; The section is complete. CALL CLESTR ; Turn OFF streaming MOV TCDONE,R0 ; check DONE flag BMI 150$ ; Branch if error ; Verify the saveset section against the input disk or file(s) TSTB GIV.V ; /VERIFY ? BPL TBAC2 ; No, branch TSTB GIV.W ; /NOLOG? BMI 110$ ; If so, skip the message .PRINT #MESVER ; Starting Verify pass... 110$: CALL GETVER ; prepare data for verify CALL PREVER ; prepare drive for verify MOVB #377,VERFYG ; turn off logging CALL TVCOPY ; VERIFY the section CALL AFTVER ; restore BACKUP op. data .DBTYP #MSG3 ; If not done, proceed with the next output volume TBAC2: TST TCDONE ; Any more to do? BNE 130$ ; If not, leave tape where it is. CALL REWOFL ; rewind and dismount this volume. INC VOLNUM ; Next volume TPROM2: CALL PROM2 ; Request mount output vol 120$: .WAIT TAPCHA ; Wait for rewind to complete CALL CHKSTA ; Get new tape information BCS TPROM2 ; Branch if no init desired CALL TINIT ; Go initialize BCS TPROM2 ; Branch if error CLR APENDD ; no longer appending BR NEXTAP ; Go do next tape volume. ; The current backup operation is complete. 130$: TSTB GIV.V ; was VERIFY on? BMI 140$ ; if so, we're in correct position CALL BAKUP ; Back up over *EOF1EOF2*** ; We are all done. 140$: CALL BAKDON ;<-I-Backup operation complete> 150$: CALL CLOTAP ; Close Tape channel .CLOSE DSKCHA ; and disk channel CALL PURGTM ; and temp channel RETURN ; return to BUP main. .DSABL LSB .SBTTL FNDEND - Find logical end of tape ;+ ; Prepare for appending data to the end of a mounted magtape. ; Find the logical end of tape and position the head just before ; the second tape mark. ;- .ENABL LSB FNDEND: CLR FSEQNO ;Clear file sequence number CALL SHDR1 ;Get squeezed version of saveset name JSR R5,STRNCP ; for checking duplicates .WORD DUPNBF .WORD LBLBUF+4 .WORD 10. CLR TEMP1 ;Clear TAPEMARK indicator TSTB GIV.M ;Inhibit Rewind specified? BMI 30$ ;Branch around if not. CALL REWCHK ;Initial Rewind of 1st mounted vol BCS 80$ ;User typed 'NO' to 'Tape Not Ready'? BR 30$ ;Begin by reading block 10$: CALL FSPFIL ;Move tape forward one tape mark INC TEMP1 ;Set TAPEMARK indicator TSTB @#$ERRBY BEQ 30$ ;error returned from SPFUN? 20$: MOV #NOTRDY,R1 ;Tape unit not ready? CALL ANSWRP ;Do prompt, get answer BGT 10$ ;YES? Continue? BNE 20$ ;What? JMP 130$ ;NO? Don't? 30$: CALL READHD ;Read tape block CALL TEOF ;tape mark? (or hardware error?) BCC 40$ ;Branch if not. TST TEMP1 ;2nd TAPEMARK? BNE LEOTF ;logical end of tape. INC TEMP1 ;Set TAPEMARK flag BR 30$ ;Read another record. 40$: CLR TEMP1 ;Indicate NOT TAPEMARK. .IF NE DEBUG MOV #0,80.@R1 .PRINT R1 .ENDC CMP @R1,VO ;VOL1? BNE 45$ ; Branch if not CMP DK.TAG(R1),#BU.TAG ;Old BUP VOL1? BEQ 65$ ; can't use that tape. BR 30$ ; read HDR1 record. 45$: CMP @R1,HD ;normal tape block. BNE 60$ ;Is it HDR1? TST (R1)+ ;point to name field CMP (R1)+,#"R1 BNE 10$ CALL CHKBUP ;Check for legitimate BUP saveset ; check for file sequence no = 0000 here. If so, backspace and return. CALL DCODVL ;Get file seq no, and file id. TST FSEQNO BNE 50$ ;If Non-zero, normal append. CALL BACKSP ;Otherwise backspace over ZEROED hdr1, CALL BACKSP ; and (for safety) over the VOL1 CALL FORWSP ; now (for safety) fwd over VOL1, BR 120$ ; and the tape is now positioned. 50$: MOV #LBLBUF+AH1.FI,R1 ;Point to ID field, CALL CHKDUP ;Check for duplicate saveset name BR 10$ 60$: CMP @R1,#"EO ;Is it a EO(F,V) label? BNE 10$ ;if not, continue... ADD #4,R1 ;Point to name field, CMP @R1,#20040 ;old BUP tape? BNE 50$ ;Check for duplicate name 65$: .PRINT #OLDBUP BR 80$ LEOTF: ;TWO TAPEMARKS FOUND--- CALL BACKSP ;Back up over both tape marks, CALL BACKSP MOV #4,R3 ; (allow four EO(F,V)n records) CALL BACKSN ;And then over (EOFs) or (VOL1,HDR1) CALL READHD ;Read record CALL TEOF ;tapemark? BCS 70$ ;Yes. Now read and decode EOF1. CMP @R1,VO ;Was it a VOL1? BNE BADFMT ;No? Aaw shucks. CALL CHKBVL ;Insist on genuine BUP VOL1 labels JSR R5,STRNCP ;Decode Volume Label .WORD FSETID ;destination is FSETID field .WORD LBLBUF+4. ;source is buffer .WORD 6 ;6 characters max BR 120$ ;Ready for HDR1 write. ...... 70$: CALL READHD CMP (R1)+,EO ;Check for EOFn or EOVn BNE BADFMT ;oops. CMP @R1,#"V1 BNE 100$ ;End of volume - go to next. CALL REWIND ;Initiate rewind, .ERR #ERRARE,#SPA,LEVEL=W,RETURN=YES ; no room on output CALL PROM1 ; prompt for next input volume. BCC 90$ ;Resume (start over again) 80$: BR 130$ ;or else give up. 90$: .WAIT TAPCHA ;Wait for rewind to finish, BR 10$ ; and go continue. ...... 100$: CMP @R1,#"F1 BNE BADFMT CALL DCODVL ;Decode it MOV #LBLBUF+4,R1 CALL CHKDUP ;Check for duplicate saveset name CALL CHKBUP ;Check for BUP tape ; Appending to existing tape CALL FSPFIL ;Move past tapemark again. 120$: INC FSEQNO ;Set up new file number TST (PC)+ ;Done. Return SUCCESS 130$: SEC ;Abort the operation 140$: RETURN ...... BADFMT: MOV #BAK,R1 ;<-F-Not a BACKUP volume > JMP FATALD ...... .SBTTL READHD - Read a tape VOL, HDR, EOF or EOV label READHD: MOV #LBLBUF,R1 ;point to label record buffer, CALL READMT ;read record from tape, BIT #TS.ERR,R0 ;error on tape? BEQ 150$ ;Return if no errors MOV #RE2,R1 ;<-F-Input error > BR FATO ; Decode the File Sequence Number and get the File Set ID from ; a HDR1 or EOF1 record. DCODVL: MOV #LBLBUF,R2 ADD #AH1.SN,R2 ;Point to it in buffer MOV #4,R3 ;Number of chars expected CALL ASCBIN ;Extract the File Sequence No. MOV R0,FSEQNO ;Store it. JSR R5,STRNCP ;Decode Volume Label .WORD FSETID ;destination is FSETID field .WORD LBLBUF+21. ;source is buffer .WORD 6 ;6 characters max 150$: RETURN ...... ; Check for duplicate saveset name. ; Assumes R1 already pointing to HDR1 or EOF1 file ID field CHKDUP: MOV #DUPNBF,R0 ;Does the name agree with new name? MOV #10.,R3 ;check first 10 characters in field CALL STRNCM BCC 150$ CALL BACKSP ;Back over the (HDR,EOF)1 block MOV #DSS,R1 ;<-F-Duplicate Saveset name <>> FATO: JMP FATALO ...... ; Check for BUP-initialized VOL1 label CHKBVL: MOV #,R1 ;Point to VOL1's IMPID BR 160$ ; Check for BUP-initialized HDR1 or EOF1 label CHKBUP: MOV #,R1 ;Point to tape buffer IMPID 160$: MOV #IMPID,R0 ;Point to DECRT11BUP in static area, MOV #10.,R3 ;check 10 characters CALL STRNCM ;Is it BUP initialized? BCS 170$ TSTB GIV.B ; NON-BUP tape allowed? BPL BADFMT ; if not, report NOT BACKUP VOLUME 170$: RETURN ...... .DSABL LSB .SBTTL CHKSTA - Check status of tape ;+ ; This routine will check that the tape has a valid RT11 directory ; (following ANSI). It checks the VOL and HDR label. If the directory ; is not valid then the user is prompted to initialize the volume. ; If it is a valid directory it is check to see if files exist. This ; is informed to the user which then decides if he still wants to ; initialize. ;- .ENABL LSB CHKSTA: TSTB GIV.Y ;/NOQUERY? BMI INJMP ; then go do it. (TINIT ; will REWIND anyway) TSTB GIV.Z ;/INITIALIZE? BPL INJMP ; if not, skip this stuff. CALL REWCHK ;Rewind magtape BCC 10$ JMP ABORET ;Failed. abort. 10$: MOV #LBLBUF,R1 ;R1 -> vol label buffer CLR TEMP1 ;Clear error indicator CALL READMT ;Read a record BCC 20$ ;Branch if no error CMP #EM.SML,LKBLK ;Check for short record BEQ 20$ ;Yes, branch INC TEMP1 ; Indicate read error ; Hard error is inmaterial to initialization of tape. ; Check more the cause of the error to see if is fatal to continue. 20$: TST TEMP1 ;Read error? BNE ASKINI ; If so, don't check VOL1 MOV #LBLBUF,R1 ;R1 -> vol label buffer CMP #MT.VOL,@R1 ;Vol1 label? BNE ASKINI ;No, branch (not rt) 30$: MOV #LBLBUF,R1 ;Read buffer for label CALL READMT ;Read a record BCC 40$ ;Branch if no error CMP #EM.SML,LKBLK ;Check for short record BNE ASKINI ;No. read error. Initialize. ; Check more about cause of error if fatal to continue. ; again the error should not interfere with initialization. 40$: CMP #MT.HDR,@R1 ; HDR1 label? BNE 30$ ; Read another record ADD #AH1.SN,R1 ; Point to sequence number MOV #4,R0 ; Look for '0000' 50$: CMPB #'0,(R1)+ ; Zero? BNE FEXIST ; No, branch DEC R0 BGT 50$ BR ASKINI ; Branch to init ; Indicate files exist FEXIST: TSTB GIV.Y ; /NOQUERY? BMI INJMP .ERR #ERRARE,#VCF,LEVEL=WARNING,RETURN=YES ASKINI: TSTB GIV.Y ; /NOQUERY? BMI INJMP 60$: MOV #INIDEV,R1 CALL ANSWRP ; Continue? YES or NO? BMI 60$ ; Neither, branch repeat BEQ ABORET ; branch if NO. Fall if YES INJMP: TST (PC)+ ; Skip next, clear carry ABORET: SEC ; Return not done. RETURN ...... .DSABL LSB .SBTTL TCOPY - the BACKUP operation ;+ ; Transfer disk blocks to tape using a double buffering scheme. ; The number of 8-block chunks is predetermined (NUMSPF), and ; the variable RBLOCK contains an equivalent number of disk blocks. ;- .ENABL LSB TCOPY: MOV NUMSPF,-(SP) ; Save number of .SPFUNS MOV RBLOCK,-(SP) ; Save block chunk MOV SPFBUF,R1 ; addr of buffer 1 MOV BUFADD,BFA2 ; addr of buffer 2 SAMTAP: TST BLKCOP ; Are any left at all? BNE 10$ JMP TEND ; BLKCOP = 0; done. ; Adjust RBLOCK down if the number of blocks remaining to copy is less ; than what it specifies. 10$: CMP RBLOCK,BLKCOP ; Are blk left less than usual? BLOS 20$ ; No, branch CALL ADJUST ; Adjust NUMSPF - spfuns to issue MOV BLKCOP,RBLOCK ; last time through - fewer blocks. ; READ data blocks from disk 20$: .DBTP1 INBLK,MSG8 MOV INBLK,R2 ; Starting block MOV RBLOCK,R3 ; blocks to read SWAB R3 ; get wordcount MOV R1,-(SP) CALL GINBLK ; Read input blocks MOV (SP)+,R1 ADD RBLOCK,INBLK ; Update input block .WAIT TAPCHA ; Wait for tape writes BCS ABORT ; Abort on tape write error TST REABAD ; Did GINBLK run into trouble? BNE ABORTI ; If so, quit early. ; Get ready for magtape block output 30$: MOV R1,R2 ; Magtape output buffer address MOV BFA2,R1 ; Switch buffer pointers MOV R2,BFA2 ; WRITE a bunch of mag tape blocks (NUMSPF) MOV NUMSPF,R4 ; do this many 40$: .DBTP1 NXTBLK,MSG5 JSR R5,RWVMT ; Write Magtape Data Block .WORD SF.MWR ; Write code BCC 50$ ; Continue on success ; Problem encountered on tape output. EOT or error? CALL TEOT ; Is error due to end of tape? INC EOTFLG ; Yes. Set EOT flag .WAIT TAPCHA ; Wait for write to complete BR 40$ ; and try it again! (MS specific?) 50$: .IF NE DEBUG ADD #TBLOCK,NXTBLK ; update Next-Blk-Needed .ENDC INC BSEQNO ; Increment blk sequence no. ADD #TREC,R2 ; advance buffer pointer DEC R4 ; Count one spfun BNE 40$ ; Loop till done ; Tape records are written. Update variables and go read some more ; from the disk. 60$: SUB RBLOCK,BLKCOP ; Update number of blks to copy BEQ TEND ; If no more, get out. TST EOTFLG ; was EOT reached above? BNE TNEXT ; if so, change volumes. JMP SAMTAP ; Go keep copying on same tape ; End of saveset TEND: MOV #1,TCDONE ; Indicate good done. BR 70$ ; Abort BACKUP due to INPUT errors. Report errors but try to ; write EOF records and tapemarks so that tape is left useful. ABORTI: .ERR #ERRARE,#RE2,LEVEL=FATAL,RETURN=YES,FILE=#INFIL MOV #-1,TCDONE ; Finish tape volume 70$: .WAIT TAPCHA ; Wait for writes CALL WREOF ; Go write * EOF1EOF2 * * * .DBTYP #MSG6 ; (Debugging message only) BR TCOUT ; Abort BACKUP due to OUTPUT errors ABORT: ; .TYPE1 LKBLK,OUTERR ; debug only .ERR #ERRARE,#WR2,LEVEL=FATAL,RETURN=YES,FILE=#OUTFIL ;;;<-F-OUTPUT ERROR > MOV #-1.,TCDONE ; Signify error BR TCOUT ; Prepare for next tape volume. ; Finish current volume by writing EOV labels and tape marks. TNEXT: .WAIT TAPCHA CALL TAPMRK ; THIS ONE WILL NOT WRITE - CLEARS ERR CMP INBLK,#72. ; Did we not get a complete BHI 90$ ; set of directory blocks output? ; CALL BSPFIL ; Then almost start over. 80$: CALL BACKSP ; Backspace records until BIT #TS.EOF,TPSTAT ; tapemark hit. (BSPFIL doesn't BEQ 80$ ; work on MM when past EOT) CALL FORWSP ; Move forward over tapemark, CALL FORWSP ; (leave one data block) MOV #TBLOCK,R0 MOV FILSIZ,BLKCOP SUB R0,BLKCOP MOV R0,INBLK ; Fix control variables for next tape. .IF NE DEBUG MOV #1.,NXTBLK .ENDC ; Write final TM, EOV's, TM,TM 90$: CALL WREOV ; Write EOV & tapemarks *EOV1EOV2*** TST APENDD ; 1st file on tape? BEQ 110$ ; If so, rewind will take care of it. CALL BAKUP ; Otherwise, back over *EOV1EOV2*** 110$: INC FSECNO ; Next section number CLR TCDONE ; Signify NOT DONE TCOUT: MOV (SP)+,RBLOCK ; RESTORE BLOCK CHUNK MOV (SP)+,NUMSPF ; RESTORE SPFUNS RETURN ...... BAKUP: MOV #6,R2 ; Backspace over 3 tapemarks, 120$: CALL BACKSP ; the EOF2, EOF1, and tapemark. DEC R2 BGT 120$ RETURN ...... .DSABL LSB .SBTTL TEOT - Check for end of tape ;+ ; When an error results from writing to tape, it is checked to see ; if is an end of tape error. This means we have reached the end ; of a tape and we need a new one. If the error is something else ; the program is aborted. ;- .ENABL LSB TEOT: TSTB @#$ERRBY ;Is it zero? BNE 10$ ;No, branch CMP #EM.EOT,LKBLK ;Was it end of tape? BNE 10$ ;No, branch RETURN ;Yes, return. ...... 10$: MOV #WR2,R1 ;<-F-Output error > JMP FATALO ...... .DSABL LSB .SBTTL TINIT - INITIALIZE THE TAPE ;+ ; The VOL and HDR labels are initialized to the information at the ; prototypes VOL and HDR labels at the end of this module. ;- .ENABL LSB TINIT: CALL REWCHK ;Rewind magtape with check. BCS 40$ ;Failed. 'Wants to quit. .IF NE AUTOLB CMP VOLNUM,#1 ; If creating new volume past 1st, BEQ 10$ ; (branch if first volume of backup) MOV #TMPFMT,R0 ; format the volume number into MOV VOLNUM,R1 ; the VOL1 label (VMS compatible) MOV R1,R2 ; non-zero Z-SUP FLAG CALL $CBDMG ; Convert binary to unsigned decimal JSR R5,STRNCP ; copy to last 2 chars of vol label .WORD VLABEL+4 ; destination: LABLnn .WORD TMPFMT+3 ; source: 000xx .WORD 2 10$: .ENDC CALL SVOL1 ; setup VOL1 record CALL WRITLB ; write label BCS 30$ ; Branch if error FINIT: ; File init entry point CLR BSEQNO ; INIT block seq no. CALL SHDR1 ; Save bup inform for header CALL WRITLB ; write label BCS 30$ ; Branch if error BIT #A$GRP,OPTACT ; INIT only? BNE 20$ ; If so, don't do HDR2 CALL SHDR2 ; Setup HDR2 CALL WRITLB ; write label BCS 30$ ; Branch if error 20$: CALLR ONETM ; Write tape mark ...... 30$: .ERR #ERRARE,#WR2,LEVEL=ERROR,RETURN=YES,FILE=#OUTFIL ;;;<-E-Output error Mxx:file.ext> 40$: SEC ; Indicate error RETURN ; Write label record WRITLB: MOV R3,R1 ; R1 -> vol label buffer CALLR MTWR80 ; Write 80 char label ...... .DSABL LSB .SBTTL SETHOM - Put information in VOL, HDR, EOV and EOF labels ;+ ; This routine is in charge of loading the prototype VOL and HDR label ; information into the buffer which will be written to tape. ; ; R0 -> Prototype information ; R3 -> Buffer address ; ; CALL SETHOM ;- .ENABL LSB SETHOM: MOV (R0)+,R1 ; R1 = size of data to move MOV (R0)+,R2 ; R2 = offset from start label ADD R3,R2 ; Point to place to load data 10$: MOVB (R0)+,(R2)+ ; Move a byte SOB R1,10$ ; Loop RETURN ...... .DSABL LSB .SBTTL TYPE1 - Display a one-line message with decimal value ;+ ; Display a one-line message with a decimal value ; ; JSR R5,TYPE1 ; .WORD messag ; message address ; .WORD valadr ; value's address ;- .ENABL LSB TYPE1: MOV R0,-(SP) MOV R2,-(SP) MOV R4,-(SP) MOV (R5)+,R0 .PRINT R0 ; print the message part MOV @(R5)+,R2 CALL DECIMA ; convert and display value .PRINT #CRLF ; do carriage-return MOV (SP)+,R4 MOV (SP)+,R2 MOV (SP)+,R0 RTS R5 ...... .DSABL LSB .SBTTL SVOL1-SHDR1 - Initialize VOL, HDR, EOV, and EOF labels ;+ ; The information obtained from the input device and the BUP specific ; information is loaded into the buffer to be written to tape at this ; point. ;- .ENABL LSB SVOL1: CALL CLRHDR ; Clear out buffer JSR R5,STRNCP ; copy 6 char File Set ID .WORD VLABEL ; destination .WORD FSETID ; source .WORD 6. MOV #VOL1,R0 ; R0 -> info for vol label CALL SETHOM ; Put info in buffer MOV #VOL11,R0 ; R0 -> more vol label CALL SETHOM ; Put it too MOV #VOL12,R0 ; R0 -> more CALL SETHOM ; Put it JSR R5,STRNCP ; Move copy of Implementation ID .WORD LBLBUF+AV1.II ; to appropriate VOL1 buffer .WORD IMPID .WORD 13. RETURN ...... .SBTTL SHDR1 - Setup HDR1 record SHDR1: MOV R0,-(SP) ; Save pointer to label ID, CALL CLRHDR ; Clear out header buffer MOV #OUTNAM,R2 ; Move backup set name MOV #HMTFIL,R1 ; Destination string BIT #A$GRP,OPTACT ; INIT only? BEQ 10$ ; If not, branch. MOV #ZNAME,R2 ; If so, use ZEROED.ZZZ string CLR FSEQNO ; and clear the sequence number 10$: MOV #6,R0 20$: CMPB @R2,#40 ; Name char blank? BEQ 30$ ; Squeeze them out. MOVB @R2,(R1)+ 30$: INC R2 DEC R0 BGT 20$ MOVB #'.,(R1)+ ; Store period, then extension MOVB (R2)+,(R1)+ ; of three characters MOVB (R2)+,(R1)+ MOVB (R2)+,(R1)+ 40$: CMP R1,#FSETID ; At end of field? BHIS 50$ MOVB #40,(R1)+ ; if not, pad with blanks BR 40$ ; Convert file sequence number, file section number, and block sequence ; numbr to decimal values with leading zeros. Store them in the HDR1 ; prototype buffer. 50$: MOV #FSQNP-1,R0 ; File sequence number position MOV FSEQNO,R1 MOV #1,R2 ; non-zero Z-SUP FLAG CALL $CBDMG ; Convert binary to unsigned decimal CALL ANSDAT ; Get ANSI compatible date string MOV #BSQNP,R0 ; Use block seq no. position MOV FSECNO,R1 ; because it's 6 chars long. CALL $CBDMG ; Cvt File sect no. to decimal JSR R5,STRNCP ; Move to its proper place .WORD FSCNP .WORD BSQNP+1 .WORD 4. MOV #BSQNP+1,R0 ; Block seq no position MOV BSEQNO,R1 ; Convert block seq no. CALL $CBDMG ; Convert binary to unsigned decimal ; Now, move the prototype buffer to the label buffer MOV #LBLBUF,R3 ; Get buffer address, (again) MOV #HDR1,R0 ; R0-> HDR1 label BR RETHDR ...... .SBTTL SHDR2 - Setup HDR2 record SHDR2: MOV R0,-(SP) ; Save R0 CALL CLRHDR ; Clear it out, MOV #"00,AH2.OL(R3) ; Store "offset length" field MOV R3,R0 ADD #AH2.SZ+3,R0 ; Point to char no. 20. MOV FILSIZ,R1 CALL $CBDMG ; store file size in decimal MOV #'0,R1 ; grab a zero MOV R3,R0 ; get address of buffer, ADD #AH2.SZ,R0 ; point to size field MOVB R1,(R0)+ ; 0 nnnnn MOVB R1,(R0)+ ; 00 nnnnn MOVB R1,(R0)+ ; 000nnnnn ADD #5.,R0 MOVB R1,(R0)+ ; 000nnnnn0 MOVB R1,(R0)+ ; 000nnnnn00 MOVB R1,(R0)+ ; Point to char no. 28. MOV INBLK,R1 CALL $CBDMG ; store starting block in decimal ; 000nnnnn000mmmmm MOV #HDR2,R0 ; point to HDR2 stuff RETHDR: CALL SETHOM ; Put stuff into buffer MOV (SP)+,R0 ; Get pointer to label ID RETURN ...... ;Setup EOV1 record SEOV1: MOV #EOV1,R0 ; EOV2 label info BR SETH1 ;Setup EOV2 record SEOV2: MOV #EOV2,R0 ; EOV2 label info BR SETH2 ;Setup EOF1 record SEOF1: MOV #EOF1,R0 ; EOF1 label info SETH1: CALL SHDR1 ; Start with HDR1 format, BR SETALL ;Setup EOF2 record SEOF2: MOV #EOF2,R0 ; EOF2 label info SETH2: CALL SHDR2 ; Start with HDR2 format, SETALL: CALLR SETHOM ; Store it on buffer ...... ; Clear header buffer with blanks CLRHDR: MOV #LBLBUF,R1 ; Get buffer address, MOV R1,R3 ; Save for WRITE SPFUNs MOV #512.,R0 ; Size of hdr label buff 60$: MOVB #40,(R1)+ ; Store blanks SOB R0,60$ ; Until all buffer is full RETURN .DSABL LSB .SBTTL ANSDAT - Assemble ANSI-compatible date string ;+ ; Convert an RT-11 date into CYYDDD notation for ANSI label ;- .ENABL LSB ; R0 through R5 are destroyed ANSDAT: MOV #IDBLK,R5 ; Point to IDATE arg block MOV #IDATE,R0 CALL CALL$F ; call IDATE MOV YEARVL,R2 ; let R2 = Year (72-199) MOV MONVAL,R1 ASL R1 ; let R1 = MONTH * 2 MOV #MONTAB,R4 ADD R1,R4 ; point to month entry MOV @R4,R3 ; R3=NUMBER OF DAYS TO FIRST OF MONTH CMP R1,#<2*2> ; IS MONTH = JANUARY OR FEBRUARY? BLE 10$ ; YES-NO LEAP YEAR YET BIT #3,R2 ; IF NOT DIVIS BY 4, THEN LEAP YEAR BNE 10$ ; AND THERE IS EXTRA DAY INC R3 10$: ADD DAYVAL,R3 ; Add today's date to other months CMP R2,#100. ; 21st century? BLT 20$ ; branch if not. MOVB #'0,CENTUR ; insert ANSI tape 21st Century SUB #100.,R2 ; adjust year for 2-digit conversion 20$: MOV R2,-(SP) ; save year, MOV #CDATE,R0 ; Use date position MOV R3,R1 ; Convert days this year MOV #1,R2 ; Want leading zeros CALL $CBDMG ; Convert binary to 5 chars decimal MOV #BSQNP+1,R0 ; Use Block seq no position MOV (SP)+,R1 ; to convert year. CALL $CBDMG ; Convert it to 5 characters MOV #BSQNP+4,R0 ; Dip into Block seq no position MOV #CDATE,R1 ; point to destination MOVB (R0)+,(R1)+ ; Get the two year characters MOVB (R0)+,(R1)+ RETURN .DSABL LSB .SBTTL TVCOPY - the VERIFY operation ;+ ; Verify a backup saveset section ;- .ENABL LSB TVCOPY: MOV NUMSPF,-(SP) MOV RBLOCK,-(SP) MOV SPFBUF,R2 ;R2-> addr of SPFUN buffer MOV BUFADD,R3 ;R3-> addr of read buffer CLR ENDTAP ; Clear EOT/F flag SAMT: MOV NUMSPF,R1 ;R1 = number of SPFUNs issue .DBTP1 BLKCOP,MSG14 ;debug message CMP RBLOCK,BLKCOP ;Are blk left less than usual? BLOS 10$ ;No, branch TST BLKCOP ;Are any left at all? BEQ TTEND ;No, branch to end CALL ADJUST ;Adjust SPFUNs to issue MOV NUMSPF,R1 ;R1 = number of SPFUNs MOV BLKCOP,RBLOCK ;New blocks ; READ Disk blocks... 10$: MOV R1,-(SP) ; save SPFUN count-down MOV R2,-(SP) ; save tape buff address MOV R3,-(SP) ; save disk buffer address MOV R3,R1 ; R1 = buffer address MOV INBLK,R2 ; R2 = starting block MOV RBLOCK,R3 ; blocks to read SWAB R3 ; R3 = wordcount CALL GINBLK ; Read input blocks MOV (SP)+,R3 ; retain disk buff address MOV (SP)+,R2 ; restore tape buff address MOV (SP)+,R1 ; restore SPFUN count-down ; READ magtape blocks... ADD RBLOCK,INBLK ; Update input block CLR BLKCNT ; clear BLOCKS-FOUND counter 40$: .SPFUN #EMTARE,TAPCHA,#SF.MRD,R2,#TWNCT,#LKBLK,#0 ;READ/WAIT BCC 80$ ;Branch if no error ; Test for END-OF-FILE and hard errors after READ operation TSTB @#$ERRBY ;Is it zero? BEQ 60$ ;If not, Hard error. 50$: MOV #RE2,R1 ;<-F-Input error > JMP FATALO ...... TTEND: MOV (SP)+,RBLOCK ; Normal RETURN exit from TVCOPY MOV (SP)+,NUMSPF RETURN ...... 60$: MOV LKBLK,R0 ; Get .SPFUN status DEC R0 ; Was it end of file? (=1) BEQ 70$ ; Yes, branch DEC R0 ; Was it end of tape alone? (=2) BEQ 80$ ; Yes, branch - that's ok. DEC R0 ; Was it end of file with eot? (=3) BNE 50$ ; If not it's something weird. ; Else, fall to EOF handling. ; TAPEMARK has been encountered. 70$: INC ENDTAP .DBTYP #MSG12 BR 100$ ; exit from read loop ...... ; Good block read. Account for it. 80$: ADD #TBLOCK,BLKCNT ; Accumulate BLOCK count DEC R1 ; Count one spfun BEQ 100$ ; Branch if finished ADD #TREC,R2 ; R2 -> start of next buffer BR 40$ ; Go issue another SPFUN ; The tape and disk blocks have been read... ; BLKCNT contains the equivalent number of 256-word blocks ; read from mag tape. If it is zero, EOF was found. If it ; is greater than BLKCOP, then there is excess info. The ; number of valid data blocks is put into RBLOCK for the ; VERIFY routine. It then compares the appropriate number ; of words with the disk buffer. 100$: MOV BLKCNT,R2 ; Anything to verify? BEQ TTEND ; If not, get out. .DBTP1 BLKCNT,MSG13 MOV RBLOCK,-(SP) ; keep old RBLOCK for later... MOV R2,RBLOCK ; let RBLOCK = BLKCNT CMP R2,BLKCOP ; if (RBLOCK < BLKCOP) ok BLOS 110$ MOV BLKCOP,RBLOCK ; else, let RBLOCK = BLKCOP; 110$: MOV SPFBUF,R2 ; Reset buffer pointer ; Verify the data, restore the original value of RBLOCK, reduce ; BLKCOP by it. If the end of tape was reached in the last go-round, ; stop now. Otherwise, continue. CALL VERIFY ; go verify write MOV (SP)+,RBLOCK SUB RBLOCK,BLKCOP ;Update number of blks to vfy TST ENDTAP ; End of tape encountered? BNE TTEND ; If so, return from TVCOPY. JMP SAMT ; Otherwise, continue. .DSABL LSB .SBTTL VERIFY - Verify the buffer contents ;+ ; Test contents of DISK and TAPE buffers against one another ;- .ENABL LSB VERIFY: JSR R5,$SAVR1 ; Save registers MOV R2,INBUF ; Save buffer addresses MOV R3,OUTBUF CLR R4 ; Use R4 as block counter 10$: CMP R4,RBLOCK ; For I=0,RBLOCK BLT 20$ RETURN ...... 20$: MOV INBUF,R2 MOV OUTBUF,R3 MOV R4,R1 ; Create block offset into buffers SWAB R1 ; make word count ASL R1 ; make byte count ADD R1,R2 ADD R1,R3 MOV #256.,R1 ; One block at a time, 30$: CMP (R2)+,(R3)+ ; compare each word... BEQ 40$ ; Mismatch found... MOV INBLK,R1 ; get block number SUB RBLOCK,R1 ; (roll back to starting block) ADD R4,R1 ; add in the current one, MOV R1,TEMP ; store for TYPE1 .TYPE1 TEMP,VERMES ; print error message, INC VBAD ; count bad verify. CMP VBAD,..MBAD ; too many bad verifies ? BLO 50$ ; NO, go on to next block MOV #MIS,R1 ; Give TOO MANY MISMATCHES error JMP FATAL ...... 40$: SOB R1,30$ ; next word 50$: INC R4 ; next block BR 10$ .DSABL LSB .SBTTL PREVER - PRE-VERify code ;+ ; Rewind/backspace tape in preparation for a verify scan. ;- .ENABL LSB PREVER: MOV R1,-(SP) ; save register TST APENDD ; Is this file appended? BEQ 10$ ; branch if not to rewind CALL SETST1 ; Turn ON Streaming (TS05) CALL BAKUP ; Back over *EOF1EOF2*** MOV BSEQNO,R3 ; while backspacing. INC R3 ; one more than written CALL BACKSN ; backspace blocks CALL CLESTR ; Turn OFF Streaming BR 20$ 10$: CALL REWIND ; No. Rewind to BOT .WAIT TAPCHA 20$: CALL FSPFIL ; Move over the (VOL1, HDRn) TM MOV (SP)+,R1 ; restore register RETURN .DSABL LSB .SBTTL ADJUST - Calculate the SPFUNs to issue on a new wordcount ;+ ; When the blocks left to read are smaller that the initial chunks of data ; read from tape, then the SPFUNs to be issued to write to tape are adjusted, ; and also the chunks to be read. ;- .ENABL LSB ADJUST: SUB #TBLOCK,RBLOCK ; Reduce by one tape record CMP BLKCOP,RBLOCK ; Still more than required? BHI 20$ ; No, branch DEC NUMSPF ; Reduce number of SPFUNs BR ADJUST ; Repeat ...... .SBTTL ADJST2 - Calculate the lost information from EOT detection ;+ ; The number of SPFUNs left to be issued are subracted from the original count ; and this equal the number of SPFUNs that were issued so far. This is used ; to correct the input block to were the next read will be issued. ;- ADJST2: MOV NUMSPF,R2 ; R2 = total number of SPFUNs SUB RBLOCK,INBLK ; Original before last read SUB R1,R2 ; R1 = SPFUNs issued so far BEQ 20$ ; Return if need to repeat all 10$: ADD #TBLOCK,INBLK ; Adjust input blocks... SUB #TBLOCK,BLKCOP ; and blocks copied so far SOB R2,10$ ; by SPFUNS issued so far 20$: RETURN ...... .DSABL LSB .SBTTL WREOF - Write EOF labels and tape marks ;+ ; Write EOF (End of saveset) labels and tape marks. ;- .ENABL LSB WREOF: CALL TAPMRK ; Write one tape mark CALL SEOF1 ; Setup EOF1 record CALL WRITLB ; write it CALL SEOF2 ; Setup EOF2 record CALL WRITLB ; write it BR THRETM ; write tapemarks ...... .SBTTL WREOV - Write EOV labels and tape marks ;+ ; Write END_OF_VOLUME labels and tapemarks. This happens when there ; is more data to back up and an additional tape volume must be used. ;- WREOV: CALL TAPMRK ; EOV1 - Write tape mark, CALL SEOV1 ; Setup EOV1, CALL WRITLB ; write it, CALL SEOV2 ; Setup EOV2, CALL WRITLB ; write it, .BR THRETM ; go write tape marks. THRETM: CALL TAPMRK ; Define LEOT TWOTM: CALL TAPMRK ; by writing 2 tapemarks plus spare. ONETM: .BR TAPMRK ; Write tape mark TAPMRK: MOV #TAPCHA,R2 ; One tape mark CALLR WTMRK ; use routine in BUPSUB ...... .DSABL LSB .SBTTL LABELS - VOL1 and HDR data ;+ ; VOL1 label data ;- .PSECT MT1DAT,D .NLIST BEX ZNAME: .ASCII /ZEROEDZZZ/ ; Init file name TMPFMT: .BLKB 6 ; Temporary format buffer .EVEN ; -------------------------------------------------------------------- .SBTTL VOL1 definition ; -------------------------------------------------------------------- VOL1: .WORD VOL11-VOL1-4,0 VO: .ASCII /VOL1/ ; Label ID and Number VLABEL: .ASCII /xxxxxx/ ; Volume ID (copied from FSETID) .EVEN VOL11: .WORD VOL12-VOL11-4,37. ..OWNR::.ASCII / / ; Owner ID .EVEN VOL12: .WORD EVOL-VOL12-4,79. .ASCII /4/ ; Label Standard Version .EVEN EVOL: ; -------------------------------------------------------------------- .SBTTL HDR1 definition ; Most of HDR1 is applicable to EOF1, and EOV1 ; -------------------------------------------------------------------- HDR1: .WORD EHDR1-HDR1-4,0 HD: .ASCII /HDR1/ HMTFIL: .ASCII / / ; File ID ..VOLU:: FSETID: .ASCII /RTBUP / ; File Set ID FSCNP: .ASCII /0001/ ; File Section Number FSQNP: .ASCII /0001/ ; File Sequence Number .ASCII /0001/ ; Generation Number .ASCII /00/ ; Generation Version Number CENTUR: .ASCII / / ; Start of date; blnk==20th cent. CDATE: .ASCII / / ; RT-11 date (supposed to be year) JDAY: .ASCII /000/ ; Remainder of date (day of year) EDATE: .ASCII / 00000/ ; Expiration Date FACCES: .ASCII / / ; File accessibility BSQNP: .ASCII /000000/ ; Block count IMPID: .ASCII /DECRT11BUP/ ; Implementation ID IMPVID: ; .ASCII /560/ ; Implementation ID (BUP version no.) .BYTE ; RT-11 release number (5) .BYTE <<.BUP/10.>+'0> .BYTE <.BUP-<<.BUP/10.>*10.>+'0> V1RFS: .ASCII / / ; Reserved area EHDR1: .EVEN ; -------------------------------------------------------------------- .SBTTL HDR2 definition ; Most of HDR2 is applicable to EOF2 and EOV2 as well. ; -------------------------------------------------------------------- HDR2: .WORD EHDR2-HDR2-4,0 .ASCII /HDR2/ .ASCII /F/ ; fixed-length records .ASCII /04096/ ; block length .ASCII /00512/ ; record length EHDR2: .EVEN ; -------------------------------------------------------------------- .SBTTL EOF1, EOF2, EOV1, EOV2 pieces ; -------------------------------------------------------------------- EOF1: .WORD EEOF1-EOF1-4,0 EO: .ASCII /EOF1/ EEOF1: .EVEN ; -------------------------------------------------------------------- EOF2: .WORD EEOF2-EOF2-4,0 .ASCII /EOF2/ EEOF2: .EVEN ; -------------------------------------------------------------------- EOV1: .WORD EEOV1-EOV1-4,0 .ASCII /EOV1/ EEOV1: .EVEN ; -------------------------------------------------------------------- EOV2: .WORD EEOV2-EOV2-4,0 .ASCII /EOV2/ EEOV2: .EVEN ; -------------------------------------------------------------------- .END