-- VMMgr>SpaceImplB.mesa  (last edited by Levin on October 25, 1982 3:32 pm)

-- Note: There is another version of SpaceImpl for UtilityPilot which should
-- track changes to this module.

-- Handling of transactions:  In the beginning, a space is created, and it is
-- not part of a transaction.  A space becomes associated with a transaction
-- whenever a non-null transaction handle is passed to a Space operation
-- (except CopyIn/Out), and the transaction handle is stored in the space
-- descriptor at that time.  If later a different transaction handle comes
-- along for an operation on that space, it is an error.  A space ceases to
-- be part of a transaction when:  (1) ReleaseFromTransaction is called;
-- (2) the space is unmapped or deleted.  Remap is handled as as if it
-- were an Unmap followed by a Map.

-- Implementation Notes:
-- All client processes which wish to enter the Space Monitor MUST enter
-- via the procedure EnterSpace.
-- The routines herein have this organization:  first, check for all client
-- errors, and RETURN WITH ERROR if any;  then, make changes to the VM databases.

-- Future Improvements:
-- If we would remember when a whole mapping space had been logged, we could
-- avoid doing it again later.

DIRECTORY
  CachedRegion USING [
    Apply, BackFileType, Desc, forceOut, invalidate, makeWritable, Mapped,
    maxRemapSpaceSize, needsLogging, Operation, Outcome, pageLocationInSpace,
    startUnmap, wait, writeProtect],
  CachedSpace USING [DataOrFile, Desc, Handle, Level],
  Environment USING [bitsPerWord, PageNumber, wordsPerPage],
  File USING [
    Capability, Error, ErrorType, firstPageNumber, lastPageNumber, nullID,
    PageCount, read, Unknown, write],
  Hierarchy USING [GetDescriptor, GetInterval, NotFound, Touch, Update],
  Inline USING [BITAND, LowHalf],
  KernelFile USING [GetFileAttributes, LogContents],
  KernelSpace USING [],
  MapLog USING [WriteLog],
  PageFault USING [ReportAddressFault],
  Process USING [GetPriority, Priority, SetPriority],
  ProcessPriorities USING [priorityPageFaultHigh],
  Projection USING [Get, Touch],
  ResidentHeap USING [first64K, FreeNode, MakeNode],
  Space USING [
    defaultWindow, Error, ErrorType, PageCount, PageNumber, WindowOrigin],
  SpaceImplInternal USING [
    ApplyToInterval, EnterSpace, Interval, ForAllRegions, Level, NotePinned,
    RegionD, SpaceD, spaceLock],
  SpecialSpace USING [],
  SwapperException USING [Await],
  SystemInternal USING [Unimplemented],
  Transaction USING [Handle, InvalidHandle, nullHandle],
  TransactionState USING [AddToTransaction, WithdrawFromTransaction],
  VM USING [Interval],
  VMMPrograms USING [],
  VMMgrStore USING [AllocateWindow, DeallocateWindow],
  WriteFault USING [AwaitWriteFault, ReportWriteProtectFault, RestartWriteFault],
  Volume USING [ID, InsufficientSpace, Unknown],
  Zone USING [Base, Status];

