-- File: PupRouterIn.mesa,  Last Edit: HGM  October 15, 1979  10:08 PM
-- Last Edit: HGM  October 15, 1979  10:08 PM
-- Last Edit: Taft  April 21, 1983  3:46 PM

-- Copyright  Xerox Corporation 1979, 1980

DIRECTORY
  StatsDefs: FROM "StatsDefs" USING [StatIncr],
  CommUtilDefs: FROM "CommUtilDefs" USING [GetTicks],
  PupRouterDefs: FROM "PupRouterDefs" USING [
    routerLock, routingTableUpdateTimeout, probeResponse, InThings,
    PupGateInfo, PupRouterSocket, PupRoutingTableEntry, maxHop, emptyCacheEntry,
    ForwardThisPupBuffer, TestPupChecksum, RejectPupWithBadChecksum, Reject,
    IfMissing, RoutingCacheEntry, InsertRoutingCacheEntry, DeleteRoutingCacheEntry,
    probesLeftToDo, pleaseProbe],
  DriverDefs: FROM "DriverDefs" USING [doShow, doStats, doStorms, Network, Glitch],
  PupDefs: FROM "PupDefs" USING [
    EnqueuePup, ReturnFreePupBuffer, PupBuffer,
    incomingPup, zappedIncomingPup],
  BufferDefs: FROM "BufferDefs" USING [BuffersLeft],
  PupTypes: FROM "PupTypes" USING [
    allHosts, gatewaySoc,
    PupAddress, PupHostID, PupNetID,
    noProcessPupErrorCode,  resourceLimitsPupErrorCode],
  DriverTypes: FROM "DriverTypes";

PupRouterIn: MONITOR LOCKS PupRouterDefs.routerLock
  IMPORTS StatsDefs, CommUtilDefs, PupRouterDefs, DriverDefs, PupDefs, BufferDefs
  EXPORTS PupRouterDefs
  SHARES BufferDefs, DriverTypes =
BEGIN OPEN StatsDefs, PupRouterDefs, DriverDefs, PupDefs, PupTypes;

-- SemiPublic things for PupRouterCold and friends
pupRouterIsActive: PUBLIC BOOLEAN ← FALSE;
firstSocket: PUBLIC PupRouterSocket ← NIL;
routingCacheHead, routingCacheTail: PUBLIC POINTER TO RoutingCacheEntry ← NIL;

inThings: PUBLIC InThings ← [
  inStormy: FALSE,
  watcherIsWatching: FALSE,
  watcherSeesBroadcast: FALSE,
  watcherCallsThis: ,
  badChecksumProc: PupRouterDefs.RejectPupWithBadChecksum,
  showIn: FALSE,
  inShower:  ];

-- parameters for killing packets
lightning: INTEGER ← 30;
bolt: INTEGER ← 10;

PupRouterNotActive: PUBLIC ERROR = CODE;

BeSurePupIsOn: PUBLIC PROCEDURE =
  BEGIN
  IF ~pupRouterIsActive THEN DriverDefs.Glitch[PupRouterNotActive];
  END;

