Dependencies.mesa
last edited by Paul Rovner on December 3, 1983 12:52 pm
DIRECTORY
Ascii USING [Lower],
BcdDefs
USING [
BcdBase, FTHandle, FTIndex, NameRecord, NameString],
BcdOps USING [ProcessFiles],
Commander USING [CommandProc, Register, Handle],
CommandTool USING [ArgumentVector, Parse, Failed],
DFInternal
USING [
AbortDF, GetFileInfo, LocalFile, LocalFileInfo, RemoteFileInfo, ReportFSError, RetryFSOperation],
DFUtilities
USING [
Date, DirectoryItem, FileItem, Filter, ImportsItem, IncludeItem, ParseFromStream, ProcessItemProc, RemoveVersionNumber, SyntaxError],
FS USING [Close, Error, GetInfo, Open, OpenFile, PagesForBytes, Read, StreamOpen],
IO USING [card, int, Close, GetIndex, rope, STREAM, PutF, Put, PutRope, PutChar],
IOClasses USING [CreateDribbleOutputStream],
List USING [CompareProc, Sort],
ProcessExtras USING [CheckForAbort],
Rope USING [Compare, Concat, Equal, Fetch, Find, FromProc, Index, Length, ROPE, Substr, SkipTo],
VM USING [AddressForPageNumber, Allocate, Free, Interval, nullInterval, PageCount];
Dependencies:
CEDAR
PROGRAM
IMPORTS Ascii, BcdOps, Commander, CommandTool, DFInternal, DFUtilities, FS, IO, IOClasses, List, ProcessExtras, Rope, VM
= BEGIN
OPEN Int: DFInternal, Utils: DFUtilities;
ROPE: TYPE = Rope.ROPE;
FileDesc:
TYPE =
RECORD [
shortName: ROPE ← NIL,
path: ROPE ← NIL,
importedFrom: REF FileDesc ← NIL, -- highest level Imports with Using containing 'shortName'
parent: ROPE ← NIL, -- DF file containing defining occurrence of 'shortName'
date: Utils.Date ← [],
dependers: LIST OF REF ANY ← NIL,
ofInterest: BOOL ← FALSE
];
htSize: NAT = 97;
HashIndex: TYPE = [0..htSize);
HashTable: TYPE = REF HashTableArray;
HashTableArray: TYPE = ARRAY HashIndex OF LIST OF REF FileDesc;
cacheSize: NAT = 10;
Construct:
PROC [dfFile:
ROPE, cmd: Commander.Handle]
RETURNS [errors, warnings, filesActedUpon: INT ← 0] = {
logFileStream: IO.STREAM ← FS.StreamOpen[fileName: "Dependencies.log", accessOptions: $create];
log: IO.STREAM ← IOClasses.CreateDribbleOutputStream[cmd.out, logFileStream];
rootList: LIST OF REF FileDesc ← NIL;
hashTable: HashTable = NEW[HashTableArray ← ALL[NIL]];
bcdCache: BcdCache = CreateBcdCache[cacheSize];
importedFrom: REF FileDesc ← NIL;
Hash:
PROC [name:
ROPE]
RETURNS [HashIndex] = {
x: NAT ← name.Length[];
FOR i: INT IN [0..x) DO x ← x + (Ascii.Lower[name.Fetch[i]] - 0C); ENDLOOP;
RETURN[x MOD htSize]
};
EnterInHashTable:
PROC [desc:
REF FileDesc]
RETURNS [BOOL ← TRUE] = {
hi: HashIndex = Hash[desc.shortName];
FOR l:
LIST
OF
REF FileDesc ← hashTable[hi], l.rest
UNTIL l =
NIL
DO
IF desc.shortName.Equal[l.first.shortName,
FALSE]
THEN {
IF desc.date ~= l.first.date
THEN {
duplicate short file name with different file creation dates
warnings ← warnings.SUCC;
log.PutF[
"Warning: '%g' appears more than once (via '%g' and '%g').",
IO.rope[desc.shortName],
IO.rope[
IF l.first.importedFrom = NIL THEN l.first.parent
ELSE FullName[l.first.importedFrom]
],
IO.rope[
IF desc.importedFrom = NIL THEN desc.parent
ELSE FullName[desc.importedFrom]
]
];
};
RETURN[FALSE]
};
ENDLOOP;
hashTable[hi] ← CONS[desc, hashTable[hi]];
filesActedUpon ← filesActedUpon.SUCC;
};
LookupInHashTable:
PROC [shortName:
ROPE]
RETURNS [desc:
REF FileDesc ←
NIL] = {
FOR l:
LIST
OF
REF FileDesc ← hashTable[Hash[shortName]], l.rest
UNTIL l =
NIL
DO
IF shortName.Equal[l.first.shortName, FALSE] THEN RETURN[l.first];
ENDLOOP;
};
EnumerateHashTable:
PROC [proc:
PROC [
REF FileDesc]] = {
FOR hi: HashIndex
IN HashIndex
DO
FOR l:
LIST
OF
REF FileDesc ← hashTable[hi], l.rest
UNTIL l =
NIL
DO
proc[l.first];
ENDLOOP;
ENDLOOP;
};
WorthRemembering:
PROC [desc:
REF FileDesc]
RETURNS [
BOOL ←
FALSE] = {
ext: ROPE = desc.shortName.Substr[start: desc.shortName.Index[s2: "."]];
IF ext.Equal[".bcd", FALSE] THEN RETURN[TRUE];
};
ConstructInner:
PROC [dfFile:
ROPE, date: Utils.Date, filter: Utils.Filter, nestingDepth:
NAT]
RETURNS [finished: BOOL ← FALSE] = {
directoryPath: ROPE ← NIL;
DoOneItem: Utils.ProcessItemProc = {
ProcessExtras.CheckForAbort[];
WITH item
SELECT
FROM
directory:
REF Utils.DirectoryItem =>
directoryPath ← directory.path1;
file:
REF Utils.FileItem => {
desc:
REF FileDesc =
NEW[FileDesc ← [
shortName: Utils.RemoveVersionNumber[file.name],
path: directoryPath,
parent: dfFile,
importedFrom: importedFrom
]];
remoteInfo:
REF Int.RemoteFileInfo =
NEW[Int.RemoteFileInfo ← [
name: FullName[desc],
date: file.date
]];
Int.GetFileInfo[info: remoteInfo, client: NIL, errorLevel: $warning
! FS.Error => CONTINUE
];
desc.date ← remoteInfo.date;
IF filter.list ~= NIL OR WorthRemembering[desc] THEN [] ← EnterInHashTable[desc];
AND
file.verifyRoot AND importedFrom = NIL THEN
rootList ← CONS[desc, rootList];
};
imports:
REF Utils.ImportsItem =>
IF imports.form ~= $list
AND filter.list =
NIL
THEN {
warnings ← warnings.SUCC;
log.PutF[
"Warning: '%g' appears in an Imports statement (in '%g') without a Using list.\n",
IO.rope[imports.path1],
IO.rope[dfFile]
];
could check here for imports.path1 awready seen
[] ← ConstructInner[imports.path1, imports.date, filter, nestingDepth + 1];
}
ELSE {
outerMostImports: BOOL = (filter.list = NIL);
newFilter: Utils.Filter = [
comments: filter.comments, -- comments processing is unaffected by imports
filterA: filter.filterA, -- source/derived distinction is unaffected by imports
filterB: IF imports.form = $exports THEN $public ELSE filter.filterB,
filterC: $all, -- if the top level passes imports, they can come from anywhere
list: IF imports.form = $list THEN imports.list ELSE filter.list
];
IF outerMostImports
THEN
importedFrom ←
NEW[FileDesc ← [
path: imports.path1, -- hack: shortName is NIL, but only CheckIfNeeded cares.
date: imports.date,
parent: dfFile
]];
IF ConstructInner[imports.path1, imports.date, newFilter, nestingDepth + 1]
AND outerMostImports
THEN {
FOR i:
NAT
IN [0..imports.list.nEntries)
DO
desc: REF FileDesc = LookupInHashTable[imports.list.u[i].name];
IF desc =
NIL
THEN {
warnings ← warnings.SUCC;
log.PutF[
"Warning: '%g' could not be found inside '%g' (or any nested DF file).\n",
IO.rope[imports.list.u[i].name],
IO.rope[imports.path1]
];
};
ENDLOOP;
importedFrom ← NIL;
};
};
include:
REF Utils.IncludeItem =>
[] ← ConstructInner[include.path1, include.date, filter, nestingDepth + 1];
ENDCASE;
}; -- end DoOneItem
dfInfo: REF Int.RemoteFileInfo = NEW[Int.RemoteFileInfo ← [name: dfFile, date: date]];
dfStream: IO.STREAM;
Int.GetFileInfo[info: dfInfo, client: NIL ! FS.Error => {errors ← errors.SUCC; GO TO skip}];
dfStream ←
FS.StreamOpen[fileName: dfInfo.name
! FS.Error => {errors ← errors.SUCC; Int.ReportFSError[error, dfInfo, NIL]; GO TO skip}
];
dfInfo.name ← Utils.RemoveVersionNumber[dfInfo.name];
FOR i: NAT IN [1..nestingDepth] DO log.PutRope[" "] ENDLOOP;
log.Put[IO.rope["starting to look at "], IO.rope[dfInfo.name], IO.rope["\n"]];
Utils.ParseFromStream[dfStream, DoOneItem, filter !
Utils.SyntaxError
-- [reason: ROPE]-- => {
errors ← errors.SUCC;
log.PutF[
"Error: Syntax error in '%g'[%d]: %g\NProcessing of this DF file aborted.",
IO.rope[dfInfo.name], IO.card[dfStream.GetIndex[]], IO.rope[reason]
];
CONTINUE
};
ABORTED => dfStream.Close[];
];
dfStream.Close[];
FOR i: NAT IN [1..nestingDepth] DO log.PutRope[" "] ENDLOOP;
log.Put[IO.rope["finished looking at "], IO.rope[dfInfo.name], IO.rope["\n"]];
RETURN[TRUE];
}; -- end ConstructInner
START Construct HERE
IF Int.LocalFile[dfFile]
THEN {
dfInfo: REF Int.LocalFileInfo = NEW[Int.LocalFileInfo ← [name: dfFile]];
Int.GetFileInfo[info: dfInfo, client: NIL, errorLevel: $abort];
IF (dfFile ← dfInfo.attachedTo) =
NIL
THEN {
warnings ← warnings.SUCC;
log.PutF[
"Warning: '%g' isn't a remote file and therefore dependencies can't be analyzed.",
IO.rope[dfInfo.name]
];
};
};
BEGIN
ENABLE
BEGIN
ABORTED => {
errors ← errors.SUCC;
log.Put[IO.rope["Error: ABORT looking at "], IO.rope[dfFile], IO.rope["\n"]];
We would like to RESUME at this point, but until ABORTED is redeclared as a SIGNAL, it won't work.
};
Int.AbortDF => {
errors ← errors.SUCC;
log.Put[IO.rope["Error: ABORT looking at "], IO.rope[dfFile], IO.rope["\n"]];
CONTINUE
};
END;
The following is a terrible cheat, since the date is technically illegal. However, the (desired!) effect is to treat a version number on 'dfFile' as truth (i.e., it won't be stripped off by Int.GetFileInfo.)
IF ConstructInner[dfFile, [format: $explicit], [], 0]
THEN {
lookAtBCDFile:
PROC [depender:
REF FileDesc] = {
parentBcd: BcdDefs.BcdBase;
IF ~WorthRemembering[depender] THEN RETURN;
parentBcd ← GetBcd[bcdCache, depender
!
FS.Error =>
IF Int.RetryFSOperation[error, NIL] THEN RETRY
ELSE {
errors ← errors.SUCC;
log.Put[IO.rope["Error: Can't get BCD file named "], IO.rope[depender.shortName], IO.rope["\n"]];
GOTO skipThisBCD
}
];
TRUSTED {
IF parentBcd.nConfigs = 0
THEN {
DoOneFile:
PROC [fth: BcdDefs.FTHandle, fti: BcdDefs.FTIndex]
RETURNS [BOOL ← FALSE] = TRUSTED {
RopeForNameRecord:
PROC [bcd: BcdDefs.BcdBase, name: BcdDefs.NameRecord]
RETURNS [r: ROPE] = TRUSTED {
ssb: BcdDefs.NameString = LOOPHOLE[bcd + bcd.ssOffset];
len: NAT;
i: INT ← name;
GetFromNameString:
SAFE
PROC
RETURNS [char:
CHAR] =
TRUSTED {
char ← ssb.string[i]; i ← i + 1};
r ← Rope.FromProc[ssb.size[name], GetFromNameString];
len ← r.Length[];
IF len > 0 AND r.Fetch[len-1] = '. THEN r ← r.Substr[len: len-1];
};
file: ROPE ← Rope.Concat[RopeForNameRecord[parentBcd, fth.name], ".bcd"];
dependee: REF FileDesc ← LookupInHashTable[file];
IF dependee =
NIL
THEN {
warnings ← warnings.SUCC;
log.PutRope["Warning: "];
log.Put[
IO.rope[depender.shortName],
IO.rope[" depends on "],
IO.rope[file]
];
log.Put[
IO.rope[", but "],
IO.rope[file],
IO.rope[" was not found in any DF file\n"]
];
[] ← EnterInHashTable[dependee ← NEW[FileDesc ← [shortName: file]]];
};
here with depender depends on dependee
dependee.dependers ← CONS[depender, dependee.dependers];
}; -- end DoOneFile
depender.ofInterest ← TRUE;
[] ← BcdOps.ProcessFiles[parentBcd, DoOneFile];
}; -- end parentBcd.nConfigs = 0
}; -- end TRUSTED
ReleaseBcd[bcdCache, parentBcd];
EXITS skipThisBCD => RETURN;
}; -- end lookAtBCDFile
buildList:
PROC [dependee:
REF FileDesc] = {
listOfFileDescRefs ← CONS[dependee, listOfFileDescRefs];
};
compare: List.CompareProc = {
PROC[ref1: REF ANY, ref2: REF ANY] RETURNS [Comparison];
f1: REF FileDesc = NARROW[ref1];
f2: REF FileDesc = NARROW[ref2];
RETURN[f1.shortName.Compare[f2.shortName, FALSE]];
};
printDependencies:
PROC [dependee:
REF FileDesc] = {
lineLength: NAT ← 0;
IF NOT dependee.ofInterest THEN RETURN;
IF dependee.dependers =
NIL
THEN {
log.Put[IO.rope["No interface or program module was found to depend on "], IO.rope[dependee.shortName]];
log.PutChar['\n];
RETURN;
};
out.PutRope[dependee.shortName.Substr[0, dependee.shortName.SkipTo[0, "."]]];
out.PutChar['\n];
out.PutChar['\t];
dependee.dependers ← List.Sort[dependee.dependers, compare];
FOR fdl:
LIST
OF
REF
ANY ← dependee.dependers, fdl.rest
UNTIL fdl =
NIL
DO
fd: REF FileDesc = NARROW[fdl.first];
name: ROPE ← fd.shortName.Substr[0, fd.shortName.SkipTo[0, "."]];
lineLength ← lineLength + name.Length[];
IF lineLength > 72
AND lineLength # name.Length[]
THEN {out.PutRope["\n\t"]; lineLength ← name.Length[]};
out.PutRope[name];
IF fdl.rest = NIL THEN out.PutRope["\n"] ELSE out.PutRope[" "]
ENDLOOP;
}; -- end printDependencies
The hash table has now been constructed.
out: IO.STREAM = FS.StreamOpen[fileName: "Dependencies.txt", accessOptions: $create];
listOfFileDescRefs: LIST OF REF ANY ← NIL;
EnumerateHashTable[lookAtBCDFile];
out.PutRope["List of BCD file dependencies from "];
out.PutRope[dfFile];
out.PutRope["\n\n"];
EnumerateHashTable[buildList];
listOfFileDescRefs ← List.Sort[listOfFileDescRefs, compare];
FOR l:
LIST
OF
REF
ANY ← listOfFileDescRefs, l.rest
UNTIL l =
NIL
DO
printDependencies[NARROW[l.first]];
ENDLOOP;
out.PutRope["\nEND of list of BCD file dependencies from "];
out.PutRope[dfFile];
out.PutRope["\n"];
out.Close[];
log.Put[
IO.rope["\n***BCD dependencies from "],
IO.rope[dfFile],
IO.rope[" written onto Dependencies.txt"]
];
IF errors # 0
OR warnings # 0
THEN {
log.PutRope["\n*** "];
log.Put[
IO.int[errors],
IO.rope[" errors and "],
IO.int[warnings]
];
log.PutRope[" warnings written onto Dependencies.log\n"];
}
ELSE log.PutRope[".\n"];
}; -- end IF ConstructInner[dfFile, [format: $explicit], [], 0] THEN
END; -- ENABLE
logFileStream.Close[];
}; -- end Construct
Internal procedures
BcdCache: TYPE = REF BcdCacheObject;
BcdCacheObject:
TYPE =
RECORD [
locked: CachedBcdList ← NIL, -- linear list
available: CachedBcdList ← NIL, -- circularly chained
size: NAT ← 0,
replacementSize: NAT
];
CachedBcdList: TYPE = LIST OF CachedBcd;
CachedBcd: TYPE = REF CachedBcdEntry;
CachedBcdEntry:
TYPE =
RECORD [
buffer: VM.Interval ← VM.nullInterval,
desc: REF FileDesc ← NIL
];
initialVM: VM.PageCount = 10;
A bcd cache is managed as two singly-linked lists of cache entries. The 'available' list consists of cached bcd's that are eligible for replacement. The 'locked' list consists of cached bcd's that are actually being touched; they cannot be replaced until they are moved to the 'available' list. The maximum size of the two lists is (almost) bounded by a creation-time parameter; however, if the 'available' list is empty when a new entry is needed, the entry will be created regardless of the size bound.
Cache replacement occurs in the 'available' list in LRU order. New cache entries appear at the tail of the list; victims are taken from the head. BcdCache.available points at the logical tail of the list, that is, the MRU entry, and BcdCache.list.rest points at the logical head, the LRU entry.
CreateBcdCache:
PROC [replacementSize:
NAT]
RETURNS [bcdCache: BcdCache] = {
RETURN[NEW[BcdCacheObject ← [replacementSize: replacementSize]]]
};
GetBcd:
PROC [bcdCache: BcdCache, desc:
REF FileDesc]
RETURNS [bcd: BcdDefs.BcdBase ← NIL] = {
prev: CachedBcdList ← bcdCache.available;
new: CachedBcd ← NIL;
list: CachedBcdList ← NIL;
NewEntry:
PROC
RETURNS [CachedBcdList] = {
bcdCache.size ← bcdCache.size.SUCC;
RETURN[CONS[NEW[CachedBcdEntry ← []], NIL]]
};
SELECT
TRUE
FROM
prev =
NIL =>
'available' list is empty. Create a new cache entry regardless of present cache size.
list ← NewEntry[];
prev = prev.rest => {
'available' list has precisely one entry, which may or may not be the file of interest.
list ← bcdCache.available;
bcdCache.available ← NIL;
IF list.first.desc ~= desc THEN list.first.desc ← NIL;
};
ENDCASE => {
'available' list has at least two entries.
list ← prev.rest;
DO
assert: list = prev.rest
IF list.first.desc = desc THEN GO TO dequeue; -- 'list.first' is a cache hit
prev ← list;
IF (list ← list.rest) = bcdCache.available.rest
THEN {
cache miss.
IF bcdCache.size < bcdCache.replacementSize THEN {list ← NewEntry[]; EXIT}
ELSE {list.first.desc ← NIL; GO TO dequeue};
};
REPEAT
dequeue => {
prev.rest ← list.rest;
IF bcdCache.available = list THEN bcdCache.available ← list.rest;
};
ENDLOOP;
};
'list' is a single element list (although list.rest may be garbage) containing the CachedBcd to be (re)used. We link it on the 'locked' list.
list.rest ← bcdCache.locked;
bcdCache.locked ← list;
We now have a cache entry, which either is empty or has the desired file.
IF (new ← list.first).desc =
NIL
THEN {
ENABLE
UNWIND => {
bcdCache.locked ← bcdCache.locked.rest;
bcdCache.size ← bcdCache.size.PRED;
};
name: ROPE = FullName[desc];
file: FS.OpenFile;
nPages: INT;
file ← FS.Open[name: name, wantedCreatedTime: desc.date.gmt];
IF new.buffer.count = 0 THEN new.buffer ← VM.Allocate[initialVM];
nPages ← MIN[FS.PagesForBytes[FS.GetInfo[file].bytes], new.buffer.count];
TRUSTED {
bcd ← VM.AddressForPageNumber[new.buffer.page];
FS.Read[file: file, from: 0, nPages: nPages, to: bcd];
IF bcd.nPages > nPages
THEN {
buffer too small; grow it.
nPages ← bcd.nPages;
VM.Free[new.buffer];
new.buffer ← VM.Allocate[nPages];
bcd ← VM.AddressForPageNumber[new.buffer.page];
FS.Read[file: file, from: 0, nPages: nPages, to: bcd];
};
};
FS.Close[file];
new.desc ← desc;
}
ELSE TRUSTED {bcd ← VM.AddressForPageNumber[new.buffer.page]};
};
ReleaseBcd:
PROC [bcdCache: BcdCache, bcd: BcdDefs.BcdBase] = {
list: CachedBcdList ← bcdCache.locked;
prev: CachedBcdList ← NIL;
UNTIL list =
NIL
DO
TRUSTED {IF VM.AddressForPageNumber[list.first.buffer.page] = bcd THEN EXIT};
prev ← list;
list ← list.rest;
REPEAT
FINISHED => ERROR;
ENDLOOP;
dequeue from 'locked' list.
IF prev = NIL THEN bcdCache.locked ← list.rest ELSE prev.rest ← list.rest;
enqueue on 'available' list.
IF bcdCache.available = NIL THEN list.rest ← list
ELSE {list.rest ← bcdCache.available.rest; bcdCache.available.rest ← list};
bcdCache.available ← list;
};
FlushBcdCache:
PROC [bcdCache: BcdCache] = {
list: CachedBcdList;
flush 'locked' list.
FOR list ← bcdCache.locked, list.rest
UNTIL list =
NIL
DO
TRUSTED {VM.Free[list.first.buffer]};
ENDLOOP;
bcdCache.locked ← NIL;
IF bcdCache.available = NIL THEN RETURN;
list ← bcdCache.available.rest; -- head of 'available' list
bcdCache.available.rest ← NIL; -- break circular chain
bcdCache.available ← NIL;
UNTIL list =
NIL
DO
TRUSTED {VM.Free[list.first.buffer]};
list ← list.rest;
ENDLOOP;
};
FullName:
PROC [desc:
REF FileDesc]
RETURNS [
ROPE] =
INLINE {
RETURN[desc.path.Concat[desc.shortName]]
};
DoDependencies: Commander.CommandProc = {
PROC [cmd: Commander.Handle] RETURNS [result: REF ← NIL, msg: Rope.ROPE ← NIL]
dfFileName: ROPE ← NIL;
length: NAT;
argv: CommandTool.ArgumentVector ← NIL;
argv ← CommandTool.Parse[cmd ! CommandTool.Failed => { msg ← errorMsg; CONTINUE; }];
IF argv = NIL THEN RETURN[$Failure, msg];
IF argv.argc # 2 THEN RETURN[$Failure, "Usage: Dependencies dfFileName\n"];
dfFileName ← argv[1];
length ← dfFileName.Length[];
IF length < 4
OR (Rope.Compare[Rope.Substr[dfFileName, length - 3, 3], ".df",
FALSE] # equal
AND Rope.Find[dfFileName, "!", MAX[0, length-5]] = -1)
THEN dfFileName ← Rope.Concat[dfFileName, ".df"];
[] ← Construct[dfFileName, cmd];
}; -- end DoDependencies
START HERE
Commander.Register[
"Dependencies", DoDependencies, "Build a list of bcd dependencies from a df file."
];
END.