SpaceImplB: MONITOR LOCKS SpaceImplInternal.spaceLock
  -- this lock protects the VMMgr's data and databases.
  IMPORTS
    CachedRegion, File, Hierarchy, Inline, KernelFile, MapLog, PageFault,
    Process, Projection, ResidentHeap, Space, SpaceImplInternal, SwapperException,
    SystemInternal, Transaction, TransactionState, VMMgrStore, Volume, WriteFault
  EXPORTS KernelSpace, Space, SpaceImplInternal
  SHARES File -- USING [fID, permissions] -- =

  BEGIN OPEN Space, SpaceImplInternal;

  Handle: PUBLIC TYPE = CachedSpace.Handle;

  Bug: PRIVATE ERROR [type: BugType] = CODE;
  BugType: TYPE = {
    badTxButNeedsLogging, fileDisappeared, funnyErrorState, funnyOutcome,
    initHeapErr, nullTxButNeedsLogging, noSpaceForLogging, remapHeapAlloc,
    remapHeapFree, spaceDAbsent, unmappedSpaceToUnmapInternal, volDisappeared,
    yourSpaceIsAlreadyWritableinOtherTransaction};

  countVM: Space.PageCount;
  pageSize: CARDINAL = Environment.wordsPerPage;

  nullTransaction: Transaction.Handle = Transaction.nullHandle;

  initRemapSize: PageCount = 250;  -- initial guess at page count of largest space to be remapped.
  currentRemapSize: PageCount ← initRemapSize;

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Initialization:
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  --SpaceImplInternal.--
  InitializeSpaceImplB: PUBLIC --EXTERNAL-- PROCEDURE [sizeVM: Space.PageCount] =
    BEGIN
    throwAway: PROCESS;
    priorityPrev: Process.Priority;
    node: Zone.Base RELATIVE POINTER TO UNSPECIFIED;
    status: Zone.Status;
    size: CARDINAL =
      (initRemapSize + Environment.bitsPerWord - 1)/Environment.bitsPerWord;
    [node, status] ← ResidentHeap.MakeNode[n: size, alignment:];  -- for remapping operations.
    IF status ~= okay THEN ERROR Bug[initHeapErr];
    CachedRegion.pageLocationInSpace ← DESCRIPTOR[
      @ResidentHeap.first64K[node], size];  -- for remapping operations.
    countVM ← sizeVM;  -- save in global.
    priorityPrev ← Process.GetPriority[];
    -- In order to avoid being deadlocked on a stateVector, the WriteFaultProcess
    -- must run at a reserved priority level and have a state vector allocated for
    -- it (in the bootmesa file).
    Process.SetPriority[ProcessPriorities.priorityPageFaultHigh];
    throwAway ← FORK VMHelperProcess[];  -- (no profit in Detaching)
    throwAway ← FORK WriteFaultProcess[];
    Process.SetPriority[priorityPrev];
    END;

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Monitor External (and Nested Internal) Procedures:
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  CopyIn: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, window: WindowOrigin, transaction: Transaction.Handle] =
    -- The transaction parameter is only present for possible future implementation
    -- of locking.  It is not relevant to the current implementation.
    BEGIN
    CopyInInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD, mappingSpaceD, fromSpaceD: SpaceD;
      GetCopyInfo[@spaceD, @mappingSpaceD, space];
      IF mappingSpaceD.writeProtected THEN {
        IF KernelFile.GetFileAttributes[mappingSpaceD.window.file].immutable THEN
          File.Error[immutable]
        ELSE File.Error[insufficientPermissions]};
      fromSpaceD ← mappingSpaceD;  -- generate a desc for the new window..
      fromSpaceD.interval ← spaceD.interval;
      ProcessWindow[@fromSpaceD, @window, forReadingOrWriting, fileSpaceOnly];  -- may raise File.Unknown or Volume.Unknown.
      IF mappingSpaceD.transaction ~= nullTransaction THEN
        BEGIN
        ApplyToInterval[spaceD.interval, CachedRegion.forceOut];  -- make sure backing file is up-to-date.
        KernelFile.LogContents[  -- may raise Volume.InsufficientSpace.
          transaction: mappingSpaceD.transaction,
          file: [mappingSpaceD.window.file.fID, File.read + File.write],
          base:
          mappingSpaceD.window.base +
            (spaceD.interval.page - mappingSpaceD.interval.page),
          count:
          IF mappingSpaceD.interval.page + mappingSpaceD.countMapped <=
          spaceD.interval.page THEN 0
          ELSE
            IF spaceD.interval.page + spaceD.interval.count <=
            mappingSpaceD.interval.page + mappingSpaceD.countMapped THEN
            spaceD.interval.count
            ELSE
              (mappingSpaceD.interval.page + mappingSpaceD.countMapped) -
                spaceD.interval.page];
        END;
      ApplyToInterval[
        spaceD.interval, [
        ifMissing: report, ifCheckedOut: wait, afterForking: return,
        vp: copyIn[from: @fromSpaceD]]];
      ApplyToInterval[spaceD.interval, CachedRegion.wait];  -- must wait for complete, since client could delete the source window. 
      END --CopyInInternal-- ;
    EnterSpace[CopyInInternal];
    END;

  CopyOut: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, window: WindowOrigin, transaction: Transaction.Handle] =
    BEGIN
    CopyOutInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD, mappingSpaceD, toSpaceD: SpaceD;
      GetCopyInfo[@spaceD, @mappingSpaceD, space];
      toSpaceD ← mappingSpaceD;  -- generate a desc for the new window..
      toSpaceD.interval ← spaceD.interval;
      ProcessWindow[@toSpaceD, @window, forWriting, fileSpaceOnly];  -- may raise File.Unknown or Volume.Unknown.
      IF transaction ~= nullTransaction THEN
        KernelFile.LogContents[
          transaction, toSpaceD.window.file, toSpaceD.window.base,
          toSpaceD.countMapped];  -- may raise Transaction.InvalidHandle.
      -- We don't need to update the space desc with the possibly-new transaction
      -- since the transaction is associated with the window copied to, not the current space.
      ApplyToInterval[
        spaceD.interval, [
        ifMissing: report, ifCheckedOut: wait, afterForking: return,
        vp: copyOut[to: @toSpaceD]]];
      ApplyToInterval[spaceD.interval, CachedRegion.wait];  -- must wait for complete, since client could delete the destination window. 
      END --CopyOutInternal-- ;
    EnterSpace[CopyOutInternal];
    END;

  MakeReadOnly: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, transaction: Transaction.Handle] =
    BEGIN
    MakeReadOnlyInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD, mappingSpaceD: SpaceD;
      GetSpaceDesc[@spaceD, space, --requiredState:-- dontCare];
      GetMappingSpaceDesc[@mappingSpaceD, space];
      JoinTransaction[space, @mappingSpaceD, transaction];  -- may raise Transaction.InvalidHandle.
      spaceD.writeProtected ← TRUE;
      Hierarchy.Update[@spaceD];  -- note that the Projection and Hierarchy disagree until the following statement is completed.
      ApplyToInterval[spaceD.interval, CachedRegion.writeProtect];
      END;
    EnterSpace[MakeReadOnlyInternal];
    END;

  MakeWritable: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, file: File.Capability, transaction: Transaction.Handle] =
    BEGIN
    MakeWritableInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD, mappingSpaceD: SpaceD;
      immutable, readOnly, workToDo: BOOLEAN;
      GetSpaceDesc[@spaceD, space, --requiredState:-- dontCare];
      GetMappingSpaceDesc[@mappingSpaceD, space];
      IF file.fID ~=
        (SELECT mappingSpaceD.dataOrFile FROM
           data => File.nullID,
           file => mappingSpaceD.window.file.fID,
           ENDCASE => ERROR) THEN Error[invalidMappingOperation];
      IF mappingSpaceD.dataOrFile = file THEN {
        [immutable: immutable, readOnly: readOnly] ← KernelFile.GetFileAttributes[
          file];
        IF immutable THEN File.Error[immutable];
        IF readOnly THEN File.Error[insufficientPermissions]};
      IF ~spaceD.writeProtected AND mappingSpaceD.transaction ~= nullTransaction
        AND transaction ~= mappingSpaceD.transaction THEN
        Bug[yourSpaceIsAlreadyWritableinOtherTransaction];
      workToDo ← spaceD.writeProtected OR mappingSpaceD.writeProtected
        OR
          (mappingSpaceD.transaction = nullTransaction
            AND transaction ~= nullTransaction);
      JoinTransaction[space, @mappingSpaceD, transaction];  -- may raise Transaction.InvalidHandle.
      IF workToDo THEN
        BEGIN
        spaceD.writeProtected ← FALSE;
        Hierarchy.Update[@spaceD];  -- note that the Projection and Hierarchy disagree until the following statement is completed.
        ApplyToInterval[
          spaceD.interval,
          IF mappingSpaceD.transaction = nullTransaction THEN CachedRegion.makeWritable
          ELSE CachedRegion.needsLogging];
        END;
      END;
    EnterSpace[MakeWritableInternal];
    END;

  Map: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, window: WindowOrigin, transaction: Transaction.Handle] =
    BEGIN
    MapInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD: SpaceD;
      GetSpaceDesc[@spaceD, space, --requiredState:-- unmapped];
      ProcessWindow[@spaceD, @window, forReadingOrWriting, dataSpaceOK];  -- may raise File.Unknown, Volume.InsufficientSpace, or Volume.Unknown.
      JoinTransaction[
        space, @spaceD, transaction  -- may raise Transaction.InvalidHandle.
        ! UNWIND => ReleaseDefaultWindow[@spaceD]; ];
      -- No more signals should be raised past this point!
      spaceD.state ← mapped;
      Hierarchy.Update[@spaceD];
      ApplyToInterval[
        spaceD.interval, [
        ifMissing: report, ifCheckedOut: wait, afterForking: --don't care-- ,
        vp: map[
        level: space.level,
        backFileType:
        IF spaceD.dataOrFile = CachedSpace.DataOrFile[file] THEN file ELSE data,
        andWriteProtect: spaceD.writeProtected,
        andNeedsLogging: ~spaceD.writeProtected
        AND spaceD.transaction ~= nullTransaction]]];
      MapLog.WriteLog[Interval[spaceD.interval.page, spaceD.countMapped], @spaceD]
      END --MapInternal-- ;
    EnterSpace[MapInternal];
    END;

  --KernelSpace.--
  ReleaseFromTransaction: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, transaction: Transaction.Handle, andInvalidate: BOOLEAN] =
    BEGIN
    ReleaseFromTransactionInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceD: SpaceD;
      GetSpaceDesc[@spaceD, space, --requiredState:-- dontCare];
      IF spaceD.transaction ~= transaction THEN RETURN  -- the space in the given transaction has been deleted.  This is a different space (but with the same handle).
      ELSE
        BEGIN
        IF spaceD.state = mapped THEN {
          IF andInvalidate THEN
            ApplyToInterval[spaceD.interval, CachedRegion.invalidate];
          IF ~spaceD.writeProtected THEN
            ApplyToInterval[spaceD.interval, CachedRegion.makeWritable]};
        spaceD.transaction ← nullTransaction;
        Hierarchy.Update[@spaceD];
        END;
      END;
    EnterSpace[ReleaseFromTransactionInternal];
    END;

  Remap: PUBLIC --EXTERNAL-- PROCEDURE [
    space: Handle, window: WindowOrigin, transaction: Transaction.Handle] =
    BEGIN
    RemapInternal: INTERNAL PROCEDURE[] =
      BEGIN
      spaceDOld, spaceDNew: SpaceD;
      GetSpaceDesc[@spaceDOld, space, --requiredState:-- mapped];
      spaceDNew ← spaceDOld;  -- generate a desc for the new space/window.
      IF spaceDOld.transaction ~= nullTransaction THEN
        TransactionState.WithdrawFromTransaction[
          spaceDOld.transaction, space ! Transaction.InvalidHandle => CONTINUE];  -- (tx had already ended)
      spaceDNew.transaction ← nullTransaction;  -- (will join if caller passed new transacton)
      ProcessWindow[@spaceDNew, @window, forWriting, dataSpaceOK];  -- may raise File.Unknown, Volume.InsufficientSpace, or Volume.Unknown.
      -- scope of UNWIND --
      BEGIN
      ENABLE UNWIND => ReleaseDefaultWindow[@spaceDNew];
      JoinTransaction[space, @spaceDNew, transaction];  -- may raise Transaction.InvalidHandle.
      IF spaceDNew.transaction ~= nullTransaction THEN  -- log the contents of the destination window..
        KernelFile.LogContents[
          spaceDNew.transaction, spaceDNew.window.file, spaceDNew.window.base,
          spaceDNew.countMapped];  -- may raise Volume.InsufficientSpace.
      END --scope of UNWIND-- ;
      -- No more signals should be raised past this point!
      IF spaceDOld.interval.count > currentRemapSize THEN  -- get a bigger remap array
        BEGIN
        node: Zone.Base RELATIVE POINTER TO UNSPECIFIED;
        size: CARDINAL;
        status: Zone.Status;
        IF spaceDOld.interval.count > CachedRegion.maxRemapSpaceSize THEN
          ERROR SystemInternal.Unimplemented;
        IF ResidentHeap.FreeNode[
          Inline.LowHalf[
          BASE[CachedRegion.pageLocationInSpace] - ResidentHeap.first64K]] ~= okay
          THEN ERROR Bug[remapHeapFree];
        currentRemapSize ← spaceDOld.interval.count;
        size ←
          (currentRemapSize + Environment.bitsPerWord -
             1)/Environment.bitsPerWord;
        [node, status] ← ResidentHeap.MakeNode[n: size, alignment:];
        IF status ~= okay THEN ERROR Bug[remapHeapAlloc];
        CachedRegion.pageLocationInSpace ← DESCRIPTOR[
          @ResidentHeap.first64K[node], size];
        END;
      -- At this point, swap units may soon reside in either of two windows.  Mark
      -- all swap units "in old window", and force out dirty ones unless data space or write protected:
      ApplyToInterval[
        spaceDOld.interval, [
        ifMissing: report, ifCheckedOut: wait, afterForking: return,
        vp: remapA[
        firstClean: spaceDOld.dataOrFile = file AND ~spaceDOld.writeProtected]]];
      --   (assume writeProtected implies clean, i.e. no magic stores by debugger, etc.)
      -- implicit parameter: CachedRegion.pageLocationInSpace. 
      spaceDNew.state ← beingRemapped;  -- "the space desc has changed to the new window".
      Hierarchy.Update[@spaceDNew];
      -- Ensure each region is in the new window, or is in and dirty:
      ApplyToInterval[
        spaceDNew.interval, [
        ifMissing: report, ifCheckedOut: wait, afterForking: return,
        vp: remapB[from: @spaceDOld]]];
      -- implicit parameter: CachedRegion.pageLocationInSpace. 
      spaceDNew.state ← mapped;  -- "once again, there is only one window for this space"
      Hierarchy.Update[@spaceDNew];
      -- (end of scope of pageLocationInSpace)
      -- (For remote swapping, must unpin old file (and containing volume) from FilePageTransferrer cache)
      ApplyToInterval[spaceDNew.interval, CachedRegion.wait];  -- must wait for complete, since we or client may delete the old window. 
      ReleaseDefaultWindow[@spaceDOld];
      MapLog.WriteLog[Interval[spaceDOld.interval.page, spaceDOld.countMapped], NIL];
      MapLog.WriteLog[Interval[spaceDNew.interval.page, spaceDNew.countMapped], @spaceDNew];
      END --RemapInternal-- ;
    EnterSpace[RemapInternal];
    END;

  Unmap: PUBLIC --EXTERNAL-- PROCEDURE [space: Handle] =
    BEGIN
    UnmapLocalInternal: INTERNAL PROCEDURE[] = {
      spaceD: SpaceD;
      GetSpaceDesc[@spaceD, space, --requiredState:-- mapped];
      IF spaceD.transaction ~= nullTransaction THEN {
        TransactionState.WithdrawFromTransaction[
          spaceD.transaction, space ! Transaction.InvalidHandle => CONTINUE];  -- (tx had already ended)
        spaceD.transaction ← nullTransaction};
      UnmapInternal[@spaceD]};
    EnterSpace[UnmapLocalInternal];
    END;

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  --Monitor Internal Procedures:
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  GetCopyInfo: INTERNAL PROCEDURE [
    pSpaceD, pMappingSpaceD: POINTER TO SpaceD, space: Handle] =
    -- Validates space, assures that it is mapped or a descendent of a mapped space,
    -- returns space descriptor for space (synthesizes one if space is a swap unit) and mapping space.
    BEGIN
    validSpace, validSwapUnit: BOOLEAN;
    region: RegionD;
    [validSpace, validSwapUnit] ← Hierarchy.GetDescriptor[pSpaceD, space];
    IF ~validSpace AND ~validSwapUnit THEN Error[invalidHandle];
    region ← Projection.Get[space.page];
    IF ~(region.state IN CachedRegion.Mapped) THEN Error[noWindow];
    IF space.level = pSpaceD.level AND pSpaceD.level = region.levelMapped THEN
      pMappingSpaceD↑ ← pSpaceD↑
    ELSE
      [] ← Hierarchy.GetDescriptor[
        pMappingSpaceD, Handle[level: region.levelMapped, page: space.page]];
    IF validSwapUnit THEN
      pSpaceD.interval ← Hierarchy.GetInterval[space].interval;
    END;

  GetSpaceDesc: INTERNAL PROCEDURE [
    pSpaceD: POINTER TO SpaceD, space: Handle,
    requiredState: {mapped, unmapped, dontCare}] =
    -- Validates that space is a real space (not a swap unit), gets space descriptor,
    -- assures desired mapping state.
    BEGIN
    Unmapped: INTERNAL PROCEDURE [regionD: RegionD] RETURNS [BOOLEAN] = {
      RETURN[regionD.state = unmapped]};
    validSpace, validSwapUnit: BOOLEAN;
    [validSpace, validSwapUnit] ← Hierarchy.GetDescriptor[pSpaceD, space];
    IF validSwapUnit THEN Error[notApplicableToSwapUnit]
    ELSE IF ~validSpace THEN Error[invalidHandle];
    SELECT requiredState FROM
      mapped => IF pSpaceD.state ~= mapped THEN Error[noWindow];
      unmapped =>
        IF ~ForAllRegions[pSpaceD.interval, Unmapped] THEN
          Error[invalidMappingOperation];
      dontCare => NULL;
      ENDCASE;
    END;

  GetMappingSpaceDesc: INTERNAL PROCEDURE [
    pMappingSpaceD: POINTER TO SpaceD, space: Handle] =
    -- Validates that space is a real space (not a swap unit) and is either
    -- mapped or a subspace of a mapped space, and gets the mapping space
    -- descriptor.
    BEGIN
    validSpace, validSwapUnit: BOOLEAN;
    region: RegionD;
    [validSpace, validSwapUnit] ← Hierarchy.GetDescriptor[pMappingSpaceD, space];
    IF validSwapUnit THEN Error[notApplicableToSwapUnit]
    ELSE IF ~validSpace THEN Error[invalidHandle];
    region ← Projection.Get[space.page];
    IF ~(region.state IN CachedRegion.Mapped) THEN Error[noWindow];
    IF pMappingSpaceD.level ~= region.levelMapped THEN
      [] ← Hierarchy.GetDescriptor[
        pMappingSpaceD, Handle[level: region.levelMapped, page: space.page]];
    END;

  JoinTransaction: INTERNAL PROCEDURE [
    space: Handle, pSpaceD: POINTER TO SpaceD, transaction: Transaction.Handle] =
    INLINE
    -- It is best if this procedure is called after all other possible errors have
    -- been detected, since there is no way to back out of the AddToTransaction.
    -- May raise Transaction.InvalidHandle.
    {
    IF transaction ~= nullTransaction AND pSpaceD.transaction ~= transaction THEN
      {
      IF pSpaceD.transaction ~= nullTransaction
        --AND pSpaceD.transaction~=transaction-- THEN
        TransactionState.WithdrawFromTransaction[pSpaceD.transaction, space];
      pSpaceD.transaction ← transaction;
      TransactionState.AddToTransaction[transaction, space]}};

  ProcessWindow: INTERNAL PROCEDURE [
    pSpaceD: POINTER TO SpaceD, pWindow: POINTER TO Space.WindowOrigin,
    usage: {forWriting, forReadingOrWriting},
    kind: {dataSpaceOK, fileSpaceOnly}] =
    -- Fills in pSpaceD.dataOrFile, .writeProtected, .countMapped, and .window.  Allocates window if data space.
    -- May raise File.Unknown, Volume.InsufficientSpace, or Volume.Unknown (as well as Space.Error, etc. etc.).
    BEGIN
    IF pWindow↑ = defaultWindow THEN  --data space--
      BEGIN
      IF kind = fileSpaceOnly THEN Error[invalidMappingOperation];
      pSpaceD.dataOrFile ← data;
      pSpaceD.writeProtected ← FALSE;
      pSpaceD.countMapped ← pSpaceD.interval.count;
      pSpaceD.window.file.fID ← File.nullID;  -- "backing store not allocated yet"
      VMMgrStore.AllocateWindow[@(pSpaceD.window), pSpaceD.interval.count];  -- may raise Volume.InsufficientSpace.
      END
    ELSE  --file space--
      BEGIN
      countFile: File.PageCount;
      immutable: BOOLEAN;
      countMappedFile: File.PageCount;
      pSpaceD.dataOrFile ← file;
      [size: countFile, immutable: immutable, readOnly: pSpaceD.writeProtected] ←
        KernelFile.GetFileAttributes[pWindow.file];
      IF ~(pWindow.base IN [File.firstPageNumber..File.lastPageNumber]) THEN
        Error[invalidWindow];
      IF Inline.BITAND[pWindow.file.permissions, File.read] = 0 THEN
        File.Error[insufficientPermissions];
      IF pSpaceD.writeProtected AND usage = forWriting THEN {
        IF immutable THEN File.Error[immutable]
        ELSE File.Error[insufficientPermissions]};
      IF ~pSpaceD.writeProtected AND immutable THEN File.Error[immutable];
      countMappedFile ←
        IF countFile <= pWindow.base THEN 0 ELSE countFile - pWindow.base;  -- the mapped amount of this space (no danger of underflow)
      pSpaceD.countMapped ←
        IF pSpaceD.interval.count <= countMappedFile THEN pSpaceD.interval.count
        ELSE Inline.LowHalf[countMappedFile];  -- (no danger of truncation)
      pSpaceD.window ← pWindow↑;
      END;
    -- (For remote swapping, must pin file (and containing volume) in FilePageTransferrer caches)
    END;

  ReleaseDefaultWindow: INTERNAL PROCEDURE [pSpaceD: POINTER TO SpaceD] = INLINE {
    IF pSpaceD.dataOrFile = data AND pSpaceD.window.file.fID ~= File.nullID THEN
      VMMgrStore.DeallocateWindow[@(pSpaceD↑.window), pSpaceD.interval.count]};

  --SpaceImplInternal.--
  UnmapInternal: PUBLIC INTERNAL PROCEDURE [pSpaceD: POINTER TO SpaceD] =
    BEGIN OPEN s: pSpaceD;
    IF s.state ~= mapped THEN ERROR Bug[unmappedSpaceToUnmapInternal];
    ApplyToInterval[
      s.interval, CachedRegion.startUnmap !
      NotePinned -- [levelMax, page] -- =>
        BEGIN
        levelSub: Level;
        spaceDSub: SpaceD;
        FOR levelSub IN [s.level + 1..levelMax] DO
          [] ← Hierarchy.GetDescriptor[
            @spaceDSub, CachedSpace.Handle[levelSub, page]];
          IF spaceDSub.pinned THEN {
            spaceDSub.pinned ← FALSE; Hierarchy.Update[@spaceDSub]; EXIT};
          ENDLOOP;
        RESUME
        ;
        END; ];
    ApplyToInterval[s.interval, CachedRegion.wait];
    s.pinned ← FALSE;
    s.state ← unmapped;
    s.transaction ← nullTransaction;  -- since there's no longer any assosciated file.
    Hierarchy.Update[pSpaceD];
    -- (For remote swapping, must unpin old file (and containing volume) from FilePageTransferrer cache)
    IF s.dataOrFile = data THEN
      VMMgrStore.DeallocateWindow[@s.window, s.interval.count];
    MapLog.WriteLog[Interval[s.interval.page, s.countMapped], NIL];
    END;


  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Virtual Memory Management support functions
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  VMHelperProcess: --EXTERNAL-- PROCEDURE =
    -- Provides access to the Hierarchy and Projection for the PageFaultProcess and the ReplacementProcess.
    BEGIN
    page: PageNumber;
    operation: CachedRegion.Operation;
    outcome: CachedRegion.Outcome;
    HandleException: ENTRY PROCEDURE = INLINE
      -- Since this is a monitor entry, new entries may not be added asynchronously
      -- to the space and region caches due to page faults.  Thus, if a region or space
      -- descriptor is flushed from its cache, the higher-level databases can be
      -- temporarily inconsistent (not satisfying the monitor invariant).
      BEGIN
      --UNTIL outcome=ok--
      DO
        WITH outcome SELECT FROM
          ok => RETURN;  -- done.
          regionDMissing =>
            IF page >= countVM THEN GO TO AddressFault
            ELSE Projection.Touch[page];
          spaceDMissing --[level] -- =>
            -- If a pagefault or an age happens, and then the space is deleted
	    -- before this process can service its needs, the space desc will be
	    -- missing.  In this case, we just retry the operation in the current
	    -- context (and the right thing will happen).
            Hierarchy.Touch[[level, page] ! Hierarchy.NotFound => CONTINUE];
          error --[state]-- =>
            IF operation.action = activate THEN GO TO AddressFault
            ELSE ERROR Bug[funnyErrorState];
          ENDCASE => ERROR Bug[funnyOutcome];
        outcome ← CachedRegion.Apply[page, operation].outcome;
        ENDLOOP;
      EXITS
        AddressFault => PageFault.ReportAddressFault[page];
      END;
    DO  --FOREVER--
      [page, operation, outcome] ← SwapperException.Await[];  -- wait for work..
      HandleException[];  -- do what's wanted.
      ENDLOOP;
    END;

  WriteFaultProcess: --EXTERNAL-- PROCEDURE[] =
    BEGIN
    HandleFault: ENTRY PROCEDURE [page: PageNumber] = INLINE {
      mappingSpace: SpaceD;
      swapInterval: VM.Interval;
      region: RegionD ← Projection.Get[page];
      -- Either this region is in a transaction and needs to be logged,
      -- or this is a real write protect fault.
      IF ~region.needsLogging THEN {WriteFault.ReportWriteProtectFault[page]; RETURN};
      [] ← Hierarchy.GetDescriptor[@mappingSpace, [region.levelMapped, region.interval.page]];
      IF mappingSpace.state = missing THEN ERROR Bug[spaceDAbsent];
      IF mappingSpace.transaction = nullTransaction THEN
        ERROR Bug[nullTxButNeedsLogging];
      swapInterval ← Hierarchy.GetInterval[
        CachedSpace.Handle[
        region.level + (IF region.hasSwapUnits THEN 1 ELSE 0), page]].interval;
      KernelFile.LogContents[
        transaction: mappingSpace.transaction,
        file: [mappingSpace.window.file.fID, File.read + File.write],
        base: mappingSpace.window.base + (swapInterval.page - mappingSpace.interval.page),
        count:
          IF swapInterval.page + swapInterval.count <=
           mappingSpace.interval.page + mappingSpace.countMapped THEN swapInterval.count
          ELSE (mappingSpace.interval.page + mappingSpace.countMapped) - swapInterval.page
        ! File.Unknown => ERROR Bug[fileDisappeared];
          Transaction.InvalidHandle => ERROR Bug[badTxButNeedsLogging];
          Volume.InsufficientSpace => ERROR Bug[noSpaceForLogging];
          Volume.Unknown => ERROR Bug[volDisappeared]];
      ApplyToInterval[swapInterval, CachedRegion.makeWritable];
      WriteFault.RestartWriteFault[swapInterval];
      };
    DO
      HandleFault[WriteFault.AwaitWriteFault[]];
      ENDLOOP;
    END;


  END.


