<<>> <> <> <> <> <<>> DIRECTORY Ascii, Atom, Basics, BasicTime, Commander, CommanderOps, Convert, DFPorter, DFUtilities, IO, List, PFS, PFSNames, PFSPrefixMap, RefTab, RefText, Rope, RopeList, SymTab, UserProfile; DFPorterImpl: CEDAR MONITOR IMPORTS Ascii, Atom, Basics, BasicTime, Commander, CommanderOps, Convert, DFUtilities, IO, List, PFS, PFSNames, PFSPrefixMap, RefTab, RefText, Rope, RopeList, SymTab, UserProfile EXPORTS DFPorter ~ BEGIN OPEN DFUtilities; LORA: TYPE ~ LIST OF REF ANY; PATH: TYPE ~ PFSNames.PATH; ROPE: TYPE ~ Rope.ROPE; Oops: ERROR ~ CODE; DFContents: TYPE ~ DFPorter.DFContents; FullFileItem: TYPE ~ DFPorter.FullFileItem; OrderedCommentItem: TYPE ~ DFPorter.OrderedCommentItem; ReadDFs: PUBLIC PROC [dfNames: LIST OF ROPE, followImports: BOOL ¬ FALSE] RETURNS [LIST OF DFContents] ~ { cache: SymTab.Ref ~ SymTab.Create[]; alreadyRead: RefTab.Ref ~ RefTab.Create[]; head: LIST OF DFContents ~ LIST[[NIL]]; last: LIST OF DFContents ¬ head; Inner: PROC [dfName: ROPE] ~ { cname: ATOM ~ CanonicalFileID[dfName, cache].atom; IF NOT RefTab.Fetch[x: alreadyRead, key: cname].found THEN { df: DFContents ~ ReadDF1[dfName, cache]; [] ¬ RefTab.Insert[x: alreadyRead, key: cname, val: $TRUE]; last ¬ last.rest ¬ LIST[df]; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF IncludeItem => { Inner[a.path1 ! Oops => CONTINUE]; }; a: REF ImportsItem => { IF followImports AND (allImports OR NOT a.exported) THEN Inner[a.path1 ! Oops => CONTINUE]; }; ENDCASE => NULL; ENDLOOP; }; }; FOR tail: LIST OF ROPE ¬ dfNames, tail.rest UNTIL tail = NIL DO Inner[tail.first]; ENDLOOP; RETURN [head.rest] }; SelfName: PUBLIC PROC [df: DFContents] RETURNS [ROPE] ~ { shortName: ROPE ~ ShortName[df.name]; currentDir: REF DirectoryItem ¬ NIL; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM new: REF DirectoryItem => { currentDir ¬ new }; file: REF FileItem => { IF Rope.Equal[ShortName[file.name], shortName, FALSE] THEN RETURN [Rope.Concat[currentDir.path1, file.name]]}; full: REF FullFileItem => { IF Rope.Equal[ShortName[full.file.name], shortName, FALSE] THEN RETURN [Rope.Concat[full.directory.path1, full.file.name]]}; ENDCASE => NULL; ENDLOOP; RETURN [shortName] }; ShortName: PUBLIC PROC [fileName: Rope.ROPE] RETURNS [ROPE] ~ { comp: PFSNames.Component ~ PFSNames.ShortName[PFS.PathFromRope[fileName]]; RETURN [Rope.Substr[comp.name.base, comp.name.start, comp.name.len]] }; BaseName: PUBLIC PROC [fileName: Rope.ROPE] RETURNS [ROPE] ~ { comp: PFSNames.Component ~ PFSNames.ShortName[PFS.PathFromRope[fileName]]; dot: INT ~ Rope.SkipTo[s: comp.name.base, pos: comp.name.start, skip: "."]; RETURN [Rope.Substr[comp.name.base, comp.name.start, MIN[comp.name.len, dot-comp.name.start]]] }; Fetch: PROC [name: PATH, index: NAT] RETURNS [ROPE] ~ { IF index < PFSNames.ComponentCount[name] THEN { comp: PFSNames.Component ~ PFSNames.Fetch[name: name, index: index]; RETURN [Rope.Substr[comp.name.base, comp.name.start, comp.name.len]] } ELSE { RETURN [NIL] }; }; StripVersion: PUBLIC PROC [fileName: Rope.ROPE] RETURNS [ROPE] ~ { len: INT ¬ INT.LAST; FOR i: INT DECREASING IN [0..Rope.Size[fileName]) DO SELECT Rope.Fetch[fileName, i] FROM IN ['0..'9] => NULL; '! => {len ¬ i; EXIT}; ENDCASE => EXIT; ENDLOOP; RETURN [Rope.Substr[base: fileName, start: 0, len: len]] }; tryLocal: BOOL ¬ FALSE; cacheNew: BOOL ¬ FALSE; rewritePorted: BOOL ¬ FALSE; FileID: TYPE ~ RECORD [atom: ATOM, fullFName: PATH]; CanonicalFileID: PROC [fileName: Rope.ROPE, cache: SymTab.Ref ¬ NIL] RETURNS [result: FileID] ~ { IF cache # NIL THEN { WITH SymTab.Fetch[cache, fileName].val SELECT FROM x: REF FileID => RETURN [x­]; ENDCASE => { result ¬ CanonicalFileID[fileName]; [] ¬ SymTab.Store[cache, fileName, NEW[FileID ¬ result]]; }; } ELSE { text: REF TEXT ¬ RefText.ObtainScratch[nChars: 100]; attachedTo, localFName, fullFName: PATH ¬ NIL; localDate, created: PFS.UniqueID ¬ []; s: PFSNames.Component; IF tryLocal THEN [fullFName: localFName, uniqueID: localDate, attachedTo: attachedTo] ¬ PFS.FileInfo[name: PFS.PathFromRope[ShortName[fileName]] ! PFS.Error => CONTINUE]; [fullFName: fullFName, uniqueID: created] ¬ PFS.FileInfo[name: PFS.PathFromRope[fileName] ! PFS.Error => IF localFName # NIL THEN CONTINUE]; IF localDate.egmt.gmt#BasicTime.nullGMT AND attachedTo = NIL AND (created.egmt.gmt = BasicTime.nullGMT OR BasicTime.Period[from: created.egmt.gmt, to: localDate.egmt.gmt] > 0) THEN { fullFName ¬ localFName; created ¬ localDate; }; s ¬ PFSNames.ShortName[fullFName]; text ¬ RefText.AppendRope[to: text, from: s.name.base, start: s.name.start, len: s.name.len]; FOR i: NAT IN [0..text.length) DO text[i] ¬ Ascii.Lower[text[i]]; ENDLOOP; text ¬ RefText.AppendChar[to: text, from: '-]; text ¬ Convert.AppendCard[to: text, from: LOOPHOLE[created.egmt.gmt], base: 16, showRadix: FALSE]; result.atom ¬ Atom.MakeAtomFromRefText[rt: text]; result.fullFName ¬ fullFName; RefText.ReleaseScratch[text]; }; }; allImports: BOOL ¬ TRUE; -- If FALSE, Exports Imports are not counted as dependencies. TopoSortDFs: PROC [in: LIST OF DFContents] RETURNS [LIST OF LIST OF DFContents] ~ { Vertex: TYPE ~ REF VertexRep; VertexRep: TYPE ~ RECORD [ data: DFContents, label: ATOM, onStack: BOOL, number: NAT, needs: LIST OF NAT, rank: INT, f: INT -- minimum rank branched to by desecendants ]; VertexSeqRep: TYPE ~ RECORD[SEQUENCE n: NAT OF Vertex]; labelToNumber: RefTab.Ref ~ RefTab.Create[]; graph: REF VertexSeqRep ~ CreateGraph[]; CreateGraph: PROC RETURNS [REF VertexSeqRep] ~ { cache: SymTab.Ref ~ SymTab.Create[]; v: REF VertexSeqRep ¬ NEW[VertexSeqRep[DFContentsListLength[in]]]; n: INT ¬ 0; FOR tail: LIST OF DFContents ¬ in, tail.rest UNTIL tail = NIL DO label: ATOM ~ CanonicalFileID[tail.first.name, cache].atom; v[n] ¬ NEW[VertexRep ¬ [ data: tail.first, label: label, onStack: FALSE, number: n, needs: NIL, rank: 0, f: LAST[INT] ]]; [] ¬ RefTab.Insert[labelToNumber, label, NEW[NAT ¬ n]]; n ¬ n + 1; ENDLOOP; FOR i: NAT IN [0..v.n) DO df: DFContents ~ v[i].data; needs: LIST OF NAT ¬ NIL; NoteNeed: PROC [fileName: ROPE] ~ { d: REF NAT ~ NARROW[RefTab.Fetch[labelToNumber, CanonicalFileID[fileName, cache].atom].val]; IF d # NIL THEN needs ¬ CONS[d­, needs]; }; FOR t: LORA ¬ df.contents, t.rest UNTIL t = NIL DO WITH t.first SELECT FROM a: REF ImportsItem => IF (allImports OR (NOT a.exported)) THEN NoteNeed[a.path1]; a: REF IncludeItem => NoteNeed[a.path1]; ENDCASE => NULL; ENDLOOP; v[i].needs ¬ needs; ENDLOOP; RETURN [v] }; stack: LIST OF Vertex ¬ NIL; -- the vertices examined but not yet output k: NAT ¬ 0; -- number of vertices examined so far; Examine: PROC [u: Vertex] ~ { <> min: INT ¬ LAST[INT]; k ¬ k + 1; u.rank ¬ k; stack ¬ CONS[u, stack]; u.onStack ¬ TRUE; FOR tail: LIST OF NAT ¬ u.needs, tail.rest UNTIL tail = NIL DO v: Vertex ~ graph[tail.first]; IF v.rank = 0 THEN { Examine[v]; IF v.f < min THEN min ¬ v.f; } ELSE { IF v.rank < min AND v.onStack THEN min ¬ v.rank; }; ENDLOOP; u.f ¬ min; IF u.f >= u.rank THEN { <> head: LIST OF DFContents ~ LIST[[NIL]]; last: LIST OF DFContents ¬ head; DO w: Vertex ¬ stack.first; stack ¬ stack.rest; w.onStack ¬ FALSE; last ¬ last.rest ¬ LIST[w.data]; IF w = u THEN EXIT; ENDLOOP; Output[head.rest]; }; }; head: LIST OF LIST OF DFContents ~ LIST[NIL]; last: LIST OF LIST OF DFContents ¬ head; Output: PROC [a: LIST OF DFContents] ~ { last ¬ last.rest ¬ LIST[a]; }; FOR i: NAT IN [0..graph.n) DO v: Vertex ~ graph[i]; IF v.rank = 0 THEN Examine[v]; ENDLOOP; RETURN [head.rest] }; NamesOnly2: PROC [in: LIST OF LIST OF DFContents] RETURNS [LORA] ~ { head: LORA ~ LIST[NIL]; last: LORA ¬ head; FOR tail: LIST OF LIST OF DFContents ¬ in, tail.rest UNTIL tail = NIL DO last ¬ last.rest ¬ LIST[NamesOnly[tail.first]]; ENDLOOP; RETURN [head.rest] }; NamesOnly: PROC [in: LIST OF DFContents] RETURNS [LORA] ~ { head: LORA ~ LIST[NIL]; last: LORA ¬ head; FOR tail: LIST OF DFContents ¬ in, tail.rest UNTIL tail = NIL DO last ¬ last.rest ¬ LIST[tail.first.name]; ENDLOOP; RETURN [head.rest] }; DFContentsListLength: PROC [in: LIST OF DFContents] RETURNS [n: INT ¬ 0] ~ { FOR tail: LIST OF DFContents ¬ in, tail.rest UNTIL tail = NIL DO n ¬ n + 1; ENDLOOP; }; UncachedReadDF: PROC [name: PATH] RETURNS [DFContents] ~ { head: LORA ~ LIST[NIL]; last: LORA ¬ head; ProcessItem: DFUtilities.ProcessItemProc = { <<[item: REF ANY] RETURNS [stop: BOOL _ FALSE]>> last ¬ last.rest ¬ LIST[item]; }; stream: IO.STREAM ~ PFS.StreamOpen[name, $read]; name ¬ PFS.GetName[PFS.OpenFileFromStream[stream]].fullFName; DFUtilities.ParseFromStream[stream, ProcessItem, [comments: TRUE]]; IO.Close[stream]; RETURN [[PFS.RopeFromPath[name, brackets], head.rest]] }; dfCache: RefTab.Ref ¬ RefTab.Create[]; ReadDF: PUBLIC PROC [name: ROPE] RETURNS [DFContents] ~ { RETURN [ReadDF1[name, NIL]] }; ReadDF1: PROC [name: ROPE, cache: SymTab.Ref] RETURNS [DFContents] ~ { id: FileID ~ CanonicalFileID[name, cache]; cached: REF DFContents ¬ NARROW[RefTab.Fetch[x: dfCache, key: id.atom].val]; IF cached = NIL THEN { cached ¬ NEW[DFContents ¬ UncachedReadDF[id.fullFName]]; [] ¬ RefTab.Insert[x: dfCache, key: id.atom, val: cached]; }; RETURN [cached­] }; commentCount: CARD ¬ 0; -- should really monitor this sucker. NextCommentCount: ENTRY PROC RETURNS [unique: CARD] ~ { unique ¬ commentCount ¬ commentCount + 1; }; DistributeDF: PUBLIC PROC [df: DFContents] RETURNS [DFContents] ~ { currentDir: REF DirectoryItem ¬ NIL; head: LORA ~ LIST[NIL]; last: LORA ¬ head; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM new: REF DirectoryItem => { currentDir ¬ new }; file: REF FileItem => { last ¬ last.rest ¬ LIST[NEW[FullFileItem ¬ [currentDir, file]]] }; comment: REF CommentItem => { last ¬ last.rest ¬ LIST[NEW[OrderedCommentItem ¬ [NextCommentCount[], comment]]] }; ENDCASE => { last ¬ last.rest ¬ LIST[tail.first] }; ENDLOOP; RETURN [[df.name, head.rest, TRUE]] }; blankLine: REF WhiteSpaceItem ~ NEW[WhiteSpaceItem ¬ [1]]; FactorDF: PUBLIC PROC [df: DFContents] RETURNS [DFContents] ~ { currentDir: REF DirectoryItem ¬ NIL; head: LORA ~ LIST[NIL]; last: LORA ¬ head; prevSortClass: CARD ¬ 0; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM dir: REF DirectoryItem => { IF head.rest # NIL THEN last ¬ last.rest ¬ LIST[blankLine]; last ¬ last.rest ¬ LIST[currentDir ¬ dir] }; full: REF FullFileItem => { IF currentDir = NIL OR CompareDirs[currentDir, full.directory]#equal THEN { IF head.rest # NIL THEN last ¬ last.rest ¬ LIST[blankLine]; last ¬ last.rest ¬ LIST[currentDir ¬ full.directory] } ELSE { IF head.rest # NIL AND full.sortClass # prevSortClass THEN last ¬ last.rest ¬ LIST[blankLine]; }; prevSortClass ¬ full.sortClass; last ¬ last.rest ¬ LIST[full.file]; }; imports: REF ImportsItem => { IF head.rest # NIL THEN last ¬ last.rest ¬ LIST[blankLine]; last ¬ last.rest ¬ LIST[imports] }; orderedComment: REF OrderedCommentItem => { last ¬ last.rest ¬ LIST[orderedComment.comment] }; ENDCASE => { last ¬ last.rest ¬ LIST[tail.first] }; ENDLOOP; RETURN [[df.name, head.rest, FALSE]] }; WriteDF: PUBLIC PROC [df: DFContents] ~ { currentDir: REF DirectoryItem ¬ NIL; stream: IO.STREAM ~ PFS.StreamOpen[PFS.PathFromRope[df.name], $create]; tail: LORA ¬ FactorDF[df].contents; SupplyItem: PROC RETURNS [result: REF ANY] ~ { IF tail = NIL THEN RETURN [NIL]; result ¬ tail.first; tail ¬ tail.rest }; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO DFUtilities.WriteToStream[out: stream, proc: SupplyItem]; ENDLOOP; IO.Close[stream]; }; ItemType: TYPE ~ { orderedComment, comment, fullFile, imports, include, other }; GetItemType: PROC [a: REF ANY] RETURNS [ItemType] ~ { RETURN [WITH a SELECT FROM a: REF ImportsItem => imports, a: REF IncludeItem => include, a: REF FullFileItem => fullFile, a: REF CommentItem => comment, a: REF OrderedCommentItem => orderedComment, ENDCASE => other]; }; CompareFullFiles: PROC [i1, i2: REF FullFileItem] RETURNS [c: Basics.Comparison] ~ { IF (c ¬ CompareDirs[i1.directory, i2.directory])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[i1.sortClass, i2.sortClass])#equal THEN RETURN; IF (c ¬ CompareFiles[i1.file, i2.file])#equal THEN RETURN; RETURN; }; CompareDirs: PROC [d1, d2: REF DirectoryItem] RETURNS [c: Basics.Comparison] ~ { IF (c ¬ Basics.CompareCard[ORD[d2.exported], ORD[d1.exported]])#equal THEN RETURN; IF (c ¬ Rope.Compare[s1: d1.path1, s2: d2.path1, case: FALSE])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[d1.readOnly], ORD[d2.readOnly]])#equal THEN RETURN; IF (c ¬ Rope.Compare[s1: d1.path2, s2: d2.path2, case: FALSE])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[d1.path2IsCameFrom], ORD[d2.path2IsCameFrom]])#equal THEN RETURN; RETURN; }; FileNamePart: TYPE ~ {dir, base, ext, version}; SubRope: TYPE ~ RECORD[base: ROPE, start, length: INT]; FileNameSegments: TYPE ~ ARRAY FileNamePart OF SubRope; Subname: PROC [fns: FileNameSegments, p: FileNamePart] RETURNS [ROPE] ~ INLINE { RETURN [Rope.Substr[fns[p].base, fns[p].start, fns[p].length]] }; DissectFileName: PROC [name: ROPE] RETURNS [f: FileNameSegments] ~ { path: PATH ~ PFS.PathFromRope[name]; dir: ROPE ~ PFS.RopeFromPath[PFSNames.SubName[ name: path, start: 0, count: PFSNames.ComponentCount[path]-(IF PFSNames.IsADirectory[path] THEN 0 ELSE 1), absolute: PFSNames.IsAbsolute[path], directory: TRUE], brackets]; lastComp: PFSNames.Component ~ PFSNames.ShortName[path]; <> end: INT ~ lastComp.name.start+lastComp.name.len; dot: INT ~ MIN[Rope.SkipTo[s: lastComp.name.base, pos: lastComp.name.start, skip: "."], end]; vers: ROPE ~ IF lastComp.version.versionKind = numeric THEN Convert.RopeFromInt[lastComp.version.version] ELSE NIL; RETURN [[ dir: [dir, 0, Rope.Size[dir]], base: [lastComp.name.base, lastComp.name.start, dot-lastComp.name.start], ext: [lastComp.name.base, (dot+1), MAX[end-(dot+1), 0]], version: [vers, 0, Rope.Size[vers]] ]] }; CompareSubRope: PROC [s1, s2: SubRope] RETURNS [c: Basics.Comparison] ~ { t1: REF TEXT ~ RefText.ObtainScratch[100]; t2: REF TEXT ~ RefText.ObtainScratch[100]; c ¬ RefText.Compare[RefText.AppendRope[t1, s1.base, s1.start, s1.length], RefText.AppendRope[t2, s2.base, s2.start, s2.length], FALSE]; RefText.ReleaseScratch[t1]; RefText.ReleaseScratch[t2]; }; CompareFiles: PROC [f1, f2: REF FileItem] RETURNS [c: Basics.Comparison] ~ { p1: FileNameSegments ~ DissectFileName[f1.name]; p2: FileNameSegments ~ DissectFileName[f2.name]; IF (c ¬ CompareSubRope[p1[base], p2[base]])#equal THEN RETURN; IF (c ¬ CompareSubRope[p1[dir], p2[dir]])#equal THEN RETURN; IF (c ¬ CompareSubRope[p2[ext], p1[ext]])#equal THEN RETURN; -- reverse order on ext! IF (c ¬ Basics.CompareCard[p1[version].length, p2[version].length])#equal THEN RETURN; IF (c ¬ CompareSubRope[p1[version], p2[version]])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[f2.verifyRoot], ORD[f1.verifyRoot]])#equal THEN RETURN; RETURN; }; CompareImports: PROC [i1, i2: REF ImportsItem] RETURNS [c: Basics.Comparison] ~ { IF (c ¬ Basics.CompareCard[ORD[i2.exported], ORD[i1.exported]])#equal THEN RETURN; IF (c ¬ Rope.Compare[s1: i1.path1, s2: i2.path1, case: FALSE])#equal THEN RETURN; IF (c ¬ Rope.Compare[s1: i1.path2, s2: i2.path2, case: FALSE])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[i1.form], ORD[i2.form]])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[LOOPHOLE[i1.list], LOOPHOLE[i2.list]])#equal THEN RETURN; RETURN; }; CompareIncludes: PROC [i1, i2: REF IncludeItem] RETURNS [c: Basics.Comparison] ~ { IF (c ¬ Rope.Compare[s1: i1.path1, s2: i2.path1, case: FALSE])#equal THEN RETURN; IF (c ¬ Rope.Compare[s1: i1.path2, s2: i2.path2, case: FALSE])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[i1.path2IsCameFrom], ORD[i2.path2IsCameFrom]])#equal THEN RETURN; RETURN [less]; }; CompareOrderedComments: PROC [i1, i2: REF OrderedCommentItem] RETURNS [c: Basics.Comparison] ~ { IF (c ¬ Basics.CompareCard[i1.order, i2.order])#equal THEN RETURN; IF (c ¬ Rope.Compare[i1.comment.text, i2.comment.text])#equal THEN RETURN; RETURN [less]; }; CompareItems: List.CompareProc = { <<[ref1: REF ANY, ref2: REF ANY] RETURNS [Basics.Comparison]>> t1: ItemType = GetItemType[ref1]; t2: ItemType = GetItemType[ref2]; IF t1#t2 THEN RETURN [Basics.CompareCard[ORD[t1], ORD[t2]]]; SELECT t1 FROM fullFile => {RETURN [CompareFullFiles[NARROW[ref1], NARROW[ref2]]]}; imports => {RETURN [CompareImports[NARROW[ref1], NARROW[ref2]]]}; include => {RETURN [CompareIncludes[NARROW[ref1], NARROW[ref2]]]}; orderedComment => {RETURN [CompareOrderedComments[NARROW[ref1], NARROW[ref2]]]}; ENDCASE => RETURN [less]; }; UsingEntryCompare: PROC [ref1: REF ANY, ref2: REF ANY] RETURNS [c: Basics.Comparison] ~ { u1: REF UsingEntry ~ NARROW[ref1]; u2: REF UsingEntry ~ NARROW[ref2]; IF (c ¬ Rope.Compare[s1: u1.name, s2: u2.name, case: FALSE])#equal THEN RETURN; IF (c ¬ Basics.CompareCard[ORD[u1.verifyRoot], ORD[u2.verifyRoot]])#equal THEN RETURN; }; MergeUsingLists: PUBLIC PROC [a, b: REF UsingList ¬ NIL] RETURNS [new: REF UsingList] ~ { list: LIST OF REF ¬ NIL; IF a#NIL THEN FOR i: NAT IN [0..a.nEntries) DO list ¬ CONS[NEW[UsingEntry ¬ a[i]], list]; ENDLOOP; IF b # NIL THEN FOR i: NAT IN [0..b.nEntries) DO list ¬ CONS[NEW[UsingEntry ¬ b[i]], list]; ENDLOOP; list ¬ List.UniqueSort[list, UsingEntryCompare]; new ¬ NEW[UsingList[List.Length[list: list]]]; new.nEntries ¬ new.length; FOR i: NAT IN [0..new.length) DO new[i] ¬ NARROW[list.first, REF UsingEntry]­; list ¬ list.rest; ENDLOOP; }; SortDF: PUBLIC PROC [df: DFContents] RETURNS [DFContents] ~ { delayedImports: REF ImportsItem ¬ NIL; head: LORA ~ LIST[NIL]; last: LORA ¬ head; FOR tail: LORA ¬ List.UniqueSort[list: DistributeDF[df].contents, compareProc: CompareItems], tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF ImportsItem => { IF delayedImports = NIL THEN delayedImports ¬ a ELSE { IF Rope.Equal[delayedImports.path1, a.path1, FALSE] AND delayedImports.date = a.date AND Rope.Equal[delayedImports.path2, a.path2, FALSE] AND delayedImports.exported = a.exported AND delayedImports.form = a.form THEN { delayedImports ¬ NEW[ImportsItem ¬ delayedImports­]; delayedImports.list ¬ MergeUsingLists[delayedImports.list, a.list]; } ELSE { last ¬ last.rest ¬ LIST[delayedImports]; delayedImports ¬ a; }; }; }; ENDCASE => { IF delayedImports # NIL THEN { last ¬ last.rest ¬ LIST[delayedImports]; delayedImports ¬ NIL; }; last ¬ last.rest ¬ LIST[tail.first]; }; ENDLOOP; IF delayedImports # NIL THEN { last ¬ last.rest ¬ LIST[delayedImports]; delayedImports ¬ NIL; }; RETURN[[df.name, head.rest, TRUE]] }; ExpandIncludes: PUBLIC PROC [df: DFContents] RETURNS [DFContents] ~ { RETURN ExpandIncludes1[df, NIL]; }; ExpandIncludes1: PROC [df: DFContents, cache: SymTab.Ref] RETURNS [DFContents] ~ { head: LORA ~ LIST[NIL]; last: LORA ¬ head; stopper: NAT ¬ LAST[NAT15]; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO stopper ¬ stopper - 1; WITH tail.first SELECT FROM a: REF IncludeItem => { inner: LORA ¬ ListAppend[ReadDF1[a.path1, cache ! Oops => GOTO out].contents, NIL]; last.rest ¬ inner; UNTIL last.rest = NIL DO stopper ¬ stopper - 1; last ¬ last.rest ENDLOOP; EXITS out => {}; }; ENDCASE => last ¬ last.rest ¬ LIST[tail.first]; ENDLOOP; RETURN [[df.name, head.rest, FALSE]] }; DFType: TYPE ~ {simple, suite, source, princops, pcr, sun3, sun4, sun4o3}; MkFile: PUBLIC PROC [filename: ROPE, root: BOOL ¬ FALSE] RETURNS [REF FileItem] ~ { RETURN [NEW[FileItem ¬ [ name: filename, date: [], verifyRoot: root ]]] }; MkFull: PUBLIC PROC [dir: REF DirectoryItem, file: REF FileItem, sortClass: CARD] RETURNS [REF FullFileItem] ~ { RETURN [NEW[FullFileItem ¬ [dir, file, sortClass]]] }; MkComment: PUBLIC PROC [rope: ROPE] RETURNS [REF CommentItem] ~ { RETURN [NEW[CommentItem ¬ [rope]]] }; Attr: TYPE ~ RECORD [exported: BOOL, verifyRoot: BOOL]; CollectAttributes: PROC [df: DFContents] RETURNS [SymTab.Ref] ~ { attr: SymTab.Ref ~ SymTab.Create[case: FALSE]; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF FullFileItem => { IF a.directory.exported OR a.file.verifyRoot THEN { s: FileNameSegments ~ DissectFileName[a.file.name]; ext: ROPE ~ Rope.Substr[s[ext].base, s[ext].start, s[ext].length]; Match: PROC [x: ROPE] RETURNS [BOOL] ~ { RETURN [Rope.Equal[s1: x, s2: ext, case: FALSE]] }; SELECT TRUE FROM Match["o"], Match["c2c.o"], Match["bcd"] => { nameBase: ROPE ~ Rope.Substr[s[base].base, s[base].start, s[base].length]; b: REF Attr ¬ NARROW[SymTab.Fetch[attr, nameBase].val]; IF b = NIL THEN [] ¬ SymTab.Insert[attr, nameBase, NEW[Attr ¬ [exported: a.directory.exported, verifyRoot: a.file.verifyRoot]]] ELSE { b.exported ¬ b.exported OR a.directory.exported; b.verifyRoot ¬ b.verifyRoot OR a.file.verifyRoot; } }; ENDCASE => NULL; }; }; ENDCASE => NULL; ENDLOOP; RETURN [attr] }; topDir: ROPE ¬ "Top"; -- name of subdirectory to put files into. ConsName: PROC [world, topDir, base, ext: ROPE] RETURNS [ROPE] ~ { RETURN [IO.PutFLR["[%g]<%g>%g%g", LIST[[rope[world]], [rope[topDir]], [rope[base]], [rope[ext]]]]] }; SubstituteExt: PROC [a: REF ImportsItem, world: ROPE, dfType: DFType, newExt: ROPE, definerTable: SymTab.Ref ¬ NIL] RETURNS [LORA--OF REF ImportsItem--] ~ { result: LORA ¬ NIL; -- for the result defaultDF: ROPE ¬ NIL; -- will be the name to use if we cannot find it in definerTable activeDF: ROPE ¬ NIL; nEntries: INT ¬ 0; activeItems: LIST OF UsingEntry ¬ NIL; TargetDF: PROC [rope: ROPE] ~ { IF rope # activeDF AND nEntries # 0 THEN { new: REF ImportsItem ~ NEW[ImportsItem ¬ a­]; new.path1 ¬ activeDF; new.list ¬ NEW[UsingList[nEntries]]; new.list.nEntries ¬ nEntries; WHILE nEntries # 0 DO nEntries ¬ nEntries - 1; new.list[nEntries] ¬ activeItems.first; activeItems ¬ activeItems.rest; ENDLOOP; result ¬ CONS[new, result]; }; activeDF ¬ rope; }; dfs: FileNameSegments ~ DissectFileName[a.path1]; fromComp: ROPE ¬ Rope.Substr[dfs[base].base, dfs[base].start, dfs[base].length]; fromComp ¬ Rope.Substr[fromComp, 0, Rope.Index[s1: fromComp, s2: "-"]]; -- strip -suffix defaultDF ¬ ConsName[world, topDir, fromComp, dfModifier[dfType]]; IF a.list = NIL THEN { SIGNAL CouldntFind[defaultDF, "nothing"]; RETURN [NIL] -- no using list to translate }; IF a.list = NIL THEN { -- old code new: REF ImportsItem ~ NEW[ImportsItem ¬ a­]; new.path1 ¬ defaultDF; RETURN [LIST[new]] -- no using list to translate }; FOR i: NAT IN [0..a.list.nEntries) DO entry: UsingEntry ¬ a.list[i]; s: FileNameSegments ~ DissectFileName[entry.name]; ext: ROPE ~ IF s[ext].length = 0 THEN NIL ELSE Rope.Substr[s[ext].base, s[ext].start, s[ext].length]; Match: PROC [x: ROPE] RETURNS [BOOL] ~ { RETURN [Rope.Equal[s1: x, s2: ext, case: FALSE]] }; SELECT TRUE FROM Match["mob"], Match["bcd"] => { entry.name ¬ Rope.Cat[Rope.Substr[s[base].base, s[base].start, s[base].length], ".", newExt]; }; ENDCASE => NULL; IF definerTable = NIL THEN TargetDF[defaultDF] ELSE { WITH SymTab.Fetch[x: definerTable, key: entry.name].val SELECT FROM definer: REF DefinerRep => TargetDF[definer.dfName]; ENDCASE => {SIGNAL CouldntFind[entry.name, defaultDF]; TargetDF[defaultDF]}; }; activeItems ¬ CONS[entry, activeItems]; nEntries ¬ nEntries + 1; ENDLOOP; TargetDF["--"]; -- to flush things out RETURN [result] }; DefinerRep: TYPE ~ RECORD [dfName, fullFName: ROPE]; CouldntFind: PUBLIC SIGNAL [shortName, usingDF: ROPE] ~ CODE; MultiplyDefinedShortname: PUBLIC SIGNAL [shortName, df1, df2: ROPE] ~ CODE; AugmentDefinerTable: PROC [dfs: LIST OF DFContents, x: SymTab.Ref ¬ NIL] RETURNS [SymTab.Ref] ~ { IF x = NIL THEN x ¬ SymTab.Create[case: FALSE]; FOR each: LIST OF DFContents ¬ dfs, each.rest UNTIL each = NIL DO df: DFContents ~ each.first; selfName: ROPE ~ SelfName[df]; Note: PROC [name: ROPE, fullFName: ROPE] ~ { sansVersion: ROPE ~ Rope.Substr[name, 0, Rope.Index[s1: name, s2: "!"]]; IF NOT SymTab.Insert[x: x, key: sansVersion, val: NEW[DefinerRep ¬ [dfName: selfName, fullFName: fullFName]]] THEN { SIGNAL MultiplyDefinedShortname[sansVersion, NARROW[SymTab.Fetch[x, sansVersion].val, REF DefinerRep].dfName, selfName]; }; }; currentDir: REF DirectoryItem ¬ NIL; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF FullFileItem => { Note[a.file.name, Rope.Concat[a.directory.path1, a.file.name]]; }; a: REF DirectoryItem => { currentDir ¬ a; }; a: REF FileItem => { Note[a.name, Rope.Concat[currentDir.path1, a.name]]; }; ENDCASE => NULL; ENDLOOP; ENDLOOP; RETURN [x] }; cachedDefinerID: ATOM ¬ NIL; cachedDefinerTable: SymTab.Ref ¬ NIL; GetDefinerTable: PUBLIC PROC [dfName: ROPE] RETURNS [x: SymTab.Ref] ~ { id: ATOM ~ CanonicalFileID[dfName].atom; Inner1: ENTRY PROC ~ INLINE { IF cachedDefinerID = id THEN x ¬ cachedDefinerTable; }; Inner2: ENTRY PROC ~ INLINE { cachedDefinerID ¬ id; cachedDefinerTable ¬ x; }; Inner1[]; IF x # NIL THEN RETURN; x ¬ AugmentDefinerTable[ReadDFs[LIST[dfName]]]; Inner2[]; }; CacheDefinerTable: ENTRY PROC [dfName: ROPE, x: SymTab.Ref] ~ { id: ATOM ~ CanonicalFileID[dfName].atom; cachedDefinerID ¬ id; cachedDefinerTable ¬ x; }; BuildInversion: PUBLIC PROC [df: DFContents] RETURNS [SymTab.Ref] ~ { x: SymTab.Ref ~ SymTab.Create[case: FALSE]; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF FullFileItem => { fullName: ROPE ~ Rope.Concat[a.directory.path1, a.file.name]; sansVersion: ROPE ~ Rope.Substr[fullName, 0, Rope.Index[s1: fullName, s2: "!"]]; [] ¬ SymTab.Store[x: x, key: sansVersion, val: a]; }; ENDCASE => NULL; ENDLOOP; RETURN [x] }; IsImplementation: PUBLIC PROC [fileName: ROPE] RETURNS [impl: BOOL ¬ TRUE] ~ { text: REF TEXT ~ RefText.ObtainScratch[100]; stream: IO.STREAM ~ PFS.StreamOpen[fileName: PFS.PathFromRope[fileName], accessOptions: $read]; DO tokenKind: IO.TokenKind; token: REF TEXT; charsSkipped: INT; error: IO.TokenError; [tokenKind: tokenKind, token: token, charsSkipped: charsSkipped, error: error] ¬ IO.GetCedarToken[stream: stream, buffer: text, flushComments: TRUE]; SELECT tokenKind FROM tokenID => { SELECT TRUE FROM RefText.Equal[token, "DEFINITIONS"] => {impl ¬ FALSE; EXIT}; RefText.Equal[token, "PROGRAM"] => EXIT; RefText.Equal[token, "MONITOR"] => EXIT; ENDCASE => NULL; }; tokenEOF => { {impl ¬ FALSE; EXIT}; -- really a bad mesa file }; ENDCASE; ENDLOOP; RefText.ReleaseScratch[text]; IO.Close[stream]; }; <> sortDoc: CARD ¬ 10; sortCommand: CARD ¬ 20; sortDefs: CARD ¬ 30; sortOther: CARD ¬ 40; sortRequire: CARD ¬ 50; sortImpl: CARD ¬ 60; sortConfig: CARD ¬ 70; dfModifier: ARRAY DFType OF ROPE ~ [".df", "-Suite.df", "-Source.df", "-PrincOps.df", "-PCR.df", "-Sun3.df", "-Sun4.df", "-Sun4O3.df"]; SplitIntoSuites: PUBLIC PROC [world: ROPE, component: ROPE, df: DFContents, definerTable: SymTab.Ref ¬ NIL, quickAndDirty: BOOL, intermediateSource: BOOL, intermediateObject: BOOL] RETURNS [result: LIST OF DFContents ¬ NIL] ~ { now: BasicTime.GMT ~ BasicTime.Now[]; year: INT ~ BasicTime.Unpack[now].year; editedby: ROPE ~ UserProfile.Token["Tioga.LastEdited", NIL]; whereis: SymTab.Ref ~ BuildInversion[df]; head: ARRAY DFType OF LORA ~ [LIST[NIL], LIST[NIL], LIST[NIL], LIST[NIL], LIST[NIL], LIST[NIL], LIST[NIL], LIST[NIL]]; last: ARRAY DFType OF LORA ¬ head; Put: PROC [dfType: DFType, item: REF] ~ { last[dfType] ¬ last[dfType].rest ¬ LIST[item]; }; PutList: PROC [dfType: DFType, lora: LORA] ~ { last[dfType].rest ¬ lora; UNTIL last[dfType].rest = NIL DO last[dfType] ¬ last[dfType].rest ENDLOOP; }; PutFull: PROC [dfType: DFType, dir: REF DirectoryItem, a, b, c: ROPE, sortClass: CARD, root: BOOL ¬ FALSE] ~ { full: REF FullFileItem ~ MkFull[dir, MkFile[Rope.Cat[a, b, c], root], sortClass]; WITH SymTab.Fetch[whereis, Rope.Concat[full.directory.path1, full.file.name]].val SELECT FROM f: REF FullFileItem => { full.file ¬ f.file; -- provide version and date info that is still OK. }; ENDCASE => NULL; Put[dfType, full]; }; AddBoilerplate: PROC [df: DFContents] RETURNS [DFContents] ~ { df.contents ¬ CONS[MkFull[MkDir[TRUE, topDir], MkFile[df.name], 0], df.contents]; df.contents ¬ CONS[MkComment[IO.PutFR["-- DFPort: %g %g", [rope[editedby]], [time[now]]]], df.contents]; df.contents ¬ CONS[MkComment[IO.PutFR1["-- Copyright Ó %g by Xerox Corporation. All rights reserved.", [integer[year]]]], df.contents]; df.contents ¬ CONS[MkComment[IO.PutFR1["-- %g", [rope[df.name]]]], df.contents]; RETURN [df] }; MkDir: PROC [exported: BOOL, dir: ROPE] RETURNS [REF DirectoryItem] ~ { RETURN [NEW[DirectoryItem ¬ [ path1: IO.PutFR["[%g]<%g>", [rope[world]], [rope[dir]]], path2: NIL, path2IsCameFrom: FALSE, exported: exported, readOnly: FALSE ]]] }; MkSelfImports: PROC [type: DFType] RETURNS [REF ImportsItem] ~ INLINE { -- obsolete RETURN [NEW[ImportsItem ¬ [ path1: ConsName[world, topDir, component, dfModifier[type]], date: [notEqual], path2: NIL, -- if non-NIL, path following "CameFrom" exported: FALSE, -- if TRUE, "Exports" preceded or followed "Imports" form: exports, list: NIL ]]] }; MkInclude: PROC [type: DFType] RETURNS [REF IncludeItem] ~ { RETURN [NEW[IncludeItem ¬ [ path1: ConsName[world, topDir, component, dfModifier[type]], date: [notEqual], path2: NIL, path2IsCameFrom: FALSE ]]] }; publicDir: REF DirectoryItem ~ MkDir[TRUE, component]; privateDir: REF DirectoryItem ~ MkDir[FALSE, component]; docDir: REF DirectoryItem ~ MkDir[FALSE, "Documentation"]; schemeDir: REF DirectoryItem ~ MkDir[FALSE, "SchemeLib"]; commandsDir: REF DirectoryItem ~ MkDir[FALSE, "Commands"]; derivedDir: REF DirectoryItem ~ MkDir[FALSE, "Derived"]; attrTab: SymTab.Ref ~ CollectAttributes[df]; defaultAttr: REF Attr ~ NEW[Attr ¬ [FALSE, FALSE]]; FOR tail: LORA ¬ df.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM a: REF ImportsItem => { PutList[princops, SubstituteExt[a, world, princops, "bcd"]]; IF a.exported THEN { PutList[sun3, SubstituteExt[a, world, sun3, "c2c.o", definerTable]]; PutList[sun4, SubstituteExt[a, world, sun4, "c2c.o", definerTable]]; PutList[sun4, SubstituteExt[a, world, sun4o3, "c2c.o", definerTable]]; PutList[simple, SubstituteExt[a, world, sun4, "c2c.o", definerTable]]; } ELSE { PutList[pcr, SubstituteExt[a, world, pcr, "mob", definerTable]]; PutList[simple, SubstituteExt[a, world, pcr, "mob", definerTable]]; }; }; a: REF FullFileItem => { s: FileNameSegments ~ DissectFileName[a.file.name]; nameBase: ROPE ~ Rope.Substr[s[base].base, s[base].start, s[base].length]; ext: ROPE ~ Rope.Substr[s[ext].base, s[ext].start, s[ext].length]; Match: PROC [x: ROPE] RETURNS [BOOL] ~ { RETURN [Rope.Equal[s1: x, s2: ext, case: FALSE]] }; attr: REF Attr ¬ NARROW[SymTab.Fetch[attrTab, nameBase].val]; IF attr = NIL THEN attr ¬ defaultAttr; SELECT TRUE FROM Match["df"] => NULL; Match["mesa"] => { obdir: REF DirectoryItem ~ IF attr.exported THEN publicDir ELSE privateDir; impl: BOOL ~ IF quickAndDirty THEN Rope.Match["*impl*", nameBase, FALSE] ELSE IsImplementation[Rope.Concat[a.directory.path1, a.file.name]]; sortClass: CARD ¬ (IF impl THEN sortImpl ELSE sortDefs) + ORD[attr.verifyRoot]; Put[source, MkFull[privateDir, a.file, sortClass]]; Put[simple, MkFull[privateDir, a.file, sortClass]]; IF NOT a.file.verifyRoot THEN { -- mark sources as verify roots to indicate they are not to be compiled PutFull[pcr, privateDir, "", nameBase, ".mob", sortClass]; PutFull[princops, obdir, "", nameBase, ".bcd", sortClass, attr.verifyRoot]; IF NOT impl THEN PutFull[simple, privateDir, "", nameBase, ".mob", sortClass, attr.verifyRoot]; IF impl THEN { IF intermediateObject OR attr.verifyRoot THEN { PutFull[simple, privateDir, "", nameBase, ".mob", sortClass]; PutFull[simple, obdir, "sun4>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; }; IF intermediateSource THEN { PutFull[simple, privateDir, "", nameBase, ".c2c.c", sortClass]; }; PutFull[pcr, privateDir, "", nameBase, ".c2c.c", sortClass]; PutFull[sun3, obdir, "sun3>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; PutFull[sun4, obdir, "sun4>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; PutFull[sun4o3, obdir, "sun4-o3>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; }; }; }; Match["config"] => { obdir: REF DirectoryItem ~ IF attr.exported THEN publicDir ELSE privateDir; sortClass: CARD ¬ sortConfig + ORD[attr.verifyRoot]; Put[source, MkFull[publicDir, a.file, sortClass]]; Put[simple, MkFull[publicDir, a.file, sortClass]]; IF NOT a.file.verifyRoot THEN { IF intermediateObject OR attr.verifyRoot THEN { PutFull[simple, privateDir, "", nameBase, ".mob", sortClass]; PutFull[simple, obdir, "sun4>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; }; IF intermediateSource THEN { PutFull[simple, privateDir, "", nameBase, ".c2c.c", sortClass]; }; PutFull[pcr, privateDir, "", nameBase, ".mob", sortClass]; PutFull[princops, obdir, "", nameBase, ".bcd", sortClass, attr.verifyRoot]; PutFull[pcr, privateDir, "", nameBase, ".c2c.c", sortClass]; PutFull[sun3, obdir, "sun3>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; PutFull[sun4, obdir, "sun4>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; PutFull[sun4o3, obdir, "sun4-o3>", nameBase, ".c2c.o", sortClass, attr.verifyRoot]; }; }; Match["c"], Match["s"], Match["S"] => { obdir: REF DirectoryItem ~ IF attr.exported THEN publicDir ELSE privateDir; sortClass: CARD ¬ sortImpl + ORD[attr.verifyRoot]; Put[pcr, MkFull[privateDir, a.file, sortClass]]; Put[simple, MkFull[privateDir, a.file, sortClass]]; IF NOT a.file.verifyRoot THEN { PutFull[sun3, obdir, "sun3>", nameBase, ".o", sortClass, attr.verifyRoot]; PutFull[sun4, obdir, "sun4>", nameBase, ".o", sortClass, attr.verifyRoot]; PutFull[sun4o3, obdir, "sun4-o3>", nameBase, ".o", sortClass, attr.verifyRoot]; PutFull[simple, obdir, "sun4>", nameBase, ".o", sortClass, attr.verifyRoot]; }; }; Match["mob"], Match["o"], Match["c2c.c"], Match["c2c.o"], Match["bcd"] => NULL; Match["command"], Match["cm"] => { Put[pcr, MkFull[commandsDir, a.file, sortCommand]]; Put[simple, MkFull[commandsDir, a.file, sortCommand]]; }; Match["$cheme"] => { Put[pcr, MkFull[schemeDir, a.file, sortCommand]]; Put[simple, MkFull[schemeDir, a.file, sortCommand]]; }; Match["require"] => { Put[pcr, MkFull[privateDir, a.file, sortRequire]]; Put[simple, MkFull[privateDir, a.file, sortRequire]]; }; Match["load"], Match["install"] => { Put[princops, MkFull[publicDir, a.file, sortRequire]]; }; ENDCASE => { doc: BOOL ~ Rope.Match["*Documentation*", a.directory.path1, FALSE]; <> dir: REF DirectoryItem ~ IF a.directory.exported THEN publicDir ELSE privateDir; sortClass: CARD ~ IF doc THEN sortDoc ELSE sortOther; Put[source, MkFull[dir, a.file, sortClass]]; Put[simple, MkFull[dir, a.file, sortClass]]; }; }; ENDCASE => { Put[source, tail.first] }; ENDLOOP; <> <> <> <> Put[suite, MkInclude[source]]; Put[suite, MkInclude[pcr]]; <> Put[suite, MkInclude[sun4]]; Put[suite, MkInclude[sun4o3]]; FOR i: DFType DECREASING IN DFType DO result ¬ CONS[AddBoilerplate[SortDF[[Rope.Concat[component, dfModifier[i]], head[i].rest, TRUE]]], result]; ENDLOOP; }; Debug: SIGNAL ~ CODE; FileNameTokenBreak: PROC [char: CHAR] RETURNS [IO.CharClass] = { < CONTINUE]; IF IO.EndOf[stream] THEN RETURN; IF IO.PeekChar[self: stream] = '" THEN { rope ¬ IO.GetCedarTokenRope[stream: stream, flushComments: FALSE].token; } ELSE { rope ¬ stream.GetTokenRope[FileNameTokenBreak ! IO.EndOfStream => CONTINUE].token; }; }; GetArgs: PROC [cmd: Commander.Handle] RETURNS [LIST OF ROPE] = { head: LIST OF ROPE ¬ LIST[NIL]; last: LIST OF ROPE ¬ head; stream: IO.STREAM ~ IO.RIS[cmd.commandLine]; FOR rope: ROPE ¬ GetFileNameToken[stream], GetFileNameToken[stream] UNTIL rope = NIL DO IF last # head OR Rope.Fetch[rope, 0]#'- THEN { last ¬ last.rest ¬ LIST[rope]; }; ENDLOOP; RETURN [head.rest] }; GetSwitch: PROC [cmd: Commander.Handle, char: CHAR] RETURNS [BOOL] = { <> stream: IO.STREAM ~ IO.RIS[cmd.commandLine]; FOR rope: ROPE ¬ GetFileNameToken[stream], GetFileNameToken[stream] UNTIL rope = NIL DO IF Rope.Fetch[rope, 0]#'- THEN EXIT; FOR i: INT IN [1..Rope.Size[rope]) DO IF Ascii.Lower[Rope.Fetch[rope, i]] = char THEN RETURN [TRUE]; ENDLOOP; ENDLOOP; RETURN [FALSE] }; PrintNames: PUBLIC PROC [stream: IO.STREAM, groupFormat: ROPE, itemFormat: ROPE, stripVersion: BOOL, list: LIST OF LIST OF DFContents] = { <> <> <> buf: REF TEXT ~ RefText.ObtainScratch[256]; tos: IO.STREAM ¬ IO.TOS[buf]; FOR tail: LIST OF LIST OF DFContents ¬ list, tail.rest UNTIL tail = NIL DO tos ¬ IO.TOS[buf, tos]; FOR t: LIST OF DFContents ¬ tail.first, t.rest UNTIL t = NIL DO list: LIST OF IO.Value ¬ NIL; IF Rope.Match["*%*%*", itemFormat] THEN list ¬ CONS[[time[PFS.FileInfo[PFS.PathFromRope[t.first.name]].uniqueID.egmt.gmt]], list]; list ¬ CONS[[rope[IF stripVersion THEN StripVersion[t.first.name] ELSE t.first.name]], list]; IO.PutFL[tos, itemFormat, list]; ENDLOOP; IO.PutF1[stream, groupFormat, [text[IO.TextFromTOS[tos]]]]; ENDLOOP; RefText.ReleaseScratch[buf]; }; PrintMultiplyDefinedWarning: PUBLIC PROC [stream: IO.STREAM, shortName, df1, df2: ROPE] ~ { IF Rope.Equal[df1, df2, FALSE] THEN IO.PutF[stream, "Warning: %g is defined twice in %g\n", [rope[shortName]], [rope[df1]]] ELSE IO.PutF[stream, "Warning: %g is defined in both %g and %g\n", [rope[shortName]], [rope[df1]], [rope[df2]]]; }; ListAppend: PROC [l1: LORA, l2: LORA ¬ NIL] RETURNS[LORA] ~ { <> RETURN [List.Append[l1, List.Append[l2, NIL]]] }; DFPortCommand: Commander.CommandProc = { <<[cmd: Commander.Handle] RETURNS [result: REF ANY _ NIL, msg: ROPE _ NIL]>> ENABLE Oops => GOTO Fail; cache: SymTab.Ref ~ SymTab.Create[]; combined: DFContents ¬ [NIL, NIL, FALSE]; suites: LIST OF DFContents ¬ NIL; args: LIST OF ROPE ¬ GetArgs[cmd]; NextArg: PROC RETURNS [next: ROPE] ~ {next ¬ args.first; args ¬ args.rest}; IF RopeList.Length[args] < 4 THEN RETURN [result: $Failure, msg: cmd.procData.doc]; BEGIN ENABLE { PFS.Error => {result ¬ $Failure; msg ¬ error.explanation; GOTO Quit}}; portedDFName: ROPE ~ NextArg[]; world: ROPE ~ NextArg[]; componentName: ROPE ~ IF args.rest = NIL THEN BaseName[args.first] ELSE NextArg[]; portedDF: DFContents ¬ ReadDF1[portedDFName, cache]; definerTable: SymTab.Ref ¬ GetDefinerTable[portedDFName ! MultiplyDefinedShortname => { PrintMultiplyDefinedWarning[cmd.err, shortName, df1, df2]; RESUME; }; ]; newTopDF: ROPE ~ ConsName[world, topDir, componentName, dfModifier[suite]]; doSuites: BOOL ~ GetSwitch[cmd, 's]; FOR tail: LIST OF ROPE ¬ args, tail.rest UNTIL tail = NIL DO name: ROPE ~ tail.first; new: DFContents ~ ReadDF1[name, cache]; IF combined.name = NIL THEN combined ¬ new ELSE combined.contents ¬ ListAppend[combined.contents, new.contents]; ENDLOOP; combined ¬ SortDF[ExpandIncludes1[SortDF[combined], cache]]; suites ¬ SplitIntoSuites[world, componentName, combined, definerTable, GetSwitch[cmd, 'q], NOT GetSwitch[cmd, 'c], NOT GetSwitch[cmd, 'g] ! MultiplyDefinedShortname => { PrintMultiplyDefinedWarning[cmd.err, shortName, df1, df2]; RESUME; }; CouldntFind => { IO.PutF[cmd.err, "Warning: %g is not defined by %g; assuming %g\n", [rope[shortName]], [rope[portedDFName]], [rope[usingDF]]]; RESUME; } ]; FOR each: LIST OF DFContents ¬ suites, each.rest UNTIL each = NIL DO IF doSuites OR NOT Rope.Match["*-*", each.first.name] THEN WriteDF[each.first]; ENDLOOP; IF rewritePorted THEN { portedDF.contents ¬ ListAppend[portedDF.contents, LIST[NEW[IncludeItem ¬ [ path1: newTopDF, date: [notEqual], path2: NIL, path2IsCameFrom: FALSE ]]] ]; portedDF.name ¬ portedDFName; WriteDF[portedDF]; }; IF cacheNew THEN CacheDefinerTable[portedDFName, AugmentDefinerTable[ReadDFs[LIST[newTopDF]], definerTable] ! MultiplyDefinedShortname => { PrintMultiplyDefinedWarning[cmd.err, shortName, df1, df2]; RESUME } ] EXITS Quit => NULL; END; EXITS Fail => {result ¬ $Failure; msg ¬ "DFPort Failed."}; }; CmdReadDFs: PROC [cmd: Commander.Handle, dfNames: LIST OF ROPE, followImports: BOOL ¬ FALSE] RETURNS [LIST OF DFContents] ~ { ENABLE PFS.Error => { IO.PutF1[cmd.err, "Error: %g\n", [rope[error.explanation]]]; ERROR Oops; }; RETURN[ReadDFs[dfNames, followImports]]; }; DFSortCommand: Commander.CommandProc = { ENABLE Oops => CommanderOps.Failed["DFSort Failed."]; incl: BOOL ~ GetSwitch[cmd, 'i]; dates: BOOL ~ GetSwitch[cmd, 'd]; groupFormat: ROPE ~ IF incl THEN "%g\n" ELSE "Do %g\n"; itemFormat: ROPE ~ IF incl THEN IF dates THEN dateItemFormat ELSE oneItemFormat ELSE "%g "; PrintNames[cmd.out, groupFormat, itemFormat, incl, TopoSortDFs[CmdReadDFs[cmd, GetArgs[cmd], FALSE]]]; }; Memb: PROC [name: ROPE, b: LIST OF DFContents] RETURNS [BOOL ¬ FALSE] ~ { FOR tail: LIST OF DFContents ¬ b, tail.rest UNTIL tail=NIL DO IF Rope.Equal[name, tail.first.name, FALSE] THEN RETURN [TRUE] ENDLOOP; }; SubtractDFs: PROC [a, b: LIST OF DFContents] RETURNS [LIST OF DFContents] ~ { result: LIST OF DFContents ¬ NIL; FOR tail: LIST OF DFContents ¬ a, tail.rest UNTIL tail=NIL DO IF NOT Memb[tail.first.name, b] THEN result ¬ CONS[tail.first, result]; ENDLOOP; RETURN [result] }; oneItemFormat: ROPE ~ "Include %g Of ~=\n "; dateItemFormat: ROPE ~ "Include %g Of %u\n "; DFNeedsCommand: Commander.CommandProc = { ENABLE Oops => CommanderOps.Failed["DFNeeds Failed."]; strip: BOOL ¬ TRUE; doDates: BOOL ¬ FALSE; groupFormat: ROPE ¬ "%g\n"; itemFormat: ROPE ¬ oneItemFormat; args: ARRAY [0..1] OF LIST OF ROPE ¬ ALL[NIL]; sign: [0..1] ¬ 0; FOR arg: ROPE ¬ CommanderOps.NextArgument[cmd], CommanderOps.NextArgument[cmd] UNTIL arg = NIL DO SELECT TRUE FROM Rope.Equal[arg, "-d"] => doDates ¬ TRUE; Rope.Equal[arg, "-i"] => { strip ¬ TRUE; groupFormat ¬ "%g\n"; itemFormat ¬ oneItemFormat; }; Rope.Equal[arg, "-~i"] => { strip ¬ FALSE; groupFormat ¬ "Do %g\n"; itemFormat ¬ "%g "; }; Rope.Equal[arg, "-"] => sign ¬ 1; Rope.Equal[arg, "+"] => sign ¬ 0; Rope.Match["-*", arg] => CommanderOps.Failed[Rope.Cat["bad switch: ", arg, "\n", cmd.procData.doc]]; ENDCASE => { args[sign] ¬ CONS[arg, args[sign]] }; ENDLOOP; IF args[0]=NIL THEN CommanderOps.Failed[cmd.procData.doc]; IF strip AND doDates THEN itemFormat ¬ dateItemFormat; PrintNames[cmd.out, groupFormat, itemFormat, strip, TopoSortDFs[SubtractDFs[ CmdReadDFs[cmd, args[0], TRUE], CmdReadDFs[cmd, args[1], FALSE]]]]; }; <> <<[] _ SymTab.Insert[serverTranslation, "PCedarChest1.1", Rope.Flatten["/pixel2/pcedarchest1.1/"]];>> [] ¬ SymTab.Insert[serverTranslation, "PCedar2.0", Rope.Flatten["/volume/pixel1/pcedar2.0/"]]; RETURN [serverTranslation] };>> NFSRemoteFileNameFromFSName: PUBLIC PROC [rope: ROPE] RETURNS [ROPE] ~ { <> <> ForceLower: Rope.TranslatorType ~ { RETURN [IF old IN ['A..'Z] THEN old+('a-'A) ELSE old] }; translated: PATH ~ PFSPrefixMap.Translate[PFS.PathFromRope[rope]]; version: PFSNames.Version ~ PFSNames.ShortName[translated].version; sans: PATH ~ PFSNames.SetVersionNumber[translated, [none]]; name: ROPE ¬ PFS.RopeFromPath[sans, slashes]; colon: INT ~ Rope.Find[name, ":"]; IF colon >= 0 THEN name ¬ Rope.Substr[name, colon+1]; IF version.versionKind = numeric THEN { <> name ¬ IO.PutFR["%g.~%g~", [rope[Rope.Translate[base: name, translator: ForceLower]]], [cardinal[version.version]]]; }; RETURN [name] }; levels: LIST OF ROPE ¬ LIST["-o3", ""]; DFPCRLoadeesCommand: Commander.CommandProc = { ENABLE UNCAUGHT => {GOTO Uncaught}; BEGIN ENABLE { PFS.Error => {result ¬ $Failure; msg ¬ error.explanation; GOTO Quit}}; args: LIST OF ROPE ~ GetArgs[cmd]; definerTable: SymTab.Ref ~ GetDefinerTable[args.first ! MultiplyDefinedShortname => { PrintMultiplyDefinedWarning[cmd.err, shortName, df1, df2]; RESUME; }; ]; require: BOOL ~ GetSwitch[cmd, 'r]; model: ROPE = args.rest.first; FOR tail: LIST OF ROPE ¬ args.rest.rest, tail.rest UNTIL tail = NIL DO IF tail.first.Fetch[0] = '" THEN { IO.PutRope[cmd.out, NARROW[IO.GetRefAny[IO.RIS[tail.first]]]]; IO.PutRope[cmd.out, "\l"]; } ELSE { newestDefiner: REF DefinerRep ¬ NIL; latestTime: BasicTime.GMT ¬ BasicTime.nullGMT; level: ROPE ¬ NIL; FOR m: LIST OF ROPE ¬ levels, m.rest UNTIL m = NIL DO WITH SymTab.Fetch[definerTable, Rope.Cat[model, m.first, ">", tail.first, ".c2c.o"]].val SELECT FROM definer: REF DefinerRep => { created: BasicTime.GMT ~ PFS.FileInfo[name: PFS.PathFromRope[definer.fullFName]].uniqueID.egmt.gmt; IF newestDefiner = NIL OR BasicTime.Period[from: latestTime, to: created] > 0 THEN { newestDefiner ¬ definer; latestTime ¬ created; level ¬ m.first; }; }; ENDCASE => NULL; ENDLOOP; IF newestDefiner # NIL THEN { IF require THEN { s: PATH = PFS.PathFromRope[newestDefiner.fullFName]; n: NAT = PFSNames.ComponentCount[s]; shortName: ROPE ~ Fetch[s, 4]; IF Rope.Match[pattern: "-o*", object: level, case: FALSE] THEN IO.PutChar[cmd.out, 'O]; IO.PutF[cmd.out, "RequireFrom %g %g %g\l", [rope[Fetch[s, 1]]], [rope[Fetch[s, 2]]], [rope[Rope.Substr[shortName, 0, Rope.Index[s1: shortName, s2: "."]]]] ]; } ELSE { IO.PutF[cmd.out, "LoadAndRun %g %g\l", [rope[NFSRemoteFileNameFromFSName[newestDefiner.fullFName]]], [rope[tail.first]]]; }; } ELSE { IO.PutF[cmd.err, "-- Error: %g is not accessible via %g\n", [rope[tail.first]], [rope[args.first]]]; IO.PutF1[cmd.out, "-- %g\l", [rope[tail.first]]]; }; }; ENDLOOP; EXITS Quit => NULL; END; EXITS Uncaught => RETURN [result: $Failure, msg: "UNCAUGHT ERROR during DFPCRLoadeesCommand"] }; DFDoForSourcesCommand: Commander.CommandProc = { args: LIST OF ROPE ~ GetArgs[cmd]; doDefinitions: BOOL ~ GetSwitch[cmd, 'd]; commandName: ROPE ~ args.first; combined: DFContents ¬ [NIL, NIL, FALSE]; FOR tail: LIST OF ROPE ¬ args.rest, tail.rest UNTIL tail = NIL DO name: ROPE ~ tail.first; new: DFContents ~ ReadDF[name]; IF combined.name = NIL THEN combined ¬ new ELSE combined.contents ¬ ListAppend[combined.contents, new.contents]; ENDLOOP; combined ¬ SortDF[ExpandIncludes[SortDF[combined]]]; FOR tail: LORA ¬ combined.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM f: REF FullFileItem => { stripped: ROPE ~ StripVersion[f.file.name]; s: FileNameSegments ~ DissectFileName[f.file.name]; ext: ROPE ~ Rope.Substr[s[ext].base, s[ext].start, s[ext].length]; Match: PROC [x: ROPE] RETURNS [BOOL] ~ { RETURN [Rope.Equal[s1: x, s2: ext, case: FALSE]] }; interesting: BOOL ¬ FALSE; SELECT TRUE FROM Match["mesa"] => {interesting ¬ doDefinitions OR IsImplementation[stripped]}; Match["config"] => {interesting ¬ TRUE}; Match["scheme"] => {interesting ¬ TRUE}; Match["tioga"] => {interesting ¬ TRUE}; Match["cm"] => {interesting ¬ TRUE}; Match["require"] => {interesting ¬ TRUE}; Match["command"] => {interesting ¬ TRUE}; Match["c"] => {interesting ¬ TRUE}; ENDCASE; IF interesting THEN [] ¬ CommanderOps.DoCommand[commandLine: Rope.Cat[commandName, " ", stripped], parent: cmd]; }; ENDCASE => NULL; ENDLOOP; }; OnPatternList: PROC [patterns: LIST OF ROPE, object: ROPE] RETURNS [BOOL] ~ { FOR tail: LIST OF ROPE ¬ patterns, tail.rest UNTIL tail = NIL DO IF Rope.Match[pattern: tail.first, object: object, case: FALSE] THEN RETURN [TRUE]; ENDLOOP; RETURN [FALSE] }; FilterD: TYPE ~ {definition, implementation, all}; DFContentsCommand: Commander.CommandProc = { picture: ROPE ¬ "/dir/subdir/base.ext!vers"; combined: DFContents ¬ [NIL, NIL, FALSE]; filterA: DFUtilities.FilterA ¬ $all; filterD: FilterD ¬ $all; patterns: LIST OF ROPE ¬ NIL; remote: BOOL ¬ FALSE; FOR arg: ROPE ¬ CommanderOps.NextArgument[cmd], CommanderOps.NextArgument[cmd] UNTIL arg = NIL DO IF Rope.Match["-*", arg] THEN { FOR i: INT IN [1..Rope.Size[arg]) DO SELECT Rope.Fetch[arg, i] FROM 'b => filterA ¬ $derived; 'd => filterD ¬ $definition; 'i => filterD ¬ $implementation; 'o => patterns ¬ CONS[CommanderOps.NextArgument[cmd], patterns]; 'p => picture ¬ CommanderOps.NextArgument[cmd]; 'r => remote ¬ TRUE; 's => filterA ¬ $source; ENDCASE => GOTO Usage; ENDLOOP; } ELSE { new: DFContents ~ ReadDF[arg]; IF combined.name = NIL THEN combined ¬ new ELSE combined.contents ¬ ListAppend[combined.contents, new.contents]; }; ENDLOOP; IF combined.name = NIL THEN GOTO Usage; combined ¬ SortDF[ExpandIncludes[SortDF[combined]]]; FOR tail: LORA ¬ combined.contents, tail.rest UNTIL tail = NIL DO WITH tail.first SELECT FROM f: REF FullFileItem => { FullFName: PROC [versioned: BOOL] RETURNS [ROPE] ~ { fullFName: ROPE ¬ Rope.Concat[f.directory.path1, f.file.name]; IF NOT versioned THEN fullFName ¬ fullFName.Substr[0, fullFName.Index[0, "!"]]; RETURN [fullFName] }; MatchExt: PROC [x: ROPE] RETURNS [BOOL] ~ { RETURN [Rope.FindBackward[s1: f.file.name, s2: x, case: FALSE] + Rope.Size[x] = Rope.Index[f.file.name, 0, "!"]] }; interesting: BOOL ¬ ( (filterA=$all OR DFUtilities.ClassifyFileExtension[f.file.name]=filterA) AND (filterD = $all OR NOT MatchExt["mesa"] OR (IsImplementation[IF remote THEN FullFName[TRUE] ELSE StripVersion[f.file.name]] = (filterD=$implementation))) AND (patterns = NIL OR OnPatternList[patterns, FullFName[FALSE]])); IF interesting THEN { s: FileNameSegments ~ DissectFileName[f.file.name]; rope: ROPE ¬ picture; start: INT ¬ 0; Key: TYPE ~ {dir, slashDir, subdir, slashSubdir, base, ext, vers}; keyname: ARRAY Key OF ROPE ~ ["[dir]", "/dir/", "subdir>", "subdir/", "base", ".ext", "!vers"]; WHILE start < Rope.Size[rope] DO match: Key ¬ $base; matchIndex: INT ¬ LAST[INT]; FOR key: Key IN Key DO i: INT ~ Rope.Index[rope, start, keyname[key]]; SELECT i FROM < matchIndex => {match ¬ key; matchIndex ¬ i}; = matchIndex => {IF matchIndex=LAST[INT] OR keyname[key].Size > keyname[match].Size THEN { match ¬ key; matchIndex ¬ i }}; ENDCASE; ENDLOOP; IF matchIndex < Rope.Size[rope] THEN { ForceSlash: Rope.TranslatorType ~ { RETURN [IF old = '> THEN '/ ELSE old] }; replacement: ROPE ~ SELECT match FROM dir => f.directory.path1, slashDir => PFS.RopeFromPath[PFS.PathFromRope[f.directory.path1]], subdir => Subname[s, dir], slashSubdir => Rope.Translate[base: s[dir].base, start: s[dir].start, len: s[dir].length, translator: ForceSlash], base => Subname[s, base], ext => IF s[ext].length # 0 THEN Rope.Concat[".", Subname[s, ext]] ELSE NIL, vers => IF s[version].length # 0 THEN Rope.Concat["!", Subname[s,version]] ELSE NIL, ENDCASE => NIL; rope ¬ Rope.Replace[base: rope, start: matchIndex, len: keyname[match].Size, with: replacement]; start ¬ matchIndex + replacement.Size; } ELSE EXIT; ENDLOOP; IO.PutRope[cmd.out, rope]; IO.PutChar[cmd.out, '\n]; }; }; ENDCASE => NULL; ENDLOOP; EXITS Usage => {CommanderOps.Failed[cmd.procData.doc]}; }; Commander.Register[key: "DFPort", proc: DFPortCommand, doc: "Args: [-c] [-g] [-s] Ported.df Cedar10.1 Component [PCedar2.0]Component-Suite.df ...\n -c => omit intermediate sources (e.g., .c2c.c files)\n -g => omit non-goal object files\n -s => emit PCedar - style suites of DF files"]; Commander.Register[key: "DFSort", proc: DFSortCommand, doc: "Do a topological sort of a collection of DF files (and their includes)"]; Commander.Register[key: "DFNeeds", proc: DFNeedsCommand, doc: "Do a topological sort of a collection of DF files and their imports, optionally excluding others\nargs: { -d } { + * | - * | -i | -~i }*"]; Commander.Register[key: "DFDoForSources", proc: DFDoForSourcesCommand, doc: "Do a command for each source file\nArgs: CommandName DFFileName ...\nswitches:\n-d\t do DEFINITIONS files\n-b\tinclude base as an argument\n-x\tinclude extension as an argument"]; Commander.Register[key: "DFContents", proc: DFContentsCommand, doc: "Produce a list of filenames from DF files, subject to filters:\nargs: ( | )*\nswitches:\n-b\tderived files only\n-d\tdefinition files only (mesa interfaces)\n-i\timplementation files only (mesa programs and monitors)\n-o include files matching pattern\n-p format output according to picture (default: /dir/subdir/base.ext!vers)\n-r\tuse remote filename for -d/-i filter\n-s\tsource files only"]; Commander.Register[key: "DFPCRLoadees", proc: DFPCRLoadeesCommand, doc: "Type a Loadees file for PCR: [-r] DFName sun4 (moduleName | \"literal\") ..."]; END.