-- File: ArpaPortImpl.mesa - last edit:
-- AOF                  1-Mar-88 10:15:00
-- JAV                  8-Dec-87 17:10:09
-- SMA                 13-Jun-86 11:14:34
-- Copyright (C) 1985, 1986, 1987, 1988 by Xerox Corporation. All rights reserved.

DIRECTORY
  ArpaBuffer USING [
    AccessHandle, Body, Buffer, BufferBody, CreditReceiveBuffer,
    DataBytesPerRawBuffer, Dequeue, DestroyPool, Enqueue, GetBuffer,
    MakePool, QueueCleanup, QueueInitialize, QueueObject, TransferStatus],
  ArpaConstants USING [maxWellknownPort],
  ArpaFlags USING [doDebug, doStats],
  ArpaPort USING [
   AssignPort, defaultWaitTime, minIPHeaderBytes, PortStatus, PortType,
   UDPHeaderBytes, WaitTime],
  ArpaPortInternal USING [
    AddrMismatch, BuildMasks, Checksum, GetMyBroadcastAddr, SendPacket],
  ArpaRouter USING [
    GetAddress, InternetAddress, Port, unknownInternetAddress],
  ArpaStats USING [Incr],
  ArpaSysParameters USING [],
  ArpaTypes USING [
    BufferBody, Byte, Cardinal32, IcmpType, InternetAddress, Port, ProtocolType,
    TypeOfService],
  CommHeap USING [zone],
  CommUtil USING [PulsesToTicks],
  Driver USING [ChangeNumberOfInputBuffers, Glitch],
  Environment USING [Byte, bytesPerWord],
  Frame USING [GetReturnFrame],
  FrameExtras USING [ReadGlobalLink],
  Inline USING [BITNOT, LongCOPY, LowHalf],
  Mopcodes USING [zEXCH],
  Process USING [DisableTimeout, EnableAborts, InitializeCondition, SetTimeout],
  Protocol1 USING [GetFamilyUnit],
  System USING [GetClockPulses, MicrosecondsToPulses, Pulses],
  TcpPort USING [],
  TcpStreamInternal USING [fragAllowed, minTcpHeaderBytes, UniquePktID];