LOG

(For earlier log entries see Pilot 3.0 archive version.)
January 25, 1980  1:50 PM	Knutsen	Use new ErrorType's.
January 28, 1980  10:54 AM	Forrest	Made SpaceImpl take starting parameters and eliminated InitSpace;
				copied in (most) of LongPtr<=>Page from UtilitiesImpl.
February 25, 1980  6:04 PM	Knutsen	AR3594: CreateUSU[spaceWithSU] raised wrong signal.
				AR1935: use Projection.DeleteSwapUnits.  Renumbered the Internal errors.
April 16, 1980  10:09 AM	Knutsen	Remap must always wait for operation complete to avoid
				having the file deleted out from under the swapping operation.
				DeleteIfLeaf must avoid walking off the ends of VM.  Converted
				SpaceImpl[] into InitializeSpace[] AGAIN!
April 17, 1980  1:03 PM	Gobbel	Added transaction handles.
April 21, 1980  6:01 PM	Gobbel	Implemented Space.Copy.
May 19, 1980  5:42 PM	Gobbel	FrameOps=>Frame, ControlDefs => PrincOps.
May 21, 1980  2:31 PM	Gobbel	Mesa 6 change: f.code.longbase replaced by RuntimeInternal.CodeBase[frame]
				in SpaceForCode.
