-- Copyright (C) 1984  by Xerox Corporation. All rights reserved. 
--INRImpl.mesa last edited by: HGM on: 16-Dec-84 10:24:27, Yetch: NewInrFriends
--INRImpl.mesa last edited by: HGM on: 24-Oct-84  1:35:07
--INRImpl.mesa last edited by: Leong on: 23-Oct-84 15:54:08
--Function: The implementation module for the NS INR.

DIRECTORY
  Buffer USING [AccessHandle, MakePool, DestroyPool, Buffer,
    GetBuffer],
  Checksums USING [IncrNSTransportControlAndUpdateChecksum, SetChecksum],
  CommFlags USING [doStats],
  CommSvcFlags USING [doDebug],
  CommSvcHeap USING [FreeNode, MakeNode, GetInrHeap],
  CommunicationInternal USING [],
  CourierInternal USING [ExchWords],
  Driver USING [
    ChangeNumberOfInputBuffers, GetDeviceChain, GetInputBuffer,
    Glitch, Network, PutOnGlobalDoneQueue],
  NSConstants USING [routingInformationSocket],
  NSTypes USING [
    bytesPerIDPHeader, RoutingInfoTuple, RoutingInfoType,
    TransportControl, maxIDPDataBytes],
  Process USING [MsecToTicks, Pause, SetTimeout, DisableTimeout,
    SecondsToTicks, Abort, Detach, EnableAborts],
  RoutingTable USING [Object, Handle, Register, FlushCacheProc],
  Router USING [FindMyHostID, NoTableEntryForNet, RoutersFunction],
  RouterInternal USING [
    BroadcastThisPacket, checkIt, SendErrorPacket,
    XmitStatus, SendPacket],
  Runtime USING [CallDebugger],
  Inr USING [],
  InrFriends USING [RoutingTableObject, HopCount, RoutingTableEntry, 
    DriverDetails, Method],
  InrStats USING [Stats, RoutingTableSearch, tupleIndexTableSize],
  Inline USING [LowHalf, BITAND],
  Socket USING [ChannelHandle, Create, Delete, GetPacket, SetWaitTime,
    ReturnBuffer, infiniteWaitTime, GetBufferPool],
  Stats USING [StatIncr],
  SpecialSystem USING [HostNumber, NetworkNumber, SocketNumber],
  System USING [broadcastHostNumber, GetClockPulses, GetGreenwichMeanTime,
    gmtEpoch, GreenwichMeanTime, HostNumber, NetworkAddress, NetworkNumber,
    nullNetworkNumber, nullHostNumber, nullSocketNumber, nullNetworkAddress,
    Pulses],
  RoutingFudges USING [];

