-- PhysicalVolumeImpl.mesa (last edited by: Jose on: March 24, 1981  4:38 PM)

DIRECTORY
  Boot USING [Location, LVBootFiles, PVBootFiles, VolumeType],
  Device USING [nullType, Type],
  DiskChannel USING [
    AwaitStateChange, CompletionStatus, Create, DiskPageCount, Drive, DriveState,
    DriveStatus, GetAttributes, GetDriveAttributes, GetNextDrive, GetPageNumber,
    nullDrive, nullHandle, PVHandle, SetDriveState, SetDriveTag],
  Environment USING [wordsPerPage],
  File USING [Capability, ID, nullCapability, PageCount, Permissions, read, Type],
  FileInternal USING [maxPermissions],
  FMPrograms USING [ScavengeImpl, VolumeImpl],
  Inline USING [LowHalf],
  KernelPhysicalVolume USING [],
  LabelTransfer USING [DiskStatusToLabelStatus, ReadRootLabel, WriteLabels],
  LogicalVolume USING [Handle, rootPageNumber],
  MarkerPage USING [
    CacheKey, Enter, EnterMarkerID, Find, Flush, GetNextPhysicalVolume, NotFound,
    UpdatePhysicalMarkerPages],
  PhysicalVolume USING [
    CanNotScavenge, Error, ErrorType, ID, Layout, nullBadPage,
    nullDeviceIndex, nullID, PageNumber, VolumeType],
  PhysicalVolumeFormat USING [
    currentVersion, descriptorSize, Handle, IDCheckSum, maxSubVols, nullBadPage,
    nullPVBootFiles, PageNumber, rootPageNumber, Seal, seal],
  PilotDisk USING [GetLabelFilePage, GetLabelType, Label],
  PilotFileTypes USING [tPhysicalVolumeRootPage, tSubVolumeMarkerPage],
  PilotMP USING [cDeleteTemps, cDriveNotReady],
  PilotSwitches USING [switches],
  ProcessorFace USING [SetMP],
  Runtime USING [CallDebugger],
  SimpleSpace USING [Create, ForceOut, Handle, Map, Page, Unmap],
  SpecialVolume USING [nullSubVolume, SubVolume, SubVolumeUnknown],
  SubVolume USING [completion, Find, GetNext, Handle, OffLine, OnLine],
  System USING [GetUniversalID, nullID, LocalTimeParameters],
  Utilities USING [LongPointerFromPage],
  VolAllocMap USING [Close],
  VolFileMap USING [Close],
  Volume USING [ID, nullID, PageCount, systemID, Type, Unknown],
  VolumeImplInterface USING [
    BarePvID, CheckLogicalVolume, FindLogicalVolume, GetLVStatus,
    LogicalVolumeCreate, LogicalVolumeErase, OpenInitialVolumes, PinnedFileFlush,
    readOrWrite, RegisterLogicalSubvolume, SubvolumeOffline, SubvolumeOnline,
    VFileEnter],
  VolumeInternal USING [PageNumber];