ArpaPortImpl: MONITOR
  IMPORTS
    ArpaBuffer, ArpaPortInternal, ArpaPort, ArpaRouter, ArpaStats, CommHeap,
    CommUtil, Driver, Frame, FrameExtras, Inline, Process, Protocol1, System,
    TcpStreamInternal
  EXPORTS ArpaPortInternal, ArpaRouter, ArpaPort, ArpaSysParameters, TcpPort =
  BEGIN  --implementation for tcp and udp ports.
  
  InternetAddress: PUBLIC --ArpaRouter-- TYPE = ArpaTypes.InternetAddress;
  Port: PUBLIC --ArpaRouter-- TYPE = ArpaTypes.Port;
  nullPort: PUBLIC --ArpaPort-- Port ← [0];
  uniquePort: PUBLIC --ArpaPort-- Port;

  bpw: NATURAL = Environment.bytesPerWord;
  maxMsecToPulses: LONG CARDINAL = LAST[LONG CARDINAL] / 1000;
  receiveBuffers: INTEGER ← 0;  --to see if we need to increase
  --**Pool needs to be destroyed when unloading is implemented.
  rstPool: ArpaBuffer.AccessHandle ← ArpaBuffer.MakePool[1, 0, normalPool];

  globalTypeOfService: ArpaTypes.TypeOfService ← [
    precedence: routine, delay: FALSE, throughput: FALSE,
    reliability: FALSE, reserved: 0];
  
  
  checksums: BOOLEAN ← TRUE;
  ChecksumHeader: TYPE = MACHINE DEPENDENT RECORD [
    src: InternetAddress,
    dest: InternetAddress,
    zero: Environment.Byte,
    protocol: ArpaTypes.ProtocolType,
    length: CARDINAL];

  
  PortType: TYPE = {udp, tcp, icmp};
  Handle: TYPE = LONG POINTER TO Object;
  Object: PUBLIC TYPE = RECORD [
    next: Handle, -- used only by the router
    pool: ArpaBuffer.AccessHandle,  --accounting pool behind channel
    me: InternetAddress,  --local address
    myPort: ArpaRouter.Port,  --local port
    deleting: BOOLEAN ← FALSE,  --is port being deleted?
    waitTime: ArpaPort.WaitTime,  --set by client or defaulted
    queue: ArpaBuffer.QueueObject,  --to queue inputs
    newInput: CONDITION,
    protocolDependent: SELECT type: PortType FROM
      tcp => [hmsk: InternetAddress,  --mask for outgoing packets
	      him: InternetAddress,  --remote's address
	      hisPort: Port],  --remotePort
      udp, icmp => [],
      ENDCASE];
  
      
  ports: PortTable ← [0, NIL];
  PortTable: TYPE = RECORD [length: CARDINAL, first: Handle];
  
  Timeout: PUBLIC ERROR = CODE;         --Get procedure timed out.
  --Glitches
  PortAbuse: ERROR = CODE;  --packet protocol and handle protocol don't match.
  UnboundHandle: ERROR = CODE;  --port handle was neither udp nor tcp. 
  BadProtocol: ERROR = CODE;  --not udp or tcp.
  <<IllegalArpaPktLength: ERROR = CODE;   --Tried to set too large (Glitch).>>

      
  AddPort: ENTRY PROC [pH: Handle] =
    BEGIN
    SELECT TRUE FROM
      (receiveBuffers > 0), (pH.pool.seal = listenPool) => NULL;
      (pH.pool.receive > 0) =>
        BEGIN
	Driver.ChangeNumberOfInputBuffers[TRUE];
	receiveBuffers ← receiveBuffers + INTEGER[pH.pool.receive];
	END;
      ENDCASE;

    --add new port to the head of the table
    pH.next ← ports.first;
    ports.first ← pH;
    ports.length ← ports.length + 1;
    END;  --AddPort
    
    
  AssignPort: PUBLIC <<ArpaPort>> ENTRY PROC RETURNS [p: ArpaRouter.Port] =
    BEGIN
    p ← uniquePort;
    IF (uniquePort ← [uniquePort + 1]) = Port[0] THEN
      uniquePort ← [LOOPHOLE[ArpaConstants.maxWellknownPort, CARDINAL] + 1];
    END;  --AssignPort
    
    
  Broadcast: PUBLIC PROCEDURE[pH: Handle, b: ArpaBuffer.Buffer] =
    {
    b.fo.status ← goodCompletion;
    b.fo.time ← System.GetClockPulses[];
    ArpaPortInternal.SendPacket[b, remote];
    };  --Broadcast;
    
    
  BuildULPChecksum: PROC [b: ArpaBuffer.Buffer] RETURNS[cs: WORD] =
    BEGIN
    << Builds the psuedo header and generates a checksum for udp and tcp. >>
    body: ArpaBuffer.Body = b.arpa;
    ipData: CARDINAL ← body.ipHeader.length - (body.ipHeader.ihl * 4);
    h: ChecksumHeader ← [
      body.ipHeader.source, body.ipHeader.destination, 0,
      body.ipHeader.protocol,];
    <<
    Zeroing the pad byte of an odd-byte packet for checksumming is ok
    because we know that buffer size allocation is in words.
    >>
    IF (body.ipHeader.length MOD 2) # 0 THEN body.ipBytes[ipData] ← 0;
      
    SELECT h.protocol FROM
      tcp => h.length ← ipData;
      userDatagram => h.length ← body.user.length;
      icmp => h.length ← ipData;
      ENDCASE => Driver.Glitch[BadProtocol];
      
    cs ← ArpaPortInternal.Checksum[
      Inline.BITNOT[ArpaPortInternal.Checksum[0, SIZE[ChecksumHeader], @h]],
      (h.length + bpw - 1) / bpw, @body.ipData];
    END;  --BuildULPChecksum
    
  
  Create: PUBLIC <<ArpaPort>> PROC [
    port: ArpaRouter.Port, send, receive: CARDINAL,
    portType: ArpaPort.PortType] RETURNS [pH: Handle] =
    BEGIN  --Creates a udp port.
    pH ← CommHeap.zone.NEW[udp Object];
    CreateInternal[pH, portType, port, send, receive];
    END;  --Create
  
  CreateICMPEcho: PUBLIC <<ArpaPort>> PROC [send, receive: CARDINAL] RETURNS [pH: Handle] =
    BEGIN  --Creates a icmp echo port.
    pH ← CommHeap.zone.NEW[icmp Object];
    CreateInternal[pH, listen, nullPort, send, receive];
    END;  --CreateICMPEcho
    
    
  CreateTcpPort: PUBLIC <<TcpPort>> PROC [
    port: ArpaRouter.Port, send, receive: CARDINAL, portType: ArpaPort.PortType,
    remote: ArpaRouter.InternetAddress ← ArpaRouter.unknownInternetAddress,
    remotePort: ArpaRouter.Port] RETURNS [pH: Handle] =
    BEGIN  --creates a tcp port
    pH ← CommHeap.zone.NEW[tcp Object];
    CreateInternal[pH, portType, port, send, receive];
    WITH p: pH SELECT FROM
      tcp =>
        BEGIN
        p.him ← remote;
        p.hisPort ← remotePort;
        IF (p.him # ArpaRouter.unknownInternetAddress) THEN
          p.hmsk ← ArpaPortInternal.BuildMasks[p.him].hostMask;
	END;
       ENDCASE;
    END;  --CreateTcpPort
    
    
  CreateInternal: PROC[pH: Handle, portType: ArpaPort.PortType, port: Port,
    send, receive: CARDINAL] =
    BEGIN
    pH.next ← NIL;
    pH.me ← ArpaRouter.GetAddress[];
    IF port = nullPort THEN pH.myPort ← ArpaPort.AssignPort[]
    ELSE pH.myPort ← port;
    pH.pool ← ArpaBuffer.MakePool[send, receive,
      SELECT portType FROM normal => normalPool,
      ENDCASE => listenPool];
    pH.deleting ← FALSE;
    Process.InitializeCondition[@pH.newInput, 0];
    Process.EnableAborts[@pH.newInput];
    SetWaitTime[pH, ArpaPort.defaultWaitTime];
    ArpaBuffer.QueueInitialize[@pH.queue];
    pH.pool.frame ← FrameExtras.ReadGlobalLink[Frame.GetReturnFrame[]];
    AddPort[pH !
      UNWIND => {ArpaBuffer.DestroyPool[pH.pool]; CommHeap.zone.FREE[@pH]}];
    END;  --CreateInternal
    
    
  Delete, DeleteTcpPort: PUBLIC <<ArpaPort, TcpPort>> PROC[pH: Handle] =
    BEGIN
    Abort: ENTRY PROC =
      BEGIN
      pH.deleting ← TRUE;
      BROADCAST pH.newInput;
      END;  --Abort
    RemovePort[pH];  --inhibit new input being queued
    Abort[];  --get rid of all clients waiting
    ArpaBuffer.QueueCleanup[@pH.queue];  --flush input queue
    ArpaBuffer.DestroyPool[pH.pool];
    CommHeap.zone.FREE[@pH];
    END;  --Delete
    
  GetAssignedAddress: PUBLIC PROC[pH: Handle]
    RETURNS [InternetAddress] = {RETURN[pH.me]};
    
  
  GetBufferPool: PUBLIC PROC[pH: Handle]
    RETURNS[ArpaBuffer.AccessHandle] = {RETURN[pH.pool]};
    
    
  GetDestination: PUBLIC PROC [b: ArpaBuffer.Buffer]
    RETURNS[InternetAddress, Port] =
    {RETURN[b.arpa.ipHeader.destination,
      SELECT b.arpa.ipHeader.protocol FROM
        tcp => b.arpa.tcp.destinationPort,
        userDatagram => b.arpa.user.destinationPort,
        ENDCASE => [0]]};  --GetDestination
	
	
  GetPacket: PUBLIC <<ArpaPort>> ENTRY PROC [pH: Handle]
    RETURNS[b: ArpaBuffer.Buffer] =
    BEGIN
    ENABLE UNWIND => NULL;
    startTime: System.Pulses = System.GetClockPulses[];
    WHILE (b ← ArpaBuffer.Dequeue[@pH.queue]) = NIL DO
      SELECT TRUE FROM
        (pH.deleting) => RETURN WITH ERROR ABORTED;
	(pH.waitTime = LAST[ArpaPort.WaitTime]) => NULL;  --disabled timeouts
	((System.GetClockPulses[] - startTime) >= pH.waitTime) => 
	  RETURN WITH ERROR Timeout;
	ENDCASE;  --hasn't timed out yet
      WAIT pH.newInput;  --propogate ERROR ABORTED
      ENDLOOP;
    END;  --GetPacket
	
   
  GetUDPLength: PUBLIC PROC [body: ArpaBuffer.Body] RETURNS [n: CARDINAL] =
    {RETURN[body.user.length - ArpaPort.UDPHeaderBytes]};
    
  GetSendBuffer: PUBLIC PROC[pH: Handle] RETURNS[b: ArpaBuffer.Buffer] =
    BEGIN
    body: ArpaBuffer.Body;
    body ← (b ← ArpaBuffer.GetBuffer[pH.pool, send, TRUE, Protocol1.GetFamilyUnit[arpa].maxBufferSize]).arpa;
    IF ArpaFlags.doDebug THEN
      b.fo.debug ← FrameExtras.ReadGlobalLink[Frame.GetReturnFrame[]];
    --Set buffer defaults and initialize.
    body.ipHeader.ihl ← 5;
    body.ipHeader.service ← [routine, FALSE, FALSE, FALSE, 0];
    body.ipHeader.lifetime ← 15;
    body.ipHeader.flags ← [FALSE, TRUE, FALSE];
    body.ipHeader.length ← 24B;
    END;  --GetSendBuffer
    
    
  GetSource: PUBLIC PROC[b: ArpaBuffer.Buffer]
    RETURNS[InternetAddress, Port] =
    {RETURN[b.arpa.ipHeader.source,
      SELECT b.arpa.ipHeader.protocol FROM
        tcp, telnet => b.arpa.tcp.sourcePort,
        userDatagram => b.arpa.user.sourcePort,
        ENDCASE => [0]]};  --GetSource
    
    
  GetStatus: PUBLIC PROC[pH: Handle] RETURNS [ArpaPort.PortStatus] =
    {RETURN [[pH.myPort, pH.queue.length]]};

  GetTypeOfService: PUBLIC <<ArpaSysParameters>> PROC[]
    RETURNS[ArpaTypes.TypeOfService] = {RETURN[globalTypeOfService]};

  SetTypeOfService: PUBLIC <<ArpaSysParameters>> PROC[
    set: ArpaTypes.TypeOfService] = {globalTypeOfService ← set};
      
      
  InitUniquePort: PUBLIC --ArpaPortInternal-- PROC =
    BEGIN
    UNTIL LOOPHOLE[uniquePort, CARDINAL] >
      LOOPHOLE[ArpaConstants.maxWellknownPort, CARDINAL] DO
      uniquePort ← Inline.LowHalf[System.GetClockPulses[]];
      ENDLOOP;
    END;  --InitUniqueuePort
    
    
  PutPacket: PUBLIC PROC[pH: Handle, b: ArpaBuffer.Buffer] =
    BEGIN
    hmsk: InternetAddress;
    body: ArpaBuffer.Body = b.arpa;
    
    body.ipHeader.source ← pH.me;
    WITH p: pH SELECT FROM
      tcp =>
        BEGIN
	IF b.arpa.ipHeader.protocol # tcp THEN Driver.Glitch[PortAbuse];
	IF ArpaFlags.doStats THEN ArpaStats.Incr[tcpsSent];
	--We built this mask when the other end of the connection became known.
	body.tcp.sourcePort ← pH.myPort;
	hmsk ← p.hmsk;
	body.tcp.checksum ← 0;
	IF checksums THEN body.tcp.checksum ← BuildULPChecksum[b];
	END;
      udp =>
        BEGIN
	<<
	Don't know what class the client's packet is, so we have to build masks
        for every packet sent (sigh).
	>>
	IF b.arpa.ipHeader.protocol # userDatagram THEN Driver.Glitch[PortAbuse];
	IF ArpaFlags.doStats THEN ArpaStats.Incr[udpsSent];
	body.user.sourcePort ← pH.myPort;
        hmsk ← ArpaPortInternal.BuildMasks[body.ipHeader.destination].hostMask;
	body.user.checksum ← 0;
	IF checksums THEN body.user.checksum ← BuildULPChecksum[b];
	END;
      icmp =>
	WITH icmp: body.icmp SELECT FROM
	  echo =>
	    BEGIN
	    bytes: NATURAL = (body.ipHeader.length - (body.ipHeader.ihl * 4));
	    IF (bytes MOD 2) # 0 THEN body.ipBytes[bytes] ← 0;  --pad with null
	    IF ArpaFlags.doStats THEN ArpaStats.Incr[icmpEcho];
	    hmsk ← ArpaPortInternal.BuildMasks[
	      body.ipHeader.destination].hostMask;
	    icmp.checksum ← 0;
	    IF checksums THEN icmp.checksum ←
	      ArpaPortInternal.Checksum[0, (bytes + bpw - 1) / bpw, @body.icmp];
	    END;
	  ENDCASE => Driver.Glitch[PortAbuse];

      ENDCASE => Driver.Glitch[UnboundHandle];	
	
    b.fo.status ← ArpaBuffer.TransferStatus[goodCompletion];
    
    --Is destination a broadcast?
    IF ~ArpaPortInternal.AddrMismatch[hmsk, body.ipHeader.destination,
      ArpaPortInternal.GetMyBroadcastAddr[]] THEN Broadcast[pH, b]
    ELSE   --destination is valid address (myself or remote).
      BEGIN
      b.fo.time ← System.GetClockPulses[];
      ArpaPortInternal.SendPacket[b,
	IF ~ArpaPortInternal.AddrMismatch[
	  hmsk, body.ipHeader.destination, pH.me] THEN local ELSE remote];
      END;
    END;  --PutPacket
    
    
  QueueForClient: PUBLIC <<ArpaPortInternal>> ENTRY PROC[
    b: ArpaBuffer.Buffer, copy: BOOLEAN] RETURNS[BOOLEAN] =
    BEGIN
    cached, pH: Handle ← NIL;
    pktType: PortType;
    port: ArpaRouter.Port;
    checksum: CARDINAL;
    body: ArpaBuffer.Body = b.arpa;
    
    AddressPairMatch: PROC [pH: Handle] RETURNS [BOOLEAN] =
      BEGIN
      WITH p: pH SELECT FROM
        tcp =>
	  RETURN[SELECT TRUE FROM
	    --no broadcasts and the like.
	    (ArpaPortInternal.AddrMismatch[
	      p.hmsk, body.ipHeader.destination, p.me]) => FALSE,
	    --not even close. 
	    (body.ipHeader.protocol # icmp AND -- won't work since icmp from gateway
	      ArpaPortInternal.AddrMismatch[
	        p.hmsk, p.him, body.ipHeader.source]) => FALSE,
	    (body.ipHeader.protocol # icmp AND p.hisPort # body.tcp.sourcePort) => FALSE,  --closer, but...if it is icmp who cares
	    ENDCASE => TRUE];  --that's it!
        ENDCASE => RETURN[FALSE];
      END;  --AddressPairMatch
      
    CacheUnspecified: PROC [pH: Handle] =
      BEGIN
      <<
      Caches the port handle if the remote is unspecified, in case
      we find no fully specified port to deliver the packet to.
	>>
      WITH p: pH SELECT FROM
        tcp =>	
	  SELECT TRUE FROM
	    (p.him # ArpaRouter.unknownInternetAddress) AND
	      (p.hisPort # nullPort) => NULL;  --for some other conn.
	    (p.him # ArpaRouter.unknownInternetAddress) AND (p.hisPort = nullPort)
	      AND (cached # NIL) => NULL;    --if both null, first in list got it.
	    (ArpaPortInternal.AddrMismatch[
	      p.hmsk, body.ipHeader.source, p.him]) AND
	      (p.him # ArpaRouter.unknownInternetAddress) => NULL;  --wrong addr.
	    (body.tcp.sourcePort # p.hisPort) AND
	      (p.hisPort # nullPort) => NULL;  --wrong port.
	    ENDCASE => cached ← pH;
	ENDCASE;
      END;  --CacheUnspecified

    SELECT body.ipHeader.protocol FROM
      tcp =>
        BEGIN
	checksum ← body.tcp.checksum; body.tcp.checksum ← 0;
	IF ArpaFlags.doStats THEN ArpaStats.Incr[tcpsRcvd];
	IF (body.tcp.checksum # 0) AND (BuildULPChecksum[b] # checksum) THEN
	  {IF ArpaFlags.doStats THEN ArpaStats.Incr[badTcpChecksum];
	  RETURN[FALSE]};
	port ← body.tcp.destinationPort;
	pktType ← tcp;
	END;  --tcp
	
      userDatagram =>
        BEGIN
	checksum ← body.user.checksum; body.user.checksum ← 0;
	IF ArpaFlags.doStats THEN ArpaStats.Incr[udpsRcvd];
	IF (body.user.checksum # 0) AND (BuildULPChecksum[b] # checksum) THEN
	  {IF ArpaFlags.doStats THEN ArpaStats.Incr[badUdpChecksum];
	  RETURN[FALSE]};
	port ← body.user.destinationPort;
	pktType ← udp;
	END;  --userDatagram
	
      icmp =>
        BEGIN  --queue it for the guy who sent the offending packet.
	offender: ArpaBuffer.Body;
	WITH r: body.icmp SELECT FROM
          unreachable =>
	    BEGIN
	    offender ← LOOPHOLE[@r.icmpData];
	    port ← offender.tcp.sourcePort;
	    pktType ← IF offender.ipHeader.protocol = tcp THEN tcp ELSE udp;
	    END;
	  timeExceeded =>
	    BEGIN
	    offender ← LOOPHOLE[@r.icmpData];
	    port ← offender.tcp.sourcePort;
	    pktType ← IF offender.ipHeader.protocol = tcp THEN tcp ELSE udp;
	    END;
	  paramProblem =>
	    BEGIN
	    offender ← LOOPHOLE[@r.icmpData];
	    port ← offender.tcp.sourcePort;
	    pktType ← IF offender.ipHeader.protocol = tcp THEN tcp ELSE udp;
	    END;
	  quench =>
	    BEGIN
	    offender ← LOOPHOLE[@r.icmpData];
	    port ← offender.tcp.sourcePort;
	    pktType ← IF offender.ipHeader.protocol = tcp THEN tcp ELSE udp;
	    END;
	  echoReply => pktType ← icmp;
          ENDCASE;
	--tcp and udp ports are in the same position in the packet.
	END;  --icmp
	
      ENDCASE =>
        {IF ArpaFlags.doStats THEN ArpaStats.Incr[badProtocol]; RETURN[FALSE]};

    <<
    Find the destination port.  If there is a fully specified port handle that
    matches the incoming packet, it gets the packet.  If there is not a fully
    specified port handle, then the packet is given to the first unspecifed
    port handle.  The port handle does not become fully specified until
    tcp calls TcpPort.SpecifyRemote.  (A fully specified port handle is one
    where both the source address/port and the destination address/port are
    known.
    >>
   
    FOR pH ← ports.first, pH.next UNTIL pH = NIL DO
      SELECT TRUE FROM
	--icmp packets don't have prots.
        (port # pH.myPort) AND (pktType # icmp) => NULL;
	--not for us
	(pH.type # pktType) => NULL;
	(pktType = tcp) AND (~AddressPairMatch[pH]) => CacheUnspecified[pH];
	ENDCASE => EXIT;  --a match!
      REPEAT FINISHED =>
	IF (pH ← cached) = NIL THEN
	  {IF (pktType = tcp) AND (~body.tcp.rst) THEN SendRst[b]; RETURN[FALSE]};
      ENDLOOP;

      IF copy THEN  --sending to ourselves.
	BEGIN
	c: ArpaBuffer.Buffer ← ArpaBuffer.GetBuffer[
	  pH.pool, receive, FALSE, ArpaBuffer.DataBytesPerRawBuffer[b]];
	IF c # NIL THEN
	  BEGIN
	  Inline.LongCOPY[from: body, to: c.arpa,
	    nwords: (body.ipHeader.length + bpw - 1) / bpw];
	  c.fo.status ← goodCompletion;
	  ArpaBuffer.Enqueue[@pH.queue, c];
	  BROADCAST pH.newInput;
	  END
	ELSE RETURN[FALSE];
	END
      ELSE
	IF ArpaBuffer.CreditReceiveBuffer[pH.pool, b] THEN
	  BEGIN
	  b.fo.status ← goodCompletion;
	  ArpaBuffer.Enqueue[@pH.queue, b];
	  BROADCAST pH.newInput;
	  END
	ELSE RETURN[FALSE];
	  
      RETURN[TRUE];
    END;  --QueueForClient
    
    
  RemovePort: ENTRY PROC[pH: Handle] =
    BEGIN
    prevPH: Handle;
    IF ports.first = pH THEN ports.first ← pH.next
    ELSE
      BEGIN
      prevPH ← ports.first;
      UNTIL prevPH = NIL DO
        IF prevPH.next = pH THEN {prevPH.next ← pH.next; EXIT};
        prevPH ← prevPH.next;
        ENDLOOP;
      END;
    ports.length ← ports.length - 1;
    SELECT TRUE FROM
      (receiveBuffers = 0), (pH.pool.seal = listenPool) => NULL;
      ((receiveBuffers ← receiveBuffers - INTEGER[pH.pool.receive]) <= 0) =>
        {Driver.ChangeNumberOfInputBuffers[FALSE]; receiveBuffers ← 0};
      ENDCASE;
    END;  --RemovePort
    
    
  SendRst: PROC [b: ArpaBuffer.Buffer] =
    BEGIN
    <<
    Sends a tcp rst packet in response to a packet to non-existent port.  We 
    have to fabricate the packet from scratch and send it directly through the
    ip interface because there is no tcp port or connection.
    >>
    CardToSeq: PROC [LONG CARDINAL] RETURNS [ArpaTypes.Cardinal32] =
      MACHINE CODE {Mopcodes.zEXCH};
      
    SeqToCard: PROC [ArpaTypes.Cardinal32] RETURNS [LONG CARDINAL] =
      MACHINE CODE {Mopcodes.zEXCH};
      
    GetDataLength: PROC [b: ArpaBuffer.Buffer] RETURNS [l: CARDINAL] = INLINE
    --returns the data length in bytes.
      BEGIN
      body: ArpaBuffer.Body = b.arpa;
      l ← (body.ipHeader.ihl * 4) + (body.tcp.dataOffset * 4);
      --we don't want l going negative if remote screwed up.
      RETURN[IF l > body.ipHeader.length THEN 0 ELSE body.ipHeader.length - l];
      END;  --GetDataLength

    r: ArpaBuffer.Buffer ← ArpaBuffer.GetBuffer[rstPool, send, TRUE,
      TcpStreamInternal.minTcpHeaderBytes + ArpaPort.minIPHeaderBytes];
    body: ArpaBuffer.Body = b.arpa;
    rody: ArpaBuffer.Body = r.arpa;
      
     b.fo.time ← System.GetClockPulses[];
     b.fo.tries ← 1;
     IF ArpaFlags.doDebug THEN
      b.fo.debug ← FrameExtras.ReadGlobalLink[Frame.GetReturnFrame[]];
     
    --ip fields.
    
    rody.ipHeader.flags ← [FALSE, ~TcpStreamInternal.fragAllowed, FALSE];
    rody.ipHeader.service ← [routine, FALSE, FALSE, FALSE, 0];
    rody.ipHeader.identification ← TcpStreamInternal.UniquePktID[];
    rody.ipHeader.lifetime ← 60;
    rody.ipHeader.protocol ← tcp;
    rody.ipHeader.source ← body.ipHeader.destination;
    rody.ipHeader.destination ← body.ipHeader.source;
    rody.ipHeader.ihl ← 5;
    rody.ipHeader.length ←
      TcpStreamInternal.minTcpHeaderBytes + ArpaPort.minIPHeaderBytes;
      
    --tcp fields.
    rody.tcp.urg ← rody.tcp.ack ← rody.tcp.psh ←
       rody.tcp.syn ← rody.tcp.fin ← FALSE;
    rody.tcp.reserved ← 0;
    rody.tcp.dataOffset ← (TcpStreamInternal.minTcpHeaderBytes + 3)/4;
    rody.tcp.rst ← TRUE;
    rody.tcp.urgentPointer ← LOOPHOLE[0];
    rody.tcp.sourcePort ← body.tcp.destinationPort;
    rody.tcp.destinationPort ← body.tcp.sourcePort;
    rody.tcp.window ← 0;
    IF body.tcp.ack THEN
      rody.tcp.sequence ← body.tcp.acknowledgement
    ELSE
      {rody.tcp.sequence ← CardToSeq[0];
      rody.tcp.acknowledgement ← CardToSeq[SeqToCard[body.tcp.sequence] +
	GetDataLength[b]];
      rody.tcp.ack ← TRUE};
    rody.tcp.checksum ← 0;
    rody.tcp.checksum ← BuildULPChecksum[r];
    
    ArpaPortInternal.SendPacket[r, remote];
    IF ArpaFlags.doStats THEN ArpaStats.Incr[resetsSent];
    END;  --SendRst
    
    
  SetDestination: PUBLIC <<ArpaPort>> PROC [b: ArpaBuffer.Buffer,
    destAddr: InternetAddress, destPort: Port] =
    BEGIN
    b.arpa.ipHeader.destination ← destAddr;
    --Client's responsibility to set protocol before calling SetDestination.
    SELECT b.arpa.ipHeader.protocol FROM
      tcp, telnet => b.arpa.tcp.destinationPort ← destPort;
        userDatagram => b.arpa.user.destinationPort ← destPort;
        ENDCASE;
    END;  --SetDestination
    
    
  SpecifyRemote: PUBLIC <<TcpPort>> ENTRY PROC [pH: Handle,
    remote: ArpaRouter.InternetAddress, remotePort: ArpaRouter.Port] =
    BEGIN
    --called by TCP after creating the port with an unspecified remote, and
    --receiving a valid syn.
    WITH p: pH SELECT FROM
      tcp =>
        BEGIN
	p.him ← remote;
	p.hisPort ← remotePort;
	p.hmsk ← ArpaPortInternal.BuildMasks[p.him].hostMask;
	END;
      ENDCASE => Driver.Glitch[PortAbuse];
    END;  --SpecifyRemote
    
    
  SetUDPLength: PUBLIC <<ArpaPort>> PROC[body: ArpaBuffer.Body, n: CARDINAL] =
    BEGIN
    --Sets the UDP length.
    --should we check for packet too large here?
    body.user.length ← n + ArpaPort.UDPHeaderBytes;
    END;  --SetPacketBytes
    
    
  SetWaitTime: PUBLIC ENTRY PROC [pH: Handle, time: ArpaPort.WaitTime] =
    BEGIN
    --Sets the time a Get will wait for an incoming packet before raising
    --Timeout.
    pH.waitTime ← IF time > maxMsecToPulses THEN LAST[LONG CARDINAL]
      ELSE System.MicrosecondsToPulses[time*1000];
    IF pH.waitTime = LAST[LONG CARDINAL] THEN Process.DisableTimeout[@pH.newInput]
    ELSE Process.SetTimeout[@pH.newInput, CommUtil.PulsesToTicks[[pH.waitTime]]];
    END;  --SetWaitTime
    
    
  SwapSourceAndDestination: PUBLIC PROC[b: ArpaBuffer.Buffer] =
    BEGIN
    body: ArpaBuffer.Body = b.arpa;
    tmpAddr: InternetAddress ← body.ipHeader.source;
    body.ipHeader.source ← body.ipHeader.destination;
    body.ipHeader.destination ← tmpAddr;
    <<
    Only tcp and user datagram protocols use the port field. Luckily they're
    at the same offsets so this code should collapse. You could also add more
    arms to the select statement without adding code.
    >>
    SELECT body.ipHeader.protocol FROM
      tcp =>
        BEGIN
	tmpPort: Port ← body.tcp.sourcePort;
	body.tcp.sourcePort ← body.tcp.destinationPort;
	body.tcp.destinationPort ← tmpPort;
	END;
      userDatagram =>
        BEGIN
	tmpPort: Port ← body.user.sourcePort;
	body.user.sourcePort ← body.user.destinationPort;
	body.user.destinationPort ← tmpPort;
	END;
      ENDCASE;
    --There needs to be code in here to take care of the 0 net number case, and
    --the multicast/broadcast case.
    END;  --SwapSourceAndDestination
    

    
  END...
  
LOG

21-Jan-85 10:44:13  SMA  Created file.
23-Oct-85 10:14:15  SMA  Multiplexing on socket pairs for tcp.
13-Nov-85 15:10:24  SMA  ArpaProtocol => Arpa10MBit and ArpaPortInternal.
 7-Jan-86 14:51:02  SMA  Added icmp.
28-Jan-86 14:10:12  SMA  Checksums, checksums, checksums.
13-Jun-86 11:09:44  SMA  Fill in all the packet fields in SendRst. 
10-Mar-87 20:13:38  AOF  Funston buffer manager. 
 6-May-87 11:29:51  JAV  ICMP echo and redirect
26-May-87 13:04:18  AOF  Make SwapSourceAndDestination sensitive to ICMP
 2-Jun-87  7:54:18  AOF  Use ArpaTypes.Icmp record instead of LOOPHOLE'ng
28-Sep-87 13:29:29  JAV  Broadcasts for RIP
 1-Mar-88 10:10:55  AOF  Implement ArpaSysParameters$Get/Set TypeOfService