-- MesaRuntime>PilotNub.mesa   (May 11, 1983 2:45 pm by Levin)

DIRECTORY
  Boot USING [ReadMDS],
  BootSwap USING [InLoad, OutLoad, Teledebug],
  CPSwapDefs USING [
    BBArray, BBHandle, CallDP, DebugParameter, ExternalStateVector, SwapInfo,
    StartDP, SwapReason, UBBPointer, UserBreakBlock, VersionID],
  DebuggerSwap USING [canSwap, parameters],
  DeviceCleanup USING [Item, Linkage, Perform, Reason],
  Environment USING [Byte, maxPagesInMDS, PageCount, PageNumber],
  Frame USING [
    GetReturnFrame, GetReturnLink, MyLocalFrame, SetReturnFrame,
    SetReturnLink],
  Inline USING [HighHalf, LowHalf],
  KeyboardFace USING [keyboard],
  Keys USING [DownUp, KeyBits],
  Mopcodes USING [zDUP, zRFS],
  PilotMP USING [cCantSwap, cCleanup, cClient, cHang, Code],
  PilotSwitches USING [switches--.h, .i, .r--],
  PrincOps USING [
    ControlLink, FieldDescriptor, FrameHandle, GlobalFrameHandle, NullFrame,
    NullLink, Port, StateVector, SVPointer],
  Process USING [GetPriority, Priority, SetPriority, SetTimeout, Ticks],
  ProcessInternal USING [DisableInterrupts, EnableInterrupts],
  ProcessOperations USING [HandleToIndex, IndexToHandle, ReadPSB, ReadPTC,
    ReadWDC, WritePSB, WritePTC, WriteWDC],
  ProcessPriorities USING [priorityRealTime],
  ProcessorFace USING [BootButton, GetClockPulses,
        microsecondsPerHundredPulses, SetMP],
  PSB USING [PDA],
  Runtime USING [Interrupt],
  RuntimeInternal USING [],
  RuntimePrograms USING [],
  SDDefs USING [
    sAlternateBreak, sBreak, sBreakBlock, sBreakBlockSize, sCallDebugger,
    sCoreSwap, SD, sInterrupt, sProcessBreakpoint, sUncaughtSignal,
    sWorryCallDebugger, sXferTrap],
  XferTrap USING [ReadXTS, Status, WriteXTS];

