-- Copyright (C) 1984, 1985, 1986, 1987  by Xerox Corporation. All rights reserved. 
-- Germ>GermOpsImpl.mesa    23-Nov-87  8:39:34 by CAJ 
<<

The BOOTING ACTION defined by the Principles of Operation should include:
   1. Put real memory behind any special processor pages (I/O pages); then put all remaining usable real memory behind other virtual memory pages beginning at virtual page 0, and working upward sequentially (skipping any already-mapped special processor pages).
   2. Read consecutive pages of the Germ into virtual memory beginning at page Boot.pageGerm + Boot.mdsiGerm*Environment.MaxPagesInMDS (i.e page 1).  At present, the way the initial microcode figures out the device and device address of the Germ, and the number of pages which comprise the Germ, is processor-dependent.
   3. Set Boot.pRequest↑ to e.g. [Boot.currentRequestBasicVersion, Boot.bootPhysicalVolume, locationOfPhysicalVolume].
   4. Set WDC>0, NWW=0, MDS=Boot.mdsiGerm, STKP=0.
   5. Xfer[dest: Boot.pInitialLink].


RUNTIME FACILITIES implemented for programs which comprise the Germ:
     Start traps
     SIGNAL and ERRORs will result in mp code cGermERROR.
     GermOps: PointerFromPage, GermWorldError, ShowCodeInMP,
       ShowCardinalInMP, etc. See GermOps for complete list.
     ResidentHeap: MakeNode, FreeNode (see Storage Allocation notes)
     ResidentMemory: Allocate, Free, AllocateMDS, FreeMDS
       (see Storage Allocation notes)
     Runtime.IsBound
     System.MicrosecondsToPulses

 Runtime facilities NOT implemented for programs which comprise the Germ:
     Frame, Page, and Write fault processing
     Mesa operations START, RESTART, STOP, FORK, JOIN, NEW
     C/Mesa operations CONTROL
     Constant initialization of arrays of strings
     Processor instructions implemented by software


STORAGE ALLOCATION NOTES:

      ResidentMemory facilities:

  Storage allocated during Germ initialization using the ResidentMemory interface is retained forever.  ResidentMemory may be allocated by a BootChannel implementation at the time the channel is Created and freed when it is closed (ResidentMemory.Free and FreeMDS are implemented as no-ops; the storage is actually recovered in bulk after the Channel is closed).  Currently, BootChannelSPP allocates temporary buffer space when its network channel is created.  When network operations other than Inload[inloadeMode: load] are implemented, BootChannelSPP will have to allocate this buffer space at germ initialization time and retain it forever.

      ResidentHeap facilities:

  At present, heap storage may not be allocated during Germ initialization using the ResidentHeap interface.  ResidentHeap may be allocated by a BootChannel implementation at the time the channel is Created and freed when it is closed (ResidentHeap.FreeNode is implemented as a no-op; the storage is actually recovered in bulk after the Channel is closed).  ResidentHeap.MakeNode and FreeNode only return status=okay; any allocation errors will result in an MP code.
  
  The storage for ResidentHeap is allocated either in the page containing the frame allocation vector (AV), past the part that is acutally used or from germ VM after germ code, depending on the size heap needed.


DEBUGGING:

  See the definition of GermOps.GermWorldError. debug mode is turned on by a boot switch. [If you can't get the germ past the boot-button boot, compile this module with debug turned on.]
  
  You may find it useful to insert special code that displays key values in the mp via GermOps.Show*InMP. Often, just displaying "progress codes" through a failing section of code is enough to point out the problem.
  
  If you get a reschedule error mp code, it is probably because you got a page or frame fault. [You get a reschedule error because the PDA FaultQueue.conditions are all zero and interrupts are disabled. [The germ initially zeroes these Conditions, and Pilot does so before calling the germ.]] The mp will show (in debug mode) the offending instruction. If it is a procedure call or ALLOC instruction, it is presumably a frame fault. You can verify this by allocating more frames in the bootmesa and trying again. Alternatively, a frame fault can be verified by inserting the following debugging code immediately before the problem statement:
  
    codeBase: LONG POINTER TO PACKED ARRAY [0..0) OF [0..256) =
      LOOPHOLE[FrameExtras.ReadCodebase[FrameExtras.MyGlobalFrame[]]];
    IF PrincOps.AV[codeBase
      prefixHandle.entry[<entry point index of called procedure>].pc]].tag # frame THEN
      GermOps.GermWorldError[<specialCode>];

The code given assumes a local function call. If this is not the case, you will have to supply the global frame address or codebase of the called module.

The debugging tool LocalFrameTool has facilities for examing the germ's frame heap. This is useful for seeing how close the germ is to running out of frames. See comments in Germ.bootmesa for frame heap tuning strategies. 

The debugging tool Microscope has facilities for dumping germ memory.

>>

DIRECTORY
  Boot USING [
    bootPhysicalVolume, bootPhysicalVolumeDiskAddress, countGermVM,
    currentRequestBasicVersion, currentRequestExtensionVersion, inLoad, Location,
    mdsiGerm, noOp, outLoad, pageGerm, pCountGerm, pRequest, Session, teledebug],
  BootChannel USING [
    Create, Handle, Operation, Result, Transfer, transferCleanup, transferWait],
  BootFile USING [
    currentVersion, MapEntry, Header, InLoadMode, maxEntriesPerHeader,
    maxEntriesPerTrailer, MDSIndex, Trailer],
  ControlModuleFormat USING [Call, MainBody],
  Device USING [nullType, Type],
  DeviceTypesExtras4 USING [FloppyTape],
  Environment USING [
    Base, bytesPerWord, first64K, LongPointerFromPage, maxPagesInMDS, PageCount,
    PageFromLongPointer, PageNumber, wordsPerPage],
  EthernetFace USING [TurnOn],
  Frame USING [
    Free, GetReturnFrame, ReadPC, ReadReturnLink, SetReturnLink],
  FrameExtras USING [
    LongGFToGFTHandle, ReadCodebase, ReadGlobalLink, WriteCodebase],
  GermMarkers USING [GatesOfHellMarker],
  GermOps USING [
    BackToPilot, BoundsReservedMemory, CallPilotInMds, GetTeledebugged,
    InitializeLinkage, InvokersMds, pCodeSharingHandles,
    ProcessMachineDependentSwitches, SharedCode],
  HeadStartChain USING [Start],
  Inline USING [BITOR, LongDiv, LowHalf, HighHalf],
  PageMap USING [
    ExchangeFlags, Flags, flagsClean, flagsVacant, GetState, IsMapped,
    maskReadOnly, PageNumber, RealPageNumber, SetMapFlags, State],
  PhysicalVolumeFormat USING [currentVersion, Descriptor, Seal],
  PilotDiskFace USING [
    GetControllerAttributes, GetNextController, InitializeController,
    nullControllerHandle, operationAlignment, operationSize],
  PilotMP USING [
    cCantTeledebug, cGerm, cGermAction, cGermBadBootFile, cGermBadBootFileVersion,
    cGermBadPhysicalVolume, cGermControlTrap, cGermDeviceError, cGermDriver,
    cGermERROR, cGermFinished, cGermInsufficientRealMemory, cGermWrongPilot, Code,
    cGermRescheduleTrap, cWrongGerm],
  PilotSwitches USING [germExtendedErrorReports],
  PrincOps USING [
    AV, AVHeapSize, BytePC, ESCTrapTable, GlobalCodebase, LocalFrameHandle,
    nullLocalFrame, ShortControlLink, StateVector],
  PrincOpsExtras2 USING [
    ControlLink, GFTHandle, nullLink, ProcDesc, trapLink, UnboundLink, GFT,
    ControlLinkTag],
  ProcessOperations USING [ReadMDS, WriteWDC],
  ProcessorFace USING [
    GetNextAvailableVM, microsecondsPerHundredPulses, mp, SetMP, SpecialSetMP,
    Start],
  PSB USING [Condition, PDA, PsbNull, QueueEmpty],
  ResidentHeap USING [HeapLocation],
  ResidentMemory USING [
    AllocateInternal, AllocateMDSInternal, FreeInternal, Location],
  Runtime USING [ControlLink],
  SDDefs USING [
    sCodeTrap, sControlTrap, SD, sError, sRescheduleError, sSignal],
  SpecialRuntimeExtras USING [GlobalFrameFromProgram],
  StartList USING [Base],
  System USING [Microseconds, Pulses, Switches],
  Trap USING [Parameter],
  Zone USING [Alignment, BlockSize, nil, Status];

