-- File: TeledebugImplNoDisk.mesa - last edit:
-- AOF                 11-Feb-88 16:44:31
-- HGM                 14-Nov-83 19:20:32, Discard disk stuff
-- DKntusen            14-Nov-83 10:31:45 
-- Copyright (C) 1983, 1988 by Xerox Corporation. All rights reserved. 
<<
This module implements a teledebugging server using the Packet Exchange Protocol over the Ethernet, device # 0. The implementation only talks to the first PilotDisk. Later versions could support other device types and ordinals.

At present, this teledebug server is promiscuous: it is willing to indiscriminately talk to several debuggers simultaneously. This is not much of a problem at present. In the future, we could envision it latching on to the "master" - the first debugger that gave it a write-type request; it would still allow other debuggers to read (only). This would require that the protocol be enhanced with a "speakToMe" PacketType, which would override the identity of the debugger that currently was the master.

There are provisions here for DEBUGGING THIS IN CoPilot. To do so:

  o  run any debugger client (Othello is good);
  o  get from the client to the debugger (by breakpoint is good);
  o  Run SimpleNSIOEthernetImpl and TeledebugImpl, in that order.
  o  Interpret call TestTeledebugging in this module.

Bottom line, this doesn't work very good. The remote debugger looks at the ESV in the PDA; this tells about CoPilot's debugee. However, it reads memory directly from CoPilot, itself. Not too good. This debugging technique may be useful for debugging the basics of communication, if they are not working.

Alternatively, you can insert code which displays values of key variables in the maintenance panel. See GermOps.ShowCardinalInMP, etc.
>>

DIRECTORY
  Boot USING [Location],
  BootChannel USING [Result],
  DeviceTypes USING [ethernet],
  Environment USING [
    Base, bytesPerWord, Long, LongPointerFromPage,
    PageFromLongPointer, PageCount, PageNumber, wordsPerPage],
  GermOps USING [GermWorldError],
  IEEE8023 USING [EncapObject],
  NSConstants USING [teleDebugSocket],
  NSTypes USING [
    BufferBody, bytesPerExchangeHeader, maxDataBytesPerExchange, PacketType],
  PacketExchange USING [ExchangeClientType, ExchangeID],
  PageMap USING [ExchangeFlags, Flags, GetState, IsMapped],
  PilotMP USING [
    cGermDeviceError, cGermERROR, cGermFunnyPacket, Code,
    cRespondingToEtherDebugger, cWaitingForEtherDebugger],
  ProcessorFace USING [BootButton, GetNextAvailableVM, SetMP],
  SimpleNSIO USING [
    ByteCount, Finalize, fromAnyHost, fromAnyNetwork, fromAnySocket, GetRawBufferSize, Initialize,
    noTimeOut, ReceivePacket, ReturnPacket, SendPacket, timedOutBytes],
  System USING [
    broadcastHostNumber, GetClockPulses, Microseconds, MicrosecondsToPulses,
    NetworkAddress, nullNetworkNumber, Pulses],
  TeledebugProtocol;

