Consolidate license copies
[its.git] / system / imp.361
1 ;;; -*- Mode:MIDAS -*- 
2 ;;; Copyright (c) 1999 Massachusetts Institute of Technology
3 ;;;
4 ;;; This program is free software; you can redistribute it and/or
5 ;;; modify it under the terms of the GNU General Public License as
6 ;;; published by the Free Software Foundation; either version 3 of the
7 ;;; License, or (at your option) any later version.
8 ;;;
9 ;;; This program is distributed in the hope that it will be useful,
10 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
11 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
12 ;;; General Public License for more details.
13 ;;;
14 ;;; You should have received a copy of the GNU General Public License
15 ;;; along with this program; if not, write to the Free Software
16 ;;; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
17
18
19 IMPVRS==.IFNM2  ; Version of IMP code
20
21 IFN NCPP,.FATAL IMP Code doesn't support NCP any more!
22 IFNDEF IMPDBG,IMPDBG==:0        ;Random bits of debugging code
23 IFN IMPDBG,PRINTX /IMP Debugging code included
24 /
25
26 IFN KAIMP,[
27 $INSRT KAIMP
28 ];KAIMP
29
30 IFN KSIMP,[
31 $INSRT LHDH
32 IMPLW==400000                   ;Bit unused by hardware
33 ];IFN KSIMP
34 \f
35 ; IMP 1822 PROTOCOL INFORMATION (EXTENDED-LEADER VERSION)
36
37 ; The IMP leader is 96 bits long, usually organized as 3 words of 32 bits.
38 ; For further details, these documents are available from the Network
39 ; Information Center:
40 ;       IMP-HOST protocol: BBN Report No. 1822
41 ;       NCP protocol: NIC 8246, Host-to-Host Protocol for the ARPANET
42 ;       IP, TCP: Internet Protocol Transition Workbook, and
43 ;                Internet Protocol Implementor's Guide
44 ;
45 ; Here is the leader format used by the IMP code. This format uses
46 ; no IMP padding, assumes IP only, and expects all IMP<->HOST data
47 ; transfers in 32-bit mode.
48 ;
49 ; Previous versions of this code which supported NCP used a much more
50 ; complicated leader formatting scheme based on 36 bit transfers and
51 ; IMP padding. That scheme is dead, see SYSTEM;IMPOLD WTHNCP for details.
52 ;
53 ; All data from the IMP interface ends up in the -10 as left-justified
54 ; 32-bit words. Objects of less than 32 bits length, such as IP octets,
55 ; are stored in PDP10 ILDB byte order.
56 ;
57 ;------------------------------------------------------------------------
58 ;1:  4.9-4.6 not used (0)
59 ;    4.5-4.2 all 1's for new format, else old msg type (4=old nop)
60 ;    4.1-3.3 network number (0)
61 ;    3.2-2.8 not used (0)
62 ;        2.7 trace (ignored)
63 ;    2.6-2.4 leader flags (2.6 is to be ignored, 2.5-2.4 are not used!)
64 ;    2.3-1.5 message type
65 ;
66 ;2:  4.9-4.2 Handling type (7 for big buffers, 4 for small buffers,
67 ;                           0 for the control link)
68 ;    4.1-3.3 Host number on IMP
69 ;    3.2-1.5 IMP number
70 ;
71 ;3:  4.9-4.2 Link Number (High 8 bits of Message ID)
72 ;    4.1-3.7 Low 4 bits of Message ID (0) 
73 ;    3.6-3.3 Sub-type
74 ;    3.2-1.5 Message length
75 ;------------------------------------------------------------------------
76 ;4:  4.9-1.5 First word of IP datagram
77 ;    ....
78 ;------------------------------------------------------------------------
79 ;
80 ;In message types 2 and 6, the going-down status 16-bit word is
81 ;in word 3 bits 4.9-3.3.
82
83 ;3.6-3.3 of word 3 are the padding count for type 4 (nop) from host.
84 ;This is currently 0 (none).  Padding is only put on type-0 messages.
85
86 IMOTBP: 340400,,IMPILB+0        ;BYTE POINTER FOR MESSAGE FORMAT TYPE
87 IMTBP:  041000,,IMPILB+0        ;BYTE POINTER FOR MESSAGE TYPE FIELD
88 IMSABP: 043000,,IMPILB+1        ;BYTE POINTER FOR SOURCE ADDR FIELD (HOST+IMP)
89 IMSHBP: 241000,,IMPILB+1        ;BYTE POINTER FOR SOURCE HOST FIELD
90 IMSIBP: 042000,,IMPILB+1        ;BYTE POINTER FOR SOURCE IMP FIELD
91 IMLNBP: 341000,,IMPILB+2        ;BYTE POINTER FOR LINK NUMBER FIELD
92 IMSTBP: 240400,,IMPILB+2        ;BYTE POINTER FOR SUBTYPE FIELD
93 IMMLBP: 042000,,IMPILB+2        ;BYTE POINTER FOR MESSAGE LENGTH FIELD
94 \f
95
96
97 SUBTTL  ARPANET VARIABLES AND TABLES
98
99 EBLK
100
101 IMPN::          ;IMP DATA AREA CLEARED WHEN IMPUP
102
103 %IMXLN==:<<8159.-96.>+31.>/32.  ; Max # of 32-bit words in IMP regular msg,
104                 ; exclusive of leader and leader padding.  = 252.
105 IMPIBS: 0       ; Saved initial BLKI pointer for IP datagram read
106 IMPIDP: 0       ; Pointer to IP datagram being input at PI level
107 IMPODP: 0       ; Pointer to IP datagram being output at PI level
108
109 IFN KAIMP,[
110 IMPI:   0       ;-1 => IMPCHN INPUT INTERRUPT OCCURRED
111 IMPO:   0       ;-1 => IMPCHN OUTPUT INTERRUPT OCCURRED
112 IMPB:   0       ;-1 => IMPCHN FLAG INTERRUPT OCCURRED
113 IMPIH:  0       ;-1 => INPUT WANTS PIA = IMPCHN
114 IMPOH:  0       ;-1 => OUTPUT WANTS PIA = IMPCHN
115 ]
116 IFN KSIMP,[
117 IMPIEC: 0       ;Count of input errors while down.
118 ]
119 IMPIS:  0       ;INPUT STATE
120  %ISIDN==:-1    ; Network shut off
121  %ISIDL==:0     ; Normal - idle, not expecting input (i.e. between msgs)
122  %ISIGN==:1     ; Ignore input until end of current message (32 bit mode)
123  %ISIML==:2     ; Reading IMP initial leader    (32 bit mode)
124  %ISIID==:3     ; Reading IP datagram           (32 bit mode)
125
126 IMPOS:  0       ;OUTPUT STATE
127  %ISODL==:0     ; Not expecting output done (i.e. between messages)
128  %ISONP==:1     ; Sending NOP
129  %ISOID==:2     ; Sending IP Datagram
130  %ISOIL==:3     ; Sending IMP leader
131
132 ; ACTIVE HOST TABLE.  Entries herein are allocated as needed, using garbage
133 ; collection.  Most "host number" fields are really indices into this table.
134 ;
135 LIMPHT==<XBL+10.>       ; TCP conns plus a few extra
136 IMPHTN: BLOCK LIMPHT    ; Host number.  1.1-1.8 HOST, 2.1-3.7 IMP
137 IMPHTB: BLOCK LIMPHT    ;Bits:
138                         ;4.9            UNUSED
139                         ;4.8            GC MARK BIT
140                         ;4.7-4.3        UNUSED
141                         ;4.2-4.1        STATUS OF HOST 0 DOWN, 1 RST SENT, 2 UP
142                         ;3.9-3.1        UNUSED
143         .SEE IMPHDS     ;RH   Last message from IMP about "host dead status"
144 IMPHTC: BLOCK LIMPHT    ; # active messages outstanding for host (8 max)
145 IMPHTT: BLOCK LIMPHT    ; Time of last RFNM received
146
147 LIMPN==.-1      
148 ;Last location BLT'ed to zero when initialized
149
150 IMNBLK: 0       ;Number of times blockage avoided (output held up by ITS)
151 IMPHTF: -1      ;Host table free list, threaded through IMPHTB, end with -1
152 IMPUP:  -1      ;0 => IMP up  ;-1 => down  ;-2 => coming up, PI lvl still off
153                 ;1 => down for good, until next time IMP ready line changes
154 IMPTCU: 0       ;0 IMP up/down status not changing
155                 ;>0 Trying to reinitialize, SYSJOB hasn't done so yet
156                 ;-1 Has been reinitialized, haven't exchanged NOPs yet
157 IMPUCT: 0       ;IMP coming up timeout, if 4 NOPs don't go through promptly.
158 IMPDWN: BLOCK 3 ;Last message from IMP that it is going down
159                 ;WD0: "Reason" claimed by IMP (see ch 3 of BBN report 1822)
160                 ;WD1: Time when expected down
161                 ;WD2: Time when expected up (SYS time=1/30 sec since up)
162 IFN KAIMP,[
163 IMPPIA: 0       ;Current IMP PIA
164 IMPCNI: 0       ;CONI into here at slow clock level
165 IMPA:   0       ;Save A at IMPCHN PI level
166 ]
167
168 IMERCN: -1      ;CONI into here when net goes down
169
170 BBLK
171
172 \f
173 EBLK
174
175 IMPCSH: -1      ;Current source host (IMPHTB index).  -1 when idle.
176 IMPCLN: 0       ;Current link number
177 IMNWSI: 0       ;Second BLKI pointer, zero if none
178 IMBLKI: 0       ;Place to store BLKI pointer
179  IFN KSIMP,[
180 IMIFLS: 0       ;Flushing output at interrupt handler
181 IMPIBP: 0       ;Pointer to input buffer data
182  ]
183
184 IMPILB: BLOCK 6 ;Input leader buffer
185
186 IMNOPC: 0       ;< 0 => Send NOPs
187 IMPOAC: 0       ;> 0 => Output active, don't restart
188 IMBLKO: 0       ;Place to store BLKO pointer
189 IMPBZY: 0       ;Software interrupt start flag
190
191 ; IMP output list.
192 ;
193 ; NEGATIVE = BLKO POINTER
194 ; 0=STOP, 1=SET LAST WORD
195 ; 2=32-BIT MODE
196 ; 3=NOP
197 ;
198 IMOPNT: 0       ;Index of next "instruction" in IMP output list:
199 IMOLST: 0       ;BLKO for second and third leader words (first is DATAOed)
200 IMOBK1: 0       ;First BLKO pointer
201 IMOBK2: 0       ;Usually 1, set LAST IMP BIT
202 IMOBK3: 0       ;Second BLKO pointer
203         0       ;Stop
204
205 IMOLDR: BLOCK 6 ;Build preamble here for data messages
206
207 ;METERS
208
209 ;IP meters
210 IMNIPI: 0       ; # of IP datagrams input (rcvd)
211 IMNIPF: 0       ; # of IP datagrams flushed (input threw away)
212 IMNIPO: 0       ; # of IP datagrams output (sent)
213 IMNIPR: 0       ; # of IP RFNMs received
214 IMNIP7: 0       ; # of IP Type 7 (Dest Host Dead) messages received
215 IMNIP8: 0       ; # of IP Type 8 (Error) msgs rcvd
216 IMNIP9: 0       ; # of IP Type 9 (Incomplete Transmission) msgs rcvd
217 IMNWIG: 0       ; # words ignored by "Ignore" state (%ISIGN)
218 IMNWIF: 0       ; # words flushed by IMPRM5
219
220 ;IMP meters
221 IMNSRF: 0       ;Number of spurious RFNMs on non-IP links
222
223 IMPMSR: BLOCK 20;Count of IMP messages rcvd
224 IMPM1S: BLOCK 4 ; # Type 1 (Error in Leader) subtype msgs
225 IMPM9S: BLOCK 2 ; # Type 9 (Incomplete Transmission) subtype msgs
226 IMPMSS: BLOCK 1 ;Count of IMP msg sent (we only send regular msgs)
227 IMCT1:  0       ;# Times at IMPBKZ
228 IMCT2:  0       ;# Times at IMPIBZ
229 IMCT3:  0       ;# Times at IMPOBZ
230 BBLK
231 \f
232 SUBTTL  ARPANET MAIN-PROGRAM LEVEL
233
234 ;(Re)Start IMP
235 ;
236 IMPINI:
237 IFN KAIMP,[
238         CONO IMP,IMI32S         ;32-bit data mode
239         DATAI IMP,A             ;Clear any cruft
240         CONO IMP,IMPODC         ;Clear OUTPUT DONE and PIA
241         CONSZ IMP,IMPOD+7       ;Check OUTPUT DONE, PIA, cause HOST READY
242          BUG HALT,[IMP: Hardware dead]          ;CONO didn't clear some bits?
243         CONO IMP,IMPIR+IMPHEC   ;Clear HOST ERR, enable int on IMP READY
244 ]
245 IFN KSIMP,[
246 IF2,IFN IMPIBF&777,.FATAL IMPIBF not on DEC page boundary
247         MOVEI A,IMPIBF_-9.      ;DEC page # of IMP buffer page
248         TRO A,%UQ16B\%UQVAL     ;Valid mapping, 16 bit device
249         IOWRI A,UBAPAG+IUIMPG_1 ;Set up 1 DEC page of UBA mapping. Note that
250                                 ; the second half of IUIMPG isn't mapped at all
251         MOVEI A,%LHRST
252         IOWRI A,%LHOCS          ;Reset output side
253         IOWRI A,%LHICS          ;Reset Input side
254 ]
255         MOVE T,TIME
256         ADDI T,30.
257         CAMLE T,TIME
258          PUSHJ P,UFLS           ;Wait one sec for IMP to notice rdy line drop
259 IFN KAIMP,[
260         CONO IMP,0              ;Clear "ENA IMP RDY" int (turns off IMP error)
261         MOVEI A,NETCHN          ;Set idle PIA
262         MOVEM A,IMPPIA
263         MOVE A,[JSR IMPIBK]     ;Set up default interrupt handlers
264         MOVEM A,IMPILC
265         MOVE A,[JSR IMPOBK]
266         MOVEM A,IMPOLC
267 ]
268 ;IMP now shut down. Reset variables
269
270 IFN KAIMP,[
271         SETZM IMPILC+1          ;Clear BLKI, BLKO runout locations (KA\DM)
272         SETZM IMPOLC+1
273 ]
274 IFN KSIMP,[
275         SETZM IMPIBP            ;Reset DMA input buffer pointer
276         SETZM IMIFLS            ;Not flushing output at PI handler
277 ]
278         SETOM IMPOAC            ;Output not active
279         SETOM IMPBZY            ;Don't start interrupts by accident
280         SETOM IMPUP             ;Not up yet
281         SETOM IMPTCU            ;Note trying to come up
282         MOVNI A,30.             ;Allow 15 seconds to come up
283         MOVEM A,IMPUCT
284         SETOM IMPHTF            ;Will GC IMPHTB on first reference
285         MOVE A,[IMPN,,IMPN+1]   ;This resets IMPIBS,IMPIDP,IMPODP,IMPI,IMPO,
286         SETZM IMPN              ; IMPB,IMPIH,IMPOH,IMPI,IMPOS, and host
287         BLT A,LIMPN             ; tables.
288         SETOM IMPIS             ;Init input state FSM correctly
289         MOVE T,TIME             ;Note when we last started IMP
290         MOVEM T,LNETIM
291 IFN KAIMP,[
292         CONO IMP,NETCHN         ;Enable interrupts on NETCHN, start input
293 ]
294 IFN KSIMP,[
295         CALL IMPHRS             ;Set host ready
296         CALL IMPIST             ;Start input
297 ]
298         SETOM IMPDWN+1          ;Time for IMP to go down, not known
299         MOVE T,TIME
300         ADDI T,15.              ;Wait 1/2 sec before we try to output
301         CAMLE T,TIME
302          PUSHJ P,UFLS
303         MOVNI A,4
304         MOVEM A,IMNOPC          ;Send 4 NOPs to start
305         ;Falls through to start output
306
307 ;Start IMP output, from process level
308 ;
309 IMPOST: CONO PI,NETOFF          ;Kill interrupts
310 IFN KAIMP,[
311         MOVE TT,IMPPIA          ;Get desired level for output done int
312         AOSN IMPOAC             ;Skip if output already active
313          CONO IMP,IMPODS(TT)    ;Generate output done int to start things
314         JRST NETONJ             ;Reenable interrupt system
315
316 ];IFN KAIMP
317 IFN KSIMP,[
318         SKIPL IMPOAC            ;Skip if output already active
319          JRST NETONJ            ;Yes, nothing to do
320         SETZM IMPBZY            ;Tell interrupt handler to run
321         CONO PI,NETRQ           ;Request interrupt on net channel
322         JRST NETONJ             ;Reenable interrupt system
323 ]
324
325 ;Start output, called from PI (NETCHN) level
326 ;
327 IMPIOS:
328 IFN KAIMP,[
329         AOSE IMPOAC             ;Note output active. If already active,
330          POPJ P,                ; nothing more to do
331         PUSH P,TT
332         CONO PI,400             ;Turn PI off, IMP may have PIA = 1
333         MOVE TT,IMPPIA          ;Get current PI level
334         CONO IMP,IMPODS(TT)     ;Set OUTPUT DONE to cause interrupt
335         CONO PI,200             ;Reenable interrupts
336         POP P,TT
337         POPJ P,
338 ]
339 IFN KSIMP,[
340         SKIPL IMPOAC            ;Output already active?
341          POPJ P,                ;Yes, do nothing
342         SKIPE IMPOS             ;Output state is idle?
343          BUG HALT,[IMP: Bad IMPOS state, ],DEC,IMPOS
344         SETZM IMPBZY            ;Tell interrupt handler to run
345         CONO PI,NETRQ           ;Request net interrupt
346         POPJ P,                 ;all done.
347 ]
348
349 ;Check if IMP ready line is set
350 ; Called from SYSJOB.
351 ; Return +1 if IMP not ready, +2 if so
352 ;
353 IMPCKR:
354 IFN KSIMP,[
355         IORDI A,%LHICS          ;Get input CSR
356         TRNN A,%LHINR           ;Skip if IMP not ready
357          AOS (P)                ;Return +2 if ready
358         POPJ P,                 ;That's all
359 ]
360 IFN KAIMP,[
361         CONSZ IMP,IMPR          ;Skip if IMP not ready
362          AOS (P)                ;Return +2 if ready
363         POPJ P,
364 ]
365
366 \f
367 SUBTTL  HOST-TABLE MANAGEMENT
368
369 ; FNDHST - Look up host-table index for a given IMP host address.
370 ;       Call with NETOFF or NETCHN PI in progress.
371 ;       T/ IMP host address (maybe someday other nets?)
372 ; Returns .+1 if failed (no room in table)
373 ; Returns .+2
374 ;       H/ host-table index
375 ; Smashes W.
376
377 FNDHST: MOVEI H,LIMPHT-1        ;Search for an entry for this host
378         CAME T,IMPHTN(H)
379          SOJGE H,.-1
380         JUMPGE H,POPJ1          ;Found
381         SKIPGE H,IMPHTF         ;Not found, cons one off free list
382          JRST FNDHS1            ;Oops, must garbage collect
383         MOVE W,IMPHTB(H)
384         CAIGE H,LIMPHT          ;Make sure H is valid idx
385          CAIL W,LIMPHT          ;ditto W
386           BUG HALT,[NET: FNDHST idx clobbered!!!]
387         MOVEM W,IMPHTF
388         MOVEM T,IMPHTN(H)
389         SETZM IMPHTB(H)         ;Nothing is known about this host
390         SETZM IMPHTC(H)         ;Assume no RFNMs outstanding
391         SETZM IMPHTT(H)         ;Clear out time of last RFNM.
392         JRST POPJ1
393
394 ; Host-Table full, attempt to GC it and flush unused entries, by
395 ; scanning all possible pointers into table.
396 ;       IMP pointers are IMPCSH and IMPHTC(H)
397 ;       TCP pointers are XBNADR(I)
398
399 ; GC mark phase - mark entries in use
400 FNDHS1: PUSH P,I
401         MOVSI W,200000          ;Mark bit
402         MOVEI H,LIMPHT-1        ;Clear all mark bits
403         ANDCAM W,IMPHTB(H)
404         SOJGE H,.-1
405         SKIPL H,IMPCSH          ;Mark from IMPCSH
406          IORM W,IMPHTB(H)
407 IFN TCPP,[
408         MOVEI I,XBL-1
409         SKIPL H,XBNADR(I)       ; See if TCP conn has a net addr specified
410          IORM W,IMPHTB(H)       ; Yes, set the mark bit.
411         SOJGE I,.-2
412 ] ;IFN TCPP
413
414 ; GC sweep phase - free all unmarked entries
415         SETO I,                 ;Free pointer
416         MOVEI H,LIMPHT-1
417         MOVSI W,601000          ;Protect if RFNM-WAIT, RST-WAIT, or marked
418 FNDHS4:
419         SKIPG IMPHTC(H)         ;Also protect if any outstanding RFNMs
420          TDNE W,IMPHTB(H)
421           SOJGE H,FNDHS4
422         JUMPL H,FNDHS5
423         SETZM IMPHTN(H)         ;Don't belong to any host
424         MOVEM I,IMPHTB(H)       ;Cons onto free list
425         MOVE I,H
426         SOJGE H,FNDHS4
427 FNDHS5: MOVEM I,IMPHTF          ;Free list
428         POP P,I
429         SKIPGE IMPHTF
430          POPJ P,                ;GC-overflow
431         JRST FNDHST             ;Try again, should win
432 \f
433 SUBTTL  ARPANET INPUT INTERRUPT LEVEL
434
435 COMMENT |
436 The KA/KL IMP interrupt level structure is fairly complicated and
437 deserves some explanation.  Because the IMP interface is not a DMA
438 device, all I/O is done "by hand", a word at a time; for this reason
439 all I/O is done at PI level IMPCHN=1 (the highest) whenever possible.
440 However, to prevent general IMP processing from taking complete
441 precedence over everything else, all non-I/O handling is done at
442 PI level NETCHN=2, which is the same level as disk devices.
443
444 Because the KA/KL interface only has one PI assignment available,
445 the software to switch levels is much more complicated.  For either
446 case, the code will not make sense unless you understand the channel 1
447 multiplexing feature (see interface CONI bit descriptions).
448
449 The KS interface avoids all this cruft by being a DMA device and only
450 interrupting on NETCHN when it has finished a transfer. The first-level
451 KS interrupt handler dispatches to IMPBER on errors, IMPBKZ for "control"
452 interrupts (Last Imp Word seen) and IMPIBZ for other Input Done interrupts;
453 this is very similar to the DM interface.
454 |
455
456 ; Here when IMP interface is interrupting at PI level 2 (NETCHN)
457 ; TT has CONI bits.  Can clobber most ACs
458 ;
459 IMPINT: 
460 IFN KAIMP,[
461         AOSN IMPB               ;Requested by PI 1 control interrupt?
462          JRST IMPBKZ            ; Yes
463         AOSN IMPI               ;Requested by PI 1 Input Done interrupt?
464          JRST IMPIBZ            ; Yes
465         AOSN IMPO               ;Requested by PI 1 Output Done interrupt?
466          JRST IMPOBZ            ; Yes already
467         TRNE TT,IMPLW+IMPHER+IMPERR     ;No PI 1 ints, check status bits
468          JRST IMPBKZ            ;PI 2 Control interrupt (error, Last Imp Word)
469         TRNE TT,IMPID
470          JRST IMPIBZ            ;PI 2 Input Done
471         TRNE TT,IMPOD
472          JRST IMPOBZ            ;PI 2 Output Done
473         BUG HALT,[IMP: Bogus interrupt]
474 ]
475 IFN KSIMP,[
476         SETOM IMPBZY            ;Tell MP we are handling request
477         SKIPL IMPOAC            ;Output already active?
478          JRST IMPEX             ;Yes, do nothing
479         AOS IMPOAC              ;Output is now active
480         JRST IMPOBZ             ;No, go try to start output
481 ]
482 \f
483 IFN KAIMP,[
484 ; IMPIBK - Default PI 1 Input Done routine, called from IMPILC.
485 ;       We're idling, switch to PI 2 to handle the input
486 ;       (normally 1st word of new IMP message)
487 EBLK
488 IMPIBK: 0
489 BBLK
490         SETOM IMPI              ;Set flag saying PI 1 Input Int seen
491         CONO IMP,NETCHN         ;Switch PIA to 2
492         JRST 12,@IMPIBK         ;Go re-interrupt, will get to IMPINT->IMPIBK
493
494 ; IMPBRK - PI 1 Control interrupt, called from PI0LOC+2 (= 42 on KA's)
495 ;       which is the standard PI 1 vector location.
496 ;       Again, switch to PI 2 to handle the condition
497 ;       (typically Last Imp Word seen on input)
498 EBLK
499 IMPBRK: 0                       ;This interrupt is to 42, may not be the IMP
500 BBLK
501         CONSO IMP,IMPLW+IMPHER+IMPERR   ;This really from the IMP?
502 IFE NEWDTP,JRST RC1INT
503 IFN NEWDTP,JRST IMPBR1
504         SETOM IMPB              ;Yes, re-interrupt and handle at NETCHN level
505         CONO IMP,NETCHN         ;Switch PIA to 2 (NETCHN)
506         JRST 12,@IMPBRK         ;Go re-interrupt, will get to IMPINT->IMPBKZ
507
508 IFN NEWDTP,[
509 IMPBR1: CONSZ DTC,70            ;Allow for non-IMP interrupt on PI chan 1
510          JRST 12,@IMPBRK
511 ]
512
513 RC1INT: MOVEM 17,R1NTAC+17
514         MOVEI 17,R1NTAC
515         BLT 17,R1NTAC+16
516         MOVEI J,1
517         JSP E,SPUR
518         MOVSI 17,R1NTAC
519         BLT 17,17
520         JRST 12,@IMPBRK
521
522 ; IMPRM4 - PI 1 Input-Done handler during readin of IMP data (not leader)
523 ;       BLKI has run out but haven't yet gotten Last Imp Word!
524 ;       Either read more (if 2nd ptr specifed) or ignore following data.
525 EBLK
526 IMPRM4: 0
527 BBLK
528         MOVEM A,IMPA            ;Save A
529         SKIPL A,IMNWSI          ;Second BLKI pointer exists?
530          JRST IMPRM6            ;Nope, none now
531         MOVEM A,IMBLKI          ;Yes, store it!
532         SETZM IMNWSI            ;Clear this flag so don't do it again
533         MOVE A,IMPA             ;Restore A
534         JRST 12,@IMPRM4         ;Return, continuing BLKI.
535
536 IMPRM6: MOVE A,[JSR IMPRM5]     ;Ugh!  Ignore additional input
537         MOVEM A,IMPILC          ;Set up new vector to "ignore" routine
538         MOVE A,IMPA
539         JRST 12,@IMPRM4
540
541 ; IMPRM5 - PI 1 Input-Done handler while ignoring IMP data, only
542 ;       set up by IMPRM6 above.
543 ;       Just reads a word and ignores it.  This loop is broken
544 ;       by a control interrupt when Last-Imp-Word is seen.
545 EBLK
546 IMPRM5: 0                       ;Hmm? Flush input at PI 1
547 BBLK
548         DATAI IMP,IMPA
549         AOS IMNWIF              ;See how often we come here.
550         JRST 12,@IMPRM5
551 ];IFN KAIMP
552
553 \f
554 IFN KSIMP,[
555 ;First level interrupt handling for input side. Here from UBA vector hardware.
556 IMPIBK:
557 IFN NETCHN-UTCCHN,.ERR You lost at IMPIBK
558
559         EBLK
560 IMPIBK: 0
561         BBLK
562         JSR UTCSAV              ;Save AC's, get a stack
563         IORDI TT,%LHICS         ;Get CS register
564         TRNE TT,%LHERR\%LHNXM
565          BUG HALT,[IMP: I NXM]
566         TRNE TT,%LHMRE          ;Ready line flapped
567          JRST IMPIER            ;Go directly to error routine
568         TRNN TT,%LHRDY          ;Device ready for new operation?
569          BUG HALT,[IMP: Input device not ready]
570         TRNN TT,%LHEOM          ;Saw EOM from IMP?
571          JRST IMPIB1            ;No, word count ran out before message
572         SKIPGE IMIFLS           ;Flushing output?
573          JRST [ SETZM IMIFLS    ;Not any more!
574                 JRST IMPIRT ]   ;But flush last piece by queueing new request
575         IORDI A,%LHIWC          ;End of message. Get remaining UB word count
576         SKIPE A                 ;This would be a surprise, really
577          TDO A,[-1,,600000]     ;36bit number of UBA words remaining in bfr
578         IDIVI A,2               ;Number of PDP10 words (cleverly rounded)
579         ADDI A,IMPBFS           ;Number of PDP10 words of message
580         MOVNS A                 ;Negative word count
581         HRLZS A                 ;NWG,,0
582         HRRI A,IMPIBF           ;NWG,,Start of buffer
583         MOVEM A,IMPIBP          ;Init input buffer pointer for new data
584         MOVE A,[-3,,IMPILB-1]   ;Read leader - 3 words to IMPILB
585         CALL IMPGRI             ;Do it
586         MOVEI A,%ISIML
587         SKIPN IMPIS             ;Already in non-idle state? (shouldn't happen)
588          MOVEM A,IMPIS          ;Was idling, set state to "Saw IMP LEADER"
589         TRNE TT,IMPLW           ;Saw last word of message?
590          JRST IMPBKZ            ;EOM, so this is a control interrupt
591         JRST IMPIBZ             ;Not EOM, handle differently
592
593 ;Message didn't fit in input buffer. Shouldn't ever get here, but
594 ;might if messages concatenated due to ready line randomness
595 ;
596 IMPIB1: BUG INFO,[IMP: Huge message]
597         SETOM IMIFLS            ;Say we are flushing output
598         JRST IMPIRT             ;And go queue up another read
599
600 ;Fake output interrupt - come here when we have read more data from the
601 ;input buffer and want to re-dispatch.
602 ;
603 IMPIBL: TRNE TT,IMPLW           ;Saw last word of message?
604          JRST IMPBKZ            ;EOM, so this is a control interrupt
605         JRST IMPIBZ             ;Not EOM, handle differently
606
607 ];IFN KSIMP
608 \f
609 ; IMPIBZ - PI 2 (NETCHN) "Input Done", via IMPINT (KA) or IMPIBK (KS)
610 ;KA\KL: Note there is one input word waiting in the IMP interface,
611 ;       but it is NOT the last IMP word (if it was, we would get a
612 ;       control interrupt and go to IMPBKZ instead).  This situation
613 ;       should only happen while reading the IMP leader and there is
614 ;       more input than just the leader, i.e. it is a NCP or IP message.
615 ;       This is also where we come after being in idle state.
616 ;
617 ;KS:    A bunch of stuff has been DMA'd into the input buffer and the
618 ;       DMA word count ran out before the IMP sent EOM.
619 ;
620 ;       TT/ IMP CONI word or status register
621
622 IMPIBZ: AOS IMCT2
623 IFN KAIMP&IMPDBG,[
624         TRNN TT,IMPI32          ;Debugging, make sure we reading in 32 bit mode
625          BUG HALT,[IMP: 36bit mode at IMPIBZ]
626 ];IFN KAIMP&IMPDBG
627         MOVE B,IMPIS            ;Skip hold-up check unless start of msg (idle)
628         CAILE B,%ISIID
629          BUG HALT,[IMP: Bad IMPIBZ state]       ;Unknown input state
630         JRST @.+2(B)            ;Dispatch, note data not read yet
631
632                 IMPIGN          ;-1 Supposed to be shut off, go ignore message.
633         OFFSET -.
634  %ISIDL::       IMSTR1          ; 0 Was idle, this is start of a message!
635  %ISIGN::       IMPIGN          ; 1 Ignoring this message.
636  %ISIML::       IMPLD2          ; 2 Reading IMP leader, see what we got.
637  %ISIID::       [JRST 4,.]      ; 3 Was reading IP datagram!  Runout is error.
638         OFFSET 0
639
640 IMPIGN: AOS IMNWIG              ;See how often we come here.
641 IFN KAIMP,[
642         DATAI IMP,A             ;Ignore input (only come here via table above)
643         JRST IMPRET
644 ]
645 IFN KSIMP,JRST IMPIRT
646
647 ; All routines dispatched to from IMPIBZ and IMPOBZ return via IMPRET.
648 IMPRET:
649 IFN KAIMP,[
650  IFN IMPDBG,[
651         CONSO IMP,IMPI32        ;Make sure input is in 32-bit mode
652          BUG HALT,[IMP: 36bit mode at IMPRET]
653  ]
654         CONO IMP,@IMPPIA        ;Switch to desired exit PIA
655         JRST IMPEX
656 ]
657 IFN KSIMP,JRST IMPEX
658
659 ; IMPBKZ - PI 2 (NETCHN) Control interrupt, via IMPINT (KA) or IMPIBK (KS)
660 ;       Error or Last Imp Word on input.
661 ;       TT/ IMP CONI word or status register
662
663 IMPBKZ: AOS IMCT1               ;Bump count of control interrupts
664 IFN KAIMP,[
665         TRNE TT,IMPERR+IMPHER   ;See if error or last-imp-word.
666          JRST IMPBER            ;Jump if IMP Error or Host Error
667 ]
668 ; Not an error, interface has Last Imp Word ready for DATAI'ing!
669 ; Go handle end of IMP message
670 IFN KAIMP,[
671         MOVE A,[JSR IMPIBK]     ;Get rid of input BLKI
672         MOVEM A,IMPILC          ;Replace with default switch-PIA vector
673         SETZM IMPIH             ;Say don't need PI 1 for input any more.
674         MOVEI A,NETCHN          ;And change exit PIA to 2
675         SKIPL IMPOH             ;Unless output side still needs PI 1.
676          MOVEM A,IMPPIA         ;Set value of PI level desired on exit.
677         DATAI IMP,A             ;Get the last input word for processing
678 ]
679         SKIPGE B,IMPIS          ; Unless network has been shut off
680          JRST IMPIGN            ; (in which case ignore input)
681         JRST @IMSDT2(B)         ; then go process end of IMP message.
682
683 IMSDT2: OFFSET -.
684  %ISIDL::       IMPBKN  ; 0 Was idle - leader only 1 word long??
685  %ISIGN::       IMPIRT  ; 1 Ignore input
686  %ISIML::       IMPLD1  ; 2 End of IMP leader - can't be regular msg
687  %ISIID::       IMPRMI  ; 3 End of IP datagram
688         OFFSET 0
689
690
691 IMPBKN:
692 IFN KSIMP,BUG HALT,[IMP: Bad state IMPBKN]
693 IFN KAIMP,[
694 ; Here from table above for old-type leader (1 word)
695 ; IMPBN1 is used by IMPLD2 if long leader has wrong format.
696 ;
697         MOVEM A,IMPILB          ;Store first (and only) word of leader
698                                 ;Falls through
699 ];IFN KAIMP
700 ;Here from KA short leader or all long leader with wrong format
701 ;
702 IMPBN1: LDB A,IMOTBP            ; Get message format type
703         CAIN A,4                ; Old-type NOP?
704          JRST IMPIRT            ;  Just ignore it.
705         CAIN A,16               ; Is it 1822L format?
706          BUG INFO,[IMP: 1822L leader],OCT,IMPILB
707         CAIE A,17               ; Is it not the long-leader format?
708          BUG INFO,[IMP: Old-type leader],OCT,IMPILB
709         JRST IMPIRT             ; Ignore rest of message, if any
710
711 \f
712 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
713 ;;;             IMP LEADER READING/DISPATCH             ;;;
714 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
715 ;;;     Code on this page handles the initial processing of
716 ;;;     IMP messages and dispatches to the appropriate
717 ;;;     routines for each message type.  Only Type 0 ("Regular")
718 ;;;     messages carry Host-Host traffic.
719
720 IMSTR1:
721 IFN KAIMP,[
722 ; Here from IMPIBZ only, to handle first word of an IMP message.
723 ; (It's not the last word or IMPBKZ would complain about it)
724 ; Set up a BLKI to get the rest of the leader.
725         DATAI IMP,A             ;Get 1st word from interface
726 ; Entry point from IMPOB6 only to restart input from "held-up" state
727 ; First word already in A
728 IMSTRT: MOVEM A,IMPILB          ;Store first word of leader
729         MOVEI C,%ISIML          ;Set new state = reading rest of IMP leader
730         MOVE B,[-2,,IMPILB]     ;There are two more words in the leader
731         JRST IMPRM9             ;Go read the leader.
732 ];IFN KAIMP
733 IFN KSIMP,BUG HALT,[IMP: Bad state IMSTR1]
734
735 ; Here from IMPBKZ only for a leader not followed by any data.
736 ;       KA/KL has last word in A
737 ;       IMPLW flag in TT.
738 ;
739 IMPLD1: 
740 IFN KAIMP,[
741         AOS B,IMBLKI            ;Update pointer to buffer
742         MOVEM A,(B)             ;and store last word in right place.
743 ]
744         JRST IMPLDD
745         ; Fall through to handle what should be an IMP-Host note.
746         ; The IMPLW flag distinguishes this entry point from IMPLD2,
747         ; so we know there isn't a data word in the interface.
748
749 ; Here from IMPIBZ only, for an IMP leader with more data following;
750 ; almost certainly a "Regular" host-host message.  
751 ;
752 IMPLD2:
753 IFN KAIMP,[ +++++       ;Missing DATAI of current word first??
754         AOS B,IMBLKI            ;Update pointer to buffer
755         MOVEM A,(B)             ;and store last word in right place.
756 ]
757         JRST IMPLDD
758         ; Fall through to handle what should be a real message
759         ; The IMPLW flag distinguishes this entry point from IMPLD2,
760         ; so we know there is a data word in the interface. (KA)
761
762 \f
763         SUBTTL IMP leader dispatch handling
764 IMPLDD: HRRZ B,IMBLKI           ;Get address of last word read
765         CAIGE B,IMPILB+2        ;Must be at least 3 words to be valid
766          JRST IMPLD3
767         LDB T,IMOTBP            ;Examine new-format flag bits of leader
768         CAIN T,16               ;Is it 1822L format?
769          BUG INFO,[IMP: 1822L leader],OCT,IMPILB
770         CAIE T,17               ;Verify that leader is "new" 96-bit fmt.
771          JRST IMPBN1            ;Something else?? Go discard.
772         LDB T,IMLNBP            ;Extract link number (high 8 bits of msg-id)
773         MOVEM T,IMPCLN          ;Save link message arrived on
774         LDB T,IMSABP            ;Get arpanet address (source host+imp)
775 IFN 0,[ 
776         LDB T,IMSHBP            ;Source host
777         LDB A,IMSIBP            ;Source imp
778         DPB A,[112000,,T]       ;Form host address
779 ];IFN 0
780         PUSHJ P,FNDHST          ;H gets host table index
781          JRST IMPLD9            ;Host table full
782         MOVEM H,IMPCSH          ;Save current host
783         LDB A,IMTBP             ;Get message type in A
784         CAILE A,10.
785          JRST IMPUN             ;Unknown type?
786         AOS IMPMSR(A)           ;Count IMP msgs rcvd
787         JRST @IMTDT(A)          ;Dispatch
788
789 IMTDT:  IMPRM   ; 0 Regular Message
790         IMPBE1  ; 1 Error in Leader (no msg-id)
791         IMPGD   ; 2 IMP Going Down
792         IMPUN   ; 3  -
793         IMPIN   ; 4 NOP
794         IMPRFN  ; 5 RFNM - Ready For Next Message (transmit succeeded)
795         IMPHDS  ; 6 Host Dead Status (general info)
796         IMPDHD  ; 7 Destination Host Dead (transmit failed)
797         IMPBE8  ; 8 Error in Data (has msg-id)
798         IMPINC  ; 9 Incomplete Transmission (transmit failed temporarily)
799         IMPIRS  ;10 Interface Reset - IMP dropped its ready line
800
801 IMPLD9: BUG INFO,[IMP: Message discarded due to host table full],OCT,IMPILB,OCT,IMPILB+1,OCT,IMPILB+2
802         JRST IMPIRT
803
804 ;Here from IMPLDD if leader is too short
805 ;
806 IMPLD3: SUBI B,IMPILB-1         ;Number of words read
807         BUG INFO,[IMP: Short leader, ],DEC,B,[wds. WD1=],OCT,IMPILB,[WD2=],OCT,IMPILB+1
808         JRST IMPIRT             ;Flush rest of message
809
810 ;;; IMP->Host Type X (e.g. 3, 11-255) - bad type
811
812 IMPUN:  BUG INFO,[IMP: Unknown msg type ],OCT,A,[ leader ],OCT,IMPILB,OCT,IMPILB+1,OCT,IMPILB+2
813         JRST IMPIRT
814
815
816 ;;; IMP->Host Type 1 - Error in leader (msg-id not given)
817 ;;; IMP->Host Type 8 - Error in data  (msg-id given)
818
819 IMPBE1: LDB T,IMSTBP            ;Get subtype (4 bits)
820         ANDI T,3                ;Only 2 bits should be used
821         AOS IMPM1S(T)           ;Increment count of Type 1 subtype messages
822 IMPBE8: MOVE T,TIME
823         SUB T,LNETIM
824         CAIL T,60.              ;Ignore error during initial synchronization
825          BUG INFO,[IMP: Type ],DEC,A,[err msg, leader],OCT,IMPILB,OCT,IMPILB+1,OCT,IMPILB+2
826         MOVE B,IMPCLN           ;Get link msg came in on
827         CAIN B,233              ;Internet link?
828          AOS IMNIP8             ;Yes, count IP meter
829         CAIN A,8.               ;Error identified with a particular message?
830          JSP T,IMPBLD           ;Decrement count of active messages
831         JRST IMPIRT
832
833 ;;; IMP->Host Type 2 - IMP going down
834
835 IMPGD:  LDB B,[420200,,IMPILB+2]        ;Reason (see 1822)
836         MOVEM B,IMPDWN
837         LDB B,[360400,,IMPILB+2]        ;How soon going down * 5 mins
838         MOVE H,B
839         IMULI B,5*60.*30.       ;Ticks in 5 mins
840         ADD B,TIME
841         MOVEM B,IMPDWN+1
842         LDB C,[241200,,IMPILB+2]        ;How long to be down * 5 minutes
843         MOVE Q,C
844         IMULI C,5*60.*30.       ;Downtime in ticks
845         ADD C,B                 ;Add to time down
846         MOVEM C,IMPDWN+2        ;Store time when will be up
847         IMULI H,5               ;Minutes
848         IMULI Q,5
849         BUG INFO,[IMP: Going down in ],DEC,H,[mins for ],DEC,Q,[mins, reason],DEC,IMPDWN
850         JRST IMPIRT
851
852 ;;; IMP->Host Type 4 - NOP
853
854 IMPIN:  JRST IMPIRT             ;One more NOP from IMP
855
856 ;;; IMP->Host Type 5 - RFNM (Ready For Next Message)
857
858 IMPRFN: JSP T,IMPBLD    ; Decrement count of active IMP messages for this host
859         MOVE A,IMPCLN           ;Get link #
860         CAIE A,233              ;IP link number?
861          JRST IMRFNX            ;No, skip IP code
862 IFN INETP,.ERR INETP needs handling for RFNM on link 233
863         AOS IMNIPR              ;Bump count of IP RFNMs received
864         JRST IMPIRT             ; and do nothing else about it, ugh.
865
866 IMRFNX: BUG INFO,[IMP: Spurious RFNM from ],OCT,IMPHTN(H),[link],OCT,IMPCLN
867         AOS IMNSRF
868         JRST IMPIRT
869
870
871 ;;; IMP->Host Type 6 - Host Down Status
872 ;       H/ host index
873
874 IMPHDS: LDB A,[301400,,IMPILB+2];Bits 65-76 of leader, 4.9-3.7 3rd word
875         HRRM A,IMPHTB(H)        ;Store, hope user read RFC 611
876         JRST IMPIRT
877
878 ;;; IMP->Host Type 7 - Destination Host Dead
879
880 IMPDHD: MOVEI E,%NCDED
881         JRST IMPHNR
882
883 ;;; IMP->Host Type 9 - Incomplete Transmission
884
885 IMPINC: LDB T,IMSTBP            ;Get subtype field (4 bit reason for failure)
886         AOS IMPM9S(T)           ;Bump count of subtypes
887         MOVEI E,%NCINC          ;This is an incomplete msg response
888
889 IMPHNR: JSP T,IMPBLD            ;Decrement active IMP msg count for this host
890         MOVE A,IMPCLN           ;Link for this message?
891         CAIE A,233              ;IP Link?
892          JRST IMPHN1
893         CAIN E,%NCINC           ;Yes, count IP meters
894          AOS IMNIP9
895         CAIN E,%NCDED
896          AOS IMNIP7
897         JRST IMPIRT
898
899 IMPHN1: BUG INFO,[IMP: DHD or IT msg rcvd on non-IP link]
900         JRST IMPIRT
901
902 ;;; IMP->Host Type 10 - Interface Reset
903
904 IMPIRS: BUG INFO,[IMP: Interface-reset msg]
905         JRST IMPIRT             ;Probably nothing useful to do about it.
906
907 \f
908 ; Here from all over, to flush rest of this message.
909 ; All non-regular messages (not type 0) return here, as well as some
910 ; errors with regular msgs.
911 ; TT says whether there is any more data to read from this message.
912 IFN KAIMP,[
913 IMPIRT: SETZM IMPIS             ;Assume end of message, reset to normal state
914         TRNN TT,IMPLW           ;But if we haven't yet read the last word,
915          AOSA IMPIS             ;then change state to "Ignore" and flush input.
916                                 ;Note skip over following SETZM.
917
918 ; Regular messages (type 0) return here, when we already know this message
919 ; was completely read.  TT isn't valid.
920 IMPIR1: SETZM IMPIS             ;Reset to normal idle state
921         SETOM IMPCSH            ;Say no current host
922         CONO IMP,IMI32S         ;Make sure in 32 bit data mode
923         JRST IMPRET
924 ]
925 IFN KSIMP,[
926 ;We have already read the whole message from the IMP into the input buffer,
927 ; so flushing excess input is no work at all.
928 IMPIRT: 
929
930 ;Regular messages (type 0) return here, when we already know this message
931 ;was completely read.  TT isn't valid.
932 IMPIR1: SETZM IMPIS             ;Set idle state
933         CALL IMPIST             ;Start listening for new input
934         SETOM IMPCSH            ;Say no current host
935         JRST IMPRET
936 ];IFN KSIMP
937
938 \f
939 ;;; IMP->Host Type 0 - Regular Host-Host message
940 ; Unless the source host screwed up and sent a dataless message,
941 ; there is at least one word waiting to be read from the interface.
942 ; For IP this is the 4th word and we are in 32-bit mode.
943 ;       TT/ IMP CONI bits or status register
944 ;       B/ addr of last wd input (counted-out BLKI pointer)
945
946 IMPRM:  TRNE TT,IMPLW
947          JRST IMPRM3            ;Foo, message shouldn't end so soon.  Go barf.
948         MOVE A,IMPCLN           ;Is link number the magic cookie for IP?
949         CAIE A,233
950          JRST IMPIRT            ;No, ignore it since we don't have NCP
951
952 ;This is an Internet Protocol datagram.  Make sure we are
953 ;in right mode for reading.
954 ;
955         AOS IMNIPI              ;Bump count of IP datagrams received
956 IFN KAIMP&IMPDBG,[
957         TRNN TT,IMPI32          ;Should already be in 32-bit mode
958          BUG PAUSE,[IMP: Reading IP dgm in 36-bit mode]
959 ]
960         MOVEI A,%IMXLN          ;Specify max size of IMP message
961                                 ; (we can't trust msg-len leader field)
962         PUSHJ P,IPGIPT          ;Call IP module - get input buffer pointer
963          JRST [ AOS IMNIPF      ;Punted, bump cnt of datagrams lost
964                 JRST IMPIRT]    ;Flush this message (err msg already printed)
965         MOVEM A,IMPIDP          ;Save datagram pointer
966         MOVEM B,IMPIBS          ;Save input BLKI pointer for later check
967         MOVEI C,%ISIID          ;Set state = reading IP datagram
968         ;JRST IMPRM9            ;Go do it.
969
970 ; Set up and start multiword data input. This place is jumped to by
971 ; several things that initiate IMP input, specifically IMSTRT, IMPRMT,
972 ; and IMPRM.
973 ;       B/ BLKI pointer
974 ;       C/ New input FSM state
975 ;
976 IMPRM9: MOVEM C,IMPIS           ;Save current input state
977         MOVEM B,IMBLKI          ;Save BLKI pointer
978 IFN KSIMP,[
979         MOVE A,B                ;Set up BLKI pointer
980         CALL IMPGRI             ;Get requested data from input buffer
981         JRST IMPIBL             ;Jump back to handle new input data!
982 ]
983 IFN KAIMP,[
984         MOVE B,[BLKI IMP,IMBLKI]
985         MOVEM B,IMPILC
986         MOVE B,IMPBRO(C)        ;Get BLKI runout instruction and set vector;
987         MOVEM B,IMPILC+1        ; will execute when ptr counts out.
988         SETOM IMPIH             ;Say that input wants high pri
989         MOVEI B,IMPCHN          ;And set our exit PIA to it (IMP)
990         MOVEM B,IMPPIA
991         JRST IMPRET             ;Return from interrupt
992 ];IFN KAIMP
993
994 ;Message with no data. Just ignore it, could print a note
995 IMPRM3: JRST IMPIRT
996 \f
997 IFN KAIMP,[
998         ; This table holds the instruction to execute after the input
999         ; BLKI has counted out the ptr and stored the current input word.
1000         ; Note that if the IMP message ends during the BLKI, a control
1001         ; interrupt will happen instead and control goes to IMPBKZ
1002         ; where there is another state dispatch table.
1003         ; Normally only %ISIML and %ISINL actually use these instructions;
1004         ; the other states are impossible or expect to read the entire
1005         ; remaining message.
1006 IMPBRO: OFFSET -.
1007  %ISIDL::       JRST 4,IMPBRO   ; 0 Idle   - shouldn't be BLKI'ing.
1008  %ISIGN::       JRST 4,IMPBRO+1 ; 1 Ignore - shouldn't be BLKI'ing.
1009  %ISIML::       JSR IMPLD5      ; 2 Reading IMP leader (4 wds partial msg)
1010  %ISIID::       JSR IMPRM4      ; 3 Reading IP datagram (get all)
1011         OFFSET 0
1012
1013 EBLK            ; PI 1 Input Done interrupt (from IMPILC+1, runout)
1014 IMPLD5: 0       ; JSR here on BLKI runout after reading 3rd wd of IMP leader.
1015 BBLK            ; Input Done is not set, because BLKI just turned it off.
1016         MOVEM A,IMPILC          ;Save A
1017         MOVE A,[JSR IMPLD6]     ;Make very next input word interrupt to IMPLD6
1018         EXCH A,IMPILC           ;Do it, restore A
1019         JRST 12,@IMPLD5
1020
1021 EBLK            ; PI 1 Input Done interrupt (from IMPILC)
1022 IMPLD6: 0       ; JSR here with 4th wd of leader in interface.
1023 BBLK            ; Must decide whether to continue reading leader in
1024                 ; 36-bit mode (NCP) or 32-bit mode (IP).
1025         MOVEM A,IMPILC          ; Save A
1026         MOVE A,IMPILB+1         ; Get word with link number in it
1027         ANDI A,377              ; Mask off
1028         CAIN A,233              ; Internet Protocol "link"?
1029          JRST IMPLI3            ; Yes!  Go handle it.
1030
1031         ; NCP read will immediately store current 36-bit word (4th),
1032         ; store another 36-bit word (5th), and then run out to IMPLD4.
1033         MOVE A,[-2,,IMPILB+2]   ; Reading NCP message.
1034         MOVEM A,IMBLKI
1035         MOVEI A,%ISINL          ; Reading NCP leader, set state thereto.
1036         MOVEM A,IMPIS
1037         MOVE A,[JSR IMPLD4]     ; And change dispatch vector.
1038         MOVEM A,IMPILC+1
1039         MOVE A,[BLKI IMP,IMBLKI]
1040         EXCH A,IMPILC           ; Set up BLKI and restore A
1041         JRST 12,@IMPLD6 ; Return.  Note current input word is still waiting.
1042
1043         ; IP read will immediately store current 36-bit word (4th),
1044         ; then set up so next input-done interrupt (on 5th, 32-bit word)
1045         ; goes directly to IMPIBZ->IMPLD2 with NETCHN PI.
1046         ; (For AI-KA/ML-KA/MC-KL, perhaps by way of IMPIBK if output is active)
1047 IMPLI3: MOVEI A,%ISIIL          ; Say reading IP type leader.
1048         MOVEM A,IMPIS
1049         CONO IMP,IMI32S+IMPCHN  ; Set further input to 32-bit mode
1050         DATAI IMP,IMPILB+3      ; Store the 4th 36-bit word immediately; this
1051                                 ; also starts interface reading the 5th word.
1052         MOVE A,IMPLD6           ; Now must set up for next interrupt.
1053         MOVEM A,IMPLD4          ; Fake out the common code below
1054         JRST IMPLI4             ; Set up for next Input-Done interrupt
1055
1056 EBLK            ; PI 1 Input Done interrupt (from IMPILC+1, runout)
1057 IMPLD4: 0       ; JSR here on BLKI runout after reading IMP leader
1058 BBLK            ; There is still one word to go, to be gotten at NETCHN level
1059
1060         MOVEM A,IMPILC          ; Save A
1061                                 ; Drop through to common code
1062
1063 IMPLI4: SETZM IMPIH             ; Say input no longer needs PI 1
1064         MOVEI A,NETCHN          ; Make PI 2 (NETCHN) the exit PIA,
1065         SKIPL IMPOH             ; unless output side needs PI 1.
1066          MOVEM A,IMPPIA         ; Set desired PIA channel on exit
1067         CONO IMP,@IMPPIA        ; Set PIA to whatever it was!
1068         MOVE A,[JSR IMPIBK]     ; Reset PI 1 Input-Done vector back to std.
1069         EXCH A,IMPILC           ; and restore A.
1070         JRST 12,@IMPLD4
1071
1072 IMPBCM: BUG INFO,[NCP: CTL MSG BS NOT 8 OR CT>120. HST ],OCT,IMPHTN(H),[BS ],DEC,IMPCBS,[BC ],DEC,IMPCBC
1073         JRST IMPIRT
1074 ];IFN KAIMP
1075 \f
1076 ; IMPRMI - End of IP datagram, PI in progress on NETCHN, here from IMPBKZ
1077 ;       A/ Last IMP word (32-bit) (KA/KL only)
1078 ;       TT/ CONI bits as of interrupt
1079 ;
1080 IMPRMI: AOS B,IMBLKI            ;Get address to store last word in
1081 IFN KAIMP,MOVEM A,(B)           ;Store it away
1082         SUB B,IMPIBS            ;Get # words read into datagram buffer
1083         MOVEI B,(B)
1084         MOVE A,IMPIDP           ;Get pointer to IP datagram buffer we're using
1085         SETZ C,                 ;Say zero offset to IP header.
1086         MOVE J,IMPCSH           ;Set idx to host-table entry dgm received from.
1087         PUSHJ P,IPRDGM          ;Hand off rcvd datagram to IP
1088         SETZM IMPIDP            ;Clear PI level pointer
1089         JRST IMPIR1             ;Return from PI level, setting up for next msg
1090 \f
1091 IFN KSIMP,[
1092 ;Set HOST READY. From SYS job only, please, loops waiting.
1093 ;
1094 IMPHRS: IORDI T,%LHICS
1095         TRNN T,%LHRDY           ;Can we mung?
1096          BUG
1097         IORI T,%LHHRC\%LHSE     ;Turn on HR. SE prevents dropping messages
1098         IOWRI T,%LHICS
1099         MOVEI A,777777          ;I don't know why this takes so long.
1100 IMPHR1: IORDI T,%LHICS          ;Get the bits back
1101         TRNE T,%LHHR            ;LHDH thinks host ready is ready
1102          RET                    ;HR line set
1103         SOJG A,IMPHR1           ;Timed out yet?
1104          BUG CHECK,[IMP: Timed out setting Host Ready]
1105         RET
1106
1107 ;Start listening for new input from IMP
1108 ;
1109 IMPIST: HRREI T,-IMPBFS*2
1110         IOWRI T,%LHIWC          ;Read up to a buffer full of data
1111         MOVEI T,<IUIMPG_12.>+<4*<IMPIBF&777>>
1112         IOWRI T,%LHICA          ;Read data to here
1113         MOVEI T,%LHIE\%LHHRC\%LHSE\%LHGO ;Interrupt, store data, go
1114         IOWRI T,%LHICS          ;Start read
1115         RET
1116
1117 ;Move data from IMP DMA buffer to somewhere else, reformatting as we go.
1118 ; IMBLKI/ BLKI ptr -count,,dest-addr-1
1119 ; Updates IMBLKI
1120 ; Bashes A,B,C,D,E
1121 ; Sets IMPLW in TT iff last word we read was last word available.
1122
1123 IMPGRI: 
1124 IFN IMPDBG,[
1125         SKIPL IMPIBP            ;Make sure we have something to give
1126          BUG HALT,[IMP: IMPGRI called with no more data]
1127 ]
1128         MOVE B,IMPIBP           ;Get current count,,location in input bfr.
1129 IMPGR1: MOVE C,(B)              ;Get data word from message
1130         LDB D,[.BP <377_26.>,C] ;Get Byte 2
1131         LDB E,[.BP <377_8.>,C]  ;Get Byte 4
1132         LSH C,10.               ;Shift so Byte 1 is correct
1133         DPB D,[.BP <377_20.>,C] ;Put Byte 2
1134         LDB D,[.BP <377_10.>,C] ;Get Byte 3
1135         DPB E,[.BP <377_4.>,C]  ;Put Byte 4
1136         DPB D,[.BP <377_12.>,C] ;Put Byte 3
1137         MOVEM C,1(A)            ;Store word. It's a BLKI ptr, remember?
1138         AOBJP B,IMPGR2          ;Incr source, exit if done
1139         AOBJN A,IMPGR1          ;Incr dest, maybe loop for more
1140
1141 ;Here if ran out of desstination buffer space
1142         TRZ TT,IMPLW            ;Didn't see last word
1143         MOVEM A,IMBLKI
1144         MOVEM B,IMPIBP
1145         RET
1146
1147 ;Here if ran out of source data
1148 IMPGR2: IORI TT,IMPLW           ;Say we read last word
1149         AOBJN A,.+1             ;Adjust BLKI ptr for last word read
1150         MOVEM A,IMBLKI          ;Update IMBLKI for everyone else
1151         MOVEM B,IMPIBP
1152         RET
1153 ];IFN KSIMP
1154 \f
1155 ;Here if error during IMP message transfer
1156 ;
1157 IFN KAIMP,[
1158 IMPBER: SKIPGE IMPUP            ;Skip if up, or thought to be broken
1159          JRST IMPBE2            ;Already down, let it come up in peace
1160         MOVSI J,SCLNET          ;Thinks it's up, reset it
1161         IORM J,SUPCOR           ;By getting system job to run SYSNET
1162         CONI IMP,IMERCN         ;Record if imp error flip/flop set
1163         SETOM IMPUP             ;IMP is down
1164         SETZM IMPTCU            ;And not trying to come up
1165 IFN INETP,.ERR IP/TCP code needs handling for IMP crashing.
1166
1167 IMPBE2: SETZM IMPPIA            ;No PI expected
1168         CONO IMP,0              ;Clear IMP
1169         BUG INFO,[IMP: Ready line flapped, resetting]
1170         JRST IMPEX
1171 ];IFN KAIMP
1172 IFN KSIMP,[
1173 ;Input side saw ready line flap
1174 IMPIER: SKIPE IMPUP             ;Is the IMP supposed to be up?
1175          JRST IMPIE1            ;No, handle differently
1176         IORDI T,%LHICS          ;Was up; get status
1177         BUG INFO,[IMP: Input RDY error, Status ],OCT,T
1178         JRST IMPRST             ;And go request a full cycling of IMP
1179
1180 IMPIE1: AOS T,IMPIEC
1181         CAIG T,10.              ;Huge number of errors whiile down?
1182          JRST IMPIRT            ;No, just ignore this input and start another
1183         SETZM IMPIEC            ;Reset
1184         BUG INFO,[IMP: Excessive input errors while down]
1185         JRST IMPIRT
1186
1187 ;Output side flapped
1188 IMPOER: SKIPN IMPUP             ;IMP up?
1189          JRST IMPOE1            ;Running, request a full reset
1190         MOVE T,IMPOS
1191         CAIE T,%ISONP           ;Were we sending a NOP?
1192          BUG CHECK,[IMP: Confusing output error]
1193         SOS IMNOPC              ;Add another NOP to make up for this one
1194         SETZM IMPOS
1195         JRST IMPOB0             ;Go send it
1196
1197 IMPOE1: IORDI T,%LHOCS
1198         BUG INFO,[IMP: Output RDY error, Status ],OCT,T
1199 ;;;     JRST IMPRST
1200
1201 IMPRST: BUG INFO,[IMP: Ready line flapped, resetting]
1202         MOVSI J,SCLNET          ;Thinks it's up, reset it
1203         IORM J,SUPCOR           ;By getting system job to run SYSNET
1204         IORDI T,%LHICS
1205         HRLZM T,IMERCN
1206         IORDI T,%LHOCS
1207         HRRM T,IMERCN
1208         SETOM IMPUP             ;IMP is down
1209         MOVEI T,1
1210         MOVEM T,IMPTCU          ;But trying to come up (sysjob poked)
1211 IFN INETP,.ERR IP/TCP code needs handling for IMP crashing.
1212         JRST IMPEX
1213
1214 ];IFN KSIMP
1215 \f
1216 ;;; IMP Blockage avoidance
1217 ;       The current IMP software will not accept more than 8 active
1218 ; messages to a single host; attempting to send a 9th message will block
1219 ; ALL output to the interface, until the first message has been ack'd
1220 ; by means of one of the following message types:
1221 ;       Type 5, RFNM - Message delivered OK
1222 ;       Type 7, Host dead - transmit failed ("permanent")
1223 ;       Type 8, Error in data - interface spazzed
1224 ;       Type 9, Incomplete Transmission - temporary failure
1225 ; If for some reason the first message simply becomes lost, the IMP timeout
1226 ; (and blockage) can last for up to 30-45 seconds.
1227 ; More details in BBN Report 1822.
1228 ;       ITS attempts to fix this by keeping a count of active un-ACKed
1229 ; messages for each host it is communicating with.  A timeout is also
1230 ; associated with each host; if output to a given host is blocked by ITS
1231 ; because there are 8 active messages, trying to send a 9th message
1232 ; will check the last-RFNM-received time and if this was more than
1233 ; 30 or so seconds then the IMP is probably not giving us what it should
1234 ; and we should reset things for that host.
1235
1236 %IMPMA==:8.     ; # of maximum active IMP messages allowed
1237
1238 ; IMPBLI, IMPBLD - routines to hack active-message counts, called via JSP T,
1239 ;       IMPBLD decrements count.
1240 ;       IMPBLI increments count and skips if successful (else failed,
1241 ;               and must NOT output another message to this host!)
1242 ;               Also clobbers Q.
1243 ;
1244 IMPBLI: AOS Q,IMPHTC(H)
1245         CAIGE Q,%IMPMA          ;Trying to send max or more messages?
1246          JRST 1(T)              ;No, can return safely.
1247         CAIG Q,8.               ;Is this the maximum # allowed?
1248          JRST [ MOVE Q,TIME     ;Yes, set up blockage timeout
1249                 ADDI Q,60.*30.  ; for one minute.
1250                 MOVEM Q,IMPHTT(H)
1251                 JRST 1(T)]      ;And allow this one to be sent
1252
1253         ; Trying to send too many messages, block it (check for timeout though)
1254         SOS IMPHTC(H)           ;Restore original count
1255         AOS IMNBLK              ;Increment # of times softwarily blocked.
1256         MOVE Q,IMPHTT(H)
1257         CAML Q,TIME             ;See if timeout still in the future
1258          JRST (T)               ;Yes, just take failure-return to block.
1259         BUG INFO,[IMP: RFNM-wait timeout! Hst=],OCT,IMPHTN(H)
1260         SETZM IMPHTC(H)         ;This may be dangerous... oh well.
1261         SETZM IMPHTT(H)
1262         JRST (T)                ;Block one last time, next try will win.
1263
1264 ;Decrement block count on reciept of any kind of ACK
1265 ;
1266 IMPBLD: SOSL Q,IMPHTC(H)
1267          JRST IMPBL2
1268         BUG INFO,[IMP: neg RFNM-wait cnt, Hst=],OCT,IMPHTN(H)
1269         SETZB Q,IMPHTC(H)
1270 IMPBL2: CAIL Q,8.-1             ;If we were blocking on this host,
1271          CALL IMPIOS            ;Ensure IMP output started up so blocked stuff
1272         JRST (T)                ; gets sent promptly.
1273
1274 \f
1275
1276 SUBTTL  ARPANET OUTPUT INTERRUPT LEVEL
1277
1278 IFN KAIMP,[
1279
1280 ; See comments at IMPINT for a description of the overall IMP interrupt
1281 ; structure.  Output is simpler than input, however.
1282 ; Each IMP message is output at PI level 1 except for the initial DATAO;
1283 ; the setup and takedown for each message is done at PI level 2.
1284 ; The code on this page is not referenced by anything outside the page
1285 ; except interrupt vector setup at IMPINI (to IMPOBK) and IMOB9 (to IMPCH1).
1286
1287 ; IMPCH1 - PI 1 Output-Done interrupt, from IMPOLC.
1288 ;       Comes here when last word DATAO'd has been sent to IMP.
1289 EBLK
1290 IMPCH1: 0
1291 BBLK
1292         MOVEM A,IMPOLC          ;Save A
1293         MOVE A,IMOPNT
1294 IMCH1A: SKIPGE A,IMOLST(A)      ;Get next "instruction"
1295          JRST IMCH1B            ;Jump if it's a BLKO pointer
1296         CAILE A,3               ;Ensure valid operation
1297          BUG HLT,[IMP: Bad command in output list.]
1298         XCT IMCH1I(A)           ;Do it
1299         AOS A,IMOPNT            ;Still here?  Point to next operation
1300         JRST IMCH1A             ;and loop to do it.
1301
1302 IMCH1I: JRST IMCH1C             ;0 Stop - end of output list
1303         CONO IMP,IMPLHW+IMPCHN  ;1 Set Last Word
1304         CONO IMP,IMO32S+IMPCHN  ;2 Set 32-bit mode
1305         JFCL                    ;3 NOP
1306
1307 IMCH1B: MOVEM A,IMBLKO          ;Set up BLKO - store the pointer
1308         MOVE A,[JSR IMCH1D]     ;Set dispatch for BLKO runout
1309         MOVEM A,IMPOLC+1
1310         MOVE A,[BLKO IMP,IMBLKO]
1311         EXCH A,IMPOLC           ;Store the BLKO and restore A
1312         AOS IMOPNT              ;Increment output list ptr past this op.
1313         JRST 12,@IMPCH1         ;Will interrupt immediately for first BLKO
1314                                 ;word, since Output-Done wasn't cleared.
1315
1316 ; PI 1 Output-Done, from IMPOLC+1 (BLKO runout)
1317 ;       Final word of the BLKO pointer is now in interface, being sent
1318 ;       to IMP, and Output-Done flag is off.
1319 EBLK
1320 IMCH1D: 0
1321 BBLK
1322         MOVEM A,IMPOLC
1323         MOVE A,[JSR IMPCH1]     ;Interrupt back when output of final word done
1324         EXCH A,IMPOLC
1325         JRST 12,@IMCH1D
1326
1327 ; Here from IMPCH1, PI 1 Output-Done interrupt
1328 ;       Output list has hit "stop" operation (previous op had better be
1329 ;       1 to set Last-Host-Word!)
1330 ;       This code reverts control back to PI level 2 (IMPOBK).
1331 ;
1332 IMCH1C: SETZM IMPOH             ;Say output side doesn't need PI 1 anymore
1333         MOVEI A,NETCHN          ;And set exit PIA to 2,
1334         SKIPL IMPIH             ;unless input side still needs PI 1
1335          MOVEM A,IMPPIA         ;Set it.
1336         CONO IMP,@IMPPIA
1337         SETOM IMPO              ;Tell IMPINT we have output-done interrupt.
1338         MOVE A,[JSR IMPOBK]     ;Point PI 1 channel at switch-PIA routine,
1339         EXCH A,IMPOLC
1340         JRST 12,@IMPCH1
1341
1342 ; PI 1 Output Done interrupt, when we should really be interrupting
1343 ;       at IMPINT on PI 2.
1344 EBLK
1345 IMPOBK: 0
1346 BBLK
1347         SETOM IMPO              ;Tell IMPINT what kind of interrupt
1348         CONO IMP,NETCHN         ;Reset PIA to 2
1349         JRST 12,@IMPOBK
1350 ];IFN KAIMP
1351 \f
1352 IFN KSIMP,[
1353 ;First-level interrupt handling, from hardware dispatch.
1354 IFN NETCHN-UTCCHN,.ERR Interrupt channel mismatch at IMPOBK
1355
1356         EBLK
1357 IMPOBK: 0
1358         BBLK
1359         JSR UTCSAV              ;Save AC's, get a stack
1360         IORDI TT,%LHOCS         ;Get CS register
1361         TRNE TT,%LHERR\%LHNXM   ;Interface lost?
1362          BUG HALT,[IMP: O NXM]
1363         TRNE TT,%LHMRE          ;Somebody bounce a ready line?
1364          JRST IMPOER
1365         TRNN TT,%LHRDY          ;Device ready for new operation?
1366          BUG HALT,[IMP: Output device not ready]
1367         TRZ TT,%LHIE\%LHGO      ;Is this right?
1368         IOWRI TT,%LHOCS
1369         AOS IMPOAC              ;Output active. Reset when no more output
1370         ;JRST IMPOBZ            ;Falls through
1371 ];IFN KSIMP
1372
1373 ; IMPOBZ - PI 2 (NETCHN) "Output Done" interrupt, via IMPINT (or IMPOBK on KS)
1374 ;       KA/KL, come here when we have finished sending stuff out at PI 1,
1375 ;       also when something wants output to start and tickled the "Done"
1376 ;       flag.
1377 ;       TT/ IMP CONI word.
1378 ;
1379 ;       KS, come here from output done interrupt if no errors, or when
1380 ;       someone wants to start output.
1381 ;
1382 IMPOBZ: AOS IMCT3
1383         SKIPL B,IMPOS
1384          CAIL B,IMPODL
1385           BUG HALT,[IMP: Bad output state]
1386         JRST @IMPODT(B)
1387
1388 IMPODT: OFFSET -.
1389 %ISODL::        IMPOB0  ; 0 Idle, look for something to send
1390 %ISONP::        IMPOB1  ; 1 Finished NOP
1391 %ISOID::        IMPOB2  ; 2 Finished IP datagram messge
1392 %ISOIL::        IMPOB3  ; 3 Finished IP leader (KS10 only)
1393 IMPODL::OFFSET 0
1394
1395 ;Return from all output finished interrupts
1396 ; KA interface, we don't turn off Output Done unless there is no more
1397 ; output to go. Thus if there is more output we will immediately 
1398 ; re-interrupt to look for it.
1399 ;
1400 ; KS, we explicitly look here for more output to send
1401 ;
1402 IMORET: SKIPE IMPOS
1403          BUG HALT,[IMP: Bad state at output finish]
1404 IFN KAIMP,[
1405         JRST IMPRET
1406 ]
1407 IFN KSIMP,[
1408         SKIPGE IMPOAC           ;Output still active?
1409          JRST IMPRET            ;Yes or no, don't look for more output
1410         ;JRST IMPOB0            ;Fall through to try for more
1411 ];IFN KSIMP
1412
1413 ; Idle - Look for output to send.  First ensure we can send stuff,
1414 ;       then try things in the order:
1415 ;       (1) Send NOP if net coming up
1416 ;       (2) Check IP datagram queue
1417 ;
1418 IMPOB0: HRRZ T,IMPUP
1419         CAIE T,-2               ;Don't say it's up when it's still going down
1420          CAIN T,1               ;or when it is broken
1421           JRST IMPOBN
1422
1423         ; First check to see if NOP needs to be sent.
1424         AOSG IMNOPC             ;Check to see if sending NOPs
1425          JRST IMONOP            ;Output a NOP
1426         SETZM IMPUP             ;Say IMP is up
1427         SETZM IMPTCU            ;Say no longer trying to come up
1428
1429         ; Now see if there is any real traffic to send
1430
1431         PUSHJ P,IPGIOQ          ;Check IP. Get IP IMP output queue entry if any
1432          JRST IMPOBN            ;Nothing there, we're done.
1433         ; Returns A/ ptr to IP dgm struct
1434         ;         B/ BLKO pointer to 32-bit words
1435         ;         C/ Arpanet address
1436         ;
1437         ;KA/KL interfaces build an output list which is interpreted
1438         ;by code running at PI 1. The output list should be set up as:
1439         ;IMOLST: -2,,IMOLDR     ; Send 2nd and 3rd word of IMP leader
1440         ;IMOBK1: Output BLKO    ; Send datagram minus last word
1441         ;IMOBK2: 1              ; Set last IMP bit
1442         ;IMOBK3: -1,,lstwd-1    ; BLKO to last word of datagram
1443         ;       0               ; Stop
1444         ;
1445         ;KS interface uses locations in IMOLST to store data for various
1446         ;output routines, which are dispatched to at PI 2 by the state
1447         ;machine at IMPOBZ. These locations are:
1448         ;IMOLST: Unused
1449         ;IMOBK1: Datagram BLKO
1450         ;IMOBK2: Unused
1451         ;IMOBK3: Unused
1452 IMOB01:
1453         MOVEM A,IMPODP          ;Save ptr to datagram being output
1454         AOS IMNIPO              ;# of IP datagrams sent
1455 IFN KAIMP,[
1456         MOVE D,[-2,,IMOLDR]     ;IMP leader is always three words output
1457         MOVEM D,IMOLST          ; from IMOLST (first with DATAO)
1458         ADD B,[1,,]             ;Reduce BLKO count by one
1459         MOVEM B,IMOBK1          ;Store in output list
1460         HLRO D,B                ;Get -<# wds-1>
1461         MOVN D,D                ;Get <#wds-1>
1462         ADDI D,(B)              ;Get addr for last-word BLKO
1463         HRROM D,IMOBK3          ;Store -1,,lastwd-1
1464 ]
1465 IFN KSIMP,[
1466         MOVEM B,IMOBK1          ;Save BLKO pointer for IP datagram
1467 ]
1468         ;Output list set up, now must put together the IMP leader in IMOLDR.
1469         MOVE B,[17_10.,,0]      ;Regular message
1470         MOVEM B,IMOLDR
1471         LSH C,4.                ;Move net address to correct field
1472         MOVEM C,IMOLDR+1        ;Set up second word
1473         MOVSI B,233_10.         ;IP link # in left 8 bits
1474         MOVEM B,IMOLDR+2        ;Set up third word
1475
1476         ;IMP leader set up, start output
1477 IFN KAIMP,[
1478         CONO IMP,IMO32S         ;Set 32 bit mode, clear PIA
1479         DATAO IMP,IMOLDR        ;Start it going!
1480         MOVEI C,%ISOID          ;State = outputting IP datagram.
1481 ]
1482 IFN KSIMP,[
1483         MOVE A,[-3,,IMOLDR-1]   ;IMP leader is three words output from IMOLDR
1484         PUSHJ P,IMOST           ;Go set up and start output
1485         MOVEI C,%ISOIL          ;Remember we are outputting IP leader
1486 ]
1487 ;Here after output of any kind started
1488 ;
1489 IMOB9:  MOVEM C,IMPOS           ;Save current output state
1490 IFN KAIMP,[
1491         SETZM IMOPNT            ;Initialize output list pointer
1492         SETOM IMPOH             ;Output side wants IMP to run on channel 1
1493         MOVEI A,IMPCHN
1494         MOVEM A,IMPPIA
1495         MOVE C,[JSR IMPCH1]     ;Set up handler for CH1 interrupts
1496         MOVEM C,IMPOLC
1497 ]
1498         JRST IMPRET
1499
1500 ;Couldn't find anything to output
1501 IMPOBN: SETOM IMPOAC            ;No more output
1502 IFN KAIMP,[
1503         CONO IMP,IMPODC         ;Clear Output-Done interrupt bit, so we won't
1504 ]                               ;immediately re-interrupt to start next output
1505         JRST IMORET
1506
1507 \f
1508 ;IMONOP - Send a NOP, here from IMPOBZ only.
1509 ;
1510 IMONOP:
1511 IFN KAIMP,[
1512         MOVEI A,IMPNOP          ;Get address of NOP leader
1513         MOVEI B,1               ;No text, but one extra wd (to make BLKO win)
1514         CONO IMP,IMO32S         ;Put IMP in 32-bit mode, Clear PIA
1515         DATAO IMP,(A)           ;Output first leader word
1516         MOVEI C,(A)             ;Set up BLKO pointer for 2nd word of NOP
1517         HRLI C,-1               ;Including count
1518         MOVEM C,IMOLST
1519         AOS C                   ;Now a BLKO ptr for third word
1520         MOVEM C,IMOBK2          ;Save it in output list
1521         MOVEI C,1               ;Command to set last IMP bit
1522         MOVEM C,IMOBK1          ;Set that in list
1523         SETZM IMOBK3            ;End of output list
1524         MOVEI C,%ISONP          ;State for control return to NETCHN
1525         JRST IMOB9              ;Falls through
1526 ];IFN KAIMP
1527
1528 IFN KSIMP,[
1529         MOVE A,[-3,,IMPNOP-1]   ;Get address of a BLKO word for NOP leader
1530         PUSHJ P,IMOSTL          ;Start output to IMP
1531         MOVEI C,%ISONP          ;State for control return to NETCHN
1532         JRST IMOB9              ;Go finish up interrupt
1533 ]
1534
1535 ;Prefabricated NOP Host-IMP leader
1536 IMPNOP: 17_10.,,4_4             ;New format, type 4 = NOP
1537         0
1538         0                       ;No padding required on regular messages
1539
1540 ;Finished sending NOP, from IMPOBZ
1541 ;
1542 IMPOB1: SETZM IMPOS             ;Reset state
1543         JRST IMORET             ;No, was a NOP. Done.
1544
1545 \f
1546 ;Was sending IP datagram, from IMPOBZ
1547 ;
1548 IMPOB2: SETZM IMPOS             ;Reset output state
1549         MOVE A,IMPODP
1550         PUSHJ P,IPIODN          ;Tell IP level that datagram was output
1551         SETZM IMPODP
1552         JRST IMORET             ;Go see if there is anything else to do.
1553
1554 IFN KSIMP,[
1555 ;Was sending IP leader, from IMPOBZ. Start actual datagram output
1556 ;
1557 IMPOB3: MOVE A,IMOBK1           ;Get BLKO word set up before
1558         PUSHJ P,IMOSTL          ;Go start output
1559         MOVEI C,%ISOID          ;Remember sending IP datagram
1560         JRST IMOB9              ;Go clean up and dismiss
1561 ];IFN KSIMP
1562
1563 \f
1564 IFN KSIMP,[
1565 ;Output startup routines for KS IMP. Call from NETCHN level or interrupts off.
1566 ; IMOST - start output
1567 ; IMOSTL - start output for last segment of message
1568 ; A/ BLKO word describing output.
1569 ; Bashes A,B,C,D,E,T,TT
1570 ;
1571 IMOSTL: TLOA T,-1               ;Remember which entry point
1572 IMOST:   SETZ T,
1573 IFN 0,[
1574         HLRE TT,A               ;Get count
1575         MOVN C,TT               ;Make positive
1576         CAILE C,IMPBFS          ;Message fits in output buffer?
1577          JRST IMOSTE
1578         HRLZI B,1(A)            ;Build BLT arg IO_buffer,,IMPOBF
1579         HRRI B,IMPOBF
1580         BLTBU B,IMPOBF-1(C)     ;Move and reformat data
1581 ]
1582 IFN 1,[
1583         AOS A                   ;Point to first data address
1584         HLRE TT,A               ;Get count
1585         MOVN C,TT               ;Make positive
1586         CAILE C,IMPBFS          ;Message fits in output buffer?
1587          JRST IMOSTE
1588         MOVNI B,-IMPOBF(A)      ;B = <IMPOBF - msg_address>
1589         HRLI B,A                ;B = <IMPOBF - msg_address>(A)
1590 IMOST1: MOVE C,(A)              ;Get data word from message
1591         LDB D,[341000,,C]       ;Get Byte 1
1592         LDB E,[141000,,C]       ;Get Byte 3
1593         LSH C,6.                ;Shift so Byte 2 is correct
1594         DPB D,[221000,,C]       ;Put byte 1
1595         LDB D,[121000,,C]       ;Get Byte 4
1596         DPB D,[101000,,C]       ;Put Byte 4
1597         DPB E,[001000,,C]       ;Put Byte 3
1598         MOVEM C,@B              ;Store reformatted word in temp buffer
1599         AOBJN A,IMOST1          ;Do more words if there are any
1600 ]
1601         ASH TT,1                ;Convert PDP10 word count to unibus word count
1602         IOWRI TT,%LHOWC         ;Tell the IMP interface
1603         MOVEI TT,<IUIMPG_12.>+<4*<IMPOBF&777>>
1604         IOWRI TT,%LHOCA         ;Unibus address of output buffer
1605         MOVEI TT,%LHIE\%LHGO    ;IMP Interface interrupt enable, GO
1606         SKIPE T                 ;This the last segment in the message?
1607          IORI TT,%LHELB         ;Yep, turn on EOM bit in interface
1608         IOWRI TT,%LHOCS         ;Start DMA transfer
1609         POPJ P,                 ;And forget it.
1610
1611 IMOSTE: BUG CHECK,[IMP output msg too big],DEC,C
1612         POPJ P,                 ;Ignore overly large msg
1613
1614 ];IFN KSIMP
1615 \f
1616 SUBTTL  ARPANET CLOCK LEVEL
1617
1618 OVHMTR IMP      ;NETWORK INTERRUPT LEVEL (NOT STYNET STUFF)
1619
1620 IMRSTO: RET                     ;Nothing to do any more?
1621 \f
1622 ;NETHST (HOST INFO)
1623 ; ARG 1 - HOST => VAL 1 - STATUS, VAL 2 - HOST NUMBER
1624 ; ARG 1 - -1 => VAL 1 - (STATUS), VAL 2 - OUR HOST NUMBER
1625 ;NOT CURRENTLY IMPLEMENTED- ARG 1 - -1, ARG 2 - OUR GOING-DOWN REASON
1626 ;
1627 ANETHST:HRRE T,A                ;Let immediate -1 win (777777 not a valid host)
1628         AOJE T,ANETH2           ;Jump if want local status and host number
1629         MOVE T,A
1630         JSP J,STDHST            ;Standardize and error-check host number
1631         MOVE B,T                ;Return new format
1632         TLO B,(NW%ARP)
1633         MOVEI H,LIMPHT-1
1634         CONO PI,NETOFF          ;Do we have status for this host?
1635         CAME T,IMPHTN(H)        ;Scan table
1636          SOJGE H,.-1
1637         JUMPGE H,ANETH1         ;Yes, return it
1638         CONO PI,NETON           ;No, have to go get it
1639         MOVEM T,SRN3(U)
1640         POPJ P,                 ;Oh, too bad
1641
1642 ;Here to return status of foreign ARPAnet host
1643 ANETH1: MOVE A,IMPHTB(H)        ;Get status
1644         CONO PI,NETON
1645         EXCH A,B
1646         CALL CVH2NA             ;Convert to HOSTS2 for compat
1647         EXCH A,B
1648         JRST LSWCJ1             ;Return IMSOC, NETLST if not done already
1649
1650 ;Here to return our status, host
1651 ANETH2:
1652 REPEAT 0,[
1653         CAIL W,2                ;(This is a crock)
1654          MOVEM B,NTHDSW         ;If 2 args, set our reason for going down.
1655 ]
1656         SKIPE IMPUP             ;Fake up our status
1657          TDZA A,A               ;We're down
1658           MOVSI A,2000          ;We are up
1659         MOVEI B,IMPUS           ;And our host umber
1660         JRST POPJ1
1661
1662
1663 ;NETIMP (REASON,TIMEDOWN,TIMEUP)  READ/SET
1664 ;
1665 ANETIM: JUMPLE W,ANETM1         ;No args, return current data
1666         CAIGE W,3               ;Must have 3 args if any
1667          JRST OPNL30
1668         MOVEM A,IMPDWN          ;Set data
1669         MOVEM B,IMPDWN+1
1670         MOVEM C,IMPDWN+2
1671         JRST POPJ1
1672
1673 ANETM1: MOVE A,IMPDWN           ;Get data to return
1674         MOVE B,IMPDWN+1
1675         MOVE C,IMPDWN+2
1676         SKIPE IMPUP             ;Note current condition of IMP, too
1677          TLO A,400000
1678         JRST POPJ1