.TITLE PCDRIVER - VAX/VMS PAPER TAPE READER/PUNCH DRIVER  .IDENT /V06/  (; 2; COPYRIGHT (C) 1979 <; DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS. F; P; THE INFORMATION IN THIS SOFTWARE IS SUBJECT TO CHANGE WITHOUT Z; NOTICE AND SHOULD NOT BE CONSTRUED AS A COMMITMENT BY DIGITAL d; EQUIPMENT CORPORATION. n; x; DEC ASSUMES NO RESPONSIBILITY FOR THE USE OR RELIABILITY OF ITS ; SOFTWARE ON EQUIPMENT THAT IS NOT SUPPLIED BY DEC. ; ;++ ; ; FACILITY: ; ; VAX/VMS Paper Tape Reader/Punch Driver ; ; ABSTRACT: ; ; This driver controls the PC11 paper tape reader/punch. READ and ; WRITE QIOs are accepted (VBLK, LBLK, AND PBLK), as are MOUNT, ; ACPCONTROL, and WRITEOF QIOs (which call on the ACP -- PCACP). ; MODIFY, DELETE, and DEACCESS QIOs are valid for the punch, ; as are CREATE and READPROMPT QIOs (valid for both reader/punch). ; "; READVBLK and READLBLK cause characters to be read from the ,; reader with leading null bytes ignored (for the first read 6; request); READPBLK is the same, except that leading null bytes @; are treated as data characters. An EOF byte is recognized if J; the user requested looking for EOF (default if not physical). T; ^; WRITEVBLK and WRITELBLK cause characters to be punched (a h; header and trailer of null bytes is punched--default is to r; punch NULL_BYTES null bytes in the header and trailer tape). |; WRITEPBLK is the same, except that no header/trailer is punched. ; If first QIO wasn't physical, an EOF is punched before trailer. ; ; The MOUNT QIO is used to synchronize with the ACPMNT program ; which loads the paper tape punch ACP (PCACP). The ACPCONTROL ; QIO is a no-op function which serves to awaken the ACP if it is ; hibernating. The WRITEOF QIO is turned into an equivalent ; WRITEVBLK QIO by the ACP. ; ; The MODIFY QIO changes the default (NULL_BYTES) number of null ; bytes to punch in the header/trailer tape. P2 specifies the ; new number of null bytes to be punched. ; ; The DELETE QIO restores the default (NULL_BYTES) number of null ; bytes to punch in the header/trailer tape. ; ; The DEACCESS QIO returns the current number of null bytes which &; are to be punched for the header/trailer tape in the high order 0; longword of the IOSB specified in the QIO call. :; D; The CREATE QIO is used to enable searching for an EOF byte (for N; the reader), or to enable the punching of an EOF byte (for the X; punch). b; l; The READPROMPT QIO is used to disable searching for an EOF byte v; (for the reader), or to disable the punching of an EOF byte (for ; the punch). ; ; When used, P1 is the starting address of the buffer, and P2 is ; the buffer length. The driver performs buffered I/O. ; ; An EOF character is equal to a decimal 26 (control-Z). ; ; Note that the ACP (PCACP) is not required for the driver to ; work. PCDRIVER may be loaded and used independent of the ACP. ; The ACP's main function is to serve as an instructional tool ; showing how ACPs are written; the ACP does not provide any ; added functionality for either the reader or punch. ; ; AUTHOR: ; ; VIK MUIZNIEKS -- JULY 1979 ; *;-- 4 .SBTTL External and local symbol definitions > .PAGE H; R; External symbols \; f $CRBDEF ; Channel request block p $VCBDEF ; Volume control block z $DCDEF ; Device classes and types  $DDBDEF ; Device data block  $DEVDEF ; Device characteristics  $EMBDEF ; Error logging fields(not in template)  $IDBDEF ; Interrupt data block  $IODEF ; I/O function codes  $IPLDEF ; Hardware IPL definitions  $IRPDEF ; I/O request packet  $SSDEF ; System status codes  $UCBDEF ; Unit control block  $VECDEF ; Interrupt vector block   ; ; Argument list (AP) offsets for device-dependent QIO parameters ; (Only P1 and P2 are used in this driver) ; $ .P1 = 0 ; First QIO parameter 8P2 = 4 ; Second QIO parameter BP3 = 8 ; Third QIO parameter LP4 = 12 ; Fourth QIO parameter VP5 = 16 ; Fifth QIO parameter `P6 = 20 ; Sixth QIO parameter j; t; Other constants ~;  LOOP_CNT=15 ; before issuing off-line msg. SHORT_WAIT=2 ; # sec for device to go online BUF_OVR_HD=12 ; system buffer overhead PT_TIMEOUT_SEC=10 ; 10 second device timeout PT_NUM_REGS=2 ; Each device has 2 registers MY_CLASS=252 ; My own device class number MY_TYPE=200 ; My own device type number ERBFSIZE=12 ; Size of err. log buf. in bytes NULL=0 ; null byte EOF=26 ; EOF byte = control-Z NULL_BYTES=50 ; for header/trailer PUNCH_HDR=1 ; bit pos. flagging  ; header/trailer punched START=4 ; mask for punch. hdr. END=16 ; mask for punch. trail. (PNCH=8 ; flag-->punch op. perf. (mask) 2RD_HDR=32 ; flag-->read hdr. tape (mask) <STARTING=7 ; bit pos.--> 1st operation FFRST_QIO=6 ; flag-->read 1st header (pos.) PBIT0=1 ; mask-->EOF byte handling ZBIT8=256 ; mask-->EOF byte handling dBIT9=512 ; mask-->EOF byte handling n .PAGE x; ; Definitions that follow the standard UCB fields ;  $DEFINI UCB ; Start of UCB definitions   .=UCB$L_DPC+4 ; Position at end of error log  ; extension to UCB $DEF UCB$L_SAV_R4 .BLKL 1 ; copy of R4 for CANCEL routine  $DEF UCB$W_PT_PPS .BLKW 1 ; copy of status reg. (err. log)  $DEF UCB$B_PT_OFLCNT .BLKB 1 ; Off-line counter  $DEF UCB$B_PT_PPB .BLKB 1 ; Copy of data reg. for err. log  $DEF UCB$W_MY_REFCNT .BLKW 1 ; Counter for channels assigned  "$DEF UCB$K_PT_UCBLEN ; Length of extended UCB , 6 $DEFEND UCB ; End of UCB definitions @; J; Device register offsets from CSR address T; ^ $DEFINI PT ; Start of status definitions h r$DEF PT_PRS ; reader Control/status register | .BLKW 1 ; ; Bit positions for device control/status registers ;  _VIELD PT_CSR,0,<- ; Control/status register  ,- ; Reader enable bit  <,5>,- ; Skip five bits  ,- ; Reader interrupt enable bit  ,- ; Reader done bit  <,3>,- ; Skip three bits  ,- ; Reader busy bit  <,3>,- ; Skip three bits  ,- ; Reader error bit  > $DEF PT_PRB ; reader data register  .BLKW 1 $DEF PT_PPS ; Punch Control/status register & .BLKW 1 0 _VIELD PT_STS,0,<- ; Control/status register : <,6>,- ; disregard bits D ,- ; interrupt enable N ,- ; device ready bit X <,7>,- ; disregard bits b ,- ; device error bit l > v$DEF PT_PPB ; Punch data register  .BLKW 1  $DEFEND PT ; End of device register  ; definitions.  .SBTTL Standard tables  .PAGE  ; ; Driver prologue table ;   DPTAB - ; DPT-creation macro  END=PT_END,- ; End of driver label  ADAPTER=UBA,- ; Adapter type  UCBSIZE=,- ; Length of UCB  NAME=PCDRIVER ; Driver name  DPT_STORE INIT ; Start of load  ; initialization table * DPT_STORE UCB,UCB$B_FIPL,B,8 ; Device fork IPL 4 DPT_STORE UCB,UCB$B_DIPL,B,20 ; Device int. IPL (BR4) > DPT_STORE UCB,UCB$L_DEVCHAR,L,<- ; Device characteristics H DEV$M_AVL!- ; e.g., dev. available R DEV$M_ELG!- ; error logging enabled \ DEV$M_REC!- ; record oriented f DEV$M_IDV!- ; input device-reader p DEV$M_ODV> ; output device-punch z DPT_STORE UCB,UCB$B_DEVCLASS,B,MY_CLASS ; store my device class  DPT_STORE UCB,UCB$B_DEVTYPE,B,MY_TYPE ; Store my device type  DPT_STORE UCB,UCB$W_DEVSTS,W,0 ; Clear all flags  DPT_STORE UCB,UCB$W_DEVBUFSIZ,W,NULL_BYTES ; init. # null bytes   DPT_STORE REINIT ; Start of reload  ; initialization table  DPT_STORE DDB,DDB$L_DDT,D,PC$DDT ; Address of DDT  DPT_STORE CRB,CRB$L_INTD+4,D,- ; Address of reader int.  PR_INTERRUPT ; service routine  DPT_STORE CRB,CRB$L_INTD2+4,D,- ; Address of punch int.  PT_INTERRUPT ; service routine  DPT_STORE CRB,- ; Address of controller  CRB$L_INTD+VEC$L_INITIAL,- ; initialization routine  D,PT_CONTROL_INIT  DPT_STORE CRB,- ; Address of device  CRB$L_INTD+VEC$L_UNITINIT,- ; unit initialization $ D,PT_UNIT_INIT ; routine . DPT_STORE CRB,CRB$L_INTD2+VEC$L_UNITINIT,- ; same for both 8 D,PT_UNIT_INIT ; reader and punch B L DPT_STORE END ; End of initialization V ; tables ` j ; t ; Driver dispatch table ~ ; DDTAB - ; DDT-creation macro DEVNAM=PC,- ; Name of device START=PT_START,- ; Start I/O routine FUNCTB=PT_FUNCTABLE,- ; FDT address CANCEL=PT_CANCEL,- ; Cancel I/O routine REGDMP=PT_REG_DUMP,- ; Register dump routine ERLGBF=ERBFSIZE+EMB$L_DV_REGSAV ; Size of err. log. buf. ; (plus system overhead) ; ; Function dispatch table ; PT_FUNCTABLE: ; FDT for driver FUNCTAB ,- ; Valid I/O functions  ; Write physical FUNCTAB ,- ; Buffered functions ; Write physical 6 FUNCTAB PT_FDT_ROUTINE,- ; FDT write routine for @ ; and write physical. ^ FUNCTAB PR_FDT_ROUTINE,- ; FDT READ routine for h ; and READ physical. FUNCTAB ACP_FDT, ; FDT ACP routines FUNCTAB Q_TO_ACP,- ; Check for ACP FDTs ; WRITE EOF routine FUNCTAB FOR_PNCH,- ; Make sure for punch ; read # null bytes FUNCTAB SET_FDT, ; set # null bytes FUNCTAB +EXE$QIODRVPKT,- ; no more checking ; reading # null bytes  .SBTTL PT_CONTROL_INIT, Controller initialization routine  .PAGE & 0 ;++ : ; PT_CONTROL_INIT, Readies controller for I/O operations D ; N ; Functional description: X ; b ; The operating system calls this routine in 3 places: l ; v ; at system startup ; during driver loading and reloading ; during recovery from a power failure ; ; Inputs: ; ; R4 - address of the CSR (controller status register) ; R5 - address of the IDB (interrupt data block) ; R6 - address of the DDB (device data block) ; R8 - address of the CRB (channel request block) ; ; Outputs: ; ; The routine must preserve all registers except R0-R3.  ; ;--  PT_CONTROL_INIT: ; Initialize controller * RSB ; Return 4 .SBTTL PT_UNIT_INIT, Unit initialization routine > .PAGE H R ;++ \ ; PT_UNIT_INIT, Readies unit for I/O operations f ; p ; Functional description: z ; ; The operating system calls this routine after calling the ; controller initialization routine: ; ; at system startup ; during driver loading ; during recovery from a power failure ; ; When using the SYSGEN CONNECT command, the reader is ; connected first (as PC0:), and the punch is connected ; second (as PC1:). The initialization routine sets both ; units on-line, and clears the appropriate device ; characteristics bit (i.e., punch does only output oper- ; ations, reader does only input operations). Two UCBs ; are used so that operations can be overlapped on the ; reader and punch. No controller channel is ever requested ; (with REQPCHAN) since the PC11 reader/punch is essentially $; two independent devices in one box, and no controller is .; really present. (Therefore operations may occur on both 8; the reader and the punch at the same time.) B; L; Inputs: V; `; R4 - address of the CSR (controller status register) j; R5 - address of the UCB (unit control block) t; ~; Outputs: ; ; The routine must preserve all registers except R0-R3. ; ;--  PT_UNIT_INIT: ; Initialize unit  BISW #UCB$M_ONLINE,UCB$W_STS(R5) ; SET UNIT ONLINE  MOVW UCB$W_UNIT(R5),R0 ; GET UNIT #  TSTW R0 ; IS UNIT # 0?  BEQL 10$ ; IF SO, READER  BICL #DEV$M_IDV,UCB$L_DEVCHAR(R5) ; NO INPUT IF PUNCH  BRB 20$ 10$: BICL #DEV$M_ODV,UCB$L_DEVCHAR(R5) ; NO OUTPUT IF READER 20$: RSB ; Return  .SBTTL PT_FDT_ROUTINE, Punch FDT routine  .PAGE ( 2;++ <; PT_FDT_ROUTINE, Punch FDT routine F; P; Functional description: Z; d; This FDT routine makes all the standard accessibility checks n; for buffered I/O operations, allocates a buffer from system x; pool, and copies the user data to be punched to the system ; buffer. The standard IRP and PCB fields are updated. In the ; case of a WRITEOF function code, the IRP is queued to the ACP. ; The routine makes sure that the punch UCB is being ; referenced by the user. ; ; Inputs: ; ; R0-R2 - scratch registers ; R3 - address of the IRP (I/O request packet) ; R4 - address of the PCB (process control block) ; R5 - address of the UCB (unit control block) ; R6 - address of the CCB (channel control block) ; R7 - bit number of the I/O function code ; R8 - address of the FDT table entry for this routine ; R9-R11 - scratch registers ; AP - address of the 1st function dependent QIO parameter "; ,; Outputs: 6; @; The routine must preserve all registers except R0-R2, and J; R9-R11. T; ^;-- h rPT_FDT_ROUTINE: ; Punch FDT routine ala CRDRIVER | MOVL #SS$_ILLIOFUNC,R0 ; ASSUME WRONG UCB  BBS #DEV$V_ODV,UCB$L_DEVCHAR(R5),5$ ; CHECK FOR PUNCH UCB  JMP G^EXE$ABORTIO ; ERROR IF NOT 5$: MOVL P1(AP),R0 ; GET ADD. OF BUFFER  MOVZWL P2(AP),R1 ; GET LENGTH OF BUFFER  BEQL 10$ ; ZERO LENGTH TRANSFER?  JSB G^EXE$WRITECHK ; CHECK ACCESS OF USER  ; BUFFER -- NO RETURN IF  ; NO ACCESSIBILITY  MOVW R1,IRP$W_BCNT(R3) ; SAVE USER BUFFER LEN.  PUSHR #^M ; SAVE REGISTERS  ADDL2 #BUF_OVR_HD,R1 ; ACCOUNT FOR OVERHEAD  JSB G^EXE$BUFFRQUOTA ; CHECK BUFFER QUOTA  BLBC R0,20$ ; ABORT IF INSUFFICIENT  JSB G^EXE$ALLOCBUF ; ALLOCATE SYSTEM BUFFER  BLBC R0,20$ ; ABORT ON FAILURE  POPR #^M ; RESTORE REGISTERS & MOVL R2,IRP$L_SVAPTE(R3) ; STORE RETURNED BUF ADD 0 MOVW R1,IRP$W_BOFF(R3) ; AND BYTE QUOTA CHARGED : SUBW2 R1,PCB$W_BYTCNT(R4) ; CHARGE PROCESS FOR BUF D PUSHR #^M ; SAVE REG.'S FOR MOVC3 N ADDL3 #BUF_OVR_HD,R2,R3 ; FIND SYSTEM DATA AREA X MOVL R3,(R2)+ ; SAVE ITS ADDRESS b MOVL R0,(R2) ; SAVE USER BUFFER ADD. l SUBL2 #BUF_OVR_HD,R1 ; SET TRANSFER LENGTH v MOVC3 R1,(R0),(R3) ; COPY USER BUFFER TO  ; SYSTEM DATA BUFFER  POPR #^M ; RESTORE REG.'S  MOVW IRP$W_FUNC(R3),R9 ; GET FUNCTION CODE  CMPZV S^#IO$V_FCODE,S^#IO$S_FCODE,R9,-; SEE IF WRITEOF QIO  S^#IO$_WRITEOF ; IF SO,  BEQL TO_ACP ; QUEUE IRP TO ACP  JMP G^EXE$QIODRVPKT ; QUEUE DRIVER PACKET  ; FDT ROUTINE DONE  ; ; ENTERED ON ZERO-LENGTH TRANSFER OR ALLOCATION FAILURE ; 10$: MOVZWL #SS$_NORMAL,R0 ; NORMAL COMPLETION  JMP G^EXE$FINISHIOC ; GOTO FINISH I/O 20$: POPR #^M ; CLEAN UP STACK  JMP G^EXE$ABORTIO ; QUOTA OR BUFFER  ; ALLOCATION FAILURE * .SBTTL ACP_FDT ACP QIO FDT Routine 4 .PAGE >;++ H; ACP_FDT, ACP QIO FDT routine R; \; Functional description: f; p; This FDT routine increments the transaction count in the VCB, z; and queues the IRP to the paper tape ACP (PCACP). It is ; used for the MOUNT QIO. MOUNT privilege is required to ; successfully issue the MOUNT QIO request. ; ; Entry point Q_TO_ACP is used to service both the WRITEOF and ; ACPCONTROL QIOs. Control is re-transferred to TO_ACP from ; routine PT_FDT_ROUTINE in the case of a WRITEOF QIO. ; ; No check is made on the punch or reader UCB, since ; requests for ACP operation will find the errors. ; ; Inputs: ; ; R0-R2 - scratch registers ; R3 - address of the IRP (I/O request packet) ; R4 - address of the PCB (process control block) ; R5 - address of the UCB (unit control block) $; R6 - address of the CCB (channel control block) .; R7 - bit number of the I/O function code 8; R8 - address of the FDT table entry for this routine B; R9-R11 - scratch registers L; AP - address of the 1st function dependent QIO parameter V; `; Outputs: j; t; The routine must preserve all registers except R0-R2, and ~; R9-R11. ; ;--  ACP_FDT: ; MOUNT QIO ISSUED  MOVZWL #SS$_NOPRIV,R0 ; ASSUME INSUF. PRIV.  IFNPRIV MOUNT,NO_PRIV ; HAVE MOUNT PRIVILEGE?  BBCC #UCB$V_MOUNTING,UCB$W_STS(R5),NT_MNT ; IF CLR, NOT SYNC.  BRB Q_TO_ACP ; YES, CONTINUE NT_MNT: MOVZWL #SS$_DEVNOTMOUNT,R0 ; NOT MOUNTING STATUS NO_PRIV:JMP G^EXE$ABORTIO ; SIGNAL ERROR Q_TO_ACP: ; IRP REQUEST OKAY  MOVL UCB$L_VCB(R5),R0 ; GET VCB ADDRESS  BEQL NT_MNT ; IS ACP MOUNTED?  CMPZV S^#IO$V_FCODE,S^#IO$S_FCODE,- ; CHECK FOR WRITEOF  IRP$W_FUNC(R3),S^#IO$_WRITEOF ; FUNCTION CODE  BNEQ NT_WRT ; IF NEQ, Q TO ACP ( BRW PT_FDT_ROUTINE ; IF EQL, WRITEOF 2TO_ACP: MOVL UCB$L_VCB(R5),R0 ; RESTORE VCB ADDRESS <NT_WRT: SETIPL #IPL$_SYNCH ; SYNCH. ACCESS TO VCB F INCW VCB$W_TRANS(R0) ; INCREMENT TRANS. COUNT P JMP G^EXE$QIOACPPKT ; QUEUE IRP TO ACP Z .SBTTL NULL_BYTES FDT Routines for header/trailer d .PAGE n; x; FDT ROUTINES FOR PROCESSING MODIFY, DELETE, AND DEACCESS ; QIOS. VERY SIMILAR, AND VERY SIMPLE. ; FOR_PNCH: ; HAVE PUNCH UCB?  MOVL #SS$_ILLIOFUNC,R0 ; ASSUME NOT  BBS #DEV$V_ODV,UCB$L_DEVCHAR(R5),5$ ; CHECK FOR PUNCH  JMP G^EXE$ABORTIO ; NOT PUNCH UCB 5$: MOVL #SS$_NORMAL,R0 ; HAVE PUNCH  RSB ; RETURN TO FDT TABLE SET_FDT: ; GET # NULL BYTES  MOVZWL P2(AP),IRP$L_MEDIA(R3) ; STORE # OF NULL BYTES  JMP G^EXE$QIODRVPKT ; SYNCHRONIZE WITH OTHER  ; I/O REQUESTS FOR UNIT  .SBTTL PR_FDT_ROUTINE Reader FDT Routine  .PAGE ;++ ; PR_FDT_ROUTINE, READER FDT routine "; ,; Functional description: 6; @; This FDT routine makes all the standard accessibility checks J; for buffered I/O operations, and allocates a buffer from system T; pool (into which the data will be read). ^; The standard IRP and PCB fields are updated. h; A check is made to determine if the reader UCB is being r; referenced. |; Inputs: ; R0-R2 - scratch registers ; R3 - address of the IRP (I/O request packet) ; R4 - address of the PCB (process control block) ; R5 - address of the UCB (unit control block) ; R6 - address of the CCB (channel control block) ; R7 - bit number of the I/O function code ; R8 - address of the FDT table entry for this routine ; R9-R11 - scratch registers ; AP - address of the 1st function dependent QIO parameter ; Outputs: ; The routine must preserve all registers except R0-R2, and ; R9-R11. ;-- PR_FDT_ROUTINE: ; reader FDTroutine ala CRDRIVER  MOVL #SS$_ILLIOFUNC,R0 ; ASSUME WRONG UCB  BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),5$ ; TEST FOR READER UCB & JMP G^EXE$ABORTIO ; ERROR IF NOT 05$: MOVL P1(AP),R0 ; GET ADD. OF BUFFER : MOVZWL P2(AP),R1 ; GET LENGTH OF BUFFER D BEQL 10$ ; ZERO LENGTH TRANSFER? N JSB G^EXE$READCHK ; CHECK ACCESS OF USER X ; BUFFER -- NO RETURN IF b ; NO ACCESSIBILITY l MOVW R1,IRP$W_BCNT(R3) ; SAVE USER BUFFER LEN. v PUSHR #^M ; SAVE REGISTERS  ADDL2 #BUF_OVR_HD,R1 ; ACCOUNT FOR OVERHEAD  JSB G^EXE$BUFFRQUOTA ; CHECK BUFFER QUOTA  BLBC R0,20$ ; ABORT IF INSUFFICIENT  JSB G^EXE$ALLOCBUF ; ALLOCATE SYSTEM BUFFER  BLBC R0,20$ ; ABORT ON FAILURE  POPR #^M ; RESTORE REGISTERS  MOVL R2,IRP$L_SVAPTE(R3) ; STORE RETURNED BUF ADD  MOVW R1,IRP$W_BOFF(R3) ; AND BYTE QUOTA CHARGED  SUBW2 R1,PCB$W_BYTCNT(R4) ; CHARGE PROCESS FOR BUF  MOVAB BUF_OVR_HD(R2),(R2)+ ; SAVE DATA AREA ADD.  MOVL R0,(R2) ; SAVE USER BUFFER ADD.  JMP G^EXE$QIODRVPKT ; QUEUE DRIVER PACKET ; ENTERED ON ZERO-LENGTH TRANSFER OR ALLOCATION FAILURE 10$: MOVZWL #SS$_NORMAL,R0 ; NORMAL COMPLETION  JMP G^EXE$FINISHIOC ; GOTO FINISH I/O 20$: POPR #^M ; CLEAN UP STACK  JMP G^EXE$ABORTIO ; QUOTA OR BUFFER * ; ALLOCATION FAILURE 4 .SBTTL PT_START, Start I/O routine > .PAGE H R; \; ENTER HERE AT THE START OF AN I/O OPERATION. THE FIRST STEP f; IS TO DETERMINE WHAT I/O FUNCTION CODE WAS SPECIFIED IN THE p; QIO BEING SERVICED. z; PT_START: ; DET. FUNC. REQ.  BBSC #UCB$V_POWER,UCB$W_STS(R5),1$ ; MAKE SURE BIT CLEAR 1$: MOVW IRP$W_FUNC(R3),UCB$W_FUNC(R5) ; ALLOW INHIBIT OF ERROR  ; LOGGING VIA MODIFIERS  CMPZV #IRP$V_FCODE,#IRP$S_FCODE,- ; LOOK FOR MODIFY QIO  IRP$W_FUNC(R3),#IO$_MODIFY  BEQL 10$ ; FOUND IF EQL  CMPZV #IRP$V_FCODE,#IRP$S_FCODE,- ; LOOK FOR DEACCESS QIO  IRP$W_FUNC(R3),#IO$_DEACCESS  BEQL 20$ ; FOUND IF EQL  CMPZV #IRP$V_FCODE,#IRP$S_FCODE,- ; LOOK FOR DELETE QIO  IRP$W_FUNC(R3),#IO$_DELETE  BEQL 3$ ; FOUND IF EQL  CMPZV #IRP$V_FCODE,#IRP$S_FCODE,- ; LOOK FOR CREATE QIO  IRP$W_FUNC(R3),#IO$_CREATE  BEQL 30$ ; FOUND IF EQL $ CMPZV #IRP$V_FCODE,#IRP$S_FCODE,- ; LOOK FOR READPROMPT . IRP$W_FUNC(R3),#IO$_READPROMPT ; QIO 8 BNEQ 100$ ; READ/WRITE IF NEQ B BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),2$ ; READER? DSABLE--> SET L25$: BICW #BIT0,UCB$W_DEVSTS(R5) ; ENABLE FUNCTION V BISW #BIT8,UCB$W_DEVSTS(R5) ; MARK ENABLE FOR READ PHYS. ` BRB 5$ ; ALL DONE j30$: BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),25$; READER? ENABLE-->CLR t2$: BISW #BIT0!BIT9,UCB$W_DEVSTS(R5) ; DISABLE FUNCTION ~ BRB 5$ ; ALL DONE 3$: MOVW #NULL_BYTES,UCB$W_DEVBUFSIZ(R5) ; RESET # OF NULL BYTES 5$: CLRL R1 ; NO DEV. DEP. INFO. 7$: MOVL #SS$_NORMAL,R0 ; SUCCESSFUL COMPLETION  REQCOM ; ALL DONE 10$: MOVW IRP$L_MEDIA(R3),UCB$W_DEVBUFSIZ(R5) ; SET # NULL BYTES  BRB 5$ ; AND FINISH UP 20$: MOVZWL UCB$W_DEVBUFSIZ(R5),R1 ; READ # NULL BYTES  BRB 7$ ; AND FINISH UP 100$: BBC #IRP$V_FUNC,IRP$W_STS(R3),PT_PUNCH ; WRITE IF CLEAR  BRW PR_START ; OTHERWISE, READ FUNC  .SBTTL PT_PUNCH, Start a punch operation  .PAGE ;++ ; PT_PUNCH - Start a punch operation ; ; Functional description: (; 2; The punch interrupt enable bit is set. One character at a <; time (from the system buffer pointed to by UCB$L_SVAPTE) is F; moved to the punch's data buffer, and an interrupt is awaited. P; If powerfail occurs, the entire operation is retried (if it is Z; the first QIO for the user); otherwise, the operation is aborted d; (unless the powerfail occurs while punching the trailer, in n; which case the entire trailer may not be punched). In the case x; of an aborted punch, the high-order word of the first longword ; in the IOSB will contain the number of bytes punched before the ; powerfail occurred (error code = SS$_TAPEPOSLOST). ; ; A counter is kept on the number of bytes left to be punched ; (UCB$W_BCNT). When this counter goes to zero, the request ; is complete. ; ; In the case of a virtual or logical I/O operation ; a header of UCB$W_DEVBUFSIZ null bytes is punched ; before the actual data is punched; similarly a trailer ; tape (of UCB$W_DEVBUFSIZ null bytes) is punched when the ; channel to the punch is deassigned/deallocated by the ; user (in the cancel I/O routine (PT_CANCEL)). The user can ; suppress the defaults and/or punching an EOF byte (cntrl-Z). ; ; Inputs: "; R3 - address of the IRP (I/O request packet) ,; R5 - address of the UCB (unit control block) 6; Outputs: @; R0 - 1st longword of I/O status: contains status code and J; number of bytes transferred T; R1 - 2nd longword of I/O status: device-dependent ^; h; The routine must preserve all registers except R0-R2 and R4. r;-- |PT_PUNCH: ; Process an I/O packet  BICW #END,UCB$W_DEVSTS(R5) ; NOT PUNCHING TRAILER  MOVQ IRP$L_SVAPTE(R3),UCB$L_SVAPTE(R5); NOTE QUAD TRANSFER  ; FOR POWERFAIL RECOVERY  ADDL2 #BUF_OVR_HD,UCB$L_SVAPTE(R5) ; SKIP SYS BUF HEADER PNCH_HDR: ; TRAILER PUNCH ENTRY PT  .ENABL LSB  MOVL UCB$L_CRB(R5),R0 ; GET CRB  MOVL @CRB$L_INTD+VEC$L_IDB(R0),R4 ; GET CSR ADDRESS  BISW #PT_STS_M_IE,PT_PPS(R4) ; SET INT. ENABLE BIT   BBSS #PUNCH_HDR,UCB$W_DEVSTS(R5),5$ ; HDR ALREADY PNCHD?  MOVW UCB$W_REFC(R5),UCB$W_MY_REFCNT(R5) ; SAVE REFERENCE COUNT  BRB 10$ ; NO - PUNCH HEADER 5$: BRW MAINLP ; PUNCH DATA 10$: BITW #END,UCB$W_DEVSTS(R5) ; PUNCHING TRAILER?  BNEQ 12$ ; YES, IF NEQ & MOVW IRP$W_FUNC(R3),R0 ; GET FUNCTION CODE 0 CMPZV S^#IO$V_FCODE,S^#IO$S_FCODE,R0,-; NO HEADER PUNCHED FOR : S^#IO$_WRITEPBLK ; PHYSICAL I/O FUNC. D BNEQ 11$ ; NOT PHYS. IF NEQ N BITW #BIT9,UCB$W_DEVSTS(R5) ; WANT TRAILER BYTE? X BEQL 8$ ; NO, IF EQL b BISW #BIT0,UCB$W_DEVSTS(R5) ; MARK WANT TRAILER l8$: BRW MAINLP ; SKIP HEADER PUNCHING v11$: BISW #PNCH!BIT0!START,UCB$W_DEVSTS(R5) ; SET FLAG BITS  BITW #BIT8,UCB$W_DEVSTS(R5) ; NO EOF BYTE?  BEQL 12$ ; NO, IF EQL  BICW #BIT0,UCB$W_DEVSTS(R5) ; NO EOF BYTE, IF NEQ 12$: MOVZWL UCB$W_DEVBUFSIZ(R5),UCB$L_DEVDEPEND(R5); SET # NULLBYTES  BITW #END,UCB$W_DEVSTS(R5) ; PUNCHING TRAILER?  BEQL NUL ; NO, IF EQL  BITW #BIT0,UCB$W_DEVSTS(R5) ; PUNCH EOF BYTE?  BEQL NUL ; NO IF EQL  INCL UCB$L_DEVDEPEND(R5) ; ONE EXTRA BYTE PNCHD. PUNEOF: MOVB #EOF,UCB$B_PT_PPB(R5) ; SAVE FOR ERROR LOG.  DSBINT ; RAISE TO POWERFAIL  BBSC #UCB$V_POWER,UCB$W_STS(R5),20$ ; CHECK FOR POWERFAIL  MOVB #EOF,PT_PPB(R4) ; PUNCH EOF BYTE  BRB WAIT ; WAIT FOR INTERRUPT NUL: MOVB #NULL,UCB$B_PT_PPB(R5) ; SAVE FOR ERR. LOG. NULLP: DSBINT ; NO INTERRUPTS  BBSC #UCB$V_POWER,UCB$W_STS(R5),20$ ; CHECK FOR POWERFAIL * MOVB #NULL,PT_PPB(R4) ; PUNCH NULL BYTE 4WAIT: WFIKPCH 25$,#PT_TIMEOUT_SEC ; WAIT FOR I/O COMP. >; H; ENTER HERE AFTER INTERRUPT SERVICE ROUTINE R; \ BRW AFTINT ; CHECK FOR ERRORS fBACK: DECL UCB$L_DEVDEPEND(R5) ; DEC NULL BYTE COUNT p BNEQ NULLP ; LOOP IF MORE TO PUNCH z BICW #START,UCB$W_DEVSTS(R5) ; CLEAR HDR. PUNCH FLAG  BITW #END,UCB$W_DEVSTS(R5) ; PUNCHING HEADER?  BEQL MAINLP ; YES IF EQL  BRW INCAN ; RETURN FOR TRAILER 20$: ; POWERFAIL RECOVERY  ENBINT ; ALLOW INTERRUPTS  BBSC #PUNCH_HDR,UCB$W_DEVSTS(R5),22$ ; CLEAR HDR. PNCHD FLAG 22$: BITW #END,UCB$W_DEVSTS(R5) ; HEADER OR TRAILER?  BEQL 23$ ; HEADER IF EQL  MOVL UCB$L_IRP(R5),R3 ; RETRIEVE IRP ADDRESS  BRW PNCH_HDR ; RETRY PUNCHING TRAILER 23$: BRW POW_FAIL ; RETRY PUNCHING HEADER  ; AFTER POWERFAIL RECOV. 25$: BITW #END,UCB$W_DEVSTS(R5) ; HEADER OR TRAILER?  BEQL 30$ ; HEADER IF EQUAL  RSB ; RETURN IF TRAILER 30$: BBSC #PUNCH_HDR,UCB$W_DEVSTS(R5),35$ ; REPORT TIMEOUT $35$: BRW PT_TIMEOUT ; MAKE SURE FLAG CLEAR . .DSABL LSB 8MAINLP: BBC #UCB$V_CANCEL,UCB$W_STS(R5),1$ ; CHECK FOR $CANCEL B BRW CANCEL ; $CANCEL IF SET L1$: DSBINT UCB$B_DIPL(R5) ; NO DEVICE INTERRUPTS V MOVB @UCB$L_SVAPTE(R5),UCB$B_PT_PPB(R5) ; SAVE DATA FOR ERR. ` ; LOG BUF. DUMP ROUTINE j SETIPL #IPL$_POWER ; RAISE TO POWERFAIL t BBSC #UCB$V_POWER,UCB$W_STS(R5),PT_RESTART ; POWERFAIL? ~ MOVB @UCB$L_SVAPTE(R5),PT_PPB(R4) ; LOAD PUNCH DATA BUFFER  WFIKPCH PT_TIMEOUT,#PT_TIMEOUT_SEC ; 10 SEC. TIMEOUT ; ; Enter here from interrupt service routine (PT_INTERRUPT) ; AFTINT: MOVW PT_PPS(R4),UCB$W_PT_PPS(R5) ; READ CSR (SAVE FOR  ; ERROR LOGGING LATER)  IOFORK ; RETURN TO FORK LEVEL  BITW #PT_STS_M_READY,UCB$W_PT_PPS(R5); PUNCH READY AGAIN?  BEQL PT_ERROR ; IF SO, ERROR  BITW #PT_STS_M_ERROR,UCB$W_PT_PPS(R5); ERROR DURING PUNCH?  BNEQ PT_ERROR ; YES, REPORT IT  BITW #START,UCB$W_DEVSTS(R5) ; PUNCHING USER DATA?  BEQL 10$ ; YES, IF EQL  BRW BACK ; PUNCHING HEADER/TRALR 10$: INCL UCB$L_SVAPTE(R5) ; POINT TO NEXT BYTE TO  ; BE PUNCHED ( DECW UCB$W_BCNT(R5) ; DECREMENT BYTE COUNT 2 BNEQ MAINLP ; ALL DONE? < BICW #PT_STS_M_IE,PT_PPS(R4) ; CLEAR INT. ENABLE BIT F BBCS #STARTING,UCB$W_DEVSTS(R5),FINISH ; PUNCHED >= 1 OPER. Z; After a transfer completes successfully, return the number of bytes d; transferred and a success status code. xFINISH: INSV IRP$W_BCNT(R3),#16,- ; Load number of bytes trans-  #16,R0 ; ferred into high word of R0.  MOVW #SS$_NORMAL,R0 ; Load a success code into R0. ; ; Call I/O postprocessing. ; COMPLETE_IO: ; Driver processing is finished.  BICW #RD_HDR,UCB$W_DEVSTS(R5); MAKE SURE READER FLAG CLEAR  CLRL R1 ; No device dependent information  REQCOM ; Complete I/O. ; ; RECOVER FROM POWERFAIL BY RETRYING ENTIRE OPERATION (FOR PUNCH) ; IF POWERFAIL OCCURRED ON FIRST QIO REQUEST FROM USER. ; PT_RESTART: ; POWERFAIL ENTRY POINT  ENBINT ; ALLOW INTERRUPTS (pop IPL) POW_FAIL: ; ENTER AFTER TIMEOUT " BBS #STARTING,UCB$W_DEVSTS(R5),POWER_FAIL ; NO RECOVERY IF , ; NOT PUNCHING 1ST REC. 6 MOVL UCB$L_IRP(R5),R3 ; RETRIEVE IRP ADDRESS @ BBSC #PUNCH_HDR,UCB$W_DEVSTS(R5),1$ ; CLEAR HEADER PUNCHED BIT J1$: BRW PT_PUNCH ; AND RETRY OPERATION ^; NO RECOVERY POSSIBLE FROM READER POWERFAIL; TELL USER HOW MANY h; BYTES READ BEFORE POWERFAIL OCCURRED. ALSO, NO RECOVERY FROM r; PUNCH IF NOT PUNCHING 1ST QIO REQUEST FOR THIS USER. TELL USER |; HOW MANY BYTES WERE PUNCHED BEFORE POWERFAIL OCCURRED. PR_POWFAIL: ; POWERFAIL ENTRY POINT  ENBINT ; ALLOW INTERRUPTS (pop IPL) POWER_FAIL: ; ENTER AFTER TIMEOUT  BSBW SETOFF ; CLEAR INT. ENABLE BIT  ; NOTE THAT A BSB-RSB SEQUENCE CAN BE USED SINCE  ; THE SUBROUTINE WILL NOT CALL ANY SYSTEM MACROS  ; OR ROUTINES (WHICH WOULD CAUSE UNPREDICTABLE  ; RESULTS WHEN CONTROL WOULD BE RETURNED TO THE  ; CALLER'S CALLER)  SUBW2 UCB$W_BCNT(R5),IRP$W_BCNT(R3) ; RECORD BYTES READ/PUN.  INSV IRP$W_BCNT(R3),#16,#16,R0 ; FOR STATUS RETURN  MOVW #SS$_TAPEPOSLOST,R0 ; RETURN STATUS  BRB COMPLETE_IO ; COMPLETE I/O  ;  ; DEVICE ERROR HAS OCCURRED -- SIGNAL VIA SS$_DRVERR & ; ERROR CODE 0 ; : PT_ERROR: ; ERROR HANDLING D BSBW SETOFF ; CLEAR INTERRUPT ENABLE BIT N JSB G^ERL$DEVICERR ; REPORT DEVICE ERROR X MOVZWL #SS$_DRVERR,R0 ; RETURN ERROR STATUS b SUBW2 UCB$W_BCNT(R5),IRP$W_BCNT(R3) ; RECORD BYTES READ/PUN. l INSV IRP$W_BCNT(R3),#16,#16,R0 ; FOR STATUS RETURN v BRB COMPLETE_IO ; CALL I/O POSTPROCESSING ; ; ASSUME THAT "NO MORE TAPE IN READER" IS ERROR GENERATED, AND ; TELL USER HOW MANY BYTES WERE READ BEFORE ERROR WAS ENCOUNTERED ; IN CASE P2 PARAMETER SPECIFIED MORE BYTES THAN WERE READ. ; PR_SPERR: ; ENTERED IF NO TAPE IN READER, ; READER OFF-LINE AFTER AT LEAST ; ONE PREVIOUS CHARACTER READ, ; OR NO POWER TO READER BSBW SETOFF ; CLEAR INT. ENABLE BIT SUBW2 UCB$W_BCNT(R5),IRP$W_BCNT(R3) ; STORE NUM BYTES READ INSV IRP$W_BCNT(R3),#16,#16,R0 ; IN RETURN STATUS MOVW #SS$_ENDOFFILE,R0 ; SET RETURN STATUS CODE BBCS #PUNCH_HDR,UCB$W_DEVSTS(R5),DON ; SPECIAL CASE FOR $COPY ; SO THAT READING WILL END ON END ! ; OF FILE (COPY ISSUES 2ND READ) !DON: BRW COMPLETE_IO ; COMPLETE I/O !COPY: MOVL #SS$_ENDOFFILE,R0 ; FUDGE RETURN TO COPY ! BRW COMPLETE_IO ; FINISH OPERATION !; !; Device timeout handling. Return an error status code for punch. !; Send message to operator, and loop until reader is set online. *!; 4!PR_TIMEOUT: ; Timeout handling >! SETIPL UCB$B_FIPL(R5) ; Lower to fork first H! BBSC #UCB$V_POWER,UCB$W_STS(R5),POWER_FAIL ; POWERFAIL? R! BRB COMMON ; ENTER COMMON TIMEOUT CODE \!SKIP2: BRW POW_FAIL ; HANDLE POWERFAIL f!PT_TIMEOUT: ; Timeout handling p! SETIPL UCB$B_FIPL(R5) ; Lower to fork first z! BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),PUN_OT ; READER TIMEOUT? ! BBSC #UCB$V_POWER,UCB$W_STS(R5),SKIP2; POWERFAIL? !COMMON: BBS #UCB$V_CANCEL,UCB$W_STS(R5),CANCEL ; CANCEL I/O? ! BBS #DEV$V_ODV,UCB$L_DEVCHAR(R5),PUN_OT ; PUNCH TIMEOUT? ! BBS #STARTING,UCB$W_DEVSTS(R5),PR_SPERR ; READER EOF ERR? ! ACBB #LOOP_CNT,#1,UCB$B_PT_OFLCNT(R5),MAIN ; RDR-WAIT 30 SEC. ! CLRB UCB$B_PT_OFLCNT(R5) ; CLEAR OFF-LINE COUNTER ! PUSHR #^M ; SAVE REGISTERS ! MOVZBL #MSG$_DEVOFFLIN,R4 ; SET MESSAGE TYPE ! MOVAB G^SYS$GL_OPRMBX,R3 ; GET OPR. MBX. ADDRESS ! JSB G^EXE$SNDEVMSG ; SEND MSG. TO OPR. ! POPR #^M ; RESTORE REGISTERS ! BRW MAIN ; TRY AGAIN !; "; Note that the punch is always assumed to be on-line, and "; an error is recorded if it is not. Also, the I/O request "; is terminated with an error code. (There is no on/off switch $"; for the punch unit on the PC11). The reader does have an ."; on/off switch, and the I/O operation is retried until the 8"; reader unit is set on-line, with a message being sent to B"; the operator's mailbox (console) every 30 seconds informing L"; the operator that the paper-tape reader (PC0:) is off-line. V"; If an error occurs after some data has been read, it is `"; assumed that the error is "no more tape in reader" rather j"; than "reader is off-line". t"; ~"PUN_OT: BBCC #UCB$V_POWER,UCB$W_STS(R5),1$ ; READER POWERFAIL? " BRW POWER_FAIL ; YES, GO REPORT POWERFAIL "1$: BSBW SETOFF ; CLEAR INTERRUPT ENABLE BIT " JSB G^ERL$DEVICTMO ; REPORT TIMEOUT ERROR " MOVZWL #SS$_TIMEOUT,R0 ; Return error status. " SUBW2 UCB$W_BCNT(R5),IRP$W_BCNT(R3) ; RECORD BYTES READ/PUN. " INSV IRP$W_BCNT(R3),#16,#16,R0 ; FOR STATUS RETURN " BRW COMPLETE_IO ; Call I/O postprocessing. "CANCEL: ; HANDLE CANCEL I/O " SUBW2 UCB$W_BCNT(R5),IRP$W_BCNT(R3) ; NUM BYTES READ/PUNCH " INSV IRP$W_BCNT(R3),#16,#16,R0 ; IN RETURN STATUS " MOVW #SS$_CANCEL,R0 ; RETURN CANCEL ERROR STATUS " BRW COMPLETE_IO ; CALL I/O POSTPROCESSING # .SBTTL PR_START, Start I/O routine (Reader) # .PAGE #;++ #; PR_START - Start a reader operation (#; 2#; Functional description: <#; F#; One character at a time (from the system buffer pointed to P#; by UCB$L_SVAPTE) is moved to the reader's data buffer. The Z#; interrupt enable bit is then set, after which powerfail is d#; tested for, and an interrupt is awaited. (If powerfail n#; occurs, the entire operation is aborted.) x#; #; A counter is kept on the number of bytes left to be read #; (UCB$W_BCNT). When this counter goes to zero, the request #; is complete. The request is also considered complete when an #; EOF byte is read, if looking for EOF bytes is enabled. #; #; Before the first character is read (in a virtual or #; logical I/O operation), the tape is first scanned for #; the first non-null character (i.e. the header part of #; the tape is skipped). In the case of a physical I/O #; function, the header null bytes are considered data. #; Inputs: #; R3 - address of the IRP (I/O request packet) $; R5 - address of the UCB (unit control block) $; Outputs: $; R0 - 1st longword of I/O status: contains status code and "$; number of bytes transferred ,$; R1 - 2nd longword of I/O status: device-dependent @$; The routine must preserve all registers except R0-R2 and R4. J$;-- T$PR_START: ; Process an I/O packet V$ BBCC #PUNCH_HDR,UCB$W_DEVSTS(R5),1$ ; SPECIAL CASE FOR $COPY? X$ BRW COPY ; YES, IF BIT SET ^$1$: MOVL @IRP$L_SVAPTE(R3),UCB$L_SVAPTE(R5); GET BUFFER ADDRESS h$ MOVL IRP$W_BCNT(R3),UCB$W_BCNT(R5) ; BYTE COUNT, AND OFFSET r$ CLRB UCB$B_PT_OFLCNT(R5) ; CLEAR OFF-LINE COUNTER |$ MOVW IRP$W_FUNC(R3),R0 ; GET FUNCTION CODE $ BBSS #FRST_QIO,UCB$W_DEVSTS(R5),MAIN ; FIRST QIO? $ MOVW UCB$W_REFC(R5),UCB$W_MY_REFCNT(R5) ; SAVE REFERENCE COUNT $ CMPZV S^#IO$V_FCODE,S^#IO$S_FCODE,- ; NO HEADER READ IF $ R0,S^#IO$_READPBLK ; PHYS. I/O OPERATION $ BEQL FIX ; CONTINUE PROCESSING $ BISW #RD_HDR,UCB$W_DEVSTS(R5) ; UPDATE DEFAULT FLAGS $ BITW #BIT9,UCB$W_DEVSTS(R5) ; DISABLE EOF SEARCH? $ BEQL MAIN ; NO, IF EQL $ BRB DSABL ; YES, IF NEQ $ BRB MAIN $FIX: BITW #BIT8,UCB$W_DEVSTS(R5) ; LOOK FOR EOF BYTES? $ BNEQ MAIN ; LOOK FOR EOF BYTES IF EQL $DSABL: BISW #BIT0,UCB$W_DEVSTS(R5) ; UPDATE DEFAULT %MAIN: DSBINT UCB$B_DIPL(R5) ; NO DEVICE INTERRUPTS % MOVL UCB$L_CRB(R5),R0 ; GET CRB % MOVL @CRB$L_INTD+VEC$L_IDB(R0),R4 ; GET CSR ADDRESS &% BITW #PT_CSR_M_ERROR,PT_PRS(R4) ; READER ON-LINE? 0% BEQL READ ; IF EQL, YES :% WFIKPCH PR_TIMEOUT,#SHORT_WAIT ; NO, SEE IF NOW ON D% IOFORK ; LOWER TO FORK IPL N% BRB MAIN ; CHECK IF ON-LINE X%READ: SETIPL #IPL$_POWER ; RAISE TO POWERFAIL b% BBSC #UCB$V_POWER,UCB$W_STS(R5),30$ ; POWERFAIL? l% BRB GO ; NO, TRY OPERATION v%30$: BRW PR_POWFAIL ; YES--ABORT OPERATION %GO: MOVZBW #PT_CSR_M_IE!PT_CSR_M_RDENA,- ; START READER AND % PT_PRS(R4) ; ENABLE READER INT. % WFIKPCH PT_TIMEOUT,#PT_TIMEOUT_SEC ; 10 SEC. TIMEOUT %; Enter here from interrupt service routine (PR_INTERRUPT) % MOVW PT_PRS(R4),UCB$W_PT_PPS(R5) ; READ CSR (AND STORE % ; FOR ERROR LOGGING) % MOVB PT_PRB(R4),UCB$B_PT_PPB(R5) ; GET DATA READ (ALSO % ; KEEP FOR ERR. LOG.) % IOFORK ; LOWER IPL % BITW #PT_CSR_M_ERROR,UCB$W_PT_PPS(R5); ERROR DURING READ? % BNEQ SKIP1 ; YES, SPECIAL CASE & BITW #PT_CSR_M_BUSY,UCB$W_PT_PPS(R5) ; BUSY BIT SET? & BNEQ SKIP ; IF SO, ERROR & BITW #PT_CSR_M_DONE,UCB$W_PT_PPS(R5) ; DONE BIT SET? & BEQL SKIP ; IF NOT, ERROR *& BBCS #STARTING,UCB$W_DEVSTS(R5),5$ ; READ >= 1 CHAR. 4&5$: BITW #RD_HDR,UCB$W_DEVSTS(R5) ; READING TAPE HEADER? >& BEQL 10$ ; NO, IF EQL H& CMPB #NULL,UCB$B_PT_PPB(R5) ; SEE IF NULL BYTE R& BEQL 15$ ; IF EQL, NULL \& BICW #RD_HDR,UCB$W_DEVSTS(R5) ; NOT READING HEADER NOW f&10$: BITW #BIT0,UCB$W_DEVSTS(R5) ; LOOKING FOR EOF BYTE? p& BNEQ 13$ ; NO, IF NEQ z& CMPB #EOF,UCB$B_PT_PPB(R5) ; EOF BYTE FOUND? & BNEQ 13$ ; NO, IF NEQ & BRW PR_SPERR ; REPORT EOF CONDITION &13$: MOVB UCB$B_PT_PPB(R5),@UCB$L_SVAPTE(R5) ; RECORD DATA READ & INCL UCB$L_SVAPTE(R5) ; POINT TO WHERE NEXT & ; BYTE IS TO BE READ & DECW UCB$W_BCNT(R5) ; DECREMENT BYTE COUNT & BEQL 25$ ; ALL DONE? & BBC #UCB$V_CANCEL,UCB$W_STS(R5),15$ ; CHECK FOR $CANCEL & BRW CANCEL ; $CANCEL IF SET &15$: DSBINT UCB$B_DIPL(R5) ; PUT IPL ON STACK & BRW READ ; READ NEXT CHARACTER &25$: BICW #PT_CSR_M_IE,PT_PRS(R4) ; CLEAR INT. ENABLE BIT & BBSC #STARTING,UCB$W_DEVSTS(R5),30$ ; CLEAR BIT FOR NEXT QIO '30$: BRW FINISH ; AND FINISH UP 'SKIP: BRW PT_ERROR ; NEED WORD OFFSETS 'SKIP1: BBC #STARTING,UCB$W_DEVSTS(R5),40$ ; RETRY IF ASSUME $' ; READER OFF-LINE .' BRW PR_SPERR ; OTHERWISE, ASSUME 8' ; NO MORE TAPE IN READER B'40$: BRW COMMON ; NEED WORD OFFSET L' .SBTTL PT_INTERRUPT, Interrupt service routine V' .PAGE `';++ j'; PT_INTERRUPT, Analyzes interrupts, processes solicited interrupts t'; ~'; Functional description: '; '; This driver is for a multiple-unit controller, and the '; two interrupt service routines (PR_INTERRUPT and PT_INTERRUPT) '; are used to distinguish which unit caused the interrupt. '; Common checking for solicited interrupts occurs after '; entry point INTCOM, where control is returned back to the '; driver after the appropriate WFIKPCH macro. '; '; Inputs: '; '; 0(SP) - pointer to the address of the IDB '; 4(SP) - saved R0 (; 8(SP) - saved R1 (; 12(SP) - saved R2 (; 16(SP) - saved R3 (; 20(SP) - saved R4 ((; 24(SP) - saved R5 2(; 28(SP) - saved PSL (program status longword) <(; 32(SP) - saved PC F(; P(; The IDB contains the CSR address and the UCB address. Z(; d(; Outputs: n(; x(; The routine must preserve all registers except R0-R5. (; (;-- (PT_INTERRUPT: ; Service punch interrupt ( MOVL @(SP)+,R3 ; Get address of IDB and remove ( ; pointer from stack. ( MOVL IDB$L_UCBLST+4(R3),R5 ; PUNCH IS UNIT # 1 (PC1:) ( BRB INTCOM ; GO TO COMMON CODE (PR_INTERRUPT: ; SERVICE READER INTERRUPT ( MOVL @(SP)+,R3 ; GET IDB ADDRESS ( MOVL IDB$L_UCBLST(R3),R5 ; READER IS UNIT # 0 (PC0:) (INTCOM: MOVL IDB$L_CSR(R3),R4 ; Get CSR address ( BBCC #UCB$V_INT,- ; If device does not expect ( UCB$W_STS(R5),- ; interrupt, dismiss it. ) UNSOL_INTERRUPT ); This is a solicited interrupt. Restore control to the main driver. )RESTORE_DRIVER: ; Jump to main driver code. ") MOVL UCB$L_FR3(R5),R3 ; Restore driver's R3 ,) JSB @UCB$L_FPC(R5) ; Call driver at interrupt 6) ; wait address. @); Dismiss the interrupt. J)UNSOL_INTERRUPT: ; Dismiss unsolicited interrupt. T) MOVQ (SP)+,R0 ; Restore R0-R5 ^) MOVQ (SP)+,R2 ; This is faster than a h) MOVQ (SP)+,R4 ; POPR #^M r) REI ; Return from interrupt. |) .SBTTL PT_CANCEL, Cancel I/O routine ) .PAGE ) );++ ); PT_CANCEL, Cancels an I/O operation in progress ); ); Functional description: ); ); This routine tests to see if the punch is being deallocated ); or deassigned by checking the reference count field in the ); UCB. It checks to see if a trailer needs to be punched, ); and if so, then a trailer is punched (possibly with an ); EOF byte). Also, regardless of whether a ); header has been punched, the default number of null bytes to *; punch in a header/trailer is restored to NULL_BYTES. The *; flag indicating that a header has not been punched is cleared *; for the next I/O operation, as is the bit indicating that &*; the current QIO is the first QIO for the user (since the 0*; channel was assigned to the device). Other flags are :*; reset to their initial state for the next user. D*; N*; This routine calls IOC$CANCELIO to set the cancel bit in the X*; UCB status word if: b*; l*; the device is busy, v*; the IRP's process ID matches the cancel process ID, *; the IRP channel matches the cancel channel. *; *; The routine then does device-dependent cancel I/O fixups by *; clearing the interrupt enable bit for either the reader or *; the punch, as appropriate. *; *; Inputs: *; *; R2 - negated value of the channel index number *; R3 - address of the current IRP (I/O request packet) *; R4 - address of the PCB (process control block) for the *; process canceling I/O *; R5 - address of the UCB (unit control block) +; +; Outputs: +; +; The routine must preserve all registers except R0-R3. *+; 4+; The routine sets the UCB$M_CANCEL bit in UCB$W_STS. >+; H+; The routine restores UCB fields to their original state. R+; \+;-- f+ p+PT_CANCEL: ; Cancel an I/O operation z+ .ENABL LSB + CMPW UCB$W_REFC(R5),UCB$W_MY_REFCNT(R5) ; DEAL OR DEASSGN? + BEQL 10$ ; NO, IF EQL + ; NOTE THAT THE COUNT IS NOT DECREMENTED. + ; THEREFORE THE USER WILL NOT GET TWO + ; TRAILERS IF HE ALLOCATES THE DEVICE AND + ; ASSIGNS A CHANNEL; THE DEALLOCATE WILL NOT + ; MATCH THE COUNT FIELD (LIKE A $CANCEL). + MOVL R4,UCB$L_SAV_R4(R5) ; SAVE R4 SINCE NOT CSR + BBSC #FRST_QIO,UCB$W_DEVSTS(R5),3$ ; CLEAR READ HEADER BIT +3$: BITW #PNCH,UCB$W_DEVSTS(R5) ; TRAILER NEEDED? + BNEQ 4$ ; YES, IF NEQ + BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),8$ ; READER?, GO AWAY + BITW #BIT0,UCB$W_DEVSTS(R5) ; USER WANT EOF BYTE? , BEQL 8$ ; NO, IF EQL , MOVZBL #1,UCB$L_DEVDEPEND(R5) ; PUNCHING ONLY EOF BYTE , BISW #END!START,UCB$W_DEVSTS(R5) ; FLAG PUNCHING TRAILER TAPE $, MOVL UCB$L_CRB(R5),R0 ; GET CRB ., MOVL @CRB$L_INTD+VEC$L_IDB(R0),R4 ; GET CSR ADDRESS 8, BISW #PT_STS_M_IE,PT_PPS(R4) ; SET INT. ENABLE BIT B, BRW PUNEOF ; PUNCH EOF BYTE L,4$: BISW #END!START,UCB$W_DEVSTS(R5) ; FLAG PUNCHING TRAILER TAPE V, BBSC #PUNCH_HDR,UCB$W_DEVSTS(R5),5$ ; ENABLE TRAILER PUNCHNG `,5$: BRW PNCH_HDR ; PUNCH TRAILER TAPE j,INCAN: BICW #PNCH,UCB$W_DEVSTS(R5) ; CLEAR FLAG FOR NEXT OPERATION t, MOVL UCB$L_SAV_R4(R5),R4 ; RESTORE R4 IF CHANGED ~,8$: BBSC #PUNCH_HDR,UCB$W_DEVSTS(R5),9$ ; CLEAR FOR NEXT OP. ,9$: BICW #BIT0!BIT8!BIT9!END,UCB$W_DEVSTS(R5) ; CLEAR FOR NEXT USER , MOVW #NULL_BYTES,UCB$W_DEVBUFSIZ(R5) ; RESTORE DEF NULLBYTES , BBSC #STARTING,UCB$W_DEVSTS(R5),10$ ; CLEAR FOR NEXT OPER. ,10$: JSB G^IOC$CANCELIO ; Set cancel bit if appropriate. , BLBC R0,OKAY ; If bit not set, branch. , .DSABL LSB , ,; ,; Device-dependent cancel operations go next. The appropriate int. ena. ,; bit is cleared. This subroutine is called from several timeout and ,; powerfail recovery routines; it must be very careful NOT to issue ,; a macro (or call on a system routine) that returns control to the -; caller's caller (since the stack contains "local" return info). -; -SETOFF: MOVL UCB$L_CRB(R5),R1 ; GET ADDRESS OF CRB - MOVL @CRB$L_INTD+VEC$L_IDB(R1),R1 ; GET ADDRESS OF CSR (- BBS #DEV$V_IDV,UCB$L_DEVCHAR(R5),5$ ; TEST FOR READER 2- BICW #PT_STS_M_IE,PT_PPS(R1) ; TURN OFF PUNCH INT. ENA. BIT <- BRB OKAY ; AND FINISH UP F-5$: BICW #PT_CSR_M_IE,PT_PRS(R1) ; TURN OFF READER INT. ENA. BIT P-OKAY: Z- RSB ; Return d- .SBTTL PT_REG_DUMP, Device register dump routine n- .PAGE x- -;++ -; PT_REG_DUMP, Dumps the contents of device registers to a buffer -; -; Functional description: -; -; Writes the number of device registers, and their current -; contents into a diagnostic or error buffer. Reader and -; punch both have two registers (a status register, and a -; data register). -; -; Inputs: -; -; R0 - address of the output buffer .; R4 - address of the CSR (controller status register) .; R5 - address of the UCB (unit control block) .; ".; Outputs: ,.; 6.; The routine must preserve all registers except R1-R3. @.; J.; The output buffer contains the current contents of the device T.; registers. R0 contains the address of the next empty longword in ^.; the output buffer. h.; r.;-- |. .PT_REG_DUMP: ; Dump device registers . MOVZBL #PT_NUM_REGS,(R0)+ ; STORE DEVICE REGISTER COUNT . MOVZWL UCB$W_PT_PPS(R5),(R0)+ ; STORE STATUS REGISTER . MOVZBL UCB$B_PT_PPB(R5),(R0)+ ; STORE DATA REGISTER . RSB ; Return . .;++ .; Label that marks the end of the driver .;-- . .PT_END: ; Last location in driver . .END