PhysicalVolumeImpl: MONITOR [
  bootFile: LONG POINTER TO disk Boot.Location,
  pLVBootFiles: POINTER TO Boot.LVBootFiles]
  RETURNS [debuggerDeviceType: Device.Type, debuggerDeviceOrdinal: CARDINAL]
  IMPORTS
    DiskChannel, FMPrograms, Inline, LabelTransfer, MarkerPage, PhysicalVolume,
    PhysicalVolumeFormat, PilotDisk, PilotSwitches, ProcessorFace, Runtime,
    SimpleSpace, SpecialVolume, SubVolume, System, Utilities, VolAllocMap,
    VolFileMap, Volume, VolumeImplInterface
  EXPORTS FMPrograms, KernelPhysicalVolume, PhysicalVolume, SpecialVolume,
    VolumeImplInterface
  SHARES File, PhysicalVolume =
  BEGIN
  -- A note about dependencies.  Logically, physical volumes lie below logical volumes.
  -- Thus, this module may not call any of the logical volume entries while it has the
  -- monitor locked.  The volume online/offline machinery is special in that it is logically
  -- above logical volumes.  Thus, it has need to call into that machinery.  The current
  -- implementation of these functions imply assumes that no calls back into this module
  -- will occur.

  PhysicalVolumeImplError: ERROR [ErrorType] = CODE;
  ErrorType: TYPE = {
    impossibleDriveStateChangeFailure, impossibleOffLineFailure,
    impossibleSelectError, invalidSubVolumeNumber, physicalVolumeNotFound};
  LvHandle: TYPE = LogicalVolume.Handle;
  PvHandle: TYPE = PhysicalVolumeFormat.Handle;
  debugClass: Boot.VolumeType;
  debugSearchState: {tooSoonToLook, looking, done} ← tooSoonToLook;
  pvRootPage: PhysicalVolumeFormat.PageNumber =
    PhysicalVolumeFormat.rootPageNumber;

  -- Buffer variables for accessing physical volume root page
 
  -- Eventually, set rootPagePages based upon the device type of a volume.  When this
  -- happens, we will have to arrange to have (arbitrarily?) larger buffers.
  rootPagePages: File.PageCount =
                     PhysicalVolumeFormat.descriptorSize/Environment.wordsPerPage;
   -- the following space MUST be used by PhysicalRootPageAccessInternal as there
   -- procedures that do ForceOut's on this space before returning to  this procedure
  physicalRootPageBuffer: SimpleSpace.Handle =
       -- WE ASSUME that the root page isn't too big
       SimpleSpace.Create[LOOPHOLE[Inline.LowHalf[rootPagePages]], hyperspace, 1];
  physicalVolume: PvHandle = Utilities.LongPointerFromPage[
    SimpleSpace.Page[physicalRootPageBuffer]];

  --
  -- PhysicalVolume

  maxSubvolumesOnPhysicalVolume: PUBLIC CARDINAL ←
         PhysicalVolumeFormat.maxSubVols;
  CanNotScavenge: PUBLIC ERROR = CODE;
  -- The following is exported by ScavengeImpl due to a compiler limitation.  It should be exported here logically.
  --Error: PUBLIC ERROR [PhysicalVolume.ErrorType] = CODE;
  Handle: PUBLIC TYPE = DiskChannel.PVHandle;

  AssertNotAPilotVolume: PUBLIC ENTRY PROCEDURE [instance: Handle] =
    BEGIN
    IF ~ValidateDrive[instance.drive] THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    SELECT DiskChannel.SetDriveState[instance.drive, instance.changeCount, channel]
      FROM
      invalidDrive => RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
      alreadyAsserted => RETURN WITH ERROR PhysicalVolume.Error[alreadyAsserted];
      ENDCASE;
    END;

  AssertPilotVolume: PUBLIC ENTRY PROCEDURE [instance: Handle]
    RETURNS [pvID: PhysicalVolume.ID] =
    -- This procedure assumes that this module will not be called by VolumeImpl when this procedure calls VolumeImpl through VolumeImplInterface.  If this assumption should ever not be true, this procedure must be modified to release the monitor lock before calling into VolumeImpl.
    BEGIN
    localError: PhysicalVolume.ErrorType;
    resetDriveState: BOOLEAN ← FALSE;
    BEGIN
    IF ~ValidateDrive[instance.drive] THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    IF ~DiskChannel.GetDriveAttributes[instance.drive].ready THEN
      RETURN WITH ERROR PhysicalVolume.Error[notReady];
    SELECT DiskChannel.SetDriveState[instance.drive, instance.changeCount, pilot]
    FROM
      invalidDrive => RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
      alreadyAsserted => RETURN WITH ERROR PhysicalVolume.Error[alreadyAsserted];
      ENDCASE;
    resetDriveState ← TRUE;
    [id: pvID] ← PhysicalVolumeOnLineInternal[instance.drive !
         PhysicalVolume.Error => {localError ← error; GO TO pvError};
         PhysicalVolume.CanNotScavenge => GO TO unscavengeable; ];
    EXITS
    pvError => { IF resetDriveState THEN -- 0 2'nd arg => guaranteed ok as a status
                      [] ← DiskChannel.SetDriveState[instance.drive, 0, inactive];
                    RETURN WITH ERROR PhysicalVolume.Error[localError] };
    unscavengeable => { IF resetDriveState THEN -- 0 as 2'nd arg => ok as a status
                                 [] ← DiskChannel.SetDriveState[instance.drive, 0, inactive];
                              RETURN WITH ERROR PhysicalVolume.CanNotScavenge };
    END
    END;

  AwaitStateChange: PUBLIC PROCEDURE [
    changeCount: CARDINAL, type: Device.Type, index: CARDINAL]
    RETURNS [currentChangeCount: CARDINAL] =
    { RETURN[DiskChannel.AwaitStateChange[changeCount, type, index]]};

  CreateLogicalVolume: PUBLIC PROCEDURE [
    pvID: PhysicalVolume.ID, size: Volume.PageCount, name: STRING,
    type: Volume.Type, minPVPageNumber: PhysicalVolume.PageNumber]
    RETURNS [Volume.ID] =
    { RETURN[
      VolumeImplInterface.LogicalVolumeCreate[
         pvID, size, name, type, minPVPageNumber]] };

  CreatePhysicalVolume: PUBLIC ENTRY PROCEDURE [instance: Handle, name: STRING]
    RETURNS [PhysicalVolume.ID] =
    BEGIN
    localError: PhysicalVolume.ErrorType;
    BEGIN
    i, labelLength: CARDINAL;
    pvID: VolumeImplInterface.BarePvID;
    ready: BOOLEAN;
    changeCount: CARDINAL;
    state: DiskChannel.DriveState;
    IF name = NIL OR name.length = 0 THEN
      RETURN WITH ERROR PhysicalVolume.Error[nameRequired];
    IF ~ValidateDrive[instance.drive] THEN
      RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    [ready: ready, changeCount: changeCount, state: state] ←
       DiskChannel.GetDriveAttributes[instance.drive];
    IF changeCount ~= instance.changeCount THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    IF ~ready THEN RETURN WITH ERROR PhysicalVolume.Error[notReady];
    IF state = pilot THEN
       BEGIN
       PhysicalVolumeOffLineInternal[instance.drive !
         PhysicalVolume.Error => {localError ← error; GO TO pvError}];
       IF DiskChannel.SetDriveState[
            instance.drive, instance.changeCount, inactive] ~= ok THEN ERROR;
       END
    ELSE IF state = channel THEN
       RETURN WITH ERROR PhysicalVolume.Error[alreadyAsserted];
    IF DiskChannel.SetDriveState[instance.drive, instance.changeCount, pilot] ~= ok
       THEN ERROR;
    pvID ← System.GetUniversalID[];
    RegisterPvInfo[pvID, instance.drive];
    [] ← LabelTransfer.WriteLabels[-- take care.  The label may be more than one page!
      [[pvID], [pvID],
       local[FALSE, FALSE, rootPagePages, PilotFileTypes.tPhysicalVolumeRootPage]],
      [pvRootPage, pvRootPage, pvRootPage+rootPagePages]];
    PhysicalRootPageMap[pvID, readWrite];
    labelLength ← MIN[name.length, LENGTH[physicalVolume.label]];
    -- When the bad page list has a device dependent length, be sure to assign to
    -- maxBadPages in the following constructor.
    physicalVolume↑ ←
      [subVolumeCount: 0, labelLength: labelLength, pvID: [pvID], label: NULL,
       subVolumes: NULL, badPageList: ALL[PhysicalVolumeFormat.nullBadPage]];
    FOR i IN [0..labelLength) DO physicalVolume.label[i] ← name[i]; ENDLOOP;
    RegisterSubvolumeMarker[physicalVolume];
    PhysicalRootPageUnmap[];
    RETURN[[pvID]];
    EXITS pvError => RETURN WITH ERROR PhysicalVolume.Error[localError];
    END
    END;

  EraseLogicalVolume: PUBLIC PROCEDURE [lvID: Volume.ID] =
    { VolumeImplInterface.LogicalVolumeErase[lvID] };

  FinishWithNonPilotVolume: PUBLIC ENTRY PROCEDURE [instance: Handle] =
    BEGIN
    IF ~ValidateDrive[instance.drive] THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    SELECT DiskChannel.GetDriveAttributes[instance.drive].state FROM
        inactive => RETURN;
        pilot => RETURN WITH ERROR PhysicalVolume.Error[hasPilotVolume];
        ENDCASE;
    SELECT DiskChannel.SetDriveState[
                instance.drive, instance.changeCount, inactive] FROM
      invalidDrive => RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
      ok => NULL;
      ENDCASE => ERROR;
    END;

  GetAttributes: PUBLIC ENTRY PROCEDURE [pvID: PhysicalVolume.ID, label: STRING]
    RETURNS [instance: Handle, layout: PhysicalVolume.Layout] =
    BEGIN
    drive: DiskChannel.Drive = GetPVDrive[pvID];
    IF drive = DiskChannel.nullDrive THEN
       RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    instance ← [drive, DiskChannel.GetDriveAttributes[drive].changeCount];
    IF GetPhysicalVolumeAttributes[pvID, label].subvolumeCount = 1 THEN
      -- Has the side effect of setting the callers label.  Can not return with found = FALSE. 
      BEGIN
      lvSize: Volume.PageCount;
      svSize: Volume.PageCount;
      [lvSize: lvSize, subVolumeSize: svSize] ← GetSubVolumeAttributes[pvID, 0];
      -- Can not raise its error due to success of GetPhysicalVolumeAttributes above.
      layout ← IF lvSize = svSize THEN singleLogicalVolume ELSE partialLogicalVolume;
      END
    ELSE layout ← multipleLogicalVolumes;
    END;

  GetContainingPhysicalVolume: PUBLIC ENTRY PROCEDURE [lvID: Volume.ID]
    RETURNS [pvID: PhysicalVolume.ID] =
    BEGIN
    -- This is an ENTRY procedure so that the volume containing lvID can not go
    -- away between the time that SubVolume is called and MarkerPage is called
    success: BOOLEAN;
    sv: SubVolume.Handle;
    [success, sv] ← SubVolume.Find[lvID, LogicalVolume.rootPageNumber];
    IF ~success THEN RETURN WITH ERROR Volume.Unknown[lvID];
    RETURN[MarkerPage.Find[[drive[DiskChannel.GetAttributes[sv.channel]]]].physicalID↑]
    END;

  GetHandle: PUBLIC ENTRY PROCEDURE [type: Device.Type, index: CARDINAL]
    RETURNS [Handle] =
    BEGIN
    drive: DiskChannel.Drive;
    IF type = Device.nullType OR index = PhysicalVolume.nullDeviceIndex THEN
      RETURN WITH ERROR PhysicalVolume.Error[noSuchDrive];
    IF (drive ← GetDrive[type, index]) = DiskChannel.nullDrive THEN
      RETURN WITH ERROR PhysicalVolume.Error[noSuchDrive];
    RETURN[[drive, DiskChannel.GetDriveAttributes[drive].changeCount]]
    END;

  GetHints: PUBLIC ENTRY PROCEDURE [instance: Handle, label: STRING]
    RETURNS [pvID: PhysicalVolume.ID, volumeType: PhysicalVolume.VolumeType] =
    BEGIN
    -- This should get smarter about returning information when the volume is partially
    -- trashed.  Also, it should not work by onlining/offlining the volume as this has side
    -- effects (in principle) which this operation should not produce.
    CopyLabel: PROCEDURE [pvLabel: PvHandle] =
      BEGIN
      IF label # NIL THEN
        FOR i: CARDINAL IN [0..(label.length ← MIN[label.maxlength, pvLabel.labelLength])) DO
         label[i] ← pvLabel.label[i];
         ENDLOOP;
      END;
    driveChangeCount: CARDINAL;
    driveState: DiskChannel.DriveState;
    ready: BOOLEAN;
    found: BOOLEAN;
    onlineFound: BOOLEAN;
    IF ~ValidateDrive[instance.drive] THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    [changeCount: driveChangeCount, state: driveState, ready: ready] ←
       DiskChannel.GetDriveAttributes[instance.drive];
    IF ~ready THEN RETURN WITH ERROR PhysicalVolume.Error[notReady];
    IF instance.changeCount ~= driveChangeCount THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    IF driveState = channel THEN GO TO notPilot;
    found ← TRUE;
    pvID ← MarkerPage.Find[[drive[instance.drive]] !
       MarkerPage.NotFound => {found ← FALSE; CONTINUE }].physicalID↑;
    IF ~found THEN
       BEGIN -- temporarily bring the drive online
       -- at this point the drive must be in the inactive state
       SELECT DiskChannel.SetDriveState[instance.drive, instance.changeCount, pilot]
          FROM
          invalidDrive => RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
          ok => NULL;
          ENDCASE => ERROR;
      -- the following should return onlineFound as FALSE since MarkerPage.Find failed!
      [pvID, onlineFound] ← PhysicalVolumeOnLineInternal[instance.drive !
         PhysicalVolume.Error, PhysicalVolume.CanNotScavenge =>
               BEGIN
               [] ← DiskChannel.SetDriveState[instance.drive, 0, inactive];
               GO TO notPilot
               END];
      IF onlineFound THEN ERROR;
      END;
    [] ← PhysicalRootPageAccessInternal[pvID, CopyLabel];
    IF ~found THEN -- undo the temporary online that we did above
       BEGIN
       PhysicalVolumeOffLineInternal[instance.drive];
       [] ← DiskChannel.SetDriveState[instance.drive, 0, inactive];
       END;
    RETURN[pvID, isPilot];
    EXITS notPilot => RETURN[PhysicalVolume.nullID, notPilot]
    END;

  GetNext: PUBLIC PROCEDURE [pvID: PhysicalVolume.ID]
    RETURNS [PhysicalVolume.ID] =
    BEGIN
    RETURN[
      MarkerPage.GetNextPhysicalVolume[pvID !
          MarkerPage.NotFound => GO TO notFound].nextPvID];
    EXITS
    notFound => ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    END;

  GetNextBadPage: PUBLIC PROCEDURE [
    pvID: PhysicalVolume.ID, thisBadPageNumber: PhysicalVolume.PageNumber]
    RETURNS [nextBadPageNumber: PhysicalVolume.PageNumber] =
    BEGIN
    found: BOOLEAN ← thisBadPageNumber = PhysicalVolume.nullBadPage;
    Proc: PROCEDURE [p: PvHandle] =
      BEGIN
      i: CARDINAL; -- ASSUME <= MAX[CARDINAL] bad pages
      FOR i IN [0..Inline.LowHalf[p.badPageCount]) DO
           IF found THEN { nextBadPageNumber ← p.badPageList[i]; RETURN };
           found ← p.badPageList[i] = thisBadPageNumber;
           ENDLOOP;
      nextBadPageNumber ← PhysicalVolume.nullBadPage;
      END;
    PhysicalRootPageAccess[pvID, Proc];
    END;

  GetNextDrive: PUBLIC PROCEDURE [type: Device.Type, index: CARDINAL]
    RETURNS [nextType: Device.Type, nextIndex: CARDINAL] =
    BEGIN
    drive: DiskChannel.Drive ← GetDrive[type, index];
    IF drive = DiskChannel.nullDrive AND
      ~(type = Device.nullType AND index = PhysicalVolume.nullDeviceIndex) THEN
      ERROR PhysicalVolume.Error[noSuchDrive];
    drive ← DiskChannel.GetNextDrive[drive];
    IF drive = DiskChannel.nullDrive THEN
      RETURN[Device.nullType, PhysicalVolume.nullDeviceIndex];
    [deviceType: nextType, deviceOrdinal: nextIndex] ←
      DiskChannel.GetDriveAttributes[drive];
    END;

  GetNextLogicalVolume: PUBLIC ENTRY PROCEDURE [
    pvID: PhysicalVolume.ID, lvID: Volume.ID] RETURNS [Volume.ID] =
    BEGIN
    found: BOOLEAN;
    newLVID: Volume.ID;
    svCount: CARDINAL;
    [found, svCount] ← GetPhysicalVolumeAttributes[pvID, NIL];
    IF ~found THEN RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    IF svCount = 0 THEN RETURN[Volume.nullID];
    IF lvID = Volume.nullID THEN RETURN[GetSubVolumeAttributes[pvID, 0].lvID];
    FOR i: CARDINAL IN [0..svCount) DO
         IF lvID = GetSubVolumeAttributes[pvID, i].lvID THEN
            -- handle special case of a volume with multiple pieces on one phys. vol.
            FOR j: CARDINAL IN [i+1..svCount) DO
                 IF lvID ~= (newLVID ← GetSubVolumeAttributes[pvID, j].lvID) THEN
                    RETURN[newLVID];
                 REPEAT FINISHED => RETURN[Volume.nullID]
                 ENDLOOP;
         ENDLOOP;
    RETURN WITH ERROR PhysicalVolume.Error[noSuchLogicalVolume]
    END;

  InterpretHandle: PUBLIC PROCEDURE [instance: Handle]
    RETURNS [type: Device.Type, index: CARDINAL] =
    BEGIN
    changeCount: CARDINAL;
    IF ~ValidateDrive[instance.drive] THEN
      ERROR PhysicalVolume.Error[invalidHandle];
    [deviceType: type, deviceOrdinal: index, changeCount: changeCount] ←
      DiskChannel.GetDriveAttributes[instance.drive];
    IF instance.changeCount ~= changeCount THEN
      ERROR PhysicalVolume.Error[invalidHandle]
    END;

  IsReady: PUBLIC ENTRY PROCEDURE [instance: Handle] RETURNS [ready: BOOLEAN] =
    BEGIN
    changeCount: CARDINAL;
    IF ~ValidateDrive[instance.drive] THEN
       RETURN WITH ERROR PhysicalVolume.Error[invalidHandle];
    [ready: ready, changeCount: changeCount] ← DiskChannel.GetDriveAttributes[
      instance.drive];
    IF changeCount = instance.changeCount THEN RETURN[ready]
    ELSE RETURN WITH ERROR PhysicalVolume.Error[invalidHandle]
    END;

  MarkPageBad: PUBLIC ENTRY PROCEDURE [
    pvID: PhysicalVolume.ID, badPage: PhysicalVolume.PageNumber] =
    BEGIN
    error: BOOLEAN ← FALSE;
    Proc: PROCEDURE [p: PvHandle] =
      BEGIN -- ASSUME <= MAX[CARDINAL] bad pages
      i: CARDINAL;
      tmp: PhysicalVolume.PageNumber;
      FOR i IN [0..Inline.LowHalf[p.badPageCount]) DO
           IF p.badPageList[i] = badPage THEN RETURN;
           ENDLOOP;
      IF error ← (p.badPageCount >= p.maxBadPages) THEN RETURN;
      FOR i IN [0..Inline.LowHalf[p.badPageCount]) DO
           SELECT p.badPageList[i] FROM
             > badPage =>
               BEGIN
               tmp ← p.badPageList[i];
               p.badPageList[i] ← badPage;
               badPage ← tmp;
               END;
             < badPage => LOOP;
             ENDCASE => ERROR;
            ENDLOOP;
      p.badPageList[Inline.LowHalf[p.badPageCount]] ← badPage;
      p.badPageCount ← p.badPageCount + 1;
      END;
    IF ~PhysicalRootPageAccessInternal[pvID, Proc, readWrite] THEN
      RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    IF error THEN RETURN WITH ERROR PhysicalVolume.Error[badSpotTableFull];
    END;

  Offline: PUBLIC ENTRY PROCEDURE [pvID: PhysicalVolume.ID] =
    BEGIN
    localError: PhysicalVolume.ErrorType;
    BEGIN
    drive: DiskChannel.Drive = GetPVDrive[pvID];
    IF drive = DiskChannel.nullDrive THEN
      RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    PhysicalVolumeOffLineInternal[
      drive ! PhysicalVolume.Error => {localError ← error; GO TO OfflineError}];
    IF DiskChannel.SetDriveState[drive, 0, inactive] ~= ok THEN
      ERROR PhysicalVolumeImplError[impossibleDriveStateChangeFailure];
    EXITS
    OfflineError => RETURN WITH ERROR PhysicalVolume.Error[localError];
    END;
    END;

  --
  -- SpecialVolume

  SubVolumeUnknown: PUBLIC ERROR = CODE;
  GetNextSubVolume: PUBLIC ENTRY PROCEDURE [
    pvID: PhysicalVolume.ID, this: SpecialVolume.SubVolume]
    RETURNS [next: SpecialVolume.SubVolume] =
    BEGIN
    error: BOOLEAN ← FALSE;
    Proc: PROCEDURE [p: PvHandle] =
      BEGIN
      IF this = SpecialVolume.nullSubVolume THEN
         IF p.subVolumeCount = 0 THEN {next ← SpecialVolume.nullSubVolume; RETURN}
         ELSE
             BEGIN OPEN sv: p.subVolumes[0];
             next ← [sv.lvID, sv.nPages, sv.lvPage, sv.pvPage];
             RETURN;
             END;
      FOR i: [0..PhysicalVolumeFormat.maxSubVols) IN [0..p.subVolumeCount) DO
           OPEN sv: p.subVolumes[i];
           IF sv.lvID = this.lvID AND sv.nPages = this.subVolumeSize
               AND sv.lvPage = this.firstLVPageNumber
               AND sv.pvPage = this.firstPVPageNumber THEN
              IF i + 1 >= p.subVolumeCount -- Zero orgin count
                THEN {next ← SpecialVolume.nullSubVolume; RETURN}
              ELSE
                BEGIN OPEN sv: p.subVolumes[i + 1];
                next ← [sv.lvID, sv.nPages, sv.lvPage, sv.pvPage];
                RETURN;
                END;
            ENDLOOP;
      error ← TRUE;
      END;
    IF ~PhysicalRootPageAccessInternal[pvID, Proc] THEN
       RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    IF error THEN RETURN WITH ERROR SpecialVolume.SubVolumeUnknown;
    END;

  GetPhysicalVolumeBootFiles: PUBLIC ENTRY PROCEDURE [
    pvID: PhysicalVolume.ID, pBootFiles: LONG POINTER TO Boot.PVBootFiles] =
    BEGIN
    Copy: PROCEDURE [p:PvHandle] = {pBootFiles↑ ← p.bootingInfo};
    IF ~PhysicalRootPageAccessInternal[pvID, Copy, read] THEN
      RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    END;

  SetPhysicalVolumeBootFiles: PUBLIC ENTRY PROCEDURE [
    pvID: PhysicalVolume.ID, pBootFiles: LONG POINTER TO Boot.PVBootFiles] =
    BEGIN
    Copy: PROCEDURE [p: PvHandle] =
       BEGIN
       p.bootingInfo ← pBootFiles↑;
       SimpleSpace.ForceOut[physicalRootPageBuffer];
       MarkerPage.UpdatePhysicalMarkerPages[p];
       END;
    IF ~PhysicalRootPageAccessInternal[pvID, Copy, readWrite] THEN
      RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    END;

  --
  -- VolumeImplInterface

  AccessPhysicalVolumeRootPage: PUBLIC PROCEDURE [
    id: VolumeImplInterface.BarePvID,
    proc: PROCEDURE [PhysicalVolumeFormat.Handle],
    access: VolumeImplInterface.readOrWrite] =
    { PhysicalRootPageAccess[id, proc, access] };

  --
  --  KernelPhysicalVolume

