SymbolFindingImpl.mesa
Sturgis, November 2, 1989 2:55:32 pm PST
Last changed by Theimer on November 1, 1989 10:30:26 am PST
Coolidge, July 11, 1990 11:25 am PDT
DIRECTORY
Atom USING[MakeAtom],
BasicTime USING[GMT, Now, Pack, Period, Update],
CirioNubAccess USING[FileEntry, Handle, LookupSymEntryResult, LookupSymEntryResultBody, LookupSymEntryByID, PCInfo, PCtoInfo, Read32BitsAsCard, ReadBytes, RemoteAddress],
Convert USING[CardFromRope, Error, RopeFromCard],
Commander USING[CommandProc, Register],
CommandTool USING[ArgumentVector, Parse],
DotOAccess USING[CreateDotOCookie, DotOCookie, EmbeddedDotO, EmbeddedDotOInfo, FindEmbeddedDotOStabRange, FindVersionStamp, GetEmbeddedDotO, GetEmbeddedDotOInfo, VersionStampInfo],
FS USING[EnumerateForNames, EnumerateForInfo, Error, InfoProc, NameProc, StreamOpen],
IO USING[Close, EndOf, GetChar, PutFR, rope, STREAM],
MobAccess USING[CreateMobCookie, MobCookie, ReadMobVersionStamp],
MobDefs USING[VersionStamp],
MobDotOAccess USING[CreateJointMobDotOInfo, JointMobDotOInfo],
PBasics USING[BITXOR, LongNumber],
PFS USING [RopeFromPath, PathFromRope, InfoProc],
PFSNames USING [PATH, Component, ShortName, ComponentRope, Equal],
RefTab USING[Create, Fetch, Key, Insert, Ref],
Rope USING[Cat, Equal, Fetch, Find, FindBackward, FromRefText, Length, Replace, ROPE, Substr],
RopeSequence USING [RopeSeq, RopePart, PartFromRope, RopeFromPart, ParsePartToSeq, UnparseSeqToPart, ComponentCount, Fetch, ConstructSeq],
RuntimeError USING[BoundsFault],
SymbolFinding USING[DotODesc, FoundSymbols, ShowReport, FactoredUnixFileName],
SystemInterface USING [CirioFile, FileSet, GetCirioFile, MachineDependentSubdirectoryName],
UnixRemoteFile USING[CreateHandle, OpenReadStream, UnixServerHandle];
SymbolFindingImpl: CEDAR PROGRAM IMPORTS Atom, BasicTime, CirioNubAccess, Commander, CommandTool, Convert, DotOAccess, FS, IO, MobAccess, MobDotOAccess, PBasics, PFS, PFSNames, RefTab, Rope, RopeSequence, RuntimeError, SymbolFinding, SystemInterface, UnixRemoteFile EXPORTS SymbolFinding =
BEGIN OPEN DOA: DotOAccess, MA: MobAccess, MDA: MobDotOAccess, SymbolFinding;
PATH: TYPE ~ PFSNames.PATH;
Component: TYPE ~ PFSNames.Component;
RopePart: TYPE ~ RopeSequence.RopePart;
RopeSeq: TYPE ~ RopeSequence.RopeSeq;
FoundSymbols: TYPE = SymbolFinding.FoundSymbols;
global code
SymbolInfo: TYPE = REF SymbolInfoBody;
SymbolInfoBody: PUBLIC TYPE = RECORD[
fileSet: SystemInterface.FileSet,
doaHash: DotOHashTable,
mobHash: MobHashTable,
cacheFlushTime: BasicTime.GMT];
CreateSymbolInfo: PUBLIC PROC[fileSet: SystemInterface.FileSet] RETURNS[SymbolInfo] =
BEGIN
si: SymbolInfo ← NEW[SymbolInfoBody←[
fileSet: fileSet,
doaHash: CreateDotOHashTable[],
mobHash: CreateMobHashTable[],
cacheFlushTime: BasicTime.Now[]]];
RETURN[si];
END;
FlushSymbolFileCache: PUBLIC PROC[si: SymbolInfo] =
BEGIN
si.cacheFlushTime ← BasicTime.Now[];
END;
FindSymbols: PUBLIC PROC[serverName: Rope.ROPE, nub: CirioNubAccess.Handle, desc: SymbolFinding.DotODesc, absPC: CARD, si: SymbolInfo, searchDirectories: LIST OF PATH] RETURNS[FoundSymbols] =
BEGIN
factoredName: FactoredUnixFileName ← FactorUnixFileName[desc.fileInfo.fileName];
foundDotO: FoundDotO ← FindC2CDotO[factoredName, serverName, nub, desc, absPC, si];
IF foundDotO.dotO = NIL THEN RETURN[[NIL, NIL, NIL, NIL]]
ELSE IF foundDotO.vsi = NIL THEN RETURN[[foundDotO.dotO, foundDotO.embedded, NIL, NIL]]
ELSE
BEGIN
ENABLE NoSymbols => GOTO mesaFails;
tailPos: INT;
embeddedInfo: REF DotOAccess.EmbeddedDotOInfo ← DOA.GetEmbeddedDotOInfo[foundDotO.embedded];
The next line breaks the shortName (last component of the part) into a RopeSeq
split on .'s (i.e., the stem and extensions).
embeddedFileName: RopeSeq ← RopeSequence.PartFromRope[embeddedInfo.fileName.ShortName.ComponentRope].
ParsePartToSeq['.];
embeddedStem: RopePart;
stamp: MobDefs.VersionStamp;
mob: MA.MobCookie;
IF embeddedFileName.ComponentCount = 1 THEN NoSymbols[Rope.Cat["mesa for ", PFS.RopeFromPath[embeddedInfo.fileName]]]
ELSE embeddedStem ← SELECT embeddedFileName.ComponentCount FROM
2 => IF embeddedFileName.Fetch[1].RopeFromPart.Equal["c"] THEN embeddedFileName.Fetch[0] ELSE NoSymbols[Rope.Cat["mesa for ", PFS.RopeFromPath[embeddedInfo.fileName]]],
3 => IF embeddedFileName.Fetch[1].RopeFromPart.Equal["c2c"] AND embeddedFileName.Fetch[2].RopeFromPart.Equal["c"] THEN
embeddedFileName.Fetch[0] ELSE NoSymbols[Rope.Cat["mesa for ", PFS.RopeFromPath[embeddedInfo.fileName]]],
ENDCASE => RopeSequence.PartFromRope[NoSymbols[Rope.Cat["mesa for ", PFS.RopeFromPath[embeddedInfo.fileName]]]];
stamp ← ConvertDotOFormatVersionStampToMobFormat[foundDotO.vsi.contents, embeddedStem];
mob ← FindMob[stamp, factoredName, embeddedStem, serverName, si, searchDirectories];
IF mob = NIL THEN GOTO mesaFails
ELSE
BEGIN
jmdi: MDA.JointMobDotOInfo ← MDA.CreateJointMobDotOInfo[mob, foundDotO.dotO, foundDotO.embedded];
RETURN[[foundDotO.dotO, foundDotO.embedded, mob, jmdi]];
END;
EXITS
mesaFails => RETURN[[foundDotO.dotO, foundDotO.embedded, NIL, NIL]];
END;
END;
NoSymbols: ERROR[cantFind: Rope.ROPE] = CODE;
ConvertDotOFormatVersionStampToMobFormat: PROC[dotOVersionStamp: Rope.ROPE, nameStem: RopePart] RETURNS[MobDefs.VersionStamp] =
BEGIN
ENABLE
BEGIN
RuntimeError.BoundsFault => GOTO fails;
Convert.Error => GOTO fails;
END;
expectedPreamble: Rope.ROPE ← Rope.Cat["@", "(#)", "mob←version ["];
note: the version stamp key is broken into pieces so that it won't look like a version stamp in the various files.
expectedPostamble: Rope.ROPE ← Rope.Cat["] ", nameStem.RopeFromPart];
stampLength: INT ← Rope.Length[dotOVersionStamp];
preambleLength: INT ← Rope.Length[expectedPreamble];
postambleLength: INT ← Rope.Length[expectedPostamble];
preamble: Rope.ROPE ← Rope.Substr[dotOVersionStamp, 0, preambleLength];
postamble: Rope.ROPE ← Rope.Substr[dotOVersionStamp, stampLength-postambleLength, postambleLength];
digits: Rope.ROPE ← Rope.Substr[dotOVersionStamp, preambleLength, stampLength-preambleLength-postambleLength];
comma: INT ← Rope.Find[digits, ","];
digits1: Rope.ROPE ← Rope.Substr[digits, 0, comma];
digits2: Rope.ROPE ← Rope.Substr[digits, comma+1, Rope.Length[digits]-comma-1];
stamp: MobDefs.VersionStamp ← [Convert.CardFromRope[digits1], Convert.CardFromRope[digits2]];
IF NOT Rope.Equal[preamble, expectedPreamble] THEN NoSymbols[dotOVersionStamp];
IF NOT Rope.Equal[postamble, expectedPostamble, FALSE] THEN NoSymbols[dotOVersionStamp];
RETURN[stamp];
EXITS
fails => NoSymbols[dotOVersionStamp];
END;
Dot O location mechanism
FoundDotO: TYPE = RECORD[dotO: DOA.DotOCookie, embedded: DOA.EmbeddedDotO, vsi: REF DOA.VersionStampInfo];
This procedure differs from FindDotO only in that it performs some confirmations that can not be performed for arbitrary DotO files.
We assume that factoredName = FactorUnixFileName[longPathName]
There are several possibilities:
we did not find a dotO
we return NIL and NIL
the dotO does not have a version stamp
we return the dotO and a NIL vsi
the dotO has a version stamp, but it doesn't match memory
we return NIL and NIL
the dotO has a version stamp, and it matches memory
we return the dotO and the vsi
FindC2CDotO: PROC[factoredName: FactoredUnixFileName, serverName: Rope.ROPE, nub: CirioNubAccess.Handle, desc: SymbolFinding.DotODesc, absPC: CARD, si: SymbolInfo] RETURNS[FoundDotO] =
BEGIN
the following procedure is used only during a break point for random testing. See "PlantRandomTestBreakHere" below.
FindForTesting: PROC[relativePC: CARD] RETURNS[first: CARD, count: CARD] =
BEGIN
range: StabRange ← FindStabRange[nub, desc.fileInfo, relativePC+desc.fileInfo.textReloc, tentativeDotO];
IF range.limitX = range.firstX THEN RETURN[0, 0]
ELSE RETURN[range.firstX, range.limitX-range.firstX];
END;
tentativeDotO: DOA.DotOCookie ← FindDotO[factoredName, serverName, desc, si];
IF tentativeDotO = NIL THEN RETURN[[NIL, NIL]]
ELSE IF absPC < desc.fileInfo.textReloc OR desc.fileInfo.textReloc+ desc.fileInfo.textSize <= absPC THEN RETURN[[NIL, NIL]] -- probably in some breakpoint patch area
ELSE
BEGIN
stabRange: StabRange ← FindStabRange[nub, desc.fileInfo, absPC, tentativeDotO];
embedded: DOA.EmbeddedDotO ← DOA.GetEmbeddedDotO[tentativeDotO, stabRange.firstX, stabRange.limitX];
vsi: REF DOA.VersionStampInfo ← IF embedded # NIL THEN DOA.FindVersionStamp[embedded] ELSE NIL;
PlantRandomTestBreakHere for random test of FindStabRange.
execute
DotOAccessImpl.RandomTestOtherFindStabRange[4466, tentativeDotO, FindForTesting, &H.tsOutStream, 1000]
IF vsi = NIL THEN -- no version stamp
RETURN[[tentativeDotO, embedded, NIL]]
ELSE IF nub = NIL THEN -- no remote world
RETURN[[tentativeDotO, embedded, vsi]]
ELSE
BEGIN -- we have a version stamp and a live remote world, so check it
stampInMem: Rope.ROPE ← ReadCRope[RemoteAddrFromCard[nub, desc.fileInfo.dataReloc+vsi.relativeAddress]];
IF NOT Rope.Equal[vsi.contents, stampInMem] THEN RETURN[[NIL, NIL, NIL]]
ELSE RETURN[[tentativeDotO, embedded, vsi]];
END;
END;
END;
The assumption here is that, even if there is more than one possible place to look for the dotO file, if we find a file in any of those places with the right mtime and size, then it is the only possible candidate for the dotO. (Though it may still fail a subsequent check.)
We assume that factoredName = FactorUnixFileName[longPathName]
We use a rather simplified strategy. More complicated versions will try to open streams using our connection back to the SUN.
FindDotO: PROC[factoredName: FactoredUnixFileName, serverName: Rope.ROPE, desc: SymbolFinding.DotODesc, si: SymbolInfo] RETURNS[DOA.DotOCookie] =
BEGIN
key: ATOM ← CreateDotOKey[desc.fileInfo.fileName, desc.fileInfo.mtime, desc.fileInfo.size];
packagedDotO: PackagedDotO ← NARROW[RefTab.Fetch[si.doaHash.table, key].val];
IF packagedDotO = NIL THEN -- we haven't seen it before, so we have to go looking for it
BEGIN
dotO: DOA.DotOCookie ← NIL;
dotOShortName: PATHPFS.PathFromRope[RopeSequence.ConstructSeq[LIST[factoredName.stem, factoredName.secondaryExtension, factoredName.extension]].UnparseSeqToPart['.].RopeFromSeq];
mTimeAsGMT: BasicTime.GMT ← GMTFromSunTime[desc.fileInfo.mtime];
prefix: PATH ← CirioDeltaFace.GetOurPrefixForUnixPrefix[factoredName.volume, factoredName.name1, serverName];
fullPath: PATH ← prefix.Cat[
factoredName.remainingPath.Cat[factoredName.machineDependentSubdir]];
foundName: PATHNIL;
SeeDotOInfo: PFS.InfoProc =
PROC [
fullFName, attachedTo: PATH,
uniqueID: PFS.UniqueID,
bytes: INT,
keep: CARDINAL,
fileType: FileType
] RETURNS [continue: BOOL]
BEGIN
lets see if it satisfies our constraints
IF desc.fileInfo.mtime # 0 THEN -- we are supposed to check the file identity
BEGIN
IF umiqueID.time.egmt # mTimeAsGMT THEN RETURN[TRUE]; -- no
IF CARD[bytes] # desc.fileInfo.size THEN RETURN[TRUE]; -- no
END;
ok, we buy it
foundName ← fullFName;
RETURN[FALSE]; -- stop the iteration
END;
SymbolFinding.ShowReport[IO.PutFR["looking for dotO %g", IO.rope[PFS.RopeFromPath[dotOShortName]]]];
PFS.EnumerateForInfo[PFSNames.SetVersionNumber[fullPath.Cat[dotOShortName], factoredName.version], SeeDotOInfo];
IF foundName # NIL THEN -- we found it
BEGIN
file: SystemInterface.CirioFile ← SystemInterface.GetCirioFile[si.fileSet, foundName];
dotO ← DOA.CreateDotOCookie[file];
END;
ok, lets record the result of our hunt
packagedDotO ← NEW[DOA.DotOCookie ← dotO];
[] ← RefTab.Insert[si.doaHash.table, key, packagedDotO];
END;
RETURN[packagedDotO^];
END;
This procedure uses UnixRemoteFile for files which have remote server names of the form "foo-UX". Thus, we avoid copying the file onto the local D-machine disk cache. Copying would be particularly unfortunate for 15 megabyte dotO files.
If the file name is not of that form, then we use FS.StreamOpen.
At the moment, this code is disabled if the client calls with cachedOnly = TRUE. I tried it with "palain-UX" and "palain" as server names. Both times I got "ERROR UnixRemoteFileImpl.Error[code: $viewNotImplemented, msg: "Unix(tm) view not implemented by server"]" from UnixRemoteFileImpl.
In fact, I have removed all calls to this procedure, since it should really be embedded in SystemInterfaceImpl. (I left one call in the test code.)
OldOpenDotOStream: PROC[name: PATH, cachedOnly: BOOLEANFALSE] RETURNS[IO.STREAM] =
BEGIN
nameRope: ROPEPFS.RopeFromPath[name];
IF cachedOnly THEN RETURN[PFS.StreamOpen[name]]
ELSE
IF Rope.Fetch[nameRope, 0] = '/ THEN
BEGIN
uxLoc: INT ← Rope.Find[nameRope, "-UX/"];
secondSlash: INT ← Rope.Find[nameRope, "/", 1];
IF uxLoc > 0 AND secondSlash = uxLoc + 3 THEN
BEGIN
serverName: Rope.ROPE ← Rope.Cat[Rope.Substr[name, 1, uxLoc], "NFS"];
pathName: Rope.ROPE ← Rope.Substr[nameRope, uxLoc+3, Rope.Length[name]-uxLoc-3];
handle: UnixRemoteFile.UnixServerHandle ← UnixRemoteFile.CreateHandle[serverName];
RETURN[UnixRemoteFile.OpenReadStream[handle, [pathName]]];
END
ELSE RETURN[PFS.StreamOpen[name]];
END
ELSE IF Rope.Fetch[nameRope, 0] = '[ THEN
BEGIN
uxLoc: INT ← Rope.Find[nameRope, "-UX]"];
secondBracket: INT ← Rope.Find[nameRope, "]", 1];
IF uxLoc > 0 AND secondBracket = uxLoc + 3 THEN
BEGIN
UseSlashes: PROC[path: Rope.ROPE] RETURNS[Rope.ROPE] =
BEGIN
fixed: Rope.ROPE ← Rope.Cat["/", Rope.Substr[path, 1, Rope.Length[path]-1]];
lastFirstBracket: INT ← -1;
FOR firstBracketPos: INT ← Rope.Find[fixed, ">", lastFirstBracket+1], Rope.Find[fixed, ">", lastFirstBracket+1] WHILE firstBracketPos >= 0 DO
fixed ← Rope.Replace[fixed, firstBracketPos, 1, "/"];
lastFirstBracket ← firstBracketPos;
ENDLOOP;
RETURN[fixed];
END;
serverName: Rope.ROPE ← Rope.Cat[Rope.Substr[nameRope, 1, uxLoc], "NFS"];
pathName1: Rope.ROPE ← Rope.Substr[nameRope, uxLoc+4, Rope.Length[nameRope]-uxLoc-4];
pathName: Rope.ROPE ← UseSlashes[pathName1]; -- UnixRemoteFile insists upon the slash syntax
handle: UnixRemoteFile.UnixServerHandle ← UnixRemoteFile.CreateHandle[serverName];
RETURN[UnixRemoteFile.OpenReadStream[handle, [pathName]]];
END
ELSE RETURN[PFS.StreamOpen[name]];
END
ELSE RETURN[PFS.StreamOpen[name]];
END;
FactorUnixFileName: PUBLIC PROC[unixFileName: PATH] RETURNS[FactoredUnixFileName] =
BEGIN
ENABLE RuntimeError.BoundsFault => GOTO fails;
unixFileName: PATH ← unixFileName;
exit: BOOLEANFALSE;
cirioPrefix: PATH ← PFSNames.EmptyPath;
cirioRemainingFileName: PATH ← PFSNames.EmptyPath;
volume: PATH ← PFSNames.EmptyPath;
name1: PATH ← PFSNames.EmptyPath;
remainingPath: PATH ← PFSNames.EmptyPath;
machineDependentSubdir: PATH ← PFSNames.EmptyPath;
stem: RopePart;
secondaryExtension: RopePart;
extension: RopePart;
version: PFSNames.Version;
fileNameSeq: RopeSeq ← NIL;
tentativeRemainingPath: LIST OF Component ← NIL;
First, figure out volume
curPart: Component ← unixFileName.Fetch[1];
curPartRope: Rope.ROPE ← curPart.ComponentRope;
nextPart: INT ← 1;
IF Rope.Equal[curPartRope, "tmp←mnt", FALSE] THEN
BEGIN
curPart ← unixFileName.Fetch[2];
curPartRope ← curPart.ComponentRope;
IF Rope.Equal[curPartRope, "net", FALSE] THEN BEGIN
nextPart ← 3;
volume ← PFSNames.ConstructName[LIST[unixFileName.Fetch[0],unixFileName.Fetch[1],curPart], FALSE, TRUE];
END;
END
ELSE
IF Rope.Equal[curPartRope, "volume", FALSE] OR Rope.Equal[curPartRope, "net", FALSE] THEN
BEGIN
nextPart ← 2;
volume ← PFSNames.ConstructName[LIST[unixFileName.Fetch[0],curPart],FALSE,TRUE];
END;
IF volume = PFSNames.EmptyPath THEN volume ← PFSNames.ConstructName[LIST[unixFileName.Fetch[0]], FALSE, TRUE];
OK, that's done. Now for name1.
curPart ← unixFileName.Fetch[nextPart];
name1 ← PFSNames.ConstructName[LIST[curPart], FALSE, TRUE];
That was easy. Now to tackle remainingPath
FOR part: INT ← nextPart + 1, part+1 UNTIL part = unixFileName.ComponentCount-1 OR exit = TRUE DO
nextPart ← part+1;
curPart ← unixFileName.Fetch[part];
IF CirioDeltaFace.IsMachineDependentSubdirectory[curPart] THEN
BEGIN
exit ← TRUE;
machineDependentSubdir ← PFSNames.ConstructName[LIST[curPart], FALSE, TRUE];
END
ELSE
tentativeRemainingPath ← CONS[curPart, tentativeRemainingPath];
ENDLOOP;
remainingPath ← PFSNames.ConstructName[tentativeRemainingPath, FALSE, TRUE, TRUE];
OK, we've found remainingPath. There should be only one remaining component.
FIX: Why doesn't this work? What am I missing (must be obvious)?
IF nextPart # unixFileName.ComponentCount THEN
out.PutF["Serious error. Too many components!\n"];
We're still going. Time to disassemble the filename.
curPart ← unixFileName.Fetch[nextPart];
version ← curPart.version;
curPartRope ← curPart.ComponentRope;
{
fnPart: RopePart ← RopeSequence.PartFromRope[curPartRope];
fileNameSeq ← RopeSequence.ParsePartToSeq[fnPart, '.];
stem ← fileNameSeq.Fetch[0];
IF fileNameSeq.ComponentCount = 2 THEN extension ← fileNameSeq.Fetch[1]
ELSE {
secondaryExtension ← fileNameSeq.Fetch[1];
extension ← fileNameSeq.Fetch[2];
};
};
cirioPrefix ← volume.Cat[name1];
cirioRemainingFileName ← PFSNames.EmptyPath;
cirioRemainingFileName ← remainingPath.Cat[machineDependentSubdir];
cirioRemainingFileName ← cirioRemainingFileName.Cat[
PFS.PathFromRope[fileNameSeq.UnparseSeqToPart['.].RopeFromPart]];
cirioRemainingFileName ← cirioRemainingFileName.SetVersionNumber[version];
RETURN[[
cirioPrefix: cirioPrefix,
cirioRemainingFileName: cirioRemainingFileName,
volume: volume,
name1: name1,
remainingPath: remainingPath,
machineDependentSubdir: machineDependentSubdir,
stem: stem,
secondaryExtension: secondaryExtension,
extension: extension,
version: version]];
EXITS
fails => BadDotONameSyntax[];
END;
BadDotONameSyntax: ERROR = CODE;
BasicTime.mesa says that earliestGMT is the beginning of 1968
Sun documentation says that Sun time (Unix standard?) is zero at beginning of 1970
GMTFromSunTime: PROC[sunTime: CARD] RETURNS[BasicTime.GMT] =
BEGIN
RETURN[BasicTime.Update[BasicTime.Pack[[1970, January, 1, 0, 0, 0, 0, no]], sunTime]];
END;
DotOHashTable: TYPE = REF DotOHashTableBody;
DotOHashTableBody: TYPE = RECORD[table: RefTab.Ref];
PackagedDotO: TYPE = REF DOA.DotOCookie;
CreateDotOHashTable: PROC RETURNS[DotOHashTable] =
{RETURN[NEW[DotOHashTableBody ← [RefTab.Create[]]]]};
CreateDotOKey: PROC[longPathName: PATH, mtime: CARD, size: CARD] RETURNS[ATOM] =
{RETURN[Atom.MakeAtom[Rope.Cat[Convert.RopeFromCard[mtime], Convert.RopeFromCard[size], PFS.RopeFromPath[longPathName]]]]};
Stab ranges
StabRange: TYPE = RECORD[firstX, limitX: CARD];
(limitX = firstX+count)
We consult a table located in the target world.
That table is described in
/palain-UX/jaune/xrhome/DEVELOPMENT/loading/INCLUDE/xr/ADotOutExtras.h
in vicinity of dbxstabgroup
(tentativeDotO included as a parameter only to permit calls to DOA.FindEmbeddedDotOStabRange)
We return [1,0] if there are no dbx symbol table entries for the given pc.
FindStabRange: PROC[nub: CirioNubAccess.Handle, fileInfo: CirioNubAccess.FileEntry, absPC: CARD, tentativeDotO: DOA.DotOCookie] RETURNS[StabRange] =
BEGIN
pcInfo: CirioNubAccess.PCInfo ← CirioNubAccess.PCtoInfo[nub, absPC];
pcSymEntryResult: CirioNubAccess.LookupSymEntryResult ← CirioNubAccess.LookupSymEntryByID[nub, pcInfo.procSymID];
procValue: CARDWITH pcSymEntryResult SELECT FROM
ser: REF CirioNubAccess.LookupSymEntryResultBody.case0 => ser.symEntry.value,
ENDCASE => ERROR;
procedureStartRelativePC: CARD ← procValue - fileInfo.textReloc;
GroupSize: CARD = 16;
nGroups: INT ← fileInfo.readerDataSize/GroupSize;
x: CARD ← 0;
y: CARD ← nGroups;
Suppose that nGroups = 0. We probably do not have the latest Demers code in the remote nub, so lets try the fall back.
IF nGroups = 0 THEN
BEGIN
firstX: CARD;
count: CARD;
SymbolFinding.ShowReport[Rope.Cat["using fallback to find embeddedDotO in ", PFS.RopeFromPath[fileInfo.fileName]]];
[firstX, count] ← DOA.FindEmbeddedDotOStabRange[tentativeDotO, procedureStartRelativePC];
RETURN[[firstX, firstX+count]];
END;
lets check x
BEGIN
xData: StbGpEntry ← ReadOneDbxStabGroupEntry[nub, fileInfo, x];
IF procedureStartRelativePC < xData.firstPC THEN RETURN[[0, 0]];
IF procedureStartRelativePC <= xData.lastPC THEN RETURN[[xData.firstX, xData.firstX+xData.count]];
END;
invariant:
procedureStartRelativePC > group[x].lastPC
y = nGroups OR procedureStartRelativePC < group[y].firstPC
WHILE x+1 < y DO
mid: CARD ← (x+y)/2;
midData: StbGpEntry ← ReadOneDbxStabGroupEntry[nub, fileInfo, mid];
SELECT TRUE FROM
procedureStartRelativePC < midData.firstPC => y ← mid;
midData.firstPC <= procedureStartRelativePC AND procedureStartRelativePC <= midData.lastPC =>
RETURN[[midData.firstX, midData.firstX+midData.count]];
midData.lastPC < procedureStartRelativePC => x ← mid;
ENDCASE => ERROR;
ENDLOOP;
no dbx symbols
RETURN[[0, 0]];
END;
StbGpEntry: TYPE = RECORD[firstX: INT, count: INT, firstPC: CARD, lastPC: CARD];
ReadOneDbxStabGroupEntry: PROC[nub: CirioNubAccess.Handle, fileInfo: CirioNubAccess.FileEntry, gpIndex: CARD] RETURNS[StbGpEntry] =
BEGIN
bytesForOneGroup: CARD = 16;
firstAddr: CARD ← fileInfo.readerData+gpIndex*bytesForOneGroup;
RETURN[[
ReadIntAtCardAddr[nub, firstAddr],
ReadIntAtCardAddr[nub, firstAddr+4],
ReadCardAtCardAddr[nub, firstAddr+8],
ReadCardAtCardAddr[nub, firstAddr+12]]];
END;
ReadCardAtCardAddr: PROC[nub: CirioNubAccess.Handle, addr: CARD32] RETURNS[CARD32] =
BEGIN
RETURN[CirioNubAccess.Read32BitsAsCard[[nub, addr, 0, FALSE, TRUE]]];
END;
ReadIntAtCardAddr: PROC[nub: CirioNubAccess.Handle, addr: CARD32] RETURNS[INT32] =
BEGIN
RETURN[LOOPHOLE[CirioNubAccess.Read32BitsAsCard[[nub, addr, 0, FALSE, TRUE]]]];
END;
Mob location mechanism
FindMob: PROC[stamp: MobDefs.VersionStamp, factoredName: FactoredUnixFileName, embeddedStem: RopePart, serverName: Rope.ROPE, si: SymbolInfo, searchDirectories: LIST OF PATH] RETURNS[MA.MobCookie] =
BEGIN
vsKey: REF MobDefs.VersionStamp ← NEW[MobDefs.VersionStamp ← stamp];
packagedMob: PackagedMob ← NARROW[RefTab.Fetch[si.mobHash.table, vsKey].val];
simpleDotO: BOOLEAN ← Rope.Equal[factoredName.stem.RopeFromPart, embeddedStem.RopeFromPart];
foundMob: MA.MobCookie ← NIL;
IF packagedMob # NIL AND packagedMob.mob # NIL THEN RETURN[packagedMob.mob];
IF packagedMob # NIL AND BasicTime.Period[si.cacheFlushTime, packagedMob.searchTime] > 0 THEN RETURN[NIL];
wasn't in the hash table, so we have to start looking for it
BEGIN
ourUxPrefix: PATH;
ourNfsPrefix: PATH;
mobName: PATH;
This code runs mob mapper on each prospective mob. That is very probably overkill.
On the other hand, we won't try a prospective mob unless it has the right short name.
ConfirmMobFSName: PROC[name: PATH] RETURNS[--ok-- BOOLEAN] =
BEGIN
file: SystemInterface.CirioFile ← SystemInterface.GetCirioFile[si.fileSet, name];
mob: MA.MobCookie ← MA.CreateMobCookie[file];
mobStamp: MobDefs.VersionStamp ← MA.ReadMobVersionStamp[mob];
result: BOOLEAN ← stamp = mobStamp;
IF result THEN foundMob ← mob;
RETURN[result]
END;
FSNameProc: PFS.NameProc =
{RETURN[NOT ConfirmMobFSName[fullFName]]};
The first qustion is whether the dotO file is embedded in a compound file or not. Perhaps there should be an explicit flag available to decide, possibly in the embeddedInfo. For the moment, we assume that we are dealing with a compound file if factoredName.stem # embeddedStem. (reflected as NOT simpleDotO.)
ourNfsPrefix ← CirioDeltaFace.GetOurPrefixForUnixPrefix[factoredName.volume, factoredName.name1, serverName, "nfs"];
ourUxPrefix ← CirioDeltaFace.GetOurPrefixForUnixPrefix[factoredName.volume, factoredName.name1, serverName];
If we are starting from a machine-dependent directory then look in the machine-independent directory first since that's the common case.
IF NOT Rope.Equal[PFS.RopeFromPath[factoredName.machineDependentSubdir], ""] THEN
BEGIN
Look through the nfs file system view first, since that's the common case.
mobName ←
ourNfsPrefix.Cat[factoredName.remainingPath.Cat[
PFS.PathFromRope[Rope.Cat[embeddedStem.RopeFromPart,".mob"]]]];
PFS.EnumerateForNames[mobName, FSNameProc!
PFS.Error => IF error.group = user THEN
BEGIN
foundMob ← NIL;
CONTINUE;
END];
IF foundMob # NIL THEN GOTO found;
Look through the ux file system view.
mobName ← ourUxPrefix.Cat[
factoredName.remainingPath.Cat[
PFS.PathFromRope[embeddedStem.RopeFromPart.Cat[".mob"]]]];
PFS.EnumerateForNames[mobName, FSNameProc!
PFS.Error => IF error.group = user THEN
BEGIN
foundMob ← NIL;
CONTINUE;
END];
IF foundMob # NIL THEN GOTO found;
Look in the same directory as held the dotO file
mobName ← ourUxPrefix.Cat[
factoredName.remainingPath.Cat[factoredName.machineDependentSubdir[
PFS.PathFromRope[embeddedStem.RopeFromPart.Cat[".mob"]]]]];
PFS.EnumerateForNames[mobName, FSNameProc!
PFS.Error => IF error.group = user THEN
BEGIN
foundMob ← NIL;
CONTINUE;
END];
IF foundMob # NIL THEN GOTO found;
Try looking through the nfs view of the file system.
mobName ← ourNfsPrefix.Cat[
factoredName.remainingPath.Cat[factoredName.machineDependentSubdir[
PFS.PathFromRope[embeddedStem.RopeFromPart.Cat[".mob"]]]]];
PFS.EnumerateForNames[mobName, FSNameProc!
PFS.Error => IF error.group = user THEN
BEGIN
foundMob ← NIL;
CONTINUE;
END];
IF foundMob # NIL THEN GOTO found;
END;
We didn't find it by the usual means, so lets try the search directories.
FOR sps: LIST OF PATH ← searchDirectories, sps.rest WHILE sps # NIL DO
mobName: PATH ← sps.first.Cat[PFS.PathFromRope[embeddedStem.RopeFromPart.Cat[".mob"]]];
PFS.EnumerateForNames[mobName, FSNameProc!
PFS.Error => IF error.group = user THEN
BEGIN
foundMob ← NIL;
CONTINUE;
END];
IF foundMob # NIL THEN GOTO found;
ENDLOOP;
GOTO failed;
EXITS
found =>
BEGIN
packagedMob: PackagedMob ← NEW[PackagedMobBody ← [BasicTime.Now[], foundMob]];
[] ← RefTab.Insert[si.mobHash.table, vsKey, packagedMob];
RETURN[foundMob];
END;
failed =>
BEGIN
packagedMob: PackagedMob ← NEW[PackagedMobBody ← [BasicTime.Now[], NIL]];
[] ← RefTab.Insert[si.mobHash.table, vsKey, packagedMob];
RETURN[NIL];
END;
END;
END;
MobHashTable: TYPE = REF MobHashTableBody;
MobHashTableBody: TYPE = RECORD[table: RefTab.Ref];
PackagedMob: TYPE = REF PackagedMobBody;
PackagedMobBody: TYPE = RECORD[searchTime: BasicTime.GMT, mob: MA.MobCookie];
CreateMobHashTable: PROC RETURNS[MobHashTable] =
{RETURN[NEW[MobHashTableBody ← [table: RefTab.Create[equal: MobKeyEqualProc, hash: MobKeyHashProc]]]]};
CreateMobKey: PROC[stamp: MobDefs.VersionStamp] RETURNS[RefTab.Key] =
{RETURN[NEW[MobDefs.VersionStamp ← stamp]]};
MobKeyEqualProc: PROC[key1, key2: RefTab.Key] RETURNS[BOOL] =
BEGIN
vs1: REF MobDefs.VersionStamp ← NARROW[key1];
vs2: REF MobDefs.VersionStamp ← NARROW[key2];
RETURN[vs1^ = vs2^];
END;
MobKeyHashProc: PROC[key: RefTab.Key] RETURNS[CARDINAL] =
BEGIN
vs: REF MobDefs.VersionStamp ← NARROW[key];
word0: PBasics.LongNumber ← LOOPHOLE[vs^[0]];
word1: PBasics.LongNumber ← LOOPHOLE[vs^[1]];
RETURN[PBasics.BITXOR[PBasics.BITXOR[word0.lo, word0.hi], PBasics.BITXOR[word1.lo, word1.hi]]];
END;
This stuff should be available from CirioNubAccess
RemoteAddress: TYPE = CirioNubAccess.RemoteAddress;
InvalidRemoteAddress: RemoteAddress ← [NIL, 0, 0, FALSE, FALSE];
RemoteAddrFromCard: PROC[nub: CirioNubAccess.Handle, card: CARD, bitOffset: CARD ← 0] RETURNS[RemoteAddress] =
{RETURN[[nub, card, bitOffset, FALSE, nub # NIL]]};
RopeBufferSize: CARD = 100;
ReadCRope: PROC[at: RemoteAddress] RETURNS[Rope.ROPE] =
BEGIN
ENABLE UNWIND => NULL;
x: RemoteAddress ← at;
rope: Rope.ROPENIL;
WHILE TRUE DO
nChars: CARD ← RopeBufferSize; -- tentative
rt: REF TEXT ← CirioNubAccess.ReadBytes[x, RopeBufferSize];
r: Rope.ROPE;
FOR I: CARD IN [0..RopeBufferSize) DO
IF rt[I] = '\000 THEN {nChars ← I; EXIT};
ENDLOOP;
r ← Rope.FromRefText[rt, 0, nChars];
rope ← IF rope = NIL THEN (IF nChars = 0 THEN "" ELSE r)
ELSE (IF nChars = 0 THEN rope ELSE Rope.Cat[rope, r]);
IF nChars < RopeBufferSize THEN EXIT;
x.byteAddress ← x.byteAddress+ nChars;
ENDLOOP;
RETURN[rope];
END;
test code
Read all characters of a file sequentually.
(we use this to compare local and remote sequential performance)
ScanAFile cached fileName
ScanAFile remote fileName
If the first parameter = "cached" or if the server name is not of the form foo-UX, then we use the standard FS stream mechanism. If the first parameter = "remote" and server name has the form foo-UX, then we use UnixRemoteFile directly.
Note that, if we use the standard FS stream mechanism, then the first time we do it we pay for the copy time.
ScanAFile: Commander.CommandProc =
BEGIN
args: CommandTool.ArgumentVector ← CommandTool.Parse[cmd];
case: Rope.ROPE ← args[1];
fileName: PATH ← args[2];
stream: IO.STREAM ← OldOpenDotOStream[fileName, SELECT TRUE FROM
Rope.Equal[case, "cached"] => TRUE,
Rope.Equal[case, "remote"] => FALSE,
ENDCASE => ERROR];
WHILE NOT IO.EndOf[stream] DO [] ← IO.GetChar[stream] ENDLOOP;
IO.Close[stream];
END;
reports
ShowReport: PUBLIC SIGNAL[msgText: Rope.ROPE] = CODE;
main code
Commander.Register["ScanAFile", ScanAFile];
some examples for ScanAFile
ScanAFile cached /palain-UX/jaune/xrhome/DEVELOPMENT/BIN/Threads-sparc/PortableCommonRuntime
ScanAFile remote /palain-UX/jaune/xrhome/DEVELOPMENT/BIN/Threads-sparc/PortableCommonRuntime
END.