-- File: EthernetDriver.mesa - last edit:
-- AOF                 17-Feb-88 15:25:51
-- MI                   1-Aug-86 16:03:13
-- SMA                 21-May-86 15:46:20
-- Copyright (C) 1984, 1985, 1986, 1987, 1988 by Xerox Corporation. All rights reserved. 

DIRECTORY
  Buffer USING [
    AccessHandle, Buffer, DataBytesPerRawBuffer, Dequeue,
    DestroyPool, Enqueue, MakePool, QueueInitialize, QueueObject],
  CommFlags USING [doDebug, doStats, driverStats],
  CommPriorities USING [driver],
  CommSwitches USING [noEthernet],
  CommUtil USING [AllocateIocbs, FreeIocbs],
  Driver USING [
    AddDeviceToChain, Glitch, GetDeviceChain, GetInputBuffer, Device,
    DeviceObject, ChangeNumberOfInputBuffers, PutOnGlobalDoneQueue,
    PutOnGlobalInputQueue, RemoveDeviceFromChain, ReturnFreeBuffer],
  Environment USING [bytesPerWord],
  EthernetFace USING [
    AddCleanup, controlBlockSize, DeviceHandle, GetPacketLength, GetRetries,
    GetStatus, GetPacketsMissed, GlobalStatePtr, hearSelf, QueueInput,
    GetNextDevice, nullDeviceHandle,  QueueOutput, RemoveCleanup, Status,
    TurnOn, TurnOff, globalStateSize],
  EthernetDriverFriends USING [EtherStatsInfo],
  HostNumbers USING [IsMulticastID],
  IEEE8023 USING [
    Encapsulation, ethernetBroadcastHost, minWordsPerEthernetPacket,
    EncapObject, EthernetCRC, maxBytesPerEthernetPacket],
  Inline USING [LongCOPY],
  Stats USING [StatBump, StatIncr, StatCounterIndex],
  PrincOpsMinus USING [NewSelf],
  Process USING [
    Abort, DisableAborts, DisableTimeout, EnableAborts, GetPriority,
    MsecToTicks, Priority, SetPriority, SetTimeout],
  ProcessorFace USING [SetMP],
  ResidentHeap USING [MakeNode, FreeNode],
  Runtime USING [GlobalFrame, SelfDestruct],
  SpecialCommunication USING [],
  SpecialRuntime USING [AllocateNakedCondition, DeallocateNakedCondition],
  SpecialSystem USING [
    ProcessorID, HostNumber, GetProcessorID, nullHostNumber],
  System USING [
    GetClockPulses, Pulses, MicrosecondsToPulses, switches--['>]--],
  Zone USING [Status];

EthernetDriver: MONITOR
  IMPORTS
    Buffer, CommUtil, Driver, Stats, EthernetFace, Inline, HostNumbers,
    PrincOpsMinus, Process, ProcessorFace, ResidentHeap, Runtime, SpecialRuntime,
    System, SpecialSystem
  EXPORTS Buffer, IEEE8023, SpecialCommunication, System =
  BEGIN

  --EXPORTed TYPEs
  Device: PUBLIC TYPE = Driver.Device;  --to Buffer
  HostNumber: PUBLIC <<System>> TYPE = SpecialSystem.HostNumber;

  ether: EthernetFace.DeviceHandle;
  myEar: HostNumber;  --address I listen for
  bpw: NATURAL = Environment.bytesPerWord;
  localDevice: Device;  --cache this to get around compiler
  me: SpecialSystem.ProcessorID;  --my real (hardware) address
  all: SpecialSystem.HostNumber = IEEE8023.ethernetBroadcastHost;
  getGarbage: BOOLEAN ← FALSE; --when true, we deliver any packet
  globalStatePtr: EthernetFace.GlobalStatePtr; --Allocate space if needed
  setupEthernetDriver: PROC[etherDevice: EthernetFace.DeviceHandle];

  inputState: RECORD[
    mask: WORD,
    process: PROCESS,
    lastMissed: CARDINAL,
    q: Buffer.QueueObject,
    access: Buffer.AccessHandle,
    timeLastRecv: LONG CARDINAL,
    inWait: LONG POINTER TO CONDITION,
    queueAllowed, extraBuffers: NATURAL];
  
  outputState: RECORD[
    process: PROCESS,
    mask: WORD,
    q: Buffer.QueueObject,
    outWait: LONG POINTER TO CONDITION,
    timeSendDone: LONG CARDINAL];

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

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

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

  --THE NETWORK OBJECT FOR THIS DRIVER
  myDevice: Driver.DeviceObject ←
    [matrix: NIL, sendRawBuffer: SendRawBuffer,
    activateDriver: ActivateDriver, deactivateDriver: DeactivateDriver,
    deleteDriver: DeleteDriver, buffers:, device: ethernet,
    changeNumberOfInputBuffers: MaybeChangeNumberOfInputBuffers,
    receiveBufferLen: 1500,  -- This is the DLL size in 'bytes'.
    alive: TRUE, index:, next: NIL, lineSpeed: 10000, lineNumber: 0, stats: NIL];

  DriverNotActive: ERROR = CODE;
  DriverAlreadyActive: ERROR = CODE;
  LinkLayerNotMod4Minus1: ERROR = CODE;
  IOCBSizeIsZero: ERROR = CODE;
  LostAllIocbs: ERROR = CODE;
  LostSomeIocbs: ERROR = CODE;
  NilIocbInBuffer: ERROR = CODE;
  OverlayingIocb: ERROR = CODE;
  ResidentZoneTrouble: ERROR = CODE;
  BadHostID: ERROR = CODE;
  PacketTooLarge: ERROR = CODE;


  numberOfExtraBuffer: CARDINAL = 4;
  etherStats: EthernetDriverFriends.EtherStatsInfo;
  maxEthernetWords: NATURAL = (IEEE8023.maxBytesPerEthernetPacket / bpw) -
    SIZE[IEEE8023.EthernetCRC];

  <<
  The physical overhead is the number of bytes used by the MAC layer to
  encapsulate a Network Protocol Data Unit. This physical overhead includes
  802.2 encapsulation.
  >>
  physOverhead: NATURAL = bpw *
    (SIZE[IEEE8023.EncapObject] + SIZE[IEEE8023.EthernetCRC]);

  <<
  This driver starts the reception of physical frame offset into the space
  reserved by the buffer manager for the LLC. This is so frames received
  using one LLC (eg. Ethernet) can be encapsulated using another LLC (eg.
  IEEE 802.2) without wiping out the FixedOverhead portion of the buffer.
  The offset is based on private knowledge that this driver shouldn't
  know about, the lengths of the various encapsulations. The longest know
  to date is an old Ethernet packet encapsulated using the IEEE 802.2
  extended type field. That is SIZE[IEEE8023.EncapObject] words long.
  The shortest is Ethernet.
  errorCheck: NATURAL[22..1518] = Buffer.dataLinkReserve;  -- this must be true
  >>
  offsetToDataUnit: NATURAL =
    SIZE[IEEE8023.EncapObject] - SIZE[ethernet IEEE8023.EncapObject];  --words

  checking: BOOLEAN ← CommFlags.doDebug;
  SanityCheck: --INTERNAL-- PROC = --INLINE--
    BEGIN
    IF CommFlags.doDebug THEN
      BEGIN
      found: INTEGER ← 0;
      IF ~checking THEN RETURN;
      FOR link: FreeIocb ← iocbState.free, link.next UNTIL link = NIL DO
	found ← found + 1;
	ENDLOOP;
      FOR b: Buffer.Buffer ← inputState.q.first, b.fo.next UNTIL b = NIL DO
	IF b.fo.driver.iocb # NIL THEN found ← found + 1
	ELSE Driver.Glitch[NilIocbInBuffer];
	ENDLOOP;
      FOR b: Buffer.Buffer ← outputState.q.first, b.fo.next UNTIL b = NIL DO
	IF b.fo.driver.iocb # NIL THEN found ← found + 1
	ELSE Driver.Glitch[NilIocbInBuffer];
	ENDLOOP;
      IF found # iocbState.avail THEN Driver.Glitch[LostSomeIocbs];
      END;
    END;  --SanityCheck

    GetBufferAndIocb: INTERNAL PROC[] RETURNS[b: Buffer.Buffer] =
      BEGIN
      receiveLength: NATURAL = myDevice.receiveBufferLen + physOverhead;
      IF CommFlags.doDebug THEN SanityCheck[];
      SELECT TRUE FROM
	(iocbState.free = NIL) =>
	  {IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait]; RETURN[NIL]};
	((b ← Driver.GetInputBuffer[FALSE, receiveLength]) = NIL) => RETURN;
	ENDCASE;
      IF CommFlags.doDebug AND (b.fo.driver.iocb # NIL) THEN
	Driver.Glitch[OverlayingIocb];
      b.fo.driver.iocb ← iocbState.free;
      iocbState.free ← iocbState.free.next;
      b.fo.driver.length ← receiveLength;
      b.fo.driver.faceStatus ← ethernet[pending];
      END;  --GetBufferAndIocb

  GetBufferAndIocbEntry: ENTRY PROC[] RETURNS[b: Buffer.Buffer] = INLINE
    {RETURN GetBufferAndIocb[]};  --GetBufferAndIocbEntry

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

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

    DO
      ENABLE ABORTED => {inputState.process ← NIL; EXIT};

      IF inputState.q.length = 0 THEN
        BEGIN
	<<
	If the queue length was previously 0, then we can wait for the first
	interrupt.  'inputState.inWait' has no timeout, so the process should
	only wake when a packet is available.  If the buffer is still pending,
	something is amiss.
	>>
	WHILE inputState.q.length = 0 DO WAIT inputState.inWait; ENDLOOP;
	status ← EthernetFace.GetStatus[inputState.q.first.fo.driver.iocb];
	IF CommFlags.doStats AND status # pending THEN
	  Stats.StatIncr[statEtherInterruptDuringInterrupt];
	END
      ELSE status ← EthernetFace.GetStatus[inputState.q.first.fo.driver.iocb];

      UNTIL status # pending DO
	WAIT inputState.inWait;
	status ← EthernetFace.GetStatus[inputState.q.first.fo.driver.iocb];
	IF CommFlags.doStats AND status = pending
	  THEN Stats.StatIncr[statEtherMissingStatus];
	ENDLOOP;
      this ← Buffer.Dequeue[@inputState.q];
      words ← EthernetFace.GetPacketLength[this.fo.driver.iocb];
      IF words < IEEE8023.minWordsPerEthernetPacket THEN status ← otherError;
      IF words > maxEthernetWords THEN status ← packetTooLong;
      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
	    badAlignmentButOkCrc =>
	      BEGIN
	      acceptBuffer ← TRUE;  --we're going to keep this one
	      IF CommFlags.driverStats THEN etherStats.badAlignmentButOkCrc ←
		etherStats.badAlignmentButOkCrc + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedNot16];
	      END;
	    packetTooLong =>
	      BEGIN
	      IF CommFlags.driverStats
		THEN etherStats.packetTooLong ← etherStats.packetTooLong + 1;
	      IF CommFlags.doStats THEN Stats.StatIncr[statEtherReceivedTooLong];
	      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;
      SELECT TRUE FROM
        (acceptBuffer) =>
	  BEGIN
	  inputState.timeLastRecv ← this.fo.time ← System.GetClockPulses[];
	  this.fo.driver.faceStatus ← ethernet[status];
	  this.fo.network ← localDevice;
	  this.linkLayer ← [(this.linkLayer.blockPointer + offsetToDataUnit),
	    0, (this.fo.driver.length ← words * bpw)];  --convert length to bytes
	  IF CommFlags.driverStats THEN
	    BEGIN
	    etherStats.packetsRecv ← etherStats.packetsRecv + 1;
	    etherStats.wordsRecv ← etherStats.wordsRecv + words;
	    END;
	  IF CommFlags.doStats THEN
	    BEGIN
	    Stats.StatIncr[statEtherPacketsReceived];
	    Stats.StatBump[statEtherWordsReceived, words];
	    END;
	  FreeBufferAndIocb[Driver.PutOnGlobalInputQueue, this];  --good input
	  IF (new ← GetBufferAndIocb[]) = NIL THEN
	    BEGIN
	    IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
	    NOTIFY watcherState.timer;  --couldn't or didn't want a new buffer
	    LOOP;  --there's nothing left to do here
	    END;
	  END;
	(Buffer.DataBytesPerRawBuffer[this] < myDevice.receiveBufferLen) =>
	  BEGIN
	  FreeBufferAndIocb[Driver.ReturnFreeBuffer, this];  --can't reuse
	  IF (new ← GetBufferAndIocb[]) = NIL THEN
	    BEGIN
	    IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
	    NOTIFY watcherState.timer;  --couldn't or didn't want a new buffer
	    LOOP;  --there's nothing left to do here
	    END;
	  END;
	ENDCASE => {new ← this; new.fo.next ← NIL}; --recycle this buffer
      --add new buffer to end of input chain
      new.fo.driver.faceStatus ← ethernet[pending];
      EthernetFace.QueueInput[
	ether, (new.linkLayer.blockPointer + offsetToDataUnit),
	(new.fo.driver.length / bpw) - offsetToDataUnit, new.fo.driver.iocb];
      Buffer.Enqueue[@inputState.q, new];
      ENDLOOP;
    END;  --InInterrupt

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

    DO
      ENABLE ABORTED => {outputState.process ← NIL; EXIT};
      --UNTIL 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
	  (outputState.q.length = 0) => NULL;  --any output queued?
	  --this one's complete
	  ((status ← EthernetFace.GetStatus[
	    outputState.q.first.fo.driver.iocb]) # pending) => EXIT;
	  --then why did we interrupt??
	  ENDCASE => IF CommFlags.doStats THEN
	    Stats.StatIncr[statEtherMissingStatus];
	WAIT outputState.outWait;
	ENDLOOP;

      b ← Buffer.Dequeue[@outputState.q];  --take it out of queue
      b.fo.driver.faceStatus ← ethernet[status];  --and record the status
      outputState.timeSendDone ← System.GetClockPulses[];  --still transmiting

      IF status = ok THEN
	BEGIN
	IF CommFlags.doStats OR CommFlags.driverStats THEN
	  BEGIN
	  tries: CARDINAL = EthernetFace.GetRetries[b.fo.driver.iocb];
	  IF CommFlags.driverStats THEN
	    BEGIN
	    etherStats.packetsSent ← etherStats.packetsSent + 1;
	    etherStats.wordsSent ← etherStats.wordsSent +
	      b.fo.driver.length / bpw;
	    etherStats.loadTable[tries] ← etherStats.loadTable[tries] + 1;
	    END;
	  IF CommFlags.doStats AND tries # 0 THEN
	    Stats.StatIncr[LOOPHOLE[
	      Stats.StatCounterIndex[statEtherSendsCollision1].ORD + 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
      FreeBufferAndIocb[Driver.PutOnGlobalDoneQueue, b];
      ENDLOOP;
    END;  --OutInterrupt

  Watcher: PROC =
    BEGIN

    CheckQueues: ENTRY PROC = INLINE
      BEGIN

      enterTime ← System.GetClockPulses[];  --record time at start

      --STUCK OUTPUT
      SELECT TRUE FROM
        (outputState.q.length = 0) => NULL;
	((enterTime - outputState.timeSendDone) > seconds.fiveHalf) =>
	  BEGIN
	  IF CommFlags.doStats THEN Stats.StatIncr[statPacketsStuckInOutput];
	  IF CommFlags.driverStats THEN
	     etherStats.stuckOutput ← etherStats.stuckOutput + 1;
	  outputState.timeSendDone ← enterTime;
	  GOTO smash;
	  END;
	ENDCASE;

      --IDLE INPUT
        IF ((enterTime - inputState.timeLastRecv) > seconds.forty) THEN
	  BEGIN
	  IF CommFlags.doStats THEN Stats.StatIncr[statInputIdle];
	  IF CommFlags.driverStats THEN
	    etherStats.idleInput ← etherStats.idleInput + 1;
	  inputState.timeLastRecv ← enterTime;
	  GOTO smash;
	  END;

      EXITS smash => SmashCSBs[];
      END;  --CheckQueues

    QueueInputOrWait: ENTRY PROC = INLINE
      BEGIN
      ENABLE UNWIND => NULL;
      SELECT TRUE FROM
        (b = NIL) => NULL;  --just WAIT
	(CommFlags.doDebug AND (b.fo.driver.iocb # NIL)) =>
	  Driver.Glitch[OverlayingIocb];
	((b.fo.driver.iocb ← iocbState.free) # NIL) =>
	  BEGIN
	  iocbState.free ← iocbState.free.next;
	  b.fo.driver.faceStatus ← ethernet[pending];
	  -- EthernetFace uses words for degree of 'length'
	  EthernetFace.QueueInput[
	    ether, LOOPHOLE[b.linkLayer.blockPointer + offsetToDataUnit],
	    (bytes / bpw) - offsetToDataUnit, b.fo.driver.iocb];
	  Buffer.Enqueue[@inputState.q, b];
	  IF CommFlags.doDebug THEN SanityCheck[];
	  RETURN;  --and get out of here with b # NIL
	  END;
	ENDCASE =>  --the ENDCASE better be rare!
          BEGIN
	  IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait];
	  Driver.ReturnFreeBuffer[b]; b ← NIL  --give the buffer back (ARGH!!)
	  END;
	WAIT watcherState.timer;  --this is an alternate WAIT

	IF CommFlags.doStats OR CommFlags.driverStats THEN
	  BEGIN
	  lost, missed: CARDINAL;
	  missed ← EthernetFace.GetPacketsMissed[ether];
	  lost ← 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;
      END;  --QueueInputOrWait

    bytes: NATURAL;
    b: Buffer.Buffer;
    enterTime: LONG CARDINAL;
    DO
      ENABLE ABORTED => EXIT;
      --Check for lost interrupts
      IF CheckBuffer[@inputState.q.first] OR
        CheckBuffer[@outputState.q.first] THEN WatchCarefully[];

      CheckQueues[];  --for idle input and stuck output

      WHILE (inputState.q.length < inputState.queueAllowed) DO
        bytes ← myDevice.receiveBufferLen + physOverhead;  --compute length
        --don't lock monitor and wait for a buffer
        b ← Driver.GetInputBuffer[TRUE, bytes];  --use cached length
	QueueInputOrWait[];  -- queue buffer or give a chance to wait
	IF b = NIL THEN EXIT;  --but don't futz around forever
	ENDLOOP;

      IF (System.GetClockPulses[] - enterTime) < seconds.one THEN 
        {b ← NIL; QueueInputOrWait[]};  --just using as WAIT

      ENDLOOP;

    END;  --Watcher

  CheckBuffer: ENTRY PROC[p: LONG POINTER TO Buffer.Buffer]
    RETURNS [trouble: BOOLEAN] =
    BEGIN
    b: Buffer.Buffer ← p↑;
    IF b = NIL THEN RETURN[FALSE];
    RETURN[(EthernetFace.GetStatus[b.fo.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.q.first] THEN EXIT;
      REPEAT FINISHED => WatcherNotify[];
      ENDLOOP;
     --Check for lost output interrupt
     THROUGH [0..25) DO
      IF ~CheckBuffer[@outputState.q.first] THEN EXIT;
      REPEAT FINISHED => WatcherNotify[];
      ENDLOOP;
    END;
  
  WatcherNotify: ENTRY PROC =
    BEGIN
    IF CommFlags.doStats THEN Stats.StatIncr[statEtherLostInterrupts];
    SmashCSBs[];
    END;

  SendRawBuffer: ENTRY PROC[b: Buffer.Buffer] =
    BEGIN
    ENABLE UNWIND => NULL;  --I don't see any signals, but...
    e: IEEE8023.Encapsulation = LOOPHOLE[b.linkLayer.blockPointer];
    SELECT TRUE FROM
      (~myDevice.alive) =>
        {b.fo.status ← rejected; Driver.PutOnGlobalDoneQueue[b]; RETURN};
      (e.ethernetDest = SpecialSystem.nullHostNumber) =>
	{b.fo.status ← invalidDestAddr; Driver.PutOnGlobalDoneQueue[b]; RETURN};
      (EthernetFace.hearSelf) => NULL;  --is okay
      (HostNumbers.IsMulticastID[@e.ethernetDest]),
      (e.ethernetDest = me) =>
	BEGIN --sending to ourself, copy it over since we can't hear it
	-- Order buffer for length 'b.fo.driver.length' bytes.
	copy: Buffer.Buffer ← Driver.GetInputBuffer[
	  FALSE, Buffer.DataBytesPerRawBuffer[b]];
	IF copy # NIL THEN
	  BEGIN
	  words: NATURAL = (b.fo.driver.length + bpw - 1) / bpw;
	  Inline.LongCOPY[
	    from: e, to: copy.linkLayer.blockPointer, nwords: words];
	  copy.linkLayer.startIndex ← 0;
	  copy.linkLayer.stopIndexPlusOne ← b.fo.driver.length;  --copy length
	  copy.fo.driver.length ← b.fo.driver.length;  --same length as last one
	  copy.fo.driver.faceStatus ← ethernet[ok];  --should be ok from here on
	  copy.fo.network ← localDevice;  --set the driver field
	  copy.fo.time ← System.GetClockPulses[];  --pretty close to this time
	  IF CommFlags.doStats THEN
	    BEGIN
	    Stats.StatIncr[statEtherPacketsLocal];
	    Stats.StatBump[statEtherWordsLocal, words];
	    END;
	  Driver.PutOnGlobalInputQueue[copy];  --doesn't have iocb associated
	  END
	ELSE IF CommFlags.doStats THEN Stats.StatIncr[statEtherEmptyFreeQueue];
	END;
      ENDCASE;
    SendBufferInternal[b];
    END;  --SendRawBuffer

  SendBufferInternal: INTERNAL PROC[b: Buffer.Buffer] =
    BEGIN
    e: IEEE8023.Encapsulation = LOOPHOLE[b.linkLayer.blockPointer];
    -- EthernetFace uses words for degree of 'length'
    words: CARDINAL ← MAX[
      (b.fo.driver.length + bpw - 1) / bpw, IEEE8023.minWordsPerEthernetPacket];
    IF CommFlags.doDebug AND (b.fo.driver.length > bpw * maxEthernetWords) THEN
      Driver.Glitch[PacketTooLarge];
    b.fo.driver.faceStatus ← ethernet[pending];
    IF CommFlags.doDebug AND (b.fo.driver.iocb # NIL) THEN
      Driver.Glitch[OverlayingIocb];
    IF (b.fo.driver.iocb ← iocbState.free) = NIL THEN
      BEGIN
      IF CommFlags.doStats THEN Stats.StatIncr[statsIocbWait];
      b.fo.status ← aborted; Driver.PutOnGlobalDoneQueue[b]; RETURN;
      END;
    iocbState.free ← iocbState.free.next;
    EthernetFace.QueueOutput[ether, e, words, b.fo.driver.iocb];
    SELECT TRUE FROM
      (outputState.q.length = 0) =>
        outputState.timeSendDone ← System.GetClockPulses[];
      (CommFlags.doStats) =>
        Stats.StatIncr[statEtherSendFromOutputQueue];
      ENDCASE;
    Buffer.Enqueue[@outputState.q, b];

    IF CommFlags.doDebug THEN SanityCheck[];
    IF CommFlags.doStats THEN Stats.StatIncr[statEtherPacketsSent];
    IF CommFlags.doStats THEN Stats.StatBump[statEtherWordsSent, words];
    END;  --SendBufferInternal


  --No MONITOR PROTECTION here.
  MaybeChangeNumberOfInputBuffers: PROC[increaseBuffers: BOOLEAN] =
    BEGIN
    IF increaseBuffers THEN
      BEGIN
      IF inputState.access = NIL THEN
        BEGIN
        inputState.access ← Buffer.MakePool[0, inputState.extraBuffers];
	--make sure we don't over commit the buffers we've allocated
	IF inputState.queueAllowed < inputState.extraBuffers THEN
	  inputState.queueAllowed ← myDevice.buffers ←
	    myDevice.buffers + inputState.extraBuffers;
	END;
      END
    ELSE
      BEGIN
      IF inputState.access # NIL THEN
        BEGIN
	Buffer.DestroyPool[inputState.access]; inputState.access ← NIL;
	--don't let the queue to negative | even empty
	IF inputState.queueAllowed > inputState.extraBuffers THEN
	  inputState.queueAllowed ← myDevice.buffers ←
	    inputState.queueAllowed - inputState.extraBuffers;
	END;
      END;
    END;  --MaybeChangeNumberOfInputBuffers

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

  AdjustLengtoOfD0EthernetInputQueue: PUBLIC PROC[n: CARDINAL] =
    {inputState.queueAllowed ← n};

  CreateDefaultEthernetDrivers: PUBLIC <<IEEE8023>> PROC RETURNS [BOOLEAN] =
    BEGIN
    deviceNumber: CARDINAL ← 0;
    etherDevice: EthernetFace.DeviceHandle;
    etherDevice ← EthernetFace.GetNextDevice[EthernetFace.nullDeviceHandle];
    IF System.switches[CommSwitches.noEthernet] = down THEN RETURN[FALSE];
    IF etherDevice = EthernetFace.nullDeviceHandle THEN RETURN[FALSE];
    WHILE etherDevice # EthernetFace.nullDeviceHandle DO
      CreateAnEthernetDriver[etherDevice, deviceNumber];
      etherDevice ← EthernetFace.GetNextDevice[etherDevice];
      deviceNumber ← deviceNumber + 1;
      ENDLOOP;
    RETURN[TRUE];
    END;  --CreateDefaultEthernetDrivers

  CreateAnEthernetDriver: PROC[
    etherDevice: EthernetFace.DeviceHandle, deviceNumber: CARDINAL] =
    BEGIN
    IF deviceNumber # 0 THEN
      BEGIN
      him: LONG POINTER TO FRAME[EthernetDriver];
      him ← --NEW EthernetDriver-- PrincOpsMinus.NewSelf[];
      START him;  --so he'll initialize the procedure
      him.setupEthernetDriver[etherDevice];
      END
    ELSE SetupEthernetDriver[etherDevice];
    END;  --CreateAnEthernetDriver

  SetupEthernetDriver: PROC[etherDevice: EthernetFace.DeviceHandle] =
    BEGIN
    Wait: ENTRY PROC = INLINE {WAIT condition};
    condition: CONDITION;
    ether ← etherDevice;
    myEar ← me ← SpecialSystem.GetProcessorID[];
    IF HostNumbers.IsMulticastID[@myEar] THEN
      BEGIN
      Process.DisableTimeout[@condition];  --no tricks here
      Process.DisableAborts[@condition];  --fools are so smart
      ProcessorFace.SetMP[989];  --should probably warn PSCO
      --UNTIL HELL FREEZES OVER-- DO Wait[]; ENDLOOP;
      END;
    watcherState.pleaseStop ← TRUE;
    inputState.extraBuffers ← numberOfExtraBuffer;  --set default
    myDevice.buffers ← inputState.queueAllowed ← 1;
    Driver.AddDeviceToChain[(localDevice ← @myDevice)];
    IF CommFlags.driverStats THEN
      BEGIN
      myDevice.stats ← @etherStats;
      etherStats ← [];
      END;
    END;  --SetupEthernetDriver

  ActivateDriver: PROC =
    BEGIN
    EnterMonitor: ENTRY PROC = INLINE {SmashCSBs[]};
    iocbs: CARDINAL = (myDevice.buffers + inputState.extraBuffers) * 2;
    IF ~watcherState.pleaseStop THEN Driver.Glitch[DriverAlreadyActive];
    seconds.one ← System.MicrosecondsToPulses[1D6];
    seconds.fiveHalf ← System.MicrosecondsToPulses[25D5];
    seconds.forty ← System.MicrosecondsToPulses[40D6];
    getGarbage ← watcherState.pleaseStop ← FALSE;
    EthernetFace.TurnOff[ether];
    EthernetFace.AddCleanup[ether];
    inputState.access ← NIL;
    inputState.queueAllowed ← myDevice.buffers;
    Buffer.QueueInitialize[@inputState.q];
    Buffer.QueueInitialize[@outputState.q];
    inputState.timeLastRecv ← outputState.timeSendDone ← System.GetClockPulses[];
    myEar ← me ← SpecialSystem.GetProcessorID[];
    IF HostNumbers.IsMulticastID[@myEar] THEN Driver.Glitch[BadHostID];

    IF EthernetFace.globalStateSize # 0 THEN
      BEGIN
      status: Zone.Status;
      [globalStatePtr, status] ← ResidentHeap.MakeNode[
        EthernetFace.globalStateSize, a8];
      IF status # okay THEN Driver.Glitch[ResidentZoneTrouble];
      END; 

    iocbState.free ← NIL;
    IF EthernetFace.controlBlockSize = 0 THEN Driver.Glitch[IOCBSizeIsZero];
    IF CommFlags.doDebug THEN {iocbState.avail ← iocbs};
    iocbState.first ← iocbState.free ← CommUtil.AllocateIocbs[
      EthernetFace.controlBlockSize * iocbs * bpw];
    THROUGH [0..iocbs - 1) DO
      iocbState.first ← iocbState.first.next ←
        iocbState.first + EthernetFace.controlBlockSize;
      REPEAT FINISHED =>
        {iocbState.first.next ← NIL; iocbState.first ← iocbState.free};
      ENDLOOP;

    THROUGH [0..myDevice.buffers) DO
      b: Buffer.Buffer = GetBufferAndIocbEntry[];
      IF b # NIL THEN Buffer.Enqueue[@inputState.q, b];
      ENDLOOP;

    [cv: inputState.inWait, mask: inputState.mask] ←
      SpecialRuntime.AllocateNakedCondition[];
    Process.DisableTimeout[inputState.inWait];
    [cv: outputState.outWait, mask: outputState.mask] ←
      SpecialRuntime.AllocateNakedCondition[];
    Process.DisableTimeout[outputState.outWait];
    EnterMonitor[];
    BEGIN
    priority: Process.Priority ← Process.GetPriority[];
    Process.SetPriority[CommPriorities.driver];
    inputState.process ← FORK InInterrupt[];
    outputState.process ← FORK OutInterrupt[];
    Process.SetPriority[priority];
    END;
    Process.EnableAborts[@watcherState.timer];
    Process.SetTimeout[@watcherState.timer, Process.MsecToTicks[1000]];
    watcherState.process ← FORK Watcher[];
    myDevice.alive ← TRUE;  --and I'm alive
    END;

  SetEthernetListener: PUBLIC <<SpecialCommunication>> ENTRY PROC[
    physicalOrder: CARDINAL, newHostNumber: HostNumber]
    RETURNS [success: BOOLEAN] =
    BEGIN
    him: LONG POINTER TO FRAME[EthernetDriver];
    network: Device ← GetNthDeviceLikeMe[physicalOrder];
    IF network = NIL THEN RETURN[FALSE];
    him ← LOOPHOLE[Runtime.GlobalFrame[LOOPHOLE[network.sendRawBuffer]]];
    him.EthernetListenForHost[newHostNumber];
    RETURN[TRUE];
    END;


  EthernetListenForHost: PROC[newHostNumber: HostNumber] ←
    RealEthernetListenForHost; 
    -- The procedure variable for getting linkage to RealEthernetListenForHost.
    
  RealEthernetListenForHost: INTERNAL PROC [newHostNumber: HostNumber] =
    {myEar ← newHostNumber; SmashCSBs[]};

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

  SetCollectGarbageToo: PROC[collectGarbage: BOOLEAN] ←
    RealSetCollectGarbageToo;
    -- The procedure variable for getting linkage to RealSetCollectGarbageToo.
     
  RealSetCollectGarbageToo: PROC[collectGarbage: BOOLEAN] =
    BEGIN getGarbage ← collectGarbage; END;

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

  SmashCSBs: INTERNAL PROC =
    BEGIN
    b: Buffer.Buffer;
    EthernetFace.TurnOff[ether];  --shut that down
    IF (outputState.q.length # 0) THEN
      BEGIN
      UNTIL (b ← Buffer.Dequeue[@outputState.q]) = NIL DO
        b.fo.status ← aborted;
	Stats.StatIncr[statEtherReceivedKlobberedByReset];
	FreeBufferAndIocb[Driver.PutOnGlobalDoneQueue, b];
	ENDLOOP;
      END;
    EthernetFace.TurnOn[
      ether, LOOPHOLE[myEar, SpecialSystem.ProcessorID], inputState.mask,
      outputState.mask, globalStatePtr];
    IF CommFlags.doStats THEN Stats.StatIncr[statInterfaceReset];
    inputState.lastMissed ← EthernetFace.GetPacketsMissed[ether];
    FOR b ← inputState.q.first, b.fo.next UNTIL b = NIL DO
      -- EthernetFace uses words for degree of 'length'
      EthernetFace.QueueInput[
        ether, LOOPHOLE[b.linkLayer.blockPointer + offsetToDataUnit],
	(b.fo.driver.length / bpw) - offsetToDataUnit, b.fo.driver.iocb];
      ENDLOOP;
    IF CommFlags.doDebug THEN SanityCheck[];
    END;  --SmashCSBs

  DeleteDriver: PROC =
    BEGIN
    IF watcherState.pleaseStop THEN Driver.Glitch[DriverNotActive];
    Driver.RemoveDeviceFromChain[localDevice];  --get's us out of chain
    IF ether # EthernetFace.GetNextDevice[EthernetFace.nullDeviceHandle]
      THEN Runtime.SelfDestruct[];
    END;  --DeleteDriver

  DeactivateDriver: PROC =
    BEGIN
    process: PROCESS;
    b: Buffer.Buffer;
    IF watcherState.pleaseStop THEN Driver.Glitch[DriverNotActive];
    watcherState.pleaseStop ← TRUE;  --for others to check
    myDevice.alive ← FALSE;  --I'm dying - soon
    IF (process ← inputState.process) = NIL THEN RETURN;  --already deactive
    UNTIL inputState.process = NIL DO
      Process.EnableAborts[inputState.inWait]; Process.Abort[process];
      REPEAT FINISHED => JOIN process;
      ENDLOOP;
    process ← outputState.process;
    UNTIL outputState.process = NIL DO
      Process.EnableAborts[outputState.outWait]; Process.Abort[process];
      REPEAT FINISHED => JOIN process;
      ENDLOOP;
    Process.Abort[watcherState.process]; JOIN watcherState.process;
    EthernetFace.TurnOff[ether];
    SpecialRuntime.DeallocateNakedCondition[inputState.inWait];
    SpecialRuntime.DeallocateNakedCondition[outputState.outWait];
    inputState.inWait ← outputState.outWait ← NIL;
    Driver.ChangeNumberOfInputBuffers[FALSE];  --call thur Boss to set flags
    EthernetFace.RemoveCleanup[ether];
    UNTIL (b ← Buffer.Dequeue[@inputState.q]) = NIL DO
      b.fo.status ← aborted;  --didn't make it
      b.fo.driver.iocb ← NIL;  --don't worry, iocbs will all be freed later
      Driver.ReturnFreeBuffer[b];  --no interesting requeue on input
      ENDLOOP;
    UNTIL (b ← Buffer.Dequeue[@outputState.q]) = NIL DO
      b.fo.status ← aborted;  --didn't make it
      b.fo.driver.iocb ← NIL;  --don't worry, iocbs will all be freed later
      Driver.PutOnGlobalDoneQueue[b];  --go thru requeue procedure
      ENDLOOP;

    CommUtil.FreeIocbs[iocbState.first];
    iocbState.free ← iocbState.first ← NIL;
    IF CommFlags.doDebug THEN iocbState.avail ← 0; 

    IF EthernetFace.globalStateSize # 0 THEN
      BEGIN
      status: Zone.Status;
      status ← ResidentHeap.FreeNode[globalStatePtr];
      IF status # okay THEN Driver.Glitch[ResidentZoneTrouble];
      END;
    END;  --DeactivateDriver


  --initialization
  setupEthernetDriver ← SetupEthernetDriver;  --for multi instances

  END.  --EthernetDriver

time - by - action
17-May-84 10:09:09  AOF  Post Klamath.
 5-Mar-85 19:50:07  AOF  Treating broadcast as a subset of multicast.
 5-Apr-85 10:55:50  AOF  Use PilotSwitches.noEthernet instead of '>.
 2-Aug-85 15:28:04  AOF  Initialize and allocate 'globalStatePtr'
12-May-86 16:25:15  SMA  New encapsulation scheme.
17-Jun-86 18:39:50  AOF  Driver.GetInputBuffer takes a length.
23-Jun-86  8:57:31  AOF  Readd code for changing input queue length.
 1-Aug-86 16:02:41  MI   Changed degree of driver.length from word to byte.
 4-Aug-86 18:04:21  AOF  Change number of buffers to add from 2 => 4.
18-Aug-86 20:06:36  AOF  Lengths for copies of buffers come from device object.
20-Aug-86 11:12:21  AOF  Fix copy for can't here self broadcasts.
14-Nov-86 13:31:47  AOF  Don't start driver with a multicast host ID.
18-Nov-86 16:05:34  AOF  PilotSwitches.noEthernet => CommSwitches.noEthernet
 7-Jan-87 17:05:26  AOF  Tweeks for MDS relief
19-Jan-87 15:21:41  AOF  Use bytes for allocating IOCBs
 6-Feb-87  9:28:08  AOF  Adding physical overhead to buffer size
24-Mar-87 14:52:42  AOF  set .fo.time in buffer copy in SendRawBuffer.
 9-Apr-87 17:24:39  AOF  Put code in to deal with odd length packets again.
14-Apr-87 11:09:15  AOF  Allowing for encapsulation expansion on recieve buffers.
30-Jun-87 12:14:37  AOF  Suppression of runts and too long in input
18-Jul-87 10:36:38  AOF  Moving from EtherMAC to IEEE8023
24-Jul-87 16:46:25  AOF  Glitch on transmitting too large packets
20-Aug-87  9:12:47  AOF  Use interface definition of DLL size
31-Aug-87  9:37:45  AOF  Redefinition of physical overhead
 9-Sep-87 15:53:39  AOF  User Boss's version of ChangeNumberOfInputBuffers
15-Oct-87 10:45:35  AOF  Delete driver calling RemoveDeviceFromChain
23-Oct-87 10:48:21  AOF  AR#12162 (EthernetDriver may recycle short buffer)
 5-Nov-87 10:06:46  AOF  AR#12162 More (changing buffer length ~monitored)
25-Jan-88 13:38:36  AOF  Adjusting input length by start of frame adjustment
28-Jan-88  9:47:56  AOF  AR#12727 - SmashCSBs wrong buffer length
17-Feb-88 15:24:59  AOF  Fix for compiler bug NEWing self