:TITLE[Fault]; *Fault handler. 10 September 1982 by Ed Fiala %Problems: 1) PFetch4; NextInst will normally fault abort at MesaRefillLoc and will be treated as a NextInst refill fault instead of ordinary reference; can improve things by ensuring task 0 from PipeReg2 (almost in SALUF?). 2) Try to do ReadPipe only on MC12Err path, if that path not made longer. 3) Do something useful in the mi at MC12Err+2. 4) MP report of storage failures would be desirable. 5) If branch condition on first ReadPipe mi could be eliminated (2 above), then could pick off MC1 crash in that mi by testing for FFault odd; then test for CTask=0 in the bare Disp at MC12Err+2 and branch on ALU#0 in the dispatch table to an mi that does RTMP_. This would save 2 cycles on the slowest paths. DELAY ON FAULTS until tasking MUST BE MINIMIZED to avoid data lates on io devices. Although present io devices eventually recover from data lates, keyboard input is lost (primarily on Star keyboards--CSL keyboards are rarely affected) and display jitter occurs; there are other potential problems. In computing time for an MC1 fault, allow ~6 cycles after the PFetch/PStore; the mi after that is aborted until the fault starts; the abort lasts ~10 cycles, unaffected by suspended cycles while transport for previous references takes place. Then the code here beginning at "FaultOccurred" is executed. The assumption is made that only the emulator task can legitimately have references that fault, but the fault may not occur until another task is running. In the event the emulator was running at the time of a fault, it is restarted at a fault address and tasks after a delay of 51 to 69 cycles. In this case, io task timing is worsened by ~61 to ~79 cycles minus the time to the next normal emulator tasking point. The next two emulator tasks occur after 11 and 4 cycles, respectively, which somewhat mitigates the long time to task. If an io task was running, however, the emulator TPC is changed to a fault address and the state of the io task is restored after ~83 to ~100 cycles; in this case, time in the fault handler is totally additive to worst case timing in the absence of a fault. An even longer time in the fault handler (up to ~110 cycles) occurs when an io task was running at the onset of the fault and doing a "Return" to the emulator. However, this only happens when no other io task was requesting service at the onset of the fault, so it is not as bad as the additive ~100 cycles. Code here replaces that in Kernel or Initial performing the same function. This code determines what to do based on the type of error, and bits in FFault, which are: 0: MC2 errors Return if 1, crash if 0. The return option is used by Initialize.Mc during storage initialization when WithMidas=1 (i.e., on debugging systems, not on release systems). This bit is reserved for Initial's MemInit storage diagnostic on release systems. 2: H4 parity errors ignored if 0, crash if 1 (3 MB Ethernet generates them routinely) 3: Midas is present (1), so "crash" means breakpoint, else put a code in MP and GoTo[.] until booted. 15: MC1/StackOvf errors handled by notifying PFEntry in emulator (1), or by crashing (0); the Alto emulator crashes, the Mesa emulator uses a notify for these errors [On 1 June 1982, this bit wound up in the wrong state after LoadRAM.]. % SetTask[17]; LoadPageExternal[0], GoToExternal[377], At[0]; *Buffer refill trap FaultOccurred: T _ APCTask&APC, At[1]; *Must save APC first RXAPC _ T; T _ (CTask&NCIA) xnor (170000C); RXCTask _ T; *It is necessary to ensure that StkP .ne. 17b here because, even though *ResetErrors clears stack overflow, StkP .eq. 17b instantly regenerates it *causing an endless loop back to location 1. So set StkP to a value that *will be used later. T _ RCy[Page&Par&Boot,4]; *LoadPage is necessary because, after ResetErrors, the Page register will no *longer be disabled by the error condition. RXPPB _ T, LoadPage[FaultPage], GoTo[NotStkFault,H2Bit8']; T _ (SStkP&NStkP) xor (377C); OnPage[FaultPage]; RXSTK _ IP[RXCTask]C; StkP _ RXSTK, RXSTK _ T, NoRegILockOK; *aluresult, saluf (both read complemented) NotStkFault: T _ (ALUResult&NSALUF) xnor (0C); RXALU _ T, ResetErrors; *Test first for time critical MC1/2 error without any accompanying StkOvf, *CSPE, or RMPE. Can't change ALU branch conditions until after ResetErrors. *The four bits tested here are the Parity register (Stack overflow, CS parity *error, RM parity error, and Memory error. Memory errors are time-critical, *so test for them first. LU _ (LdF[RXPPB,10,4]) - 1; *Get pipe A (Timing for this mi = 8 cycles on MC12Err) **Can loop to FaultOccurred without executing next mi on two MC2 errors. ReadPipe[PipeReg], FreezeResult, GoTo[MC12Err,ALU=0]; LU _ (RXPPB) and (140C), Skip[ALU>=0]; *Assume Midas breakpoint--i.e., SetFault function executed. T _ BrkPCrash, GoTo[CTaskCrash]; T _ RMCSCrash, GoTo[BadHWErr1,ALU#0]; *Jump if CS or RM PE *Have to do ResetMemErrs in case stack overflow occurred in conjunction with *an MC1/MC2 error. :UNLESS[LispMode]; ********************************* FFault, ResetMemErrs, GoTo[StackTrap,R Odd]; *StkOvf only :ENDIF; ******************************************** T _ StkCrash, GoTo[Crash]; *CS or RM parity error, possibly in combination with other errors. BadHWErr1: T _ (LdF[RXPPB,10,4]) + T, GoTo[Crash]; CTaskCrash: T _ (LdF[RXCTask,0,4]) + T, GoTo[Crash]; *The computation here is CrashCode+PipeTask = CrashCode+(PipeTask' xor 17b) *= CrashCode+(17b-PipeTask') = (CrashCode+17b)-PipeTask'. The value in T *when we get here is CrashCode+17b. PipeTaskCrash: T _ (LdF[PipeReg2,10,4]) - T; T _ (Zero) - T, GoTo[Crash]; %If Midas is not present, display the maintenance panel code in T and do a GoTo[.] until booted. Otherwise, do not modify the MP and transfer control to the Midas Kernel. Except on simple breakpoints, save the CrashCode and memory error information in RM 100-107 (MP crash code must be .ls 400b to see it from Midas). % :IF[WithMidas]; ********************************* ***NOTE: RM 352-353 will be smashed by PNIP. Crash: LU _ LdF[FFault,3,1], Call[Crash1]; GoTo[.]; *Wait for boot... Crash1: PipeReg5 _ (LSh[PipeReg5,10]) or T, GoTo[PNIP,ALU=0]; *Locate on page 17 with the Midas Kernel so that this code can be easily *overwritten when Midas isn't present. Reformat saved Pipe into RM 100-107 *for Midas. Note that pipe info (other than crash code and Task number) is *only interesting if CrashCode is 200d to 215d (an MC2 error). LoadPage[MidasPage]; LU _ LdF[RXPPB,10,1]; OnPage[MidasPage]; RXPPB _ LCy[RXPPB,4], GoTo[.+3,ALU#0]; *Unrotate RXPPB for Midas T _ (SStkP&NStkP) xor (377C); RXSTK _ T; LU _ LdF[RXPPB,4,4]; RTMP _ Or[And[IP[MapEntry],360],And[Sub[IP[MapEntry],1],17]]C, GoTo[Crash2,ALU#0]; :IF[IFE[MidasPage,17,0,1]]; ********************* LoadPageExternal[17]; :ENDIF; ***************************************** **Unfixup RXCTask for Midas Kernel. RXCTask _ (RXCTask) xnor (170000C), GoToExternal[MidasBreakLoc]; Crash2: StkP _ RTMP; T _ LdF[PipeReg,11,7]; *Map row address' PipeReg1 _ (LSh[PipeReg1,7]) xnor T; *Map row'' u Map column'' T _ LdF[PipeReg1,2,16], Call[FltPsh]; *MapEntry_page no. T _ (LdF[PipeReg2,10,4]) xor T, Call[FltPsh]; *TaskNumber T _ (LdF[PipeReg2,14,4]) xor T, Call[FltPsh]; *RefType T _ RHMask[PipeReg5], Call[FltPsh]; *CrashCode *Card no. (0..7) into CardNumber; offset by 5 to get actual board *number in card cage. NOTE: 14b in Card implies that this part of *the pipe is not filled by the reference. (X xor 7) + 5 = 14b - X. T _ 14C; T _ (LdF[PipeReg5,4,3]) - T; T _ (Zero) - T, Call[FltPsh]; *CardNumber *Map Flags (LogSE, WP, Dirty, Ref) into MapFlags T _ (LdF[PipeReg5,0,4]) xor T, Call[FltPsh]; T _ LdF[PipeReg4,12,6]; *Main column address (6 bits) PipeReg3 _ (LSh[PipeReg3,6]) or T; *x,x,Blk.1',,main row addr PipeReg5 _ LdF[PipeReg5,7,1]; T _ LdF[PipeReg3,2,16]; PipeReg5 _ (LSh[PipeReg5,16]) or T; *And Blk.0... *This is the (15-bit) quadword number within a 128k card. *Bits 1 and 2 give the block number. T _ (PipeReg5) xnor (100000C), Call[FltPsh]; *QuadAddr T _ RSh[PipeReg,10], Call[FltPsh]; *Interesting syndrome into 107 :IF[IFE[MidasPage,17,0,1]]; ********************* LoadPageExternal[17]; :ENDIF; ***************************************** **Unfixup RXCTask for Kernel. RXCTask _ (RXCTask) xnor (170000C), GoToExternal[MidasFaultLoc]; FltPsh: UseCTask, Stack&+1 _ T; T _ 17C, Return; :ELSE; ****************************************** Crash: Call[PNIP]; GoTo[.]; :ENDIF; ***************************************** OnPage[FaultPage]; % There are a number of bugs and non-features in the MC1/MC2 error reporting hardware which account for the peculiar way things are done here; the comments here are based upon my reading of the hardware drawings and might be wrong: 1) ResetMemErrs resets the H4PE, MOB, MC1ErA, MC1ErB, MC2ErA, and MC2ErB flipflops. Also, the next reference reloads the MC1ErA and MC1ErB flipflops. The next reference using the same pipe will reload the MC2ErA or MC2ErB flipflop. H4PE can only be reset by ResetMemErrs. 2) H4PE's do not set MC1ErA or MC1ErB, so it is impossible to report the reference and task number for these with any certainty. Hence, the MP code uses +CTask rather than +PipeTask. 3) I am not sure whether or not MOB errors are indicated correctly in MC1ErA and MC1ErB. Hence, they report +CTask rather than +PipeTask in the MP. 4) MC2ErA and MC2ErB have pipe-specific clocks, so an error indication will remain true until another reference uses the same pipe. This means that the reference after one causing an MC2 error won't disturb its error indication. 5) MC1ErA and MC1ErB have a common clock, and only one of these can be indicated at a time. The hardware is SUPPOSED to fault before another reference starts, but if the preceding reference was a PFetch4 with error correction which didn't fault, and if the transport for that reference occurred between the faulting reference and the fault, then one more instruction will be executed before the fault task executes at location 1. This instruction could be another reference. If an extraneous reference does take place, the original MC1ErA/B indication would be replaced by the results of the extraneous reference, possibly getting the MCNoneCrash MP code. 6) MC2 is never started if MC1 gets a fault, so it is impossible to have both MC1ErX and MC2ErX indicated at one time. Timing = 26 cycles from loc 1 to here. % MC12Err: Dispatch[PipeReg,4,2]; *Dispatch on H4pe, MapBnd ***This Dispatch is only useful on the MC1/MC2 path. *Dispatch on MC2ErA', MC2ErB', MC1ErA', and MC1ErB' bits Dispatch[PipeReg,0,4], Disp[.+1]; Disp[MC2ErAB], DispTable[4]; *None *23rd? or 24th? bit of memory address = 1 causes MOB. T _ MOBCrash, FFault, DblGoTo[MOBTrap,CTaskCrash,R Odd]; *MOB %Ignore improbably legit MOB&H4PE on IOStore4 to flush frequently occurring fake MOB&H4PE by 3MB Ethernet input task. Some 3MB Ethernet controllers cause H4PE's on Input's and IOStore4's erroneously; XWTask keeps control in xiTask so that the H4PE will be reported no later than the 1st mi of the next task to run, so that LoadPage errors won't happen. We could refine this check by continuing from H4PE's only when xiTask is running, but this would require one additional NOP in xiTask after IOStore4's or Input's, and it wouldn't work on gateways with more than one Ethernet controller. % LU _ LdF[FFault,2,1], Skip; *H4PE LU _ LdF[FFault,2,1]; *H4PE&MOB *Check 'ignore H4PE' bit in FFault. ResetMemErrs, Skip[ALU=0]; T _ H4PECrash, GoTo[CTaskCrash]; T _ LdF[RXCTask,4,4], GoTo[T17RestoreB]; MC2ErAB: * ResetMemErrs, GoTo[MC22Die], At[MC12,0]; *MC2A/B & MC1A/B * ResetMemErrs, GoTo[MC22Die], At[MC12,1]; *MC2A/B & MC1A * ResetMemErrs, GoTo[MC22Die], At[MC12,2]; *MC2A/B & MC1B ResetMemErrs, GoTo[MC22Die], At[MC12,3]; *MC2A/B * ResetMemErrs, FFault, * DblGoTo[MC2ErARet,MC2ErA,R<0], At[MC12,4]; *MC2A & MC1A/B * ResetMemErrs, FFault, * DblGoTo[MC2ErARet,MC2ErA,R<0], At[MC12,5]; *MC2A & MC1A ResetMemErrs, FFault, DblGoTo[MC2ErARet,MC2ErA,R<0], At[MC12,6]; *MC2A & MC1B ResetMemErrs, FFault, DblGoTo[MC2ErARet,MC2ErA,R<0], At[MC12,7]; *MC2A * ReadPipe[PipeReg,,FFault], ResetMemErrs, * DblGoTo[MC2ErBRet,MC2ErB,R<0], At[MC12,10]; *MC2B & MC1A/B ReadPipe[PipeReg,,FFault], ResetMemErrs, DblGoTo[MC2ErBRet,MC2ErB,R<0], At[MC12,11]; *MC2B & MC1A * ReadPipe[PipeReg,,FFault], ResetMemErrs, * DblGoTo[MC2ErBRet,MC2ErB,R<0], At[MC12,12]; *MC2B & MC1B ReadPipe[PipeReg,,FFault], ResetMemErrs, DblGoTo[MC2ErBRet,MC2ErB,R<0], At[MC12,13]; *MC2B * ResetMemErrs, FFault, * DblGoTo[MC1Notify,MC1Die,R Odd], At[MC12,14]; *MC1A/B ResetMemErrs, FFault, DblGoTo[MC1Notify,MC1Die,R Odd], At[MC12,15]; *MC1A ReadPipe[PipeReg,,FFault], ResetMemErrs, DblGoTo[MC1Notify,MC1Die,R Odd], At[MC12,16]; *MC1B T _ MCNoneCrash, GoTo[Crash], At[MC12,17]; *None MC22Die: T _ MC22Crash, GoTo[Crash]; MC1Die: T _ MC1Crash, GoTo[PipeTaskCrash]; %Set FaultParm to indicate cause of trap: -1 => Memory Out of Bounds negative => write protect positive => page fault Reference type put in NSALUF for fault handling later. NOTE: must not attempt to leave the fault results in PipeRegx because another fault (H4PE or LogSE) might clobber PipeRegx when an io task runs prior to servicing this fault. % MC1Notify: T _ (PipeReg) and (177C); *Low 7 bits of VPage *(High 7 bits of VPage' or low 7 bits)'; bits 0 and 1 wind up both 1. PipeReg1 _ T _ (LSh[PipeReg1,7]) xnor T; LU _ LdF[PipeReg5,12,1]; *Test dirty': 0=> page fault FaultParm _ T, Skip[ALU#0]; FaultParm _ LdF[FaultParm,2,16], Skip; *page fault *Bits 0 and 1 in FaultParm are both 1 after the xnor and we want them to *be 2 so that VPage = 37777b won't be confused with an MOB error. FaultParm _ (FaultParm) and not (40000C); *write protect fault MFault: LU _ LdF[RXCTask,0,4]; T _ (PipeReg2) or not (17C), DblGoTo[TestTA,TestTB,ALU#0]; MOBTrap: *Set trap parameter for MOB FaultParm _ (Zero) - 1, GoTo[MFault]; :UNLESS[LispMode]; ********************************* StackTrap: LU _ LdF[RXCTask,0,4]; T _ Xor[StkCrash!,377]C, DblGoTo[TestTA,TestTB,ALU#0]; :ENDIF; ******************************************** %Notify emulator at EmNotifyA if emulator was interrupted, else at EmNotifyB. SALUF is used later at CheckStackTrap to distinguish Stack errors from others and in other fault handling to give RefType. Time from location 1 through this non-tasking return: 45 or 46 cycles on MOB; 51 or 52 cycles on Stack overflow or underflow; 55 to 63 cycles on page fault; 56 to 64 cycles on write protect fault. % TestTB: RTMP _ LoA[EmuNotifyLoc], Skip; TestTA: RTMP _ LoA[NonEmuNotifyLoc]; APCTask&APC _ RTMP; SALUF _ T, Return; :IF[WithMidas]; ********************************* MC2ErARet: Return; MC2ErBRet: Return; MC2ErA: T _ LHMask[MemSyndrome], Skip; MC2ErB: T _ LSh[MemSyndrome,10]; PipeReg _ (RHMask[PipeReg]) or T; T _ MC2Crash, GoTo[PipeTaskCrash]; :ELSE; ****************************************** MC2ErARet: MC2ErBRet: Return; MC2ErA: MC2ErB: GoTo[T17RestoreA]; :ENDIF; ***************************************** %T17CheckAPC resumes an interrupted non-emulator task after the emulator's TPC has been changed; T17RestoreA and T17RestoreB are the entries used when the emulator's TPC has not been changed. Because APC is used not only for tasking and returning but also for APCTask&APC_ and for dispatches, APC must sometimes be restored to the value saved at the onset of the trap--otherwise, the mi after a Dispatch or APCTask&APC_ would continue incorrectly. However, if the mi being continued contains a Return, and if APCTask=0, then control will go to the restored APC rather than the emulator's new TPC. Consequently, if APCTask=0, the code below checks the mi at the continue address for a Return; if so, APC is changed to the emulator's new TPC; if not, APC is restored to its trap value. Delay from location 1 through the Restore below has been: 44 cycles on H4PE; 72 to 82 cycles on Stack overflow or underflow; 73 to 82 cycles on MOB; 83 to 99 cycles on page fault; 84 to 100 cycles on write protect fault. % T17CheckAPC: LU _ LdF[RXAPC,0,4], At[ContNonEmuLoc]; *test saved APCTask *Only the two low-order bits of T are significant for ReadCS. T _ 5C, GoTo[T17RestoreA,ALU#0]; *Saved APC is for emulator, must read aborted mi. APCTask&APC _ RXCTask; ReadCS; *This mi need not be at an even mi because task 17b's TPC is unimportant. LU _ (LdF[CSData,6,3]) - T - 1; *(JC field) - 6; Return = 6 T _ LdF[RXCTask,4,4], GoTo[T17RestoreB,ALU#0]; RXAPC _ LoA[NonEmuPFLoc], GoTo[T17RestoreB]; *aborted mi does Return. %Restoring control to a task, as done here, is safe against every type of interruption except between LoadPage and the subsequent mi or between a reference and the next mi using the bypass kludge. However, the error check here will crash distinctively for a LoadPage problem, and since a following reference is aborted if a page or write protect fault is about to happen for a PREVIOUS reference, intervention between a reference and the bypass kludge should only be possible in one of the following three situations: 1) A Preceding PFetch4 experiences error correction with all 8 cycles of suspension for its transport occurring between a reference and the next mi using the bypass kludge, and that reference itself page faults; but page faults by io tasks aren't allowed, so this won't happen. 2) Correctable error logging occurs between a reference and the bypass kludge (we don't ever use LogSE). 3) An H4PE intervenes between a reference and the bypass kludge; this is illegal except for the 3mb Ethernet where enough Nop's after each Input and IOStore4 ensure that any H4PE happens safely. % T17RestoreA: T _ LdF[RXCTask,4,4]; *Compare page bits T17RestoreB: LU _ (LdF[RXPPB,4,4]) xor T; *with saved page register T _ RXALU, Skip[ALU=0]; *result register T _ LPCrash, GoTo[CTaskCrash]; *LoadPage error APCTask&APC _ RXCTask; Return, Restore, A _ RXAPC, LU _ T, NoRegILockOK; *back to faulted Task SetTask[0]; NotifyBack: xBuf1 _ (xBuf1) or (HiA[ContNonEmuLoc,17]); APCTask&APC _ xBuf1, xBuf1 _ T, NoRegILockOK; *GoTo[PFExit] by MesaRefill (MesaJ.Mc) and by PNIP (Initialize.Mc). PFExit: Return; EmNotifyB: UseCTask, xBuf _ T, At[NonEmuNotifyLoc]; T _ APCTask&APC; *Prepare to notify back to Task 17, location T17CheckAPC xBuf1 _ LoA[ContNonEmuLoc], Call[NotifyBack]; *PF handling starts here if non-emulator was interrupted. *If page fault timing is not good enough to prevent UTVFC data lates in the *worst case, tasking quickly here will help avoid data lates 2/3 of the time, *so the next two calls are brief (11 cycles and 4 cycles). T _ StkCrash, Call[CheckStackTrap], At[NonEmuPFLoc]; *xBuf2 _ Saved CIA and restore StkP. T _ (Stack) and not (170000C), Call[StkPExch]; *Cannot be buffer refill trap or location 0 abort GoTo[CheckMemStat]; %SALUF holds either [PipeReg2 u 360b] (on a page, write protect, or MOB fault) or StkCrash' (stack overflow (StkP=17b) or underflow (StkP=0)). NSALUF then reads either RefType or StkCrash. First check for a stack error; if not, save StkP in xBuf2 and point StkP at task 17's RXCTask register; the caller will then save CIA of the aborted mi and restore StkP. This is done in two short subroutines rather than one longer one so io tasks which may have fallen behind during the long page fault service will have a better opportunity to catch up. % :IF[LispMode]; ************************************* CheckStackTrap: xBuf2 _ IP[RXCTask]C; :ELSE; ********************************************* CheckStackTrap: LU _ (NSALUF) xor T; xBuf2 _ IP[RXCTask]C, GoTo[StackErrorz,ALU=0]; :ENDIF; ******************************************** T _ (SStkP&NStkP) xor (377C); StkPExch: StkP _ xBuf2, xBuf2 _ T, NoRegILockOK, Return; :UNLESS[LispMode]; ********************************* *We have a stack error. Cause the trap immediately. Restore StkP to *the value in SStkP saved at the beginning of the opcode. ***Let the PC fall where it may. StackErrorz: *test SStkP for MaxStack+1 or more LU _ (SStkP&NStkP) - (LShift[Add[MaxStack!,1],10]C); T _ SStkP, Skip[Carry']; T _ MaxStack; xBuf2 _ T, LoadPage[opPage3]; StkP _ xBuf2; OnPage[opPage3]; T _ sStackError, GoTo[kfcr]; :ENDIF; ******************************************** EmNotifyA: UseCTask, xBuf _ T, At[EmuNotifyLoc]; *xBuf _ emulator's T %FINALLY, task after the following delays: 51 or 52 cycles on emulator MOB; 57 or 58 cycles on stack overflow/underflow; 61 to 68 cycles on page fault; 62 to 69 cycles on write protect fault. % T _ APCTask&APC, Task; *xBuf1 _ emulator's TPC and Task xBuf1 _ T; *PF handling starts here if the emulator was interrupted. Note that if the *emulator was NOT interrupted, then the fault cannot have come from buffer *refill. Since control entered here, the emulator's PC is in RXCTask. T _ StkCrash, Call[CheckStackTrap]; T _ (Stack) and not (170000C), Call[StkPExch]; %At this point we have: xBuf emulator's T at the time of the fault; xBuf1 emulator's TPC; xBuf2 CIA of the aborted mi. The major problem with faults is to determine the PC to store in the frame, and whether to continue the opcode, or cause the trap immediately. The cases are: 1) The fault was detected at location 0, the 1st mi of the buffer refill trap. In this case, buffer refill was just starting when some previous reference faulted. Treat this as in case 7 below. 2) A PFetch4 fault occurred on page 0 and the emulator's TPC points at the 1st mi of a bytecode (TPC = 01xxxxxxxx01). It is assumed that the fault is due to a NextData/NextInst buffer refill; SStkP and PCX do not yet reflect advance from the previous bytecode, so the trap is started with PC = 2*PCB - 1 (NextData/NextInst was accessing an operand from location 0 of the buffer, so the opcode was byte 7 of the previous buffer, but PCB _ (PCB) + (4C) occurred before the fault) and with the current value of StkP rather than SStkP. 3) A PFetch4 fault occurred on page 0 and the emulator's TPC points elsewhere than as in case 2. In this case, it is assumed that the fault is due to a NextData or NextInst buffer refill which are differentiated by the low bit of F1 in the mi pointed at by the emulator's TPC. If the fault is due to a NextData, nothing special is done, but for a NextInst, IBuf to IBuf3 are set to -1, PCF to 0, and control is sent to the NextInst so other work done by the mi containing the NextInst and the mi after that can be completed before the trap. Control then goes to opcode 377, which will cause the trap with PC = 2*PCB + PCX - 1. 4) A PFetch4 fault occurred on page 6. This is a jump opcode buffer refill handled as in case 3 without zeroing PCF. 5) The fault was due to an Xfer buffer refill (MemStat[13:15] = XferFixup). This is handled just like a jump (case 4). 6) The fault occured during the early phases of Xfer. We want to back out and redo the opcode, but CODE may have changed and we need it to compute the PC to save. Call Loadc to reload from the current LOCAL. 7) If none of these situations hold, the PC is (PCB*2) + q, where q = if (PCF>=PCX) then PCX-1 else PCX-9 (if PCF store, 0=> fetch *Count+1; if fetch, done with fixup. Stack _ (Stack) + 1, GoTo[FPCOz,ALU=0]; Stack&-1, Call[DecGlorp]; *Source - 1 Stack&+2, Call[DecGlorp]; *Dest - 1 T _ (PCXReg) - 1, GoTo[FPCOx]; DecGlorp: Stack _ (Stack) - 1, Return; FixPCOnly: T _ (PCXReg) - 1, At[FixDisp,Normal!]; *normal PC fixup FPCOx: LU _ (PCFreg) - T, Skip[ALU>=0]; T _ 7C, GoTo[.-1]; *PCX was 0; opcode started in prev. quadword *If PCF .eq. 7 then we already backed up PCB, *so don't subtract 4 from PCB again. RTemp _ T, Skip[ALU>=0]; PCB _ (PCB) - (4C); *PCX large, PCF small = > prev. quadword PCF _ RTemp; *PCF is always PCX-1, only PCB is in doubt %FaultParm has been set up by the Trap handler: -1 => Map Out of Bounds negative => write protect, page in low 14 bits positive => page fault, page in low 14 bits Here PCB,PCF is correct pc to save for trap. It will be done through KFCB. % StartMemTrap: T _ SStkP; SMTrpx: RTemp _ IP[FaultParm]C, Call[FSetStkP]; T _ (Stack) and not (140000C); LU _ (Stack) + 1; xfOTPReg _ T, Skip[ALU>=0]; T _ sWriteProtect, Skip; *Write protect fault T _ sPageFault; *Page fault or MOB LoadPage[opPage3]; StkP _ RTemp, GoToP[kfcr]; :ENDIF; ******************************************** :END[Fault];e12(1795)\f5 25433f0 245f5 28f0 23f5 26f0 343f5 88f0 35f5 554f0 100f5 57f0 243f5 15f0 23f5 27f0 144f5 255f0 81f5 628f0 29f5 56f0 16f5