bd282d7b4aaa5d240cfdbb9361a7ab54901004a9
[its.git] / system / tcp.274
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 ; This file holds the modules for TCP.
18 comment |       STUFF TO DO
19
20 Incoming ACKs should prevent retrans from aborting connection, since
21 clearly it is still alive, just doesn't have room for our stuff (which
22 is possibly overflowing its window).
23
24 Note Clark suggs on windowing/ACKing.
25         If input data seg doesnt have PUSH, don't send ACK, but set
26         a timeout for sending ACK.  Send ACK when:
27                 PUSH is seen
28                 outgoing seg forced out (new or retrans)
29                 timed out
30
31 Output buffering stinks.  If can't send buff due to too many segs,
32 then should be able to keep adding to present segment.
33
34 Provide way for output IOT to specify URGENT, and 
35 Handle URGENT when received on input.
36
37 |
38 \f
39 SUBTTL TCP definitions
40
41 %WYTCP==:7              ; Move to BITS later
42
43 %MOD32==:740000         ; LH mask used for mod 32 arithmetic
44 %TCPMI==:5              ; Max # segments in input queue per connection
45 %TCPMO==:5              ; Max # segments in output queue per connection
46 %TCPDS==:536.           ; Default max # bytes per segment (when no
47                         ;  knowledge of receiving host)
48 %TCPMS==:2048.-40.      ; Maximum possible segment size we can support
49                         ;  This must be 7777 (octal) or less.
50 %TCPMB==:%TCPMI*%TCPMS  ; Max # bytes of data in queue (a bit fictional)
51 %TCPMR==:20.            ; Max # retransmit retries allowed
52 %TCPMQ==:20             ; Max # pending RFCs allowed
53 %TCPMP==:777            ; Max port # allowed for pending-RFC (SYN) conns
54                         ;       Note pending-RFCs used ONLY for job startups,
55                         ;       SYNs are not queued in general.
56
57 ; Defintions of TCP Segment Header fields.
58 %TCPHL==:5              ; # of 32-bit words in fixed part of TCP header
59
60 TH%SRC==:777774,,       ; 0 Source Port
61 TH%DST==:     3,,777760 ; 0 Destination Port
62 TH%SEQ==:777777,,777760 ; 1 Sequence Number
63 TH%ACK==:777777,,777760 ; 2 Acknowledgement Number
64 TH%THL==:740000,,       ; 3 Data Offset (TCP Header Length in 32-bit wds)
65 TH%RES==: 37400,,       ; 3 Reserved (should be 0)
66 TH%CTL==:   374,,       ; 3 Control bits
67 TH%WND==:     3,,777760 ; 3 Window
68 TH%CKS==:777774,,       ; 4 Checksum
69 TH%UP==:      3,,777760 ; 4 Urgent Pointer
70                         ; 5 Start of Options/Data
71
72 TH$SRC==:<.BP TH%SRC,0>
73 TH$DST==:<.BP TH%DST,0 >
74 TH$SEQ==:<.BP TH%SEQ,1>
75 TH$ACK==:<.BP TH%ACK,2>
76 TH$THL==:<.BP TH%THL,3>
77 TH$RES==:<.BP TH%RES,3>
78 TH$CTL==:<.BP TH%CTL,3>
79 TH$WND==:<.BP TH%WND,3>
80 TH$CKS==:<.BP TH%CKS,4>
81 TH$UP==: <.BP TH%UP, 4>
82 TH$OPT==:<441000,,5>    ; An ILDB-type pointer to start of options.
83
84         ; Control bit definitions (as located in full word)
85 TC%URG==:<200,,>                ; Urgent Pointer significant
86 TC%ACK==:<100,,>                ; Ack field significant
87 TC%PSH==:< 40,,>                ; Push Function
88 TC%RST==:< 20,,>                ; Reset connection
89 TC%SYN==:< 10,,>                ; Synchronize sequence numbers
90 TC%FIN==:<  4,,>                ; Finalize - no more data from sender
91 \f
92 ; TCP Connection tables, normally indexed by I
93 ; These correspond to what the TCP document (RFC-793) calls
94 ; the "Transmission Control Block" parameters.
95 ; A TCB is "in use" if either XBUSER or XBSTAT is non-zero.
96 ;       XBUSER is set if a user job has channels associated with the TCB.
97 ;       XBSTAT is set if TCP is dealing with the TCB.
98 ; PI level will never touch any TCBs which have a zero XBSTAT, so it is
99 ;       safe for the MP level to hack a zero-XBSTAT TCB without using NETOFF.
100
101 IFNDEF XBL,XBL==10.     ; Allow this many TCP connections for now.
102
103 EBLK    ; General variables
104
105 XBUSER: BLOCK XBL       ; RH User index
106         XB%STY==:<770000,,>     ; TTY # of STY connected to (0 if none)
107         XB%ICH==:<007700,,>     ; Input  channel #+1 (77=IOPUSHed)
108         XB%OCH==:<000077,,>     ; Output channel #+1 (77=IOPUSHed)
109         XB$STY==:<.BP XB%STY,XBUSER>
110         XB$ICH==:<.BP XB%ICH,XBUSER>
111         XB$OCH==:<.BP XB%OCH,XBUSER>
112 XBSTAT: BLOCK XBL       ; <flags>,,<TCP state>
113         ; Connection flags (internal to ITS)
114         %XBMPL==:SETZ   ; Current output segment locked at MP level (IOT)
115                         ; This must be sign bit for SGNSET/PCLSR to work.
116         %XBCTL==:<374,,> ; Array of output request bits
117         IFN %XBCTL-TH%CTL,.ERR %XBCTL flags must be the same as TH%CTL!!
118                         ; For all bits in %XBCTL the general meaning is
119                         ; "Set this bit in next outgoing segment".  If no bits
120                         ; are set, output is sent every 2 sec, otherwise every
121                         ; 1/2 sec.  If %XBNOW is set, output is sent as soon
122                         ; as something notices it.
123         %XBNOW==:<1,,>  ; Send output segment ASAP (else 1/2 sec clock)
124         %XBACF==:<2,,>  ; Our FIN has been ACKed
125
126         %XBABT==:< 400,,>       ; We're aborting.
127         %XBFIN==:<1000,,>       ; FIN received for input, input queue will not
128                                 ; get any more additions.
129 ;       %XBWOK==:<100,,> ; State is OK for user to write (else get IOC err)
130 ;       %XBROK==:<200,,> ; State is OK for user to read (else get IOC err)
131         
132         ; Connection state, as in TCP document (RFC-793)
133         ; Some test/dispatch code depends on the fact that the first
134         ; 4 states have the values they do.
135         ;   ** NOTE: These .XSzzz symbols are not advertised to users.
136         ;   ** Maybe I'll rename them in here sometime. --  CSTACY 9/84
137         .XSCLS==:0      ; Closed (must be zero)
138         .XSSYQ==:1      ; ADDITIONAL ITS STATE: Syn-Queued
139         .XSLSN==:2      ; Listen
140         .XSSYN==:3      ; Syn-Sent
141         .XSSYR==:4      ; Syn-Rcvd
142         .XSOPN==:5      ; Established (Open)
143         .XSFN1==:6      ; Fin-Wait-1
144         .XSFN2==:7      ; Fin-Wait-2
145         .XSCLW==:10     ; Close-Wait
146         .XSCLO==:11     ; Closing
147         .XSCLA==:12     ; Last-Ack
148         .XSTMW==:13     ; Time-Wait
149         .XSTOT==:14     ; Total # of states
150 XBSTAU: BLOCK XBL       ; User Channel state <input>,,<output>
151 XBCLSU: BLOCK XBL       ; Close reason <input>,,<output>
152                 .XCNTO==:0      ; Never opened
153                 .XCUSR==:1      ; Closed by user
154                 .XCFRN==:2      ; Closed by foreign host
155                 .XCRST==:3      ; Fgn host reset things
156                 .XCDED==:4      ; Fgn host dead (apparently)
157                 .XCINC==:5      ; Incomplete transmission (retrans timeout)
158                 ;     ==:6      ; Byte size mismatch - can't happen
159                 .XCNCP==:7      ; Local TCP went down
160                 .XCRFS==:10     ; Fgn host refused connection (valid RST
161                                 ; received in SYN-SENT state)
162
163 XBPORT: BLOCK XBL       ; <remote port><local port><4 zero bits>
164                         ; It is set up this way for fast lookup of
165                         ; incoming segments.
166 XBHOST: BLOCK XBL       ; Remote host (HOSTS3 format)
167 XBLCL:  BLOCK XBL       ; Local host (HOSTS3 format)
168 XBNADR: REPEAT XBL,-1   ; Net host address to give the device driver (-1 none)
169
170 ; MP Input - see TCPI for detailed description
171 XBITQH: BLOCK XBL       ; Input Segment TCP queue header
172 XBINBS: BLOCK XBL       ; Total # bytes in input queue
173 XBINPS: BLOCK XBL       ; Total # segments in input queue
174 XBIBP:  BLOCK XBL       ; Main prog BP to input
175 XBIBC:  BLOCK XBL       ;  # bytes available for this BP
176
177 ; MP Output - see TCPW for detailed description
178 XBOCOS: BLOCK XBL       ; Current Output Segment pointer (0 if none)
179 XBOBP:  BLOCK XBL       ; Main prog BP into output segment
180 XBOBC:  BLOCK XBL       ;  # bytes of room for this BP
181
182 XBORTP: BLOCK XBL       ; Retransmit parameters
183 XBORTQ: BLOCK XBL       ; Retransmit queue header
184 XBORTL: BLOCK XBL       ; Retransmit queue length (# of segments)
185 XBORTC: BLOCK XBL       ; Retransmit count (1st msg on queue)
186 XBORTT: BLOCK XBL       ; Retransmit timeout (1st msg on queue)
187
188 ; TCP Send Sequence Variables
189 XBSUNA: BLOCK XBL       ; Send Unacknowledged
190 XBSNXT: BLOCK XBL       ; Send Next
191 XBSWND: BLOCK XBL       ; Send Window (offered window)
192 XBSAVW: BLOCK XBL       ; Available window (between SNXT and SUNA+WND)
193 XBSUP:  BLOCK XBL       ; Send Urgent Pointer
194 XBSWL1: BLOCK XBL       ; Segment Seq number used for last window update
195 XBSWL2: BLOCK XBL       ; Segment Ack number used for last window update
196 XBSMSS: BLOCK XBL       ; Max seg size that receiver can handle
197
198 ; TCP Receive Sequence Variables
199 XBRNXT: BLOCK XBL       ; Receive Next
200 XBRWND: BLOCK XBL       ; Receive Window
201 XBRUP:  BLOCK XBL       ; Receive Urgent Pointer
202 XBRMSS: BLOCK XBL       ; Max seg size we are expecting/ have asked for
203
204 BBLK
205 \f
206 NTSYNL: SIXBIT /TCP/            ; Start SYS;ATSIGN TCP for random SYNs.
207 EBLK
208         0       ; Word for NUJBST etc to mung for above job starting
209
210 TCPUP:  -1      ; -1 to handle TCP stuff, 0 to turn off.
211 TCPUSW: 0       ; -1 to disable net conns from anyone but ourself (like NETUSW)
212                 ; Perhaps eventually this should be the same as NETUSW.
213 TCPRQN: 0       ; # of things in SYN queue, to keep it small
214 TCPRQL: 0       ; Index of last SYN queued.
215 TCPCRI: 0       ; Counter used for gensymming local port #s
216 TISSLU: 0       ; Last ISS used
217 TISSC:  0       ; Counter to further uniquize ISS
218 TCPLCP: 0       ; Last TCB index allocated
219 TCPBSW: -1 ? 0  ; Lock switch for allocating TCB indices
220 TCPTMO: 4*30.   ; Default timeout for retransmits (in 30'ths of sec)
221 BBLK
222
223 ; Macro to perform sequence-number range checking.
224 ; Note all numbers are 32-bit positive integers, modulo 2**32.
225 ; Use it like this:
226 ;       CMPSEQ <left>,<lt or le>,<seqno>,<lt or le>,<right>,<lerr>,<rerr>
227 ;               Left and Right are addrs of the range bounds.  One of them
228 ;                       must be an AC.
229 ;               Seqno must be an AC.
230 ;               LT and LE are the strings "<" and "=<".
231 ;               Lerr and Rerr are the places to JRST to if the left or
232 ;                       right compares fail, respectively.  Rerr can
233 ;                       be omitted and will default to Lerr.
234 ;  e.g.
235 ;       CMPSEQ A,<,D,=<,XBSNXT(I),TSI30
236 ; NOTE CAREFULLY that only existence within a range is checked,
237 ; and the bounds L,R of the range MUST be known to be L =< R!
238 ; It does not work to use CMPSEQ for the degenerate case
239 ;               CMPSEQ A,<,B,<,B,ERR
240 ; to see if A < B.
241
242 DEFINE CMPSEQ (L),C1,S,C2,(R),(OUTV1),(OUTV2)
243         %%%CML==0
244         %%%CMR==0
245 IFSE [C1][<]  %%%CML==CAMG
246 IFSE [C1][=<] %%%CML==CAMGE
247 IFSE [C2][<]  %%%CMR==CAML
248 IFSE [C2][=<] %%%CMR==CAMLE
249 IFE %%%CML&%%%CMR, .ERR Seq compare has bad relational arg
250         %%%CMX==CAMLE
251 IFSE [C1][=<] %%%CMX==CAML
252
253 IFGE L-20,IFGE R-20, .ERR Seq compare needs ACs
254
255 IFL L-20,CAMLE L,R      ; Skip if normal order, L =< R
256 .ELSE    CAMGE R,L
257           JRST [        ; Reverse order, R < L.  Check S < R & L < S
258                 %%%CMR S,R      ; Skipwin if S <(=) R
259                  %%%CMX S,L     ; Unusual test here, win if S >(~=) L
260                   JRST .+5      ; If either wins, win completely!
261 IFB OUTV2,      JRST OUTV1
262 .ELSE           CAML S,[020000,,] ? JRST OUTV1 ? JRST OUTV2
263                         ]
264                         ; Normal order, L =< R 
265                 %%%CML S,L      ; Skipwin if S >(=) L
266                  JRST OUTV1
267                 %%%CMR S,R      ; Skipwin if S <(=) R
268 IFB OUTV2,       JRST OUTV1
269 .ELSE            JRST OUTV2
270 TERMIN
271 \f
272 SUBTTL TCP Open system call
273
274 ; .CALL TCPOPN
275 ;       arg 1 - receive channel number
276 ;       arg 2 - transmit channel number
277 ;       arg 3 - local port # (-1 to gensym unique port #)
278 ;       arg 4 - foreign port # (-1 for wild)
279 ;       arg 5 - foreign host address (HOSTS3 fmt) (-1 for wild)
280 ;       arg 6 - Retransmission timeout (optional)
281
282 ;Control bits:
283 ;       - None needed for channels - they are opened as .UAI and .UAO
284 ;               automatically (no other modes possible).
285 ;       - 7 vs 8 bit ASCII transfers can be determined by user-space byte
286 ;               pointer used in SIOT.  System buffers are always 8-bit bytes.
287 %NOLSN==:100    ; Listen mode
288 %NOBBI==:200    ; Use big buffer for input  (not implemented yet)
289 %NOBBO==:400    ; Use big buffer for output (not implemented yet)
290 %NOWDA==:1000   ; Use word-align algorithm on transmit (not implemented yet)
291         
292 ; Note a value of -1 for either the foreign port or host will imply
293 ; that the call is a "listen".  For the time being, either also implies
294 ; the other, i.e. wild port means wild host and vice versa.  This is
295 ; because I havent figured out what the right thing to do is for the
296 ; various combinations that could result otherwise.
297 ; Word-align means that for the transmit side, all segments sent will
298 ; have the data aligned so that the first byte, and every fourth byte
299 ; after that, will start on a 32-bit word boundary.  This should
300 ; produce a noticeable speedup for transfers that involve large blocks
301 ; of words rather than small amounts of miscellaneous text.
302 ; For the latter, it only makes things worse, so is not the default.
303
304 ;  Return is semi-immediate; the call may
305 ; hang momentarily waiting for a free network buffer.  (Have timeout?
306 ; do a SKIPA SKIPA HANG to schedule, then fail if still none?)
307 ; Use NETBLK
308 ; to determine when the channels become open.  For a non-listen call,
309 ; there is an internal ITS timeout, but for listen the state can persist
310 ; forever.
311
312 TCPOPN: METER("TCP: syscal tcpopn")
313         MOVEI A,(A)
314         MOVEI B,(B)
315         CAIGE A,NIOCHN
316          CAIL B,NIOCHN
317           JRST OPNL14           ; Bad channel # argument
318         CAIN A,(B)
319          JRST OPNL33            ; Illegal to use same channel # for both
320         MOVEI J,(B)
321         HRLI J,(A)              ; Save chan #s in J/ <rcv>,,<xmit>
322         PUSH P,C
323         PUSH P,D
324         PUSH P,E
325         PUSH P,J
326         MOVEI R,(A)             ; Close receive chan
327         ADDI R,IOCHNM(U)
328         PUSHJ P,CCLOSE          ; Close whatever is already on channels.
329         HRRZ R,(P)              ; Close xmit chan
330         ADDI R,IOCHNM(U)
331         PUSHJ P,CCLOSE
332         POP P,J
333         POP P,E
334         POP P,D
335         POP P,C
336
337         HLRZM J,UUAC(U)         ; Remember input channel # for errs.
338         SKIPN TCPUP             ; If TCP disabled,
339          JRST OPNL7             ; Fail, "device not ready".
340         CALL SWTL               ; Lock TCB assignment switch
341            TCPBSW
342         MOVE I,TCPLCP
343         SOJL I,TCPO2
344 TCPO1:  SKIPN XBUSER(I)         ; Hunt for free TCB
345          SKIPE XBSTAT(I)        ; Must be both closed and unassigned.
346           SOJGE I,TCPO1
347         JUMPGE I,TCPO3          ; Jump if got one!
348 TCPO2:  MOVEI I,XBL             ; Hit beginning, wrap back to end
349         CAMN I,TCPLCP
350          JRST OPNL6             ; No free TCB's available
351         MOVEM I,TCPLCP          ; Might as well make faster next time
352         SOJA I,TCPO1
353
354 TCPO3:  MOVEM I,TCPLCP          ; Save scan pointer for next time
355         JRST TCPO4              ; (This is here for patching. -CSTACY)
356
357         ; Got an index, now see if we're going to do a LISTEN
358         ; or an active open.
359 TCPO4:  SETZ W,                 ; Assume active
360         CAME C,[-1]             ; Verify local port is OK
361          CAIG C,177777
362           CAIA
363            JRST OPNL11          ; Complain "illegal file name"
364         CAMN D,[-1]
365          AOJA W,.+3
366           CAILE D,177777
367            JRST OPNL11
368         CAMN E,[-1]
369          ADDI W,2
370         ; W = 0 if no wildcards, =1 if port wild, =2 if host wild, =3 both.
371         MOVE B,CTLBTS(U)        ; Get control bits for call
372         CAIE W,
373          TRO B,%NOLSN           ; Set "Listen" bit if implied by args.
374 ; Crock - if either is wild, ensure both are.
375         CAIE W,
376          SETOB D,E
377
378         SETZ R,                 ; Say we have no buffer
379         TRNE B,%NOLSN           ; Skip if not listening, doing active open.
380          JRST TCPO20            ; Listening, don't need buffer.
381
382         ; No wild-cards, this is going to be an active open.  We will need
383         ; a buffer to send the initial SYN, so let's get it now and get
384         ; all possible PCLSR'ing over with, before turning off the NET PI.
385         CALL PKTGFI             ; Get a free packet, skip unless fail.
386          CAIA                   ; Didn't get, skip to schedule.
387           JRST TCPO15           ; Got it!
388         SKIPA
389          SKIPA                  ; Force a schedule
390           CALL UFLS
391         CALL PKTGFI             ; Try again.  If we fail again, net is full,
392          JRST OPNL6             ;  so better just return "device full" err.
393 TCPO15: MOVEI R,(A)             ; We have buffer!  Fall through.
394         TRCPKT R,"TCPO15 Alloc to send initial SYN"
395
396         ; Okay, nothing can stop us now from running through to completion.
397         ; We do all the following code with net interrupts OFF so that
398         ;       (a) We can scan all TCBs for port/host conflicts and be
399         ;               sure we checked everything right,
400         ;       (b) Incoming segments at int level won't be confused by
401         ;               an inconsistent state for this TCB.
402         ;       (c) We can check the pending-RFC queue safely.
403 TCPO20: CONO PI,NETOFF          ; Don't let PI level see dirty work.
404         CAMN C,[-1]
405          JRST [ CALL TCPPCR     ; Assign unique TCP port #
406                 ROT D,-16.      ; Put fgn port in high 16 bits
407                 DPB A,[.BP TH%DST,D]    ; Deposit local port
408                 JRST TCPO30]    ; Note that since port is unique, no
409                                 ; possible conflict with existing, so skip chk.
410                                 ; Also, low 4 bits indicate wildness if set.
411
412         ; Note that low 4 bits of XBPORT are set to indicate wildness.
413         ; This ensures that TCPIS won't find them, but TSISQ will.
414         ; Have specific local port, check to make sure it doesn't already
415         ; exist in TCB tables.
416         ROT D,-16.              ; Get fgn port in high 16 bits
417         DPB C,[.BP TH%DST,D]    ; Put together the ports word
418         MOVSI T,-XBL
419 TCPO22: CAMN D,XBPORT(T)        ; Look for matching port set
420          SKIPN XBSTAT(T)        ; which is in use
421           AOBJN T,TCPO22
422         JUMPL T,TCPO91          ; Ugh, found match!  Must fail...
423
424         ; OK, D has our unique port set, and we're ready to set things up.
425 TCPO30: MOVEM D,XBPORT(I)       ; Store port set <remote><local>
426         SKIPL A,E
427          CALL CVH3NA            ; Make sure it's HOSTS3 format.
428         MOVEM A,XBHOST(I)       ; Store foreign host
429         CALL IPBSLA             ; Call IP for best local address
430         MOVEM A,XBLCL(I)
431         CALL TXBINI             ; Initialize the TCB
432         CALL TCPMSS             ; Set default MSS values. Reexamined when 
433                                 ; foreign host known if this is a wild listen.
434         CALL TCPRWS             ; Open a default receive window
435         HRRZM U,XBUSER(I)       ; Make TCB/index in use
436         HLRZ A,J                ; Get back saved rcv channel #
437         DPB A,[XB$ICH (I)]      ; Deposit input channel
438         DPB J,[XB$OCH (I)]      ; and output channel
439         MOVE B,[0101,,0]        ; Increment both channel #'s by 1
440         ADDM B,XBUSER(I)        ; So can distinguish chan 0 from no chan.
441         HRLZ T,I                ; Set up user's IOCHNM words
442         HRRI T,TCPDUI
443         ADDI A,IOCHNM(U)
444         MOVEM T,(A)             ; Set up input chan <TCB idx>,,TCPDUI
445         HRRI T,TCPDUO
446         ADDI J,IOCHNM(U)
447         MOVEM T,(J)             ; Set up output chan <TCB idx>,,TCPDUO
448
449         ; Search pending-RFC queue to make sure we match up or reject
450         ; with stuff in there.
451         LDB B,[.BP TH%DST,XBPORT(I)]    ; B gets local port #
452         SETO D,                 ; D is -1 for any PE ptr.
453         CALL TCPRQS             ; Search queue, return index in A
454         JUMPL A,TCPO41          ; Ignore further RFC checks if nothing.
455         MOVEI C,(A)
456         HRRZ A,XBITQH(C)
457         CAIN A,
458          BUG HALT
459         HLRZ W,PK.IP(A)
460         HLRZ H,PK.TCP(A)
461         TRNE D,17               ; If we're "wild" accepting any request,
462          JRST TCPO35            ; Take it!
463         LDB B,[IP$SRC (W)]      ; No, must try full match.
464         CAMN B,XBHOST(I)        ; If hosts match
465          CAME D,TH$SRC(H)       ; and ports match too
466           JRST TCPO40           ; (don't)
467
468         ; Matching request!!
469         ; For now, we ignore the listen/active distinction here, and
470         ; always try to establish connection with the pending RFC.
471         ; So, can flush use of R for listen flag.  Have to flush the
472         ; extra buffer if it was "active" open, though, since we can
473         ; just re-use the pending-RFC packet.
474 TCPO35: METER("TCP: Open matched pending RFC")
475         JUMPN R,TCPO36
476         MOVEI Q,XBITQH(C)       ; If don't already have buffer,
477         CALL PKQGF(PK.TCP)      ; Get it from the queued SYN (C is idx to)
478         SKIPN R,A               ; It had better have a buffer!
479          BUG HALT
480         TRCPKT R,"TCPO36 Queued SYN used to answer pending RFC rqst"
481 TCPO36: LDB B,[IP$SRC (W)]
482         MOVEM B,XBHOST(I)       ; Set host address
483         LDB B,[IP$DST (W)]
484         MOVEM B,XBLCL(I)        ; Use local address the other end wants
485         MOVE D,TH$SRC(H)
486         MOVEM D,XBPORT(I)       ; And ports
487         CALL TCPMSS             ; Find default segment sizes for connection
488         CALL TCPRWS             ; Set up receive window
489         EXCH C,I                ; C identifies slot of queued SYN.
490         CALL TSISQF             ; Flush the SYN from queue!
491         MOVEI I,(C)
492         CALL TSILSX             ; Invoke interrupt level SYN+ACK, re-uses
493                                 ; the packet and sets state and everything.
494         JRST TCPO80             ; OK, take win return.
495
496         ; Request doesn't match, restore it and fall thru.
497 TCPO40:
498 ;       MOVEI Q,TCPRQH          ; Thought we had something but didn't,
499 ;       CALL PKQPF(PK.TCP)      ; so put back on queue.
500
501         ; No matching request on pending-RFC queue.
502 TCPO41: CAIN R,                 ; Skip if handling active open
503          JRST [ MOVEI A,.XSLSN  ; No, handling a listen.
504                 JRST TCPO70]    ; Just change state and we're done.
505         
506         ; Active open, must fire off initial SYN.
507         ; R has PE ptr to free packet to be used for the SYN.
508         CALL TCPISS             ; Get initial sequence #
509         MOVEM A,XBSUNA(I)       ; Set up sequence vars
510         MOVEM A,XBSNXT(I)
511         MOVSI T,(TC%SYN)        ; Note no ACK in initial segment!
512         TRCPKT R,"TCPO41 Send initial SYN"
513         CALL TSOSSN             ; Send SYN segment (clobber mucho ACs)
514         MOVEI A,.XSSYN          ; Set state to SYN-SENT and fall thru.
515
516 TCPO70: HRRM A,XBSTAT(I)        ; Set state LISTEN or SYN-SENT.
517         CALL TCPUSI             ; Change user state.
518 TCPO80: CONO PI,NETON
519         JRST LSWPJ1             ; Success return, unlock switch and skip.
520
521         ; Port match failure, must back off and fail.
522 TCPO91: CONO PI,NETON   ; No need to hide our shame
523         SKIPE A,R       ; If we had a buffer,
524          CALL PKTRT     ; return it to freelist.
525         JRST OPNL13     ; Say "file already exists".
526
527 ; TXBINI - Initialize TCB connection table entries for specific index.
528 ;       The things it doesn't touch are commented out below.
529 ;       I/ TCB index
530
531 TXBINI:
532 ;       SETZM XBUSER(I)         ; Set after
533 ;       SETZM XBSTAT(I)         ; Set after
534         SETZM XBSTAU(I)
535         SETZM XBCLSU(I)
536 ;       SETZM XBPORT(I)         ; Set prior
537 ;       SETZM XBHOST(I)         ; Set prior     
538 ;       SETZM XBLCL(I)
539         SETOM XBNADR(I)
540
541         ; I/O vars
542         SKIPE XBITQH(I)
543          BUG CHECK,[TCP: Init TCB has input, I=],OCT,I,[list ],OCT,XBITQH(I)
544         SETZM XBITQH(I)
545         SETZM XBINBS(I)
546         SETZM XBINPS(I)
547         SETZM XBIBP(I)
548         SETZM XBIBC(I)
549
550         SKIPE XBOCOS(I)
551          BUG CHECK,[TCP: Init TCB has output, I=],OCT,I,[list ],OCT,XBOCOS(I)
552         SETZM XBOCOS(I)
553         SETZM XBOBP(I)
554         SETZM XBOBC(I)
555
556         ; Retransmit stuff
557         SETZM XBORTP(I)
558         SKIPE XBORTQ(I)
559          BUG CHECK,[TCP: Init TCB has retrans, I=],OCT,I,[list ],OCT,XBORTQ(I)
560         SETZM XBORTQ(I)
561         SETZM XBORTL(I)
562         SETZM XBORTC(I)
563         SETZM XBORTT(I)
564
565         ; TCP Send Sequence Initialization
566         SETZM XBSUNA(I)
567         SETZM XBSNXT(I)
568         SETZM XBSWND(I)
569         SETZM XBSAVW(I)
570         SETZM XBSUP(I)
571         SETZM XBSWL1(I)
572         SETZM XBSWL2(I)
573 ;       SETZM XBSMSS(I)         ; Set after
574
575         ; TCP Receive Sequence Initialization
576         SETZM XBRNXT(I)
577         SETZM XBRUP(I)
578 ;       SETZM XBRMSS(I)         ; Set after
579 ;       SETZM XBRWND(I)         ; Set after
580         RET
581
582 ; TCPPCR - Port Create.  Creates a unique local port #.
583 ;       Returns # in A.  Current algorithm is very simple/dumb.
584 ;       Must only be called at MP level with NETOFF.
585 ;       Clobbers T,Q
586
587 TCPPCR: PUSH P,B
588         MOVEI A,(U)     ; Get user index
589         IDIVI A,LUBLK   ; Find job #
590         AOS B,TCPCRI    ; Bump and get new counter
591         ROT B,-8.       ; Put low bits into high
592         LSHC A,8.       ; Then shift them into port #
593         CALL TCPPLU     ; See if this port unique or not.
594          JRST [ AOS TCPCRI      ; If not, AOS stuff and keep going.
595                 AOJA A,.-1]
596         POP P,B
597         RET
598
599 ; TCPPLU - Port Lookup.  Skips if port # unique among local ports.
600 ;       A/ port #
601 ;       Clobbers T, Q.
602 ; Returns .+1 if fail (number not unique)
603 ;       T/ idx of matching TCB
604
605 TCPPLU: LSH A,4         ; Shift over for easier compare
606         MOVSI T,-XBL
607 TCPLU2: SKIPN Q,XBPORT(T)
608          JRST TCPLU3
609         AND Q,[TH%DST]
610         CAMN A,Q
611          JRST TCPLU7
612 TCPLU3: AOBJN T,TCPLU2
613         AOS (P)
614 TCPLU7: LSH A,-4
615         RET
616
617 ; TCPMSS - Determine and set max bytes per segment for TCB in I
618 ;       I/ TCB index. XBHOST should be set already.
619 ;       Bashes A, T
620 ; Base maximum TCP segment sizes on size of largest datagram IP wants
621 ; to send to destination. This sets the default sizes. We will tell
622 ; the foreign side what we want (XBRMSS) with a TCP MSS option in the
623 ; outgoing SYN. We will adjust what we send (XBSMSS) down if foreign
624 ; side requests it with MSS opton in an incoming SYN.
625
626 TCPMSS: MOVE A,XBHOST(I)        ; Foreign address
627         CALL IPMTU              ; IP datagram size to T
628         SUBI T,40.
629         MOVEM T,XBSMSS(I)       ; Set default send and receive segment sizes
630         MOVEM T,XBRMSS(I)
631         RET
632
633 \f
634 SUBTTL Other TCP device system call routines
635
636 ; Device name in DEVTAB, device code in DCHSTB, index in RSTB to some tables
637
638 ; OPEN - from DEVADR
639
640 TCPO:   JRST OPNL12             ; Say "mode not avail"
641         ; Save rest temporarily.
642         HLRS C
643         MOVSI A,(A)             ; Save RH of FN1 in LH of IOCHNM
644         JSP Q,OPSLC7
645           TCPDUI,,TCPDUO
646           TCPDBI,,TCPDBO
647           TCPDUI,,TCPDUO
648           TCPDBI,,TCPDBO
649
650 ; CLOSE - from CLSTB
651 ;       R/ addr of IOCHNM word
652
653 TCPCLS: METER("TCP: syscal close")
654         HLRZ I,(R)              ; Get TCB index from LH of IOCHNM
655         CAIL I,XBL              ; Make sure it's reasonable
656          BUG HALT,[TCP: CLS idx bad]
657         HRRZ A,XBUSER(I)        ; Verify user
658         CAIE A,(U)
659          BUG HALT,[TCP: CLS usr bad]
660         SETO D,                 ; See if input or output
661         HRRZ A,(R)
662         CAIN A,TCPDUO           ; Output?
663          AOSA D
664           CAIN A,TCPDUI         ; Input?
665            ADDI D,1
666         CAIGE D,                ; D/ 0 for input, 1 for output.
667          BUG                    ; IOCHNM value screwed up??
668         LDB A,[XB$ICH (I)]      ; Get input chan # according to TCB
669         LDB B,[XB$OCH (I)]      ; Ditto output
670         MOVEI C,(R)
671         SUBI C,IOCHNM(U)        ; Find channel # we're closing
672         ADDI C,1                ; Increment since TCB # is really #+1
673         CAME C,A(D)             ; Compare with channel # in TCB
674          BUG HALT,[TCP: Close chan not same as TCB chan]
675         JUMPN D,[MOVEI D,2
676                 CAIE A,
677                  MOVEI D,3
678                 JRST TCPC06]
679         CAIE B,
680          IORI D,1
681 TCPC06:
682         ; D is now a 2-bit channel status index.
683         ; Bit 1.2 is 0 for input, 1 for output.
684         ; Bit 1.1 is 0 if other channel is closed, 1 if it is still open.
685         SKIPN XBSTAT(I)         ; Perhaps already gone?
686          JRST TCPCL8            ; Yeah, flush channel etc.
687         PUSH P,D
688         CONO PI,NETOFF          ; Ensure that state doesn't change on us.
689         HRRZ J,XBSTAT(I)
690         CAIL J,.XSTOT
691          BUG HALT,[TCP: CLS state bad]
692         XCT TCPCXT(J)   ; Invoke closure stuff appropriate for state
693         CONO PI,NETON   ; TCB state hacking done, can re-enable ints.
694         POP P,D
695
696         ; Remove links between user channel and TCB.  If both channels
697         ; are gone, XBUSER is cleared completely.
698         ; The TCB is not necessarily closed at this point (XBSTAT zero)
699         ; but TCP will look after it independently to ensure it eventually
700         ; goes away.
701 TCPCL8: SETZ B,                 ; Get a zero
702         MOVEI T,.XCUSR          ; Use this for "Close reason" if needed
703         TRNE D,2                ; Remember D bit 1.2 indicates output chan
704          JRST [ DPB B,[XB$OCH (I)]      ; Yup, clear output chan.
705                 CALL TCPUCO             ; Set close reason if necessary
706                 HRRZ A,XBOCOS(I)        ; Does a COS buffer exist?
707                 CAIN A,
708                  JRST TCPCL9            ; Nope, nothing to flush.
709                 CALL PKTRTA             ; Aha, free it up.
710                 SETZM XBOCOS(I)
711                 SETZM XBOBP(I)
712                 SETZM XBOBC(I)
713                 JRST TCPCL9]
714         DPB B,[XB$ICH (I)]      ; Clear input chan.
715         CALL TCPUCI             ; Set close reason if need to.
716         CALL TXBIFL             ; Flush input queue
717
718 TCPCL9: TRNN D,1                ; Skip if other channel still there.
719          SETZM XBUSER(I)        ; Else flush whole word incl user index!
720         TRNE D,1                ; If a channel is left,
721          CALL TCPUSI            ; we may need to take interrupt on it.
722         LDB A,[XB$STY (I)]      ; Was a STY connected to channel?
723         JUMPE A,CPOPJ           ; Return if not.
724         MOVEI I,(A)             ; Ugh, must disconnect it!  Set up TTY #
725         CALL NSTYN0             ; Disconnect
726          JFCL
727         RET                     ; Return (CLOSE will clear IOCHNM/IOCHST)
728
729 TCPCLE: BUG CHECK,[TCP: Illegal state in CLOSE, J=],OCT,J,[ D=],OCT,D
730         CALL TXBFLS     ; Flush all of TCB but XBUSER
731         RET
732
733 TCPCXT: OFFSET -.
734 .XSCLS:: CALL TXBFLS    ; Closed already, but flush again to make sure
735 .XSSYQ:: CALL TCPCLE    ; Syn-Queued - can't happen!!
736 .XSLSN:: CALL TXBFLS    ; Listen        - flush TCB, enter closed state.
737 .XSSYN:: CALL TXBFLS    ; Syn-Sent      - flush TCB, enter closed state.
738 .XSSYR:: XCT TCPCXT+.XSOPN ; Syn-Rcvd - handled same as OPEN below
739 .XSOPN:: XCT (D)[       ; Established (Open)
740                 CALL TCPCLE     ; In (only)     - Can't happen
741                 JFCL            ; In (have Out) - Disconnect input
742                 CALL TCPC30     ; Out (only)    - Send FIN, enter FIN-WAIT-1
743                 CALL TCPC30]    ; Out (have In) -  "    "     "     "
744 .XSFN1:: XCT (D)[       ; Fin-Wait-1
745                 JFCL            ; In (only)     - Disconnect input
746                 CALL TCPCLE     ; In (have Out) - Can't happen
747                 CALL TCPCLE     ; Out (only)    - Can't happen
748                 CALL TCPCLE]    ; Out (have In) - Can't happen
749 .XSFN2:: XCT (D)[       ; Fin-Wait-2
750                 CALL TXBFLS     ; In (only)     - Flush, give up waiting
751                 CALL TCPCLE     ; In (have Out) - Can't happen
752                 CALL TCPCLE     ; Out (only)    - Can't happen
753                 CALL TCPCLE]    ; Out (have In) - Can't happen
754 .XSCLW:: XCT (D)[       ; Close-Wait
755                 CALL TCPCLE     ; In (only)     - Can't happen
756                 JFCL            ; In (have Out) - Disconnect input
757                 CALL TCPC70     ; Out (only)    - Send FIN, enter LAST-ACK
758                 CALL TCPC70]    ; Out (have In) -  "    "     "     "
759 .XSCLO:: XCT TCPCXT+.XSFN1 ; Closing - handled same as Fin-Wait-1 etc.
760 .XSCLA:: XCT TCPCXT+.XSFN1 ; Last-Ack - handled same as Fin-Wait-1 etc.
761 .XSTMW:: XCT TCPCXT+.XSFN1 ; Time-Wait - handled same as Fin-Wait-1 etc.
762 .XSTOT:: OFFSET 0
763
764         ; Closing output channel while in SYN-RCVD state.
765         ; Send a FIN and enter FIN-WAIT-1 state.
766 TCPC30: CALL TCPCLF
767         MOVEI J,.XSFN1
768         JRST TCPC75
769
770         ; Closing output channel  while in CLOSE-WAIT state.
771         ; Send a FIN and enter LAST-ACK state.
772 TCPC70: CALL TCPCLF
773         MOVEI J,.XSCLA
774 TCPC75: HRRM J,XBSTAT(I)
775         RET
776
777 TCPCLF: MOVSI T,(TC%ACK+TC%FIN+%XBNOW)  ; Tell TCP that output needs FIN and ACK.
778         JRST TCPOFR                     ; Go force out current buffer if any
779
780 ; TCPUC - Set "Reason-closed" states if not already set.
781 ;       T/ Reason to use, if none already exists.
782 ;       Clobbers Q
783 TCPUC:  CALL TCPUCI
784 TCPUCO: HRRZ Q,XBCLSU(I)
785         CAIN Q,
786          HRRM T,XBCLSU(I)
787         RET
788 TCPUCI: HLRZ Q,XBCLSU(I)
789         CAIN Q,
790          HRLM T,XBCLSU(I)
791         RET
792
793 ; TXBFLS - Flush all info about a TCB from TCP viewpoint.
794 ;       Mostly consists of freeing up all buffers used, and then
795 ;       clearing out most other data cells of the TCB.
796 ;       Note that XBUSER and XBSTAU are not affected!
797 ; TXBFLP - ditto but usable at PI level, it is careful not to smash
798 ;       things that MP level might be referencing.
799 ;  Clobbers A,T,Q
800 ; TXBIFL - Flushes input queue
801 ; TXBOFL - Flushes output queue (including retrans list!)
802
803 TXBFLS: SETZM XBSTAT(I)
804         CALL TXBIFL
805         CALL TXBOFL
806         SETZM XBPORT(I)
807         SETZM XBHOST(I)
808         RET
809
810 ; TXBFLP - Things to be careful of:
811 ;       - swiping COS
812 ;       - flushing input queue (don't touch it)
813
814 TXBFLP: CALL TXBOFL
815         SETZM XBSTAT(I)         ; Say off-limits to PI level now.
816         SETZM XBPORT(I)
817         SETZM XBHOST(I)
818         LDB T,[XB$ICH (I)]      ; See if input chan active
819         CAIN T,
820          CALL TXBIFL            ; No input chan, so ensure input q flushed
821         CALL TCPUSI             ; Alert user to mung
822         RET
823
824 TXBIFL: SETZM XBINBS(I)
825         SETZM XBINPS(I)
826         SETZM XBIBP(I)
827         SETZM XBIBC(I)
828         MOVEI Q,XBITQH(I)
829         CALL PKPFLS
830         SKIPE XBITQH(I)
831          BUG CHECK,[TCP: Incompl input fls I=],OCT,I,[list ],OCT,XBITQH(I)
832         CALL TCPRWS             ; Reset receive window.
833         RET
834
835 TXBOFL: HRRZ A,XBOCOS(I)        ; If current output seg exists,
836         CAIE A,
837          SKIPGE XBSTAT(I)       ; and isn't locked by MP level,
838           CAIA
839            JRST [CALL PKTRTA    ; then free it
840                 SETZM XBOCOS(I) ; and clear the pointer.
841                 SETZM XBOBP(I)
842                 SETZM XBOBC(I)
843                 JRST .+1]
844         SETZM XBORTT(I)
845         SETZM XBORTC(I)
846         MOVEI Q,XBORTQ(I)
847         CALL PKPFL              ; Flush retrans list carefully.
848         SKIPE XBORTL(I)
849          BUG CHECK,[TCP: Incompl output fls, I=],OCT,I,[list ],OCT,XBORTQ(I)
850         MOVE A,XBSNXT(I)
851         MOVEM A,XBSUNA(I)       ; Claim everything ACK'd.
852         SETZM XBSWND(I)         ; Zero our send window.
853         SETZM XBSAVW(I)         ; and available window
854         SETZM XBSUP(I)          ; and urgent pointer.
855         RET
856
857 PKPFLS: PUSH P,Q
858 PKPFL2: MOVE Q,(P)
859         CALL PKQGF(PK.TCP)
860         JUMPE A,POPQJ
861         CALL PKTRTA     ; Should always be freeable.
862         JRST PKPFL2
863
864 ; Ditto, but for flushing retransmit queue, which has to be special
865 ; since packets are linked on IP output list as well as TCP list.
866 ; Since we can't take packets off the IP output list here, we just set
867 ; a flag telling output PI level to ignore the packet.
868
869 PKPFL:  PUSH P,Q
870 PKPFL3: MOVE Q,(P)
871         CALL PKQGF(PK.TCP)
872         JUMPE A,POPQJ
873         CONO PI,PIOFF
874         MOVE T,PK.FLG(A)        ; Check packet flags
875         TLNN T,(%PKODN)         ; Output done?
876          JRST [ TLO T,(%PKFLS)  ; No, say to flush when hit it.
877                 MOVEM T,PK.FLG(A)
878                 CONO PI,PION
879                 TRCPKT A,"PKPFL3 Packet not flushed"
880                 JRST PKPFL4]
881         CONO PI,PION
882         CALL PKTRT
883 PKPFL4: SOSGE XBORTL(I)
884          BUG CHECK,[TCP: Retrans Q count err]
885         JRST PKPFL3
886 \f
887 SUBTTL TCP Main Program Input
888
889 ; All TCP input segments for a connection are put on a queue that
890 ; is headed at XBITQH.  When this header is zero, there is no more
891 ; input; if the %XBFIN flag is also set, the remote host has closed
892 ; its transmit side and there will never be any more input.
893 ;       Segments are only added by PI level, at the end of the queue.
894 ;       Segments are only removed by MP level IOTs, at the start of the queue.
895 ; (An incoming RST will of course flush the queue at PI level)
896
897 ; If XBIBP is non-zero, it points into the first segment on the input queue,
898 ; and XBIBC is also valid; things are ready for MP IOTing.
899 ; However, neither XBIBP nor XBIBC is meaningful if XBITQH is zero.
900
901 ; Input IOT - from IOTTB
902         SKIPA T,[SIOKT]         ; Come here for SIOT entry
903 TCPI:    MOVEI T,CHRKT
904         METER("TCP: syscal in")
905         HLRZ I,(R)              ; Get TCB index
906         
907         ; Verify state, do misc setup for reading
908         MOVSI B,(XB%STY)
909         TDNE B,XBUSER(I)        ; Can't IOT if direct-connected to STY.
910          JRST IOCR10            ; "Chan in illegal mode"
911         HLRZ B,XBSTAU(I)        ; Just reading state, don't need NETOFF.
912         SKIPG TCPTBI(B)         ; Ensure meta-state allows reading.
913          JRST [ HLRZ B,XBCLSU(I)        ; Can't read, see if reason OK
914                 CAIN B,.XCFRN           ; Only OK reason is clean fgn close.
915                  JRST UNIEOF            ; Yeah, just return quietly.
916                 JRST IOCR10]
917
918         MOVE E,[441000,,4]      ; 8-bit bytes, 4 to a word
919         MOVEI B,[
920             XBIBP(I)    ; Byte pointer
921             XBIBC(I)    ; # bytes to read
922             TCPIBG      ; Routine to get next buffer
923             TCPIBD      ; Routine to discard buffer
924             0           ; not used
925             TRNA        ; Negative - TCPIBG and TCPIBD will do waiting.
926                 ]
927         CALL (T)
928          CAIA
929           AOS (P)
930         SKIPG XBIBC(I)  ; If count for this buffer reached zero,
931          CALL TCPIBD    ; Flush it so XBITQH is valid indication of input avail
932         RET
933
934 ; TCPIBD - Discard input buffer, invoked by I/O.
935 ;       This is always called before TCPIBG is.
936
937 TCPIBD: SKIPN XBIBP(I)          ; Make sure something's there to discard.
938          RET                    ; Nope, gone or was never set up.
939         MOVEI Q,XBITQH(I)       ; Point to TCP input queue header
940         CALL PKQGF(PK.TCP)      ; Get first thing off queue, into A
941         CAIN A,                 ; Something better be there.
942          BUG HALT,[TCP: IOTI queue lost]
943
944         ; Check BP just out of sheer paranoia.
945         HRRZ T,XBIBP(I)         ; Find addr BP points to (maybe +1 actual)
946         HLRZ Q,PK.TCP(A)        ; Get addr of TCP header
947         CAIL Q,(T)              ; Header better be less than BP!
948          JRST TCPIB2
949         TRZ Q,PKBSIZ-1          ; Get addr of start of buffer
950         CAILE T,PKBSIZ(Q)       ; BP should be within or just past end.
951 TCPIB2:  BUG HALT,[TCP: IOTI BP incons]
952
953         ; Okay, end of paranoia, just flush the buffer.
954         LDB T,[PK$TDL (A)]      ; Find # chars we read
955         MOVN T,T
956         ADDM T,XBINBS(I)        ; Update # chars avail for input.
957         CALL PKTRT              ; Return packet to freelist.
958         SOSGE T,XBINPS(I)       ; Decrement count of segs on input queue
959          BUG CHECK,[TCP: Input Q count incons]
960         CAIL T,%TCPMI/2         ; If we are now handling past 50% input,
961          JRST [ MOVSI T,(TC%ACK)        ; Make sure we send an ACK
962                 IORM T,XBSTAT(I)        ; so new rcv window is reported.
963                 JRST .+1]
964         CONO PI,NETOFF
965         CALL TCPRWS             ; Set new receive window
966         CALL TXBIST             ; Get new input chan state
967         HRLM T,XBSTAU(I)        ; Set it.  Note interrupt is avoided here.
968         CONO PI,NETON
969         SETZM XBIBP(I)
970         SETZM XBIBC(I)
971         RET             ; Always return with simple POPJ
972
973 TCPRWS: MOVEI T,%TCPMI
974         SUB T,XBINPS(I)         ; Find # segs we can still queue up
975         CAIGE T,1               ; If no full segs left,
976          TDZA T,T               ; Zero the window, no more segs allowed
977           IMUL T,XBRMSS(I)      ; Else will take N * MSS bytes
978 TCPRW3: MOVEM T,XBRWND(I)
979         RET
980
981 IFN 0,[
982         ; This code turns out to lose because the code at TCPIS only
983         ; checks XBRWND to see whether to compact input or not, and as
984         ; long as XBRWND is non-zero, stuff will always be added to queue,
985         ; using up all the packet buffers.
986         ; Basically it's a question of whether or not to allow more input,
987         ; up to limits of last queued buffer, if the queue has too many
988         ; buffers on it.  Metering will show whether most other implementations
989         ; win or lose with our buffer-alloc type windowing.
990 TCPRW2: HLRZ Q,XBITQH(I)        ; Find # chars room in last seg
991         LDB T,[PK$TDL (Q)]
992         LDB Q,[PK$TDO (Q)]
993         ADDI Q,(T)
994         MOVEI T,576.
995         SUBI T,(Q)
996         CAIGE T,
997          SETZ T,
998         MOVEM T,XBRWND(I)
999         RET
1000 ]
1001
1002 ; TCPIBG - Get new input buffer (invoked by I/O, after TCPIBD)
1003 ; Return .+1 if can't get new buffer, must wait (Never, we do waiting)
1004 ; Return .+2 if OK, new BP and count set up.
1005 ; Return .+3 if "EOF", transfer complete
1006
1007 TCPIBG: SKIPE XBIBP(I)  ; Shouldn't be anything already there.
1008          BUG HALT,[TCP: IOTI buf incons]
1009 TCPIB3: SKIPN A,XBITQH(I)       ; See if anything in input queue
1010          JRST TCPIB5            ; No, go handle EOF.
1011         LDB T,[PK$TDL (A)]      ; Find # bytes input for this segment
1012         CAIN T,                 ; Something probably shd be there.
1013          BUG HALT,[TCP: IOTI null seg]
1014         MOVEM T,XBIBC(I)        ; Store as new # bytes
1015         LDB T,[PK$TDO (A)]      ; Get offset from start of header
1016         HLRZ Q,PK.TCP(A)        ; Get addr of TCP header
1017         ROT T,-2                ; Divide offset by 4
1018         ADDI Q,(T)              ; Point to right word
1019         LSH T,-34.              ; Right-justify the low 2 bits
1020         HRL Q,(T)[441000 ? 341000 ? 241000 ? 141000]    ; Get right LH for BP
1021         MOVEM Q,XBIBP(I)        ; Now store BP!
1022         JRST POPJ1              ; Say ready to go again...
1023
1024         ; No input available.  First check to see if there will ever
1025         ; be any more (FIN seen?), then whether to return right away or
1026         ; hang.
1027 TCPIB5: CONO PI,NETOFF          ; Avoid timing inconsistencies
1028         SKIPE A,XBITQH(I)       ; Check again
1029          JRST [ CONO PI,NETON   ; Got some??
1030                 JRST TCPIB3]    ; Try again.
1031         SKIPN XBINPS(I)         ; No, should also have no segments
1032          SKIPE XBINBS(I)        ; and no bytes
1033           BUG HALT,[TCP: IOTI count incons]
1034         MOVE A,XBRWND(I)        ; Save value of rcv window
1035         CALL TCPRWS             ; Then reset the window
1036         CAME A,XBRWND(I)        ; Was previous value correct?
1037          METER("TCP: RCV.WND out of synch")
1038         MOVE T,XBSTAT(I)        ; Get flags
1039         CONO PI,NETON
1040         TLNE T,(%XBFIN)         ; FIN seen, and input queue empty?
1041          JRST TCPIB6            ; Yes, true EOF now.
1042
1043         MOVE T,CTLBTS(U)        ; See if call had "don't-hang" bit set
1044         TRNE T,10
1045          JRST TCPIB7            ; No, return EOF.
1046         SKIPN XBITQH(I)         ; Wait until input queue has something.
1047          CALL UFLS              
1048         JRST TCPIBG             ; Then call again.
1049
1050 TCPIB6:
1051 TCPIB7: CALL TCPUSI             ; Adjust user state.
1052         JRST POPJ2              ; and return "EOF"
1053
1054 \f
1055 SUBTTL TCP Main Program Output
1056
1057 ; Output IOT - from IOTTB
1058 ; Output segments are chained together from XBORTQ, which is
1059 ; the "retransmit queue".
1060 ; The queue only contains segments which occupy sequence space, since
1061 ; these are the only ones which require ACKs and possible retransmit.
1062 ; All others are sent directly to the IP output queue.
1063 ; While the transmit connection is open,
1064 ;       Segments are only added by MP level IOTs, at the end of the queue.
1065 ;       Segments are only removed by PI level ACKs, at the start of the queue.
1066
1067 ; Main program I/O is done into the "Current Output Segment", which is NOT
1068 ; on the retransmit queue.  There are three variables related to this COS.
1069 ;       XBOCOS - <original # bytes XBOBC started with>,,<PE ptr to COS>
1070 ;       XBOBP - BP into the COS, for MP IOT writing.
1071 ;       XBOBC - Count of # bytes left that MP IOT can deposit into.
1072 ; Note that the maximum possible size of the buffer is kept in PK$TDL
1073 ; (TCP segment Data Length).  For windowing reasons it may be necessary
1074 ; to restrict the amount of space actually used, thus the initial value
1075 ; of XBOBC may be less than PK$TDL.  This is why the initial value is also
1076 ; copied into the RH of XBOCOS, so that when XBOBC counts out we know
1077 ; exactly how much of the buffer was actually used.  It is possible for
1078 ; XBOBC to be increased by interrupt level window processing, in order
1079 ; to increase utilization of the buffer.
1080 ; States:
1081 ;       If XBOCOS is zero, XBOBP and XBOBC must also be zero; there is
1082 ;               no COS.
1083 ;       If XBOCOS is non-zero (a current output seg exists), then:
1084 ;               if LH(XBOCOS) is zero, the segment hasn't yet been written
1085 ;                       into, and needs to be set up.
1086 ;                       XBOBP and XBOBC should be zero!
1087 ;               else the segment is set up for writing.  XBOBP should be set!
1088 ;                       If XBOBC is zero it means the segment now contains
1089 ;                       LH(XBOCOS) bytes of data.  If this number is less
1090 ;                       than PK$TDL (max possible seg data) then the count
1091 ;                       may be reset to allow further output into this
1092 ;                       segment, or it may simply be sent as is.
1093 ;
1094 ; The current segment is put on the retransmit queue (and IP output queue)
1095 ; when:
1096 ;       PI level (eg clock) decides it's time to send an ACK or do a FORCE.
1097 ;       MP level IOT fills up the segment completely.
1098 ;       MP level FORCE or CLOSE is invoked.
1099 ; The current segment is locked down during MP IOT, to keep PI level
1100 ; from ripping it away (which would leave entrails dangling).
1101 ; PCLSR'ing will clear this lock.  If TCP flushes the TCB at PI level
1102 ; for some reason, XBOCOS will be freed unless locked.  XBOBC and XBOBP
1103 ; will still be cleared even if locked, so as to cause a call to TCPOBW
1104 ; which will notice the condition and free the COS itself.
1105
1106         SKIPA A,[SIOKT]         ; Come here for SIOT entry
1107 TCPW:    MOVEI A,CHRKT
1108         METER("TCP: syscal out")
1109         HLRZ I,(R)              ; Get TCB index from IOCHNM wd
1110
1111         ; Verify state, do misc setup for writing, lock segment.
1112         CONO PI,NETOFF
1113         HRRZ B,XBSTAU(I)        ; Get output chan state
1114         SKIPG TCPTBO(B)         ; See if meta-state allows writing
1115          JRST IOCR10            ; Can't, say "chan not open" (ugh)
1116         MOVSI B,(XB%STY)
1117         TDNE B,XBUSER(I)        ; Also can't if direct-connected to STY.
1118          JRST IOCR10
1119         MOVSI B,(%XBMPL)        ; Set locked flag (must be sign bit!)
1120         IORM B,XBSTAT(I)
1121         CONO PI,NETON           ; Okay, we've got it.
1122         CALL SGNSET             ; Set PCLSR routine to unlock flag.
1123             XBSTAT(I)
1124         SKIPN XBOCOS(I)         ; If no COS there,
1125          SETZM XBOBC(I)         ; make SURE count is zapped so refill invoked.
1126         MOVE E,[441000,,4]      ; 8-bit bytes, 4 to a word
1127         MOVEI B,[
1128                 SETZ XBOBP(I)   ; Output BP found here (sign sez is output)
1129                 XBOBC(I)        ; # bytes of room remaining
1130                 TCPOBG          ; Routine to get another buffer (not used)
1131                 TCPOBW          ; Buffer full, routine to send it.
1132                 0               ; Not used
1133                 TRNA]           ; Negative - TCPOBG and TCPOBW will do waiting.
1134         CALL (A)
1135          CAIA
1136           AOS (P)               ; Pass on a skip return.
1137
1138         ; User IOT is done, now unlock the segment.
1139         ; We also check for wanting to do an immediate ACK and if needed
1140         ; ship out the current buffer right now, without waiting
1141         ; for the 1/2-sec clock to do it.
1142         SKIPN A,XBSTAT(I)       ; See if XBSTAT is still set
1143          JRST IOCR10            ; No, take IOC error return!
1144         CAIL A,                 ; It better still be locked!
1145          BUG CHECK,[TCP: Output not locked]
1146         CALL LSWPOP             ; Clear the lock flag
1147         TLNN A,(%XBNOW)         ; Was "immediate-send" flag set?
1148          RET                    ; Nope, can just return.
1149         METER("TCP: TCPW exit force")
1150         CONO PI,NETOFF
1151         MOVSI T,(TC%PSH)        ; Hmm, set up and shove out.
1152         CALL TCPOFR             ; and force out current output segment.
1153         CONO PI,NETON
1154         RET
1155
1156 TCPOBG: BUG CHECK,[TCP: IOT called wrong rtn (TCPOBG)]
1157         AOS (P)         ; If proceeded, can still win.  Make skip return
1158                         ; and drop through to TCPOBW.
1159
1160 ; TCPOBW - Write/Get output buffer, invoked by SIOKT/CHRKT when the
1161 ;       buffer count (XBOBC) is zero.  This routine can figure out
1162 ;       whether it needs to ship out a full buffer, or get a new
1163 ;       output buffer, or both.  Always returns with XBOBP and
1164 ;       XBOBC set up for additional output (otherwise it hangs and
1165 ;       can be PCLSR'd)
1166
1167 TCPOBW: SKIPE R,XBOCOS(I)       ; Get PE ptr to COS
1168          JRST [ HLRZ A,R        ; Got a COS, see if already set up
1169                 JUMPN A,TCPOB5  ; Jump if so.
1170                 JRST TCPOB2]    ; Else must set it up.
1171
1172         ; No current segment, must get a new one.
1173         HRRZ T,XBSTAU(I)        ; First ensure output state is OK.
1174         SKIPG TCPTBO(T)         ; Skip if still OK to output.
1175          JRST IOCR10            ; Blooie, say "Chan not open".
1176         CALL PKTGF              ; Get one, hang until we succeed.
1177         MOVEI R,(A)             ; Set up in std AC
1178         TRCPKT R,"TCPOBW Alloc for IOT output buffer"
1179         HRRZM R,XBOCOS(I)       ; Store ptr
1180
1181         ; Set up segment for IOT to deposit into.
1182 TCPOB2: MOVEI T,%TCPMO          ; Get max # segments allowed on queue
1183         CAMG T,XBORTL(I)        ; Hang until we have less than this.
1184          CALL UFLS              ; Note that conn closure will unhang too,
1185                                 ; because it flushes output queue.
1186         CALL TSOINI             ; Initialize the segment (set up W, H)
1187         LDB A,[PK$TDO (R)]      ; Find offset data should start at.
1188         TRNE A,3
1189          BUG HALT               ; Should always start at wd boundary!
1190         LSH A,-2                ; Find # words
1191         ADDI A,(H)              ; Add address of TCP header,
1192         HRLI A,441000           ; and now we have our initial BP.
1193         MOVEM A,XBOBP(I)        ; Set it up.
1194         LDB A,[PK$TDL (R)]      ; Get max length avail in this segment
1195
1196         ; Now have a fresh buffer and nothing else to wait for.
1197         ; Freeze the world, make sure it's still OK to output, and find
1198         ; out how big an output segment we can allow.
1199 TCPOB4: CONO PI,NETOFF
1200         HRRZ T,XBSTAU(I)        ; Still OK to output?  Check again.
1201         SKIPG TCPTBO(T)
1202          JRST [ MOVEI A,(R)     ; Bah, must return buffer.
1203                 CALL PKTRTA
1204                 SETZM XBOCOS(I)
1205                 CONO PI,NETON
1206                 JRST IOCR10]    ; Barf "Chan not open".
1207         MOVEI T,(I)             ; Get index in T for PCLSRing.
1208         CALL TCPOB9             ; Check available window
1209          JRST [ CONO PI,NETON   ; Window too small, allow ints
1210                 CALL TCPOB9
1211                  CALL UFLS
1212                 JRST TCPOB4]    ; Big enough, go back and re-try stuff.
1213         LDB Q,[PK$TDL (R)]      ; Get max # bytes available
1214         CAMLE Q,XBSAVW(I)       ; Greater than window?
1215          MOVE Q,XBSAVW(I)       ; Yeah, truncate down to this size.
1216         HRLM Q,XBOCOS(I)        ; Store original # bytes in LH of XBOCOS
1217         MOVEM Q,XBOBC(I)
1218         CONO PI,NETON
1219         RET                     ; Okay, all set up, return.
1220
1221 TCPOB9: MOVE A,XBSWND(T)
1222         LSH A,-2                ; Get 25% offered window
1223         CAML A,XBSAVW(T)        ; If 25% offered > avail window,
1224          RET                    ; punt and wait for better stuff.
1225         JRST POPJ1
1226
1227         ; Here when we were all set up, and output has used up all
1228         ; of the buffer space initially available.  Check to make sure
1229         ; there isn't more we can fill out, and if not then fire off
1230         ; the segment.
1231 TCPOB5: HLRZ T,XBOCOS(I)        ; Get # bytes we originally had
1232         CONO PI,NETOFF          ; Avoid magic changes in send window
1233         CAML T,XBSAVW(I)        
1234          JRST TCPOB6            ; Send window same or smaller (!), send seg.
1235         MOVE Q,XBSAVW(I)        ; Send window is bigger!  Get new size
1236         LDB A,[PK$TDL (R)]      ; Get max size
1237         CAMLE A,Q
1238          MOVEI A,(Q)            ; Use minimum of max size and send window.
1239         MOVEI Q,(A)             ; Save result
1240         SUBI A,(T)              ; Find # more bytes we can hack
1241         CAIG A,                 ; If there's no more,
1242          JRST TCPOB6            ; Just send it off anyway.
1243         HRLM Q,XBOCOS(I)        ; Hurray, got more!  Store new original #
1244         MOVEM A,XBOBC(I)        ; And set up new count
1245         CONO PI,NETON
1246         RET                     ; And return happily.
1247
1248 TCPOB6: TRCPKT R,"TCPOB6 IOT Send"
1249         CALL TCPOB7
1250         JRST TCPOBW
1251
1252 TCPOB7: DPB T,[PK$TDL (R)]      ; Okay, say this many bytes of data are in seg
1253         PUSH P,B
1254         PUSH P,C
1255         PUSH P,E
1256         MOVSI T,(TC%PSH)        ; Ensure seg is pushed out.
1257         IORM T,XBSTAT(I)
1258         CALL TSOSND             ; Send data segment (# bytes in PK.TCI)
1259                                 ; This clobbers a lot of ACs!
1260         SETZM XBOCOS(I) ; No current output segment now.
1261         CONO PI,NETON
1262         SETZM XBOBP(I)
1263         SETZM XBOBC(I)
1264         POP P,E
1265         POP P,C
1266         POP P,B
1267         RET
1268
1269 ; TCPOFR - Force out partially-filled current output segment
1270 ;       Must have NETOFF.
1271 ;       Called by FORCE and CLOSE at MP level
1272 ;       by TCPCLK at PI clock level
1273 ;       Note that we try to never have stuff in the COS which would
1274 ;       over-run our send window, by hanging in MP IOT.  This will
1275 ;       be slightly screwed up if the receiver suddenly decreases the window
1276 ;       size, since this routine always sends the whole thing anyway,
1277 ;       but it's probably OK (helps avoid SWS)
1278 ;       I/ TCB index
1279 ;       T/ additional flags to use (PUSH, URG, FIN)
1280 ;       Clobbers R and everything that TSOSND does (a lot!)
1281
1282 TCPOFR: MOVE A,XBSTAT(I)        ; Get flags for connection
1283         TLNE A,(%XBCTL)         ; Wants anything added on?
1284          IOR T,A                ; Yes, OR the bits in.
1285         JUMPL A,TCPOF6          ; If locked at MP level, don't send it!
1286         SKIPN R,XBOCOS(I)       ; See if current output seg exists
1287          JRST TCPOF5            ; No, can't hack now.
1288         HLRZ TT,R               ; Get # bytes of original buffer size
1289         JUMPE TT,TCPOF5         ; If none, nothing to hack.
1290         SUB TT,XBOBC(I)         ; Subtract # left, to get # bytes data
1291         CAIG TT,
1292          JRST [ SETZ TT,        ; No data, see if a flag wants to be sent.
1293                 TLNN T,(TC%FIN+TC%ACK+TC%SYN)   ; Any of these are impt.
1294                  JRST TCPOF9    ; Nope, do nothing.
1295                 JRST .+1]       
1296         DPB TT,[PK$TDL (R)]     ; Store back # bytes of real data
1297         AND T,[TH%CTL]          ; Mask off the flags
1298         IORM T,XBSTAT(I)        ; Stuff in as requests
1299         TRCPKT R,"TCPOFR Force send"
1300         CALL TSOSND             ; Send out the stuff
1301         SETZM XBOCOS(I)
1302         SETZM XBOBP(I)
1303         SETZM XBOBC(I)
1304 TCPOF9: RET
1305
1306         ; No current output segment, so no data to send.  Check, though,
1307         ; to see if any flags need sending.
1308 TCPOF5: TLNN T,(TC%SYN+TC%ACK+TC%FIN)
1309          RET                    ; Nope, just return.
1310         MOVE E,T                ; They do!  Save em against smashage
1311         CALL PKTGFI             ; Try to get a buffer (clobbers T,Q)
1312          JRST TCPOF6            ; Ugh, failed, see about setting flags.
1313         MOVEI R,(A)
1314         TRCPKT R,"TCPOF5 Alloc and send flags only in TCPOFR"
1315         MOVE T,E                ; Restore flags
1316         CALL TSOSNR             ; Set up the packet and send it!
1317         RET
1318
1319         ; Can't get packet now, so set up the request flags for later hacking.
1320         ; Also comes here when current output seg is locked at MP level.
1321 TCPOF6: AND T,[%XBCTL]          ; Clear out extraneous bits
1322         TLO T,(%XBNOW)          ; Ask to send stuff immediately
1323         IORM T,XBSTAT(I)        ; and set flags back.
1324         RET
1325 \f
1326 ; TCPOSB - Routine similar to TCPOBW, except that it doesn't hang,
1327 ;       so that it is suitable for calling at PI level (by STYNTC esp)
1328 ; Returns .+1 if can't set up output buffer for writing.
1329 ; Returns .+2 if output buff is all set up, with non-zero XBOBC.
1330
1331 TCPOSB: SKIPE R,XBOCOS(I)
1332          JRST [ HLRZ A,R        ; Have COS, see if already set up
1333                 JUMPN A,TCPOS5  ; Jump if so.
1334                 JRST TCPOS2]    ; Else just set it up.
1335         
1336         ; No current segment, get a new one.
1337         HRRZ T,XBSTAU(I)        ; First ensure output state is OK.
1338         SKIPG TCPTBO(T)         ; Skip if still OK to output.
1339          RET                    ; Blooie.
1340         CALL PKTGFI             ; Get one, skip if successful
1341          RET                    ; Sigh...
1342         MOVEI R,(A)             ; Set up in std AC
1343         TRCPKT R,"TCPOSB Alloc for STYNET output data"
1344         HRRZM R,XBOCOS(I)       ; Store ptr
1345
1346         ; Set up segment for IOT to deposit into.
1347 TCPOS2: MOVEI T,%TCPMO          ; Get max # segments allowed on queue
1348         CAMG T,XBORTL(I)        ; Fail if we have more than this.
1349          RET
1350         CALL TSOINI             ; Initialize the segment (set up W, H)
1351         LDB A,[PK$TDO (R)]      ; Find offset data should start at.
1352         TRNE A,3
1353          BUG HALT               ; Should always start at wd boundary!
1354         LSH A,-2                ; Find # words
1355         ADDI A,(H)              ; Add address of TCP header,
1356         HRLI A,441000           ; and now we have our initial BP.
1357         MOVEM A,XBOBP(I)        ; Set it up.
1358         LDB A,[PK$TDL (R)]      ; Get max length avail in this segment
1359
1360         ; Now have a fresh buffer and nothing else to wait for.
1361         ; Freeze the world, make sure it's still OK to output, and find
1362         ; out how big an output segment we can allow.
1363 TCPOS4: CONO PI,NETOFF
1364         HRRZ T,XBSTAU(I)        ; Still OK to output?  Check again.
1365         SKIPG TCPTBO(T)
1366          JRST [ MOVEI A,(R)     ; Bah, must return buffer.
1367                 CALL PKTRTA
1368                 SETZM XBOCOS(I)
1369                 CONO PI,NETON
1370                 RET]            ; Barf "Chan not open".
1371         MOVEI T,(I)             ; Get index in T for testing (no PCLSR)
1372         CALL TCPOB9             ; Check available window
1373          JRST NETONJ            ; Window too small, just return
1374
1375         LDB Q,[PK$TDL (R)]      ; Get max # bytes available
1376         CAMLE Q,XBSAVW(I)       ; Greater than window?
1377          MOVE Q,XBSAVW(I)       ; Yeah, truncate down to this size.
1378         HRLM Q,XBOCOS(I)        ; Store original # bytes in LH of XBOCOS
1379         MOVEM Q,XBOBC(I)
1380         CONO PI,NETON
1381         AOS (P)
1382         RET                     ; Okay, all set up, return.
1383
1384         ; Here when we were all set up, and output has used up all
1385         ; of the buffer space initially available.  Check to make sure
1386         ; there isn't more we can fill out, and if not then fire off
1387         ; the segment.
1388 TCPOS5: HLRZ T,XBOCOS(I)        ; Get # bytes we originally had
1389         CONO PI,NETOFF          ; Avoid magic changes in send window
1390         CAML T,XBSAVW(I)        
1391          JRST TCPOS6            ; Send window same or smaller (!), send seg.
1392         MOVE Q,XBSAVW(I)        ; Send window is bigger!  Get new size
1393         LDB A,[PK$TDL (R)]      ; Get max size
1394         CAMLE A,Q
1395          MOVEI A,(Q)            ; Use minimum of max size and send window.
1396         MOVEI Q,(A)             ; Save result
1397         SUBI A,(T)              ; Find # more bytes we can hack
1398         CAIG A,                 ; If there's no more,
1399          JRST TCPOS6            ; Just send it off anyway.
1400         HRLM Q,XBOCOS(I)        ; Hurray, got more!  Store new original #
1401         MOVEM A,XBOBC(I)        ; And set up new count
1402         CONO PI,NETON
1403         AOS (P)
1404         RET                     ; And return happily.
1405
1406 TCPOS6: TRCPKT R,"TCPOS6 STYNET Send"
1407         CALL TCPOB7
1408         JRST TCPOSB
1409 \f
1410 TCPBI:
1411 TCPBO:  RET             ; No-ops, labels left in case want to use.
1412
1413 ; STATUS - from LH(DTSTB)
1414 ;       Must return status in LH(D).  Must not smash C,R.
1415 ;       R/ addr of IOCHNM word
1416
1417 TCPSTA: HLRZ I,(R)      ; Get TCB index
1418         SKIPN XBUSER(I) ; Probably an error if this is zero.
1419          BUG CHECK,[TCP: STATUS on unused conn ],OCT,I
1420         SETZ D,
1421         SKIPN XBSTAT(I)
1422          RET
1423         HRRZ A,(R)      ; Find whether input or output
1424         CAIN A,TCPDUI
1425          SKIPA T,[TXBIST]
1426           MOVEI T,TXBOST
1427         CALL (T)
1428         DPB T,[140600,,D]
1429         RET
1430
1431
1432 TXBIST: HRRZ T,XBSTAT(I)
1433         CAIL T,.XSTOT
1434          BUG HALT
1435         SKIPGE T,XBCTBI(T)      ; Get conversion
1436          JRST [ SKIPN XBITQH(I) ; Must test for input avail - any segs?
1437                  SKIPA T,(T)    ; None avail, use standard
1438                   MOVE T,1(T)   ; Have some waiting, use alternate state
1439                 RET]
1440         RET
1441 XBCTBI: OFFSET -.
1442 .XSCLS:: SETZ [%NTCLS ? %NTCLI] ; 0 Closed 
1443 .XSSYQ:: 0                      ; Technically this is an impossible state...
1444 .XSLSN:: %NTLSN                 ; 1 Listen
1445 .XSSYN:: %NTSYN                 ; 4 Syn-Sent
1446 .XSSYR:: %NTSYR                 ; 2 Syn-Rcvd
1447 .XSOPN:: SETZ [%NTOPN ? %NTINP] ; 5/11 Established (open)
1448 .XSFN1:: SETZ [%NTOPN ? %NTINP] ; 7 Fin-Wait-1
1449 .XSFN2:: SETZ [%NTOPN ? %NTINP] ; 7 Fin-Wait-2
1450 .XSCLW:: SETZ [%NTCLU ? %NTCLI] ; 3/10 Close-Wait
1451 .XSCLO:: SETZ [%NTCLS ? %NTCLI] ; 7/10 Closing
1452 .XSCLA:: SETZ [%NTCLS ? %NTCLI] ; 7 Last-Ack
1453 .XSTMW:: SETZ [%NTCLS ? %NTCLI] ; 7 Time-Wait
1454 .XSTOT:: OFFSET 0
1455
1456
1457 TXBOST: HRRZ T,XBSTAT(I)
1458         CAIL T,.XSTOT
1459          BUG HALT
1460         SKIPGE T,XBCTBO(T)      ; Get conversion
1461          JRST [ SKIPN XBORTQ(I) ; Must test for output queued
1462                  SKIPA T,(T)    ; None, use standard
1463                   MOVE T,1(T)   ; Have some output waiting, use alternate state
1464                 RET]
1465         RET
1466 XBCTBO: OFFSET -.
1467 .XSCLS:: %NTCLS         ; 0 Closed 
1468 .XSSYQ:: 0              ; Technically this is an impossible state...
1469 .XSLSN:: %NTLSN         ; 1 Listen
1470 .XSSYN:: %NTSYN         ; 4 Syn-Sent
1471 .XSSYR:: %NTSYR         ; 2 Syn-Rcvd
1472 .XSOPN:: SETZ [%NTOPN ? %NTWRT]         ; 5/6 Established (open)
1473 .XSFN1:: %NTCLX         ; 7 Fin-Wait-1
1474 .XSFN2:: %NTCLX         ; 7 Fin-Wait-2
1475 .XSCLW:: SETZ [%NTOPN ? %NTWRT]         ; 5/6 Close-Wait
1476 .XSCLO:: %NTCLX         ; 7 Closing
1477 .XSCLA:: %NTCLX         ; 7 Last-Ack
1478 .XSTMW:: %NTCLX         ; 7 Time-Wait
1479 .XSTOT:: OFFSET 0
1480
1481
1482 \f
1483 ; WHYINT - from RH(DTSTB)
1484 ; Results are:
1485 ;       A/ %WYTCP
1486 ;       B/ <state>
1487 ;       C/ input  - # bytes in input buff
1488 ;          output - # bytes of room avail in output buff
1489 ;       D/ Close reason (only valid if state %NTCLS)
1490
1491 TCPWHY: HLRZ I,(R)              ; Get TCB index
1492         METER("TCP: syscal whyint")
1493         CAIL I,XBL
1494          BUG HALT,[TCP: WHY idx bad]
1495         CALL TCPSTA
1496         LDB B,[140600,,D]       ; Get state for channel
1497         HRRZ A,(R)              ; Find whether input or output
1498         CAIN A,TCPDUI
1499          JRST [ HLRZ D,XBCLSU(I)        ; Get input close reason
1500                 MOVSI C,(XB%STY)
1501                 TDNE C,XBUSER(I)        ; No input avail if direct-conn to STY
1502                  JRST [ SETZ C, ? JRST TCPWH5]
1503                 SKIPLE C,XBINBS(I)
1504                  JRST TCPWH5
1505                 SKIPN C,XBITQH(I)
1506                  JRST TCPWH5
1507                 LDB C,[PK$TDL (C)]
1508                 JRST TCPWH5]
1509         HRRZ D,XBCLSU(I)        ; Get output close reason
1510         SKIPN C,XBOBC(I)        ; Get # bytes of room left in current pkt
1511          JRST [ MOVEI C,%TCPMO  ; If none, return total queue space instead
1512                 SUB C,XBORTL(I)
1513                 IMUL C,XBSMSS(I)
1514                 CAIG C,
1515                  SETZ C,
1516                 JRST .+1]
1517 TCPWH5: MOVEI A,%WYTCP
1518         JRST POPJ1
1519         
1520
1521
1522 ; RFNAME - from LH(DRFNTB)
1523 ;       A/ LH of IOCHNM word for channel.
1524
1525 TCPRCH: MOVEI I,(A)
1526         LDB B,[.BP TH%DST,XBPORT(I)]
1527         LDB C,[.BP TH%SRC,XBPORT(I)]
1528         MOVE D,XBHOST(I)
1529         MOVEI W,4
1530         POPJ P,
1531
1532 ; RFPNTR - from RH(DRFNTB)
1533 TCPRFP: JRST OPNL34
1534
1535 ; IOPUSH/POP - from LH(RSTBI)
1536 TCPIOP: HRRZ T,R
1537         SUBI T,IOCHNM(U)
1538         CAIN I,
1539          SKIPA T,[77]   ; IOPUSH, use 77
1540           ADDI T,1      ; IOPOP, use chan+1
1541         HLRZ I,(R)      ; Get TCB index
1542         HRRZ B,(R)      ; Get direction
1543         CAIN B,TCPDUI   ; as a BP to chan #
1544          SKIPA B,[XB$ICH (I)]
1545           MOVE B,[XB$OCH (I)]
1546         DPB T,B         ; Store new saved channel #
1547         POPJ P,
1548
1549 ; RESET - from RH(RSTBI)
1550 ;       This doesn't have to do anything for a while yet.
1551 TCPRST:
1552         POPJ P,
1553
1554 ; FORCE - from LH(DFRCTB)
1555 ;       Should force out the TCP segment currently being written,
1556 ;       and give it a good shove (ie PUSH).
1557 ;       A/ LH of IOCHNM word, in RH.
1558 ;       H/ IOCHNM word
1559 ;       R/ <LH of CLSTB entry>,,<addr of IOCHNM word>
1560 TCPFRC: METER("TCP: syscal force")
1561         HRRZ B,(R)              ; This should be a TCP output channel.
1562         CAIE B,TCPDUO           ; If not output, must be input, so
1563          JRST OPNL2             ; say "wrong direction".
1564         HLRZ I,(R)              ; Get TCB index
1565         CAIL I,XBL              ; Ensure validity
1566          BUG HALT,[TCP: FRC bad idx]
1567
1568         ; Ensure that state allows sending anything.
1569         CONO PI,NETOFF          ; So state doesn't change while we think.
1570         HRRZ J,XBSTAT(I)
1571         CAIE J,.XSOPN
1572          CAIN J,.XSCLW
1573           CAIA
1574            JRST OPNL7           ; Bad state, say "device not ready".
1575         
1576         PUSH P,R
1577         MOVSI T,(TC%PSH)        ; Set PUSH flag (but not ACK, to avoid 
1578                                 ; forcing send of empty buffer)
1579         CALL TCPOFR             ; Force out!  Clobber many ACs.
1580         CONO PI,NETON
1581         POP P,R
1582         JRST POPJ1
1583
1584
1585 ; FINISH - from RH(DFRCTB)
1586 ;       We already know that R is OK since FORCE looked at it first.
1587 ;       In fact, I is still set up.
1588 ;       R/ addr of IOCHNM word
1589
1590 TCPFIN: METER("TCP: syscal finish")
1591         MOVSI T,(%XBNOW)
1592         TDNE T,XBSTAT(I) ; Wait until this bit is off (XBOCOS put on Q)
1593          CALL UFLS
1594         SKIPE XBORTQ(I) ; Hang until retransmit queue is empty.
1595          CALL UFLS
1596         JRST POPJ1
1597 \f
1598 SUBTTL TCP STY connection routines
1599
1600 ; STYTCP - invoked by STYNTC routine during 1/2 sec clock, for
1601 ;       STYs connected to TCP channels.
1602 ;       R/ TTY #
1603
1604 STYTCP: MOVE I,STYNTI-NFSTTY(R) ; Get TCB index for connection
1605         LDB TT,[XB$STY (I)]     ; Verify that TCB thinks we're hooked up
1606         CAIE TT,(R)
1607          BUG                    ; It doesn't??
1608
1609         ; First, check for and transfer any input for the STY.
1610         HLRZ T,XBSTAU(I)        ; Get input state
1611         SKIPG TCPTBI(T)         ; Make sure we can do input.
1612          JRST STYTC9            ; Nope, must disconnect.
1613 STYTC1: SOSGE XBIBC(I)
1614          JRST [ CALL TCPIBD     ; Discard input buffer if any
1615                 HRRZ A,XBITQH(I) ; Any more input avail?
1616                 JUMPE A,STYTC5  ; No, done, check for output.
1617                 CALL TCPIBG     ; Have some!  Set it up.  Shd never hang.
1618                  JFCL
1619                 JRST STYTC1]
1620         ILDB A,XBIBP(I)         ; Get the byte
1621         TRNE A,200              ; Special char?
1622          JRST [ AOS XBIBC(I)    ; Ugh, must back up and get user's attention
1623                 MOVSI B,8._14   ; Back up both count and 8-bit byte pointer
1624                 ADDM B,XBIBP(I) ; by adding to P field of BP
1625                 JRST STYTC9]    ; Go disconnect.
1626         EXCH R,I        ; I gets TTY #, R gets TCB index
1627         PUSH P,R
1628         PUSH P,I
1629         CONO PI,TTYOFF
1630         CALL NTYI5      ; Give the char to TTY input interrupt level
1631         CONO PI,TTYON
1632         POP P,R         ; Note reverse order, so R gets TTY #
1633         POP P,I         ; and I gets TCB index again.
1634         JRST STYTC1     ; Try for more input.
1635
1636         ; Transfer chars from STY output to TCP connection
1637 STYTC5: SKIPGE TTYOAC(R)        ; Do we have any output?
1638          JRST STYTC7            ; No, all's done, force out what we did.
1639         HRRZ A,XBSTAU(I)        ; Check output state
1640         SKIPG TCPTBO(A)         ; to verify that TCB is healthy.
1641          JRST STYTC9            ; Ugh, go disconnect STY.
1642         MOVSI A,(%XBMPL)
1643         IORM A,XBSTAT(I)        ; Lock COS against PI level snarfing
1644
1645         SKIPE XBOCOS(I)
1646          SKIPG E,XBOBC(I)       ; Get # bytes room in output buff
1647           JRST [
1648                 ; Set up buffer, etc, possibly forcing out existing buff.
1649                 PUSH P,R
1650                 CALL TCPOSB     ; Invoke special hang-less routine.
1651                  JRST [POP P,R  ; If can't get any more room, jump to STYTC6
1652                         JRST STYTC6]
1653                 POP P,R
1654                 SKIPG E,XBOBC(I)        ; OK, should have bytes now.
1655                  BUG
1656                 JRST .+1]
1657         SKIPN D,XBOBP(I)        ; Get BP into buffer
1658          BUG
1659         EXCH R,I
1660         CONO PI,TTYOFF
1661         MOVEM D,DBBBP           ; Set up buffer for TTY output interrupt level
1662         MOVEM E,DBBCC
1663         MOVEM E,DBBCC1
1664         PUSH P,R
1665         SETOM TYPNTF
1666         PUSHJ P,TYP             ; Generate output
1667         SETZM TYPNTF
1668         POP P,R
1669         EXCH R,I                ; Restore I/ TCB #, R/ TTY #
1670         MOVE D,DBBBP            ; Advance pointers
1671         MOVEM D,XBOBP(I)
1672         MOVE E,DBBCC
1673         SUB E,DBBCC1            ; Minus # chars output generated
1674         CONO PI,TTYON
1675         ADDM E,XBOBC(I)
1676         JRST STYTC5             ; Check for more output
1677
1678         ; No more output or we can't get more room, force out what
1679         ; we've currently got.
1680 STYTC6: CALL TCPUII             ; Reactivate STY (expensive crock, but...)
1681 STYTC7: MOVSI A,(%XBMPL)        ; Unlock the COS
1682         ANDCAM A,XBSTAT(I)
1683         MOVSI T,(TC%PSH)        ; PUSH this stuff
1684         CALL TCPOFR             ; Force out buffer
1685         JRST STYNT8             ; Then go check other STYs.
1686
1687
1688         ; Disconnect STY and get user's attention.  Note this may be
1689         ; buggy in that STY output has not yet been transferred to the
1690         ; net by the time we get here, if we're here due to a 200 char.
1691 STYTC9: PUSH P,I
1692         MOVEI I,(R)     ; Set up I/ TTY #
1693         CALL NSTYN0     ; Disconnect it
1694          BUG
1695         POP P,I
1696         CALL TCPUII     ; Wake up the user program
1697         JRST STYNT8     ; Go handle other STYs.
1698
1699 IFN 0,[
1700 ;CALLED AT CLOCK LEVEL FROM STYNTC WHEN A CHAOS STY IS ENCOUNTERED
1701 ;TTY NUMBER IN I & R
1702 STYCHA: MOVE I,STYNTI-NFSTTY(R) ;GET CHAOS INDEX
1703         MOVE TT,CHSSTA(I)
1704         TLNN TT,%CFSTY
1705          JRST 4,.               ;CHAOS CONNECTION CLAIMS NOT BE CONNECTED?
1706         JUMPL TT,STYCH9 .SEE %CFOFF     ;OK TO USE?  IF NOT, DISCONNECT
1707         SKIPGE TTYOAC(R)        ;ANY OUTPUT?
1708          JRST STYCH1            ;NO, CHECK FOR INPUT
1709         SKIPN D,CHSOBP(I)       ;IF BUFFER ALLOCATED, USE IT
1710          JRST [ SKIPG CHSNOS(I) ;OTHERWISE ALLOCATE ONE
1711                  JRST STYCH1    ;WINDOW FULL, WAIT UNTIL REACTIVATED
1712                 PUSHJ P,CHABGI
1713                  JRST STYCH3    ;NO CORE, WAIT ONE CLOCK TICK
1714                 MOVEI D,%CPKDT(A)
1715                 HRLI D,440800
1716                 MOVEM D,CHSOBP(I)
1717                 MOVEI E,%CPMXC
1718                 MOVEM E,CHSOBC(I)
1719                 JRST .+3 ]
1720           SKIPG E,CHSOBC(I)
1721            JRST STYCH4          ;BUFFER FULL, FORCE IT
1722         EXCH R,I                ;I GETS TTY, R GETS CHAOS
1723         CONO PI,TTYOFF
1724         MOVEM D,DBBBP           ;SET UP BUFFER FOR TTY OUTPUT INTERRUPT LEVEL
1725         MOVEM E,DBBCC
1726         MOVEM E,DBBCC1
1727         PUSH P,R
1728         SETOM TYPNTF
1729         PUSHJ P,TYP             ;GENERATE OUTPUT
1730         SETZM TYPNTF
1731         POP P,R
1732         EXCH R,I                ;I GETS CHAOS, R GETS TTY
1733         MOVE D,DBBBP            ;ADVANCE POINTERS
1734         MOVEM D,CHSOBP(I)
1735         MOVE E,DBBCC
1736         SUB E,DBBCC1            ;MINUS # CHARS OUTPUT GENERATED
1737         CONO PI,TTYON
1738         ADDM E,CHSOBC(I)
1739 STYCH4: PUSHJ P,CHAFC1          ;FORCE THE BUFFER
1740         JRST STYCHA             ;CHECK FOR MORE OUTPUT
1741 \f
1742 STYCH3: PUSHJ P,CHINTI          ;REACTIVATE SO WILL COME BACK ON NEXT CLOCK TICK
1743 STYCH1: SOSGE CHSIBC(I)         ;GET INPUT, IF ANY
1744          JRST [ PUSHJ P,CHAIBD  ;DISCARD EXHAUSTED INPUT BUFFER, IF ANY
1745                 HLRZ A,CHSIBF(I)
1746                 JUMPE A,STYNT8  ;NONE, RETURN TO STYNTC
1747                 LDB TT,[$CPKOP(A)]
1748                 CAIE TT,%CODAT
1749                  JRST STYCH9    ;RANDOM PACKET, DISCONNECT
1750                 PUSHJ P,CHPKIA  ;ACKNOWLEDGE GOBBLING OF THIS PACKET
1751                 SOS CHSNBF(I)   ;REMOVE BUFFER FROM RECEIVE LIST
1752                 MOVEI Q,CHSIBF(I)
1753                 PUSHJ P,CHAQGF
1754                 LDB E,[$CPKNB(A)]       ;SET UP FOR BYTE STREAM INPUT
1755                 MOVEM E,CHSIBC(I)
1756                 MOVEI D,%CPKDT(A)
1757                 HRLI D,440800
1758                 MOVEM D,CHSIBP(I)
1759                 JRST STYCH1 ]
1760         ILDB A,CHSIBP(I)        ;GET CHARACTER OF INPUT
1761         TRNE A,200
1762          JRST [ AOS CHSIBC(I)   ;WOOPS, SPECIAL CHARACTER, NEEDS USER ATTENTION
1763                 MOVSI A,8_14    ;SO PUT IT BACK AND DISCONNECT
1764                 ADDM A,CHSIBP(I)
1765                 JRST STYCH9 ]
1766         EXCH R,I                ;I GETS TTY, R GETS CHAOS
1767         PUSH P,R
1768         PUSH P,I
1769         CONO PI,TTYOFF
1770         PUSHJ P,NTYI5           ;GIVE CHARACTER TO TTY INPUT INTERRUPT LEVEL
1771         CONO PI,TTYON
1772         POP P,R
1773         POP P,I                 ;I GETS CHAOS, R GETS TTY ((POP IN REVERSE ORDER))
1774         JRST STYCH1             ;TRY FOR MORE INPUT
1775
1776 STYCH9: PUSH P,I
1777         MOVE I,R                ;I GETS TTY
1778         PUSHJ P,NSTYN0          ;DISCONNECT THE STY
1779          JRST 4,.
1780         POP P,I                 ;I GETS CHAOS
1781         PUSHJ P,CHINTI          ;WAKE UP THE TELNET SERVER
1782         JRST STYNT8             ;GO HANDLE OTHER STYS
1783 ] ;ifn 0
1784 \f
1785 SUBTTL Other TCP system call functions
1786
1787 ; TCPRQ - Handle .CALL NETRFC, return port # of next pending
1788 ;       request for connection (SYN).
1789 ;       Perhaps return a uniquizer in LH, so know when see
1790 ;       the same request again?
1791
1792 TCPRQ:  TRNE C,%NQREF           ; Skip if just getting, not flushing.
1793          JRST TCPRQ5
1794         METER("TCP: syscal netrfc get")
1795         CONO PI,NETOFF          ; In case a RST comes for it or something.
1796 ;       MOVE I,TCPRQL           ; Get last thing stored on queue
1797         SETOB B,D               ; Look for any match
1798         CALL TCPRQS             ; Search the queue...
1799         JUMPL A,OPNL4           ; None, say "file not found".
1800         MOVEI I,(A)
1801         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get local port # for the SYN
1802         HRLI A,(I)              ; And put index in LH as uniquizer.
1803         CONO PI,NETON
1804         JRST POPJ1
1805
1806 TCPRQ2: BUG CHECK,[TCP: Pending SYN smashed!]
1807         RET
1808
1809         ; Refuse indicated connection.
1810 TCPRQ5: METER("TCP: syscal netrfc ref")
1811         CAIGE W,2               ; Must have 2 args
1812          JRST OPNL30            ; "Too few args"
1813         HLRE D,A                ; Get identifier
1814         HRRE B,A
1815         CONO PI,NETOFF
1816         CALL TCPRQS             ; Search for the queued SYN
1817         JUMPL A,OPNL4
1818
1819         ; Now must refuse connection.
1820         MOVEI I,(A)
1821         MOVEI Q,XBITQH(I)
1822         CALL PKQGF(PK.TCP)      ; Get queued SYN segment 
1823         SKIPN XBITQH(I)         ; Should have been only one
1824          SKIPG R,A              ; and should have been one!
1825           BUG HALT
1826         CALL TXBFLS             ; Flush the TCB.
1827         SOSGE TCPRQN            ; Decrement count of queued SYNs
1828          BUG HALT
1829         HLRZ W,PK.IP(R)         ; Move all this setup somewhere modular.
1830         HLRZ H,PK.TCP(R)
1831         LDB TT,[PK$TDL (R)]
1832         MOVE E,TH$CTL(H)
1833         TLNE E,(TC%SYN)
1834          ADDI TT,1
1835         TLNE E,(TC%FIN)
1836          ADDI TT,1
1837         CALL TSISLR             ; Respond to this req with RST+ACK
1838         CONO PI,NETON
1839         JRST POPJ1
1840
1841 ; TCPRQS - Search pending-RFC queue.  Must be called with NETOFF!!
1842 ;       B/ local port # (-1 for any)
1843 ;       D/ Index #, -1 for any (searches back from last one stored)
1844 ; Clobbers T,Q
1845 ; Returns
1846 ;       A/ Index to matching SYN (-1 if no match)
1847
1848 TCPRQS: JUMPGE D,TCPRQ7
1849         MOVE A,TCPRQL
1850         MOVEI C,1
1851 TCPRQ6: HRRZ T,XBSTAT(A)        ; See if right state
1852         CAIN T,.XSSYQ
1853          JRST [ LDB T,[.BP TH%DST,XBPORT(A)]
1854                 CAIL B,
1855                  CAMN T,B
1856                   RET
1857                 JRST .+1]
1858         SOJGE A,TCPRQ6
1859         MOVEI A,XBL-1
1860         SOJGE C,TCPRQ6
1861 TCPRQ9: SETO A,
1862         RET
1863
1864 TCPRQ7: SKIPL A,D
1865          CAIL D,XBL
1866           JRST TCPRQ9
1867         HRRZ T,XBSTAT(A)        ; Verify state
1868         CAIE T,.XSSYQ
1869          JRST TCPRQ9
1870         LDB T,[.BP TH%DST,XBPORT(A)]     ; Got one!  Get local port #
1871         CAIL B,
1872          CAIN T,(B)     ; Must match given arg unless -1
1873           RET           ; Won!
1874         JRST TCPRQ9
1875
1876 ifn 0,[
1877 TCPRQS: MOVEI A,TCPRQH-PK.TCP
1878 TCPRQ6: MOVEI Q,(A)             ; Save ptr to prev node
1879         HRRZ A,PK.TCP(A)        ; Get ptr to next PE
1880         JUMPE A,TCPRQ8          ; If not there, return 0 as error.
1881         JUMPL D,TCPRQ7
1882         CAIE A,(D)              ; See if identifier matches
1883          JRST TCPRQ6            ; Jump if not.
1884 TCPRQ7: HLRZ T,PK.TCP(A)        ; Yes, verify port number
1885         CAIN T,                 ; Ensure ptr to TCP header exists.
1886          BUG HALT
1887         LDB T,[TH$DST (T)]
1888         CAIE T,(B)
1889          JRST TCPRQ6            ; Nope, get next thing.
1890
1891         ; Found it!  Take off list, a bit tricky.
1892         SOSGE TCPRQN            ; Decrement count of entries
1893          BUG HALT
1894         MOVSI T,(%PQFL2)        ; Clear the on-list flag for PK.TCP
1895         ANDCAM T,PK.FLG(A)
1896 IFN 2-PK.TCP,.ERR TCPRQS must fix %PQFL2 to match PK.TCP
1897         HRRZ T,PK.TCP(A)        ; Get its next-ptr
1898         HRRM T,PK.TCP(Q)        ; Store in node previous to this one.
1899         JUMPN T,TCPRQ8          ; If wasn't last thing, all's well.
1900         CAIN Q,TCPRQH-PK.TCP    ; Last thing.  If prev was actually hdr,
1901          SETZ Q,                ; must store zero.
1902         HRLM Q,TCPRQH           ; Set new "last" ptr in hdr.
1903 TCPRQ8: 
1904         RET
1905
1906 ] ;ifn 0
1907 \f
1908 ; TSOINI - set up a raw PE for use as a TCP output segment.  Means
1909 ;       setting IP, TCP header pointers properly, so that all fields
1910 ;       are contiguous.  Note that PK.TCI is set to indicate XBSMSS(I)
1911 ;       bytes of (available) data storage!
1912 ;       Sets up PK.IP, PK.TCP, and PK.TCI.
1913 ;       R/ PE ptr
1914 ;       I/ TCB connection index (val put into PK.TCI)
1915 ; Returns with R, W, H pointing to PE, IP hdr, and TCP hdr.
1916 ;       
1917 ; TSOINA - Ditto, but takes arg in A and only clobbers T (doesn't set W, H)
1918
1919
1920 TSOINI: HRRZ W,PK.BUF(R)        ; Get addr of buffer
1921         HRLM W,PK.IP(R)         ; Store as IP header addr
1922         MOVEI H,(I)             ; Set up TCI with all fields.
1923         ANDI H,PK%TCB
1924         IOR H,[<<%TCPHL*4>_<.TZ PK%TDO,>>]
1925         MOVEM H,PK.TCI(R)       ; 
1926         MOVE H,XBSMSS(I)        ; Allow XBSMSS(I) bytes with assumed offset.
1927         DPB H,[PK$TDL (R)]
1928         MOVEI H,%TCPHL(W)       ; For now, this will do.
1929         HRLM H,PK.TCP(R)        ; Store as TCP header addr
1930         RET
1931
1932 TSOINA: HRRZ T,PK.BUF(A)        ; Get addr of buffer
1933         HRLM T,PK.IP(A)         ; Store as IP header addr
1934         ADDI T,%TCPHL           ; For now, this will do to get TCP hdr.
1935         HRLM T,PK.TCP(A)        ; Store as TCP header addr
1936         MOVEI T,(I)             ; Set up TCI with all fields.
1937         ANDI T,PK%TCB
1938         IOR T,[<<%TCPHL*4>_<.TZ PK%TDO,>>]
1939         MOVEM T,PK.TCI(A)       ; Set up index and header length fields
1940         MOVE H,XBSMSS(I)        ; Allow XBSMSS(I) bytes with assumed offset.
1941         DPB H,[PK$TDL (R)]
1942         RET
1943
1944 ; TCPUSI - TCP User State-change Interrupt.  Called each time connection
1945 ;       changes state (.XSnnn) or I/O queues start/end.  Always tries
1946 ;       to interrupt user, except for change %NTWRT->%NTOPN on output
1947 ;       and %NTINP->%NTOPN on input.
1948 ;       Moon: Interrupt when input rcvd and buff empty, or output full
1949 ;               and becomes reasonably non-full.
1950 ; Clobbers T, Q
1951
1952 TCPUSI: METER("TCP: tcpusi called")
1953         CALL TXBIST             ; Check input state
1954         HLRZ Q,XBSTAU(I)
1955         CAIE T,(Q)              ; New state?
1956          JRST TCPUS3            ; Yes, go handle.
1957 TCPUS2: CALL TXBOST
1958         HRRZ Q,XBSTAU(I)
1959         CAIN T,(Q)
1960          RET
1961
1962         ; Output channel state change
1963         ; Q/ old state, T/ new state  (%NT values, not .XS)
1964         HRRM T,XBSTAU(I)        ; Store new state (old in Q)
1965         CAIN Q,%NTOPN           ; If was open
1966          CAIE T,%NTWRT          ; Changing to buff-full
1967           CAIA
1968            RET                  ; Then don't interrupt.
1969         MOVE Q,TCPTBO(Q)
1970         CAMN Q,TCPTBO(T)        ; See if meta-state change
1971          RET                    ; Nope, ignore.
1972         LDB Q,[XB$OCH (I)]      ; Yes, get channel #
1973         METER("TCP: User O ints")
1974         CALRET TCPUS5
1975
1976         ; Input channel state change
1977 TCPUS3: HRLM T,XBSTAU(I)        ; Store new state (old in Q)
1978         CAIN Q,%NTINP           ; If was input avail
1979          CAIE T,%NTOPN          ; Changing to plain open
1980           CAIA
1981            JRST TCPUS2          ; Then don't interrupt.
1982         MOVE Q,TCPTBI(Q)
1983         CAMN Q,TCPTBI(T)        ; See if meta-state change
1984          JRST TCPUS2            ; No
1985                                 ; Drop thru to interrupt
1986
1987         ; Give input channel interrupt
1988 TCPUII: METER("TCP: User I ints")
1989         LDB Q,[XB$STY (I)]      ; See if hooked to STY
1990         JUMPN Q,TCPUSS          ; Jump to handle STY stuff if so.
1991         LDB Q,[XB$ICH (I)]      ; No, just get input chan
1992         CALL TCPUS5
1993         JRST TCPUS2
1994
1995         ; Give interrupt to STY that TCB is connected to.
1996         ; Q/ TTY #
1997 TCPUSS: CONO PI,PIOFF           ; Protect list hacking
1998         SKIPL STYNTL-NFSTTY(Q)  ; Don't put on list twice
1999          JRST PIONJ
2000         MOVE T,STYNTA           ; Add to list
2001         MOVEM T,STYNTL-NFSTTY(Q)
2002         MOVEM Q,STYNTA
2003         JRST PIONJ
2004
2005         ; Interrupt on channel in Q.
2006 TCPUS5: JUMPE Q,CPOPJ           ; May be no channel there.
2007         PUSH P,U
2008         SKIPN U,XBUSER(I)
2009          BUG HALT               ; Jumpe above should catch this.
2010         MOVSI T,(SETZ)
2011         IORM T,PIRQC(U)
2012         CAIN Q,77               ; If IOPUSH'ed, no interrupt.
2013          JRST POPUJ
2014         MOVE T,CHNBIT-1(Q)      ; Q is -1 based.
2015         AND T,MSKST2(U)
2016         IORM T,IFPIR(U)
2017         POP P,U
2018         RET
2019
2020         ; Input chan state type.  Pos # means can read.
2021         ; 0 is pre-open, 1 is open, 2 is input avail, -1 is post-open.
2022 TCPTBI: OFFSET -.
2023 %NTCLS:: 0      ; 0 CLS
2024 %NTLSN:: 0      ; 1 LSN
2025 %NTSYR:: 0      ; 2 RFC
2026 %NTCLU:: -1     ; 3 RCL?
2027 %NTSYN:: 0      ; 4 RFS
2028 %NTOPN:: 1      ; 5 OPN
2029 %NTWRT:: 1      ; 6 RFN
2030 %NTCLX:: -1     ; 7 CLW
2031 %NTCLI:: 1      ; 10 CLI
2032 %NTINP:: 2      ; 11 INP
2033         OFFSET 0
2034
2035         ; Output chan state type. Pos # means can write.
2036         ; 0 is pre-open, 1 is open, 2 is buff full, -1 is post-open.
2037 TCPTBO: OFFSET -.
2038 %NTCLS:: 0
2039 %NTLSN:: 0
2040 %NTSYR:: 0
2041 %NTCLU:: 1
2042 %NTSYN:: 0
2043 %NTOPN:: 1
2044 %NTWRT:: 2
2045 %NTCLX:: -1
2046 %NTCLI:: 1
2047 %NTINP:: 1
2048         OFFSET 0
2049
2050 \f
2051 SUBTTL TCP Input Interrupt Level
2052
2053 ; TCPIS - Process TCP Input Segment (PI level)
2054 ;       R/ PE ptr to packet, not on any list.
2055 ;               PK.BUF is set, ditto IP/TCP header pointers.
2056 ;       W/ addr of IP header
2057 ;       H/ addr of IP data (start of TCP header)
2058 ;       J/ host-table index for address datagram received from.
2059 ; Can clobber all ACs except P, returns with POPJ.
2060 ; AC usage during incoming segment processing:
2061 ;       R/ PE ptr to packet
2062 ;       W/ addr of IP header
2063 ;       H/ addr of TCP header
2064 ;       I/ TCB index (if any)
2065 ;       J/ TCB connection state
2066 ;       TT/ # bytes of TCP data in segment
2067 ;       E/ <seg control bits>,,<temp flags>
2068 ;       D/ Segment Sequence no.
2069 ; Flags for RH of E
2070 %TSISL==1       ; Seq starts to left of rcv.nxt
2071 %TSISR==2       ; Seq starts to right of  "  ; if neither on, is = rcv.nxt
2072 %TSIFL==4       ; Bad seq, flush after handling RST/ACK/URG
2073
2074 TCPIS:  METER("TCP: Segs rcvd")
2075         SKIPN TCPUP     ; Unless TCP claims to be up,
2076          JRST TSIFL     ; Throw it away, no TCP yet, sigh.
2077
2078         ; First verify that this is a valid TCP segment, by
2079         ; checksumming it (sigh!).  TT gets total # bytes in TCP segment.
2080         CALL THCKSI             ; Get checksum in A for segment
2081         LDB B,[TH$CKS (H)]      ; Get segment's checksum
2082         CAME A,B                ; Should match.
2083          JRST TSIF01            ; Failed, go bump err count and flush it.
2084         LDB T,[TH$THL (H)]      ; Find TCP header length in words
2085         LSH T,2                 ; Make it in octets
2086         SUBI TT,(T)             ; TT now has # octets of segment data.
2087
2088         ; Contents of segment have been validated (more or less),
2089         ; now set up convenient context values
2090         ;       PK.TCI contents
2091         ;       E/ Segment control flags (in LH)
2092         ;       TT/ SEG.LEN
2093         HLLZ E,TH$CTL(H)        ; Get word with segment control flags
2094         DPB T,[PK$TDO (R)]      ; Store offset of data (from THCKSI)
2095         DPB TT,[PK$TDL (R)]     ; Store length of data
2096         TLNE E,(TC%SYN)         ; Note that SYN counts in seg.len
2097          ADDI TT,1              ;  so allow for it
2098         TLNE E,(TC%FIN)         ; And do same thing for FIN.
2099          ADDI TT,1              ;  Either way, get SEG.LEN set up in TT.
2100
2101         ; Then see if any TCB exists for this segment.
2102         SKIPE A,TH$SRC(H)       ; Get source/dest port word
2103          SKIPN B,IP$SRC(W)      ; Get source addr from IP header
2104           JRST TSIF02           ; Flush anything with zero field.
2105         LSH B,-4                ; Right-justify the addr
2106         MOVSI I,-XBL
2107 TSI02:  CAMN A,XBPORT(I)        ; Loop til we find it
2108          CAME B,XBHOST(I)
2109 TSI03:    AOBJN I,TSI02
2110         JUMPL I,TSI05           ; Jump if found existing connection
2111         JRST TSISQ              ; Jump if no existing connection.
2112
2113 TSI04:  SKIPE XBSTAT(I)         ; Found "closed" connection????
2114          JRST TSI02             ; LH must have crud still set, ignore for now
2115         BUG CHECK,[TCP: Clsed TCB has active port/host] ; Shouldn't happen!
2116         SETZM XBHOST(I)         ; If continued, fix up.
2117         JRST TSI02
2118
2119         ; Connection exists, TCB index now in I.
2120         ; Set up a little more context (PK.TCI and J)
2121 TSI05:  DPB I,[PK$TCB (R)]      ; Store TCB index in packet info
2122         MOVEM J,XBNADR(I)       ; Save host-table idx of addr this seg is from.
2123         HRRZ J,XBSTAT(I)        ; Get connection state
2124         CAIL J,.XSTOT           ; Highest possible state.
2125          BUG HALT,[TCP: Bad conn state]
2126         METER("TCP: IS all states")
2127         XCT XSMTRS(J)           ; Bump meter for each state
2128         CAIG J,.XSSYN           ; If it's CLS, SYQ, LSN or SYN-SENT
2129          JRST @(J)[             ; then process specially.
2130                 TSI04           ; Closed???
2131                 TSISQQ          ; Syn-Queued?  (Probably re-trans)
2132                 TSILS           ; Listen
2133                 TSISS]          ; Syn-sent
2134         ; Drop through to perform general sequence-number checking.
2135 \f
2136         ; Check Sequence Number!!!
2137         ; This code doesn't do two things:
2138         ;       1) it doesn't keep around stuff that arrives to the
2139         ;               right of rcv.nxt.
2140         ;       2) for situation where seg.seq number is valid,
2141         ;               (i.e. seq =< rcv.nxt) the code punts if
2142         ;               end of seg is out of window.  It should simply
2143         ;               expand the window!
2144         LDB D,[TH$SEQ (H)]      ; Get sequence number
2145         JUMPG TT,TSI10          ; Jump if data present.
2146         JUMPL TT,TSIF03         ; No data.  Jump if error (neg data!)
2147
2148         ; No data in this segment, it is probably a simple ACK.
2149         CAME D,XBRNXT(I)        ; Seg.seq == snd.nxt (as expected?)
2150          JRST TSI01
2151         METER("TCP: 0-len seg seq match")
2152         JRST TSI20              ; Yep, seg is acceptable instantly!
2153
2154 TSI01:  SKIPN C,XBRWND(I)       ; Have some receive window?
2155          JRST TSI09
2156         ADD C,XBRNXT(I)         ; Get nxt+wnd
2157         TLZ C,%MOD32            ; all arith mod 32
2158         CMPSEQ XBRNXT(I),=<,D,<,C,TSI07,TSI08
2159         JRST TSI20              ; Within rcv window, buy it
2160
2161 TSI07:  METER("TCP: 0-len seg before rcv window")
2162         JRST TSISNE
2163
2164 TSI08:  METER("TCP: 0-len seg after rcv window")
2165         JRST TSISNE
2166
2167         ; 0-data, 0-window, and SEG.SEQ != RCV.NXT
2168 TSI09:  METER("TCP: Ifl 0-len 0-window seqerr")
2169         JRST TSISNE             ; Sigh, flush it.
2170
2171         ; Seq number check when data present.
2172 TSI10:  CAME D,XBRNXT(I)        ; Is seq # what we expect (seq = nxt)?
2173          JRST TSI11
2174         SKIPE C,XBRWND(I)       ; Yes!  And is our window open?
2175          JRST TSI20             ; Yes!  Fast dispatch!
2176
2177         ; Data segment, with valid sequence number, but our window is
2178         ; zero.  See if there's some way we can avoid throwing away the
2179         ; segment... if we can't take it then still must handle
2180         ; ACK/URG/RST flags.  For now, we really handle this at TSI70.
2181 TSI12:  METER("TCP: 0-wnd data seg")
2182         JRST TSI20
2183
2184         ; Sequence # isn't exactly what we hoped for, see if the
2185         ; segment overlaps a valid portion of sequence space.
2186 TSI11:  SKIPN C,XBRWND(I)       ;#3: Get window, is it zero?
2187          MOVEI C,512.           ; If zero, substitute a dummy window.
2188
2189         ; Both len>0 and wnd>0.
2190         ADD C,XBRNXT(I)         ; Get nxt+wnd
2191         TLZ C,%MOD32            ; all arith mod 32
2192                                 ;#4a: nxt =< seq < nxt+wnd
2193         CMPSEQ XBRNXT(I),=<,D,<,C,TSI13 ; Jump if fail this test, try 4b.
2194
2195         ; Come here when sequence # is OK, but segment starts farther on
2196         ; than we want, i.e. there is a "hole" between rcv.nxt and seg.seq.
2197         ; Eventually we could keep this segment around, to speed up
2198         ; throughput for nets that get packets out of order, but for
2199         ; now we'll just flush it and force a retransmit.
2200         METER("TCP: Iseg hole")
2201         TRO E,%TSISR+%TSIFL     ; Say starts to right, and flush later.
2202         JRST TSI20              ; Go process RST/ACK/URG etc.
2203
2204 TSIF12: METER("TCP: Ifl seq dup")       ; Segment falls in prev rcvd data.
2205         MOVE D,XBRNXT(I)                ; Fake out, say seq # OK
2206         TRO E,%TSIFL                    ; and don't process data.
2207         JRST TSI20                      ; Go handle RST/ACK/URG.
2208
2209 TSIF13: METER("TCP: Ifl seq int err")   ; Shouldn't ever happen, due to
2210         JRST TSISNE                     ; right-bound check code above.
2211 TSIF14: METER("TCP: Ifl seq old")
2212         JRST TSISNE
2213 TSIF15: METER("TCP: Ifl monster seg")   ; Impossible error
2214         JRST TSISNE
2215
2216         ; Segment does not overlap window to right, so see if it
2217         ; overlaps to left, i.e. sequence # falls within data we have
2218         ; already received.
2219 TSI13:  MOVE A,XBRNXT(I)
2220         SUBI A,%TCPMB           ; Make a fictional lower bound
2221         CAIGE A,
2222          ADD A,[1_32.]          ; Keep bound mod 2^32
2223         CMPSEQ A,=<,D,=<,XBRNXT(I),TSIF14,TSIF13
2224
2225         ; Yep, falls within received data.  It's probably a duplicate
2226         ; retransmitted segment; see if there's any new data on right side.
2227         ; Note that we are not using XBRWND here, because as long as we
2228         ; have a non-zero window we will always accept everything in the
2229         ; segment.  So we create another fictional bound to the right.
2230         ADD A,[%TCPMB*2]        ; Get back to other side of rcv.nxt
2231         TLZ A,%MOD32            ; Keep mod 2^32
2232         MOVE C,D
2233         ADDI C,-1(TT)           ; Get seq+len-1
2234         TLZ C,%MOD32
2235                                 ;#4b: nxt =< seq+len-1 < nxt+wnd?
2236         CMPSEQ XBRNXT(I),=<,C,=<,A,TSIF12,TSIF15 ; If fail this too, error.
2237
2238         ; Aha, have some new data in spite of being overlapped with some
2239         ; previously received data!  Here, we
2240         ; twiddle things so that it appears to start properly at
2241         ; rcv.nxt.  This is done without touching the segment contents
2242         ; at all, just modifying the packet entry info.
2243         METER("TCP: Iseg ovlap")
2244         MOVE A,XBRNXT(I)        ; Get rcv.nxt
2245         CAMGE A,D               ; Make sure it's greater than seg.seq
2246          TLO A,(1_32.)          ; Mod 2^32 screw, make it greater (add 33d bit)
2247         SUB A,D                 ; Find # octets of sequence space diff
2248         CAMLE A,TT              ; Shouldn't be greater than seg.len!!
2249          BUG CHECK,[TCP: Trim error]
2250         SUBI TT,(A)
2251         JUMPLE TT,TSIF12        ; If nothing left, drop this segment.
2252         TLZE E,(TC%SYN)         ; Clear SYN since it's at front.
2253          SUBI A,1               ;  If it was set, reduce cnt of actual data
2254         LDB T,[PK$TDL (R)]      ; that we're going to flush.  Get cnt
2255         SUBI T,(A)              ; Decrement # valid data bytes in segment
2256         DPB T,[PK$TDL (R)]      ; Put back
2257         LDB T,[PK$TDO (R)]      ; Also adjust offset to valid data
2258         ADDI T,(A)              ; Increment to point at new data
2259         DPB T,[PK$TDO (R)]      ; Put back
2260         MOVE D,XBRNXT(I)        ; Now say seg.seq = rcv.nxt!
2261                                 ; Segment sanitized, drop through.
2262         SKIPN XBRWND(I)         ; Only proceed if our window not zero.
2263          JRST TSI12             ; It's zero!  May have to flush it...
2264
2265         ; Fall through to TSI20 for RST/ACK/URG processing.
2266 \f
2267         ; Now check RST
2268 TSI20:  TLNE E,(TC%RST)         ; RST bit set?
2269          JRST TSIRST            ; Yeah, go process it.
2270
2271         ; Now check security/precedence
2272         JFCL                    ; ho ho ho
2273
2274         ; Now check SYN bit
2275 TSI40:  TLNE E,(TC%SYN)         ; SYN bit set?
2276          JRST TSISYN            ; Yeah, go process it (basically error)
2277
2278         ; Now check ACK bit
2279 TSI50:  TLNN E,(TC%ACK)         ; ACK bit set?
2280          JRST TSIF50            ; No, error.  Drop segment.
2281         JRST @TSI51(J)          ; Yes, dispatch depending on state.
2282 TSI51:  OFFSET -.
2283 .XSCLS:: [JRST 4,TSI51] ; Closed
2284 .XSSYQ:: [JRST 4,TSI51] ; ITS: Syn-Queued
2285 .XSLSN:: [JRST 4,TSI51] ; Listen
2286 .XSSYN:: [JRST 4,TSI51] ; Syn-Sent
2287 .XSSYR:: TSI53          ; Syn-Rcvd
2288 .XSOPN:: TSI54          ; Established (open)
2289 .XSFN1:: TSI54          ; Fin-Wait-1
2290 .XSFN2:: TSI54          ; Fin-Wait-2
2291 .XSCLW:: TSI54          ; Close-Wait
2292 .XSCLO:: TSI54          ; Closing
2293 .XSCLA:: TSI54          ; Last-Ack
2294 .XSTMW:: TSIATW         ; Time-Wait
2295 .XSTOT:: OFFSET 0
2296
2297
2298         ; SYN-RCVD state, handling ACK.
2299 TSI53:  LDB A,[TH$ACK (H)]      ; Get ACK field
2300         MOVE B,XBSUNA(I)        ; Need one CMPSEQ arg in AC
2301                                 ; Test: snd.una =< seg.ack =< snd.nxt
2302         CMPSEQ B,=<,A,=<,XBSNXT(I),TSISRA       ; Jump if fail
2303         MOVEI J,.XSOPN          ; ACK wins, we're now open!
2304         HRRM J,XBSTAT(I)        ; Set new state, fall through to handle.
2305         CALL TCPUSI             ; Adjust user state.
2306         ; Must initialize SND.WL1, SND.WL2, and SND.WND.
2307         ; Maybe later merge this with TSI55.
2308         MOVEM A,XBSWL2(I)       ; Yes!  Update send window, set WL2 to ACK
2309         MOVEM D,XBSWL1(I)       ; and WL1 to SEQ
2310         LDB B,[TH$WND (H)]
2311         MOVEM B,XBSWND(I)       ; and snd.WND to seg.WND.
2312         MOVEM B,XBSAVW(I)       ; and make avail window be same as send wind.
2313         JRST TSI54X             ; Skip repeating the ACK test.
2314
2315         ; Handle ACK while in open state (also other receive-OK states)
2316 TSI54:  LDB A,[TH$ACK (H)]      ; Get ACK field
2317         MOVE B,XBSUNA(I)        ; Need one CMPSEQ arg in AC
2318                 ; Test: snd.una =< seg.ack =< snd.nxt
2319                 ; If seg.ack < snd.una, go to TSI60 and ignore the ACK.
2320                 ; If seg.ack > snd.nxt, go to TSISAK to drop segment (ACKing)
2321         CMPSEQ B,=<,A,=<,XBSNXT(I),TSI60,TSISAK ; Jump if fail
2322
2323         ; ACK is fine.  Update SND.UNA and clean up retransmit queue.
2324 TSI54X: MOVEM A,XBSUNA(I)       ; Update snd.una
2325         
2326         ; Must check retransmit queue slowly to find right place to flush,
2327         ; if any.
2328         ; Procedure is: (1) pull off 1st thing on queue.
2329         ; (2) If the new 1st thing has a seq # =< snd.una,
2330         ;       then can flush what we pulled off, and try again.
2331         ; (3) otherwise put it back on at front.
2332 TSI54A: MOVE C,A                ; Save ACK # in C
2333 TSI54B: MOVEI Q,XBORTQ(I)       ; Get pointer to retrans q
2334         CALL PKQGF(PK.TCP)      ; Get 1st thing on queue
2335         JUMPE A,TSI54Z          ; None left?  Win!
2336         TRCPKT A,"TSI54B Mabye flush from rexmit Q"
2337         MOVE T,PK.FLG(A)        ; Check packet flags,
2338         TLNN T,(%PKODN)         ; to make sure output was completed.
2339          JRST TSI54Y            ; Not done yet, so don't flush yet.
2340         HRRZ B,XBORTQ(I)        ; Get pointer to next thing
2341         JUMPE B,[CAMN C,XBSNXT(I) ; No next thing, compare with snd.nxt
2342                  JRST TSI54D    ; Equal, can flush!
2343                 JRST TSI54Y]    ; If not equal, must have ack < snd.nxt
2344                                 ; so previous segment can't be flushed.
2345         HLRZ B,PK.TCP(B)        ; Get addr of TCP hdr for 2nd queued segment
2346         LDB B,[TH$SEQ (B)]      ; Get sequence # for it
2347 TSI54C: CMPSEQ B,=<,C,=<,XBSNXT(I),TSI54Y ; See if ACK comes after that #
2348
2349         ; Hurray, matches or exceeds this seq #,
2350         ; So we can flush the seg we pulled off!
2351 TSI54D: TRCPKT A,"TSI54D Flushing from Q"
2352         TLO T,(%PKFLS)          ; Tell IP to forget it if queued
2353         MOVEM T,PK.FLG(A)
2354         CALL PKTRT              ; Flush if not otherwise occupied
2355 TSI54E: MOVE A,TIME             ; Crock crock, set up new timeout.
2356         ADD A,TCPTMO
2357         MOVEM A,XBORTT(I)
2358         SETZM XBORTC(I)         ; Reset retry counts
2359         SOSGE XBORTL(I)         ; Decrement # segments on retrans q.
2360          BUG HALT,[TCP: Retrans Q count error]
2361         JRST TSI54B             ; Keep going as long as we can.
2362
2363 TSI54Y: MOVEI Q,XBORTQ(I)
2364         CALL PKQPF(PK.TCP)      ; Put back on front of queue
2365 TSI54Z: MOVE A,C                ; Restore ACK # to A.
2366
2367         ; Now see if send window should be updated.
2368         CAMN D,XBSWL1(I)        ; Fast check first, WL1 = SEQ?
2369          JRST TSI55C            ; Yes, go check ACK then
2370         MOVE T,XBSWL1(I)
2371         ADDI T,-1
2372         TLZ T,%MOD32
2373         CMPSEQ XBSWL1(I),<,D,<,T,TSI56  ; Check if wl1 < seq < wl1+xxx
2374         JRST TSI55                      ; Yes, must update window.
2375 TSI55C: MOVE T,XBSWL2(I)
2376         ADDI T,-1
2377         TLZ T,%MOD32
2378         CMPSEQ XBSWL2(I),=<,A,=<,T,TSI56 ; Fall-thru win if snd.wl2 =< seg.ack
2379
2380 TSI55:  MOVEM A,XBSWL2(I)       ; Yes!  Update send window, set WL2 to ACK
2381         MOVEM D,XBSWL1(I)       ; and WL1 to SEQ
2382         LDB B,[TH$WND (H)]
2383         MOVEM B,XBSWND(I)       ; and snd.WND to seg.WND.
2384                                 ; Drop thru
2385
2386         ; Either SND.UNA or SND.WND was probably updated, so lets update
2387         ; SND.AVW also (available window).  The following computes
2388         ; WND - (NXT - UNA) and assumes UNA =< NXT.
2389 TSI56:  MOVE A,XBSNXT(I)
2390         CAMGE A,XBSUNA(I)       ; If need mod 32 wrap,
2391          TLO A,(1_32.)          ; wrap up the number that should be higher.
2392         SUB A,XBSUNA(I)         ; Find NXT-UNA (# bytes not yet acked)
2393         CAIL A,0
2394          CAILE A,177777         ; Make simple check
2395           BUG INFO,[TCP: Bad AVW calc, UNA=],OCT,XBSNXT(I),[NXT=],OCT,XBSUNA(I)
2396         MOVE B,XBSWND(I)
2397         SUBI B,(A)              ; Find # bytes we can still send
2398         CAIGE B,                ; Make sure it's not negative!
2399          SETZ B,
2400         MOVEM B,XBSAVW(I)
2401
2402         ; Done with ACK processing for OPEN state, see if must handle
2403         ; idiosyncracies of other states.
2404 TSI57:  CAIN J,.XSOPN           ; Skip other checks if state is OPEN (normal)
2405          JRST TSI60             ; Go check for URG etc.
2406         CAIN J,.XSCLW
2407          JRST TSI80
2408         CAIN J,.XSFN1
2409          JRST [ SKIPE XBORTQ(I) ; If our FIN is ACK'd, enter FIN-WAIT-2
2410                  JRST TSI60     ; Not yet.
2411                 MOVEI J,.XSFN2  ; Yes, FIN was ACKed, change state.
2412                 HRRM J,XBSTAT(I)
2413                 CALL TCPUSI     ; Call this for any state change.
2414                 LDB T,[XB$ICH (I)]      ; Do we have an input chan?
2415                 JUMPN T,TSI60           ; If so, CLOSE will handle the wrapup.
2416                 MOVE T,TIME     ; No, must set timeout.
2417                 ADDI T,2*60.*30.        ; Use 2*MSL
2418                 MOVEM T,XBORTT          ; set timeout.
2419                 JRST TSI60]
2420         CAIN J,.XSFN2
2421          JRST [         ; If retrans queue empty, transmit-chan CLOSE done.
2422                 JRST TSI60]
2423         CAIN J,.XSCLO
2424          JRST [ SKIPE XBORTQ(I) ; If our FIN is ACK'd,
2425                  JRST TSIF55    ;  No-- flush the segment.
2426                 CALL TSITMW     ; then enter TIME-WAIT state, start timeout.
2427                 JRST TSI80]     ; Then go check for FIN, etc.
2428         CAIN J,.XSCLA           ; LAST-ACK waiting for ACK of our FIN.
2429          JRST [ SKIPE XBORTQ(I) ; If our FIN has been ACK'd,
2430                  JRST TSIF56    ;  No-- flush the segment.
2431                 METER("TCP: FIN acked in .XSCLA")
2432                 CALL TXBFLP     ; Flush the TCB immediately, PI level
2433                 JRST TSIFL]     ; then flush the segment.
2434         BUG CHECK,[TCP: Bad ACK state]
2435
2436         ; Check the URG bit.  The only states which get to this
2437         ; point are OPEN, FIN-WAIT-1, and FIN-WAIT-2.
2438 TSI60:  TLNN E,(TC%URG)         ; Segment has urgent pointer set?
2439          JRST TSI70             ; Nope, on to next step.
2440         LDB A,[TH$UP (H)]       ; Get SEG.UP (urgent ptr from segment)
2441
2442         ; This is where URGENT should be handled!!!!
2443                                 ; Drop through
2444 \f
2445         ; Finally process segment text!
2446         ; Only states OPEN, FIN-WAIT-1 and FIN-WAIT-2 can get here.
2447 TSI70:  TRNE E,%TSIFL           ; If segment being flushed after ACK/URG,
2448          JRST TSIF70            ; flush it now!
2449
2450
2451         LDB A,[PK$TDL (R)]      ; Find # bytes of real data in segment
2452         JUMPLE A,TSI80          ; If none, no text processing.
2453         TLNE E,(TC%FIN)         ; Check that # bytes data == seg.len
2454          JRST [ CAIE A,-1(TT)   ; Must allow for funny non-data FIN.
2455                  JRST TSI71     ; Nope
2456                 JRST TSI72]     ; Yep
2457         CAIE A,(TT)             ; # bytes data should == seg.len
2458 TSI71:   BUG CHECK,[TCP: seglen error]
2459 TSI72:  SKIPE D,XBRWND(I)       ; Note D used for flag,
2460          JRST TSI75             ; and is non-zero if no compaction done.
2461
2462         ; Our window is zero, and technically we should throw away the
2463         ; data now that all RST/ACK/URG processing has been done.  However,
2464         ; we try to see if we can possibly do a little compaction, since
2465         ; the overhead of doing this is a lot less than the overhead
2466         ; of re-processing the re-transmitted segment!
2467         MOVE A,XBINPS(I)        ; Check length of input queue
2468         CAIL A,2                ; Must be at least 2
2469          SKIPN XBITQH(I)
2470           BUG CHECK,[TCP: Wind & Queue both 0]
2471
2472         ; See if it's worth trying to compact the input seg into the
2473         ; last one received (which hasn't yet been seen by MP level)
2474         HLRZ A,XBITQH(I)        ; Get ptr to last input seg on queue
2475         LDB B,[PK$TDO (A)]      ; Get offset to data in old seg
2476         LDB C,[PK$TDL (A)]      ; See how much data is there
2477         LDB T,[PK$TDL (R)]      ; Find # bytes in new segment
2478         ADDI B,(C)              ; Get offset to end of data
2479         MOVEI D,(B)
2480         ADDI D,(T)              ; Get projected total offset
2481         CAML D,XBRMSS(I)        ; Crock method of ensuring enuf room.
2482          JRST TSI17             ; Not enough, we lose.  Lose.  Lose.
2483
2484         ; Win!  We're gonna compact!
2485         METER("TCP: Iseg cmpct")
2486         ADDI C,(T)              ; Get new # bytes for prev seg
2487         DPB C,[PK$TDL (A)]      ; Store it in advance.
2488         HLRZ D,PK.TCP(A)        ; Find addr of TCP header in prev seg
2489         IDIVI B,4
2490         ADDI D,(B)              ; Get addr for BP to end of data
2491         HRL D,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
2492         LDB B,[PK$TDO (R)]      ; Get data offset for new segment
2493         IDIVI B,4
2494         ADDI B,(H)              ; Get addr for BP to start of new data
2495         HRL B,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
2496         ; B/ BP to new data
2497         ; D/ BP to end of old data
2498         ; T/ # bytes of new data
2499         MOVEI A,(T)             ; Save # added data in A
2500 TSI74:  ILDB C,B
2501         IDPB C,D
2502         SOJG T,TSI74
2503         SETZ D,                 ; Clear D to indicate compaction done.
2504         JRST TSI75
2505
2506         ; Can't accept segment data, period.
2507 TSI17:  METER("TCP: Ifl 0-wnd")
2508         JRST TSIFL              ; Flush the seg, sob.
2509
2510 TSI75:  MOVEI B,(TT)
2511         ADDB B,XBRNXT(I)        ; Update rcv.nxt value by adding seg.len
2512         TLZE B,%MOD32
2513          MOVEM B,XBRNXT(I)      ; Updated!
2514         LDB B,[XB$ICH (I)]      ; See if we have an input channel #
2515         JUMPE B,[METER("TCP: IS fl no chan")
2516                 JRST TSI78]     ; No input channel, so just throw away.
2517         MOVEI C,(A)             ; Save # bytes data.
2518         ADDM A,XBINBS(I)        ; Add new bytes to # bytes in input queue
2519         JUMPE D,TSI78           ; If compaction done, that's all...
2520         SKIPE B,XBINPS(I)       ; If no segments previously on queue,
2521          MOVE B,XBIBC(I)        ; or current input buff has zero cnt,
2522                                 ; then will definitely interrupt user later.
2523         AOS XBINPS(I)           ; Bump # segments on queue
2524
2525         ; Check to see how much to reduce window by.
2526         ; Amount is in C (defaults to amount we just received)
2527         CALL TCPRWS             ; Set receive window
2528
2529         ; Finally add segment to queue!
2530         MOVEI A,(R)             ; Set up pointer to packet/segment
2531         MOVEI Q,XBITQH(I)       ; Point to TCP input queue
2532         CALL PKQPL(PK.TCP)      ; Add to end of queue, using TCP links.
2533         JUMPN B,TSI78           ; Check, jump unless had no input before
2534         CALL TXBIST             ; If none, then must definitely change state!
2535         HRLM T,XBSTAU(I)        ; 
2536         CALL TCPUII             ; And always give an input-avail int!
2537
2538         ; Now must send an ACK, or rather arrange for one to be
2539         ; sent soon.  FIN is also checked here, so as to bypass the
2540         ; code which assumes that XBRNXT hasn't been updated (if we are
2541         ; here, it certainly has!)
2542 TSI78:  MOVSI A,(TC%ACK)        ; Set bit asking for ACK to be sent.
2543         IORM A,XBSTAT(I)
2544         TLNN E,(TC%FIN)         ; Perform FIN-bit check
2545          JRST TSI90             ; None, all done with segment!
2546         JRST TSI82              ; FIN exists, handle it (bypass bump of XBRNXT)
2547
2548         ; Lastly check the FIN bit.  Not clear if a bunch of states
2549         ; want to come here from ACK processing or not.
2550         ; Anyway, code assumes could be in any state.
2551 TSI80:  TLNN E,(TC%FIN)
2552          JRST TSI90
2553         CAIG J,.XSSYN
2554          JRST TSIF80            ; Flush if CLOSED, LISTEN, SYN-SENT
2555
2556         ; Advance RCV.NXT over the FIN and send an ACK for it.
2557         AOS A,XBRNXT(I)
2558         TLZE A,%MOD32
2559          MOVEM A,XBRNXT(I)
2560 TSI82:  MOVSI A,(TC%ACK+%XBFIN) ; Set bit asking that ACK be sent, and FIN 
2561         IORM A,XBSTAT(I)        ; was seen.
2562         MOVEI T,.XCFRN          ; Say foreign host closed input side.
2563         CALL TCPUCI
2564
2565         ; Now effect some state changes
2566         CAIE J,.XSOPN           ; If OPEN
2567          CAIN J,.XSSYR          ; or SYN-RCVD
2568           JRST [MOVEI J,.XSCLW  ; Change state to CLOSE-WAIT
2569                 JRST TSI85]
2570         CAIN J,.XSFN1
2571          JRST [ SKIPN XBORTQ(I) ; If our FIN was ACK'd,
2572                  JRST TSI84     ; Go enter TIME-WAIT state
2573                 MOVEI J,.XSCLO  ; Otherwise enter CLOSING state.
2574                 JRST TSI85]
2575         CAIE J,.XSFN2
2576          CAIN J,.XSTMW
2577           JRST TSI84            ; Go to TIME-WAIT
2578         JRST TSI90              ; Any other states just do nothing.
2579
2580 TSI84:  CALL TSITMW             ; Enter TIME-WAIT state, starting 2-MSL timeout
2581         JRST TSI90
2582 TSI85:  HRRM J,XBSTAT(I)        ; Set new state and fall through.
2583         CALL TCPUSI             ; Set user state.
2584
2585         ; Done.  Finally decide whether to keep segment around or not.
2586 TSI90:  HLRZ A,XBITQH(I)        ; Get ptr to last thing on input queue
2587         CAIN A,(R)              ; Same as current seg (ie it was queued?)
2588          RET                    ; Yes, just return!
2589         JRST TSIF90             ; Else drop through to flush the segment.
2590 \f
2591 XSMTRS: OFFSET -.
2592 .XSCLS:: METER("TCP: state CLS")
2593 .XSSYQ:: METER("TCP: state SYQ")
2594 .XSLSN:: METER("TCP: state LSN")
2595 .XSSYN:: METER("TCP: state SYN")
2596 .XSSYR:: METER("TCP: state SYR")
2597 .XSOPN:: METER("TCP: state OPN")
2598 .XSFN1:: METER("TCP: state FN1")
2599 .XSFN2:: METER("TCP: state FN2")
2600 .XSCLW:: METER("TCP: state CLW")
2601 .XSCLO:: METER("TCP: state CLO")
2602 .XSCLA:: METER("TCP: state CLA")
2603 .XSTMW:: METER("TCP: state TMW")
2604 .XSTOT:: OFFSET 0
2605
2606
2607 TSIF01: METER("TCP: ISeg cksm errs ")
2608         JRST TSIFL
2609 TSIF02: METER("TCP: IS zero port/addr")
2610         JRST TSIFL
2611 TSIF03: METER("TCP: IS fl neg data")
2612         JRST TSIFL
2613 ;TSIF10:        ; Flush this later (retain til get new .METER LIST)
2614         METER("TCP: IS fls Seq # err")
2615         JRST TSIFL
2616 TSIF50: METER("TCP: IS fls Seq no ACK ")
2617         JRST TSIFL
2618 TSIF55: METER("TCP: IS fls CLO & FIN not ACKed")
2619         JRST TSIFL
2620 TSIF56: METER("TCP: IS fls CLA & FIN not ACKed")
2621         JRST TSIFL
2622 TSIF70: METER("TCP: IS fls seqerr processed A/U/R")
2623         JRST TSISNE             ; Go respond with ACK
2624 TSIF80: METER("TCP: IS fls FINchk state")
2625         JRST TSIFL
2626 TSIF2A: METER("TCP: IS fls random RST")
2627         JRST TSIFL
2628 TSIF2B: METER("TCP: IS fls Fresh SYN already on SYNQ")
2629         JRST TSIFL
2630
2631 TSIF90: METER("TCP: IS fls processed seg")
2632         JRST TSIFL
2633
2634         ; Come here to flush the datagram/segment and return.
2635 TSIFL:  METER("TCP: Isegs flushed")
2636         MOVEI A,(R)
2637         CALRET PKTRT
2638
2639 ; TSITMW - Routine to enter TIME-WAIT state.
2640 ; TSITM2 is entry point when already in that state.
2641 ; Clobbers T, Q
2642 TSITMW: MOVEI J,.XSTMW
2643         HRRM J,XBSTAT(I)
2644         CALL TCPUSI             ; Alert user if necessary.
2645 TSITM2: SKIPE XBORTQ(I)         ; Unless retransmit still hogs timeout
2646          RET                    ; (if so, return)
2647         MOVE T,TIME             ; then set up 2-MSL timeout.
2648         ADDI T,30.*2.*60.
2649         MOVEM T,XBORTT(I)
2650         RET
2651
2652 ; TSISNE - Sequence number error, segment not acceptable,
2653 ;       return an ACK unless RST was set.
2654
2655 TSISNE: METER("TCP: IS NE seqerr")
2656         TLNE E,(TC%RST)
2657          JRST TSIFL             ; Flush segment if RST was set
2658
2659         ; Send an immediate ACK without data, re-using the
2660         ; packet/segment that R points to.
2661 TSOACK: MOVSI T,(TC%ACK)        ; Send an ACK immediately
2662         TRCPKT R,"TSOACK return ACK in response to out-of-seq ACK"
2663         CALL TSOSNR
2664         RET
2665 \f
2666 ; TSISQ - Jumped to from TCPIS when TCP segment is received that matches
2667 ;       no existing connection.  Check to see if it's a valid connection
2668 ;       request.  If so,
2669 ;       (1) see if it matches any wild listens; if so, process.
2670 ;       (2) see if it's OK to start up a server for it; if so, process.
2671
2672 TSISQ:  TLNE E,(TC%RST) ; If it has RST set,
2673          JRST TSIF2A    ;  Go drop it quietly.
2674         TLNE E,(TC%ACK) ; If ACK, can't be a valid request either
2675          JRST TSISAR    ;  Go send a RST in response (with SEQ=SEG.ACK)
2676         TLNN E,(TC%SYN) ; Anything else had better have a SYN
2677          JRST TSISLR    ;  otherwise send RST with SEQ=0,ACK=SEQ+LEN
2678
2679         ; Okay, we have a promising SYN.  See if it matches any
2680         ; "wild" listens.
2681         METER("TCP: Fresh SYN")
2682         LDB B,[TH$DST (H)]      ; Get desired port #
2683         LDB C,[TH$SRC (H)]      ; Find port it's from 
2684         LDB D,[IP$SRC (W)]      ; and host it's from.
2685         MOVSI I,-XBL
2686 TSISQ2: HRRZ J,XBSTAT(I)        ; Get state for TCB
2687         CAIE J,.XSLSN           ; We're hunting for LISTEN
2688 TSISQ3:  AOBJN I,TSISQ2
2689         JUMPGE I,TSISQ5         ; Jump if no match.
2690         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get our local port (never wild)
2691         CAIE A,(B)              ; It must match desired "dest port"!
2692          JRST TSISQ3            ; Nope, doesn't want this one.
2693         SKIPL XBHOST(I)         ; Aha, very likely will match. Follow thru.
2694          CAMN D,XBHOST(I)
2695           CAIA
2696            JRST TSISQ3          ; Host didn't match.
2697         MOVE A,XBPORT(I)        ; Check remote port field
2698         TRNE A,17               ; Low 4 bits are non-zero if remote wild.
2699          JRST TSISQ4            ; Won!
2700         LDB A,[.BP TH%SRC,A]    ; Not wild, see if it matches request.
2701         CAIE A,(C)              ; Compare our remote with its source.
2702          JRST TSISQ3            ; No, no match here.
2703
2704         ; Matched a wild listen!  Must fill in various stuff.
2705 TSISQ4: MOVEI A,17
2706         ANDCAM A,XBPORT(I)      ; Clear wild bits
2707         DPB C,[.BP TH%SRC,XBPORT(I)]    ; Set remote port #
2708         MOVEM D,XBHOST(I)               ; Set remote host addr
2709         LDB D,[IP$DST (W)]      ; Set local address to whichever address other guy knows
2710         MOVEM D,XBLCL(I)
2711         DPB I,[PK$TCB (R)]      ; Finish setting up context for dispatch
2712         CALL TCPMSS             ; Correct MSS values for specified foreign host
2713         CALL TCPRWS             ; Open up a receive window
2714         JRST TSILS              ; Go handle SYN rcvd for LISTEN.
2715
2716         ; No outstanding listens.  Check the port number, to
2717         ; see if it's something we are likely to service.
2718 TSISQ5: LDB A,[TH$DST (H)]      ; Get destination port #
2719         CAILE A,%TCPMP          ; Fits max port # for RFC service?
2720          JRST TSISLR            ; Naw, barf about it (send RST).
2721         
2722         ; See if we're actually willing to start up a job...
2723         LDB A,[IP$SRC (W)]      ; See who it's from
2724         JSP T,IPLCLH            ; Ask IP if this is one of us
2725          SKIPL TCPUSW           ; It isn't, so make sure we're open for biz
2726           CAIA
2727            JRST TSISLR          ; Sorry charlie (send RST)
2728
2729         ; Okay, we'll take it as SYN-QUEUED!  We know this is a new
2730         ; request, otherwise it would have been matched at TSI02 and
2731         ; dispatched to TSISQQ instead.
2732
2733 ifn 0,[
2734         ;   first see if it's already on the queue!
2735         ; Note that we still have remote host # in D.
2736         SKIPN Q,TCPRQH          ; Get pointer to 1st item on queue
2737          JRST TSISQ7            ; No queue, so not on.
2738         MOVE B,TH$SRC(H)        ; Get req's source/dest ports
2739         MOVE D,IP$SRC(W)        ; and its source addr
2740 TSISQ6: HLRZ T,PK.TCP(Q)        ; Get addr of TCP header from queue
2741         HLRZ C,PK.IP(Q)         ; and addr of IP header
2742         CAIE T,
2743          CAIN C,
2744           BUG CHECK,[TCP: SYNQ smashed]
2745         CAMN B,TH$SRC(T)        ; Same ports?
2746          CAME D,IP$SRC(C)       ; Same host?
2747           CAIA                  ; No
2748            JRST TSIF2B          ; Yes, assume SYN is a dup, ignore it.
2749         HRRZ Q,PK.TCP(Q)        ; Get next thing on pending queue
2750         JUMPN Q,TSISQ6
2751
2752         ; Not on queue, let's try to add it.
2753 TSISQ7: MOVE A,TCPRQN           ; Find # of things on queue already
2754         CAIL A,%TCPMQ           ; Keep its length reasonable
2755          JRST TSISQ8            ; Sigh, ran out.
2756         HRROI T,NTSYNL          ; OK, now try loading job up!
2757         CALL NUJBST             ; Queue request for job TCPRFC
2758          JRST TSISLR            ; Bah, no job slots or something!
2759         MOVEI A,(R)             ; It's on the way!  Queue the SYN now.
2760         MOVEI Q,TCPRQH
2761         CALL PKQPL(PK.TCP)      ; Add onto end of pending-RFC queue.
2762 ] ;ifn 0
2763
2764         MOVSI I,-XBL
2765 TSISQ6: SKIPN XBUSER(I)
2766          SKIPE XBSTAT(I)
2767           AOBJN I,TSISQ6
2768         JUMPGE I,TSISQ8         ; Jump if no free slots.
2769         CALL TXBINI             ; Got one, might as well verify it's cleared.
2770         MOVE A,TCPRQN           ; Find # of things on queue already
2771         CAIL A,XBL/2            ; Keep number reasonable
2772          JRST TSISQ8            ; Sorry, too many.
2773         HRROI T,NTSYNL          ; Now see if we can load up handler job.
2774         CALL NUJBST             ; Do it
2775          JRST TSISLR            ; Ugh, couldn't start new job...
2776         MOVEI J,.XSSYQ
2777         MOVEM J,XBSTAT(I)       ; Set state SYN-QUEUED
2778         LDB A,[IP$SRC (W)]
2779         MOVEM A,XBHOST(I)       ; Set up host #
2780         MOVE A,TH$SRC(H)        ; and ports
2781                                 ; Don't need to set XBLCL, won't be looked at
2782         MOVEM A,XBPORT(I)       ; That's all we need for now.
2783         CALL TCPMSS             ; Might as well keep these right even though
2784         CALL TCPRWS             ;  this TCB will be flushed when conn opens.
2785         MOVE A,TIME
2786         ADDI A,10.*30.          ; Let it stay queued for 10 seconds.
2787         MOVEM A,XBORTT(I)
2788         MOVEI Q,XBITQH(I)       ; Put the segment on input queue for slot.
2789         MOVEI A,(R)
2790         CALL PKQPF(PK.TCP)
2791
2792         HRRZM I,TCPRQL          ; Save # of last SYN queued.
2793         AOS TCPRQN              ; And increment count of entries.
2794         METER("TCP: Srvjob starts")
2795         RET                     ; All done!
2796
2797 TSISQ8: BUG INFO,[TCP: SYN queue full]
2798         JRST TSISLR             ; Sigh.
2799
2800
2801 ; TSISQQ - Come here when segment received that matches an
2802 ;       existing port/host which is in SYN-QUEUED state.
2803
2804 TSISQQ: TLNE E,(TC%RST)         ; Is it an RST?
2805          JRST [ CALL TSISQF     ; Yeah, flush the queued SYN.
2806                 JRST TSIFL]     ; and drop segment.
2807         TLNE E,(TC%ACK)         ; An ACK?  That's illegal etc...
2808          JRST [ CALL TSISQF     ; Flush the queued SYN,
2809                 JRST TSISAR]    ; and send a RST in response.
2810         TLNN E,(TC%SYN)         ; Anything else better be a SYN
2811          JRST [ CALL TSISQF     ; else send RST.
2812                 JRST TSISLR]
2813         JRST TSIF2B             ; Most likely a duplicate SYN, so just
2814                                 ; flush it and return.
2815
2816         ; Flush TCB for a queued SYN.
2817 TSISQF: SETZM XBSTAT(I)
2818         SETZM XBPORT(I)
2819         SETZM XBHOST(I)
2820         SETZM XBORTT(I)
2821         SKIPE XBITQH(I)
2822          CALL TXBIFL
2823         SOSGE TCPRQN
2824          BUG HALT
2825         RET
2826
2827 \f
2828 ; TSISAR - Respond to current segment by sending a RST with
2829 ;       SEQ=SEG.ACK.  Re-uses the current segment's packet buffer.
2830 ;       R, W, H set up for PE, IP, and TCP.
2831 ;       E has seg flags.  May not be anything in I, so re-use fields
2832 ;       from given packet!
2833 ; TSISAQ - like TSISAR but just drops segment if it has RST in it.
2834 ; TSISLR - like TSISAR, but SEQ=0, ACK=SEG.SEQ+SEG.LEN
2835 ;       This is used when responding to segments without an ACK, i.e.
2836 ;       initial SYNs.
2837
2838 TSISLR: METER("TCP: times at TSISLR")
2839         LDB A,[TH$SEQ (H)]      ; Get SEQ.  Assume TT still valid.
2840         ADDI A,(TT)             ; ACK=SEG.SEQ+SEG.LEN
2841         LSH A,4                 ; Left justify it.
2842         SETZ D,                 ; SEQ=0
2843         MOVSI T,(TC%RST+TC%ACK)
2844         JRST TSISA2
2845
2846 TSISAQ: TLNE E,(TC%RST)         ; Here, if incoming seg was RST,
2847          JRST TSIFL             ; just ignore, don't respond.
2848 TSISAR: METER("TCP: times at TSISAR")
2849         MOVE D,TH$ACK(H)        ; Use SEG.ACK for SEQ
2850         MOVSI T,(TC%RST)
2851
2852         ; Here, A, D, and T must be set up.
2853 TSISA2: SETZ B,
2854         LDB C,[TH$SRC (H)]      ; Get source port
2855         DPB C,[.BP TH%DST,B]    ; Use as dest port
2856         LDB C,[TH$DST (H)]      ; Get dest
2857         DPB C,[.BP TH%SRC,B]    ; Use as... you guessed it.
2858         PUSH P,IP$DST(W)        ; Which of my addresses to claim to be from
2859         MOVE C,IP$SRC(W)
2860
2861 ;       A/ ACK field (left justified)
2862 ;       B/ <loc port><rem port> (left justified)
2863 ;       C/ remote host (left justified)
2864 ;       D/ SEQ field (left justified)
2865 ;       R/ PE ptr to packet responding to
2866 ;       T/ flags to use
2867
2868
2869         SETZ I,
2870         CALL TSOINI             ; Initialize W,H,PK.IP(R),PK.TCP(R),PK.TCI(R)
2871                                 ; Note everything in PK.TCI will be wrong.
2872         MOVEM C,IP$DST(W)       ; Store remote host
2873         MOVEM B,TH$SRC(H)       ; Store loc/rem ports
2874         MOVEM D,TH$SEQ(H)       ; Deposit new SEQ field
2875         TLNN T,(TC%ACK)         ; If sending an ACK
2876          SETZ A,
2877         MOVEM A,TH$ACK(H)       ; Deposit ACK field.
2878         TLO T,240000            ; Set IHL
2879         MOVEM T,TH$CTL(H)       ; Deposit segment flags
2880         MOVEI A,5*4
2881         DPB A,[IP$TOL (W)]      ; Say length just a std TCP header.
2882         POP P,IP$SRC(W)
2883         CALL THCKSM             ; Figure TCP checksum
2884         DPB A,[TH$CKS (H)]      ; Deposit in
2885         CALL IPKSND             ; Put this buffer on IP output queue!
2886         RET
2887
2888 \f
2889 ; TSILS - Segment received for this connection while in LISTEN state.
2890 ;       
2891 TSILS:  METER("TCP: Segs rcvd in LSN")
2892         TLNE E,(TC%RST)         ; Ignore any RSTs.
2893          JRST TSIFL
2894         TLNE E,(TC%ACK)         ; ACKs are bad too.
2895          JRST TSISAR            ;  Respond with a RST to them.
2896         TLNN E,(TC%SYN)         ; It should be a SYN.
2897          JRST TSIFL             ;  If not, just flush.
2898
2899         ; We've received a SYN that should be valid.  Set up for
2900         ; SYN-RCVD state.  Note that we ignore security/precedence
2901         ; except to remember it so our transmits look OK.
2902         ; NOTE!!! TSILSX is an entry point from MP level TCPOPN call,
2903         ; which is used to hook up a user OPEN to a matching SYN on
2904         ; the pending-RFC queue!
2905         METER("TCP: SYN in LSN")
2906 TSILSX: LDB D,[TH$SEQ (H)]      ; Get sequence number
2907         LDB A,[TH$WND (H)]
2908         MOVEM A,XBSWND(I)       ; Initialize send window
2909         MOVEM A,XBSAVW(I)       ; and available window
2910         MOVEM D,XBSWL1(I)       ; Save seg.seq used for last window update
2911         LDB A,[TH$ACK (H)]
2912         MOVEM A,XBSWL2(I)       ; Save seg.ack used for last window update
2913         ADDI D,1
2914         TLZ D,%MOD32            ; Get seg.seq+1
2915         MOVEM D,XBRNXT(I)       ; Store as initial RCV.NXT
2916         CALL TCPISS             ; Select a new ISS in A (Initial Send Seq#) 
2917         MOVEM A,XBSUNA(I)       ; Set SND.UNA to ISS
2918 ;       ADDI A,1
2919 ;       TLZ A,%MOD32
2920         MOVEM A,XBSNXT(I)       ; And SND.NXT also; assume that process of
2921                                 ; sending it will increment by 1.
2922
2923         ; Check for TCP options at this point, and process if present
2924         LDB A,[TH$THL (H)]      ; TCP header length
2925         CAILE A,%TCPHL          ; If default, no options present
2926          CALL TCPPIO            ; Else, process input options
2927
2928         ; Nasty business - put together and send a segment with
2929         ; seq=ISS,ack=RCV.NXT,ctl=SYN+ACK.
2930         ; For now we can assume that initial SYNs will never
2931         ; contain text, and so we don't have to queue it up.
2932         ; Alternatively can hope that remote site is clever about
2933         ; retransmitting!
2934         ; This is because if we don't need to keep received segment
2935         ; around, can just re-use it.
2936         MOVSI T,(TC%SYN+TC%ACK)
2937         TRCPKT R,"TSISLX Reflecting incoming SYN with SYN"
2938         CALL TSOSSN             ; Fire off SYN. Sends MSS option too.
2939         MOVEI J,.XSSYR          ; Change state to SYN-RCVD.
2940         HRRM J,XBSTAT(I)
2941         CALL TCPUSI             ; Set user state.
2942         RET
2943
2944 ; TCPISS - Select new ISS, return in A
2945
2946 TCPISS: MOVE A,TIME
2947         LSH A,13.
2948 TCPIS2: TLZ A,%MOD32
2949         CAMN A,TISSLU   ; Same as last used?
2950          JRST [ AOS A,TISSC
2951                 ANDI A,17
2952                 LSH A,9.
2953                 ADD A,TISSLU
2954                 JRST TCPIS2]    ; Jump to mask off and test again.
2955         MOVEM A,TISSLU
2956         RET
2957
2958 ; TCPPIO - Process TCP options from incoming segment.
2959 ;       This is only checked for SYN segments because the only interesting
2960 ;       option (Max Segment Size) is only sent with SYN segments
2961 ;
2962 ;       R/ Pkt buffer
2963 ;       I/ TCB Index
2964 ;       H/ TCP Header
2965 ;       A/ TCP header size in 32-bit words
2966
2967 TCPPIO: SUBI A,%TCPHL
2968         LSH A,2                 ; Options length in bytes
2969         MOVE B,[TH$OPT (H)]     ; BP to start of options
2970 TCPPIL: SKIPG A                 ; Anything left?
2971          RET                    ; Nope, done
2972         ILDB C,B                ; Get option type
2973         CAIL C,TCPPIS           ; In range?
2974          RET                    ; Have to give up if unknown option
2975         JRST @TCPPIT(C)
2976
2977 TCPPIT: TCPPI0
2978         TCPPI1
2979         TCPPI2
2980 TCPPIS==.-TCPPIT
2981
2982         ;End of option list
2983 TCPPI0: RET
2984
2985         ;NOP
2986 TCPPI1: SOJA A,TCPPIL           ; Decrement length and loop
2987
2988         ;Max Seg Size   TYPE ? LENGTH ? MSB ? LSB
2989 TCPPI2: ILDB C,B                ; Get length
2990         SUB A,C                 ; Count it
2991         ILDB C,B                ; Get 16-bit quantity, updating B
2992         LSH C,8.
2993         ILDB D,B
2994         ADD C,D                 ; Now contains foreign MSS request
2995         CAMGE C,XBSMSS(I)       ; Don't exceed our own limits!
2996          MOVEM C,XBSMSS(I)      ; Set new value in TCB
2997         JRST TCPPIL
2998
2999 \f
3000 ; TSISS - Segment received while in SYN-SENT state.
3001 ;       Note that being in this state implies that there is one
3002 ;       segment on the retransmit queue, which must be the initial SYN
3003 ;       that we sent.
3004
3005 TSISS:  METER("TCP: Segs rcvd in SYN-SENT")
3006         LDB D,[TH$SEQ (H)]      ; Get SEG.SEQ
3007         TLNN E,(TC%ACK)         ; Has an ACK?
3008          JRST TSISS2            ; Nope, it better be RST or SYN.
3009
3010         ; See if our SYN has been ACKed. Since we only send SYNs
3011         ; without data, this just means a test for SEG.ACK = SND.NXT.
3012         LDB B,[TH$ACK (H)]      ; Have ACK. Get ack field
3013         CAME B,XBSNXT(I)        ; It should ACK our initial SYN
3014          JRST TSISAQ            ; If not, send a RST.
3015 ;       MOVE A,XBSUNA(I)        ; snd.una =< seg.ack =< snd.nxt ?
3016 ;       CMPSEQ A,=<,B,=<,XBSNXT(I),TSISAQ       ; If not good, send RST.
3017
3018 TSISS2: TLNE E,(TC%RST)         ; Check for RST
3019          JRST [ TLNN E,(TC%ACK) ; Ugh, have RST.  Did we also get good ACK?
3020                  JRST TSIFL     ; No, can just flush this segment.
3021                 MOVEI T,.XCRFS  ; Yeah, our SYN is being refused, so
3022                 CALL TCPUC      ; say this is close-reason.
3023                 JRST TSIRST]    ; Then must go abort connection.
3024
3025         ; Here we get to check security/precedence.  Hurray.
3026         ; We should just copy the seg values, so as to fake sender out.
3027
3028         ; Now finally check the SYN bit!
3029         TLNN E,(TC%SYN)         ; Must be set
3030          JRST TSIFL             ; Neither RST nor SYN?  Flush it.
3031
3032         ; It's a SYN.  Update our send params from its values.
3033         ; We will either send an ACK or another SYN; in both cases the
3034         ; SYN segment currently on the retransmit queue should be flushed.
3035         MOVEI Q,XBORTQ(I)       ; Point to retrans q
3036         CALL PKQGF(PK.TCP)      ; Pluck off 1st thing
3037         SOSN XBORTL(I)          ; Verify none left on queue
3038          CAIN A,                ; and something was there!
3039           BUG CHECK,[TCP: SYN-SENT retrans Q bad]
3040         JUMPE A,TSISS3          ; Just for robustness
3041         TRCPKT A,"TSISS2 Flushing our SYN from rexmit Q"
3042         MOVE T,PK.FLG(A)
3043         TLO T,%PKFLS            ; Tell IP to flush packet if seen
3044         MOVEM T,PK.FLG(A)
3045         CALL PKTRT              ; Flush SYN packet if not otherwise busy
3046         SETZM XBORTT(I)         ; and flush timeout.
3047
3048 TSISS3: LDB A,[TH$WND (H)]
3049         MOVEM A,XBSWND(I)       ; Initialize send window
3050         MOVEM A,XBSAVW(I)       ; and available window
3051         MOVEM D,XBSWL1(I)       ; Save seg.seq used for last window update
3052         LDB A,[TH$ACK (H)]
3053         MOVEM A,XBSWL2(I)       ; Save seg.ack used for last window update
3054         ADDI D,1
3055         TLZ D,%MOD32
3056         MOVEM D,XBRNXT(I)       ; Set RCV.NXT to SEQ+1
3057
3058         ; Process segment options in case sender specified MSS
3059         LDB A,[TH$THL (H)]      ; TCP header length
3060         CAILE A,%TCPHL          ; If default, no options present
3061          CALL TCPPIO            ; Else, process input options
3062
3063         TLNN E,(TC%ACK)
3064          JRST TSISS4
3065         LDB A,[TH$ACK (H)]      ; If ACK also present, (known acceptable)
3066         MOVEM A,XBSUNA(I)       ; Set SND.UNA to SEG.ACK.
3067
3068         ; Here must test if SND.UNA > ISS (our SYN has been ACKed).
3069         ; But this was already checked just before TSISS2.
3070         MOVSI T,(TC%ACK)        ; Hurray, we're open!  Must ACK the SYN
3071         TRCPKT R,"TSISS3 ACK SYN to open conn"
3072         CALL TSOSNR             ; (Re-using its segment)
3073         MOVEI J,.XSOPN          ; Hurray, we're open now!
3074         HRRM J,XBSTAT(I)
3075         CALL TCPUSI             ; Update user state
3076         RET
3077
3078         ; Our SYN not ACKed yet, so enter SYN-RCVD state.
3079 TSISS4:
3080         ; Must go send seq=ISS,ack=RCV.NXT,ctl=SYN+ACK
3081         LDB D,[TH$SEQ (H)]      ; Get sequence number
3082         ADDI D,1
3083         TLZ D,%MOD32            ; Get seg.seq+1
3084         MOVEM D,XBRNXT(I)       ; Store as initial RCV.NXT
3085         SOSGE A,XBSUNA(I)       ; Set SND.UNA to ISS
3086          JRST [ MOVEI A,1
3087                 MOVEM A,XBSUNA(I)
3088                 JRST .+1]
3089         MOVEM A,XBSNXT(I)       ; And SND.NXT also; assume that process of
3090                                 ; sending it will increment by 1.
3091         MOVSI T,(TC%SYN+TC%ACK)
3092         TRCPKT R,"TSISS4 ACK and re-SYN SYN-SENT conn"
3093         CALL TSOSSN             ; Fire off SYN/ACK with MSS option included.
3094         MOVEI J,.XSSYR          ; Change state to SYN-RCVD.
3095         HRRM J,XBSTAT(I)
3096         CALL TCPUSI             ; Set user state.
3097         RET
3098 \f
3099 ; TSIRST - valid RST segment received (not in LISTEN).
3100 ;       Basically must flush the connection, signal user, etc.
3101
3102 TSIRST: METER("TCP: Valid RSTs")
3103         CALL TXBFLP             ; Flush the TCB immediately, PI level
3104         MOVEI T,.XCRST          ; Say fgn host reset stuff
3105         CALL TCPUC              ; as "close reason"
3106         CALRET TSIFL            ; Flush segment.
3107 \f
3108 ; TSISYN - SYN segment received.
3109 ;       If in window, error - send a RST and close things up.
3110 ;       If not in window, return an ACK as for TSISNE.
3111
3112 TSISYN: METER("TCP: Random SYN")
3113
3114         CALRET TSIFL
3115
3116 ; TSISRA - Bad ACK seen while in SYN-RCVD state,
3117 ;       send a RST.
3118
3119 TSISRA: METER("TCP: Bad ACK in SYR")
3120         CALRET TSIFL
3121
3122 ; TSISAK - Received ACK for something not yet seen, send ACK and
3123 ;       drop segment.
3124 TSISAK: METER("TCP: ACK for nxm")
3125         CALRET TSIFL
3126
3127 ; TSIATW - Received ACK while in TIME-WAIT state.  This should be
3128 ;       a re-transmit of the remote FIN.  ACK it, and restart
3129 ;       2-MSL timeout.
3130
3131 TSIATW: METER("TCP: ACK in .XSTMW")
3132         MOVSI T,(TC%ACK)
3133         TRCPKT R,"TSIATW ACK send in TIME-WAIT"
3134         CALL TSOSNR             ; Send simple ACK in response.
3135         JRST TSITM2             ; and restart 2-MSL timeout.
3136 \f
3137 SUBTTL TCP Send output segment
3138
3139 ; Send TCP output segment.
3140 ; Send output (usually data) segment, for connection indexed by I.
3141 ; Note this differs from TSISAR etc. which don't have any active connection,
3142 ; thus no valid I.  As much context as possible is taken from the
3143 ; TCB tables indexed by I.
3144 ; In particular, the %XBCTL flags are examined to see if anything should
3145 ; be added to the outgoing segment, other than what was requested in the
3146 ; call.
3147
3148 ; Sequence space variables are updated.
3149 ; The following possibilities are independently possible:
3150 ;       Re-using packet / using fresh packet
3151 ;       Uses seq space (must retrans) / no seq space used
3152 ;
3153 ; TSOSND - send output segment while connection established
3154 ;       R/ PE ptr to packet,
3155 ;               PK.BUF, PK.IP and PK.TCP must be set.
3156 ;               If these were not initialized by TSOINI so as to get
3157 ;               the right offsets, you will probably lose.
3158 ;               PK.TCI should have the # bytes of data and offset.
3159 ;       I/ TCB index
3160 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3161
3162 ; TSOSNR - Just sends a data-less "reply" type segment using
3163 ;       TCB's sequence space vars.  Seq=snd.nxt, ack=rcv.nxt, etc.
3164 ;       R/ PE ptr to packet (packet will be smashed and re-used)
3165 ;       I/ TCB index
3166 ;       T/ flags to use (Neither ACK nor %XBCTL will be added automatically!)
3167
3168 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3169
3170 TSOSNR: CALL TSOINI     ; Initialize (sets up W,H PK.IP,PK.TCP,PK.TCI)
3171         SETZ TT,        ; Say zero bytes of real data
3172         DPB TT,[PK$TDL (R)]     ; and make sure packet entry reflects this.
3173         JRST TSOSN      ; Jump in to do it.
3174
3175
3176 ; TSOSSN - Send an initial SYN segment. No data, but add a TCP
3177 ;       MSS option set from XBRMSS(I), and using TCB's sequence space
3178 ;       vars.  Seq=snd.nxt, ack=rcv.nxt, etc.
3179 ;       R/ PE ptr to packet (packet will be smashed and re-used)
3180 ;       I/ TCB index
3181 ;       T/ flags to use (None, including SYN, will be added automatically)
3182
3183 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3184
3185 TSOSSN: CALL TSOINI             ; Initialize (sets up W,H PK.IP,PK.TCP,PK.TCI)
3186         MOVE TT,XBRMSS(I)       ; Max seg size we would like
3187         LSH TT,4                ; 32-bit option
3188         IOR TT,TSOMSO           ; Add in type and length fields of option
3189         MOVEM TT,TH$OPT(H)      ; Write it. Damn well better be first option.
3190         LDB TT,[PK$TDO (R)]     ; Get current TCP header size
3191         ADDI TT,4               ; Adding 4-byte option
3192         DPB TT,[PK$TDO (R)]
3193         SETZ TT,                ; Say zero bytes of real data
3194         DPB TT,[PK$TDL (R)]     ; and make sure packet entry reflects this.
3195         JRST TSOSN              ; Jump in to do it.
3196
3197 TSOMSO: .BYTE 8 ? 2 ? 4 ? 0 ? 0 ? .BYTE ; Option 2, length 4, two data words
3198
3199 TSOSND: MOVSI T,(TC%ACK)        ; Simple data segment
3200         IOR T,XBSTAT(I)         ; Plus whatever is being requested.
3201         HLRZ W,PK.IP(R)         ; Get ptr to IP header
3202         HLRZ H,PK.TCP(R)        ; and TCP header
3203         LDB TT,[PK$TDL (R)]     ; Get # bytes of data
3204 ;       LDB A,[PK$TDO (R)]      ; Get offset of data
3205 ;       ADDI TT,(A)             ; Now have # bytes past std hdr length.
3206
3207 ; TSOSN - Entry point if W, H, and TT already set up.
3208 ;       I/ TCB index
3209 ;       T/ flags for segment
3210 ;       R/ PE ptr (PK.BUF, PK.IP, PK.TCP, PK.TCI must all be set)
3211 ;       W/ IP header ptr
3212 ;       H/ TCP header ptr
3213 ;       TT/ # bytes of data (real data, not including header or SYN/FIN)
3214 ; Clobbers A,B,C,D,E,TT,T,Q and updates various TCB data.
3215
3216 ; This code assumes TT is the bytes of DATA only.
3217 ; Must store the out-of-TCP info in the IP header field, so that
3218 ; the checksum and IPKSND routines will find it there.
3219 ; This info consists of:
3220 ;       IP$SRC - Source address
3221 ;       IP$DST - Dest address
3222 ;       IP$TOL - TCP segment length including header
3223 ;       IP$PTC - Protocol number (needn't set, assumes %PTCTC always)
3224
3225 TSOSN:  METER("TCP: Out segs")
3226         AND T,[TH%CTL]          ; Ensure non-flag bits are flushed.
3227         MOVE A,T
3228         ANDCAB A,XBSTAT(I)              ; Turn off these request bits
3229         TLNE A,(TH%CTL)                 ; Any request bits left?
3230          JRST TSOSN2                    ; Yeah, can't turn off "now" bit.
3231         MOVSI A,(%XBNOW)                ; Satisfied everything, so flush
3232         ANDCAM A,XBSTAT(I)              ; the send-immediately bit.
3233
3234 TSOSN2: LDB A,[PK$TDO (R)]              ; Bytes of header
3235         ADDI A,(TT)                     ; Add bytes of data
3236         DPB A,[IP$TOL (W)]              ; Store in IP length field
3237         MOVE A,XBLCL(I)
3238         LSH A,4
3239         MOVEM A,IP$SRC(W)               ; Set source host
3240         MOVE A,XBHOST(I)
3241         LSH A,4
3242         MOVEM A,IP$DST(W)               ; Set dest host
3243
3244         ; Out-of-TCP info set up, now build the real TCP header.
3245         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get port sending from (local)
3246         DPB A,[TH$SRC (H)]
3247         LDB A,[.BP TH%SRC,XBPORT(I)]    ; Get port to send to
3248         DPB A,[TH$DST (H)]
3249         MOVE A,XBSNXT(I)                ; Get sequence number to use
3250         LSH A,4
3251         MOVEM A,TH$SEQ(H)               ; Set SEQ field
3252         TLNN T,(TC%ACK)                 ; Check flags, sending ACK?
3253          TDZA A,A                       ;   If not, use zero field anyway.
3254           MOVE A,XBRNXT(I)              ; Get ack number to use
3255         LSH A,4
3256         MOVEM A,TH$ACK(H)               ; Set ACK field
3257
3258         SKIPE A,XBSUP(I)                ; Urgent data being sent?
3259          JRST [ TLO T,(TC%URG)          ; Yes!  Say urgent pointer signif
3260                 METER("TCP: Urgent dgms")
3261                 MOVNI B,(TT)
3262                 ADDB B,XBSUP(I)         ; Adjust pointer as result of data sent
3263                 CAIGE B,
3264                  SETZM XBSUP(I)
3265                 LSH A,4
3266                 JRST .+1]
3267         MOVEM A,TH$UP(H)                ; Set urgent pointer if any
3268
3269         MOVE A,XBRWND(I)                ; Get our current receive window
3270         LSH A,4
3271         IOR A,T                         ; Add in caller's flags
3272         LDB B,[PK$TDO (R)]              ; Header length in bytes
3273         LSH B,-2                        ; TCP wants length in 32-bit words
3274         DPB B,[<.BP TH%THL,A>]
3275         MOVEM A,TH$THL(H)               ; Store header len, flags, window
3276
3277         PUSH P,TT                       ; Goddam checksum clobberage
3278         CALL THCKSM                     ; Now figure out checksum
3279         POP P,TT
3280         DPB A,[TH$CKS (H)]
3281
3282         ; TCP header set up.  Now update our TCB connection vars to
3283         ; account for the stuff we're sending.
3284         TLNE T,(TC%SYN)                 ; Now find new seq # (SND.NXT)
3285          ADDI TT,1                      ; SYN counts as 1 octet
3286         TLNE T,(TC%FIN)                 ; So does a FIN
3287          ADDI TT,1
3288         JUMPLE TT,TSOSN8                ; If not actually using seq space, skip
3289                                         ; a bunch of update/retrans stuff.
3290
3291         ; We're using up some sequence space!  Must update avail window,
3292         ; and put the segment on retransmit queue.
3293         MOVE A,XBSAVW(I)                ; Must update avail send window
3294         SUBI A,(TT)
3295         CAIGE A,                        ; If window becomes negative,
3296          SETZ A,                        ; keep it at zero.
3297         MOVEM A,XBSAVW(I)
3298         ADD TT,XBSNXT(I)                ; Get new SND.NXT
3299         TLZ TT,%MOD32
3300         MOVEM TT,XBSNXT(I)
3301         SKIPN XBORTT(I)                 ; Retrans timeout already set?
3302          JRST [ MOVE A,TIME
3303                 ADD A,TCPTMO            ; Make it 5 sec for now.
3304                 MOVEM A,XBORTT(I)
3305                 SETZM XBORTC(I)         ; Clear count of retries.
3306                 JRST .+1]
3307         TRCPKT R,"TSOSND Pkt w/seq space added to retransmit queue"
3308         MOVEI A,(R)                     ; Arg to PKQPL, A/ PE ptr
3309         MOVEI Q,XBORTQ(I)               ; Arg to PKQPL, Q/ queue hdr ptr
3310         CALL PKQPL(PK.TCP)              ; Put on TCP retrans queue
3311         AOS XBORTL(I)                   ; Bump count of segs on queue
3312
3313 TSOSN8: CALL IPKSND                     ; Put on IP output queue
3314         RET
3315 \f
3316 SUBTTL TCP Retransmit and Timeout
3317
3318 Comment |
3319         The following things in TCP need some sort of timeout:
3320         Retransmit output segment if not ACKed (removed) within RT sec
3321         Timeout to abort connection if retransmission fails for UT sec
3322         Timeout to ACK incoming data (ie avoid ACKing immediately,
3323                 wait for more output or input).
3324         Timeout during TIME-WAIT to flush connection.
3325 |
3326
3327 ; TCPCLK - This routine is called by 1/2-sec "slow" clock.  What it has to do
3328 ;       is scan all active TCB's for the following conditions:
3329 ;       (1) Retransmit timeout has expired, must resend something.
3330 ;               or TIME-WAIT timeout has expired.
3331 ;       (2) An ACK must be sent, either by sending the current output
3332 ;               buffer, or by generating an ACK without data.
3333
3334 EBLK
3335 TCLKRC: 0               ; Count of segs compacted in pass over a retrans Q
3336 BBLK
3337
3338 TCPCLK: SKIPN TCPUP             ; Do nothing if turned off.
3339          RET
3340         MOVSI I,-XBL
3341         CONO PI,NETOFF
3342         SKIPA A,TIME
3343 TCLK05:  SKIPA A,TIME
3344
3345 TCLK10: SKIPN B,XBSTAT(I)
3346          JRST TCLK15
3347         SKIPE C,XBORTT(I)
3348          CAMG A,C
3349           CAIA
3350            JRST TCLK20          ; Retrans timeout
3351 TCLK12: TLNE B,(TH%CTL+%XBNOW)  ; Any flags set?
3352          JRST TCLK50            ; Wants ACK sent
3353 TCLK15: AOBJN I,TCLK10
3354         CONO PI,NETON
3355         RET
3356 TCLK16: MOVE A,TIME
3357         AOBJN I,TCLK10
3358         CONO PI,NETON
3359         RET
3360
3361         ; Come here for timeout of some sort.
3362 TCLK20: SKIPE XBORTQ(I)         ; If a retrans queue exists,
3363          JRST TCLK22            ; then assume it was a retrans timeout.
3364         MOVEI C,(B)             ; No retrans Q, probably a TIME-WAIT one?
3365         CAIN C,.XSTMW           ; State TIME-WAIT?
3366          JRST [ METER("TCP: Time-Wait timeout")
3367                 CALL TXBFLP     ; Flush the TCB completely, PI level
3368                 JRST TCLK16]
3369         CAIN C,.XSSYQ           ; State SYN-QUEUED?
3370          JRST [ METER("TCP: SYQ timeout")
3371                 CALL TSISQF     ; Flush the queued SYN.
3372                 JRST TCLK16]
3373         CAIN C,.XSFN2           ; State FIN-WAIT-2?
3374          JRST TCLK21
3375         METER("TCP: Random timeout")    ; Sigh.
3376         SETZM XBORTT(I)                 ; Flush whatever it was.
3377         JRST TCLK16
3378
3379 TCLK21: METER("TCP: FN2 timeout")
3380         CALL TXBFLP     ; Flush the TCB completely, PI level
3381         SKIPE XBUSER(I) ; Shouldn't still have anything open.
3382          BUG CHECK,[TCP: FN2 timo with active user]
3383         JRST TCLK16
3384
3385 TCLK22: METER("TCP: Retrans")
3386         AOS C,XBORTC(I)         ; Retrans timeout.  Send it again.
3387         SKIPE D,XBORTP(I)       ; Has user set any retrans params?
3388          JRST [ JRST TCLK25]    ; Yes! For now, non-Z means skip abort check.
3389         CAILE C,%TCPMR          ; Tried too many times?
3390          JRST TCLK80            ; Ugh, abort the connection!
3391         SKIPN R,XBORTQ(I)
3392          JRST [ SETZM XBORTT(I) ; If nothing on queue,
3393                 JRST TCLK12]    ; just reset the timeout to nothing.
3394         SKIPGE A,PK.FLG(R)      ; Ensure that packet isn't being output now
3395          JRST TCLK25            ; Still being output??  Reset timeout.
3396         ; Note that we don't check to see whether segment has already
3397         ; been transmitted, on the theory that compaction is going to
3398         ; pay off anyway.
3399         HLRZ W,PK.IP(R)
3400         HLRZ H,PK.TCP(R)
3401         SETZM TCLKRC            ; Clear compaction count.
3402
3403         ; Looks like we have to retransmit.  Try to compact up as much
3404         ; stuff as possible into a single segment; this gets a bit
3405         ; hairy.  Note that we compact as much as we can, ignoring the
3406         ; %PKPIL and %PKODN bits (except for setting the appropriate flush
3407         ; flags).
3408         TRCPKT R,"TCLK30 Segment being retransmitted"
3409 TCLK30: HRRZ J,PK.TCP(R)        ; Get pointer to succeeding segment
3410         JUMPE J,TCLK39          ; If none following, can't compact (ignore
3411                                 ; possibility of adding XBOCOS for now)
3412         LDB B,[PK$TDO (R)]      ; Get 1st offset
3413         LDB C,[PK$TDL (R)]      ; Get 1st length
3414         LDB T,[PK$TDL (J)]      ; Get 2nd length
3415         ADDI B,(C)              ; Find offset to end of 1st data
3416         MOVEI D,(B)
3417         ADDI D,(T)              ; Find total length after compaction
3418         CAILE D,576.-<5*4>      ; Hack hack hack!  Limit to 556. so std
3419                                 ; IP datagram is limited to 576.
3420          JRST TCLK39            ; If too big, don't compact.
3421
3422         ; Compact two segments into one!
3423         ; R/ 1st seg    D/ offset to end of data
3424         ; J/ 2nd seg    T/ len of 2nd data
3425         METER("TCP: Retrans compact")
3426         TRCPKT J,"TCLK30 Segment being compacted into previous seg for rexmit"
3427         ADDI C,(T)              ; Get new # bytes for 1st seg
3428         DPB C,[PK$TDL (R)]      ; Store it in advance.
3429 ;       HLRZ D,PK.TCP(R)        ; Find addr of TCP header in 1st seg
3430         MOVEI D,(H)
3431         IDIVI B,4
3432         ADDI D,(B)              ; Get addr for BP to end of data
3433         HRL D,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
3434         LDB B,[PK$TDO (J)]      ; Get data offset for 2nd seg
3435         IDIVI B,4
3436         HLRZ A,PK.TCP(J)        ; Get addr for BP to start of 2nd data
3437         ADDI B,(A)
3438         HRL B,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
3439         ; B/ BP to 2nd data
3440         ; D/ BP to end of 1st data
3441         ; T/ # bytes of 2nd data
3442         LDB A,[IP$TOL (W)]      ; Get current length of whole datagram
3443         ADDI A,(T)              ; Increment by length of added stuff
3444         DPB A,[IP$TOL (W)]      ; Store back
3445         ADDI A,3
3446         LSH A,-2
3447         HRLM A,PK.BUF(R)        ; Set up new count of # words in datagram.
3448 TCLK32: ILDB C,B
3449         IDPB C,D
3450         SOJG T,TCLK32
3451
3452         ; Data copied over, now update flags and stuff.
3453         HLRZ D,PK.TCP(J)
3454         MOVE A,TH$CTL(D)        ; Get flags for 2nd seg
3455         AND A,[TH%CTL]          ; Mask off just flags
3456         IORM A,TH$CTL(H)        ; Add them to flags for 1st seg
3457         TLNE A,(TC%URG)         ; If URGENT bit set,
3458          JRST [ LDB B,[TH$UP (D)]       ; Get pointer from 2nd seg
3459                 LDB C,[PK$TDL (R)]      ; Sigh, get new len of 1st seg
3460                 ADDI B,(C)              ; Adjust for bytes in front
3461                 LDB C,[PK$TDL (J)]      ; But have to subtract length
3462                 SUBI B,(C)              ; of 2nd seg (already in 1st len)
3463                 DPB B,[TH$UP (H)]       ; Store ptr back in 1st seg
3464                 JRST .+1]
3465
3466         ; Compaction done!  Now have to remove 2nd seg from queue.
3467         HRRZ B,PK.TCP(J)        ; Get pointer to 3rd seg
3468         HRRM B,PK.TCP(R)        ; Point 1st at it
3469         CAIN B,                 ; If 2nd was the last one,
3470          HRLM R,XBORTQ(I)       ; must update "last" ptr in queue header.
3471         MOVE A,PK.FLG(J)        ; Get flags
3472 IFN PK.TCP-2,.ERR %PQFL flag must match PK.TCP
3473         TLZ A,(%PQFL2)          ; Say it's off the TCP list, to allow
3474                                 ; flushing from IP queue.
3475         TLO A,(%PKFLS)          ; In fact, require it
3476         MOVEM A,PK.FLG(J)       ; Store flags back
3477         JUMPGE A,[MOVEI A,(J)   ; If not locked by PI output,
3478                 TRCPKT A,"TCLK32 Seg flushed from rexmit by compaction"
3479                 CALL PKTRT      ; try to flush it now.
3480                 JRST .+1]
3481         SOSGE XBORTL(I)         ; Decrement count of retrans queue segs
3482          BUG HALT
3483         AOS TCLKRC              ; Bump count of recompacts done
3484         JRST TCLK30             ; OK, try to recompact next seg!
3485
3486         ; Note one possible problem with following code; although
3487         ; the segment being re-trans'd is given latest poop (ACK, WND),
3488         ; the ones following are not.  This is usually OK as we assume
3489         ; that following segs have actually been sent out, but if it
3490         ; happens that they HAVEN'T (i.e. %PKODN not set) then their
3491         ; info is going to be a little out of date.  This shouldn't
3492         ; screw things too much, however.
3493 TCLK39: MOVE D,XBRNXT(I)        ; Get latest ACK value
3494         LSH D,4
3495         MOVEM D,TH$ACK(H)       ; Set it
3496         MOVE D,XBRWND(I)        ; And latest window
3497         DPB D,[TH$WND (H)]
3498         CALL THCKSI             ; Compute checksum for it (note not THCKSM)
3499         DPB A,[TH$CKS (H)]
3500         SKIPE TCLKRC            ; Was any recompaction done?
3501          CALL IPKHD2            ; Yes, must recompute IP header (checksum etc)
3502         MOVE A,PK.FLG(R)
3503         TLNN A,(%PKODN)         ; Has segment already been tried once?
3504          JRST [         ; No, don't put on output queue twice!!
3505                 TRCPKT R,"TCLK39 Rexmit skipped because seg not yet output"
3506                 METER("TCP: Pretrans compact")
3507                 JRST TCLK25]
3508         TLO A,(%PKRTR)          ; Set flag saying this is a retransmit
3509         MOVEM A,PK.FLG(R)
3510         MOVEI A,(R)
3511         CALL IPKSNQ             ; Put back on IP output queue
3512                                 ; Note PK.BUF shd still be set up right.
3513 TCLK25: MOVE A,TIME
3514         HRRZ B,XBORTP(I)        ; If RH set, use it for new timeout.
3515         CAIN B,
3516          MOVE B,TCPTMO          ; Use timeout default.
3517         ADD B,A
3518         MOVEM B,XBORTT(I)
3519         JRST TCLK79
3520
3521         ; Here when need to send an ACK.  First see if we can
3522         ; make use of existing output buffer.
3523 TCLK50: METER("TCP: slow ACKs")
3524         TLNE B,(TC%SYN+TC%RST)
3525          BUG CHECK,[TCP: SYN or RST set in XBSTAT clock req]
3526         SKIPE R,XBOCOS(I)       ; Ensure there is one.
3527          TLNE B,(%XBMPL)        ; and that it isn't locked.
3528           JRST TCLK60           ; Sigh, can't use it.
3529
3530         ; There is an output buffer, and it's not locked, so use that
3531         ; to send stuff out!
3532         TRCPKT R,"TCLK50 COS used to send clock level ACK"
3533         MOVSI T,(TC%PSH)
3534         CALL TCPOFR             ; Force it out.
3535         JRST TCLK16
3536
3537         ; Come here when we have to generate a new segment for ACK.
3538 TCLK60: TLNN B,(%XBNOW)         ; Insisting that we ACK?
3539          JRST TCLK65            ; No, can semi-punt.
3540         CALL PKTGFI             ; Get buffer
3541          JRST TCLK65            ; and forget about ACKing if we cant get one
3542         METER("TCP: Clk ACK")
3543         MOVEI R,(A)
3544         MOVE T,B                ; Use request flags in segment.
3545         TRCPKT R,"TCLK60 Alloc and send ACK from clock level"
3546         CALL TSOSNR             ; Send a simple ACK
3547         JRST TCLK16
3548
3549 TCLK65: MOVSI A,(%XBNOW)        ; No, so just set insist flag
3550         IORM A,XBSTAT(I)        ; and wait a bit longer.
3551         JRST TCLK16
3552
3553 TCLK79:
3554         JRST TCLK16
3555
3556         ; Abort the connection, timed out.
3557 TCLK80: METER("TCP: Timeout abort")
3558         CALL TXBFLP             ; This is pretty drastic... flush, PI level.
3559         MOVEI T,.XCINC          ; Say "incomplete transmission"
3560         CALL TCPUC              ; as close reason.
3561         JRST TCLK16
3562
3563 TCLK90: CONO PI,NETON
3564         RET
3565
3566 \f
3567 ; Checksum cruft.
3568
3569 ; THCKSM - Figures TCP segment checksum, IP$TOL has TCP segment length.
3570 ; THCKSI - Figures TCP segment checksum, IP$TOL has IP header plus TCP seg.
3571 ;       W/ addr of IP header
3572 ;       H/ addr of TCP header
3573 ;       Note that the following out-of-TCP values are looked up
3574 ;       from the IP header in order to compute sum for the "pseudo header".
3575 ;               IP$SRC - source host
3576 ;               IP$DST - dest host
3577 ;               IP$TOL - # octets in TCP segment (plus IP header)
3578 ;       Finally,
3579 ;               %PTCTC - Assumed value
3580 ;       
3581 ; Clobbers B,C,D,E
3582 ; Returns
3583 ;       A/ checksum
3584 ;       TT/ Total # bytes in TCP segment
3585
3586 THCKSM: TDZA C,C                ; Compute as if IHL=0
3587 THCKSI:  MOVNI C,5*4
3588         ; First compute pseudo header
3589         LDB A,[IP$SRC (W)]      ; Source addr
3590         LDB B,[IP$DST (W)]      ; Dest addr
3591         ADD A,B
3592         ADDI A,%PTCTC           ; Add TCP protocol number
3593         LDB TT,[IP$TOL (W)]     ; Get total length in octets
3594         JUMPE C,THCKS2
3595         LDB B,[IP$IHL (W)]      ; Find IP header length in 32-bit wds
3596         LSH B,2                 ; mult by 4 to get # octets
3597         SUBI TT,(B)             ; Find # octets of IP data (TCP segment)
3598 THCKS2: ADDI A,(TT)             ; Add in.
3599         MOVEI C,-<5*4>(TT)      ; Get # bytes in segment after 1st 5 wds
3600
3601         ; Done with pseudo header (not folded yet, though).
3602         LDB B,[044000,,0(H)]    ; Get wd 0 (src/dest)
3603         ADD A,B
3604         LDB B,[TH$SEQ (H)]      ; Get wd 1 (seqno)
3605         ADD A,B
3606         LDB B,[TH$ACK (H)]      ; wd 2
3607         ADD A,B
3608         LDB B,[044000,,3(H)]    ; wd 3
3609         ADD A,B
3610         LDB B,[TH$UP (H)]       ; wd 4 (part of)
3611         ADDI A,(B)
3612
3613         LSHC A,-16.
3614         LSH B,-<16.+4>
3615         ADDI A,(B)              ; Now have it folded up.
3616         JUMPLE C,THCKS7         ; If nothing more, can leave now.
3617         MOVEI E,5(H)
3618         HRLI E,442000           ; Set up 16-bit byte ptr to options/data
3619         LSHC C,-1
3620         JUMPLE C,THCKS6
3621 THCKS5: ILDB B,E
3622         ADDI A,(B)
3623         SOJG C,THCKS5
3624 THCKS6: JUMPL D,[               ; Jump if odd byte left.
3625                 ILDB B,E        ; get it
3626                 ANDCMI B,377    ; mask off low (unused) byte.
3627                 ADDI A,(B)      
3628                 JRST .+1]
3629 %CKMSK==<-1#177777>             ; Mask for stuff above 16 bits
3630 THCKS7: TDNE A,[%CKMSK]         ; If any carries, add them in.
3631          JRST [ LDB B,[.BP %CKMSK,A]
3632                 TDZ A,[%CKMSK]
3633                 ADD A,B
3634                 JRST THCKS7]
3635         ANDCAI A,177777         ; Complement sum and mask off.
3636         RET
3637
3638 \f
3639 MTRCOD          ; Last stuff -- expand meter tables.
3640 TRCCOD          ; Expand trace tables