-- File: ArpaRoutingTableImpl.mesa - last edit:
-- AOF                  1-Mar-88  9:54:38
-- JAV                  7-Dec-87 16:54:06
-- SMA                 11-Jun-86 16:24:41
-- Copyright (C) 1985, 1986, 1987, 1988 by Xerox Corporation. All rights reserved.

DIRECTORY
  ArpaBuffer USING [
    Body, Buffer, BufferBody, DestroyPool, GetBuffer, MakePool, AccessHandle, To,
    QueueCleanup, QueueInitialize, QueueObject, ReturnBuffer, TransferStatus],
  ArpaFlags USING [doStats],
  ArpaPortInternal USING [AddrMatch, AddrMismatch, BuildMasks, Checksum,
    GetGatewayAddr, GetMyBroadcastAddr, GetMyNullAddr, GetSubnetMask, SendPacket],
  ArpaPort USING [Handle, minIPHeaderBytes],
  ArpaRouter USING [GetAddress, unknownInternetAddress],
  ArpaRoutingTable USING [AddNetworkProc, AddRouteProc, EnumerateProc,
    FillTableProc, FindNetworkProc, FlushCacheProc, GetDelayProc, NetworkContext,
    RemoveRouteProc, RemoveNetworkProc, RoutersFunction, 
    StateChangedProc, Handle, Object],
  ArpaStats USING [Incr],
  ArpaSysParameters USING [GetTypeOfService],
  ArpaTypes USING [BufferBody, Byte, Icmp, IcmpType, InternetAddress, Port],
  Buffer USING [],
  ByteBlt USING [ByteBlt],
  CommHeap USING [zone],
  Driver USING [GetDeviceChain, Device, PutOnGlobalDoneQueue],
  Environment USING [Byte, bytesPerWord],
  Inline USING [DBITAND],
  Process USING [MsecToTicks, Pause],
  Protocol1 USING [EncapsulateAndTransmit, GetContext],
  System USING [GetClockPulses];

