-- ScavengeImplExtras.mesa   (edited 28-Oct-81 18:24:02 by Fay)

DIRECTORY
  Environment USING [wordsPerPage],
  File USING [Capability, Error, GetAttributes, read, SetSize, shrink,
    Unknown, write],
  Scavenger USING [Error, ErrorType, FileEntry, Header, Problem, ReadBadPage,
    RewritePage, Scavenge],
  Space USING [Create, defaultWindow, GetWindow, Handle, LongPointer, Map,
    PageNumber, Unmap, virtualMemory, VMPageNumber, WindowOrigin],
  Transaction USING [nullHandle],
  Volume USING [Close, ID, Open, Unknown];

ScavengeImplExtras: MONITOR
  IMPORTS File, Scavenger, Space, Transaction, Volume
  -- Transaction is implicitly imported because of Space, but is explicitly
  -- listed in the IMPORTS to allow positional notation to specify the
  -- imports of ScavengeImplExtras in an enclosing configuration (i.e. to
  -- allow binder magic).
  EXPORTS Scavenger
  SHARES File =

  BEGIN

  -- Global spaces (create them only once to avoid running out of region
  -- cache in UtilityPilot)
  bufferSpace: Space.Handle = Space.Create[1, Space.virtualMemory];
  pilotLogSpace: Space.Handle = Space.Create[pilotLogSpaceSize,
      Space.virtualMemory];
  pilotLogSpaceSize: CARDINAL = 1;

  -- debugging stuff
  BugType: TYPE = {impossibleSelectError, pilotLogFileUnknown};
  Bug: ERROR [BugType] = CODE;

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Scavenger implementation (exported procedure)
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  Scavenge: PUBLIC ENTRY PROC [volume, logDestination: Volume.ID,
    repair: BOOLEAN] RETURNS [logFile: File.Capability] =
    -- Does a regular logical volume scavenge and then takes care of any
    -- problems in temporary files.
    -- Note: this must be called from a UtilityPilot client ONLY.  If it is
    -- called from a Pilot client, and there are unreadable or missing pages
    -- in temporary files, we will crash on the automatic temporary file
    -- deletion attempted during Volume.Open.  This would defeat the whole
    -- purpose of this special version of the scavenger.
    BEGIN ENABLE UNWIND => NULL;  -- for Bug or errors from FixTempFiles
    theError: Scavenger.ErrorType;
    BEGIN
    holeFound: BOOLEAN ← TRUE;  -- needed for Rubicon workaround for
        -- missing pages.  We have to scavenge again after truncating files
	-- with missing pages in order to clean up the VFM.  If n is the
	-- number of holes in the file with the most holes, we will have to
	-- call the scavenger n + 1 times to get rid of the holes, since we
	-- can only truncate down to the last hole each time.  Ugh!
    WHILE holeFound DO
      logFile ← Scavenger.Scavenge[volume: volume,
        logDestination: logDestination, repair: repair !
	  Scavenger.Error => {theError ← error; GOTO ScavengerError}];
      -- repair must always be TRUE in Rubicon, so we can always fix
      -- temporary files.  Scavenger.Scavenge will catch the repair=FALSE
      -- error for us.
      Volume.Open[volume];
      holeFound ← FixTempFiles[volume, logFile];
      Volume.Close[volume];
      ENDLOOP;
    EXITS
      ScavengerError => RETURN WITH ERROR Scavenger.Error[theError];
    END;  -- ScavengerError scope
    END;  -- Scavenge

  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  -- Internal procedures
  --~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

  Backup: PUBLIC PROC [bufferPointer: LONG POINTER TO UNSPECIFIED,
    currentWord, count: CARDINAL] RETURNS [nextWord: CARDINAL] =
    -- Backs up count words in the Pilot scavenger log.
    BEGIN
    pilotLogWindow: Space.WindowOrigin;
    THROUGH [0..count) DO
      IF currentWord = 0 THEN
        {pilotLogWindow ← Space.GetWindow[pilotLogSpace];
        pilotLogWindow.base ← pilotLogWindow.base - pilotLogSpaceSize;
        currentWord ← (Environment.wordsPerPage*pilotLogSpaceSize) - 1;
        Space.Unmap[pilotLogSpace];
        Space.Map[pilotLogSpace, pilotLogWindow]}
      ELSE currentWord ← currentWord - 1;
      ENDLOOP;
    nextWord ← currentWord;
    END;  -- Backup

  ClosePilotLogFile: PROC =
    BEGIN
    Space.Unmap[pilotLogSpace];
    END;  -- ClosePilotLogFile

  FixOneProblem: PROC [
    fileEntry: POINTER TO Scavenger.FileEntry,
    problem: POINTER TO Scavenger.Problem]
    RETURNS [holeFound: BOOLEAN] =
    -- Fixes one file problem reported in a Problem entry in the Pilot
    -- scavenger log.  (Note that MakePage0Readable has already fixed any
    -- unreadable page group which starts with page 0, so those are skipped
    -- over here.)
    BEGIN
    WITH problem↑ SELECT FROM
      missing =>
        {holeFound ← TRUE;
        MissingPages[fileEntry, problem]};
      unreadable =>
        {holeFound ← FALSE;
        IF first # 0 THEN UnreadablePages[fileEntry, problem]};
      ENDCASE => ERROR Bug[impossibleSelectError];
        -- duplicate page detection is not implemented in Pilot 6.0.
	-- orphan pages have no fileID, so we shouldn't get here with one.
    END;  -- FixOneProblem

  FixProblems: PROC [currentProblem: CARDINAL,
    fileEntry: POINTER TO Scavenger.FileEntry,
    pilotLogPointer: LONG POINTER TO UNSPECIFIED, currentWord: CARDINAL,
    holeAlreadyFound: BOOLEAN]
    RETURNS [nextWord: CARDINAL, holeFound: BOOLEAN] =
    -- Fixes no more than one missing page and all other Problems for one
    -- file.  Uses recursion to allow it to deal with the last missing page
    -- first, due to the algorithm used (truncation of the file).  It also
    -- makes sure that all problems other than missing pages are fixed before
    -- fixing a missing page to avoid tripping over them when trying to
    -- truncate the file.  Depends on missing pages being reported in order
    -- from first to last.
    BEGIN
    lastProblem: BOOLEAN = currentProblem=fileEntry.numberOfProblems;
    problem: Scavenger.Problem;
    nextWord ← GetWords[@problem, pilotLogPointer, currentWord,
        SIZE[Scavenger.Problem]];
    IF problem.entryType # missing OR lastProblem THEN
      {holeFound ← FixOneProblem[fileEntry, @problem] OR holeAlreadyFound;
      IF ~lastProblem THEN
	[nextWord, holeFound] ← FixProblems[currentProblem + 1, fileEntry,
	    pilotLogPointer, nextWord, holeFound]}
    ELSE  -- this is a missing page but not the last problem, so process
        -- all other problems first
      {[nextWord, holeFound] ← FixProblems[currentProblem + 1, fileEntry,
          pilotLogPointer, nextWord, holeAlreadyFound];
      -- now fix this missing page if there were no following missing pages
      IF ~holeFound THEN
        holeFound ← FixOneProblem[fileEntry, @problem]};
    END;  -- FixProblems

  FixTempFiles: PUBLIC PROC [volume: Volume.ID, logFile: File.Capability]
    RETURNS [holeFound: BOOLEAN] =
    -- Scans the Pilot Scavenger log for Problem entries, and repairs any
    -- damaged temporary files.
    BEGIN
    newHoleFound: BOOLEAN;
    fileEntry: Scavenger.FileEntry;
    nextWord: CARDINAL ← SIZE[Scavenger.Header];
    numberOfFiles: LONG CARDINAL;
    pilotLogPointer: LONG POINTER TO UNSPECIFIED;
    holeFound ← FALSE;
    pilotLogPointer ← OpenPilotLogFile[logFile];
    numberOfFiles ← LOOPHOLE[
        pilotLogPointer, LONG POINTER TO Scavenger.Header].numberOfFiles;
    FOR counter: LONG CARDINAL ← 1, counter + 1
        WHILE counter <= numberOfFiles DO
      nextWord ← GetWords[@fileEntry, pilotLogPointer, nextWord,
          SIZE[Scavenger.FileEntry]];
      IF fileEntry.numberOfProblems # 0 THEN
        {[nextWord, newHoleFound] ← ProcessProblems[@fileEntry,
	    pilotLogPointer, nextWord !
	  Scavenger.Error, File.Error, File.Unknown, Volume.Unknown =>
	    {ClosePilotLogFile[]; REJECT}];
	holeFound ← holeFound OR newHoleFound};  -- must be cumulative
      ENDLOOP;
    ClosePilotLogFile[];
    END;  -- FixTempFiles

  GetWords: PUBLIC PROC [
    toPointer, bufferPointer: LONG POINTER TO UNSPECIFIED,
    currentWord, count: CARDINAL] RETURNS [nextWord: CARDINAL] =
    -- Gets the next count words from the Pilot scavenger log.
    BEGIN
    pilotLogWindow: Space.WindowOrigin;
    THROUGH [0..count) DO
      IF currentWord >= (Environment.wordsPerPage*pilotLogSpaceSize) THEN
        {pilotLogWindow ← Space.GetWindow[pilotLogSpace];
        pilotLogWindow.base ← pilotLogWindow.base + pilotLogSpaceSize;
        currentWord ← 0;
        Space.Unmap[pilotLogSpace];
        Space.Map[pilotLogSpace, pilotLogWindow]};
      toPointer↑ ← (bufferPointer + currentWord)↑;
      toPointer ← toPointer + 1;
      currentWord ← currentWord + 1;
      ENDLOOP;
    nextWord ← currentWord;
    END;  -- GetWords

  MakePage0Readable: PROC [fileEntry: POINTER TO Scavenger.FileEntry,
    pilotLogPointer: LONG POINTER TO UNSPECIFIED, currentWord: CARDINAL] =
    BEGIN
    problem: Scavenger.Problem;
    -- scan through this file's problems to see if page 0 is unreadable and
    -- fix it if so.
    THROUGH [0..fileEntry.numberOfProblems) DO
      currentWord ← GetWords[@problem, pilotLogPointer, currentWord,
        SIZE[Scavenger.Problem]];
      WITH problem SELECT FROM
        missing => NULL;
	orphan => NULL;
	unreadable =>
	  IF first = 0 THEN UnreadablePages[fileEntry, @problem];
	ENDCASE => ERROR Bug[impossibleSelectError];
      ENDLOOP;
    -- now backup the log file "reader" so the problems can be read again
    THROUGH [0..fileEntry.numberOfProblems) DO
      currentWord ← Backup[pilotLogPointer, currentWord,
          SIZE[Scavenger.Problem]];
      ENDLOOP;
    END;  -- MakePage0Readable

  MissingPages: PROC [fileEntry: POINTER TO Scavenger.FileEntry,
    problem: POINTER TO Scavenger.Problem] =
    BEGIN
    -- Takes care of one missing Problem entry from the Pilot scavenger log.
    -- Truncates the file to n + 1 pages long assuming the last page of the
    -- hole is at page n.  (We can't just fill in the hole with a new page,
    -- because of a Rubicon VFM bug.  Replacing a page missing in the middle
    -- of a page group with another page causes an invalid VFM to be built.
    -- The workaround is to truncate the file so that the last page is the
    -- missing page, then close the volume and scavenge again.  This causes
    -- the VFM to be rebuilt.  Since there are now no file pages after the
    -- missing page, the missing page just falls off the end and disappears
    -- when we rebuild the VFM.  Repeat this process until all the holes
    -- have disappeared, and then the file no longer contains any holes and
    -- can be safely deleted.)
    WITH problem↑ SELECT FROM
      missing =>
        File.SetSize[[fileEntry.file, File.write + File.shrink],
	    first + count];
	    -- let FixTempFiles catch any errors from SetSize
      ENDCASE => ERROR Bug[impossibleSelectError];
    END;  -- MissingPages

  OpenPilotLogFile: PUBLIC PROC [logFile: File.Capability]
    RETURNS [bufferPointer: LONG POINTER TO UNSPECIFIED] =
    -- Maps the Pilot scavenger log into a space and returns a pointer to the
    -- header information.
    BEGIN
    Space.Map[
      pilotLogSpace, [logFile, 0] !
      File.Unknown, Volume.Unknown =>
        ERROR Bug[pilotLogFileUnknown]];
    bufferPointer ← Space.LongPointer[pilotLogSpace];
    END;  -- OpenPilotLogFile

  ProcessProblems: PROC [fileEntry: POINTER TO Scavenger.FileEntry,
    pilotLogPointer: LONG POINTER TO UNSPECIFIED, currentWord: CARDINAL]
    RETURNS [nextWord: CARDINAL, holeFound: BOOLEAN] =
    -- Either fixes problems or skips over Problem entries in log, depending
    -- on whether the file is known and temporary or not.  Will also fix page
    -- 0 in any file in which it is unreadable.  (If page 0 of a file is
    -- unreadable, File.GetAttributes gets an unrecoverable disk error, so we
    -- cannot call GetAttributes in this case.  Thus we are unable to
    -- determine if the file is temporary or not.  Page 0 must be fixed
    -- first so that the File.GetAttributes works.  It also insures that
    -- DeleteTempsInternalOld and the client scavenger won't trip over the
    -- unreadable page.  If page 0 is missing, File.GetAttributes raises
    -- File.Unknown, and we will just skip the file.)
    BEGIN
    knownAndTemporary: BOOLEAN ← FALSE;
    holeFound ← FALSE;
    MakePage0Readable[fileEntry, pilotLogPointer, currentWord];
    [temporary: knownAndTemporary] ←
        File.GetAttributes[[fileEntry.file, File.read] !
      File.Unknown, Volume.Unknown =>
	{knownAndTemporary ← FALSE; CONTINUE}];
    IF knownAndTemporary THEN
      [nextWord, holeFound] ← FixProblems[1, fileEntry, pilotLogPointer,
          currentWord, holeFound]
    ELSE  -- just skip over the Problem entries to get to the next FileEntry
      {problem: Scavenger.Problem;
      nextWord ← currentWord;
      THROUGH [0..fileEntry.numberOfProblems) DO
        nextWord ← GetWords[
	    @problem, pilotLogPointer, nextWord, SIZE[Scavenger.Problem]];
	ENDLOOP};
    END;  -- ProcessProblems

  UnreadablePages: PROC [fileEntry: POINTER TO Scavenger.FileEntry,
    problem: POINTER TO Scavenger.Problem] =
    -- Takes care of one unreadable Problem entry from the Pilot scavenger
    -- log.  Tries to read the page and then rewrites the page with whatever
    -- the read produces, if anything.  Getting the contents right is
    -- less important than clearing the CRC error, because the chief goal is
    -- to make the file deletable.  If the first unreadable page is page 0 of
    -- the file, it is not guaranteed that the file exists, since we are
    -- unable to call File.GetAttributes in this case.  Thus File.Unknown is
    -- treated differently (not as an error) if page 0 is unreadable.
    BEGIN
    Space.Map[bufferSpace, Space.defaultWindow];
    WITH problem↑ SELECT FROM
      unreadable =>
	FOR i: LONG CARDINAL ← 0, i + 1 WHILE i < count DO
	  Scavenger.ReadBadPage[fileEntry.file, first + i,
	      Space.VMPageNumber[bufferSpace] !
	    File.Unknown => IF first = 0 THEN EXIT ELSE CONTINUE;
	    Scavenger.Error => CONTINUE];
          Scavenger.RewritePage[fileEntry.file, first + i,
	      Space.VMPageNumber[bufferSpace] !
	    Scavenger.Error, File.Unknown, File.Error =>
	      {Space.Unmap[bufferSpace]; REJECT}];
          ENDLOOP;
      ENDCASE => ERROR Bug[impossibleSelectError];
    Space.Unmap[bufferSpace];
    END;  -- UnreadablePages

  END.


LOG

28-Oct-81 18:23:57   Fay   Created file.