PilotNub: MONITOR -- for CheckInterrupt, DeviceCleanup.Install
  IMPORTS
    Boot, BootSwap, DebuggerSwap, DeviceCleanup, Frame, Inline, KeyboardFace,
    PilotSwitches, Process, ProcessInternal, ProcessOperations, ProcessorFace,
    Runtime, XferTrap
  EXPORTS DeviceCleanup, RuntimeInternal, RuntimePrograms
  SHARES DeviceCleanup =
  BEGIN

  -- This module is the debugger's representative in the client world.

  loadStatePage: PUBLIC Environment.PageNumber; -- exported to RuntimeInternal

  CAbort: PUBLIC SIGNAL = CODE;
  CantSwap: PUBLIC SIGNAL = CODE;
  KillThisTurkey: SIGNAL = CODE;
  Quit: SIGNAL = CODE;

  --
  -- Breakpoints

  numberBlocks: CARDINAL = 5; -- number of break blocks
  BreakBlocks: TYPE = MACHINE DEPENDENT RECORD [
    header(0): CPSwapDefs.BBArray, -- length plus (zero-length) array of blocks
    body(1): ARRAY [0..numberBlocks) OF CPSwapDefs.UserBreakBlock];
  breakBlocks: BreakBlocks;

  InitBreakBlocks: PROC =
    BEGIN OPEN SDDefs;
    SD[sBreakBlock] ← Inline.LowHalf[LONG[@breakBlocks]];
      -- mds relative (should really be long pointer)
    SD[sBreakBlockSize] ← SIZE[BreakBlocks];
    breakBlocks.header.length ← 0;
    END;

  Break: PROC = -- executed by (non-worry) BRK instruction
    BEGIN
    state: RECORD [
      padding: ARRAY [0..2) OF UNSPECIFIED, v: PrincOps.StateVector];
    state.v ← STATE;
    state.v.dest ← Frame.GetReturnLink[];
    state.v.source ← PrincOps.NullLink;
    ProcessBreakpoint[@state.v];  -- isn't this supposed to go through SD[sProcessBreakpoint]?
    IF XferTrap.ReadXTS[] = on THEN XferTrap.WriteXTS[skip1];
    RETURN WITH state.v;
    END;

  ProcessBreakpoint: PROC [s: PrincOps.SVPointer] =
    BEGIN
    inst: Environment.Byte;
    swap: BOOLEAN;
    [inst, swap] ← DoBreakpoint[s];
    IF swap THEN CoreSwap[breakpoint, s]
    ELSE s.instbyte ← inst  -- replant the instruction and go on
    END;

  -- make this INLINE someday??
  DoBreakpoint: PROC [s: PrincOps.SVPointer]
        RETURNS [Environment.Byte, BOOLEAN] =
    BEGIN
    bba: CPSwapDefs.BBHandle = SDDefs.SD[SDDefs.sBreakBlock];
    l: PrincOps.FrameHandle ← LOOPHOLE[s.frame];
    FOR i: CARDINAL IN [0..bba.length) DO
      ubb: CPSwapDefs.UBBPointer = @bba.blocks[i];
      IF ubb.frame = l.accesslink AND ubb.pc = CARDINAL[l.pc] THEN
	IF TrueCondition[ubb, l, s] THEN EXIT ELSE RETURN[ubb.inst, FALSE]
      ENDLOOP;
    RETURN[0, TRUE]
    END;

   -- decide whether to take the breakpoint
  TrueCondition: PROC [
    ubb: CPSwapDefs.UBBPointer, base: POINTER, s: PrincOps.SVPointer]
    RETURNS [BOOLEAN] =
    INLINE BEGIN
    ReadField: PROC [POINTER, PrincOps.FieldDescriptor] RETURNS [UNSPECIFIED] =
      MACHINE CODE BEGIN Mopcodes.zRFS END;
    fd: PrincOps.FieldDescriptor;
    locL, locR: POINTER;
    left, right: UNSPECIFIED;
    IF ubb.counterL THEN RETURN[(ubb.ptrL ← ubb.ptrL + 1) = ubb.ptrR];
    locL ← SELECT TRUE FROM
      ubb.stackRelative => @s.stk[LOOPHOLE[ubb.ptrL, CARDINAL]],
      ubb.localL => base + LOOPHOLE[ubb.ptrL, CARDINAL],
      ENDCASE => ubb.ptrL;
    fd ← [offset: 0, posn: ubb.posnL, size: ubb.sizeL];
    left ← ReadField[locL, fd];
    IF ~ubb.immediateR THEN
      BEGIN
      fd ← [offset: 0, posn: ubb.posnR, size: ubb.sizeR];
      locR ← IF ubb.localR THEN base + LOOPHOLE[ubb.ptrR, CARDINAL] ELSE ubb.ptrR;
      right ← ReadField[locR, fd]
      END
    ELSE right ← ubb.ptrR;
    RETURN[
      SELECT ubb.relation FROM
	lt => left < right, gt => left > right, eq => left = right,
	ne => left # right, le => left <= right, ge => left >= right,
	ENDCASE => FALSE]
    END;

  -- executed by worry-mode BRK instruction
  WorryBreaker: PROC RETURNS [PrincOps.FrameHandle] =
    BEGIN OPEN PrincOps;
    state: RECORD [padding: ARRAY [0..2) OF UNSPECIFIED, v: StateVector];
    state.v.instbyte ← 0;
    state.v.stkptr ← 1;
    state.v.stk[0] ← Frame.MyLocalFrame[];
    state.v.dest ← Frame.GetReturnLink[];
    state.v.source ← PrincOps.NullLink;
    ProcessInternal.DisableInterrupts[];
    DO
      IF XferTrap.ReadXTS[] = on THEN XferTrap.WriteXTS[skip1];
      ProcessInternal.EnableInterrupts[];
      TRANSFER WITH state.v;
      ProcessInternal.DisableInterrupts[];
      state.v ← STATE;
      state.v.dest ← Frame.GetReturnLink[];
      state.v.source ← PrincOps.NullLink;
      swapInfo.state ← @state.v;
      swapInfo.reason ← worrybreak; -- set mds too
      ToDebugger[@swapInfo];
      ENDLOOP;
    END;

  --
  -- Uncaught signals

  Catcher: PROC [msg, signal: UNSPECIFIED, frame: PrincOps.FrameHandle] =
    BEGIN
    Punt: PROC [c: PilotMP.Code] = INLINE
        {ProcessorFace.SetMP[c]; DO ENDLOOP};
    SignallerGF: PrincOps.GlobalFrameHandle;
    state: PrincOps.StateVector;
    f: PrincOps.FrameHandle;
    state.stk[0] ← msg;
    state.stk[1] ← signal;
    state.stkptr ← 0;
    -- The call stack below here is: Signaller, [Signaller,] offender
    f ← Frame.GetReturnFrame[];
    SignallerGF ← f.accesslink;
    f ← LOOPHOLE[state.dest ← f.returnlink, PrincOps.FrameHandle];
    IF f.accesslink = SignallerGF THEN state.dest ← f.returnlink;
    IF signal = CantSwap THEN Punt[PilotMP.cCantSwap];
    CoreSwap[uncaughtsignal, @state ! CAbort => GOTO abort];
    EXITS
      abort =>
        IF signal = ABORTED THEN {BackStop[frame]; ERROR KillThisTurkey}
        ELSE ERROR ABORTED;
    END;

  BackStop: PROC [root: PrincOps.FrameHandle] =
    BEGIN
    endProcess: PrincOps.ControlLink = root.returnlink;
    Caller: PROC = LOOPHOLE[Frame.GetReturnLink[]];
    root.returnlink ← [frame[Frame.MyLocalFrame[]]];
    Frame.SetReturnFrame[PrincOps.NullFrame];
    Caller[ ! KillThisTurkey => CONTINUE];
    Frame.SetReturnLink[endProcess];
    END;


  --~~~~~~~~~ Interrupts (e.g. CTRL-SWAT) ~~~~~~~~~

  wakeup: CONDITION;
  ticksPerWakeup: Process.Ticks = 1;

  CheckInterrupt: ENTRY PROC = -- default CTRL-SWAT watcher
    BEGIN
    interruptState: Keys.DownUp ← up;
    pKeys: LONG POINTER TO Keys.KeyBits = LOOPHOLE[KeyboardFace.keyboard];
    DO --FOREVER--
      ENABLE ABORTED => CONTINUE;
      WAIT wakeup;
      IF pKeys[Spare3]=down AND pKeys[Ctrl]=down AND pKeys[LeftShift]=up
	AND interruptState = up
	AND LOOPHOLE[PSB.PDA.available, CPSwapDefs.SwapInfo]
	       .externalStateVector ~= NIL THEN
	  { interruptState ← down; Runtime.Interrupt[] }
      ELSE interruptState ← up;
      ENDLOOP;
    END;

  Interrupt: PROC = -- implementation of Runtime.Interrupt
    BEGIN
    state: RECORD [a, b: UNSPECIFIED, v: PrincOps.StateVector];
    state.v ← STATE;
    state.v.dest ← LOOPHOLE[Frame.MyLocalFrame[], PrincOps.ControlLink];
    CoreSwap[interrupt, @state.v]
    END;

  InitializeInterrupt: PUBLIC PROC =
    -- Initialize Pilot's CTRL-SWAT watcher (if one was requested).
    -- Must not be invoked until KeyboardFace has been initialized.
    BEGIN
    IF PilotSwitches.switches.i = down THEN
      BEGIN
      throwAway: PROCESS;
      priorityPrev: Process.Priority = Process.GetPriority[];
      Process.SetTimeout[@wakeup, ticksPerWakeup];
      Process.SetPriority[ProcessPriorities.priorityRealTime];
      throwAway ← FORK CheckInterrupt[];  -- (no profit in Detaching)
      Process.SetPriority[priorityPrev];
      END;
    END;

  --
  -- Miscellaneous Runtime, RuntimeInternal items

  CallDebugger: PROC [s: STRING] =
    -- Runtime.CallDebugger is KFCB[sCallDebugger]
    BEGIN
    state: RECORD [a, b: UNSPECIFIED, v: PrincOps.StateVector];
    state.v ← STATE;
    state.v.stk[0] ← s;
    state.v.stkptr ← 1;
    state.v.dest ← Frame.GetReturnLink[];
    CoreSwap[explicitcall, @state.v]
    END;

  worryCallIndirect: PORT;
  
  WorryCallDebugger: PROC RETURNS [PrincOps.FrameHandle] =
    BEGIN OPEN PrincOps;
    state: RECORD [padding: ARRAY [0..2) OF UNSPECIFIED, v: StateVector];
    state.v.instbyte ← 0;
    state.v.stkptr ← 1;
    -- The following dance is needed because fixed frame procedures that are not
    -- called as trap handlers don't have source & destination links put on the
    -- stack.  We insert an indirect link to force them to be put there.
    LOOPHOLE[worryCallIndirect, PrincOps.Port].frame ← Frame.MyLocalFrame[];
    state.v.stk[0] ← @worryCallIndirect;
    state.v.dest ← Frame.GetReturnLink[];
    state.v.source ← PrincOps.NullLink;
    ProcessInternal.DisableInterrupts[];
    DO --FOREVER--
      IF XferTrap.ReadXTS[] = on THEN XferTrap.WriteXTS[skip1];
      ProcessInternal.EnableInterrupts[];
      TRANSFER WITH state.v;
      ProcessInternal.DisableInterrupts[];
      state.v ← STATE;
      state.v.dest ← state.v.stk[state.v.stkptr + 1];
      Frame.SetReturnLink[state.v.dest];
      state.v.source ← PrincOps.NullLink;
      swapInfo.state ← @state.v;
      swapInfo.reason ← worrycall;
      ToDebugger[@swapInfo];
      ENDLOOP
    END;

  CleanMapLog: PUBLIC PROC =
    BEGIN
    state: RECORD [a, b: UNSPECIFIED, v: PrincOps.StateVector];
    state.v ← STATE;
    state.v.stkptr ← 0;
    state.v.dest ← Frame.GetReturnLink[];
    CoreSwap[cleanmaplog, @state.v]
    END;

  -- Procedures that cause swap to debugger

  swapInfo: CPSwapDefs.ExternalStateVector; -- nub-debugger communication area

  parmstring: STRING = [40];

  GetMDS: PROC RETURNS [Environment.PageNumber] =
    BEGIN RETURN[Boot.ReadMDS[]*Environment.maxPagesInMDS] END;

  CoreSwap: PROC [why: CPSwapDefs.SwapReason, sp: PrincOps.SVPointer] =
    BEGIN
    DP: CPSwapDefs.DebugParameter;

    decode: PROC RETURNS [proceed: BOOLEAN] = -- decode the SwapReason
      BEGIN
      f: PrincOps.GlobalFrameHandle;
      lsv: PrincOps.StateVector;
      SELECT swapInfo.reason FROM
	proceed, resume => RETURN[TRUE];
	call =>
	  BEGIN
	  lsv ← LOOPHOLE[swapInfo.parameter, CPSwapDefs.CallDP].sv;
	  lsv.source ← LOOPHOLE[Frame.MyLocalFrame[], PrincOps.ControlLink];
	  TRANSFER WITH lsv;
	  lsv ← STATE;
	  LOOPHOLE[swapInfo.parameter, CPSwapDefs.CallDP].sv ← lsv;
	  why ← return
	  END;
	start =>
	  BEGIN
	  f ← LOOPHOLE[swapInfo.parameter, CPSwapDefs.StartDP].frame;
	  IF ~f.started THEN START LOOPHOLE[f, PROGRAM] ELSE RESTART f;
	  why ← return
	  END;
	quit => SIGNAL Quit;
	ENDCASE => RETURN[TRUE];
      RETURN[FALSE]
      END; --decode--

    -- Body of CoreSwap:

    -- IF ~DebuggerSwap.canSwap THEN SIGNAL CantSwap;
    swapInfo.state ← sp;
    DP.string ← parmstring;
    swapInfo.parameter ← @DP;
    -- versionident, debuggee, lspages, fill, mapLog set by Initialize
    -- level, loadstatepage set by MemorySwap
    swapInfo.mds ← GetMDS[];
    DO
      swapInfo.reason ← why;
      ProcessInternal.DisableInterrupts[];
      ToDebugger[@swapInfo];
      ProcessInternal.EnableInterrupts[];
      BEGIN
      IF decode[
	! CAbort => IF swapInfo.level > 0 THEN {why ← return; CONTINUE};
	  Quit => GOTO abort] THEN EXIT
      EXITS abort => SIGNAL CAbort
      END
      ENDLOOP
    END;

  -- Serious swapper

  level: INTEGER ← -1;

  ToDebugger: PORT [POINTER TO CPSwapDefs.ExternalStateVector]; -- formerly WBPort
  FromPilot: PORT RETURNS [POINTER TO CPSwapDefs.ExternalStateVector]; -- formerly CSPort

  pulsesPerTwentySeconds: LONG CARDINAL;

  MemorySwap: PROC [pESV: POINTER TO CPSwapDefs.ExternalStateVector] =
    BEGIN

    PKeys: PROC RETURNS [LONG POINTER TO Keys.KeyBits] = INLINE
      {RETURN[LOOPHOLE[KeyboardFace.keyboard]]};

    SwapIt: PROC = INLINE
      BEGIN
      savewdc, saveptc: UNSPECIFIED;
      xferTrapStatus: XferTrap.Status = XferTrap.ReadXTS[];
      xferTrapHandler: UNSPECIFIED = SDDefs.SD[SDDefs.sXferTrap];
      pESV.level ← level;
      pESV.loadstatepage ← loadStatePage; -- (possibly updated by loader)
      pESV.mds ← Inline.HighHalf[LONG[LOOPHOLE[1, POINTER]]];  -- ("1" since
	    -- 0 collides with NIL.)
      pESV.psb ← ProcessOperations.HandleToIndex[ProcessOperations.ReadPSB[]];
      SDDefs.SD[SDDefs.sXferTrap] ← Frame.MyLocalFrame[];  -- in case we are restarted in trap mode
      XferTrap.WriteXTS[off];
      -- Save processor state not captured in PDA:
      saveptc ← ProcessOperations.ReadPTC[];
      savewdc ← ProcessOperations.ReadWDC[];
      -- Manually save the state of the current process so that Copilot
      --   will be able to examine it just as if we were waiting:
      PSB.PDA.block[pESV.psb].link.vector ← FALSE;
      PSB.PDA.block[pESV.psb].context.frame ← Frame.MyLocalFrame[];
      DeviceCleanup.Perform[turnOff]; -- turn all devices off
      IF PilotSwitches.switches.h = down THEN
	BEGIN
	AddToStack: PROC [BOOLEAN] = MACHINE CODE BEGIN END;
	GetTOS: PROC RETURNS [BOOLEAN] = MACHINE CODE BEGIN Mopcodes.zDUP; END;
	RemoveFromStack: PROC RETURNS [BOOLEAN] = MACHINE CODE BEGIN END;
	AddToStack[TRUE];
	ProcessorFace.SetMP[PilotMP.cHang];
	WHILE GetTOS[] DO ENDLOOP;
	[] ← RemoveFromStack[];
	END
      ELSE IF ~DebuggerSwap.canSwap OR PilotSwitches.switches.r = down THEN
	BEGIN
	ProcessorFace.SetMP[PilotMP.cCantSwap];
	BootSwap.Teledebug[@DebuggerSwap.parameters.locDebugger];
	END
      -- OutLoad onto swatee, then boot Debugger.
      ELSE IF BootSwap.OutLoad[@DebuggerSwap.parameters.locDebuggee, restore] =
	      outLoaded THEN
	BEGIN OPEN DebuggerSwap, parameters;
	-- The next line should be in BootSwap.InLoad but blows up the compiler
	IF pMicrocodeCopy ~= NIL THEN DeviceCleanup.Perform[kill];
	BootSwap.InLoad[pMicrocodeCopy, pGermCopy, nGerm, @locDebugger]
	      -- never returns
	END;
      -- Restore processor state not captured in PDA:
      ProcessOperations.WriteWDC[savewdc];
      ProcessOperations.WritePTC[saveptc];
      -- Restore process state not captured in PDA:
      ProcessOperations.WritePSB[ProcessOperations.IndexToHandle[pESV.psb]];
      DeviceCleanup.Perform[turnOn]; -- turn devices back on
      level ← pESV.level;
      XferTrap.WriteXTS[xferTrapStatus];
      SDDefs.SD[SDDefs.sXferTrap] ← xferTrapHandler;
      ProcessorFace.SetMP[PilotMP.cClient]; -- announce our return
      END;
      DO
	pESV ← FromPilot[];
	-- Set our return link so Display Stack will work:
	Frame.SetReturnLink[LOOPHOLE[FromPilot, PrincOps.Port].dest.link↑];
	DO
	  SwapIt[];
	  SELECT pESV.reason FROM
	    kill => ProcessorFace.BootButton[];
	    showscreen =>
	      BEGIN
	      pulsesThen: LONG CARDINAL = ProcessorFace.GetClockPulses[];
	      prevSpare3: Keys.DownUp ← PKeys[][Spare3];
	      DO
	        IF (ProcessorFace.GetClockPulses[] - pulsesThen)
 	            > pulsesPerTwentySeconds THEN EXIT;
	        IF prevSpare3=down THEN prevSpare3 ← PKeys[][Spare3]
	        ELSE IF PKeys[][Spare3]=down THEN
	          {WHILE PKeys[][Spare3]=down DO --snoore-- ENDLOOP; EXIT}
	        ELSE NULL -- both up
	        ENDLOOP;
	      END;
	    ENDCASE => EXIT;
	  pESV.reason ← return;
	  ENDLOOP
	ENDLOOP
      END;

    --
    -- DeviceCleanup implementation

    linkage: PUBLIC DeviceCleanup.Linkage;
    InitializeDeviceCleanup: PROC =
      BEGIN
      reason: DeviceCleanup.Reason;
      pItem: POINTER TO Item;
      LOOPHOLE[AwaitPerform, PrincOps.Port].dest ← Frame.GetReturnLink[];
      linkage.Perform ← LOOPHOLE[@AwaitPerform];
      DO
	linkage.Await ← LOOPHOLE[Install];
	reason ← AwaitPerform[];
	ProcessorFace.SetMP[PilotMP.cCleanup];
	linkage.Await ← LOOPHOLE[Frame.MyLocalFrame[]];
	FOR pItem ← pItemFirst, pItem.pItemNext WHILE pItem ~= NIL DO
	  [] ← pItem.Procedure[reason] -- value should be pItem
	  ENDLOOP
	ENDLOOP
      END;

    AwaitPerform: PORT RETURNS [reason: DeviceCleanup.Reason];

    Install: ENTRY PROC [pItem: POINTER TO Item] =
      BEGIN
      fCaller: PrincOps.FrameHandle = Frame.GetReturnFrame[]; -- cleanup procedure
      pItem↑ ← [pItemNext: pItemFirst, Procedure: LOOPHOLE[fCaller]];
      pItemFirst ← pItem;
      Frame.SetReturnLink[fCaller.returnlink]
      END;

    Item: PUBLIC TYPE = RECORD [
      pItemNext: POINTER TO Item,
      Procedure: PROC [DeviceCleanup.Reason] RETURNS [POINTER TO Item] ← NULL];
    pItemFirst: POINTER TO Item ← NIL; -- list of waiting cleanup procedures

    --
    -- Initialization

    InitializePilotNub: PUBLIC PROC [
      pageLoadState: Environment.PageNumber,
      countLoadState: Environment.PageCount,
      pVMMapLog: LONG POINTER --TO VMMMapLog.Descriptor--] =
      BEGIN
      InitializeDeviceCleanup[];

      loadStatePage ← pageLoadState;
      -- swapInfo.state set in caller of MemorySwap
      --   (e.g. CoreSwap, WorryBreaker, WorryCallDebugger)
      -- swapInfo.reason set in caller of MemorySwap
      --   (e.g. CoreSwap, WorryBreaker, WorryCallDebugger)
      -- swapInfo.level set in MemorySwap
      -- swapInfo.parameter set by debugger and obeyed by CoreSwap
      swapInfo.versionident ← CPSwapDefs.VersionID;
      -- swapInfo.loadstatepage set in MemorySwap
      swapInfo.lspages ← countLoadState;
      swapInfo.mapLog ← pVMMapLog;
      swapInfo.mds ← GetMDS[]; -- delete this when WorryBreak, etc. set the field
      swapInfo.fill ← ALL[0];
      LOOPHOLE[PSB.PDA.available, CPSwapDefs.SwapInfo].externalStateVector
	  ← @swapInfo;
      InitBreakBlocks[];
      BEGIN OPEN SDDefs;
      pSD: POINTER TO ARRAY [0..0) OF UNSPECIFIED = SD;
      pSD[sProcessBreakpoint] ← ProcessBreakpoint;
      pSD[sUncaughtSignal] ← Catcher;
      pSD[sInterrupt] ← Interrupt;
      pSD[sCallDebugger] ← CallDebugger;
      pSD[sBreak] ← Break;
      pSD[sAlternateBreak] ← WorryBreaker[];
      pSD[sWorryCallDebugger] ← WorryCallDebugger[];
      pulsesPerTwentySeconds ←
	LONG[20]*1000000*100/ProcessorFace.microsecondsPerHundredPulses;
      LOOPHOLE[ToDebugger, PrincOps.Port].out ← @FromPilot;
        -- connect ToDebugger to FromPilot
      LOOPHOLE[FromPilot, PrincOps.Port].out ← @ToDebugger;
        -- connect FromPilot to ToDebugger
      pSD[sCoreSwap] ← @FromPilot;
      LOOPHOLE[FromPilot, PrincOps.Port].in ← MemorySwap;
      ToDebugger[NIL]; -- allocate frame for MemorySwap
      END;
      END;

    END.