ArpaRoutingTableImpl: MONITOR
  IMPORTS
    ArpaBuffer, ArpaPortInternal, ArpaRouter, ArpaStats, 
    ArpaSysParameters, ByteBlt, CommHeap, Driver, Inline,
    Process, Protocol1, System
  EXPORTS ArpaRouter, ArpaRoutingTable, Buffer =
  BEGIN
  
  <<
  This is the implementation module for local routing.  Subnet local routing
  will probably live here also.  Beware - lots of work needs to be done
  for this to run on multiple interfaces.
  >>
  
  Device: PUBLIC --Buffer-- TYPE = Driver.Device;
  Port: PUBLIC --ArpaPort-- TYPE = ArpaTypes.Port;
  InternetAddress: PUBLIC --ArpaRouter-- TYPE = ArpaTypes.InternetAddress;
  
  RTEntry: TYPE = LONG POINTER TO RTEObject;
  RTEObject: TYPE = RECORD [
    next: RTEntry,		            -- pointer to next entry in "table".
    dest: InternetAddress,                    -- ultimate destination address.
    mask: InternetAddress,		    -- for comparisons.
    delay: CARDINAL,			    -- measured in hops to the dest.
    lastAccess: LONG CARDINAL,		    -- when this entry was last used.
    route: InternetAddress,	            -- host num of gateway to next net.
    context: ArpaRoutingTable.NetworkContext, -- my protocol specific addresses.
    changed: BOOLEAN ← FALSE]; 	    -- set when value is changed or added
    
  pleaseStop: BOOLEAN;  
  routingTableSize: CARDINAL ← 0;
  routingTableHead: RTEntry ← NIL;
  routerPool: ArpaPort.Handle ← NIL;
  requestPool: ArpaBuffer.AccessHandle;
  bpw: NATURAL = Environment.bytesPerWord;
  outQueue: ArpaBuffer.QueueObject;  --send buffers needing routing information.
  startEnum: InternetAddress = ArpaRouter.unknownInternetAddress;
  endEnum: InternetAddress = [LAST[CARDINAL], LAST[CARDINAL]];

  
  --Information about the primary network interface.
  myDevice: Device ← NIL;
  myNullAddr: InternetAddress;
  myGatewayAddr: InternetAddress;
  myBroadcastAddr: InternetAddress;
  myContext: ArpaRoutingTable.NetworkContext ← NIL;
    
  defaultRth: PUBLIC ArpaRoutingTable.Handle ← @rto;
  rto: ArpaRoutingTable.Object ← [
    type: normal, start: Start, stop: Stop, startEnumeration: startEnum,
    endEnumeration: endEnum, enumerate: Enumerate, fillTable: Fill,
    getDelay: GetDelay, transmit: Transmit, forward: Forward,
    findNetwork: FindLocalNetID, addNetwork: AddNet, removeNetwork: RemoveNet,
    flushCache: FlushCache, stateChanged: ChangedState, addRoute: AddRoute,
    removeRoute: RemoveRoute];
  
  AddEntry: INTERNAL PROC [e: RTEntry] =
    BEGIN
    entry, previous: RTEntry ← NIL;
    
    Greater: PROC [a, b: InternetAddress] RETURNS [BOOLEAN] =  
      BEGIN
      NetWithCardinal: TYPE = MACHINE DEPENDENT RECORD [a, b: CARDINAL];
      aWithCardinal: NetWithCardinal ← LOOPHOLE[a];
      bWithCardinal: NetWithCardinal ← LOOPHOLE[b];
      --RETURNS[a > b];
      RETURN[
        (aWithCardinal.a > bWithCardinal.a)
          OR
            ((aWithCardinal.a = bWithCardinal.a)
              AND (aWithCardinal.b > bWithCardinal.b))];
      END;  --Greater
    
    FOR entry ← routingTableHead, entry.next UNTIL entry = NIL DO
      IF ~Greater[e.dest, entry.dest] THEN {
        e.next ← entry;
	previous.next ← e;
	EXIT};
      previous ← entry;
    ENDLOOP;
    IF entry = NIL THEN 
      IF routingTableHead = NIL THEN 
        routingTableHead ← e ELSE previous.next ← e;
    routingTableSize ← routingTableSize + 1;
    END; -- of AddEntry
    
  
  AddNet: PUBLIC PROCEDURE [context: ArpaRoutingTable.NetworkContext] =
    BEGIN  --Add state for an attached net.
    IF context.net = ArpaRouter.unknownInternetAddress THEN NULL
    ELSE AddDriverInternal[context];
    END;  --AddNet
    
  AddDriverInternal: PROC [context: ArpaRoutingTable.NetworkContext] =
    BEGIN
      <<
      Tells the routing table about a new attached network.  The driver
      must know the network number at this point.  Called by 
      ExamineResponse and Locked, both of which hold the monitor.
      >>
      entry: RTEntry;
      SELECT TRUE FROM
	(~context.network.alive) => RETURN;
	((entry ← FindNetworkNumber[context.net]) # NIL) => RETURN;
	ENDCASE;
      AddRoute[context.net,
        IF ArpaPortInternal.GetSubnetMask[] # ArpaRouter.unknownInternetAddress
	  THEN ArpaPortInternal.GetSubnetMask[] ELSE context.netMask,
	ArpaRouter.unknownInternetAddress, 0, context];
	<<
	The route should be the unknownInternetAddress since all routes are to
	directly connected devices.
	>>
    END;  --AddDriverInternal
   
  AddRoute: ENTRY ArpaRoutingTable.AddRouteProc =
    BEGIN
    <<
    It is the user's responsibility to choose his host and subnet number 
    carefully enough that there is no confusion between subnetted and 
    non-subnetted hosts!
    >>
    e: RTEntry ← NIL;
    IF (e ← FindNetworkNumber[dest]) = NIL THEN
      BEGIN
      e ← CommHeap.zone.NEW[RTEObject ← [
        next: NIL, dest: dest, mask: mask, delay: delay,
        lastAccess: System.GetClockPulses[], route: route,
	context: context, changed: TRUE]];
	AddEntry[e];
      END
    ELSE
      BEGIN
      e.mask ← mask;
      IF e.delay >= delay THEN
        BEGIN
	e.delay ← delay;
	e.route ← route;
	e.context ← context;
	e.changed ← TRUE;
	END;
      END;
    END;  --AddRoute
    
  
  CleanUpRoutingTable: PROC =
    BEGIN
    temp: RTEntry;
    WHILE routingTableHead # NIL DO
      temp ← routingTableHead; routingTableHead ← routingTableHead.next;
      routingTableSize ← routingTableSize - 1; CommHeap.zone.FREE[@temp];
      ENDLOOP;
    END;  --CleanUpRoutingTable
  
  
  Enumerate: ENTRY ArpaRoutingTable.EnumerateProc =
    BEGIN  --This procedure will return any but the null entry.

    Greater: PROC [a, b: InternetAddress] RETURNS [BOOLEAN] =  
      BEGIN
      NetWithCardinal: TYPE = MACHINE DEPENDENT RECORD [a, b: CARDINAL];
      aWithCardinal: NetWithCardinal ← LOOPHOLE[a];
      bWithCardinal: NetWithCardinal ← LOOPHOLE[b];
      --RETURNS[a > b];
      RETURN[
        (aWithCardinal.a > bWithCardinal.a)
          OR
            ((aWithCardinal.a = bWithCardinal.a)
              AND (aWithCardinal.b > bWithCardinal.b))];
      END;  --Greater
      
    e: RTEntry;
    next: InternetAddress ← endEnum;
    route ← endEnum;
    FOR e ← routingTableHead, e.next UNTIL e = NIL DO
      IF delay # e.delay THEN LOOP;
      IF Greater[e.dest, previous]  --greater than the one he has now
        AND ~Greater[e.dest, next] THEN { --less than any we know about since 
	 IF onlyChangedValues THEN 
	   IF e.changed THEN {e.changed ← FALSE; route ← e.dest}
	   ELSE LOOP ELSE route ← e.dest;
	 RETURN};
      ENDLOOP;
    END;  --Enumerate
    
    
  Fill: ArpaRoutingTable.FillTableProc =
    BEGIN  --PROC[maxDelay: CARDINAL]
    END;  --Fill
    
    
  FindLocalNetID: ArpaRoutingTable.FindNetworkProc =
    BEGIN
    <<
    PROC[net: ArpaRouter.InternetAddress] RETURNS[ArpaRouter.InternetAddress];
    Returns the network number relative to the destination network specified.
    If we cannot find a number relative to the destination, we use the first
    network with a known number. **we need to do the dest relative part!
    >>
    myNet: InternetAddress ← ArpaRouter.unknownInternetAddress;
    FOR n: Device ← Driver.GetDeviceChain[], n.next UNTIL n = NIL DO
        c: ArpaRoutingTable.NetworkContext ← Protocol1.GetContext[n, arpa];
	SELECT TRUE FROM
	  (c = NIL) => NULL;  --not even close
	  (~c.network.alive) => NULL;  --no better
	  (c.net = ArpaRouter.unknownInternetAddress) => NULL;
	  ENDCASE => {myNet ← c.net; EXIT};  --good enough
        ENDLOOP;
    RETURN[LOOPHOLE[myNet]];
    END;  --FindLocalNetID
    
    
  Forward: PROC[b: ArpaBuffer.Buffer] =
    BEGIN
    e: RTEntry;
    nextHost: InternetAddress;
    body: ArpaBuffer.Body ← b.arpa;
    
      SendIcmp: PROCEDURE [type: ArpaTypes.IcmpType, body: ArpaBuffer.Body] =
        BEGIN
	  b: ArpaBuffer.Buffer ← ArpaBuffer.GetBuffer[
	    requestPool, send, TRUE, 120];
          icmpBody: LONG POINTER TO icmp ArpaBuffer.BufferBody ← LOOPHOLE[b.arpa];
	  icmpData: LONG POINTER TO PACKED ARRAY CARDINAL[1..1) OF
	    ArpaTypes.Byte ← LOOPHOLE[icmpBody];
	  
	  --ip fields
	  icmpBody.ipHeader.destination ← body.ipHeader.source;
	  icmpBody.ipHeader.source ← myGatewayAddr;
	  icmpBody.ipHeader.protocol ← icmp;
	  icmpBody.ipHeader.service ← ArpaSysParameters.GetTypeOfService[];
	  icmpBody.ipHeader.identification ← 0;
	  icmpBody.ipHeader.lifetime ← 60;
	  icmpBody.ipHeader.ihl ← (ArpaPort.minIPHeaderBytes+3)/4;
	  SELECT type FROM
	    redirect => {
	      icmpBody.icmp ← [redirect[
	        code: 0, checksum: 0, redirect: e.route, icmpData: ]];
	      WITH redirect: icmpBody.icmp SELECT FROM
	        redirect => icmpData ← LOOPHOLE[@redirect.icmpData]; ENDCASE;
	      --BLT ipHeader + first 64 bits of data or 4 words
	      [] ← ByteBlt.ByteBlt[
		to: [LOOPHOLE[icmpData], 0,
		  120 - ArpaPort.minIPHeaderBytes -
		  SIZE[redirect ArpaTypes.Icmp]*bpw],
		from: [LOOPHOLE[body], 0,
		  body.ipHeader.ihl * 4 + 8]];
	      icmpBody.ipHeader.length ←
	        icmpBody.ipHeader.ihl*4 +
	        body.ipHeader.ihl*4 +
	        SIZE[redirect ArpaTypes.Icmp]*bpw + 8;
	      WITH redirect: icmpBody.icmp SELECT FROM
		redirect => redirect.checksum ← ArpaPortInternal.Checksum[
		  0, body.ipHeader.ihl*2 +
		  SIZE[redirect ArpaTypes.Icmp] +
		  4, @icmpBody.icmp];
		ENDCASE
	      };
	      
	    <<
	    The size of the packet is the IP overhead + ICMP fields +
	    offending IP header + 8 bytes of the offenders data.
	    >>
	    timeExceeded => {
	      icmpBody.icmp ← [timeExceeded[
	        code: toLive, checksum: 0, unused: [0, 0], icmpData: ]];
	      WITH timeExceeded: icmpBody.icmp SELECT FROM
	        timeExceeded => icmpData ← LOOPHOLE[@timeExceeded.icmpData];
	        ENDCASE;
	      --BLT ipHeader + first 64 bits of data or 4 words
	      [] ← ByteBlt.ByteBlt[
		to: [LOOPHOLE[icmpData], 0,
		  120 - ArpaPort.minIPHeaderBytes -
		  SIZE[timeExceeded ArpaTypes.Icmp]*bpw],
		from: [LOOPHOLE[body], 0, body.ipHeader.ihl * 4 + 8]];
	      icmpBody.ipHeader.length ← icmpBody.ipHeader.ihl*4 + body.ipHeader.ihl*4 + SIZE[timeExceeded ArpaTypes.Icmp]*bpw + 8;
	      WITH timeExceeded: icmpBody.icmp SELECT FROM
		timeExceeded => timeExceeded.checksum ←
		  ArpaPortInternal.Checksum[0,
		    body.ipHeader.ihl*2 + SIZE[timeExceeded ArpaTypes.Icmp] + 4,
		    @icmpBody.icmp];
		ENDCASE
	      };
	      
	    unreachable => {
	      icmpBody.icmp ← [unreachable[
	        code: net, checksum: 0, unused: [0, 0], icmpData: ]];
	      WITH unreachable: icmpBody.icmp SELECT FROM
	        unreachable => icmpData ← LOOPHOLE[@unreachable.icmpData];
	        ENDCASE;
	      --BLT ipHeader + first 64 bits of data or 4 words
	      [] ← ByteBlt.ByteBlt[
		to: [LOOPHOLE[icmpData], 0,
	          120 - ArpaPort.minIPHeaderBytes -
		  SIZE[unreachable ArpaTypes.Icmp]*bpw],
		from: [LOOPHOLE[body], 0, body.ipHeader.ihl * 4 + 8]];
	      icmpBody.ipHeader.length ←
	        icmpBody.ipHeader.ihl*4 + body.ipHeader.ihl*4 +
	        SIZE[unreachable ArpaTypes.Icmp]*bpw + 8;
	      WITH unreachable: icmpBody.icmp SELECT FROM
		unreachable => unreachable.checksum ←
		  ArpaPortInternal.Checksum[0,
		    body.ipHeader.ihl*2 + SIZE[unreachable ArpaTypes.Icmp] + 4,
		    @icmpBody.icmp];
		ENDCASE
	      };
	  ENDCASE;
	  ArpaPortInternal.SendPacket[b, remote];
	END;

    SELECT TRUE FROM
      (e ← FindNetworkNumber[body.ipHeader.destination]) = NIL => {
	-- noRoute - send ICMP unreachable
        SendIcmp[unreachable, body]; ArpaBuffer.ReturnBuffer[b]};
      (e.delay = 0) AND (b.fo.context = e.context) =>
        BEGIN
	<<
	Looping to same net send redirect to source and packet
	to correct gateway.
	>>
	body.ipHeader.lifetime ← body.ipHeader.lifetime - 1;  -- reduce lifetime
	<<THIS IS AN INTERESTING CONSTRUCT. I'M AT A LOSS AS TO WHAT IT DOES.>>
	IF body.ipHeader.lifetime = 0 THEN NULL;
	--we are directly attached so let's give it to them.
	nextHost ← body.ipHeader.destination;
	body.ipHeader.checksum ← 0;
	body.ipHeader.checksum ← ArpaPortInternal.Checksum[
	  0, body.ipHeader.ihl * bpw, @body.ipHeader];
	  -- recompute checksum for new packet.
	b.fo.status ← ArpaBuffer.TransferStatus[goodCompletion];
	SendIcmp[redirect, body];	-- do it before we lose the data
	Protocol1.EncapsulateAndTransmit[ArpaBuffer.To[b], @nextHost];
	END;
    ENDCASE =>
      BEGIN
      --packet destined for another net and should be forwarded to next gateway.
      body.ipHeader.lifetime ← body.ipHeader.lifetime - 1;  -- reduce lifetime
      IF body.ipHeader.lifetime = 0 THEN
        BEGIN
	--SEND ICMP timeExceeded;
	SendIcmp[timeExceeded, body];
	ArpaBuffer.ReturnBuffer[b];
	RETURN;
	END;
      nextHost ← IF e.delay # 0 THEN e.route ELSE body.ipHeader.destination;
      b.fo.network ← e.context.network;
      b.fo.context ← e.context;	-- what driver gets buffer
      body.ipHeader.checksum ← 0;
      body.ipHeader.checksum ← ArpaPortInternal.Checksum[
        0, body.ipHeader.ihl * bpw, @body.ipHeader];
      b.fo.status ← ArpaBuffer.TransferStatus[goodCompletion];
      Protocol1.EncapsulateAndTransmit[ArpaBuffer.To[b], @nextHost];
      END;
    END;  --Forward
    
  
  FindNetworkNumber: PROC [dest: InternetAddress] RETURNS [e: RTEntry] =
    BEGIN
    <<
    Searches for and returns the entry the specified network number (dest).
    If an entry is not found, e is NIL.
    >>
    e ← routingTableHead;
    FOR e ← routingTableHead, e.next UNTIL e = NIL
      OR ArpaPortInternal.AddrMatch[e.mask, dest, e.dest] DO ENDLOOP;
    END;  --FindNetworkNumber
    
    
  FlushCache: ArpaRoutingTable.FlushCacheProc =
    BEGIN
    END;  --FlushCache
    
  
  GetDelay: ArpaRoutingTable.GetDelayProc =
    BEGIN
    END;  --GetDelay
    
    
  InfoReply: PUBLIC <<ArpaRoutingTable>> PROC [b: ArpaBuffer.Buffer] =
    BEGIN OPEN c: NARROW[b.fo.context, ArpaRoutingTable.NetworkContext];
    <<
    Processes an ICMP information reply message.  If the net number is unknown,
    we will take any info, regardless of whether or not it is an answer to our
    request.
    >>
    nmsk: InternetAddress = c.netMask;
    SELECT TRUE FROM 
      (ArpaPortInternal.AddrMismatch[c.netMask, c.net, myNullAddr]) => NULL;
      (ArpaPortInternal.BuildMasks[b.arpa.ipHeader.source].netMask # nmsk) =>
        NULL;  --incorrect address class.
      ENDCASE => c.net ← LOOPHOLE[Inline.DBITAND[
        LOOPHOLE[b.arpa.ipHeader.source], LOOPHOLE[nmsk]]];
    END;  --InfoReply
    
    
  InfoRequest: PROC =
    BEGIN  --Sends a ICMP info request to the local gateway.
    b: ArpaBuffer.Buffer ← ArpaBuffer.GetBuffer[requestPool, send, TRUE, 120];
    body: LONG POINTER TO icmp ArpaBuffer.BufferBody ← LOOPHOLE[b.arpa];
      
    --ip fields
    body.ipHeader.destination ← myGatewayAddr;
    body.ipHeader.source ← ArpaRouter.GetAddress[];
    body.ipHeader.protocol ← icmp;
    body.ipHeader.service ← ArpaSysParameters.GetTypeOfService[];
    body.ipHeader.identification ← 0;
    body.ipHeader.lifetime ← 60;
    body.ipHeader.ihl ← (ArpaPort.minIPHeaderBytes+3)/4;
    body.ipHeader.length ← body.ipHeader.ihl*4 + 8;
    body.icmp ← [infoRequest[code: 0, identifier: 0, sequence: 0, checksum: 0]];
    WITH info: body.icmp SELECT FROM
      infoRequest => info.checksum ← ArpaPortInternal.Checksum[
        0, SIZE[infoRequest ArpaTypes.Icmp], @body.icmp.body];
      ENDCASE; 
    ArpaPortInternal.SendPacket[b, remote];
    END;  --InfoRequest
    
    
  ProbeGateway: PUBLIC <<ArpaRoutingTable>> PROC =
    BEGIN
    c: ArpaRoutingTable.NetworkContext ← NIL;
    
    NullNet: ENTRY PROC [nw: Device]
      RETURNS [ct: ArpaRoutingTable.NetworkContext] =
      --checks if any of the devices supporting arpa have null net numbers.
      BEGIN
      ct ← Protocol1.GetContext[nw, arpa];
      SELECT TRUE FROM
	(ct = NIL) => NULL;  --He doesn't support us?!
	(~ct.network.alive) => NULL;  --he would but he croaked
	(ct.net = ArpaRouter.unknownInternetAddress) => RETURN[ct];
	ENDCASE;
      ct ← NIL;
      END;  --NullNet
        
    FOR n: Device ← Driver.GetDeviceChain[], n.next UNTIL n = NIL DO
      IF (c ← NullNet[n]) # NIL THEN
	SELECT TRUE FROM
	--the "host" has a net specified in it.
	  ArpaPortInternal.AddrMismatch[c.netMask, c.host, myNullAddr] =>
	    BEGIN
	    e: RTEntry;
	    AddLocked: ENTRY PROC = {AddEntry[e]};
	    c.net ← LOOPHOLE[
	      Inline.DBITAND[LOOPHOLE[c.host], LOOPHOLE[c.netMask]]];
	    e ← CommHeap.zone.NEW[RTEObject ← [
	      next: NIL, dest: c.net, mask: c.netMask, delay: 0,
	      lastAccess: System.GetClockPulses[],
	      route: ArpaRouter.unknownInternetAddress,
	      context: c, changed: TRUE]];
	    AddLocked[];
	    END;
	  myGatewayAddr = ArpaRouter.unknownInternetAddress => NULL;  --no gateway
	  ENDCASE =>
	    FOR i: CARDINAL IN [0..5) UNTIL
	      c.net # ArpaRouter.unknownInternetAddress DO
	      InfoRequest[];
	      Process.Pause[Process.MsecToTicks[1000]];
	      ENDLOOP;
      ENDLOOP;
    END;  --ProbeGateway
    
    
  Redirect: PUBLIC <<ArpaRoutingTable>> ENTRY PROC [b: ArpaBuffer.Buffer] =
    BEGIN  --processes an ICMP redirect packet.
    ENABLE UNWIND => NULL;
    body: ArpaBuffer.Body ← b.arpa;  --This is the redirect icmp packet
    WITH redirect: body.icmp SELECT FROM
      redirect =>
        BEGIN
	e: RTEntry ← NIL;
	route: InternetAddress;
	icmp: ArpaBuffer.Body ← LOOPHOLE[@redirect.icmpData];  --offending packet
	route ← redirect.redirect;  --the new, improved gateway to use
	IF (e ← FindNetworkNumber[icmp.ipHeader.destination]) = NIL THEN
	  BEGIN
	  e ← CommHeap.zone.NEW[RTEObject ← [
	    next: NIL, dest: icmp.ipHeader.destination,
	    mask: ArpaPortInternal.BuildMasks[icmp.ipHeader.destination].netMask,
	    delay: 0, lastAccess: System.GetClockPulses[], route: route,
	    context: b.fo.context, changed: TRUE]];
	    AddEntry[e];
	  END
	ELSE
	  BEGIN
	  e.route ← route;
	  e.delay ← 0;
	  e.context ← b.fo.context;
	  END;
	END;
      ENDCASE;
    END;  --Redirect
    
  RemoveEntry: INTERNAL PROC [e: RTEntry] =
    BEGIN  -- Removes the specified entry from the routing table.
    prev: RTEntry ← NIL;
    temp: RTEntry ← routingTableHead;
    UNTIL (temp = NIL) OR (temp = e) DO prev ← temp; temp ← temp.next; ENDLOOP;
    IF prev = NIL THEN routingTableHead ← e.next
    ELSE prev.next ← e.next;
    e.next ← NIL;
    CommHeap.zone.FREE[@e];
    routingTableSize ← routingTableSize - 1;
    END;  --RemoveEntry 
    
    
  RemoveNet: ENTRY PROCEDURE [context: ArpaRoutingTable.NetworkContext] =
    BEGIN  --remove state for attached network.    
    <<
    This procedure removes the specified attached network and all entries
    referencing it from the routing table. Multi entries may use this net.
    The loop doesn't increment the count on elements removed because the
    number of entries will be decremented by the "RemoveElement[entry.net]"
    statement.  In effect the number of entries is coming back to equal the
    number of elements counted.
    >>
    entry: RTEntry ← routingTableHead;
    UNTIL entry = NIL DO
      SELECT TRUE FROM
        (entry.context = NIL) => NULL;  --don't increment count
        (entry.context = context) => RemoveEntry[entry];
        ENDCASE;
      entry ← entry.next;
      ENDLOOP;
    END;  --RemoveNet
    
     
  RemoveRoute: ENTRY ArpaRoutingTable.RemoveRouteProc =
    BEGIN
    e: RTEntry ← NIL;
    IF (e ← FindNetworkNumber[dest]) = NIL THEN RETURN;
    RemoveEntry[e];
    END;  --RemoveRoute
    
  RoutingTableActivate: PROC =
    BEGIN
    ActivateLocked: ENTRY PROC =
      BEGIN
      ArpaBuffer.QueueInitialize[@outQueue];
      requestPool ← ArpaBuffer.MakePool[send: 2, receive: 0, type: normalPool];
      myDevice ← Driver.GetDeviceChain[];
      myContext ← Protocol1.GetContext[myDevice, arpa];
      myGatewayAddr ← ArpaPortInternal.GetGatewayAddr[];
      myBroadcastAddr ← ArpaPortInternal.GetMyBroadcastAddr[];
      myNullAddr ← ArpaPortInternal.GetMyNullAddr[];
      END;
    ActivateLocked[];
    <<
    Add the special null entry for talking without a net number. This entry
    does not show up in Enumerate.
    >>
    AddRoute[myNullAddr, myContext.netMask, ArpaRouter.unknownInternetAddress, 0, myContext];
    AddRoute[myBroadcastAddr, myContext.netMask, ArpaRouter.unknownInternetAddress, 0, myContext];
    END;  --RoutingTableActivate
    
    
  RoutingTableDeactivate: ENTRY PROC = INLINE
    BEGIN
    pleaseStop ← TRUE;
    routingTableSize ← 0;
    ArpaBuffer.QueueCleanup[@outQueue];
    ArpaBuffer.DestroyPool[requestPool];
    END;  --RoutingTableDeactivate
    
    
  Start: PROC =
    BEGIN  --This procedure turns the router on.
    pleaseStop ← FALSE;
    RoutingTableActivate[];
    END;  --Start
    
    
  ChangedState: PUBLIC PROCEDURE [context: ArpaRoutingTable.NetworkContext] =
    BEGIN
    RemoveNet[context];
    AddNet[context];
    END;  --ChangedState
    
    
  Stop: PROC =
    BEGIN
    RoutingTableDeactivate[];
    CleanUpRoutingTable[];
    END;  --Stop
    
    
  Transmit: ENTRY PROC [b: ArpaBuffer.Buffer] =
    BEGIN
    body: ArpaBuffer.Body ← b.arpa;
    nextHost, nmsk: InternetAddress;
    e: RTEntry;
    
    nmsk ← ArpaPortInternal.BuildMasks[body.ipHeader.destination].netMask;
    SELECT TRUE FROM
      (e ← FindNetworkNumber[body.ipHeader.destination]) = NIL =>
	BEGIN
	--if we don't know the route, we will try sending it to our default
	--gateway.
	IF myGatewayAddr # ArpaRouter.unknownInternetAddress THEN
	  BEGIN
	  nextHost ← myGatewayAddr;
	  b.fo.context ← myContext;
	  b.fo.network ← myDevice;
	  END
	ELSE  --we don't know how to get there, and we have no gateway to ask.
	  BEGIN
	  IF ArpaFlags.doStats THEN ArpaStats.Incr[noRoute];
	  b.fo.status ← noRouteToNetwork;
	  Driver.PutOnGlobalDoneQueue[ArpaBuffer.To[b]];
	  RETURN;
	  END;
	END;
      ENDCASE =>
        BEGIN  --entry exists in table already.
        e.lastAccess ← System.GetClockPulses[];
        nextHost ←
          IF e.route # ArpaRouter.unknownInternetAddress THEN e.route  --gateway 
          ELSE body.ipHeader.destination;  --attached to target net
        b.fo.context ← e.context;
        b.fo.network ← e.context.network;
        END;
    b.fo.status ← ArpaBuffer.TransferStatus[goodCompletion];
    Protocol1.EncapsulateAndTransmit[ArpaBuffer.To[b], @nextHost];
    END;  --Transmit


  END.
  
LOG

14-Jan-85 15:28:22  SMA  Created file.
13-Jul-85 13:54:29  SMA  Added stats.
13-Nov-85 15:07:43  SMA  ArpaProtocol => Arpa10MBit and ArpaPortInternal.
 7-Jan-86 19:49:30  SMA  Added Redirect and InfoReply for icmp. 
14-Feb-86 13:40:19  SMA  Added InfoRequest.
10-Mar-86 13:28:10  SMA  ICMP checksums.
10-Jun-86 14:45:45  SMA  Different Enumerate.
19-Nov-86 11:52:23  JAV  Added RIP
10-Mar-87 19:41:47  AOF  Funston buffer manager
21-May-87 13:23:54  AOF  Correct spelling of infoReqeust => infoRequest
21-May-87 13:50:33  AOF  Use existance of info request/response in ArpaTypes
29-Sep-87 17:59:12  JAV  Ordered routing list in ascending order for enumeration.
29-Sep-87 17:59:12  JAV  Removed advanceEntry from FindNetworkNumber
 1-Mar-88  9:46:24  AOF  Sort out code