DIRECTORY
BootFile USING[ Location ],
Disk USING[ Add, Channel, defaultTries, DoIO, DriveAttributes, GetBootChainLink, GetDeviceFromChannel, invalid, Label, labelCheck, ok, PageNumber, PageCount, Request, SameDrive, Status ],
DiskFace USING[ DiskAddress, DontCare, GetTrueDeviceAttributes, wordsPerPage ],
File USING[ Error, FP, nullDA, nullFP, PageCount, PageNumber, PagesForWords, PropertyStorage, RC, Reason, SystemVolume, Volume, VolumeFile ],
FileBackdoor USING[ GetVolumePages, IsDebugger],
FileInternal,
FileStats USING[ Data, Type, Pulses ],
PhysicalVolume USING [Physical, SubVolumeDetails],
PrincOpsUtils USING[ LongCopy ],
Process USING [GetPriority, Pause, Priority, priorityForeground, priorityNormal, SetPriority],
ProcessorFace USING[ GetClockPulses ],
VolumeFormat USING[ AbsID, allocatedBadPages, Attributes, lastLogicalRun, LogicalPage, LogicalPageCount, LogicalRun, LogicalRunObject, RelID, RunPageCount ],
VM USING[ AddressForPageNumber, Allocate, Free, Interval, PageCount, PageNumber, PageNumberForAddress, PagesForWords, SwapIn, Unpin, wordsPerPage],
VMBacking USING[ AttachBackingStorage, Run, RunTableIndex, RunTableObject, RunTablePageNumber ];
--DiskFace.--Attributes: PUBLIC TYPE = VolumeFormat.Attributes;
--DiskFace.--AbsID: PUBLIC TYPE = VolumeFormat.AbsID;
--DiskFace.--RelID: PUBLIC TYPE = VolumeFormat.RelID;
--File.--DA: PUBLIC TYPE = VolumeFormat.LogicalPage;
Handle: TYPE = REF Object;
--File.--Object: PUBLIC TYPE = FileInternal.Object;
Volume: TYPE = REF VolumeObject;
--File.--VolumeObject: PUBLIC TYPE = FileInternal.VolumeObject;
RunTable: TYPE = FileInternal.RunTable;
RunTableObject: TYPE = VMBacking.RunTableObject;
RunTableIndex: TYPE = VMBacking.RunTableIndex;
PhysicalRun: TYPE = FileInternal.PhysicalRun;
lastRun: VMBacking.RunTablePageNumber = LAST[INT]; -- end marker in runTable --
initRuns: CARDINAL = HeaderPagesToRuns[1];
normalHeaderSize: CARDINAL = 2;
GetHeaderVM:
PUBLIC
PROC [file: Handle, runs:
CARDINAL, propertyPages:
CARDINAL ← 1 ] =
TRUSTED {
oldVM: LONG POINTER = file.headerVM;
oldHeaderVMPages: INT = file.headerVMPages;
oldProperties: File.PropertyStorage = file.properties;
oldLogical: LONG POINTER TO VolumeFormat.LogicalRunObject = file.logicalRunTable;
runTableWords: INT = SIZE[VolumeFormat.LogicalRunObject[runs]];
runTablePages: INT = VM.PagesForWords[runTableWords];
vmPages: INT = VM.PagesForWords[runTableWords] + propertyPages;
runTableFilePages: File.PageCount = File.PagesForWords[runTableWords];
interval: VM.Interval ← VM.Allocate[vmPages];
VM.SwapIn[interval];
Avoids page faults, which would take longer to handle but have the same effect.
file.headerVM ← VM.AddressForPageNumber[interval.page];
file.headerVMPages ← vmPages; -- assign only after VM.Allocate succeeds
file.properties ← LOOPHOLE[file.headerVM+runTableFilePages*DiskFace.wordsPerPage];
file.logicalRunTable ← LOOPHOLE[file.headerVM];
file.logicalRunTable.headerPages ← runTableFilePages + propertyPages;
file.logicalRunTable.maxRuns ← runs;
IF oldVM =
NIL
THEN {
initialise only
temp: LONG POINTER TO ARRAY [0..DiskFace.wordsPerPage) OF WORD;
file.logicalRunTable[0].first ← VolumeFormat.lastLogicalRun;
temp ← LOOPHOLE[file.properties];
temp^ ← ALL[0];
}
ELSE {
initialise from old tables
runWords: CARDINAL = oldProperties-oldVM;
propertyWords: LONG CARDINAL = MAX[0, VM.wordsPerPage*oldHeaderVMPages - runWords];
PrincOpsUtils.LongCopy[from: oldLogical, to: file.logicalRunTable,
nwords: runWords];
PrincOpsUtils.LongCopy[from: oldLogical+ runWords, to: file.properties,
nwords: propertyWords];
VM.Free[[VM.PageNumberForAddress[oldVM], oldHeaderVMPages]];
};
file.runPages ← runTablePages;
file.propertyPages ← propertyPages;
};
FreeHeaderVM:
PUBLIC
PROC [file: Handle] =
TRUSTED {
exported to FileInternal
IF file.headerVMPages # 0
THEN
VM.Free[[VM.PageNumberForAddress[file.headerVM], file.headerVMPages]];
file.headerVMPages ← 0;
file.headerVM ← NIL;
file.logicalRunTable ← NIL;
file.properties ← NIL
};
TranslateLogicalRunTable:
PUBLIC
PROC [file: Handle, prefixOnly:
BOOL ←
FALSE]
RETURNS [ File.PageCount ] =
TRUSTED {
exported to FileInternal
nRuns: CARDINAL;
filePage: File.PageNumber ← [-file.logicalRunTable.headerPages];
FOR nRuns
IN [0..file.logicalRunTable.maxRuns)
DO
IF file.logicalRunTable[nRuns].first = VolumeFormat.lastLogicalRun THEN EXIT;
REPEAT FINISHED => IF ~prefixOnly THEN ERROR File.Error[inconsistent]
ENDLOOP;
IF file.runTable = NIL OR file.runTable.length < nRuns+10--arbitrary--
THEN file.runTable ← NEW[RunTableObject[nRuns+10]];
file.runTable.nRuns ← nRuns;
FOR i:
CARDINAL
IN [0..nRuns)
DO
IF file.logicalRunTable[i].first = VolumeFormat.lastLogicalRun THEN EXIT;
[channel: file.runTable[i].channel, diskPage: file.runTable[i].diskPage] ←
FileInternal.TranslateLogicalRun[file.logicalRunTable[i], file.volume];
file.runTable[i].filePage ← filePage;
filePage ← [filePage + file.logicalRunTable[i].size];
ENDLOOP;
file.runTable.nDataPages ← filePage;
file.runTable[file.runTable.nRuns].filePage ← lastRun;
RETURN[ file.runTable.nDataPages ]
};
SetPropertiesSize:
PUBLIC
PROC [file: Handle, nPages: File.PageCount] =
TRUSTED {
exported to File
runPages: CARDINAL ← file.runPages;
IF file.runTable.nRuns+3 >= file.logicalRunTable.maxRuns THEN runPages ← runPages + 1;
ExtendFileHeader[file: file, newRunPages: runPages, newPropertyPages: nPages];
FileInternal.WriteRunTable[file];
};
ExtendFileHeader:
PUBLIC
PROC [file: Handle, newRunPages:
CARDINAL, newPropertyPages:
CARDINAL] =
TRUSTED {
exported to FileInternal
newMaxRuns: CARDINAL = HeaderPagesToRuns[newRunPages];
GetHeaderVM[file: file, runs: newMaxRuns, propertyPages: newPropertyPages ];
file.logicalRunTable.maxRuns ← newMaxRuns;
file.logicalRunTable.headerPages ← newRunPages + newPropertyPages;
};
LastLogicalPage:
PUBLIC
PROC [file: Handle]
RETURNS [VolumeFormat.LogicalPage] =
TRUSTED {
exported to FileInternal
Assumes file.runTable.nRuns > 0
lastRun: VolumeFormat.LogicalRun = file.logicalRunTable[file.runTable.nRuns-1];
RETURN[ [lastRun.first + lastRun.size-1] ]
};
******** Some Subroutines for access to file pages. Others in FilePagesImpl ********
UnstableRunTable:
PROC [file: Handle, newSize: File.PageCount] =
TRUSTED {
file.logicalRunTable.intention ← [unstable: TRUE, size: newSize];
FileInternal.Transfer[file: file, data: file.headerVM, filePage: [0], nPages: 1, action: write, where: header];
};
StableRunTable:
PROC [file: Handle] =
TRUSTED {
file.logicalRunTable.intention ← [unstable: FALSE];
FileInternal.Transfer[file: file, data: file.headerVM, filePage: [0], nPages: 1, action: write, where: header];
};
MakeBootable:
PROC [file: Handle, firstPage: File.PageNumber]
RETURNS [id: RelID, firstLink: DiskFace.DontCare, channel: Disk.Channel] = {
eof: DiskFace.DontCare = LOOPHOLE[LONG[-1]]; -- bit-pattern known by microcode
data: LONG POINTER;
label: Disk.Label ← FileInternal.DataLabel[file.fp];
req: Disk.Request;
filePage: File.PageNumber ← firstPage;
thisDiskPage: Disk.PageNumber;
WriteLink:
PROC [link: DiskFace.DontCare] = {
Write boot-chain link at "thisDiskPage" for current "filePage"
status: Disk.Status;
countDone: Disk.PageCount;
label.filePage ← filePage-1;
req ← [
diskPage: thisDiskPage,
data: data,
incrementDataPtr: TRUE,
command: [header: verify, label: verify, data: read],
count: 1 ];
TRUSTED{[status, countDone] ← DoPinnedIO[channel, @label, @req]}; -- get data
CheckStatus[status, thisDiskPage+countDone]; -- use thisDiskPage instead of req.diskPage since DiskImpl modifies req.diskPage
label.dontCare ← link;
label.filePage ← filePage-1; -- previous transfer incremented it
TRUSTED{[status, countDone] ← FileInternal.WriteLabels[channel, thisDiskPage, 1, data, @label]};
CheckStatus[status, thisDiskPage+countDone];
};
thisSize: Disk.PageCount;
IF file.size <= firstPage THEN ERROR File.Error[unknownPage, firstPage];
[diskPage: thisDiskPage, size: thisSize, channel: channel] ←
FileInternal.FindRun[start: filePage, nPages: file.size-filePage, runTable: file.runTable];
firstLink ← Disk.GetBootChainLink[channel, thisDiskPage];
id ← RelID[file.fp];
data ← FileInternal.GetScratchPage[];
DO {
ENABLE UNWIND => FileInternal.FreeScratchPage[data];
At top of loop, thisDiskPage, thisSize and filePage correspond to the start of a run
nextDiskPage: Disk.PageNumber;
nextSize: Disk.PageCount;
nextChannel: Disk.Channel;
filePage ← [filePage+thisSize]; -- file page number of start of next run
thisDiskPage ← [thisDiskPage + thisSize - 1]; -- disk page number of last page of this run
IF filePage >= file.size THEN EXIT;
[diskPage: nextDiskPage, size: nextSize, channel: nextChannel] ←
FileInternal.FindRun[start: filePage, nPages: file.size-filePage, runTable: file.runTable];
IF
NOT Disk.SameDrive[nextChannel, channel]
THEN
ERROR File.Error[mixedDevices, thisDiskPage];
WriteLink[ Disk.GetBootChainLink[channel, nextDiskPage] ];
thisDiskPage ← nextDiskPage; thisSize ← nextSize;
}
ENDLOOP;
Here, thisDiskPage, thisSize and filePage correspond to the last page of the file
WriteLink[eof];
FileInternal.FreeScratchPage[data];
};
Reporter: TYPE = PROC [file: File.FP, props: File.PropertyStorage, nPages: File.PageCount];
TryToMakeALotOfExtensions: BOOL ← FALSE; -- debugging
Extend:
PROC [file: Handle, delta, min:
INT, report: Reporter, VMBackingCreate:
BOOL ←
FALSE] = {
NOTE: on entry for creation, file.size = -(number of header pages) and file.fp = nullFP.
volume: File.Volume = file.volume;
amount: INT ← delta;
nearTo: VolumeFormat.LogicalPage ←
-- hint for FileInternal.Alloc --
IF file.runTable.nRuns = 0 THEN [0] ELSE FileInternal.LastLogicalPage[file];
headerVMPos: LONG POINTER ← file.headerVM; -- headerVM to be written to disk (creating)
freeLabel: Disk.Label ← FileInternal.FreeLabel[volume];
label: Disk.Label;
loopCount:
INT ← 0 ;
the next four variables are only used when allocating the VM Backing File
nChunksLeft: INT;
chunkSize: INT;
chunkEnd: INT;
incrementToNextChunk: INT;
ComputeVMBackingLocation:
PROC [] = {
channel: Disk.Channel;
firstBigBlock: VolumeFormat.LogicalPage;
countBigBlock: VolumeFormat.LogicalPageCount;
opaqueDiskAddress: DiskFace.DontCare;
diskAddress: DiskFace.DiskAddress ;
sectorsPerTrack: INT ← 0 ;
subVolume: PhysicalVolume.SubVolumeDetails;
cylinders: INT ← 1 ;
[firstBigBlock, countBigBlock, subVolume] ← FileInternal.FindLargestFreeBlockInBiggestSubVolume[volume];
IF countBigBlock > delta
THEN {
get a empty logical run so that we can find out the channel
logicalRun ← FileInternal.Alloc[volume: volume, first: 0, size: 0, min: 10 ];
[channel: channel] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
channel ← subVolume.channel;
[cylinders: cylinders, sectorsPerTrack: sectorsPerTrack] ← DiskFace.GetTrueDeviceAttributes[Disk.GetDeviceFromChannel[channel]];
DO
opaqueDiskAddress ← Disk.GetBootChainLink[channel, [sectorsPerTrack]];
diskAddress ← LOOPHOLE[opaqueDiskAddress];
IF diskAddress.cylinder ~= 0
THEN {
Cylinder changed before head. This is an Alto Environment compatible disk such as currently used on the Dorado.
sectorsPerPlatter: INT;
firstPhysicalInBigBlock: INT ;
firstPhysicalInBigBlockOnNewPlatter: INT ;
firstLogicalInBigBlockOnNewPlatter: INT ;
firstPhysicalInBigBlock ← subVolume.address + firstBigBlock - subVolume.start;
sectorsPerPlatter ← sectorsPerTrack * cylinders;
Compute the number of platters to use. This is done by finding the number of completely free platters, and dividing the backing file evenly between them. The last platter is allowed to have a little bit on the end already allocated (an eighth of the platter).
firstPhysicalInBigBlockOnNewPlatter ← ((firstPhysicalInBigBlock+sectorsPerPlatter-1)/sectorsPerPlatter) * sectorsPerPlatter;
firstLogicalInBigBlockOnNewPlatter ← subVolume.start + firstPhysicalInBigBlockOnNewPlatter - subVolume.address ;
nChunksLeft ← (countBigBlock - firstLogicalInBigBlockOnNewPlatter + firstBigBlock + (sectorsPerPlatter/8)) / sectorsPerPlatter ;
IF nChunksLeft <= 1
THEN {
chunkEnd ← 0;
nChunksLeft ← 1;
chunkSize ← delta;
incrementToNextChunk ← 1;
EXIT;
}
ELSE {
chunkSize ← delta/nChunksLeft ;
incrementToNextChunk ← sectorsPerPlatter ;
chunkEnd ← firstLogicalInBigBlockOnNewPlatter + (sectorsPerPlatter+chunkSize)/2;
EXIT;
};
};
IF diskAddress.head ~= 0
THEN {
Head changed before cylinder. Disk is organized in a more standard manner, as on a DLion. Put the backing file in the center of the largest subVolume.
chunkEnd ← subVolume.start + (subVolume.size+delta)/2;
nChunksLeft ← 1;
chunkSize ← delta;
incrementToNextChunk ← 1;
EXIT;
};
sectorsPerTrack ← sectorsPerTrack + 1;
ENDLOOP;
}
ELSE {
disk is already fragmented - give up
nChunksLeft ← 1;
chunkSize ← delta;
incrementToNextChunk ← 1;
chunkEnd ← 0;
};
};
Start of body for Extend
IF file.size >= 0
THEN {
label ← FileInternal.DataLabel[file.fp];
label.filePage ← file.size;
}; -- Otherwise, wait until we know the FP!
Record the safe length of the file in the disk run table
TRUSTED{ file.logicalRunTable.intention ← [unstable: TRUE, size: file.size] };
IF VMBackingCreate THEN ComputeVMBackingLocation[];
WHILE amount > 0
DO
Loop for each allocated disk run
logicalRun: VolumeFormat.LogicalRun ;
nowAmount: INT ← amount ;
IF VMBackingCreate
THEN {
IF loopCount = 0
THEN {
nearTo ← [chunkEnd];
nowAmount ← chunkSize ;
}
ELSE {
chunkEnd ← chunkEnd + incrementToNextChunk ;
nChunksLeft ← nChunksLeft - 1 ;
nearTo ← [chunkEnd];
nowAmount ← chunkSize ;
};
IF nChunksLeft <= 0 THEN nowAmount ← amount ;
};
loopCount ← loopCount.SUCC;
IF TryToMakeALotOfExtensions THEN nearTo ← [nearTo+nowAmount+2]; -- debugging
logicalRun ← FileInternal.Alloc[volume: volume, first: nearTo, size: nowAmount, min: min ];
nearTo ← [logicalRun.first + logicalRun.size]; -- hint for next call of Alloc --
WHILE logicalRun.size > 0
DO
Loop for each available fragment of disk run --
labelsOK: Disk.PageCount; -- count of labels that are genuinely free pages --
status: Disk.Status;
run: PhysicalRun;
labelsThisTime: Disk.PageCount ← 0; -- labels written in this transfer --
[run.channel, run.diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
run.filePage ← file.size;
freeLabel.filePage ← logicalRun.first;
TRUSTED{ [status, labelsOK] ←
FileInternal.VerifyLabels[run.channel, run.diskPage, logicalRun.size, @freeLabel] };
IF status # Disk.ok THEN FileInternal.notReallyFree ← FileInternal.notReallyFree+1; -- statistics
IF labelsOK > 0
THEN {
labelsWritten: Disk.PageCount ← 0; -- total labels actually written --
Consume:
PROC = {
file.size ← file.size + labelsThisTime;
labelsWritten ← labelsWritten + labelsThisTime;
amount ← amount - labelsThisTime;
logicalRun.first ← [logicalRun.first+labelsThisTime];
logicalRun.size ← logicalRun.size - labelsThisTime;
};
firstHeaderPage: BOOL = file.runTable.nRuns = 0;
TRUSTED{FileInternal.AddRun[file, @run, logicalRun.first, labelsOK]};
IF firstHeaderPage
THEN {
IF file.size >= 0 THEN ERROR File.Error[inconsistent, run.diskPage];
file.fp ← [id: FileInternal.NewID[volume], da: logicalRun.first];
label ← FileInternal.HeaderLabel[file.fp];
IF report # NIL THEN report[file.fp, file.properties, file.propertyPages];
Ensuing transfer will write the run table to disk
}
ELSE {
Ensure disk run-table is superset of allocated pages
FileInternal.WriteRunTable[file];
};
IF file.size < 0
THEN {
write labels and data for header area
TRUSTED{[status, labelsThisTime] ← FileInternal.WriteLabels[run.channel,
run.diskPage, MIN[-file.size, labelsOK], headerVMPos, @label]};
Consume[];
IF file.size < 0
-- still writing header pages, even after the ones we just wrote
THEN
TRUSTED {
headerVMPos ← headerVMPos + labelsThisTime * DiskFace.wordsPerPage}
ELSE {
label ← FileInternal.DataLabel[file.fp];
label.filePage ← file.size;
};
};
IF labelsOK > labelsWritten
AND file.size >= 0
THEN {
i.e. if there's still pages free and we've finished the header
TRUSTED{[status, labelsThisTime] ← FileInternal.WriteLabels[run.channel,
[run.diskPage+labelsThisTime], labelsOK-labelsWritten, NIL, @label]};
Consume[];
};
correct run-table to number of pages successfully written --
IF labelsOK > labelsWritten
THEN
FileInternal.RemoveFromRunTable[file, labelsOK-labelsWritten];
};
SELECT status
FROM
Disk.ok => NULL;
Disk.invalid => ERROR File.Error[wentOffline, run.diskPage+labelsThisTime];
ENDCASE => {
skip bad/in-use page
logicalRun.first ← [logicalRun.first+1];
logicalRun.size ← logicalRun.size-1 };
ENDLOOP-- Loop for each available fragment of disk run --;
ENDLOOP-- Loop for each allocated disk run --;
StableRunTable[file]
};
Contract:
PROC [file: Handle, delete:
BOOL, newSize: File.PageCount
-- -1 if delete--, recovery:
BOOL] =
TRUSTED {
logical: LONG POINTER TO VolumeFormat.LogicalRunObject = file.logicalRunTable;
Write new length and "unstable" in disk run table in case of crash
IF NOT recovery THEN UnstableRunTable[file, newSize];
WHILE delete
OR file.size > newSize
DO
IF file.runTable.nRuns=0
THEN {
IF delete THEN EXIT ELSE ERROR File.Error[inconsistent];
};
{
label: Disk.Label;
labelPtr: POINTER TO Disk.Label ← NIL;
lastRun: VolumeFormat.LogicalRun ← logical[file.runTable.nRuns-1];
thisTime: VolumeFormat.RunPageCount =
IF delete
THEN
IF recovery
AND file.size > 0
THEN --restrict to data pages for label-check--MIN[file.size, lastRun.size]
ELSE --run is entirely data or entirely header--lastRun.size
ELSE MIN[file.size-newSize, lastRun.size];
file.size ← file.size - thisTime;
IF recovery
THEN {
IF file.size + thisTime > 0
THEN {
label ← FileInternal.DataLabel[file.fp];
label.filePage ← file.size;
}
ELSE {
label ← FileInternal.HeaderLabel[file.fp];
label.filePage ← logical.headerPages + file.size;
};
labelPtr ← @label;
}
ELSE labelPtr ← NIL;
FileInternal.RemoveFromRunTable[file, thisTime];
FileInternal.FreeRun[
[first: [lastRun.first + lastRun.size-thisTime], size: thisTime], file.volume, labelPtr];
};
ENDLOOP;
IF
NOT delete
THEN {
logical.intention ← [unstable: FALSE];
FileInternal.WriteRunTable[file];
};
};
recoveries: INT ← 0;
DoOpen:
PROC [file: Handle] =
TRUSTED {
volume: File.Volume = file.volume;
diskPage: Disk.PageNumber;
FileInternal.GetHeaderVM[file, initRuns];
{
-- First try to transfer entire header in a single request (an optimisation!)
initTryPages: INT = file.logicalRunTable.headerPages;
logicalRun: VolumeFormat.LogicalRun = [first: file.fp.da, size: initTryPages];
channel: Disk.Channel;
label: Disk.Label;
req: Disk.Request;
status: Disk.Status;
countDone: Disk.PageCount;
[channel, diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
label ← FileInternal.HeaderLabel[file.fp];
req ← [
diskPage: diskPage,
data: file.headerVM,
incrementDataPtr: TRUE,
command: [header: verify, label: verify, data: read],
count: initTryPages,
tries: 1 -- one try at first. If we have guessed wrong about the length of the header and there is only one header page here, we would do lots of retries.
];
TRUSTED{[status, countDone] ← DoPinnedIO[channel, @label, @req]};
req.tries ← Disk.defaultTries;
IF countDone = 0
THEN {
TRUSTED{[status, countDone] ← DoPinnedIO[channel, @label, @req]}; -- try again with retries
IF countDone = 0
THEN {
IF status = Disk.labelCheck
THEN ERROR File.Error[unknownFile, diskPage+countDone]
ELSE CheckStatus[status, diskPage+countDone];
};
};
file.runPages ← RunsToHeaderPages[file.logicalRunTable.maxRuns];
file.diskRunPages ← file.runPages;
file.propertyPages ← file.logicalRunTable.headerPages - file.runPages;
file.diskPropertyPages ← file.propertyPages;
Got the whole header, but is page 1 the correct page for the run specified in the header?
IF countDone = file.logicalRunTable.headerPages
THEN {
diskPageForHeader1: Disk.PageNumber;
file.size ← FileInternal.TranslateLogicalRunTable[file];
[diskPage: diskPageForHeader1] ← FileInternal.FindRun[
start: [-file.logicalRunTable.headerPages+1] ,
nPages: 1,
runTable: file.runTable] ;
IF Disk.Add[diskPage, 1] # diskPageForHeader1 THEN countDone ← 1 ;
};
Normally, this IF is false because almost all files have exactly two header pages and they are allocated together. Hence, they have already been read.
IF countDone # file.logicalRunTable.headerPages
THEN {
read in the remaining header pages
savedMaxRuns:
CARDINAL ← file.logicalRunTable.maxRuns;
get a new VM buffer, and copy data read above into it. This time we know that we will allocate a big enough chunk of VM
FileInternal.GetHeaderVM[file, file.logicalRunTable.maxRuns, file.diskPropertyPages];
We set countDone to one because we have to rely on header page 0 to discriminate between possible duplicate sets of header pages 1..n caused by a crash. If the header is more than 2 pages, and we read two here ok, the second is almost certainly bogus anyway.
countDone ← 1;
Loop to read in all the header pages. The normal case is that this will do one Transfer, but in case the header cannot all fit in one page of runs (currently not supported) we do a loop.
WHILE countDone < file.logicalRunTable.headerPages
DO
doneThisTime: Disk.PageCount = MIN[initRuns, file.logicalRunTable.headerPages-countDone]; -- read at most 83 pages at a time to be sure we do not exceed the known run table
file.logicalRunTable.maxRuns ← MIN[savedMaxRuns, HeaderPagesToRuns[countDone]]; -- fix up file so it will translate OK for a big enough prefix of the file.
[] ← FileInternal.TranslateLogicalRunTable[file: file, prefixOnly:
TRUE];
read the more of the header
FileInternal.Transfer[file: file, data: file.headerVM + countDone*DiskFace.wordsPerPage,
filePage: [countDone],
nPages: doneThisTime,
action: read, where: header];
countDone ← countDone + doneThisTime;
ENDLOOP;
file.logicalRunTable.maxRuns ← savedMaxRuns;
file.size ← FileInternal.TranslateLogicalRunTable[file];
};
};
IF file.logicalRunTable.intention.unstable
THEN {
delete: BOOL = file.logicalRunTable.intention.size < 0;
recoveries ← recoveries+1;
Contract[file: file,
delete: delete,
newSize: file.logicalRunTable.intention.size,
recovery: TRUE];
IF delete THEN { file.state ← deleted; ERROR File.Error[unknownFile, diskPage] };
};
file.state ← opened;
nowHaveBackingFile: BOOL ← FALSE;
HaveBackingFile:
ENTRY
PROC
RETURNS [did:
BOOL] = {
ENABLE UNWIND => NULL;
did ← nowHaveBackingFile; nowHaveBackingFile ← TRUE;
};
RegisterVMFile:
PUBLIC
PROC [file: Handle] = {
exported to FileInternal
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
label: Disk.Label ← FileInternal.DataLabel[file.fp];
IF NOT HaveBackingFile[]
THEN TRUSTED{ VMBacking.AttachBackingStorage[label, 0, file.runTable] };
};
Unlock[file];
};
unlocked: CONDITION;
Acquire:
PUBLIC
PROC [file: Handle, mode: FileInternal.LockMode] = {
exported to FileInternal
Called instead of Lock to re-open file if it was invalidated by a checkpoint
Lock[file, mode];
IF file.state = none
THEN {
File is in table but has not yet been opened. We try it, under the file's exclusive lock
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
DoOpen[file];
Incr[open, file.size, startPulse];
};
};
Lock:
PUBLIC
ENTRY
PROC [file: Handle, mode: FileInternal.LockMode] = {
exported to FileInternal
ENABLE UNWIND => NULL;
IF file = NIL THEN RETURN WITH ERROR File.Error[unknownFile];
Wrinkle: if file.state=none, we need exclusive access, so we can call DoOpen
DO
IF file.state = deleted
THEN
RETURN
WITH
ERROR File.Error[unknownFile];
IF mode = shared AND file.state # none
THEN { IF file.users >= 0 --no writers-- THEN { file.users ← file.users + 1; EXIT } }
ELSE { IF file.users = 0 --nobody-- THEN { file.users ← -1; EXIT } };
WAIT unlocked;
ENDLOOP;
};
Unlock:
PUBLIC
ENTRY
PROC [file: Handle] = {
exported to FileInternal
SELECT file.users
FROM
< 0 => file.users ← file.users + 1;
> 0 => file.users ← file.users - 1;
ENDCASE => NULL;
BROADCAST unlocked;
};
******** Top-level procedures ********
Create:
PUBLIC
PROC [volume: File.Volume, size: File.PageCount, report: Reporter ←
NIL]
RETURNS [file: Handle] = {
exported to File
startPulse: FileStats.Pulses = GetPulses[];
file ← FileInternal.AllocForCreate[]; -- gives us a handle not yet in FileTable
{
ENABLE UNWIND => FileInternal.DontInsert[];
file.volume ← volume;
GetHeaderVM[file, initRuns];
file.size ← TranslateLogicalRunTable[file];
InnerSetSize[file: file, size: size, create:
TRUE, report: report !
UNWIND => FileInternal.FreeHeaderVM[file]--Delete[File]???--];
file.state ← opened;
};
FileInternal.Insert[file];
Incr[create, size, startPulse];
};
CreateVMBacking:
PUBLIC
PROC [volume: File.Volume, size: File.PageCount, report: Reporter ←
NIL]
RETURNS [file: Handle] = {
exported to FileBackdoor
startPulse: FileStats.Pulses = GetPulses[];
file ← FileInternal.AllocForCreate[]; -- gives us a handle not yet in FileTable
{
ENABLE UNWIND => FileInternal.DontInsert[];
file.volume ← volume;
GetHeaderVM[file, initRuns];
file.size ← TranslateLogicalRunTable[file];
InnerSetSize[file: file, size: size, create:
TRUE, report: report, VMBackingCreate:
TRUE !
UNWIND => FileInternal.FreeHeaderVM[file]--Delete[File]???--];
file.state ← opened;
};
FileInternal.Insert[file];
Incr[create, size, startPulse];
};
Open:
PUBLIC
PROC [volume: File.Volume, fp: File.
FP]
RETURNS [file: Handle] = {
exported to File
IF fp = File.nullFP THEN ERROR File.Error[unknownFile];
file ← FileInternal.Lookup[volume, fp];
Acquire[file, shared];
Unlock[file];
};
Delete:
PUBLIC
PROC [file: Handle] = {
exported to File
Acquire[file, exclusive];
{
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
delta: INT = file.size;
Contract[file, TRUE, -1, FALSE];
file.state ← deleted;
Incr[delete, delta, startPulse];
};
Unlock[file];
};
SetSize:
PUBLIC
PROC [file: Handle, size: File.PageCount] = {
exported to File
InnerSetSize[file: file, size: size, create: FALSE, report: NIL];
};
minFactor: INT ← 10; -- => initial minimal runs are 1/10th of size change
InnerSetSize:
PROC [file: Handle, size: File.PageCount, create:
BOOL, report: Reporter, VMBackingCreate:
BOOL ←
FALSE ] = {
flushes: INT ← 0;
startingFree: INT ← -1; -- free pages on volume; initially -1 for not-known
minRun: INT ← MAX[MIN[FileInternal.MaxTransferRun, size / minFactor], MIN[size+normalHeaderSize, 10]]; -- smallest run we will accept; decreased if necessary
DO
IF create THEN Lock[file, exclusive] ELSE Acquire[file, exclusive];
{
startPulse: FileStats.Pulses = GetPulses[];
delta: INT = size-file.size;
SELECT
TRUE
FROM
delta > 0 => {
ENABLE File.Error => {
lack: INT = MIN[minRun, size-file.size]; -- calculate it while we still have the file locked
IF startingFree = -1 THEN startingFree ← FileBackdoor.GetVolumePages[file.volume].free;
IF why = volumeFull
THEN {
hardExtend: BOOL;
flushedOK: BOOL ← TRUE;
FSRootFile: BOOL ← FALSE;
volume: Volume ← file.volume;
We know that the disk run-table matches the in-core one (???).
IF volume #
NIL
THEN
TRUSTED {
Prevent flushes when extending the FS BTree - or we will deadlock
IF file.fp = volume.root.rootFile[client].fp THEN FSRootFile ← TRUE;
};
IF size > 5000 AND minRun <= 5 AND flushes > 50 THEN REJECT; -- a big file is filling up the disk => treat the error as real
Unlock[file];
hardExtend ← (FileBackdoor.GetVolumePages[file.volume].free - startingFree) > 8 * lack AND flushes > 10 ;
flushes ← flushes + 1;
IF ~FSRootFile THEN flushedOK ← FileInternal.Flush[file.volume, lack];
SELECT
TRUE
FROM
FSRootFile => {
Incr[hardExtends, delta, startPulse];
minRun ← minRun / 2;
IF minRun < 2 THEN REJECT; -- never let minRun get below 2
LOOP;
};
flushedOK
AND ~FSRootFile => {
Flusher succeeded
Notes: FS flusher will flush at most one file per Flush request! It ignores lack completely
LogicalVolumeImpl.Alloc will not even try to allocate if the size is bigger than free on the volume - it ignores minRun completely in this case.
IF FileBackdoor.GetVolumePages[file.volume].free >= delta
AND (hardExtend
OR (flushes
MOD 8) = 7)
THEN {
Incr[hardExtends, delta, startPulse];
minRun ← minRun / 2;
IF minRun < 2 THEN REJECT; -- never let minRun get below 2
};
LOOP;
};
~flushedOK => {
IF FileBackdoor.GetVolumePages[file.volume].free >= lack
THEN {
can't flush, but enough room so go for it
Incr[hardExtends, delta, startPulse];
minRun ← minRun / 2;
IF minRun < 2 THEN REJECT; -- never let minRun get below 2
LOOP;
}
ELSE REJECT;
};
ENDCASE => REJECT;
-- old code below
IF ~FSRootFile AND flushedOK AND ~hardExtend AND flushes < 8 THEN { -- Flusher succeeded
Note: FS flusher will flush at most one file per Flush request! It ignores lack completely
LOOP;
}
ELSE { -- can't flush anymore
IF FileBackdoor.GetVolumePages[file.volume].free >= lack THEN {
Incr[hardExtends, delta, startPulse];
minRun ← minRun / 2;
IF minRun < 2 THEN REJECT; -- never let minRun get below 2
LOOP;
};
};
}
ELSE {
IF NOT create -- core run-table # disk, so close the file; let DoOpen recover.
THEN { file.state ← none; FileInternal.FreeHeaderVM[file] };
Unlock[file];
};
Otherwise, let the error propagate to our client
};
IF delta < minRun THEN minRun ← delta;
Extend[file, delta, minRun, report, VMBackingCreate];
Incr[extend, delta, startPulse];
};
delta < 0 => {
ENABLE File.Error => {
core run-table # disk, so close the file. DoOpen will try to recover.
file.state ← none;
FileInternal.FreeHeaderVM[file];
Unlock[file];
};
Contract[file, FALSE, size, FALSE]; Incr[contract, -delta, startPulse];
};
ENDCASE => NULL;
};
Unlock[file];
EXIT
ENDLOOP;
};
Info:
PUBLIC
PROC [file: Handle]
RETURNS [volume: File.Volume, fp: File.
FP, size: File.PageCount] = {
exported to File
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
volume ← file.volume; fp ← file.fp; size ← file.size;
};
Unlock[file];
};
SetRoot:
PUBLIC
PROC [root: File.VolumeFile, file: Handle, page: File.PageNumber ← [0]] =
TRUSTED {
exported to FileBackdoor
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
id: RelID;
firstLink: DiskFace.DontCare;
channel: Disk.Channel;
[id, firstLink, channel] ← MakeBootable[file, page];
FileInternal.RecordRootFile[file.volume, root, file.fp, page, id, firstLink, channel];
};
Unlock[file];
{
ENABLE File.Error => CONTINUE;
IF root =
VM
AND File.SystemVolume[] # NIL
AND FileBackdoor.IsDebugger[File.SystemVolume[]] = FileBackdoor.IsDebugger[file.volume]
THEN RegisterVMFile[file];
};
};
GetFileLocation:
PUBLIC
PROC [file: Handle, firstPage: File.PageNumber]
RETURNS [location: BootFile.Location] =
TRUSTED {
exported to FileInternal
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
id: RelID;
firstLink: DiskFace.DontCare;
channel: Disk.Channel;
[id, firstLink, channel] ← MakeBootable[file, firstPage];
location.diskFileID ← [fID: [rel[id]], firstPage: firstPage, firstLink: firstLink];
[type: location.deviceType, ordinal: location.deviceOrdinal] ←
Disk.DriveAttributes[channel];
};
Unlock[file];
};
Read:
PUBLIC
UNSAFE
PROC [file: Handle, from: File.PageNumber, nPages: File.PageCount, to:
LONG
POINTER] = {
exported to File
IF from < 0 THEN ERROR File.Error[unknownPage, from];
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
FileInternal.Transfer[file: file, data: to, filePage: from, nPages: nPages, action: read, where: data];
Incr[read, nPages, startPulse];
};
Unlock[file];
};
Write:
PUBLIC
PROC [file: Handle, to: File.PageNumber, nPages: File.PageCount, from:
LONG
POINTER] = {
exported to File
IF to < 0 THEN ERROR File.Error[unknownPage, to];
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
FileInternal.Transfer[file: file, data: from, filePage: to, nPages: nPages, action: write, where: data];
Incr[write, nPages, startPulse];
};
Unlock[file];
};
GetProperties:
PUBLIC
PROC [file: Handle]
RETURNS [prop: File.PropertyStorage, nPages: File.PageCount] = {
exported to File
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
prop ← file.properties;
nPages ← file.propertyPages;
};
Unlock[file];
};
WriteProperties:
PUBLIC
PROC [file: Handle] =
TRUSTED {
exported to File
Acquire[file, shared];
{
ENABLE File.Error => Unlock[file];
FileInternal.Transfer[file: file, data: file.properties,
filePage: [file.logicalRunTable.headerPages-file.propertyPages],
nPages: file.propertyPages, action: write, where: header]
};
Unlock[file];
};
}.