LOG
(For earlier log entries see Pilot 4.0 archive version.)

April 29, 1980  9:50 PM   Forrest   Move in  Memory swap stuff from Traps

May 3, 1980  2:29 PM   Forrest   Mesa 6.0

June 23, 1980  6:26 PM   McJones   Fix WorryCallDebugger bug; OISProcessorFace=>ProcessorFace; make TrueCondition INLINE; allocate break blocks in global frame

July 28, 1980  6:46 PM   McJones   New KeyboardFace, Keys

July 31, 1980  7:21 PM   Forrest   Implement Hang switch

August 28, 1980  2:59 PM   McJones   Merge InterruptKey with PilotNub; timeout userscreen after twenty seconds; SetMP[cCleanup]

August 27, 1980  4:00 PM   McJones   New PSB, ProcessOperations, XferTrap

October 3, 1980  1:30 PM   Forrest   Reverse sense of i switch; add code to dally during userscreen as long as swat held down; Jim Sandman fixed conditional Break logic

December 10, 1980  9:58 AM   Knutsen   New PDA layout. externalStateVector now not defined in PSB.mesa.

January 19, 1981  5:03 PM   Knutsen   Twiddle process priorities.

January 30, 1981  5:35 PM   Luniewski   Make conditional breakpoints at procedure entry/exit work.

February 4, 1981  11:51 AM   Knutsen   PrincOps fields changed names.

25-Feb-81 16:24:10	Gobbel	Make Interrupt use correct SwapReason.

31-Mar-81 11:41:06	Sandman	Correct XferTrapStatus check and BreakPoints.

March 31, 1981  12:46 PM   Luniewski State vectors can't be in local 0 or 1.

June 16, 1982 5:35 pm	Levin	WorryCallDebugger indirection to get links pushed on stack.

May 11, 1983 2:41 pm	Birrell	SwapIt clears link.vector; no indirect return link in call stack.