Consolidate license copies
[its.git] / system / nmtape.30
1 ;;; Copyright (c) 1999 Massachusetts Institute of Technology
2 ;;;
3 ;;; This program is free software; you can redistribute it and/or
4 ;;; modify it under the terms of the GNU General Public License as
5 ;;; published by the Free Software Foundation; either version 3 of the
6 ;;; License, or (at your option) any later version.
7 ;;;
8 ;;; This program is distributed in the hope that it will be useful,
9 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
10 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
11 ;;; General Public License for more details.
12 ;;;
13 ;;; You should have received a copy of the GNU General Public License
14 ;;; along with this program; if not, write to the Free Software
15 ;;; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
16
17 ;********************************
18 ;**
19 ;** TO BE DONE:
20 ;**
21 ;** RECORDS LONGER THAN 1K
22 ;** AUTOMATIC DETERMINATION OF DENSITY AND RECORD LENGTH WHEN READING
23 ;** ALLOW CLOSE WHEN TAPE HAS BEEN TAKEN OFF
24 ;** BE MORE FORGIVING OF CONTROLLER LOSSAGE
25 ;** PASS .MTAPE TO JOB DEVICE
26 ;** HAVE AN IGNORE ERRORS SWITCH
27 ;** THIS HORRIBLE BLETCHEROUS IOT CODE SHOULD BE REDESIGNED
28 ;**
29 ;********************************
30
31 ;Do not be deceived by the TM10 conditionals. This file is only good
32 ; for a TM03/RH11 on a KS10. See MTAPE for anything else. Barf.
33
34 IFE TM10A+TM10B+TM03S,.ERR NO MAGTAPE CONTROLLER TYPE SELECTED
35 IFN TM10A,INFORM IO BUSS MAG TAPE,1
36 IFN TM10B,INFORM DATA CHANNEL MAG TAPE,1
37 IFN TM03S,INFORM RH11/TM03 MAG TAPE,1
38
39 IFN TM10P,[
40 $INSRT TM10
41 ]
42 IFN TM03S,[
43 $INSRT TM03S
44 ]
45 $INSRT T20MAC
46
47 MSCBL==8                        ;Command buffer length
48 MGQDLL==10.                     ;PI level PDL length
49 IF2 IFN MNUMB-140600, .ERR IMPLICIT DEPENDENCY ON MNUMB
50 MSEOFP==210100                  ;High bit of MNUMB in MEMBLT is EOF flag
51 MSCHN==140500                   ;Other 5 bits of MNUMB is drive number
52
53 MTXP==410300,,                  ;BP to set/get transport number from IOCHNM
54 MUNITF==170300                  ;BP to set/get unit field in MTC CONI
55
56 IFN TM10P,[
57 ;Tape controller commands
58 MNOPIN==10000                   ;NOP and interrupt when idle
59 MWRITE==4000                    ;Write data
60 MW3IN==14000                    ;Write data and long EOR gap
61 MSPRR==7000                     ;Space in reverse direction
62 MREAD==2000                     ;Read data
63 MSPFR==6000                     ;Space in forward direction
64 MSPFF==16000                    ;Space forward to EOF
65 MSPRF==17000                    ;Space reverse to EOF
66 MREWND==1000                    ;Rewind
67 MRWNDD==11000                   ;Rewind and unload
68 MWEOF==5000                     ;Write EOF mark
69 ]
70
71 MGNRTY==10.                     ;Number of retries on read
72
73 ;Modes in OPEN call
74 ;
75 %MMOUT==1,,0                    ;Open for output, 0=>input
76 %MMBLK==2,,0                    ;Block mode, 0=>unit mode
77 %MMIMG==4,,0                    ;Image mode, 0=>Ascii
78 %MMCNK==10,,0                   ;"Chunk" mode, 0=>stream mode
79 %MMNSE==20,,0                   ;No skip to EOF on close, 0=>do skip
80 %MMEP==40,,0                    ;Even parity, 0=>odd
81 %MMDEN==300,,0                  ;Density select
82                                 ; 00=> "Default" - 1600 for KS/TU77
83                                 ; 01=> 800 BPI
84                                 ; 10=> 1600 BPI
85                                 ; 11=> 6250 BPI
86 %MM32B==400,,0                  ;"IBM" mode, write 8-bit bytes from LH 32 bits
87                                 ; 0=> core dump
88 %MMRSZ==7000,,0                 ;Record Size
89                                 ; Ranging binarily from 0=>1024. to 7=>8. bytes
90
91 \f
92 EBLK
93
94 SUBTTL MAG TAPE STORAGE AREA
95
96 MGVTC:  0                       ;Scratch word for virgin tape check
97 MGJDTI: 0                       ;"Wait for job done" time out value
98 MGNWRD: 0                       ;Number of words read in a PI level read
99 MGTBZY: -1                      ;Flag to get interrupt started
100 MGSFTI: 0                       ;Software interrupt in progress
101 MGUNIT: -1                      ;Unit expecting interrupt
102 MGWCW:  0                       ;"Wait for control word written" flag
103 LMIOWD: 0                       ;Last MIOWD
104
105 MSRAC:  BLOCK NMTCS             ;Transport software status flags
106  %MA==1,,525252
107  %MAEOF==400000                 ;4.9 EOF seen on read - must be 4.9
108  %MAETR==200000                 ;4.8 EOT on internal read
109  %MAETW==100000                 ;4.7 EOT on write
110  %MAERR==040000                 ;4.6 PI level got an error
111  %MARCE==020000                 ;4.5 Read compare error
112  %MACTH==014000                 ;4.4 Core allocator says stop
113                                 ;4.3 "  (WHY 2 BITS?)
114  %MASTP==002000                 ;4.2 Stop read ahead
115  %MANWT==001000                 ;4.1 Nothing written on tape yet
116  %MAEFA==000400                 ;3.9 EOF seen on read-ahead, user hasn't seen
117  %MAESO==000200                 ;3.8 EOF read since open
118  %MAMSO==000100                 ;3.7 Tape moved since first open
119  %MAREW==000040                 ;3.6 "Tape is rewinding" flag
120  %MARAC==000020                 ;3.5 Read active flag
121  %MAMOL==000010                 ;3.4 Transport on line
122  %MAWSW==000004                 ;3.3 Wants software (timing) interrupts
123 MGERRC: BLOCK NMTCS             ;Error count
124 MTCEFW: BLOCK NMTCS             ;Number of EOF's written at close
125 MGEOFR: BLOCK NMTCS             ;Number of EOF's since last read
126 MTPSAV: BLOCK NMTCS             ;Storage to restore P on EOF
127 MSCMDC: REPEAT NMTCS,0          ;Number of commands in command list
128 MGSPCD: BLOCK NMTCS             ;Spacing operation command
129 MGSCNT: BLOCK NMTCS             ;Spacing operation count
130 MGEOTT: BLOCK NMTCS             ;Timeout for detecting virgin tape
131 MSBUFP: REPEAT NMTCS,0          ;Mag tape MP<->PI buffer queue  in,,out
132 MSNBOL: BLOCK NMTCS             ;Number of buffers on list
133 MSCRW:  BLOCK NMTCS             ;R/W flag, -1=>output 0=>input
134 MSMPRC: BLOCK NMTCS             ;Words left in buffer
135 MSMPRP: BLOCK NMTCS             ;Next word in buffer
136 MTMDN:  REPEAT NMTCS,-1         ;Block active at MP
137 MGCABN: REPEAT NMTCS,-1         ;Buffer active at PI level
138 MTUSE:  REPEAT NMTCS,-1         ;Number of channels open on this transport
139 MTUSR:  REPEAT NMTCS,-1         ;User index of transport user
140 MTBLKS: BLOCK NMTCS             ;If write, buffer size
141                                 ;If read, size of last record read
142 MTMFNC: BLOCK NMTCS             ;.MTAPE function storage
143 MTMCNT: BLOCK NMTCS             ;.MTAPE count
144 MTMTAP: BLOCK NMTCS             ;MTAPE call word
145
146 MGCMTS: BLOCK NMTCS             ;PI level status info (CONI MTS or similar)
147 MGCMTC: BLOCK NMTCS             ;PI level controller info (CONI MTC or similar)
148
149  IFN TM10P,[
150 MTCONO: REPEAT NMTCS,\.RPCNT_17+20 ;Prototype CONO word for each transport
151  ]
152  IFN TM03S,[
153 MTSELW: BLOCK NMTCS             ;Select word (TC reg val) for each transport
154  MTSELM==3777                   ;density/format/parity/unit bits mask
155 MTWTFC: BLOCK NMTCS             ;-10 word count to tape frame conversion factor
156  ]
157
158 ;Build table of QDL (PI level stack) pointers
159 MGQDLP: REPEAT NMTCS,-MGQDLL,,CONC MGQD,\.RPCNT,-1
160
161 ;Built storage for command lists and PI level stacks
162 REPEAT NMTCS,[
163         CONC MSCB,\.RPCNT,:
164                 BLOCK MSCBL     ;Space for command list
165                 MGRCV           ;Fake "command", causes list to wrap around
166
167                 MGNCMD          ;Function on botton of Q PDL, gets new command
168         CONC MGQD,\.RPCNT,:
169                 BLOCK MGQDLL    ;Space for PI level stack
170
171         IFE .RPCNT,MSLCTB==.-MSCB0      ;Length of each table
172 ]
173
174 ;Build table of pointers for adding commands to command list
175 MTCMBP: REPEAT NMTCS,-MSCBL-1,,CONC MSCB,\.RPCNT,-1
176
177 ;Build table of bytepointers for removing commands from command list
178 MGCMBP: REPEAT NMTCS,4400,,CONC MSCB,\.RPCNT,-1
179
180 ;It is depressing to discover that the DUMP program sucks these directly
181 ; out of the running ITS. If you change what's in here fix DUMP too.
182
183 MGEMTC: 0                       ;CONI MTC, at last error
184 MGEMTS: 0                       ;CONI MTS, at last error
185
186 IFE TM10B,[
187 MIOWD: BLOCK 2                  ;Channel program
188 ]
189 IFN TM10A,[
190 MGDBRK: 0
191         CONO MTS,1
192         JRST 12,@MGDBRK
193 ];TM10A
194
195 BBLK
196
197 \f
198 ;Random Macros
199
200 ;Enqueue and Dequeue buffers from the lists used to pass buffers between
201 ; main program and PI level. Assumes W has a valid transport number...
202
203 DEFINE MTENQB REG,TEMP=TT
204         SKIPG MSNBOL(W)         ;;Any buffers on list already?
205         IFSKP.
206          HLRZ TEMP,MSBUFP(W)    ;;Yes, get old tail pointer
207          DPB REG,[MLO,,MEMBLT(TEMP)]    ;;Add new one onto end of list
208         ELSE.
209          HRRM REG,MSBUFP(W)     ;;No, make new buffer head of list
210         ENDIF.
211         HRLM REG,MSBUFP(W)      ;;New buffer is tail in any event
212         SETZM TEMP
213         DPB TEMP,[MLO,,MEMBLT(REG)]     ;;Indicate end of list
214         AOS MSNBOL(W)           ;;Increment count of buffers on list
215 TERMIN
216
217 DEFINE MTDEQB REG,TEMP=TT
218         HRRZ REG,MSBUFP(W)      ;;Get head of buffer list
219         HLRZ TEMP,MSBUFP(W)     ;;Get tail
220         CAMN REG,TEMP           ;;Tail == head?
221         IFSKP.
222          LDB TEMP,[MLO,,MEMBLT(REG)]    ;;No, get next buffer on list
223          HRRM TEMP,MSBUFP(W)    ;;Make it the new head of list
224         ELSE.
225          SETZM MSBUFP(W)        ;;Only one buffer, list is now empty
226         ENDIF.
227         SOS MSNBOL(W)           ;;Decrement count of buffers on list
228 TERMIN
229
230 IFN TM03S,[
231 ;Macros for testing various status bits as set up by MGGXPT and friends
232 IRP OP,,[NN,NE,NA,O,OE,ON,OA,Z,ZE,ZN,ZA,C,CE,CN,CA]
233   DEFINE TT!OP REG,#MSK
234     ...TSF==0
235     IFSE REG,CS1,[
236         TL!OP I,MSK
237         ...TSF==-1
238         ]
239     IFSE REG,CS2,[
240         TR!OP I,MSK
241         ...TSF==-1
242         ]
243     IFSE REG,FS,[
244         TL!OP J,MSK
245         ...TSF==-1
246         ]
247     IFSE REG,ERR,[
248         TR!OP J,MSK
249         ...TSF==-1
250         ]
251     IFE ...TSF,.ERR Invalid register name REG given in TTxxx macro
252   TERMIN
253 TERMIN
254 ];IFN TM03S
255 \fSUBTTL MAG TAPE OPEN ROUTINE
256
257 ;       C/      MODE,,DEV
258 ;       D/      MODE (ROT 1) 4.9=1=>OUTPUT
259 ;       I/      DEVICE NUMBER
260 ;       R/      IOCHNM WORD POINTER
261
262 MAGTO:  SKIPL W,I               ;Get device
263          CAIL W,NMTCS           ;Too big?
264           JRST OPNL1            ;No such device
265         MOVSI T,%MAREW
266         TDNE T,MSRAC(W)         ;Rewinding?
267          PUSHJ P,UFLS           ;Yes, wait for completion
268         CONO PI,CLKOFF          ;Don't want transport status changed under me
269         SKIPL MTUSE(W)          ;See if we are the first opener
270         IFSKP.                  ;First opener. Initialize database for device
271          SETZM MSBUFP(W)        ;Indicate no buffers on chain
272          SETZM MSNBOL(W)        ;Another way of saying above
273          SETZM MSMPRC(W)        ;Buffer words remaining
274          SETZM MSMPRP(W)        ;Pointer to buffers
275          SETOM MTMDN(W)         ;No buffer at MP level
276          SETOM MGCABN(W)        ;No buffer owned by PI code
277          SETZM MSRAC(W)         ;Initialize transport software status word
278          MOVEI A,2
279          MOVEM A,MTCEFW(W)      ;Number of EOF's written
280          MOVSI A,%MANWT
281          IORM A,MSRAC(W)        ;Indicate nothing written on tape
282         ELSE.                   ;Not first opener. Check legality of this open
283          CAME U,MTUSR(W)        ;Same user as previous open?
284           JRST OPNL10           ;Different user, report error
285          MOVE B,D               ;Check direction of open
286          EQV B,MSCRW(W)         ;Same as previous direction?
287          SKIPL B                ;Yes, OK
288           JRST OPNL2            ;No, wrong direction
289         ENDIF.
290         MOVEM U,MTUSR(W)        ;Store user
291         SETZM MSCRW(W)          ;Indicate read until found to be otherwise
292         TLNE C,1                ;Read or write?
293          SETOM MSCRW(W)         ;Indicate write
294         AOS MTUSE(W)            ;Indicate 1 more user
295         PUSHJ P,SOSSET
296             MTUSE(W)            ;SOS if PCLSR'd
297         CONO PI,CLKON           ;Let um (em?) get me (who's em?)
298         PUSHJ P,MTSTAT          ;Get transport status in standard form
299         MOVE A,MSRAC(W)
300         TLNE A,%MAERR           ;PI error means device not there
301          JRST MTODNP            ;Go report error
302 IFN TM03S,[
303         TTNN FS,%TMSFP          ;Formatter present?
304          JRST MTODNP            ;No, can't win
305         TTNN FS,%TMSOL          ;Slave on line?
306          JRST MTODOL            ;No, lose
307 ]
308 IFN TM10P,[
309         TXNN J,%T1STH           ;Transport hung, by chance?
310          JRST MTOW1             ;No, proceed
311         TXNN J,%T1SRW           ;OK if rewinding
312          JRST OPNL7             ;Device not working
313 ]
314 MTOW1:  SKIPN MSCRW(W)          ;Writing?
315          JRST MTOW2             ;No...
316 IFN TM10P,TXNE J,%T1SWL         ;Yes. Write locked?
317 IFN TM03S,TTNE FS,%TMSWL
318          JRST OPNL26            ;Yes, device writelocked error
319 IFN TM10P, TXNN J,%T1SET        ;At EOT?
320 IFN TM03S, TTNN FS,%TMSET
321           JRST MTOW2            ;No
322         MOVSI A,%MAETW+%MAERR   ;If write and EOT, make .IOT give IOC error,
323                                 ;  but let open win
324         IORM A,MSRAC(W)
325
326 MTOW2:  TXNE C,%MMDEN           ;Density specified explicitly?
327          JRST MTOW3             ;Yes, go check for validity
328 IFN TM10P,MOVEI A,1             ;No, pick one. Use 800 for TM10
329 IFN TM03S,MOVEI A,2             ;Use 1600 for TM03
330         DPB A,[.BP %MMDEN,C]    ;Set value
331         JRST MTOW4              ;Done and assumed correct
332
333 MTOW3:  LDB A,[.BP %MMDEN,C]    ;Get density from open
334 IFN TM10P,[
335         CAIE A,1                ;800 is the only currently OK speed for TM10
336          JRST OPNL12
337  IFN 0,[
338 ;You need something like this if you arrange to allow non-800 TM10 speeds
339         TXNN C,%MM32B           ;32-bit compatible mode requested?
340          JRST MTOW4             ;No, core dump
341         CAIN A,1                ;Density specified as 800?
342          JRST MTOW4             ;Yes, we can do that
343         JRST OPNL12             ;32-bit and not 800BPI, controller can't do it
344  ]
345 ];IFN TM10P
346 IFN TM03S,[
347         CAIN A,3                ;Specified 6250?
348          JRST OPNL12            ;Yep, loser. Else OK
349 ]
350
351 ;Here on successful open.
352 ; Set up CONO or select word, IOCHNM word, blocksize
353 ;
354 MTOW4:  PUSHJ P,LSWDEL          ;Release MTUSE switch
355 IFN TM10P,[
356         MOVEI A,MTCCHN_3        ;Start building CONO word. Set control PI level
357 IFN TM10A,TRO A,1               ;Add in data PI level for non-DF10 controller
358         LDB B,[.BP %MMDEN,C]    ;Get density from open
359         CAIE B,1                ;800 BPI
360          BUG INFO,[ILLEGAL TM10 TAPE SPEED SETTING, USING 800BPI]
361         MOVEI B,%T1D80          ; Yep.  
362         DPB B,[.BP %T1CDS,A]    ;Set density field of CONO word
363         TXNN C,%MM32B           ;32-bit mode specified?
364          TXO A,%T1CCD           ;No, set core dump mode in CONO
365         TXNN C,%MMEP            ;User wants even parity?
366          TXO A,%T1COP           ;No, set odd parity
367         DPB W,[.BP %T1CNU,A]    ;Set unit number field of CONO
368         MOVEM A,MTCONO(W)       ;Save assembled CONO word
369 ];IFN TM10P
370 IFN TM03S,[
371         MOVE A,W                ;Get unit number being initialized
372         TXNN C,%MM32B           ;User asked for industry compatible?
373         IFSKP.                  ;Yes...
374          MOVEI B,4              ;Set word-to-frame conversion factor
375          MOVEM B,MTWTFC(W)
376          MOVEI B,%TMFIC         ;Set mode in budding select word
377         ELSE.                   ;Core dump...
378          MOVEI B,5              ; takes 5 tape frames per word
379          MOVEM B,MTWTFC
380          MOVEI B,%TMFCD         ;Set CD format in select word
381         ENDIF.
382         DPB B,[.BP %TMTFS,A]    ;Set format in select word
383         TXNE C,%MMEP            ;User wants even parity?
384          TXO A,%TMTEP           ;Yes, set even parity flag
385         LDB B,[.BP %MMDEN,C]    ;Get density from open  
386         CAIE B,1                ;800 BPI specified?
387          SKIPA B,[%TMD16]       ;Anything else, use 16
388           MOVEI B,%TMD08        ;800, use that
389         DPB B,[.BP %TMTDS,A]    ;Set density in select word
390         MOVEM A,MTSELW(W)       ;Set select word for this unit
391 ];IFN TM03S
392         LDB B,[.BP %MMRSZ,C]    ;Get record size from open call
393         TRC B,7                 ;Convert to power of two
394         MOVEI A,10              ;Minimum record size is 10 (8.) words 
395         LSH A,(B)               ;Blocksize = minimum * 2^power
396         MOVEM A,MTBLKS(W)       ;Save blocksize in words
397         LDB A,[.BP <%MMBLK\%MMIMG>,C]
398                                 ;Use unit/block and ascii/image bits as index
399         HLR C,MTOPTB(A)         ;Get input dispatch routine from table
400         TLNE D,400000           ;Remember D? Skip if user opened in input mode
401          HRR C,MTOPTB(A)        ;OK, get output dispatch routine instead
402         MOVEM C,(R)             ;Save routine in IOCHNM word
403         DPB W,[MTXP(R)]         ;Set transport number in IOCHNM word
404         JRST POPJ1              ;Skip return means success
405
406 ;Here if device is not present
407 MTODNP: SETZM MSRAC(W)  ;Too bad. Clear status word and report error
408         JRST OPNL1
409
410 ;Here if device off line
411 MTODOL: SETZM MSRAC(W)
412         JRST OPNL7
413
414 ;Table of I/O routines
415 ;
416 MTOPTB: MTUAIX,,MTUAOX          ;Unit Ascii
417         MTBIX,,MTBOX            ;Block Ascii
418         MTUIIX,,MTUIOX          ;Unit Image
419         MTBIX,,MTBOX            ;Block Image
420
421 \f
422
423 SUBTTL MAG TAPE CLOSE ROUTINES
424
425 ;MTOCL - CLOSE TAPE OPEN FOR OUTPUT
426
427 MTOCL:  LDB W,[MTXP(R)]         ;Set up transport number
428         SOSL MTUSE(W)           ;Decrement transport use counter
429          POPJ P,                ;Not only channel open, all done
430         AOS MTUSE(W)            ;Consistant state in case PCLSR'd
431         MOVSI A,%MAERR
432         TDNE A,MSRAC(W)         ;See if error has occurred
433          PUSHJ P,MTOCL3         ;Yes, clean up a few things
434
435         SKIPL MTMDN(W)          ;Is there a partially processed buffer?
436          PUSHJ P,MTWBFD         ;Yes, write it to tape
437
438         MOVEI B,MGMEOT          ;Queue a "Write EOT" command to PI level
439         PUSHJ P,MTCMD
440         SKIPLE MSCMDC(W)
441          PUSHJ P,UFLS           ;Wait till done. 
442         MOVEI A,1
443         MOVEM A,MGEOFR(W)
444         SKIPGE MTMDN(W)         ;Active buffer at MP level?
445         IFSKP.
446          MOVE A,MTMDN(W)
447          BUG PAUSE,[MT: MP BUF REMAINS AT CLOSE],OCT,A
448          PUSHJ P,MEMR
449         ENDIF.
450         SKIPGE MGCABN(W)                ;Active buffer at PI level?
451         IFSKP.
452          MOVE A,MGCABN(W)
453          BUG PAUSE,[MT: PI BUF REMAINS AT CLOSE],OCT,A
454          PUSHJ P,MEMR
455         ENDIF.
456         SKIPN MSNBOL(W)         ;Any buffers on buffer queue?
457         IFSKP.
458          BUG PAUSE,[MT:],DEC,MSNBOL(W),[BFRS QUEUED AT CLOSE]
459          PUSHJ P,MTCBFF
460         ENDIF.
461         SETOM MTUSE(W)          ;Nobody is using this transport
462         SETOM MTUSR(W)          ;No user associated with this transport
463         SETZM MSRAC(W)          ;reset transport software status word
464         POPJ P,
465
466 MTOCL3: SKIPL A,MTMDN(W)        ;Have a buffer active at MP level?
467          PUSHJ P,MEMR           ;Flush it if so
468         SETOM MTMDN(W)
469         SETZM MSMPRC(W)         ;Say no words left in current buffer
470         POPJ P,
471 \f
472 ;Close routine for MT open for input
473
474 MTICL:  LDB W,[MTXP(R)]         ;Set up channel data pointer
475         SOSL MTUSE(W)           ;Last user?
476          POPJ P,                ;No, nothing to do
477         AOS MTUSE(W)            ;Yes, save state for possible PCLSR
478         MOVEI T,1               ;This crock is because we want to allow
479         CAMGE T,MSCMDC(W)       ; one outstanding command if rewinding
480          PUSHJ P,UFLS           ;Wait till one or less outstanding command
481         MOVE T,MSRAC(W)         ;Get transport software status
482         TLNE T,%MAREW           ;Is it rewinding?
483         IFSKP.
484          SKIPLE MSCMDC(W)       ;No, wait till no outstanding commands
485           PUSHJ P,UFLS
486         ENDIF.
487         SKIPGE MGCABN(W)        ;Any PI-level buffers left?
488         IFSKP.
489          MOVE A,MGCABN(W)        
490          BUG PAUSE,[MT: PI INPUT BUF LEFT AT CLOSE],OCT,A
491          PUSHJ P, MEMR
492         ENDIF.
493         PUSHJ P,MTRBD           ;Release any MP-level buffers
494         SETOM MTUSR(W)          ;Reset user identifier
495         PUSHJ P,MTCBFF          ;Free some buffers ?whose+++
496         SOS MTUSE(W)            ;Decrement use count
497         MOVE T,MSRAC(W)         ;Get transport software status again
498         TLNE T,%MAREW           ;Are we rewinding?
499          JRST MTICL2            ;Yes, don't have to skip to EOF
500         MOVSI A,(%MMNSE)
501         TDNE A,(R)              ;Check if user wants skip to EOF
502          JRST MTICL2            ;No, forget it
503         MOVSI A,%MAMSO
504         TDNN A,MSRAC(W)         ;Has tape moved at all since open?
505          JRST MTICL2            ;No...
506         SKIPE MGEOFR(W)         ;
507          JRST MTICL2            ;Note that this disposes of a read-ahead EOF.
508         PUSHJ P,MTSTAT
509 IFN TM10P,[
510         MOVE B,MGCMTS(W)
511         TXNE B,%T1SBT           ;BOT?
512          JRST MTICL2
513 ]
514 IFN TM03S,[
515         TTNN FS,%TMSOL          ;Still online?
516          JRST MTICL2            ;No, can't very well skip to EOF
517         TTNE FS,%TMSBT
518          JRST MTICL2
519 ]
520         MOVEI B,MGSPFF          ;Space forward to end of file
521         PUSHJ P,MTCMD
522         SKIPLE MSCMDC(W)        ;Wait till command done
523          PUSHJ P,UFLS
524
525 MTICL2: MOVSI T,%MAREW
526         ANDM T,MSRAC(W)         ;Clear all software status except rewinding
527         POPJ P,                 ;Done
528
529 ;Free a chain of IO buffers pointed to by MSBUFP(W)
530 ; Count of buffers is in MSNBOL(W)
531 ;
532 MTCBFF: SKIPN MSNBOL(W)         ;Any buffers on chain?
533          POPJ P,                ;No, fine
534         DO.
535          HRRZ A,MSBUFP(W)       ;Yes, get pointer
536          LDB T,[MLO,,MEMBLT(A)] ;Get pointer to next buffer
537          HRRM T,MSBUFP(W)       ;Write that in chain header
538          PUSHJ P,MEMR           ;Return buffer to IO pool
539          SOSLE MSNBOL(W)        ;Any more to do?
540           JRST TOP.             ;Yes, loop back for more
541         ENDDO.
542         SETZM MSBUFP(W)         ;Zero buffer list pointer
543         POPJ P,
544
545 \f
546
547 SUBTTL MAG TAPE INPUT .IOT ROUTINES
548
549         SKIPA B,[SIOKT]
550 MTUAI:   MOVEI B,CHRKTI         ;Unit ASCII input
551         MOVE E,[440700,,5]
552         JRST MTREAD
553
554         SKIPA B,[SIOKT]
555 MTUII:   MOVEI B,CHRKTI         ;Unit image input
556         MOVE E,[444400,,1]
557         JRST MTREAD
558
559 MTBI:   MOVE E,[444400,,1]      ;Block input
560         MOVEI B,BLKT
561
562 MTREAD: LDB W,[MTXP(R)]         ;W <= Transport number
563         PUSHJ P,MTIECK          ;Check for tape errors first
564         MOVEM P,MTPSAV(W)       ;Save P for EOF return
565         JSP B,(B)               ;IO Routine. BLKT,CHRKT,SIOKT
566             MSMPRP(W)           ;Pointer to next word
567             MSMPRC(W)           ;Count of words remaining
568             SETZ MTRBG          ;Get new buffer (SETZ for CHRKT return on EOF)
569             MTRBD               ;Discard buffer
570             JRST 4,.            ;Unused
571             PUSHJ P,MTRBFW      ;Code to wait for new buffer from PI level
572
573 ;Get a new buffer for I/O code.
574 ; This routine assumes that there is a buffer ready to get
575 ; (i.e. MTRBFW was called)
576 ;
577 MTRBG:  SKIPG MSNBOL(W)         ;Any buffers on list?
578          JRST MTRBG3            ;No, must be error or EOF
579         CONO PI,UTCOFF          ;Stop I/O for a bit
580         MTDEQB TT,A             ;Dequeue buffer into TT using A as temp
581         MOVEM TT,MTMDN(W)       ;Remember buffer active at MP level
582         CONO PI,UTCON           ;Turn I/O back on
583         LDB J,[MWC,,MEMBLT(TT)] ;Get word count from buffer
584         MOVEM J,MTBLKS(W)       ;Save for .MTAPE 13
585         LSH TT,10.              ;Convert buffer number into address
586         JRST SIOBGX             ;TT/address, J/word count /E unchanged
587
588 ;Here if no buffer ready, error or EOF assumed
589 ;
590 MTRBG3: SKIPL MSRAC(W) .SEE %MAEOF      ;EOF flag set in transport status?
591         IFSKP.
592          MOVSI T,%MAEFA         ;The EOF is now no longer read-ahead
593          ANDCAM T,MSRAC(W)      ;So remember that fact
594          JRST POPJ2             ;Double skip to tell I/O code about EOF
595         ENDIF.
596         PUSHJ P,MTIECK          ;Not EOF. Check for error conditions
597         BUG HALT,[TAPE READ BUFFER VANISHED] ;No error, shoulda been a buffer
598 \f
599 ;MAG TAPE READ BUFFER DISCARD ROUTINE
600 MTRBD:  SKIPGE A,MTMDN(W)       ;Have an active MP buffer?
601          JRST MOVTWJ            ;Set up T for buffer wait, return
602         CONO PI,UTCOFF          ;Stop IO for a bit
603         SETOM MTMDN(W)          ;No active MP buffer
604         SETZM MSMPRC(W)         ;No data in nonexistant buffer
605         LDB TT,[MSEOFP,,MEMBLT(A)]      ;Get EOF flag from PI level
606         PUSHJ P,MGMEMR          ;Return buffer, enable UTC
607         JUMPN TT, [ MOVSI A,%MAEOF      ;EOF seen?
608                     IORM A,MSRAC(W)     ;Record EOF in software status
609                     JRST .+1 ]
610 MOVTWJ: MOVE T,W                ;T gets transport number for bfr wait UFLS
611         POPJ P,                 ;Also MTRBG, MTRBFW rely on this setting T
612
613
614 ;MAG TAPE READ WAIT FOR DATA ROUTINE
615 ; Called under a UFLS by system IO code to wait for data to arrive.
616 ; Note T, not W, has transport number. T must be set up by some
617 ; previous routine
618 ;
619 MTRBFW: MOVE TT,MSRAC(T)        ;Get software status of transport
620         TLNN TT,%MAEOF\%MAERR   ;PI code reports EOF or error?
621         SKIPLE MSNBOL(T)        ;Or are any buffers available for reading?
622          JRST POPJ1             ;SOme interesting condition, unhang
623         TLNE TT,%MARAC          ;Have we asked for a tape read yet?
624          POPJ P,                ;Yes, nothing to do but wait, wait, wait
625         PUSH P,W                ;This being done under a UFLS. only T good
626         PUSH P,B
627         MOVE W,T                ;Set up transport number in usual place
628         MOVEI B,MGREAD          ;What we want the PI level to do
629         MOVEI T,MSCBL           ;Make sure that there is room in command list
630         CAMG T,MSCMDC(W)        ;If there is room,
631         IFSKP.                  ; we will request a read operation
632          MOVSI TT,%MARAC
633          IORM TT,MSRAC(W)       ;Read is active now, or will be shortly
634          PUSHJ P,MTCMD1         ;Queue up command request for PI level
635         ENDIF.                  ;If no room for command, all we can do is wait
636         MOVE T,W                ;Fix up T for UFLS
637         POP P,B                 ;Clean up everything else
638         POP P,W
639         POPJ P,
640 \f
641 SUBTTL MAG TAPE OUTPUT .IOT ROUTINES
642
643         SKIPA B,[SIOKT]
644 MTUAO:   MOVEI B,CHRKT          ;Unit ASCII output
645         MOVE E,[440700,,5]
646         JRST MTWRIT
647
648         SKIPA B,[SIOKT]
649 MTUIO:   MOVEI B,CHRKT          ;Unit image output
650         MOVE E,[444400,,1]
651         JRST MTWRIT
652
653 MTBO:   MOVE E,[444400,,1]      ;Block output
654         MOVEI B,BLKT
655
656 MTWRIT: LDB W,[MTXP(R)]         ;Get transport number
657         PUSHJ P,MTIECK          ;Check for tape errors first
658         HRLZI A,%MAETW
659         TDNE A,MSRAC(W)         ;PI code think it hit EOT?
660          JRST IOCER9            ;Yep, go lose
661         JSP B,(B)
662             SETZ MSMPRP(W)      ;Pointer to next word
663             MSMPRC(W)           ;Count
664             SETZ MTWBFG         ;Get new buffer
665             MTWBFD              ;Write out buffer to tape
666             JRST 4,.
667             TRNA                ;No wait for buffer routine needed
668 \f
669 ;MAG TAPE WRITE - BUFFER GET ROUTINE
670
671 MTWBFG: PUSHJ P,MTIECK          ;Check for tape errors
672         PUSHJ P,TCALL           ;Turn off UTC
673             JRST IOMQ           ;Try to get buffer
674          POPJ P,                ;Return noskip if no buffers available
675         MOVEM A,MTMDN(W)        ;Store active buffer number
676         MOVEI T,MUMGB
677         DPB T,[MUR,,MEMBLT(A)]  ;Tell world that it is a mag tape buffer
678         DPB W,[MSCHN,,MEMBLT(A)] ;Store channel number in buffer header
679         SETZM TT
680         DPB A,[121000,,TT]      ;Convert block number in A to address in TT
681         MOVE J,MTBLKS(W)        ;Get block size of write
682         JRST SIOBGX
683
684 ;MAG TAPE WRITE - BUFFER FINISHED ROUTINE
685 ; General IO code has filled a buffer or otherwise finished with it.
686 ; Queue the buffer for writing if there is anything in it.
687
688 MTWBFD: PUSHJ P,MTIECK          ;Check for tape errors
689         SKIPGE A,MTMDN(W)       ;Have an active buffer?
690          POPJ P,                ;No, nothing to do
691         MOVEI T,MSCBL           ;See if there is any room in command list
692         CAMG T,MSCMDC(W)
693          PUSHJ P,UFLS           ;Wait for room in command list
694         MOVE T,MTBLKS(W)        ;Get blocksize we are writing
695         SUB T,MSMPRC(W)         ;Subtract number of words remaining in buffer
696         CONO PI,UTCOFF          ;Lock up while frobbing buffer lists
697         SETOM MTMDN(W)          ;Clear active buffer
698         SETZM MSMPRC(W)         ;Clear free word in buffer count
699         JUMPE T,MEMR            ;Nothing in buffer, just return block
700         DPB T,[MWC,,MEMBLT(A)]  ;Store word count
701         MTENQB A                ;Queue buffer on to-PI list
702         CONO PI,UTCON           ;Finished mucking with buffer list
703         PUSH P,B
704         MOVEI B,MGWRIT          ;Issue a write request to PI level
705         PUSHJ P,MTCMD
706         MOVSI B,%MANWT
707         ANDCAM B,MSRAC(W)       ;Note that we have written something to tape
708         SETZM MTCEFW(W)         ;Note no EOF's written at end of tape
709         JRST POPBJ              ;Restore B and return
710 \f
711 SUBTTL MTCMD - GIVE COMMAND TO PI LEVEL
712
713 ;PUSHJ P,MTCMD
714         ;RH(W) has transport number
715         ;RH(B) has address of PI level routine to execute
716
717 MTCMD:  MOVEI T,MSCBL           ;Pending command list length
718         CAMG T,MSCMDC(W)        ;Count of commands currently in list
719          PUSHJ P,UFLS           ;Wait for room in pending command list 
720         CONO PI,UTCOFF          ;Grab machine, keep count accurate
721 MTCMD1: MOVE T,MTCMBP(W)        ;Get pointer to next slot in command list
722         AOBJN T,MTCMD2          ;Increment slot and check for wraparound
723          SUB T,[MSCBL,,MSCBL]   ;Reached end of list, ring it
724 MTCMD2: MOVEM B,(T)             ;Store new command
725         MOVEM T,MTCMBP(W)       ;Store new pointer
726         AOS MSCMDC(W)           ;Indicate one more command in list
727         JRST MSTRTR             ;Go start up PI routine
728
729 SUBTTL MTIECK - CHECK FOR IOC ERROR
730
731 ;PUSHJ P,MTIECK
732         ;Returns +1 if no error
733         ;Gives IOC error to user if error - never returns.
734
735 MTIECK: PUSH P,A
736         MOVE A,MSRAC(W)         ;Get transport software status
737         TLNN A,%MAERR           ;PI level report an error?
738          JRST POPAJ             ;No, all is OK
739         SKIPLE MSCMDC(W)        ;Wait for PI level to finish cleaning up
740          PUSHJ P,UFLS           ; before throwing away buffers
741         SKIPL A,MTMDN(W)        ;Have an active MP-level buffer?
742          PUSHJ P,MEMR           ;Yes, throw it away
743         SETOM MTMDN(W)          ;No active MP buffer
744         SETZM MSMPRP(W)         ;No place to get/put next character
745         SETZM MSMPRC(W)         ;No room to do it anyway
746         PUSHJ P,MTCBFF          ;Free any buffers waiting for MP processing
747         POP P,A
748         MOVE T,MGCMTS(W)        ;Get transport status data from PI level
749 IFN TM10P,[
750         TRNE T,%T1STH\%T1SIO    ;Transport hung or illegal operation?
751          JRST IOCER1            ;Yes, report device error
752         TRNE T,%T1SPE\%T1SRC\%T1SRL\%T1SDL\%T1SBT       ;Gruesome errors
753          JRST IOCER3            ;Report irrecoverable data error
754         TRNE T,%T1SET           ;(Real) End of Tape?
755          JRST IOCER9            ;Device Full error
756 ];IFN TM10P
757 IFN TM03S,[
758         MOVE I,MGCMTC(W)        ;Get controller transport status from PI level
759         MOVE J,MGCMTS(W)
760         TTNE CS1,%TM1MP         ;Control bus parity error?
761          JRST IOCER1
762         TTNN CS1,%TM1TE         ;Transfer error? Could be TM03 or RH11
763         IFSKP.
764          TTNE CS2,%TM2DL\%TM2UP\%TM2NF\%TM2NM\%TM2PE\%TM2MT\%TM2MP
765           JRST IOCER1           ;Non-data errors
766          TTNN FS,%TMSES         ;Formatter error?
767          IFSKP.
768           TTNE ERR,%TMEUS\%TMECT\%TMENX\%TMEMD\%TMEFS\%TMEMC\%TMERM\%TMEIR\%TMEIF
769            JRST IOCER1          ;Fatal formatter errors
770           TTNE ERR,%TMECE\%TMECS\%TMEFC\%TMENG\%TMEFL\%TMEIC
771            JRST IOCER3          ;Non-recoverable data errors
772          ENDIF.
773         ENDIF.
774         TTNE FS,%TMSET          ;End of tape?
775          JRST IOCER9
776 ];IFN TM03S
777         MOVE A,MGEOFR(W)        ;Check for logical EOT
778         CAIL A,2                ;Read two EOF's since last record?
779          JRST IOCER9            ;Yes, report EOT
780         JRST IOCER3             ;No, give irrecoverable data error for now
781 \f
782 SUBTTL MAG TAPE .STATUS ROUTINE
783 ;Building a status word in D.
784 ;Routine sets:
785 ; 1.7-1.9 open modes
786 ; 2.3 BOT
787 ; 2.4 EOT
788 ; 2.5 9 track (0 = 7 track)
789 ; 2.6 IBM mode (0 = coredump)
790 ; 2.7 Transport idle (no pending command)
791 ; 2.8 EOF (last thing seen was a tape mark)
792 ;
793 STAMTC: 
794 ;Open modes
795         LDB W,[MTXP(R)]         ;Get transport number
796         DPB A,[60300,,D]        ;Open mode
797         PUSHJ P,MTSTAT          ;Get tape status from transport
798 ;EOT?
799         LDB A,[.BP %MAETW_22,MSRAC(W)]  ;EOT on write
800         LDB B,[.BP %MAETR_22,MSRAC(W)]  ;EOT on read
801         IOR A,B
802         DPB B,[140100,,D]       ;Tape at EOT?
803 IFN TM10P,[
804 ;7 or 9 track drive?
805         LDB A,[20100,,J]        ;Get 7/9 track bit
806         TRC A,1
807         DPB A,[150100,,D]       ;7 or 9 track drive
808         .ERR Missing TM10 .STATUS code at STAMTC
809 ]
810 IFN TM03S,[
811 ;A bunch of new stuff. BOT?
812         SETZ A,
813         TTNE FS,%TMSBT          ;Transport is at BOT?
814          SETO A,
815         DPB A,[130100,,D]       ;BOT.
816 ;7 or 9 track drive?
817         SETOM A                 ;TM03 is always 9-track
818         DPB A,[150100,,D]       ;7 or 9 track drive
819 ;Core dump or 32 bit mode?
820         MOVE A,MTWTFC(W)        ;Get word to frame conversion. 4 or 5
821         TRC A,1                 ;Flip last bit. Last bit now on iff 32bit mode
822         DPB A,[160100,,D]       ;Sorry.
823 ;Formatter busy?
824         SETO A,
825         SKIPLE MSCMDC(W)        ;Idle if no pending commands
826          SETZ A,
827         DPB A,[170100,,D]
828 ;EOF last thing seen?
829         SETZ A,
830         TTNE FS,%TMSTM          ;Last thing seen was a tape mark?
831          SETO A,
832         DPB A,[200100,,D]       ;EOF. 
833 ];IFN TM03S
834         POPJ P,
835
836 ;RCHST ROUTINE FOR MAG TAPE
837
838 RCHMGT: HLRZ E,(R)              ;Get open mode from IOCHNM word
839         LDB J,[MTXP(R)]         ;Get the mag tape drive number
840         MOVSI J,'MT0(J)         ;Return that drive's device name
841         TRZ E,(.BM MTXP)        ;Clear drive # field in OPEN modes
842         JRST POPJ1              ;Skip so that J overrides built-in device name
843
844 \f
845 SUBTTL MAG TAPE PI LEVEL
846
847 ;Request magtape interrupt from MP-level software
848 ; Must be called with I/O interrupts off (CONO PI,UTCOFF)
849 ; This is called every 1/2 second by the ITS slow clock routine
850
851 MSTRTR: SETZM MGTBZY            ;No busy tapes, flag software interrupt
852         CONO PI,MTCRQ           ;Request interrupt on magtape channel
853         CONO PI,UTCON           ;Reenable IO interrupt system
854         POPJ P,                 ;That is all
855
856 ;Handle tape interrupt requested by software or other nonspecific cause
857 ; Get here via non-vectored MTCCHN interrupt on the KS
858 ;
859 MGSBRK: AOS MGTBZY              ;Note interrupt level is busy
860         SETOM MGSFTI            ;Note software interrupt in progress
861         MOVEI B,NMTCS-1         ;Loop over all transports
862         SKIPG MSCMDC(B)         ;Any commands in command list?
863 MGSBK1:  SOJGE B,.-1            ;No, try next transport
864         SKIPGE B                ;Found command or finished scan. Which?
865          JRST MGSBK2            ;Finished scanning. Go check other things
866         MOVE W,B                ;Have a command. Set up transport number
867         PUSH P,B                ;Save B over call to command routine
868         MOVSI B,%MACTH
869         TDNN B,MSRAC(W)         ;Core allocator saying go away?
870          PUSHJ P,MGXGO          ;No, go start requested routine
871         POP P,B                 ;Restore transport count
872         JRST MGSBK1             ;Loop back for another transport
873
874 MGSBK2: SETZM MGSFTI            ;Clear software interrupt flag
875         JRST MGEX               ;That's all for now
876 ;This probably should check for lost IE bits on TM03
877
878 ;Handle interrupt caused by specific hardware conditions
879 ; Get here via vectored interrupt on the KS
880 ;
881
882 IFN TM10P,[
883 ; A - result of CONI MTC,
884 ; C - result of CONI MTS,
885 ;
886 MGHBRK: SKIPGE W,MGUNIT         ;Get unit we are expecting interrupt on
887          JRST MGUBRK            ;None? Probably MP level bailed out. Punt.
888         LDB B,[MUNITF,,A]       ;Get unit that controller is squacking about
889         CAME W,B                ;Same unit?
890          BUG HALT,[MT PI CODE LOST TRANSPORT]
891         MOVE J,C
892         PUSH P,[MGEX]           ;Cause POPJ P, in handler to dismiss interrupt
893 IFN TM10B,[
894         TXNE C,%T1SCP\%T1SNM\%T1SDP     ;Check for DF10 errors
895          JRST MGERR             ;Yes, go to error routine
896 ];TM10B
897         TXNE C,%T1SIO           ;Illegal operation error?
898          JRST MGERR             ;Yes, go to error routine
899         JRST MGXGO              ;No, go handle interrupt
900
901 ;Here to unbreak on unexpected hardware interrupt
902 ;
903 MGUBRK: LDB W,[MUNITF,,A]       ;Who's the loser, anyway
904         MOVE B,MTCONO(W)        ;Get prototype CONO word for that transport
905         CONO MTC,(B)            ;Select offending unit
906         CONO MTS,31             ;Clear interrupt, DF10, stop any op in progress
907         JRST MGEX               ;Go dismiss interrupt
908 ];IFN TM10P
909
910 IFN TM03S,[
911 ;Check for active unit. If none, go directly to inactive slave
912 ;polling code. If active unit,check that controller is talking about
913 ;this unit, then jump to its routine (MGXGO). When that finishes,
914 ;see if controller is still showing attention, and check status
915 ;of other transports if so.
916 ;
917 ;Well, almost.
918
919         EBLK
920 MGHBRK: 0
921         BBLK
922         JSR UTCSAV              ;Save AC,s set up interrupt P PDL
923         AOS MGTBZY              ;Note interrupt level is alive
924         SKIPGE W,MGUNIT         ;Some transport waiting for an interrupt?
925          JRST MGNOUW            ;Nope, either Slave Status Change or lossage
926         IORDI B,%TMTC           ;Get transport the TM03 is thinking about
927         ANDI B,7
928         CAME B,W                ;Same as the one we were waiting for?
929          BUG HALT,[MT PI CODE LOST TRANSPORT]
930         PUSHJ P,MGXGO           ;Go jump into this unit's handler
931
932 MGNOUW:
933 IFN NMTCS-1,[
934 .ERR Missing multi-transport code at MGNOUW!
935 If more than one unit, have to see if this is an interrupt caused by a
936 SSC (slave status change), and if so poll all the inactive units and
937 update their software status (rewinding, on/off line, etc.) With only
938 one transport we currently avoid this by keeping the unit active
939 (MGUNIT set) as long as it is doing *anything*, and giving it all the
940 hardware interrupts. See rewind code, too.
941 ];IFN NMTCS-1
942         JRST MGEX               ;Go dismiss interrupt
943 ];IFN TM03S
944 \f
945 ;Interrupt level control flow
946 ;
947 ; Each transport maintains the current state of its PI-level action
948 ; routines on a seperate (per-transport) PDL with its SP in Q. This
949 ; allows you to save the current state, dismiss the interrupt, and
950 ; resume where you left off when the next interrupt for this transport
951 ; arrives.
952
953 ; Subroutine linkage between routines handling a per-drive PI-level
954 ; action is with PUSHJ Q,xxx and POPJ Q,
955 ;
956 ; The MP level queues commands for the PI level to process on a per-
957 ; transport queue at MGSBx (x=unit number)
958 ;
959 ; Ths general interrupt code transfers to the per-drive actions by
960 ; jumping to MGXGO, which will load Q from the saved state of the
961 ; current drive and start up whatever it finds there. This may be
962 ; the MGNCMD routine, which will start a new command, or it may be
963 ; the middle of an in-progress PI-level command handler.
964 ;
965 ; PI-level action routines can relinquish control in several ways:
966 ;
967 ;  PUSHJ Q, CPOPJ will dismiss the current interrupt, arranging for
968 ;  control to return to the instruction following the PUSHJ when the
969 ;  next interrupt for this unit occurs.
970 ;
971 ;  JRST MGOVER will dismiss the current interrupt, arranging for the
972 ;  currently executing subroutine to be restarted "from the top" when
973 ;  the next interrupt for this unit occurs.
974 ;
975 ;  A simple POPJ P, will dismiss the current interrupt, arranging for
976 ;  the routine that called this one to be started at the point immediately
977 ;  after the call when the next interrupt comes in. This is generally not
978 ;  useful except from first-level action routines, where a POPJ P, will
979 ;  indicate that you have finished handling the current command and cause
980 ;  the next interrupt to fetch and start execution of a new command from the
981 ;  queued command list by transferring to MGNCMD. Got that?
982
983 ;Transfer control to whatever the per-transport code wants to do.
984 ;
985 MGXGO:  MOVE Q,MGQDLP(W)        ;Getsaved Q PDL pointer for current transport
986         PUSHJ P,QPOPJ           ;"Return" to whatever is on top of Q PDL,
987                                 ; arranging for POPJ P, to return to here
988
989         MOVEM Q,MGQDLP(W)       ;Save current Q PDL for next time
990         POPJ P,                 ;Return, dismissing this interrupt
991
992 ;Dismiss interrupt, arranging for next interrupt to restart routine
993 ; we are currently executing (rather than either continuing here or
994 ; starting a new command)
995 ;
996 MGOVER:
997 IFN TM10P,[
998         CONSZ MTS,%T1STH\%T1SIO\%T1SCE  ;Tape hung/ill op/DF10 error, 
999          JRST MGERR             ; go handle error condition
1000 ]
1001         SOS (Q)                 ;Decrement address at top of Q PDL, now
1002                                 ; points to PUSHJ Q, <us> instruction so
1003                                 ; that we will get called again from MGXGO
1004                                 ; at next interrupt dispatch
1005         POPJ P,                 ;Return to P PDL caller, dismissing interrupt
1006
1007
1008 ;This routine is always the last "command" in a transport command list
1009 ; Wraps the command list BP around the the beginning of the list,
1010 ; then gets and executes the next command.
1011 ;
1012 MGRCV:  MOVNI A,MSCBL+1         ;Get negative length of command list
1013         ADDM A,MGCMBP(W)        ;Wrap command extraction pointer back to start
1014 MGNCM1: ILDB B,MGCMBP(W)        ;Get new command from list
1015         JRST (B)                ;And jump to it
1016
1017 ;This code is always the first (bottom) thing in a transport's Q PDL
1018 ; It is therefore executed whenever MGXGO transfers control to the
1019 ; Q PDL and there is no command in progress.
1020 ;
1021 MGNCMD: AOBJN Q,MGNCM1          ;Got here w/ POPJ Q,. Fake PUSHJ to restore Q,
1022                                 ; then go get the next command
1023         
1024         BUG                     ;Q PDL pointer clobbered
1025
1026 QPOPJ1: AOS (Q)
1027 QPOPJ:  POPJ Q,
1028
1029 \f
1030 ;WAIT FOR JOB DONE BIT TO SET
1031 ; Called from PI-level command routines to wait for end of command.
1032 ; Called with PUSHJ Q,MGWTJD
1033 ;
1034 ; Returns +1 to caller if unusual termination
1035 ;         +2 to caller if operation terminated normally
1036
1037 ;       I,J contain tape status:
1038 ;        On TM10, I=CONI MTC,
1039 ;                 J=CONI MTS
1040 ;        On TM03S, I=%TMCS1,,%TMCS2 (controller status),
1041 ;                  J=%TMFS,,%TMERR (formatter status)
1042
1043 IFN TM10P,[
1044 MGWTJD: CONI MTS,J              ;Get transport status
1045         TXNE J,%T1STH\%T1SIO    ;Transport hung or Illegal operation?
1046          JRST MGERR             ;Yes, job-done isn't ever going to get set
1047 MGWJD1: CONI MTS,J              ;Get status again
1048         SKIPN MGJDTI            ;Is there a time out set?
1049         IFSKP.
1050          MOVE T,TIME            ;Yes, check it. Get current time
1051          CAML T,MGJDTI          ;Smaller than specified timeout time?
1052           JRST MGERR            ;No, lose
1053         ENDIF.
1054         TXNN J,%T1SJD           ;JOB-DONE bit set?
1055          JRST MGOVER            ;No, we want to wait for it
1056         CONI MTS,J              ;Job Done. Get status
1057         CONI MTC,I              ;Get CONI MTC
1058         MOVEM J,MGCMTS(W)       ;Save for MP level
1059         MOVEM I,MGCMTC(W)
1060 IFN TM10B,[
1061         SKIPE MGWCW             ;Want to wait for control word?
1062          PUSHJ Q,MGWCWC         ;Check to see if it is written
1063         SETZM MGWCW             ;Clear wait-for-control-word request flag
1064 ]
1065         CONO MTS,30             ;Clear channel conditions
1066         MOVE B,MTCONO(W)
1067         CONO MTC,(B)            ;Release mtc, clear job done bit
1068 IFN TM10B,[
1069         TXNE J,%T1SCP\%T1SNM\%T1SDP     ;Check for channel errors
1070          POPJ Q,                ;Channel error, return nonskip
1071 ]
1072         TXNE J,%T1STH\%T1SIO\%T1SPE\%T1SRC%\T1SRL\%T1SDL\%T1SBT
1073          POPJ Q,                ;Random other things, not necessarily errors
1074         JRST QPOPJ1             ;Success
1075 ];IFN TM10P
1076 IFN TM03S,[
1077 MGWTJD: 
1078 MGWJD1: IORDI T,%TMCS1          ;Get controller status
1079         TXNN T,%TM1GO           ;Go bit still set?
1080          JRST MGWJD2            ;No, command is finished. Go check errors
1081         SKIPE T,MGJDTI          ;Is there a time out set? Get it if so.
1082          CAML T,TIME            ;Past timeout time
1083           JRST MGOVER           ;No timeout or not timed out yet, go wait
1084         JRST MGERR              ;Timed out. Go check transport
1085
1086 ;Here if action has terminated. Set up status bits before returning
1087 MGWJD2: HRLZ I,T                ;%TMCS1,,?
1088         IORDI T,%TMCS2
1089         HRR I,T                 ;I = %TMCS1,,%TMCS2
1090         IORDI J,%TMERR
1091         IORDI T,%TMFS
1092         HRL J,T                 ;J = %TMFS,,%TMERR - I,J now in standard form
1093         MOVEM J,MGCMTS(W)       ;Save for MP level
1094         MOVEM I,MGCMTC(W)
1095         TTNE CS1,%TM1MP         ;Massbus control parity error
1096          JRST MGERR             ;Who knows what the transport is doing
1097         TTNN CS1,%TM1TE         ;Controller error?
1098          TTNE FS,%TMSES         ;Formatter error?
1099           POPJ Q,               ;Yes, return +1 for closer examination
1100         JRST QPOPJ1             ;Success
1101 ];IFN TM03S
1102
1103 ;Select the transport given by W
1104 ; Returns +1 with transport selected, status in I,J
1105 ; May dismiss and wait for a while first
1106 ;
1107 MGGXPT: 
1108 IFN TM10P,[
1109         CONSO MTS,%T1SNU        ;Can controller select new unit right now?
1110          JRST MGOVER            ;No, wait for it
1111         MOVE T,TIME
1112         ADDI T,10.*30.          ;Time out in 10. seconds
1113         MOVEM T,MGJDTI          ;Set up job-done timeout
1114         MOVEM W,MGUNIT          ;Note unit waiting for hardware interrupt
1115         MOVE B,MTCONO(W)        ;Get CONO word for new unit
1116         CONO MTC,MNOPIN(B)      ;NOP, but interrupt when new drive is ready
1117         PUSHJ Q,MGWJD1          ;Wait for job done
1118          JFCL                   ;Ignore any errors
1119         SETZM MGJDTI            ;No more timeout
1120         SETOM MGUNIT            ;Not waiting any more
1121         POPJ Q,                 ;Return to caller
1122 ];IFN TM10P
1123 IFN TM03S,[
1124         IORDI T,%TMFS           ;Get current formatter status
1125         TXNN T,%TMSES\%TMSSC    ;Showing error or slave status change?
1126         IFSKP.                  ;Yes, clear errors before going ahead
1127          IOWRI W,%TMTC          ;Select slave
1128          MOVEI A,10.            ;Try 10 times to clear drive
1129          MOVEI B,%TMCLR
1130          DO.
1131           IOWRI B,%TMCS1        ;Write drive clear command
1132           IORDI T,%TMFS         ;Get status
1133           TXNN T,%TMSES         ;Still have error
1134            JRST ENDLP.          ;No, done
1135           SOJG A,TOP.           ;Retry up to 10 times
1136           JRST MGERR            ;Else give up
1137          ENDDO.
1138         ENDIF.
1139         MOVE T,MTSELW(W)        ;Get desired settings
1140         IOWRI T,%TMTC           ;Tell TM03
1141         MOVEI T,%TMNOP          ;You may need this to set status values
1142         IOWRI T,%TMCS1          ; but I'm not really sure
1143         IORDI T,%TMCS1
1144         PUSHJ Q,MGWJD2          ;Go set status registers appropriately
1145          JFCL                   ;Maybe should check non-existant slave?
1146         POPJ Q,
1147 ];IFN TM03S
1148
1149 ;MGERR - HANDLE TAPE ERROR
1150 ;
1151 ;Called from PI level command routines which detect a tape or controller error
1152 ; Flags error in software status word, records error status in MGExxx.
1153 ; Flushes command in progress by resetting Q PDL to base.
1154 ; Flushes commands in PI-level command queue by resetting queue pointers.
1155 ; Flushes any buffers which might be queued for writing.
1156 ; Returns to P PDL, to wait for new commands.
1157
1158 MGERR:
1159 IFN TM10P,[
1160         CONI MTS,MGEMTS         ;Get transport status for MP level analysis
1161         CONI MTC,MGEMTC
1162 ]
1163 IFN TM03S,[
1164         IORDI T,%TMCS1          ;Get controller and transport status into
1165         HRLM T,MGEMTC           ; standard form
1166         IORDI T,%TMCS2
1167         HRRM T,MGEMTC
1168         IORDI T,%TMFS
1169         HRLM T,MGEMTS
1170         IORDI T,%TMERR
1171         HRRM T,MGEMTS
1172         MOVE I,MGEMTC           ;Get status to standard place for macros
1173         MOVE J,MGEMTS
1174 ];IFN TM03S
1175         MOVSI T,%MARAC          ;Read not active, for sure
1176         ANDCAM T,MSRAC(W)
1177         SETZM MSCMDC(W)         ;No commands active
1178         SETOM MGUNIT            ;Clear unit wait flag
1179         SETZM MGJDTI            ;No job-done timeout
1180 IFN TM10B,[
1181         TXNE J,%T1SCP\%T1SNM\%T1SDP     ;Channel error?
1182          BUG PAUSE,[MTAPE: CHANNEL ERROR, STATUS=],OCT,J,[MICWA+1=],OCT,MICWA+1,[MIOWD=],OCT,MIOWD
1183 ];TM10B
1184 IFN TM03S,[
1185         .ERR UBA errors? More gentle cleanup? 
1186         TTNE CS1,%TM1MP\%TM1TE  ;Cbus parity or transfer error?
1187          TTNE FS,%TMSES         ;And no formatter error?
1188           SKIPA                 ;Yes and yes (no) (what?). Controller error
1189            BUG INFO,[MTAPE: RH11 ERROR, STATUS=],OCT,MGEMTC,[TM STATUS=],OCT,MGEMTS
1190         TTNE FS,%TMSES          ;Formatter error?
1191          BUG INFO,[MTAPE: FORMATTER ERROR, STATUS=],OCT,MGEMTS
1192         PUSHJ P,TMINIC          ;Go reinit controller
1193 ];IFN TM03S
1194         SKIPL A,MGCABN(W)       ;Any buffers owned by PI routines?
1195          PUSHJ P,IMEMR          ;Yes, give them back to system
1196         SETOM MGCABN(W)         ;No PI buffer any more
1197         HRLZI B,%MAERR          ;Flag error detected by PI level
1198         IORM B,MSRAC(W)         ;Store in transport status word
1199         MOVE Q,[-MGQDLL,,MGQD0-1];Reset Q PDL to base of this unit's stack,
1200         MOVE T,MSLCTB           ; thus flushing whatever command is in progress
1201         IMUL T,W                ;Find offset to base of Q PDL for this unit
1202         ADD Q,T                 ;Add to prototype unit 0 QDP pointer,
1203         PUSH P,Q                ; and save it away
1204         MOVE Q,[-MSCBL-1,,MSCB0-1]      ;Get command list input pointer
1205         ADD Q,T                 ;Offset it to this unit's command queue,
1206         MOVEM Q,MTCMBP(W)       ;And save it as new MP (input) queue pointer
1207         MOVE Q,[4400,,MSCB0-1]  ;Get new command list output pointer
1208         ADD Q,T                 ;Offset correctly for this unit,
1209         MOVEM Q,MGCMBP(W)       ;And save as PI (output) command queue pointer
1210         MOVSI B,%MAREW          ;Does initting xport stop TM03 rewind?
1211         ANDCAM B,MSRAC(W)       ;Say not rewinding
1212         SKIPN MSCRW(W)          ;If reading,
1213          JRST POPQJ             ; we're done. Restore Q and exit
1214         SKIPN MSNBOL(W)         ;Writing. Any buffers on list?
1215          JRST POPQJ             ;No, restore Q and exit
1216         DO.                     ;Here to free buffers on IO list
1217          HRRZ A,MSBUFP(W)       ;Get buffer pointer from head of chain
1218          LDB T,[MLO,,MEMBLT(A)] ;Get back pointer (next buffer)
1219          HRRM T,MSBUFP(W)       ;Make next buffer head of chain
1220          PUSHJ P,IMEMR          ;Free current buffer
1221          SOSLE MSNBOL(W)        ;Decrement count, check for more
1222          JRST TOP.              ;More, loop back
1223         ENDDO.
1224         SETZM MSBUFP(W)         ;Mark list as empty
1225         JRST POPQJ              ;Restore Q and return
1226
1227 IFN TM10B,[
1228 ;Wait for control word to get written
1229 ;
1230 MGWCWC: SKIPE MICWA+1           ;Control word written?
1231          POPJ Q,                ;Yes, return to caller
1232         CONO MTS,4              ;No, tell DF10 to write it
1233 MGWCW1: SKIPE MICWA+1           ;Written yet?
1234          JRST MGWCW2            ;Good, done
1235         PUSHJ Q,CPOPJ           ;Not written. Dismiss interrupt and wait
1236         JRST MGWCW1             ;We're back. See if written yet.
1237
1238 MGWCW2: MOVE I,MGCMTC(W)
1239         MOVE J,MGCMTS(W)        ;Restore status
1240         TLO J,10                ;Set control word written
1241         POPJ Q,                 ;Return to caller
1242 ];IFN TM10B
1243
1244 IFN TM10A,[
1245 MGDCSI: SKIPA A,[BLKI MTC,MIOWD]
1246 MGDCSO:  MOVE A,[BLKO MTC,MIOWD]
1247         MOVEM A,MAGLOC
1248         MOVE A,[JSR MGDBRK]
1249         MOVEM A,MAGLOC+1
1250         POPJ Q,
1251 ];IFN TM10A
1252
1253 IFN TM03S,[
1254 ;Note this one's called on P PDL
1255 TMINIC: IORDI A,%TMTC           ;Get TC reg value
1256         ANDI A,MTSELM           ;Keep interesting bits only
1257         IORDI B,%TMCS2          ;Get CS2
1258         ANDI B,7                ;Keep selected "drive" (TM03) number only
1259         MOVEI T,%TM2CC
1260         IOWRI T,%TMCS2          ;Clear controller logic
1261         IOWRI B,%TMCS2          ;Reselect TM03
1262         IOWRI A,%TMTC           ;Reselect transport
1263         MOVX T,%TMCLR           ;Do a formatter clear command
1264         IOWRI T,%TMCS1
1265         POPJ P,
1266 ];IFN TM03S
1267
1268 \f
1269 SUBTTL MAG TAPE PI LEVEL WRITE
1270
1271 MGWRIT: PUSHJ Q,MGGXPT          ;Select desired transport
1272 IFN TM10P,[
1273         TXNE J,%T1STH\%T1SRW\%T1SWL     ;Write locked, hung or rewinding?
1274          JRST MGERR             ;Not a good thing
1275 ]
1276 IFN TM03S,[
1277         TTNE FS,%TMSFR          ;Formatter ready?
1278          TTNN FS,%TMSOL         ;Transport on line?
1279           JRST MGERR            ;No or no, can't do operation
1280         TTNE FS,%TMSWL          ;Transport write locked?
1281          JRST MGERR             ;Shouldn't happen, we checked at open.
1282 ]
1283         MOVSI A,%MACTH
1284         TDNE A,MSRAC(W)         ;Core alloc want quit temporarly?
1285          JRST [ PUSHJ Q,CPOPJ   ;OK, wait a while
1286                 JRST MGWRIT ]   ;Then go back and try again
1287         MOVEM W,MGUNIT          ;Set unit
1288         HRREI B,-MGNRTY         ;Number of retries
1289         MOVEM B,MGERRC(W)       ;Store error count
1290         MTDEQB A                ;Get buffer to write off list
1291         MOVEM A,MGCABN(W)       ;Note this buffer active at PI
1292         LDB B,[MWC,,MEMBLT(A)]  ;Get word count from buffer
1293         MOVNS B                 ;B -> -COUNT
1294         HRLZS B                 ;B -> -COUNT,,0
1295 IFN KL10P,LSH B,4               ;Shift if KL10 data channel
1296 IFN KL10P,MOVE R,A              ;Save core page number for cache sweep
1297 IFE TM03S,[                     ;TM03S IOWD is -COUNT,,ITS PAGE
1298         LSH A,10.               ;Convert buffer number to memory address
1299         SUBI A,1                ;Address - 1
1300 ]
1301         HRRM A,B                ;B -> -COUNT,,ADDRESS-1; an IO word
1302 IFN TM10B,DATAO MTS,[MICWA]     ;Tell DF10 where IO channel program is
1303 IFN TM10A,PUSHJ Q,MGDCSO        ;
1304         MOVEM B,MIOWD           ;Put IO word where controller looks
1305         MOVEM B,LMIOWD          ;Remember what we're about to do
1306 IFN TM10P,SETZM MIOWD+1         ;Stop after one operation
1307 IFN KL10P,[
1308         PUSHJ P,CSHSWP          ;Unload buffer from cache into core
1309           CAI
1310 ]
1311 MGWRT2:
1312 IFN TM10P,[
1313         MOVE B,MTCONO(W)        ;Get prototype CONO word
1314         CONO MTC,MWRITE(B)      ;Perform WRITE operation
1315 ]
1316 IFN TM03S,[
1317         HLRE A,MIOWD            ;Get PDP10 word count
1318         ASH A,1                 ; * 2
1319         IOWRI A,%TMWC           ; = number of unibus words to transfer
1320         HLRE A,MIOWD            ;Get PDP10 word count again
1321         IMUL A,MTWTFC(W)        ;Convert to tape frame count
1322         IOWRI A,%TMFC           ;Set tape frames to write
1323         HRRZ A,MIOWD            ;Get ITS page to transfer to
1324         LSH A,1                 ;Convert ITS pg # to DEC pg #
1325         TXO A,%UQVAL            ;Valid mapping, I should hope
1326         IOWRI A,UBAPAG+IUTPG_1  ;Set up first half of UBA mapping
1327         TXO A,1                 ;Next DEC page number
1328         IOWRI A,UBAPAG+IUTPG_1+1        ;Set second half of UBA mapping
1329         MOVEI A,IUTPG_14                ;Unibus address to DMA to
1330         IOWRI A,%TMBA           ;Tell controller
1331         MOVX A,%TM1IE\%TMWRT    ;Write, enable interrupts
1332         IOWRI A,%TMCS1          ;Start controller
1333 ]
1334         PUSHJ Q,MGWTJD          ;Wait for job done
1335          JRST MGWERR            ;Error, go attempt to repair
1336
1337 ;Here if tape written OK
1338 MGWRT3: MOVE A,MGCABN(W)        ;Get buffer number
1339         HRLZI B,%MAETW+%MAERR   ;End of tape check
1340 IFN TM10P,TXNE J,%T1SET         ;Controller says we're at EOT?
1341 IFN TM03S,TTNE FS,%TMSET
1342          IORM B,MSRAC(W)        ;Tell MP
1343         LDB T,[MUR,,MEMBLT(A)]  ;Get buffer flavor from buffer
1344         CAIE T,MUMGB            ;Still a magtape buffer?
1345          BUG HALT,[MT BUF CHANGED INTO SOME OTHER KIND??]
1346         SETOM MGCABN(W)         ;No buffer active at PI anymore
1347         PUSHJ P,IMEMR           ;Return buffer to system
1348         MOVSI A,%MAMSO          ;Note tape has moved since open
1349         IORM A,MSRAC(W)
1350         ;JRST MGCMDR ;Falls through
1351
1352 ;General exit routine for most PI-level command handlers
1353 ; Check command queue for more commands.
1354 ;  If no further commands, dismiss interrupt.
1355 ;  If further commands queued, wait for this one to finish, then fetch
1356 ;   and begin processing of next command.
1357 ;
1358 MGCMDR: SOS MSCMDC(W)           ;Decrement command count
1359         SETOM MGUNIT            ;Reset active unit
1360         SKIPG MSCMDC(W)         ;Any more commands?
1361          JRST MGCMR1            ;No. Go see about other units
1362 IFN TM10P,[
1363         MOVE B,MTCONO(W)
1364         CONO MTC,MNOPIN(B)      ;Tell controller to interupt when unit ready
1365         MOVEM W,MGUNIT          ;Set up unit number again for MGWTJD
1366         PUSHJ Q,MGWTJD          ;Go wait for unit to finish current command
1367          JRST MGERR             ;Oops
1368         SETOM MGUNIT            ;No unit waiting any more
1369 ];IFN TM10P
1370         POPJ Q,                 ;Return on Q PDL. Most likely this will
1371                                 ; transfer control to MGNCMD routine at
1372                                 ; base of PDL, which will fetch and execute
1373                                 ; next command.
1374
1375 MGCMR1:
1376 IFN NMTCS-1,[
1377 ;Ought to check other transports for commands to start.
1378 ; For now, will get started by 1/2 second timeout, if nothing else.
1379         .ERR Unfinished multi-transport code at MGCMR1
1380 ];IFN NMTCS-1   
1381         POPJ P,                 ;No more, return on P to dismiss interrupt
1382
1383
1384 \f
1385 ;CONTROLLER DETECTED ERROR ON WRITE OPERATION
1386 ; Retry, or give up, or write some blank tape and then try again, 
1387 ; depending on the type of error.
1388 ;
1389 MGWERR:
1390 IFN TM10P,[
1391 IFN TM10B,SETZM MIOWD           ;Seems to do one record anyway
1392 IFN TM10A,[     
1393         MOVE A,[-1,,MGVTC-1]
1394         MOVEM A,MIOWD           ;Specify one record to space back cmd.
1395 ]
1396         TXNE J,%T1STH\%T1SRW\%T1SIO\%T1SET\%T1SWL       ;Bad types of errors
1397          JRST MGERR             ;OK, give up
1398         AOSL MGERRC(W)          ;Still retrying?
1399          JRST MGERR             ;No, give up
1400         MOVE B,MTCONO(W)
1401         CONO MTC,MSPRR(B)       ;Space reverse one record
1402         PUSHJ Q,MGWTJD          ;Wait for job done
1403          JRST MGERR             ;Error
1404         MOVE B,LMIOWD           ;Get last operation's IOWD
1405         MOVEM B,MIOWD           ;We're going to try it again
1406         MOVE B,MTCONO(W)        ;Get prototype CONO
1407         CONO MTC,14000(B)       ;Write with extended EOR gap
1408         PUSHJ Q,MGWTJD          ;Wait for completion
1409          JRST MGWBT             ;Lost again, retry some more
1410         JRST MGWRT3             ;Worked, return to normal write sequence
1411 ];IFN TM10P
1412 IFN TM03S,[
1413         TTNE ERR,%TMERM\%TMEUS\%TMEFS\%TMEIR\%TMEIF\%TMEMC\%TMECT\%TMENX\%TMEOI
1414          JRST MGERR             ;Fatal errors
1415         TTNN FS,%TMSOL          ;On line?
1416          JRST MGERR             ;This isn't so good either
1417         TTNE ERR,%TMEFC\%TMENG\%TMEMD\%TMEIC\%TMECE\%TMECS\%TMEFL
1418          JRST MGWER1            ;Error which retrying might fix
1419
1420 ;Formatter seems happy. Check channel status before returning
1421 ; Currently this only catches the case where there was an RH11 error
1422 ; but no TM03 error, and thus should always end up jumping to MGERR.
1423 ; Formatter errors on which it might be OK to get here are %TMECE,
1424 ; %TMECS, %TMEFL, but someone needs to test this...
1425         TTNE CS1,%TM1TE         ;Transfer error?
1426          TTNE FS,%TMSES         ;And not formatter error?
1427           CAIA
1428            JRST MGERR           ;Just lose for now
1429         BUG INFO,[MT: ACCEPTING QUESTIONABLE WRITE OPERATION]
1430         JRST MGWRT3
1431
1432 ;Retry errors
1433 MGWER1: AOSL MGERRC(W)          ;Still retrying?
1434          JRST MGERR             ;No, give up
1435         BUG INFO,[MT: RETRYING WRITE OPERATION]
1436         PUSHJ P,TMINIC          ;Hit controller with hammer
1437         MOVEI B,1
1438         MOVEM B,MGSPCD(W)       ;1 record
1439         PUSHJ Q,MGSPCR          ;Reselect transport space back a record
1440         TTNE FS,%TMSTM          ;Stopped on EOF?
1441          SOSGE MGEOFR(W)        ;Yes, one less EOF in front of us
1442           SETZM MGEOFR(W)       ;But never less than zero
1443         PUSHJ P,TMINIC          ;Hit controller with hammer again
1444         PUSHJ Q,MGGXPT          ;Set up transport again
1445         MOVEI B,%TMER3\%TM1IE
1446         IOWRI B,%TMCS1          ;Erase a few inches of tape
1447         PUSHJ Q,MGWTJD          ;Wait for job done
1448          JRST MGERR             ;Can't get anything right...
1449         MOVE B,LMIOWD           ;Get last operation's IOWD
1450         MOVEM B,MIOWD           ;We're going to try it again
1451         JRST MGWRT2             ;Go back to write code and retry operation
1452 ];IFN TM03S
1453
1454 \f
1455 SUBTTL MAG TAPE PI LEVEL READ
1456
1457 MGREAD: PUSHJ Q,MGGXPT          ;Select desired transport
1458 MGRD0:  
1459 IFN TM10P,[
1460         TXNE J,%T1STH\%T1SRW\%T1SET     ;Unit hung, rewinding, or EOT
1461          JRST MGERR             ;Seems so, report error
1462 ]
1463 IFN TM03S,[
1464         TTNE FS,%TMSFR          ;Formatter ready?
1465          TTNN FS,%TMSOL         ;Transport on line
1466           JRST MGERR            ;No or no, can't do operation
1467 ]
1468         MOVE B,MGEOFR(W)        ;EOF's seen since last read
1469         CAIL B,2                ;Apparent logical EOT?
1470          JRST MGERR             ;Yes, can't read anything
1471         SKIPE MSCRW(W)          ;Make sure open for reading
1472          BUG HALT,[MT: CHN NOT OPEN FOR READING]
1473         MOVSI B,%MACTH          ;Core allocator wants to wait?
1474         TDNN B,MSRAC(W)         ;Check in status word
1475          PUSHJ P,IOMQ           ;No, get a buffer
1476           JRST [PUSHJ Q,CPOPJ   ;Wanted to wait some or failed,
1477                 JRST MGREAD ]   ; wait a while, then start over
1478         MOVEM A,MGCABN(W)       ;Note active buffer at PI level
1479         MOVEI B,MUMGB
1480         DPB B,[MUR,,MEMBLT(A)]  ;Note buffer belongs to mag tape code
1481         MOVEM W,MGUNIT          ;Set active unit number
1482         HRREI B,-MGNRTY         ;Number of retries
1483         MOVEM B,MGERRC(W)       ;Store error count
1484 IFN KL10P, MOVE R,A             ;Get page for cache flush routine
1485 IFE TM03S,[                     ;TM03S IOWD is -COUNT,,ITS PAGE
1486         LSH A,10.               ;Convert buffer number to memory address
1487         SUBI A,1                ;address-1
1488 ]
1489 IFE KL10P,HRLI B,-2000          ;Get count half of IOWD
1490 IFN KL10P,HRLI B,-2000_4        ;The KL is, of course, different
1491         HRR B,A                 ;-count,,address-1
1492         MOVEM B,LMIOWD          ;Remember IOWD for possible retry
1493 IFN TM10B,[
1494         DATAO MTS,[MICWA]       ;Tell DF10 where the channel program is
1495         SETZM MICWA+1           ;Stop after one operation
1496 ]
1497 IFN TM10A,PUSHJ Q,MGDCSI
1498 IFN TM10P,SETZM MIOWD+1
1499 MGRD1:  MOVEM B,MIOWD           ;Save IOWD where channel expects it
1500         MOVEI B,2000            ;Assume for now that the record has 2K words
1501         MOVEM B,MGNWRD          ;Set up word count
1502 IFN KL10P,[
1503         PUSHJ P,CSHSWP          ;Ensure no residue of this page in cache
1504             CAIA
1505 ]
1506 IFN KS10P,CLRCSH                ;KS needs cache invalidated on read
1507 IFN TM10P,[
1508         MOVE B,MTCONO(W)        ;Get prototype CONO word
1509         CONO MTC,MREAD(B)       ;Issue READ command
1510 ]
1511 IFN TM03S,[
1512         HLRE A,MIOWD            ;Get PDP10 word count
1513         ASH A,1                 ; * 2
1514         IOWRI A,%TMWC           ; = number of unibus words to transfer
1515         SETZ A,                 ;Set FC to zero
1516         IOWRI A,%TMFC           ;Set tape frames to write
1517         HRRZ A,MIOWD            ;Get ITS page to transfer to
1518         LSH A,1                 ;Convert ITS pg # to DEC pg #
1519         TXO A,%UQVAL
1520         IOWRI A,UBAPAG+IUTPG_1  ;Set up first half of UBA mapping
1521         TXO A,1                 ;Next DEC page number
1522         IOWRI A,UBAPAG+IUTPG_1+1        ;Set second half of UBA mapping
1523         MOVEI A,IUTPG_14        ;Unibus address for DMA
1524         IOWRI A,%TMBA           ;Tell controller
1525         MOVX A,%TM1IE\%TMRDF    ;Read forward, enable interrupts
1526         IOWRI A,%TMCS1          ;Start controller
1527 ];IFN TM03S
1528 IFN TM10B,SETOM MGWCW           ;Tell MGWTJD to wait for control word written
1529         PUSHJ Q,MGWTJD          ;Wait for command to complete
1530          JRST MGRERR            ;Error, go do something. May be retry, correct
1531                                 ; MGNWRD if frame count error, or give up
1532 IFN TM03S,[
1533 ;Get true record size for TM03, which doesn't give a FC error on READ
1534 MGRD1A: TTNE FS,%TMSTM          ;Read a tape mark?
1535          JRST [ SETZM MGNWRD    ;Read a tape mark. No data, just EOF
1536                 JRST MGRD2 ]
1537         IORDI A,%TMFC           ;Get record size in tape frames
1538         ADD A,MTWTFC(W)         ;Round up to PDP10 words.
1539         SUBI A,1                ;Add frames_per_word - 1
1540         IDIV A,MTWTFC(W)        ;Get record size in PDP10 words
1541         MOVEM A,MGNWRD
1542 ];IFN TM03S
1543 ;Here if OK or error handler has fixed things up
1544 MGRD2:  MOVE A,MGCABN(W)        ;Get buffer we just wrote
1545         SETOM MGCABN(W)         ;No buffer active at PI level
1546         MTENQB A                ;Queue buffer up for MP level
1547         MOVE B,MGNWRD           ;Get number of words we read
1548         DPB B,[MWC,,MEMBLT(A)]  ;Set number of words in buffer
1549 IFN TM10P,TXNE J,%T1SEF         ;Read an EOF?
1550 IFN TM03S,TTNE FS,%TMSTM        ; i.e. a tape mark?
1551         IFSKP.
1552          SETZM MGEOFR(W)        ;No. Note no EOFs read since last record
1553         ELSE.
1554          MOVSI B,%MAESO+%MAEFA  ;EOF seen since open, EOF read ahead
1555          IORM B,MSRAC(W)        ;Note this in transport status word
1556          SETO B,
1557          DPB B,[MSEOFP,,MEMBLT(A)]      ;Set EOF flag in this buffer
1558          AOS A,MGEOFR(W)        ;Count EOFs
1559          CAIL A,2               ;Enough for EOT?
1560           JRST MGRD4            ;Logical EOT, space back over it
1561         ENDIF.
1562         MOVSI A,%MAMSO
1563         IORB A,MSRAC(W)         ;Note tape movement
1564 IFN TM10P,TXNE J,%T1SET         ;Real EOT reached?
1565 IFN TM03S,TTNE FS,%TMSET
1566          JRST MGRD3
1567         MOVE C,MSNBOL(W)        ;Get count of buffers on list
1568 IFN TM10P,TXNN J,%T1SEF         ;EOF?
1569 IFN TM03S,TTNN FS,%TMSTM
1570
1571 ;        CAIL C,6               ; or read ahead six records?
1572         JFCL                    ;Or just for the hell of it
1573
1574           JRST MGRD5            ;Yes, stop reading
1575         TLNN A,%MASTP           ;Somebody request we stop?
1576          JRST MGRD0             ;No, go back and read another record
1577                                 ;Yes, fall through to terminate read
1578 ;Here to terminate read command
1579 ;
1580 MGRD5:  MOVSI A,%MASTP+%MARAC   ;Clear read active, any read stop request
1581         ANDCAM A,MSRAC(W)
1582         JRST MGCMDR             ;Go to standard command return routine
1583
1584 ;Controller saw a real EOT
1585 ;
1586 MGRD3:  DPB B,[MSEOFP,,MEMBLT(A)]       ;Fake EOF
1587         DPB B,[420100,,MSRAC(W)] .SEE %MAETR    ;Indicate EOT on read
1588         JRST MGRD5              ;Terminate read
1589
1590 ;Here if logical EOT (two EOF's in a row)
1591 ; Back up till between the two EOF's
1592 ;
1593 MGRD4:  MOVSI A,%MAESO+%MARAC+%MASTP    ;SECOND EOF, LOGICAL EOT
1594         ANDCAM A,MSRAC(W)
1595         JRST MGSPRF             ;Space reverse one file
1596
1597 ;Error detected on read.
1598 ; Analyze error, retry read if it might help
1599 ;
1600 MGRERR:
1601 IFN TM10P,[
1602  IFN TM10B,[
1603         TXNE J,%T1SCP\%T1SNM\%T1SDP
1604          JRST MGERR             ;Channel error, forget it
1605  ]
1606         TXNE J,%T1STH\%T1SRW\%T1SIO\%T1SRC      ;Hard error?
1607          JRST MGERR             ;Yes, abandon read
1608         TXNE J,%T1SPE\%T1SDL%T1SBT      ;Parity, data-late, or bad tape?
1609          JRST MGMRT             ;Yes, a read retry might fix it
1610         TXNN J,%T1SRL           ;Record length error?
1611          JRST MGERR             ;No, who knows what is going on
1612
1613 ;Here if record length error. Adjust MGNWRD to reflect data actually read
1614 ;
1615 IFN TM10B,HRRZ A,MICWA+1
1616 IFN TM10A,HRRZ A,MIOWD          ;Get final control word
1617         HRRZ B,LMIOWD           ;Get original IOWD
1618         SUB A,B                 ;Calculate words read
1619 IFN TM10B,SOS A                 ;Channel funnyness
1620         CAIE A,1                ;Length of 1 may just be EOF indication
1621         IFSKP.
1622          TXNE J,%T1SEF\%T1SET   ;1 word, EOF? EOT?
1623           SETZM A               ;Yes, zero length record, just carries MSEOFP
1624         ENDIF.
1625         MOVEM A,MGNWRD          ;Save new record length
1626         JRST MGRD2              ;Go process as potentially correctly read data
1627 ];IFN TM10P
1628 IFN TM03S,[
1629         TTNE ERR,%TMERM\%TMEUS\%TMEFS\%TMEIR\%TMEIF\%TMEMC\%TMECT\%TMENX
1630          JRST MGERR             ;Fatal errors
1631         TTNN FS,%TMSOL          ;On line?
1632          JRST MGERR             ;This isn't so good either
1633         TTZ ERR,%TMEFC\%TMENG   ;Ignore NSG, Frame count error
1634         TTNE FS,%TMSPE          ;Phase encoded (1600BPI) mode?
1635          TTZ ERR,%TMECE\%TMECS  ;If so, ignore errors hardware already fixed
1636         TTZN ERR,%TMECE\%TMECS\%TMEFC\%TMENG\%TMEFL\%TMEMD\%TMEIC ;Retryable?
1637          JRST MGRER1            ;Nothing retrying will help
1638         TTNE FS,%TMSTM          ;Tape mark?
1639          JRST MGRER2            ;Yes, no point in retrying
1640         JRST MGMRT              ;OK, go retry read
1641
1642 ;Formatter seems happy. Check channel status before returning
1643 MGRER1: TTNE ERR,177777         ;Sanity check. Shouldn't be any errors left
1644          JRST MGERR
1645         TTNE CS1,%TM1TE         ;Transfer error?
1646          TTNE FS,%TMSES         ;And not formatter error?
1647           CAIA
1648            JRST MGERR           ;Just lose for now
1649 MGRER2: JRST MGRD1A
1650
1651 ];IFN TM03S
1652
1653 \f
1654 ;Retry a read operation
1655 ;
1656 MGMRT:  AOSL MGERRC(W)          ;Still retrying?
1657          JRST MGERR             ;No, give up
1658 IFN TM10P,[
1659  IFN TM10B,SETZM MIOWD
1660  IFN TM10A,[
1661         MOVE A,[-1,,MGVTC-1]
1662  ]
1663         MOVEM A,MIOWD           ;One record
1664         PUSHJ Q,MGDCSO
1665         MOVE B,MTCONO(W)
1666         CONO MTC,MSPRR(B)       ;Back up one record
1667         PUSHJ Q,MGWTJD          ;Wait till done
1668          JRST MGERR             ;No errors allowed
1669  IFN TM10A,PUSHJ Q,MGDCSI       ;Put back PI 1 BLKI
1670 ];IFN TM10P
1671 IFN TM03S,[
1672 ;This could be more refined
1673         PUSHJ P,TMINIC          ;Hit controller with hammer
1674         PUSHJ Q,MGGXPT          ;Set up transport again
1675         SETO A,
1676         IOWRI A,%TMFC           ;1 record
1677         MOVEI A,%TM1IE\%TMSPR   ;Space backwards command
1678         IOWRI A,%TMCS1          ;Do it
1679         PUSHJ Q,MGWTJD          ;Wait till finished
1680          JRST MGERR             ;Give up if error
1681 ];IFN TM03S
1682         MOVE B,LMIOWD           ;Get IOWD from last command
1683         JRST MGRD1              ;Try operation again
1684
1685 \f
1686 SUBTTL MAG TAPE PI LEVEL SPACING COMMANDS
1687 ;Space forward and space reverse are completely under conditionals
1688
1689 IFN TM03S,[
1690
1691 ;Space forward MGSPCD(W) records
1692 MGSPCF: PUSHJ Q,MGGXPT          ;Acquire transport
1693         TTNE FS,%TMSFR          ;Formatter ready?
1694          TTNN FS,%TMSOL         ;Transport on line
1695           JRST MGERR            ;No or no, can't do operation
1696         MOVEM W,MGUNIT          ;Note active transport
1697         MOVN A,MGSPCD(W)        ;Get -count
1698         IOWRI A,%TMFC           ;Tell controller
1699         MOVEI A,%TMSPF          ;Get command
1700         TXO A,%TM1IE            ;Turn on interrupts
1701         IOWRI A,%TMCS1          ;Start controller
1702         PUSHJ Q,MGWTJD          ;Wait till command completes
1703         IFNSK.                  ;Error?
1704          TTNE CS1,%TM1MP        ;Control parity err?
1705           JRST MGERR            ;Yes, nothing else valid
1706          TTNE FS,%TMSES         ;Formatter errors?
1707          IFSKP.
1708           PUSHJ P, TMINIC       ;No formatter errors, ignore RH errors
1709          ELSE.
1710           TTNN ERR,%TMEFC       ;Frame count error?
1711            JRST MGERR           ;Nope, must be important
1712           PUSHJ P,TMINIC
1713          ENDIF.
1714         ENDIF.
1715         POPJ Q,
1716
1717 ;Space forward record
1718 MGSPFR: MOVEI B,1               ;Do one record
1719         MOVEM B,MGSPCD(W)       ;Set count
1720         MOVSI B,%MAMSO          ;Note this command causes tape movement
1721         IORM B,MSRAC(W)         ;Set in transport software status
1722         PUSHJ Q,MGSPCF          ;Do spacing op
1723         TTNN FS,%TMSTM
1724          SETZB B,MGEOFR(W)      ;Count EOFs since last record. None here
1725         TTNE FS,%TMSTM
1726          AOS B,MGEOFR(W)        ;Saw one.
1727         CAIL B,2                ;Saw two?
1728          JRST MGSPRR            ;Back up over last one...
1729         JRST MGCMDR             ;Clean up and leave
1730
1731 ;Space forward file
1732 MGSPFF: MOVSI B,%MAESO          ;See if tape has already read ahead to EOF
1733         TDZE B,MSRAC(W)
1734          JRST MGCMDR            ;EOF already read during the read, done
1735         MOVEI B,1               ;Do one record
1736         MOVEM B,MGSPCD(W)       ;Set count
1737         MOVSI B,%MAMSO          ;Note this command causes tape movement
1738         IORM B,MSRAC(W)         ;Set in transport software status
1739         PUSHJ Q,MGSPCF          ;Space forward one record
1740         TTNN FS,%TMSTM
1741         IFSKP.                  ;Saw a TM
1742          AOS B,MGEOFR(W)        ;Saw one.
1743          CAIL B,2               ;Saw two?
1744           JRST MGSPRR           ;Yes, back up over last one, and leave
1745          JRST MGCMDR            ;No, OK, but we're done
1746         ENDIF.
1747         SETZB B,MGEOFR(W)       ;No tape mark, reset count of EOFs seen
1748 MGSPF1: MOVEM B,MGSPCD(W)       ;Set count to 0 (B zero from above)
1749         PUSHJ Q,MGSPCF          ;Do it
1750         TTNE FS,%TMSTM          ;Saw a EOF?
1751         IFSKP.                  ;No..
1752          TTNE FS,%TMSET         ;Saw an EOT?
1753           JRST MGERR            ;Really shouldn't happen
1754          JRST MGSPF1            ;Else go look for TM again
1755         ENDIF.
1756         AOS MGEOFR(W)           ;Saw one.
1757         JRST MGCMDR             ;EOF read. done
1758
1759 ;Space reverse MGSPCD(W) records
1760 MGSPCR: PUSHJ Q,MGGXPT          ;Set up transport and get status
1761         TTNE FS,%TMSFR          ;Formatter ready?
1762          TTNN FS,%TMSOL         ;Transport on line
1763           JRST MGERR            ;No or no, can't do operation
1764         TTNE FS,%TMSBT          ;At BOT?
1765          POPJ Q,
1766         MOVEM W,MGUNIT          ;Save selected transport
1767         MOVN A,MGSPCD(W)        ;Get -count
1768         IOWRI A,%TMFC           ;Tell controller
1769         MOVEI A,%TMSPR          ;Space Reverse command
1770         TXO A,%TM1IE            ;Turn on interrupts
1771         IOWRI A,%TMCS1          ;Start controller
1772         PUSHJ Q,MGWTJD          ;Wait till command completes
1773         IFNSK.                  ;Error?
1774          TTNE CS1,%TM1MP        ;Control parity err?
1775           JRST MGERR            ;Yes, nothing else valid
1776          TTNE FS,%TMSES
1777          IFSKP.
1778           PUSHJ P,TMINIC
1779          ELSE.
1780           TTNN ERR,%TMEFC       ;Frame count error?
1781            JRST MGERR           ;Nope, must be important
1782           PUSHJ P,TMINIC
1783          ENDIF.
1784         ENDIF.
1785         POPJ Q,
1786
1787 ;Space reverse one record
1788 MGSPRR: MOVEI B,1
1789         MOVEM B,MGSPCD(W)       ;1 record
1790         MOVSI B,%MAMSO          ;Note this command causes tape movement
1791         IORM B,MSRAC(W)         ;Set in transport software status
1792         PUSHJ Q,MGSPCR
1793         TTNE FS,%TMSTM          ;Stopped on EOF?
1794          SOSGE MGEOFR(W)        ;Yes, one less EOF in front of us
1795           SETZM MGEOFR(W)       ;But never less than zero
1796         JRST MGCMDR             ;Leave through general exit     
1797
1798 ;Space reverse fill
1799 MGSPRF: MOVSI B,%MAESO          ;See if tape has already read ahead to EOF
1800         TDNN B,MSRAC(W)
1801          JRST MGSPR2            ;No, we can just do command
1802 MGSPR1: MOVEI B,1
1803         MOVEM B,MGSPCD(W)
1804         PUSHJ Q,MGSPCR          ;Skip back 1 record, should backup over EOF
1805         TTNN FS,%TMSTM          ;Tape mark seen?
1806          JRST MGSPR1            ;Well, apparently not
1807         MOVSI B,%MAESO
1808         ANDCAM B,MSRAC(W)       ;Turn off EOF-read-ahead flag
1809 MGSPR2: SETZ B,
1810         MOVEM B,MGSPCD(W)       ;Space backwards the maximum number of records
1811         PUSHJ Q,MGSPCR          ;Do it
1812         TTNN FS,%TMSBT          ;BOT?
1813          TTNE FS,%TMSTM         ;Tape mark seen?
1814           JRST MGCMDR           ;Yes or Yes, all done
1815         JRST MGSPR2             ;No, go back and try to find one.
1816
1817 ];End TM03S way back
1818
1819 \f;Rewind commands
1820 ;
1821 MGRWND:
1822 IFN TM10P,MOVEI B,MREWND        ;Normal rewind
1823 IFN TM03S,MOVEI B,%TMREW
1824         CAIA
1825 MGRWDM:
1826 IFN TM10P, MOVEI B,MRWNDD       ;Rewind and dismount
1827 IFN TM03S, MOVEI B,%TMUNL
1828         MOVEM B,MGSPCD(W)       ;Set up command
1829         PUSHJ Q,MGRWD1          ;Call action routine
1830         JRST MGCMDR
1831
1832 ;Action routine for rewind commands
1833 MGRWD1: PUSHJ Q,MGGXPT
1834 IFN TM03S,[
1835         TTNE FS,%TMSFR          ;Formatter ready?
1836          TTNN FS,%TMSOL         ;Transport on line
1837           JRST MGERR            ;No or no, can't do operation
1838 ]
1839         MOVEM W,MGUNIT
1840         MOVE B,MGSPCD(W)        ;Get desired command
1841 IFN TM10P,[
1842         ADD B,MTCONO(W)
1843         CONO MTC,(B)
1844 ]
1845 IFN TM03S,[
1846         TXO B,%TM1IE
1847         IOWRI B,%TMCS1
1848 ]
1849         PUSHJ Q,MGWTJD          ;Start controller and wait till done
1850         IFNSK.
1851          TTNE FS,%TMSES
1852           JRST MGERR            ;Oops.
1853         ENDIF.
1854         SETZM MGEOFR(W)         ;Seen no EOFs since last record
1855
1856 ;Here after rewind command has started.
1857 ;  Two possibilities: Tape is rewound already, or controller is finished
1858 ;  but tape is still rewinding.
1859 IFN TM10P,[
1860 MGRWD2: TXNN J,%T1SRW           ;Slave still rewinding tape?
1861          JRST MGRWD3            ;No, at BOT
1862         PUSHJ Q,CPOPJ           ;Wait some.
1863         CONI MTS,J              ;Get status again
1864         MOVEM J,MGCMTS(W)       ;Update in memory
1865         JRST MGRWD2             ;Go see if we're done yet.
1866
1867 ;Here when tape has rewound
1868 MGRWD3: MOVE T,TIME             ;Wait 1 second more
1869         ADDI T,30.              ;This is an attempt to fix a hardware bug
1870         MOVEM T,MGJDTI
1871 MGRWD4: MOVE T,TIME
1872         CAML T,MGJDTI           ;Check time
1873          JRST MGRWD5            ;Finished waiting, go clean up
1874         PUSHJ Q,CPOPJ           ;No, wait some more
1875         JRST MGRWD4
1876
1877 MGRWD5: MOVSI A,%MAMSO+%MAREW
1878         ANDCAM A,MSRAC(W)       ;Say not rewinding, hasn't moved
1879         SETZM MGJDTI            ;Clear timeout
1880         POPJ Q,
1881 ];IFN TM10P
1882 IFN TM03S,[
1883 ;This could be a lot smarter; should dismiss the command completely
1884 ; after rewind is started, and just scan for rewinding transports
1885 ; when a SSC interrupt is received. This change is also necessary
1886 ; to make multiple slaves work right; currently the rewinding unit
1887 ; holds active unit (MGUNIT) until the rewind is completed.
1888 MGRWD2: TTNN FS,%TMSPP          ;Transport still rewinding?
1889          JRST MGRWD3            ;No, go finish up
1890         PUSHJ Q,CPOPJ           ;Dismiss interrupt, wait a while
1891         PUSHJ Q,MGGXPT          ;Get right slave, set up status
1892         JRST MGRWD2
1893
1894 MGRWD3: MOVSI A,%MAMSO+%MAREW
1895         ANDCAM A,MSRAC(W)       ;Say not rewinding, hasn't moved
1896         POPJ Q,
1897 ];IFN TM03S
1898 \f
1899 ;SKIP TO LOGICAL EOT
1900 ;
1901 MGSEOT: PUSHJ Q,MGGXPT          ;Get transport
1902 IFN TM10P,[
1903         TXNE J,%T1STH\%T1SRW    ;Hung or rewinding?
1904          JRST MGERR
1905 ]
1906 IFN TM03S,[
1907         TTNE FS,%TMSFR          ;Formatter ready?
1908          TTNN FS,%TMSOL         ;Transport on line
1909           JRST MGERR            ;No or no, can't do operation
1910 ]
1911         MOVEM W,MGUNIT          ;Set active unit
1912 IFN TM10P,TXNE J,%T1SBT         ;BOT?
1913 IFN TM03S,TTNE FS,%TMSBT
1914          JRST MGVTCK            ;Yep, do virgin tape check
1915
1916 ;Not at BOT
1917 ; Do we have enough CONDITIONALS yet?
1918 MGNVT:  
1919 IFN TM10P,[
1920         MOVE B,MTCONO(W)        ;Get CONO word
1921  IFN TM10A,[
1922         PUSHJ Q,MGDCSO
1923         MOVE A,[-1,,MGVTC-1]
1924         MOVEM A,MIOWD           ;Tell it to move one record
1925  ]
1926  IFN TM10B,SETZM MIOWD
1927         CONO MTC,MSPRR(B)       ;Space reverse first
1928 ];IFN TM10P
1929 IFN TM03S,[
1930         SETO B,                 ;Space backwards one record
1931         IOWRI B,%TMFC
1932         MOVEI B,%TMSPR\%TM1IE
1933         IOWRI B,%TMCS1
1934 ];IFN TM03S
1935         PUSHJ Q,MGWTJD          ;Wait till done
1936         IFNSK.
1937          TTNE FS,%TMSES
1938           JRST MGERR
1939         ENDIF.
1940         SETZM MGEOFR(W)
1941         AOS MGEOFR(W)           ;Claim to have seen one EOF
1942 MGEOT2: 
1943 IFN TM10P,[
1944         MOVE B,MTCONO(W)
1945         CONO MTC,MSPFF(B)       ;Skip forward to EOF
1946         PUSHJ Q,MGWTJD
1947          JRST MGERR
1948 ]
1949 IFN TM03S,[
1950         AOS MSCMDC(W)           ;Kludge so MGSPFF will return here.
1951         PUSHJ Q,MGSPFF          ;Space forward file
1952 ]
1953         MOVSI B,%MAETR          ;See if we hit real EOT
1954 IFN TM10P, TXNE J,%T1SET
1955 IFN TM03S, TTNE FS,%TMSET
1956          IORM B,MSRAC(W)        ;Yep, tell MP
1957 IFN TM10P,[
1958         MOVE B,MTCONO(W)
1959  IFN TM10A,[
1960         MOVE A,[-1,,MGVTC-1]
1961         MOVEM A,MIOWD           ;One record
1962  ]
1963  IFN TM10B,SETZM MIOWD
1964         CONO MTC,MSPFR(B)       ;Space forward one record
1965 ]
1966 IFN TM03S,[
1967         SETO B,
1968         IOWRI B,%TMFC
1969         MOVEI B,%TMSPF\%TM1IE
1970         IOWRI B,%TMCS1
1971 ]
1972         PUSHJ Q,MGWTJD
1973         IFNSK.
1974          TTNE FS,%TMSES
1975          JRST MGERR
1976         ENDIF.
1977         MOVSI B,%MAETR          ;Check for real EOT again
1978 IFN TM10P,TXNE J,%T1SET
1979 IFN TM03S,TTNE FS,%TMSET
1980          IORM B,MSRAC(W)
1981 IFN TM10P,TXNN J,%T1SEF         ;Is this another EOF?
1982 IFN TM03S,TTNN FS,%TMSTM        ;(i.e. a tape mark)
1983          JRST MGEOT2            ;No, not at logical EOT. Go try again
1984 IFN TM10P,[
1985         MOVE B,MTCONO(W)        ;Yes, at logical EOT, Back up over 1 EOF
1986         CONO MTC,MSPRF(B)       ;Space back one file
1987 ]
1988 IFN TM03S,[
1989         SETO B,
1990         IOWRI B,%TMFC
1991         MOVEI B,%TMSPR\%TM1IE
1992         IOWRI B,%TMCS1
1993 ]
1994         PUSHJ Q,MGWTJD
1995         IFNSK.
1996          TTNE FS,%TMSES
1997          JRST MGERR
1998         ENDIF.
1999         MOVSI B,%MAEOF+%MAETR   ;Tell MP at EOF, EOT
2000         IORM B,MSRAC(W)
2001         JRST MGCMDR
2002 \f
2003 ;Check for virgin tape
2004 MGVTCK: MOVE T,TIME
2005         ADDI T,60.              ;Set a two second timeout
2006         MOVEM T,MGEOTT(W)       ; before we must see an EOT
2007 IFN TM10P,[
2008  IFN TM10B,[
2009         SETZM MIOWD
2010         DATAO MTS,[MICWA]
2011  ]
2012  IFN TM10A,[
2013         MOVE A,[-1,,MGVTC-1]
2014         MOVEM A,MIOWD
2015         PUSHJ Q,MGDCSO
2016  ]
2017         MOVE B,MTCONO(W)
2018         CONO MTC,MREAD(B)       ;Read record. will time out if no EOF marks
2019 MGVTC1: CONI MTS,J
2020         MOVEM J,MGCMTS(W)
2021         TXNE J,%T1SJD           ;Job done?
2022          JRST MGNVT             ;Yep,  not virgin tape
2023         TXNE J,%T1STH\%T1SIO    ;Transport hung or illegal operation?
2024          JRST MGERR             ;Yes, give up
2025         MOVE T,MGEOTT(W)        ;Get the timeout value
2026         CAMG T,TIME             ;Time up?
2027          JRST MGVT              ;Yes, it's a new tape
2028         PUSHJ Q,CPOPJ           ;Wait a while
2029         JRST MGVTC1             ;Go back and check again
2030 ];IFN TM10P
2031 IFN TM03S,[
2032         SETO B,
2033         IOWRI B,%TMFC           ;Do one record
2034         MOVEI B,%TMSPF\%TM1IE   ;Space forward command
2035         IOWRI B,%TMCS1
2036
2037 MGVTC1: IORDI T,%TMCS1          ;Get status
2038         TXNN T,%TM1GO           ;Still going?
2039         IFSKP.                  ;Yep.
2040          MOVE T,MGEOTT(W)       ;Get the timeout value
2041          CAMG T,TIME            ;Time up?
2042           JRST MGVT             ;Yes, it's a new tape
2043          PUSHJ Q,CPOPJ          ;Wait a while
2044          JRST MGVTC1            ;Go back and check again
2045         ENDIF.
2046         TXNE T,%TM1TE\%TM1MP    ;Controller error?
2047          JRST MGERR             ;Yes, bad
2048         IORDI T,%TMFS           ;Get formatter status
2049         TXNE T,%TMSES           ;Formatter error?
2050          JRST MGNVT             ;No error, not a new tape
2051         IORDI T,%TMERR          ;Get formatter error register
2052         TXNE T,%TMEFC           ;Frame Count error?
2053          JRST MGNVT             ;Yes, that is probably an OK tape
2054         JRST MGERR              ;Not FC, must be a real problem
2055 ];IFN TM03S
2056 \f
2057 ;Virgin tape. Abort operation in progress, rewind tape
2058 MGVT:   
2059 IFN TM10P,[
2060         MOVE B,MTCONO(W)
2061         CONO MTS,31             ;Clear controller
2062         CONO MTC,MNOPIN(B)      ;Start new command to clear things out
2063         PUSHJ Q,MGWTJD
2064          JFCL                   ;Ignore errors
2065 ]
2066 IFN TM03S,[
2067         PUSHJ P,TMINIC
2068 ]
2069 IFN TM10P,MOVEI B,MREWND                ;Do a rewind
2070 IFN TM03S,MOVEI B,%TMREW
2071         MOVEM B,MGSPCD(W)
2072         PUSHJ Q,MGRWD1  
2073         SETZM MGEOFR(W)         ;No EOFs seen
2074         AOS MGEOFR(W)           ;???
2075         JRST MGCMDR             ;Done
2076
2077 ;Write EOT mark (two EOF's) on tape
2078 ;
2079 MGMEOT: PUSHJ Q,MGGXPT
2080 IFN TM10P,[
2081         TXNE J,%T1STH\%T1SRW\%T1SWL ;Hung, rewinding, or write locked...
2082          JRST MGERR
2083 ]
2084 IFN TM03S,[
2085         TTNE FS,%TMSFR          ;Formatter ready?
2086          TTNN FS,%TMSOL         ;Transport on line
2087           JRST MGERR            ;No or no, can't do operation
2088         TTNE FS,%TMSWL          ;Transport write locked?
2089          JRST MGERR             ;Shouldn't happen, we checked at open.
2090 ];IFN TM03S
2091         MOVEM W,MGUNIT          ;Note active unit
2092         SKIPE MTCEFW(W)         ;Check # of EOF's already written
2093         IFSKP.                  ;None. Need to write two
2094          AOS MSCMDC(W)          ;Kludge so MGWEOF will return here.
2095          AOS MTCEFW(W)          ;Increment EOF count
2096          PUSHJ Q,MGWEOF         ;Write an EOF
2097         ENDIF.
2098         MOVE A,MTCEFW(W)        ;Get EOF count
2099         SOSLE A                 ;Check for at least two EOF's written
2100         IFSKP.                  ;No, need one more on tape
2101          AOS MSCMDC(W)          ;Again, force MGWEOF to return
2102          AOS MTCEFW(W)          ;Incr EOF count
2103          PUSHJ Q,MGWEOF         ;Write EOF
2104         ENDIF.
2105         MOVE A,MSRAC(W)         ;Get transport software status
2106         TLNE A,%MANWT           ;Are we supposed to back up over last EOF?
2107         IFSKP.
2108          AOS MSCMDC(W)          ;Yes. Force MGSPRF to return, then...
2109          PUSHJ Q,MGSPRF         ; ...do space reverse file command
2110         ENDIF.
2111         MOVSI A,%MANWT          ;Note what we've done
2112         IORM A,MSRAC(W)         
2113         JRST MGCMDR             ;Leave through general exit routine
2114 \f
2115 ;Write one EOF mark on tape
2116 ;
2117 MGWEOF: PUSHJ Q,MGGXPT          ;Set up transport for IO
2118 IFN TM10P,[     
2119         TXNE J,%T1STH\%T1SRW\%T1SWL ;Hung, rewinding, or write locked...
2120          JRST MGERR             ; ..lose
2121 ]
2122 IFN TM03S,[
2123         TTNE FS,%TMSFR          ;Formatter ready?
2124          TTNN FS,%TMSOL         ;Transport on line
2125           JRST MGERR            ;No or no, can't do operation
2126         TTNE FS,%TMSWL          ;Transport write locked?
2127          JRST MGERR             ;Shouldn't happen, we checked at open.
2128 ]
2129         MOVEM W,MGUNIT          ;Remember active unit
2130 IFN TM10P,[
2131         MOVE B,MTCONO(W)        ;Get CONO word for this unit
2132         CONO MTC,MWEOF(B)       ;Execute Write EOF function
2133 ]
2134 IFN TM03S,[
2135         MOVEI B,%TM1IE\%TMWTM   ;Write tape mark, enable interrupts
2136         IOWRI B,%TMCS1          ;Do it
2137 ]
2138         PUSHJ Q,MGWTJD          ;Wait around till command is complete
2139         IFNSK.
2140          TTNE FS,%TMSES
2141          JRST MGERR
2142         ENDIF.
2143         MOVSI A,%MAMSO
2144         IORM A,MSRAC(W)         ;Note tape movement in software status
2145         JRST MGCMDR             ;Return through general exit routine
2146
2147 ;Get transport and controller status
2148 ;
2149 MGSTAT: PUSHJ Q,MGGXPT
2150         JRST MGCMDR
2151
2152 ;Write some blank space
2153 ;
2154 MGW3IN: PUSHJ Q,MGGXPT
2155 IFN TM10P,[
2156         TXNE J,%T1STH\%T1SRW\%T1SWL ;Hung, rewinding, or write locked...
2157          JRST MGERR
2158 ]
2159 IFN TM03S,[
2160         TTNE FS,%TMSFR          ;Formatter ready?
2161          TTNN FS,%TMSOL         ;Transport on line
2162           JRST MGERR            ;No or no, can't do operation
2163         TTNE FS,%TMSWL          ;Transport write locked?
2164          JRST MGERR             ;Shouldn't happen, we checked at open.
2165 ];IFN TM03S
2166         MOVEM W,MGUNIT          ;Note active transport
2167 IFN TM10P,[                     
2168 ;TM10 can't just write blank space, it has to write blank space followed
2169 ; by a data record
2170  IFN TM10B,[
2171         SETZM MIOWD             ;Tell TM10 to write 1-word record
2172         DATAO MTS,[MICWA]
2173  ]
2174  IFN TM10A,[
2175         MOVE A,[-1,,MGVTC-1]    ;1-word record
2176         MOVEM A,MIOWD
2177         PUSHJ Q,MGDCSO
2178  ]
2179         MOVE B,MTCONO(W)
2180         CONO MTC,MW3IN(B)       ;Write date record preceeded by 3-in gap
2181 ];IFN TM10P
2182 IFN TM03S,[
2183         MOVEI B,%TM1IE\%TMER3   ;Erase 3 inches command, enable interrupts
2184         IOWRI B,%TMCS1          ;Do it
2185 ];IFN TM03S
2186         PUSHJ Q,MGWTJD          ;Wait...
2187          JFCL                   ;Ignore errors (really should check kind)
2188 IFN TM10P,JRST MGSPRR           ;Now space record reverse over the bogus record
2189 IFN TM03S,JRST MGCMDR           ;TM03 does it right
2190
2191 \f
2192 SUBTTL .MTAPE UUO 
2193
2194 ;.MTAPE AC,
2195 ;       AC/     CHNM,,COMMAND
2196 ;               COMMAND/        COUNT,,FUNCTION
2197
2198 ;Called with    J/ AC field from UUO
2199
2200 AMTAPE: XCTR XR,[HLRZ R,(J)]    ;Get IO channel from user
2201         TRNE R,-NIOCHN          ;Legal channel?
2202          JRST ILUUO             ;Lose
2203         HRRZM R,UUAC(U)         ;Cause errors to report on the correct channel
2204         ADDI R,IOCHNM(U)        ;Form IOCHNM pointer
2205         HRRZ A,(R)              ; A: CLSTB/IOTTB index
2206         CAIL A,MTUAIX           ; Min index for tape
2207          CAILE A,MTBOX          ; Max
2208           POPJ P,               ; Laconic error reportage.
2209         LDB W,[MTXP(R)]         ;Get transport number
2210         CAME U,MTUSR(W)         ;Same user?
2211          POPJ P,                ;No, give up
2212         UMOVE A,(J)             ;Get Channel,,Command from user
2213         MOVEM A,MTMTAP(W)       ;Save it
2214         HRRZS A                 ;Get user address of Count,,Function word
2215         PUSHJ P,MTIECK          ;Check transport for error states
2216         UMOVE A,(A)             ;Get Count,,Function from user
2217         HRRZM A,MTMFNC(W)       ;Store function
2218         HLREM A,MTMCNT(W)       ; and count
2219         SKIPN MTMCNT(W)         ;Count of zero always means one, for
2220          AOS MTMCNT(W)          ; compatibility with the old code.
2221         HRRZS A                 ;Just Function
2222         CAIL A,NMTAPC           ;Command in range?
2223          POPJ P,                ;No...
2224         AOS (P)                 ;Command OK, skip return
2225         JRST @MTAPDT(A)         ;Go do command
2226
2227 MTAPDT: MTHANG                  ;0 Hang till tape motion done
2228         MTRWND                  ;1 Rewind
2229         MTRWDM                  ;2 Rewind and dismount
2230         MTWEOR                  ;3 Write EOR if appropriate
2231         MTW3IN                  ;4 Write 3 inches of blank tape
2232         MTWEOF                  ;5 Write EOF
2233         MTSPR                   ;6 Space records
2234         MTSPF                   ;7 Space files
2235         MTSPEOT                 ;10 Space to EOT
2236         MTSTOP                  ;11 Abort all operations immediately
2237         MTSBKS                  ;12 Set block size (to COUNT)
2238         MTRBKS                  ;13 Read block size (to AC)
2239 IFN 0,[
2240         MTRTSW                  ;14 Read Transport Information (to AC)
2241         MTRTEW                  ;15 Read Tape Error Word (to AC)
2242 ]
2243 NMTAPC==.-MTAPDT
2244
2245 ;Set block size for write
2246 ;
2247 MTSBKS: MOVE A,MTMCNT(W)        ;Desired blocksize
2248         CAIL A,4                ;Check reasonableness
2249          CAILE A,2000
2250           SOSA (P)              ;Fail if too big or too small
2251            MOVEM A,MTBLKS(W)    ;OK, change write-buffer size
2252         POPJ P,
2253
2254 ;Read current write blocksize
2255 ;
2256 MTRBKS: MOVE A,MTBLKS(W)        ;Get current write block size
2257         JRST APTUAJ             ;Return it
2258 \f
2259 ;Hang until all motion finished
2260 ;
2261 MTHANG: SKIPLE MSCMDC(W)        ;Check count of queued commands
2262          PUSHJ P,UFLS           ;Wait if there are any
2263         JRST MTIECK             ;Done, check for errors and return
2264
2265 ;Rewind, Rewind and dismount
2266 ;
2267 MTRWND: SKIPA B,[MGRWND]        ;Get "REWIND" PI level command
2268 MTRWDM:  MOVEI B,MGRWDM         ; or "REWIND and DISMOUNT" if appropriate
2269         SKIPE MSCRW(W)          ;Writing?
2270          JRST MTSOSP            ;Yes, error. Go undo skip rtn and exit
2271         MOVSI A,%MAREW          ;Note rewinding in software status
2272         IORM A,MSRAC(W)
2273         JRST MTCMD              ;Go queue command for PI level
2274
2275
2276 ;"Write End of Record" 
2277 ; This is really the FORCE system call, or should be.
2278 ;
2279 MTWEOR: SKIPG MTMDN(W)          ;MP level have an active buffer?
2280          POPJ P,                ;No, nothing to do
2281         SKIPE MSCRW(W)          ;Writing?
2282          JRST MTWBFD            ;Yes, go write buffer to tape
2283 MTSOSP: SOS (P)                 ;Not writing, error. Undo skip return
2284         POPJ P,                 ;Return
2285
2286 ;Write EOF
2287 ;
2288 MTWEOF: SKIPN MSCRW(W)          ;Writing?
2289          JRST MTSOSP            ;No, can't write EOF. Take error exit
2290         PUSHJ P,MTWEOR          ;Flush current buffer, if any
2291         MOVEI B,MGWEOF          ;Get PI level EOF routine
2292         AOS MTCEFW(W)           ;Increment count of EOF's written
2293         MOVSI TT,%MANWT         ;Flag something written on tape
2294         ANDCAM TT,MSRAC(W)
2295         JRST MTCMD              ;Queue MGWEOF command for PI level
2296
2297 ;Write blank tape
2298 ;
2299 MTW3IN: SKIPN MSCRW(W)          ;Error if tape not open for write
2300          JRST MTSOSP
2301         MOVEI B,MGW3IN          ;Get PI level command
2302         SETZM MTCEFW(W)         ;No EOF's since last record
2303         MOVSI TT,%MANWT
2304         ANDCAM TT,MSRAC(W)      ;Note written something to tape
2305         JRST MTCMD              ;Go queue command for PI
2306
2307 ;Space records, +=forward, -=back
2308 ;
2309 MTSPR:  SKIPE MSCRW(W)          ;Not allowed if writing
2310          JRST MTSOSP
2311         PUSHJ P,MTFLRA          ;Flush read-ahead, find out how far off we are
2312         ADD B,C                 ;Get records tape is ahead of user (EOF=record)
2313         MOVNS B                 ;Subtract this from user's request
2314         ADDB B,MTMCNT(W)        ;Adjust count
2315         JUMPE B,CPOPJ           ;If count is now zero, we are done
2316 MTSPR1: PUSHJ P,MTCNTR          ;Update user's copy in case PCLSR
2317         JUMPG B,MTSPFR          ;Space forward
2318         MOVEI B,MGSPRR          ;Get SPACE REVERSE command
2319         PUSHJ P,MTCMD           ;Queue it
2320         AOSGE B,MTMCNT(W)       ;Increment count, check if done
2321          JRST MTSPR1            ;More
2322         POPJ P,                 ;No more
2323
2324 MTSPFR: MOVEI B,MGSPFR          ;Get SPACE FORWARD command
2325         PUSHJ P,MTCMD           ;Queue it
2326         SOSLE B,MTMCNT(W)       ;Decr count, check if done
2327          JRST MTSPR1            ;More
2328         POPJ P,
2329
2330 ;This routine flushes readahead.  Call before doing a spacing operation
2331 ; this doesn't actually undo the effect on the drive of the read-ahead.
2332 ; It does make sure that read-ahead's effect can't change, then returns
2333 ; in B the number of records ahead (non-negative) and in C the number of
2334 ; EOF's ahead (0 or 1).  If called twice it will return zero the second
2335 ; time.  Be sure to update your parameters.
2336 ;
2337 MTFLRA: PUSHJ P,MTCNTR          ;Make sure user space is writable first
2338         MOVSI B,%MASTP
2339         MOVSI T,%MARAC
2340         IORM B,MSRAC(W)         ;Tell PI-level read routine to stop reading
2341         TDNE T,MSRAC(W)         ;Wait until PI level actually stops
2342          PUSHJ P,UFLS
2343         ANDCAM B,MSRAC(W)       ;Turn off %MASTP, things are now quiet
2344         SKIPLE MSCMDC(W)        ;Make sure PI level is completely inactive
2345          PUSHJ P,UFLS           ;Wait if necessary
2346         MOVE B,MSNBOL(W)        ;Get # bufs on read list (='s # records ahead)
2347         LDB C,[.BP (%MAEFA),MSRAC(W)] ;1 if EOF read ahead
2348         MOVSI T,%MAEFA          ;Clear read-ahead EOF 
2349         ANDCAM T,MSRAC(W)
2350         JRST MTCBFF             ;Go flush read-ahead buffers
2351 \f
2352 ;Space files, + = forward, - = back
2353 MTSPF:  SKIPE MSCRW(W)          ;Not allowed if writing
2354          JRST MTSOSP
2355         PUSHJ P,MTFLRA          ;Flush read-ahead
2356         MOVN B,C                ;Number of files tape is ahead of user
2357         ADDB B,MTMCNT(W)        ;Adjust desired count
2358         JUMPE B,CPOPJ           ;If now zero we are done
2359 MTSPF1: PUSHJ P,MTCNTR          ;Update user's count in case of PCLSR
2360         JUMPG B,MTSPFF          ;Go do forward if needed
2361         MOVEI B,MGSPRF          ;Get space reverse file command
2362         PUSHJ P,MTCMD           ;Queue it
2363         AOSGE B,MTMCNT(W)       ;Done?
2364          JRST MTSPF1            ;Nope
2365         POPJ P,
2366
2367 MTSPFF: MOVEI B,MGSPFF          ;Get space forward file command
2368         PUSHJ P,MTCMD           ;Do it
2369         SOSLE B,MTMCNT(W)       ;Count down
2370          JRST MTSPF1            ; till done
2371         POPJ P,
2372
2373 ;Update user's FUNCTION,,COUNT word in case he's PCLSR'd
2374 ;
2375 MTCNTR: HRRZ A,MTMTAP(W)
2376         MOVE T,MTMFNC(W)
2377         HRL T,MTMCNT(W)
2378         XCTR XW,[MOVEM T,(A)]
2379         POPJ P,
2380
2381 ;Get Controller status words to I,J
2382 ;
2383 MTSTAT: SKIPLE MSCMDC(W)        ;Wait till commands queued to PI level are done
2384          PUSHJ P,UFLS
2385         MOVEI B,MGSTAT          ;GET STATUS command
2386         PUSHJ P,MTCMD           ;Give to PI
2387         SKIPLE MSCMDC(W)        ;Wait till done
2388          PUSHJ P,UFLS
2389         MOVE I,MGCMTC(W)
2390         MOVE J,MGCMTS(W)
2391         POPJ P,
2392
2393 ;Go to EOT
2394 ;
2395 MTSPEOT:MOVEI B,MGSEOT          ;Get SPACE-TO-LOGICAL-EOT command
2396         JRST MTCMD              ;Queue it. Note read-ahead doesn't matter here
2397
2398 ;Stop whatever we are doing right now
2399 ; Very brute-force - throws away all pending commands, read-ahead buffers, etc.
2400 ;
2401 MTSTOP: CONO PI,UTCOFF          ;We are going to mess with buffer lists
2402         SETZM MSCMDC(W)         ;Poof, no more commands
2403         MOVE Q,[-MGQDLL,,MGQD0-1] ;Reset Q PDL pointer to base of stack
2404         MOVE T,MSLCTB
2405         IMUL T,W
2406         ADD Q,T
2407         MOVEM Q,MGQDLP(W)
2408         MOVE Q,[-MSCBL-1,,MSCB0-1] ;Reset command queue input pointer
2409         ADD Q,T
2410         MOVEM Q,MTCMBP(W)
2411         MOVE Q,[4400,,MSCB0-1]  ;Reset command queue output pointer
2412         ADD Q,T
2413         MOVEM Q,MGCMBP(W)
2414         SKIPL A,MTMDN(W)        ;Buffer active at MP level?
2415          PUSHJ P,IMEMR          ;Yes, release it
2416         SETOM MTMDN(W)          ;No buffer active at MP level
2417         SETZM MSMPRP(W)         ;Zero MP pointer into current buffer
2418         SETZM MSMPRC(W)         ;Zero count of available words in buffer
2419         PUSHJ P,MTCBFF          ;Flush any buffers queued for PI level
2420         CAME W,MGUNIT           ;Is interrupt level waiting for this unit?
2421          JRST UTCONJ            ;No, all set
2422         SETOM MGUNIT            ;Yes, say no unit waiting for interrupt.
2423                                 ;(Makes interrupt go away w/out doing anything)
2424 IFN TM10P,[
2425         CONI MTC,I              ;See what drive controller thinks it's using
2426         LDB B,[MUNITF,,I]
2427         CAME W,B                ;Same as the drive we're clearing?
2428          JRST UTCONJ            ;If not same unit, don't do anything
2429         MOVE B,MTCONO(W)        ;Yes, abort operation in progress
2430         CONO MTS,31             ;Stop the tape
2431         CONO MTC,(B)            ;Clear interupts
2432 ];IFN TM10P
2433 IFN TM03S,[
2434         IORDI B,%TMTC
2435         ANDI B,7                ;Get selected transport
2436         CAME W,B                ;Same?
2437          JRST UTCONJ
2438         PUSHJ P,TMINIC          ;Yes, go reinit controller
2439 ];IFN TM03S
2440         SKIPGE A,MGCABN(W)      ;Any buffers active at PI level?
2441          JRST UTCONJ            ;No
2442         PUSHJ P,IMEMR           ;Yes, return buffer to system
2443         SETOM MGCABN(W)         ;Say no buffer active at PI level
2444         JRST UTCONJ             ;Leave
2445
2446
2447 \f
2448