-- Swapper>MStoreImpl.mesa  (February 23, 1981 by Knutsen)

-- The monitor lock serializes calls on Allocate and Deallocate, but in addition interrupts are disabled whenever allocationMap and the hardware page map are inconsistent.  The reason for this is that RecoverMStore must be called when interrupts are disabled and hence can't wait on a monitor lock.

-- Note: No frame heap ALLOC's may be executed within any ENTRY procedures in this monitor, so that they may be called from the allocation fault handler.  If this rule were not followed, we could get an allocation fault when we held the monitor lock, thus making Deallocate inaccessible to the allocation fault handler.  Please see comments in MStore.mesa.

-- Things to consider:
--   1) Divide allocationMap into "segments"

DIRECTORY
  Environment USING [bitsPerWord],
  Frame USING [GetReturnLink, SetReturnLink],
  Inline USING [BITAND, BITNOT, BITOR, BITSHIFT, COPY],
  MStore,
  PageMap,
  PilotSwitches USING [switches--.t--],
  PrincOps USING [Port],
  Process USING [DisableAborts, DisableTimeout],
  ProcessInternal USING [DisableInterrupts, EnableInterrupts],
  ProcessorFace USING [dedicatedRealMemory],
  RealMemory USING [allocMap],
  RuntimeInternal USING [WorryCallDebugger],
  SpecialSpace USING [],
  StoragePrograms USING [countVM],
  SwapperPrograms USING [],
  VM USING [Interval, PageCount, PageNumber, PageOffset];

MStoreImpl: MONITOR LOCKS mStoreLock
  IMPORTS Frame, Inline, PageMap, PilotSwitches, Process, ProcessInternal,
    ProcessorFace, RealMemory, RuntimeInternal, StoragePrograms
  EXPORTS MStore, SpecialSpace, StoragePrograms
  SHARES MStore, PageMap =
BEGIN OPEN Environment, MStore, PageMap, VM;

--SpecialSpace.--realMemorySize: PUBLIC PageCount;  -- see definition in SpecialSpace

dandelionMemSize: PageCount = 768 --two boards--
    --Dandelion:-- - 64 --map-- - 256 --display+germ--
    --Dolphin:-- + 202 --display-- + 16 --germ--;

-- Monitor data:

mStoreLock: PUBLIC MONITORLOCK;  -- (PRIVATE in interface)

-- Bit (rp MOD bitsPerWord) of word rp/bitsPerWord of RealMemory.allocMap
-- is 1 iff real page rp is allocated.  Initially all real pages are
-- allocated.
allocationMap: POINTER TO ARRAY OF WORD ← BASE[RealMemory.allocMap];

-- Bounds on in-use part of allocation map:
-- Assertion: all free real pages are IN [realPageMin..realPageMax].
realPageMin: RealPageNumber ← LAST[RealPageNumber];
realPageMax: RealPageNumber ← FIRST[RealPageNumber];

countFree: PageCount ← 0;
countPromised: PageCount ← 0;
countThreshold: PageCount ← 0;
countHeldBack: PageCount ← 0;  -- for simulation of Dandelion memory size.

allocation: CONDITION;  -- BROADCASTed whenever the amount of mstore now available plus that available soon falls below the desired amount (when countFree + countPromised <= countThreshold + countHeldBack).
deallocation: CONDITION;  -- BROADCASTed whenever there is some usable mstore made available (when countFree > countHeldBack).

