Cedar Nucleus (Files): per-file operations, locking file header data structures
FileImpl.mesa
Andrew Birrell December 8, 1983 9:51 am
Last Edited by: Levin, August 8, 1983 5:57 pm
Last Edited by: Schroeder, June 10, 1983 5:20 pm
Last Edited by: Bob Hagmann, May 10, 1984 9:28:27 am PDT
DIRECTORY
BootFile USING[ Location ],
Disk USING[ Channel, DoIO, DriveAttributes, GetBootChainLink, invalid, Label, labelCheck, ok, PageNumber, PageCount, Request, SameDrive, Status ],
DiskExtras USING[ GetDeviceFromChannel ],
DiskFace USING[ DiskAddress, DontCare, wordsPerPage ],
DiskFaceExtras USING[ GetTrueDeviceAttributes],
File USING[ Error, FP, GetVolumePages, GetVolumeID, IsDebugger, nullFP, PageCount, PageNumber, PagesForWords, PropertyStorage, propertyWords, RC, Reason, SystemVolume, Volume, VolumeFile, VolumeID ],
FileExtrasForFS,
FileInternal,
FileStats USING[ Data, Type, Pulses ],
PhysicalVolume USING [SubVolumeDetails],
PrincOpsUtils USING[ LongCOPY ],
ProcessorFace USING[ GetClockPulses ],
VolumeFormat USING[ AbsID, 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 ];
FileImpl:
CEDAR
MONITOR
IMPORTS Disk, DiskExtras, DiskFaceExtras, File, FileInternal, PrincOpsUtils, ProcessorFace, VM, VMBacking
EXPORTS DiskFace--RelID,AbsID,Attributes--, File, FileExtrasForFS, FileInternal, FileStats
SHARES File =
-- ******** Data Types and minor subroutines ******** --
--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;
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 = (DiskFace.wordsPerPage-
SIZE[VolumeFormat.LogicalRunObject[0]]) /
SIZE[VolumeFormat.LogicalRun];
DoPinnedIO:
PROC[channel: Disk.Channel, label:
POINTER
TO Disk.Label, req:
POINTER
TO Disk.Request]
RETURNS[ status: Disk.Status, countDone: Disk.PageCount] = TRUSTED
BEGIN
interval:
VM.Interval = [
page: VM.PageNumberForAddress[req.data],
count:
VM.PagesForWords[
(IF req.incrementDataPtr THEN req.count ELSE 1)*DiskFace.wordsPerPage] ];
VM.SwapIn[interval: interval, kill: req.command.data=read, pin: TRUE];
[status, countDone] ← Disk.DoIO[channel, label, req ! UNWIND => VM.Unpin[interval] ];
VM.Unpin[interval];
END;
--File.--Error: PUBLIC ERROR[why: File.Reason] = CODE;
badData: Disk.Status = [unchanged[dataCRCError]]; -- indicates data is bad but label is ok
CheckStatus:
PROC[status: Disk.Status] =
BEGIN
why: File.RC = FileInternal.TranslateStatus[status];
IF why # ok THEN ERROR File.Error[why];
END;
-- ******** Header and Run-table management ******** --
propFilePages: File.PageCount = File.PagesForWords[File.propertyWords];
--FileInternal.--
GetHeaderVM:
PUBLIC
PROC[file: Handle, runs:
CARDINAL] =
TRUSTED
BEGIN
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]];
vmPages: INT = VM.PagesForWords[runTableWords] + VM.PagesForWords[File.propertyWords];
runTableFilePages: File.PageCount = File.PagesForWords[runTableWords];
file.headerVM ← VM.AddressForPageNumber[VM.Allocate[vmPages].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 + propFilePages;
file.logicalRunTable.maxRuns ← runs;
IF oldVM = NIL
THEN
BEGIN
-- initialise only --
file.logicalRunTable[0].first ← VolumeFormat.lastLogicalRun;
file.properties^ ← ALL[0];
END
ELSE
BEGIN
-- initialise from old tables --
PrincOpsUtils.LongCOPY[from: oldLogical, to: file.logicalRunTable,
-- may copy extra
nwords: MIN[runTableWords, oldHeaderVMPages*VM.wordsPerPage] ];
file.properties^ ← oldProperties^;
VM.Free[[VM.PageNumberForAddress[oldVM], oldHeaderVMPages]];
END;
END;
--FileInternal.--
FreeHeaderVM:
PUBLIC
PROC[file: Handle] =
TRUSTED
BEGIN
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
END;
--FileInternal.--
TranslateLogicalRunTable:
PUBLIC
PROC[file: Handle]
RETURNS[ File.PageCount ] =
TRUSTED
BEGIN
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 => 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 ]
END;
--FileInternal.--
AddRun:
PUBLIC
PROC[file: Handle,
run: POINTER TO PhysicalRun,
logicalPage: VolumeFormat.LogicalPage,
okPages: VolumeFormat.RunPageCount] = TRUSTED
BEGIN
Either extend last run, or add new run
logical: LONG POINTER TO VolumeFormat.LogicalRunObject = file.logicalRunTable;
physical: RunTable = file.runTable;
oldNRuns: CARDINAL = physical.nRuns;
physical.nDataPages ← file.size + okPages;
IF oldNRuns > 0
AND logical[oldNRuns-1].first + logical[oldNRuns-1].size = logicalPage
AND logical[oldNRuns-1].size <= LAST[VolumeFormat.RunPageCount] - okPages
AND run.channel = physical[oldNRuns-1].channel
THEN logical[oldNRuns-1].size ← logical[oldNRuns-1].size + okPages
ELSE
BEGIN
-- Add another run
IF physical.nRuns+1 = logical.maxRuns
THEN
BEGIN
-- extend logical run table to ensure there is space to record an extension --
ERROR File.Error[fragmented]
END;
physical[oldNRuns] ← run^;
logical[oldNRuns].first ← logicalPage;
logical[oldNRuns].size ← okPages;
physical.nRuns ← oldNRuns + 1;
IF physical.nRuns = physical.length
THEN
BEGIN
-- extend physical run table object --
file.runTable ← NEW[RunTableObject[physical.length*2]];
file.runTable^ ← physical^ . . . . but the compiler can't copy sequences
file.runTable.nDataPages ← physical.nDataPages;
file.runTable.nRuns ← physical.nRuns;
FOR i: CARDINAL IN [0..physical.length) DO file.runTable[i] ← physical[i] ENDLOOP;
END;
file.runTable[oldNRuns + 1].filePage ← lastRun;
logical[oldNRuns + 1].first ← VolumeFormat.lastLogicalRun;
END;
END;
--FileInternal.--
LastLogicalPage:
PUBLIC
PROC[file: Handle]
RETURNS [VolumeFormat.LogicalPage] =
TRUSTED
BEGIN
Assumes file.runTable.nRuns > 0
lastRun: VolumeFormat.LogicalRun = file.logicalRunTable[file.runTable.nRuns-1];
RETURN[ [lastRun.first + lastRun.size-1] ]
END;
--FileInternal.--
RemoveFromRunTable:
PUBLIC
PROC[file: Handle, remove:
INT] =
TRUSTED
BEGIN
logical: LONG POINTER TO VolumeFormat.LogicalRunObject = file.logicalRunTable;
physical: RunTable = file.runTable;
physical.nDataPages ← file.size;
WHILE remove > 0
DO
IF physical.nRuns = 0
THEN
ERROR File.Error[inconsistent];
BEGIN
runSize: VolumeFormat.RunPageCount = logical[physical.nRuns-1].size;
amount: VolumeFormat.RunPageCount = MIN[remove, runSize];
logical[physical.nRuns-1].size ← runSize - amount;
IF runSize - amount = 0
THEN
BEGIN
-- Remove the new run table entry entirely! --
physical.nRuns ← physical.nRuns - 1;
physical[physical.nRuns].filePage ← lastRun;
logical[physical.nRuns].first ← VolumeFormat.lastLogicalRun;
END;
remove ← remove - amount;
END;
ENDLOOP;
END;
--FileInternal.--
FindRun:
PUBLIC
PROC[start: File.PageNumber, nPages: File.PageCount, runTable: RunTable]
RETURNS[diskPage: Disk.PageNumber, size: Disk.PageCount, channel: Disk.Channel] =
BEGIN
probe: RunTableIndex ← runTable.nRuns / 2; -- NB: round down --
increment: CARDINAL ← probe;
IF runTable.nRuns = 0 THEN ERROR File.Error[inconsistent];
IF start + nPages > runTable.nDataPages THEN ERROR File.Error[unknownPage];
IF start < runTable[0].filePage THEN ERROR File.Error[unknownPage];
DO increment ← (increment+1)/2;
SELECT
TRUE
FROM
runTable[probe].filePage > start =>
probe ← IF probe < increment THEN 0 ELSE probe-increment;
runTable[probe+1].filePage <= start =>
probe ← MIN[probe + increment, runTable.nRuns-1];
ENDCASE =>
RETURN[
diskPage: [runTable[probe].diskPage + (start-runTable[probe].filePage)],
size:
IF start + nPages <= runTable[probe+1].filePage
THEN nPages
ELSE runTable[probe+1].filePage - start,
channel: runTable[probe].channel ]
ENDLOOP;
END;
-- ******** Subroutines for access to file pages ******** --
HeaderLabel:
PROC[fp: File.
FP]
RETURNS[Disk.Label] =
BEGIN
RETURN[ [
fileID: [rel[RelID[fp]]],
filePage: 0,
attributes: Attributes[header],
dontCare: LOOPHOLE[LONG[0]]
] ]
END;
DataLabel:
PROC[fp: File.
FP]
RETURNS[Disk.Label] =
BEGIN
RETURN[ [
fileID: [rel[RelID[fp]]],
filePage: 0,
attributes: Attributes[data],
dontCare: LOOPHOLE[LONG[0]]
] ]
END;
FreeLabel:
PROC[volume: File.Volume]
RETURNS[Disk.Label] =
BEGIN
RETURN[ [
fileID: [abs[AbsID[File.GetVolumeID[volume]]]],
filePage: 0,
attributes: Attributes[freePage],
dontCare: LOOPHOLE[LONG[0]]
] ]
END;
WriteLabels:
PROC[channel: Disk.Channel, diskPage: Disk.PageNumber, count: Disk.PageCount, data:
LONG
POINTER, label:
POINTER
TO Disk.Label]
RETURNS[ status: Disk.Status, countDone: Disk.PageCount] = TRUSTED
BEGIN
req: Disk.Request ← [
diskPage: diskPage,
data: IF data = NIL THEN scratchWriter ELSE data,
incrementDataPtr: data # NIL,
command: [header: verify, label: write, data: write],
count: count ];
[status, countDone] ← DoPinnedIO[channel, label, @req];
END;
VerifyLabels:
PROC[channel: Disk.Channel, diskPage: Disk.PageNumber, count: Disk.PageCount, label:
POINTER
TO Disk.Label]
RETURNS[ status: Disk.Status, countDone: Disk.PageCount] = TRUSTED
BEGIN
req: Disk.Request ← [
diskPage: diskPage,
data: scratchReader,
incrementDataPtr: FALSE,
command: [header: verify, label: verify, data: read],
count: count ];
[status, countDone] ← DoPinnedIO[channel, label, @req];
IF status = badData
THEN { status ← Disk.ok; countDone ← countDone+1; label.filePage ← label.filePage+1 };
END;
GetScratchPage:
PROC
RETURNS[data:
LONG
POINTER] =
TRUSTED
BEGIN
temp: LONG POINTER TO ARRAY [0..DiskFace.wordsPerPage) OF WORD;
data ← VM.AddressForPageNumber[VM.Allocate[VM.PagesForWords[DiskFace.wordsPerPage]].page];
temp ← LOOPHOLE[data];
temp^ ← ALL[0];
END;
FreeScratchPage:
PROC[data:
LONG
POINTER] =
TRUSTED
BEGIN
VM.Free[
[ page: VM.PageNumberForAddress[data],
count: VM.PagesForWords[DiskFace.wordsPerPage] ]
];
END;
scratchWriter: LONG POINTER = GetScratchPage[]; -- scratch buffer for writing (all 0)
scratchReader: LONG POINTER = GetScratchPage[]; -- scratch buffer for reading
--FileInternal.--
FreeRun:
PUBLIC
PROC[logicalRun: VolumeFormat.LogicalRun, volume: File.Volume, verifyLabel:
POINTER
TO Disk.Label ←
NIL] =
BEGIN
Write page labels as "free" and mark as unused in VAM. Iff verifyLabel # NIL, do so only to pages whose labels verify correctly.
label: Disk.Label ← FreeLabel[volume];
WHILE logicalRun.size > 0
DO channel: Disk.Channel;
diskPage: Disk.PageNumber;
status: Disk.Status;
verifyStatus: Disk.Status ← Disk.ok;
thisTime: Disk.PageCount ← logicalRun.size;
countDone: Disk.PageCount;
Consume:
PROC =
BEGIN
logicalRun.first ← [logicalRun.first + countDone];
logicalRun.size ← logicalRun.size - countDone;
IF verifyLabel # NIL
THEN TRUSTED{ verifyLabel.filePage ← verifyLabel.filePage + countDone };
countDone ← 0;
END;
[channel, diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
IF verifyLabel # NIL
THEN
TRUSTED
BEGIN
-- verify which pages are part of our file
temp: Disk.Label ← verifyLabel^;
[verifyStatus, thisTime] ← VerifyLabels[channel, diskPage, thisTime, @temp];
END;
label.filePage ← logicalRun.first;
FileInternal.Free[volume, [first: logicalRun.first, size: thisTime]];
TRUSTED{[status, countDone] ← WriteLabels[channel, diskPage, thisTime, NIL, @label]};
SELECT status
FROM
Disk.ok => NULL;
Disk.invalid => ERROR File.Error[wentOffline];
ENDCASE => countDone ← countDone + 1; -- Page is in our file, but not writeable --
Consume[];
IF verifyLabel # NIL AND status = Disk.ok AND verifyStatus # Disk.ok
THEN
TRUSTED
BEGIN
We've freed everything up to but excluding a label mis-match. Now, look for free pages which should be notified to the VAM in case the VAM thinks they're in use.
free: Disk.Label ← FreeLabel[volume];
free.filePage ← logicalRun.first;
[channel, diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
[verifyStatus, countDone] ← VerifyLabels[channel, diskPage, logicalRun.size, @free];
IF verifyStatus # Disk.ok AND countDone = 0
THEN -- label isn't in our file, but isn't free, so ignore it -- countDone ← 1
ELSE FileInternal.Free[volume, [first: logicalRun.first, size: countDone]];
Consume[];
END;
ENDLOOP;
END--FreeRun--;
maxTransferRun: Disk.PageCount ← 200;
Largest number of disk pages to transfer in single request. This much VM will be pinned during the transfer. Variable, not constant, to allow patching.
Transfer:
PROC[file: Handle, data:
LONG
POINTER, filePage: File.PageNumber, nPages: File.PageCount, action: {write, read}, where: {header, data} ] =
BEGIN
label: Disk.Label ←
IF where = header THEN HeaderLabel[file.fp] ELSE DataLabel[file.fp];
label.filePage ← filePage;
WHILE nPages > 0
DO status: Disk.Status;
countDone: Disk.PageCount;
channel: Disk.Channel;
req: Disk.Request;
req.data ← data;
req.incrementDataPtr ← TRUE;
req.command ←
IF action = read
THEN [header: verify, label: verify, data: read]
ELSE [header: verify, label: verify, data: write];
TRUSTED{ [diskPage: req.diskPage, size: req.count, channel: channel] ← FileInternal.FindRun[
-- NB: first call of FindRun checks entire transfer is within file
start: IF where = header THEN [-file.logicalRunTable.headerPages+filePage] ELSE filePage,
nPages: nPages,
runTable: file.runTable] };
IF req.count > maxTransferRun THEN req.count ← maxTransferRun;
TRUSTED{[status, countDone] ← DoPinnedIO[channel, @label, @req]};
CheckStatus[status];
TRUSTED{data ← data + countDone * DiskFace.wordsPerPage};
nPages ← nPages - countDone;
filePage ← [filePage + countDone];
ENDLOOP;
END;
WriteRunTable:
PROC[file: Handle] =
TRUSTED
BEGIN
Transfer[file: file, data: file.headerVM, filePage: [0],
nPages: file.logicalRunTable.headerPages - propFilePages, action: write, where: header]
END;
UnstableRunTable:
PROC[file: Handle, newSize: File.PageCount] =
TRUSTED
BEGIN
file.logicalRunTable.intention ← [unstable: TRUE, size: newSize];
Transfer[file: file, data: file.headerVM, filePage: [0], nPages: 1, action: write, where: header];
END;
StableRunTable:
PROC[file: Handle] =
TRUSTED
BEGIN
file.logicalRunTable.intention ← [unstable: FALSE];
Transfer[file: file, data: file.headerVM, filePage: [0], nPages: 1, action: write, where: header];
END;
MakeBootable:
PROC[file: Handle, firstPage: File.PageNumber]
RETURNS[id: RelID, firstLink: DiskFace.DontCare, channel: Disk.Channel] =
BEGIN
eof: DiskFace.DontCare = LOOPHOLE[LONG[-1]]; -- bit-pattern known by microcode
data: LONG POINTER;
label: Disk.Label ← 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"
BEGIN
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];
label.dontCare ← link;
label.filePage ← filePage-1; -- previous transfer incremented it
TRUSTED{[status, countDone] ← WriteLabels[channel, thisDiskPage, 1, data, @label]};
CheckStatus[status];
END;
thisSize: Disk.PageCount;
IF file.size <= firstPage THEN ERROR File.Error[unknownPage];
[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 ← GetScratchPage[];
DO
BEGIN
ENABLE UNWIND => 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];
WriteLink[ Disk.GetBootChainLink[channel, nextDiskPage] ];
thisDiskPage ← nextDiskPage; thisSize ← nextSize;
END
ENDLOOP;
Here, thisDiskPage, thisSize and filePage correspond to the last page of the file
WriteLink[eof];
FreeScratchPage[data];
END;
--FileStats.--notReallyFree: INT ← 0;
Reporter: TYPE = PROC[File.FP, File.PropertyStorage];
Extend:
PROC[file: Handle, delta, min:
INT, report: Reporter, VMBackingCreate:
BOOL ←
FALSE] =
BEGIN
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 ← 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;
IF file.size >= 0
THEN
BEGIN
label ← DataLabel[file.fp];
label.filePage ← file.size;
END; -- 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 {
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] ← DiskFaceExtras.GetTrueDeviceAttributes[DiskExtras.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;
};
};
WHILE amount > 0
-- Loop for each allocated disk run --
DO
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;
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
-- Loop for each available fragment of disk run --
DO labelsOK: Disk.PageCount;
-- count of labels that are genuinely free pages --
status: Disk.Status;
run: PhysicalRun;
[run.channel, run.diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
run.filePage ← file.size;
freeLabel.filePage ← logicalRun.first;
TRUSTED{ [status, labelsOK] ←
VerifyLabels[run.channel, run.diskPage, logicalRun.size, @freeLabel] };
IF status # Disk.ok THEN notReallyFree ← notReallyFree+1; -- statistics
IF labelsOK > 0
THEN
BEGIN
labelsWritten: Disk.PageCount ← 0; -- total labels actually written --
labelsThisTime: Disk.PageCount ← 0; -- labels written in this transfer --
Consume:
PROC =
BEGIN
file.size ← file.size + labelsThisTime;
labelsWritten ← labelsWritten + labelsThisTime;
amount ← amount - labelsThisTime;
logicalRun.first ← [logicalRun.first+labelsThisTime];
logicalRun.size ← logicalRun.size - labelsThisTime;
END;
firstHeaderPage: BOOL = file.runTable.nRuns = 0;
TRUSTED{FileInternal.AddRun[file, @run, logicalRun.first, labelsOK]};
IF firstHeaderPage
THEN
BEGIN
IF file.size >= 0 THEN ERROR File.Error[inconsistent];
file.fp ← [id: FileInternal.NewID[volume], da: logicalRun.first];
label ← HeaderLabel[file.fp];
IF report # NIL THEN report[file.fp, file.properties];
Ensuing transfer will write the run table to disk
END
ELSE
BEGIN
Ensure disk run-table is superset of allocated pages
WriteRunTable[file];
END;
IF file.size < 0
THEN
BEGIN
-- write labels and data for header area --
TRUSTED{[status, labelsThisTime] ← 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
BEGIN
label ← DataLabel[file.fp];
label.filePage ← file.size;
END;
END;
IF labelsOK > labelsWritten
AND file.size >= 0 -- i.e. if there's still pages free and we've finished the header
THEN
BEGIN
TRUSTED{[status, labelsThisTime] ← WriteLabels[run.channel,
[run.diskPage+labelsThisTime], labelsOK-labelsWritten, NIL, @label]};
Consume[];
END;
-- correct run-table to number of pages successfully written --
IF labelsOK > labelsWritten
THEN FileInternal.RemoveFromRunTable[file, labelsOK-labelsWritten];
END;
SELECT status
FROM
Disk.ok => NULL;
Disk.invalid => ERROR File.Error[wentOffline];
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]
END--Extend--;
Contract:
PROC[file: Handle, delete:
BOOL, newSize: File.PageCount
-- -1 if delete--, recovery:
BOOL] =
TRUSTED
BEGIN
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] };
BEGIN
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
BEGIN
IF file.size + thisTime > 0
THEN
BEGIN
label ← DataLabel[file.fp];
label.filePage ← file.size;
END
ELSE
BEGIN
label ← HeaderLabel[file.fp];
label.filePage ← logical.headerPages + file.size;
END;
labelPtr ← @label;
END
ELSE labelPtr ← NIL;
FileInternal.RemoveFromRunTable[file, thisTime];
FreeRun[
[first: [lastRun.first + lastRun.size-thisTime], size: thisTime], file.volume, labelPtr];
END;
ENDLOOP;
IF NOT delete
THEN { logical.intention ← [unstable: FALSE]; WriteRunTable[file] };
END--Contract--;
--FileStats.--recoveries: INT ← 0;
DoOpen:
PROC[file: Handle] =
TRUSTED
BEGIN
volume: File.Volume = file.volume;
FileInternal.GetHeaderVM[file, initRuns];
BEGIN
-- 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;
diskPage: Disk.PageNumber;
label: Disk.Label;
req: Disk.Request;
status: Disk.Status;
countDone: Disk.PageCount;
[channel, diskPage] ← FileInternal.TranslateLogicalRun[logicalRun, volume];
label ← HeaderLabel[file.fp];
req ← [
diskPage: diskPage,
data: file.headerVM,
incrementDataPtr: TRUE,
command: [header: verify, label: verify, data: read],
count: initTryPages ];
TRUSTED{[status, countDone] ← DoPinnedIO[channel, @label, @req]};
IF countDone = 0
THEN
BEGIN
IF status = Disk.labelCheck
THEN ERROR File.Error[unknownFile]
ELSE CheckStatus[status];
END;
IF file.logicalRunTable.headerPages # initTryPages -- multi-page run-tables!
THEN ERROR File.Error[inconsistent];
file.size ← FileInternal.TranslateLogicalRunTable[file]; -- assumes single-page run-table
IF countDone # file.logicalRunTable.headerPages
THEN
-- read in the remaining header pages (e.g. property page)
Transfer[file: file, data: file.headerVM + countDone*DiskFace.wordsPerPage,
filePage: [countDone],
nPages: file.logicalRunTable.headerPages - countDone,
action: read, where: header];
END;
IF file.logicalRunTable.intention.unstable
THEN
BEGIN
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] };
END;
file.state ← opened;
END;
nowHaveBackingFile: BOOL ← FALSE;
HaveBackingFile:
ENTRY
PROC
RETURNS[did:
BOOL] =
BEGIN
ENABLE UNWIND => NULL;
did ← nowHaveBackingFile; nowHaveBackingFile ← TRUE;
END;
--FileInternal.--
RegisterVMFile:
PUBLIC
PROC[file: Handle] =
BEGIN
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
label: Disk.Label ← DataLabel[file.fp];
IF NOT HaveBackingFile[]
THEN TRUSTED{ VMBacking.AttachBackingStorage[label, 0, file.runTable] };
END;
Unlock[file];
END;
unlocked: CONDITION;
Acquire:
PROC[file: Handle, mode: FileInternal.LockMode] =
BEGIN
Called instead of Lock to re-open file if it was invalidated by a checkpoint
Lock[file, mode];
IF file.state = none
THEN
BEGIN
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];
END;
END;
--FileInternal.--
Lock:
PUBLIC
ENTRY
PROC[file: Handle, mode: FileInternal.LockMode] =
BEGIN
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;
END;
--FileInternal.--
Unlock:
PUBLIC
ENTRY
PROC[file: Handle] =
BEGIN
SELECT file.users
FROM
< 0 => file.users ← file.users + 1;
> 0 => file.users ← file.users - 1;
ENDCASE => NULL;
BROADCAST unlocked;
END;
-- ******** Scanning for files (File.NextFile) ******** --
--File.--
NextFile:
PUBLIC
PROC[volume: File.Volume, prev: File.
FP]
RETURNS[next: File.
FP ← File.nullFP] =
TRUSTED
BEGIN
finishedStatus: Disk.Status ← Disk.ok;
Work: FileInternal.EnumeratePagesProc =
TRUSTED
BEGIN
attr: Attributes = label.attributes;
rel: RelID = label.fileID.relID;
SELECT
TRUE
FROM
status # Disk.ok => { exit ← TRUE; finishedStatus ← status };
attr = header AND label.filePage = 0 => { exit ← TRUE; next ← rel };
ENDCASE => NULL;
END;
EnumeratePages[volume, prev.da, Work];
CheckStatus[finishedStatus];
END;
--FileInternal.--
EnumeratePages:
PUBLIC
PROC[
volume: File.Volume,
start: VolumeFormat.LogicalPage,
work: FileInternal.EnumeratePagesProc] = TRUSTED
BEGIN
size: INT = File.GetVolumePages[volume].size;
current: VolumeFormat.LogicalPage ← start;
done: VolumeFormat.LogicalPage ← current;
finished: BOOL ← FALSE;
changed: CONDITION;
Next:
ENTRY
PROC
RETURNS[VolumeFormat.LogicalPage] =
CHECKED
INLINE
{ RETURN[current ← [current+1]] };
Scan:
PROC =
TRUSTED
BEGIN
exit: BOOL ← FALSE;
UNTIL exit
DO this: VolumeFormat.LogicalPage = Next[];
WaitTurn:
ENTRY
PROC =
CHECKED
INLINE
{ UNTIL done = this-1 DO WAIT changed[! UNWIND => NULL] ENDLOOP };
CompletedTurn:
ENTRY
PROC =
CHECKED
INLINE
{ done ← this; BROADCAST changed };
channel: Disk.Channel;
diskPage: Disk.PageNumber;
label: Disk.Label;
req: Disk.Request;
status: Disk.Status;
IF this >= size THEN EXIT;
[channel, diskPage] ← FileInternal.TranslateLogicalRun[[first: this, size: 1], volume];
req ← [
diskPage: diskPage,
data: scratchReader,
command: [header: verify, label: read, data: read],
count: 1 ];
status ← Disk.DoIO[channel, @label, @req].status;
IF status = badData THEN status ← Disk.ok; -- don't care about the data, only the label!
WaitTurn[];
IF NOT finished
THEN finished ← work[status, this, @label ! UNWIND => CompletedTurn[]];
exit ← finished;
CompletedTurn[];
ENDLOOP;
END;
scratchInterval:
VM.Interval = [
page: VM.PageNumberForAddress[scratchReader],
count: VM.PagesForWords[DiskFace.wordsPerPage] ];
VM.SwapIn[interval: scratchInterval, kill: TRUE, pin: TRUE];
BEGIN
ENABLE UNWIND => VM.Unpin[scratchInterval];
otherGuy: PROCESS = FORK Scan[];
Scan[];
JOIN otherGuy;
END;
VM.Unpin[scratchInterval];
END;
-- ******** Statistics ******** --
statistics:
REF
ARRAY FileStats.Type
OF FileStats.Data ←
NEW[ARRAY FileStats.Type OF FileStats.Data ← ALL[]];
hardExtends: FileStats.Type = spare0;
GetPulses:
PROC
RETURNS[FileStats.Pulses] =
TRUSTED
INLINE
{ RETURN[ ProcessorFace.GetClockPulses[] ] };
Incr:
PUBLIC
ENTRY
PROC[type: FileStats.Type, pages:
INT, startPulse: FileStats.Pulses] =
BEGIN
old: FileStats.Data = statistics[type];
statistics[type] ←
[calls: old.calls+1, pages: old.pages+pages, pulses: old.pulses + (GetPulses[]-startPulse)];
END;
--FileStats.--
GetData:
PUBLIC
ENTRY
PROC[type: FileStats.Type]
RETURNS[FileStats.Data] =
{ RETURN[statistics[type]] };
--FileStats.--
ClearData:
PUBLIC
ENTRY
PROC[type: FileStats.Type] =
{ statistics[type] ← [] };
-- ******** Top-level procedures ******** --
--File.--
Create:
PUBLIC
PROC[volume: File.Volume, size: File.PageCount, report: Reporter ←
NIL]
RETURNS[file: Handle] =
BEGIN
startPulse: FileStats.Pulses = GetPulses[];
file ← FileInternal.AllocForCreate[]; -- gives us a handle not yet in FileTable
BEGIN
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;
END;
FileInternal.Insert[file];
Incr[create, size, startPulse];
END;
--FileExtrasForFS.--
CreateVMBacking:
PUBLIC
PROC[volume: File.Volume, size: File.PageCount, report: Reporter ←
NIL]
RETURNS[file: Handle] =
BEGIN
startPulse: FileStats.Pulses = GetPulses[];
file ← FileInternal.AllocForCreate[]; -- gives us a handle not yet in FileTable
BEGIN
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;
END;
FileInternal.Insert[file];
Incr[create, size, startPulse];
END;
--File.--
Open:
PUBLIC
PROC[volume: File.Volume, fp: File.
FP]
RETURNS[file: Handle] =
BEGIN
IF fp = File.nullFP THEN ERROR File.Error[unknownFile];
file ← FileInternal.Lookup[volume, fp];
Acquire[file, shared];
Unlock[file];
END;
--File.--
Delete:
PUBLIC
PROC[file: Handle] =
BEGIN
Acquire[file, exclusive];
BEGIN
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];
END;
Unlock[file];
END;
--File.--
SetSize:
PUBLIC
PROC[file: Handle, size: File.PageCount] =
{ 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 ] =
BEGIN
minRun: INT ← size / minFactor; -- smallest run we will accept; decreased if necessary
DO
IF create
THEN Lock[file, exclusive]
ELSE Acquire[file, exclusive];
BEGIN
startPulse: FileStats.Pulses = GetPulses[];
delta: INT = size-file.size;
SELECT
TRUE
FROM
delta > 0 =>
BEGIN
ENABLE File.Error =>
BEGIN
lack: INT = size-file.size; -- calculate it while we still have the file locked
IF why = volumeFull
THEN
BEGIN
We know that the disk run-table matches the in-core one (???).
Unlock[file];
IF FileInternal.Flush[file.volume, lack] THEN LOOP;
IF File.GetVolumePages[file.volume].free >= lack
THEN { Incr[hardExtends, delta, startPulse]; minRun ← minRun / 2; LOOP };
END
ELSE
BEGIN
IF NOT create -- core run-table # disk, so close the file; let DoOpen recover.
THEN { file.state ← none; FileInternal.FreeHeaderVM[file] };
Unlock[file];
END;
Otherwise, let the error propagate to our client
END;
Extend[file, delta, minRun, report, VMBackingCreate];
Incr[extend, delta, startPulse];
END;
delta < 0 =>
BEGIN
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];
END;
ENDCASE => NULL;
END;
Unlock[file];
EXIT
ENDLOOP;
END;
--File.--
Info:
PUBLIC
PROC[file: Handle]
RETURNS[volume: File.Volume, fp: File.FP, size: File.PageCount] =
BEGIN
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
volume ← file.volume; fp ← file.fp; size ← file.size;
END;
Unlock[file];
END;
--File.--
SetRoot:
PUBLIC
PROC[root: File.VolumeFile, file: Handle, page: File.PageNumber ← [0]] =
TRUSTED
BEGIN
Acquire[file, shared];
BEGIN
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];
END;
Unlock[file];
BEGIN
ENABLE File.Error => CONTINUE;
IF root = VM
AND File.SystemVolume[] # NIL
AND File.IsDebugger[File.SystemVolume[]] = File.IsDebugger[file.volume]
THEN RegisterVMFile[file];
END;
END;
--FileInternal.--
GetFileLocation:
PUBLIC
PROC[file: Handle, firstPage: File.PageNumber]
RETURNS[location: BootFile.Location] =
TRUSTED
BEGIN
Acquire[file, shared];
BEGIN
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];
END;
Unlock[file];
END;
--File.--
Read:
PUBLIC
UNSAFE
PROC[file: Handle,
from: File.PageNumber,
nPages: File.PageCount,
to: LONG POINTER] =
BEGIN
IF from < 0 THEN ERROR File.Error[unknownPage];
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
Transfer[file: file, data: to, filePage: from, nPages: nPages, action: read, where: data];
Incr[read, nPages, startPulse];
END;
Unlock[file];
END;
--File.--
Write:
PUBLIC
PROC[file: Handle,
to: File.PageNumber,
nPages: File.PageCount,
from: LONG POINTER] =
BEGIN
IF to < 0 THEN ERROR File.Error[unknownPage];
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
startPulse: FileStats.Pulses = GetPulses[];
Transfer[file: file, data: from, filePage: to, nPages: nPages, action: write, where: data];
Incr[write, nPages, startPulse];
END;
Unlock[file];
END;
--File.--
GetProperties:
PUBLIC
PROC[file: Handle]
RETURNS[p: File.PropertyStorage] =
BEGIN
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
p ← file.properties;
END;
Unlock[file];
END;
--File.--
WriteProperties:
PUBLIC
PROC[file: Handle] =
TRUSTED
BEGIN
Acquire[file, shared];
BEGIN
ENABLE File.Error => Unlock[file];
Transfer[file: file, data: file.properties,
filePage: [file.logicalRunTable.headerPages-propFilePages],
nPages: propFilePages, action: write, where: header]
END;
Unlock[file];
END;
END.