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; 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]; 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 ["]; 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; FoundDotO: TYPE = RECORD[dotO: DOA.DotOCookie, embedded: DOA.EmbeddedDotO, vsi: REF DOA.VersionStampInfo]; FindC2CDotO: PROC[factoredName: FactoredUnixFileName, serverName: Rope.ROPE, nub: CirioNubAccess.Handle, desc: SymbolFinding.DotODesc, absPC: CARD, si: SymbolInfo] RETURNS[FoundDotO] = BEGIN 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; 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; 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: PATH _ PFS.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: PATH _ NIL; SeeDotOInfo: PFS.InfoProc = BEGIN 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; 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; packagedDotO _ NEW[DOA.DotOCookie _ dotO]; [] _ RefTab.Insert[si.doaHash.table, key, packagedDotO]; END; RETURN[packagedDotO^]; END; OldOpenDotOStream: PROC[name: PATH, cachedOnly: BOOLEAN _ FALSE] RETURNS[IO.STREAM] = BEGIN nameRope: ROPE _ PFS.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: BOOLEAN _ FALSE; 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; 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]; curPart _ unixFileName.Fetch[nextPart]; name1 _ PFSNames.ConstructName[LIST[curPart], FALSE, TRUE]; 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]; 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; 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]]]]}; StabRange: TYPE = RECORD[firstX, limitX: CARD]; 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: CARD _ WITH 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; 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; 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; 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; 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; 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]; BEGIN ourUxPrefix: PATH; ourNfsPrefix: PATH; mobName: PATH; 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]]}; ourNfsPrefix _ CirioDeltaFace.GetOurPrefixForUnixPrefix[factoredName.volume, factoredName.name1, serverName, "nfs"]; ourUxPrefix _ CirioDeltaFace.GetOurPrefixForUnixPrefix[factoredName.volume, factoredName.name1, serverName]; IF NOT Rope.Equal[PFS.RopeFromPath[factoredName.machineDependentSubdir], ""] THEN BEGIN 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; 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; 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; 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; 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; 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.ROPE _ NIL; 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; 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; ShowReport: PUBLIC SIGNAL[msgText: Rope.ROPE] = CODE; Commander.Register["ScanAFile", ScanAFile]; END. . 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 global code The next line breaks the shortName (last component of the part) into a RopeSeq split on .'s (i.e., the stem and extensions). note: the version stamp key is broken into pieces so that it won't look like a version stamp in the various files. Dot O location mechanism 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 the following procedure is used only during a break point for random testing. See "PlantRandomTestBreakHere" below. PlantRandomTestBreakHere for random test of FindStabRange. execute DotOAccessImpl.RandomTestOtherFindStabRange[4466, tentativeDotO, FindForTesting, &H.tsOutStream, 1000] 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. PROC [ fullFName, attachedTo: PATH, uniqueID: PFS.UniqueID, bytes: INT, keep: CARDINAL, fileType: FileType ] RETURNS [continue: BOOL] lets see if it satisfies our constraints ok, we buy it ok, lets record the result of our hunt 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.) First, figure out volume OK, that's done. Now for name1. That was easy. Now to tackle remainingPath 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. BasicTime.mesa says that earliestGMT is the beginning of 1968 Sun documentation says that Sun time (Unix standard?) is zero at beginning of 1970 Stab ranges (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. Suppose that nGroups = 0. We probably do not have the latest Demers code in the remote nub, so lets try the fall back. lets check x invariant: procedureStartRelativePC > group[x].lastPC y = nGroups OR procedureStartRelativePC < group[y].firstPC no dbx symbols Mob location mechanism wasn't in the hash table, so we have to start looking for it 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. 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.) If we are starting from a machine-dependent directory then look in the machine-independent directory first since that's the common case. Look through the nfs file system view first, since that's the common case. Look through the ux file system view. Look in the same directory as held the dotO file Try looking through the nfs view of the file system. We didn't find it by the usual means, so lets try the search directories. This stuff should be available from CirioNubAccess 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. reports main code 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 Κ •NewlineDelimiter ™Jšœ™šœ(™(Icode™;K™$—J˜šΟk ˜ Jšœœ ˜Jšœ œœ˜0Jšœœ–˜ͺJšœœ$˜1Jšœ œ˜'Jšœ œ˜)Jšœ œ€˜΄JšœœM˜UJšœœ%œ˜5Jšœ œ2˜AJšœœ˜Jšœœ+˜>Jšœœœ˜"Jšœœ(˜1Jšœ œœ.˜BJšœœ"˜.JšœœFœ ˜^Jšœ œx˜ŠJšœ œ˜ Jšœœ;˜NKšœœF˜[Jšœœ1˜E—J˜˜J˜™J™——šΟnœœœœOœœŽœ˜’Jš œœœœ œ˜MJ™Jšœœ œ˜Jšœ œ˜%Jšœ œ˜'Kšœ œ˜%J˜Jšœœ˜0J˜J˜J™ ™Jšœ œœ˜&šœœœœ˜%J˜!Jšœ˜J˜Jšœœ˜—J˜šžœœœ#œ˜UJš˜šœœ˜%Jšœ˜Jšœ˜Jšœ˜Jšœ"˜"—Jšœ˜ Jšœ˜—J˜šžœœœ˜3Jš˜J˜$Jšœ˜—J˜šž œœœœCœ%œœœœ˜ΏJš˜J˜JšœP˜PJšœS˜SJ˜Jšœœœœœœœœ˜9Jšœœœœœœ&œœ˜Xšœ˜Jš˜Jšœœ ˜#Jšœ œ˜ Jšœœœ)˜\J™|J˜zJšœ˜J˜Jšœœ ˜Kšœ$œJ˜ušœœ!˜?Kš œœ3œœ!œ'˜¨Kš œœ5œ3œœ!œ'˜ΰKšœi˜p—JšœW˜WJšœT˜TJšœœœœ ˜ šœ˜Jš˜JšœœœA˜aJšœ2˜8Jšœ˜—J˜š˜Jšœ œ&œœ˜D—Jšœ˜—Jšœ˜—J˜Jšž œœœœ˜-J˜šž(œœœœ˜Jš˜š˜Jš˜Jšœœ˜'Jšœœ˜Jšœ˜—J˜šœœ)˜DJ™r—Jšœœ)˜EJšœ œ!˜1Jšœœ"˜5Jšœœ#˜7Jšœœ4˜GJšœœO˜cJšœ œ]˜nJšœœ˜$Jšœœ!˜3Jšœœ=˜OJšœ]˜]J˜Jšœœ(œ˜OJšœœ*œœ˜XJ˜Jšœ˜J˜š˜Jšœ%˜%—Jšœ˜—J˜—J˜™J˜Jš œ œœœœœœ˜j˜J™„Jšœ>™>J™™ ™Jšœ œ™—™&Jšœœ™ —™9Jšœ œ™—™3J™———J˜š ž œœ6œCœœ ˜Έš˜J™t—š žœœ œœœ œ˜JJš˜Jšœh˜hJšœœœ˜0Jšœœœ*˜6Jšœ˜J˜—Jšœœ;˜MJ˜Jš œœœœœœ˜.Jšœœ!œ;œœœœΟc)˜¦š˜Jš˜JšœO˜OJšœ œœD˜dJšœœœœ œœœœœ˜_J™šœ:™:šœ™Jšœf™fJ™——šœœœŸ˜%Jšœœ˜&—š œœœœœŸ˜*Jšœ!˜'—šœ˜JšœŸ?˜EJšœœS˜hJšœœ&œœœœœ˜HJšœœœ!˜-Jšœ˜—Jšœ˜—šœ˜J˜——J˜˜J™’Jšœ>™>Jšœzœ™~—š žœœ6œ0œœ˜‘Jš˜JšœœR˜[Jšœœ*˜MJ˜šœœœΠci=˜XJšœ˜Jšœœœ˜Jšœœœ(œp˜ΆJšœœ'˜@Jšœœa˜mJšœ œT˜bJšœ œœ˜J˜šž œœ ˜Jš œœ!œ œœ œ™†Jš˜J˜J™(šœœŸ-˜MJš˜Jš œ!œœœΟi ˜Jšœ˜Jšœ˜——J˜™J˜Jš ž œœœœœ˜5—J™™ J˜Jšœ+˜+˜™Jšœ\™\Jšœ\™\———Jšœ˜——…—Z²Œλ