--MesaRuntime>FrameImpl.mesa  (December 8, 1982 9:57 pm by Levin)

DIRECTORY
  CPSwapDefs USING [SwapInfo],
  Environment USING [wordsPerPage],
  File USING [Capability, GetAttributes, Type],
  FileTypes USING [DCSFileType],
  Frame USING [Alloc, Free, GetReturnFrame, SetReturnLink],
  Inline USING [BITAND, COPY],
  PrincOps USING [
    AllocationVectorSize, AV, AVHandle, AVItem, ControlLink, CSegPrefix, EPRange,
    Frame, FrameCodeBase, FrameHandle, FrameSizeIndex, FrameVec, GFTIndex,
    GlobalFrameHandle, LargeReturnSlot, LastAVSlot, MainBodyIndex, NullFrame,
    NullLink, NullGlobalFrame, UnboundLink],
  PrincOpsRuntime USING [EmptyGFTItem, FreedGFTItem, GetFrame, GFT, GFTItem],
  Process USING [GetPriority, Priority, SetPriority],
  ProcessInternal USING [DisableInterrupts, EnableInterrupts],
  ProcessOperations USING [Enter, IndexToHandle, LongReEnter, LongWait, Requeue],
  ProcessPriorities USING [priorityFrameFault],
  PSB USING [
    FaultIndex, NoTimeout, PDA, PDABase, PsbHandle, Queue, QueueEmpty,
    qFrameFault],
  ResidentMemory USING [AllocateMDS, FreeMDS],
  Runtime USING [NullProgram, UnboundProcedure, UnNew],
  RuntimeInternal USING [],
  RuntimePrograms USING [],
  SDDefs USING [sCopy, SD, sGFTLength, sUnNew],
  Space USING [
    Create, Delete, Error, GetAttributes, GetHandle, GetWindow, Handle, LongPointer, Map,
    PageFromLongPointer, virtualMemory, WindowOrigin],
  System USING [GreenwichMeanTime];