--StoragePrograms.--InitializeMStore:
    PUBLIC ENTRY --so Initialize* can be called-- PROCEDURE =
  BEGIN
  page: PageNumber;
  Process.DisableAborts[@allocation];  Process.DisableTimeout[@allocation];
  Process.DisableAborts[@deallocation];  Process.DisableTimeout[@deallocation];
  allocationMap[0] ← 177777B;
  Inline.COPY[
    from: @allocationMap[0], to: @allocationMap[1],
    nwords: SIZE[WORD]*(LENGTH[RealMemory.allocMap] - 1)];
  realMemorySize ← ProcessorFace.dedicatedRealMemory;
  FOR page IN [0 .. 0+StoragePrograms.countVM)
    DO
     -- Should be able to change SetF below to GetF...
    value: Value = SetF[page + FIRST[PageNumber], valueClean];
    IF value.flags # flagsVacant THEN
	BEGIN
	realMemorySize ← realMemorySize + 1;
	realPageMin ← MIN[realPageMin, value.realPage];
	realPageMax ← MAX[realPageMax, value.realPage];
	CheckRealPageMax[];
	END;
    ENDLOOP;
  IF PilotSwitches.switches.t = down THEN
    {countHeldBack ← realMemorySize - dandelionMemSize;
    realMemorySize ← dandelionMemSize}
  ELSE countHeldBack ← 0;
  [] ← InitializeAllocateIfFree[]; -- allocate frame;  initialize PORT.
  InitializeDeallocate[]; -- allocate frame;  initialize PORT.
  END;
  
Allocate: PUBLIC ENTRY PROCEDURE [interval: Interval] =
  BEGIN
  countBatch: PageCount;
  WHILE interval.count > 0 DO
    UNTIL countFree > countHeldBack DO WAIT deallocation ENDLOOP;
    countBatch ← MIN[interval.count, countFree - countHeldBack];
    [] ← allocateIfFreeInternal[interval: [interval.page, countBatch]];
    interval.page ← interval.page + countBatch;
    interval.count ← interval.count - countBatch;
    ENDLOOP;
  END;
  
allocateIfFreeInternal: PUBLIC --INTERNAL--AllocateIfFreeInternal ←
  -- (PRIVATE in interface)  ("←" due to compiler glitch)
  -- Guaranteed not to do an ALLOC from the frame heap.
  [LOOPHOLE[@AwaitAllocateIfFreeRequest]];
    -- an indirect control link to the PORT.

AwaitAllocateIfFreeRequest: --RESPONDING--PORT [countAllocated: PageCount]
  RETURNS [interval: Interval];
  -- args/results match allocateIfFreeInternal (but swapped).

InitializeAllocateIfFree: INTERNAL PROCEDURE []
	RETURNS [countAllocated: PageCount]  --to match PORT args-- =
  BEGIN
  interval: Interval;
  w, b: CARDINAL; -- allocationMap rover: word and bit number
  word: WORD; -- temporary, used to hold allocationMap[w]
  -- set my PORT call to return to my caller on call below.
  LOOPHOLE[AwaitAllocateIfFreeRequest, PrincOps.Port].dest ←
    Frame.GetReturnLink[];
  w ← realPageMin/bitsPerWord;
  b ← 0; -- ok to check of a couple unnecessary pages at first
  DO --FOREVER--
    -- Return result;  Await new request;  Process it;
    interval ← AwaitAllocateIfFreeRequest[countAllocated];
    Frame.SetReturnLink[  -- for debugger --
      LOOPHOLE[AwaitAllocateIfFreeRequest, PrincOps.Port].dest];
    interval.count ← countAllocated ←
      MIN[interval.count, countFree - countHeldBack];
    WHILE interval.count > 0 DO -- allocate page at interval.page
      word ← allocationMap[w];
      DO -- Advance to next possible bit position
	IF (b ← (b + 1) MOD bitsPerWord) = 0 THEN DO
	  w ← IF w = realPageMax/bitsPerWord
	    THEN realPageMin/bitsPerWord
	    ELSE w + 1;
	  IF (word ← allocationMap[w]) ~= 177777B THEN EXIT;
	  ENDLOOP;
        -- See if it is free:
	IF Inline.BITAND[word, Inline.BITSHIFT[1, b]] = 0 THEN EXIT;
	ENDLOOP;
      ProcessInternal.DisableInterrupts[];  -- maintain consistency for RecoverMStore
      allocationMap[w] ← Inline.BITOR[word, Inline.BITSHIFT[1, b]];
      -- Verify that page is not already mapped:
      IF GetF[interval.page].valueOld.flags~=flagsVacant THEN
        RuntimeInternal.WorryCallDebugger[
	  "MStore.Allocate given already-mapped vm"];
      Assoc[interval.page, Value[FALSE, flagsClean, w*bitsPerWord + b]];
      countFree ← countFree - 1;
      ProcessInternal.EnableInterrupts[];
      interval.page ← interval.page + 1;
      interval.count ← interval.count - 1;
      ENDLOOP;
    IF countFree + countPromised <= countThreshold + countHeldBack THEN
      BROADCAST allocation;  -- wake up the SwapOutProcess.
    ENDLOOP;
  END;
  