TeledebugImplNoDisk: PROGRAM
  IMPORTS
    Environment, GermOps, PageMap, ProcessorFace, SimpleNSIO, System
  EXPORTS GermOps
  SHARES GermOps, PageMap =
  BEGIN

  -- Parameters:

  broadcastForDebuggerInterval: System.Microseconds = 30000000;
  proceedSequenceTimeout: System.Microseconds = 60000000;  -- for go, remoteDestruct
  exchangeIDTimeout:  -- a trojan horse ExchangeID will get thrown out after this delay.
    System.Microseconds = 120000000;

  -- TYPES and Constants:
  
  MaxSize: TYPE = CARDINAL [0..NSTypes.maxDataBytesPerExchange];
  bytesPerWord: CARDINAL = Environment.bytesPerWord;
  nil: Environment.Base RELATIVE POINTER = LOOPHOLE[0];
  nullExchangeID: PacketExchange.ExchangeID = [0, 0];  -- should be in PacketExchange!

  RequesterPacketType: TYPE =  -- SHOULD be in TeledebugProtocol!
    TeledebugProtocol .PacketType[coreStore..remoteDestructReply];

  -- Variables:

  -- The following ethernet buffer is allocated here statically because
  -- (1) if this module is present, we need it at any time
  -- (2) the buffer used by BootChannelSPP is only temporarily allocated,
  -- thus there is never more than one buffer permanently allocated.
  rawNSBufferSize: CARDINAL =  -- if not enough, dies with mp code.
    SIZE[ethernet IEEE8023.EncapObject] +
    NSTypes.maxDataBytesPerExchange/Environment.bytesPerWord + 36--say--;
  rawNSBuffer: ARRAY [0..rawNSBufferSize) OF WORD;
  
  b: LONG POINTER TO NSTypes.BufferBody;  -- the network buffer.

  firstUnimplementedVMPage: Environment.PageNumber;
  
  beingDebuggedInCopilot: BOOLEAN ← FALSE;
  
  protocolFlagsToPageMapFlags: ARRAY TeledebugProtocol .PageFlags[clean..vacant]
    OF PageMap.Flags = [
    clean: [readonly: FALSE, dirty: FALSE, referenced: FALSE],
    referenced: [readonly: FALSE, dirty: FALSE, referenced: TRUE],
    dirty: [readonly: FALSE, dirty: TRUE, referenced: FALSE],
    dirtyReferenced: [readonly: FALSE, dirty: TRUE, referenced: TRUE],
    writeProtected: [readonly: TRUE, dirty: FALSE, referenced: FALSE],
    writeProtectedReferenced: [readonly: TRUE, dirty: FALSE, referenced: TRUE],
    vacant: [readonly: TRUE, dirty: TRUE, referenced: FALSE]];

  coreStoreReqSize: MaxSize = TeledebugProtocol.coreStoreReqSize*bytesPerWord;
  coreStoreAckSize: MaxSize = TeledebugProtocol.coreStoreAckSize*bytesPerWord;
  coreFetchReqSize: MaxSize = TeledebugProtocol.coreFetchReqSize*bytesPerWord;
  coreFetchAckSize: MaxSize = TeledebugProtocol.coreFetchAckSize*bytesPerWord;
  diskStoreReqSize: MaxSize = TeledebugProtocol.diskStoreReqSize*bytesPerWord;
  diskStoreAckSize: MaxSize = TeledebugProtocol.diskStoreAckSize*bytesPerWord;
  diskFetchReqSize: MaxSize = TeledebugProtocol.diskFetchReqSize*bytesPerWord;
  diskFetchAckSize: MaxSize = TeledebugProtocol.diskFetchAckSize*bytesPerWord;
  nullPacketSize: MaxSize =
    SIZE[null TeledebugProtocol.TeledebugBuffer]*bytesPerWord;


  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Main Teledebugee server
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  GetTeledebugged: PUBLIC --GermOps.-- PROC [
    pLocation: LONG POINTER TO Boot.Location,
    scratchPage: Environment.PageNumber] =
    BEGIN
    -- (scratchPage is used for reading page labels.)
    packet: LONG POINTER TO TeledebugProtocol.TeledebugBuffer;
    gotADebugger: BOOLEAN ← FALSE;
    receiveTimeout: System.Microseconds ← broadcastForDebuggerInterval;
    -- Information about current request packet.
    dataBytes: SimpleNSIO.ByteCount;
    thisExchangeID: PacketExchange.ExchangeID;
    prevExchangeID: PacketExchange.ExchangeID ← nullExchangeID;
    timePrevExchangeID: System.Pulses;
    nilRequest: TeledebugProtocol.PacketType = TeledebugProtocol.PacketType.last;
    requiredRequest: TeledebugProtocol.PacketType ←  --
      -- If non-nil, next packet must be this type (or requiredRequest.PRED).
      nilRequest;

    ProcessorFace.SetMP[PilotMP.cWaitingForEtherDebugger];

    -- Initialize Network I/O:
    -- SOMEDAY, we could make the call to Debug be passed a device
    -- and type (just like BootChannel), and thus allow teledebugging
    -- over a variety of networks.
    BEGIN
    result: BootChannel.Result;
    IF rawNSBufferSize < SimpleNSIO.GetRawBufferSize[] THEN
      GermOps.GermWorldError[PilotMP.cGermERROR];
    [bufferBody: b, result: result] ← SimpleNSIO.Initialize[
      DeviceTypes.ethernet, 0, @rawNSBuffer,
      IF beingDebuggedInCopilot THEN doCleanup ELSE avoidCleanup];
    IF result # [ok[]] THEN GermOps.GermWorldError[PilotMP.cGermDeviceError];
    packet ← LOOPHOLE[@b.exchangeWords];
    END;

    DO  --until go or remoteDestruct request--
    
      -- Get next request:
      DO  -- until got a request packet

        IF NOT gotADebugger THEN
          BEGIN  -- send mayday packet
          -- don't use a constructor here unless you want a LARGE frame
          -- packet↑ ← [type: mayday, body: null[]]];
          packet.type ← mayday;
          packet.spare ← 0;
          packet.body ← null[];
          PacketExchangeSend[
            dataBytes: nullPacketSize,
            exchangeID: LOOPHOLE[System.GetClockPulses[]],
            dest: [
            System.nullNetworkNumber, System.broadcastHostNumber,
            NSConstants.teleDebugSocket]];
	  receiveTimeout ← broadcastForDebuggerInterval;
          END;

        [dataBytes, thisExchangeID] ← PacketExchangeReceive[
          minBytes: nullPacketSize, prevExchangeID: prevExchangeID,
	  timePrevExchangeID: timePrevExchangeID,
          timeout:
          IF gotADebugger THEN SimpleNSIO.noTimeOut
          ELSE broadcastForDebuggerInterval,
          getFrom: [
          SimpleNSIO.fromAnyNetwork, SimpleNSIO.fromAnyHost,
          SimpleNSIO.fromAnySocket]];
        --ASSERT: timed out or got a packet of at least nullPacketSize.
        IF --UNTIL-- dataBytes # SimpleNSIO.timedOutBytes THEN EXIT;
	--ASSERT: timed out.
	IF requiredRequest # nilRequest THEN
	  BEGIN
	  -- Fabricate desired request packet and process it:
	  packet.type ← requiredRequest;
	  dataBytes ← nullPacketSize;
	  packet.body ← null[];
	  EXIT;
	  END;
        ENDLOOP;

      -- Process request:
      BEGIN  --scope of BadPacket--
      IF requiredRequest # nilRequest AND
        (packet.type # requiredRequest AND packet.type # requiredRequest.PRED) THEN
        GOTO BadPacket;
      SELECT packet.type FROM

        -- Each arm below sets dataBytes and the buffer body for the appropriate
        -- response and falls through to send it back to the requestor.

        mayday, ack, nak => GOTO IgnorePacket;  -- broadcast from some other debugee.

        coreFetch =>
          BEGIN
          -- this depends upon FetchReq and FetchAck pageNumber
          -- being in the same place.
          OPEN pAck: LOOPHOLE[packet, TeledebugProtocol.CoreFetchAckHandle];
          IF dataBytes # coreFetchReqSize THEN GOTO BadPacket;
          WITH pReq: packet SELECT FROM
            coreFetchReq =>
              BEGIN
              page: Environment.PageNumber = pReq.page;
              IF ImplementedAndMapped[page] THEN
                BEGIN
                pData: LONG POINTER TO TeledebugProtocol.PageData =
                  Environment.LongPointerFromPage[page];
                flags: PageMap.Flags = PageMap.GetState[page].state.flags;
                pAck.flags ← ProtocolFlagsFromPageMapFlags[flags];
                pAck.data ← pData↑;
                [] ← PageMap.ExchangeFlags[  -- restore referenced bit.
                  virtual: page, newFlags: flags];
                END
              ELSE pAck.flags ← vacant;
              END;
            ENDCASE => GOTO BadPacket;
          packet.body ← coreFetchAck[  -- (body all already set)
            page: NULL, flags: NULL, data: NULL];
          dataBytes ← coreFetchAckSize;
          packet.type ← ack;
	  receiveTimeout ← SimpleNSIO.noTimeOut;
          END;  --coreFetch--

        coreStore =>
          BEGIN
          -- this depends upon both StoreReq and StoreAck
          -- page and flags being in the same place
          IF dataBytes # coreStoreReqSize THEN GOTO BadPacket;
          WITH pReq: packet SELECT FROM
            coreStoreReq =>
              BEGIN
              page: Environment.PageNumber = pReq.page;
              IF pReq.flags ~IN [clean..vacant] THEN GOTO BadPacket;
              IF ImplementedAndMapped[page] THEN
                BEGIN
                pData: LONG POINTER TO TeledebugProtocol.PageData =
                  Environment.LongPointerFromPage[page];
                MakeWritable[page];
                pData↑ ← pReq.data;
                [] ← PageMap.ExchangeFlags[
                  virtual: page,
                  newFlags: protocolFlagsToPageMapFlags[pReq.flags]]
                END
              ELSE pReq.flags ← vacant;
              END;
            ENDCASE => GOTO BadPacket;
          packet.body ← coreStoreAck[page: NULL, flags: NULL];  -- (body all already set)
          dataBytes ← coreStoreAckSize;
          packet.type ← ack;
	  receiveTimeout ← SimpleNSIO.noTimeOut;
          END;  --coreStore--

        go, remoteDestruct =>
          BEGIN
          goReplyIsSUCCGo: BOOLEAN [TRUE..
	    (TeledebugProtocol.PacketType.goReply =
              TeledebugProtocol.PacketType.go.SUCC)] = TRUE;
          remoteDestructReplyIsSUCCGo: BOOLEAN [TRUE..
	    (TeledebugProtocol.PacketType.remoteDestructReply =
              TeledebugProtocol.PacketType.remoteDestruct.SUCC)] = TRUE;
          requiredRequest ← packet.type.SUCC;
	  IF dataBytes # nullPacketSize OR packet.request # null THEN
            GOTO BadPacket;
	  packet.type ← ack;
          packet.body ← null[];
	  dataBytes ← nullPacketSize;
	  receiveTimeout ← proceedSequenceTimeout;
          END;  --go, remoteDestruct--

        goReply =>
          BEGIN
          IF dataBytes # nullPacketSize OR packet.request # null THEN
            GOTO BadPacket;
          SimpleNSIO.Finalize[
	    IF beingDebuggedInCopilot THEN doCleanup ELSE avoidCleanup];
          RETURN;
          END;  --goReply--

        remoteDestructReply =>
          BEGIN
          IF dataBytes # nullPacketSize OR packet.request # null THEN
            GOTO BadPacket;
	  ProcessorFace.BootButton[];
          END;  --remoteDestructReply--

        ENDCASE => GOTO BadPacket;  -- unknown request type.

      -- Return response packet sitting in buffer:
      prevExchangeID ← thisExchangeID;  -- remember ID of good packets.
      timePrevExchangeID ← System.GetClockPulses[];
      PacketExchangeReturn[dataBytes: dataBytes];
      ProcessorFace.SetMP[PilotMP.cRespondingToEtherDebugger];
      gotADebugger ← TRUE;

      EXITS
        BadPacket => ProcessorFace.SetMP[PilotMP.cGermFunnyPacket];
        IgnorePacket => NULL;
      END;  --scope of BadPacket--
      ENDLOOP;  --until go or remoteDestruct request--
    END;  --Debug--


  ImplementedAndMapped: PROC [page: Environment.PageNumber] RETURNS [BOOLEAN] = {
    IF page >= firstUnimplementedVMPage THEN RETURN[FALSE]
    ELSE RETURN[PageMap.IsMapped[page]]};

  MakeWritable: PROC [page: LONG CARDINAL] = {
    flags: PageMap.Flags ← PageMap.GetState[page].state.flags;
    flags.readonly ← FALSE;
    [] ← PageMap.ExchangeFlags[virtual: page, newFlags: flags]};

  ProtocolFlagsFromPageMapFlags: PROC [in: PageMap.Flags]
    RETURNS [out: TeledebugProtocol.PageFlags] =
    BEGIN
    out ← clean;
    DO
      IF protocolFlagsToPageMapFlags[out] = in THEN RETURN;
      IF (out ← SUCC[out]) = illegal THEN RETURN;
      ENDLOOP;
    END;


  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- PacketExchange Network I/O
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  -- This supports sending and receiving level three packets
  -- using the Packet Exchange Protocol.

  -- Note this isn't very clean since we know some about teledebug socket etc.

  PacketExchangeReceive: PROC [
    timeout: LONG CARDINAL, getFrom: System.NetworkAddress,
    minBytes: SimpleNSIO.ByteCount, prevExchangeID: PacketExchange.ExchangeID,
    timePrevExchangeID: System.Pulses]
    RETURNS [
      dataBytes: SimpleNSIO.ByteCount, exchangeID: PacketExchange.ExchangeID,
      source: LONG POINTER TO System.NetworkAddress] =
    -- The returned dataBytes is the number of client bytes in the level
    --   three packet. Returns dataBytes = SimpleNSIO.timedOutBytes if
    --   times out. In this case, exchangeID will be TRASH.
    -- Supresses duplicates of packets with exchangeID previous to
    --   prevExchangeID, and packets shorter than minBytes.
    -- ExchangeIDs which look bad are discarded for a maximum of two minutes,
    --   then are accepted as good.
    -- Duplicates of packets with exchangeID equal to prevExchangeID are
    --   returned to caller; he can suppress them if he wants.
    -- prevExchangeID = nullExchangeID means accept any exchangeID.
    BEGIN
    type: NSTypes.PacketType;
    levelTwoBytes: SimpleNSIO.ByteCount;
    result: BootChannel.Result;
    DO  --until correct teleDebug packet arrives--
      [dataBytes: levelTwoBytes, type: type, source: source, result: result] ←
        SimpleNSIO.ReceivePacket[
        getFrom: getFrom, timeout: timeout,
        mySocket: NSConstants.teleDebugSocket];
      IF levelTwoBytes = SimpleNSIO.timedOutBytes THEN
        RETURN[SimpleNSIO.timedOutBytes, TRASH, NIL];
      HandleResult[result];
      -- This packet was sent to teleDebugSocket. It should be correct.
      IF --UNTIL-- type = packetExchange
        AND levelTwoBytes >= NSTypes.bytesPerExchangeHeader + minBytes
        AND b.exchangeType = teledebug AND
          (prevExchangeID = nullExchangeID
           OR NewerOrSame[
             thisExchangeID: b.exchangeID, prevExchangeID: prevExchangeID]
	   OR System.GetClockPulses[] - timePrevExchangeID >
	     System.MicrosecondsToPulses[exchangeIDTimeout]) THEN EXIT;
      ProcessorFace.SetMP[PilotMP.cGermFunnyPacket];
      ENDLOOP;
    RETURN[levelTwoBytes - NSTypes.bytesPerExchangeHeader, b.exchangeID, source];
    END;  --PacketExchangeReceive--

  PacketExchangeReturn: PROC [dataBytes: SimpleNSIO.ByteCount] = INLINE
    -- Returns the contents of the buffer to where it came from.
    BEGIN
    -- Note that the exchangeID, teledebugExchangeType already set
    HandleResult[
      SimpleNSIO.ReturnPacket[
      dataBytes: dataBytes + NSTypes.bytesPerExchangeHeader,
      type: packetExchange].result];
    END;

  PacketExchangeSend: PROC [
    dataBytes: SimpleNSIO.ByteCount, exchangeID: PacketExchange.ExchangeID,
    dest: System.NetworkAddress] = INLINE
    BEGIN
    b.exchangeID ← exchangeID;
    b.exchangeType ← teledebug;
    HandleResult[
      SimpleNSIO.SendPacket[
      dataBytes: dataBytes + NSTypes.bytesPerExchangeHeader, type: packetExchange,
      sourceSocket: NSConstants.teleDebugSocket, dest: dest].result];
    END;

  HandleResult: PROC [result: BootChannel.Result] =
    BEGIN
    WITH r: result SELECT FROM
      ok => NULL;
      error => GermOps.GermWorldError[r.code];
      ENDCASE => GermOps.GermWorldError[PilotMP.cGermERROR];
    END;

  NewerOrSame: PROC [thisExchangeID, prevExchangeID: PacketExchange.ExchangeID]
    RETURNS [BOOLEAN] = --INLINE--
    -- Returns TRUE if thisExchangeID is newer than or the same as prevExchangeID
    -- (and therefore should not be discarded).
    BEGIN
    << We call an exchangeID older if it happened in the recent past;
    that is, its value is within the range [thisExchangeID -
    LAST[ExchangeID]/8..thisExchangeID). This means that duplicates of recent
    previous packets will be discarded with high reliability. >>

    LongCardFromExchangeID: PROC [exchangeID: PacketExchange.ExchangeID]
      RETURNS [LONG CARDINAL] = INLINE {
      RETURN[LOOPHOLE[
        Environment.Long[num[lowbits: exchangeID.b, highbits: exchangeID.a]]]]};

    newerLimit: LONG CARDINAL = 7*(LAST[LONG CARDINAL]/8);  -- utilizes wraparound
    amountThisNewer: LONG CARDINAL =  -- the amount that thisExchangeID
      -- is newer than prevExchangeID (the usual case)
      LongCardFromExchangeID[thisExchangeID] - LongCardFromExchangeID[
        prevExchangeID];  -- underflow is fine here.

    -- TEMP DEBUG
    --IF amountThisNewer >= newerLimit THEN {
    --  ShowCodeInMP[2222];
    --  ShowCardinalInMP[Inline.HighHalf[amountThisNewer]];
    --  ShowCardinalInMP[Inline.LowHalf[amountThisNewer]];
    --  ShowCodeInMP[2224];
    --  ShowCardinalInMP[Inline.HighHalf[newerLimit]];
    --  ShowCardinalInMP[Inline.LowHalf[newerLimit]];
    --  };
    RETURN[ --newerOrSame:-- amountThisNewer < newerLimit];
    END;

  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Main body, debugging code
  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  TestTeledebugging: PROC[deviceOrdinal: CARDINAL ← 0]  =
    -- To test this module in CoPilot, interpret call this proc from the debugger.
    -- See comments at head of module.
    BEGIN
    location: Boot.Location;
    storage: ARRAY  -- need one word-aligned page of storage.
      [0..2*Environment.wordsPerPage) OF WORD;
    beingDebuggedInCopilot ← TRUE;
    location.deviceOrdinal ← deviceOrdinal;  -- only relevant value in location
    GetTeledebugged[pLocation: @location, scratchPage: 
      Environment.PageFromLongPointer[
      @storage + Environment.wordsPerPage-1]];
    END;


  -- MAIN BODY:

  -- Find the size of VM for this processor:  (sets firstUnimplementedVMPage)
  BEGIN
  page: Environment.PageNumber;
  count: Environment.PageCount;
  FOR firstUnimplementedVMPage ← FIRST[Environment.PageNumber], page + count DO
    [firstPage: page, count: count] ← ProcessorFace.GetNextAvailableVM[
      firstUnimplementedVMPage];
    IF count = 0 THEN EXIT;
    ENDLOOP;
  END;
  

  END.


LOG  (For previous log entries, please see Mesa 10.0 archive version.)

1-Sep-81 15:17:25   Forrest   8.0c; add DetermineDiskShape
6-Dec-81  4:27:00   Forrest   NS Teledebug lives
7-Jun-83 23:18:09   DKnutsen
   OISCP => NS. Get LongPointerFromPage from Environment. Changed IsVacant to IsMapped. Convert to new PageMap. Make compatible with new SimpleNSIO interface. Use official type definitions rather than private copies. Some responses didn't set ack packet.type. Doubled proceedSequenceTimeout. Supress copies of previous request packets. Now retransmits "shutUp" packet. Documented operation of go sequencing. Use informative mp codes. Allocate ethernet buffer here.
20-Jul-83 10:16:14   Luniewski
   NSTypes.maxDataBytePerExchange => NSTypes.maxDataBytesPerExchange, long page numbers in map log entries.
11-Nov-83 13:55:50   DKnutsen
   Must not use SendPacket to talk to remote network. Simplify Proceed logic and use timeout.
14-Nov-83 10:31:50   DKnutsen	Handle duplicate go packets.