FrameImpl: MONITOR LOCKS gftLock
  IMPORTS
    File, Frame, Inline, PrincOpsRuntime, Process, ProcessInternal, ProcessOperations,
    ResidentMemory, Runtime, Space
  EXPORTS Runtime, RuntimeInternal, RuntimePrograms =

  BEGIN OPEN PrincOpsRuntime;

  ControlLink: TYPE = PrincOps.ControlLink;
  FrameHandle: TYPE = PrincOps.FrameHandle;
  GFTIndex: TYPE = PrincOps.GFTIndex;
  GlobalFrameHandle: TYPE = PrincOps.GlobalFrameHandle;
  LargeReturnSlot: CARDINAL = PrincOps.LargeReturnSlot;
  NullGlobalFrame: PrincOps.GlobalFrameHandle = PrincOps.NullGlobalFrame;
  AV: PrincOps.AVHandle = PrincOps.AV;
  NullProgram: PROGRAM = Runtime.NullProgram;

  -- Public SIGNALs and ERRORs:
  --Runtime.-- InvalidFrame: PUBLIC ERROR [frame: FrameHandle] = CODE;
  --Runtime.-- InvalidGlobalFrame: PUBLIC ERROR [frame: GlobalFrameHandle] = CODE;
  --RuntimePrograms.-- NoGlobalFrameSlots: PUBLIC SIGNAL [CARDINAL] = CODE;

  gftLock: MONITORLOCK;  -- This lock protects the GlobalFrameTable (and gftRover).
  -- frameFaultLock protects the local frame heap (and the Frane Fault Handler's variables).
  -- (However, since there is only one process that explicitly updates the frame heap,
  -- this lock is only necessary to allow the frame fault process to have a monitor to
  -- wait from.  We use a separate lock so that the frame fault process will not be blocked
  -- by other processes accessing the GFT.)
  frameHeapLock: MONITORLOCK;

  gftRover: CARDINAL ← 1;  -- for creation of new GFT entries. (Note that 0 is reserved.)

  --RuntimePrograms.--
  InitializeFrameImpl: PUBLIC PROCEDURE[] =
    BEGIN
    throwAway: PROCESS;
    priorityPrev: Process.Priority = Process.GetPriority[];
    Process.SetPriority[ProcessPriorities.priorityFrameFault];
    throwAway ← FORK FrameFaultProcess[];  -- no profit in detaching.
    Process.SetPriority[priorityPrev];
    SDDefs.SD[SDDefs.sCopy] ← Copy;
    SDDefs.SD[SDDefs.sUnNew] ← zUnNew;
    END;

  -- Procedures: (ordered by kind {external, entry, internal};  within a kind, alphabetically)

  -- External Procedures (public and private):

  --RuntimeInternal.--
  Codebase: PUBLIC PROC [frame: PROGRAM] RETURNS [l: LONG POINTER] =
    BEGIN OPEN c: LOOPHOLE[l, PrincOps.FrameCodeBase];
    c ← LOOPHOLE[frame, GlobalFrameHandle].code;
    c.out ← FALSE;
    END;

  --RuntimeInternal.--
  DeletedFrame: PUBLIC PROCEDURE [gfi: GFTIndex] RETURNS [BOOLEAN] = {
    RETURN[GFT[gfi] = FreedGFTItem]};

  --RuntimeInternal.--
  FrameSize: PUBLIC PROCEDURE [fsi: CARDINAL] RETURNS [CARDINAL] = {
    RETURN[PrincOps.FrameVec[fsi]]};

  --Runtime.--
  GetCaller: PUBLIC SAFE PROCEDURE RETURNS [PROGRAM] = TRUSTED {
    RETURN[LOOPHOLE[Frame.GetReturnFrame[].returnlink.frame.accesslink]]; };

  --Runtime.--
  GetTableBase: PUBLIC PROC [frame: PROGRAM] RETURNS [l: LONG POINTER] = Codebase;

  --Runtime.--
  GlobalFrame: PUBLIC PROCEDURE [link: UNSPECIFIED] RETURNS [PROGRAM] =
    BEGIN OPEN l: LOOPHOLE[link, ControlLink];
    DO
      IF l = PrincOps.UnboundLink THEN
        link ← SIGNAL Runtime.UnboundProcedure[link]
      ELSE
        IF l.proc THEN
          RETURN[
            IF l.gfi IN [1..SDDefs.SD[SDDefs.sGFTLength]) THEN LOOPHOLE[GetFrame[
            GFT[l.gfi]], PROGRAM] ELSE NullProgram]
        ELSE
          IF l.indirect THEN link ← l.link↑
          ELSE  -- Frame
            BEGIN
            IF link = 0 THEN RETURN[NullProgram];
            IF ValidGlobalFrame[link] THEN RETURN[link];
            RETURN[
              IF ValidGlobalFrame[l.frame.accesslink] THEN
              LOOPHOLE[l.frame.accesslink, PROGRAM] ELSE NullProgram];
            END;
      ENDLOOP;
    END;

  --Runtime.--
  IsBound: PUBLIC PROCEDURE [link: UNSPECIFIED] RETURNS [BOOLEAN] = {
    RETURN[link # PrincOps.UnboundLink AND link # PrincOps.NullLink]; };

  --RuntimeInternal.--
  MakeFsi: PUBLIC PROCEDURE [words: CARDINAL] RETURNS [fsi: CARDINAL] = {
    FOR fsi IN [0..PrincOps.LastAVSlot) DO
      IF PrincOps.FrameVec[fsi] >= words THEN RETURN; ENDLOOP;
    RETURN[words]};

  --Runtime.--
  GetBcdTime: PUBLIC SAFE PROCEDURE RETURNS [time: System.GreenwichMeanTime] = TRUSTED
    BEGIN
    codeFile: File.Capability;
    BEGIN
    ENABLE Space.Error => GO TO noLeader;
    -- don't want Pilot to depend on DCSFileTypes
    tLeaderPage: File.Type = [FileTypes.DCSFileType[515]];
    space: Space.Handle ← Space.GetHandle[Space.PageFromLongPointer[
    	Codebase[GlobalFrame[Frame.GetReturnFrame[]]]]];
    DO
		parent: Space.Handle;
		mapped: BOOLEAN;
		[parent: parent, mapped: mapped] ← Space.GetAttributes[space];
		IF mapped THEN EXIT;
		space ← parent;
		ENDLOOP;
    codeFile ← Space.GetWindow[space].file;
    IF File.GetAttributes[codeFile].type ~= --DCSFileTypes.--tLeaderPage THEN GO TO noLeader;
    EXITS
      noLeader => RETURN[GetBuildTime[]];
    END;
    BEGIN
    LeaderPageFront: TYPE = -- stolen from FileStreamImpl
      MACHINE DEPENDENT RECORD [
        versionID: CARDINAL,
        dataType: --FileStream.Subtype-- WORD,
        create: System.GreenwichMeanTime];
    leaderSpace: Space.Handle = Space.Create[size: 1, parent: Space.virtualMemory];
    leader: LONG POINTER TO LeaderPageFront = Space.LongPointer[leaderSpace];
    Space.Map[leaderSpace, Space.WindowOrigin[codeFile, 0]];
    time ← leader.create;
    Space.Delete[leaderSpace];
    END;
    END;

  --Runtime.--
  GetBuildTime: PUBLIC SAFE PROCEDURE RETURNS [time: System.GreenwichMeanTime] = TRUSTED {
    pdaDumpingGround: LONG POINTER TO CPSwapDefs.SwapInfo = LOOPHOLE[@PSB.PDA.available];
    -- Assumes MakeBoot has put a copy of the boot file creation date in
    -- PSB.PDA.available[3..4].  This will be available even if we were ether-booted
    -- and the boot file header is no longer available.  (Of course, it shouldn't have
    -- to do this; the Germ should save the creation date from the header and store it
    -- somewhere, but this requires changing too many interfaces.)
    RETURN[LOOPHOLE[pdaDumpingGround.availableB]]
    };


  --Runtime.--
  SelfDestruct: PUBLIC PROCEDURE[] = {
    destructee: PrincOps.FrameHandle = Frame.GetReturnFrame[];
    Frame.SetReturnLink[destructee.returnlink];
    Runtime.UnNew[LOOPHOLE[GlobalFrame[destructee], PROGRAM]];
    Frame.Free[destructee]};

  -- Entry Procedures:

  Copy: --PUBLIC-- ENTRY PROCEDURE [old: GlobalFrameHandle]
    RETURNS [new: GlobalFrameHandle] =
    -- conceptually, Copy is PUBLIC, but it is accessed via the System Dispatch table.
    BEGIN
    linkspace: CARDINAL;
    codebase: LONG POINTER TO PrincOps.CSegPrefix;
    IF ~ValGlobalFrame[old] THEN RETURN WITH ERROR InvalidGlobalFrame[old];
    codebase ← Codebase[LOOPHOLE[old, PROGRAM]];
    [new, linkspace] ← AllocGlobalFrame[old, codebase];
    new ← new + linkspace;
    new↑ ← [
      gfi:, alloced: TRUE, shared: TRUE, copied: TRUE, started: FALSE,
      trapxfers: FALSE, codelinks: old.codelinks, code: old.code, global:];
    new.code.out ← TRUE;  -- cause trap
    new.global[0] ← NullGlobalFrame;
    IF linkspace # 0 THEN
      Inline.COPY[from: old - linkspace, to: new - linkspace, nwords: linkspace];
    IF ~EntGlobalFrame[new, codebase.header.info.ngfi] THEN
      RETURN WITH ERROR NoGlobalFrameSlots[codebase.header.info.ngfi];
    old.shared ← TRUE;
    END;

  --RuntimeInternal.--
  EnterGlobalFrame: PUBLIC ENTRY PROCEDURE [frame: GlobalFrameHandle, nslots: CARDINAL]
    RETURNS [entryindex: GFTIndex] = {
    IF ~EntGlobalFrame[frame, nslots] THEN RETURN WITH ERROR NoGlobalFrameSlots[nslots];
    RETURN[frame.gfi]};

  --RuntimeInternal.--
  GetNextGlobalFrame: PUBLIC ENTRY PROCEDURE [frame: GlobalFrameHandle]
    RETURNS [GlobalFrameHandle] = {
    IF frame # NullGlobalFrame AND ~ValGlobalFrame[frame] THEN
      RETURN WITH ERROR InvalidGlobalFrame[frame]
    ELSE RETURN[GetNxGlobalFrame[frame]]};


  --RuntimePrograms.--
  RemoveGlobalFrame: PUBLIC ENTRY PROCEDURE [frame: GlobalFrameHandle] = {
    RemvGlobalFrame[frame]};

  zUnNew: --PUBLIC-- ENTRY PROCEDURE [frame: GlobalFrameHandle] =
    -- conceptually, (z)UnNew is PUBLIC, but is accessed via the System Dispatch table.
    BEGIN
    sharer: GlobalFrameHandle ← NullGlobalFrame;
    original: GlobalFrameHandle ← NullGlobalFrame;
    copy, f: GlobalFrameHandle ← NullGlobalFrame;
    codebase: LONG POINTER TO PrincOps.CSegPrefix;
    nothers: CARDINAL ← 0;
    nlinks: CARDINAL;
    IF ~ValGlobalFrame[frame] THEN RETURN WITH ERROR InvalidGlobalFrame[frame];
    codebase ← Codebase[LOOPHOLE[frame, PROGRAM]];
    nlinks ← codebase.header.info.nlinks;
    FOR f ← GetNxGlobalFrame[NullGlobalFrame], GetNxGlobalFrame[f] UNTIL f =
      NullGlobalFrame DO
      IF f # frame THEN
        BEGIN
        IF f.global[0] = frame AND ~f.started THEN
          f.global[0] ← PrincOps.NullFrame;
        IF Codebase[LOOPHOLE[f, PROGRAM]] = codebase THEN
          IF f.copied THEN copy ← f ELSE original ← f;
        END;
      ENDLOOP;
    -- To aid debugging, at present we don't delete the original copy because it has the original links:
    IF original = NullGlobalFrame AND ~frame.copied AND copy # NullGlobalFrame
      THEN RETURN WITH ERROR InvalidGlobalFrame[frame];
    --    BEGIN OPEN LoadStateDefs;
    --    config: ConfigIndex;
    --    cgfi: GFTIndex;
    --    copy.copied ← FALSE;
    --    [] ← InputLoadState[];
    --    [cgfi: cgfi, config: config] ← MapRealToConfig[frame.gfi];
    --    EnterGfi[cgfi: 0, rgfi: frame.gfi, config: ConfigNull];
    --    EnterGfi[cgfi: cgfi, rgfi: copy.gfi, config: config];
    --    ReleaseLoadState[];
    --    END;
    RemvGlobalFrame[frame];
    IF frame.alloced THEN {
      Align: PROCEDURE [POINTER, WORD] RETURNS [POINTER] =
        LOOPHOLE[Inline.BITAND];
      IF frame.codelinks THEN Frame.Free[frame]
      ELSE Frame.Free[Align[frame - nlinks, 177774B]]};
    END;

  --Runtime.--
  ValidateFrame: PUBLIC PROCEDURE [frame: FrameHandle] = {
    OPEN LOOPHOLE[frame, rep ControlLink];
    IF proc OR indirect OR ~ValidGlobalFrame[frame.accesslink] THEN ERROR InvalidFrame[frame]};

  --Runtime.--
  ValidateGlobalFrame: PUBLIC PROCEDURE [g: GlobalFrameHandle] = {
    IF ~ValidGlobalFrame[g] THEN ERROR InvalidGlobalFrame[g]};

  ValidGlobalFrame: PRIVATE ENTRY PROCEDURE [g: GlobalFrameHandle]
    RETURNS [BOOLEAN] = INLINE {RETURN[ValGlobalFrame[g]]};

  -- Internal Procedures:

  AllocGlobalFrame: INTERNAL PROCEDURE [
    old: GlobalFrameHandle, cp: LONG POINTER TO PrincOps.CSegPrefix]
    RETURNS [frame: GlobalFrameHandle, linkspace: CARDINAL] =
    BEGIN
    pbody: LONG POINTER =
      cp + CARDINAL[cp.entry[PrincOps.MainBodyIndex].initialpc];
    nlinks: CARDINAL = cp.header.info.nlinks;
    linkspace ←
      IF ~old.codelinks THEN
      nlinks + Inline.BITAND[-LOOPHOLE[nlinks, INTEGER], 3B] ELSE 0;
    frame ← Frame.Alloc[MakeFsi[(pbody - 1)↑ + linkspace]];
    END;

  EntGlobalFrame: INTERNAL PROCEDURE [frame: GlobalFrameHandle, nslots: CARDINAL]
    RETURNS [ok: BOOLEAN] =
    BEGIN
    entryindex: GFTIndex;
    k, kMax, n, epoffset: CARDINAL;
    k ← gftRover;
    kMax ← SDDefs.SD[SDDefs.sGFTLength] - nslots;
    n ← 0;
    DO
      IF (k ← IF k >= kMax THEN 1 ELSE k + 1) = gftRover THEN RETURN[FALSE];
      IF GFT[k] # EmptyGFTItem THEN n ← 0 ELSE IF (n ← n + 1) = nslots THEN EXIT;
      ENDLOOP;
    entryindex ← (gftRover ← k) - nslots + 1;
    epoffset ← 0;
    FOR k IN [entryindex..gftRover] DO
      GFT[k].framePtr ← frame;
      GFT[k].epbias ← epoffset;
      epoffset ←
        epoffset +
          -- 1 with new format, 32 with old format
          (IF SIZE[GFTItem] = 2 THEN PrincOps.EPRange ELSE 1);
      ENDLOOP;
    frame.gfi ← entryindex;
    RETURN[TRUE];
    END;

  GetNxGlobalFrame: INTERNAL PROCEDURE [frame: GlobalFrameHandle]
    RETURNS [GlobalFrameHandle] =
    BEGIN
    gfi: GFTIndex;
    IF frame = NullGlobalFrame THEN gfi ← 1 ELSE gfi ← frame.gfi + 1;
    WHILE gfi < SDDefs.SD[SDDefs.sGFTLength] DO
      frame ← GetFrame[GFT[gfi]];
      IF frame # NullGlobalFrame AND GFT[gfi].epbias = 0 THEN RETURN[frame];
      gfi ← gfi + 1;
      ENDLOOP;
    RETURN[NullGlobalFrame]
    END;

  InGFT: INTERNAL PROCEDURE [g: GlobalFrameHandle] RETURNS [BOOLEAN] = {
    FOR k: CARDINAL IN [1..SDDefs.SD[SDDefs.sGFTLength]) DO
      entry: GFTItem = GFT[k];
      IF entry ~= EmptyGFTItem AND entry ~= FreedGFTItem AND
       GetFrame[entry] = g AND g.gfi = k THEN RETURN[TRUE];
      ENDLOOP;
    RETURN[FALSE]};

  RemvGlobalFrame: INTERNAL PROCEDURE [frame: GlobalFrameHandle] = {
    FOR k: CARDINAL ← frame.gfi, k + 1 WHILE k < SDDefs.SD[SDDefs.sGFTLength]
      AND GetFrame[GFT[k]] = frame DO
      GFT[k] ← IF frame.copied THEN EmptyGFTItem ELSE FreedGFTItem ENDLOOP};

  ValGlobalFrame: INTERNAL PROCEDURE [g: GlobalFrameHandle] RETURNS [BOOLEAN] =
    INLINE {
    OPEN LOOPHOLE[g, rep ControlLink]; RETURN[~proc AND ~indirect AND InGFT[g]]};

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Frame Allocation Fault Handler
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- The global variables below are protected by frameHeapLock.

  pda: PSB.PDABase = PSB.PDA;
  qFrameFault: PSB.FaultIndex = PSB.qFrameFault;
  pFrameFaultCondition: LONG POINTER TO CONDITION = LOOPHOLE[@pda.fault[
    qFrameFault].condition];

  AnyFrameSizeIndex: TYPE = CARDINAL [0..PrincOps.AllocationVectorSize);  -- note that a AnyFrameSizeIndex immediately preceeds a Frame.
  NormalFrameSizeIndex: TYPE = PrincOps.FrameSizeIndex;
  FsiFrame: TYPE = MACHINE DEPENDENT RECORD [
    fsi(0): AnyFrameSizeIndex,  -- must be at 3 MOD 4 boundary.
    frame(1): local PrincOps.Frame];
  FrameSegment: TYPE = POINTER TO FrameSegmentHeader;
  FrameSegmentHeader: TYPE = MACHINE DEPENDENT RECORD [
    link(0): FrameSegment,
    pages(1): CARDINAL,
    sizeIfLargeFrame(2): CARDINAL,  -- (for debugging only. not used in small frame segment)
    fsiFrame(3): ARRAY [0..0) OF --WORD-- FsiFrame];  -- must be at 3 MOD 4 boundary.

  largeFrameThresholdFsi: NormalFrameSizeIndex = 12;  -- frames this size or larger will be allocated in an integral number of pages, and reclaimed when they are freed. FrameVec[largeFrameThresholdFsi] must be < wordsPerPage.
  frameListHead: FrameSegment ← NIL;  -- list of all dynamically-allocated "permanent"  (small) frame segments (for debugging only).
  pNewFsiFrame: POINTER TO --ARRAY [0..0) OF WORD-- FsiFrame;  -- storage available for building new frames.
  storageRemaining: CARDINAL ← 0;  -- words remaining in pNewFsiFrame↑.

  FrameFaultProcess: --ENTRY-- PROCEDURE[] --LOCKS frameHeapLock--  =
    BEGIN
    -- "arguments":
    process: PSB.PsbHandle;
    fsi: NormalFrameSizeIndex;  -- frame size index of frame desired.
    -- "results":
    pNewFrame: FrameHandle;  -- the frame we will allocate and paste into the AV.
    -- "temporary" variables:
    frSize: CARDINAL;  -- word size of frame desired, including fsi word.  Guaranteed to be a multiple of 4.
    k: CARDINAL;
    frameSeg: FrameSegment;
    UNTIL ProcessOperations.Enter[@frameHeapLock] DO NULL ENDLOOP;
    --FOREVER--
    DO
      WHILE pda.fault[qFrameFault].queue = PSB.QueueEmpty DO  -- await next Frame Fault..
        ProcessOperations.LongWait[
          @frameHeapLock, pFrameFaultCondition, PSB.NoTimeout];
        UNTIL ProcessOperations.LongReEnter[@frameHeapLock, pFrameFaultCondition]
          DO NULL ENDLOOP;
        ENDLOOP;
      process ← ProcessOperations.IndexToHandle[
        pda.block[pda.fault[qFrameFault].queue.tail].link.next];  -- walk to tail, then to head.
      fsi ← pda[pda[process].context.state].fsi;
      frSize ← PrincOps.FrameVec[fsi] + SIZE[AnyFrameSizeIndex];  -- must be a multiple of 4!
      -- First free any unused large frames:
      -- (Note that AV[LargeReturnSlot].tag, .frame, and .link are overlaid.)
      WHILE AV[LargeReturnSlot].tag = frame DO
        -- Atomically remove some large frame from freelist:
        ProcessInternal.DisableInterrupts[];  -- so no one frees during list delete.
        frameSeg ←  -- grab addr of large frame and back over overhead stuff
          LOOPHOLE[AV[LargeReturnSlot].frame - SIZE[FrameSegmentHeader] - SIZE[
                     AnyFrameSizeIndex]];
        AV[LargeReturnSlot].link ← AV[LargeReturnSlot].link↑.link;
        ProcessInternal.EnableInterrupts[];
        ResidentMemory.FreeMDS[frameSeg, frameSeg.pages];
        ENDLOOP;
      IF fsi >= largeFrameThresholdFsi THEN
        BEGIN  --alloc large frame--
        frameSeg ← ResidentMemory.AllocateMDS[
          pages: k ←
          (frSize + SIZE[FrameSegmentHeader] + Environment.wordsPerPage -
             1)/Environment.wordsPerPage];
        frameSeg↑ ← [
          link: NIL, pages: k, sizeIfLargeFrame: frSize, fsiFrame: NULL];
        frameSeg.fsiFrame[0].fsi ← LargeReturnSlot;  -- (a fsi never generated by the compiler.)
        pNewFrame ← @frameSeg.fsiFrame[0].frame;
        END  -- alloc large frame
      ELSE
        BEGIN  --alloc small frame--
        IF storageRemaining < frSize THEN
          BEGIN  --alloc more storage for frame--
          -- Use any remaining storage for a frame:
          FOR k DECREASING IN [0..fsi) DO
            IF CARDINAL[PrincOps.FrameVec[k] + SIZE[FrameSegmentHeader]] <=
              storageRemaining THEN {
              pNewFsiFrame.fsi ← k;
              Frame.Free[@pNewFsiFrame.frame];  -- atomically paste onto frame heap.
              EXIT}
            ENDLOOP;
          -- Allocate a new page from which to build frames:
          frameSeg ← ResidentMemory.AllocateMDS[pages: 1];
          frameSeg.link ← frameListHead;
          frameListHead ← frameSeg;
          frameSeg.pages ← 1;
          pNewFsiFrame ← @frameSeg.fsiFrame[0];  -- must be at 3 MOD 4 boundary.
          storageRemaining ← Environment.wordsPerPage - SIZE[FrameSegmentHeader];
          END;  --alloc more storage for frame--
        -- IF storageRemaining < frSize THEN
        --     RuntimeInternal.WorryCallDebugger["FrameFaultBug"L];
        -- Fabricate a new frame:
        pNewFsiFrame.fsi ← fsi;
        pNewFrame ← @pNewFsiFrame.frame;
        pNewFsiFrame ← pNewFsiFrame + frSize;
        storageRemaining ← storageRemaining - frSize;
        END;  --alloc small frame--
      -- 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.
      ProcessInternal.DisableInterrupts[];  -- so no one frees during the list insert.
      LOOPHOLE[pNewFrame, POINTER TO PrincOps.AVItem]↑.link ← AV[fsi].link;
      AV[fsi]. --link-- frame ← pNewFrame;
      ProcessInternal.EnableInterrupts[];
      -- Restart faulted process:
      ProcessOperations.Requeue[
        @pda.fault[qFrameFault].queue, @pda.ready, process];
      ENDLOOP;
    END;

  END.

LOG
(For earlier log entries see Pilot 4.0 archive version.)
April 14, 1980  10:45 AM        Knutsen        Now STARTed by InitializeFrames[].
April 29, 1980  9:04 PM        Forrest        Put back old InGFT
May 3, 1980  11:44 AM        Forrest        Initial Mesa 6.0 conversion
July 20, 1980  9:03 PM        Forrest        PrincOpsRuntime
August 1, 1980  2:04 PM        Luniewski        Rename to FrameImpl
August 26, 1980  12:27 PM        McJones        Add GetBcdTime
January 19, 1981  9:40 AM        Knutsen        Frame faults, not traps.  Fault handler, Codebase, GetTableBase moved here from Traps.
January 29, 1981  1:59 PM        Knutsen        Remove LOOPHOLEs used to get fault parameter.
February 14, 1981  5:44 PM        Knutsen        Leave faulted process on PDA queue.
14-Jan-82 16:57:39        Levin        Improve GetBcdTime/GetBuildTime
16-Feb-82 12:15:45        Levin        Fix InGFT not to consider GFT[0] (matches g=NIL!)
23-Mar-82 15:55:50        Levin        Fix GetBuildTime to work on ether booting.
June 1, 1982 3:56 pm        Levin        New loadstate format
August 18, 1982 3:46 pm		Levin		Change GetBcdTime to eliminate dependence on loadstate.
August 26, 1982 11:20 am		Levin		Make things SAFE.
September 8, 1982 12:55 pm	Levin	Fix frame validate procedures to avoid address faults within monitor.
October 25, 1982 1:20 pm	Levin	Fix EnterGlobalFrame to set gfi in new frame before exiting monitor (for Loader).
December 8, 1982 9:57 pm	Levin	InGFT no longer address faults if NullGlobalFrame is passed in.