GermOpsImpl: MONITOR LOCKS residentMemoryLock
  IMPORTS
    importedBootChannel: BootChannel, ControlModuleFormat, Environment,
    EthernetFace, GermMarkers, GermOps, Frame, FrameExtras,
    heads: HeadStartChain, Inline, ProcessorFace, PageMap, PilotDiskFace,
    ProcessOperations, SpecialRuntimeExtras, Trap
  EXPORTS BootChannel, GermOps, ResidentHeap, ResidentMemory, Runtime, System
  SHARES Boot, GermOps, PageMap, ResidentMemory =
  BEGIN

  -- PARAMETERS:

  debug: PUBLIC BOOLEAN ← FALSE;  -- set to TRUE by boot switch.

  -- TYPEs and TYPE CONVERSION:

  ConditionEmpty: PSB.Condition = [  -- TEMP until in PSB (AR 3927)
    tail: PSB.PsbNull, abortable: FALSE, wakeup: FALSE];

  PMapEntry: TYPE = ORDERED POINTER TO BootFile.MapEntry;
  OrderedPMapEntry: PROC [pme: POINTER TO BootFile.MapEntry]
    RETURNS [ORDERED POINTER TO BootFile.MapEntry] = INLINE {
      RETURN[LOOPHOLE[pme]]};

  PageNumber: TYPE = Environment.PageNumber;
  PageCount: TYPE = Environment.PageCount;

  -- CONSTANTS:

  pageZero: PageNumber = FIRST[PageNumber];
  sizeMapEntry: CARDINAL = SIZE[BootFile.MapEntry];

  bPW: CARDINAL = Environment.bytesPerWord;
  wordsPerPage: CARDINAL = Environment.wordsPerPage;

  flagsVacant: PageMap.Flags = PageMap.flagsVacant;
  flagsClean: PageMap.Flags = PageMap.flagsClean;

  -- GERM STORAGE ALLOCATION AND USE:

  -- ResidentHeap storage:
  -- This is in the first 64K for allocating IOCB's etc., since the germ is in
  -- the first 64K.
  -- The heap occupies one of two places depending on the size needed, which
  -- is calculated at germ init time.  A small heap uses the space in the page
  -- reserved for the allocation vector, past the part actually used by the AV.
  -- A large heap is allocated in germ VM after germ code.
  First64KStorage: TYPE = ARRAY [0..0) OF WORD;
  pHeap: Environment.Base RELATIVE ORDERED POINTER TO First64KStorage;
  pHeapAllocEnd: Environment.Base RELATIVE ORDERED POINTER;
  pHeapAllocNext: Environment.Base RELATIVE ORDERED POINTER;
    -- next storage to be allocated.

  -- Page buffer storage:
  -- used to read/write boot file Header/Trailer pages and phys vol root page.
  pageBuffer: PageNumber;
  pBuffer: POINTER;  -- pointer to pageBuffer.

  -- GERM GEOGRAPHY:

  pageGerm: PageNumber = Boot.pageGerm + Boot.mdsiGerm*Environment.maxPagesInMDS;
  pageEndGermVM: PageNumber = pageGerm + Boot.countGermVM;
  -- end VM page usable by Germ.
  pageGFT: PageNumber = Environment.PageFromLongPointer[PrincOpsExtras2.GFT];

  beforePage: PageNumber;
  middlePage: PageNumber;
  afterPage: PageNumber;

  flushFloppy: BOOLEAN ← TRUE;


  -- PROCEDURES:

  Create: PUBLIC --BootChannel.-- PROC [
    pLocation: LONG POINTER TO Boot.Location, operation: BootChannel.Operation,
    buffer: LONG POINTER]
    RETURNS [result: BootChannel.Result, handle: BootChannel.Handle] = {
    -- Backstop Create routine to plug end of chain of BootChannel interfaces.
    -- (Possibly invoked by dummy call to initialize BootChannel implementations)
    RETURN[[error[PilotMP.cGermDeviceError]], NIL]};


  ProcessRequests: PROC =
    -- Never returns to caller.  Frees caller's frame.
    BEGIN
    bootChannel: BootChannel.Handle;
    result: BootChannel.Result;
    ProcessorFace.SetMP[PilotMP.cGermAction];
    Frame.Free[Frame.GetReturnFrame[]];  -- free our caller's frame.
    Frame.SetReturnLink[
      Inline.LowHalf[
       LOOPHOLE[PrincOpsExtras2.trapLink]]];  -- (just in case)
    -- (The initial microcode has supplied the first Request.)
    IF Boot.pRequest.requestBasicVersion # Boot.currentRequestBasicVersion THEN
      GermWorldError[PilotMP.cWrongGerm];
    -- reclaim initialization code memory (heads.Start must have been called).
    FlushMemory[middlePage, afterPage + 1];  -- inclusive interval
    DO --FOREVER--
      BEGIN  --scope of HandleProblem--
      -- Each arm of the select statement below does:
      --   Process current Request;
      --   Generate new request, possibly by going back to Pilot until it
      --   generates one;
      SELECT Boot.pRequest.action FROM
        Boot.bootPhysicalVolume =>
          BEGIN
          -- Reads physical volume root page of request's device and
          --    generates an inload Request for that device:
          pvDesc: POINTER TO PhysicalVolumeFormat.Descriptor = PointerFromPage[
            pageBuffer];
          Boot.pRequest.location.diskFileID.da ←
            Boot.bootPhysicalVolumeDiskAddress;
          [result, bootChannel] ← importedBootChannel.Create[
            @Boot.pRequest.location, rawRead, LONG[pBuffer]];
	  IF result # [ok[]] THEN GO TO HandleProblem;
	  result ← DoTransfer[bootChannel, pageBuffer, 1];
	  IF result # [ok[]] THEN GO TO HandleProblem;
	  result ← DoTransfer[bootChannel, 0, BootChannel.transferWait];
	  IF result # [ok[]] THEN GO TO HandleProblem;
          IF pvDesc.seal ~= PhysicalVolumeFormat.Seal
            OR pvDesc.version ~= PhysicalVolumeFormat.currentVersion THEN
            GermWorldError[PilotMP.cGermBadPhysicalVolume];
	  [] ← DoTransfer[
	    bootChannel, 0, BootChannel.transferCleanup];  -- shut down channel.
          Boot.pRequest.location.diskFileID ← pvDesc.bootingInfo[pilot];
          Boot.pRequest.action ← Boot.inLoad;
          Boot.pRequest.requestExtensionVersion ←
            Boot.currentRequestExtensionVersion;
          -- Fall through to process the generated inload Request..
          END;
        Boot.inLoad =>
          BEGIN
          mds: BootFile.MDSIndex;
          IF allocationDifficulty = impossible THEN  --
	    -- (can alloc temp storage only for inLoad[inloadMode: load])
	    allocationDifficulty ← hard;
          [result, bootChannel] ← importedBootChannel.Create[
	    @Boot.pRequest.location, read, LONG[pBuffer]];
          IF result # [ok[]] THEN GO TO HandleProblem;
          [mds, Boot.pRequest.pStartListHeader, result] ←
	    DoInLoad[bootChannel];
          IF result # [ok[]] THEN GO TO HandleProblem;
	  IF flushFloppy THEN
	    {flushFloppy ← FALSE;  -- only do this once
	     IF LOOPHOLE[Boot.pRequest.location.deviceType, CARDINAL]
	       ~IN DeviceTypesExtras4.FloppyTape THEN
                 -- Reclaim floppy section of Marker-ed memory
		 -- unless booting from floppy tape.
                 FlushMemory[beforePage, middlePage]};
          Boot.pRequest.requestExtensionVersion ←
	    Boot.currentRequestExtensionVersion;
          IF Boot.pRequest.switches[
	    PilotSwitches.germExtendedErrorReports] = down OR
	    (Boot.pRequest.pStartListHeader # NIL AND
	    LOOPHOLE[Boot.pRequest.pStartListHeader.switches, System.Switches][
	      PilotSwitches.germExtendedErrorReports] = down) THEN debug ← TRUE;
          Boot.pRequest.session ← newSession;
	  GermOps.InitializeLinkage[mds];  -- sets linkage for target mds
          ProcessorFace.SetMP[PilotMP.cGermFinished];
          --[pRequest↑]←-- GermOps.CallPilotInMds[mds];
	    -- (uses entry point in given mds.)
          -- Now we're back with another Request.
	  allocationDifficulty ← impossible;
	    -- all free real mem is owned by Pilot.
          END;
        Boot.noOp => {
          ProcessorFace.SetMP[PilotMP.cGermFinished];
          --[pRequest↑] ← -- GermOps.BackToPilot[];
	    -- (continues from where Pilot left off)
          -- Now we're back with another Request.
          allocationDifficulty ← impossible};
	    -- all free real mem is owned by Pilot.
        Boot.outLoad =>
          BEGIN
          mds: BootFile.MDSIndex = GermOps.InvokersMds[];
	  IF Boot.pRequest.requestExtensionVersion #
            Boot.currentRequestExtensionVersion THEN
            GermWorldError[PilotMP.cGermWrongPilot];
          [result, bootChannel] ← importedBootChannel.Create[
            @Boot.pRequest.location, write, LONG[pBuffer]];
	  IF result # [ok[]] THEN GOTO HandleProblem;
	  result ← DoOutLoad[bootChannel, mds, Boot.pRequest.inLoadMode];
	  IF result # [ok[]] THEN GOTO HandleProblem;
          Boot.pRequest.session ← continuingAfterOutLoad;
	  -- (pRequest.requestExtensionVersion is already set right.)
          -- (The linkage to the client was already set up by his call to us.)
          ProcessorFace.SetMP[PilotMP.cGermFinished];
          --[pRequest↑] ← -- GermOps.BackToPilot[];
	    -- (continues from where Pilot left off)
          -- Now we're back with another Request.
          allocationDifficulty ← impossible;
	    -- all free real mem is owned by Pilot.
          END;
        Boot.teledebug =>
          BEGIN
          IF ~IsBound[LOOPHOLE[GermOps.GetTeledebugged]] THEN
	    GermWorldError[PilotMP.cCantTeledebug];
          GermOps.GetTeledebugged[
	    pLocation: @Boot.pRequest.location, scratchPage: pageBuffer];
          -- (The linkage to the client was already set up by his call to us.)
          ProcessorFace.SetMP[PilotMP.cGermFinished];
          --[pRequest↑] ← -- GermOps.BackToPilot[];
	    -- (continues from where Pilot left off)
          -- Now we're back with another Request.
          allocationDifficulty ← impossible;
	    -- all free real mem is owned by Pilot.
          END;
        ENDCASE => Error[];
      EXITS
        HandleProblem  --[result]-- =>
	  WITH r: result SELECT FROM
	    error => GermWorldError[r.code];
	    tryOtherLocation =>
	      -- We overwrite the Location we were working on with the 
	      -- new suggested Location, fall through, and try again.
	      Boot.pRequest.location ← r.pOtherLocation↑;
	    --ok,-- ENDCASE => Error[];
      END;  --scope of HandleProblem--
      ProcessorFace.SetMP[PilotMP.cGermAction];
      FreeResidentHeap[];  -- recover any heap storage used by BootChannel.
      IF Boot.pRequest.requestBasicVersion # Boot.currentRequestBasicVersion THEN
        GermWorldError[PilotMP.cGermWrongPilot];
      ENDLOOP; --FOREVER--
    END;  --ProcessRequests--


  DoTransfer: PROC [
    handle: BootChannel.Handle, page: PageNumber, count: PageCount]
    RETURNS [result: BootChannel.Result] =
    BEGIN
    prevMP: PilotMP.Code = ProcessorFace.mp;
    ProcessorFace.SetMP[PilotMP.cGermDriver];
    result ← importedBootChannel.Transfer[handle, page, count];
    ProcessorFace.SetMP[prevMP];
    END; --DoTransfer--


  --~~~~~~~~~~~~~~~~~~~~ InLoad and OutLoad ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  DoInLoad: PROC [channel: BootChannel.Handle]
    RETURNS [
      mds: BootFile.MDSIndex, pStartListHeader: StartList.Base,
      result: BootChannel.Result] =
    BEGIN
    -- uses global highestMappedPage
    inLoadMode: BootFile.InLoadMode;
    remainingMapEntries: CARDINAL;
    curMapEntry: PMapEntry;  -- in current header/trailer page.
    endMapEntry: PMapEntry;  -- 	"
    startMapEntry: PMapEntry;  -- 	"
    runMapEntry: PMapEntry;
    countRun: CARDINAL;  -- current run of pages.
    page, pageIntervalEnd: PageNumber;  -- interval of Pilot VM to be restored.
    realPage: PageMap.RealPageNumber;
    state: PageMap.State;

    FinishRun: PROCEDURE [] --RETURNS [result: BootChannel.Result]-- =
      -- (Returns result directly into paren't frame.)
      BEGIN
      IF countRun > 0 THEN
        BEGIN
        result ←
	  DoTransfer[channel, runMapEntry.virtual, page - runMapEntry.virtual];
	IF result # [ok[]] THEN RETURN;
        countRun ← 0;
        END;
      result ← [ok[]];
      END;  --FinishRun--

    -- Read first page of boot file, containing header:
    result ← DoTransfer[channel, pageBuffer, 1];
    IF result # [ok[]] THEN RETURN[TRASH, TRASH, result];
    result ← DoTransfer[channel, 0, BootChannel.transferWait];
    IF result # [ok[]] THEN RETURN[TRASH, TRASH, result];
    BEGIN OPEN header: LOOPHOLE[pBuffer, POINTER TO BootFile.Header];
    IF header.version ~= BootFile.currentVersion THEN
      GermWorldError[PilotMP.cGermBadBootFileVersion];
    pStartListHeader ← header.pStartListHeader;
    inLoadMode ← header.inLoadMode;
    mds ← header.mds;
    remainingMapEntries ← CARDINAL[header.countData];
    startMapEntry ← curMapEntry ← OrderedPMapEntry[@header.entries[0]];
    endMapEntry ←
      startMapEntry +
        sizeMapEntry*MIN[BootFile.maxEntriesPerHeader, remainingMapEntries];
    END;
    
    -- The following code is performing two variations of the same function:
    --     If inLoadMode=load, all Pilot-available real memory (excludes that
    --       behind Germ and I/O pages) is mapped behind consecutive Pilot
    --       VM pages starting at 0, and as we pass pages which the boot file
    --       specifies to be unmapped, we shuffle the real memory pages found
    --       there down to the end of mapped Pilot VM.
    --     If inLoadMode=restore, all Pilot-available real memory is mapped
    --       behind arbitrary pages, and as we pass pages which the boot file
    --       specifies to be unmapped, we merely ignore the real memory pages
    --       found there.. the boot file will cause them to be put in the
    --       right place.
    SELECT inLoadMode FROM
      load =>
        CompactVM[onlyKeepVanillaRealMemory:TRUE];
      restore =>  -- XXXXX pages not in boot file are set vacant:
        BEGIN
        IF AnyTempStorageAllocated[] THEN  -- can't alloc any real mem..
          Error[];  -- cause Pilot owns it all.
	-- If the processor has an associative page map, we must avoid duplicate
	-- use of real pages. We make an initial pass and unmap all of Pilot VM.
	-- This also serves to set vacant all pages not mentioned in boot file.
	[page, pageIntervalEnd] ← GetNextPilotVM[pageZero];
        WHILE page < pageIntervalEnd DO   --process nonempty interval
          WHILE page < pageIntervalEnd DO
            PageMap.SetMapFlags[virtual: page, real: NULL, flags: flagsVacant];
            page ← page+1;
            ENDLOOP;
          [page, pageIntervalEnd] ← GetNextPilotVM[page];
          ENDLOOP;
	END;
      ENDCASE => Error[];
      
    IF IsBound[LOOPHOLE[GermOps.ProcessMachineDependentSwitches]]
    THEN highestMappedPage ← GermOps.ProcessMachineDependentSwitches[
		   LOOPHOLE[LONG[pBuffer]], highestMappedPage];
    
    
    allocationDifficulty ← impossible;  -- memory must be static during inLoad.

    -- Starting at page 0 and scanning forward, restore virtual memory and
    -- hardware map from boot file:
    -- Within the following loop, we always have the following context: an
    -- interval of Pilot VM that we are processing/restoring, a header/trailer
    -- page of MapEntries, the total number of remaining MapEntries to be
    -- processed, and a run of mapped pages from the boot file.  Initially, we
    -- have the MapEntries of the boot file header page.
    [page, pageIntervalEnd] ← GetNextPilotVM[pageZero]; -- 1st interval to restore
    --ASSERT page = pageZero AND page <= curMapEntry.virtual;
    countRun ← 0;  -- no pages in current run yet.
    DO  --UNTIL last mapEntry in last header/trailer page in boot file processed
      -- What do we do with this page of VM?
      -- (If inLoadMode=load, it has a real page behind it, and if
      -- inLoadMode=restore, it might.)
      IF page < curMapEntry.virtual THEN
        BEGIN --page not mentioned in boot file
	-- (Such pages are to be made vacant)
        IF countRun > 0 THEN  -- (test for performance only)
	  BEGIN
	  --result ←-- FinishRun[];  -- (sets countRun ← 0)
	  IF result # [ok[]] THEN RETURN;
	  END;
        [state, realPage] ←
	  PageMap.ExchangeFlags[virtual: page, newFlags: flagsVacant];
        IF inLoadMode = load THEN
	  BEGIN
          IF state.flags = flagsVacant THEN  -- should be real page there.
            GermWorldError[PilotMP.cGermInsufficientRealMemory];
          PageMap.SetMapFlags[  -- shuffle real page to end of mapped VM.
            virtual: IF (highestMappedPage ← highestMappedPage+1) = pageGFT
	      THEN (highestMappedPage ← highestMappedPage+1)
	      ELSE highestMappedPage,
	    real: realPage, flags: flagsClean];
	  END
        ELSE --inLoadMode = restore-- NULL;  -- Forget any real page there now.
        page ← page+1;
        END  --page not mentioned in boot file--
      ELSE
        BEGIN  --page in boot file--
        --ASSERT page = curMapEntry.virtual;
        -- Set up map and accumulate run-of-pages info to restore data..
        IF countRun > 0 AND page = (curMapEntry - sizeMapEntry)↑.virtual+1
          THEN countRun ← countRun+1  -- continuation of run
        ELSE
	  BEGIN
	  --result ←-- FinishRun[];  -- (sets countRun ← 0)
	  IF result # [ok[]] THEN RETURN;
          runMapEntry ← curMapEntry;  -- remember start of new run.
          countRun ← 1;
	  END;
        IF inLoadMode = restore THEN  -- Use the real page boot file says.
          PageMap.SetMapFlags[  -- (must make page writable to start)
            virtual: page, real: curMapEntry.real, flags: flagsClean]
        ELSE --inLoadMode = load--
	  BEGIN
	  -- use the real page that's laying there.
	  IF page > highestMappedPage THEN
	    GermWorldError[PilotMP.cGermInsufficientRealMemory];
	  END;
        page ← page+1;
        remainingMapEntries ← remainingMapEntries-1;
        curMapEntry ← curMapEntry + sizeMapEntry;
        IF curMapEntry >= endMapEntry THEN
          BEGIN  -- clean up, get next Trailer
	  
	  -- first cleanup any pending I/O
	  --result ←-- FinishRun[];  -- (sets countRun ← 0)
	  IF result # [ok[]] THEN RETURN;
	  result ← DoTransfer[channel, 0, BootChannel.transferWait].result;
	  IF result # [ok[]] THEN RETURN;
	  
	  -- Now we set map flags for all pages defined by this Trailer
	  BEGIN OPEN trailer: LOOPHOLE[pBuffer, POINTER TO BootFile.Trailer];
	  FOR mapEntry: PMapEntry ← startMapEntry, mapEntry + sizeMapEntry
	    UNTIL mapEntry >= endMapEntry DO
	    [] ← PageMap.ExchangeFlags[
	      virtual: mapEntry.virtual, newFlags: mapEntry.flags];
	    ENDLOOP;
	  END;
	  
	  -- Now read the next Trailer, if any
          IF remainingMapEntries = 0 THEN EXIT  -- boot file processing complete.
          ELSE  -- read next Trailer page to get more MapEntries
            BEGIN OPEN trailer: LOOPHOLE[pBuffer, POINTER TO BootFile.Trailer];
	    result ← DoTransfer[channel, pageBuffer, 1];
	    IF result # [ok[]] THEN RETURN;
	    result ← DoTransfer[channel, 0, BootChannel.transferWait].result;
	    IF result # [ok[]] THEN RETURN;
            IF trailer.version ~= BootFile.currentVersion THEN
              GermWorldError[PilotMP.cGermBadBootFileVersion];
            startMapEntry ← curMapEntry ← OrderedPMapEntry[@trailer.entries[0]];
            endMapEntry ←
              startMapEntry +
                sizeMapEntry*MIN[
                  BootFile.maxEntriesPerTrailer, remainingMapEntries];
            END;  --OPEN trailer--
          END;  --clean up, get next Trailer--
        END;  --page in boot file--
      IF page >= pageIntervalEnd THEN {
	--result ←-- FinishRun[];  -- (sets countRun ← 0)
	IF result # [ok[]] THEN RETURN;
        [page, pageIntervalEnd] ← GetNextPilotVM[page];
        IF page = pageIntervalEnd THEN Error[];  -- ran out of VM!
        IF curMapEntry.virtual < page THEN
	  -- boot file has page on I/O or germ page.
          GermWorldError[PilotMP.cGermBadBootFile];
        };
      ENDLOOP;
    -- All boot file pages are now loaded/restored and the channel has
    -- no outstanding requests on it.  Final call to shut down channel.
    [] ← DoTransfer[channel, 0, BootChannel.transferCleanup];
    IF inLoadMode = load THEN FreeTempResidentMemory[highestMappedPage];
    END;  --DoInLoad--


  DoOutLoad: PROC [
    channel: BootChannel.Handle, mds: BootFile.MDSIndex,
    inLoadMode: BootFile.InLoadMode]
    RETURNS [result: BootChannel.Result] =
    BEGIN
    remainingMapEntries: CARDINAL;
    page, pageIntervalEnd: PageNumber;  -- interval of Pilot VM to be saved.
    firstHTMapEntry: PMapEntry;  -- in current header/trailer page.
    curMapEntry: PMapEntry;  -- 	"
    endMapEntry: PMapEntry;  --		"
    runMapEntry: PMapEntry;  -- current run of pages.
    realPage: PageMap.RealPageNumber;
    state: PageMap.State;

    -- Find how many pages we have to save:
    remainingMapEntries ← 0;
    [page, pageIntervalEnd] ← GetNextPilotVM[pageZero];
    --UNTIL end of Pilot VM reached--
    DO
      IF PageMap.IsMapped[page] THEN
        remainingMapEntries ← remainingMapEntries+1;
      page ← page+1;
      IF page >= pageIntervalEnd THEN {
        [page, pageIntervalEnd] ← GetNextPilotVM[page];
        IF page = pageIntervalEnd THEN EXIT};
      ENDLOOP;

    -- Construct boot file Header page:
    BEGIN OPEN header: LOOPHOLE[pBuffer, POINTER TO BootFile.Header];
    header.version ← BootFile.currentVersion;
    -- header.creationDate ← XXX;  ++ fill this when we have a Pilot T.O.D clock?
    header.pStartListHeader ← NIL;
    header.mds ← mds;
    header.inLoadMode ← inLoadMode;
    header.countData ← remainingMapEntries;
    firstHTMapEntry ← OrderedPMapEntry[@header.entries[0]];
    endMapEntry ←
      firstHTMapEntry +
        sizeMapEntry*MIN[BootFile.maxEntriesPerHeader, remainingMapEntries];
    END;

    -- Starting at page 0 and scanning forward, save virtual memory and hardware
    -- map into boot file:

    -- Within the following loop, we always have the following context:
    --    an interval of Pilot VM that we are saving,
    --    a header/trailer page in which to generate MapEntries,
    --    the total number of remaining MapEntries to be processed,
    --    a run of mapped pages from the boot file.
    -- Initially, we are generating the MapEntries of the boot file header page.
    allocationDifficulty ← impossible;  -- memory must be static during outLoad.
    [page, pageIntervalEnd] ← GetNextPilotVM[pageZero];  -- 1st interval to save.

    --UNTIL last page in VM saved in boot file--
    DO
      -- First, scan enough VM to fill in MapEntries in Header/Trailer, then
      --   write H/T out:
      curMapEntry ← firstHTMapEntry;
      -- We first wait for pending I/O to complete to ensure
      -- that the contents of pageBuffer may be overwritten.
      result ← DoTransfer[channel, 0, BootChannel.transferWait];
      IF result # [ok[]] THEN RETURN;
      DO --UNTIL desired number of mapped pages found
        [state, realPage] ← PageMap.GetState[page];
        IF state.flags ~= flagsVacant THEN
	  BEGIN
          curMapEntry↑ ← [virtual: page, real: realPage, flags: state.flags];
          curMapEntry ← curMapEntry + sizeMapEntry;
          IF curMapEntry >= endMapEntry THEN {page ← page+1; EXIT};
          END;
        page ← page+1;
        IF page >= pageIntervalEnd THEN
	  BEGIN
          [page, pageIntervalEnd] ← GetNextPilotVM[page];
          IF page = pageIntervalEnd THEN Error[];  -- ran out of VM!
	  END;
        ENDLOOP;
      -- Write out the H/T page.
      result ← DoTransfer[channel, pageBuffer, 1];
      IF result # [ok[]] THEN RETURN;

      -- Use the accumulated H/T page MapEntries to write out runs of data pages:
      curMapEntry ← firstHTMapEntry;
      --UNTIL all mapEntries in H/T page processed--
      DO
        runMapEntry ← curMapEntry;  -- current entry begins a new run.
        --UNTIL end of run found--
        DO
          curMapEntry ← curMapEntry + sizeMapEntry;
          IF curMapEntry >= endMapEntry
            OR curMapEntry.virtual ~= (curMapEntry - sizeMapEntry)↑.virtual+1
            THEN EXIT;  -- run ends.
          ENDLOOP;
        result ← DoTransfer[  -- write out a run of data pages
          channel, runMapEntry.virtual,
          (curMapEntry - sizeMapEntry)↑.virtual + 1 - runMapEntry.virtual];
	    -- (last+1-first)
	IF result # [ok[]] THEN RETURN;
        IF curMapEntry >= endMapEntry THEN EXIT;  -- all map entries processed
        ENDLOOP;
      remainingMapEntries ←
        remainingMapEntries - (endMapEntry - firstHTMapEntry)/sizeMapEntry;
      IF remainingMapEntries = 0 THEN EXIT;  -- all pages written to boot file.

      -- Construct next boot file Trailer page:
      BEGIN OPEN trailer: LOOPHOLE[pBuffer, POINTER TO BootFile.Trailer];
      trailer.version ← BootFile.currentVersion;
      firstHTMapEntry ← OrderedPMapEntry[@trailer.entries[0]];
      endMapEntry ←
        firstHTMapEntry +
          sizeMapEntry*MIN[BootFile.maxEntriesPerTrailer, remainingMapEntries];
      END;

      ENDLOOP;  --loop for all {Trailer page, runs of data pages} groups.
    
    -- Wait for any pending I/O to complete before shutting down the channel
    result ← DoTransfer[channel, 0, BootChannel.transferWait];
    IF result # [ok[]] THEN RETURN;
    [] ← DoTransfer[channel, 0, BootChannel.transferCleanup];
    END;  --DoOutLoad--

   
  CompactVM: PROC [onlyKeepVanillaRealMemory:BOOLEAN ← FALSE] =
    -- Finds all real pages currently mapped to Pilot virtual pages, and puts
    -- them (writable) behind contiguous Pilot virtual addresses starting at 0.
    -- Sets global highestMappedPage as the resulting highest page in VM which
    -- is mapped.
    BEGIN
    pageSource, pageSourceIntervalEnd, pageDest, pageDestIntervalEnd: PageNumber;
    reservedMin, reservedMax: PageNumber;
    IF onlyKeepVanillaRealMemory 
    THEN [reservedMin: reservedMin, reservedMax: reservedMax] ← 
      GermOps.BoundsReservedMemory[];
    [pageDest, pageDestIntervalEnd] ← GetNextPilotVM[pageZero];
      -- next interval to put mem into.
    pageSource ← pageZero;
    --UNTIL end of VM reached--
    DO
      [pageSource, pageSourceIntervalEnd] ← GetNextPilotVM[pageSource];
        -- next source interval to scan.
      IF pageSource = pageSourceIntervalEnd THEN EXIT;  -- end of VM.
      WHILE pageSource < pageSourceIntervalEnd DO
        realPage: PageMap.RealPageNumber;
        state: PageMap.State;
        [state, realPage] ← PageMap.ExchangeFlags[
          virtual: pageSource, newFlags: flagsVacant];
        IF (state.flags=flagsVacant)
        OR (onlyKeepVanillaRealMemory AND realPage IN [reservedMin..reservedMax])
	THEN {-- either there's no real page, or its to be left out of VM--}
	ELSE {
          PageMap.SetMapFlags[
            virtual: pageDest, real: realPage, flags: flagsClean];
          highestMappedPage ← pageDest;  -- set the global variable.
          pageDest ← pageDest+1;
          IF pageDest >= pageDestIntervalEnd THEN  -- get next dest interval.
            [pageDest, pageDestIntervalEnd] ← GetNextPilotVM[pageDest];
          };
        pageSource ← pageSource+1;
        ENDLOOP;
      ENDLOOP;
    END;  --CompactVM--
  
  Error: PROCEDURE = {GermWorldError[PilotMP.cGermERROR]};

  GetNextPilotVM: PUBLIC --GermOps.-- PROC [page: PageNumber]
    RETURNS [firstPage, endPage: PageNumber] =
    << Returns next area of virtual memory, beginning at or after given page,
    which is available for Pilot on this processor.  Returns endPage=firstPage
    if no such available area exists.  The available areas exclude pages
    used by the Germ, device face implementations, and unimplemented virtual pages
    but include pages allocated in the Principles of Operation
    (e.g. process data area, AV, SD, GFT).
      Similar to ProcessorFace.GetNextAvailableVM except that the Germ VM
    is also excluded.
      endPage is the page following the interval of Pilot VM.>>
    BEGIN

    PageBeforeOrAtInterval: PROC [pageInterval, pageEndInterval: PageNumber]
      RETURNS [BOOLEAN] =
      BEGIN
      -- If GetNextPilotVM.page is <= pageInterval,
      -- then sets GetNextPilotVM.firstPage, .endPage and returns TRUE. 
      IF pageEndInterval = pageInterval  -- (Germ caused null interval)
        OR page > pageInterval THEN RETURN[FALSE]
      ELSE --page <= pageInterval and non-null interval-- {
        firstPage ← pageInterval; endPage ← pageEndInterval; RETURN[TRUE]};
      END;

    pageStart: PageNumber;
    count: PageCount;
    pageNext: PageNumber ← pageZero;  -- end of current interval / start of next.
    --REPEAT .. UNTIL interval at or after page--
    DO
      [pageStart, count] ← ProcessorFace.GetNextAvailableVM[pageNext];
      IF count = 0 THEN RETURN[0, 0];  -- no further available VM.
      pageNext ← pageStart + count;  -- end of current interval
      SELECT TRUE FROM 
        pageGerm IN [pageStart..pageNext) => {
	  IF pageEndGermVM > pageNext THEN Error[];  -- Germ slops onto I/O page.
	  IF PageBeforeOrAtInterval[pageStart, pageGerm] THEN RETURN;
	  IF PageBeforeOrAtInterval[pageEndGermVM, pageNext] THEN RETURN};
	pageGFT IN [pageStart..pageNext) => {
	  IF PageBeforeOrAtInterval[pageStart, pageGFT] THEN RETURN;
	  IF PageBeforeOrAtInterval[pageGFT+1, pageNext] THEN RETURN};
        ENDCASE => IF PageBeforeOrAtInterval[pageStart, pageNext] THEN RETURN;
      ENDLOOP;
    END;  --GetNextPilotVM--


  --~~~~~~~~~~~~~~~~~~~~ Simple Mesa Runtime ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  
  << We can't set up handlers to catch Frame, Page, and Write Faults because the
  PDA belongs to the client being outloaded, and we can't modify it.
  However, at germ initialization, we zero the PDA fault vectors,
  and thereafter Pilot is supposed to manually save their contents
  and zero them before calling the germ. Thus any fault in the germ will result
  in a reschedule error, which we CAN catch and handle. >>

  CodeTrap: PROC =  -- entered via SD[sCodeTrap]
    -- This trap is used to implement start traps.
    -- Neither single nor multiple control modules are implemented.
    -- The code here is derived from the code of Traps.CodeTrap[].
    BEGIN
    d: RECORD [  -- keeps state away from trap params.
      trapee: PrincOps.LocalFrameHandle,
      gfi: PrincOpsExtras2.GFTHandle,
      dest: PrincOpsExtras2.ControlLink,  -- procedure being called.
      opLength: INTEGER,
      state: dst PrincOps.StateVector];  -- holds args of called procedure.
    cb: PrincOps.GlobalCodebase;
    d.state ← STATE;  -- save args for called proc. Must be first.
    d.gfi ← Trap.Parameter[];  -- Must be second.
    d.trapee ← Frame.GetReturnFrame[];
    cb ← FrameExtras.ReadCodebase[d.gfi];
    cb.out ← FALSE;
    FrameExtras.WriteCodebase[gfi: d.gfi, cb: cb];
    ControlModuleFormat.Call[ControlModuleFormat.MainBody[d.gfi]];
    STATE ← d.state;  -- Must be last.
    END;

  ControlTrap: PROC =  -- (entered via sControlTrap)
    BEGIN
    stuff: RECORD [  -- a record to keep state out of local zero
      fillerA, fillerB, fillerC: WORD, state: PrincOps.StateVector];
    stuff.state ← STATE;  -- Must be first. resets stack pointer
    GermWorldError[PilotMP.cGermControlTrap];
    END;
  
  Start: PUBLIC --GermOps.-- PROCEDURE [program: PROGRAM] =
    BEGIN
    -- This trap is used to implement start programs.
    -- Neither single nor multiple control modules are implemented.
    -- The code here is derived from the code of Traps.CodeTrap[].
    -- This is called from the Germ*Start.mesa module specific to germ flavors.
    d: RECORD [  -- keeps state away from trap params.
      trapee: PrincOps.LocalFrameHandle,
      gfi: PrincOpsExtras2.GFTHandle,
      dest: PrincOpsExtras2.ControlLink,  -- procedure being called.
      opLength: INTEGER,
      state: dst PrincOps.StateVector];  -- holds args of called procedure.
    cb: PrincOps.GlobalCodebase;
    
    d.state ← STATE;  -- save args for called proc. Must be first.
    d.gfi ← FrameExtras.LongGFToGFTHandle[
      SpecialRuntimeExtras.GlobalFrameFromProgram[program]];  -- Must be second.
    d.trapee ← Frame.GetReturnFrame[];
    cb ← FrameExtras.ReadCodebase[d.gfi];
    cb.out ← FALSE;
    FrameExtras.WriteCodebase[gfi: d.gfi, cb: cb];
    ControlModuleFormat.Call[ControlModuleFormat.MainBody[d.gfi]];
    STATE ← d.state;  -- Must be last.
    END; --Start--

  IsBound: PUBLIC --Runtime.-- PROC [link: Runtime.ControlLink]
    RETURNS [BOOLEAN] =
    BEGIN
    RETURN[
      LOOPHOLE[link, PrincOpsExtras2.ControlLink] ~= PrincOpsExtras2.UnboundLink
        AND
      LOOPHOLE[link, PrincOpsExtras2.ControlLink] ~= PrincOpsExtras2.nullLink];
    END;

  PointerFromPage: PUBLIC --GermOps.-- PROC [page: Environment.PageNumber]
    RETURNS [p: POINTER] = {
    lp: LONG POINTER ← Environment.LongPointerFromPage[page];
    IF Inline.HighHalf[lp] ~= ProcessOperations.ReadMDS[] THEN Error[];
    RETURN[
      Inline.LowHalf[
        lp - ProcessOperations.ReadMDS[]*Environment.maxPagesInMDS]]};

  RescheduleErrorTrap: PROC =  -- (entered via sRescheduleError)
    BEGIN
    stuff: RECORD [  -- a record to keep state out of local zero
      fillerA, fillerB, fillerC: WORD, state: PrincOps.StateVector];
    stuff.state ← STATE;  -- Must be first. resets stack pointer
    GermWorldError[PilotMP.cGermRescheduleTrap];
    END;

  SignalHandler: PROC [signal: SIGNAL, code: PilotMP.Code] = {
    -- (entered via sSignal or sError KFCB)
    GermWorldError[PilotMP.cGermERROR]};

  GermWorldError: PUBLIC --GermOps.-- PROC [
    mpCode: --PilotMP.Code-- UNSPECIFIED] =
    -- See comments in GermOps for description of operation.
    BEGIN
    DO  --FOREVER--
      localFrame: PrincOps.LocalFrameHandle ← Frame.GetReturnFrame[];
      ShowCodeInMP[mpCode];
      IF debug THEN
        BEGIN
        ShowCodeInMP[999];
	THROUGH [1..5] DO
	  gfi: PrincOpsExtras2.GFTHandle =
	    FrameExtras.ReadGlobalLink[localFrame];
	  pc: PrincOps.BytePC = Frame.ReadPC[localFrame];
	  ShowCardinalInMP[gfi]; 
	  -- ShowCardinalInMP[localFrame]; ++ not very useful.
	  ShowCardinalInMP[pc]; 
	  localFrame ← Frame.ReadReturnLink[localFrame].frame;
	  IF localFrame = PrincOps.nullLocalFrame THEN EXIT;
	  ENDLOOP;
	END;
      ENDLOOP;  --FOREVER--
    END;  --GermWorldError--

  mpModulus: NAT = 1000;  -- mp only guaranteed to be three digits.

  ShowCodeInMP: PUBLIC --GermOps.--  PROC [mpCode: PilotMP.Code] = {
    ProcessorFace.SpecialSetMP[mpCode];
    FOR delay: LONG CARDINAL IN [0..400000) DO ENDLOOP};

  ShowCardinalInMP: PUBLIC --GermOps.--  PROC [cardinal: UNSPECIFIED] = {
    ShowCodeInMP[cardinal/mpModulus]; ShowCodeInMP[cardinal MOD mpModulus]};

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  -- ResidentHeap implementation, for allocating storage in the germ's world.

  -- See Storage Allocation notes at head of module.

  EnvBaseRelOrdPtr: PROC [rp: Environment.Base RELATIVE POINTER]
    RETURNS [Environment.Base RELATIVE ORDERED POINTER] = INLINE {
    RETURN[LOOPHOLE[rp]]};

  MakeNode: PUBLIC --ResidentHeap.-- PROCEDURE [
    n: Zone.BlockSize, alignment: Zone.Alignment ← a1,
    location: ResidentHeap.HeapLocation ← first64K]
    RETURNS [node: Environment.Base RELATIVE POINTER, s: Zone.Status] =
    BEGIN
    align: CARDINAL;
    IF n = 0 THEN RETURN [Zone.nil, okay];
    align ← SELECT alignment FROM
      a1 => 1, a2 => 2, a4 => 4, a8 => 8, ENDCASE => 16;
    node ← LOOPHOLE[((LOOPHOLE[pHeapAllocNext, CARDINAL] + align-1)/align)*align];
    --REPEAT ... UNTIL node does not cross page boundary--
    DO
      IF (EnvBaseRelOrdPtr[node] + n) >= pHeapAllocEnd THEN Error[];
      IF Environment.PageFromLongPointer[@Environment.first64K[node + n - 1]] =
        Environment.PageFromLongPointer[@Environment.first64K[node]] THEN EXIT;
      -- ELSE node crosses page boundary.  Move up to page boundary and retry:
      node ←
        LOOPHOLE[((LOOPHOLE[node, CARDINAL] + wordsPerPage - 1)
          /wordsPerPage)*wordsPerPage];
      ENDLOOP;
    pHeapAllocNext ← EnvBaseRelOrdPtr[node] + n;
    s ← okay;
    END;

  FreeNode: PUBLIC --ResidentHeap.-- PROCEDURE [
    p: Environment.Base RELATIVE POINTER,
    location: ResidentHeap.HeapLocation ← first64K]
    -- For simplicity, FreeNode does nothing immediately; all of the temporary
    -- storage allocated is freed en masse after the BootChannel is closed.
    RETURNS [s: Zone.Status] = {RETURN[okay]};

  FreeResidentHeap: PROC[] = INLINE {
    -- Recover any ResidentHeap allocated during BootChannel Creation.
    pHeapAllocNext ← pHeap};

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  -- ResidentMemory implementation, for allocating storage in the germ's world.

  -- See Storage Allocation notes at head of module.
  -- Allocate* and Free* may not be called during inLoad and outLoad, because
  -- the configuration of real memory must be static while the operations are
  -- in progress.
  -- For simplicity, the Free* calls do nothing immediately; all of the temporary
  -- storage allocated is freed en masse after the BootChannel is closed.

  residentMemoryLock: PUBLIC --ResidentMemory.-- MONITORLOCK;

  allocationDifficulty: {
    easy,  -- highestMappedPage is valid and that's where to get real mem from.
    hard,  -- highestMappedPage is not valid, but could be made so.
    impossible};  -- storage allocation not allowed at the moment.

  pageAllocFirst: PageNumber;  -- end permanent storage / begin temp storage.
  pageAllocNext: PageNumber;  -- next page to be allocated.

  highestMappedPage: PageNumber;
  -- value only valid if allocationDifficulty=easy.

  allocateMDSInternal: PUBLIC --ResidentMemory.-- --INTERNAL--
    ResidentMemory.AllocateMDSInternal ← [AllocateMDSLocal];

  AllocateMDSLocal: PROC [count: PageCount]
    RETURNS [p: POINTER TO UNSPECIFIED] =
    BEGIN
    realPage: PageMap.RealPageNumber;
    IF allocationDifficulty = impossible THEN Error[]; -- can't alloc storage now
    IF allocationDifficulty = hard THEN {
      CompactVM[onlyKeepVanillaRealMemory: TRUE]; allocationDifficulty ← easy};
    p ← PointerFromPage[pageAllocNext];
    THROUGH [0..count) DO
      IF pageAllocNext >= pageEndGermVM THEN Error[];  -- out of germ vm.
      -- Snatch real page from last mapped page:
      realPage ← PageMap.ExchangeFlags[
        virtual: highestMappedPage, newFlags: flagsVacant].real;
      highestMappedPage ← highestMappedPage-1;
      PageMap.SetMapFlags[
        virtual: pageAllocNext, real: realPage,
        flags: flagsClean];
      pageAllocNext ← pageAllocNext+1;
      ENDLOOP;
    END;

  allocateInternal: PUBLIC --ResidentMemory.-- --INTERNAL--
    ResidentMemory.AllocateInternal ← [AllocateLocal];

  AllocateLocal: PROC [
    location: ResidentMemory.Location, count: PageCount]
    RETURNS [lp: LONG POINTER TO UNSPECIFIED] =
    -- Note that mds = first64K = hyperspace for the Germ.
    -- (Should actually check here to verify that location # pda.
    {RETURN[LONG[AllocateMDSLocal[count]]]};

  freeInternal: PUBLIC --ResidentMemory.-- --INTERNAL--
    ResidentMemory.FreeInternal ← [FreeLocal];

  FreeLocal: PROC [
    location: ResidentMemory.Location, count: PageCount,
    lp: LONG POINTER TO UNSPECIFIED] = {};  -- (freed when channel closed)

  FreeTempResidentMemory: PROC [highestMappedPage: PageNumber] = {
    -- Recover any ResidentMemory allocated during BootChannel Creation.
    realPage: PageMap.RealPageNumber;
    FOR page: PageNumber IN [pageAllocFirst..pageAllocNext) DO
      realPage ← PageMap.ExchangeFlags[
        virtual: page, newFlags: flagsVacant].real;
      PageMap.SetMapFlags[
        virtual: (highestMappedPage ← highestMappedPage+1),
        real: realPage, flags: flagsClean];
      ENDLOOP;
    pageAllocNext ← pageAllocFirst};

  AnyTempStorageAllocated: PROC RETURNS [anyAllocate: BOOLEAN] = INLINE {
    RETURN[pageAllocNext ~= pageAllocFirst]};


  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  -- System implementation.

  -- usec/sec * (hundredPulses/usec) * (100 pulses/hundredPuliss)
  MicrosecondsToPulses: PUBLIC --System.-- PROC [usec: System.Microseconds]
    RETURNS [System.Pulses] =
    BEGIN
    RETURN[
      [
        Times10[
        Times10[LongDivide[
	  num: usec, den: ProcessorFace.microsecondsPerHundredPulses]]]]];
    END;

  Times10: PROC [in: LONG CARDINAL] RETURNS [out: LONG CARDINAL] = {
    in ← in + in;  -- in  = 2x
    out ← in + in;  -- out = 2*2x = 4x
    out ← out + out + in};  -- out = 2*2*2x + 2x = 10x

  LongDivide: PROC [num: LONG CARDINAL, den: CARDINAL]
    RETURNS [quo: LONG CARDINAL ← 0] =
    BEGIN
    OPEN n: LOOPHOLE[num, MACHINE DEPENDENT RECORD [lo, hi: CARDINAL]],
      q: LOOPHOLE[quo, MACHINE DEPENDENT RECORD [lo, hi: CARDINAL]];
    quo ← 0;
    num ← num + (den - 1);
    q.hi ← n.hi/den;
    n.hi ← n.hi - q.hi*den;
    quo ← quo + LONG[Inline.LongDiv[num, den]];
    END;


  FlushMemory: PROCEDURE [startPage, endPage: PageNumber] =
    -- this causes real memory behind [startPage..endPage) to be made Vacant.
    BEGIN
    state:  PageMap.State; realPage: PageMap.RealPageNumber;
    FOR page: PageNumber IN [startPage..endPage) DO
      [oldState: state, real: realPage] ← PageMap.ExchangeFlags[
        virtual: page, newFlags: flagsVacant];
      IF state.flags ~= flagsVacant THEN
	PageMap.SetMapFlags[
	  virtual: 
	    IF (highestMappedPage ← highestMappedPage+1) = pageGFT
	    THEN (highestMappedPage ← highestMappedPage+1) ELSE highestMappedPage,
	  real: realPage, flags: flagsClean];
      ENDLOOP;
    END; --FlushMemory--



  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  BEGIN  --main body code.. initialization--
  -- Calls ProcessRequests[], which never returns.
  -- Assumes all SD entries set initally zero by MakeBoot.
  pageGermEnd: PageNumber;  -- end of Germ's VM allocated by MakeBoot.

  ProcessorFace.SpecialSetMP[PilotMP.cGerm];  -- let them know we are here
  -- Interrupts are supposed to be disabled by the boot button, but just in case..
  ProcessOperations.WriteWDC[1];

  SDDefs.SD[SDDefs.sCodeTrap] ← LOOPHOLE[CodeTrap];  -- (start traps)
  SDDefs.SD[SDDefs.sControlTrap] ← LOOPHOLE[ControlTrap];
  SDDefs.SD[SDDefs.sRescheduleError] ← LOOPHOLE[RescheduleErrorTrap];
  SDDefs.SD[SDDefs.sSignal] ← SDDefs.SD[SDDefs.sError] ← LOOPHOLE[SignalHandler];

  IF PageMap.IsMapped[Environment.PageFromLongPointer[@PSB.PDA.fault]] THEN
    -- Clear fault queues to aid debugging (makes fault cause  reschedule error).
    PSB.PDA.fault ← ALL[[PSB.QueueEmpty, ConditionEmpty]];

  ProcessorFace.Start[];

  -- no heap allocation allowed during initialization.
  pHeapAllocNext ← pHeapAllocEnd;
    
  BEGIN
  realPage: PageMap.RealPageNumber;
  -- (ProcessorFace must be started previously)
  CompactVM[]; -- (We don't have to compact now, we just need highest mapped page)
  -- reclaim real page behind ESCTrapTable
  realPage ← PageMap.ExchangeFlags[
    virtual: Environment.PageFromLongPointer[PrincOps.ESCTrapTable],
    newFlags: flagsVacant].real;
  PageMap.SetMapFlags[
    virtual: (highestMappedPage ← highestMappedPage+1),
    real: realPage, flags: flagsClean];
  END;
  allocationDifficulty ← easy;


  -- end of Germ's VM allocated by MakeBoot.
  pageGermEnd ← pageGerm + Boot.pCountGerm↑;

  -- Flush any excess real memory from the Germ's VM:
  -- (Real memory may be there from the action of the initial microcode,
  --  or as a result of microcode+Germ swapping.)
  FlushMemory[pageGermEnd, pageEndGermVM];
  
  -- Identify germ boundaries and make code readOnly.
  BEGIN 
  FlagsOr: PROCEDURE [flags1, flags2: PageMap.Flags] RETURNS [PageMap.Flags] =
      LOOPHOLE[Inline.BITOR];
  gatesOfHellDesc: PrincOpsExtras2.ControlLink =
    LOOPHOLE[GermMarkers.GatesOfHellMarker, PrincOpsExtras2.ProcDesc];
  globalCodebase: LONG POINTER = 
    SELECT gatesOfHellDesc.tag FROM
      shortProc => 
	FrameExtras.ReadCodebase[
	  FrameExtras.LongGFToGFTHandle[LONG[gatesOfHellDesc.gf -
	    PrincOpsExtras2.ControlLinkTag.shortProc.ORD]]].codebase,
      longProc => 
	FrameExtras.ReadCodebase[
	  LOOPHOLE[gatesOfHellDesc, PrincOpsExtras2.ProcDesc].gfi
	    - PrincOpsExtras2.ControlLinkTag.longProc.ORD].codebase,
      ENDCASE => NIL;
  gatesOfHellPage: PageNumber = Environment.PageFromLongPointer[
    globalCodebase +
      LOOPHOLE[gatesOfHellDesc, PrincOpsExtras2.ProcDesc].pc / bPW];
  oldflags: PageMap.Flags;

  FOR page: PageNumber IN [gatesOfHellPage + 1..afterPage] DO
    [state:[flags: oldflags]] ← PageMap.GetState[page];
    [] ← PageMap.ExchangeFlags[
	  virtual: page,
	  newFlags: FlagsOr[oldflags, PageMap.maskReadOnly]];
    ENDLOOP;

  -- Germ's page buffer now lives on top of gatesOfHell marker, separate from
  -- any other permanent storage allocated following.

  pageBuffer ← gatesOfHellPage;
  pBuffer ← PointerFromPage[pageBuffer];

  END;

  -- Init storage allocation to start just after germ code.
  -- Set up structures which must live forever, i.e., through world swaps,
  -- then init beginning of temp storage after that.
  pageAllocNext ← pageGermEnd;

  heads.Start[];  -- start the heads (who could allocate resident memory)

  -- The size of the heap must be fixed at germ init time because memory
  -- cannot always be allocated later.  In order not to tie up extra real memory,
  -- several assumptions are employed here in determining heap size.  If these
  -- assumptions become invalid, the likely result will be MP 909 for heap
  -- overflow.
  -- Assumptions are as follows:  The required size of the heap varies
  -- considerably depending on what disks are attached to the system being
  -- booted.  The disk subsystem requires the largest heapspace of the various
  -- boot channels so is used to calculate the size to allocate.  The maximum
  -- number of disk controllers is 1, and the disk boot channel allocates 2
  -- disk operations.
  -- Heads must have been started.
  BEGIN
  maxDiskControllers: CARDINAL = 7;
  maxDiskOps: CARDINAL = 2;
  wordsSmallResHeapStorage: CARDINAL = 200;  -- amount left in AV page.
  heapWordsNeeded: CARDINAL ←
    (maxDiskControllers *
       (PilotDiskFace.GetControllerAttributes[
          PilotDiskFace.GetNextController[PilotDiskFace.nullControllerHandle]]
	    .globalStateSize + PilotDiskFace.operationAlignment - 1)) +
    (maxDiskOps * (PilotDiskFace.operationSize +
      PilotDiskFace.operationAlignment - 1));
  IF heapWordsNeeded <= wordsSmallResHeapStorage THEN
    BEGIN
    pHeap ← LOOPHOLE[@PrincOps.AV[PrincOps.AVHeapSize]];
    pHeapAllocEnd ← pHeap + wordsSmallResHeapStorage;
    END
  ELSE
    BEGIN
    pages: CARDINAL ← (heapWordsNeeded + wordsPerPage - 1)/wordsPerPage;
    pHeap ← LOOPHOLE[AllocateMDSLocal[count: pages]];
    pHeapAllocEnd ← pHeap + pages * wordsPerPage;
    END;
  pHeapAllocNext ← pHeap;
  END;

  BEGIN
  -- Initialize the BootChannels.. allow them to allocate permanent storage:
  location: Boot.Location;
  location.deviceType ← Device.nullType;
  [] ←  --(null device doesn't really create a Channel; just inits)--
    importedBootChannel.Create[@location, read];
  END;

  -- Remember end of permanent storage / begin temp storage now that Heads etc.
  -- have had their chance.
  pageAllocFirst ← pageAllocNext;

  FreeResidentHeap[];  -- initialize/reset heap allocator.
  
  -- The following correspondences {codePackIndex, procedure} must be the same
  -- as in PilotKernel. IF YOU MAKE A CHANGE HERE, make the corresponding
  -- change there too.
  BEGIN  --workaround for compiler constant folding problem--
  index: GermOps.SharedCode;  -- TEMP
  <<GermOps.pCodeSharingHandles[codePackA] ← ProcessorFace.Start;>>
  index ← codePackA;
  GermOps.pCodeSharingHandles[index] ← ProcessorFace.Start;
  
  <<GermOps.pCodeSharingHandles[codePackB] ←
    LOOPHOLE[PilotDiskFace.InitializeController, PROCEDURE];>>
  index ← codePackB;
  GermOps.pCodeSharingHandles[index] ←
    LOOPHOLE[PilotDiskFace.InitializeController, PROCEDURE];

  <<GermOps.pCodeSharingHandles[codePackC] ←  --
    LOOPHOLE[EthernetFace.TurnOn];  -- may be unbound.>>
  index ← codePackC;
  GermOps.pCodeSharingHandles[index] ←  --
    LOOPHOLE[EthernetFace.TurnOn];  -- may be unbound.
  <<GermOps.pCodeSharingHandles[codePackD] ← NIL;>>
  index ← codePackD;
  GermOps.pCodeSharingHandles[index] ← NIL;
  END;  --workaround for compiler constant folding problem--

  Frame.SetReturnLink[
    Inline.LowHalf[
      LOOPHOLE[PrincOpsExtras2.trapLink]]];  -- (just in case)
  ProcessRequests[];  -- never returns.
  END;  --main body code.. initialization--
  
  END.


LOG

(For earlier log entries, see Mesa 8.0 archive version.)
 3-Nov-81 19:01:38	WDK    
   Germ is now a coroutine with Pilot.  Major rework of InLoad and OutLoad.  Germ moves to mds 0.  New instruction set.  Make compatible with new linkage mechanism in GermOps.  Module renamed from BootSwapGerm to GermOpsImpl.
 4-Nov-81  9:06:23	JGS
    EXPORT ResidentHeapImpl.
10-Nov-81 21:44:59	WDK    
   ResidentHeap.MakeNode must not cross page boundaries for DLion.
17-Nov-81  9:49:28	WDK    
    Added Noop Action.
22-Nov-81 15:42:09	WDK    
    Export GermOps.
23-Nov-81 10:22:30	JGS
   Check curMapEntry >= endMapEntry in 1st of OR in Outload.
23-Nov-81 16:10:33	FXH    
   entriesPerHeader ==> entriesPerTrailer in end of outload.
10-Dec-81 11:40:57	AWL      
   System.MicrosecondsToPulses implemented here.
25-Oct-82 14:40:11	WDK    
    Made compatible with new PageMap.
22-Dec-82 11:01:47	AWL      
   Long page numbers, HeapLocation args to makeNode and FreeNode.
26-Feb-83 13:29:31	AWL      
   Get rid of compiler truncation warnings. When storing page into a BootFile
MapEntry in DoOutLoad, explicitly shorten it (BootFile.PageNumber[page]).
 6-Jun-83  9:29:43	WDK     
   Get LongPointerFromPage from Environment. Add check for too-big vm page number. Make compatible with new BootChannel, handling returned errors and new Locations. Add debug via mp facility, controlled by boot switch. Documented debugging and tuning strategies. Add another check for running out of real memory. Use unused AV for resident heap space. Recover real page behind esc trap table.
19-Jul-83 16:15:58	AWL      
   CodeTrap changes for 32-bit procedure descriptors.  BootFile.{PageNumber, RealPageNumber} are dead.  Misc changes for 32-bit procedure descriptors.
21-Jul-83 15:08:39	AWL      
   GetMainBody from RuntimeInternal not ControlModuleFormat.
27-Jul-83 12:27:42	AWL      
   MakeNode[0] returns Zone.nil.
10-Aug-83 10:42:20	JXG    
    mods to allow germ to load into special memory - export GetNextPilotVM
13-Sep-83 13:39:42	KAM     
   fixed GetNextPilotVM so it returns vm interval if handed an arbitrary page  
21-Sep-83  8:47:37	WDK     
   Must set extension version sooner.
28-Oct-83 12:21:03	WDK     
   Restored GetNextPilotVM to documented semantics (i.e. analagous as ProcessorFace).
28-Nov-83 17:25:59   WDK     
   Turn debug mode off.
13-Jun-84 12:49:08   AWL      
   New BootChannel interface for multiple buffering.  Increase size of resident heap to 200 words.
 8-Nov-84 13:51:43   KEK    
   added code to reclaim memory behind floppy and initialization code (including MarkerPages and Start).
19-Mar-85 17:04:01   CAJ 
   Moved {GatesOfHell, Before, Middle, After}Marker to GermMarkers, rearranged
   packaging order.
18-Apr-85 13:35:39   AWL      
   Can't free global frame via Frame.Free!
 2-Oct-85 23:09:15   CAJ 
   Moved freeing of Floppy code and GatesOfHell; CompactVM with
   onlyKeepVanillaRealMemory=TRUE in AllocateMDSLocal.
17-Oct-85 11:02:07   CAJ 
   Turn debug mode off for 12.0 release.
 4-Sep-86 15:42:53   CAJ 
   Add large object handling to ResidentHeap; MakeNode now pays attention to
   requested alignment.  Turn debug back on.
 4-Nov-86  7:11:05   CAJ 
   Add transferPrimer call to outload.  Make heap annex allocated only if disk
   op won't fit regular heap (until VM size overflow for Dove germ is resolved).
15-Jan-87 16:32:59   CAJ 
   Changes to replace BoundsVanillaMemory with BoundsReservedMemory, which is
   same thing with reversed semantics, to allow Daisy to join the crew.
20-Jun-86 17:56:26   MEW
   Upgraded to move global frames out of MDS. (MDS relief)
16-Jan-87 11:46:52   CAJ 
   MDS relief: merge in changes of 2 previous log entries.
19-Jan-87  6:51:00   CAJ 
   Move page buffer on top of gatesOfHell marker instead of allocating at end of germ with other allocated storage to reclaim a page of VM.
27-Apr-87 13:08:53   CAJ 
   BootChannel.Create now passes a buffer on non-init Creates.  Remove transferPrimer.  Remove heap annex restrictions.  Turn debug off.  Correct some comments.
15-Jun-87 10:11:47   CAJ 
   Add real buffer to rawRead Create.
27-Oct-87 12:21:04   CAJ 
   Make heap size determined at init time based on disk storage requirements.  Remove heap annex.
23-Nov-87  8:37:06   CAJ 
   Make markers global.  Avoid flushing floppy code if booting from floppyTape.  Add PLocation arg to GetTeledebugged.  (GermOpsImpl is different from the corresponding 13.0 version only in the use of PilotDiskFace.operationAlignment, which differs between 13 and 14.)