VMFaultsImpl.mesa
Copyright © 1985 by Xerox Corporation. All rights reserved.
created by Levin
Bob Hagmann, January 30, 1985 10:54:09 am PST
Russ Atkinson (RRA) October 29, 1985 2:22:03 pm PST
DIRECTORY
BootStartList USING [EntryPointer, Enumerate, IndexToEntryPointer, IndexToSpaceEntryPointer, Proc],
DebuggerSwap USING [CallDebugger, WorryCallDebugger],
GermSwap USING [switches],
MPCodes USING [vmInitialized],
PrincOps USING [AV, AVItem, FaultIndex, flagsVacant, FrameHandle, LargeReturnSlot, NoTimeout, PageValue, PDA, PsbHandle, PsbNull, qFrameFault, qPageFault, qWriteProtectFault, Queue, QueueEmpty, StateVector],
PrincOpsUtils USING [DisableInterrupts, EnableInterrupts, FrameSize, Free, GetReturnFrame, LongEnter, LongExit, LongReEnter, LongWait, LowHalf, MyLocalFrame, PsbIndexToHandle, Requeue, SetReturnFrame],
Process USING [Detach, DisableTimeout, priorityFaultHandlers, priorityForeground, SecondsToTicks, SetPriority, SetTimeout, Ticks, Yield],
ProcessorFace USING [SetMP],
VM USING [AddressFault, AddressForPageNumber, CantDoIO, DataState, Free, IOErrorType, Interval, PageCount, PageNumber, PageNumberForAddress, PagesForWords, PageState, SimpleAllocate, State, SwapIn, WordsForPages, WriteProtectFault],
VMEmergency,
VMInternal USING [AllocateRealMemoryForLocalFrames, AllocateVirtualMemoryInternal, allocationLock, AllocationOutcome, AnyFrameSizeIndex, FrameHeapPiece, FrameHeapPieceHeader, FsiFrame, GetPageValue, GetVMMap, InOut, LargeFrame, LargeFrameHeader, largeFrameThresholdFsi, lastVMPage, NormalFrameSizeIndex, PageStateFromFlags],
VMSideDoor USING [rmPages],
VMStatistics USING [];
VMFaultsImpl: MONITOR
LOCKS monitor^ USING monitor: POINTER TO MONITORLOCK
IMPORTS BootStartList, DebuggerSwap, GermSwap, PrincOpsUtils, Process, ProcessorFace, VM, VMEmergency, VMInternal, VMSideDoor
EXPORTS VMInternal, VMStatistics
= BEGIN OPEN PrincOps;
Global Variables
largeFramesLock: MONITORLOCK;
largeFramesInUse: CONDITION;
largeFrameTimeout: Process.Ticks = Process.SecondsToTicks[1];
Some VM tuning parameters.
The desired size of the interval to swapin around a faulted page. A size of 1 means only swapin the faulted page. Sizes are set independantly by type of page faulted: readOnly pages (code) and readWrite pages (data). By convention ReadOnlyPageInSize >= ReadWritePageInSize. The values of these entries can be changed during initialization.
ReadOnlyPageInSize: INT ← 4 ;
ReadWritePageInSize: INT ← 2 ;
Exports to VMStatistics
pageFaults, writeFaults: PUBLIC INT ← 0;
frameFaults: PUBLIC INT ← 0;
smallFramesAllocated, frameHeapExtensions: PUBLIC INT ← 0;
largeFramesAllocated, largeFramesFreed: PUBLIC INT ← 0;
Exports to VMInternal
frameHeapPieceList: PUBLIC VMInternal.FrameHeapPiece ← NIL;
largeFrameList: PUBLIC VMInternal.LargeFrame ← NIL; -- protected by largeFramesLock
Fault-Handling Processes
Debugging Info
debugInfo: LONG POINTER TO DebugInfo ← NIL;
DebugInfo: TYPE = RECORD [
lastFaultedPage: VM.PageNumber ← 0,
lastAddressFaultPage: VM.PageNumber ← 0,
addressFaultCounter: INT ← 0,
lastPageFaultIndex: [0..FaultsInRing) ← FaultsInRing-1,
retries: INT ← 0,
frameAllocs: ARRAY VMInternal.NormalFrameSizeIndex OF INTALL[0],
faultRing: ARRAY [0..FaultsInRing) OF PageFaultInfo ← ALL[PageFaultInfo[-1, NIL, GetStateHelper[0]]]
];
FaultsInRing: NAT = 16;
PageFaultInfo: TYPE = RECORD [
page: VM.PageNumber,
addr: LONG POINTER,
state: PrincOps.PageValue];
PageFaultProcess: PROC = {
Reserve a state vector for this process
Process.SetPriority[Process.priorityFaultHandlers];
DO
process: PsbHandle = WaitForFaultee[qPageFault];
faultAddress: LONG POINTER = PDA[PDA[process].context.state].memPointer;
faultedPage: VM.PageNumber = VM.PageNumberForAddress[faultAddress];
IF debugInfo # NIL THEN debugInfo.lastFaultedPage ← faultedPage;
IF faultedPage <= 0 OR faultedPage > VMInternal.lastVMPage
THEN ReportFault[process, VM.AddressFault, faultedPage, faultAddress]
ELSE {
interval: VM.Interval ← MapAddressToContainingInterval[faultedPage];
ok: BOOLTRUE;
IF debugInfo # NIL THEN {
lpx: [0..FaultsInRing) ← debugInfo.lastPageFaultIndex ← (debugInfo.lastPageFaultIndex+1) MOD FaultsInRing;
debugInfo.faultRing[lpx] ← [faultedPage, faultAddress, GetStateHelper[faultedPage]];
};
VM.SwapIn[interval: interval, nextPage: GetNextPageHint[process]
! VM.AddressFault => {ok ← FALSE; CONTINUE};
VM.CantDoIO => { ReportCantDoIO[process, reason, page]; CONTINUE};
];
IF NOT ok THEN {
Give this thing a retry with the exact page to avoid confusion with surrounding pages.
IF debugInfo # NIL THEN debugInfo.retries ← debugInfo.retries + 1;
VM.SwapIn[interval: [faultedPage, 1], nextPage: 0
! VM.AddressFault => {
ReportFault[process, VM.AddressFault, faultedPage, faultAddress];
CONTINUE;
};
VM.CantDoIO => { ReportCantDoIO[process, reason, page]; CONTINUE};
];
};
};
RestartFaultee[qPageFault, process];
pageFaults ← pageFaults.SUCC;
ENDLOOP;
};
WriteProtectFaultProcess: PROC = {
Reserve a state vector for this process
Process.SetPriority[Process.priorityFaultHandlers];
DO
process: PsbHandle = WaitForFaultee[qWriteProtectFault];
ReportFault[process, VM.WriteProtectFault];
RestartFaultee[qWriteProtectFault, process];
--*stats*-- writeFaults ← writeFaults.SUCC;
ENDLOOP;
};
FrameFaultProcess: PROC = {
Reserve a state vector for this process.
OPEN VMInternal;
Process.SetPriority[Process.priorityFaultHandlers];
DO
process: PsbHandle = WaitForFaultee[qFrameFault];
fsi: NormalFrameSizeIndex = PDA[PDA[process].context.state].fsi;
frSize: CARDINAL = PrincOpsUtils.FrameSize[fsi] + AnyFrameSizeIndex.SIZE;
newFrame: FrameHandle; -- the frame we will allocate and paste into the AV.
IF fsi >= largeFrameThresholdFsi THEN {
We will allocate a large frame (i.e., an integral number of pages).
pages: CARDINAL = VM.PagesForWords[frSize + LargeFrameHeader.SIZE];
largeFrame: LargeFrame = PageNumberToMDSAddress[AllocateForLocalFrames[pages].page];
largeFrame.next ← largeFrame.prev ← NIL;
largeFrame.trueFsi ← fsi;
NotifyLargeFrame[largeFrame];
largeFrame.fsiFrame[0].fsi ← LargeReturnSlot; -- (a fsi never generated by the compiler.)
newFrame ← @largeFrame.fsiFrame[0].frame;
--*stats*-- largeFramesAllocated ← largeFramesAllocated.SUCC;
}
ELSE {
We will allocate a small frame, which may or may not require extension of the heap.
Assert: frSize MOD 4 = 0.
piece: FrameHeapPiece ← frameHeapPieceList;
newFsiFrame: POINTER TO FsiFrame; -- assert: newFsiFrame MOD 4 = 3
IF piece ~= NIL AND piece.wordsInUse + frSize > piece.wordsAllocated THEN {
The remaining space in the most recent extension piece is insufficient for the faultee. We subdivide the available space into the smallest set of frames that will exhaust (or nearly exhaust) it.
framePiecePages: VM.PageCount =
VM.PagesForWords[frSize + FrameHeapPieceHeader.SIZE];
framePieceWords: CARDINAL = VM.WordsForPages[framePiecePages];
minFrameSize: CARDINAL = PrincOpsUtils.FrameSize[0] + AnyFrameSizeIndex.SIZE;
wordsAvailable: CARDINAL;
trialFsi: NormalFrameSizeIndex ← fsi;
newFsiFrame ← @piece.fsiFrame[0] + piece.wordsInUse - FrameHeapPieceHeader.SIZE;
UNTIL (wordsAvailable ← piece.wordsAllocated - piece.wordsInUse) < minFrameSize DO
tFsiWords: CARDINAL =
PrincOpsUtils.FrameSize[trialFsi ← trialFsi.PRED] + AnyFrameSizeIndex.SIZE;
UNTIL wordsAvailable < tFsiWords DO
newFsiFrame.fsi ← trialFsi;
PrincOpsUtils.Free[@newFsiFrame.frame]; -- atomically paste onto frame heap.
newFsiFrame ← newFsiFrame + tFsiWords;
piece.wordsInUse ← piece.wordsInUse + tFsiWords;
wordsAvailable ← wordsAvailable - tFsiWords;
ENDLOOP;
ENDLOOP;
We now allocate a new piece from which to build frames.
piece ← PageNumberToMDSAddress[AllocateForLocalFrames[framePiecePages].page];
piece.next ← frameHeapPieceList;
piece.wordsAllocated ← framePieceWords;
piece.wordsInUse ← FrameHeapPieceHeader.SIZE;
frameHeapPieceList ← piece;
--*stats*-- frameHeapExtensions ← frameHeapExtensions.SUCC;
};
Fabricate a new frame
newFsiFrame ← @piece.fsiFrame[0] + piece.wordsInUse - FrameHeapPieceHeader.SIZE;
newFsiFrame.fsi ← fsi;
newFrame ← @newFsiFrame.frame;
piece.wordsInUse ← piece.wordsInUse + frSize;
--*stats*-- smallFramesAllocated ← smallFramesAllocated.SUCC;
};
Atomically chain the new frame onto the AV:
Note that we can not do a Frame.Free[] here because large frames
have an fsi different than that of the AV slot we put them in.
PrincOpsUtils.DisableInterrupts[];
LOOPHOLE[newFrame, POINTER TO AVItem]^.link ← AV[fsi].link;
AV[fsi].frame ← newFrame;
IF debugInfo # NIL THEN debugInfo.frameAllocs[fsi] ← debugInfo.frameAllocs[fsi].SUCC;
PrincOpsUtils.EnableInterrupts[];
Restart faulted process:
RestartFaultee[qFrameFault, process];
--*stats*-- frameFaults ← frameFaults.SUCC;
ENDLOOP;
};
FlushLargeFramesProcess: PROC = {
This process can run at any priority and without a reserved state vector.
Process.SetPriority[Process.priorityFaultHandlers];
DO
largeFrame: VMInternal.LargeFrame = WaitForLargeFrame[];
VM.Free[
[page: VM.PageNumberForAddress[largeFrame],
count: VM.PagesForWords[PrincOpsUtils.FrameSize[largeFrame.trueFsi]]]];
--*stats*-- largeFramesFreed ← largeFramesFreed.SUCC;
ENDLOOP;
};
Emergency frame stuff
EmergencyRefillProcess: PROC = {
This process refills the emergency page list used by frame allocation when there are no available clean pages. We give this a foreground priority to try to stay ahead of greedy processes.
WaitForEmergency: ENTRY PROC [monitor: POINTER TO MONITORLOCK] = INLINE {
WHILE lagChange = eList.change DO WAIT emergencyCond; ENDLOOP;
lagChange ← eList.change;
};
interval: VM.Interval = VM.SimpleAllocate[count: 1];
lagChange: INT ← -1;
eList: VMEmergency.EmergencyList = VM.AddressForPageNumber[interval.page];
eList.change ← 0;
eList.max ← 16;
eList.pages ← ALL[0];
Process.SetPriority[Process.priorityForeground];
VM.SwapIn[interval: interval, pin: TRUE];
VMEmergency.emergencyList ← eList; -- install the emergency list
{
Allocate and initialize the debugging information. This eliminates a fair chunk of MDS usage.
debugPages: VM.Interval = VM.SimpleAllocate[VM.PagesForWords[SIZE[DebugInfo]]];
temp: LONG POINTER TO DebugInfo ← VM.AddressForPageNumber[debugPages.page];
temp^ ← [];
VM.SwapIn[interval: debugPages, pin: TRUE];
debugInfo ← temp;
};
DO
WaitForEmergency[@emergencyLock];
lagChange ← eList.change;
FOR i: NAT IN [0..eList.max) DO
page: VM.PageNumber ← eList.pages[i];
IF page = 0 THEN {
This page needs a new allocation
page ← VM.SimpleAllocate[count: 1].page;
};
IF VMInternal.InOut[VMInternal.GetVMMap[page]] = out THEN {
The page needs to have real memory pinned beneath it for the use of the frame allocator. We temporarily remove it from the emergency list to keep from being found in an unhappy state.
eList.pages[i] ← 0;
VM.SwapIn[interval: [page, 1], pin: TRUE];
eList.pages[i] ← page;
emergencyCount ← emergencyCount + 1;
};
ENDLOOP;
ENDLOOP;
};
NoteEmergency: ENTRY PROC [monitor: POINTER TO MONITORLOCK] = INLINE {
BROADCAST emergencyCond;
};
emergencyCond: CONDITION;
emergencyLock: MONITORLOCK;
emergencyCount: INT ← 0;
Internal Procedures
MapAddressToContainingInterval: PROC [faultedPage: VM.PageNumber] RETURNS [VM.Interval] = {
firstPage: VM.PageNumber ← faultedPage ;
lastPage: VM.PageNumber ← firstPage ;
pageState: VM.PageState ← VM.State[firstPage];
dataState: VM.DataState ← pageState.dataState;
pageCount: INT ← 1 ;
maxSize: INT = MAX[ReadOnlyPageInSize, ReadWritePageInSize];
IF firstPage > VMInternal.lastVMPage THEN RETURN [[page: firstPage, count: 0]];
IF pageState.hasRealMemory OR dataState = none OR dataState = undefined THEN
This fault does NOT require I/O, so enlarging it does us no real good
RETURN [ [firstPage, 1] ];
WHILE pageCount < maxSize AND lastPage < VMInternal.lastVMPage DO
page: VM.PageNumber ← lastPage.SUCC;
pageState ← VM.State[page];
dataState ← pageState.dataState;
IF pageState.hasRealMemory OR dataState = none OR dataState = undefined OR (NOT pageState.readOnly AND (pageCount >= ReadWritePageInSize)) THEN EXIT ;
lastPage ← page ;
pageCount ← pageCount.SUCC;
ENDLOOP;
WHILE pageCount < maxSize AND firstPage > 0 DO
page: VM.PageNumber ← firstPage.PRED;
pageState ← VM.State[page];
dataState ← pageState.dataState;
IF pageState.hasRealMemory OR dataState = none OR dataState = undefined OR (NOT pageState.readOnly AND (pageCount >= ReadWritePageInSize)) THEN EXIT ;
firstPage ← page ;
pageCount ← pageCount.SUCC;
ENDLOOP;
RETURN[[page: firstPage, count: pageCount]]
};
GetNextPageHint: PROC [process: PsbHandle] RETURNS [VM.PageNumber] = INLINE {
If the successor of "process" on the queue differs from "process", we extract the page number on which it has faulted. Note that another process may come along and be inserted between the two, but this is unlikely and we're only looking for a hint to optimize disk arm motion.
nextProcess: PsbHandle = PrincOpsUtils.PsbIndexToHandle[PDA[process].link.next];
RETURN[
IF nextProcess = process THEN 0
ELSE VM.PageNumberForAddress[PDA[PDA[nextProcess].context.state].memPointer]]
};
GetStateHelper: PROC [page: VM.PageNumber] RETURNS [PrincOps.PageValue] = {
This routine can be called from a world-swap debugger to examine the current state of a page. It is also used inside of ReportFault to capture the state at the time of the fault.
IF page <= 0 OR page > VMInternal.lastVMPage THEN
RETURN [[
state: VMInternal.PageStateFromFlags[PrincOps.flagsVacant],
real: 0
]];
RETURN [VMInternal.GetPageValue[page]];
};
ReportFault: PROC [psb: PsbHandle, error: ERROR [LONG POINTER], faultedPage: VM.PageNumber ← 0, faultAddress: LONG POINTER ← NIL] = {
Return: PROCLOOPHOLE[PrincOpsUtils.GetReturnFrame[]];
state: StateVector = PDA[PDA[psb].context.state];
Variables for easy inspection from the debugger if something goes wrong
address: LONG POINTER = state.memPointer;
There will be something funny if faultAddress # address AND error = VM.AddressFault!
pageValue: PrincOps.PageValue ← GetStateHelper[faultedPage];
This lets us see the state roughly at the time of the fault.
IF error = VM.AddressFault AND debugInfo # NIL THEN {
Remember the last page that gets an address fault (just in case the user recovers).
debugInfo.lastAddressFaultPage ← faultedPage;
debugInfo.addressFaultCounter ← debugInfo.addressFaultCounter + 1;
};
Splice me in as top-of-stack of psb.
PDA[PDA[psb].context.state].stkptr ← PDA[PDA[psb].context.state].instbyte ← 0;
PrincOpsUtils.SetReturnFrame[state.frame];
PDA[PDA[psb].context.state].frame ← LOOPHOLE[PrincOpsUtils.MyLocalFrame[]];
Return to caller without disturbing this frame.
Return[];
Control returns here in the context of the faulting process. If it has
a dirty cleanup link, disaster may ensue if a signal is raised, since it is
almost certain to be uncaught and the AMEvents stuff will doubtless do a WAIT.
If someone caught it and did a wait, similar bad things would happen. So, we
call the world-swap debugger instead.
IF PDA[psb].flags.cleanup ~= PsbNull THEN
DebuggerSwap.WorryCallDebugger["Address fault with dirty cleanup link (see a wizard)"L];
ERROR error[state.memPointer];
};
ReportCantDoIO: PROC [psb: PsbHandle, reason: VM.IOErrorType, page: VM.PageNumber] = {
Return: PROCLOOPHOLE[PrincOpsUtils.GetReturnFrame[]];
state: StateVector = PDA[PDA[psb].context.state];
address: LONG POINTER = state.memPointer; -- for easy inspection from the debugger.
Splice me in as top-of-stack of psb.
PDA[PDA[psb].context.state].stkptr ← PDA[PDA[psb].context.state].instbyte ← 0;
PrincOpsUtils.SetReturnFrame[state.frame];
PDA[PDA[psb].context.state].frame ← LOOPHOLE[PrincOpsUtils.MyLocalFrame[]];
Return to caller without disturbing this frame.
Return[];
Control returns here in the context of the faulting process. If it has
a dirty cleanup link, disaster may ensue if a signal is raised, since it is
almost certain to be uncaught and the AMEvents stuff will doubtless do a WAIT.
If someone caught it and did a wait, similar bad things would happen. So, we
call the world-swap debugger instead.
IF PDA[psb].flags.cleanup ~= PsbNull THEN
DebuggerSwap.WorryCallDebugger["Address fault with dirty cleanup link (see a wizard)"L];
ERROR VM.CantDoIO[reason, page];
};
WaitForFaultee: PROC [q: FaultIndex] RETURNS [psb: PsbHandle] = INLINE {
Implementation note: The explicit use of PrincOpsUtils to invoke monitor instructions is required because FaultQueues do not have full CONDITION variables in them. Rather, they have only the Queue portion; there is no timeout field. Since the generated code for WAIT assumes a timeout word follows the Queue, the language construct can't be used. Of course, the use of monitor locks is really unnecessary anyway, since there is only a single process doing waits and the condition variable is notified by microcode with a naked notify. However, it is the easiest way to achieve the desired effect.
lock: MONITORLOCK;
pCondition: LONG POINTER TO CONDITION = LOOPHOLE[@PDA.fault[q].condition];
--Temp kludge to allow Laundry to get in: -- Process.Yield[]; -- (ADB)
UNTIL PrincOpsUtils.LongEnter[@lock] DO ENDLOOP;
WHILE PDA.fault[q].queue = QueueEmpty DO
PrincOpsUtils.LongWait[@lock, pCondition, NoTimeout];
UNTIL PrincOpsUtils.LongReEnter[@lock, pCondition] DO ENDLOOP;
ENDLOOP;
psb ← PrincOpsUtils.PsbIndexToHandle[PDA.block[PDA.fault[q].queue.tail].link.next];
PrincOpsUtils.LongExit[@lock];
};
RestartFaultee: PROC [q: FaultIndex, psb: PsbHandle] = INLINE {
PrincOpsUtils.Requeue[@PDA.fault[q].queue, @PDA.ready, psb];
};
WaitForLargeFrame: PROC RETURNS [largeFrame: VMInternal.LargeFrame] = INLINE {
WaitForLargeFrameEntry: ENTRY PROC [monitor: POINTER TO MONITORLOCK] = INLINE {
Note: AV[LargeReturnSlot] can go from non-empty to empty only as a result of this procedure. Therefore, the test of AV[LargeReturnSlot] need not be made with interrupts disabled.
OPEN VMInternal;
DO
IF AV[LargeReturnSlot].tag = frame THEN EXIT;
The following are legal only because they are INLINEs.
IF largeFrameList = NIL
THEN Process.DisableTimeout[@largeFramesInUse]
ELSE Process.SetTimeout[@largeFramesInUse, largeFrameTimeout];
WAIT largeFramesInUse;
ENDLOOP;
PrincOpsUtils.DisableInterrupts[]; -- prevent AV manipulation
largeFrame ← LOOPHOLE[
AV[LargeReturnSlot].frame - LargeFrameHeader.SIZE - AnyFrameSizeIndex.SIZE];
AV[LargeReturnSlot].link ← AV[LargeReturnSlot].link^.link;
PrincOpsUtils.EnableInterrupts[]; -- AV is now consistent
IF largeFrame = largeFrameList THEN
head of large frame list is being freed.
IF (largeFrameList ← largeFrame.next) ~= NIL THEN largeFrameList.prev ← NIL ELSE NULL
ELSE
IF (largeFrame.prev.next ← largeFrame.next) ~= NIL THEN
largeFrame.next.prev ← largeFrame.prev;
};
WaitForLargeFrameEntry[@largeFramesLock];
};
NotifyLargeFrame: PROC [largeFrame: VMInternal.LargeFrame] = INLINE {
NotifyLargeFrameEntry: ENTRY PROC [monitor: POINTER TO MONITORLOCK] = INLINE {
largeFrame.next ← largeFrameList;
IF largeFrameList ~= NIL THEN largeFrameList.prev ← largeFrame;
largeFrameList ← largeFrame;
Process.SetTimeout[@largeFramesInUse, largeFrameTimeout]; -- OK because it's INLINE
NOTIFY largeFramesInUse;
};
NotifyLargeFrameEntry[@largeFramesLock];
};
AllocateForLocalFrames: PROC [count: VM.PageCount] RETURNS [interval: VM.Interval] = INLINE {
This is a specialized procedure for use by the frame fault handler. It is semantically equivalent to {interval ← Allocate[count, mds]; SwapIn[interval, kill: TRUE, pin: TRUE]}, but must be implemented carefully because of the delicate state of the world at the time it is invoked.
outcome: VMInternal.AllocationOutcome;
AllocateForLocalFramesEntry: ENTRY PROC [monitor: POINTER TO MONITORLOCK] = INLINE {
The following is actually a coroutine call (to avoid frame allocation).
[outcome, interval] ← VMInternal.AllocateVirtualMemoryInternal[count, $mds];
};
AllocateForLocalFramesEntry[@VMInternal.allocationLock];
IF outcome ~= ok THEN DebuggerSwap.WorryCallDebugger["No VM for frame heap"L];
FOR page: VM.PageNumber IN [interval.page..interval.page+interval.count) DO
The following is actually a coroutine call (to avoid frame allocation).
VMInternal.AllocateRealMemoryForLocalFrames[page];
ENDLOOP;
NoteEmergency[@emergencyLock];
};
PageNumberToMDSAddress: PROC [page: VM.PageNumber] RETURNS [address: POINTER] = INLINE {
RETURN[PrincOpsUtils.LowHalf[VM.AddressForPageNumber[page]]]
};
Initialization
Initialize: PROC = {
myFramePage: VM.PageNumber = VM.PageNumberForAddress[PrincOpsUtils.MyLocalFrame[]];
FindOriginalFrameHeap: BootStartList.Proc = {
OPEN BootStartList;
entry: EntryPointer = IndexToEntryPointer[index];
WITH e: entry SELECT FROM
space => NULL;
swapUnit => {
suPage: VM.PageNumber = IndexToSpaceEntryPointer[e.parent].vmPage + e.base;
IF myFramePage IN [suPage..suPage + e.pages) THEN {
frameHeapPieceList ← PageNumberToMDSAddress[suPage];
RETURN[TRUE]
};
};
ENDCASE;
};
PDA.fault[qFrameFault] ← PDA.fault[qPageFault] ← PDA.fault[qWriteProtectFault] ←
[queue: QueueEmpty, condition: [tail: PsbNull, abortable: FALSE, wakeup: FALSE]];
Process.Detach[FORK PageFaultProcess];
Process.Detach[FORK WriteProtectFaultProcess];
BootStartList.Enumerate[FindOriginalFrameHeap];
Process.Detach[FORK FrameFaultProcess];
Process.DisableTimeout[@largeFramesInUse];
Process.Detach[FORK FlushLargeFramesProcess];
Process.Detach[FORK EmergencyRefillProcess];
SELECT VMSideDoor.rmPages FROM
IN [0 .. 3100] => {ReadOnlyPageInSize ← 2; ReadWritePageInSize ← 1};
IN (3100 .. 6200] => {ReadOnlyPageInSize ← 4; ReadWritePageInSize ← 2};
> 6200 => {ReadOnlyPageInSize ← 7; ReadWritePageInSize ← 4};
ENDCASE;
IF GermSwap.switches[two] THEN DebuggerSwap.CallDebugger["Key stop 2 (VM)"L];
ProcessorFace.SetMP[MPCodes.vmInitialized];
};
Initialize[];
END.
Bob Hagmann January 30, 1985 10:04:43 pm PST
added code to PageFaultProcess to retry and help find the address fault sometimes encountered during booting