-- File: AltoEthernetDriver.mesa,  Last Edit: HGM  March 27, 1981  12:17 AM

DIRECTORY
  BcplOps USING [CleanupReason],
  ImageDefs USING [
    CleanupItem, AddCleanupProcedure, RemoveCleanupProcedure, AllReasons],
  Inline USING [BITSHIFT, BITAND, HighHalf, LowHalf, LowByte],
  MiscDefs USING [Zero],
  Process USING [
    Detach, SetPriority, DisableTimeout, SetTimeout, MsecToTicks, SecondsToTicks],
  Runtime USING [SelfDestruct],
  Storage USING [Free, Node],
  CommFlags USING [doDebug, doStats],
  CommUtilDefs USING [
    CopyLong, GetEthernetHostNumber, InterruptLevel, AddInterruptHandler,
    RemoveInterruptHandler],
  StatsDefs USING [StatBump, StatIncr, StatCounterIndex],
  AltoRam USING [Shorten, GetTicks, msPerTick],
  AltoEthernetDefs,
  DriverDefs USING [
    GetGiantVector, GiantVector, Glitch, GetInputBuffer,
    Network, NetworkObject, AddDeviceToChain, PutOnGlobalDoneQueue,
    PutOnGlobalInputQueue],
  BufferDefs,
  OISCP USING [allHostIDs],
  PupTypes USING [allHosts, PupErrorCode, PupHostID],
  DriverTypes USING [
    Byte, ethernetEncapsulationOffset, ethernetEncapsulationBytes],
  SpecialSystem USING [GetProcessorID, HostNumber];

