Consolidate license copies
[its.git] / system / tcp.273
1 ;;; Copyright (c) 1999 Massachusetts Institute of Technology
2 ;;;
3 ;;; This program is free software; you can redistribute it and/or
4 ;;; modify it under the terms of the GNU General Public License as
5 ;;; published by the Free Software Foundation; either version 3 of the
6 ;;; License, or (at your option) any later version.
7 ;;;
8 ;;; This program is distributed in the hope that it will be useful,
9 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
10 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
11 ;;; General Public License for more details.
12 ;;;
13 ;;; You should have received a copy of the GNU General Public License
14 ;;; along with this program; if not, write to the Free Software
15 ;;; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
16
17 ; 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                 TLZ T,(%PKNOF)  ; and just in case, turn don't-free flag off.
878                 MOVEM T,PK.FLG(A)
879                 CONO PI,PION
880                 TRCPKT A,"PKPFL3 Packet not flushed"
881                 JRST PKPFL4]
882         CONO PI,PION
883         CALL PKTRT
884 PKPFL4: SOSGE XBORTL(I)
885          BUG CHECK,[TCP: Retrans Q count err]
886         JRST PKPFL3
887 \f
888 SUBTTL TCP Main Program Input
889
890 ; All TCP input segments for a connection are put on a queue that
891 ; is headed at XBITQH.  When this header is zero, there is no more
892 ; input; if the %XBFIN flag is also set, the remote host has closed
893 ; its transmit side and there will never be any more input.
894 ;       Segments are only added by PI level, at the end of the queue.
895 ;       Segments are only removed by MP level IOTs, at the start of the queue.
896 ; (An incoming RST will of course flush the queue at PI level)
897
898 ; If XBIBP is non-zero, it points into the first segment on the input queue,
899 ; and XBIBC is also valid; things are ready for MP IOTing.
900 ; However, neither XBIBP nor XBIBC is meaningful if XBITQH is zero.
901
902 ; Input IOT - from IOTTB
903         SKIPA T,[SIOKT]         ; Come here for SIOT entry
904 TCPI:    MOVEI T,CHRKT
905         METER("TCP: syscal in")
906         HLRZ I,(R)              ; Get TCB index
907         
908         ; Verify state, do misc setup for reading
909         MOVSI B,(XB%STY)
910         TDNE B,XBUSER(I)        ; Can't IOT if direct-connected to STY.
911          JRST IOCR10            ; "Chan in illegal mode"
912         HLRZ B,XBSTAU(I)        ; Just reading state, don't need NETOFF.
913         SKIPG TCPTBI(B)         ; Ensure meta-state allows reading.
914          JRST [ HLRZ B,XBCLSU(I)        ; Can't read, see if reason OK
915                 CAIN B,.XCFRN           ; Only OK reason is clean fgn close.
916                  JRST UNIEOF            ; Yeah, just return quietly.
917                 JRST IOCR10]
918
919         MOVE E,[441000,,4]      ; 8-bit bytes, 4 to a word
920         MOVEI B,[
921             XBIBP(I)    ; Byte pointer
922             XBIBC(I)    ; # bytes to read
923             TCPIBG      ; Routine to get next buffer
924             TCPIBD      ; Routine to discard buffer
925             0           ; not used
926             TRNA        ; Negative - TCPIBG and TCPIBD will do waiting.
927                 ]
928         CALL (T)
929          CAIA
930           AOS (P)
931         SKIPG XBIBC(I)  ; If count for this buffer reached zero,
932          CALL TCPIBD    ; Flush it so XBITQH is valid indication of input avail
933         RET
934
935 ; TCPIBD - Discard input buffer, invoked by I/O.
936 ;       This is always called before TCPIBG is.
937
938 TCPIBD: SKIPN XBIBP(I)          ; Make sure something's there to discard.
939          RET                    ; Nope, gone or was never set up.
940         MOVEI Q,XBITQH(I)       ; Point to TCP input queue header
941         CALL PKQGF(PK.TCP)      ; Get first thing off queue, into A
942         CAIN A,                 ; Something better be there.
943          BUG HALT,[TCP: IOTI queue lost]
944
945         ; Check BP just out of sheer paranoia.
946         HRRZ T,XBIBP(I)         ; Find addr BP points to (maybe +1 actual)
947         HLRZ Q,PK.TCP(A)        ; Get addr of TCP header
948         CAIL Q,(T)              ; Header better be less than BP!
949          JRST TCPIB2
950         TRZ Q,PKBSIZ-1          ; Get addr of start of buffer
951         CAILE T,PKBSIZ(Q)       ; BP should be within or just past end.
952 TCPIB2:  BUG HALT,[TCP: IOTI BP incons]
953
954         ; Okay, end of paranoia, just flush the buffer.
955         LDB T,[PK$TDL (A)]      ; Find # chars we read
956         MOVN T,T
957         ADDM T,XBINBS(I)        ; Update # chars avail for input.
958         CALL PKTRT              ; Return packet to freelist.
959         SOSGE T,XBINPS(I)       ; Decrement count of segs on input queue
960          BUG CHECK,[TCP: Input Q count incons]
961         CAIL T,%TCPMI/2         ; If we are now handling past 50% input,
962          JRST [ MOVSI T,(TC%ACK)        ; Make sure we send an ACK
963                 IORM T,XBSTAT(I)        ; so new rcv window is reported.
964                 JRST .+1]
965         CONO PI,NETOFF
966         CALL TCPRWS             ; Set new receive window
967         CALL TXBIST             ; Get new input chan state
968         HRLM T,XBSTAU(I)        ; Set it.  Note interrupt is avoided here.
969         CONO PI,NETON
970         SETZM XBIBP(I)
971         SETZM XBIBC(I)
972         RET             ; Always return with simple POPJ
973
974 TCPRWS: MOVEI T,%TCPMI
975         SUB T,XBINPS(I)         ; Find # segs we can still queue up
976         CAIGE T,1               ; If no full segs left,
977          TDZA T,T               ; Zero the window, no more segs allowed
978           IMUL T,XBRMSS(I)      ; Else will take N * MSS bytes
979 TCPRW3: MOVEM T,XBRWND(I)
980         RET
981
982 IFN 0,[
983         ; This code turns out to lose because the code at TCPIS only
984         ; checks XBRWND to see whether to compact input or not, and as
985         ; long as XBRWND is non-zero, stuff will always be added to queue,
986         ; using up all the packet buffers.
987         ; Basically it's a question of whether or not to allow more input,
988         ; up to limits of last queued buffer, if the queue has too many
989         ; buffers on it.  Metering will show whether most other implementations
990         ; win or lose with our buffer-alloc type windowing.
991 TCPRW2: HLRZ Q,XBITQH(I)        ; Find # chars room in last seg
992         LDB T,[PK$TDL (Q)]
993         LDB Q,[PK$TDO (Q)]
994         ADDI Q,(T)
995         MOVEI T,576.
996         SUBI T,(Q)
997         CAIGE T,
998          SETZ T,
999         MOVEM T,XBRWND(I)
1000         RET
1001 ]
1002
1003 ; TCPIBG - Get new input buffer (invoked by I/O, after TCPIBD)
1004 ; Return .+1 if can't get new buffer, must wait (Never, we do waiting)
1005 ; Return .+2 if OK, new BP and count set up.
1006 ; Return .+3 if "EOF", transfer complete
1007
1008 TCPIBG: SKIPE XBIBP(I)  ; Shouldn't be anything already there.
1009          BUG HALT,[TCP: IOTI buf incons]
1010 TCPIB3: SKIPN A,XBITQH(I)       ; See if anything in input queue
1011          JRST TCPIB5            ; No, go handle EOF.
1012         LDB T,[PK$TDL (A)]      ; Find # bytes input for this segment
1013         CAIN T,                 ; Something probably shd be there.
1014          BUG HALT,[TCP: IOTI null seg]
1015         MOVEM T,XBIBC(I)        ; Store as new # bytes
1016         LDB T,[PK$TDO (A)]      ; Get offset from start of header
1017         HLRZ Q,PK.TCP(A)        ; Get addr of TCP header
1018         ROT T,-2                ; Divide offset by 4
1019         ADDI Q,(T)              ; Point to right word
1020         LSH T,-34.              ; Right-justify the low 2 bits
1021         HRL Q,(T)[441000 ? 341000 ? 241000 ? 141000]    ; Get right LH for BP
1022         MOVEM Q,XBIBP(I)        ; Now store BP!
1023         JRST POPJ1              ; Say ready to go again...
1024
1025         ; No input available.  First check to see if there will ever
1026         ; be any more (FIN seen?), then whether to return right away or
1027         ; hang.
1028 TCPIB5: CONO PI,NETOFF          ; Avoid timing inconsistencies
1029         SKIPE A,XBITQH(I)       ; Check again
1030          JRST [ CONO PI,NETON   ; Got some??
1031                 JRST TCPIB3]    ; Try again.
1032         SKIPN XBINPS(I)         ; No, should also have no segments
1033          SKIPE XBINBS(I)        ; and no bytes
1034           BUG HALT,[TCP: IOTI count incons]
1035         MOVE A,XBRWND(I)        ; Save value of rcv window
1036         CALL TCPRWS             ; Then reset the window
1037         CAME A,XBRWND(I)        ; Was previous value correct?
1038          METER("TCP: RCV.WND out of synch")
1039         MOVE T,XBSTAT(I)        ; Get flags
1040         CONO PI,NETON
1041         TLNE T,(%XBFIN)         ; FIN seen, and input queue empty?
1042          JRST TCPIB6            ; Yes, true EOF now.
1043
1044         MOVE T,CTLBTS(U)        ; See if call had "don't-hang" bit set
1045         TRNE T,10
1046          JRST TCPIB7            ; No, return EOF.
1047         SKIPN XBITQH(I)         ; Wait until input queue has something.
1048          CALL UFLS              
1049         JRST TCPIBG             ; Then call again.
1050
1051 TCPIB6:
1052 TCPIB7: CALL TCPUSI             ; Adjust user state.
1053         JRST POPJ2              ; and return "EOF"
1054
1055 \f
1056 SUBTTL TCP Main Program Output
1057
1058 ; Output IOT - from IOTTB
1059 ; Output segments are chained together from XBORTQ, which is
1060 ; the "retransmit queue".
1061 ; The queue only contains segments which occupy sequence space, since
1062 ; these are the only ones which require ACKs and possible retransmit.
1063 ; All others are sent directly to the IP output queue.
1064 ; While the transmit connection is open,
1065 ;       Segments are only added by MP level IOTs, at the end of the queue.
1066 ;       Segments are only removed by PI level ACKs, at the start of the queue.
1067
1068 ; Main program I/O is done into the "Current Output Segment", which is NOT
1069 ; on the retransmit queue.  There are three variables related to this COS.
1070 ;       XBOCOS - <original # bytes XBOBC started with>,,<PE ptr to COS>
1071 ;       XBOBP - BP into the COS, for MP IOT writing.
1072 ;       XBOBC - Count of # bytes left that MP IOT can deposit into.
1073 ; Note that the maximum possible size of the buffer is kept in PK$TDL
1074 ; (TCP segment Data Length).  For windowing reasons it may be necessary
1075 ; to restrict the amount of space actually used, thus the initial value
1076 ; of XBOBC may be less than PK$TDL.  This is why the initial value is also
1077 ; copied into the RH of XBOCOS, so that when XBOBC counts out we know
1078 ; exactly how much of the buffer was actually used.  It is possible for
1079 ; XBOBC to be increased by interrupt level window processing, in order
1080 ; to increase utilization of the buffer.
1081 ; States:
1082 ;       If XBOCOS is zero, XBOBP and XBOBC must also be zero; there is
1083 ;               no COS.
1084 ;       If XBOCOS is non-zero (a current output seg exists), then:
1085 ;               if LH(XBOCOS) is zero, the segment hasn't yet been written
1086 ;                       into, and needs to be set up.
1087 ;                       XBOBP and XBOBC should be zero!
1088 ;               else the segment is set up for writing.  XBOBP should be set!
1089 ;                       If XBOBC is zero it means the segment now contains
1090 ;                       LH(XBOCOS) bytes of data.  If this number is less
1091 ;                       than PK$TDL (max possible seg data) then the count
1092 ;                       may be reset to allow further output into this
1093 ;                       segment, or it may simply be sent as is.
1094 ;
1095 ; The current segment is put on the retransmit queue (and IP output queue)
1096 ; when:
1097 ;       PI level (eg clock) decides it's time to send an ACK or do a FORCE.
1098 ;       MP level IOT fills up the segment completely.
1099 ;       MP level FORCE or CLOSE is invoked.
1100 ; The current segment is locked down during MP IOT, to keep PI level
1101 ; from ripping it away (which would leave entrails dangling).
1102 ; PCLSR'ing will clear this lock.  If TCP flushes the TCB at PI level
1103 ; for some reason, XBOCOS will be freed unless locked.  XBOBC and XBOBP
1104 ; will still be cleared even if locked, so as to cause a call to TCPOBW
1105 ; which will notice the condition and free the COS itself.
1106
1107         SKIPA A,[SIOKT]         ; Come here for SIOT entry
1108 TCPW:    MOVEI A,CHRKT
1109         METER("TCP: syscal out")
1110         HLRZ I,(R)              ; Get TCB index from IOCHNM wd
1111
1112         ; Verify state, do misc setup for writing, lock segment.
1113         CONO PI,NETOFF
1114         HRRZ B,XBSTAU(I)        ; Get output chan state
1115         SKIPG TCPTBO(B)         ; See if meta-state allows writing
1116          JRST IOCR10            ; Can't, say "chan not open" (ugh)
1117         MOVSI B,(XB%STY)
1118         TDNE B,XBUSER(I)        ; Also can't if direct-connected to STY.
1119          JRST IOCR10
1120         MOVSI B,(%XBMPL)        ; Set locked flag (must be sign bit!)
1121         IORM B,XBSTAT(I)
1122         CONO PI,NETON           ; Okay, we've got it.
1123         CALL SGNSET             ; Set PCLSR routine to unlock flag.
1124             XBSTAT(I)
1125         SKIPN XBOCOS(I)         ; If no COS there,
1126          SETZM XBOBC(I)         ; make SURE count is zapped so refill invoked.
1127         MOVE E,[441000,,4]      ; 8-bit bytes, 4 to a word
1128         MOVEI B,[
1129                 SETZ XBOBP(I)   ; Output BP found here (sign sez is output)
1130                 XBOBC(I)        ; # bytes of room remaining
1131                 TCPOBG          ; Routine to get another buffer (not used)
1132                 TCPOBW          ; Buffer full, routine to send it.
1133                 0               ; Not used
1134                 TRNA]           ; Negative - TCPOBG and TCPOBW will do waiting.
1135         CALL (A)
1136          CAIA
1137           AOS (P)               ; Pass on a skip return.
1138
1139         ; User IOT is done, now unlock the segment.
1140         ; We also check for wanting to do an immediate ACK and if needed
1141         ; ship out the current buffer right now, without waiting
1142         ; for the 1/2-sec clock to do it.
1143         SKIPN A,XBSTAT(I)       ; See if XBSTAT is still set
1144          JRST IOCR10            ; No, take IOC error return!
1145         CAIL A,                 ; It better still be locked!
1146          BUG CHECK,[TCP: Output not locked]
1147         CALL LSWPOP             ; Clear the lock flag
1148         TLNN A,(%XBNOW)         ; Was "immediate-send" flag set?
1149          RET                    ; Nope, can just return.
1150         METER("TCP: TCPW exit force")
1151         CONO PI,NETOFF
1152         MOVSI T,(TC%PSH)        ; Hmm, set up and shove out.
1153         CALL TCPOFR             ; and force out current output segment.
1154         CONO PI,NETON
1155         RET
1156
1157 TCPOBG: BUG CHECK,[TCP: IOT called wrong rtn (TCPOBG)]
1158         AOS (P)         ; If proceeded, can still win.  Make skip return
1159                         ; and drop through to TCPOBW.
1160
1161 ; TCPOBW - Write/Get output buffer, invoked by SIOKT/CHRKT when the
1162 ;       buffer count (XBOBC) is zero.  This routine can figure out
1163 ;       whether it needs to ship out a full buffer, or get a new
1164 ;       output buffer, or both.  Always returns with XBOBP and
1165 ;       XBOBC set up for additional output (otherwise it hangs and
1166 ;       can be PCLSR'd)
1167
1168 TCPOBW: SKIPE R,XBOCOS(I)       ; Get PE ptr to COS
1169          JRST [ HLRZ A,R        ; Got a COS, see if already set up
1170                 JUMPN A,TCPOB5  ; Jump if so.
1171                 JRST TCPOB2]    ; Else must set it up.
1172
1173         ; No current segment, must get a new one.
1174         HRRZ T,XBSTAU(I)        ; First ensure output state is OK.
1175         SKIPG TCPTBO(T)         ; Skip if still OK to output.
1176          JRST IOCR10            ; Blooie, say "Chan not open".
1177         CALL PKTGF              ; Get one, hang until we succeed.
1178         MOVEI R,(A)             ; Set up in std AC
1179         TRCPKT R,"TCPOBW Alloc for IOT output buffer"
1180         HRRZM R,XBOCOS(I)       ; Store ptr
1181
1182         ; Set up segment for IOT to deposit into.
1183 TCPOB2: MOVEI T,%TCPMO          ; Get max # segments allowed on queue
1184         CAMG T,XBORTL(I)        ; Hang until we have less than this.
1185          CALL UFLS              ; Note that conn closure will unhang too,
1186                                 ; because it flushes output queue.
1187         CALL TSOINI             ; Initialize the segment (set up W, H)
1188         LDB A,[PK$TDO (R)]      ; Find offset data should start at.
1189         TRNE A,3
1190          BUG HALT               ; Should always start at wd boundary!
1191         LSH A,-2                ; Find # words
1192         ADDI A,(H)              ; Add address of TCP header,
1193         HRLI A,441000           ; and now we have our initial BP.
1194         MOVEM A,XBOBP(I)        ; Set it up.
1195         LDB A,[PK$TDL (R)]      ; Get max length avail in this segment
1196
1197         ; Now have a fresh buffer and nothing else to wait for.
1198         ; Freeze the world, make sure it's still OK to output, and find
1199         ; out how big an output segment we can allow.
1200 TCPOB4: CONO PI,NETOFF
1201         HRRZ T,XBSTAU(I)        ; Still OK to output?  Check again.
1202         SKIPG TCPTBO(T)
1203          JRST [ MOVEI A,(R)     ; Bah, must return buffer.
1204                 CALL PKTRTA
1205                 SETZM XBOCOS(I)
1206                 CONO PI,NETON
1207                 JRST IOCR10]    ; Barf "Chan not open".
1208         MOVEI T,(I)             ; Get index in T for PCLSRing.
1209         CALL TCPOB9             ; Check available window
1210          JRST [ CONO PI,NETON   ; Window too small, allow ints
1211                 CALL TCPOB9
1212                  CALL UFLS
1213                 JRST TCPOB4]    ; Big enough, go back and re-try stuff.
1214         LDB Q,[PK$TDL (R)]      ; Get max # bytes available
1215         CAMLE Q,XBSAVW(I)       ; Greater than window?
1216          MOVE Q,XBSAVW(I)       ; Yeah, truncate down to this size.
1217         HRLM Q,XBOCOS(I)        ; Store original # bytes in LH of XBOCOS
1218         MOVEM Q,XBOBC(I)
1219         CONO PI,NETON
1220         RET                     ; Okay, all set up, return.
1221
1222 TCPOB9: MOVE A,XBSWND(T)
1223         LSH A,-2                ; Get 25% offered window
1224         CAML A,XBSAVW(T)        ; If 25% offered > avail window,
1225          RET                    ; punt and wait for better stuff.
1226         JRST POPJ1
1227
1228         ; Here when we were all set up, and output has used up all
1229         ; of the buffer space initially available.  Check to make sure
1230         ; there isn't more we can fill out, and if not then fire off
1231         ; the segment.
1232 TCPOB5: HLRZ T,XBOCOS(I)        ; Get # bytes we originally had
1233         CONO PI,NETOFF          ; Avoid magic changes in send window
1234         CAML T,XBSAVW(I)        
1235          JRST TCPOB6            ; Send window same or smaller (!), send seg.
1236         MOVE Q,XBSAVW(I)        ; Send window is bigger!  Get new size
1237         LDB A,[PK$TDL (R)]      ; Get max size
1238         CAMLE A,Q
1239          MOVEI A,(Q)            ; Use minimum of max size and send window.
1240         MOVEI Q,(A)             ; Save result
1241         SUBI A,(T)              ; Find # more bytes we can hack
1242         CAIG A,                 ; If there's no more,
1243          JRST TCPOB6            ; Just send it off anyway.
1244         HRLM Q,XBOCOS(I)        ; Hurray, got more!  Store new original #
1245         MOVEM A,XBOBC(I)        ; And set up new count
1246         CONO PI,NETON
1247         RET                     ; And return happily.
1248
1249 TCPOB6: TRCPKT R,"TCPOB6 IOT Send"
1250         CALL TCPOB7
1251         JRST TCPOBW
1252
1253 TCPOB7: DPB T,[PK$TDL (R)]      ; Okay, say this many bytes of data are in seg
1254         PUSH P,B
1255         PUSH P,C
1256         PUSH P,E
1257         MOVSI T,(TC%PSH)        ; Ensure seg is pushed out.
1258         IORM T,XBSTAT(I)
1259         CALL TSOSND             ; Send data segment (# bytes in PK.TCI)
1260                                 ; This clobbers a lot of ACs!
1261         SETZM XBOCOS(I) ; No current output segment now.
1262         CONO PI,NETON
1263         SETZM XBOBP(I)
1264         SETZM XBOBC(I)
1265         POP P,E
1266         POP P,C
1267         POP P,B
1268         RET
1269
1270 ; TCPOFR - Force out partially-filled current output segment
1271 ;       Must have NETOFF.
1272 ;       Called by FORCE and CLOSE at MP level
1273 ;       by TCPCLK at PI clock level
1274 ;       Note that we try to never have stuff in the COS which would
1275 ;       over-run our send window, by hanging in MP IOT.  This will
1276 ;       be slightly screwed up if the receiver suddenly decreases the window
1277 ;       size, since this routine always sends the whole thing anyway,
1278 ;       but it's probably OK (helps avoid SWS)
1279 ;       I/ TCB index
1280 ;       T/ additional flags to use (PUSH, URG, FIN)
1281 ;       Clobbers R and everything that TSOSND does (a lot!)
1282
1283 TCPOFR: MOVE A,XBSTAT(I)        ; Get flags for connection
1284         TLNE A,(%XBCTL)         ; Wants anything added on?
1285          IOR T,A                ; Yes, OR the bits in.
1286         JUMPL A,TCPOF6          ; If locked at MP level, don't send it!
1287         SKIPN R,XBOCOS(I)       ; See if current output seg exists
1288          JRST TCPOF5            ; No, can't hack now.
1289         HLRZ TT,R               ; Get # bytes of original buffer size
1290         JUMPE TT,TCPOF5         ; If none, nothing to hack.
1291         SUB TT,XBOBC(I)         ; Subtract # left, to get # bytes data
1292         CAIG TT,
1293          JRST [ SETZ TT,        ; No data, see if a flag wants to be sent.
1294                 TLNN T,(TC%FIN+TC%ACK+TC%SYN)   ; Any of these are impt.
1295                  JRST TCPOF9    ; Nope, do nothing.
1296                 JRST .+1]       
1297         DPB TT,[PK$TDL (R)]     ; Store back # bytes of real data
1298         AND T,[TH%CTL]          ; Mask off the flags
1299         IORM T,XBSTAT(I)        ; Stuff in as requests
1300         TRCPKT R,"TCPOFR Force send"
1301         CALL TSOSND             ; Send out the stuff
1302         SETZM XBOCOS(I)
1303         SETZM XBOBP(I)
1304         SETZM XBOBC(I)
1305 TCPOF9: RET
1306
1307         ; No current output segment, so no data to send.  Check, though,
1308         ; to see if any flags need sending.
1309 TCPOF5: TLNN T,(TC%SYN+TC%ACK+TC%FIN)
1310          RET                    ; Nope, just return.
1311         MOVE E,T                ; They do!  Save em against smashage
1312         CALL PKTGFI             ; Try to get a buffer (clobbers T,Q)
1313          JRST TCPOF6            ; Ugh, failed, see about setting flags.
1314         MOVEI R,(A)
1315         TRCPKT R,"TCPOF5 Alloc and send flags only in TCPOFR"
1316         MOVE T,E                ; Restore flags
1317         CALL TSOSNR             ; Set up the packet and send it!
1318         RET
1319
1320         ; Can't get packet now, so set up the request flags for later hacking.
1321         ; Also comes here when current output seg is locked at MP level.
1322 TCPOF6: AND T,[%XBCTL]          ; Clear out extraneous bits
1323         TLO T,(%XBNOW)          ; Ask to send stuff immediately
1324         IORM T,XBSTAT(I)        ; and set flags back.
1325         RET
1326 \f
1327 ; TCPOSB - Routine similar to TCPOBW, except that it doesn't hang,
1328 ;       so that it is suitable for calling at PI level (by STYNTC esp)
1329 ; Returns .+1 if can't set up output buffer for writing.
1330 ; Returns .+2 if output buff is all set up, with non-zero XBOBC.
1331
1332 TCPOSB: SKIPE R,XBOCOS(I)
1333          JRST [ HLRZ A,R        ; Have COS, see if already set up
1334                 JUMPN A,TCPOS5  ; Jump if so.
1335                 JRST TCPOS2]    ; Else just set it up.
1336         
1337         ; No current segment, get a new one.
1338         HRRZ T,XBSTAU(I)        ; First ensure output state is OK.
1339         SKIPG TCPTBO(T)         ; Skip if still OK to output.
1340          RET                    ; Blooie.
1341         CALL PKTGFI             ; Get one, skip if successful
1342          RET                    ; Sigh...
1343         MOVEI R,(A)             ; Set up in std AC
1344         TRCPKT R,"TCPOSB Alloc for STYNET output data"
1345         HRRZM R,XBOCOS(I)       ; Store ptr
1346
1347         ; Set up segment for IOT to deposit into.
1348 TCPOS2: MOVEI T,%TCPMO          ; Get max # segments allowed on queue
1349         CAMG T,XBORTL(I)        ; Fail if we have more than this.
1350          RET
1351         CALL TSOINI             ; Initialize the segment (set up W, H)
1352         LDB A,[PK$TDO (R)]      ; Find offset data should start at.
1353         TRNE A,3
1354          BUG HALT               ; Should always start at wd boundary!
1355         LSH A,-2                ; Find # words
1356         ADDI A,(H)              ; Add address of TCP header,
1357         HRLI A,441000           ; and now we have our initial BP.
1358         MOVEM A,XBOBP(I)        ; Set it up.
1359         LDB A,[PK$TDL (R)]      ; Get max length avail in this segment
1360
1361         ; Now have a fresh buffer and nothing else to wait for.
1362         ; Freeze the world, make sure it's still OK to output, and find
1363         ; out how big an output segment we can allow.
1364 TCPOS4: CONO PI,NETOFF
1365         HRRZ T,XBSTAU(I)        ; Still OK to output?  Check again.
1366         SKIPG TCPTBO(T)
1367          JRST [ MOVEI A,(R)     ; Bah, must return buffer.
1368                 CALL PKTRTA
1369                 SETZM XBOCOS(I)
1370                 CONO PI,NETON
1371                 RET]            ; Barf "Chan not open".
1372         MOVEI T,(I)             ; Get index in T for testing (no PCLSR)
1373         CALL TCPOB9             ; Check available window
1374          JRST NETONJ            ; Window too small, just return
1375
1376         LDB Q,[PK$TDL (R)]      ; Get max # bytes available
1377         CAMLE Q,XBSAVW(I)       ; Greater than window?
1378          MOVE Q,XBSAVW(I)       ; Yeah, truncate down to this size.
1379         HRLM Q,XBOCOS(I)        ; Store original # bytes in LH of XBOCOS
1380         MOVEM Q,XBOBC(I)
1381         CONO PI,NETON
1382         AOS (P)
1383         RET                     ; Okay, all set up, return.
1384
1385         ; Here when we were all set up, and output has used up all
1386         ; of the buffer space initially available.  Check to make sure
1387         ; there isn't more we can fill out, and if not then fire off
1388         ; the segment.
1389 TCPOS5: HLRZ T,XBOCOS(I)        ; Get # bytes we originally had
1390         CONO PI,NETOFF          ; Avoid magic changes in send window
1391         CAML T,XBSAVW(I)        
1392          JRST TCPOS6            ; Send window same or smaller (!), send seg.
1393         MOVE Q,XBSAVW(I)        ; Send window is bigger!  Get new size
1394         LDB A,[PK$TDL (R)]      ; Get max size
1395         CAMLE A,Q
1396          MOVEI A,(Q)            ; Use minimum of max size and send window.
1397         MOVEI Q,(A)             ; Save result
1398         SUBI A,(T)              ; Find # more bytes we can hack
1399         CAIG A,                 ; If there's no more,
1400          JRST TCPOS6            ; Just send it off anyway.
1401         HRLM Q,XBOCOS(I)        ; Hurray, got more!  Store new original #
1402         MOVEM A,XBOBC(I)        ; And set up new count
1403         CONO PI,NETON
1404         AOS (P)
1405         RET                     ; And return happily.
1406
1407 TCPOS6: TRCPKT R,"TCPOS6 STYNET Send"
1408         CALL TCPOB7
1409         JRST TCPOSB
1410 \f
1411 TCPBI:
1412 TCPBO:  RET             ; No-ops, labels left in case want to use.
1413
1414 ; STATUS - from LH(DTSTB)
1415 ;       Must return status in LH(D).  Must not smash C,R.
1416 ;       R/ addr of IOCHNM word
1417
1418 TCPSTA: HLRZ I,(R)      ; Get TCB index
1419         SKIPN XBUSER(I) ; Probably an error if this is zero.
1420          BUG CHECK,[TCP: STATUS on unused conn ],OCT,I
1421         SETZ D,
1422         SKIPN XBSTAT(I)
1423          RET
1424         HRRZ A,(R)      ; Find whether input or output
1425         CAIN A,TCPDUI
1426          SKIPA T,[TXBIST]
1427           MOVEI T,TXBOST
1428         CALL (T)
1429         DPB T,[140600,,D]
1430         RET
1431
1432
1433 TXBIST: HRRZ T,XBSTAT(I)
1434         CAIL T,.XSTOT
1435          BUG HALT
1436         SKIPGE T,XBCTBI(T)      ; Get conversion
1437          JRST [ SKIPN XBITQH(I) ; Must test for input avail - any segs?
1438                  SKIPA T,(T)    ; None avail, use standard
1439                   MOVE T,1(T)   ; Have some waiting, use alternate state
1440                 RET]
1441         RET
1442 XBCTBI: OFFSET -.
1443 .XSCLS:: SETZ [%NTCLS ? %NTCLI] ; 0 Closed 
1444 .XSSYQ:: 0                      ; Technically this is an impossible state...
1445 .XSLSN:: %NTLSN                 ; 1 Listen
1446 .XSSYN:: %NTSYN                 ; 4 Syn-Sent
1447 .XSSYR:: %NTSYR                 ; 2 Syn-Rcvd
1448 .XSOPN:: SETZ [%NTOPN ? %NTINP] ; 5/11 Established (open)
1449 .XSFN1:: SETZ [%NTOPN ? %NTINP] ; 7 Fin-Wait-1
1450 .XSFN2:: SETZ [%NTOPN ? %NTINP] ; 7 Fin-Wait-2
1451 .XSCLW:: SETZ [%NTCLU ? %NTCLI] ; 3/10 Close-Wait
1452 .XSCLO:: SETZ [%NTCLS ? %NTCLI] ; 7/10 Closing
1453 .XSCLA:: SETZ [%NTCLS ? %NTCLI] ; 7 Last-Ack
1454 .XSTMW:: SETZ [%NTCLS ? %NTCLI] ; 7 Time-Wait
1455 .XSTOT:: OFFSET 0
1456
1457
1458 TXBOST: HRRZ T,XBSTAT(I)
1459         CAIL T,.XSTOT
1460          BUG HALT
1461         SKIPGE T,XBCTBO(T)      ; Get conversion
1462          JRST [ SKIPN XBORTQ(I) ; Must test for output queued
1463                  SKIPA T,(T)    ; None, use standard
1464                   MOVE T,1(T)   ; Have some output waiting, use alternate state
1465                 RET]
1466         RET
1467 XBCTBO: OFFSET -.
1468 .XSCLS:: %NTCLS         ; 0 Closed 
1469 .XSSYQ:: 0              ; Technically this is an impossible state...
1470 .XSLSN:: %NTLSN         ; 1 Listen
1471 .XSSYN:: %NTSYN         ; 4 Syn-Sent
1472 .XSSYR:: %NTSYR         ; 2 Syn-Rcvd
1473 .XSOPN:: SETZ [%NTOPN ? %NTWRT]         ; 5/6 Established (open)
1474 .XSFN1:: %NTCLX         ; 7 Fin-Wait-1
1475 .XSFN2:: %NTCLX         ; 7 Fin-Wait-2
1476 .XSCLW:: SETZ [%NTOPN ? %NTWRT]         ; 5/6 Close-Wait
1477 .XSCLO:: %NTCLX         ; 7 Closing
1478 .XSCLA:: %NTCLX         ; 7 Last-Ack
1479 .XSTMW:: %NTCLX         ; 7 Time-Wait
1480 .XSTOT:: OFFSET 0
1481
1482
1483 \f
1484 ; WHYINT - from RH(DTSTB)
1485 ; Results are:
1486 ;       A/ %WYTCP
1487 ;       B/ <state>
1488 ;       C/ input  - # bytes in input buff
1489 ;          output - # bytes of room avail in output buff
1490 ;       D/ Close reason (only valid if state %NTCLS)
1491
1492 TCPWHY: HLRZ I,(R)              ; Get TCB index
1493         METER("TCP: syscal whyint")
1494         CAIL I,XBL
1495          BUG HALT,[TCP: WHY idx bad]
1496         CALL TCPSTA
1497         LDB B,[140600,,D]       ; Get state for channel
1498         HRRZ A,(R)              ; Find whether input or output
1499         CAIN A,TCPDUI
1500          JRST [ HLRZ D,XBCLSU(I)        ; Get input close reason
1501                 MOVSI C,(XB%STY)
1502                 TDNE C,XBUSER(I)        ; No input avail if direct-conn to STY
1503                  JRST [ SETZ C, ? JRST TCPWH5]
1504                 SKIPLE C,XBINBS(I)
1505                  JRST TCPWH5
1506                 SKIPN C,XBITQH(I)
1507                  JRST TCPWH5
1508                 LDB C,[PK$TDL (C)]
1509                 JRST TCPWH5]
1510         HRRZ D,XBCLSU(I)        ; Get output close reason
1511         SKIPN C,XBOBC(I)        ; Get # bytes of room left in current pkt
1512          JRST [ MOVEI C,%TCPMO  ; If none, return total queue space instead
1513                 SUB C,XBORTL(I)
1514                 IMUL C,XBSMSS(I)
1515                 CAIG C,
1516                  SETZ C,
1517                 JRST .+1]
1518 TCPWH5: MOVEI A,%WYTCP
1519         JRST POPJ1
1520         
1521
1522
1523 ; RFNAME - from LH(DRFNTB)
1524 ;       A/ LH of IOCHNM word for channel.
1525
1526 TCPRCH: MOVEI I,(A)
1527         LDB B,[.BP TH%DST,XBPORT(I)]
1528         LDB C,[.BP TH%SRC,XBPORT(I)]
1529         MOVE D,XBHOST(I)
1530         MOVEI W,4
1531         POPJ P,
1532
1533 ; RFPNTR - from RH(DRFNTB)
1534 TCPRFP: JRST OPNL34
1535
1536 ; IOPUSH/POP - from LH(RSTBI)
1537 TCPIOP: HRRZ T,R
1538         SUBI T,IOCHNM(U)
1539         CAIN I,
1540          SKIPA T,[77]   ; IOPUSH, use 77
1541           ADDI T,1      ; IOPOP, use chan+1
1542         HLRZ I,(R)      ; Get TCB index
1543         HRRZ B,(R)      ; Get direction
1544         CAIN B,TCPDUI   ; as a BP to chan #
1545          SKIPA B,[XB$ICH (I)]
1546           MOVE B,[XB$OCH (I)]
1547         DPB T,B         ; Store new saved channel #
1548         POPJ P,
1549
1550 ; RESET - from RH(RSTBI)
1551 ;       This doesn't have to do anything for a while yet.
1552 TCPRST:
1553         POPJ P,
1554
1555 ; FORCE - from LH(DFRCTB)
1556 ;       Should force out the TCP segment currently being written,
1557 ;       and give it a good shove (ie PUSH).
1558 ;       A/ LH of IOCHNM word, in RH.
1559 ;       H/ IOCHNM word
1560 ;       R/ <LH of CLSTB entry>,,<addr of IOCHNM word>
1561 TCPFRC: METER("TCP: syscal force")
1562         HRRZ B,(R)              ; This should be a TCP output channel.
1563         CAIE B,TCPDUO           ; If not output, must be input, so
1564          JRST OPNL2             ; say "wrong direction".
1565         HLRZ I,(R)              ; Get TCB index
1566         CAIL I,XBL              ; Ensure validity
1567          BUG HALT,[TCP: FRC bad idx]
1568
1569         ; Ensure that state allows sending anything.
1570         CONO PI,NETOFF          ; So state doesn't change while we think.
1571         HRRZ J,XBSTAT(I)
1572         CAIE J,.XSOPN
1573          CAIN J,.XSCLW
1574           CAIA
1575            JRST OPNL7           ; Bad state, say "device not ready".
1576         
1577         PUSH P,R
1578         MOVSI T,(TC%PSH)        ; Set PUSH flag (but not ACK, to avoid 
1579                                 ; forcing send of empty buffer)
1580         CALL TCPOFR             ; Force out!  Clobber many ACs.
1581         CONO PI,NETON
1582         POP P,R
1583         JRST POPJ1
1584
1585
1586 ; FINISH - from RH(DFRCTB)
1587 ;       We already know that R is OK since FORCE looked at it first.
1588 ;       In fact, I is still set up.
1589 ;       R/ addr of IOCHNM word
1590
1591 TCPFIN: METER("TCP: syscal finish")
1592         MOVSI T,(%XBNOW)
1593         TDNE T,XBSTAT(I) ; Wait until this bit is off (XBOCOS put on Q)
1594          CALL UFLS
1595         SKIPE XBORTQ(I) ; Hang until retransmit queue is empty.
1596          CALL UFLS
1597         JRST POPJ1
1598 \f
1599 SUBTTL TCP STY connection routines
1600
1601 ; STYTCP - invoked by STYNTC routine during 1/2 sec clock, for
1602 ;       STYs connected to TCP channels.
1603 ;       R/ TTY #
1604
1605 STYTCP: MOVE I,STYNTI-NFSTTY(R) ; Get TCB index for connection
1606         LDB TT,[XB$STY (I)]     ; Verify that TCB thinks we're hooked up
1607         CAIE TT,(R)
1608          BUG                    ; It doesn't??
1609
1610         ; First, check for and transfer any input for the STY.
1611         HLRZ T,XBSTAU(I)        ; Get input state
1612         SKIPG TCPTBI(T)         ; Make sure we can do input.
1613          JRST STYTC9            ; Nope, must disconnect.
1614 STYTC1: SOSGE XBIBC(I)
1615          JRST [ CALL TCPIBD     ; Discard input buffer if any
1616                 HRRZ A,XBITQH(I) ; Any more input avail?
1617                 JUMPE A,STYTC5  ; No, done, check for output.
1618                 CALL TCPIBG     ; Have some!  Set it up.  Shd never hang.
1619                  JFCL
1620                 JRST STYTC1]
1621         ILDB A,XBIBP(I)         ; Get the byte
1622         TRNE A,200              ; Special char?
1623          JRST [ AOS XBIBC(I)    ; Ugh, must back up and get user's attention
1624                 MOVSI B,8._14   ; Back up both count and 8-bit byte pointer
1625                 ADDM B,XBIBP(I) ; by adding to P field of BP
1626                 JRST STYTC9]    ; Go disconnect.
1627         EXCH R,I        ; I gets TTY #, R gets TCB index
1628         PUSH P,R
1629         PUSH P,I
1630         CONO PI,TTYOFF
1631         CALL NTYI5      ; Give the char to TTY input interrupt level
1632         CONO PI,TTYON
1633         POP P,R         ; Note reverse order, so R gets TTY #
1634         POP P,I         ; and I gets TCB index again.
1635         JRST STYTC1     ; Try for more input.
1636
1637         ; Transfer chars from STY output to TCP connection
1638 STYTC5: SKIPGE TTYOAC(R)        ; Do we have any output?
1639          JRST STYTC7            ; No, all's done, force out what we did.
1640         HRRZ A,XBSTAU(I)        ; Check output state
1641         SKIPG TCPTBO(A)         ; to verify that TCB is healthy.
1642          JRST STYTC9            ; Ugh, go disconnect STY.
1643         MOVSI A,(%XBMPL)
1644         IORM A,XBSTAT(I)        ; Lock COS against PI level snarfing
1645
1646         SKIPE XBOCOS(I)
1647          SKIPG E,XBOBC(I)       ; Get # bytes room in output buff
1648           JRST [
1649                 ; Set up buffer, etc, possibly forcing out existing buff.
1650                 PUSH P,R
1651                 CALL TCPOSB     ; Invoke special hang-less routine.
1652                  JRST [POP P,R  ; If can't get any more room, jump to STYTC6
1653                         JRST STYTC6]
1654                 POP P,R
1655                 SKIPG E,XBOBC(I)        ; OK, should have bytes now.
1656                  BUG
1657                 JRST .+1]
1658         SKIPN D,XBOBP(I)        ; Get BP into buffer
1659          BUG
1660         EXCH R,I
1661         CONO PI,TTYOFF
1662         MOVEM D,DBBBP           ; Set up buffer for TTY output interrupt level
1663         MOVEM E,DBBCC
1664         MOVEM E,DBBCC1
1665         PUSH P,R
1666         SETOM TYPNTF
1667         PUSHJ P,TYP             ; Generate output
1668         SETZM TYPNTF
1669         POP P,R
1670         EXCH R,I                ; Restore I/ TCB #, R/ TTY #
1671         MOVE D,DBBBP            ; Advance pointers
1672         MOVEM D,XBOBP(I)
1673         MOVE E,DBBCC
1674         SUB E,DBBCC1            ; Minus # chars output generated
1675         CONO PI,TTYON
1676         ADDM E,XBOBC(I)
1677         JRST STYTC5             ; Check for more output
1678
1679         ; No more output or we can't get more room, force out what
1680         ; we've currently got.
1681 STYTC6: CALL TCPUII             ; Reactivate STY (expensive crock, but...)
1682 STYTC7: MOVSI A,(%XBMPL)        ; Unlock the COS
1683         ANDCAM A,XBSTAT(I)
1684         MOVSI T,(TC%PSH)        ; PUSH this stuff
1685         CALL TCPOFR             ; Force out buffer
1686         JRST STYNT8             ; Then go check other STYs.
1687
1688
1689         ; Disconnect STY and get user's attention.  Note this may be
1690         ; buggy in that STY output has not yet been transferred to the
1691         ; net by the time we get here, if we're here due to a 200 char.
1692 STYTC9: PUSH P,I
1693         MOVEI I,(R)     ; Set up I/ TTY #
1694         CALL NSTYN0     ; Disconnect it
1695          BUG
1696         POP P,I
1697         CALL TCPUII     ; Wake up the user program
1698         JRST STYNT8     ; Go handle other STYs.
1699
1700 IFN 0,[
1701 ;CALLED AT CLOCK LEVEL FROM STYNTC WHEN A CHAOS STY IS ENCOUNTERED
1702 ;TTY NUMBER IN I & R
1703 STYCHA: MOVE I,STYNTI-NFSTTY(R) ;GET CHAOS INDEX
1704         MOVE TT,CHSSTA(I)
1705         TLNN TT,%CFSTY
1706          JRST 4,.               ;CHAOS CONNECTION CLAIMS NOT BE CONNECTED?
1707         JUMPL TT,STYCH9 .SEE %CFOFF     ;OK TO USE?  IF NOT, DISCONNECT
1708         SKIPGE TTYOAC(R)        ;ANY OUTPUT?
1709          JRST STYCH1            ;NO, CHECK FOR INPUT
1710         SKIPN D,CHSOBP(I)       ;IF BUFFER ALLOCATED, USE IT
1711          JRST [ SKIPG CHSNOS(I) ;OTHERWISE ALLOCATE ONE
1712                  JRST STYCH1    ;WINDOW FULL, WAIT UNTIL REACTIVATED
1713                 PUSHJ P,CHABGI
1714                  JRST STYCH3    ;NO CORE, WAIT ONE CLOCK TICK
1715                 MOVEI D,%CPKDT(A)
1716                 HRLI D,440800
1717                 MOVEM D,CHSOBP(I)
1718                 MOVEI E,%CPMXC
1719                 MOVEM E,CHSOBC(I)
1720                 JRST .+3 ]
1721           SKIPG E,CHSOBC(I)
1722            JRST STYCH4          ;BUFFER FULL, FORCE IT
1723         EXCH R,I                ;I GETS TTY, R GETS CHAOS
1724         CONO PI,TTYOFF
1725         MOVEM D,DBBBP           ;SET UP BUFFER FOR TTY OUTPUT INTERRUPT LEVEL
1726         MOVEM E,DBBCC
1727         MOVEM E,DBBCC1
1728         PUSH P,R
1729         SETOM TYPNTF
1730         PUSHJ P,TYP             ;GENERATE OUTPUT
1731         SETZM TYPNTF
1732         POP P,R
1733         EXCH R,I                ;I GETS CHAOS, R GETS TTY
1734         MOVE D,DBBBP            ;ADVANCE POINTERS
1735         MOVEM D,CHSOBP(I)
1736         MOVE E,DBBCC
1737         SUB E,DBBCC1            ;MINUS # CHARS OUTPUT GENERATED
1738         CONO PI,TTYON
1739         ADDM E,CHSOBC(I)
1740 STYCH4: PUSHJ P,CHAFC1          ;FORCE THE BUFFER
1741         JRST STYCHA             ;CHECK FOR MORE OUTPUT
1742 \f
1743 STYCH3: PUSHJ P,CHINTI          ;REACTIVATE SO WILL COME BACK ON NEXT CLOCK TICK
1744 STYCH1: SOSGE CHSIBC(I)         ;GET INPUT, IF ANY
1745          JRST [ PUSHJ P,CHAIBD  ;DISCARD EXHAUSTED INPUT BUFFER, IF ANY
1746                 HLRZ A,CHSIBF(I)
1747                 JUMPE A,STYNT8  ;NONE, RETURN TO STYNTC
1748                 LDB TT,[$CPKOP(A)]
1749                 CAIE TT,%CODAT
1750                  JRST STYCH9    ;RANDOM PACKET, DISCONNECT
1751                 PUSHJ P,CHPKIA  ;ACKNOWLEDGE GOBBLING OF THIS PACKET
1752                 SOS CHSNBF(I)   ;REMOVE BUFFER FROM RECEIVE LIST
1753                 MOVEI Q,CHSIBF(I)
1754                 PUSHJ P,CHAQGF
1755                 LDB E,[$CPKNB(A)]       ;SET UP FOR BYTE STREAM INPUT
1756                 MOVEM E,CHSIBC(I)
1757                 MOVEI D,%CPKDT(A)
1758                 HRLI D,440800
1759                 MOVEM D,CHSIBP(I)
1760                 JRST STYCH1 ]
1761         ILDB A,CHSIBP(I)        ;GET CHARACTER OF INPUT
1762         TRNE A,200
1763          JRST [ AOS CHSIBC(I)   ;WOOPS, SPECIAL CHARACTER, NEEDS USER ATTENTION
1764                 MOVSI A,8_14    ;SO PUT IT BACK AND DISCONNECT
1765                 ADDM A,CHSIBP(I)
1766                 JRST STYCH9 ]
1767         EXCH R,I                ;I GETS TTY, R GETS CHAOS
1768         PUSH P,R
1769         PUSH P,I
1770         CONO PI,TTYOFF
1771         PUSHJ P,NTYI5           ;GIVE CHARACTER TO TTY INPUT INTERRUPT LEVEL
1772         CONO PI,TTYON
1773         POP P,R
1774         POP P,I                 ;I GETS CHAOS, R GETS TTY ((POP IN REVERSE ORDER))
1775         JRST STYCH1             ;TRY FOR MORE INPUT
1776
1777 STYCH9: PUSH P,I
1778         MOVE I,R                ;I GETS TTY
1779         PUSHJ P,NSTYN0          ;DISCONNECT THE STY
1780          JRST 4,.
1781         POP P,I                 ;I GETS CHAOS
1782         PUSHJ P,CHINTI          ;WAKE UP THE TELNET SERVER
1783         JRST STYNT8             ;GO HANDLE OTHER STYS
1784 ] ;ifn 0
1785 \f
1786 SUBTTL Other TCP system call functions
1787
1788 ; TCPRQ - Handle .CALL NETRFC, return port # of next pending
1789 ;       request for connection (SYN).
1790 ;       Perhaps return a uniquizer in LH, so know when see
1791 ;       the same request again?
1792
1793 TCPRQ:  TRNE C,%NQREF           ; Skip if just getting, not flushing.
1794          JRST TCPRQ5
1795         METER("TCP: syscal netrfc get")
1796         CONO PI,NETOFF          ; In case a RST comes for it or something.
1797 ;       MOVE I,TCPRQL           ; Get last thing stored on queue
1798         SETOB B,D               ; Look for any match
1799         CALL TCPRQS             ; Search the queue...
1800         JUMPL A,OPNL4           ; None, say "file not found".
1801         MOVEI I,(A)
1802         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get local port # for the SYN
1803         HRLI A,(I)              ; And put index in LH as uniquizer.
1804         CONO PI,NETON
1805         JRST POPJ1
1806
1807 TCPRQ2: BUG CHECK,[TCP: Pending SYN smashed!]
1808         RET
1809
1810         ; Refuse indicated connection.
1811 TCPRQ5: METER("TCP: syscal netrfc ref")
1812         CAIGE W,2               ; Must have 2 args
1813          JRST OPNL30            ; "Too few args"
1814         HLRE D,A                ; Get identifier
1815         HRRE B,A
1816         CONO PI,NETOFF
1817         CALL TCPRQS             ; Search for the queued SYN
1818         JUMPL A,OPNL4
1819
1820         ; Now must refuse connection.
1821         MOVEI I,(A)
1822         MOVEI Q,XBITQH(I)
1823         CALL PKQGF(PK.TCP)      ; Get queued SYN segment 
1824         SKIPN XBITQH(I)         ; Should have been only one
1825          SKIPG R,A              ; and should have been one!
1826           BUG HALT
1827         CALL TXBFLS             ; Flush the TCB.
1828         SOSGE TCPRQN            ; Decrement count of queued SYNs
1829          BUG HALT
1830         HLRZ W,PK.IP(R)         ; Move all this setup somewhere modular.
1831         HLRZ H,PK.TCP(R)
1832         LDB TT,[PK$TDL (R)]
1833         MOVE E,TH$CTL(H)
1834         TLNE E,(TC%SYN)
1835          ADDI TT,1
1836         TLNE E,(TC%FIN)
1837          ADDI TT,1
1838         CALL TSISLR             ; Respond to this req with RST+ACK
1839         CONO PI,NETON
1840         JRST POPJ1
1841
1842 ; TCPRQS - Search pending-RFC queue.  Must be called with NETOFF!!
1843 ;       B/ local port # (-1 for any)
1844 ;       D/ Index #, -1 for any (searches back from last one stored)
1845 ; Clobbers T,Q
1846 ; Returns
1847 ;       A/ Index to matching SYN (-1 if no match)
1848
1849 TCPRQS: JUMPGE D,TCPRQ7
1850         MOVE A,TCPRQL
1851         MOVEI C,1
1852 TCPRQ6: HRRZ T,XBSTAT(A)        ; See if right state
1853         CAIN T,.XSSYQ
1854          JRST [ LDB T,[.BP TH%DST,XBPORT(A)]
1855                 CAIL B,
1856                  CAMN T,B
1857                   RET
1858                 JRST .+1]
1859         SOJGE A,TCPRQ6
1860         MOVEI A,XBL-1
1861         SOJGE C,TCPRQ6
1862 TCPRQ9: SETO A,
1863         RET
1864
1865 TCPRQ7: SKIPL A,D
1866          CAIL D,XBL
1867           JRST TCPRQ9
1868         HRRZ T,XBSTAT(A)        ; Verify state
1869         CAIE T,.XSSYQ
1870          JRST TCPRQ9
1871         LDB T,[.BP TH%DST,XBPORT(A)]     ; Got one!  Get local port #
1872         CAIL B,
1873          CAIN T,(B)     ; Must match given arg unless -1
1874           RET           ; Won!
1875         JRST TCPRQ9
1876
1877 ifn 0,[
1878 TCPRQS: MOVEI A,TCPRQH-PK.TCP
1879 TCPRQ6: MOVEI Q,(A)             ; Save ptr to prev node
1880         HRRZ A,PK.TCP(A)        ; Get ptr to next PE
1881         JUMPE A,TCPRQ8          ; If not there, return 0 as error.
1882         JUMPL D,TCPRQ7
1883         CAIE A,(D)              ; See if identifier matches
1884          JRST TCPRQ6            ; Jump if not.
1885 TCPRQ7: HLRZ T,PK.TCP(A)        ; Yes, verify port number
1886         CAIN T,                 ; Ensure ptr to TCP header exists.
1887          BUG HALT
1888         LDB T,[TH$DST (T)]
1889         CAIE T,(B)
1890          JRST TCPRQ6            ; Nope, get next thing.
1891
1892         ; Found it!  Take off list, a bit tricky.
1893         SOSGE TCPRQN            ; Decrement count of entries
1894          BUG HALT
1895         MOVSI T,(%PQFL2)        ; Clear the on-list flag for PK.TCP
1896         ANDCAM T,PK.FLG(A)
1897 IFN 2-PK.TCP,.ERR TCPRQS must fix %PQFL2 to match PK.TCP
1898         HRRZ T,PK.TCP(A)        ; Get its next-ptr
1899         HRRM T,PK.TCP(Q)        ; Store in node previous to this one.
1900         JUMPN T,TCPRQ8          ; If wasn't last thing, all's well.
1901         CAIN Q,TCPRQH-PK.TCP    ; Last thing.  If prev was actually hdr,
1902          SETZ Q,                ; must store zero.
1903         HRLM Q,TCPRQH           ; Set new "last" ptr in hdr.
1904 TCPRQ8: 
1905         RET
1906
1907 ] ;ifn 0
1908 \f
1909 ; TSOINI - set up a raw PE for use as a TCP output segment.  Means
1910 ;       setting IP, TCP header pointers properly, so that all fields
1911 ;       are contiguous.  Note that PK.TCI is set to indicate XBSMSS(I)
1912 ;       bytes of (available) data storage!
1913 ;       Sets up PK.IP, PK.TCP, and PK.TCI.
1914 ;       R/ PE ptr
1915 ;       I/ TCB connection index (val put into PK.TCI)
1916 ; Returns with R, W, H pointing to PE, IP hdr, and TCP hdr.
1917 ;       
1918 ; TSOINA - Ditto, but takes arg in A and only clobbers T (doesn't set W, H)
1919
1920
1921 TSOINI: HRRZ W,PK.BUF(R)        ; Get addr of buffer
1922         HRLM W,PK.IP(R)         ; Store as IP header addr
1923         MOVEI H,(I)             ; Set up TCI with all fields.
1924         ANDI H,PK%TCB
1925         IOR H,[<<%TCPHL*4>_<.TZ PK%TDO,>>]
1926         MOVEM H,PK.TCI(R)       ; 
1927         MOVE H,XBSMSS(I)        ; Allow XBSMSS(I) bytes with assumed offset.
1928         DPB H,[PK$TDL (R)]
1929         MOVEI H,%TCPHL(W)       ; For now, this will do.
1930         HRLM H,PK.TCP(R)        ; Store as TCP header addr
1931         RET
1932
1933 TSOINA: HRRZ T,PK.BUF(A)        ; Get addr of buffer
1934         HRLM T,PK.IP(A)         ; Store as IP header addr
1935         ADDI T,%TCPHL           ; For now, this will do to get TCP hdr.
1936         HRLM T,PK.TCP(A)        ; Store as TCP header addr
1937         MOVEI T,(I)             ; Set up TCI with all fields.
1938         ANDI T,PK%TCB
1939         IOR T,[<<%TCPHL*4>_<.TZ PK%TDO,>>]
1940         MOVEM T,PK.TCI(A)       ; Set up index and header length fields
1941         MOVE H,XBSMSS(I)        ; Allow XBSMSS(I) bytes with assumed offset.
1942         DPB H,[PK$TDL (R)]
1943         RET
1944
1945 ; TCPUSI - TCP User State-change Interrupt.  Called each time connection
1946 ;       changes state (.XSnnn) or I/O queues start/end.  Always tries
1947 ;       to interrupt user, except for change %NTWRT->%NTOPN on output
1948 ;       and %NTINP->%NTOPN on input.
1949 ;       Moon: Interrupt when input rcvd and buff empty, or output full
1950 ;               and becomes reasonably non-full.
1951 ; Clobbers T, Q
1952
1953 TCPUSI: METER("TCP: tcpusi called")
1954         CALL TXBIST             ; Check input state
1955         HLRZ Q,XBSTAU(I)
1956         CAIE T,(Q)              ; New state?
1957          JRST TCPUS3            ; Yes, go handle.
1958 TCPUS2: CALL TXBOST
1959         HRRZ Q,XBSTAU(I)
1960         CAIN T,(Q)
1961          RET
1962
1963         ; Output channel state change
1964         ; Q/ old state, T/ new state  (%NT values, not .XS)
1965         HRRM T,XBSTAU(I)        ; Store new state (old in Q)
1966         CAIN Q,%NTOPN           ; If was open
1967          CAIE T,%NTWRT          ; Changing to buff-full
1968           CAIA
1969            RET                  ; Then don't interrupt.
1970         MOVE Q,TCPTBO(Q)
1971         CAMN Q,TCPTBO(T)        ; See if meta-state change
1972          RET                    ; Nope, ignore.
1973         LDB Q,[XB$OCH (I)]      ; Yes, get channel #
1974         METER("TCP: User O ints")
1975         CALRET TCPUS5
1976
1977         ; Input channel state change
1978 TCPUS3: HRLM T,XBSTAU(I)        ; Store new state (old in Q)
1979         CAIN Q,%NTINP           ; If was input avail
1980          CAIE T,%NTOPN          ; Changing to plain open
1981           CAIA
1982            JRST TCPUS2          ; Then don't interrupt.
1983         MOVE Q,TCPTBI(Q)
1984         CAMN Q,TCPTBI(T)        ; See if meta-state change
1985          JRST TCPUS2            ; No
1986                                 ; Drop thru to interrupt
1987
1988         ; Give input channel interrupt
1989 TCPUII: METER("TCP: User I ints")
1990         LDB Q,[XB$STY (I)]      ; See if hooked to STY
1991         JUMPN Q,TCPUSS          ; Jump to handle STY stuff if so.
1992         LDB Q,[XB$ICH (I)]      ; No, just get input chan
1993         CALL TCPUS5
1994         JRST TCPUS2
1995
1996         ; Give interrupt to STY that TCB is connected to.
1997         ; Q/ TTY #
1998 TCPUSS: CONO PI,PIOFF           ; Protect list hacking
1999         SKIPL STYNTL-NFSTTY(Q)  ; Don't put on list twice
2000          JRST PIONJ
2001         MOVE T,STYNTA           ; Add to list
2002         MOVEM T,STYNTL-NFSTTY(Q)
2003         MOVEM Q,STYNTA
2004         JRST PIONJ
2005
2006         ; Interrupt on channel in Q.
2007 TCPUS5: JUMPE Q,CPOPJ           ; May be no channel there.
2008         PUSH P,U
2009         SKIPN U,XBUSER(I)
2010          BUG HALT               ; Jumpe above should catch this.
2011         MOVSI T,(SETZ)
2012         IORM T,PIRQC(U)
2013         CAIN Q,77               ; If IOPUSH'ed, no interrupt.
2014          JRST POPUJ
2015         MOVE T,CHNBIT-1(Q)      ; Q is -1 based.
2016         AND T,MSKST2(U)
2017         IORM T,IFPIR(U)
2018         POP P,U
2019         RET
2020
2021         ; Input chan state type.  Pos # means can read.
2022         ; 0 is pre-open, 1 is open, 2 is input avail, -1 is post-open.
2023 TCPTBI: OFFSET -.
2024 %NTCLS:: 0      ; 0 CLS
2025 %NTLSN:: 0      ; 1 LSN
2026 %NTSYR:: 0      ; 2 RFC
2027 %NTCLU:: -1     ; 3 RCL?
2028 %NTSYN:: 0      ; 4 RFS
2029 %NTOPN:: 1      ; 5 OPN
2030 %NTWRT:: 1      ; 6 RFN
2031 %NTCLX:: -1     ; 7 CLW
2032 %NTCLI:: 1      ; 10 CLI
2033 %NTINP:: 2      ; 11 INP
2034         OFFSET 0
2035
2036         ; Output chan state type. Pos # means can write.
2037         ; 0 is pre-open, 1 is open, 2 is buff full, -1 is post-open.
2038 TCPTBO: OFFSET -.
2039 %NTCLS:: 0
2040 %NTLSN:: 0
2041 %NTSYR:: 0
2042 %NTCLU:: 1
2043 %NTSYN:: 0
2044 %NTOPN:: 1
2045 %NTWRT:: 2
2046 %NTCLX:: -1
2047 %NTCLI:: 1
2048 %NTINP:: 1
2049         OFFSET 0
2050
2051 \f
2052 SUBTTL TCP Input Interrupt Level
2053
2054 ; TCPIS - Process TCP Input Segment (PI level)
2055 ;       R/ PE ptr to packet, not on any list.
2056 ;               PK.BUF is set, ditto IP/TCP header pointers.
2057 ;       W/ addr of IP header
2058 ;       H/ addr of IP data (start of TCP header)
2059 ;       J/ host-table index for address datagram received from.
2060 ; Can clobber all ACs except P, returns with POPJ.
2061 ; AC usage during incoming segment processing:
2062 ;       R/ PE ptr to packet
2063 ;       W/ addr of IP header
2064 ;       H/ addr of TCP header
2065 ;       I/ TCB index (if any)
2066 ;       J/ TCB connection state
2067 ;       TT/ # bytes of TCP data in segment
2068 ;       E/ <seg control bits>,,<temp flags>
2069 ;       D/ Segment Sequence no.
2070 ; Flags for RH of E
2071 %TSISL==1       ; Seq starts to left of rcv.nxt
2072 %TSISR==2       ; Seq starts to right of  "  ; if neither on, is = rcv.nxt
2073 %TSIFL==4       ; Bad seq, flush after handling RST/ACK/URG
2074
2075 TCPIS:  METER("TCP: Segs rcvd")
2076         SKIPN TCPUP     ; Unless TCP claims to be up,
2077          JRST TSIFL     ; Throw it away, no TCP yet, sigh.
2078
2079         ; First verify that this is a valid TCP segment, by
2080         ; checksumming it (sigh!).  TT gets total # bytes in TCP segment.
2081         CALL THCKSI             ; Get checksum in A for segment
2082         LDB B,[TH$CKS (H)]      ; Get segment's checksum
2083         CAME A,B                ; Should match.
2084          JRST TSIF01            ; Failed, go bump err count and flush it.
2085         LDB T,[TH$THL (H)]      ; Find TCP header length in words
2086         LSH T,2                 ; Make it in octets
2087         SUBI TT,(T)             ; TT now has # octets of segment data.
2088
2089         ; Contents of segment have been validated (more or less),
2090         ; now set up convenient context values
2091         ;       PK.TCI contents
2092         ;       E/ Segment control flags (in LH)
2093         ;       TT/ SEG.LEN
2094         HLLZ E,TH$CTL(H)        ; Get word with segment control flags
2095         DPB T,[PK$TDO (R)]      ; Store offset of data (from THCKSI)
2096         DPB TT,[PK$TDL (R)]     ; Store length of data
2097         TLNE E,(TC%SYN)         ; Note that SYN counts in seg.len
2098          ADDI TT,1              ;  so allow for it
2099         TLNE E,(TC%FIN)         ; And do same thing for FIN.
2100          ADDI TT,1              ;  Either way, get SEG.LEN set up in TT.
2101
2102         ; Then see if any TCB exists for this segment.
2103         SKIPE A,TH$SRC(H)       ; Get source/dest port word
2104          SKIPN B,IP$SRC(W)      ; Get source addr from IP header
2105           JRST TSIF02           ; Flush anything with zero field.
2106         LSH B,-4                ; Right-justify the addr
2107         MOVSI I,-XBL
2108 TSI02:  CAMN A,XBPORT(I)        ; Loop til we find it
2109          CAME B,XBHOST(I)
2110 TSI03:    AOBJN I,TSI02
2111         JUMPL I,TSI05           ; Jump if found existing connection
2112         JRST TSISQ              ; Jump if no existing connection.
2113
2114 TSI04:  SKIPE XBSTAT(I)         ; Found "closed" connection????
2115          JRST TSI02             ; LH must have crud still set, ignore for now
2116         BUG CHECK,[TCP: Clsed TCB has active port/host] ; Shouldn't happen!
2117         SETZM XBHOST(I)         ; If continued, fix up.
2118         JRST TSI02
2119
2120         ; Connection exists, TCB index now in I.
2121         ; Set up a little more context (PK.TCI and J)
2122 TSI05:  DPB I,[PK$TCB (R)]      ; Store TCB index in packet info
2123         MOVEM J,XBNADR(I)       ; Save host-table idx of addr this seg is from.
2124         HRRZ J,XBSTAT(I)        ; Get connection state
2125         CAIL J,.XSTOT           ; Highest possible state.
2126          BUG HALT,[TCP: Bad conn state]
2127         METER("TCP: IS all states")
2128         XCT XSMTRS(J)           ; Bump meter for each state
2129         CAIG J,.XSSYN           ; If it's CLS, SYQ, LSN or SYN-SENT
2130          JRST @(J)[             ; then process specially.
2131                 TSI04           ; Closed???
2132                 TSISQQ          ; Syn-Queued?  (Probably re-trans)
2133                 TSILS           ; Listen
2134                 TSISS]          ; Syn-sent
2135         ; Drop through to perform general sequence-number checking.
2136 \f
2137         ; Check Sequence Number!!!
2138         ; This code doesn't do two things:
2139         ;       1) it doesn't keep around stuff that arrives to the
2140         ;               right of rcv.nxt.
2141         ;       2) for situation where seg.seq number is valid,
2142         ;               (i.e. seq =< rcv.nxt) the code punts if
2143         ;               end of seg is out of window.  It should simply
2144         ;               expand the window!
2145         LDB D,[TH$SEQ (H)]      ; Get sequence number
2146         JUMPG TT,TSI10          ; Jump if data present.
2147         JUMPL TT,TSIF03         ; No data.  Jump if error (neg data!)
2148
2149         ; No data in this segment, it is probably a simple ACK.
2150         CAMN D,XBRNXT(I)        ; Seg.seq == snd.nxt (as expected?)
2151          JRST TSI20             ; Yep, seg is acceptable instantly!
2152         METER("TCP: Ifl 0-len seqerr")
2153         JRST TSISNE             ; Sigh, flush it.
2154
2155         ; Seq number check when data present.
2156 TSI10:  CAME D,XBRNXT(I)        ; Is seq # what we expect (seq = nxt)?
2157          JRST TSI11
2158         SKIPE C,XBRWND(I)       ; Yes!  And is our window open?
2159          JRST TSI20             ; Yes!  Fast dispatch!
2160
2161         ; Data segment, with valid sequence number, but our window is
2162         ; zero.  See if there's some way we can avoid throwing away the
2163         ; segment... if we can't take it then still must handle
2164         ; ACK/URG/RST flags.  For now, we really handle this at TSI70.
2165 TSI12:  METER("TCP: 0-wnd data seg")
2166         JRST TSI20
2167
2168         ; Sequence # isn't exactly what we hoped for, see if the
2169         ; segment overlaps a valid portion of sequence space.
2170 TSI11:  SKIPN C,XBRWND(I)       ;#3: Get window, is it zero?
2171          MOVEI C,512.           ; If zero, substitute a dummy window.
2172
2173         ; Both len>0 and wnd>0.
2174         ADD C,XBRNXT(I)         ; Get nxt+wnd
2175         TLZ C,%MOD32            ; all arith mod 32
2176                                 ;#4a: nxt =< seq < nxt+wnd
2177         CMPSEQ XBRNXT(I),=<,D,<,C,TSI13 ; Jump if fail this test, try 4b.
2178
2179         ; Come here when sequence # is OK, but segment starts farther on
2180         ; than we want, i.e. there is a "hole" between rcv.nxt and seg.seq.
2181         ; Eventually we could keep this segment around, to speed up
2182         ; throughput for nets that get packets out of order, but for
2183         ; now we'll just flush it and force a retransmit.
2184         METER("TCP: Iseg hole")
2185         TRO E,%TSISR+%TSIFL     ; Say starts to right, and flush later.
2186         JRST TSI20              ; Go process RST/ACK/URG etc.
2187
2188 TSIF12: METER("TCP: Ifl seq dup")       ; Segment falls in prev rcvd data.
2189         MOVE D,XBRNXT(I)                ; Fake out, say seq # OK
2190         TRO E,%TSIFL                    ; and don't process data.
2191         JRST TSI20                      ; Go handle RST/ACK/URG.
2192
2193 TSIF13: METER("TCP: Ifl seq int err")   ; Shouldn't ever happen, due to
2194         JRST TSISNE                     ; right-bound check code above.
2195 TSIF14: METER("TCP: Ifl seq old")
2196         JRST TSISNE
2197 TSIF15: METER("TCP: Ifl monster seg")   ; Impossible error
2198         JRST TSISNE
2199
2200         ; Segment does not overlap window to right, so see if it
2201         ; overlaps to left, i.e. sequence # falls within data we have
2202         ; already received.
2203 TSI13:  MOVE A,XBRNXT(I)
2204         SUBI A,%TCPMB           ; Make a fictional lower bound
2205         CAIGE A,
2206          ADD A,[1_32.]          ; Keep bound mod 2^32
2207         CMPSEQ A,=<,D,=<,XBRNXT(I),TSIF14,TSIF13
2208
2209         ; Yep, falls within received data.  It's probably a duplicate
2210         ; retransmitted segment; see if there's any new data on right side.
2211         ; Note that we are not using XBRWND here, because as long as we
2212         ; have a non-zero window we will always accept everything in the
2213         ; segment.  So we create another fictional bound to the right.
2214         ADD A,[%TCPMB*2]        ; Get back to other side of rcv.nxt
2215         TLZ A,%MOD32            ; Keep mod 2^32
2216         MOVE C,D
2217         ADDI C,-1(TT)           ; Get seq+len-1
2218         TLZ C,%MOD32
2219                                 ;#4b: nxt =< seq+len-1 < nxt+wnd?
2220         CMPSEQ XBRNXT(I),=<,C,=<,A,TSIF12,TSIF15 ; If fail this too, error.
2221
2222         ; Aha, have some new data in spite of being overlapped with some
2223         ; previously received data!  Here, we
2224         ; twiddle things so that it appears to start properly at
2225         ; rcv.nxt.  This is done without touching the segment contents
2226         ; at all, just modifying the packet entry info.
2227         METER("TCP: Iseg ovlap")
2228         MOVE A,XBRNXT(I)        ; Get rcv.nxt
2229         CAMGE A,D               ; Make sure it's greater than seg.seq
2230          TLO A,(1_32.)          ; Mod 2^32 screw, make it greater (add 33d bit)
2231         SUB A,D                 ; Find # octets of sequence space diff
2232         CAMLE A,TT              ; Shouldn't be greater than seg.len!!
2233          BUG CHECK,[TCP: Trim error]
2234         SUBI TT,(A)
2235         JUMPLE TT,TSIF12        ; If nothing left, drop this segment.
2236         TLZE E,(TC%SYN)         ; Clear SYN since it's at front.
2237          SUBI A,1               ;  If it was set, reduce cnt of actual data
2238         LDB T,[PK$TDL (R)]      ; that we're going to flush.  Get cnt
2239         SUBI T,(A)              ; Decrement # valid data bytes in segment
2240         DPB T,[PK$TDL (R)]      ; Put back
2241         LDB T,[PK$TDO (R)]      ; Also adjust offset to valid data
2242         ADDI T,(A)              ; Increment to point at new data
2243         DPB T,[PK$TDO (R)]      ; Put back
2244         MOVE D,XBRNXT(I)        ; Now say seg.seq = rcv.nxt!
2245                                 ; Segment sanitized, drop through.
2246         SKIPN XBRWND(I)         ; Only proceed if our window not zero.
2247          JRST TSI12             ; It's zero!  May have to flush it...
2248
2249         ; Fall through to TSI20 for RST/ACK/URG processing.
2250 \f
2251         ; Now check RST
2252 TSI20:  TLNE E,(TC%RST)         ; RST bit set?
2253          JRST TSIRST            ; Yeah, go process it.
2254
2255         ; Now check security/precedence
2256         JFCL                    ; ho ho ho
2257
2258         ; Now check SYN bit
2259 TSI40:  TLNE E,(TC%SYN)         ; SYN bit set?
2260          JRST TSISYN            ; Yeah, go process it (basically error)
2261
2262         ; Now check ACK bit
2263 TSI50:  TLNN E,(TC%ACK)         ; ACK bit set?
2264          JRST TSIF50            ; No, error.  Drop segment.
2265         JRST @TSI51(J)          ; Yes, dispatch depending on state.
2266 TSI51:  OFFSET -.
2267 .XSCLS:: [JRST 4,TSI51] ; Closed
2268 .XSSYQ:: [JRST 4,TSI51] ; ITS: Syn-Queued
2269 .XSLSN:: [JRST 4,TSI51] ; Listen
2270 .XSSYN:: [JRST 4,TSI51] ; Syn-Sent
2271 .XSSYR:: TSI53          ; Syn-Rcvd
2272 .XSOPN:: TSI54          ; Established (open)
2273 .XSFN1:: TSI54          ; Fin-Wait-1
2274 .XSFN2:: TSI54          ; Fin-Wait-2
2275 .XSCLW:: TSI54          ; Close-Wait
2276 .XSCLO:: TSI54          ; Closing
2277 .XSCLA:: TSI54          ; Last-Ack
2278 .XSTMW:: TSIATW         ; Time-Wait
2279 .XSTOT:: OFFSET 0
2280
2281
2282         ; SYN-RCVD state, handling ACK.
2283 TSI53:  LDB A,[TH$ACK (H)]      ; Get ACK field
2284         MOVE B,XBSUNA(I)        ; Need one CMPSEQ arg in AC
2285                                 ; Test: snd.una =< seg.ack =< snd.nxt
2286         CMPSEQ B,=<,A,=<,XBSNXT(I),TSISRA       ; Jump if fail
2287         MOVEI J,.XSOPN          ; ACK wins, we're now open!
2288         HRRM J,XBSTAT(I)        ; Set new state, fall through to handle.
2289         CALL TCPUSI             ; Adjust user state.
2290         ; Must initialize SND.WL1, SND.WL2, and SND.WND.
2291         ; Maybe later merge this with TSI55.
2292         MOVEM A,XBSWL2(I)       ; Yes!  Update send window, set WL2 to ACK
2293         MOVEM D,XBSWL1(I)       ; and WL1 to SEQ
2294         LDB B,[TH$WND (H)]
2295         MOVEM B,XBSWND(I)       ; and snd.WND to seg.WND.
2296         MOVEM B,XBSAVW(I)       ; and make avail window be same as send wind.
2297         JRST TSI54X             ; Skip repeating the ACK test.
2298
2299         ; Handle ACK while in open state (also other receive-OK states)
2300 TSI54:  LDB A,[TH$ACK (H)]      ; Get ACK field
2301         MOVE B,XBSUNA(I)        ; Need one CMPSEQ arg in AC
2302                 ; Test: snd.una =< seg.ack =< snd.nxt
2303                 ; If seg.ack < snd.una, go to TSI60 and ignore the ACK.
2304                 ; If seg.ack > snd.nxt, go to TSISAK to drop segment (ACKing)
2305         CMPSEQ B,=<,A,=<,XBSNXT(I),TSI60,TSISAK ; Jump if fail
2306
2307         ; ACK is fine.  Update SND.UNA and clean up retransmit queue.
2308 TSI54X: MOVEM A,XBSUNA(I)       ; Update snd.una
2309         
2310         ; Must check retransmit queue slowly to find right place to flush,
2311         ; if any.
2312         ; Procedure is: (1) pull off 1st thing on queue.
2313         ; (2) If the new 1st thing has a seq # =< snd.una,
2314         ;       then can flush what we pulled off, and try again.
2315         ; (3) otherwise put it back on at front.
2316 TSI54A: MOVE C,A                ; Save ACK # in C
2317 TSI54B: MOVEI Q,XBORTQ(I)       ; Get pointer to retrans q
2318         CALL PKQGF(PK.TCP)      ; Get 1st thing on queue
2319         JUMPE A,TSI54Z          ; None left?  Win!
2320         TRCPKT A,"TSI54B Mabye flush from rexmit Q"
2321         MOVE T,PK.FLG(A)        ; Check packet flags,
2322         TLNN T,(%PKODN)         ; to make sure output was completed.
2323          JRST TSI54Y            ; Not done yet, so don't flush yet.
2324         HRRZ B,XBORTQ(I)        ; Get pointer to next thing
2325         JUMPE B,[CAMN C,XBSNXT(I) ; No next thing, compare with snd.nxt
2326                  JRST TSI54D    ; Equal, can flush!
2327                 JRST TSI54Y]    ; If not equal, must have ack < snd.nxt
2328                                 ; so previous segment can't be flushed.
2329         HLRZ B,PK.TCP(B)        ; Get addr of TCP hdr for 2nd queued segment
2330         LDB B,[TH$SEQ (B)]      ; Get sequence # for it
2331 TSI54C: CMPSEQ B,=<,C,=<,XBSNXT(I),TSI54Y ; See if ACK comes after that #
2332
2333         ; Hurray, matches or exceeds this seq #,
2334         ; So we can flush the seg we pulled off!
2335 TSI54D: TRCPKT A,"TSI54D Flushing from Q"
2336         TLNE T,(%PKPIL)         ; 
2337          JRST [ TLZ T,(%PKNOF)  ; Packet is locked by PI I/O
2338                 MOVEM T,PK.FLG(A)       ; So just say to flush when done.
2339                 JRST TSI54E]
2340         CALL PKTRT
2341 TSI54E: MOVE A,TIME             ; Crock crock, set up new timeout.
2342         ADD A,TCPTMO
2343         MOVEM A,XBORTT(I)
2344         SETZM XBORTC(I)         ; Reset retry counts
2345         SOSGE XBORTL(I)         ; Decrement # segments on retrans q.
2346          BUG HALT,[TCP: Retrans Q count error]
2347         JRST TSI54B             ; Keep going as long as we can.
2348
2349 TSI54Y: MOVEI Q,XBORTQ(I)
2350         CALL PKQPF(PK.TCP)      ; Put back on front of queue
2351 TSI54Z: MOVE A,C                ; Restore ACK # to A.
2352
2353         ; Now see if send window should be updated.
2354         CAMN D,XBSWL1(I)        ; Fast check first, WL1 = SEQ?
2355          JRST TSI55C            ; Yes, go check ACK then
2356         MOVE T,XBSWL1(I)
2357         ADDI T,-1
2358         TLZ T,%MOD32
2359         CMPSEQ XBSWL1(I),<,D,<,T,TSI56  ; Check if wl1 < seq < wl1+xxx
2360         JRST TSI55                      ; Yes, must update window.
2361 TSI55C: MOVE T,XBSWL2(I)
2362         ADDI T,-1
2363         TLZ T,%MOD32
2364         CMPSEQ XBSWL2(I),=<,A,=<,T,TSI56 ; Fall-thru win if snd.wl2 =< seg.ack
2365
2366 TSI55:  MOVEM A,XBSWL2(I)       ; Yes!  Update send window, set WL2 to ACK
2367         MOVEM D,XBSWL1(I)       ; and WL1 to SEQ
2368         LDB B,[TH$WND (H)]
2369         MOVEM B,XBSWND(I)       ; and snd.WND to seg.WND.
2370                                 ; Drop thru
2371
2372         ; Either SND.UNA or SND.WND was probably updated, so lets update
2373         ; SND.AVW also (available window).  The following computes
2374         ; WND - (NXT - UNA) and assumes UNA =< NXT.
2375 TSI56:  MOVE A,XBSNXT(I)
2376         CAMGE A,XBSUNA(I)       ; If need mod 32 wrap,
2377          TLO A,(1_32.)          ; wrap up the number that should be higher.
2378         SUB A,XBSUNA(I)         ; Find NXT-UNA (# bytes not yet acked)
2379         CAIL A,0
2380          CAILE A,177777         ; Make simple check
2381           BUG INFO,[TCP: Bad AVW calc, UNA=],OCT,XBSNXT(I),[NXT=],OCT,XBSUNA(I)
2382         MOVE B,XBSWND(I)
2383         SUBI B,(A)              ; Find # bytes we can still send
2384         CAIGE B,                ; Make sure it's not negative!
2385          SETZ B,
2386         MOVEM B,XBSAVW(I)
2387
2388         ; Done with ACK processing for OPEN state, see if must handle
2389         ; idiosyncracies of other states.
2390 TSI57:  CAIN J,.XSOPN           ; Skip other checks if state is OPEN (normal)
2391          JRST TSI60             ; Go check for URG etc.
2392         CAIN J,.XSCLW
2393          JRST TSI80
2394         CAIN J,.XSFN1
2395          JRST [ SKIPE XBORTQ(I) ; If our FIN is ACK'd, enter FIN-WAIT-2
2396                  JRST TSI60     ; Not yet.
2397                 MOVEI J,.XSFN2  ; Yes, FIN was ACKed, change state.
2398                 HRRM J,XBSTAT(I)
2399                 CALL TCPUSI     ; Call this for any state change.
2400                 LDB T,[XB$ICH (I)]      ; Do we have an input chan?
2401                 JUMPN T,TSI60           ; If so, CLOSE will handle the wrapup.
2402                 MOVE T,TIME     ; No, must set timeout.
2403                 ADDI T,2*60.*30.        ; Use 2*MSL
2404                 MOVEM T,XBORTT          ; set timeout.
2405                 JRST TSI60]
2406         CAIN J,.XSFN2
2407          JRST [         ; If retrans queue empty, transmit-chan CLOSE done.
2408                 JRST TSI60]
2409         CAIN J,.XSCLO
2410          JRST [ SKIPE XBORTQ(I) ; If our FIN is ACK'd,
2411                  JRST TSIF55    ;  No-- flush the segment.
2412                 CALL TSITMW     ; then enter TIME-WAIT state, start timeout.
2413                 JRST TSI80]     ; Then go check for FIN, etc.
2414         CAIN J,.XSCLA           ; LAST-ACK waiting for ACK of our FIN.
2415          JRST [ SKIPE XBORTQ(I) ; If our FIN has been ACK'd,
2416                  JRST TSIF56    ;  No-- flush the segment.
2417                 METER("TCP: FIN acked in .XSCLA")
2418                 CALL TXBFLP     ; Flush the TCB immediately, PI level
2419                 JRST TSIFL]     ; then flush the segment.
2420         BUG CHECK,[TCP: Bad ACK state]
2421
2422         ; Check the URG bit.  The only states which get to this
2423         ; point are OPEN, FIN-WAIT-1, and FIN-WAIT-2.
2424 TSI60:  TLNN E,(TC%URG)         ; Segment has urgent pointer set?
2425          JRST TSI70             ; Nope, on to next step.
2426         LDB A,[TH$UP (H)]       ; Get SEG.UP (urgent ptr from segment)
2427
2428         ; This is where URGENT should be handled!!!!
2429                                 ; Drop through
2430 \f
2431         ; Finally process segment text!
2432         ; Only states OPEN, FIN-WAIT-1 and FIN-WAIT-2 can get here.
2433 TSI70:  TRNE E,%TSIFL           ; If segment being flushed after ACK/URG,
2434          JRST TSIF70            ; flush it now!
2435
2436
2437         LDB A,[PK$TDL (R)]      ; Find # bytes of real data in segment
2438         JUMPLE A,TSI80          ; If none, no text processing.
2439         TLNE E,(TC%FIN)         ; Check that # bytes data == seg.len
2440          JRST [ CAIE A,-1(TT)   ; Must allow for funny non-data FIN.
2441                  JRST TSI71     ; Nope
2442                 JRST TSI72]     ; Yep
2443         CAIE A,(TT)             ; # bytes data should == seg.len
2444 TSI71:   BUG CHECK,[TCP: seglen error]
2445 TSI72:  SKIPE D,XBRWND(I)       ; Note D used for flag,
2446          JRST TSI75             ; and is non-zero if no compaction done.
2447
2448         ; Our window is zero, and technically we should throw away the
2449         ; data now that all RST/ACK/URG processing has been done.  However,
2450         ; we try to see if we can possibly do a little compaction, since
2451         ; the overhead of doing this is a lot less than the overhead
2452         ; of re-processing the re-transmitted segment!
2453         MOVE A,XBINPS(I)        ; Check length of input queue
2454         CAIL A,2                ; Must be at least 2
2455          SKIPN XBITQH(I)
2456           BUG CHECK,[TCP: Wind & Queue both 0]
2457
2458         ; See if it's worth trying to compact the input seg into the
2459         ; last one received (which hasn't yet been seen by MP level)
2460         HLRZ A,XBITQH(I)        ; Get ptr to last input seg on queue
2461         LDB B,[PK$TDO (A)]      ; Get offset to data in old seg
2462         LDB C,[PK$TDL (A)]      ; See how much data is there
2463         LDB T,[PK$TDL (R)]      ; Find # bytes in new segment
2464         ADDI B,(C)              ; Get offset to end of data
2465         MOVEI D,(B)
2466         ADDI D,(T)              ; Get projected total offset
2467         CAML D,XBRMSS(I)        ; Crock method of ensuring enuf room.
2468          JRST TSI17             ; Not enough, we lose.  Lose.  Lose.
2469
2470         ; Win!  We're gonna compact!
2471         METER("TCP: Iseg cmpct")
2472         ADDI C,(T)              ; Get new # bytes for prev seg
2473         DPB C,[PK$TDL (A)]      ; Store it in advance.
2474         HLRZ D,PK.TCP(A)        ; Find addr of TCP header in prev seg
2475         IDIVI B,4
2476         ADDI D,(B)              ; Get addr for BP to end of data
2477         HRL D,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
2478         LDB B,[PK$TDO (R)]      ; Get data offset for new segment
2479         IDIVI B,4
2480         ADDI B,(H)              ; Get addr for BP to start of new data
2481         HRL B,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
2482         ; B/ BP to new data
2483         ; D/ BP to end of old data
2484         ; T/ # bytes of new data
2485         MOVEI A,(T)             ; Save # added data in A
2486 TSI74:  ILDB C,B
2487         IDPB C,D
2488         SOJG T,TSI74
2489         SETZ D,                 ; Clear D to indicate compaction done.
2490         JRST TSI75
2491
2492         ; Can't accept segment data, period.
2493 TSI17:  METER("TCP: Ifl 0-wnd")
2494         JRST TSIFL              ; Flush the seg, sob.
2495
2496 TSI75:  MOVEI B,(TT)
2497         ADDB B,XBRNXT(I)        ; Update rcv.nxt value by adding seg.len
2498         TLZE B,%MOD32
2499          MOVEM B,XBRNXT(I)      ; Updated!
2500         LDB B,[XB$ICH (I)]      ; See if we have an input channel #
2501         JUMPE B,[METER("TCP: IS fl no chan")
2502                 JRST TSI78]     ; No input channel, so just throw away.
2503         MOVEI C,(A)             ; Save # bytes data.
2504         ADDM A,XBINBS(I)        ; Add new bytes to # bytes in input queue
2505         JUMPE D,TSI78           ; If compaction done, that's all...
2506         SKIPE B,XBINPS(I)       ; If no segments previously on queue,
2507          MOVE B,XBIBC(I)        ; or current input buff has zero cnt,
2508                                 ; then will definitely interrupt user later.
2509         AOS XBINPS(I)           ; Bump # segments on queue
2510
2511         ; Check to see how much to reduce window by.
2512         ; Amount is in C (defaults to amount we just received)
2513         CALL TCPRWS             ; Set receive window
2514
2515         ; Finally add segment to queue!
2516         MOVEI A,(R)             ; Set up pointer to packet/segment
2517         MOVEI Q,XBITQH(I)       ; Point to TCP input queue
2518         CALL PKQPL(PK.TCP)      ; Add to end of queue, using TCP links.
2519         JUMPN B,TSI78           ; Check, jump unless had no input before
2520         CALL TXBIST             ; If none, then must definitely change state!
2521         HRLM T,XBSTAU(I)        ; 
2522         CALL TCPUII             ; And always give an input-avail int!
2523
2524         ; Now must send an ACK, or rather arrange for one to be
2525         ; sent soon.  FIN is also checked here, so as to bypass the
2526         ; code which assumes that XBRNXT hasn't been updated (if we are
2527         ; here, it certainly has!)
2528 TSI78:  MOVSI A,(TC%ACK)        ; Set bit asking for ACK to be sent.
2529         IORM A,XBSTAT(I)
2530         TLNN E,(TC%FIN)         ; Perform FIN-bit check
2531          JRST TSI90             ; None, all done with segment!
2532         JRST TSI82              ; FIN exists, handle it (bypass bump of XBRNXT)
2533
2534         ; Lastly check the FIN bit.  Not clear if a bunch of states
2535         ; want to come here from ACK processing or not.
2536         ; Anyway, code assumes could be in any state.
2537 TSI80:  TLNN E,(TC%FIN)
2538          JRST TSI90
2539         CAIG J,.XSSYN
2540          JRST TSIF80            ; Flush if CLOSED, LISTEN, SYN-SENT
2541
2542         ; Advance RCV.NXT over the FIN and send an ACK for it.
2543         AOS A,XBRNXT(I)
2544         TLZE A,%MOD32
2545          MOVEM A,XBRNXT(I)
2546 TSI82:  MOVSI A,(TC%ACK+%XBFIN) ; Set bit asking that ACK be sent, and FIN 
2547         IORM A,XBSTAT(I)        ; was seen.
2548         MOVEI T,.XCFRN          ; Say foreign host closed input side.
2549         CALL TCPUCI
2550
2551         ; Now effect some state changes
2552         CAIE J,.XSOPN           ; If OPEN
2553          CAIN J,.XSSYR          ; or SYN-RCVD
2554           JRST [MOVEI J,.XSCLW  ; Change state to CLOSE-WAIT
2555                 JRST TSI85]
2556         CAIN J,.XSFN1
2557          JRST [ SKIPN XBORTQ(I) ; If our FIN was ACK'd,
2558                  JRST TSI84     ; Go enter TIME-WAIT state
2559                 MOVEI J,.XSCLO  ; Otherwise enter CLOSING state.
2560                 JRST TSI85]
2561         CAIE J,.XSFN2
2562          CAIN J,.XSTMW
2563           JRST TSI84            ; Go to TIME-WAIT
2564         JRST TSI90              ; Any other states just do nothing.
2565
2566 TSI84:  CALL TSITMW             ; Enter TIME-WAIT state, starting 2-MSL timeout
2567         JRST TSI90
2568 TSI85:  HRRM J,XBSTAT(I)        ; Set new state and fall through.
2569         CALL TCPUSI             ; Set user state.
2570
2571         ; Done.  Finally decide whether to keep segment around or not.
2572 TSI90:  HLRZ A,XBITQH(I)        ; Get ptr to last thing on input queue
2573         CAIN A,(R)              ; Same as current seg (ie it was queued?)
2574          RET                    ; Yes, just return!
2575         JRST TSIF90             ; Else drop through to flush the segment.
2576 \f
2577 XSMTRS: OFFSET -.
2578 .XSCLS:: METER("TCP: state CLS")
2579 .XSSYQ:: METER("TCP: state SYQ")
2580 .XSLSN:: METER("TCP: state LSN")
2581 .XSSYN:: METER("TCP: state SYN")
2582 .XSSYR:: METER("TCP: state SYR")
2583 .XSOPN:: METER("TCP: state OPN")
2584 .XSFN1:: METER("TCP: state FN1")
2585 .XSFN2:: METER("TCP: state FN2")
2586 .XSCLW:: METER("TCP: state CLW")
2587 .XSCLO:: METER("TCP: state CLO")
2588 .XSCLA:: METER("TCP: state CLA")
2589 .XSTMW:: METER("TCP: state TMW")
2590 .XSTOT:: OFFSET 0
2591
2592
2593 TSIF01: METER("TCP: ISeg cksm errs ")
2594         JRST TSIFL
2595 TSIF02: METER("TCP: IS zero port/addr")
2596         JRST TSIFL
2597 TSIF03: METER("TCP: IS fl neg data")
2598         JRST TSIFL
2599 ;TSIF10:        ; Flush this later (retain til get new .METER LIST)
2600         METER("TCP: IS fls Seq # err")
2601         JRST TSIFL
2602 TSIF50: METER("TCP: IS fls Seq no ACK ")
2603         JRST TSIFL
2604 TSIF55: METER("TCP: IS fls CLO & FIN not ACKed")
2605         JRST TSIFL
2606 TSIF56: METER("TCP: IS fls CLA & FIN not ACKed")
2607         JRST TSIFL
2608 TSIF70: METER("TCP: IS fls seqerr processed A/U/R")
2609         JRST TSISNE             ; Go respond with ACK
2610 TSIF80: METER("TCP: IS fls FINchk state")
2611         JRST TSIFL
2612 TSIF2A: METER("TCP: IS fls random RST")
2613         JRST TSIFL
2614 TSIF2B: METER("TCP: IS fls Fresh SYN already on SYNQ")
2615         JRST TSIFL
2616
2617 TSIF90: METER("TCP: IS fls processed seg")
2618         JRST TSIFL
2619
2620         ; Come here to flush the datagram/segment and return.
2621 TSIFL:  METER("TCP: Isegs flushed")
2622         MOVEI A,(R)
2623         CALRET PKTRT
2624
2625 ; TSITMW - Routine to enter TIME-WAIT state.
2626 ; TSITM2 is entry point when already in that state.
2627 ; Clobbers T, Q
2628 TSITMW: MOVEI J,.XSTMW
2629         HRRM J,XBSTAT(I)
2630         CALL TCPUSI             ; Alert user if necessary.
2631 TSITM2: SKIPE XBORTQ(I)         ; Unless retransmit still hogs timeout
2632          RET                    ; (if so, return)
2633         MOVE T,TIME             ; then set up 2-MSL timeout.
2634         ADDI T,30.*2.*60.
2635         MOVEM T,XBORTT(I)
2636         RET
2637
2638 ; TSISNE - Sequence number error, segment not acceptable,
2639 ;       return an ACK unless RST was set.
2640
2641 TSISNE: METER("TCP: IS NE seqerr")
2642         TLNE E,(TC%RST)
2643          JRST TSIFL             ; Flush segment if RST was set
2644
2645         ; Send an immediate ACK without data, re-using the
2646         ; packet/segment that R points to.
2647 TSOACK: MOVSI T,(TC%ACK)        ; Send an ACK immediately
2648         TRCPKT R,"TSOACK return ACK in response to out-of-seq ACK"
2649         CALL TSOSNR
2650         RET
2651 \f
2652 ; TSISQ - Jumped to from TCPIS when TCP segment is received that matches
2653 ;       no existing connection.  Check to see if it's a valid connection
2654 ;       request.  If so,
2655 ;       (1) see if it matches any wild listens; if so, process.
2656 ;       (2) see if it's OK to start up a server for it; if so, process.
2657
2658 TSISQ:  TLNE E,(TC%RST) ; If it has RST set,
2659          JRST TSIF2A    ;  Go drop it quietly.
2660         TLNE E,(TC%ACK) ; If ACK, can't be a valid request either
2661          JRST TSISAR    ;  Go send a RST in response (with SEQ=SEG.ACK)
2662         TLNN E,(TC%SYN) ; Anything else had better have a SYN
2663          JRST TSISLR    ;  otherwise send RST with SEQ=0,ACK=SEQ+LEN
2664
2665         ; Okay, we have a promising SYN.  See if it matches any
2666         ; "wild" listens.
2667         METER("TCP: Fresh SYN")
2668         LDB B,[TH$DST (H)]      ; Get desired port #
2669         LDB C,[TH$SRC (H)]      ; Find port it's from 
2670         LDB D,[IP$SRC (W)]      ; and host it's from.
2671         MOVSI I,-XBL
2672 TSISQ2: HRRZ J,XBSTAT(I)        ; Get state for TCB
2673         CAIE J,.XSLSN           ; We're hunting for LISTEN
2674 TSISQ3:  AOBJN I,TSISQ2
2675         JUMPGE I,TSISQ5         ; Jump if no match.
2676         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get our local port (never wild)
2677         CAIE A,(B)              ; It must match desired "dest port"!
2678          JRST TSISQ3            ; Nope, doesn't want this one.
2679         SKIPL XBHOST(I)         ; Aha, very likely will match. Follow thru.
2680          CAMN D,XBHOST(I)
2681           CAIA
2682            JRST TSISQ3          ; Host didn't match.
2683         MOVE A,XBPORT(I)        ; Check remote port field
2684         TRNE A,17               ; Low 4 bits are non-zero if remote wild.
2685          JRST TSISQ4            ; Won!
2686         LDB A,[.BP TH%SRC,A]    ; Not wild, see if it matches request.
2687         CAIE A,(C)              ; Compare our remote with its source.
2688          JRST TSISQ3            ; No, no match here.
2689
2690         ; Matched a wild listen!  Must fill in various stuff.
2691 TSISQ4: MOVEI A,17
2692         ANDCAM A,XBPORT(I)      ; Clear wild bits
2693         DPB C,[.BP TH%SRC,XBPORT(I)]    ; Set remote port #
2694         MOVEM D,XBHOST(I)               ; Set remote host addr
2695         LDB D,[IP$DST (W)]      ; Set local address to whichever address other guy knows
2696         MOVEM D,XBLCL(I)
2697         DPB I,[PK$TCB (R)]      ; Finish setting up context for dispatch
2698         CALL TCPMSS             ; Correct MSS values for specified foreign host
2699         CALL TCPRWS             ; Open up a receive window
2700         JRST TSILS              ; Go handle SYN rcvd for LISTEN.
2701
2702         ; No outstanding listens.  Check the port number, to
2703         ; see if it's something we are likely to service.
2704 TSISQ5: LDB A,[TH$DST (H)]      ; Get destination port #
2705         CAILE A,%TCPMP          ; Fits max port # for RFC service?
2706          JRST TSISLR            ; Naw, barf about it (send RST).
2707         
2708         ; See if we're actually willing to start up a job...
2709         LDB A,[IP$SRC (W)]      ; See who it's from
2710         JSP T,IPLCLH            ; Ask IP if this is one of us
2711          SKIPL TCPUSW           ; It isn't, so make sure we're open for biz
2712           CAIA
2713            JRST TSISLR          ; Sorry charlie (send RST)
2714
2715         ; Okay, we'll take it as SYN-QUEUED!  We know this is a new
2716         ; request, otherwise it would have been matched at TSI02 and
2717         ; dispatched to TSISQQ instead.
2718
2719 ifn 0,[
2720         ;   first see if it's already on the queue!
2721         ; Note that we still have remote host # in D.
2722         SKIPN Q,TCPRQH          ; Get pointer to 1st item on queue
2723          JRST TSISQ7            ; No queue, so not on.
2724         MOVE B,TH$SRC(H)        ; Get req's source/dest ports
2725         MOVE D,IP$SRC(W)        ; and its source addr
2726 TSISQ6: HLRZ T,PK.TCP(Q)        ; Get addr of TCP header from queue
2727         HLRZ C,PK.IP(Q)         ; and addr of IP header
2728         CAIE T,
2729          CAIN C,
2730           BUG CHECK,[TCP: SYNQ smashed]
2731         CAMN B,TH$SRC(T)        ; Same ports?
2732          CAME D,IP$SRC(C)       ; Same host?
2733           CAIA                  ; No
2734            JRST TSIF2B          ; Yes, assume SYN is a dup, ignore it.
2735         HRRZ Q,PK.TCP(Q)        ; Get next thing on pending queue
2736         JUMPN Q,TSISQ6
2737
2738         ; Not on queue, let's try to add it.
2739 TSISQ7: MOVE A,TCPRQN           ; Find # of things on queue already
2740         CAIL A,%TCPMQ           ; Keep its length reasonable
2741          JRST TSISQ8            ; Sigh, ran out.
2742         HRROI T,NTSYNL          ; OK, now try loading job up!
2743         CALL NUJBST             ; Queue request for job TCPRFC
2744          JRST TSISLR            ; Bah, no job slots or something!
2745         MOVEI A,(R)             ; It's on the way!  Queue the SYN now.
2746         MOVEI Q,TCPRQH
2747         CALL PKQPL(PK.TCP)      ; Add onto end of pending-RFC queue.
2748 ] ;ifn 0
2749
2750         MOVSI I,-XBL
2751 TSISQ6: SKIPN XBUSER(I)
2752          SKIPE XBSTAT(I)
2753           AOBJN I,TSISQ6
2754         JUMPGE I,TSISQ8         ; Jump if no free slots.
2755         CALL TXBINI             ; Got one, might as well verify it's cleared.
2756         MOVE A,TCPRQN           ; Find # of things on queue already
2757         CAIL A,XBL/2            ; Keep number reasonable
2758          JRST TSISQ8            ; Sorry, too many.
2759         HRROI T,NTSYNL          ; Now see if we can load up handler job.
2760         CALL NUJBST             ; Do it
2761          JRST TSISLR            ; Ugh, couldn't start new job...
2762         MOVEI J,.XSSYQ
2763         MOVEM J,XBSTAT(I)       ; Set state SYN-QUEUED
2764         LDB A,[IP$SRC (W)]
2765         MOVEM A,XBHOST(I)       ; Set up host #
2766         MOVE A,TH$SRC(H)        ; and ports
2767                                 ; Don't need to set XBLCL, won't be looked at
2768         MOVEM A,XBPORT(I)       ; That's all we need for now.
2769         CALL TCPMSS             ; Might as well keep these right even though
2770         CALL TCPRWS             ;  this TCB will be flushed when conn opens.
2771         MOVE A,TIME
2772         ADDI A,10.*30.          ; Let it stay queued for 10 seconds.
2773         MOVEM A,XBORTT(I)
2774         MOVEI Q,XBITQH(I)       ; Put the segment on input queue for slot.
2775         MOVEI A,(R)
2776         CALL PKQPF(PK.TCP)
2777
2778         HRRZM I,TCPRQL          ; Save # of last SYN queued.
2779         AOS TCPRQN              ; And increment count of entries.
2780         METER("TCP: Srvjob starts")
2781         RET                     ; All done!
2782
2783 TSISQ8: BUG INFO,[TCP: SYN queue full]
2784         JRST TSISLR             ; Sigh.
2785
2786
2787 ; TSISQQ - Come here when segment received that matches an
2788 ;       existing port/host which is in SYN-QUEUED state.
2789
2790 TSISQQ: TLNE E,(TC%RST)         ; Is it an RST?
2791          JRST [ CALL TSISQF     ; Yeah, flush the queued SYN.
2792                 JRST TSIFL]     ; and drop segment.
2793         TLNE E,(TC%ACK)         ; An ACK?  That's illegal etc...
2794          JRST [ CALL TSISQF     ; Flush the queued SYN,
2795                 JRST TSISAR]    ; and send a RST in response.
2796         TLNN E,(TC%SYN)         ; Anything else better be a SYN
2797          JRST [ CALL TSISQF     ; else send RST.
2798                 JRST TSISLR]
2799         JRST TSIF2B             ; Most likely a duplicate SYN, so just
2800                                 ; flush it and return.
2801
2802         ; Flush TCB for a queued SYN.
2803 TSISQF: SETZM XBSTAT(I)
2804         SETZM XBPORT(I)
2805         SETZM XBHOST(I)
2806         SETZM XBORTT(I)
2807         SKIPE XBITQH(I)
2808          CALL TXBIFL
2809         SOSGE TCPRQN
2810          BUG HALT
2811         RET
2812
2813 \f
2814 ; TSISAR - Respond to current segment by sending a RST with
2815 ;       SEQ=SEG.ACK.  Re-uses the current segment's packet buffer.
2816 ;       R, W, H set up for PE, IP, and TCP.
2817 ;       E has seg flags.  May not be anything in I, so re-use fields
2818 ;       from given packet!
2819 ; TSISAQ - like TSISAR but just drops segment if it has RST in it.
2820 ; TSISLR - like TSISAR, but SEQ=0, ACK=SEG.SEQ+SEG.LEN
2821 ;       This is used when responding to segments without an ACK, i.e.
2822 ;       initial SYNs.
2823
2824 TSISLR: METER("TCP: times at TSISLR")
2825         LDB A,[TH$SEQ (H)]      ; Get SEQ.  Assume TT still valid.
2826         ADDI A,(TT)             ; ACK=SEG.SEQ+SEG.LEN
2827         LSH A,4                 ; Left justify it.
2828         SETZ D,                 ; SEQ=0
2829         MOVSI T,(TC%RST+TC%ACK)
2830         JRST TSISA2
2831
2832 TSISAQ: TLNE E,(TC%RST)         ; Here, if incoming seg was RST,
2833          JRST TSIFL             ; just ignore, don't respond.
2834 TSISAR: METER("TCP: times at TSISAR")
2835         MOVE D,TH$ACK(H)        ; Use SEG.ACK for SEQ
2836         MOVSI T,(TC%RST)
2837
2838         ; Here, A, D, and T must be set up.
2839 TSISA2: SETZ B,
2840         LDB C,[TH$SRC (H)]      ; Get source port
2841         DPB C,[.BP TH%DST,B]    ; Use as dest port
2842         LDB C,[TH$DST (H)]      ; Get dest
2843         DPB C,[.BP TH%SRC,B]    ; Use as... you guessed it.
2844         PUSH P,IP$DST(W)        ; Which of my addresses to claim to be from
2845         MOVE C,IP$SRC(W)
2846
2847 ;       A/ ACK field (left justified)
2848 ;       B/ <loc port><rem port> (left justified)
2849 ;       C/ remote host (left justified)
2850 ;       D/ SEQ field (left justified)
2851 ;       R/ PE ptr to packet responding to
2852 ;       T/ flags to use
2853
2854
2855         SETZ I,
2856         CALL TSOINI             ; Initialize W,H,PK.IP(R),PK.TCP(R),PK.TCI(R)
2857                                 ; Note everything in PK.TCI will be wrong.
2858         MOVEM C,IP$DST(W)       ; Store remote host
2859         MOVEM B,TH$SRC(H)       ; Store loc/rem ports
2860         MOVEM D,TH$SEQ(H)       ; Deposit new SEQ field
2861         TLNN T,(TC%ACK)         ; If sending an ACK
2862          SETZ A,
2863         MOVEM A,TH$ACK(H)       ; Deposit ACK field.
2864         TLO T,240000            ; Set IHL
2865         MOVEM T,TH$CTL(H)       ; Deposit segment flags
2866         MOVEI A,5*4
2867         DPB A,[IP$TOL (W)]      ; Say length just a std TCP header.
2868         POP P,IP$SRC(W)
2869         CALL THCKSM             ; Figure TCP checksum
2870         DPB A,[TH$CKS (H)]      ; Deposit in
2871         CALL IPKSND             ; Put this buffer on IP output queue!
2872         RET
2873
2874 \f
2875 ; TSILS - Segment received for this connection while in LISTEN state.
2876 ;       
2877 TSILS:  METER("TCP: Segs rcvd in LSN")
2878         TLNE E,(TC%RST)         ; Ignore any RSTs.
2879          JRST TSIFL
2880         TLNE E,(TC%ACK)         ; ACKs are bad too.
2881          JRST TSISAR            ;  Respond with a RST to them.
2882         TLNN E,(TC%SYN)         ; It should be a SYN.
2883          JRST TSIFL             ;  If not, just flush.
2884
2885         ; We've received a SYN that should be valid.  Set up for
2886         ; SYN-RCVD state.  Note that we ignore security/precedence
2887         ; except to remember it so our transmits look OK.
2888         ; NOTE!!! TSILSX is an entry point from MP level TCPOPN call,
2889         ; which is used to hook up a user OPEN to a matching SYN on
2890         ; the pending-RFC queue!
2891         METER("TCP: SYN in LSN")
2892 TSILSX: LDB D,[TH$SEQ (H)]      ; Get sequence number
2893         LDB A,[TH$WND (H)]
2894         MOVEM A,XBSWND(I)       ; Initialize send window
2895         MOVEM A,XBSAVW(I)       ; and available window
2896         MOVEM D,XBSWL1(I)       ; Save seg.seq used for last window update
2897         LDB A,[TH$ACK (H)]
2898         MOVEM A,XBSWL2(I)       ; Save seg.ack used for last window update
2899         ADDI D,1
2900         TLZ D,%MOD32            ; Get seg.seq+1
2901         MOVEM D,XBRNXT(I)       ; Store as initial RCV.NXT
2902         CALL TCPISS             ; Select a new ISS in A (Initial Send Seq#) 
2903         MOVEM A,XBSUNA(I)       ; Set SND.UNA to ISS
2904 ;       ADDI A,1
2905 ;       TLZ A,%MOD32
2906         MOVEM A,XBSNXT(I)       ; And SND.NXT also; assume that process of
2907                                 ; sending it will increment by 1.
2908
2909         ; Check for TCP options at this point, and process if present
2910         LDB A,[TH$THL (H)]      ; TCP header length
2911         CAILE A,%TCPHL          ; If default, no options present
2912          CALL TCPPIO            ; Else, process input options
2913
2914         ; Nasty business - put together and send a segment with
2915         ; seq=ISS,ack=RCV.NXT,ctl=SYN+ACK.
2916         ; For now we can assume that initial SYNs will never
2917         ; contain text, and so we don't have to queue it up.
2918         ; Alternatively can hope that remote site is clever about
2919         ; retransmitting!
2920         ; This is because if we don't need to keep received segment
2921         ; around, can just re-use it.
2922         MOVSI T,(TC%SYN+TC%ACK)
2923         TRCPKT R,"TSISLX Reflecting incoming SYN with SYN"
2924         CALL TSOSSN             ; Fire off SYN. Sends MSS option too.
2925         MOVEI J,.XSSYR          ; Change state to SYN-RCVD.
2926         HRRM J,XBSTAT(I)
2927         CALL TCPUSI             ; Set user state.
2928         RET
2929
2930 ; TCPISS - Select new ISS, return in A
2931
2932 TCPISS: MOVE A,TIME
2933         LSH A,13.
2934 TCPIS2: TLZ A,%MOD32
2935         CAMN A,TISSLU   ; Same as last used?
2936          JRST [ AOS A,TISSC
2937                 ANDI A,17
2938                 LSH A,9.
2939                 ADD A,TISSLU
2940                 JRST TCPIS2]    ; Jump to mask off and test again.
2941         MOVEM A,TISSLU
2942         RET
2943
2944 ; TCPPIO - Process TCP options from incoming segment.
2945 ;       This is only checked for SYN segments because the only interesting
2946 ;       option (Max Segment Size) is only sent with SYN segments
2947 ;
2948 ;       R/ Pkt buffer
2949 ;       I/ TCB Index
2950 ;       H/ TCP Header
2951 ;       A/ TCP header size in 32-bit words
2952
2953 TCPPIO: SUBI A,%TCPHL
2954         LSH A,2                 ; Options length in bytes
2955         MOVE B,[TH$OPT (H)]     ; BP to start of options
2956 TCPPIL: SKIPG A                 ; Anything left?
2957          RET                    ; Nope, done
2958         ILDB C,B                ; Get option type
2959         CAIL C,TCPPIS           ; In range?
2960          RET                    ; Have to give up if unknown option
2961         JRST @TCPPIT(C)
2962
2963 TCPPIT: TCPPI0
2964         TCPPI1
2965         TCPPI2
2966 TCPPIS==.-TCPPIT
2967
2968         ;End of option list
2969 TCPPI0: RET
2970
2971         ;NOP
2972 TCPPI1: SOJA A,TCPPIL           ; Decrement length and loop
2973
2974         ;Max Seg Size   TYPE ? LENGTH ? MSB ? LSB
2975 TCPPI2: ILDB C,B                ; Get length
2976         SUB A,C                 ; Count it
2977         ILDB C,B                ; Get 16-bit quantity, updating B
2978         LSH C,8.
2979         ILDB D,B
2980         ADD C,D                 ; Now contains foreign MSS request
2981         CAMGE C,XBSMSS(I)       ; Don't exceed our own limits!
2982          MOVEM C,XBSMSS(I)      ; Set new value in TCB
2983         JRST TCPPIL
2984
2985 \f
2986 ; TSISS - Segment received while in SYN-SENT state.
2987 ;       Note that being in this state implies that there is one
2988 ;       segment on the retransmit queue, which must be the initial SYN
2989 ;       that we sent.
2990
2991 TSISS:  METER("TCP: Segs rcvd in SYN-SENT")
2992         LDB D,[TH$SEQ (H)]      ; Get SEG.SEQ
2993         TLNN E,(TC%ACK)         ; Has an ACK?
2994          JRST TSISS2            ; Nope, it better be RST or SYN.
2995
2996         ; See if our SYN has been ACKed. Since we only send SYNs
2997         ; without data, this just means a test for SEG.ACK = SND.NXT.
2998         LDB B,[TH$ACK (H)]      ; Have ACK. Get ack field
2999         CAME B,XBSNXT(I)        ; It should ACK our initial SYN
3000          JRST TSISAQ            ; If not, send a RST.
3001 ;       MOVE A,XBSUNA(I)        ; snd.una =< seg.ack =< snd.nxt ?
3002 ;       CMPSEQ A,=<,B,=<,XBSNXT(I),TSISAQ       ; If not good, send RST.
3003
3004 TSISS2: TLNE E,(TC%RST)         ; Check for RST
3005          JRST [ TLNN E,(TC%ACK) ; Ugh, have RST.  Did we also get good ACK?
3006                  JRST TSIFL     ; No, can just flush this segment.
3007                 MOVEI T,.XCRFS  ; Yeah, our SYN is being refused, so
3008                 CALL TCPUC      ; say this is close-reason.
3009                 JRST TSIRST]    ; Then must go abort connection.
3010
3011         ; Here we get to check security/precedence.  Hurray.
3012         ; We should just copy the seg values, so as to fake sender out.
3013
3014         ; Now finally check the SYN bit!
3015         TLNN E,(TC%SYN)         ; Must be set
3016          JRST TSIFL             ; Neither RST nor SYN?  Flush it.
3017
3018         ; It's a SYN.  Update our send params from its values.
3019         ; We will either send an ACK or another SYN; in both cases the
3020         ; SYN segment currently on the retransmit queue should be flushed.
3021         MOVEI Q,XBORTQ(I)       ; Point to retrans q
3022         CALL PKQGF(PK.TCP)      ; Pluck off 1st thing
3023         SOSN XBORTL(I)          ; Verify none left on queue
3024          CAIN A,                ; and something was there!
3025           BUG CHECK,[TCP: SYN-SENT retrans Q bad]
3026         JUMPE A,TSISS3          ; Just for robustness
3027         TRCPKT A,"TSISS2 Flushing our SYN from rexmit Q"
3028         MOVE T,PK.FLG(A)
3029         TLNE T,(%PKPIL)         ; See if packet locked by PI I/O
3030          JRST [ TLZ T,(%PKNOF)  ; Yeah, so just say to flush when done.
3031                 MOVEM T,PK.FLG(A)
3032                 JRST .+2]       ; Skip over the freecall
3033         CALL PKTRT              ; Flush SYN packet
3034         SETZM XBORTT(I)         ; and flush timeout.
3035
3036 TSISS3: LDB A,[TH$WND (H)]
3037         MOVEM A,XBSWND(I)       ; Initialize send window
3038         MOVEM A,XBSAVW(I)       ; and available window
3039         MOVEM D,XBSWL1(I)       ; Save seg.seq used for last window update
3040         LDB A,[TH$ACK (H)]
3041         MOVEM A,XBSWL2(I)       ; Save seg.ack used for last window update
3042         ADDI D,1
3043         TLZ D,%MOD32
3044         MOVEM D,XBRNXT(I)       ; Set RCV.NXT to SEQ+1
3045
3046         ; Process segment options in case sender specified MSS
3047         LDB A,[TH$THL (H)]      ; TCP header length
3048         CAILE A,%TCPHL          ; If default, no options present
3049          CALL TCPPIO            ; Else, process input options
3050
3051         TLNN E,(TC%ACK)
3052          JRST TSISS4
3053         LDB A,[TH$ACK (H)]      ; If ACK also present, (known acceptable)
3054         MOVEM A,XBSUNA(I)       ; Set SND.UNA to SEG.ACK.
3055
3056         ; Here must test if SND.UNA > ISS (our SYN has been ACKed).
3057         ; But this was already checked just before TSISS2.
3058         MOVSI T,(TC%ACK)        ; Hurray, we're open!  Must ACK the SYN
3059         TRCPKT R,"TSISS3 ACK SYN to open conn"
3060         CALL TSOSNR             ; (Re-using its segment)
3061         MOVEI J,.XSOPN          ; Hurray, we're open now!
3062         HRRM J,XBSTAT(I)
3063         CALL TCPUSI             ; Update user state
3064         RET
3065
3066         ; Our SYN not ACKed yet, so enter SYN-RCVD state.
3067 TSISS4:
3068         ; Must go send seq=ISS,ack=RCV.NXT,ctl=SYN+ACK
3069         LDB D,[TH$SEQ (H)]      ; Get sequence number
3070         ADDI D,1
3071         TLZ D,%MOD32            ; Get seg.seq+1
3072         MOVEM D,XBRNXT(I)       ; Store as initial RCV.NXT
3073         SOSGE A,XBSUNA(I)       ; Set SND.UNA to ISS
3074          JRST [ MOVEI A,1
3075                 MOVEM A,XBSUNA(I)
3076                 JRST .+1]
3077         MOVEM A,XBSNXT(I)       ; And SND.NXT also; assume that process of
3078                                 ; sending it will increment by 1.
3079         MOVSI T,(TC%SYN+TC%ACK)
3080         TRCPKT R,"TSISS4 ACK and re-SYN SYN-SENT conn"
3081         CALL TSOSSN             ; Fire off SYN/ACK with MSS option included.
3082         MOVEI J,.XSSYR          ; Change state to SYN-RCVD.
3083         HRRM J,XBSTAT(I)
3084         CALL TCPUSI             ; Set user state.
3085         RET
3086 \f
3087 ; TSIRST - valid RST segment received (not in LISTEN).
3088 ;       Basically must flush the connection, signal user, etc.
3089
3090 TSIRST: METER("TCP: Valid RSTs")
3091         CALL TXBFLP             ; Flush the TCB immediately, PI level
3092         MOVEI T,.XCRST          ; Say fgn host reset stuff
3093         CALL TCPUC              ; as "close reason"
3094         CALRET TSIFL            ; Flush segment.
3095 \f
3096 ; TSISYN - SYN segment received.
3097 ;       If in window, error - send a RST and close things up.
3098 ;       If not in window, return an ACK as for TSISNE.
3099
3100 TSISYN: METER("TCP: Random SYN")
3101
3102         CALRET TSIFL
3103
3104 ; TSISRA - Bad ACK seen while in SYN-RCVD state,
3105 ;       send a RST.
3106
3107 TSISRA: METER("TCP: Bad ACK in SYR")
3108         CALRET TSIFL
3109
3110 ; TSISAK - Received ACK for something not yet seen, send ACK and
3111 ;       drop segment.
3112 TSISAK: METER("TCP: ACK for nxm")
3113         CALRET TSIFL
3114
3115 ; TSIATW - Received ACK while in TIME-WAIT state.  This should be
3116 ;       a re-transmit of the remote FIN.  ACK it, and restart
3117 ;       2-MSL timeout.
3118
3119 TSIATW: METER("TCP: ACK in .XSTMW")
3120         MOVSI T,(TC%ACK)
3121         TRCPKT R,"TSIATW ACK send in TIME-WAIT"
3122         CALL TSOSNR             ; Send simple ACK in response.
3123         JRST TSITM2             ; and restart 2-MSL timeout.
3124 \f
3125 SUBTTL TCP Send output segment
3126
3127 ; Send TCP output segment.
3128 ; Send output (usually data) segment, for connection indexed by I.
3129 ; Note this differs from TSISAR etc. which don't have any active connection,
3130 ; thus no valid I.  As much context as possible is taken from the
3131 ; TCB tables indexed by I.
3132 ; In particular, the %XBCTL flags are examined to see if anything should
3133 ; be added to the outgoing segment, other than what was requested in the
3134 ; call.
3135
3136 ; Sequence space variables are updated.
3137 ; The following possibilities are independently possible:
3138 ;       Re-using packet / using fresh packet
3139 ;       Uses seq space (must retrans) / no seq space used
3140 ;
3141 ; TSOSND - send output segment while connection established
3142 ;       R/ PE ptr to packet,
3143 ;               PK.BUF, PK.IP and PK.TCP must be set.
3144 ;               If these were not initialized by TSOINI so as to get
3145 ;               the right offsets, you will probably lose.
3146 ;               PK.TCI should have the # bytes of data and offset.
3147 ;       I/ TCB index
3148 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3149
3150 ; TSOSNR - Just sends a data-less "reply" type segment using
3151 ;       TCB's sequence space vars.  Seq=snd.nxt, ack=rcv.nxt, etc.
3152 ;       R/ PE ptr to packet (packet will be smashed and re-used)
3153 ;       I/ TCB index
3154 ;       T/ flags to use (Neither ACK nor %XBCTL will be added automatically!)
3155
3156 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3157
3158 TSOSNR: CALL TSOINI     ; Initialize (sets up W,H PK.IP,PK.TCP,PK.TCI)
3159         SETZ TT,        ; Say zero bytes of real data
3160         DPB TT,[PK$TDL (R)]     ; and make sure packet entry reflects this.
3161         JRST TSOSN      ; Jump in to do it.
3162
3163
3164 ; TSOSSN - Send an initial SYN segment. No data, but add a TCP
3165 ;       MSS option set from XBRMSS(I), and using TCB's sequence space
3166 ;       vars.  Seq=snd.nxt, ack=rcv.nxt, etc.
3167 ;       R/ PE ptr to packet (packet will be smashed and re-used)
3168 ;       I/ TCB index
3169 ;       T/ flags to use (None, including SYN, will be added automatically)
3170
3171 ; Clobbers A,B,C,D,E,W,H,Q,T,TT
3172
3173 TSOSSN: CALL TSOINI             ; Initialize (sets up W,H PK.IP,PK.TCP,PK.TCI)
3174         MOVE TT,XBRMSS(I)       ; Max seg size we would like
3175         LSH TT,4                ; 32-bit option
3176         IOR TT,TSOMSO           ; Add in type and length fields of option
3177         MOVEM TT,TH$OPT(H)      ; Write it. Damn well better be first option.
3178         LDB TT,[PK$TDO (R)]     ; Get current TCP header size
3179         ADDI TT,4               ; Adding 4-byte option
3180         DPB TT,[PK$TDO (R)]
3181         SETZ TT,                ; Say zero bytes of real data
3182         DPB TT,[PK$TDL (R)]     ; and make sure packet entry reflects this.
3183         JRST TSOSN              ; Jump in to do it.
3184
3185 TSOMSO: .BYTE 8 ? 2 ? 4 ? 0 ? 0 ? .BYTE ; Option 2, length 4, two data words
3186
3187 TSOSND: MOVSI T,(TC%ACK)        ; Simple data segment
3188         IOR T,XBSTAT(I)         ; Plus whatever is being requested.
3189         HLRZ W,PK.IP(R)         ; Get ptr to IP header
3190         HLRZ H,PK.TCP(R)        ; and TCP header
3191         LDB TT,[PK$TDL (R)]     ; Get # bytes of data
3192 ;       LDB A,[PK$TDO (R)]      ; Get offset of data
3193 ;       ADDI TT,(A)             ; Now have # bytes past std hdr length.
3194
3195 ; TSOSN - Entry point if W, H, and TT already set up.
3196 ;       I/ TCB index
3197 ;       T/ flags for segment
3198 ;       R/ PE ptr (PK.BUF, PK.IP, PK.TCP, PK.TCI must all be set)
3199 ;       W/ IP header ptr
3200 ;       H/ TCP header ptr
3201 ;       TT/ # bytes of data (real data, not including header or SYN/FIN)
3202 ; Clobbers A,B,C,D,E,TT,T,Q and updates various TCB data.
3203
3204 ; This code assumes TT is the bytes of DATA only.
3205 ; Must store the out-of-TCP info in the IP header field, so that
3206 ; the checksum and IPKSND routines will find it there.
3207 ; This info consists of:
3208 ;       IP$SRC - Source address
3209 ;       IP$DST - Dest address
3210 ;       IP$TOL - TCP segment length including header
3211 ;       IP$PTC - Protocol number (needn't set, assumes %PTCTC always)
3212
3213 TSOSN:  METER("TCP: Out segs")
3214         AND T,[TH%CTL]          ; Ensure non-flag bits are flushed.
3215         MOVE A,T
3216         ANDCAB A,XBSTAT(I)              ; Turn off these request bits
3217         TLNE A,(TH%CTL)                 ; Any request bits left?
3218          JRST TSOSN2                    ; Yeah, can't turn off "now" bit.
3219         MOVSI A,(%XBNOW)                ; Satisfied everything, so flush
3220         ANDCAM A,XBSTAT(I)              ; the send-immediately bit.
3221
3222 TSOSN2: LDB A,[PK$TDO (R)]              ; Bytes of header
3223         ADDI A,(TT)                     ; Add bytes of data
3224         DPB A,[IP$TOL (W)]              ; Store in IP length field
3225         MOVE A,XBLCL(I)
3226         LSH A,4
3227         MOVEM A,IP$SRC(W)               ; Set source host
3228         MOVE A,XBHOST(I)
3229         LSH A,4
3230         MOVEM A,IP$DST(W)               ; Set dest host
3231
3232         ; Out-of-TCP info set up, now build the real TCP header.
3233         LDB A,[.BP TH%DST,XBPORT(I)]    ; Get port sending from (local)
3234         DPB A,[TH$SRC (H)]
3235         LDB A,[.BP TH%SRC,XBPORT(I)]    ; Get port to send to
3236         DPB A,[TH$DST (H)]
3237         MOVE A,XBSNXT(I)                ; Get sequence number to use
3238         LSH A,4
3239         MOVEM A,TH$SEQ(H)               ; Set SEQ field
3240         TLNN T,(TC%ACK)                 ; Check flags, sending ACK?
3241          TDZA A,A                       ;   If not, use zero field anyway.
3242           MOVE A,XBRNXT(I)              ; Get ack number to use
3243         LSH A,4
3244         MOVEM A,TH$ACK(H)               ; Set ACK field
3245
3246         SKIPE A,XBSUP(I)                ; Urgent data being sent?
3247          JRST [ TLO T,(TC%URG)          ; Yes!  Say urgent pointer signif
3248                 METER("TCP: Urgent dgms")
3249                 MOVNI B,(TT)
3250                 ADDB B,XBSUP(I)         ; Adjust pointer as result of data sent
3251                 CAIGE B,
3252                  SETZM XBSUP(I)
3253                 LSH A,4
3254                 JRST .+1]
3255         MOVEM A,TH$UP(H)                ; Set urgent pointer if any
3256
3257         MOVE A,XBRWND(I)                ; Get our current receive window
3258         LSH A,4
3259         IOR A,T                         ; Add in caller's flags
3260         LDB B,[PK$TDO (R)]              ; Header length in bytes
3261         LSH B,-2                        ; TCP wants length in 32-bit words
3262         DPB B,[<.BP TH%THL,A>]
3263         MOVEM A,TH$THL(H)               ; Store header len, flags, window
3264
3265         PUSH P,TT                       ; Goddam checksum clobberage
3266         CALL THCKSM                     ; Now figure out checksum
3267         POP P,TT
3268         DPB A,[TH$CKS (H)]
3269
3270         ; TCP header set up.  Now update our TCB connection vars to
3271         ; account for the stuff we're sending.
3272         TLNE T,(TC%SYN)                 ; Now find new seq # (SND.NXT)
3273          ADDI TT,1                      ; SYN counts as 1 octet
3274         TLNE T,(TC%FIN)                 ; So does a FIN
3275          ADDI TT,1
3276         JUMPLE TT,TSOSN8                ; If not actually using seq space, skip
3277                                         ; a bunch of update/retrans stuff.
3278
3279         ; We're using up some sequence space!  Must update avail window,
3280         ; and put the segment on retransmit queue.
3281         MOVE A,XBSAVW(I)                ; Must update avail send window
3282         SUBI A,(TT)
3283         CAIGE A,                        ; If window becomes negative,
3284          SETZ A,                        ; keep it at zero.
3285         MOVEM A,XBSAVW(I)
3286         ADD TT,XBSNXT(I)                ; Get new SND.NXT
3287         TLZ TT,%MOD32
3288         MOVEM TT,XBSNXT(I)
3289         SKIPN XBORTT(I)                 ; Retrans timeout already set?
3290          JRST [ MOVE A,TIME
3291                 ADD A,TCPTMO            ; Make it 5 sec for now.
3292                 MOVEM A,XBORTT(I)
3293                 SETZM XBORTC(I)         ; Clear count of retries.
3294                 JRST .+1]
3295         MOVSI A,(%PKNOF)                ; Don't free packet when output done
3296         IORM A,PK.FLG(R)
3297         TRCPKT R,"TSOSND Pkt w/seq space added to retransmit queue"
3298         MOVEI A,(R)                     ; Arg to PKQPL, A/ PE ptr
3299         MOVEI Q,XBORTQ(I)               ; Arg to PKQPL, Q/ queue hdr ptr
3300         CALL PKQPL(PK.TCP)              ; Put on TCP retrans queue
3301         AOS XBORTL(I)                   ; Bump count of segs on queue
3302
3303 TSOSN8: CALL IPKSND                     ; Put on IP output queue
3304         RET
3305 \f
3306 SUBTTL TCP Retransmit and Timeout
3307
3308 Comment |
3309         The following things in TCP need some sort of timeout:
3310         Retransmit output segment if not ACKed (removed) within RT sec
3311         Timeout to abort connection if retransmission fails for UT sec
3312         Timeout to ACK incoming data (ie avoid ACKing immediately,
3313                 wait for more output or input).
3314         Timeout during TIME-WAIT to flush connection.
3315 |
3316
3317 ; TCPCLK - This routine is called by 1/2-sec "slow" clock.  What it has to do
3318 ;       is scan all active TCB's for the following conditions:
3319 ;       (1) Retransmit timeout has expired, must resend something.
3320 ;               or TIME-WAIT timeout has expired.
3321 ;       (2) An ACK must be sent, either by sending the current output
3322 ;               buffer, or by generating an ACK without data.
3323
3324 EBLK
3325 TCLKRC: 0               ; Count of segs compacted in pass over a retrans Q
3326 BBLK
3327
3328 TCPCLK: SKIPN TCPUP             ; Do nothing if turned off.
3329          RET
3330         MOVSI I,-XBL
3331         CONO PI,NETOFF
3332         SKIPA A,TIME
3333 TCLK05:  SKIPA A,TIME
3334
3335 TCLK10: SKIPN B,XBSTAT(I)
3336          JRST TCLK15
3337         SKIPE C,XBORTT(I)
3338          CAMG A,C
3339           CAIA
3340            JRST TCLK20          ; Retrans timeout
3341 TCLK12: TLNE B,(TH%CTL+%XBNOW)  ; Any flags set?
3342          JRST TCLK50            ; Wants ACK sent
3343 TCLK15: AOBJN I,TCLK10
3344         CONO PI,NETON
3345         RET
3346 TCLK16: MOVE A,TIME
3347         AOBJN I,TCLK10
3348         CONO PI,NETON
3349         RET
3350
3351         ; Come here for timeout of some sort.
3352 TCLK20: SKIPE XBORTQ(I)         ; If a retrans queue exists,
3353          JRST TCLK22            ; then assume it was a retrans timeout.
3354         MOVEI C,(B)             ; No retrans Q, probably a TIME-WAIT one?
3355         CAIN C,.XSTMW           ; State TIME-WAIT?
3356          JRST [ METER("TCP: Time-Wait timeout")
3357                 CALL TXBFLP     ; Flush the TCB completely, PI level
3358                 JRST TCLK16]
3359         CAIN C,.XSSYQ           ; State SYN-QUEUED?
3360          JRST [ METER("TCP: SYQ timeout")
3361                 CALL TSISQF     ; Flush the queued SYN.
3362                 JRST TCLK16]
3363         CAIN C,.XSFN2           ; State FIN-WAIT-2?
3364          JRST TCLK21
3365         METER("TCP: Random timeout")    ; Sigh.
3366         SETZM XBORTT(I)                 ; Flush whatever it was.
3367         JRST TCLK16
3368
3369 TCLK21: METER("TCP: FN2 timeout")
3370         CALL TXBFLP     ; Flush the TCB completely, PI level
3371         SKIPE XBUSER(I) ; Shouldn't still have anything open.
3372          BUG CHECK,[TCP: FN2 timo with active user]
3373         JRST TCLK16
3374
3375 TCLK22: METER("TCP: Retrans")
3376         AOS C,XBORTC(I)         ; Retrans timeout.  Send it again.
3377         SKIPE D,XBORTP(I)       ; Has user set any retrans params?
3378          JRST [ JRST TCLK25]    ; Yes! For now, non-Z means skip abort check.
3379         CAILE C,%TCPMR          ; Tried too many times?
3380          JRST TCLK80            ; Ugh, abort the connection!
3381         SKIPN R,XBORTQ(I)
3382          JRST [ SETZM XBORTT(I) ; If nothing on queue,
3383                 JRST TCLK12]    ; just reset the timeout to nothing.
3384         SKIPGE A,PK.FLG(R)      ; Ensure that packet isn't being output now
3385          JRST TCLK25            ; Still being output??  Reset timeout.
3386         ; Note that we don't check to see whether segment has already
3387         ; been transmitted, on the theory that compaction is going to
3388         ; pay off anyway.
3389         HLRZ W,PK.IP(R)
3390         HLRZ H,PK.TCP(R)
3391         SETZM TCLKRC            ; Clear compaction count.
3392
3393         ; Looks like we have to retransmit.  Try to compact up as much
3394         ; stuff as possible into a single segment; this gets a bit
3395         ; hairy.  Note that we compact as much as we can, ignoring the
3396         ; %PKPIL and %PKODN bits (except for setting the appropriate flush
3397         ; flags).
3398         TRCPKT R,"TCLK30 Segment being retransmitted"
3399 TCLK30: HRRZ J,PK.TCP(R)        ; Get pointer to succeeding segment
3400         JUMPE J,TCLK39          ; If none following, can't compact (ignore
3401                                 ; possibility of adding XBOCOS for now)
3402         LDB B,[PK$TDO (R)]      ; Get 1st offset
3403         LDB C,[PK$TDL (R)]      ; Get 1st length
3404         LDB T,[PK$TDL (J)]      ; Get 2nd length
3405         ADDI B,(C)              ; Find offset to end of 1st data
3406         MOVEI D,(B)
3407         ADDI D,(T)              ; Find total length after compaction
3408         CAILE D,576.-<5*4>      ; Hack hack hack!  Limit to 556. so std
3409                                 ; IP datagram is limited to 576.
3410          JRST TCLK39            ; If too big, don't compact.
3411
3412         ; Compact two segments into one!
3413         ; R/ 1st seg    D/ offset to end of data
3414         ; J/ 2nd seg    T/ len of 2nd data
3415         METER("TCP: Retrans compact")
3416         TRCPKT J,"TCLK30 Segment being compacted into previous seg for rexmit"
3417         ADDI C,(T)              ; Get new # bytes for 1st seg
3418         DPB C,[PK$TDL (R)]      ; Store it in advance.
3419 ;       HLRZ D,PK.TCP(R)        ; Find addr of TCP header in 1st seg
3420         MOVEI D,(H)
3421         IDIVI B,4
3422         ADDI D,(B)              ; Get addr for BP to end of data
3423         HRL D,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
3424         LDB B,[PK$TDO (J)]      ; Get data offset for 2nd seg
3425         IDIVI B,4
3426         HLRZ A,PK.TCP(J)        ; Get addr for BP to start of 2nd data
3427         ADDI B,(A)
3428         HRL B,(C)[441000 ? 341000 ? 241000 ? 141000]    ; Make LH
3429         ; B/ BP to 2nd data
3430         ; D/ BP to end of 1st data
3431         ; T/ # bytes of 2nd data
3432         LDB A,[IP$TOL (W)]      ; Get current length of whole datagram
3433         ADDI A,(T)              ; Increment by length of added stuff
3434         DPB A,[IP$TOL (W)]      ; Store back
3435         ADDI A,3
3436         LSH A,-2
3437         HRLM A,PK.BUF(R)        ; Set up new count of # words in datagram.
3438 TCLK32: ILDB C,B
3439         IDPB C,D
3440         SOJG T,TCLK32
3441
3442         ; Data copied over, now update flags and stuff.
3443         HLRZ D,PK.TCP(J)
3444         MOVE A,TH$CTL(D)        ; Get flags for 2nd seg
3445         AND A,[TH%CTL]          ; Mask off just flags
3446         IORM A,TH$CTL(H)        ; Add them to flags for 1st seg
3447         TLNE A,(TC%URG)         ; If URGENT bit set,
3448          JRST [ LDB B,[TH$UP (D)]       ; Get pointer from 2nd seg
3449                 LDB C,[PK$TDL (R)]      ; Sigh, get new len of 1st seg
3450                 ADDI B,(C)              ; Adjust for bytes in front
3451                 LDB C,[PK$TDL (J)]      ; But have to subtract length
3452                 SUBI B,(C)              ; of 2nd seg (already in 1st len)
3453                 DPB B,[TH$UP (H)]       ; Store ptr back in 1st seg
3454                 JRST .+1]
3455
3456         ; Compaction done!  Now have to remove 2nd seg from queue.
3457         HRRZ B,PK.TCP(J)        ; Get pointer to 3rd seg
3458         HRRM B,PK.TCP(R)        ; Point 1st at it
3459         CAIN B,                 ; If 2nd was the last one,
3460          HRLM R,XBORTQ(I)       ; must update "last" ptr in queue header.
3461         MOVE A,PK.FLG(J)        ; Get flags
3462 IFN PK.TCP-2,.ERR %PQFL flag must match PK.TCP
3463         TLZ A,(%PKNOF+%PQFL2)   ; Say it's off the TCP list, and allow
3464                                 ; flushing from IP queue.
3465         TLO A,(%PKFLS)          ; In fact, require it
3466         MOVEM A,PK.FLG(J)       ; Store flags back
3467         JUMPGE A,[MOVEI A,(J)   ; If not locked by PI output,
3468                 TRCPKT A,"TCLK32 Seg flushed from rexmit by compaction"
3469                 CALL PKTRT      ; try to flush it now.
3470                 JRST .+1]
3471         SOSGE XBORTL(I)         ; Decrement count of retrans queue segs
3472          BUG HALT
3473         AOS TCLKRC              ; Bump count of recompacts done
3474         JRST TCLK30             ; OK, try to recompact next seg!
3475
3476         ; Note one possible problem with following code; although
3477         ; the segment being re-trans'd is given latest poop (ACK, WND),
3478         ; the ones following are not.  This is usually OK as we assume
3479         ; that following segs have actually been sent out, but if it
3480         ; happens that they HAVEN'T (i.e. %PKODN not set) then their
3481         ; info is going to be a little out of date.  This shouldn't
3482         ; screw things too much, however.
3483 TCLK39: MOVE D,XBRNXT(I)        ; Get latest ACK value
3484         LSH D,4
3485         MOVEM D,TH$ACK(H)       ; Set it
3486         MOVE D,XBRWND(I)        ; And latest window
3487         DPB D,[TH$WND (H)]
3488         CALL THCKSI             ; Compute checksum for it (note not THCKSM)
3489         DPB A,[TH$CKS (H)]
3490         SKIPE TCLKRC            ; Was any recompaction done?
3491          CALL IPKHD2            ; Yes, must recompute IP header (checksum etc)
3492         MOVE A,PK.FLG(R)
3493         TLNN A,(%PKODN)         ; Has segment already been tried once?
3494          JRST [         ; No, don't put on output queue twice!!
3495                 TRCPKT R,"TCLK39 Rexmit skipped because seg not yet output"
3496                 METER("TCP: Pretrans compact")
3497                 JRST TCLK25]
3498         TLO A,(%PKRTR)          ; Set flag saying this is a retransmit
3499         MOVEM A,PK.FLG(R)
3500         MOVEI A,(R)
3501         CALL IPKSNQ             ; Put back on IP output queue
3502                                 ; Note PK.BUF shd still be set up right,
3503                                 ; and shd still have %PKNOF set.
3504 TCLK25: MOVE A,TIME
3505         HRRZ B,XBORTP(I)        ; If RH set, use it for new timeout.
3506         CAIN B,
3507          MOVE B,TCPTMO          ; Use timeout default.
3508         ADD B,A
3509         MOVEM B,XBORTT(I)
3510         JRST TCLK79
3511
3512         ; Here when need to send an ACK.  First see if we can
3513         ; make use of existing output buffer.
3514 TCLK50: METER("TCP: slow ACKs")
3515         TLNE B,(TC%SYN+TC%RST)
3516          BUG CHECK,[TCP: SYN or RST set in XBSTAT clock req]
3517         SKIPE R,XBOCOS(I)       ; Ensure there is one.
3518          TLNE B,(%XBMPL)        ; and that it isn't locked.
3519           JRST TCLK60           ; Sigh, can't use it.
3520
3521         ; There is an output buffer, and it's not locked, so use that
3522         ; to send stuff out!
3523         TRCPKT R,"TCLK50 COS used to send clock level ACK"
3524         MOVSI T,(TC%PSH)
3525         CALL TCPOFR             ; Force it out.
3526         JRST TCLK16
3527
3528         ; Come here when we have to generate a new segment for ACK.
3529 TCLK60: TLNN B,(%XBNOW)         ; Insisting that we ACK?
3530          JRST TCLK65            ; No, can semi-punt.
3531         CALL PKTGFI             ; Get buffer
3532          JRST TCLK65            ; and forget about ACKing if we cant get one
3533         METER("TCP: Clk ACK")
3534         MOVEI R,(A)
3535         MOVE T,B                ; Use request flags in segment.
3536         TRCPKT R,"TCLK60 Alloc and send ACK from clock level"
3537         CALL TSOSNR             ; Send a simple ACK
3538         JRST TCLK16
3539
3540 TCLK65: MOVSI A,(%XBNOW)        ; No, so just set insist flag
3541         IORM A,XBSTAT(I)        ; and wait a bit longer.
3542         JRST TCLK16
3543
3544 TCLK79:
3545         JRST TCLK16
3546
3547         ; Abort the connection, timed out.
3548 TCLK80: METER("TCP: Timeout abort")
3549         CALL TXBFLP             ; This is pretty drastic... flush, PI level.
3550         MOVEI T,.XCINC          ; Say "incomplete transmission"
3551         CALL TCPUC              ; as close reason.
3552         JRST TCLK16
3553
3554 TCLK90: CONO PI,NETON
3555         RET
3556
3557 \f
3558 ; Checksum cruft.
3559
3560 ; THCKSM - Figures TCP segment checksum, IP$TOL has TCP segment length.
3561 ; THCKSI - Figures TCP segment checksum, IP$TOL has IP header plus TCP seg.
3562 ;       W/ addr of IP header
3563 ;       H/ addr of TCP header
3564 ;       Note that the following out-of-TCP values are looked up
3565 ;       from the IP header in order to compute sum for the "pseudo header".
3566 ;               IP$SRC - source host
3567 ;               IP$DST - dest host
3568 ;               IP$TOL - # octets in TCP segment (plus IP header)
3569 ;       Finally,
3570 ;               %PTCTC - Assumed value
3571 ;       
3572 ; Clobbers B,C,D,E
3573 ; Returns
3574 ;       A/ checksum
3575 ;       TT/ Total # bytes in TCP segment
3576
3577 THCKSM: TDZA C,C                ; Compute as if IHL=0
3578 THCKSI:  MOVNI C,5*4
3579         ; First compute pseudo header
3580         LDB A,[IP$SRC (W)]      ; Source addr
3581         LDB B,[IP$DST (W)]      ; Dest addr
3582         ADD A,B
3583         ADDI A,%PTCTC           ; Add TCP protocol number
3584         LDB TT,[IP$TOL (W)]     ; Get total length in octets
3585         JUMPE C,THCKS2
3586         LDB B,[IP$IHL (W)]      ; Find IP header length in 32-bit wds
3587         LSH B,2                 ; mult by 4 to get # octets
3588         SUBI TT,(B)             ; Find # octets of IP data (TCP segment)
3589 THCKS2: ADDI A,(TT)             ; Add in.
3590         MOVEI C,-<5*4>(TT)      ; Get # bytes in segment after 1st 5 wds
3591
3592         ; Done with pseudo header (not folded yet, though).
3593         LDB B,[044000,,0(H)]    ; Get wd 0 (src/dest)
3594         ADD A,B
3595         LDB B,[TH$SEQ (H)]      ; Get wd 1 (seqno)
3596         ADD A,B
3597         LDB B,[TH$ACK (H)]      ; wd 2
3598         ADD A,B
3599         LDB B,[044000,,3(H)]    ; wd 3
3600         ADD A,B
3601         LDB B,[TH$UP (H)]       ; wd 4 (part of)
3602         ADDI A,(B)
3603
3604         LSHC A,-16.
3605         LSH B,-<16.+4>
3606         ADDI A,(B)              ; Now have it folded up.
3607         JUMPLE C,THCKS7         ; If nothing more, can leave now.
3608         MOVEI E,5(H)
3609         HRLI E,442000           ; Set up 16-bit byte ptr to options/data
3610         LSHC C,-1
3611         JUMPLE C,THCKS6
3612 THCKS5: ILDB B,E
3613         ADDI A,(B)
3614         SOJG C,THCKS5
3615 THCKS6: JUMPL D,[               ; Jump if odd byte left.
3616                 ILDB B,E        ; get it
3617                 ANDCMI B,377    ; mask off low (unused) byte.
3618                 ADDI A,(B)      
3619                 JRST .+1]
3620 %CKMSK==<-1#177777>             ; Mask for stuff above 16 bits
3621 THCKS7: TDNE A,[%CKMSK]         ; If any carries, add them in.
3622          JRST [ LDB B,[.BP %CKMSK,A]
3623                 TDZ A,[%CKMSK]
3624                 ADD A,B
3625                 JRST THCKS7]
3626         ANDCAI A,177777         ; Complement sum and mask off.
3627         RET
3628
3629 \f
3630 MTRCOD          ; Last stuff -- expand meter tables.
3631 TRCCOD          ; Expand trace tables