-- Only called by dispatcher when a Pup arrives.
PupInputer: PUBLIC ENTRY PROCEDURE [b: PupBuffer] =
  BEGIN
  so: PupRouterSocket;
  d: PupAddress ← b.dest;
  targetNet: PupNetID ← d.net;
  network: Network;
  routing: POINTER TO RoutingCacheEntry;
  IF doStats THEN StatIncr[statPupReceived];

  IF ~TestPupChecksum[b] THEN
    BEGIN
    IF doStats THEN StatIncr[statReceivedBadPupChecksum];
    inThings.badChecksumProc[b];
    RETURN;
    END;

  IF doStorms AND inThings.inStormy  -- for debugging only
  AND ((lightning←lightning+1)>bolt OR lightning<0) THEN
    BEGIN
    IF lightning>bolt THEN
      BEGIN
      IF bolt>100 THEN
        BEGIN
        lightning←-INTEGER[CommUtilDefs.GetTicks[] MOD 20B];
        bolt←10;
        END
      ELSE BEGIN lightning←0; bolt←bolt+1; END;
      END;
    IF doShow AND inThings.showIn THEN inThings.inShower[zappedIncomingPup,b];
    ReturnFreePupBuffer[b];
    IF doStats THEN StatIncr[statZappedP];
    RETURN
    END;
  IF doShow AND inThings.showIn THEN inThings.inShower[incomingPup,b];

  network ← b.network;
  routing ← GetRoutingCacheEntry[net: targetNet, ifMissing: return];
  IF targetNet#0 AND network.netNumber#0 THEN
    BEGIN
    IF routing=NIL
    OR routing.entry.network=NIL
    OR routing.entry.hop#0
    OR (d.host=allHosts AND routing.entry.network#network) THEN
      BEGIN
      ForwardThisPupBuffer[b];
      RETURN;
      END;
IF FALSE THEN  -- It is more complicated than that.....
    b.pupTransportControl ← b.pupTransportControl+20B;  -- Hack for Gateway init
    network ← routing.entry.network;  -- fixup backdoor problems
    END;

  IF (d.host=network.hostNumber OR d.host=allHosts) THEN
    BEGIN  -- packet for us - incomming or local
    FOR so←firstSocket,so.next UNTIL so=NIL DO
      IF so.local.socket=d.socket THEN
        BEGIN
        IF network.netNumber=0 AND targetNet#0 THEN
          BEGIN  -- packet for us, believe network number
          network.netNumber ← targetNet;
          routing ← InsertRoutingCacheEntry[targetNet];
          routing.entry ← [hop: 0, time: 0, route: [0], network: network];
          END;
        IF so.input.length>1 AND BufferDefs.BuffersLeft[]<2 THEN
          BEGIN
          IF doStats THEN StatIncr[statPupInputQueueOverflow];
          Reject[b,resourceLimitsPupErrorCode];
          EXIT;
          END;
        EnqueuePup[@so.input,b];
        NOTIFY so.ready;
        EXIT;
        END;
    REPEAT FINISHED =>
      BEGIN  -- not in socket table
      IF b.pupType=gatewayInfo AND d.socket=gatewaySoc THEN [] ← GatewaySee[b]
      ELSE
        BEGIN  -- non gateway packet for unknown socket
        IF doStats THEN
          IF d.host#allHosts
          THEN StatIncr[statJunkPupsForUsNoLocalSocket]
          ELSE StatIncr[statJunkBroadcastPups];
        IF ~inThings.watcherIsWatching THEN GOTO RejectThisPup;
        IF (d.host#allHosts OR inThings.watcherSeesBroadcast)
        AND inThings.watcherCallsThis[b] THEN
          GOTO RejectThisPup;
        END;
      ReturnFreePupBuffer[b];
      EXITS
        RejectThisPup => 
          BEGIN
          -- Hack special case check to avoid touching another module
          IF b.dest.host=allHosts THEN ReturnFreePupBuffer[b]
          ELSE
            Reject[b,noProcessPupErrorCode];
          END;
      END;
    ENDLOOP;
    END
  ELSE
    ForwardThisPupBuffer[b];
  END;

Timeout: PUBLIC ENTRY PROCEDURE =
  BEGIN
  rte: POINTER TO RoutingCacheEntry;
  WHILE pupRouterIsActive DO
    FOR rte ← routingCacheHead, rte.next WHILE rte#NIL DO
      IF rte.net=emptyCacheEntry THEN LOOP;  -- empty cache slot
      IF rte.entry.hop=0 THEN LOOP;  -- directly connected
      -- There is a bug here: deleting an entry puts it at the tail of the queue,
      -- thereby disrupting the enumeration.  The effect of this is to delay the timeout
      -- of later entries.  Big deal.  (The BCPL version has this bug too!)
      IF (rte.entry.time←rte.entry.time+30)>180 THEN DeleteRoutingCacheEntry[[rte.net]];
      ENDLOOP;
    WAIT routingTableUpdateTimeout;  -- 30 seconds
    ENDLOOP;
  END;

PupGatewaySee: PUBLIC ENTRY PROCEDURE [b: PupBuffer] RETURNS [BOOLEAN] =
  BEGIN
  RETURN[GatewaySee[b]];
  END;

GatewaySee: INTERNAL PROCEDURE [b: PupBuffer] RETURNS [new: BOOLEAN] =
  BEGIN
  newRoute: PupHostID = b.source.host;
  network: Network = b.network;
  length: CARDINAL = b.pupLength-22;
  new ← FALSE;  -- no changes yet

  IF b.pupType#gatewayInfo
  OR b.source.net=0
  OR newRoute=0
  OR (length MOD (2*SIZE[PupGateInfo]))#0 THEN
    BEGIN
    IF doStats THEN StatIncr[statMouseTrap];
    RETURN;
    END;
  IF newRoute=network.hostNumber THEN RETURN; -- from self
  IF doStats THEN StatIncr[statPupGatewayPacketsRecv];
  IF network.netNumber=0 THEN
    BEGIN  -- we don't know our network number on this device yet
    network.netNumber ← b.source.net;
    InsertRoutingCacheEntry[[network.netNumber]].entry ←
      [hop: 0, time: 0, route: [0], network: network];
    END;
-- What should we do if the network number from this Pup doesn't match the one we know in network.netNumber?

-- This is where we actually update the routing table.  For all the details, see Taft's memo stored on: [MAXC]<Pup>GatewayInformation.bravo
  BEGIN
  newHop, newTime, net: CARDINAL;
  data: POINTER TO PupGateInfo ← LOOPHOLE[@b.pupWords[0]];
  rt: POINTER TO RoutingCacheEntry;
  THROUGH [0..length/(2*SIZE[PupGateInfo])) DO
    net ← data.net;
    newHop ← data.hop+1;
    data ← data+SIZE[PupGateInfo];
    rt ← GetRoutingCacheEntry[net: [net], ifMissing: return, promote: FALSE];
    IF rt=NIL THEN
      BEGIN
      -- Insert new RT entry only if an empty cache entry is available and the
      -- target net is accessible.
      IF routingCacheTail.net#emptyCacheEntry OR newHop>maxHop THEN LOOP;
      rt ← InsertRoutingCacheEntry[[net]];
      END
    ELSE IF rt.entry.hop=0 THEN LOOP;  -- directly connected
    -- This is a bit tricky.  We want to keep entries with hop>maxHop until they timeout so that Gateways will do the right things about propagating changes, but we don't want to learn new paths to nowhere.
    IF ((rt.entry.network=NIL OR rt.entry.hop>maxHop) AND newHop>maxHop) THEN LOOP;
    IF rt.entry.network=NIL
    OR (rt.entry.route=newRoute AND rt.entry.network=network)
    OR rt.entry.time>=90
    OR newHop<rt.entry.hop
    -- hack to give Larry's PacketRadio preference over SLA lines
    -- OR (newHop=rt.entry.hop AND network.device=packetradio)
    THEN
      BEGIN
      IF newHop>maxHop THEN
        BEGIN
        newHop ← maxHop+1;  -- dangling entry, don't rejuvenate timer
        newTime ← rt.entry.time;
        END
      ELSE newTime ← 0;
      IF rt.entry.hop#newHop THEN new ← TRUE;
      -- rejuvenate timer if nothing else
      rt.entry ← [ hop: newHop, time: newTime, route: newRoute, network: network ];
      END;
    ENDLOOP;
  probesLeftToDo ← 0;
  NOTIFY probeResponse;
  END;
  END;

GetRoutingCacheEntry: PUBLIC PROCEDURE [
  net: PupNetID, ifMissing: IfMissing ← probeAndWait, promote: BOOLEAN ← TRUE]
  RETURNS [POINTER TO RoutingCacheEntry] = GetRoutingCacheEntryInternal;
  -- This is how we make a PUBLIC INTERNAL procedure without getting a compiler warning!

GetRoutingCacheEntryInternal: INTERNAL PROCEDURE [
  net: PupNetID, ifMissing: IfMissing ← probeAndWait, promote: BOOLEAN ← TRUE]
  RETURNS [POINTER TO RoutingCacheEntry] =
  BEGIN
  this: POINTER TO RoutingCacheEntry ← routingCacheHead;
  -- See whether head item is the one we want; if so, return it quickly.
  IF this.net#net THEN
    BEGIN
    -- Search queue for matching one.
    prev: POINTER TO RoutingCacheEntry ← this;
    FOR this ← prev.next, this.next UNTIL this=NIL DO
      IF this.net=net THEN
        BEGIN
        IF promote THEN
          BEGIN
          prev.next ← this.next;
          IF this.next=NIL THEN routingCacheTail ← prev;
          this.next ← routingCacheHead;
          routingCacheHead ← this;
          END;
        EXIT;
        END;
      prev ← this;
      ENDLOOP;
    END;
  -- this = matching entry; NIL means not in cache
  IF (this#NIL AND this.entry.hop<=maxHop) OR ifMissing=return THEN RETURN [this];
  IF this=NIL THEN
    this ← InsertRoutingCacheEntry[net]; -- insert empty entry
  probesLeftToDo ← 10;
  NOTIFY pleaseProbe;
  IF ifMissing=probeAndReturn THEN RETURN [NIL];
  WHILE probesLeftToDo#0 DO
    WAIT probeResponse;
    this ← GetRoutingCacheEntryInternal[net: net, ifMissing: return, promote: FALSE];
    IF this#NIL AND this.entry.hop<=maxHop THEN EXIT;
    ENDLOOP;
  RETURN [this];
  END;


-- initialization
END.  -- PupRouterIn