INRImpl: MONITOR
  IMPORTS
    Buffer, Inline, Checksums, CommSvcHeap, CourierInternal, Driver, 
    Process, Router, RouterInternal, Socket, Stats,
    System, RoutingTable, Runtime
  EXPORTS Inr, InrFriends, InrStats, Buffer, System, RoutingFudges =
  BEGIN
  
  doNSStats: BOOLEAN = TRUE OR CommFlags.doStats;  --tied to TRUE for now

  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  --EXPORTed TYPEs
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  Network: PUBLIC TYPE = Driver.Network;
  NetworkNumber: PUBLIC TYPE = SpecialSystem.NetworkNumber;
  HostNumber: PUBLIC TYPE = SpecialSystem.HostNumber;
  SocketNumber: PUBLIC TYPE = SpecialSystem.SocketNumber;
  
  RoutingTableObject: TYPE = InrFriends.RoutingTableObject;
  RoutingTableEntry: TYPE = InrFriends.RoutingTableEntry;
  HopCount: TYPE = InrFriends.HopCount;
  
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  -- CONSTANTS that make it all happen
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  unknownHostID: HostNumber = System.nullHostNumber;
  extraBuffersForForwarding: CARDINAL = 40;
  mask: CARDINAL = 31;  -- for masking out the high eleven bits of the incoming
                        -- delay, as we don't use them (yet).
  anyNetNetworkNumber: NetworkNumber = [177777B, 177777B];
  anyNetNetworkNumberFor860: NetworkNumber = [0AAFFH, 0FFFFH];
  nullNetworkNumber: NetworkNumber = System.nullNetworkNumber;
     -- routing info request network number that indicates all networks
  initialTransportControl: NSTypes.TransportControl = [
    trace: FALSE, filler: 0, hopCount: 0];
  localHop: InrFriends.HopCount = 0;  -- rte delay for attached network(s) is zero hops.
  updateCycles: InrFriends.HopCount = 4;
    -- timeUnits gets reset to this; number of routing table update cycles.
  alternatePathTimeUnitThreshHold: CARDINAL = 3;
    -- we look for alternate routing path if timeUnits fall BELOW this value.
  maxInternetrouterHops: CARDINAL = 15;
  infinityHopCount: CARDINAL = 16;
  decrementTO: CARDINAL = 40; -- seconds for decrementing table entries
  
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  -- VARIABLES or semi-Variables
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  myHostID: HostNumber;  --host ID of this system element
  nullEnum: NetworkNumber ← nullNetworkNumber;
  -- Routing table constants and variables
  routingTableHead: RoutingTableEntry ← NIL;
  routingTableSize: CARDINAL ← 0;
  pleaseStop: BOOLEAN ← TRUE; << controls the processes. TRUE if we are OFF,
     FALSE if we are ON >>
  internetRouterTimer, -- times out to send gratuitous routing packets
    routingTableChanged, -- notified to send info on routes that have changed
    auxInternetRouterTimer: -- times out by a random amount so we don't all send the gratuitous packets at the same time.
    CONDITION; 
  routingInformationSupplierFork, internetRouterServerFork,
    decrementRoutingTableEntriesFork, routingTableChangedFork: PROCESS ← NIL;
  stats: LONG POINTER TO InrStats.Stats ← NIL;
  
  lastGetStats: System.GreenwichMeanTime ← System.gmtEpoch;
    --mark the last time a snap of the statistics was taken
    
  --various Glitches generated by the Router
  RoutingTableScrambled: ERROR = CODE;

  --Routing Table Object
  rto: PUBLIC RoutingTable.Object ← [
    type: interNetworkRouting, start: Start, stop: Stop,
    startEnumeration: nullEnum, endEnumeration: nullEnum,
    enumerate: EnumerateByDistance, fillTable: Fill,
    getDelay: GetDelay, transmit: Transmit,
    forward: Forward, findNetwork: FindNetID,
    addNetwork: AddNet, removeNetwork: RemoveNet,
    flushCache: FlushCacheNoOp, stateChanged: ChangedState];
    
  ptrToRto:RoutingTable.Handle ← @rto;
  
  extraHops: CARDINAL ← 0; -- fudge factor on the hop count to trick other
    -- routers into using another path for forwarding packets
  
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----
  -- Routing Table (list) handling Routines
  ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ---- ----

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure adds an entry to the beginning of the Routingtable list.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  AddEntry: INTERNAL PROCEDURE [e: RoutingTableEntry] =
    BEGIN
    e.nextRTE ← routingTableHead;
    routingTableHead ← e;
    routingTableSize ← routingTableSize + 1;
    StatIncr [@stats.destNetsAdded];
    END; -- of AddEntry

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- AddNet
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  AddNet: ENTRY PROCEDURE [net: Network] =
    BEGIN ENABLE UNWIND => NULL;
    AddNetworkInternal[net];  --AddNet
    -- send out gratuitous routing response so inrs learn about each other
    NOTIFY routingTableChanged;
    END;

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure tells the NS Router about a new network.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  AddNetworkInternal: INTERNAL PROCEDURE [newNetwork: Network] =
    BEGIN
    IF NOT newNetwork.alive THEN RETURN;
    IF newNetwork.netNumber # nullNetworkNumber THEN
      BEGIN
      -- the driver already knows the number of its net, add or modify a rte
      e: RoutingTableEntry ← FindNetworkNumber[
        newNetwork.netNumber, FALSE];
      IF e = NIL THEN
        BEGIN
        e ← CommSvcHeap.MakeNode[n: SIZE[RoutingTableObject]];
        AddEntry[e];
        END;
      e↑ ← RoutingTableObject[
        nextRTE: e.nextRTE, nextNSE: NIL, destNetwork: newNetwork.netNumber, delay: localHop,
        timeUnits: updateCycles, route: unknownHostID,
        network: newNetwork, changed: TRUE];
      END;
      
    IF FindNetworkNumber[nullNetworkNumber, FALSE] = NIL THEN
      BEGIN
      -- there is no "default" rte, add one
      e: RoutingTableEntry ← CommSvcHeap.MakeNode[
        n: SIZE[RoutingTableObject]];
      e↑ ← RoutingTableObject[
        nextRTE: NIL, nextNSE: NIL, destNetwork: nullNetworkNumber, delay: localHop,
        timeUnits: updateCycles, route: unknownHostID,
        network: newNetwork, changed: FALSE];
      AddEntry[e];
      END;
    END;  --AddNetworkInternal
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- RemoveEntry
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RemoveEntry: INTERNAL PROCEDURE [e: RoutingTableEntry] =
    BEGIN
    prev: RoutingTableEntry ← NIL;
    temp: RoutingTableEntry ← routingTableHead;
    UNTIL (temp = NIL) OR (temp = e) DO prev ← temp; temp ← temp.nextRTE; ENDLOOP;
    IF CommSvcFlags.doDebug AND (temp = NIL) THEN
      Driver.Glitch[RoutingTableScrambled];
    IF prev = NIL THEN routingTableHead ← e.nextRTE
    ELSE
      BEGIN
      IF CommSvcFlags.doDebug AND (prev.nextRTE # e) THEN
        Driver.Glitch[RoutingTableScrambled];
      IF CommSvcFlags.doDebug AND (prev.nextRTE = NIL) THEN
        Driver.Glitch[RoutingTableScrambled];
      prev.nextRTE ← e.nextRTE;
      END;
    e.nextRTE ← NIL;
    routingTableSize ← routingTableSize - 1;
    StatIncr [@stats.destNetsDeleted];
    END; -- of RemoveEntry
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure removes a network from the NS Router's tables.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RemoveNet: PROCEDURE [net: Network] =
    BEGIN
    unknownNetwork: Network;
    
    FindNetworkNumberLocked: ENTRY PROCEDURE [n: NetworkNumber]
      RETURNS [e: RoutingTableEntry] = INLINE
      BEGIN ENABLE UNWIND => NULL;
      e ← FindNetworkNumber[n, FALSE-- don't reorder chain--]; END;
      
    RemoveNetworkLocked[net];
    --we may have removed the nullNetworkNumber network;  if so replace it
    IF FindNetworkNumberLocked[nullNetworkNumber] = NIL THEN
      BEGIN
      unknownNetwork ← Driver.GetDeviceChain[];
      UNTIL (unknownNetwork # net) OR (unknownNetwork = NIL) DO
        unknownNetwork ← unknownNetwork.next;
       	ENDLOOP; --try to find another network
      IF (unknownNetwork # NIL) THEN AddNet[unknownNetwork];
      END; -- of replacing the net 0 rte
    END;  --RemoveNet
 
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure removes a network from the NS Router's tables.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RemoveNetworkLocked: ENTRY PROCEDURE [oldNetwork: Network] =
    BEGIN
    ENABLE UNWIND => NULL;
    e: RoutingTableEntry;
    anyChanges: BOOLEAN ← FALSE;
    DO
      IF (e ← FindNetwork[oldNetwork]) = NIL THEN EXIT;
      -- mark the rte as pointing to an obsolete network driver
      e↑ ← [destNetwork: e.destNetwork, delay: infinityHopCount,
        timeUnits: updateCycles, -- so we keep the rte entry around for awhile
	nextRTE: e.nextRTE, nextNSE: NIL, route: unknownHostID, network: NIL, changed: TRUE];
      anyChanges ← TRUE;
      ENDLOOP;
    IF anyChanges THEN
      -- send out gratuitous routing response for the new info
      NOTIFY routingTableChanged;
    END;  --RemoveNetworkLocked

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- CleanUpRoutingTable
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  CleanUpRoutingTable: ENTRY PROCEDURE = INLINE
    BEGIN ENABLE UNWIND => NULL;
    e, temp: RoutingTableEntry;
    e ← routingTableHead;
    WHILE (e # NIL) DO
      temp ← e;
      e ← e.nextRTE;
      CommSvcHeap.FreeNode[p: temp];
      ENDLOOP;
    routingTableSize ← 0;
    END;  -- of CleanUpRoutingTable

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure goes through the routing table entries decrementing by 
  -- one the time since the entry was last updated.  If the time is zero,
  -- then the destination net is deemed unreachable.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  DecrementRoutingTableEntries: ENTRY PROCEDURE =
    BEGIN ENABLE UNWIND => NULL;
    rte: RoutingTableEntry;
    timer: CONDITION;
    Process.SetTimeout [@timer, Process.SecondsToTicks [decrementTO]];
    Process.EnableAborts [@timer];
    UNTIL pleaseStop DO
      ENABLE ABORTED => EXIT;
      WAIT timer;
      rte ← routingTableHead;
      WHILE (rte # NIL) DO
	IF (rte.delay # localHop) THEN
	  BEGIN
	  IF rte.timeUnits = 0 THEN
	    BEGIN -- remove the dead entry
	    temp: RoutingTableEntry ← rte;
	    rte ← rte.nextRTE;
	    RemoveEntry[temp];
	    CommSvcHeap.FreeNode[p: temp];
	    LOOP;
	    END
	    ELSE rte.timeUnits ← rte.timeUnits - 1;
	  END;
	rte ← rte.nextRTE;
	ENDLOOP;
      ENDLOOP;
    END;  -- of DecrementRoutingTableEntries

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- EnumerateByDistance
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  EnumerateByDistance: ENTRY PROCEDURE [
    previous: NetworkNumber, delay: CARDINAL]
    RETURNS [net: NetworkNumber] =
    --Start enumeration with nullNetworkNumber and finish with lastNetworkNumber
    --enumeration happens in order of net #, so table can change between calls
    BEGIN
    ENABLE UNWIND => NULL;
    test: NetworkNumber;
    n: RoutingTableEntry ← routingTableHead;
    foundOne: BOOLEAN ← FALSE;
    pulses: System.Pulses ← System.GetClockPulses[]; --for time duration
    
    IF (n = NIL) THEN {net ← nullEnum; RETURN};
    UNTIL (n = NIL) DO
      test ← n.destNetwork;
      IF (n.delay = delay)  --within the desired hop count
	AND NetAgtNetB[test, previous]  --greater than the one he has now
        AND (~NetAgtNetB[test, net] OR ~foundOne)
	   --less than any we know about since
	AND (n.network # NIL)
	  THEN --is interesting-- {net ← test; foundOne ← TRUE};
      n ← n.nextRTE;  --but continue looking for an even better one
      ENDLOOP;
    IF ~foundOne THEN net ← nullEnum;
    SearchDurationBump[pulses, enumerateByDistance]; --increments duration
    END; -- of EnumerateByDistance
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- EnumerateByNetNumber
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --  
  EnumerateByNetNumber: ENTRY PROCEDURE [previous: NetworkNumber]
    RETURNS [net: NetworkNumber, delay: HopCount] =
    --Start enumeration with nullNetworkNumber and finish with lastNetworkNumber
    --enumeration happens in order of net #, so table can change between calls
    BEGIN
    ENABLE UNWIND => NULL;
    test: NetworkNumber;
    n: RoutingTableEntry ← routingTableHead;
    foundOne: BOOLEAN ← FALSE;
    pulses: System.Pulses ← System.GetClockPulses[]; --for time duration
    
    IF (n = NIL) THEN {net ← nullEnum; RETURN};
    UNTIL (n = NIL) DO
      test ← n.destNetwork;
      IF NetAgtNetB[test, previous]  --greater than the one he has now
        AND (~NetAgtNetB[test, net] OR  ~foundOne)
	  --less than any we know about since
	AND (n.network # NIL)
          THEN --is interesting-- {net ← test; delay ← n.delay;
	    foundOne ← TRUE};
      n ← n.nextRTE;  --but continue looking for an even better one
      ENDLOOP;
    IF ~foundOne THEN net ← nullEnum;
    SearchDurationBump[pulses, enumerateByNetNumber]; --increments duration
    END; -- of EnumerateByNetNumber
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- EnumerateRoutes
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  EnumerateRoutes: PUBLIC PROCEDURE [previousNet: NetworkNumber,
    previousDelay: HopCount, method: InrFriends.Method,
    alwaysDetermineViaNet: BOOLEAN ← FALSE] 
    RETURNS [net: NetworkNumber,
    delay: HopCount, details: InrFriends.DriverDetails]=
    BEGIN
     << Stateless enumerator starts
      with nullNetworkNumber and zeroHopCount.  Ends with nullNetworkNumber >>
    SELECT method FROM
      byNetNumber =>
        BEGIN
	[net, delay] ← EnumerateByNetNumber [previousNet];
	IF (net = nullEnum) THEN RETURN;
	details ← GetRouteDetails[net, alwaysDetermineViaNet! 
	  Router.NoTableEntryForNet => {net ← nullEnum; CONTINUE}].details;
	END;
      byDistance =>
        BEGIN
        ENABLE Router.NoTableEntryForNet => RETRY;
	net ← EnumerateByDistance [previousNet, previousDelay];
	UNTIL (net # nullEnum) OR (previousDelay = maxInternetrouterHops) DO
	  previousDelay ← previousDelay + 1;
	  previousNet ← nullEnum; -- start over
	  net ← EnumerateByDistance [previousNet, previousDelay];
	  ENDLOOP;
	IF (net = nullEnum) THEN RETURN;
	delay ← previousDelay;
	previousNet ← net;
	details ← GetRouteDetails[net, alwaysDetermineViaNet].details;
	END;
      ENDCASE => NULL;  -- we handled all of the enumerated type's values
    END; -- of EnumerateRoutes

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  --Client requests that we gather routing table information.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  Fill: PROCEDURE [maxDelay: CARDINAL] =
    BEGIN
    << Since we are already an inr this proc. is a NOP, (we leave it in for the time being because its part of the routing object). >>
    END; -- of Fill

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This returns the ID of the locally connected networkmost suitable to get
  -- to the destination network.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  FindNetID: ENTRY PROCEDURE [net: NetworkNumber]
    RETURNS [NetworkNumber] =
    BEGIN ENABLE UNWIND => NULL;
    RETURN[FindNetIDInternal[net]];
    END; -- of FindNetID
    
  FindNetIDInternal: INTERNAL PROCEDURE [
    destNet: NetworkNumber] RETURNS [netNumber: NetworkNumber] =
    BEGIN
    e: RoutingTableEntry;
    netNumber ←
      IF destNet = nullNetworkNumber OR -- accelerator so we don't search
      -- for the net zero rte
      (e ← FindNetworkNumber[destNet]) = NIL OR (e.network = NIL) THEN
      nullNetworkNumber ELSE e.network.netNumber;
    IF netNumber = nullNetworkNumber THEN
      BEGIN
      --since nullNetworkNumber is uninformative find the first network
      --with a known network Number and use it.
      FOR n: Network ← Driver.GetDeviceChain[], n.next UNTIL n = NIL DO
        IF (netNumber ← n.netNumber) # nullNetworkNumber THEN EXIT;
        ENDLOOP;
      END;  --find non - nullNetworkNumber network clause
    END;  --FindNetIDInternal

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This procedure searches for an entry with network field equal to net and
  -- returns that entry.  It also reorders the rte chain. If the entry cannot
  -- be found then e is NIL.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  FindNetwork: INTERNAL PROCEDURE [net: Network]
    RETURNS [e: RoutingTableEntry] =
    BEGIN
    prev: RoutingTableEntry ← e ← routingTableHead;
    pulses: System.Pulses ← System.GetClockPulses[]; --for time duration
    UNTIL (e = NIL) DO
      IF (e.network = net) THEN
        BEGIN
        IF (prev # routingTableHead) THEN
          BEGIN
          prev.nextRTE ← e.nextRTE;
          e.nextRTE ← routingTableHead;
          routingTableHead ← e;
          END;
        EXIT; --exit from until-do loop
        END;
      prev ← e;
      e ← e.nextRTE;
      ENDLOOP;
    SearchDurationBump[pulses, findByNetworkDriver]; --increments duration
    END; -- of FindNetwork

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This hot procedure fills in some routing information and sends the buffer
  -- out on the appropriate network.  The send is asynchronous;  the caller
  -- owns the buffer andreceives its back from the the dispatcher via
  -- b.requeueProcedure (when the send is completed).
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  Transmit: PROCEDURE[b: Buffer.Buffer] =
    BEGIN
    destHost: HostNumber ← b.ns.destination.host;
    nextHost: HostNumber;
    destNetNumber: NetworkNumber ← b.ns.destination.net;
    network: Network;
    e: RoutingTableEntry;
    
    FindNetworkNumberLocked: ENTRY PROCEDURE [n: NetworkNumber]
      RETURNS [e: RoutingTableEntry] = INLINE
      BEGIN
      ENABLE UNWIND => NULL;
      e ← FindNetworkNumber[n];
      END; -- of FindNetworkNumberLocked
      
    -- start of procedure
    e ← FindNetworkNumberLocked[destNetNumber];
    IF (e = NIL) OR (network ← e.network) = NIL THEN
      BEGIN  --outgoing packet for unknown net
      --return b to the system buffer pool
      b.status ← LOOPHOLE[RouterInternal.XmitStatus[noRouteToNetwork]];
      Driver.PutOnGlobalDoneQueue[b];
      IF doNSStats THEN Stats.StatIncr[statNSSentNowhere];
      RETURN;
      END;

    --outgoing packet to be transmitted over the correct network
    nextHost ← IF e.route # unknownHostID THEN 
      e.route -- next inr's address 
      ELSE destHost; -- we are attached to the destination net
    b.status ← LOOPHOLE[RouterInternal.XmitStatus[goodCompletion]];
    b.network ← network; -- mark the network being used
    b.type ← ns;
    --synchronous buffer send
    network.encapsulateAndSendNS [b, nextHost];
    StatIncr [@stats.pktsTransmitted];
    END;  --Transmit

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This hot procedure searches for an entry with destNetwork field equal to
  -- num and returns that entry.  If the entry cannot be found then e is NIL.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  FindNetworkNumber:  INTERNAL PROCEDURE [
    num: NetworkNumber, advanceEntry: BOOLEAN ← TRUE]
    RETURNS [e: RoutingTableEntry] =
    BEGIN
    prev: RoutingTableEntry ← e ← routingTableHead;
    pulses: System.Pulses ← System.GetClockPulses[]; --for time duration
    i: CARDINAL ← 0;
    UNTIL (e = NIL) DO
      IF (e.destNetwork = num) THEN
        BEGIN
        IF advanceEntry AND (i > 4) THEN
          BEGIN
	  --advance entry to the beginning of the list
          prev.nextRTE ← e.nextRTE;
          e.nextRTE ← routingTableHead;
          routingTableHead ← e;
          END;
	IF advanceEntry THEN StatIncr [@stats.tupleIndexTable[
	  MIN[i, InrStats.tupleIndexTableSize-1]]];
        EXIT; --exit the until-do loop
        END;
      prev ← e;
      e ← e.nextRTE;
      i ← i + 1;
      ENDLOOP;
    SearchDurationBump[pulses, findByNetNumber]; --increments duration
    END; -- of FindNetworkNumber
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- FlushCacheNoOp is a no operation routine.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
    
  FlushCacheNoOp: RoutingTable.FlushCacheProc = {};
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- Forward
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  Forward: PROCEDURE [b: Buffer.Buffer] =
    BEGIN
    ENABLE UNWIND => NULL;
    nextHost: HostNumber;
    e: RoutingTableEntry;
    network: Network;

    NotFoundDestinationNetworkLocked: ENTRY PROCEDURE RETURNS [BOOLEAN] = INLINE
      BEGIN ENABLE UNWIND => NULL;
      RETURN[
        (e ← FindNetworkNumber[b.ns.destination.net]) = NIL
        OR (network ← e.network) = NIL];
      END; -- of NotFoundDestinationNetworkLocked

    --see if we have traversed max number of internet routers already
    SELECT TRUE FROM
      (maxInternetrouterHops <= b.ns.transportControl.hopCount) =>
       -- note that it is "<=" - this prevents a packet from being
       -- forwarded past the farthest net a source knows about (15 hops)
        BEGIN
        RouterInternal.SendErrorPacket[b, excessHopsErrorCode, 0];
        IF doNSStats THEN Stats.StatIncr[statNSNotForwarded];
	StatIncr [@stats.tooManyHops]
        END;
      (NotFoundDestinationNetworkLocked[]) =>
        BEGIN  --outgoing packet for unknown net
	IF b.ns.source.host # myHostID THEN
          RouterInternal.SendErrorPacket[b, cantGetThereErrorCode, 0]
	ELSE
          {b.status ← LOOPHOLE[RouterInternal.XmitStatus[noRouteToNetwork]];
          --return b to the system buffer pool
          Driver.PutOnGlobalDoneQueue[b]};
	IF doNSStats THEN Stats.StatIncr[statNSNotForwarded];
	StatIncr [@stats.unknownNet];
        END;
      ENDCASE =>
        BEGIN  --outgoing packet
        Checksums.IncrNSTransportControlAndUpdateChecksum[b];
        --now transmit it over the correct network
        IF (nextHost ← e.route) = unknownHostID THEN
          nextHost ← b.ns.destination.host;
        b.network ← network; -- mark the network being used
	b.type ← ns;
        --maintain the crude counters of packets and bytes forwarded
        StatIncr [@stats.statNSForwarded];
        StatBump [@stats.bytesForwarded, b.ns.pktLength];
	network.encapsulateAndSendNS[b, nextHost]; --same net
        IF doNSStats THEN Stats.StatIncr[statNSForwarded];
        END;
    END;  --Forward

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- Provide the crude couters of packets forwarded by the router
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  ForwardingStats: PUBLIC PROCEDURE RETURNS [packets, bytes: LONG CARDINAL] =
    BEGIN
    IF (stats = NIL) THEN RETURN [0, 0]; --forwarding hasn't been activated
    packets ← stats.statNSForwarded;
    bytes ← stats.bytesForwarded;
    END;  --ForwardingStats
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- GetDelay
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  GetDelay: PROCEDURE [net: NetworkNumber] RETURNS [delay: CARDINAL] =
    BEGIN
    LockedFindNet: ENTRY PROC = INLINE
      {ENABLE UNWIND => NULL; e ← FindNetworkNumber[net, FALSE]};
    
    e: RoutingTableEntry;
    LockedFindNet[];  --try searching first time
    IF (e = NIL) OR (e.network = NIL) THEN
      ERROR Router.NoTableEntryForNet; -- a net is not accessible unless we have a 
      -- rte AND a network pointer
    delay ← e.delay;  --value of interest
    END;  --GetDelay
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- GetRouteDetails
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  GetRouteDetails: PROCEDURE [destNet: NetworkNumber,
    alwaysDetermineViaNet: BOOLEAN]
    RETURNS [details: InrFriends.DriverDetails, delay: HopCount] =
    BEGIN
    e: RoutingTableEntry;
    net: Driver.Network;
    host: HostNumber;
    
    LockedFindNet: ENTRY PROC = INLINE
      {ENABLE UNWIND => NULL; e ← FindNetworkNumber[destNet, FALSE]};
      
    LockedFindFarNet: ENTRY PROCEDURE [net: Driver.Network] 
      RETURNS [farNet: NetworkNumber] = 
      BEGIN ENABLE UNWIND => NULL;
      << net is a network driver that is anonyomous--it isn't assigned
        its own network number.  Point to Point connections between INRs
	are anonymous E.g. a phoneline between two INRs.
	
        This procedure searches to find the rte in the table 
	that uses <net> and has the lowest delay to a destination net of
	all the rtes that use <net>.  That rte's destNetwork should be
	a viable network for reaching the INR at the far end of the anonymous
	driver.
	
	We make only one pass through the rtes. >>
	
      bestHopsSoFar: HopCount ← infinityHopCount;
      oneAway: HopCount ← localHop + 1;
      
      farNet ← nullNetworkNumber;
      FOR e: RoutingTableEntry ← routingTableHead, e.nextRTE 
        UNTIL e = NIL OR bestHopsSoFar = oneAway DO
	IF e.network # net OR e.destNetwork = nullNetworkNumber
	  THEN LOOP;  -- ignore
	IF e.delay < bestHopsSoFar THEN
	  BEGIN
	  farNet ← e.destNetwork;
	  bestHopsSoFar ← e.delay;
	  END;
	ENDLOOP;
      END; --of LockedFindFarNet
      
    -- Mainline of the procedure ...
    
    LockedFindNet[];  --try searching first time
    IF (e = NIL) OR (e.network = NIL) THEN
      ERROR Router.NoTableEntryForNet; --no such entry in table
    net ← e.network;
    delay ← e.delay;
    host ← e.route;
    details.driverType ← net.device;
    details.driverNetwork ← net.netNumber;
    IF details.driverType = phonenet THEN
      BEGIN
      PhoneNetInternalState: TYPE = LONG POINTER TO PhoneNetInternalObject;
      -- This better be the same as the first two fields of StateObject in
      -- PhoneNetInternal def.
      PhoneNetInternalObject: TYPE = MONITORED RECORD [
        clientData: LONG UNSPECIFIED,
        lineNumber: CARDINAL];
	
      -- this LOOPHOLE-ing between the inr and a specific driver is both
      -- amazingly yucky and useful. Sigh.
      details.clientData ← LOOPHOLE [net.statsLevel0,
        PhoneNetInternalState].clientData;
      details.lineNumber ← LOOPHOLE [net.statsLevel0,
        PhoneNetInternalState].lineNumber;
      END;
    IF details.driverType = x25 THEN
      details.clientData ← net.statsLevel0;
    IF delay # localHop THEN
      BEGIN
      details.via.socket ← System.nullSocketNumber;
      details.via.host ← host;
      details.via.net ← IF alwaysDetermineViaNet AND
        net.netNumber = nullNetworkNumber THEN LockedFindFarNet [net] ELSE
          net.netNumber; 
      END
      ELSE details.via ← System.nullNetworkAddress;
    END; -- of GetRouteDetails
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- GetRouteInfo
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  GetRouteInfo: PUBLIC PROCEDURE [net: System.NetworkNumber]
    RETURNS [delay: HopCount, details: InrFriends.DriverDetails] =
    BEGIN
    [delay: delay, details: details] ← GetRouteDetails [destNet: net,
      alwaysDetermineViaNet: TRUE];
    END;
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- MisnumberedNetTrap
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  
  MisnumberedNetTrap: PROCEDURE = {Runtime.CallDebugger ["Misnumbered net trap."L]};
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This process wakes up every 30 seconds and sends out Routing Information
  -- Protocol Response packets gratuitously, if this system element is an
  -- internet router.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  InternetRouterServer: PROCEDURE =
    BEGIN
    
    InternetRouterServerLocked: ENTRY PROCEDURE = INLINE
      BEGIN
      ENABLE UNWIND => NULL;
      bufferHandle: Buffer.AccessHandle;
      
      --create extra buffers because we are an inr
      bufferHandle ← Buffer.MakePool [send: 0,
        receive: extraBuffersForForwarding];
      UNTIL pleaseStop DO
        ENABLE ABORTED => EXIT;
        WAIT internetRouterTimer;
        IF pleaseStop THEN EXIT;
	-- wait a random amount of time [0..7] seconds before sending out the
	-- gratuitous response packet.  This will help prevent all inrs 
	-- from sending at the same time.
	Process.SetTimeout[@auxInternetRouterTimer,
	  Process.SecondsToTicks[Inline.LowHalf[System.GetClockPulses[]] MOD 8]];
	WAIT auxInternetRouterTimer;
	IF pleaseStop THEN EXIT;
        SendGratuitousResponse [[nullNetworkNumber, System.broadcastHostNumber,
          NSConstants.routingInformationSocket]];
	StatIncr [@stats.gratuitousRoutingResponseSent];
        ENDLOOP;
      SendGratuitousResponse [to: [nullNetworkNumber, System.broadcastHostNumber,
        NSConstants.routingInformationSocket], b: NIL, 
	allAreUnreachable: TRUE]; -- tell everyone not to use us as a route anymore
      StatIncr [@stats.gratuitousRoutingResponseSent];
      
      -- delete the buffers allocated for the INR
      Buffer.DestroyPool [bufferHandle];
      END; -- of InternetRouterServerLocked

    -- start of procedure, when this process is first started it waits a while to allow
    -- the routing table to be built by the incoming routing response packets.
    Process.Pause[Process.MsecToTicks[100]];
    Driver.ChangeNumberOfInputBuffers[TRUE];
    InternetRouterServerLocked[];
    Driver.ChangeNumberOfInputBuffers[FALSE];
    END;  --InternetRouterServer
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- NetAgtNetB
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --  
  NetAgtNetB: PROC [a, b: NetworkNumber] RETURNS [BOOLEAN] =  INLINE
    BEGIN
    --RETURNS[a > b];
    RETURN[LOOPHOLE[CourierInternal.ExchWords[LOOPHOLE[a]], LONG CARDINAL] >
      LOOPHOLE[CourierInternal.ExchWords[LOOPHOLE[b]], LONG CARDINAL] ];
    END;
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- RoutingInformationPacket either sends or examine the packet depending
  -- on if the packet is a routingInfoRequest or routingInfoResponse. As part
  -- of an examination of a routingInfoResponse packet, the routing table is
  -- updated.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RoutingInformationPacket: PROCEDURE [b: Buffer.Buffer] 
    RETURNS [bufferWasReturned: BOOLEAN] =
    BEGIN
    newRoute: HostNumber = b.ns.source.host;
    routingPacketType: NSTypes.RoutingInfoType = b.ns.routingType;
    incomingNetwork: Driver.Network ← b.network; -- check before using since
    -- we aren't always holding the monitor

    ExamineResponsePacket: ENTRY PROCEDURE =
      BEGIN ENABLE UNWIND => NULL;
      networkStillExists: BOOLEAN ← FALSE;
      
      IF CommSvcFlags.doDebug AND
         (b.ns.source.socket # NSConstants.routingInformationSocket) THEN
	 ERROR; -- why isn't the response pkt's source socket 1?
	 
      IF (b.ns.source.socket # NSConstants.routingInformationSocket) THEN
        RETURN;  -- don't use
	
      IF b.ns.transportControl.hopCount > 0 THEN
        BEGIN
	-- routing response packets should never be forwarded
	StatIncr [@stats.forwardedRoutingResponsesRecv];
	RETURN;   -- don't use
	END;
		
      IF NOT incomingNetwork.alive THEN RETURN; -- don't use
            
      IF UpdateUnnumberedNetTable [b].use THEN
        UpdateRoutingTable [b];
	
      END; -- of ExamineResponsePacket
    
      
   UpdateUnnumberedNetTable: INTERNAL PROC [b: Buffer.Buffer]
     RETURNS [use: BOOLEAN] =
      BEGIN  << Sets a null network number.  b.ns.source.net is the field to use
      for setting the incomingNetwork.netNumber because we know this is a routing 
      response which came from the INR on this net! >>
      
      use ← TRUE;
      
      SELECT TRUE FROM
        (incomingNetwork.netNumber = b.ns.source.net) => NULL;  -- we know our net number and it matches with the routing response
        (incomingNetwork.netNumber = nullNetworkNumber) =>
	  BEGIN -- our driver wants the new net number
          incomingNetwork.netNumber ← b.ns.source.net;  -- update
	  AddNetworkInternal[incomingNetwork];
          END;
	(b.ns.source.net # nullNetworkNumber) => -- since the incoming net number is interesting ('cause it isn't zero) and it didn't match, then the network has two different, non-zero net numbers.  Log the occurance and crash.
	  BEGIN
	  StatIncr [@stats.misnumberedNetTrapHits];
	  MisnumberedNetTrap[];
	  ERROR; -- MisnumberedNetTrap should never return; but if it does ...
	  END;
	ENDCASE => NULL;
	
      END;  --UpdateUnnumberedNetTable


    -- START of procedure's main body 
    
    IF CommSvcFlags.doDebug AND (b.ns.source.host # myHostID)
      AND incomingNetwork = NIL THEN ERROR;
      -- driver didn't note the incoming network in the object?
    -- do we handle this packet?
    IF  (b.ns.packetType # routingInformation)
      OR (b.ns.source.host = myHostID
          AND routingPacketType = routingInfoResponse)
	  --don't need to listen to myself
      OR (newRoute = unknownHostID) -- would be unhelpful
      OR (incomingNetwork = NIL AND b.ns.source.host # myHostID) -- driver didn't note the network in the object?
      THEN RETURN [FALSE];-- NO, don't use this pkt
      
    -- YES, a routingInfo packet for us (Yeah!)
    IF doNSStats THEN Stats.StatIncr[statNSGatewayPacketsRecv];
    SELECT TRUE FROM
      (routingPacketType = routingInfoRequest) =>
	BEGIN
	SendRoutingInfoResponse[b.ns.source, b]; -- we respond to request
	bufferWasReturned ← TRUE; -- SendRoutingInfoResponse proc
	-- always returns the buffer that it is given
	StatIncr [@stats.routingRequestRecv];
	END;
      (routingPacketType = routingInfoResponse) =>
	BEGIN
	pulses: System.Pulses ← System.GetClockPulses[];
	ExamineResponsePacket[]; 
	bufferWasReturned ← FALSE; -- we merely examined it
	pulses ← System.Pulses[System.GetClockPulses[] - pulses];
	PulsesBump [@stats.pulsesProcessingRoutingResponse, pulses];
	StatIncr [@stats.routingResponseRecv];
	END;
      ENDCASE => bufferWasReturned ← FALSE; -- we should never get to this arm
    
    END;  --RoutingInformationPacket

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This process handles packets that come in over Socket # 1
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RoutingInformationSupplier: PROCEDURE =
    BEGIN
    BEGIN -- extra begin is to put the Enable within <timedOut>'s scope
    myAddr: System.NetworkAddress = [
      FindNetID[nullNetworkNumber],
      myHostID, NSConstants.routingInformationSocket];
    cH: Socket.ChannelHandle;
    b: Buffer.Buffer;
    
    cH ← Socket.Create [local: myAddr, send: 1, receive: 5];
    Socket.SetWaitTime [cH, Socket.infiniteWaitTime];
    Process.Detach [FORK BroadcastRoutingRequest[cH]]; --to build routing table.
    
    UNTIL pleaseStop DO
      ENABLE ABORTED => EXIT; -- the condition 
      -- variable that we would get aborted on is in the Socket.Get
      b ← Socket.GetPacket [cH];
      IF NOT RoutingInformationPacket[b].bufferWasReturned THEN
	  Socket.ReturnBuffer [b]; -- if the buffer wasn't returned, then we 
	  -- return it here.  Driver.PutOnGlobalDoneQueue would be overkill since 
	  -- we know that we got the buffer through the Socket.Get procedure.
      ENDLOOP;
    Socket.Delete [cH];
    END; -- extra end is because of the extra begin
    END; -- of RoutingInformationSupplier
   
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- RoutingTableChanged
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- 
  RoutingTableChanged: PROCEDURE =
    BEGIN
    << This process sends out gratuitous routing response packets for tuples that have changed. It will not send out packets faster than once per second >>
    
    Wait: ENTRY PROCEDURE = 
      INLINE BEGIN ENABLE UNWIND => NULL;
      WAIT routingTableChanged;
      END;
      
    UNTIL pleaseStop DO
      ENABLE ABORTED => EXIT;
      Wait [];
      Process.Pause [Process.SecondsToTicks [1]];
      SendGratuitousResponseLocked [to: [nullNetworkNumber,
        System.broadcastHostNumber, NSConstants.routingInformationSocket],
	b: NIL, allAreUnreachable: FALSE, onlyChangedEntries: TRUE];
      StatIncr [@stats.gratuitousRoutingResponseSent];
      ENDLOOP;
    END; -- of RoutingTableChanged
   
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- SendGratuitousResponse
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  SendGratuitousResponse: INTERNAL PROCEDURE [to: System.NetworkAddress,
    b: Buffer.Buffer ← NIL, allAreUnreachable, onlyChangedEntries: BOOLEAN ← FALSE] =
    BEGIN ENABLE UNWIND => NULL;
    -- This procedure will send a gratuitous type of routing response (information
    -- will be sent on all of the entries we know about).  Most often, this proc
    -- called to send a broadcast gratuitous reponse to everyone every 30 seconds
    -- or so.  But it is also called when a request for information comes in that
    -- asks for info on all the nets we know about.
    -- If we are supplied with a buffer, then we'll use it and use its b.network
    -- if the destination net address is the nullNetNumber.
    -- If allAreUnreachable is TRUE, then the delay we'll use in all the tuples
    -- will be <infinityHopCount>.  This tells all listeners that we
    -- are not a good route for any destinatination nets
    -- This proc will send two or more pkts if there are too many tuples for one
    -- packet.
    nextRoutingEntry: RoutingTableEntry ← routingTableHead;
    maxTuplesPerRoutingPacket: CARDINAL =
       (NSTypes.maxIDPDataBytes - 2*SIZE[NSTypes.RoutingInfoType]) /
       (2*SIZE[NSTypes.RoutingInfoTuple]);
    tupleNumber: CARDINAL ← 0;
    destNetwork: Driver.Network ← NIL;
    
    IF b # NIL THEN 
      BEGIN
      destNetwork ← b.network;
      b.ns.destination ← to;
      b.ns.pktLength ← NSTypes.bytesPerIDPHeader + 2*SIZE[NSTypes.RoutingInfoType];
      END;
       
    UNTIL nextRoutingEntry = NIL DO
      SELECT TRUE FROM
        nextRoutingEntry.destNetwork = nullNetworkNumber,
	onlyChangedEntries AND (NOT nextRoutingEntry.changed) => NULL;
	ENDCASE =>
        BEGIN
	-- handle this valid rte;  Do we have a buffer?
	IF b = NIL THEN
	  BEGIN
	  -- get and set a new buffer.  Other fields of buffer are set by
	  -- RoutAndSendRoutingInfoResponse proc
	  b ← Driver.GetInputBuffer[!ABORTED => {b ← NIL; CONTINUE}];
	  IF b = NIL THEN RETURN; -- give up!
	  b.ns.destination ← to;
	  b.network ← destNetwork;  -- RoutAndSendRoutingInfoResponse proc will
	  -- check that the b.network is valid, and set it if we are
	  -- broadcasting this response.
	  b.ns.pktLength ← NSTypes.bytesPerIDPHeader + 
	    2*SIZE[NSTypes.RoutingInfoType];
	  tupleNumber ← 0;
	  END; -- of getting a new buffer
	   
        b.ns.routingTuple[tupleNumber] ← [nextRoutingEntry.destNetwork,
	  IF allAreUnreachable THEN infinityHopCount ELSE
	  MIN [nextRoutingEntry.delay + 1 + extraHops, infinityHopCount]]; -- we increment here!
	nextRoutingEntry.changed ← FALSE; -- reset
        tupleNumber ← tupleNumber + 1;
        b.ns.pktLength ←
          b.ns.pktLength + 2*SIZE[NSTypes.RoutingInfoTuple];
        END; -- of handling a valid rte
      nextRoutingEntry ← nextRoutingEntry.nextRTE; 
      
      IF b # NIL AND (
	nextRoutingEntry = NIL --we have done all of the rte's-- OR
        tupleNumber >= maxTuplesPerRoutingPacket --pkt is full--) THEN
        BEGIN
        IF NOT RoutAndSendRoutingInfoResponse[b] THEN 
	  Driver.PutOnGlobalDoneQueue[b];
        b ← NIL;
        END;  --of sending a routing buffer
      ENDLOOP;  --end of send loop
    END;  --SendGratuitousResponse
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- SendGratuitousResponseLocked
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  SendGratuitousResponseLocked: ENTRY PROCEDURE [
    to: System.NetworkAddress, b: Buffer.Buffer ← NIL, allAreUnreachable,
    onlyChangedEntries: BOOLEAN ← FALSE] = INLINE {
      ENABLE UNWIND => NULL;
      SendGratuitousResponse [to, b, allAreUnreachable, onlyChangedEntries];
      };
      
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- SendRoutingInfoResponse
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  SendRoutingInfoResponse: PROCEDURE [
    to: System.NetworkAddress, b: Buffer.Buffer] =
    -- This proc will send out a response packet.  It is given the incoming 
    -- routing request packet, which it will properly handle.  It will set the
    -- destination to be <to>.
    BEGIN
    maxTuplesPerRoutingPacket: CARDINAL =
       (NSTypes.maxIDPDataBytes - 2*SIZE[NSTypes.RoutingInfoType]) /
       (2*SIZE[NSTypes.RoutingInfoTuple]);
    numberOfTuples: CARDINAL = (b.ns.pktLength - NSTypes.bytesPerIDPHeader -
       2*SIZE[NSTypes.RoutingInfoType]) /
      (2*SIZE[NSTypes.RoutingInfoTuple]);
      
    SendRoutingInfoResponseLocked: ENTRY PROCEDURE
      RETURNS [sent: BOOLEAN ← TRUE] =
      BEGIN ENABLE UNWIND => NULL;
      e: RoutingTableEntry;
      
      FOR i: CARDINAL IN [0..numberOfTuples) DO
        IF (b.ns.routingTuple[i].objectNetID = anyNetNetworkNumber) OR
	  (b.ns.routingTuple[i].objectNetID = anyNetNetworkNumberFor860)
	  -- Hack for the dumb 860! 
	  THEN 
	  RETURN [FALSE]; -- we'll send him a gratitous packet with all the rte's
	e ← FindNetworkNumber [b.ns.routingTuple[i].objectNetID, FALSE];
	b.ns.routingTuple[i].interrouterDelay ← 
	  IF (e = NIL) OR (e.network = NIL) THEN infinityHopCount -- no route
	  ELSE MIN [e.delay + 1, infinityHopCount];  -- we increment the count here!
	ENDLOOP;
      b.ns.pktLength ← NSTypes.bytesPerIDPHeader + 2*SIZE[NSTypes.RoutingInfoType]
        + numberOfTuples*2*SIZE[NSTypes.RoutingInfoTuple];
      b.ns.destination ← to;
      IF NOT RoutAndSendRoutingInfoResponse[b] THEN 
        Socket.ReturnBuffer[b]; 
	<< Driver.PutOnGlobalDoneQueue would be overkill since we know that
	we got the buffer through the Socket.Get procedure. We don't
	return[False] since the source would then be sent a gratuitous
	type of packet. >>
      END; -- of SendRoutingInfoResponseLocked
      
    -- start of procedure
    IF (numberOfTuples = 0) OR (numberOfTuples > maxTuplesPerRoutingPacket) 
      OR NOT SendRoutingInfoResponseLocked[] THEN
      SendGratuitousResponseLocked [to, b];
    StatIncr [@stats.specificRoutingResponseSent];
    END; -- of SendRoutingInfoResponse
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- This routine routs a routing inforamtion response packet for its
  -- destination and sends it. A few of the packet's field should already be
  -- set coming into here. Note the two special case: sending to self and
  -- sending to everyone.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RoutAndSendRoutingInfoResponse: INTERNAL PROCEDURE [b: Buffer.Buffer]
    RETURNS [success: BOOLEAN ← TRUE] =
    BEGIN
    -- Routs and sends a routing information response.
    -- Should be called from inside the monitor.
    -- The incoming b.network, b.destination, and b.ns.pktLength should 
    -- be already set.  Source net is set to be the network's, unless = 0 and 
    -- destination socket not #1 - then it's set to a more informative number.
    -- Note the special case handling when the destination is us!
    network: Network ← b.network;
    immediateHost: HostNumber ← b.ns.destination.host;
    e: RoutingTableEntry;
    destinationIsMe: BOOLEAN ← b.ns.destination.host = myHostID;
    
    b.type ← ns;
    b.ns.packetType ← routingInformation;
    b.ns.transportControl ← initialTransportControl;
    b.ns.routingType ← routingInfoResponse;
    b.ns.source ← [IF (network # NIL) THEN network.netNumber ELSE
      nullNetworkNumber, myHostID, NSConstants.routingInformationSocket];
    IF (b.ns.destination.socket # NSConstants.routingInformationSocket) AND
      (b.ns.source.net = nullNetworkNumber) THEN
      -- give them better information
      b.ns.source.net ← FindNetIDInternal [nullNetworkNumber];
    
    IF destinationIsMe THEN 
      BEGIN
      RouterInternal.SendPacket [b];
      RETURN;
      END;
    -- destination is someone else, determine correct network
    IF b.allNets ← (b.ns.destination.host = System.broadcastHostNumber) THEN
      BEGIN
      network ← b.network ← Driver.GetDeviceChain[];
      b.ns.source.net ← b.ns.destination.net ← network.netNumber;
      END;  -- broadcast on all attached networks, start with the first one.
     
    IF NOT network.alive THEN RETURN [FALSE];
    
    IF NOT b.allNets AND (b.ns.destination.net # nullNetworkNumber) THEN
      -- if the dest. is net 0, use immediateHost's default
      BEGIN -- find the route to this guy
      e ← FindNetworkNumber [b.ns.destination.net, FALSE];
      IF (e = NIL) OR ((network ← b.network ← e.network) = NIL)
        THEN RETURN [FALSE];
        -- no route to destination (assume we already know about all routes 
	-- since we are an internetwork router)
      immediateHost ← IF (e.route = unknownHostID) THEN 
        b.ns.destination.host -- we are attached to destination net -- 
	ELSE e.route -- send to next inr on path to destination net;
      END;
    
    IF RouterInternal.checkIt THEN Checksums.SetChecksum[b]
          ELSE b.ns.checksum ← 177777B;
    network.encapsulateAndSendNS[b, immediateHost]; -- IF this buffer is a
      -- broadcast, the buffer is first broadcast on this network and then
      -- put on the done queue. The Dispatcher will reset buffer's network
      -- to the next network on the driver chain and then resend the buffer
      -- on this next network. This process happens recursively until the
      -- buffer has been broadcast on all the networks on the driver chain.
      -- The Dispatcher knows to do this by the allNets flag.
    END; -- of RoutAndSendRoutingInfoResponse
   
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- UpdateRoutingTable
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- 
  UpdateRoutingTable: INTERNAL PROCEDURE [b: Buffer.Buffer] =
    BEGIN
    i: CARDINAL;
    e: RoutingTableEntry ← NIL;
    newDelay: CARDINAL;
    changed: BOOLEAN ← FALSE;
    t: NSTypes.RoutingInfoTuple;
    tuples: CARDINAL =    -- number of tuples in the packet.
      (b.ns.pktLength - NSTypes.bytesPerIDPHeader -
       2*SIZE [NSTypes.RoutingInfoType]) / (2*SIZE[NSTypes.RoutingInfoTuple]);
      
    FOR i IN [0..tuples) DO
    
      << this is all reasonably hairy. See page 28 of Yogen's Internet Transport Protocols book for further information>>
      
      t ← b.ns.routingTuple[i];
      newDelay ← Inline.BITAND[mask, t.interrouterDelay];
	-- ignore high bits.	
      IF newDelay = localHop THEN IF CommSvcFlags.doDebug THEN ERROR ELSE LOOP; -- misleading tuple 
      
      IF (e ← FindNetworkNumber[t.objectNetID, FALSE]) # NIL THEN
        BEGIN -- update an already present tuple
	IF e.route = b.ns.source.host -- new info from our supplier (case 2 from the spec)
	  OR e.timeUnits < alternatePathTimeUnitThreshHold -- time to get better info (case 3)
	  OR e.network = NIL -- need better info
	  OR newDelay < e.delay -- better route (case 4)
	  THEN
	  BEGIN
	  e.changed ← e.delay # newDelay;
	  changed ← changed OR e.changed;
	    -- to the outside world (who hear via routing info packets), there has been a change only if the <delay> has changed. Or if a destination net has been added
	  e.delay ← newDelay;
	  e.route ← b.ns.source.host;
	  e.network ← b.network;
	  IF e.delay < infinityHopCount THEN e.timeUnits ← updateCycles
	    ELSE
	    BEGIN
	    e.delay ← infinityHopCount; -- be sure that it isn't > infinityHopCount
	    e.network ← NIL;
	    e.route ← System.nullHostNumber;
	    END;
	  END;
	END -- End of update of existing tuple.
	
	ELSE -- no tuple so far
	-- collect new info because, as an INR, we know about every net 
	IF newDelay < infinityHopCount -- is it accessable?
	  AND t.objectNetID # anyNetNetworkNumber -- Paranoia
	  AND t.objectNetID # System.nullNetworkNumber -- Paranoia
	  THEN
	  BEGIN
	  e ← CommSvcHeap.MakeNode[n: SIZE[RoutingTableObject]];
	  e↑ ← [
	    nextRTE: NIL, nextNSE: NIL, destNetwork: t.objectNetID, delay: newDelay,
	    timeUnits: updateCycles, route: b.ns.source.host,
	    network: b.network, changed: TRUE];
	  AddEntry[e];
	  changed ← TRUE;
	  END;
      ENDLOOP;  --FOR i IN [0..tuples) do
    --if something has changed then propagate the information
    IF changed THEN NOTIFY routingTableChanged;
    END;  --UpdateRoutingTable


  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- ChangedState
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  ChangedState: PROCEDURE [network: Network] =
    BEGIN
    --used by driver when a network changes.
    RemoveNetworkLocked[network];
    AddNet[network];
    END;  --ChangedState

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- Start-up/ Shut-down routines. When a new INR is register with Pilot
  -- with the routine RoutingTable.Register[], the old INR is automatically
  -- unregistered. Upon the call to register, Pilot calls the stop routine
  -- for the previously registered INR and then subsequently calls the start
  -- routine of the newly registered INR.
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --

  ActivateINR: PUBLIC PROCEDURE =
  BEGIN --will be called by IRS to start INR
    IF pleaseStop THEN RoutingTable.Register[ptrToRto];
  END;
  
  DeactivateINR: PUBLIC PROCEDURE =
  BEGIN --will be called by IRS to stop INR.
    IF NOT pleaseStop THEN RoutingTable.Register[NIL];
  END;
  
  SetNSFudge: PUBLIC PROCEDURE [hops: CARDINAL] =
    BEGIN
    extraHops ← hops;
    END;
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- BroadcastRoutingRequest
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  BroadcastRoutingRequest: PROCEDURE
    [cH: Socket.ChannelHandle, net: NetworkNumber ← anyNetNetworkNumber] =
    BEGIN
    -- broadcasts a routing information request on all attached networks.
    -- If <net> is supplied, the request will be for info on that net only, else
    -- information will be requested for information on all networks the routing 
    -- information suppliers know about.
    
    b: Buffer.Buffer;
    
    FOR i:CARDINAL IN [1..3) DO
    IF (b ←  Buffer.GetBuffer [type: ns, aH: Socket.GetBufferPool[cH],
      function: send, size: smallBuffer, wait: TRUE]) # NIL THEN
	BEGIN
	b.type ← ns;
	b.ns.packetType ← routingInformation;
	b.ns.transportControl ← initialTransportControl;
	b.ns.source.host ← myHostID;
        b.ns.destination.socket ← b.ns.source.socket ←
          NSConstants.routingInformationSocket;
        b.ns.pktLength ← NSTypes.bytesPerIDPHeader +
	  2*(SIZE[NSTypes.RoutingInfoType]+SIZE[NSTypes.RoutingInfoTuple]);
        b.ns.routingType ← routingInfoRequest;
	b.ns.routingTuple[0] ← [net, infinityHopCount];
        RouterInternal.BroadcastThisPacket[b];
        END;
     Process.Pause [Process.SecondsToTicks [1]];
     ENDLOOP;
    END; -- of BroadcastRoutingRequest
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- Stop
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  Stop: PROCEDURE =
    BEGIN
    RoutingTableDeactivate[];
    JOIN routingInformationSupplierFork;
    JOIN internetRouterServerFork;
    JOIN decrementRoutingTableEntriesFork;
    CleanUpRoutingTable[];
    StopStats[];
    END;  --Stop

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- Start
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  Start: PROCEDURE =
    BEGIN
    pleaseStop ← FALSE;  << FALSE shows that we are ON >>
    
    StartStats[];
    RoutingTableActivate[];
    FOR n: Network ← Driver.GetDeviceChain[], n.next UNTIL n = NIL DO
      AddNet[n]; ENDLOOP;
    routingInformationSupplierFork ← FORK RoutingInformationSupplier [];
    internetRouterServerFork ← FORK InternetRouterServer[];
    decrementRoutingTableEntriesFork ← FORK DecrementRoutingTableEntries [];
    routingTableChangedFork ← FORK RoutingTableChanged [];
    END;  --Start
    
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- RoutingTableActivate
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RoutingTableActivate: ENTRY PROCEDURE = 
    BEGIN ENABLE UNWIND => NULL;
    routingTableHead ← NIL;
    myHostID ← Router.FindMyHostID[];
    routingTableSize ← 0;
    END;  --RoutingTableActivate
  
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  -- RoutingTableDeactivate
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --
  RoutingTableDeactivate: ENTRY PROCEDURE = INLINE
    BEGIN ENABLE UNWIND => NULL;
    pleaseStop ← TRUE;  << TRUE shows that we are OFF >>
    Process.Abort [routingInformationSupplierFork];
      -- poke him out of the Socket.Get on socket # 1
    Process.Abort [internetRouterServerFork];
      -- poke him out of WAITing to send a gratuitous pkt
    Process.Abort [decrementRoutingTableEntriesFork]; 
      -- poke him out of the WAIT timer statement
    Process.Abort [routingTableChangedFork];
      -- poke him out of the WAIT routingTableChanged statement
    END;  --RoutingTableDeactivate
    
  --**************** Statistics ****************
  
  GetRoutingTableSize: PUBLIC PROCEDURE RETURNS [LONG POINTER TO
    READONLY CARDINAL] = {RETURN [LONG [@routingTableSize]]};
  
  GetStats: PUBLIC PROCEDURE RETURNS [
    LONG POINTER TO READONLY InrStats.Stats, System.GreenwichMeanTime] =
    {RETURN [stats, lastGetStats ← System.GetGreenwichMeanTime[]]};
    
  SearchDurationBump: PROCEDURE [
    pulses: System.Pulses, search: InrStats.RoutingTableSearch] = INLINE
    BEGIN
    IF (stats = NIL) THEN RETURN;
    pulses ← System.Pulses[System.GetClockPulses[] - pulses];
    StatBump [@stats.searchTable[search].totalSearches, 1];
    PulsesBump [@stats.searchTable[search].pulsesSearching, pulses];
    END; --of SearchDurationBump
  
  StartStats: PROCEDURE =
    BEGIN
    z: UNCOUNTED ZONE = CommSvcHeap.GetInrHeap [];
    stats ← z.NEW [InrStats.Stats ← [System.GetGreenwichMeanTime[]]];
    END;
    
  StopStats: PROCEDURE =
    BEGIN
    z: UNCOUNTED ZONE = CommSvcHeap.GetInrHeap [];
    z.FREE [@stats];
    stats ← NIL;
    END;
  
  StatIncr: PROCEDURE [counter: LONG POINTER TO LONG CARDINAL] = INLINE
    --add one to counter
    BEGIN
    --locals
    counter↑ ← (counter↑ + 1) MOD (LAST[LONG CARDINAL] - 1);
    END;

  StatBump: PROCEDURE [
    counter: LONG POINTER TO LONG CARDINAL, bumpAmount: CARDINAL] = INLINE
    BEGIN
    --locals
    <<
    --add bumpAmount to counter; if bumpAmount < 10000, there will never
    --be overflow
    counter↑ ← (counter↑ + bumpAmount) MOD (LAST[LONG CARDINAL] - 10000);
    >>
    counter↑ ← MIN[(counter↑ + bumpAmount), (LAST[LONG CARDINAL] - 10000)];
    END;
    
  PulsesBump: PROCEDURE [
    counter: LONG POINTER TO System.Pulses, bumpAmount: System.Pulses] = INLINE
    BEGIN
    overflow: System.Pulses = LOOPHOLE[LAST[LONG CARDINAL]];
    counter↑ ← System.Pulses[MIN[(counter↑ + bumpAmount), overflow]];
    END;

  --**************** Main Program ****************

  --initialization (Cold)

  Process.SetTimeout[@internetRouterTimer, Process.MsecToTicks[25500]];
  -- set for 26.5 seconds so that when the extra random wait [0..7] seconds
  -- is added, the average time between gratuitous pkts is 30 seconds
  Process.SetTimeout[@auxInternetRouterTimer, Process.MsecToTicks[500]];
  Process.DisableTimeout [@routingTableChanged];
  Process.EnableAborts [@internetRouterTimer];
  Process.EnableAborts [@auxInternetRouterTimer];
  Process.EnableAborts [@routingTableChanged];

  END.  --RoutingTableImpl module.

<<

LOG

30-Dec-82 10:17:11  AOF  Allow for SendErrorPacket consuming errored buffer.
17-Mar-83 13:03:09  AOF  Separate from Pilot.
18-Mar-83 16:57:40  SRB  Made into an INR. Added Activate/DeactivateINR procs to register/unregister INR rto with Router. Deleted GetRoutingEntry, RoutingTableCacheFault, BroadcastRoutingRequest. Fill proc. has become a NOP, also GetDelay raises an ERROR if destNet is not found in INR table
22-Mar-83 16:07:11  SRB  Deleted ProbeAnInternetRouter and all the counters & timers that go with it. Simplified FindNetworkNumberLocked
22-Mar-83 18:21:48  SRB  Re-introduced BroadcastRoutingRequest(needed to set up the Routing Table on activation of the INR). Simplified RoutingInformationPacket (deleted tests of "are we an INR?")
23-Mar-83 13:33:01  SRB  Deleted SanityCheck(it was incorrect to say destNets with 0 delay were an ERROR)
24-Mar-83 11:58:37  SRB  BroadcastRoutingRequest returns immediately. Deleted maxRouterDelay & associated checks. Fixed up Start sequence of events. ActivateINR now takes as input param. the number of buffers to be allocated for internet.routing. 
6-Jun-83 14:54:53   SRB  Replaced CommHeap with CommSvcHeap. Detached BroadcastRoutingRequest procedure in order to build up routing table. BroadcastRoutingRequest now continues broadcasting (up to a maximum of 15 times) until it finds that UpadateRoutingTable has set routingTableChanged to TRUE - meaning that at least one routingInfo packet was received and the routing table is not empty anymore.
Open issues at start-up time: 1) Should we wait after detaching BroadcastRoutingRequest. 2) How do we acquire a network number - through IRS, drivers added by IRS, Pilot, etc. there needs to be some careful synchronization between IRS, Drivers and INR.

25-Jul-83 18:12:46	LSK	Don't check that a driver is in driver chain when responding to routing info request since a) driver may be part of clusternet (not on global chaion) b) AOF says checking the alive bit is all that is needed
 7-Oct-83 15:38:09	LSK	Update to Klamath 
 7-Oct-83 18:54:35	LSK	Forwarding stats doesn't all reset now
 9-Oct-83 15:55:13	LSK	Created buffer pool with 40 pkts for forwarding. Use small pkts for broadcasting routing request.  Now have three processes alive: 1 to age table entries. Second to handle pkts that come in on socket # 1,  and the third process sends gratuitous pkts.
10-Oct-83 13:22:05	LSK	Update to new InrFriends def
13-Oct-83 18:35:27	LSK	Only Activate if we are stopped, only deactivate if we are started
14-Oct-83 18:21:57	LSK	Redo Route enumeration
16-Oct-83 14:19:21	LSK	Added InrFriends.GetRouteInfo
17-Oct-83 15:22:13	LSK	Fix byDistance case of EnumerateRoutes
17-Oct-83 19:10:16	LSK	Initialize a couple of variables (sigh.)
18-Oct-83 13:32:44	LSK	Supply phonenetwork clientData in GetDetails procedure
27-Nov-83 18:51:26	LSK	Updated to new PhoneNet driver
29-Nov-83 21:44:56	LSK	Use PhoneNetFriends instead of PhoneNetInternal
 3-Dec-83 13:52:00	LSK	Added FlushCacheProc field to RoutingTable.Object, send out routing response when new network is added
16-Dec-83 17:55:19	LSK	Don't use routing responses that aren't from socket 1 or that are forwarded.  Don't crash with misnumbered net trap unless during doDebug
 5-Jan-84 11:42:24	LSK	Added some unwind catch code. Initialize stats counters.
 9-Feb-84 16:28:54	LSK	Bug fix noticed by Hal.
16-Feb-84 16:55:50	LSK	Use CommFlags.doStats where appropriate; Added 1 Sec delay before sending routing packet; adjusted internetRouterTimer; If a driver does go away, set the delay to be 16, not 15. Send out routing responses with max delay of 16; Munged UpdateRoutingTable
17-Feb-84 17:50:00	LSK	Only send out information on changed routes when a route changes. (Send information on all routes about every 30 sec.)
17-Feb-84 18:56:39	LSK	Set clientData for X25 routes
22-Mar-84 23:06:44	LSK	Added unwind catch phrases so the inr would deactivate instead of hang; added stats; depend on PhoneNetInternal at compile time instead of PhoneNetFriends at runtime. (The Phonenet is not included in the bootfile.)
23-Mar-84 18:42:45	LSK	Start the stats sooner in the Start proc
25-Mar-84 15:36:41	LSK	Don't scribble over memory; set the stats.timeActivated field
28-Mar-84 17:02:28	LSK	Respond to the 860's idea of the anyNet network number in routing request pkt's
28-Mar-84 17:47:18	LSK	Don't send out routing info pkts larger than IDP max length
 5-Jun-84 19:50:03	LSK	Always crash if we hit a misnumbered net trap
 6-Jun-84 16:53:53	LSK	okay to receive a RoutingInfo response that comes from a driver not on the global chain. (Such is the case for INR's attached to our clusternet.)
 6-Jun-84 19:34:16	LSK/DMT	 Broke dependency on PhoneNetInternal by LOOPHOLE.
10-Sep-84 10:31:10	Leong	bump stats.bytesForwarded by b.ns.pktLength which is ALREADY in bytes (was incremented by b.ns.pktLength*2)
10-Sep-84 11:45:19	Leong	GetStats now also returns a snap time
10-Sep-84 16:04:33	Leong	stats.tupleIndexTable is now properly incremented
12-Sep-84 14:13:46	Leong	stats initialized to NIL and ForwardingStats checks for NIL (Bug fix noticed by Hal)
13-Sep-84 17:19:40	Leong	Added stats.msSearchingRoutingTable
19-Sep-84 15:21:32	Leong	Changed stats.msSearchingRoutingTable to searchTable
19-Oct-84 15:22:30	Leong	Add fudge hops when sending RoutingReponse packets; export RoutingFudges.SetNSFudge; remove SHARE clause
22-Oct-84 13:00:39	Leong	Keep track of pulses instead of milliseconds
23-Oct-84 15:54:04	Leong	StatBump uses MIN instead of MOD; always collect NS stats (ignore CommFlags.doStats)
>>