-- File: EthernetDriver.mesa
--   Edit by: BLyon on: March 21, 1981  11:05 AM
--   Edit by: HGM on: March 14, 1981  9:10 PM
-- Last Edited by: Levin, June 15, 1983 11:01 am

DIRECTORY
  BufferDefs,
  CommFlags USING [doDebug, doStats],
  CommUtilDefs USING [Zero, GetEthernetHostNumber],
  DriverTypes USING [Encapsulation, ethernetBroadcastHost],
  DriverDefs USING [
    Glitch, GetDeviceChain, GetInputBuffer, Network,
    NetworkObject, AddDeviceToChain, PutOnGlobalDoneQueue, PutOnGlobalInputQueue],
  EthernetFace,
  GermSwap USING [switches],
  PupTypes USING [allHosts, PupErrorCode, PupHostID],
  StatsDefs USING [StatBump, StatIncr, StatCounterIndex],
  LoadState USING [SelfDestruct],
  PrincOpsUtils USING [
    AllocateNakedCondition, BITAND, DeallocateNakedCondition, GlobalFrame, HighHalf,
    LongCOPY, LowHalf],
  Process USING [
    Detach, DisableTimeout, MsecToTicks, SecondsToTicks, SetPriority, SetTimeout,
    Ticks, Yield],
  ProcessorFace USING [
    GetGreenwichMeanTime, GetClockPulses, GreenwichMeanTime,
    microsecondsPerHundredPulses],
  SpecialCommunication USING [],
  NSAddress USING [
    broadcastHostNumber, ProcessorID, HostNumber, GetProcessorID, nullHostNumber,
    nullNetworkNumber];