GetSavedLocalTimeParameters: PUBLIC PROC [pvID: PhysicalVolume.ID]
    RETURNS [valid: BOOLEAN, params: System.LocalTimeParameters] =
  BEGIN
  GetSavedLTP: PROC [h: PhysicalVolumeFormat.Handle] =
    BEGIN
    IF valid←h.localTimeParametersValid THEN params ← h.localTimeParameters;
    END;
  IF pvID=System.nullID THEN
    BEGIN
    IF IsUtilityPilot[] THEN RETURN[valid: FALSE, params: NULL];
    pvID ← GetContainingPhysicalVolume[Volume.systemID];
    END;
  AccessPhysicalVolumeRootPage[id: pvID, proc: GetSavedLTP, access: read];
  END;

SetSavedLocalTimeParameters: PUBLIC PROC [
      params: System.LocalTimeParameters, pvID: PhysicalVolume.ID]
    RETURNS [updated: BOOLEAN] =
  BEGIN
  SetSavedLTP: PROC [h: PhysicalVolumeFormat.Handle] =
    BEGIN
    h.localTimeParameters ← params; h.localTimeParametersValid ← TRUE
    END;
  IF pvID=System.nullID THEN
    BEGIN
    IF PilotSwitches.switches.u=down THEN RETURN[updated: FALSE];
    pvID ← GetContainingPhysicalVolume[Volume.systemID];
    END;
  AccessPhysicalVolumeRootPage[id: pvID, proc: SetSavedLTP, access: readWrite];
  RETURN[updated: TRUE];
  END;

  --
  -- Module private procedures

  DriveSize: PROCEDURE [pvID: PhysicalVolume.ID]
    RETURNS [DiskChannel.DiskPageCount] =
    BEGIN
    RETURN[DiskChannel.GetDriveAttributes[MarkerPage.Find[[
      physicalID[pvID]]].drive].nPages];
    END;

  CheckPhysicalRootLabel: PROCEDURE [
    label: POINTER TO PilotDisk.Label,
    pvID: POINTER TO VolumeImplInterface.BarePvID] RETURNS [BOOLEAN] =
    BEGIN OPEN label;
    pvID↑ ← fileID; -- could also check pad2...
    RETURN[
      fileID # File.nullCapability.fID
      AND PilotDisk.GetLabelFilePage[label] = pvRootPage AND ~immutable
      AND ~temporary AND ~zeroSize AND pad1 = 0
      AND  PilotDisk.GetLabelType[label] = PilotFileTypes.tPhysicalVolumeRootPage];
    END;

  GetDrive: PROCEDURE [type: Device.Type, index: CARDINAL]
    RETURNS [drive: DiskChannel.Drive] =
    BEGIN
    driveType: Device.Type;
    driveIndex: CARDINAL;
    FOR drive ← DiskChannel.GetNextDrive[DiskChannel.nullDrive],
      DiskChannel.GetNextDrive[drive] UNTIL drive = DiskChannel.nullDrive DO
      [driveType, , driveIndex, ] ← DiskChannel.GetDriveAttributes[drive];
      IF driveType = type AND driveIndex = index THEN RETURN
      ENDLOOP;
    RETURN[DiskChannel.nullDrive];
    END;

  GetPhysicalVolumeAttributes: INTERNAL PROCEDURE [
    pvID: PhysicalVolume.ID, name: STRING]
    RETURNS [found: BOOLEAN, subvolumeCount: CARDINAL] =
    BEGIN
    Proc: PROC [p: PvHandle] =
      BEGIN
      i: CARDINAL;
      IF name # NIL THEN
         BEGIN
         name.length ← MIN[name.maxlength, p.labelLength, LENGTH[p.label]];
         FOR i IN [0..name.length) DO name[i] ← p.label[i]; ENDLOOP;
         END;
      subvolumeCount ← p.subVolumeCount;
      END;
    found ← PhysicalRootPageAccessInternal[pvID, Proc]
    END;

  GetPVDrive: PROCEDURE [pvID: PhysicalVolume.ID]
    RETURNS [drive: DiskChannel.Drive] =
    BEGIN
    RETURN[
      MarkerPage.Find[[physicalID[pvID]] !
          MarkerPage.NotFound => GO TO notFound].drive];
    EXITS notFound => RETURN[DiskChannel.nullDrive];
    END;

  GetSubVolumeAttributes: INTERNAL PROCEDURE [
    pvID: PhysicalVolume.ID, subvolumeNumber: CARDINAL]
    RETURNS [
      found: BOOLEAN, lvID: Volume.ID, lvSize: Volume.PageCount,
      subVolumeSize: Volume.PageCount,
      firstLVPageNumber, firstPVPageNumber: PhysicalVolume.PageNumber] =
    BEGIN
    error: BOOLEAN ← TRUE;
    Proc: PROC [p: PvHandle] =
      BEGIN
      IF subvolumeNumber < p.subVolumeCount THEN
   BEGIN OPEN sv: p.subVolumes[subvolumeNumber];
   error ← FALSE;
   lvID ← sv.lvID;
   lvSize ← sv.lvSize;
   subVolumeSize ← sv.nPages;
   firstLVPageNumber ← sv.lvPage;
   firstPVPageNumber ← sv.pvPage;
   END;
      END;
    found ← TRUE;
    IF ~PhysicalRootPageAccessInternal[pvID, Proc] THEN
      ERROR PhysicalVolumeImplError[physicalVolumeNotFound];
    IF error THEN ERROR PhysicalVolumeImplError[invalidSubVolumeNumber];
    END;

  IsUtilityPilot: PROCEDURE RETURNS [BOOLEAN] = INLINE
    BEGIN RETURN[PilotSwitches.switches.u = down]; END;

  PhysicalRootPageAccess: ENTRY PROCEDURE [
    id: VolumeImplInterface.BarePvID, proc: PROCEDURE [PvHandle],
    access: VolumeImplInterface.readOrWrite ← read] =
    BEGIN
    IF ~PhysicalRootPageAccessInternal[id, proc, access] THEN
      RETURN WITH ERROR PhysicalVolume.Error[physicalVolumeUnknown];
    END;

  PhysicalRootPageAccessInternal: INTERNAL PROCEDURE [
    id: VolumeImplInterface.BarePvID, proc: PROCEDURE [PvHandle],
    access: VolumeImplInterface.readOrWrite ← read] RETURNS [found: BOOLEAN] =
    BEGIN
    IF ~SubVolume.Find[[id], pvRootPage].success THEN RETURN[FALSE];
    PhysicalRootPageMap[id, access];
    proc[physicalVolume];
    PhysicalRootPageUnmap[];
    RETURN[TRUE]
    END;

  PhysicalRootPageCheck: INTERNAL PROCEDURE [
    pv: PhysicalVolumeFormat.Handle, id: PhysicalVolume.ID] RETURNS [BOOLEAN] =
    BEGIN
    RETURN[pv.seal = PhysicalVolumeFormat.seal
               AND pv.version = PhysicalVolumeFormat.currentVersion AND pv.pvID = id];
    END;

  PhysicalRootPageMap: INTERNAL PROCEDURE [
    ID: VolumeImplInterface.BarePvID,
    access: VolumeImplInterface.readOrWrite ← read] =
    BEGIN
    per: File.Permissions =
      IF access = readWrite THEN FileInternal.maxPermissions ELSE File.read;
    SimpleSpace.Map[physicalRootPageBuffer, [[[ID], per], pvRootPage], FALSE];
    END;

  PhysicalRootPageUnmap: INTERNAL PROCEDURE = {
    SimpleSpace.Unmap[physicalRootPageBuffer]};

  PhysicalVolumeOffLineInternal: INTERNAL PROCEDURE [drive: DiskChannel.Drive] =
    BEGIN
    -- This procedure assumes that this module will not be called by VolumeImpl when this procedure calls VolumeImpl through VolumeImplInterface.  If this assumption should ever not be true, this procedure must be modified to release the monitor lock before calling into VolumeImpl.
    pMarkerID: POINTER TO READONLY File.ID;
    pvid: VolumeImplInterface.BarePvID;
    pPhysicalID: POINTER TO READONLY PhysicalVolume.ID;
    lv: Volume.ID;
    svH: SubVolume.Handle;


    [, pPhysicalID, pMarkerID] ← MarkerPage.Find[[drive[drive]] !
         MarkerPage.NotFound => GOTO easy];
    pvid ← LOOPHOLE[pPhysicalID↑];
    VolFileMap.Close[TRUE];
    VolAllocMap.Close[TRUE];
    svH ← NIL;
    WHILE (svH ← SubVolume.GetNext[svH]) ~= NIL DO
      -- this loop ensures that there are no open logical volumes on the volume that is to be offlined
      IF DiskChannel.GetAttributes[svH.channel].drive ~= drive
         OR (lv ← svH.lvID) = Volume.ID[pvid] THEN LOOP;
      IF VolumeImplInterface.FindLogicalVolume[@lv] THEN
         IF VolumeImplInterface.GetLVStatus[lv].open THEN
            ERROR PhysicalVolume.Error[containsOpenVolumes];
      ENDLOOP;
    svH ← NIL;
    WHILE (svH ← SubVolume.GetNext[svH]) # NIL DO
      -- This loop gets rid Subvolume's knowledge of the logical volumes that use the disappearing physical volume as well as flushing the volume from VolumeImpl and the FileCache.
      IF DiskChannel.GetAttributes[svH.channel].drive ~= drive
         OR svH.lvID = Volume.ID[pvid] THEN LOOP;
      VolumeImplInterface.SubvolumeOffline[
         svH.lvID, svH.lvPage = FIRST[VolumeInternal.PageNumber]];
      SubVolume.OffLine[svH.lvID, svH.channel];
      ENDLOOP; -- Now it is finally safe to forget about the physical volume
    VolumeImplInterface.PinnedFileFlush[[pvid]];
    MarkerPage.Flush[[drive[drive]]];
    SubVolume.OffLine[[pvid], DiskChannel.nullHandle];
    EXITS easy => RETURN;
    END;

  PhysicalVolumeOnLineInternal: INTERNAL PROCEDURE [drive: DiskChannel.Drive]
    RETURNS [id: PhysicalVolume.ID, alreadyOnline: BOOLEAN] =
    BEGIN
    -- This procedure assumes that this module will not be called by VolumeImpl when this procedure calls VolumeImpl through VolumeImplInterface.  If this assumption should ever not be true, this procedure must be modified to release the monitor lock before calling into VolumeImpl.
    CleanUpDrive: INTERNAL PROCEDURE =
       BEGIN
       PhysicalRootPageUnmap[];
       VolumeImplInterface.PinnedFileFlush[[pvID]];
       MarkerPage.Flush[[drive[drive]]];
       SubVolume.OffLine[[pvID], DiskChannel.nullHandle];
       END;
    found: BOOLEAN ← TRUE;
    dT: Device.Type;
    dO: CARDINAL;
    i: CARDINAL;
    badPageListPage: PhysicalVolumeFormat.PageNumber;
    numPagesForBadPages: PhysicalVolumeFormat.PageNumber;
    label: PilotDisk.Label;
    diskStatus: DiskChannel.CompletionStatus;
    special: CARDINAL ← LAST[CARDINAL];
    pvID: VolumeImplInterface.BarePvID;
    lvID: Volume.ID;
    pvID ← MarkerPage.Find[[drive[drive]] !
        MarkerPage.NotFound => {found ← FALSE; CONTINUE}].physicalID↑;
    IF found THEN RETURN[[pvID], TRUE];
    [label, diskStatus] ← LabelTransfer.ReadRootLabel[drive, pvRootPage];
    SELECT LabelTransfer.DiskStatusToLabelStatus[diskStatus] FROM
       valid => NULL;
       invalid => ERROR PhysicalVolume.CanNotScavenge;
       diskError => ERROR PhysicalVolume.Error[diskReadError];
       ENDCASE => ERROR PhysicalVolumeImplError[impossibleSelectError];
    IF ~CheckPhysicalRootLabel[@label, @pvID] THEN
      ERROR PhysicalVolume.CanNotScavenge;
    RegisterPvInfo[pvID, drive];
    PhysicalRootPageMap[pvID];
    IF ~PhysicalRootPageCheck[physicalVolume, [pvID]] THEN
      BEGIN
      CleanUpDrive[];
      ERROR PhysicalVolume.CanNotScavenge;
      END;
    -- Now check to see that the labels on the bad page list page(s) are correct
    numPagesForBadPages ← (physicalVolume.maxBadPages+Environment.wordsPerPage-1)/
                                  Environment.wordsPerPage;
    -- The following statement blows up the compiler
    -- FOR badPageListPage IN [pvRootPage+1..pvRootPage+numPagesForBadPages] DO
    FOR badPageListPage ← pvRootPage+1, badPageListPage+1
          WHILE badPageListPage <= pvRootPage+numPagesForBadPages DO
       [label, diskStatus] ← LabelTransfer.ReadRootLabel[drive, badPageListPage];
       SELECT LabelTransfer.DiskStatusToLabelStatus[diskStatus] FROM
          valid => NULL;
          invalid => { CleanUpDrive[]; ERROR PhysicalVolume.CanNotScavenge };
          diskError => { CleanUpDrive[]; ERROR PhysicalVolume.Error[diskReadError] };
          ENDCASE => ERROR PhysicalVolumeImplError[impossibleSelectError];
       ENDLOOP;
    RegisterSubvolumeMarker[physicalVolume];
    -- if we were booted from this volume, specials
    -- First make all of the subvolumes accessible to the VM machinery and discover if this is the bootload volume.
    FOR i IN [0..physicalVolume.subVolumeCount) DO
      OPEN sv: physicalVolume.subVolumes[i];
      VolumeImplInterface.RegisterLogicalSubvolume[sv, [pvID]];
      lvID ← sv.lvID;
      [deviceType: dT, deviceOrdinal: dO] ← DiskChannel.GetDriveAttributes[drive];
      IF debugSearchState = tooSoonToLook AND bootFile.deviceType = dT
         AND bootFile.deviceOrdinal = dO
         AND DiskChannel.GetPageNumber[drive, LOOPHOLE[bootFile.diskFileID.da]] IN
               [sv.pvPage..sv.pvPage + sv.nPages)
         THEN special ← i;
      ENDLOOP;
    IF special ~= LAST[CARDINAL] THEN -- Bring the system volume online
      BEGIN OPEN sv: physicalVolume.subVolumes[special];
      VolumeImplInterface.SubvolumeOnline[
           sv.lvID, sv.lvPage = FIRST[VolumeInternal.PageNumber]];
      VolumeImplInterface.CheckLogicalVolume[sv.lvID];
      END;
    FOR i IN [0..physicalVolume.subVolumeCount) DO
      -- Bring all other volumes online
      IF i ~= special THEN
         BEGIN OPEN sv: physicalVolume.subVolumes[i];
         VolumeImplInterface.SubvolumeOnline[
           sv.lvID, sv.lvPage = FIRST[VolumeInternal.PageNumber]];
         VolumeImplInterface.CheckLogicalVolume[sv.lvID];
         END;
      ENDLOOP;
    PhysicalRootPageUnmap[];
    RETURN[[pvID], FALSE]
    END;

  RegisterPvInfo: PUBLIC PROCEDURE [
    pvID: VolumeImplInterface.BarePvID, drive: DiskChannel.Drive] =
    BEGIN
    driveSize: LONG CARDINAL ← DiskChannel.GetDriveAttributes[drive].nPages;
    DiskChannel.SetDriveTag[drive, PhysicalVolumeFormat.IDCheckSum[[pvID]]];
    IF ~SubVolume.Find[[pvID], pvRootPage].success THEN
      -- Create a subvolume covering the drive so we can find PVDescriptor and Marker Pages
      SubVolume.OnLine[
          [[pvID], driveSize, pvRootPage, pvRootPage, driveSize],
          DiskChannel.Create[drive, SubVolume.completion]];
    -- Create a VFile for just the root page
    VolumeImplInterface.VFileEnter[
      [pvID], [pvID], pvRootPage, pvRootPage+rootPagePages,
      PilotFileTypes.tPhysicalVolumeRootPage];
    MarkerPage.Enter[drive, [pvID]];
    END;

  -- Read the ID off the disk, or if there are no subvolumes (yet) generate one.

  RegisterSubvolumeMarker: PUBLIC PROCEDURE [pv: PvHandle] =
    BEGIN
    drive: DiskChannel.Drive = MarkerPage.Find[[physicalID[pv.pvID]]].drive;
    driveSize: LONG CARDINAL = DiskChannel.GetDriveAttributes[drive].nPages;
    id: File.ID;
    page: PhysicalVolumeFormat.PageNumber;
    IF pv.subVolumeCount # 0 THEN
      BEGIN
      page ← pv.subVolumes[0].pvPage + pv.subVolumes[0].nPages;
      -- We should really check the label here...
      id ← LabelTransfer.ReadRootLabel[drive, page].label.fileID;
      END
    ELSE id ← [System.GetUniversalID[]]; -- creating a physical volume
    MarkerPage.EnterMarkerID[[drive[drive]], id];
    -- The marker pages cover the disk
    VolumeImplInterface.VFileEnter[
      LOOPHOLE[pv.pvID], id, 0, driveSize, PilotFileTypes.tSubVolumeMarkerPage];
    END;

  ValidateDrive: PROCEDURE [drive: DiskChannel.Drive] RETURNS [found: BOOLEAN] =
    BEGIN
    FOR existingDrive: DiskChannel.Drive ←
          DiskChannel.GetNextDrive[DiskChannel.nullDrive],
          DiskChannel.GetNextDrive[existingDrive]
          UNTIL existingDrive = DiskChannel.nullDrive DO
      IF existingDrive = drive THEN RETURN[TRUE];
      ENDLOOP;
    RETURN[FALSE];
    END;

  --
  --  Initialization

  InitDisks: ENTRY PROCEDURE =
    BEGIN OPEN DiskChannel;
    dT: Device.Type;
    dO: CARDINAL;
    drive, systemDrive: Drive ← nullDrive;
    volumeID: Volume.ID ← Volume.nullID;
    WHILE (systemDrive ← GetNextDrive[systemDrive]) # nullDrive DO
      [deviceType: dT, deviceOrdinal: dO] ← GetDriveAttributes[systemDrive];
      IF dT = bootFile.deviceType AND dO = bootFile.deviceOrdinal THEN EXIT;
      ENDLOOP;
    IF systemDrive = nullDrive THEN
      Runtime.CallDebugger["System Drive not found"L];
    IF DiskChannel.SetDriveState[
      systemDrive, DiskChannel.GetDriveAttributes[systemDrive].changeCount, pilot]
      ~= ok THEN
      Runtime.CallDebugger["Could not set SystemDrive state to Pilot"L];
    [] ← PhysicalVolumeOnLineInternal[systemDrive !
        PhysicalVolume.Error =>
            IF error = diskReadError THEN
               BEGIN ProcessorFace.SetMP[PilotMP.cDriveNotReady]; RETRY; END
            ELSE CONTINUE];
    IF Volume.systemID = Volume.nullID THEN
      Runtime.CallDebugger["No Logical Volumes on System Drive"L];
    IF PilotSwitches.switches.z = down THEN
      WHILE (drive ← DiskChannel.GetNextDrive[drive]) # nullDrive DO
           [deviceType: dT, deviceOrdinal: dO] ← GetDriveAttributes[drive];
           IF drive # systemDrive THEN
             BEGIN
             IF DiskChannel.SetDriveState[
               drive, DiskChannel.GetDriveAttributes[drive].changeCount, pilot] ~= ok
               THEN Runtime.CallDebugger["Could not set SystemDrive state to Pilot"L];
             [] ← PhysicalVolumeOnLineInternal[drive !
                    PhysicalVolume.Error =>
                        IF error = diskReadError THEN
                           BEGIN ProcessorFace.SetMP[PilotMP.cDriveNotReady]; RETRY; END
                        ELSE CONTINUE];
             END
       ENDLOOP;
    ProcessorFace.SetMP[PilotMP.cDeleteTemps];
    VolumeImplInterface.OpenInitialVolumes[];
    END;

  START FMPrograms.ScavengeImpl;
  START FMPrograms.VolumeImpl[
    bootFile, pLVBootFiles, @debuggerDeviceType, @debuggerDeviceOrdinal];
  debuggerDeviceType ← Device.nullType;
  -- If we are utilityPilot, the person who installed us smashed in our debugger pointers
  IF IsUtilityPilot[] THEN debugClass ← normal ELSE InitDisks[];
  debugSearchState ← done; -- We will never ever set them from here on....
  RETURN;
  END.

(For earlier log entries see Pilot 5.0 archive version.)

January 13, 1981  11:58 AM	Luniewski
	New LabelTransfer interface
	
January 23, 1981  4:23 PM	McJones
	LocalTimeParameters

January 30, 1981  12:15 PM	McJones
	SystemExtras=>System

February 6, 1981  10:59 AM	Luniewski
	Typo in GetSavedLTP

20-Mar-81 12:15:13		Gobbel
	Set subVolumeMarkerID in PhysVol root page on CreatePhysVol, make GetHints
	do the right thing if given NIL string.

March 24, 1981  4:36 PM	Jose
	Don't write subVolumeMarkerID during CreatePhysVol.