AwaitBelowThreshold: PUBLIC ENTRY PROCEDURE RETURNS [newCycle: BOOLEAN] =
  BEGIN
  IF countFree+countPromised <= countThreshold+countHeldBack THEN
    RETURN[newCycle: FALSE];
  UNTIL countFree + countPromised <= countThreshold + countHeldBack DO
    WAIT allocation ENDLOOP;
  RETURN[newCycle: TRUE];
  END;
  
deallocateInternal: PUBLIC DeallocateInternal ←
  -- (PRIVATE in interface)  ("←" due to compiler glitch)
  [LOOPHOLE[@AwaitDeallocateRequest]];
    -- an indirect control link to the PORT.

AwaitDeallocateRequest: --RESPONDING--PORT
  RETURNS [interval: Interval, promised: BOOLEAN];
  -- args/results match deallocateInternal (but swapped).

InitializeDeallocate: INTERNAL PROCEDURE =
  BEGIN
  interval: Interval;
  promised: BOOLEAN;
  count: PageCount;
  -- set my PORT call to return to my caller on call below:
  LOOPHOLE[AwaitDeallocateRequest, PrincOps.Port].dest ←
    Frame.GetReturnLink[];
  DO --FOREVER--
    -- Await new request;  Process it;
    [interval, promised] ← AwaitDeallocateRequest[];
    Frame.SetReturnLink[
      LOOPHOLE[AwaitDeallocateRequest, PrincOps.Port].dest];  -- for debugger
    count ← 0;
    ProcessInternal.DisableInterrupts[];  -- maintain consistency for RecoverMStore
    FOR offset: PageOffset IN [0..interval.count) DO
      value: Value = SetF[interval.page + offset, valueVacant];
      IF value.flags ~= flagsVacant THEN
	BEGIN
	w: CARDINAL = value.realPage/bitsPerWord;
	bit: WORD = Inline.BITSHIFT[1, value.realPage MOD bitsPerWord];
	IF value.realPage NOT IN [realPageMin..realPageMax] THEN
	  RuntimeInternal.WorryCallDebugger[
	    "MStore.Deallocate given reserved real page"];
	allocationMap[w] ←
	  Inline.BITAND[allocationMap[w], Inline.BITNOT[bit]];
	count ← count + 1;
	END;
      ENDLOOP;
    countFree ← countFree + count;
    ProcessInternal.EnableInterrupts[];
    IF promised THEN countPromised ← countPromised - count;
    IF countFree > countHeldBack THEN BROADCAST deallocation;
    ENDLOOP;
  END;
  
DonateDedicatedRealMemory:
    PUBLIC ENTRY PROCEDURE [page: PageNumber, size: PageCount] =
  BEGIN
  FOR offset: PageOffset IN [0..size) DO 
    value: Value = GetF[page+offset];
    IF value.flags = flagsVacant THEN LOOP;
    realPageMin ← MIN[realPageMin, value.realPage];
    realPageMax ← MAX[realPageMax, value.realPage];
    CheckRealPageMax[];
    ENDLOOP;
  deallocateInternal[interval: [page: page, count: size], promised: FALSE];
  END;

Promise: PUBLIC ENTRY PROCEDURE [count: PageCount] =
  {countPromised ← countPromised + count};
  
--StoragePrograms.--RecoverMStore: PUBLIC PROCEDURE =
  BEGIN
  page: PageNumber ← 0;
  FOR realPage: RealPageNumber IN [realPageMin..realPageMax] DO
    w: CARDINAL = realPage/bitsPerWord;
    bit: WORD = Inline.BITSHIFT[1, realPage MOD bitsPerWord];
    IF Inline.BITAND[allocationMap[w], bit] = 0 THEN
      DO  -- find next vacant virtual page
        IF GetF[page ← page + 1].valueOld.flags=flagsVacant THEN
          {Assoc[page, Value[FALSE, flagsClean, realPage]]; EXIT}
        ENDLOOP;
    ENDLOOP;
  END;
  
