-- Swapper>CachedRegionImplA.mesa (last edited by Knutsen on January 19, 1981 4:23 PM)
-- Implements the region cache and access to it. Implements procedures which need intimate or sequential access to the cache.
-- Exclusive access to the region cache is provided by the monitor lock regionCacheLock. Exclusive access to individual region descriptors is provided by the checkedOut field in the descriptors in the cache.
-- Note: No frame heap ALLOC’s may be executed within any ENTRY procedures in this monitor (e.g. only inline or fixed frame procedures may be called), so that they may be called from the alloc fault handler. If this rule were not followed, we could get an allocation trap when we held the monitor lock, thus making DeallocateClean inaccessible to the alloc fault handler.
DIRECTORY
CachedRegion USING [AliveSwappable, Desc, DTemperature, In, InSwappable, ReturnWait, State],
CachedRegionInternal USING [AllocateMStoreRuthlesslyInternal, LongMoveUp],
Environment USING [wordsPerPage],
Frame USING [GetReturnLink, SetReturnLink],
Inline USING [BITAND, LongCOPY],
MStore USING [Allocate, AllocateIfFree, Deallocate],
PageMap USING [Flags, flagsVacant, flagsNotReferenced, GetF, SetF, Value],
PrincOps USING [Port],
Process USING [DisableAborts, GetPriority, InitializeMonitor, MsecToTicks, Priority, SetPriority, SetTimeout],
ProcessInternal USING [DisableInterrupts, EnableInterrupts],
ProcessPriorities USING [priorityPageFaultLow],
RuntimeInternal USING [WorryCallDebugger],
SimpleSpace USING [AllocateVM],
Space USING [defaultWindow],
SpecialSpace USING [realMemorySize],
StoragePrograms USING [countVM, DescribeSpace, outlaw],
Utilities USING [LongPointerFromPage, PageFromLongPointer],
VM USING [Interval, PageCount, PageNumber, PageOffset];
CachedRegionImplA: MONITOR
LOCKS regionCacheLock
IMPORTS CachedRegionInternal, Frame, Inline, MStore, PageMap, Process, ProcessInternal, RuntimeInternal, SimpleSpace, SpecialSpace, StoragePrograms, Utilities
EXPORTS CachedRegion, CachedRegionInternal, StoragePrograms
SHARES CachedRegionInternal, PageMap =
BEGIN OPEN CachedRegion;
-- public data:
--CachedRegionInternal.--pageTop: PUBLIC VM.PageNumber;
-- inSwappableCold: PUBLIC InSwappable ← inSwappableColdest; ++ (a variable so debugger-tweakable)
-- private data:
dTemperatureHot: DTemperature ← 1; -- initial temp of recently-used Desc’s. a variable so debugger-tweakable.
--CachedRegionInternal.--regionCacheLock: PUBLIC MONITORLOCK; -- (PRIVATE in interface)
checkIn: CONDITION; -- broadcast whenever a region descriptor is checked in.
countRegionCache: VM.PageCount; -- amount of VM allocated.
countCacheMapped: VM.PageCount; -- number of pages of region cache currently mapped.
--nDescMax: CARDINAL; ++ current max number of Desc’s in cache.
IDesc: TYPE = [0..--nDescMax--0); -- index of region descriptor cache (grows dynamically).
RegionDesc: TYPE = ARRAY IDesc OF Desc;
BaseDesc: TYPE = LONG BASE POINTER TO RegionDesc; -- allocated externally.
DebuggerBaseDesc: TYPE = LONG POINTER TO RegionDesc; -- (for debugger use only.)
PDesc: TYPE = BaseDesc RELATIVE ORDERED POINTER [0..177777B] TO Desc;
nPad: CARDINAL = 1; -- For the convenience of Find, one extra dummy Desc is prepended to the cache to allow a PDesc to be less than pDescFirst.
baseDesc: BaseDesc; -- base of cache.
pDescFirst: PDesc = FIRST[PDesc] + nPad*SIZE[Desc]; -- offset of first entry of cache.
pDescLast: PDesc; -- offset of current last entry of cache.
pDescMax: PDesc; -- offset of last possible entry of caches (until more real mem allocated).
pDescMru: PDesc; -- offset of most-recently-referenced entry of cache.
-- Circular scanning cache pointers: (must be adjusted when cache shrinks)
pDescNextReplaced: PDesc; -- offset of entry which region replacement algorithm will consider next.
pDescNextAged: PDesc; -- offset of entry which aging process or FindUnreferenced will consider next.
-- Aging Process parameters:
agingTickTime: CARDINAL = 1000;--milliseconds-- --Basic tick of the Aging process timer.
chunksPerPass: CARDINAL = 8; -- a pass through the cache is broken into chunks. The purpose is to spread the computational overhead out over time, and to limit the time that the cache is locked.
maxAgingChunkTicks: CARDINAL = 4; -- max time delay between processing chunks. Max time per pass is maxAgingChunkTicks * chunksPerPass * agingTickTime milliseconds.
-- increaseChunkTimeNumerator: CARDINAL ← 2;
-- increaseChunkTimeDenominator: CARDINAL ← 3;
-- decreaseChunkTimeNumerator: CARDINAL ← 8;
-- decreaseChunkTimeDenominator: CARDINAL ← 10;
-- Aging Process variables:
agingTick: CONDITION; -- an interval timer.
agingTicksPerChunk: CARDINAL ← maxAgingChunkTicks; -- time delay between processing chunks. (A variable so debugger-tweakable)
agingTicksTillNextChunk: CARDINAL; -- (also tweaked by FindUnreferenced)
maskNotReferenced: PageMap.Value =
[logSingleError: LOOPHOLE[1], flags: PageMap.flagsNotReferenced, realPage: LOOPHOLE[7777B]];
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Initialization
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--StoragePrograms.--InitializeRegionCacheA: PUBLIC PROCEDURE =
BEGIN
Process.InitializeMonitor[@regionCacheLock]; -- must precede call to InitializeInternal
InitializeInternal[];
END;
InitializeInternal: ENTRY--so Initialize* can be called-- PROCEDURE =
BEGIN
pageRegionCache: VM.PageNumber;
nDescMax: CARDINAL; -- current max number of Desc’s in cache.
Process.DisableAborts[@checkIn];
Process.DisableAborts[@agingTick];
countRegionCache ← (SpecialSpace.realMemorySize*SIZE[Desc] + Environment.wordsPerPage-1)/Environment.wordsPerPage; -- enough VM for one region per real page.
pageRegionCache ← SimpleSpace.AllocateVM[countRegionCache, hyperspace];
countCacheMapped ← 2; -- (Pilot needs 2 mapped pages before the Client is run.)
MStore.Allocate[interval: [page: pageRegionCache, count: countCacheMapped]];
baseDesc ← Utilities.LongPointerFromPage[pageRegionCache];
nDescMax ← (countCacheMapped*Environment.wordsPerPage)/SIZE[Desc] - nPad;
pDescMax ← pDescFirst+SIZE[Desc]*(nDescMax-1);
pDescLast ← pDescNextReplaced ← pDescNextAged ← pDescMru ← pDescFirst;
pageTop ← FIRST[VM.PageNumber] + StoragePrograms.countVM;
baseDesc[pDescLast] ← [ -- initial entry in the cache.
interval: [page: pageTop, count: 0], -- page+count = end of implemented VM.
level: 0, -- don’t care
levelMapped: 0, -- don’t care
hasSwapUnits: FALSE, -- don’t care
dTemperature: FIRST[DTemperature], -- don’t care
dPinned: TRUE, -- we pin the last entry, which contains pageTop.
dDirty: FALSE, -- don’t care
state: checkedOut, -- don’t care
writeProtected: FALSE, -- don’t care
needsLogging: FALSE, -- don’t care
beingFlushed: FALSE ]; -- don’t care
IF nPad>0 THEN
{ baseDesc[pDescFirst-SIZE[Desc]] ← baseDesc[pDescLast]; -- initialize entry preceeding first to ease debugging.
baseDesc[pDescFirst-SIZE[Desc]].interval.page ← FIRST[VM.PageNumber] };
InitializeAllocateMStoreRuthlessly[]; -- allocate frame; initialize PORT.
InitializeDeallocateClean[]; -- allocate frame; initialize PORT.
[] ← InitializeFind[]; -- allocate frame; initialize PORT.
[] ← InitializeInsertIfRoom[]; -- allocate frame; initialize PORT.
END;
--StoragePrograms.--InitializeRegionCacheB: PUBLIC PROCEDURE =
BEGIN
priorityAgingProcess: Process.Priority ← ProcessPriorities.priorityPageFaultLow; -- a variable so debugger-tweakable.
throwAway: PROCESS;
priorityPrev: Process.Priority;
StoragePrograms.DescribeSpace[ -- tells Swapper about region cache space --
StoragePrograms.outlaw, Utilities.PageFromLongPointer[baseDesc],
countRegionCache, Space.defaultWindow];
-- inSwappableCold ← LOOPHOLE[LOOPHOLE[State[inSwappableWarmest], CARDINAL]-laps+1];
priorityPrev ← Process.GetPriority[];
Process.SetPriority[priorityAgingProcess];
Process.SetTimeout[@agingTick, Process.MsecToTicks[agingTickTime]]; -- we set the timeout only once so that we do not need to swap in the Process code.
throwAway ← FORK AgingProcess[]; -- no profit in detaching.
Process.SetPriority[priorityPrev];
END;
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- monitor entries:
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
AgingProcess: ENTRY PROCEDURE [] =
BEGIN
assumedSizeSwapUnit: VM.PageCount = 6; -- (since actual size not easily available)
totalSwappable, totalReferenced: VM.PageCount; -- totals over one pass through memory.
d: LONG POINTER TO CachedRegion.Desc;
DO --FOREVER-- -- make a pass through the regions in the cache..
totalSwappable ← totalReferenced ← 0;
THROUGH [0..chunksPerPass) DO --for each chunk..
agingTicksTillNextChunk ← agingTicksPerChunk;
WHILE agingTicksTillNextChunk>0 DO -- (agingTicksTillNextChunk may be reset by FindUnreferenced)
agingTicksTillNextChunk ← PRED[agingTicksTillNextChunk];
WAIT agingTick;
ENDLOOP;
THROUGH [0..((pDescLast-pDescFirst)/SIZE[Desc])/chunksPerPass) DO -- for each significant region in chunk..
pDescNextAged ←
IF pDescNextAged>=pDescLast THEN pDescFirst ELSE pDescNextAged+SIZE[Desc];
d ← @baseDesc[pDescNextAged];
IF --state~=checkedOut AND-- (d.state IN InSwappable OR (d.hasSwapUnits AND d.state IN AliveSwappable)) THEN
BEGIN --process swappable region--
endSwapunit: VM.PageNumber;
referenced: BOOLEAN;
countMapped: VM.PageCount;
value: PageMap.Value;
valueRegionClean: PageMap.Value = [ -- legal target flags for region. These flags are not definitive since needsLogging is just a hint.
logSingleError: FALSE,
flags: [writeProtected: d.writeProtected OR d.needsLogging,
dirty: --assume--FALSE,
referenced: -- desired end state--FALSE],
realPage: NULL];
sizeSwapUnit: VM.PageCount ←
IF d.hasSwapUnits THEN assumedSizeSwapUnit ELSE d.interval.count;
page: VM.PageNumber ← d.interval.page;
endRegion: VM.PageNumber = d.interval.page+d.interval.count;
WHILE page < endRegion DO -- for each swap unit..
countMapped ← 0;
referenced ← FALSE;
endSwapunit ← MIN[endRegion, page+sizeSwapUnit];
WHILE page < endSwapunit DO --for each page..
-- The following code could be replaced with a single "ClearThenSetFlags[page: ..., firstClear: referenced, thenSet: none]"
ProcessInternal.DisableInterrupts[]; -- prevents others from dirtying page.
[] ← PageMap.SetF[page, Inline.BITAND[maskNotReferenced,
(value ← PageMap.SetF[page, valueRegionClean])]]; -- reset ref’d (noop if vacant)
ProcessInternal.EnableInterrupts[];
IF value.flags~=PageMap.flagsVacant THEN
{ countMapped ← SUCC[countMapped];
referenced ← referenced OR value.flags.referenced };
page ← SUCC[page];
ENDLOOP; --processing page--
totalSwappable ← totalSwappable + countMapped;
IF referenced THEN totalReferenced ← totalReferenced + countMapped;
ENDLOOP; --processing swap unit--
END; --processing swappable region--
ENDLOOP; --processing region--
ENDLOOP; --processing chunk--
-- IF totalReferenced > (totalSwappable*decreaseChunkTimeNumerator) / decreaseChunkTimeDenominator THEN
-- agingTicksPerChunk ← MAX[2, agingTicksPerChunk/2]; ++ run more often to reduce size of working set.
-- IF totalReferenced < (totalSwappable*increaseChunkTimeNumerator) / increaseChunkTimeDenominator THEN
-- agingTicksPerChunk ← MIN[maxAgingChunkTicks, SUCC[agingTicksPerChunk]]; ++ run less often to increase size of working set.
ENDLOOP; --processing pass through region cache--
END;
--CachedRegionInternal.--AwaitNotCheckedOut: PUBLIC ENTRY PROCEDURE [pageMember: VM.PageNumber] =
BEGIN
found: BOOLEAN;
pDesc: PDesc;
DO
[found, pDesc] ← Find[pageMember];
IF ~found OR baseDesc[pDesc].state~=checkedOut THEN EXIT;
WAIT checkIn;
ENDLOOP;
END;
--CachedRegionInternal.--CheckIn: PUBLIC ENTRY PROCEDURE [desc: Desc] =
BEGIN
found: BOOLEAN;
pDesc: PDesc;
[found, pDesc] ← Find[desc.interval.page];
IF ~found OR baseDesc[pDesc].state~=checkedOut THEN ERROR;
IF desc.state=missing THEN
-- Delete the entry:
BEGIN
IF desc.dPinned THEN ERROR;
-- Move descriptors following pDesc one place towards first:
Inline.LongCOPY[
from: @baseDesc[pDesc+SIZE[Desc]],
nwords:pDescLast-pDesc, -- i.e. (pDescLast+SIZE[Desc]) - (pDesc+SIZE[Desc])
to: @baseDesc[pDesc]];
pDescLast ← pDescLast-SIZE[Desc];
IF pDescNextReplaced>pDesc THEN pDescNextReplaced ← pDescNextReplaced-SIZE[Desc];
IF pDescNextAged>pDesc THEN pDescNextAged ← pDescNextAged-SIZE[Desc];
END
ELSE --desc.state=present--
-- Update the entry:
BEGIN
desc.dTemperature ← dTemperatureHot;
baseDesc[pDesc] ← desc;
END;
BROADCAST checkIn;
END;
--CachedRegionInternal.--CheckOut: PUBLIC ENTRY PROCEDURE [pageMember: VM.PageNumber, ifCheckedOut: ReturnWait]
RETURNS [desc: Desc] =
BEGIN
found: BOOLEAN;
pDesc: PDesc;
DO
[found, pDesc] ← Find[pageMember];
desc ← baseDesc[pDesc];
IF found THEN
BEGIN OPEN baseDesc[pDesc];
IF state~=checkedOutTHEN { state ← checkedOut; EXIT }
ELSE IF ifCheckedOut=returnTHEN EXIT
ELSEWAIT checkIn;
END
ELSE
BEGIN desc.state ← missing; desc.interval.count ← 0; EXIT END;
ENDLOOP;
END;
-- totalCallsToFindUnreferenced, totalRegionsExaminedByFindUnreferenced, totalMappedSwapUnitsExaminedByFindUnreferenced: LONG CARDINAL ← 0; ++ only for instrumentation.
--CachedRegionInternal.--FindUnreferenced: PUBLIC ENTRY PROCEDURE [newCycle: BOOLEAN, pageStart: VM.PageNumber]
RETURNS [allReferenced: BOOLEAN, pageVictim: VM.PageNumber] =
BEGIN
d: LONG POINTER TO CachedRegion.Desc;
passes: CARDINAL ← 0;
allReferenced ← FALSE; -- assume.
agingTicksTillNextChunk ← agingTicksPerChunk; -- defer next aging process activity since we’re doing some now.
-- totalCallsToFindUnreferenced ← SUCC[totalCallsToFindUnreferenced];
IF ~newCycle THEN pDescNextAged ← Find[pageStart].pDesc; -- If continuation of cycle then proceed from where we left off else start where agingProcess last ran.
WHILE passes<2 DO -- look for unreferenced region..
IF pDescNextAged>=pDescLast THEN
{ pDescNextAged ← pDescFirst;
passes ← SUCC[passes] };
d ← @baseDesc[pDescNextAged];
IF --state~=checkedOut AND-- (d.hasSwapUnits AND d.state IN AliveSwappable) THEN
{ pageVictim ← (IF pageStart IN [d.interval.page .. d.interval.page+d.interval.count) THEN pageStart
ELSE d.interval.page);
GO TO Return }; -- Swap units are handled by CachedRegion.Apply[age].
IF --state~=checkedOut AND ~d.hasSwapUnits AND-- d.state IN InSwappable THEN
BEGIN --process swappable region--
endRegion: VM.PageNumber;
referenced: BOOLEAN;
value: PageMap.Value;
valueRegionClean: PageMap.Value = [ -- legal target flags for region. These flags are not definitive since needsLogging is just a hint.
logSingleError: FALSE,
flags: [writeProtected: d.writeProtected OR d.needsLogging,
dirty: --assume--FALSE,
referenced: -- desired end state--FALSE],
realPage: NULL];
-- totalRegionsExaminedByFindUnreferenced ← SUCC[totalRegionsExaminedByFindUnreferenced];
referenced ← FALSE;
pageVictim ← d.interval.page; -- assume this region will be victim..
endRegion ← pageVictim + d.interval.count;
FOR page: VM.PageNumber ← pageVictim, SUCC[page] WHILE page<endRegion DO -- for each page in region..
ProcessInternal.DisableInterrupts[]; -- prevents others from dirtying page.
[] ← PageMap.SetF[page, Inline.BITAND[maskNotReferenced,
(value ← PageMap.SetF[page, valueRegionClean])]]; -- reset ref’d (noop if vacant)
ProcessInternal.EnableInterrupts[];
SELECT value.flags FROM
PageMap.flagsVacant => EXIT;
--flagsMapped--ENDCASE => { referenced ← referenced OR value.flags.referenced };
ENDLOOP; --processing page of region--
IF PageMap.GetF[pageVictim].flags ~= PageMap.flagsVacant --mapped pages there--
AND ~referenced THEN GO TO Return; -- allReferenced, pageVictim are already set.
-- totalMappedSwapUnitsExaminedByFindUnreferenced ← SUCC[totalMappedSwapUnitsExaminedByFindUnreferenced];
END; --processing swappable region--
pDescNextAged ← pDescNextAged+SIZE[Desc];
ENDLOOP; --processing region--
allReferenced ← TRUE; RETURN; -- no victims found.
EXITS
Return => pDescMru ← pDescNextAged; -- remember for when we come back.
END;
--CachedRegion.--Insert: PUBLIC ENTRY PROCEDURE [desc: Desc] RETURNS [descVictim: Desc] =
BEGIN
success: BOOLEAN;
--REPEAT ... UNTIL region cache big enough-- DO
[success, descVictim] ← InsertIfRoom[desc];
IF success THEN EXIT
ELSE
{ IF countCacheMapped >= countRegionCache THEN ERROR; -- insufficient VM allocated for region cache.
allocateMStoreRuthlesslyInternal[interval: [Utilities.PageFromLongPointer[baseDesc]+countCacheMapped, 1]];
countCacheMapped ← countCacheMapped+1;
pDescMax ← pDescMax + (Environment.wordsPerPage/SIZE[Desc])*SIZE[Desc] };
ENDLOOP;
END;
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Monitor Internals
--~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--CachedRegionInternal.--allocateMStoreRuthlesslyInternal:
PUBLIC --INTERNAL-- CachedRegionInternal.AllocateMStoreRuthlesslyInternal ← -- (PRIVATE in interface) ("←" due to compiler glitch)
[LOOPHOLE[@AwaitAllocateMStoreRuthlesslyRequest]]; -- an indirect control link to the PORT.
AwaitAllocateMStoreRuthlesslyRequest: --RESPONDING-- PORT RETURNS [interval: VM.Interval]; -- args/results match allocateMStoreRuthlesslyInternal (but swapped).
InitializeAllocateMStoreRuthlessly: INTERNAL PROCEDURE =
BEGIN
countAllocated: VM.PageCount;
intervalRemaining: VM.Interval;
LOOPHOLE[AwaitAllocateMStoreRuthlesslyRequest, PrincOps.Port].dest ← Frame.GetReturnLink[]; -- set my PORT call to return to my caller on call below.
DO --FOREVER--
-- Return; Await new request; Process it;
intervalRemaining ← AwaitAllocateMStoreRuthlesslyRequest[];
Frame.SetReturnLink[LOOPHOLE[AwaitAllocateMStoreRuthlesslyRequest, PrincOps.Port].dest]; -- for debugger
--UNTIL whole interval allocated-- DO
countAllocated ← MStore.AllocateIfFree[intervalRemaining];
intervalRemaining ← [intervalRemaining.page+countAllocated, intervalRemaining.count-countAllocated];
IF intervalRemaining.count=0 THEN EXIT
ELSE DeallocateClean[];
ENDLOOP;
ENDLOOP;
END;
DeallocateClean: --INTERNAL-- PROCEDURE =
LOOPHOLE[@AwaitDeallocateCleanRequest]; -- an indirect control link to the PORT.
AwaitDeallocateCleanRequest: --RESPONDING-- PORT;
InitializeDeallocateClean: INTERNAL PROCEDURE =
BEGIN
victim: PDesc ← pDescFirst;
startingPoint: PDesc;
LOOPHOLE[AwaitDeallocateCleanRequest, PrincOps.Port].dest ← Frame.GetReturnLink[]; -- set my PORT call to return to my caller on call below.
DO --FOREVER--
-- Return; Await new request; Process it;
AwaitDeallocateCleanRequest[];
Frame.SetReturnLink[LOOPHOLE[AwaitDeallocateCleanRequest, PrincOps.Port].dest]; -- for debugger
IF victim>=pDescLast THEN victim ← pDescFirst; -- (assures victim is sensible.)
startingPoint ← victim;
--UNTIL checked-in, In, and clean region found-- DO
-- scope of baseDesc[victim]:
BEGIN OPEN baseDesc[victim];
IF --state~=checkedOut AND-- (state IN InSwappable OR
(hasSwapUnits
AND state IN AliveSwappable) ) THEN
BEGIN --see if all-clean region--
allVacant: BOOLEAN ← TRUE;
ProcessInternal.DisableInterrupts[]; -- prevents other processes from dirtying pages.
FOR offset: VM.PageOffset IN [0..interval.count) DO --look for any dirty pages--
flags: PageMap.Flags = PageMap.GetF[interval.page+offset].valueOld.flags;
IF flags~=PageMap.flagsVacant THEN
{IF flags.dirty THEN EXIT ELSE allVacant ← FALSE};
REPEAT
FINISHED => -- whole region is clean.
IF ~allVacant THEN
BEGIN
MStore.Deallocate[interval: interval, promised: FALSE]; -- interrupts are disabled!
state ← outAlive;
ProcessInternal.EnableInterrupts[];
GO TO Deallocated;
END;
ENDLOOP;
ProcessInternal.EnableInterrupts[];
END --seeing if all-clean region--;
END --USING desc--;
victim ← victim + SIZE[Desc];
IF victim>=pDescLast THEN victim ← pDescFirst;
IF victim=startingPoint THEN RuntimeInternal.WorryCallDebugger["All memory pinned, busy, or dirty"];
REPEAT --looking for clean region--
Deallocated => NULL;
ENDLOOP;
ENDLOOP;
END;
Find: --INTERNAL-- PROCEDURE [page: VM.PageNumber] RETURNS [found: BOOLEAN, pDesc: PDesc] =
-- Finds region which includes page. If none, returns first region in cache which follows page.
LOOPHOLE[@AwaitFindRequest]; -- an indirect control link to the PORT.
AwaitFindRequest: --RESPONDING-- PORT [found: BOOLEAN, pDesc: PDesc] RETURNS [page: VM.PageNumber]; -- args/results match Find (but swapped).
InitializeFind: INTERNAL PROCEDURE RETURNS [found: BOOLEAN, pDesc: PDesc] --to match PORT args-- =
BEGIN
page: VM.PageNumber;
iDescOrigin: CARDINAL = (pDescFirst-FIRST[PDesc])/SIZE[Desc];
iDesc, iDescL, iDescU: CARDINAL;
pageComp: VM.PageNumber;
LOOPHOLE[AwaitFindRequest, PrincOps.Port].dest ← Frame.GetReturnLink[]; -- set my PORT call to return to my caller on call below.
DO --FOREVER--
-- Return result; Await new request; Process it;
page ← AwaitFindRequest[found, pDesc];
Frame.SetReturnLink[LOOPHOLE[AwaitFindRequest, PrincOps.Port].dest]; -- for debugger
IF page=pageTop OR pDescMru<pDescFirst THEN ERROR;
IF pDescMru>=pDescLast THEN pDescMru ← pDescFirst; -- assures pDescMru is still reasonable.
-- scope of SameAsLastTime--
BEGIN
IF page IN [baseDesc[pDescMru].interval.page
.. baseDesc[pDescMru].interval.page + baseDesc[pDescMru].interval.count) THEN
GO TO SameAsLastTime;
iDescL ← iDescOrigin; iDescU ← (pDescLast-FIRST[PDesc])/SIZE[Desc];
--UNTIL search terminates-- DO
iDesc ← (iDescL+iDescU)/2;
pageComp ← baseDesc[FIRST[PDesc]+iDesc*SIZE[Desc]].interval.page;
IFpage<pageCompTHENiDescU ← iDesc-1 -- note that iDescU, a CARDINAL, might be iDescL-1 here.
ELSE IFpage>pageCompTHENiDescL ← iDesc+1
ELSEGO TO Exact;
IF iDescU<iDescL THEN GO TO NotExact;
ENDLOOP;
EXITS
Exact =>
{ pDesc ← FIRST[PDesc] + iDesc*SIZE[Desc]; found ← TRUE };
NotExact =>
-- Assert: page>"iDescU".page AND page<"iDescU+1".page AND iDescU+1 = iDescL.
IF iDescL = iDescOrigin THEN
{ pDesc ← pDescFirst; found ← FALSE }
ELSE
BEGIN
pDesc ← FIRST[PDesc] + iDescU*SIZE[Desc];
IF page < baseDesc[pDesc].interval.page + baseDesc[pDesc].interval.count THEN
found ← TRUE
ELSE
{ pDesc ← pDesc+SIZE[Desc]; found ← FALSE };
END;
SameAsLastTime => { pDesc ← pDescMru; found ← TRUE };
END;
pDescMru ← pDesc; -- remember for next time.
ENDLOOP;
END;
InsertIfRoom: --INTERNAL-- PROCEDURE [desc: Desc] RETURNS [success: BOOLEAN, descVictim: Desc] =
LOOPHOLE[@AwaitInsertIfRoomRequest]; -- an indirect control link to the PORT.
AwaitInsertIfRoomRequest: --RESPONDING-- PORT [success: BOOLEAN, descVictim: Desc] RETURNS [desc: Desc]; -- args/results match InsertIfRoom (but swapped).
InitializeInsertIfRoom: INTERNAL PROCEDURE RETURNS [success: BOOLEAN, descVictim: Desc] --to match PORT args-- =
BEGIN
desc: Desc;
found: BOOLEAN;
pDesc: PDesc;
LOOPHOLE[AwaitInsertIfRoomRequest, PrincOps.Port].dest ← Frame.GetReturnLink[]; -- set my PORT call to return to my caller on call below.
DO --FOREVER--
-- Return result; Await new request; Process it;
desc ← AwaitInsertIfRoomRequest[success, descVictim];
Frame.SetReturnLink[LOOPHOLE[AwaitInsertIfRoomRequest, PrincOps.Port].dest]; -- for debugger
-- scope of Done --
BEGIN
descVictim.dDirty ← FALSE; -- or set descVictim ← "descTop" ?
IF pDescLast>=pDescMax THEN
-- Find coldest unpinned descriptor whose swap units are all out, and kick him upstairs:
BEGIN
pDescCommOld: PDesc = pDescNextReplaced;
passesToGo: CARDINAL ← dTemperatureHot-FIRST[DTemperature]+1;
d: LONG POINTER TO Desc;
--UNTIL pDescNextReplaced is a replacable desc-- DO
IF pDescNextReplaced>=pDescLast THEN pDescNextReplaced ← pDescFirst;
d ← @baseDesc[pDescNextReplaced];
IF (~d.hasSwapUnits AND d.state IN [unmapped..--outdead..-- outAlive]
OR d.hasSwapUnits AND d.state=unmapped) --no pages are In--
AND ~d.dPinned --desc is itself swappable-- THEN
{ IF d.dTemperature=FIRST[DTemperature] THEN EXIT --replace this desc.
ELSE d.dTemperature ← PRED[d.dTemperature] };
pDescNextReplaced ← pDescNextReplaced+SIZE[Desc];
IF pDescNextReplaced=pDescCommOld THEN
IF (passesToGo ← PRED[passesToGo]) = 0 THEN
{ success←FALSE; GO TO Done }; -- no available slot in cache.
ENDLOOP;
descVictim ← baseDesc[pDescNextReplaced];
-- Move descriptors following pDescNextReplaced one place towards first:
Inline.LongCOPY[
from: @baseDesc[pDescNextReplaced+SIZE[Desc]],
nwords: pDescLast-pDescNextReplaced, -- i.e. (pDescLast+SIZE[Desc]) - (pDescNextReplaced+SIZE[Desc])
to: @baseDesc[pDescNextReplaced]];
pDescLast ← pDescLast-SIZE[Desc];
IF pDescNextAged>pDescNextReplaced THEN pDescNextAged ← pDescNextAged-SIZE[Desc];
END;
[found, pDesc] ← Find[desc.interval.page];
IF found THEN ERROR;
-- Move descriptors at and following pDesc one place towards last:
CachedRegionInternal.LongMoveUp[
pSource: @baseDesc[pDesc],
size: pDescLast+SIZE[Desc] - pDesc,
pSink: @baseDesc[pDesc+SIZE[Desc]]];
pDescLast ← pDescLast+SIZE[Desc];
IF pDescNextReplaced>=pDesc THEN pDescNextReplaced ← pDescNextReplaced+SIZE[Desc];
IF pDescNextAged>=pDesc THEN pDescNextAged ← pDescNextAged+SIZE[Desc];
-- Insert desc:
desc.dTemperature ← dTemperatureHot;
baseDesc[pDesc] ← desc;
pDescMru ← pDesc; -- make this the most-recently-used.
success ← TRUE;
EXITS
Done => NULL;
END;
ENDLOOP;
END;
END.
LOG
-- For previous log entries, see Pilot 3.0 archived version.
February 20, 1980 10:42 AMKnutsenVM for Region cache passed in as a parameter. Real mem for region cache allocated proportional to real memory size. Fix Find to not search past beginning of cache.
April 15, 1980 1:09 PMKnutsenAdded AllocateMStoreRuthlessly, DeallocateClean, InitializeRegionCacheA/B. Rename FirstNotBefore to Find. Make InsertIfFree and Find a coroutine.
April 25, 1980 2:20 PMForrestControlDefs and PrincOps.
June 16, 1980 5:24 PMGobbelMake compatible with new version of Desc.
July 30, 1980 1:37 PMKnutsenFix Insert to actually kick descs out of the cache. Make compatible with new region desc.
October 3, 1980 10:21 PMForrestUse PageMap.GetF not MStore.GetState.
October 13, 1980 9:58 AMForrest/RichardChange deallocateClean to notice when a region is allVacant, and skip to next.
December 5, 1980 12:33 PMKnutsen/McJonesAdded AgingProcess and FindUnreferenced.
January 19, 1981 4:23 PMKnutsenUse ProcessPriorities.