June 16, 1980  5:12 PM	Gobbel	Transaction operations added.
July 19, 1980  12:00 PM	McJones	Split module into SpaceImplA/B.  Define nullTransaction locally;
				don't disable interrupts in WriteProtectTrap; add new parameters
				to MakeReadonly, MakeWritable, and Remap
August 11, 1980  5:11 PM	Knutsen	Make spaces enter transactions anytime. Implement
				copy-on-write via writeProtect trap.  Use new Apply operations
				for write protection.  Add ReleaseFromTransaction.  Moved
				ApplyToInterval, etc. to SpaceImplA.  Revise error handling.
August 12, 1980  7:11 PM	Knutsen	CheckCopyArgs didn't copy space desc.
August 29, 1980  4:46 PM	Knutsen	SpaceInternal renamed to KernelSpace.  Map didn't
				return invalidWindow for bad base.  If file immutable and
				write permission, Error[immutable].  Handle some cases of
				AllocateWindow signalling Vol.InsuffSpace.
September 15, 1980  9:35 AM	Knutsen	Restructured signal handling.  Fix CopyIn/Out,
				MakeReadOnly, MakeWritable.  Fix ReleaseFromTransaction
				deadlock.  CopyIn/Out do not join transaction.  Leave
				transaction on Unmap and possibly on Remap.