Relocate: PUBLIC ENTRY PROCEDURE [
  interval: Interval, pageDest: PageNumber, flagsKeep, flagsAdd: Flags]
  RETURNS [flags: Flags, anyVacant: BOOLEAN] =
  -- See note in MStore
  BEGIN
  ValueAnd: PROCEDURE [mv1, mv2: Value] RETURNS [Value] = LOOPHOLE[Inline.BITAND];
  ValueOr: PROCEDURE [mv1, mv2: Value] RETURNS [Value] = LOOPHOLE[Inline.BITOR];
  valueKeep: Value = [FALSE, flagsKeep, 7777B];
    -- mask to extract flags and realPage
  valueAdd: Value = [FALSE, flagsAdd, 0]; -- bit mask to OR in new flags
  value1: Value;
  value2: Value =
    IF flagsKeep = flagsNone AND interval.page = pageDest THEN valueAdd
    ELSE valueVacant;
  valueMax: Value ← [logSingleError:, flags: flagsNone, realPage:];
  anyVacant ← FALSE;
  FOR offset: PageOffset IN [0..interval.count) DO
    ProcessInternal.DisableInterrupts[];
      -- maintain consistency for RecoverMStore
    value1 ← SetF[interval.page + offset, value2];
    IF value1.flags = flagsVacant THEN anyVacant ← TRUE
    ELSE
      BEGIN
      IF value2 = valueVacant THEN
        Assoc[pageDest+offset,
	  ValueOr[ValueAnd[value1, valueKeep], valueAdd]];
      valueMax ← ValueOr[valueMax, value1];
      END;
    ProcessInternal.EnableInterrupts[];
    ENDLOOP;
  flags ← valueMax.flags
  END;
  
SetThreshold: PUBLIC ENTRY PROCEDURE [count: PageCount] =
  { countThreshold ← count;  BROADCAST allocation;  BROADCAST deallocation };

CheckRealPageMax: PROCEDURE =
  BEGIN
  IF realPageMax/bitsPerWord>=LENGTH[RealMemory.allocMap] THEN
    BEGIN
    RuntimeInternal.WorryCallDebugger["Too much real memory"L];
    realPageMax ← LENGTH[RealMemory.allocMap]*bitsPerWord-1;
    END;
  END;

END.

LOG	(For earlier entries see Pilot 4.0 archive version)

	April 16, 1980  9:35 AM   Knutsen
Make Deallocate, GetState coroutines; add InitializeMStore[];
recover=>RecoverMStore; add "t" key switch

	April 28, 1980  9:35 AM   Forrest
FrameOps=>Frame, ControlDefs=>PrincOps

	May 30, 1980  9:21 AM   Knutsen
Make "t" key switch work right; also, amount of useable real mem
settable dynamically

	August 12, 1980  11:04 AM   McJones
Add ProcessorFace.dedicatedRealMemory to realMemorySize; delete
INLINE from Initialize

	September 23, 1980  11:03 AM   McJones
Add check that virtual page to be mapped is not already mapped

	October 3, 1980  9:04 PM   Forrest
Add donateDedicatedMemory.  Change some ValueAND[] = valueVacant to
.flags = flagsVacant.  Gunned GetState (the devil made me do it...)

	December 2, 1980  10:15 AM   Knutsen
Cosmetic cleanups. 

	January 15, 1981  2:54 PM   Gobbel
Import alloc table from RealMemory so we get different size arrays
for different processors. 

	January 30, 1981  11:19 AM   McJones
Add check real page being deallocated is not reserved; use
realPageMin,Max instead of wMin,Max; change sense of threshold

	January 30, 1981  11:19 AM   McJones
Add check real page being deallocated is not reserved; use
realPageMin,Max instead of wMin,Max; change sense of threshold

February 14, 1981  5:35 PM	Knutsen
	Deallocate should always BROADCAST.

	February 23, 1981  8:54 AM   Knutsen
Make wait and wakeup conditions be the same.  Disable aborts and timeouts.  Got rid of extra level of initialization procedure.