<> <> DIRECTORY Asserting USING [Assertions, Terms, Assert, AssertFn, AssertFn1, FnVal], Atom, Basics, BasicTime, Buttons, Containers, FS, HashTable, Icons, IO, LichenDataStructure, LichenDataOps, LichenSetTheory, List, PieViewers, Process, ProcessProps, RedBlackTree, RefText, Rope, RopeHash, ViewerClasses, ViewerOps, ViewerTools; LichenFromExt: CEDAR MONITOR LOCKS dr USING dr: DesignReading IMPORTS Asserting, Atom, BasicTime, Buttons, Containers, FS, HashTable, Icons, IO, LichenDataStructure, LichenDataOps, LichenSetTheory, List, PieViewers, Process, ProcessProps, RedBlackTree, RefText, Rope, RopeHash, ViewerOps, ViewerTools = BEGIN OPEN Asserting, LichenDataStructure, LichenDataOps, LichenSetTheory; REFTEXT: TYPE = REF TEXT; Viewer: TYPE = ViewerClasses.Viewer; Source: TYPE = RECORD [stream: IO.STREAM _ NIL, name: ROPE _ NIL]; Reader: TYPE = REF ReaderRep; ReaderRep: TYPE = RECORD [ keyword: ROPE, read: PROC [s: Source, reader: Reader, cr: CellReading], <> data: REF ANY]; readers: Mapper _ CreateHashDictionary[TRUE]; DesignReading: TYPE = REF DesignReadingRep; DesignReadingRep: TYPE = MONITORED RECORD [ design: Design, wDir: ROPE, cellTypesByName: Mapper, fetTypes: HashTable.Table, unkosherArrays: Set, toMerge: RedBlackTree.Table, mostRecentPathToMerge: Path _ NIL, buffer: REFTEXT, pacifier, pie, label, pause: Viewer, lastPacify: BasicTime.Pulses, stop: BOOL _ FALSE, change: CONDITION]; undefinedINT: INT = FIRST[INT]; CellReading: TYPE = REF CellReadingRep; CellReadingRep: TYPE = RECORD [ dr: DesignReading, ct: CellType, name: ROPE, resistClasses: INT _ undefinedINT, rScale: REAL--ohms-- _ 1.0E-3, cScale: REAL--farads-- _ 1.0E-18, lUnits: REAL--meters-- _ 1.0E-8, scalingDefined: BOOL _ FALSE, fetCount: INT _ 0 ]; Path: TYPE = LIST OF REF ANY--UNION [ROPE, REF Range2]--; VertexArray: TYPE = REF VertexArrayRep; VertexArrayRep: TYPE = RECORD [ shape: Size2, vertices: SEQUENCE length: NAT OF Vertex]; Use: TYPE = RECORD [childName: ROPE, as: ArraySpec]; ArraySpec: TYPE = RECORD [ variant: SELECT kind: * FROM scalar => [], array => [ range: Range2, sep: Size2 ] ENDCASE]; FetTerminal: TYPE = RECORD [ name: ROPE, length: INT, attrs: Assertions]; IntBox: TYPE = RECORD [xmin, ymin, xmax, ymax: INT]; Int2: TYPE = ARRAY Dim OF INT; TransformAsTerms: TYPE = Terms; PathPair: TYPE = REF PathPairPrivate; PathPairPrivate: TYPE = RECORD [p1, p2: Path]; pacifierIcon: Icons.IconFlavor _ Icons.NewIconFromFile["Lichen.icons", 0]; labelHeight: INTEGER _ 15; pauseWidth: INTEGER _ 75; ReadDesign: PROC [rootCellFileName: ROPE, oldDR: DesignReading _ NIL] RETURNS [dr: DesignReading] = BEGIN Doit: PROC = {[] _ ReadCellType[dr.design, rootCellFileName, dr]}; IF oldDR = NIL THEN { cp: FS.ComponentPositions; fullFName, designName: ROPE; [fullFName, cp, ] _ FS.ExpandName[rootCellFileName]; designName _ fullFName.Substr[start: cp.base.start, len: cp.base.length]; dr _ NEW [DesignReadingRep _ [ design: NEW [DesignPrivate _ [ cellTypes: CreateHashSet[], other: Assert[nameReln, LIST[designName], NIL] ]], wDir: fullFName.Substr[len: cp.base.start], cellTypesByName: CreateHashDictionary[TRUE], fetTypes: HashTable.Create[hash: HashFetType, equal: CompareFetTypes], unkosherArrays: CreateHashSet[], toMerge: RedBlackTree.Create[Id, ComparePaths], buffer: RefText.New[200], pacifier: Containers.Create[info: [name: designName.Cat[" pacifier"], icon: pacifierIcon]], pie: NIL, label: NIL, pause: NIL, lastPacify: BasicTime.GetClockPulses[] - pacifyPulses ]]; TRUSTED { Process.InitializeCondition[@dr.change, Process.SecondsToTicks[60]]; Process.EnableAborts[@dr.change]}; dr.pause _ Buttons.Create[info: [name: "Pause", parent: dr.pacifier, wx: 0, wy: 0, ww: pauseWidth, wh: labelHeight], proc: TogglePause, clientData: dr]; dr.label _ ViewerTools.MakeNewTextViewer[info: [parent: dr.pacifier, wx: dr.pause.wx+dr.pause.ww, wy: 0, ww: 100, wh: labelHeight]]; Containers.ChildXBound[container: dr.pacifier, child: dr.label]; dr.pie _ PieViewers.Create[parent: dr.pacifier, x: 0, y: dr.label.wy+dr.label.wh, diameter: 20, total: 1.0, divisions: 100]; ViewerOps.SetOpenHeight[dr.pacifier, dr.pie.wy+dr.pie.wh]; } ELSE { dr _ oldDR; }; ProcessProps.PushPropList[List.PutAssoc[$WorkingDirectory, dr.wDir, NIL], Doit]; ViewerTools.SetContents[dr.label, "Idle"]; PieViewers.Set[dr.pie, 0]; END; TogglePause: Buttons.ButtonProc = { dr: DesignReading = NARROW[clientData]; Flip: ENTRY PROC [dr: DesignReading] = { dr.stop _ NOT dr.stop; BROADCAST dr.change}; Flip[dr]; Buttons.ReLabel[dr.pause, IF dr.stop THEN "Continue" ELSE "Pause"]; }; fromExtClass: CellClass _ NEW [CellClassPrivate _ []]; pacifyPulses: BasicTime.Pulses _ BasicTime.MicrosecondsToPulses[2500000]; ReadCellType: PROC [design: Design, cellFileName: ROPE, dr: DesignReading] RETURNS [ct: CellType] = { cp: FS.ComponentPositions; fullFName, cellTypeName: ROPE; from: IO.STREAM; s: Source; cr: CellReading; length: REAL; [fullFName, cp] _ ExpandName[cellFileName, "ext"]; cellTypeName _ fullFName.Substr[start: cp.base.start, len: cp.base.length]; ct _ CreateCellType[design, dr, cellTypeName, TRUE, NIL, NIL]; cr _ NEW[CellReadingRep _ [dr: dr, ct: ct, name: cellTypeName]]; s _ [from _ FS.StreamOpen[fullFName], fullFName]; length _ INT[MAX[from.GetLength[], 1]]; DO keyword: ROPE; reader: Reader; now: BasicTime.Pulses = BasicTime.GetClockPulses[]; Process.CheckForAbort[]; [] _ from.SkipWhitespace[]; IF from.EndOf[] THEN EXIT; IF now-dr.lastPacify >= pacifyPulses THEN { index: INT = from.GetIndex[]; dr.lastPacify _ now; ViewerTools.SetContents[dr.label, IO.PutFR["%g[%g]", [rope[cellTypeName]], [integer[index]]]]; PieViewers.Set[dr.pie, index/length]; }; IF dr.stop THEN Wait[dr]; keyword _ from.GetTokenRope[TokenBreak].token; reader _ NARROW[readers.Map[keyword]]; IF reader # NIL THEN reader.read[s, reader, cr] ELSE { terms: Terms _ GetLineTerms[from]; reln: ATOM _ Atom.MakeAtom[keyword]; ct.otherPublic _ Assert[reln, terms, ct.otherPublic]; }; ENDLOOP; IF dr.toMerge.Size[] # 0 THEN DoMerges[s, ct, dr]; ct.publicKnown _ TRUE; ct.privateKnown _ TRUE; from.Close[]; }; Wait: ENTRY PROC [dr: DesignReading] = { WHILE dr.stop DO WAIT dr.change ENDLOOP}; GetLineTerms: PROC [from: IO.STREAM] RETURNS [terms: Terms] = { tail: Terms _ terms _ NIL; WHILE NOT from.EndOf[] DO peek: CHAR _ from.PeekChar[]; SELECT peek FROM '\n => {IF from.GetChar[] # peek THEN ERROR; RETURN}; IN [0C .. ' ] => IF from.GetChar[] # peek THEN ERROR; ENDCASE => { this: LORA _ LIST[from.GetRefAny[]]; IF tail = NIL THEN terms _ this ELSE tail.rest _ this; tail _ this}; ENDLOOP; }; ExpandName: PROC [fileName, defaultExtension: ROPE] RETURNS [fullFName: ROPE, cp: FS.ComponentPositions] = { [fullFName, cp, ] _ FS.ExpandName[fileName]; IF defaultExtension.Length[] > 0 AND cp.ext.length = 0 THEN { fileName _ FS.ConstructFName[[ server: fullFName.Substr[cp.server.start, cp.server.length], dir: fullFName.Substr[cp.dir.start, cp.dir.length], subDirs: fullFName.Substr[cp.subDirs.start, cp.subDirs.length], base: fullFName.Substr[cp.base.start, cp.base.length], ext: defaultExtension, ver: fullFName.Substr[cp.ver.start, cp.ver.length] ]]; [fullFName, cp, ] _ FS.ExpandName[fileName]; }; }; GetName: PROC [s: Source] RETURNS [name: ROPE] = { from: IO.STREAM = s.stream; [] _ from.SkipWhitespace[]; SELECT from.PeekChar[] FROM '" => name _ from.GetRopeLiteral[]; ENDCASE => name _ from.GetTokenRope[TokenBreak].token; }; TokenBreak: PROC [char: CHAR] RETURNS [cc: IO.CharClass] = {cc _ SELECT char FROM '\n => break, IN [0C .. ' ] => sepr, ENDCASE => other}; EndLine: PROC [from: IO.STREAM, buffer: REFTEXT] = { IF NOT from.EndOf[] THEN [] _ from.GetLine[buffer]; }; ReadTech: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; techname: ROPE _ GetName[s]; ct.otherPublic _ Assert[$tech, LIST[techname], ct.otherPublic]; EndLine[from, cr.dr.buffer]; }; ReadTimestamp: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; unixTime: INT _ from.GetInt[]; time: BasicTime.GMT _ BasicTime.Update[unixOrigin, unixTime]; ct.otherPublic _ Assert[$Source, LIST[cr.name.Cat[".mag"], IO.PutFR["%g", IO.time[time]]], ct.otherPublic]; EndLine[from, cr.dr.buffer]; }; unixOrigin: BasicTime.GMT _ BasicTime.Pack[[ year: 1970, month: January, day: 1, hour: 0, minute: 0, second: 0, zone: 0--GMT, I hope--, dst: no]]; ReadVersion: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; version: ROPE _ GetName[s]; deriver: ROPE = "UCB's Magic .extractor"; ct.otherPublic _ Assert[$DerivingProgram, LIST[deriver, version], ct.otherPublic]; EndLine[from, cr.dr.buffer]; }; ReadScale: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; rscale: INT _ from.GetInt[]; cscale: INT _ from.GetInt[]; lscale: INT _ from.GetInt[]; meters: ROPE = "meters"; IF cr.scalingDefined THEN Warn[s, "More than one scale statment"]; cr.scalingDefined _ TRUE; cr.rScale _ rscale * cr.rScale; cr.cScale _ cscale * cr.cScale; cr.lUnits _ lscale * cr.lUnits; ct.otherPublic _ AssertFn[$scale, LIST[NEW[REAL_cr.lUnits], meters], ct.otherPublic]; EndLine[from, cr.dr.buffer]; }; ReadResistClasses: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; n: INT _ 0; IF cr.resistClasses # undefinedINT THEN Warn[s, "More than one resistclasses statment"]; DO token: ROPE = from.GetTokenRope[TokenBreak].token; IF token.Equal["\n"] THEN EXIT; n _ n + 1; ENDLOOP; cr.resistClasses _ n; }; ReadNode: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; nodeName: ROPE = GetName[s]; R: INT = from.GetInt[]; C: INT = from.GetInt[]; x: INT = from.GetInt[]; y: INT = from.GetInt[]; ok: BOOL = SkipNTokens[from, cr.resistClasses*2, cr.dr.buffer]; attrs: Assertions = ReadAttrs[s]; nv: Wire = CreateWire[ containingCT: ct, other: Assert[nameReln, LIST[nodeName], Assert[$R, LIST[NEW[REAL _ R*cr.rScale]], Assert[$C, LIST[NEW[REAL _ C*cr.cScale]], Assert[$locHint, LIST[NEW[INT_x], NEW[INT_y], $UnspecifiedLayer], attrs ]]]] ]; EndLine[from, cr.dr.buffer]; }; ReadAttrs: PROC [s: Source, zeroNIL: BOOL _ FALSE] RETURNS [allTogetherNow: Assertions] = { from: IO.STREAM = s.stream; allTogetherNow _ NIL; IF zeroNIL THEN { [] _ from.SkipWhitespace[]; IF from.PeekChar[] = '0 THEN { IF from.GetChar[] # '0 THEN ERROR; RETURN}; }; DO toke: ROPE _ from.GetTokenRope[AttrBreak !IO.EndOfStream => GOTO Dun].token; attr: ROPE _ NIL; IF toke.Equal[","] THEN {Warn[s, "Extra comma"]; LOOP}; IF toke.Equal["\n"] THEN GOTO Return; IF NOT toke.Equal["\""] THEN EXIT; from.Backup['"]; attr _ from.GetRopeLiteral[ !IO.Error, IO.EndOfStream => {Warn[s, "not a rope literal"]; CONTINUE}]; IF attr # NIL THEN allTogetherNow _ Assert[$attr, LIST[attr], allTogetherNow]; toke _ from.GetTokenRope[AttrBreak !IO.EndOfStream => EXIT].token; IF toke.Equal["\n"] THEN GOTO Return; IF NOT toke.Equal[","] THEN EXIT; ENDLOOP; EXITS Return => s.stream.Backup['\n]; Dun => NULL; }; AttrBreak: PROC [char: CHAR] RETURNS [cc: IO.CharClass] = {cc _ SELECT char FROM ',, '\n, '" => break, ENDCASE => sepr}; ReadEquiv: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; <> <> EndLine[from, cr.dr.buffer]; }; ReadFet: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; type: ROPE _ GetName[s]; xl: INT _ from.GetInt[]; yl: INT _ from.GetInt[]; xh: INT _ from.GetInt[]; yh: INT _ from.GetInt[]; area: INT _ from.GetInt[]; perim: INT _ from.GetInt[]; sub: ROPE _ GetName[s]; GATE: FetTerminal _ GetFetTerminal[s]; T1: FetTerminal _ GetFetTerminal[s]; T2: FetTerminal _ GetFetTerminal[s]; sct: CellType; tv: CellInstance; DoTerm: PROC [portIndex: INT, ft: FetTerminal] = { nv: Wire = GetNet[s, ct, ft.name]; Connect[tv, nv, portIndex]; }; sct _ GetFetType[cr.dr, type, [xl, yl, xh, yh], area, perim, T1.length+T2.length]; tv _ Instantiate[sct, ct, Assert[nameReln, LIST[IO.PutFR["Q%g", IO.int[cr.fetCount _ cr.fetCount + 1]]], NIL]]; DoTerm[0, GATE]; DoTerm[1, T1]; DoTerm[2, T2]; EndLine[from, cr.dr.buffer]; }; Connect: PROC [ci: CellInstance, wire: Wire, portIndex: INT] = { [] _ AddEdge[vs: [cellward: ci, wireward: wire], port: ci.type.port.SubPort[portIndex]]; }; GetFetTerminal: PROC [s: Source] RETURNS [ft: FetTerminal] = { from: IO.STREAM = s.stream; ft.name _ GetName[s]; ft.length _ from.GetInt[]; ft.attrs _ ReadAttrs[s, TRUE]; }; GetFetType: PROC [dr: DesignReading, className: ROPE, innerGate: IntBox, area, perim, sumChannelLengths: INT] RETURNS [ct: CellType] = { design: Design = dr.design; ft: FetType = NEW [FetTypeRep _ [className, area, perim, sumChannelLengths]]; rft: FetType; rft _ NARROW[dr.fetTypes.Fetch[ft].value]; IF rft = NIL THEN { cellTypeName: ROPE = IO.PutFR["%g[%g,%g,%g]", IO.rope[ft.className], IO.int[ft.area], IO.int[ft.perim], IO.int[ft.twiceLength]]; Set: PROC [type, mode: ATOM] = { ft.ct.otherPublic _ AssertFn1[$MOSFETFlavor, LIST[type, mode], ft.ct.otherPublic]; ft.ct.otherPublic _ AssertFn1[$EquivClass, Rope.Cat["MOSFET", Atom.GetPName[type], Atom.GetPName[mode]], ft.ct.otherPublic]; }; rft _ ft; ft.ct _ CreateCellType[design, dr, cellTypeName, FALSE, AssertFn1[$MOSFETShape, LIST[NEW[REAL _ ft.twiceLength/2.0], NEW[REAL _ area*2.0/ft.twiceLength]], NIL], NIL]; FetPort[ft.ct.port]; SELECT TRUE FROM className.Equal["nfet"] => Set[$n, $E]; className.Equal["pfet"] => Set[$p, $E]; ENDCASE => ERROR; IF NOT dr.fetTypes.Insert[ft, ft] THEN ERROR; }; ct _ rft.ct; }; FetPort: PROC [fp: Port] = { [] _ AddPort[[parent: fp, other: Assert[nameReln, LIST[R["gate"]], NIL]]]; [] _ AddPort[[parent: fp, other: Assert[nameReln, LIST[R["ch1"]], NIL]]]; [] _ AddPort[[parent: fp, other: Assert[nameReln, LIST[R["ch2"]], NIL]]]; }; R: PROC [r: ROPE] RETURNS [r2: ROPE] = INLINE {r2 _ r}--stupid goddam anachronism--; FetType: TYPE = REF FetTypeRep; FetTypeRep: TYPE = RECORD [ className: ROPE, area, perim, twiceLength: INT, ct: CellType _ NIL]; HashFetType: PROC [ra: REF ANY] RETURNS [hash: CARDINAL] --HashTable.HashProc-- = { ft: FetType = NARROW[ra]; hash _ RopeHash.FromRope[ft.className]; hash _ (hash + 3*ft.area + 11*ft.perim + 101*ft.twiceLength) MOD 65536; }; CompareFetTypes: PROC [r1, r2: REF ANY] RETURNS [equal: BOOL] --HashTable.EqualProc-- = { k1: FetType = NARROW[r1]; k2: FetType = NARROW[r2]; equal _ k1.className.Equal[k2.className] AND k1.area = k2.area AND k1.perim = k2.perim AND k1.twiceLength = k2.twiceLength; }; ReadUse: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; typeName: ROPE = GetName[s]; useId: ROPE = GetName[s]; ok: BOOL = SkipNTokens[from, 6, cr.dr.buffer]; u: Use = ParseUseDef[useId]; type: CellType = EnsureType[cr.dr, typeName, u.as, ct, u.childName]; ci: CellInstance = Instantiate[type, ct, Assert[nameReln, LIST[u.childName], NIL]]; EndLine[from, cr.dr.buffer]; }; ParseUseDef: PROC [useId: ROPE] RETURNS [u: Use] = { in: IO.STREAM = IO.RIS[useId]; u.childName _ in.GetTokenRope[UseNameBreak].token; IF in.EndOf[] THEN { in.Close[]; RETURN [[u.childName, [scalar[]]]] } ELSE { as: ArraySpec.array _ [array[range: ALL[[0, 0]], sep: [0, 0]]]; Get: PROC [d: Dim] = { IF in.GetChar[] # '[ THEN ERROR; as.range[d].min _ in.GetInt[]; IF in.GetChar[] # ': THEN ERROR; as.range[d].maxPlusOne _ in.GetInt[]+1; IF in.GetChar[] # ': THEN ERROR; as.sep[d] _ in.GetInt[]; IF in.GetChar[] # '] THEN ERROR; }; Get[Foo]; Get[Bar]; IF NOT in.EndOf[] THEN ERROR; in.Close[]; RETURN [[u.childName, as]]; }; }; UseNameBreak: PROC [char: CHAR] RETURNS [cc: IO.CharClass] --IO.BreakProc-- = { cc _ SELECT char FROM '[, '], ': => break, ENDCASE => other; }; EnsureType: PROC [dr: DesignReading, typeName: ROPE, as: ArraySpec, parent: CellType, childName: ROPE] RETURNS [ct: CellType] = { design: Design = dr.design; WITH as SELECT FROM x: ArraySpec.scalar => { ct _ NARROW[dr.cellTypesByName.Map[typeName]]; IF ct = NIL THEN ct _ ReadCellType[design, typeName, dr]; }; x: ArraySpec.array => { ec: ROPE = typeName.Cat[FmtAS[as]]; cellTypeName: ROPE = IO.PutFR["%g(%g.%g)", IO.rope[ec], IO.rope[CTName[parent]], IO.rope[childName]]; eltType: CellType _ EnsureType[dr, typeName, [scalar[]], NIL, NIL]; size: Size2 = RangeSize[x.range]; ct _ CreateArray[design, dr, cellTypeName, eltType, size, [1, 1], AssertFn1[$EquivClass, ec, NIL], AssertFn1[$ArraySpec, NEW [ArraySpec.array _ x], NIL]]; }; ENDCASE => ERROR; }; RangeSize: PROC [r: Range2] RETURNS [s: Size2] = { s _ [ Foo: r[Foo].maxPlusOne-r[Foo].min, Bar: r[Bar].maxPlusOne-r[Bar].min] }; NameElt: PROC [i: INT] RETURNS [eltName: ROPE] = {eltName _ IO.PutFR["[%g]", IO.int[i]]}; NameElt2: PROC [f, b: INT] RETURNS [eltName: ROPE] = {eltName _ IO.PutFR["[%g, %g]", IO.int[f], [integer[b]]]}; FmtAS: PROC [as: ArraySpec] RETURNS [r: ROPE] = { r _ WITH as SELECT FROM scalar => "scalar", array => IO.PutFLR["[%g:%g:%g][%g:%g:%g]", LIST[ IO.int[range[Foo].min], IO.int[range[Foo].maxPlusOne-1], IO.int[sep[Foo]], IO.int[range[Bar].min], IO.int[range[Bar].maxPlusOne-1], IO.int[sep[Bar]]]], ENDCASE => ERROR; }; FmtShape: PROC [shape: Size2] RETURNS [r: ROPE] = { r _ IO.PutFR["[Foo: %g, Bar: %g]", IO.int[shape[Foo]], IO.int[shape[Bar]]]; }; FmtPath: PROC [path: Path] RETURNS [r: ROPE] = { r _ NIL; FOR path _ path, path.rest WHILE path # NIL DO step: ROPE _ WITH path.first SELECT FROM x: ROPE => x, x: REF Range2 => IO.PutFR["[%g:%g,%g:%g]", [integer[x[Foo].min]], [integer[x[Foo].maxPlusOne-1]], [integer[x[Bar].min]], [integer[x[Bar].maxPlusOne-1]]], ENDCASE => ERROR; r _ (IF r # NIL THEN r.Concat["/"] ELSE r).Concat[step]; ENDLOOP; }; ReadMerge: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; name1: ROPE = GetName[s]; name2: ROPE = GetName[s]; path1: Path _ ParsePath[s, ct, name1]; path2: Path _ ParsePath[s, ct, name2]; IF PathCompare[path1, cr.dr.mostRecentPathToMerge]#equal THEN { DoMerges[s, ct, cr.dr]; cr.dr.toMerge.Insert[path1, path1]; }; cr.dr.toMerge.Insert[path2, path2]; cr.dr.mostRecentPathToMerge _ path2; EndLine[from, cr.dr.buffer]; }; DoMerges: PROC [s: Source, from: CellType, dr: DesignReading] = { lastPath: Path _ NIL; DoAMerge: PROC [data: REF ANY] RETURNS [stop: BOOL _ FALSE] --RedBlackTree.EachNode-- = { path: Path = NARROW[data]; IF lastPath # NIL THEN MergeWork[s, dr, from, lastPath, path]; lastPath _ path; }; dr.toMerge.EnumerateIncreasing[DoAMerge]; dr.toMerge.DestroyTable[]; dr.mostRecentPathToMerge _ NIL; }; ParsePath: PROC [s: Source, from: CellType, asRope: ROPE] RETURNS [p: Path] = { in: IO.STREAM = IO.RIS[asRope]; t: Path _ p _ NIL; Append: PROC [ra: REF ANY] = { this: Path _ LIST[ra]; IF t = NIL THEN p _ this ELSE t.rest _ this; t _ this}; GetRange: PROC RETURNS [x: Range] = { x.maxPlusOne _ (x.min _ in.GetInt[]) + 1; SELECT in.PeekChar[] FROM ': => { IF in.GetChar[] # ': THEN ERROR; x.maxPlusOne _ in.GetInt[] + 1; }; ',, '] => NULL; ENDCASE => ERROR; }; WHILE NOT in.EndOf[] DO toke: ROPE _ in.GetTokenRope[PathNameBreak].token; ras: REF ArraySpec.array = NARROW[FnVal[$ArraySpec, from.otherPrivate]]; SELECT TRUE FROM toke.Equal["/"] => LOOP; toke.Equal["["] => { food: BOOL = ras.range[Foo].min # ras.range[Foo].maxPlusOne-1; bard: BOOL = ras.range[Bar].min # ras.range[Bar].maxPlusOne-1; r2: Range2 _ ras.range; twoD: BOOL _ FALSE; IF NOT (food OR bard) THEN ERROR; IF bard THEN r2[Bar] _ GetRange[] ELSE r2[Foo] _ GetRange[]; toke _ in.GetTokenRope[PathNameBreak].token; SELECT TRUE FROM toke.Equal["]"] => NULL; toke.Equal[","] => { twoD _ TRUE; r2[Foo] _ GetRange[]; toke _ in.GetTokenRope[PathNameBreak].token; IF NOT toke.Equal["]"] THEN ERROR; }; ENDCASE => ERROR; IF twoD # (food AND bard) THEN ERROR; Append[NEW [Range2 _ r2]]; from _ from.asArray.eltType; }; toke.Equal["]"] => ERROR; toke.Equal[":"] => ERROR; toke.Equal[","] => ERROR; ENDCASE => { Append[toke]; WITH LookupPart[from, toke] SELECT FROM ci: CellInstance => from _ ci.type; w: Wire => {IF NOT in.EndOf[] THEN ERROR; from _ NIL}; ENDCASE => ERROR; }; ENDLOOP; in.Close[]; }; PathNameBreak: PROC [char: CHAR] RETURNS [cc: IO.CharClass] --IO.BreakProc-- = { cc _ SELECT char FROM '[, '], ':, '/, ', => break, ENDCASE => other; }; SubType: PROC [ct: CellType, subscript: INT] RETURNS [sct: CellType] = { ci: CellInstance = NARROW[LookupPart[ct, NameElt[subscript]]]; sct _ ci.type}; lowerConnections: BOOL _ FALSE; MergeWork: PROC [s: Source, dr: DesignReading, ct: CellType, path1, path2: Path] = { IF ct.asArray # NIL THEN ERROR; IF path1.rest # NIL AND path2.rest # NIL THEN WITH path1.first SELECT FROM x: ROPE => WITH path2.first SELECT FROM y: ROPE => IF x.Equal[y] THEN { ci: CellInstance = NARROW[LookupPart[ct, x]]; IF ci.type.asArray # NIL THEN { IF ci.type.useCount # 1 THEN ERROR; ArrayMerge[s, dr, ci, x, path1.rest, path2.rest]; RETURN }; }; y: REF Range2 => ERROR; ENDCASE => ERROR; x: REF Range2 => ERROR; ENDCASE => ERROR; MergeFinal[s, dr, ct, path1, path2]; }; ArrayMerge: PROC [s: Source, dr: DesignReading, arrayInstance: CellInstance, instanceName: ROPE, path1, path2: Path] = { act: CellType = arrayInstance.type; a: Array = act.asArray; ras: REF ArraySpec.array = NARROW[FnVal[$ArraySpec, act.otherPrivate]]; et: CellType = a.eltType; rr1: REF Range2 = NARROW[path1.first]; rr2: REF Range2 = NARROW[path2.first]; r1: Range2 = rr1^; r2: Range2 = rr2^; size: Size2 = RangeSize[r2]; xlate: Int2 = [-ras.range[Foo].min, -ras.range[Bar].min]; s1: Range2 = Range2Off[r1, xlate]; s2: Range2 = Range2Off[r2, xlate]; IF RangeSize[r1] # size THEN ERROR; SELECT -1=> SELECT 0 => MakeArrayConnection[act, Foo, s2, PortGet[et, path2.rest], PortGet[et, path1.rest]]; ENDCASE => ERROR; 0 => SELECT -1=> MakeArrayConnection[act, Bar, s2, PortGet[et, path2.rest], PortGet[et, path1.rest]]; 0 => IF NOT PathEquiv[et, path1.rest, path2.rest] THEN { q1: Path = CONS[instanceName, path1]; q2: Path = CONS[instanceName, path2]; FOR foo: INT IN [0 .. size[Foo]) DO FOR bar: INT IN [0 .. size[Bar]) DO foo1: INT = foo + r1[Foo].min; bar1: INT = bar + r1[Bar].min; foo2: INT = foo + r2[Foo].min; bar2: INT = bar + r2[Bar].min; rr1^ _ [[foo1, foo1+1], [bar1, bar1+1]]; rr2^ _ [[foo2, foo2+1], [bar2, bar2+1]]; MergeFinal[s, dr, arrayInstance.containingCT, q1, q2]; ENDLOOP; ENDLOOP; rr1^ _ r1; rr2^ _ r2; }; 1 => MakeArrayConnection[act, Bar, s1, PortGet[et, path1.rest], PortGet[et, path2.rest]]; ENDCASE => ERROR; 1 => SELECT 0 => MakeArrayConnection[act, Foo, s1, PortGet[et, path1.rest], PortGet[et, path2.rest]]; ENDCASE => ERROR; ENDCASE => ERROR; }; Range2Off: PROC [r: Range2, s _ [ Foo: [min: r[Foo].min + Bar: [min: r[Bar].min + ]; }; MergeFinal: PROC [s: Source, dr: DesignReading, ct: CellType, path1, path2: Path] = { w1, w2, nw: Wire; w1 _ PathGet[ct, path1]; w2 _ PathGet[ct, path2]; nw _ MergeNets[w1, w2].merged; }; VAFetch: PROC [va: VertexArray, f, b: NAT] RETURNS [v: Vertex] = { v _ va[f*va.shape[Bar]+b]; }; VAStore: PROC [va: VertexArray, f, b: NAT, v: Vertex] = { va[f*va.shape[Bar]+b] _ v; }; PathGet: PROC [from: CellType, path: Path] RETURNS [w: Wire] = { WITH path.first SELECT FROM r: ROPE => { child: Vertex = LookupPart[from, r]; WITH child SELECT FROM x: Wire => w _ x; ci: CellInstance => { childPort: Port = PortGet[ci.type, path.rest]; w _ FindTransitiveConnection[ci, childPort]; IF w = NIL THEN ERROR; }; ENDCASE => ERROR; }; x: REF Range2 => ERROR; ENDCASE => ERROR; }; PortGet: PROC [from: CellType, path: Path] RETURNS [port: Port] = { WITH path.first SELECT FROM x: REF Range2 => { ras: REF ArraySpec.array = NARROW[FnVal[$ArraySpec, from.otherPrivate]]; a: Array = from.asArray; eltPort: Port = PortGet[a.eltType, path.rest]; index: ArrayIndex = Int2Sub[Range2Min[x^], Range2Min[ras.range]]; FOR d: Dim IN Dim DO IF x[d].min+1 # x[d].maxPlusOne THEN ERROR ENDLOOP; port _ GetArrayPort[a, index, eltPort]; IF port = NIL THEN { port _ FullyAddPort[[parent: from.port]].port; SetArrayPort[a, index, eltPort, port]; }; }; x: ROPE => { child: Vertex = LookupPart[from, x]; WITH child SELECT FROM w: Wire => IF path.rest # NIL THEN ERROR ELSE { port _ PGet[from, w, NIL].port; }; ci: CellInstance => IF path.rest = NIL THEN ERROR ELSE { childPort: Port = PortGet[ci.type, path.rest]; w: Wire = FindTransitiveConnection[ci, childPort]; port _ PGet[from, w, NIL].port; }; ENDCASE => ERROR; }; ENDCASE => ERROR; }; Range2Min: PROC [r2: Range2] RETURNS [min: Int2] = { min _ [Foo: r2[Foo].min, Bar: r2[Bar].min]}; Int2Sub: PROC [a, b: Int2] RETURNS [c: Int2] = { c _ [Foo: a[Foo]-b[Foo], Bar: a[Bar]-b[Bar]]}; WithTestRA: PROC [x: REF ANY] RETURNS [kind: ROPE] = { WITH x SELECT FROM ci: CellInstance => RETURN ["CellInstance"]; v: Vertex => RETURN ["Vertex"]; ENDCASE => RETURN ["ENDCASE"]; }; WithTestV: PROC [x: Vertex] RETURNS [kind: ROPE] = { WITH x SELECT FROM ci: CellInstance => RETURN ["CellInstance"]; v: Vertex => RETURN ["Vertex"]; ENDCASE => RETURN ["ENDCASE"]; }; PGet: PROC [ct: CellType, internal: Wire, ci: CellInstance] RETURNS [port: Port, external: Wire] = { See: PROC [p: Port, v: Vertex] = { IF IsMirror[NARROW[v]] THEN port _ p; }; IF internal.containingCT # ct THEN ERROR; internal.EnumerateTransitiveConnections[See]; IF port = NIL THEN { [port, external] _ FullyAddPort[ [parent: ct.port, wire: internal, other: Assert[nameReln, LIST[Describe[internal, ct.asUnorganized.internalWire]], NIL]], ci ]; } ELSE IF ci # NIL THEN external _ FindTransitiveConnection[ci, port]; }; GetNet: PROC [s: Source, from: CellType, name: ROPE] RETURNS [w: Wire] = { path: Path _ ParsePath[s, from, name]; w _ PathGet[from, path]; }; ReadCap: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; <> <> <> EndLine[from, cr.dr.buffer]; }; SkipNTokens: PROC [from: IO.STREAM, n: INT, buffer: REFTEXT] RETURNS [ok: BOOL] = { WHILE n > 0 DO token: REFTEXT = from.GetToken[TokenBreak, buffer].token; IF RefText.Equal[token, "\n"] THEN RETURN [FALSE]; n _ n - 1; ENDLOOP; ok _ TRUE; }; Warn: PROC [s: Source, msg: ROPE, v1, v2, v3, v4, v5: IO.Value _ [null[]]] = { IF s.name # NIL THEN msg _ IO.PutFR["At %g[%g]: %g", [rope[s.name]], [integer[s.stream.GetIndex[]]], [rope[msg]]]; msg _ IO.PutFR[msg, v1, v2, v3, v4, v5]; Log["%g", msg]; }; CreateArray: PROC [design: Design, dr: DesignReading, cellTypeName: ROPE, eltType: CellType, size, jointsPeriod: Size2, otherPublic, otherPrivate: Assertions _ NIL] RETURNS [ct: CellType] = { nj: INT = jointsPeriod[Foo] * jointsPeriod[Bar]; a: Array = NEW [ArrayPrivate _ [ eltType: eltType, prevArray: eltType.lastArray, nextArray: NIL, size: size, joints: [CreateRefSeq[nj], CreateRefSeq[nj]], jointsPeriod: jointsPeriod, portConnections: CreateRefTable[], porting: CreateRefTable[] ]]; InitializePorting: PROC [ep: Port] = { [] _ a.porting.Store[ep, notPorted]; }; ct _ CreateCellType[design, dr, cellTypeName, FALSE, otherPublic, otherPrivate]; ct.asArray _ a; IF a.prevArray # NIL THEN a.prevArray.asArray.nextArray _ ct ELSE eltType.firstArray _ ct; eltType.lastArray _ ct; eltType.useCount _ eltType.useCount + 1; FOR i: INT IN [0 .. nj) DO FOR d: Dim IN Dim DO a.joints[d][i] _ NEW [JointPrivate _ [ lowToHigh: CreateRefTable[], highToLow: CreateRefTable[] ]]; ENDLOOP ENDLOOP; EnumeratePorts[eltType, InitializePorting]; }; CreateCellType: PROC [design: Design, dr: DesignReading, cellTypeName: ROPE, internals: BOOL, otherPublic, otherPrivate: Assertions _ NIL] RETURNS [ct: CellType] = { pbn: Mapper = CreateHashDictionary[TRUE]; ct _ NEW [CellTypePrivate _ [ class: fromExtClass, designs: CreateHashSet[], publicKnown: TRUE, privateKnown: TRUE, otherPublic: Assert[nameReln, LIST[cellTypeName], otherPublic], otherPrivate: otherPrivate ]]; [] _ AddPort[[parent: ct]]; IF internals THEN { iw: Wire; ct.otherPrivate _ AssertFn1[partsByNameKey, pbn, ct.otherPrivate]; ct.asUnorganized _ NEW [UnorganizedPrivate _ [ containedInstances: CreateHashSet[] ]]; iw _ CreateWire[ct]; IF ct.asUnorganized.internalWire # iw THEN ERROR; AddMirror[ct]; }; [] _ design.cellTypes.UnionSingleton[ct]; [] _ ct.designs.UnionSingleton[design]; IF dr.cellTypesByName.SetMapping[cellTypeName, ct] THEN ERROR; }; LookupPart: PROC [ct: CellType, name: ROPE] RETURNS [v: Vertex] = { pbn: Mapper = NARROW[FnVal[partsByNameKey, ct.otherPrivate]]; v _ NARROW[pbn.Map[name]]; }; CTName: PROC [cellType: CellType] RETURNS [name: ROPE] = { name _ NARROW[FnVal[nameReln, cellType.otherPublic]]; }; PathEquiv: PROC [from: CellType, path1, path2: Path] RETURNS [equiv: BOOL] = { WHILE path1 # NIL AND path2 # NIL DO last: BOOL = path1.rest = NIL; WITH path1.first SELECT FROM r1: ROPE => WITH path2.first SELECT FROM r2: ROPE => { v1: Vertex = LookupPart[from, r1]; IF last THEN { v2: Vertex = LookupPart[from, r2]; RETURN [v1 = v2]} ELSE { ci1: CellInstance = NARROW[v1]; IF NOT r1.Equal[r2] THEN RETURN [FALSE]; from _ ci1.type}; }; x2: REF Range2 => RETURN [FALSE]; ENDCASE => ERROR; s1: REF Range2 => WITH path2.first SELECT FROM r2: ROPE => RETURN [FALSE]; s2: REF Range2 => { IF s1^ # s2^ THEN RETURN [FALSE] ELSE { from _ from.asArray.eltType; }; }; ENDCASE => ERROR; ENDCASE => ERROR; path1 _ path1.rest; path2 _ path2.rest; ENDLOOP; equiv _ path1 = path2; }; Id: PROC [data: REF ANY] RETURNS [ans: REF ANY] = { ans _ data}; ComparePaths: PROC [k, data: REF ANY] RETURNS [c: Basics.Comparison] = { k1: Path = NARROW[k]; k2: Path = NARROW[data]; c _ PathCompare[k1, k2]}; PathCompare: PROC [path1, path2: Path] RETURNS [c: Basics.Comparison] = { DO IF path1 = path2 THEN RETURN [equal]; IF path1 = NIL THEN RETURN [less]; IF path2 = NIL THEN RETURN [greater]; WITH path1.first SELECT FROM r1: ROPE => WITH path2.first SELECT FROM r2: ROPE => c _ r1.Compare[r2]; x2: REF Range2 => c _ less; ENDCASE => ERROR; s1: REF Range2 => WITH path2.first SELECT FROM r2: ROPE => c _ greater; s2: REF Range2 => IF (c _ IntCompare[s1[Foo].min, s2[Foo].min]) = equal THEN IF (c _ IntCompare[s1[Foo].maxPlusOne, s2[Foo].maxPlusOne]) = equal THEN IF (c _ IntCompare[s1[Bar].min, s2[Bar].min]) = equal THEN c _ IntCompare[s1[Bar].maxPlusOne, s2[Bar].maxPlusOne]; ENDCASE => ERROR; ENDCASE => ERROR; IF c # equal THEN RETURN; path1 _ path1.rest; path2 _ path2.rest; ENDLOOP; }; PathPairEqual: PROC [k1, k2: REF ANY] RETURNS [equal: BOOL] = { pp1: PathPair = NARROW[k1]; pp2: PathPair = NARROW[k2]; equal _ (PathCompare[pp1.p1, pp2.p1] = equal AND PathCompare[pp1.p2, pp2.p2] = equal) OR (PathCompare[pp1.p1, pp2.p2] = equal AND PathCompare[pp1.p2, pp2.p1] = equal); }; HashPathPair: PROC [key: REF ANY] RETURNS [hash: CARDINAL] = { pp: PathPair = NARROW[key]; hash _ HashPath[pp.p1] + HashPath[pp.p2]; }; HashPath: PROC [path: Path] RETURNS [hash: CARDINAL] = { hash _ 0; FOR path _ path, path.rest WHILE path # NIL DO WITH path.first SELECT FROM r: ROPE => hash _ hash + RopeHash.FromRope[r]; x: REF Range2 => hash _ hash + HashInt[x[Foo].min] + HashInt[x[Foo].maxPlusOne] + HashInt[x[Bar].min] + HashInt[x[Bar].maxPlusOne]; ENDCASE => ERROR; ENDLOOP; }; HashInt: PROC [i: INT] RETURNS [hash: CARDINAL] = { ln: Basics.LongNumber = [li[i]]; hash _ ln.lowbits + ln.highbits; }; IntCompare: PROC [i1, i2: INT] RETURNS [c: Basics.Comparison] = { c _ SELECT i1 - i2 FROM >0 => greater, =0 => equal, <0 => less, ENDCASE => ERROR; }; Lg: PROC [i: INT] RETURNS [lg: CARDINAL] = { IF i < 0 THEN ERROR; IF i = 0 THEN RETURN [0]; lg _ 1 + (SELECT i FROM <=00000001H => 00, <=00000002H => 01, <=00000004H => 02, <=00000008H => 03, <=00000010H => 04, <=00000020H => 05, <=00000040H => 06, <=00000080H => 07, <=00000100H => 08, <=00000200H => 09, <=00000400H => 10, <=00000800H => 11, <=00001000H => 12, <=00002000H => 13, <=00004000H => 14, <=00008000H => 15, <=00010000H => 16, <=00020000H => 17, <=00040000H => 18, <=00080000H => 19, <=00100000H => 20, <=00200000H => 21, <=00400000H => 22, <=00800000H => 23, <=01000000H => 24, <=02000000H => 25, <=04000000H => 26, <=08000000H => 27, <=10000000H => 28, <=20000000H => 29, <=40000000H => 30, ENDCASE => 31); }; Register: PROC [keyword: ROPE, read: PROC [s: Source, reader: Reader, cr: CellReading], data: REF ANY _ NIL] = { r: Reader _ NEW [ReaderRep _ [keyword, read, data]]; IF readers.SetMapping[keyword, r] THEN ERROR; }; Start: PROC = { Register["tech", ReadTech]; Register["timestamp", ReadTimestamp]; Register["version", ReadVersion]; Register["scale", ReadScale]; Register["resistclasses", ReadResistClasses]; Register["node", ReadNode]; Register["equiv", ReadEquiv]; Register["fet", ReadFet]; Register["use", ReadUse]; Register["merge", ReadMerge]; <> Register["cap", ReadCap]; }; Start[]; END.