October 10, 1980  10:44 PM	Fay	Fixed CopyIn to raise File.Error[immutable] for space
				with immutable backing file and [insufficientPermissions] for
				any other writeProtected spaces; reordered checks in MakeWritable
				so that File.Error[immutable] is raised for a space with immutable window.
October 16, 1980  11:02 AM	Knutsen	Fix HandleWriteProtectTrap and CopyIn to supply write
				permission in Capability used for logging.
January 19, 1981  4:57 PM	Knutsen	WriteProtect implemented as fault instead of trap.
				Fix ARs 6753, 6458, 6466, 6625.
January 27, 1981  8:45 AM	Knutsen	WriteFaultProcess must run at reserved priority.  Transiently
				boost caller's priority in EnterSpace, which was moved to ImplA.
				VMHelper moved here.
February 4, 1981  11:33 AM	Knutsen	Remove LOOPHOLEs used to get fault parameters.
February 14, 1981  5:18 PM	Knutsen	Move faulted guy to other half of PDA.fault instead of private queue.
February 17, 1981  9:37 PM	Knutsen	VMHelper must check for giant address.
February 25, 1981  2:33 PM	Knutsen	VMHelper forks process to report addr faults.
				Coundn't MakeWritable[dataSpace].
 4-Feb-82 10:35:59		Levin Change MakeReadOnly and MakeWritable to accept subspaces of
				mapped spaces as well as mapped spaces (expected use by Loader
				when fixing up code links).
 4-Feb-82 10:51:45		Levin Fix maplog usage in Remap to correspond to new implementation (i.e.,
 				make it look like Unmap followed by Map).
13-Feb-82 13:05:11		Levin Fix bug in GetMappingSpaceDesc, as well as code in GetCopyInfo
				from which it was copied, to pass correct argument to
				Hierarchy.GetDescriptor.
August 3, 1982 4:06 pm	Levin	Correct all occurrences of ~IN.
September 15, 1982 6:07 pm	Levin	Rework address and write-protect fault handling.
October 25, 1982 3:32 pm	Levin	Eliminate forking in address and write-protect fault handling.