AltoEthernetDriver: MONITOR
  IMPORTS
    ImageDefs, Inline, MiscDefs, Process, Runtime, Storage, SpecialSystem,
    AltoRam, CommUtilDefs, StatsDefs, DriverDefs, BufferDefs, AltoEthernetDefs
  EXPORTS BufferDefs, DriverDefs
  SHARES BufferDefs, DriverTypes, SpecialSystem =
  BEGIN OPEN StatsDefs, BufferDefs, DriverDefs, AltoEthernetDefs;

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

  ethernetEncapsulationOffset: CARDINAL = DriverTypes.ethernetEncapsulationOffset;
  ethernetEncapsulationBytes: CARDINAL = DriverTypes.ethernetEncapsulationBytes;

  myDevice: EthernetDeviceBlockHandle ← NIL;
  cleanupItem: ImageDefs.CleanupItem ← [, ImageDefs.AllReasons, Broom];
  hardProcess: PROCESS;
  hardware: CONDITION;
  watcherProcess: PROCESS;
  pleaseStop: BOOLEAN;
  timer: CONDITION;
  nextBufferPointer: POINTER;
  currentInputBuffer, nextInputBuffer: Buffer;
  outputQueue: QueueObject;
  currentOutputBuffer: Buffer;
  timeSendStarted: CARDINAL;
  timeLastRecv: CARDINAL;

  myNetwork: DriverDefs.NetworkObject ←
    [decapsulateBuffer: DecapsulateBuffer, encapsulatePup: EncapsulatePup,
      encapsulateOis: EncapsulateOis, sendBuffer: SendBuffer,
      forwardBuffer: ForwardBuffer, activateDriver: ActivateDriver,
      deactivateDriver: DeactivateDriver, deleteDriver: DeleteDriver,
      interrupt: Interrupt, index:, device: ethernetOne, alive: TRUE, speed: 3000,
      buffers:, spare:, netNumber:, hostNumber:, next: NIL, pupStats: NIL,
      stats: NIL];

  ImpossibleEndcase: PUBLIC ERROR = CODE;
  FunnyRetransmissionMask: PUBLIC ERROR = CODE;
  ZeroLengthBuffer: PUBLIC ERROR = CODE;
  UnreasonableHardwareStatus: PUBLIC ERROR = CODE;
  QueueScrambled: PUBLIC ERROR = CODE;
  MachineIDTooBigForEthernet: PUBLIC ERROR = CODE;
  DriverNotActive: PUBLIC ERROR = CODE;
  DriverAlreadyActive: PUBLIC ERROR = CODE;
  NoEthernetBoard: PUBLIC ERROR = CODE;
  CantSwitchMachinesWhileEtherentDriverIsActive: PUBLIC ERROR = CODE;
  CantMakImageWhileEtherentDriverIsActive: PUBLIC ERROR = CODE;
  OnlyThreeDriversArePossible: PUBLIC ERROR = CODE;
  HyperspaceNotSupported: PUBLIC ERROR = CODE;
  BufferNotAlignedProperly: PUBLIC ERROR = CODE;

  -- things needed for chained input
  first, last: EthernetDeviceBlockHandle;
  headBuffer, tailBuffer: Buffer;
  notChained: BOOLEAN;
  numberOfInputBuffers: CARDINAL = 4;

  interruptLevel: CommUtilDefs.InterruptLevel;
  interruptBit: WORD; -- BITSHIFT[1,interruptLevel];
  inputCommand: SioParameter;
  outputCommand: SioParameter;
  resetCommand: SioParameter;

  etherStats: POINTER TO EtherStatsInfo;

  Interrupt: ENTRY PROCEDURE =
    BEGIN
    b, temporaryBuffer: Buffer;
    savedWordsLeft: CARDINAL;
    savedPostData: EthernetPost;
    device: EthernetDeviceBlockHandle = myDevice;
    -- things needed for chained input
    doMoreInput: BOOLEAN;

    Process.SetPriority[4];

    UNTIL pleaseStop DO

	IF device.postData # ethernetNotPosted OR
	(~notChained AND first.postData # ethernetNotPosted) THEN
	BEGIN
	IF CommFlags.doStats THEN StatIncr[statEtherInterruptDuringInterrupt];
	END
      ELSE
	BEGIN
	DO
	  WAIT hardware;
	  IF device.postData # ethernetNotPosted OR
	    (~notChained AND first.postData # ethernetNotPosted) THEN EXIT;
	  IF CommFlags.doStats THEN StatIncr[statEtherMissingStatus];
	  ENDLOOP;
	END;

	SELECT TRUE FROM
	(~notChained AND first.postData # ethernetNotPosted) =>
	  BEGIN
	  savedPostData ← first.postData;
	  savedWordsLeft ← first.wordsLeft;
	  first ← first.inputControlBlock;
	  currentInputBuffer ← headBuffer;
	  headBuffer ← headBuffer.next;
	  doMoreInput ← TRUE;
	  END;
	device.postData # ethernetNotPosted =>
	  BEGIN
	  savedPostData ← device.postData;
	  savedWordsLeft ← device.wordsLeft;
	  device.postData ← ethernetNotPosted;
	  doMoreInput ← notChained;
	  END;
	ENDCASE => Glitch[ImpossibleEndcase];

      IF notChained THEN
	BEGIN
	-- Turn on input as soon as we can so we don't drop as many packets.
	device.inputBuffer.count ←
	  nextInputBuffer.length - ethernetEncapsulationOffset;
	device.inputBuffer.pointer ← nextBufferPointer;
	StartIO[inputCommand]; -- input now running, can relax now
	END;

      SELECT savedPostData.microcodeStatus FROM

	inputDone =>
	  IF savedPostData.hardwareStatus = hardwareAOK THEN
	    BEGIN
	    IF (temporaryBuffer ← GetInputBuffer[]) # NIL THEN
	      BEGIN
	      temporaryBuffer.device ← ethernetOne;
	      -- should unwiredown packet, not now under interface
	      b ← currentInputBuffer;
	      b.length ←
		(b.length - ethernetEncapsulationOffset) - savedWordsLeft;
	      b.network ← LONG[@myNetwork];
	      IF CommFlags.doStats THEN
		BEGIN
		etherStats.packetsRecv ← etherStats.packetsRecv + 1;
		StatIncr[statEtherPacketsReceived];
		StatBump[statEtherWordsReceived, b.length];
		END;
	      PutOnGlobalInputQueue[b];
	      currentInputBuffer ← temporaryBuffer;
	      IF CommFlags.doStats AND currentOutputBuffer # NIL THEN
		StatIncr[statEtherInUnderOut];
	      END
	    ELSE
	      IF CommFlags.doStats THEN
		BEGIN
		etherStats.inputOff ← etherStats.inputOff + 1;
		StatIncr[statEtherEmptyFreeQueue];
		END;
	    END
	  ELSE
	    IF CommFlags.doStats THEN
	      BEGIN
	      etherStats.badRecvStatus ← etherStats.badRecvStatus + 1;
	      SELECT 377B - savedPostData.hardwareStatus FROM
		1B => StatIncr[statEtherReceivedNot16];
		10B => StatIncr[statEtherReceivedBadCRC];
		11B => StatIncr[statEtherReceivedNot16BadCRC];
		40B, 50B =>
		  BEGIN
		  etherStats.overruns ← etherStats.overruns + 1;
		  StatIncr[statEtherReceivedOverrun];
		  END;
		6B, 7B, 16B, 17B => StatIncr[statEtherReceivedKlobberedByReset];
		ENDCASE => StatIncr[statEtherReceivedBadStatus];
	      END;

	outputDone =>
	  IF savedPostData.hardwareStatus = hardwareAOK THEN
	    BEGIN
	    device.outputBuffer ← [0, NIL0];
	    PutOnGlobalDoneQueue[currentOutputBuffer];
	    currentOutputBuffer ← NIL;
	    IF CommFlags.doStats THEN
	      BEGIN
	      tries: CARDINAL;
	      statEtherSendsCollision1: StatsDefs.StatCounterIndex =
		statEtherSendsCollision1;
	      first: CARDINAL = LOOPHOLE[statEtherSendsCollision1];
	      etherStats.packetsSent ← etherStats.packetsSent + 1;
	      SELECT (tries ← device.retransmissionMask) FROM
		1 => tries ← 0;
		3 => tries ← 1;
		7 => tries ← 2;
		17B => tries ← 3;
		37B => tries ← 4;
		77B => tries ← 5;
		177B => tries ← 6;
		377B => tries ← 7;
		777B => tries ← 8;
		1777B => tries ← 9;
		3777B => tries ← 10;
		7777B => tries ← 11;
		17777B => tries ← 12;
		37777B => tries ← 13;
		77777B => tries ← 14;
		177777B => tries ← 15;
		ENDCASE => Glitch[FunnyRetransmissionMask];
	      IF tries # 0 THEN StatIncr[LOOPHOLE[first + tries]];
	      etherStats.loadTable[tries] ← etherStats.loadTable[tries] + 1;
	      END;
	    END
	  ELSE
	    BEGIN
	    IF CommFlags.doStats THEN
	      etherStats.badSendSatus ← etherStats.badSendSatus + 1;
	    IF (b ← currentOutputBuffer) # NIL AND
	      (AltoRam.GetTicks[] - timeSendStarted) > 500/AltoRam.msPerTick THEN
	      BEGIN  -- requeue it so one packet won't hog the interface
	      device.outputBuffer ← [0, NIL0];
	      PutOnGlobalDoneQueue[currentOutputBuffer];
	      currentOutputBuffer ← NIL;
	      IF CommFlags.doStats THEN StatIncr[statPacketsStuckInOutput];
	      END
	    ELSE IF CommFlags.doStats THEN StatIncr[statEtherSendBadStatus];
	    END;

	inputBufferOverflow =>
	  IF CommFlags.doStats THEN StatIncr[statEtherReceivedTooLong];

	outputLoadOverflow =>
	  BEGIN
	  -- requeue it so one packet won't hog the interface
	  device.outputBuffer ← [0, NIL0];
	  PutOnGlobalDoneQueue[currentOutputBuffer];
	  currentOutputBuffer ← NIL;
	  IF CommFlags.doStats THEN
	    BEGIN
	    etherStats.loadTable[16] ← etherStats.loadTable[16] + 1;
	    StatIncr[statEtherSendsCollisionLoadOverflow];
	    END;
	  END;

	zeroLengthBuffer => Glitch[ZeroLengthBuffer];

	hardwareReset =>
	  -- two reasons for getting here:
	  -- 1) getting back from debugger
	  -- 2) stuck output packet (transciever not plugged in)
	  BEGIN
	  IF (b ← currentOutputBuffer) # NIL AND
	    (AltoRam.GetTicks[] - timeSendStarted) > 500/AltoRam.msPerTick THEN
	    BEGIN
	    -- requeue it so one packet won't hog the interface
	    -- Watch the order of these stores
	    device.outputBuffer.pointer ← NIL0;
	    device.outputBuffer.count ← 0;
	    PutOnGlobalDoneQueue[currentOutputBuffer];
	    currentOutputBuffer ← NIL;
	    IF CommFlags.doStats THEN StatIncr[statPacketsStuckInOutput];
	    END
	  ELSE IF CommFlags.doStats THEN StatIncr[statInterfaceReset];
	  IF ~notChained AND device.inputControlBlock # NIL0 THEN
	    BEGIN -- restart input which got shot down
	    -- this could screwup if the microcode got restarted
	    device.inputControlBlock.inputBuffer.pointer↑ ← 0;
	    StartIO[inputCommand];
	    END;
	  END;

	interfaceBroken => Glitch[UnreasonableHardwareStatus];

	ENDCASE => Glitch[ImpossibleEndcase];


      IF doMoreInput THEN
	BEGIN
	-- The normal mode uses two buffers for input.  The current one, and a hot standby.
	-- Way up at the beginning of this loop, a read was started into the standby buffer.
	-- At this point, currentInputBuffer has a buffer to be setup for use next time.
	-- If we just finished a read,
	--  then it is a new one left there by the inputDone processing,
	--  (or the old one if we are recycling it because we couldn't get a new one)
	-- otherwise, we are reusing the previous one.

	temporaryBuffer ← nextInputBuffer;
	nextInputBuffer ← currentInputBuffer;
	currentInputBuffer ← temporaryBuffer;
	nextBufferPointer ← AltoRam.Shorten[
	  @nextInputBuffer.encapsulation + ethernetEncapsulationOffset];
	nextBufferPointer↑ ← 0;
	IF ~notChained THEN
	  BEGIN
	  temp: EthernetDeviceBlockHandle;
	  temp ← AltoRam.Shorten[nextInputBuffer.iocbChain];
	  temp↑ ←
	    [postData: ethernetNotPosted, interruptBit: interruptBit,
	      wordsLeft: 0, retransmissionMask: 0,
	      inputBuffer:
	      [nextInputBuffer.length - ethernetEncapsulationOffset,
		AltoRam.Shorten[
		@nextInputBuffer.encapsulation + ethernetEncapsulationOffset]],
	      outputBuffer: [0, NIL0], hostNumber: 0, inputControlBlock: NIL0];
	  last.inputControlBlock ← temp;
	  last ← temp;
	  tailBuffer.next ← nextInputBuffer;
	  tailBuffer ← nextInputBuffer;
	  IF device.inputControlBlock = NIL0 AND temp.postData = ethernetNotPosted
	    THEN
	    BEGIN -- adding a new buffer
	    device.inputControlBlock ← temp;
	    StartIO[inputCommand];
	    StatIncr[statEtherEmptyInputChain];
	    END;
	  END;
	END;

      -- see if there is output to do, there will be some for several reasons:
      -- 1 output finished, and another buffer was queued
      -- 2 input finished, and leftover outputBuffer (in under out)
      -- 3 input finished, and somebody didn't kick us because a packet was pouring in
      -- 4 (chained) we got some input first

      BEGIN
      IF currentOutputBuffer # NIL THEN GOTO SendThisOne;
      IF BufferDefs.QueueEmpty[@outputQueue] THEN GOTO NothingToSend;
      currentOutputBuffer ← Dequeue[@outputQueue];
      timeSendStarted ← AltoRam.GetTicks[];
      IF CommFlags.doDebug AND currentOutputBuffer = NIL THEN
	Glitch[QueueScrambled];
      IF CommFlags.doStats THEN StatIncr[statEtherSendFromOutputQueue];
      GOTO SendThisOne;
      EXITS
	SendThisOne =>
	  BEGIN -- start output if not already input coming in
	  IF notChained THEN
	    BEGIN
	    IF device.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	    device.interruptBit ← 0; -- inhibit interrupts for reset
	    device.postData ← ethernetNotPosted;
	    -- Beware of hardware/microcode screwup
	    -- it seems to hang while sending, after a collision, until a gateway packet arrives
	    IF CommFlags.doStats THEN StartIO[resetCommand];
	    -- should post immediately
	    UNTIL device.postData # ethernetNotPosted DO
	      IF CommFlags.doStats THEN StatIncr[statResetDidntPost];
	      StartIO[resetCommand];
	      ENDLOOP;
	    device.interruptBit ← interruptBit; --interrupts back on
	    device.postData ← ethernetNotPosted;
	    END
	  ELSE
	    BEGIN
	    -- Don't reverse the order of these tests.  It might be about ready to post.
	    IF device.outputBuffer.pointer # NIL THEN GOTO AlreadySending;
	    IF device.postData # ethernetNotPosted THEN GOTO DontSendAgain;
	    END;
	  device.retransmissionMask ← 0;
	  device.outputBuffer.count ← currentOutputBuffer.length;
	  device.outputBuffer.pointer ← AltoRam.Shorten[
	    @currentOutputBuffer.encapsulation + ethernetEncapsulationOffset];
	  IF ~notChained THEN
	    BEGIN
	    now: EthernetDeviceBlockHandle = device.inputControlBlock;
	    IF now # NIL AND now.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	    IF device.retransmissionMask # 0 THEN GOTO AlreadySending;
	    END;
	  StartIO[outputCommand];
	  EXITS PouringIn, AlreadySending, DontSendAgain => NULL;
	  END;
	NothingToSend => NULL;
      END;
      ENDLOOP;
    END; -- Interrupt

  Watcher: PROCEDURE =
    BEGIN
    UNTIL pleaseStop DO
      THROUGH [0..25) DO
	IF WatcherCheck[] THEN EXIT;
	-- If the post location is not zero, 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 at the post location several times.  Of course, if it is still not zero when we look again, it could be a new interrupt that has just arrived.
	REPEAT
	  FINISHED =>
	    BEGIN
	    IF CommFlags.doStats THEN StatIncr[statEtherLostInterrupts];
	    WatcherNotify[];
	    END;
	ENDLOOP;
      IF currentOutputBuffer # NIL AND (AltoRam.GetTicks[] - timeSendStarted) >
	250/AltoRam.msPerTick THEN StartIO[resetCommand];
      -- interrupt code will flush it
      IF (AltoRam.GetTicks[] - timeLastRecv) > 30000/AltoRam.msPerTick THEN
	BEGIN
	-- Blast receiver since it may be stuck.  This might kill a good packet.
	-- This shouldn't hurt (much) if thing are ok since it won't happen very often.
	timeLastRecv ← AltoRam.GetTicks[];
	IF CommFlags.doStats THEN StatIncr[statInputIdle];
	StartIO[resetCommand];
	END;
      WatcherWait[];
      ENDLOOP;
    END;

  WatcherCheck: ENTRY PROCEDURE RETURNS [ok: BOOLEAN] =
    BEGIN
    RETURN[
      myDevice.postData = ethernetNotPosted AND
	(notChained OR first.postData = ethernetNotPosted)];
    END;

  WatcherWait: ENTRY PROCEDURE = BEGIN WAIT timer; END;

  WatcherNotify: ENTRY PROCEDURE = BEGIN NOTIFY hardware; END;

  DecapsulateBuffer: PROCEDURE [b: Buffer] RETURNS [BufferType] =
    BEGIN
    timeLastRecv ← AltoRam.GetTicks[];
    SELECT b.encapsulation.ethernetOneType FROM
      pup =>
	BEGIN
	IF b.length # ((b.pupLength + 1 + ethernetEncapsulationBytes)/2) THEN
	  BEGIN
	  IF CommFlags.doStats THEN StatIncr[statPupsDiscarded];
	  RETURN[rejected];
	  END;
	RETURN[pup];
	END;
      ois =>
	BEGIN
	IF b.length # ((b.ois.pktLength + 1 + ethernetEncapsulationBytes)/2) THEN
	  BEGIN
	  IF CommFlags.doStats THEN StatIncr[statOisDiscarded];
	  RETURN[rejected];
	  END;
	RETURN[ois];
	END;
      translation =>
	BEGIN
	SELECT b.rawWords[0] FROM
	  translationRequest => ReceiveRequest[b];
	  translationResponse => ReceiveAck[b];
	  ENDCASE => NULL;
	ReturnFreeBuffer[b];
	RETURN[processed];
	END;
      ENDCASE => RETURN[rejected];
    END;

  EncapsulatePup: PROCEDURE [b: PupBuffer, destination: PupHostID] =
    BEGIN
    b.encapsulation ←
      [ethernetOne[
	etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
	translationWorked: TRUE, ethernetOneDest: destination,
	ethernetOneSource: myNetwork.hostNumber, ethernetOneType: pup]];
    b.length ← (b.pupLength + 1 + ethernetEncapsulationBytes)/2;
    END;

  EncapsulateOis: PROCEDURE [
    b: OisBuffer, destination: SpecialSystem.HostNumber] =
    BEGIN
    foundIt: BOOLEAN;
    ethernetAddr: Ethernet1Addr;
    [foundIt, ethernetAddr] ← Translate[destination];
    IF foundIt THEN
      BEGIN
      b.encapsulation ←
	[ethernetOne[
	  etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
	  translationWorked: TRUE, ethernetOneDest: ethernetAddr,
	  ethernetOneSource: myNetwork.hostNumber, ethernetOneType: ois]];
      b.length ← (b.ois.pktLength + 1 + ethernetEncapsulationBytes)/2;
      END
    ELSE
      BEGIN
      b.encapsulation ←
	[ethernetOne[
	  etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
	  translationWorked: FALSE, ethernetOneDest:, ethernetOneSource:,
	  ethernetOneType:]];
      END;
    END;

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

  SendBuffer: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    device: EthernetDeviceBlockHandle = myDevice;
    copy: Buffer;
    IF pleaseStop THEN Glitch[DriverNotActive];
    IF ~b.encapsulation.translationWorked THEN
      BEGIN PutOnGlobalDoneQueue[b]; RETURN; END;
    b.device ← ethernetOne;
    IF b.encapsulation.ethernetOneDest = myNetwork.hostNumber OR
      b.encapsulation.ethernetOneDest = PupTypes.allHosts THEN
      BEGIN -- sending to ourself, copy it over since we can't hear it
      copy ← GetInputBuffer[];
      IF copy # NIL THEN
	BEGIN
	copy.device ← ethernetOne;
	CommUtilDefs.CopyLong[
	  from: @b.encapsulation + ethernetEncapsulationOffset, nwords: b.length,
	  to: @copy.encapsulation + ethernetEncapsulationOffset];
	copy.length ← b.length;
	copy.network ← LONG[@myNetwork];
	IF CommFlags.doStats THEN StatIncr[statEtherPacketsLocal];
	IF CommFlags.doStats THEN StatBump[statEtherWordsLocal, b.length];
	PutOnGlobalInputQueue[copy];
	END
      ELSE IF CommFlags.doStats THEN StatIncr[statEtherEmptyFreeQueue];
      END;
    IF currentOutputBuffer = NIL THEN
      BEGIN
      currentOutputBuffer ← b;
      timeSendStarted ← AltoRam.GetTicks[];
      device.retransmissionMask ← 0;
      device.outputBuffer.count ← b.length;
      device.outputBuffer.pointer ← AltoRam.Shorten[
	@b.encapsulation + ethernetEncapsulationOffset];
      IF notChained THEN
	BEGIN
	IF device.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	device.interruptBit ← 0; -- inhibit interrupts for reset
	device.postData ← ethernetNotPosted;
	-- beware of hardware/microcode screwup
	-- it seems to hang while sending, after a collision, until a gateway packet arrives
	IF CommFlags.doStats THEN StartIO[resetCommand];
	-- should post immediately
	UNTIL device.postData # ethernetNotPosted DO
	  IF CommFlags.doStats THEN StatIncr[statResetDidntPost];
	  StartIO[resetCommand];
	  ENDLOOP;
	device.interruptBit ← interruptBit; --interrupts back on
	device.postData ← ethernetNotPosted;
	END;
      IF ~notChained THEN
	BEGIN
	now: EthernetDeviceBlockHandle = device.inputControlBlock;
	IF now # NIL AND now.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	IF device.retransmissionMask # 0 THEN GOTO AlreadySending;
	END;
      StartIO[outputCommand];  -- This could possibly clobber a packet that just started
      EXITS
	AlreadySending => NULL;
	PouringIn =>
	  BEGIN -- data already arriving, don't klobber it
	  IF CommFlags.doStats THEN StatIncr[statEtherSendWhileReceiving];
	  END;
      END
    ELSE Enqueue[@outputQueue, b]; -- output already in progress, don't klobber it
    IF CommFlags.doStats THEN StatIncr[statEtherPacketsSent];
    IF CommFlags.doStats THEN StatBump[statEtherWordsSent, b.length];
    END;

  -- Saving the status is helpful when debugging.  Comment it out to save space.
  ethernetStatus: EthernetDeviceBlockHandle;
  Broom: PROCEDURE [why: BcplOps.CleanupReason] =
    BEGIN
    IF CommFlags.doDebug THEN ethernetStatus↑ ← myDevice↑;
    SELECT why FROM
      Finish, Abort, OutLd => myDevice.interruptBit ← 0;
      InLd =>
	BEGIN
	IF myNetwork.hostNumber # CommUtilDefs.GetEthernetHostNumber[] THEN
	  Glitch[CantSwitchMachinesWhileEtherentDriverIsActive];
	myDevice.interruptBit ← interruptBit;
	END;
      Save, Checkpoint => Glitch[CantMakImageWhileEtherentDriverIsActive];
      ENDCASE;
    StartIO[resetCommand];
    END;

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

  CreateDefaultEthernetOneDrivers: PUBLIC PROCEDURE RETURNS [BOOLEAN] =
    BEGIN OPEN AltoEthernetDefs;
    SetupEthernetDriver[
      0, 5, standardInput, standardOutput, standardEthernet, FALSE];
    RETURN[TRUE];
    END;

  CreateDefaultEthernetDrivers: PUBLIC PROCEDURE RETURNS [BOOLEAN] =
    BEGIN RETURN[FALSE]; END;

  CreateEthernetDriver: PUBLIC PROCEDURE [
    netNumber: CARDINAL, deviceNumber: [0..3)] RETURNS [BOOLEAN] =
    BEGIN OPEN AltoEthernetDefs;
    him: POINTER TO FRAME[AltoEthernetDriver];
    -- There is no way to delete the new frame.
    IF deviceNumber # 0 THEN him ← NEW AltoEthernetDriver;
    SELECT deviceNumber FROM
      0 =>
	SetupEthernetDriver[
	  netNumber, 5, standardInput, standardOutput, standardEthernet, FALSE];
      1 =>
	him.SetupEthernetDriver[
	  netNumber, 6, secondInput, secondOutput, secondEthernet, FALSE];
      2 =>
	him.SetupEthernetDriver[
	  netNumber, 8, -- 7 used by keyboard
	  thirdInput, thirdOutput, thirdEthernet, FALSE];
      ENDCASE => Glitch[OnlyThreeDriversArePossible];
    RETURN[TRUE];
    END;

  CreateChainedEthernetDriver: PUBLIC PROCEDURE [
    netNumber: CARDINAL, deviceNumber: [0..3)] RETURNS [BOOLEAN] =
    BEGIN OPEN AltoEthernetDefs;
    him: POINTER TO FRAME[AltoEthernetDriver];
    -- There is no way to delete the new frame.
    IF deviceNumber # 0 THEN him ← NEW AltoEthernetDriver;
    SELECT deviceNumber FROM
      0 =>
	SetupEthernetDriver[
	  netNumber, 5, standardInput, standardOutput, standardEthernet, TRUE];
      1 =>
	him.SetupEthernetDriver[
	  netNumber, 6, secondInput, secondOutput, secondEthernet, TRUE];
      2 =>
	him.SetupEthernetDriver[
	  netNumber, 8, -- 7 used by keyboard
	  thirdInput, thirdOutput, thirdEthernet, TRUE];
      ENDCASE => Glitch[OnlyThreeDriversArePossible];
    RETURN[TRUE];
    END;

  SetupEthernetDriver: PROCEDURE [
    netNumber: CARDINAL, intLevel: WORD, inputBit, outputBit: WORD,
    deviceBlock: EthernetDeviceBlockHandle, chained: BOOLEAN] =
    BEGIN
    size: CARDINAL ← IF chained THEN SIZE[EthernetDeviceBlock] ELSE 0;
    notChained ← ~chained;
    myNetwork.netNumber ← [0, netNumber];
    myNetwork.buffers ← IF chained THEN numberOfInputBuffers ELSE 2;
    inputCommand ← [inputBit];
    outputCommand ← [outputBit];
    interruptLevel ← intLevel;
    myDevice ← deviceBlock;
    resetCommand ← [inputCommand + outputCommand];
    interruptBit ← Inline.BITSHIFT[1, interruptLevel];
    pleaseStop ← TRUE;
    myDevice.postData ← ethernetNotPosted;
    AddDeviceToChain[@myNetwork, size];
    IF CommFlags.doStats THEN
      BEGIN
      myNetwork.stats ← etherStats ← Storage.Node[SIZE[EtherStatsInfo]];
      MiscDefs.Zero[etherStats, SIZE[EtherStatsInfo]];
      END;
    END;

  DeleteDriver: PROCEDURE =
    BEGIN
    IF CommFlags.doStats THEN
      BEGIN Storage.Free[etherStats]; myNetwork.stats ← etherStats ← NIL; END;
    IF myDevice # standardEthernet THEN Runtime.SelfDestruct[];
    END;

  -- Be sure the microcode has been loaded by now if this is a second Ethernet Board

  ActivateDriver: PROCEDURE =
    BEGIN
    IF ~pleaseStop THEN Glitch[DriverAlreadyActive];
    pleaseStop ← FALSE;
    StartIO[resetCommand];
    StartIO[resetCommand]; -- sometimes it doesn't work
    IF myDevice.postData = ethernetNotPosted THEN Glitch[NoEthernetBoard];
    QueueInitialize[@outputQueue];
    currentInputBuffer ← nextInputBuffer ← currentOutputBuffer ← NIL;
    myNetwork.hostNumber ← CommUtilDefs.GetEthernetHostNumber[];
    myDevice.hostNumber ← myNetwork.hostNumber;
    myDevice.inputBuffer ← [0, NIL0];
    myDevice.outputBuffer ← [0, NIL0];
    IF notChained THEN
      BEGIN
      where: LONG POINTER;
      nextInputBuffer ← GetInputBuffer[];
      currentInputBuffer ← GetInputBuffer[];
      IF Inline.HighHalf[currentInputBuffer] # 0 THEN
	Glitch[HyperspaceNotSupported];
      where ← @currentInputBuffer.encapsulation + ethernetEncapsulationOffset;
      IF Inline.BITAND[Inline.LowHalf[where], 3] # 0 THEN
	Glitch[BufferNotAlignedProperly];
      nextInputBuffer.device ← currentInputBuffer.device ← ethernetOne;
      nextBufferPointer ← AltoRam.Shorten[
	@nextInputBuffer.encapsulation + ethernetEncapsulationOffset];
      nextBufferPointer↑ ← 0; -- show no input in yet
      myDevice.inputControlBlock ← NIL0;
      END
    ELSE
      BEGIN
      temp: EthernetDeviceBlockHandle;
      where: LONG POINTER;
      first ← last ← NIL;
      headBuffer ← tailBuffer ← NIL;
      THROUGH [0..numberOfInputBuffers) DO
	currentInputBuffer ← GetInputBuffer[];
	IF Inline.HighHalf[currentInputBuffer] # 0 THEN
	  Glitch[HyperspaceNotSupported];
	where ← @currentInputBuffer.encapsulation + ethernetEncapsulationOffset;
	IF Inline.BITAND[Inline.LowHalf[where], 3] # 0 THEN
	  Glitch[BufferNotAlignedProperly];
	temp ← AltoRam.Shorten[currentInputBuffer.iocbChain];
	IF first = NIL THEN
	  BEGIN first ← temp; headBuffer ← currentInputBuffer; END;
	temp↑ ←
	  [postData: ethernetNotPosted, interruptBit: interruptBit, wordsLeft: 0,
	    retransmissionMask: 0,
	    inputBuffer:
	    [currentInputBuffer.length - ethernetEncapsulationOffset,
	      AltoRam.Shorten[
	      @currentInputBuffer.encapsulation + ethernetEncapsulationOffset]],
	    outputBuffer: [0, NIL0], hostNumber: 0, inputControlBlock: NIL0];
	temp.inputBuffer.pointer↑ ← 0;
	IF last # NIL THEN
	  BEGIN
	  last.inputControlBlock ← temp;
	  tailBuffer.next ← currentInputBuffer;
	  END;
	last ← temp;
	currentInputBuffer.next ← NIL;
	tailBuffer ← currentInputBuffer;
	ENDLOOP;
      myDevice.inputControlBlock ← first;
      END;
    ImageDefs.AddCleanupProcedure[@cleanupItem];
    CommUtilDefs.AddInterruptHandler[interruptLevel, @hardware, resetCommand];
    hardProcess ← FORK Interrupt[]; -- The first interrupt will set things up.
    myDevice.interruptBit ← interruptBit;
    StartIO[resetCommand];
    watcherProcess ← FORK Watcher[];
    CreateCache[];
    END;

  DeactivateDriver: PROCEDURE =
    BEGIN
    IF pleaseStop THEN Glitch[DriverNotActive];
    pleaseStop ← TRUE;
    StartIO[resetCommand]; -- includes (naked)NOTIFY
    JOIN hardProcess;
    ImageDefs.RemoveCleanupProcedure[@cleanupItem];
    myDevice.interruptBit ← 0;
    CommUtilDefs.RemoveInterruptHandler[interruptLevel];
    StartIO[resetCommand];
    DeleteDriverLocked[];
    JOIN watcherProcess;
    IF currentInputBuffer # NIL THEN ReturnFreeBuffer[currentInputBuffer];
    IF nextInputBuffer # NIL THEN ReturnFreeBuffer[nextInputBuffer];
    IF currentOutputBuffer # NIL THEN PutOnGlobalDoneQueue[currentOutputBuffer];
    QueueCleanup[@outputQueue];
    myNetwork.netNumber ← [0, 0];
    -- in case we turn it on after moving to another machine
    -- maybe we should turn off the SD bits if we are an extra board
    DeleteCache[];
    END;

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

  -- * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * 
  -- ADdress translation for 8 bit EthernetOne (Pup) and 48 bit Ethernet (OISCP)
  -- * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *

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

  CacheStatus: TYPE = {pending, active};
  CacheEntry: TYPE = POINTER TO CacheObject;
  CacheObject: TYPE = RECORD [
    next: CacheEntry,
    addressPair: AddressPair,
    counter: [0..deactivateCount],
    status: CacheStatus ];

  translationRequest: CARDINAL = 10101B;
  translationResponse: CARDINAL = 7070B;
  cacheQueueHead: CacheEntry ← NIL;
  broadCastPairEntry: CacheEntry; -- permanent
  myAddressPairEntry: CacheEntry; -- permanent
  retryTime: CARDINAL = 2; -- two seconds
  deactivateTime: CARDINAL = 3*60; -- three minutes
  deactivateCount: CARDINAL = deactivateTime/retryTime;
  cacheEvent: CONDITION;
  demonProcess: PROCESS;

  CreateCache: ENTRY PROCEDURE =
    BEGIN
    aP: AddressPair ← [OISCP.allHostIDs, PupTypes.allHosts, 0];
    cacheQueueHead ← NIL;
    broadCastPairEntry ← AddAddressPair[aP];
    Process.SetTimeout[@cacheEvent, Process.SecondsToTicks[retryTime]];
    demonProcess ← FORK Demon[];
    Process.Detach[FORK PutMeIntoCache[]];
    END;

  -- This crazy structure is needed because GetProcessorID hangs until we learn our network number, which may not happen until the driver has been started.
  PutMeIntoCache: PROCEDURE =
    BEGIN
    Rats: ENTRY PROCEDURE = INLINE
      BEGIN myAddressPairEntry ← AddAddressPair[aP]; END;
    aP: AddressPair;
    aP ← [SpecialSystem.GetProcessorID[], Inline.LowByte[myNetwork.hostNumber], 0];
    IF ~pleaseStop THEN Rats[];
    END;

  DeleteCache: PROCEDURE =
    BEGIN
    DeleteCacheLocked: ENTRY PROCEDURE = INLINE BEGIN NOTIFY cacheEvent; END;
    e, nextE: CacheEntry;
    DeleteCacheLocked[];
    JOIN demonProcess;
    e ← cacheQueueHead;
    cacheQueueHead ← NIL;
    WHILE e # NIL DO nextE ← e.next; Storage.Free[e]; e ← nextE; ENDLOOP;
    END;

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

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

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

  Translate: ENTRY PROCEDURE [oisAddr: OisAddr]
    RETURNS [foundIt: BOOLEAN, ethernet1Addr: Ethernet1Addr] =
    BEGIN
    e: CacheEntry ← FindEntry[oisAddr];
    IF e # NIL THEN
      BEGIN
      e.counter ← 0;
      IF foundIt ← (e.status = active) THEN
	BEGIN
	ethernet1Addr ← e.addressPair.ethernet1Addr;
	END;
      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;
      END
    ELSE -- entry not found, so add a new one
      BEGIN
      foundIt ← FALSE;
      IF CommFlags.doStats THEN StatIncr[cacheFault];
      e ← Storage.Node[SIZE[CacheObject]];
      e↑ ← [
            next: NIL,
            addressPair: [oisAddr: oisAddr, ethernet1Addr: [377B]],
            counter: 0,
            status: pending];
      AddEntry[e];
      SendRequest[e];
      END;
    END;

  AddAddressPair: INTERNAL PROCEDURE [aP: AddressPair] RETURNS [e: CacheEntry] =
    BEGIN
    IF (e ← FindEntry[aP.oisAddr]) = NIL THEN
      BEGIN e ← Storage.Node[SIZE[CacheObject]]; AddEntry[e]; END;
    e.addressPair ← aP;
    e.status ← active;
    e.counter ← 0;
    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.counter ← 0
    ELSE BEGIN RemoveEntry[e]; Storage.Free[e]; END;
    END;

  Demon: ENTRY PROCEDURE =
    BEGIN
    next: CacheEntry;
    Process.SetPriority[3];
    UNTIL pleaseStop DO
      WAIT cacheEvent;
      IF pleaseStop THEN EXIT;
      FOR e: CacheEntry ← cacheQueueHead, next WHILE (e # NIL) DO
	next ← e.next;
        e.counter ← e.counter + 1;
        SELECT TRUE FROM
          e.counter = deactivateCount => DeallocateEntry[e];
	  e.status = pending =>
	    BEGIN
	    IF CommFlags.doStats THEN StatIncr[translationRetries];
	    SendRequest[e];
	    END;
          ENDCASE;
	ENDLOOP; -- end of queue entries loop
      ENDLOOP; -- end of infinite loop
    END;

  SendRequest: INTERNAL PROCEDURE [e: CacheEntry] =
    BEGIN
    b: Buffer;
    request: LONG POINTER TO AddressPair;
    IF (b ← GetInputBuffer[]) # NIL THEN
      BEGIN  -- broadcast the translation request
      b.encapsulation ←
	[ethernetOne[
	  etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
	  translationWorked:, ethernetOneDest: PupTypes.allHosts,
	  ethernetOneSource: myNetwork.hostNumber, ethernetOneType: translation]];
      b.length ← (1 + ethernetEncapsulationBytes)/2 + 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;
      SendBufferLocked[b];
      END;
    END;

  ReceiveAck: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    IF b.encapsulation.ethernetOneDest =
      myAddressPairEntry.addressPair.ethernet1Addr THEN
      BEGIN
      receipt: LONG POINTER TO AddressPair ← LOOPHOLE[@b.rawWords[1]];
      [] ← AddAddressPair[receipt↑];
      END;
    END;

  ReceiveRequest: ENTRY PROCEDURE [b: Buffer] =
    BEGIN
    request, requesterAddr: LONG POINTER TO AddressPair;
    request ← LOOPHOLE[@b.rawWords[1]];
    IF request.oisAddr = myAddressPairEntry.addressPair.oisAddr THEN
      BEGIN
      IF CommFlags.doStats THEN StatIncr[requestsForMe];
      request.ethernet1Addr ← myAddressPairEntry.addressPair.ethernet1Addr;
      SendAck[request↑, b.encapsulation.ethernetOneSource];
      -- since the requester is probably going to talk to us, add his address before we take a fault
      requesterAddr ← request + SIZE[AddressPair];
      [] ← AddAddressPair[requesterAddr↑];
      END;
    END;

  SendAck: INTERNAL PROCEDURE [aP: AddressPair, to: DriverTypes.Byte] =
    BEGIN
    b: Buffer;
    response: LONG POINTER TO AddressPair;
    IF (b ← GetInputBuffer[]) # NIL THEN
      BEGIN
      b.encapsulation ←
	[ethernetOne[
	  etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
	  translationWorked:, ethernetOneDest: to,
	  ethernetOneSource: myNetwork.hostNumber, ethernetOneType: translation]];
      b.length ← (1 + ethernetEncapsulationBytes)/2 + SIZE[AddressPair] + 1;
      b.rawWords[0] ← translationResponse;
      response ← LOOPHOLE[@b.rawWords[1]];
      response↑ ← aP;
      SendBufferLocked[b];
      END;
    END;

  SendBufferLocked: INTERNAL PROCEDURE [b: Buffer] =
    BEGIN
    device: EthernetDeviceBlockHandle = myDevice;
    IF pleaseStop THEN Glitch[DriverNotActive];
    b.device ← ethernetOne;
    IF currentOutputBuffer = NIL THEN
      BEGIN
      currentOutputBuffer ← b;
      timeSendStarted ← AltoRam.GetTicks[];
      device.retransmissionMask ← 0;
      device.outputBuffer.count ← b.length;
      device.outputBuffer.pointer ← AltoRam.Shorten[
	@b.encapsulation + ethernetEncapsulationOffset];
      IF notChained THEN
	BEGIN
	IF device.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	device.interruptBit ← 0; -- inhibit interrupts for reset
	device.postData ← ethernetNotPosted;
	-- beware of hardware/microcode screwup
	-- it seems to hang while sending, after a collision, until a gateway packet arrives
	IF CommFlags.doStats THEN StartIO[resetCommand];
	-- should post immediately
	UNTIL device.postData # ethernetNotPosted DO
	  IF CommFlags.doStats THEN StatIncr[statResetDidntPost];
	  StartIO[resetCommand];
	  ENDLOOP;
	device.interruptBit ← interruptBit; --interrupts back on
	device.postData ← ethernetNotPosted;
	END;
      IF ~notChained THEN
	BEGIN
	now: EthernetDeviceBlockHandle = device.inputControlBlock;
	IF now # NIL AND now.inputBuffer.pointer↑ # 0 THEN GOTO PouringIn;
	IF device.retransmissionMask # 0 THEN GOTO AlreadySending;
	END;
      StartIO[outputCommand]; -- This could possibly clobber a packet that just started
      EXITS
	AlreadySending => NULL;
	PouringIn =>
	  BEGIN -- data already arriving, don't klobber it
	  IF CommFlags.doStats THEN StatIncr[statEtherSendWhileReceiving];
	  END;
      END
    ELSE Enqueue[@outputQueue, b]; -- output already in progress, don't klobber it
    IF CommFlags.doStats THEN StatIncr[statEtherPacketsSent];
    IF CommFlags.doStats THEN StatBump[statEtherWordsSent, b.length];
    END;

  -- initialization
  Process.DisableTimeout[@hardware];
  Process.SetTimeout[@timer, Process.MsecToTicks[1000]];
  IF CommFlags.doDebug THEN
    BEGIN
    debugPointer: LONG POINTER TO GiantVector ← GetGiantVector[];
    debugPointer.ethernetOutputQueue ← @outputQueue;
    debugPointer.currentInputBuffer ← @currentInputBuffer;
    debugPointer.nextInputBuffer ← @nextInputBuffer;
    debugPointer.currentOutputBuffer ← @currentOutputBuffer;
    ethernetStatus ← Storage.Node[SIZE[EthernetDeviceBlock]];
    END;
  END.