EthernetDriver: MONITOR
  IMPORTS
    BufferDefs, CommUtilDefs, DriverDefs, StatsDefs,
    EthernetFace, GermSwap, LoadState, PrincOpsUtils, Process,
    ProcessorFace, NSAddress
  EXPORTS BufferDefs, DriverDefs, SpecialCommunication
  SHARES BufferDefs, NSAddress =
  BEGIN OPEN StatsDefs, BufferDefs, EthernetFace, NSAddress;

  -- EXPORTed TYPEs
  Network: PUBLIC TYPE = DriverDefs.Network;

  ether: DeviceHandle;
  me: NSAddress.ProcessorID;
  myEar: NSAddress.HostNumber;
  -- what address am I listening for (verses me, my real address)
  getGarbage: BOOLEAN ← FALSE; -- when true, we deliver any packet
  globalStatePtr: GlobalStatePtr; -- Allocate space if needed
  inProcess, outProcess: PROCESS;
  inWait, outWait: LONG POINTER TO CONDITION ← NIL;
  firstOutputBuffer, lastOutputBuffer: Buffer;
  firstInputBuffer, lastInputBuffer: Buffer;
  inInterruptMask, outInterruptMask: WORD;

  watcherProcess: PROCESS;
  pleaseStop: BOOLEAN;
  timer: CONDITION;
  timeLastRecv, timeSendStarted: Pulses;
  oneSecondOfPulses: Pulses;

  inputQueueLength: CARDINAL ← 1;
  inputBuffersInQueue: CARDINAL;


  myNetwork: DriverDefs.NetworkObject ←
    [decapsulateBuffer: DecapsulateBuffer, encapsulatePup: EncapsulatePup,
      encapsulateOis: EncapsulateOis, sendBuffer: SendBuffer,
      forwardBuffer: ForwardBuffer, activateDriver: ActivateDriver,
      deactivateDriver: DeactivateDriver, deleteDriver: DeleteDriver,
      interrupt: InInterrupt,
      changeNumberOfInputBuffers: MaybeChangeNumberOfInputBuffers, alive: TRUE,
      speed: 10000, -- in kiloBits/sec
      buffers:, spare:, device: ethernet, index:, netNumber: nullNetworkNumber,
      hostNumber: 0, next: NIL, pupStats: NIL, stats: NIL];

  FunnyRetransmissionMask: PUBLIC ERROR = CODE;
  -- MachineIDTooBigForEthernet: PUBLIC ERROR = CODE;
  DriverNotActive: PUBLIC ERROR = CODE;
  DriverAlreadyActive: PUBLIC ERROR = CODE;
  -- EthernetNetNumberScrambled: PUBLIC ERROR = CODE;
  CantMakImageWhileEtherentDriverIsActive: PUBLIC ERROR = CODE;
  -- OnlyTwoDriversArePossible: PUBLIC ERROR = CODE;
  BufferMustBeAlmostQuadWordAligned: PUBLIC ERROR = CODE;
  IOCBMustBeQuadWordAligned: PUBLIC ERROR = CODE;
  IOCBMustBeInFirstMDS: PUBLIC ERROR = CODE;

  EtherStatsInfo: TYPE = RECORD [
    packetsSent: LONG CARDINAL,
    wordsSent: LONG CARDINAL,
    badSendStatus: LONG CARDINAL,
    overruns: LONG CARDINAL,
    packetsRecv: LONG CARDINAL,
    wordsRecv: LONG CARDINAL,
    badRecvStatus: LONG CARDINAL,
    inputOff: LONG CARDINAL,
    loadTable: ARRAY [0..16] OF LONG CARDINAL];
  etherStatsInfo: EtherStatsInfo;
  etherStats: POINTER TO EtherStatsInfo ← @etherStatsInfo;

  -- Hot Procedures

  Pulses: TYPE = LONG CARDINAL;
  
  MicrosecondsToPulses: PROC[m: LONG CARDINAL] RETURNS[ Pulses] =
    { RETURN[
      MIN[LAST[LONG CARDINAL]/100,m/ProcessorFace.microsecondsPerHundredPulses]*100 ] };

  InInterrupt: ENTRY PROCEDURE =
    BEGIN
    acceptBuffer: BOOLEAN;
    this, new: Buffer;
    status: Status;
    lastMissed, missed: CARDINAL ← GetPacketsMissed[ether];

    Process.SetPriority[3];

    DO
      UNTIL pleaseStop OR (this ← firstInputBuffer) # NIL DO WAIT inWait; ENDLOOP;
      IF pleaseStop THEN EXIT;
      status ← GetStatus[this.iocbChain];
      IF CommFlags.doStats AND status # pending THEN
	StatIncr[statEtherInterruptDuringInterrupt];
      UNTIL pleaseStop OR status # pending DO
	WAIT inWait;
	status ← GetStatus[this.iocbChain];
	IF CommFlags.doStats AND status = pending THEN StatIncr[statEtherMissingStatus];
	ENDLOOP;
      IF CommFlags.doStats AND (missed ← GetPacketsMissed[ether]) # lastMissed THEN
	BEGIN
	StatBump[statEtherEmptyNoBuffer, missed - lastMissed];
	lastMissed ← missed;
	END;
      IF pleaseStop THEN EXIT;
      firstInputBuffer ← firstInputBuffer.next;
      SELECT status FROM
	ok => acceptBuffer ← TRUE;
	ENDCASE =>
	  BEGIN
	  etherStats.badRecvStatus ← etherStats.badRecvStatus + 1;
	  acceptBuffer ← getGarbage; -- we may be collecting garbage packets
	  IF CommFlags.doStats THEN
	    SELECT status FROM
	      packetTooLong => StatIncr[statEtherReceivedTooLong];
	      badAlignmentButOkCrc => StatIncr[statEtherReceivedNot16];
	      crc => StatIncr[statEtherReceivedBadCRC];
	      crcAndBadAlignment => StatIncr[statEtherReceivedNot16BadCRC];
	      overrun =>
		BEGIN
		etherStats.overruns ← etherStats.overruns + 1;
		StatIncr[statEtherReceivedOverrun];
		END;
	      ENDCASE => StatIncr[statEtherReceivedBadStatus];
	  END;
      IF acceptBuffer THEN
	BEGIN
	this.time ← timeLastRecv ← ProcessorFace.GetClockPulses[];
	this.length ← GetPacketLength[this.iocbChain];
	this.network ← LONG[@myNetwork];  -- LONG because of Mokelumne compiler bug
	IF CommFlags.doStats THEN
	  BEGIN
	  etherStats.packetsRecv ← etherStats.packetsRecv + 1;
	  etherStats.wordsRecv ← etherStats.wordsRecv + this.length;
	  StatIncr[statEtherPacketsReceived];
	  StatBump[statEtherWordsReceived, this.length];
	  END;
	DriverDefs.PutOnGlobalInputQueue[this];
	IF (new ← DriverDefs.GetInputBuffer[]) = NIL THEN
	  BEGIN
	  -- Rats, couldn't get a new buffer
	  inputBuffersInQueue ← inputBuffersInQueue - 1;
	  NOTIFY timer;
	  IF CommFlags.doStats THEN
	    BEGIN
	    etherStats.inputOff ← etherStats.inputOff + 1;
	    StatIncr[statEtherEmptyFreeQueue];
	    END;
	  END; -- cant get new buffer clause

	END -- acceptBuffer clause

      ELSE
	BEGIN
	new ← this; -- Some kind of error, recycle this buffer

	END; -- reject buffer clause
      -- add new buffer to end of input chain
      IF new # NIL THEN
	BEGIN
	new.device ← ethernet;
	QueueInput[ether, @new.encapsulation, new.length, new.iocbChain];
	new.next ← NIL;
	IF firstInputBuffer = NIL THEN firstInputBuffer ← new
	ELSE lastInputBuffer.next ← new;
	lastInputBuffer ← new;
	END;
      ENDLOOP;
    END;

  OutInterrupt: ENTRY PROCEDURE =
    BEGIN
    b: Buffer;
    status: Status;

    Process.SetPriority[3];

    UNTIL pleaseStop DO
      DO
	-- forever until something interesting happens
	IF pleaseStop THEN EXIT;
	-- we compute the values each time around since the value of b can change if
	-- the watcher shoots down the output.
	IF (b ← firstOutputBuffer) # NIL AND (status ← GetStatus[b.iocbChain]) #
	  pending THEN EXIT;
	WAIT outWait;
	ENDLOOP;
      IF pleaseStop THEN EXIT; -- so that we do not do something below

      SELECT status FROM
	ok =>
	  BEGIN
	  IF CommFlags.doStats THEN
	    BEGIN
	    tries: CARDINAL ← GetRetries[b.iocbChain];
	    statEtherSendsCollision1: StatsDefs.StatCounterIndex =
	      statEtherSendsCollision1;
	    first: CARDINAL = LOOPHOLE[statEtherSendsCollision1];
	    etherStats.packetsSent ← etherStats.packetsSent + 1;
	    etherStats.wordsSent ← etherStats.wordsSent + b.length;
	    IF tries # 0 THEN StatIncr[LOOPHOLE[first + tries]];
	    etherStats.loadTable[tries] ← etherStats.loadTable[tries] + 1;
	    END;
	  END;
	ENDCASE =>
	  BEGIN
	  IF CommFlags.doStats THEN
	    SELECT status FROM
	      tooManyCollisions =>
		BEGIN
		etherStats.loadTable[16] ← etherStats.loadTable[16] + 1;
		StatIncr[statEtherSendsCollisionLoadOverflow];
		END;
	      underrun =>
		BEGIN
		etherStats.overruns ← etherStats.overruns + 1;
		StatIncr[statEtherSendOverrun];
		END;
	      ENDCASE =>
		BEGIN
		etherStats.badSendStatus ← etherStats.badSendStatus + 1;
		StatIncr[statEtherSendBadStatus];
		END;
	  END;

      -- We don't resend things that screwup
      firstOutputBuffer ← firstOutputBuffer.next;
      DriverDefs.PutOnGlobalDoneQueue[b];
      ENDLOOP;
    END;

  GetElapsedPulses: PROCEDURE [startTime: Pulses] RETURNS [Pulses] =
    INLINE
    BEGIN
    RETURN[ProcessorFace.GetClockPulses[] - startTime];
    END;

  Watcher: PROCEDURE =
    BEGIN
    fiveSecondsOfPulses: Pulses ← MicrosecondsToPulses[5000000];
    fiveHalfSecondsOfPulses: Pulses ← MicrosecondsToPulses[2500000];
    UNTIL pleaseStop DO
      -- In either case, an interrupt should be pending.  Since the interrupt routine is higher priority than we are, it should get processed before we can see it.  If we get here, an interrupt has probably been lost.  It could have been generated between the time we started decoding the instruction and the time that the data is actually fetched.  That is why we look several times.  Of course, if it is still not zero when we look again, it could be a new interrupt that has just arrived.
      -- Check for lost input interrupt
      THROUGH [0..25) DO
	IF InputChainOK[] THEN EXIT;
	REPEAT FINISHED => BEGIN WatcherNotify[]; END;
	ENDLOOP;
      -- Check for lost output interrupt
      THROUGH [0..25) DO
	IF OutputChainOK[] THEN EXIT;
	REPEAT FINISHED => BEGIN WatcherNotify[]; END;
	ENDLOOP;
      -- Check for stuck input
      IF GetElapsedPulses[timeLastRecv] > fiveSecondsOfPulses THEN FixupInput[];
      -- Check for stuck output
      IF firstOutputBuffer # NIL AND
	(GetElapsedPulses[timeSendStarted] > fiveHalfSecondsOfPulses) THEN
	ShootDownOutput[];
      IF InputBufferQueueOK[] THEN WatcherWait[];
      ENDLOOP;
    END;

  InputChainOK: ENTRY PROCEDURE RETURNS [BOOLEAN] = INLINE
    BEGIN
    RETURN[
      (firstInputBuffer = NIL) OR
	(GetStatus[firstInputBuffer.iocbChain] = pending)];
    END;

  OutputChainOK: ENTRY PROCEDURE RETURNS [BOOLEAN] = INLINE
    BEGIN
    RETURN[
      (firstOutputBuffer = NIL) OR
	(GetStatus[firstOutputBuffer.iocbChain] = pending)];
    END;

  InputBufferQueueOK: PROCEDURE RETURNS [BOOLEAN] = INLINE
    BEGIN
    b: Buffer;
    enterTime: Pulses ← ProcessorFace.GetClockPulses[];

    QueueInputBufferLocked: ENTRY PROCEDURE = INLINE
      BEGIN
      QueueInput[ether, @b.encapsulation, b.length, b.iocbChain];
      IF firstInputBuffer = NIL THEN firstInputBuffer ← b
      ELSE lastInputBuffer.next ← b;
      lastInputBuffer ← b;
      inputBuffersInQueue ← inputBuffersInQueue + 1;
      END;

    WHILE (inputBuffersInQueue < myNetwork.buffers) DO
      -- not MONITOR protected compair !!
      IF (b ← DriverDefs.GetInputBuffer[TRUE]) # NIL THEN
	BEGIN b.device ← ethernet; b.next ← NIL; QueueInputBufferLocked[]; END;
      IF GetElapsedPulses[enterTime] > oneSecondOfPulses THEN RETURN[FALSE];
      ENDLOOP;
    RETURN[TRUE];
    END;

  WatcherWait: ENTRY PROCEDURE = INLINE BEGIN WAIT timer; END;

  WatcherNotify: ENTRY PROCEDURE = INLINE
    BEGIN
    IF CommFlags.doStats THEN StatIncr[statEtherLostInterrupts];
    SmashCSBs[]; -- this will leave output dangling
    END;

  FixupInput: ENTRY PROCEDURE = INLINE
    BEGIN
    IF CommFlags.doStats THEN StatIncr[statInputIdle];
    SmashCSBs[]; -- this will leave output dangling

    END;

  ShootDownOutput: ENTRY PROCEDURE = INLINE
    BEGIN
    -- This happens if the transciever is unplugged
    b: Buffer;
    TurnOff[ether];
    UNTIL firstOutputBuffer = NIL DO
      b ← firstOutputBuffer;
      firstOutputBuffer ← firstOutputBuffer.next;
      DriverDefs.PutOnGlobalDoneQueue[b];
      IF CommFlags.doStats THEN StatIncr[statPacketsStuckInOutput];
      ENDLOOP;
    SmashCSBs[];
    END;

  DecapsulateBuffer: PROCEDURE [b: Buffer] RETURNS [BufferType] =
    BEGIN
    SELECT b.encapsulation.ethernetType FROM
      pup =>
	BEGIN
	IF 2*b.length < b.pupLength + 2*SIZE[DriverTypes.Encapsulation] THEN
	  BEGIN
	  IF CommFlags.doStats THEN StatIncr[statPupsDiscarded];
	  RETURN[rejected];
	  END;
	RETURN[pup];
	END;
      ois =>
	BEGIN
	IF 2*b.length < b.ois.pktLength + 2*SIZE[DriverTypes.Encapsulation] THEN
	  BEGIN IF CommFlags.doStats THEN StatIncr[statOisDiscarded]; RETURN[rejected]; END;
	RETURN[ois];
	END;
      translation =>
	BEGIN
	IF b.rawWords[0] = translationRequest THEN receiveRequest[b]
	ELSE IF b.rawWords[0] = translationResponse THEN receiveAck[b]
   ELSE RETURN[rejected];
	RETURN[processed];
	END;
      ENDCASE => RETURN[rejected];
    END;

  EncapsulatePup: PROCEDURE [b: PupBuffer, destination: PupHostID] =
    BEGIN
    foundIt: BOOLEAN;
    oisAddr: OisAddr;
    [foundIt, oisAddr] ← translate[destination];
    IF foundIt THEN
      BEGIN
      b.encapsulation ←
	[ethernet[ethernetDest: oisAddr, ethernetSource: me, ethernetType: pup]];
      b.length ← (b.pupLength + 1)/2 + SIZE[DriverTypes.Encapsulation];
      END
    ELSE
      BEGIN
      b.encapsulation ←
	[ethernet[
	  ethernetDest:, ethernetSource: NSAddress.nullHostNumber,
	  -- Marker for translation failed
	  ethernetType: pup]];
      END;
    END;

  EncapsulateOis: PROCEDURE [
    b: OisBuffer, destination: NSAddress.HostNumber] =
    BEGIN
    b.encapsulation ←
      [ethernet[ethernetDest: destination, ethernetSource: me, ethernetType: ois]];
    b.length ← (b.ois.pktLength + 1)/2 + SIZE[DriverTypes.Encapsulation];
    END;

  ForwardBuffer: PROCEDURE [b: Buffer] RETURNS [PupTypes.PupErrorCode] =
    BEGIN
    IF FALSE THEN -- outputQueue.length>10 THEN
      RETURN[gatewayResourceLimitsPupErrorCode]; -- transceiver unplugged?
    SendBuffer[b];
    RETURN[noErrorPupErrorCode];
    END;

  SendBuffer: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    IF pleaseStop THEN DriverDefs.Glitch[DriverNotActive];
    IF b.encapsulation.ethernetSource = NSAddress.nullHostNumber THEN
      BEGIN DriverDefs.PutOnGlobalDoneQueue[b]; RETURN; END;
    IF ~hearSelf AND
      (b.encapsulation.ethernetDest = me OR
	b.encapsulation.ethernetDest = DriverTypes.ethernetBroadcastHost) THEN
      BEGIN -- sending to ourself, copy it over since we can't hear it
      copy: Buffer ← DriverDefs.GetInputBuffer[];
      IF copy # NIL THEN
	BEGIN
	copy.device ← ethernet;
	PrincOpsUtils.LongCOPY[
	  from: @b.encapsulation, nwords: b.length, to: @copy.encapsulation];
	copy.length ← b.length;
	copy.network ← LONG[@myNetwork];  -- LONG because of Mokelumne compiler bug
	IF CommFlags.doStats THEN StatIncr[statEtherPacketsLocal];
	IF CommFlags.doStats THEN StatBump[statEtherWordsLocal, b.length];
	DriverDefs.PutOnGlobalInputQueue[copy];
	END
      ELSE IF CommFlags.doStats THEN StatIncr[statEtherEmptyFreeQueue];
      END;
    SendBufferInternal[b];
    END;

  SendBufferInternal: INTERNAL PROCEDURE [b: Buffer] =
    BEGIN
    minWordsPerEthernetPacket: CARDINAL = (64/2)-2;  --*** Should move to DriverTypes
    words: CARDINAL ← MAX[b.length,minWordsPerEthernetPacket];
    b.device ← ethernet;
    QueueOutput[ether, @b.encapsulation, words, b.iocbChain];
    IF CommFlags.doStats THEN StatIncr[statEtherPacketsSent];
    IF CommFlags.doStats THEN StatBump[statEtherWordsSent, b.length];
    IF firstOutputBuffer = NIL THEN firstOutputBuffer ← b
    ELSE lastOutputBuffer.next ← b;
    lastOutputBuffer ← b;
    timeSendStarted ← ProcessorFace.GetClockPulses[];
    END;

  -- for changing the number of buffers while running

  numberOfExtraBuffer: CARDINAL = 3;
  bufferAccessHandle: BufferDefs.BufferAccessHandle;
  -- this should only be called from Boss 
  -- No MONITOR PROTECTION here.
  MaybeChangeNumberOfInputBuffers: PROCEDURE [increaseBuffers: BOOLEAN] =
    BEGIN
    IF increaseBuffers THEN
      BEGIN
      IF bufferAccessHandle = NIL THEN
	BEGIN
	bufferAccessHandle ← BufferDefs.MakeBufferPool[numberOfExtraBuffer];
	myNetwork.buffers ← myNetwork.buffers + numberOfExtraBuffer;
	END;
      END
    ELSE
      BEGIN
      IF bufferAccessHandle # NIL THEN
	BEGIN
	myNetwork.buffers ← myNetwork.buffers - numberOfExtraBuffer;
	BufferDefs.FreeBufferPool[bufferAccessHandle];
	bufferAccessHandle ← NIL;
	END;
      END;
    END;

  -- COLD code, only used when turning things on+off

  AdjustLengtoOfD0EthernetInputQueue: PUBLIC PROCEDURE [n: CARDINAL] =
    BEGIN inputQueueLength ← n; END;

  CreateDefaultEthernetDrivers: PUBLIC PROCEDURE RETURNS [BOOLEAN] =
    BEGIN
    deviceNumber: CARDINAL ← 0;
    etherDevice: DeviceHandle ← GetNextDevice[nullDeviceHandle];
    IF GermSwap.switches[b] THEN RETURN[FALSE];
    IF etherDevice = nullDeviceHandle THEN RETURN[FALSE];
    WHILE etherDevice # nullDeviceHandle DO
      CreateAnEthernetDriver[etherDevice, deviceNumber];
      etherDevice ← GetNextDevice[etherDevice];
      deviceNumber ← deviceNumber + 1;
      ENDLOOP;
    RETURN[TRUE];
    END;

  CreateAnEthernetDriver: PROCEDURE [
    etherDevice: DeviceHandle, deviceNumber: CARDINAL] =
    BEGIN
    IF deviceNumber # 0 THEN
      BEGIN
      him: POINTER TO FRAME[EthernetDriver] ← NEW EthernetDriver;
      him.SetupEthernetDriver[etherDevice];
      END
    ELSE SetupEthernetDriver[etherDevice];
    END;

  SetupEthernetDriver: PROCEDURE [etherDevice: DeviceHandle] =
    BEGIN
    ether ← etherDevice;
    myEar ← me ← NSAddress.GetProcessorID[];
    myNetwork.netNumber ← nullNetworkNumber;
    pleaseStop ← TRUE;
    myNetwork.buffers ← inputQueueLength;
    DriverDefs.AddDeviceToChain[@myNetwork, controlBlockSize];
    IF CommFlags.doStats THEN
      BEGIN
      myNetwork.stats ← etherStats;
      CommUtilDefs.Zero[etherStats, SIZE[EtherStatsInfo]];
      END;
    END;

  ActivateDriver: PROCEDURE =
    BEGIN
    b: Buffer;
    IF ~pleaseStop THEN DriverDefs.Glitch[DriverAlreadyActive];
    oneSecondOfPulses ← MicrosecondsToPulses[1000000];
    getGarbage ← pleaseStop ← FALSE;
    TurnOff[ether];
    AddCleanup[ether];
    myEar ← me ← NSAddress.GetProcessorID[];
    firstInputBuffer ← lastInputBuffer ← NIL;
    firstOutputBuffer ← lastOutputBuffer ← NIL;
    bufferAccessHandle ← NIL;
    inputBuffersInQueue ← 0;
    THROUGH [0..myNetwork.buffers) DO
      IF (b ← DriverDefs.GetInputBuffer[TRUE])#NIL THEN
        BEGIN
        inputBuffersInQueue ← inputBuffersInQueue + 1;
        IF CommFlags.doDebug AND PrincOpsUtils.BITAND[PrincOpsUtils.LowHalf[@b.encapsulation], 3] # 3 THEN DriverDefs.Glitch[BufferMustBeAlmostQuadWordAligned];
        IF CommFlags.doDebug AND PrincOpsUtils.BITAND[PrincOpsUtils.LowHalf[b.iocbChain], 3] # 0 THEN
	DriverDefs.Glitch[IOCBMustBeQuadWordAligned];
        IF CommFlags.doDebug AND PrincOpsUtils.HighHalf[b.iocbChain] # 0 THEN
	DriverDefs.Glitch[IOCBMustBeInFirstMDS];
        b.device ← ethernet;
        IF firstInputBuffer = NIL THEN firstInputBuffer ← b;
        IF lastInputBuffer # NIL THEN lastInputBuffer.next ← b;
        lastInputBuffer ← b;
        END;
      ENDLOOP;
    [cv: inWait, mask: inInterruptMask] ← PrincOpsUtils.AllocateNakedCondition[
      ];
    Process.DisableTimeout[inWait];
    [cv: outWait, mask: outInterruptMask] ←
      PrincOpsUtils.AllocateNakedCondition[];
    Process.DisableTimeout[outWait];
    SmashCSBs[];
    inProcess ← FORK InInterrupt[];
    outProcess ← FORK OutInterrupt[];
    watcherProcess ← FORK Watcher[];
    CreateCache[];
    END;

  SetEthernetListener: PUBLIC ENTRY PROCEDURE [
    physicalOrder: CARDINAL, newHostNumber: NSAddress.HostNumber]
    RETURNS [success: BOOLEAN] =
    BEGIN
    him: POINTER TO FRAME[EthernetDriver];
    network: Network ← GetNthDeviceLikeMe[physicalOrder];
    IF network = NIL THEN RETURN[FALSE];
    him ← LOOPHOLE[PrincOpsUtils.GlobalFrame[network.interrupt]];
    him.EthernetListenForHost[newHostNumber];
    RETURN[TRUE];
    END;

  EthernetListenForHost: PROCEDURE [newHostNumber: NSAddress.HostNumber] =
    BEGIN myEar ← newHostNumber; SmashCSBs[]; END;

  SetEthernetCollectGarbageToo: PUBLIC ENTRY PROCEDURE [
    physicalOrder: CARDINAL, collectGarbage: BOOLEAN] RETURNS [success: BOOLEAN] =
    BEGIN
    him: POINTER TO FRAME[EthernetDriver];
    network: Network ← GetNthDeviceLikeMe[physicalOrder];
    IF network = NIL THEN RETURN[FALSE];
    him ← LOOPHOLE[PrincOpsUtils.GlobalFrame[network.interrupt]];
    him.SetCollectGarbageToo[collectGarbage];
    RETURN[TRUE];
    END;

  SetCollectGarbageToo: PROCEDURE [collectGarbage: BOOLEAN] =
    BEGIN getGarbage ← collectGarbage; END;

  GetNthDeviceLikeMe: PROCEDURE [physicalOrder: CARDINAL]
    RETURNS [net: Network] =
    BEGIN
    i: CARDINAL ← 0;
    net ← DriverDefs.GetDeviceChain[];
    WHILE net # NIL DO
      IF net.device = myNetwork.device THEN
	IF (i ← i + 1) = physicalOrder THEN RETURN;
      net ← net.next;
      ENDLOOP;
    END;

  SmashCSBs: PROCEDURE =
    BEGIN
    b: Buffer;
    TurnOn[
      ether, LOOPHOLE[myEar, NSAddress.ProcessorID], inInterruptMask,
      outInterruptMask, globalStatePtr];
    FOR b ← firstInputBuffer, b.next UNTIL b = NIL DO
      QueueInput[ether, @b.encapsulation, b.length, b.iocbChain]; ENDLOOP;
    timeLastRecv ← ProcessorFace.GetClockPulses[];
    END;

  DeleteDriver: PROCEDURE =
    BEGIN
    IF ether # GetNextDevice[nullDeviceHandle] THEN LoadState.SelfDestruct[];
    END;

  DeactivateDriver: PROCEDURE =
    BEGIN
    b: Buffer;
    IF pleaseStop THEN DriverDefs.Glitch[DriverNotActive];
    pleaseStop ← TRUE;
    KillInterruptRoutines[];
    JOIN inProcess;
    JOIN outProcess;
    TurnOff[ether];
    PrincOpsUtils.DeallocateNakedCondition[inWait];
    PrincOpsUtils.DeallocateNakedCondition[outWait];
    inWait ← outWait ← NIL;
    MaybeChangeNumberOfInputBuffers[FALSE];
    KillDriverLocked[];
    JOIN watcherProcess;
    RemoveCleanup[ether];
    UNTIL firstInputBuffer = NIL DO
      b ← firstInputBuffer;
      firstInputBuffer ← b.next;
      ReturnFreeBuffer[b];
      ENDLOOP;
    UNTIL firstOutputBuffer = NIL DO
      b ← firstOutputBuffer;
      firstOutputBuffer ← b.next;
      ReturnFreeBuffer[b];
      ENDLOOP;
    myNetwork.netNumber ← nullNetworkNumber;
    -- in case we turn it on after moving to another machine
    DeleteCache[];
    END;

  KillInterruptRoutines: ENTRY PROCEDURE = INLINE
    BEGIN NOTIFY inWait↑; NOTIFY outWait↑; END;

  KillDriverLocked: ENTRY PROCEDURE = INLINE BEGIN NOTIFY timer; END;

  OisAddr: TYPE = NSAddress.HostNumber;
  Ethernet1Addr: TYPE = PupTypes.PupHostID;
  AddressPair: TYPE = MACHINE DEPENDENT RECORD [
    oisAddr: OisAddr, ethernet1Addr: Ethernet1Addr, filler: [0..377B]];

  CacheEntry: TYPE = REF CacheObject;

  CacheObject: TYPE = MACHINE DEPENDENT RECORD [
    nextLink: CacheEntry,
    addressPair: AddressPair,
    tries: CARDINAL,
    timeStamp: ProcessorFace.GreenwichMeanTime,
    status: CacheStatus,
    filler: [0..37777B]];

  CacheStatus: TYPE = {new, pending, active, zombie};

  -- variables
  translationRequest: CARDINAL = 10101B;
  translationResponse: CARDINAL = 7070B;
  cacheQueueHead: CacheEntry;
  broadCastPairEntry: CacheEntry; -- permanent
  myAddressPairEntry: CacheEntry; -- permanent
  retryLimit: CARDINAL = 10B;
  retryTime: LONG CARDINAL = 2; -- two seconds
  demonActiveTime: Process.Ticks ← Process.SecondsToTicks[1]; -- one second
  deactivateTime: LONG CARDINAL = 3*60; -- three minutes
  demonSleepTime: Process.Ticks ← Process.SecondsToTicks[60*5]; -- five minutes
  cacheEvent: CONDITION;
  demonRunning: BOOLEAN;
  lastTranslationTime: ProcessorFace.GreenwichMeanTime;
  translate: PROCEDURE [Ethernet1Addr] RETURNS [BOOLEAN, OisAddr] ←
    InactiveTranslate;
  receiveRequest: PROCEDURE [Buffer] ← InactiveReceiveAckOrRequest;
  receiveAck: PROCEDURE [Buffer] ← InactiveReceiveAckOrRequest;


  -- interface
  CreateCache: ENTRY PROCEDURE = INLINE
    BEGIN
    cacheQueueHead ← broadCastPairEntry ← myAddressPairEntry ← NIL;
    translate ← InactiveTranslate;
    receiveRequest ← InactiveReceiveAckOrRequest;
    receiveAck ← InactiveReceiveAckOrRequest;
    demonRunning ← FALSE;
    END;

  StartCache: ENTRY PROCEDURE [myEthernetOneAddr: CARDINAL] = INLINE
    BEGIN
    aP: AddressPair ← [NSAddress.broadcastHostNumber, PupTypes.allHosts, 0];
    translate ← Translate;
    receiveRequest ← ReceiveRequest;
    receiveAck ← ReceiveAck;
    Process.SetTimeout[@cacheEvent, demonActiveTime];
    broadCastPairEntry ← AddAddressPair[aP];
    aP ← [me, [myNetwork.hostNumber ← myEthernetOneAddr], 0];
    myAddressPairEntry ← AddAddressPair[aP];
    demonRunning ← TRUE;
    Process.Detach[FORK Demon[]];
    END;

  DeleteCache: PROCEDURE = INLINE
    BEGIN
    e: CacheEntry;

    DeleteCacheLocked: ENTRY PROCEDURE = INLINE BEGIN NOTIFY cacheEvent; END;
    -- DeleteCacheLocked

    WHILE demonRunning DO DeleteCacheLocked[]; Process.Yield[]; ENDLOOP;
    -- cleanup in case demon was never running
    WHILE (cacheQueueHead # NIL) DO
      e ← cacheQueueHead;
      cacheQueueHead ← e.nextLink;
      -- Heap.FreeNode[p: e]; before conversion to REFs (ADB). --
      ENDLOOP;
    END;

  depth: CARDINAL;
  FindEntry: INTERNAL PROCEDURE [ethernet1Addr: Ethernet1Addr]
    RETURNS [entry: CacheEntry] =
    BEGIN
    IF CommFlags.doStats THEN depth ← 0;
    entry ← cacheQueueHead;
    WHILE entry # NIL DO
      IF ethernet1Addr = entry.addressPair.ethernet1Addr THEN RETURN;
      entry ← entry.nextLink;
      IF CommFlags.doStats THEN depth ← depth + 1;
      ENDLOOP;
    END;

  AddEntry: INTERNAL PROCEDURE [entry: CacheEntry] =
    BEGIN entry.nextLink ← cacheQueueHead; cacheQueueHead ← entry; END;

  RemoveEntry: INTERNAL PROCEDURE [entry: CacheEntry] =
    BEGIN
    e, pred: CacheEntry;
    IF (pred ← cacheQueueHead) = entry THEN
      BEGIN cacheQueueHead ← cacheQueueHead.nextLink; RETURN; END;
    e ← pred.nextLink;
    WHILE e # NIL DO
      IF e = entry THEN BEGIN pred.nextLink ← entry.nextLink; RETURN; END;
      pred ← e;
      e ← pred.nextLink;
      ENDLOOP;
    ERROR; -- entry not found

    END;


  InactiveTranslate: PROCEDURE [ethernet1Addr: Ethernet1Addr]
    RETURNS [foundIt: BOOLEAN, oisAddr: OisAddr] =
    BEGIN
    ethernetOneAddr: CARDINAL ← CommUtilDefs.GetEthernetHostNumber[];
    StartCache[ethernetOneAddr];
    [foundIt, oisAddr] ← Translate[ethernet1Addr];
    END;

  Translate: ENTRY PROCEDURE [ethernet1Addr: Ethernet1Addr]
    RETURNS [foundIt: BOOLEAN, oisAddr: OisAddr] =
    BEGIN
    e: CacheEntry;
    foundIt ← FALSE;
    lastTranslationTime ← ProcessorFace.GetGreenwichMeanTime[];
    IF (e ← FindEntry[ethernet1Addr]) # NIL THEN
      BEGIN
      IF e # cacheQueueHead THEN -- put e at the head of the queue
        BEGIN
        IF CommFlags.doStats THEN StatBump[cacheDepth, depth];
        RemoveEntry[e];
        AddEntry[e];
        END;
      SELECT e.status FROM
        active => BEGIN
          foundIt ← TRUE;
          oisAddr ← e.addressPair.oisAddr;
          e.timeStamp ← lastTranslationTime;
          END;
        zombie => BEGIN
          e.status ← new;
          e.tries ← 0;
          e.timeStamp ← lastTranslationTime;
          NOTIFY cacheEvent;
          END;
        ENDCASE => NULL;
      END -- of found it
    ELSE -- entry not found, so add a new one
      BEGIN
      IF CommFlags.doStats THEN StatIncr[cacheFault];
      e ← NEW[CacheObject];
      e.status ← new;
      e.tries ← 0;
      e.timeStamp ← lastTranslationTime;
      e.addressPair ← [oisAddr:, ethernet1Addr: ethernet1Addr, filler:];
      AddEntry[e];
      NOTIFY cacheEvent;
      END;
    END;

  AddAddressPair: INTERNAL PROCEDURE [aP: AddressPair] RETURNS [e: CacheEntry] =
    BEGIN
    IF (e ← FindEntry[aP.ethernet1Addr]) = NIL THEN
      BEGIN e ← NEW[CacheObject]; AddEntry[e]; END;
    e.addressPair ← aP;
    e.status ← active;
    e.timeStamp ← ProcessorFace.GetGreenwichMeanTime[];
    END;

  DeallocateEntry: INTERNAL PROCEDURE [e: CacheEntry] =
    BEGIN
    -- there are two entries that we do not want to throw out!!
    IF (e = broadCastPairEntry) OR (e = myAddressPairEntry) THEN
      e.timeStamp ← ProcessorFace.GetGreenwichMeanTime[]
    ELSE BEGIN RemoveEntry[e]; --Heap.FreeNode[p: e];-- END;
    END;

  Demon: ENTRY PROCEDURE =
    BEGIN
    translationInactiveTime: LONG CARDINAL = 10*60;
    -- demon will die if no services are needed in ten minutes
    now: ProcessorFace.GreenwichMeanTime;
    t: LONG CARDINAL;
    e, nextE: CacheEntry;
    pendingEntries: BOOLEAN;
    demonRunning ← TRUE;
    lastTranslationTime ← ProcessorFace.GetGreenwichMeanTime[];
    Process.SetPriority[3];

    UNTIL pleaseStop DO
      WAIT cacheEvent;
      IF (now ← ProcessorFace.GetGreenwichMeanTime[]) - lastTranslationTime > 	translationInactiveTime OR pleaseStop THEN EXIT;
      pendingEntries ← FALSE;
      e ← cacheQueueHead;
      WHILE (e # NIL) DO
	nextE ← e.nextLink;
	t ← now - e.timeStamp;
	SELECT e.status FROM
	  active, zombie =>
	    BEGIN IF t > deactivateTime THEN DeallocateEntry[e]; END;
	  pending =>
	    BEGIN
	    pendingEntries ← TRUE;
	    IF t > retryTime THEN
	      BEGIN
	      e.tries ← e.tries + 1;
	      IF e.tries > retryLimit THEN
		BEGIN
		e.status ← zombie;
		IF CommFlags.doStats THEN StatIncr[unsuccessfulTranslation];
		END
	      ELSE
		BEGIN
		IF CommFlags.doStats THEN StatIncr[translationRetries];
		SendRequest[e];
		e.timeStamp ← ProcessorFace.GetGreenwichMeanTime[];
		END;
	      END;
	    END;
	  new =>
	    BEGIN
	    pendingEntries ← TRUE;
	    SendRequest[e];
	    e.status ← pending;
	    e.timeStamp ← ProcessorFace.GetGreenwichMeanTime[];
	    END;
	  ENDCASE => ERROR;
	e ← nextE;
	ENDLOOP; -- end of queue entries loop
      IF pendingEntries THEN Process.SetTimeout[@cacheEvent, demonActiveTime]
      ELSE Process.SetTimeout[@cacheEvent, demonSleepTime];
      ENDLOOP; -- end of infinite loop
    receiveAck ← InactiveReceiveAckOrRequest;
    receiveRequest ← InactiveReceiveAckOrRequest;
    translate ← InactiveTranslate;
    e ← cacheQueueHead;
    cacheQueueHead ← myAddressPairEntry ← broadCastPairEntry ← NIL;
    WHILE e # NIL DO nextE ← e.nextLink; --Heap.FreeNode[p: e];-- e ← nextE; ENDLOOP;
    demonRunning ← FALSE;
    END;

  SendRequest: INTERNAL PROCEDURE [e: CacheEntry] =
    BEGIN
    b: Buffer;
    request: LONG POINTER TO AddressPair;


    IF (b ← DriverDefs.GetInputBuffer[TRUE]) # NIL THEN
      BEGIN
      -- broadcast the translation request
      b.encapsulation ←
	[ethernet[
	  ethernetDest: DriverTypes.ethernetBroadcastHost, ethernetSource: me,
	  ethernetType: translation]];
      b.length ← SIZE[DriverTypes.Encapsulation] + 2*SIZE[AddressPair] + 1;
      b.rawWords[0] ← translationRequest;
      request ← LOOPHOLE[@b.rawWords[1]];
      request↑ ← e.addressPair;
      -- also send our addresses, so responder does not fault
      request ← request + SIZE[AddressPair];
      request↑ ← myAddressPairEntry.addressPair;
      -- send it
      SendBufferInternal[b];
      END;
    END;

  -- locks
  -- we now own buffer b
  -- we donot allow back door requests if we are not actively translating
  InactiveReceiveAckOrRequest: PROCEDURE [b: Buffer] =
    BEGIN
    b.requeueProcedure[b];
    END;

  -- we now own buffer b
  ReceiveAck: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    IF b.encapsulation.ethernetDest = myAddressPairEntry.addressPair.oisAddr THEN
      BEGIN
      receipt: LONG POINTER TO AddressPair ← LOOPHOLE[@b.rawWords[1]];
      [] ← AddAddressPair[receipt↑];
      END;
    b.requeueProcedure[b];
    END;

  -- locks
  -- we now own buffer b
  ReceiveRequest: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    request, requesterAddr: LONG POINTER TO AddressPair;
    request ← LOOPHOLE[@b.rawWords[1]];
    IF (myAddressPairEntry # NIL) AND
      (request.ethernet1Addr = myAddressPairEntry.addressPair.ethernet1Addr) THEN
      BEGIN
      IF CommFlags.doStats THEN StatIncr[requestsForMe];
      -- since the requester is probably going to talk to us, add his address before we take a fault
      requesterAddr ← request + SIZE[AddressPair];
      [] ← AddAddressPair[requesterAddr↑];
      request.oisAddr ← myAddressPairEntry.addressPair.oisAddr;
      SendAck[request↑, b.encapsulation.ethernetSource, b]; -- we lose ownership of b
      END
    ELSE b.requeueProcedure[b];
    END;

  SendAck: INTERNAL PROCEDURE [
    aP: AddressPair, to: NSAddress.HostNumber, b: Buffer] = INLINE
    BEGIN
    response: LONG POINTER TO AddressPair;
    IF b # NIL THEN
      BEGIN
      b.encapsulation ←
	[ethernet[ethernetDest: to, ethernetSource: me, ethernetType: translation]];
      b.length ← SIZE[DriverTypes.Encapsulation] + SIZE[AddressPair] + 1;
      b.rawWords[0] ← translationResponse;
      response ← LOOPHOLE[@b.rawWords[1]];
      response↑ ← aP;
      -- send it
      SendBufferInternal[b];
      END;
    END;

  -- initialization

  Process.SetTimeout[@timer, Process.MsecToTicks[1000]];
  END.  -- EthernetDriver

September 5, 1980  1:36 AM By HGM; create from EthernetOneDriver. 
September 17, 1980  4:41 PM By BLyon; added myNetwork.buffers stuff. 
October 20, 1980  4:04 PM By BLyon; added SetYourHostNumber & myEar for Ois peeking. 
October 22, 1980  9:47 AM By BLyon; let the inputter collect garbage packets. 
November 6, 1980  6:18 PM By BLyon; records input time in buffer.time field. 
February 13, 1981  3:38 PM By BLyon; zombie translation entries are changed to new if needed AND Demon is immmediately started and  never dies. 
February 24, 1981  3:28 PM By BLyon; undid February 13 - demon is created when needed and goes away when not needed AND changed WatcherNotify to SmashCSBs and to NOTIFY inWait↑ and outWait↑.