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