LichenFromExt.Mesa
Last Edited by: Spreitzer, June 10, 1986 2:44:01 pm PDT
DIRECTORY
Asserting USING [Assertions, Terms, Assert, AssertFn, AssertFn1, FnVal],
Atom, Basics, BasicTime, Buttons, Containers, Convert, FS, HashTable, Histograms, Icons, IO, LichenDataStructure, LichenDataOps, LichenSetTheory, List, PieViewers, Process, ProcessProps, RefText, Rope, RopeHash, ViewerClasses, ViewerOps, ViewerTools;
LichenFromExt: CEDAR MONITOR
LOCKS dr USING dr: DesignReading
IMPORTS Asserting, Atom, BasicTime, Buttons, Containers, Convert, FS, HashTable, Histograms, Icons, IO, LichenDataStructure, LichenDataOps, LichenSetTheory, List, PieViewers, Process, ProcessProps, RefText, Rope, RopeHash, ViewerOps, ViewerTools
= BEGIN OPEN Asserting, LichenDataStructure, LichenDataOps, LichenSetTheory;
REFTEXT: TYPE = REF TEXT;
Viewer: TYPE = ViewerClasses.Viewer;
Source: TYPE = RECORD [stream: IO.STREAMNIL, name: ROPENIL];
Reader: TYPE = REF ReaderRep;
ReaderRep: TYPE = RECORD [
keyword: ROPE,
read: PROC [s: Source, reader: Reader, cr: CellReading],
Consumes newline at end of line.
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,
buffer: REFTEXT,
pacifier, pie, label, pause: Viewer,
lastPacify: BasicTime.Pulses,
stop: BOOLFALSE,
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: BOOLFALSE,
fetCount: INT ← 0];
Path: TYPE = LIST OF REF ANY--UNION [ROPE, Subrange]--;
VertexArray: TYPE = REF VertexArrayRep;
VertexArrayRep: TYPE = RECORD [
shape: ARRAY Dim OF NAT,
vertices: SEQUENCE length: NAT OF Vertex];
Use: TYPE = RECORD [childName: ROPE, as: ArraySpec];
Subrange: TYPE = REF SubrangePrivate;
SubrangePrivate: TYPE = RECORD [dim: Dim, r: OneDSubscript];
ArraySpec: TYPE = RECORD [
variant: SELECT kind: * FROM
scalar => [],
array => [dims: ARRAY Dim OF RECORD [lo, hi, sep: INT]]
ENDCASE];
OneDSubscript: TYPE = RECORD [first, last: INT];
FetTerminal: TYPE = RECORD [
name: ROPE,
length: INT,
attrs: Assertions];
IntBox: TYPE = RECORD [xmin, ymin, xmax, ymax: INT];
TransformAsTerms: TYPE = Terms;
PathPair: TYPE = REF PathPairPrivate;
PathPairPrivate: TYPE = RECORD [p1, p2: Path];
SometimesConnection: TYPE = REF SometimesConnectionPrivate;
SometimesConnectionPrivate: TYPE = RECORD [singletons, sets, allInstances: Set];
scCounts: Histograms.Histogram ← Histograms.NewHistogram[];
sccViewer: ViewerClasses.Viewer ← Histograms.Show[scCounts, [name: "SometimesConnection counts"]];
pacifierIcon: Icons.IconFlavor ← Icons.NewIconFromFile["Lichen.icons", 0];
labelHeight: INTEGER ← 15;
pauseWidth: INTEGER ← 75;
ReadDesign: PROC [rootCellFileName: ROPE, oldDR: DesignReading ← NIL] RETURNS [dr: DesignReading, design: Design] =
BEGIN
Doit: PROC = {[] ← ReadCellType[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];
design ← NEW [DesignPrivate ← [
cellTypes: CreateHashSet[],
other: Assert[nameReln, LIST[designName], NIL]
]];
dr ← NEW [DesignReadingRep ← [
design: design,
wDir: fullFName.Substr[len: cp.base.start],
cellTypesByName: CreateHashDictionary[TRUE],
fetTypes: HashTable.Create[hash: HashFetType, equal: CompareFetTypes],
unkosherArrays: CreateHashSet[],
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;
design ← dr.design;
};
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"];
};
FinishDesign: PROC [dr: DesignReading, design: Design] = {
seen: Set = CreateHashSet[];
FinishCellType: PROC [ra: REF ANY] = {
IF seen.HasMember[ra] THEN RETURN;
IF NOT seen.UnionSingleton[ra] THEN ERROR;
{
ct: CellType = NARROW[ra];
scs: Mapper = NARROW[FnVal[$SometimesConnections, ct.otherPrivate]];
FinishMerge: PROC [domain, range: REF ANY] = {
pp: PathPair = NARROW[domain];
sc: SometimesConnection = NARROW[range];
Connect: PROC [ra: REF ANY] = {
ci: CellInstance = NARROW[ra];
MergeFinal[[], dr, ci.containingCT, CONS[ci, pp.p1], CONS[ci, pp.p2]];
};
sc.allInstances.Enumerate[Connect];
};
EnumerateInstances[ct, PerInstance];
scs.EnumerateMapping[FinishMerge];
ct.otherPrivate ← AssertFn1[$SometimesConnections, NIL, ct.otherPrivate];
scCounts.Decrement[Lg[scs.MapSize[]]];
}};
PerInstance: PROC [ci: CellInstance] = {FinishCellType[ci.type]};
design.cellTypes.Enumerate[FinishCellType];
};
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;
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: LORALIST[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𡤌r.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[REALR*cr.rScale]],
Assert[$C, LIST[NEW[REALC*cr.cScale]],
Assert[$locHint, LIST[NEW[INT←x], NEW[INT←y], $UnspecifiedLayer],
attrs ]]]]
];
EndLine[from, cr.dr.buffer];
};
ReadAttrs: PROC [s: Source, zeroNIL: BOOLFALSE] 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: ROPENIL;
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;
name1: ROPE ← GetName[s];
name2: ROPE ← GetName[s];
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] = {
na: VertexArray ← GetNets[s, ct, ft.name];
nv: Vertex ← na[0];
IF na.shape # [1, 1] THEN ERROR;
Connect[tv, NARROW[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[ALL[[0, 0, 0]]]];
Get: PROC [d: Dim] = {
IF in.GetChar[] # '[ THEN ERROR;
as.dims[d].lo ← in.GetInt[];
IF in.GetChar[] # ': THEN ERROR;
as.dims[d].hi ← in.GetInt[];
IF in.GetChar[] # ': THEN ERROR;
as.dims[d].sep ← 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];
d: Dim;
IF x.dims[Foo].lo = x.dims[Foo].hi THEN d ← Bar ELSE
IF x.dims[Bar].lo = x.dims[Bar].hi THEN d ← Foo ELSE
{
d ← Bar;
eltType ← EnsureType[dr, typeName, [array[[Foo: x.dims[Foo], Bar: [0, 0, 0]]]], parent, childName];
};
ct ← CreateCellType[design, dr, cellTypeName, TRUE, AssertFn1[$EquivClass, ec, NIL], AssertFn1[$ArraySpec, NEW [ArraySpec.array ← x], NIL]];
FOR z: INT IN [x.dims[d].lo .. x.dims[d].hi] DO
ci: CellInstance = Instantiate[
type: eltType,
containingCT: ct,
other: Assert[nameReln, LIST[NameElt[z]], NIL]];
ENDLOOP;
};
ENDCASE => ERROR;
};
NameElt: PROC [i: INT] RETURNS [eltName: ROPE] =
{eltName ← IO.PutFR["[%g]", IO.int[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[dims[Foo].lo],
IO.int[dims[Foo].hi],
IO.int[dims[Foo].sep],
IO.int[dims[Bar].lo],
IO.int[dims[Bar].hi],
IO.int[dims[Bar].sep]]],
ENDCASE => ERROR;
};
FmtShape: PROC [shape: ARRAY Dim OF NAT] 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: ROPEWITH path.first SELECT FROM
x: ROPE => x,
s: Subrange => IF s.r.first = s.r.last THEN IO.PutFR["[%g]", [integer[s.r.first]]] ELSE IO.PutFR["[%g:%g]", [integer[s.r.first]], [integer[s.r.last]]],
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];
MergeWork[s, cr.dr, ct, path1, path2];
EndLine[from, cr.dr.buffer];
};
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};
GetODS: PROC RETURNS [ods: OneDSubscript] = {
ods.first ← ods.last ← in.GetInt[];
SELECT in.PeekChar[] FROM
': => {
IF in.GetChar[] # ': THEN ERROR;
ods.last ← in.GetInt[];
};
',, '] => 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["["] => {
as: ArraySpec.array;
food: BOOL = ras.dims[Foo].lo # ras.dims[Foo].hi;
bard: BOOL = ras.dims[Bar].lo # ras.dims[Bar].hi;
twoD: BOOLFALSE;
IF NOT (food OR bard) THEN ERROR;
IF bard THEN [[as.dims[Bar].lo, as.dims[Bar].hi]] ← GetODS[] ELSE [[as.dims[Foo].lo, as.dims[Foo].hi]] ← GetODS[];
toke ← in.GetTokenRope[PathNameBreak].token;
SELECT TRUE FROM
toke.Equal["]"] => NULL;
toke.Equal[","] => {
twoD ← TRUE;
[[as.dims[Foo].lo, as.dims[Foo].hi]] ← GetODS[];
toke ← in.GetTokenRope[PathNameBreak].token;
IF NOT toke.Equal["]"] THEN ERROR;
};
ENDCASE => ERROR;
IF twoD # (food AND bard) THEN ERROR;
IF bard THEN {
Append[NEW [SubrangePrivate ← [Bar, [as.dims[Bar].lo, as.dims[Bar].hi]]]];
from ← SubType[from, as.dims[Bar].lo];
};
IF food THEN {
Append[NEW [SubrangePrivate ← [Foo, [as.dims[Foo].lo, as.dims[Foo].hi]]]];
from ← SubType[from, as.dims[Foo].lo];
};
};
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: BOOLFALSE;
MergeWork: PROC [s: Source, dr: DesignReading, ct: CellType, path1, path2: Path] = {
IF lowerConnections THEN {
subType: CellType ← NIL;
ras: REF ArraySpec.array = NARROW[FnVal[$ArraySpec, ct.otherPrivate]];
sc: SometimesConnection;
add: REF ANY;
IF path1.rest # NIL AND path2.rest # NIL THEN WITH path1.first SELECT FROM
r1: ROPE => WITH path2.first SELECT FROM
r2: ROPE => {
IF r1.Equal[r2] THEN {
v1: CellInstance = NARROW[LookupPart[ct, r1]];
subType ← v1.type;
IF PathEquiv[subType, path1.rest, path2.rest] THEN RETURN;
sc ← GetSC[subType, path1.rest, path2.rest, 1];
add ← v1;
};
};
s2: Subrange => NULL;
ENDCASE => ERROR;
s1: Subrange => WITH path2.first SELECT FROM
r2: ROPE => NULL;
s2: Subrange => {
IF s1.dim # s2.dim THEN ERROR;
IF s1^ = s2^ THEN {
v1: CellInstance = NARROW[LookupPart[ct, NameElt[s1.r.first]]];
subType ← v1.type;
IF PathEquiv[subType, path1.rest, path2.rest] THEN RETURN;
sc ← GetSC[subType, path1.rest, path2.rest, s1.r.last - s1.r.first + 1];
add ← s1;
};
};
ENDCASE => ERROR;
ENDCASE => ERROR;
IF subType # NIL AND sc = NIL THEN {
MergeWork[s, dr, subType, path1.rest, path2.rest];
RETURN;
};
IF subType # NIL THEN {
WITH add SELECT FROM
v: CellInstance => [] ← sc.singletons.UnionSingleton[v];
subr: Subrange => {
va: VertexArray = LookupSR[ct, subr];
sc.sets.UnionSet[CreateVSSet[va, subr]];
};
ENDCASE => ERROR;
RETURN;
};
IF ras # NIL THEN {--we're making connections inside an array
as1: ArraySpec.array = ASHead[path1];
as2: ArraySpec.array = ASHead[path2];
kosher: BOOLTRUE;
rightOffset: BOOLFALSE;
FOR d: Dim IN Dim DO
e: Dim = OtherDim[d];
IF as1.dims[d].hi - as1.dims[d].lo # as2.dims[d].hi - as2.dims[d].lo THEN kosher ← FALSE;
IF ABS[as1.dims[d].lo - as2.dims[d].lo] = 1 AND as1.dims[e].lo = as2.dims[e].lo THEN rightOffset ← TRUE;
ENDLOOP;
IF NOT rightOffset THEN kosher ← FALSE;
IF NOT kosher THEN [] ← dr.unkosherArrays.UnionSingleton[ct];
};
};
MergeFinal[s, dr, ct, path1, path2];
};
MergeFinal: PROC [s: Source, dr: DesignReading, ct: CellType, path1, path2: Path] = {
na1, na2: VertexArray;
na1 ← PathGet[ct, path1];
na2 ← PathGet[ct, path2];
IF na1.shape = na2.shape THEN {
FOR f: INT IN [0 .. na1.shape[Foo]) DO
FOR b: INT IN [0 .. na1.shape[Bar]) DO
nv1: Wire = NARROW[VAFetch[na1, f, b]];
nv2: Wire = NARROW[VAFetch[na2, f, b]];
nv: Wire = MergeNets[nv1, nv2].merged;
ENDLOOP;
ENDLOOP;
}
ELSE {
Warn[s, "Different shapes in %g: %g is %g and %g is %g", [rope[CTName[ct]]], IO.rope[FmtPath[path1]], IO.rope[FmtShape[na1.shape]], IO.rope[FmtPath[path2]], IO.rope[FmtShape[na2.shape]]];
};
};
GetSC: PROC [ct: CellType, path1, path2: Path, instances: INT] RETURNS [sc: SometimesConnection] = {
SELECT ct.instanceCount - instances FROM
> 0 => {
scs: Mapper ← NARROW[FnVal[$SometimesConnections, ct.otherPrivate]];
pp: PathPair = NEW [PathPairPrivate ← [path1, path2]];
IF scs = NIL THEN {
ct.otherPrivate ← AssertFn1[$SometimesConnections, scs ← CreateHashMapper[PathPairEqual, HashPathPair], ct.otherPrivate];
scCounts.Increment[Lg[scs.MapSize[]]];
};
IF PathCompare[path1, path2] = greater THEN pp^ ← [path2, path1];
sc ← NARROW[scs.Map[pp]];
IF sc = NIL THEN {
oldSCCount: INT = scs.MapSize[];
sc ← NEW [SometimesConnectionPrivate ← [
singletons: CreateHashSet[],
sets: CreateUnion[NIL]
]];
sc.allInstances ← CreateUnion[LIST[sc.singletons, sc.sets], FALSE];
IF scs.SetMapping[pp, sc] THEN ERROR;
scCounts.Decrement[Lg[oldSCCount]];
scCounts.Increment[Lg[scs.MapSize[]]];
};
SELECT ct.instanceCount - (sc.allInstances.Size[] + instances) FROM
>0 => NULL;
=0 => {
sc ← NIL;
scCounts.Decrement[Lg[scs.MapSize[]]];
IF NOT scs.SetMapping[pp, NIL] THEN ERROR;
scCounts.Increment[Lg[scs.MapSize[]]];
};
<0 => ERROR;
ENDCASE => ERROR;
};
= 0 => RETURN [NIL];
< 0 => ERROR;
ENDCASE => ERROR;
};
CreateVSSet: PROC [va: VertexArray, sr: Subrange] RETURNS [set: Set] = {
vss: VSSet = NEW [VSSetPrivate ← [va, sr]];
set ← NEW [SetPrivate ← [vsSetClass, FALSE, vss]]};
VSSet: TYPE = REF VSSetPrivate;
VSSetPrivate: TYPE = RECORD [va: VertexArray, sr: Subrange];
vsSetClass: SetClass ← NEW [SetClassPrivate ← [
TestVSMembership,
DontUnionSingleton,
DontUnionSet,
DontRemoveElt,
VSEnumerate,
VSSize]];
TestVSMembership: PROC [set: Set, elt: REF ANY] RETURNS [in: BOOL] = {
vss: VSSet = NARROW[set.data];
v: Vertex = NARROW[elt];
name: ROPE = NARROW[FnVal[nameReln, v.other]];
nameLen: INT = name.Length[];
index: INT;
IF name.Fetch[0] # '[ OR name.Fetch[nameLen-1] # '] THEN ERROR;
index ← Convert.IntFromRope[name.Substr[1, nameLen-2]];
in ← index IN [vss.sr.r.first .. vss.sr.r.last];
};
VSEnumerate: PROC [set: Set, Consumer: PROC [REF ANY]] = {
vss: VSSet = NARROW[set.data];
FOR i: INT IN [0 .. vss.va.length) DO Consumer[vss.va[i]] ENDLOOP;
};
VSSize: PROC [set: Set] RETURNS [size: INT] = {
vss: VSSet = NARROW[set.data];
size ← vss.va.length};
ASHead: PROC [path: Path] RETURNS [as: ArraySpec.array] = {
as.dims ← ALL[[0, 0, 0]];
WITH path.first SELECT FROM
x: Subrange => {
as.dims[x.dim] ← [x.r.first, x.r.last, 0];
IF x.dim = Bar AND path.rest # NIL THEN WITH path.rest.first SELECT FROM
y: Subrange => IF y.dim = Foo THEN as.dims[Foo] ← [y.r.first, y.r.last, 0];
y: ROPE => NULL;
ENDCASE => ERROR;
};
x: ROPE => NULL;
ENDCASE => ERROR;
};
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 [va: VertexArray] = {
first: REF ANY = path.first;
IF path.rest # NIL THEN {
child: REF ANY --actually UNION [CellInstance, VertexArray]--;
childCellType: CellType;
childShape, shape: ARRAY Dim OF NAT;
gcva: VertexArray;
WITH first SELECT FROM
ci: CellInstance => {
childCellType ← ci.type;
childShape ← ALL[1];
child ← ci};
r: ROPE => {
v: CellInstance = NARROW[LookupPart[from, r]];
childCellType ← v.type;
childShape ← ALL[1];
child ← v};
sr: Subrange => {
cva: VertexArray = LookupSR[from, sr];
ci0: CellInstance = NARROW[cva[0]];
childCellType ← ci0.type;
childShape ← cva.shape;
child ← cva};
ENDCASE => ERROR;
gcva ← PathGet[childCellType, path.rest];
shape ← [Foo: childShape[Foo]*gcva.shape[Foo], Bar: childShape[Bar]*gcva.shape[Bar]];
va ← NEW [VertexArrayRep[shape[Foo]*shape[Bar]]];
va.shape ← shape;
FOR cx: NAT IN [0 .. childShape[Foo]) DO FOR cy: NAT IN [0 .. childShape[Bar]) DO
cv: CellInstance ← WITH child SELECT FROM
v: CellInstance => v,
cva: VertexArray => NARROW[VAFetch[cva, cx, cy]],
ENDCASE => ERROR;
FOR gx: NAT IN [0 .. gcva.shape[Foo]) DO FOR gy: NAT IN [0 .. gcva.shape[Bar]) DO
x: NAT ← cx * gcva.shape[Foo] + gx;
y: NAT ← cy * gcva.shape[Bar] + gy;
VAStore[va, x, y, VGet[cv, NARROW[VAFetch[gcva, gx, gy]]]];
ENDLOOP ENDLOOP;
ENDLOOP ENDLOOP;
}
ELSE WITH first SELECT FROM
sr: Subrange => va ← LookupSR[from, sr];
r: ROPE => {va ← NEW [VertexArrayRep[1]];
va.shape ← ALL[1];
va[0] ← LookupPart[from, r];
};
v: Vertex => {va ← NEW [VertexArrayRep[1]];
va.shape ← ALL[1];
va[0] ← v;
};
ENDCASE => ERROR;
};
CI2: TYPE = CellInstance;
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"];
};
VGet: PROC [ci: CellInstance, internal: Wire] RETURNS [external: Wire] = {
port: Port;
See: PROC [p: Port, v: Vertex] = {
IF IsMirror[NARROW[v]] THEN port ← p;
};
IF internal.containingCT # ci.type THEN ERROR;
internal.EnumerateTransitiveConnections[See];
IF port = NIL THEN {
[port, external] ← FullyAddPort[
[parent: ci.type.port, wire: internal, other: Assert[nameReln, LIST[Describe[internal, ci.type.asUnorganized.internalWire]], NIL]],
ci
];
}
ELSE external ← FindTransitiveConnection[ci, port];
IF external = NIL THEN ERROR;
};
GetNets: PROC [s: Source, from: CellType, name: ROPE] RETURNS [va: VertexArray] = {
path: Path ← ParsePath[s, from, name];
va ← PathGet[from, path];
};
ReadCap: PROC [s: Source, reader: Reader, cr: CellReading] = {
ct: CellType = cr.ct;
from: IO.STREAM = s.stream;
name1: ROPE ← GetName[s];
name2: ROPE ← GetName[s];
C: INT ← from.GetInt[];
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];
};
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]];
};
LookupSR: PROC [ct: CellType, sr: Subrange] RETURNS [va: VertexArray] = {
pbn: Mapper = NARROW[FnVal[partsByNameKey, ct.otherPrivate]];
size: INT = sr.r.last - sr.r.first + 1;
va ← NEW [VertexArrayRep[size]];
va.shape ← ALL[1];
va.shape[sr.dim] ← size;
FOR i: INT IN [sr.r.first .. sr.r.last] DO
va[i - sr.r.first] ← NARROW[pbn.Map[NameElt[i]]];
ENDLOOP;
};
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: Subrange => RETURN [FALSE];
ENDCASE => ERROR;
s1: Subrange => WITH path2.first SELECT FROM
r2: ROPE => RETURN [FALSE];
s2: Subrange => {
IF s1^ # s2^ THEN RETURN [FALSE] ELSE {
v1: CellInstance = NARROW[LookupPart[from, NameElt[s1.r.first]]];
from ← v1.type;
};
};
ENDCASE => ERROR;
ENDCASE => ERROR;
path1 ← path1.rest;
path2 ← path2.rest;
ENDLOOP;
equiv ← path1 = path2;
};
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: Subrange => c ← less;
ENDCASE => ERROR;
s1: Subrange => WITH path2.first SELECT FROM
r2: ROPE => c ← greater;
s2: Subrange => IF (c ← IntCompare[s1.dim.ORD, s2.dim.ORD]) = equal THEN IF (c ← IntCompare[s1.r.first, s2.r.first]) = equal THEN c ← IntCompare[s1.r.last, s2.r.last];
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];
s: Subrange => hash ← hash + HashInt[s.r.first] + HashInt[s.r.last] + s.dim.ORD;
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 ANYNIL] = {
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["adjust", ReadAdjust];
Register["cap", ReadCap];
};
Start[];
END.