<> <> DIRECTORY Asserting, Atom, Basics, BasicTime, Collections, Histograms, IO, LichenArrayStuff, LichenDataOps, LichenDataStructure, LichenFromExtPrivate, PairCollections, RefTab, RefText, Rope; LichenFromExt2Impl: CEDAR MONITOR LOCKS dr USING dr: DesignReading IMPORTS Asserting, Atom, BasicTime, Collections, Histograms, IO, LichenArrayStuff, LichenDataOps, LichenDataStructure, LichenFromExtPrivate, PairCollections, RefTab, RefText, Rope EXPORTS LichenFromExtPrivate = BEGIN OPEN Asserting, LichenDataOps, LichenArrayStuff, LichenDataStructure, LichenFromExtPrivate, Colls:Collections, PairColls:PairCollections; fromExtClass: CellClass _ NEW [CellClassPrivate _ []]; PrintImpossibles: PROC [to: IO.STREAM, dr: DesignReading] = { FOR ims: ImpossibleMergeList _ dr.impossibleMerges, ims.rest WHILE ims # NIL DO im: ImpossibleMerge = ims.first; to.PutF["%g: %g & %g\n", [rope[Describe[im.arrayInstance, dr.design]]], [rope[FmtPath[im.path1]]], [rope[FmtPath[im.path2]]]]; ENDLOOP; }; FinishWaitingMerges: PUBLIC PROC [cr: CellReading] = { DO progress: BOOL _ FALSE; wml: PathPairList _ cr.waitingMerges; cr.waitingMerges _ NIL; FOR wml _ wml, wml.rest WHILE wml # NIL DO progress _ MergeWork[cr, wml.first.p1, wml.first.p2] OR progress; ENDLOOP; IF NOT progress THEN EXIT; ENDLOOP; IF cr.waitingMerges # NIL THEN ERROR; }; GetLineTerms: PUBLIC 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; }; GetSteppyName: PROC [s: Source] RETURNS [name: SteppyName] ~ { raw: ROPE ~ GetName[s]; name _ ParseSteppyName[raw]; }; 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: PUBLIC 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 _ Assert1[$tech, 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; }; keepCruft: BOOL _ FALSE; ReadNode: PROC [s: Source, reader: Reader, cr: CellReading] = { ct: CellType = cr.ct; from: IO.STREAM = s.stream; fullName: SteppyName ~ GetSteppyName[s]; nodeName: NameStep ~ IF fullName.rest=NIL THEN fullName.first ELSE ERROR; 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 _ NARROW[LookupPart[ct, nodeName]]; IF nv = NIL THEN { nv _ CreateWire[ containingCT: ct, names: CreateSteppyNames[LIST[fullName]] ]; } ELSE { }; IF keepCruft THEN nv.other _ Assert1[$R, NEW[REAL _ R*cr.rScale], Assert1[$C, NEW[REAL _ C*cr.cScale], Assert[$locHint, LIST[NEW[INT_x], NEW[INT_y], $UnspecifiedLayer], Asserting.Union[attrs, nv.other, TRUE]]]]; EndLine[from, cr.dr.buffer]; }; ReadAttrs: PROC [s: Source, zeroNIL: BOOL _ FALSE] RETURNS [allTogetherNow: Assertions] = { from: IO.STREAM = s.stream; toke: ROPE _ NIL; allTogetherNow _ NIL; IF zeroNIL THEN { [] _ from.SkipWhitespace[]; IF from.PeekChar[] = '0 THEN { IF from.GetChar[] # '0 THEN ERROR; RETURN}; }; {DO attr: ROPE _ NIL; toke _ from.GetTokenRope[AttrBreak !IO.EndOfStream => EXIT].token; IF toke.Equal[","] THEN {Warn[s, "Extra comma"]; LOOP}; IF NOT toke.Equal["\""] THEN GOTO Return; from.Backup['"]; attr _ from.GetRopeLiteral[ !IO.Error, IO.EndOfStream => {Warn[s, "not a rope literal"]; CONTINUE}]; IF attr # NIL THEN allTogetherNow _ Assert1[$attr, attr, allTogetherNow]; toke _ from.GetTokenRope[AttrBreak !IO.EndOfStream => EXIT].token; IF NOT toke.Equal[","] THEN GOTO Return; ENDLOOP; EXITS Return => { FOR i: INT DECREASING IN [0 .. toke.Length[]) DO s.stream.Backup[toke.Fetch[i]]; ENDLOOP; }; }}; 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; name1: SteppyName = GetSteppyName[s]; name2: SteppyName = GetSteppyName[s]; v: Vertex _ LookupPart[ct, name1.first]; otherName: SteppyName _ name2; IF name1.rest#NIL OR name2.rest#NIL THEN ERROR; IF v=NIL THEN {v _ LookupPart[ct, name2.first]; otherName _ name1}; IF v=NIL THEN ERROR; KnowVertexName[v, otherName]; 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: SteppyName _ GetSteppyName[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, CreateSteppyNames[LIST[LIST[IO.PutFR["Q%g#", IO.int[cr.fetCount _ cr.fetCount + 1]]]]]]; 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 _ GetSteppyName[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].val]; 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 _ LocalCreateCellType[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, names: CreateSteppyNames[LIST[LIST[R["gate"]]]]]]; [] _ AddPort[[parent: fp, names: CreateSteppyNames[LIST[LIST[R["ch1"]]]]]]; [] _ AddPort[[parent: fp, names: CreateSteppyNames[LIST[LIST[R["ch2"]]]]]]; }; 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, typeName, u.as, ct, u.childName]; ci: CellInstance = FullyInstantiate[type, ct, CreateSteppyNames[LIST[LIST[u.childName]]]]; 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 [cr: CellReading, typeName: ROPE, as: ArraySpec, parent: CellType, childName: ROPE] RETURNS [ct: CellType] = { dr: DesignReading ~ cr.dr; design: Design = dr.design; WITH as SELECT FROM x: ArraySpec.scalar => { ct _ NARROW[dr.cellTypesByName.Apply[typeName].DVal]; 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[cr, typeName, [scalar[]], NIL, NIL]; size: Size2 = RangeShape[x.range]; ct _ LocalCreateArray[design, dr, cellTypeName, eltType, size, [1, 1], AssertFn1[$EquivClass, ec, NIL], AssertFn1[$ArraySpec, NEW [ArraySpec.array _ x], NIL]]; IF NOT cr.newArrays.AddElt[ct] THEN ERROR; }; ENDCASE => ERROR; }; EmptyRange2: PROC [r: Range2] RETURNS [empty: BOOL] = { empty _ r[Foo].maxPlusOne<=r[Foo].min OR r[Bar].maxPlusOne<=r[Bar].min; }; NameElt: PROC [i: INT] RETURNS [eltName: NameStep] ~ {eltName _ NewInt[i]}; 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; IF cr.firstMerge THEN {cr.firstMerge _ FALSE; TryArrayFile[cr]}; {name1: ROPE = GetName[s]; name2: ROPE = GetName[s]; path1: Path = ParsePath[s, ct, name1]; path2: Path = ParsePath[s, ct, name2]; IF ComparePaths[path1, cr.dr.mostRecentPathToMerge]#equal THEN { DoMerges[s, cr]; AddMerge[cr.dr, path1]; }; AddMerge[cr.dr, path2]; cr.dr.mostRecentPathToMerge _ path2; EndLine[from, cr.dr.buffer]; }}; AddMerge: PROC [dr: DesignReading, path: Path] ~ { arrayPrefix: Path ~ IF path#NIL AND path.rest#NIL AND path.rest.rest#NIL THEN WITH path.first SELECT FROM x: ROPE => WITH path.rest.first SELECT FROM r: REF Range2 => LIST[x, r], ENDCASE => NIL, ENDCASE => NIL ELSE NIL; rs: REF Set--of Path-- _ NARROW[dr.toMerge.Apply[arrayPrefix].DVal]; IF rs=NIL THEN dr.toMerge.AddNewPair[[arrayPrefix, rs _ NARROW[Colls.CreateHashSet[].Refify]]]; IF NOT rs^.AddElt[path] THEN ERROR; RETURN}; nsh: Histograms.Histogram ~ Histograms.Create1D[]; DoMerges: PUBLIC PROC [s: Source, cr: CellReading] = { from: CellType = cr.ct; dr: DesignReading = cr.dr; nSets: INT ~ dr.toMerge.Size[]; i: INT _ 0; lastPath: Path _ NIL; firstSet: REF Set--of Path-- _ NIL; DoAMerge: PROC [ra: REF ANY] ~ { path: Path ~ NARROW[ra]; IF lastPath # NIL THEN [] _ MergeWork[cr, lastPath, path]; IF nSets=1 THEN lastPath _ path; RETURN}; DoASet: PROC [pair: PairColls.Pair] ~ { rs: REF Set--of Path-- ~ NARROW[pair[right]]; IF i=0 THEN firstSet _ rs; IF nSets=1 AND pair[left]#NIL THEN ERROR; IF nSets=1 OR i>0 THEN rs^.Enumerate[DoAMerge]; lastPath _ NARROW[rs^.First[].val]; IF i=1 THEN firstSet^.Enumerate[DoAMerge]; i _ i + 1; RETURN}; nsh.Increment[nSets]; dr.toMerge.Enumerate[DoASet]; IF i # nSets THEN ERROR; IF NOT dr.toMerge.RemColl[dr.toMerge].hadAll[leftToRight] THEN ERROR; dr.mostRecentPathToMerge _ NIL; IF NOT dr.toMerge.Empty[] THEN ERROR; }; MergeWork: PROC [cr: CellReading, path1, path2: Path] RETURNS [success: BOOL] = { ct: CellType = cr.ct; 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; success _ ArrayMerge[cr, ci, x, path1.rest, path2.rest, cr.dr.curArray]; IF cr.dr.curArray AND NOT success THEN cr.waitingMerges _ CONS[NEW [PathPairPrivate _ [path1, path2]], cr.waitingMerges]; IF cr.dr.curArray OR success THEN RETURN; }; }; y: REF Range2 => ERROR; ENDCASE => ERROR; x: REF Range2 => ERROR; ENDCASE => ERROR; MergeFinal[ct, path1, path2]; success _ TRUE; }; ArrayMerge: PROC [cr: CellReading, arrayInstance: CellInstance, instanceName: ROPE, path1, path2: Path, may: BOOL] RETURNS [merged: BOOL] = { act: CellType = arrayInstance.type; a: Array = act.asArray; et: CellType = a.eltType; rr1: REF Range2 = NARROW[path1.first]; rr2: REF Range2 = NARROW[path2.first]; r1: Range2 = rr1^; r2: Range2 = rr2^; size: Size2 = RangeShape[r2]; mai1: ArrayIndex = Range2Min[r1]; mai2: ArrayIndex = Range2Min[r2]; p1: Port = PortGet[et, path1.rest, may]; p2: Port = PortGet[et, path2.rest, may]; IF RangeShape[r1] # size THEN ERROR; IF p1=NIL OR p2=NIL THEN {IF may THEN ERROR ELSE RETURN [FALSE]}; IF may THEN { IF ABS[ MakeArrayNewConnection[act, r1, RETURN [TRUE]} ELSE { IF size # [1, 1] THEN ERROR; merged _ ArrayEltPortsConnected[a, mai1, mai2, p1, p2]; RETURN}; }; MergeFinal: PROC [ct: CellType, path1, path2: Path] = { w1, w2, nw: Wire; w1 _ PathGet[ct, path1, TRUE]; w2 _ PathGet[ct, path2, TRUE]; nw _ MergeNets[w1, w2].merged; RETURN}; 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}; PathGet: PROC [from: CellType, path: Path, mayAdd: BOOL] 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, mayAdd]; IF childPort # NIL THEN { w _ FindTransitiveConnection[ci, childPort]; IF w=NIL THEN ERROR; }; }; ENDCASE => ERROR; }; x: REF Range2 => ERROR; ENDCASE => ERROR; }; PortGet: PROC [from: CellType, path: Path, mayAdd: BOOL] 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, mayAdd]; IF eltPort=NIL THEN port _ NIL ELSE { index: ArrayIndex = Int2Sub[Range2Min[x^], Range2Min[ras.range]]; IF NOT Range2IsSingleton[x^] THEN ERROR; port _ GetArrayPortForPort[from, index, eltPort, mayAdd]; }; }; x: ROPE => { child: Vertex = LookupPart[from, x]; WITH child SELECT FROM w: Wire => IF path.rest # NIL THEN ERROR ELSE { port _ PortForWire[from, w, NIL, mayAdd].port; }; ci: CellInstance => IF path.rest = NIL THEN ERROR ELSE { childPort: Port = PortGet[ci.type, path.rest, mayAdd]; IF childPort = NIL THEN port _ NIL ELSE { w: Wire = FindTransitiveConnection[ci, childPort]; IF w=NIL THEN ERROR; port _ PortForWire[from, w, NIL, mayAdd].port; }; }; ENDCASE => ERROR; }; ENDCASE => ERROR; port _ port; }; GetNet: PROC [s: Source, from: CellType, name: SteppyName] RETURNS [w: Wire] = { path: Path ~ Pathify[s, from, name]; w _ PathGet[from, path, TRUE]; }; Pathify: PROC [s: Source, from: CellType, steppy: SteppyName] RETURNS [p: Path] ~ { 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}; WHILE steppy#NIL DO ras: REF ArraySpec.array = NARROW[FnVal[$ArraySpec, from.otherPrivate]]; WITH steppy.first SELECT FROM x: REF INT => { 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; IF food=bard THEN ERROR; r2[IF food THEN Foo ELSE Bar] _ [min: x^, maxPlusOne: x^+1]; Append[NEW [Range2 _ r2]]; from _ from.asArray.eltType; steppy _ steppy.rest}; x: ROPE => { Append[x]; WITH LookupPart[from, x] SELECT FROM ci: CellInstance => from _ ci.type; w: Wire => {IF steppy.rest#NIL THEN ERROR; from _ NIL}; ENDCASE => ERROR; steppy _ steppy.rest}; ENDCASE => ERROR; ENDLOOP; RETURN}; 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", LIST[msg]]; }; LocalCreateArray: PROC [design: Design, dr: DesignReading, cellTypeName: ROPE, eltType: CellType, size, jointsPeriod: Size2, otherPublic, otherPrivate: Assertions _ NIL] RETURNS [ct: CellType] = { ct _ CreateArray[design, cellTypeName, fromExtClass, eltType, size, jointsPeriod, otherPublic, otherPrivate]; IF NOT dr.cellTypesByName.Store[[cellTypeName, ct]] THEN ERROR; }; LocalCreateCellType: PUBLIC PROC [design: Design, dr: DesignReading, cellTypeName: ROPE, internals: BOOL, otherPublic, otherPrivate: Assertions _ NIL] RETURNS [ct: CellType] = { ct _ CreateCellType[design, cellTypeName, fromExtClass, internals, otherPublic, otherPrivate]; IF NOT dr.cellTypesByName.Store[[cellTypeName, ct]] THEN ERROR; }; LookupPart: PROC [ct: CellType, step: NameStep] RETURNS [v: Vertex] = { pbn: VarFunction = PairColls.DeRef[FnVal[partsByNameKey, ct.otherPrivate]].AsVar; v _ NARROW[pbn.Apply[LIST[step]].DVal]; }; CTName: PROC [cellType: CellType] RETURNS [name: ROPE] = { name _ NARROW[FnVal[nameReln, cellType.otherPublic]]; }; 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]; [] _ nsh.Show[viewerInit: [name: "LichenFromExt2Impl.DoMerges.nSets"], updatePeriod: 5]; RETURN}; Start[]; END.