-- Copyright (C) 1983, 1984  by Xerox Corporation. All rights reserved. 
--EthernetOneDriver.mesa, HGM, 29-Feb-84 15:25:11
-- (last edit by: AOF on: 15-Jun-83 11:35:16)

DIRECTORY
  Buffer USING [AccessHandle, Buffer, DestroyPool, MakePool, Type],
  CommFlags USING [doDebug, doStats, driverStats],
  CommHeap USING [MakeNode, FreeNode],
  CommUtil USING [AllocateIocbs, FreeIocbs],
  Driver USING [
    Glitch, GetDeviceChain, GetInputBuffer, Network, NetworkObject,
    AddDeviceToChain, PutOnGlobalDoneQueue, PutOnGlobalInputQueue,
    ReturnFreeBuffer],
  DriverTypes USING [
    Byte, ethernetOneEncapsulationOffset, ethernetOneEncapsulationBytes],
  Environment USING [Byte],
  EthernetOneFace,
  EthernetDriverFriends USING [EtherStatsInfo],
  Inline USING [LowHalf, HighHalf, BITAND, LongCOPY],
  Process USING [
    Abort, Detach, DisableTimeout, EnableAborts, GetPriority,
    Priority, SecondsToTicks, SetPriority, SetTimeout, Yield],
  ProcessPriorities USING [priorityIOHigh],
  SpecialRuntime USING [AllocateNakedCondition, DeallocateNakedCondition],
  PupTypes USING [allHosts, PupErrorCode, PupHostID],
  Runtime USING [GlobalFrame, SelfDestruct],
  Stats USING [StatBump, StatIncr, StatCounterIndex],
  SpecialCommunication USING [],
  SpecialSystem USING [HostNumber, GetProcessorID, NetworkNumber],
  System USING [
    GetClockPulses, Pulses,
    MicrosecondsToPulses, switches--['<]--,
    broadcastHostNumber, nullNetworkNumber];

EthernetOneDriver: MONITOR
  IMPORTS
    Buffer, CommHeap, CommUtil, Driver, Stats, EthernetOneFace,
    Inline, Process, Runtime, SpecialRuntime, SpecialSystem, System
  EXPORTS Buffer, Driver, SpecialCommunication, System =
  BEGIN
  OPEN EthernetOneFace;

  --EXPORTed TYPEs
  Network: PUBLIC TYPE = Driver.Network;
  HostNumber: PUBLIC TYPE = SpecialSystem.HostNumber;
  NetworkNumber: PUBLIC TYPE = SpecialSystem.NetworkNumber;

  encapOffset: CARDINAL =
    DriverTypes.ethernetOneEncapsulationOffset;
  encapBytes: CARDINAL = DriverTypes.ethernetOneEncapsulationBytes;

  ether: DeviceHandle;
  globalStatePtr: GlobalStatePtr;  --Allocate space if needed
  myEar: CARDINAL;
  --what address am I listening for (verses myNetwork.pupHostNumber, my real address).
  getGarbage: BOOLEAN ← FALSE;  --when true, we deliver any packet
  setupEthernetOneDriver: PROC[etherDevice: DeviceHandle];
  ethernetOneListenForHost: PROC[newHostNumber: CARDINAL];

  inputState: RECORD[
    process: PROCESS,
    mask: WORD,
    access: Buffer.AccessHandle,
    inWait: LONG POINTER TO CONDITION,
    firstBuffer, lastBuffer: Buffer.Buffer,
    queueAllowed, queueLength: CARDINAL,
    timeLastRecv: LONG CARDINAL,
    lastMissed: CARDINAL];
  
  outputState: RECORD[
    process: PROCESS,
    mask: WORD,
    outWait: LONG POINTER TO CONDITION,
    firstBuffer, lastBuffer: Buffer.Buffer,
    timeSendDone: LONG CARDINAL];

  watcherState: RECORD[
    pleaseStop: BOOLEAN,
    process: PROCESS, timer: CONDITION];

  --IOCBs
  iocbState: RECORD[wait: CONDITION, first, free: FreeIocb];
  FreeIocb: TYPE = LONG POINTER TO IocbObject;
  IocbObject: TYPE = RECORD[
    next: FreeIocb, rest: SEQUENCE COMPUTED CARDINAL OF WORD];

  seconds: RECORD[one, fiveHalf, forty: LONG CARDINAL];

  myNetwork: Driver.NetworkObject ← [
    decapsulateBuffer: DecapsulateBuffer,
    encapsulateAndSendPup: EncapsulateAndSendPup,
    encapsulateAndSendNS: EncapsulateAndSendNS,
    sendRawBuffer: SendRawBuffer,
    encapsulateAndForwardPup: ForwardPup,
    encapsulateAndForwardNS: EncapsulateAndForwardNS,
    activateDriver: ActivateDriver,
    deactivateDriver: DeactivateDriver,
    deleteDriver: DeleteDriver,
    changeNumberOfInputBuffers: MaybeChangeNumberOfInputBuffers,
    alive: TRUE, buffers:, device: ethernetOne, index:,
    netNumber: System.nullNetworkNumber, pupNetNumber: 0, pupHostNumber: 0,
    next: NIL, pupStats: NIL, statsLevel0: NIL, statsLevel1: NIL];


  LostAllIocbs: PUBLIC ERROR = CODE;
  IOCBSizeIsZero: PUBLIC ERROR = CODE;
  DriverNotActive: PUBLIC ERROR = CODE;
  DriverAlreadyActive: PUBLIC ERROR = CODE;
  IOCBMustBeInFirstMDS: PUBLIC ERROR = CODE;
  IOCBMustBeQuadWordAligned: PUBLIC ERROR = CODE;
  EthernetNetNumberScrambled: PUBLIC ERROR = CODE;
  BufferMustBeAlmostQuadWordAligned: PUBLIC ERROR = CODE;

  etherStats: EthernetDriverFriends.EtherStatsInfo;

  --Hot Procedures

  GetBufferAndIocb: INTERNAL PROC RETURNS[b: Buffer.Buffer] =
    BEGIN
    SELECT TRUE FROM
      (iocbState.free = NIL) =>
        {IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait]; RETURN[NIL]};
      ((b ← Driver.GetInputBuffer[FALSE]) = NIL) => RETURN;
      ENDCASE;
    b.driver.iocb ← iocbState.free;
    iocbState.free ← iocbState.free.next;
  END;  --GetBufferAndIocb

  FreeBufferAndIocb: INTERNAL PROC[
    queueProc: PROC[b: Buffer.Buffer], b: Buffer.Buffer] =
    BEGIN
    iocb: FreeIocb ← b.driver.iocb;
    IF iocb # NIL THEN
      BEGIN
      iocb.next ← iocbState.free;
      iocbState.free ← iocb;
      b.driver.iocb ← NIL;
      NOTIFY iocbState.wait;
      END;
    queueProc[b];
    END;  --FreeBufferAndIocb

  InInterrupt: ENTRY PROC =
    BEGIN
    status: Status;
    acceptBuffer: BOOLEAN;
    this, new: Buffer.Buffer;

    DO
      ENABLE ABORTED => EXIT;
      UNTIL (this ← inputState.firstBuffer) # NIL DO
        WAIT inputState.inWait; ENDLOOP;
      status ← GetStatus[this.driver.iocb];
      IF CommFlags.doStats AND status # pending THEN
        Stats.StatIncr[statEtherInterruptDuringInterrupt];
      UNTIL status # pending DO
	WAIT inputState.inWait;
	status ← GetStatus[this.driver.iocb];
	IF CommFlags.doStats AND status = pending
	  THEN Stats.StatIncr[statEtherMissingStatus];
	ENDLOOP;
      inputState.firstBuffer ← inputState.firstBuffer.next;
      IF status = ok THEN acceptBuffer ← TRUE
      ELSE
	BEGIN
	acceptBuffer ← getGarbage; --we may be collecting garbage packets
	IF CommFlags.driverStats
	  THEN etherStats.badRecvStatus ← etherStats.badRecvStatus + 1;
	IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedBadStatus];
	IF CommFlags.doStats OR CommFlags.driverStats THEN
	  SELECT status FROM
	    packetTooLong =>
	      BEGIN
	      IF CommFlags.driverStats
		THEN etherStats.packetTooLong ← etherStats.packetTooLong + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedTooLong];
	      END;
	    badAlignmentButOkCrc =>
	      BEGIN
	      IF CommFlags.driverStats THEN etherStats.badAlignmentButOkCrc ←
		etherStats.badAlignmentButOkCrc + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedNot16];
	      END;
	    crc =>
	      BEGIN
	      IF CommFlags.driverStats THEN
		etherStats.badCrc ← etherStats.badCrc + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedBadCRC];
	      END;
	    crcAndBadAlignment =>
	      BEGIN
	      IF CommFlags.driverStats THEN
		etherStats.crcAndBadAlignment ← etherStats.crcAndBadAlignment+1;
	      IF CommFlags.doStats THEN
	        Stats.StatIncr[statEtherReceivedNot16BadCRC];
	      END;
	    overrun =>
	      BEGIN
	      IF CommFlags.driverStats THEN
		etherStats.overrun ← etherStats.overrun + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedOverrun];
	      END;
	    ENDCASE;
        END;
      IF ~acceptBuffer THEN {new ← this; new.next ← NIL} --recycle this buffer
      ELSE
	BEGIN
	inputState.timeLastRecv ← this.time ← System.GetClockPulses[];
	this.driver.length ← GetPacketLength[this.driver.iocb];
	this.driver.faceStatus ← ethernetOne[status];
	this.network ← LONG[@myNetwork];
	IF CommFlags.driverStats THEN
	  BEGIN
	  etherStats.packetsRecv ← etherStats.packetsRecv + 1;
	  etherStats.wordsRecv ← etherStats.wordsRecv + this.driver.length;
	  END;
	IF CommFlags.doStats THEN
	  BEGIN
	  Stats.StatIncr[statEtherPacketsReceived];
	  Stats.StatBump[statEtherWordsReceived, this.driver.length];
	  END;
	FreeBufferAndIocb[Driver.PutOnGlobalInputQueue, this];

	SELECT TRUE FROM
	  (inputState.queueLength > inputState.queueAllowed) =>
	    BEGIN
	    new ← NIL;
	    inputState.queueLength ← inputState.queueLength - 1;
	    NOTIFY watcherState.timer;
	    IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
	    END;
	  ((new ← GetBufferAndIocb[]) = NIL) =>
	    BEGIN --Rats, couldn't or didn't want a new buffer
	    inputState.queueLength ← inputState.queueLength - 1;
	    NOTIFY watcherState.timer;
	    IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
	    END;
	  ENDCASE;

	END; --acceptBuffer clause
      --add new buffer to end of input chain
      IF new # NIL THEN
        BEGIN
	new.driver.faceStatus ← ethernetOne[pending];
	QueueInput[
	  ether,
	  @new.encapsulation + encapOffset,
	  new.driver.length - encapOffset,
	  new.driver.iocb];
	IF inputState.firstBuffer = NIL THEN inputState.firstBuffer ← new
	ELSE inputState.lastBuffer.next ← new;
	inputState.lastBuffer ← new;
        END;
      ENDLOOP;
    END;

  OutInterrupt: ENTRY PROC =
    BEGIN
    b: Buffer.Buffer;
    status: Status;

    DO
      ENABLE ABORTED => EXIT;
      DO
        --we compute the values each time around since the value of b can
	--change if the watcher shoots down the output.
	SELECT TRUE FROM
	  ((b ← outputState.firstBuffer) = NIL) => NULL;
	  ((status ← GetStatus[b.driver.iocb]) # pending) => EXIT;
	  ENDCASE;
	WAIT outputState.outWait;
        ENDLOOP;

      outputState.timeSendDone ← System.GetClockPulses[];  --still transmiting
      b.driver.faceStatus ← ethernetOne[status];

      IF status = ok THEN
	BEGIN
	IF CommFlags.doStats OR CommFlags.driverStats THEN
	  BEGIN
	  tries: CARDINAL ← GetRetries[b.driver.iocb];
	  statEtherSendsCollision1: Stats.StatCounterIndex =
	    statEtherSendsCollision1;
	  first: CARDINAL = LOOPHOLE[statEtherSendsCollision1];
	  IF CommFlags.driverStats THEN
	    BEGIN
	    etherStats.packetsSent ← etherStats.packetsSent + 1;
	    etherStats.wordsSent ← etherStats.wordsSent + b.driver.length;
	    etherStats.loadTable[tries] ← etherStats.loadTable[tries] + 1;
	    END;
	  IF CommFlags.doStats AND tries # 0 THEN
	    Stats.StatIncr[LOOPHOLE[first + tries]];
	  END;
	END
      ELSE
	BEGIN
	IF CommFlags.driverStats THEN
	  etherStats.badSendStatus ← etherStats.badSendStatus + 1;
	IF CommFlags.doStats THEN Stats.StatIncr[statEtherSendBadStatus];
	IF CommFlags.doStats OR CommFlags.driverStats THEN
	  SELECT status FROM
	    tooManyCollisions =>
	      BEGIN
	      IF CommFlags.driverStats THEN
		etherStats.tooManyCollisions ← etherStats.tooManyCollisions + 1;
	      IF CommFlags.doStats THEN
		Stats.StatIncr[statEtherSendsCollisionLoadOverflow];
	      END;
	    underrun =>
	      BEGIN
	      IF CommFlags.driverStats THEN
		etherStats.underrun ← etherStats.underrun + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherSendOverrun];
	      END;
	    ENDCASE;
	END;
      --We don't resend things that screwup
      outputState.firstBuffer ← outputState.firstBuffer.next;
      FreeBufferAndIocb[Driver.PutOnGlobalDoneQueue, b];
      ENDLOOP;
    END;

  Watcher: PROC =
    BEGIN
    CheckForIdleInput: ENTRY PROC = INLINE
      BEGIN
      IF (System.GetClockPulses[] - inputState.timeLastRecv) <
        seconds.forty THEN RETURN;
      IF CommFlags.doStats THEN Stats.StatIncr[statInputIdle];
      IF CommFlags.driverStats THEN
        etherStats.idleInput ← etherStats.idleInput + 1;
      SmashCSBs[]; --this will leave output dangling
      END;  --CheckForIdleInput

    CheckForStuckOutput: ENTRY PROC = INLINE
      BEGIN
      SELECT TRUE FROM
        outputState.firstBuffer = NIL => NULL;
        ((System.GetClockPulses[] - outputState.timeSendDone) < seconds.fiveHalf) => RETURN;
	ENDCASE =>
	  BEGIN
        --This happens if the transciever is unplugged
        TurnOff[ether];
        UNTIL outputState.firstBuffer = NIL DO
          b ← outputState.firstBuffer;
          outputState.firstBuffer ← outputState.firstBuffer.next;
          FreeBufferAndIocb[Driver.PutOnGlobalDoneQueue, b];
          IF CommFlags.doStats THEN Stats.StatIncr[statPacketsStuckInOutput];
          IF CommFlags.driverStats THEN
            etherStats.stuckOutput ← etherStats.stuckOutput + 1;
          ENDLOOP;
        SmashCSBs[];
	END;
    outputState.timeSendDone ← System.GetClockPulses[];
    END;  --CheckForStuckOutput

    QueueInputBufferLocked: ENTRY PROC = INLINE
      BEGIN ENABLE UNWIND => NULL;
      SELECT TRUE FROM
        (b = NIL) => WAIT watcherState.timer;  --this is an alternate WAIT
	((b.driver.iocb ← iocbState.free) # NIL) =>
	  BEGIN
	  iocbState.free ← iocbState.free.next;
	  b.driver.faceStatus ← ethernetOne[pending];
	  QueueInput[
	    ether,
	    @b.encapsulation + encapOffset,
	    b.driver.length - encapOffset,
	    b.driver.iocb];
	  IF inputState.firstBuffer = NIL THEN inputState.firstBuffer ← b
	  ELSE inputState.lastBuffer.next ← b;
	  inputState.lastBuffer ← b;
	  inputState.queueLength ← inputState.queueLength + 1;
	  END;
	ENDCASE =>  --the ENDCASE better be rare!
          BEGIN
	  IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait];
	  Driver.ReturnFreeBuffer[b];  --give the buffer back (ARGH!!)
	  WAIT watcherState.timer;  --this is an alternate WAIT
	  END;
      END;  --QueueInputBufferLocked

    WaitForTimer: ENTRY PROC = INLINE
      BEGIN ENABLE UNWIND => NULL;
      WAIT watcherState.timer;
      END;

    b: Buffer.Buffer;
    enterLoop: LONG CARDINAL;
    inputState.lastMissed ← GetPacketsMissed[ether];
    DO
      ENABLE ABORTED => EXIT;
      enterLoop ← System.GetClockPulses[];
      --Check for lost interrupts
      IF CheckBuffer[@inputState.firstBuffer] OR
        CheckBuffer[@outputState.firstBuffer] THEN WatchCarefully[];
      CheckForIdleInput[];
      CheckForStuckOutput[];

      WHILE (inputState.queueLength < inputState.queueAllowed) DO
        --don't lock monitor and wait for a buffer
        b ← Driver.GetInputBuffer[tryToWaitForBuffer: TRUE];
	QueueInputBufferLocked[];  --give it a chance to wait
	IF b = NIL THEN EXIT;  --but don't futz around forever
	ENDLOOP;

      IF CommFlags.doStats OR CommFlags.driverStats THEN
        BEGIN
	missed: CARDINAL ← GetPacketsMissed[ether];
	lost: CARDINAL ← missed - inputState.lastMissed;
	IF lost # 0 THEN
	  BEGIN
	  IF CommFlags.doStats
	    THEN Stats.StatBump[statEtherEmptyNoBuffer, lost];
	  IF CommFlags.driverStats
	    THEN etherStats.packetsMissed ← etherStats.packetsMissed + lost;
	  inputState.lastMissed ← missed;
	  END;
	END;

      IF (System.GetClockPulses[] - enterLoop) < seconds.one THEN 
        WaitForTimer[];
      ENDLOOP;

    END;  --Watcher

  CheckBuffer: ENTRY PROC[p: POINTER TO Buffer.Buffer]
    RETURNS [trouble: BOOLEAN] =
    BEGIN
    b: Buffer.Buffer ← p↑;
    IF b = NIL THEN RETURN[FALSE];
    RETURN[(GetStatus[b.driver.iocb] # pending)];
    END;

  WatchCarefully: PROC =
    BEGIN
    <<
    In status # pending, an interrupt should have happened.  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 ~CheckBuffer[@inputState.firstBuffer] THEN EXIT;
      REPEAT FINISHED => WatcherNotify[];
      ENDLOOP;
     --Check for lost output interrupt
     THROUGH [0..25) DO
      IF ~CheckBuffer[@outputState.firstBuffer] THEN EXIT;
      REPEAT FINISHED => WatcherNotify[];
      ENDLOOP;
    END;
  
  WatcherNotify: ENTRY PROC =
    BEGIN
    IF CommFlags.doStats THEN Stats.StatIncr[statEtherLostInterrupts];
    SmashCSBs[]; --this will leave output dangling
    END;


  DecapsulateBuffer: PROC [b: Buffer.Buffer] RETURNS [type: Buffer.Type] =
    BEGIN
    bytes: CARDINAL ← 2*b.driver.length;
    IF bytes < encapBytes THEN GOTO Rejected;
    bytes ← bytes - encapBytes;
    SELECT b.encapsulation.ethernetOneType FROM
      ns =>
        BEGIN
	IF bytes < b.ns.pktLength THEN GOTO Rejected;
	type ← ns;
        END;
      pup =>
        BEGIN
	IF bytes < b.pup.pupLength THEN GOTO Rejected;
        type ← pup;
        END;
      translation =>
        BEGIN
	SELECT b.rawWords[0] FROM
          translationRequest => ReceiveRequest[b];
          translationResponse => receiveAck[b];
          ENDCASE => GOTO Rejected;
        type ← processed;
        END;
      ENDCASE => GOTO Rejected;
    EXITS Rejected =>
      BEGIN
      type ← rejected;
      IF CommFlags.driverStats THEN Stats.StatIncr[statPacketsDiscarded];
      END;
    END;

  EncapsulateAndSendPup: PROC[b: Buffer.Buffer, destination: PupTypes.PupHostID] =
    BEGIN
    b.encapsulation ← [
      ethernetOne[
      etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
      translationWorked: TRUE, ethernetOneDest: destination,
      ethernetOneSource: myNetwork.pupHostNumber, ethernetOneType: pup]];
    b.driver.length ← (b.pup.pupLength + 1 + encapBytes)/2;
    SendRawBuffer[b];
    END;  --EncapsulateAndSendPup

  EncapsulateAndSendNS, EncapsulateAndForwardNS: PROC[
    b: Buffer.Buffer, destination: HostNumber] =
    BEGIN
    foundIt: BOOLEAN;
    ethernetAddr: PupTypes.PupHostID;
    [foundIt, ethernetAddr] ← translate[destination];
    IF foundIt THEN
      BEGIN
      b.encapsulation ← [
        ethernetOne[
        etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
        translationWorked: TRUE, ethernetOneDest: ethernetAddr,
        ethernetOneSource: myNetwork.pupHostNumber, ethernetOneType: ns]];
      b.driver.length ← (b.ns.pktLength + 1 + encapBytes)/2;
      END
    ELSE
      BEGIN
      b.encapsulation ← [
        ethernetOne[
        etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
        translationWorked: FALSE, ethernetOneDest:, ethernetOneSource:,
        ethernetOneType:]];
      END;
    SendRawBuffer[b];
    END;  --EncapsulateAndSendNS, EncapsulateAndForwardNS

  ForwardPup: PROC[b: Buffer.Buffer, destination: PupTypes.PupHostID]
    RETURNS [PupTypes.PupErrorCode] =
    {EncapsulateAndSendPup[b, destination]; RETURN[noErrorPupErrorCode]};

  SendRawBuffer: ENTRY PROC[b: Buffer.Buffer] =
    BEGIN
    IF watcherState.pleaseStop THEN Driver.Glitch[DriverNotActive];
    IF ~b.encapsulation.translationWorked THEN
      BEGIN Driver.PutOnGlobalDoneQueue[b]; RETURN; END;
    IF ~hearSelf
      AND
        (b.encapsulation.ethernetOneDest = myNetwork.pupHostNumber
          OR b.encapsulation.ethernetOneDest = PupTypes.allHosts) THEN
      BEGIN  --sending to ourself, copy it over since we can't hear it
      copy: Buffer.Buffer ← Driver.GetInputBuffer[];
      IF copy # NIL THEN
        BEGIN
        Inline.LongCOPY[
          from: @b.encapsulation + encapOffset,
          nwords: b.driver.length,
          to: @copy.encapsulation + encapOffset];
        copy.driver ← b.driver;
        copy.network ← LONG[@myNetwork];  --LONG because of Mokelumne compiler bug
        IF CommFlags.doStats THEN Stats.StatIncr[statEtherPacketsLocal];
        IF CommFlags.doStats THEN Stats.StatBump[statEtherWordsLocal, b.driver.length];
        Driver.PutOnGlobalInputQueue[copy];
        END
      ELSE IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
      END;
    SendBufferInternal[b];
    END;

  SendBufferInternal: INTERNAL PROC[b: Buffer.Buffer] =
    BEGIN
    b.driver.faceStatus ← ethernetOne[pending];
    b.next ← NIL;
    UNTIL (b.driver.iocb ← iocbState.free) # NIL DO
      IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait];
      WAIT iocbState.wait;
      ENDLOOP;
    iocbState.free ← iocbState.free.next;
    QueueOutput[
      ether, @b.encapsulation + encapOffset, b.driver.length,
      b.driver.iocb];
    IF CommFlags.doStats THEN Stats.StatIncr[statEtherPacketsSent];
    IF CommFlags.doStats THEN Stats.StatBump[statEtherWordsSent, b.driver.length];
    IF outputState.firstBuffer = NIL THEN
      BEGIN
      outputState.firstBuffer ← b;
      outputState.timeSendDone ← System.GetClockPulses[];
      END
    ELSE outputState.lastBuffer.next ← b;
    outputState.lastBuffer ← b;
    END;

  --for changing the number of buffers while running

  numberOfExtraBuffer: CARDINAL = 2;
  --this should only be called from Boss 
  --No MONITOR PROTECTION here.
  MaybeChangeNumberOfInputBuffers: PROC[increaseBuffers: BOOLEAN] =
    BEGIN
    IF increaseBuffers THEN
      BEGIN
      IF inputState.access = NIL THEN
        inputState.access ← Buffer.MakePool[0, numberOfExtraBuffer];
      IF inputState.queueAllowed < numberOfExtraBuffer THEN
	inputState.queueAllowed ← myNetwork.buffers ←
	  myNetwork.buffers + numberOfExtraBuffer;
      END
    ELSE
      BEGIN
      IF inputState.access # NIL THEN
        {Buffer.DestroyPool[inputState.access]; inputState.access ← NIL};
      IF inputState.queueAllowed >= numberOfExtraBuffer THEN
	inputState.queueAllowed ← myNetwork.buffers ←
	  myNetwork.buffers - numberOfExtraBuffer;
      END;
    END;

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

  AdjustLengtoOfD0EthernetInputQueue: PUBLIC PROC[n: CARDINAL] =
    BEGIN inputState.queueLength ← n; END;

  CreateDefaultEthernetOneDrivers: PUBLIC PROC RETURNS [BOOLEAN] =
    BEGIN
    deviceNumber: CARDINAL ← 0;
    etherDevice: DeviceHandle ← GetNextDevice[nullDeviceHandle];
    IF System.switches['<] = down THEN RETURN[FALSE];
    IF etherDevice = nullDeviceHandle THEN RETURN[FALSE];
    WHILE etherDevice # nullDeviceHandle DO
      CreateAnEthernetOneDriver[etherDevice, deviceNumber];
      etherDevice ← GetNextDevice[etherDevice];
      deviceNumber ← deviceNumber + 1;
      ENDLOOP;
    RETURN[TRUE];
    END;

  CreateAnEthernetOneDriver: PROC[
    etherDevice: DeviceHandle, deviceNumber: CARDINAL] =
    BEGIN
    IF deviceNumber # 0 THEN
      BEGIN
      him: LONG POINTER TO FRAME[EthernetOneDriver] ← NEW EthernetOneDriver;
      START him;  --so he'll initialize the procedure
      him.setupEthernetOneDriver[etherDevice];
      END
    ELSE SetupEthernetOneDriver[etherDevice];
    END;

  first: BOOLEAN ← TRUE;
  firstPool: Buffer.AccessHandle;
  SetupEthernetOneDriver: PROC[etherDevice: DeviceHandle] =
    BEGIN
    host: Environment.Byte;
    ether ← etherDevice;
    [, host] ← GetEthernet1Address[ether];
    watcherState.pleaseStop ← TRUE;
    myNetwork.buffers ← inputState.queueLength ← 1;
    Driver.AddDeviceToChain[@myNetwork];
    IF TRUE THEN
      BEGIN  -- Startup BUGs in Boss
      firstPool ← Buffer.MakePool[0, myNetwork.buffers];
      END;
    IF CommFlags.doStats OR CommFlags.driverStats THEN
      BEGIN
      myNetwork.statsLevel0 ← @etherStats;
      etherStats ← [];
      END;
    END;

  ActivateDriver: PROC =
    BEGIN
    b: Buffer.Buffer;
    net, host: Environment.Byte;
    iocbs: CARDINAL = (myNetwork.buffers + numberOfExtraBuffer) * 2;
    size: CARDINAL = Inline.BITAND[(controlBlockSize + 3), 0FFFCH];
    IF ~watcherState.pleaseStop THEN Driver.Glitch[DriverAlreadyActive];
    seconds.forty ← System.MicrosecondsToPulses[40000000];
    seconds.fiveHalf ← System.MicrosecondsToPulses[2500000];
    seconds.one ← System.MicrosecondsToPulses[1000000];
    [net, host] ← GetEthernet1Address[ether];
    getGarbage ← watcherState.pleaseStop ← FALSE;
    TurnOff[ether];
    AddCleanup[ether];
    inputState.access ← NIL;
    inputState.queueLength ← 0;
    inputState.queueAllowed ← myNetwork.buffers;
    inputState.firstBuffer ← inputState.lastBuffer ← NIL;
    outputState.firstBuffer ← outputState.lastBuffer ← NIL;
    myEar ← myNetwork.pupHostNumber ← host;
    IF controlBlockSize = 0 THEN Driver.Glitch[IOCBSizeIsZero];
    iocbState.free ← NIL;
    Process.EnableAborts[@iocbState.wait];
    Process.DisableTimeout[@iocbState.wait];
    iocbState.first ← iocbState.free ← CommUtil.AllocateIocbs[size * iocbs];
    FOR i: CARDINAL IN[0..iocbs - 1) DO
      iocbState.first ← iocbState.first.next ←
        iocbState.first + size;
      REPEAT FINISHED =>
        {iocbState.first.next ← NIL; iocbState.first ← iocbState.free};
      ENDLOOP; 
    THROUGH [0..myNetwork.buffers) DO
      IF (b ← Driver.GetInputBuffer[TRUE]) # NIL THEN
        BEGIN
	IF iocbState.free = NIL THEN Driver.Glitch[LostAllIocbs];
	b.driver.iocb ← iocbState.free;
	iocbState.free ← iocbState.free.next;
        inputState.queueLength ← inputState.queueLength + 1;
        IF CommFlags.doDebug
          AND Inline.BITAND[Inline.LowHalf[
	    @b.encapsulation + encapOffset], 3] # 0 THEN
          Driver.Glitch[BufferMustBeAlmostQuadWordAligned];
        IF CommFlags.doDebug
          AND Inline.BITAND[Inline.LowHalf[b.driver.iocb], 3] # 0 THEN
          Driver.Glitch[IOCBMustBeQuadWordAligned];
        IF CommFlags.doDebug AND Inline.HighHalf[b.driver.iocb] # 0 THEN
          Driver.Glitch[IOCBMustBeInFirstMDS];
        b.driver.faceStatus ← ethernetOne[pending];
        IF inputState.firstBuffer = NIL THEN inputState.firstBuffer ← b;
        IF inputState.lastBuffer # NIL THEN inputState.lastBuffer.next ← b;
        inputState.lastBuffer ← b;
        END;
      ENDLOOP;
    [cv: inputState.inWait, mask: inputState.mask] ←
      SpecialRuntime.AllocateNakedCondition[];
    Process.DisableTimeout[inputState.inWait];
    Process.EnableAborts[inputState.inWait];
    [cv: outputState.outWait, mask: outputState.mask] ←
      SpecialRuntime.AllocateNakedCondition[];
    Process.DisableTimeout[outputState.outWait];
    Process.EnableAborts[outputState.outWait];
    SmashCSBs[];
    BEGIN
    priority: Process.Priority ← Process.GetPriority[];
    Process.SetPriority[ProcessPriorities.priorityIOHigh];
    inputState.process ← FORK InInterrupt[];
    outputState.process ← FORK OutInterrupt[];
    Process.SetPriority[priority];
    END;
    Process.EnableAborts[@watcherState.timer];
    Process.SetTimeout[@watcherState.timer, Process.SecondsToTicks[1]];
    watcherState.process ← FORK Watcher[];
    CreateCache[];
    END;

  SetEthernetOneListener: PUBLIC ENTRY PROC[
    physicalOrder: CARDINAL, newHostNumber: CARDINAL]
    RETURNS [success: BOOLEAN] =
    BEGIN
    him: LONG POINTER TO FRAME[EthernetOneDriver];
    network: Network ← GetNthDeviceLikeMe[physicalOrder];
    IF network = NIL THEN RETURN[FALSE];
    him ← LOOPHOLE[Runtime.GlobalFrame[LOOPHOLE[network.sendRawBuffer]]];
    him.ethernetOneListenForHost[newHostNumber];
    RETURN[TRUE];
    END;

  EthernetOneListenForHost: PROC[newHostNumber: CARDINAL] =
    BEGIN myEar ← newHostNumber; SmashCSBs[]; END;

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

  SetEthernetOneCollectGarbageToo: PUBLIC ENTRY PROC[
    physicalOrder: CARDINAL, collectGarbage: BOOLEAN]
    RETURNS [success: BOOLEAN] =
    BEGIN
    him: LONG POINTER TO FRAME[EthernetOneDriver];
    network: Network ← GetNthDeviceLikeMe[physicalOrder];
    IF network = NIL THEN RETURN[FALSE];
    him ← LOOPHOLE[Runtime.GlobalFrame[LOOPHOLE[network.sendRawBuffer]]];
    him.getGarbage ← collectGarbage;
    RETURN[TRUE];
    END;

  SmashCSBs: PROC =
    BEGIN
    b: Buffer.Buffer;
    TurnOn[ether, myEar, inputState.mask, outputState.mask, globalStatePtr];
    inputState.lastMissed ← GetPacketsMissed[ether];
    FOR b ← inputState.firstBuffer, b.next UNTIL b = NIL DO
      QueueInput[
        ether, @b.encapsulation + encapOffset,
        b.driver.length - encapOffset, b.driver.iocb];
      ENDLOOP;
    inputState.timeLastRecv ← System.GetClockPulses[];
    END;

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

  DeactivateDriver: PROC =
    BEGIN
    b: Buffer.Buffer;
    IF watcherState.pleaseStop THEN Driver.Glitch[DriverNotActive];
    watcherState.pleaseStop ← TRUE;
    Process.Abort[inputState.process]; JOIN inputState.process;
    Process.Abort[outputState.process]; JOIN outputState.process;
    Process.Abort[watcherState.process]; JOIN watcherState.process;
    TurnOff[ether];
    SpecialRuntime.DeallocateNakedCondition[inputState.inWait];
    SpecialRuntime.DeallocateNakedCondition[outputState.outWait];
    inputState.inWait ← outputState.outWait ← NIL;
    MaybeChangeNumberOfInputBuffers[FALSE];
    IF first THEN
      BEGIN
      first ← FALSE;
      Buffer.DestroyPool[firstPool];
      END;
    RemoveCleanup[ether];
    UNTIL inputState.firstBuffer = NIL DO
      b ← inputState.firstBuffer;
      inputState.firstBuffer ← b.next;
      Driver.ReturnFreeBuffer[b];
      ENDLOOP;
    UNTIL outputState.firstBuffer = NIL DO
      b ← outputState.firstBuffer;
      outputState.firstBuffer ← b.next;
      Driver.PutOnGlobalDoneQueue[b];
      ENDLOOP;
    CommUtil.FreeIocbs[iocbState.first];
    iocbState.free ← iocbState.first ← NIL; 
    DeleteCache[];
    END;

  --* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * 
  --Ugly thing to take care of handling the Ethernet1 (it uses 8 bit addresses).
  --This will go away when NS Communications stops using Ethernet1's.
  --* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
  --types

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

  CacheEntry: TYPE = LONG POINTER TO CacheObject;

  CacheObject: TYPE = MACHINE DEPENDENT RECORD [
    nextLink: CacheEntry,
    addressPair: AddressPair,
    tries: CARDINAL,
    timeStamp: System.Pulses,
    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;
  depth: CARDINAL;  --debugging
  retryPulses: System.Pulses ← System.MicrosecondsToPulses[2000000];  --two seconds
  deactivatePulses: System.Pulses ← System.MicrosecondsToPulses[180000000];  --three minutes
  cacheEvent: CONDITION;
  demonRunning: BOOLEAN;
  receiveAck: PROC[b: Buffer.Buffer] ← InactiveReceiveAck;
  translate: PROC[HostNumber] RETURNS [BOOLEAN, PupTypes.PupHostID] ←
    InactiveTranslate;
  etherHost: PupTypes.PupHostID;
  nsHost: HostNumber;

  --interface
  CreateCache: ENTRY PROC = INLINE
    BEGIN
    host: Environment.Byte;
    cacheQueueHead ← broadCastPairEntry ← myAddressPairEntry ← NIL;
    translate ← InactiveTranslate;
    receiveAck ← InactiveReceiveAck;
    demonRunning ← FALSE;
    [, host] ← GetEthernet1Address[ether];
    etherHost ← [host];
    nsHost ← SpecialSystem.GetProcessorID[];
    END;

  StartCache: ENTRY PROC = INLINE
    BEGIN
    nsHost: HostNumber ← SpecialSystem.GetProcessorID[];
    translate ← Translate;
    receiveAck ← ReceiveAck;
    Process.SetTimeout[@cacheEvent, Process.SecondsToTicks[1]];
    broadCastPairEntry ← AddAddressPair[[System.broadcastHostNumber, PupTypes.allHosts, 0]];
    myAddressPairEntry ← AddAddressPair[[nsHost, etherHost, 0]];
    demonRunning ← TRUE;
    Process.Detach[FORK Demon[]];
    END;

  DeleteCache: PROC = INLINE
    BEGIN
    e: CacheEntry;

    DeleteCacheLocked: ENTRY PROC = 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;
      CommHeap.FreeNode[p: e];
      ENDLOOP;
    END;

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

  AddEntry: INTERNAL PROC[entry: CacheEntry] =
    {entry.nextLink ← cacheQueueHead; cacheQueueHead ← entry};

  RemoveEntry: INTERNAL PROC[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: PROC[nsAddr: HostNumber]
    RETURNS [foundIt: BOOLEAN, ethernet1Addr: PupTypes.PupHostID] =
    BEGIN StartCache[]; [foundIt, ethernet1Addr] ← Translate[nsAddr]; END;

  Translate: ENTRY PROC[nsAddr: HostNumber]
    RETURNS [foundIt: BOOLEAN, ethernet1Addr: PupTypes.PupHostID] =
    BEGIN
    e: CacheEntry;
    foundIt ← FALSE;
    IF (e ← FindEntry[nsAddr]) # NIL THEN
      BEGIN
      IF e # cacheQueueHead THEN  --put e at the head of the queue
        BEGIN
        IF CommFlags.doStats THEN Stats.StatBump[cacheDepth, depth];
        RemoveEntry[e];
        AddEntry[e];
        END;
      SELECT e.status FROM
        active =>
          BEGIN
          foundIt ← TRUE;
          ethernet1Addr ← e.addressPair.ethernet1Addr;
          e.timeStamp ← System.GetClockPulses[];
          END;
        zombie =>
          BEGIN
          e.status ← new;
          e.tries ← 0;
          e.timeStamp ← System.GetClockPulses[];
          NOTIFY cacheEvent;
          END;
        ENDCASE => NULL;
      END  --of found it
    ELSE  --entry not found, so add a new one
      BEGIN
      IF CommFlags.doStats THEN Stats.StatIncr[cacheFault];
      e ← CommHeap.MakeNode[n: SIZE[CacheObject]];
      e.status ← new;
      e.tries ← 0;
      e.timeStamp ← System.GetClockPulses[];
      e.addressPair ← [nsAddr: nsAddr, ethernet1Addr:, filler:];
      AddEntry[e];
      NOTIFY cacheEvent;
      END;
    END;

  --assume protection by lock

  AddAddressPair: INTERNAL PROC[aP: AddressPair] RETURNS [e: CacheEntry] =
    BEGIN
    e ← FindEntry[aP.nsAddr];
    SELECT e FROM
      (NIL) => {e ← CommHeap.MakeNode[n: SIZE[CacheObject]]; AddEntry[e]};
      (broadCastPairEntry), (myAddressPairEntry) => RETURN;
      ENDCASE;
    e.addressPair ← aP;
    e.status ← active;
    e.timeStamp ← System.GetClockPulses[];
    END;

  --assume protection by lock

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


  --locks

  Demon: ENTRY PROC =
    BEGIN
    demonRunning ← TRUE;
    Process.SetPriority[ProcessPriorities.priorityIOHigh];

    UNTIL watcherState.pleaseStop DO
      ENABLE ABORTED => EXIT;
      pendingEntries: BOOLEAN ← FALSE;
      e: CacheEntry;
      WAIT cacheEvent;
      e ← cacheQueueHead;
      WHILE (e # NIL) DO
        age: System.Pulses ← [System.GetClockPulses[] - e.timeStamp];
        nextE: CacheEntry ← e.nextLink;
        SELECT e.status FROM
          active, zombie => { IF age > deactivatePulses THEN DeallocateEntry[e]};
          pending =>
            BEGIN
            pendingEntries ← TRUE;
            IF age > retryPulses THEN
              BEGIN
              e.tries ← e.tries + 1;
              IF e.tries > retryLimit THEN
                BEGIN
                e.status ← zombie;
                IF CommFlags.doStats THEN Stats.StatIncr[unsuccessfulTranslation];
                END
              ELSE
                BEGIN
                IF CommFlags.doStats THEN Stats.StatIncr[translationRetries];
                SendRequest[e];
                e.timeStamp ← System.GetClockPulses[];
                END;
              END;
            END;
          new =>
            BEGIN
            pendingEntries ← TRUE;
            SendRequest[e];
            e.status ← pending;
            e.timeStamp ← System.GetClockPulses[];
            END;
          ENDCASE => ERROR;
        e ← nextE;
        ENDLOOP;  --end of queue entries loop
      IF pendingEntries THEN
        Process.SetTimeout[@cacheEvent, Process.SecondsToTicks[1]]
      ELSE Process.SetTimeout[@cacheEvent, Process.SecondsToTicks[60*5]];
      ENDLOOP;  --end of infinite loop
    receiveAck ← InactiveReceiveAck;
    translate ← InactiveTranslate;
    BEGIN
    e, nextE: CacheEntry;
    e ← cacheQueueHead;
    cacheQueueHead ← myAddressPairEntry ← broadCastPairEntry ← NIL;
    WHILE e # NIL DO
      nextE ← e.nextLink; CommHeap.FreeNode[p: e]; e ← nextE; ENDLOOP;
      END;
    demonRunning ← FALSE;
    END;


  --assume locked

  SendRequest: INTERNAL PROC[e: CacheEntry] =
    BEGIN
    b: Buffer.Buffer;
    request: LONG POINTER TO AddressPair;
    IF (b ← Driver.GetInputBuffer[FALSE]) # NIL THEN
      BEGIN
      --broadcast the trnslation request
      b.encapsulation ← [
        ethernetOne[
        etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
        translationWorked:, ethernetOneDest: PupTypes.allHosts,
        ethernetOneSource: myNetwork.pupHostNumber, ethernetOneType: translation]];
      b.driver.length ← (1 + encapBytes)/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;
      --send it
      SendBufferInternal[b];
      END;
    END;

  --locks
  --we now own buffer b

  InactiveReceiveAck: PROC[b: Buffer.Buffer] = {b.requeueProcedure[b]};

  ReceiveAck: ENTRY PROC[b: Buffer.Buffer] =
    BEGIN
    IF b.encapsulation.ethernetOneDest =
      myAddressPairEntry.addressPair.ethernet1Addr 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 PROC[b: Buffer.Buffer] =
    BEGIN
    request, requesterAddr: LONG POINTER TO AddressPair;
    request ← LOOPHOLE[@b.rawWords[1]];
    IF request.nsAddr = nsHost THEN
      BEGIN
      --since the requester is probably going to talk to us, add his address before we take a fault
      requesterAddr ← request + SIZE[AddressPair];
      [] ← AddAddressPair[requesterAddr↑];
      IF CommFlags.doStats THEN Stats.StatIncr[requestsForMe];
      request.ethernet1Addr ← etherHost;
      SendAck[request↑, b.encapsulation.ethernetOneSource, b];  --we lose ownership of b

      END
    ELSE b.requeueProcedure[b];
    END;

  --assume protection by lock
  --we now own buffer b

  SendAck: INTERNAL PROC[
    aP: AddressPair, to: DriverTypes.Byte, b: Buffer.Buffer] = INLINE
    BEGIN
    response: LONG POINTER TO AddressPair;
    IF b # NIL THEN
      BEGIN
      b.encapsulation ← [
        ethernetOne[
        etherSpare1:, etherSpare2:, etherSpare3:, etherSpare4:, etherSpare5:,
        translationWorked:, ethernetOneDest: to,
        ethernetOneSource: myNetwork.pupHostNumber, ethernetOneType: translation]];
      b.driver.length ← (1 + encapBytes)/2 + SIZE[AddressPair] + 1;
      b.rawWords[0] ← translationResponse;
      response ← LOOPHOLE[@b.rawWords[1]];
      response↑ ← aP;
      --send it
      SendBufferInternal[b];
      END;
    END;

  --* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
  --End of Ethernet1 uglyness 
  --* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * 


  --initialization

  setupEthernetOneDriver ← SetupEthernetOneDriver;  --for multi instances
  ethernetOneListenForHost ← EthernetOneListenForHost;

  END.  --EthernetOneDriver