SpinifexOutputImpl.mesa
Copyright © 1984 by Xerox Corporation. All rights reserved.
Written by Shand, July 16, 1984 2:58:45 pm PDT
Last Edited by: Shand, September 7, 1984 10:02:01 pm PDT PDT PDT PDT
Last Edited by: Beretta, October 30, 1984 10:07:06 am PST
DIRECTORY
CD USING [ObPtr, ApplicationPtr, ApplicationList, lambda],
CDDirectory USING [Name],
CDObjectProcs USING [FetchFurther],
CDProperties USING [GetPropFromObject, GetPropFromApplication],
CDIO USING [GetWorkingDirectory],
TerminalIO USING [WriteRope],
Atom USING [PropList, PutPropOnList, GetPropFromList, RemPropFromList],
RefTab USING [Ref, Pairs, EachPairAction],
SymTab USING [Ref, Create, Store, Fetch],
Rope USING [ROPE, Cat, Length, Fetch, Find, Replace],
Ascii USING [Letter, Digit],
IO USING [STREAM, atom, card, char, int, Put, PutF, PutR, PutRope, rope, RopeFromROS, ROS, time, Close],
Convert USING [RopeFromInt, RopeFromRope],
FS USING [StreamOpen, Error, ExpandName],
TiogaOps USING [PutProp],
TiogaFileOps USING [Ref, CreateRoot, InsertNode, InsertAsLastChild, SetContents, AddLooks, SetFormat, SetStyle, Store],
UserCredentials USING [Get],
PupDefs USING [GetMyName],
SpinifexAtoms USING [ spinifex, SignalName, InstanceName, thymePrint, rosePrint],
SpinifexCircuit USING [ LogicalCell, Circuit, CircuitNode, AreaPerimRec, NodeLinkage, MergeRec, MergeRecList, TechHandle, FindRootNode, SignalName],
SpinifexOutput
;
SpinifexOutputImpl: CEDAR PROGRAM
IMPORTS CDDirectory, CDObjectProcs, CDProperties, CDIO, TerminalIO, Atom, RefTab, SymTab, Rope, Ascii, IO, Convert, FS, TiogaOps, TiogaFileOps, UserCredentials, PupDefs, SpinifexAtoms, SpinifexCircuit
EXPORTS SpinifexOutput
~ BEGIN
-- TYPES from SpinifexCircuit.
Circuit: TYPE ~ SpinifexCircuit.Circuit;
CircuitNode: TYPE ~ SpinifexCircuit.CircuitNode;
AreaPerimRec: TYPE ~ SpinifexCircuit.AreaPerimRec;
NodeLinkage: TYPE ~ SpinifexCircuit.NodeLinkage;
MergeRec: TYPE ~ SpinifexCircuit.MergeRec;
TechHandle: TYPE ~ SpinifexCircuit.TechHandle;
MergeRecList: TYPE ~ SpinifexCircuit.MergeRecList;
SignalName: TYPE ~ SpinifexCircuit.SignalName;
LogicalCell: TYPE ~ SpinifexCircuit.LogicalCell;
-- Implementation.
isPort: ATOM ~ $SpinifexIsPort;
carryThroughNodes: ATOM ~ $SpinifexThroughNodes;
nodeName: ATOM ~ $SpinifexNodeName;
-- All we are really interested in is .first in the following MergeRecList-s but these cannot be broken up so we just point to LIST.
CarryThrough: TYPE ~ RECORD [numCT: CARDINAL, key: REF CircuitNode, merge: MergeRecList, chainTail: LIST OF CD.ApplicationPtr];
AddPorts: PROCEDURE [cellList: LIST OF REF LogicalCell, globalNames: SymTab.Ref] ~ {
-- Process Circuits top down. Node is a port iff it appears in some merge directory.
TagSubcircuitNode: RefTab.EachPairAction -- [key: RefTab.Key, val: RefTab.Val] RETURNS [quit: BOOLEAN] -- ~ {
portNode: REF CircuitNode ~ NARROW[key];
merges: MergeRecList ~ NARROW[val];
portNode.properties ← portNode.properties.PutPropOnList[prop~ isPort, val~ isPort];
FOR ml: MergeRecList ← merges, ml.rest WHILE ml # NIL DO
-- Skip the first Application (Guaranteed to be at least one).
FOR applChain: LIST OF CD.ApplicationPtr ← ml.first.applChain.rest, applChain.rest WHILE applChain # NIL DO
intermediateCircuit: REF Circuit ~ NARROW[ CDProperties.GetPropFromObject[ from~applChain.first.ob, prop~SpinifexAtoms.spinifex]];
-- An interface carry through node is required in intermediateCircuit.
throughNodes: LIST OF CarryThrough ~ NARROW[ intermediateCircuit.properties.GetPropFromList[ carryThroughNodes] ];
-- Hmm, is ml already on throughNodes list? We'd better check.
foundIt: BOOLEANFALSE;
lag: LIST OF CarryThrough ← NIL;
FOR existingTNs: LIST OF CarryThrough ← throughNodes, existingTNs.rest WHILE existingTNs # NIL AND ~foundIt DO
IF portNode = existingTNs.first.key THEN {
thisAppl: LIST OF CD.ApplicationPtr ← ml.first.applChain;
FOR existingAppl: LIST OF CD.ApplicationPtr ← existingTNs.first.merge.first.applChain, existingAppl.rest UNTIL thisAppl.first = applChain.first DO
IF existingAppl = NIL OR thisAppl.first # existingAppl.first THEN
EXIT;
thisAppl ← thisAppl.rest;
REPEAT FINISHED => foundIt ← TRUE
ENDLOOP
};
lag ← existingTNs;
ENDLOOP;
IF ~foundIt THEN {
IF lag # NIL THEN {
IF lag.rest # NIL THEN ERROR;
lag.rest ← LIST[ CarryThrough[ 0, portNode, ml, applChain]];
}
ELSE {
IF throughNodes # NIL THEN ERROR;
intermediateCircuit.properties ← intermediateCircuit.properties.PutPropOnList[ carryThroughNodes, NARROW[ LIST[ CarryThrough[ 1, portNode, ml, applChain]], LIST OF CarryThrough -- Note: this NARROW is necessary because the LIST constructor is not defined for general lists, see CLRM for details. (Mark Shand for Cedar 5.2 July 13, 1984) --] ];
}
}
ENDLOOP;
ENDLOOP;
quit ← FALSE
};
circuit: REF Circuit ~ NARROW[ CDProperties.GetPropFromObject[ from~cellList.first.cellObj, prop~SpinifexAtoms.spinifex]];
IF cellList.rest # NIL THEN AddPorts[cellList.rest, globalNames];
IF circuit.mergeDirectory # NIL THEN
[] ← circuit.mergeDirectory.Pairs[ action~ TagSubcircuitNode];
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
signalName: REF SignalName ~ NARROW[nl.first.properties.GetPropFromList[ SpinifexAtoms.SignalName]];
IF signalName # NIL THEN {
NULL;
}
ENDLOOP;
};
ClearPorts: PROCEDURE [cellList: LIST OF REF LogicalCell] ~ {
-- Clear existing ports from cells
FOR cl: LIST OF REF LogicalCell ← cellList, cl.rest WHILE cl # NIL DO
circuit: REF Circuit ~ NARROW[ CDProperties.GetPropFromObject[ from~cl.first.cellObj, prop~SpinifexAtoms.spinifex]];
circuit.properties ← circuit.properties.RemPropFromList[ carryThroughNodes];
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
node: REF CircuitNode ~ nl.first;
node.properties ← node.properties.RemPropFromList[isPort];
node.properties ← node.properties.RemPropFromList[nodeName]
ENDLOOP;
ENDLOOP;
};
PrintCircuit: PUBLIC PROCEDURE [cellList: LIST OF REF LogicalCell, formatKey: REF ANY] ~ {
HierarchyRoot: PROCEDURE [cellList: LIST OF REF LogicalCell] RETURNS [CD.ObPtr] ~ INLINE {
FOR cl: LIST OF REF LogicalCell ← cellList, cl.rest WHILE cl # NIL DO
IF cl.rest = NIL THEN RETURN[cl.first.cellObj];
ENDLOOP;
ERROR
};
ReadGlobalSignals: PROCEDURE [glob: SymTab.Ref] ~ {
-- SymTab keyed by signal names, value is use count.
globFile: IO.STREAM;
[] ← glob.Store[ "Gnd", $GlobalSignal];
globFile ← FS.StreamOpen[ FS.ExpandName["chip.wspec", desWDir].fullFName ! FS.Error => IF error.group = user THEN { GOTO NoFile } ];
TerminalIO.WriteRope[Rope.Cat["\nProcessing wiring spec file \"", "chip.wspec", "\"\n"]];
DO
tok: IO.TokenKind;
id: Rope.ROPE;
[tok, id] ← globFile.GetCedarTokenRope[ ! IO.Error => EXIT; IO.EndOfStream => EXIT];
IF tok = tokenID THEN
[] ← glob.Store[ id, $GlobalSignal];
ENDLOOP;
EXITS NoFile => NULL;
};
globals: SymTab.Ref;
desWDir: Rope.ROPE ~ CDIO.GetWorkingDirectory[cellList.first.design];
globals ← SymTab.Create[mod~553, case~ TRUE];
FOR cl: LIST OF REF LogicalCell ← cellList, cl.rest WHILE cl # NIL DO
IF ~globals.Store[CDDirectory.Name[cl.first.cellObj], $CellName] THEN NULL;
-- Should be ERROR Duplicate name.
ENDLOOP;
ReadGlobalSignals[globals];
AddPorts[cellList, globals];
SELECT formatKey FROM
Thyme
SpinifexAtoms.thymePrint => {
thymeFileName: Rope.ROPE ~ FS.ExpandName[ CDDirectory.Name[HierarchyRoot[cellList]].Cat[".thy"], desWDir].fullFName;
thymeFile: TiogaFileOps.Ref ~ TiogaFileOps.CreateRoot[];
defnTextNode: TiogaFileOps.Ref;
TerminalIO.WriteRope[ IO.PutR[ IO.rope["Commencing output of thyme file to \""], IO.rope[thymeFileName], IO.rope["\""]] ];
thymeFile.SetStyle["Cedar"];
defnTextNode ← thymeFile.InsertAsLastChild[];
defnTextNode.SetContents[ IO.PutR[ IO.rope[thymeFileName], IO.rope[", Written by Spinifex, "], IO.time[]] ];
-- Following LOOPHOLE caused by `opaque type' compiler problems.
TRUSTED { TiogaOps.PutProp[LOOPHOLE[defnTextNode], $Comment, NEW[BOOLEANTRUE]] };
FOR cl: LIST OF REF LogicalCell ← cellList, cl.rest WHILE cl # NIL DO
defnTextNode ← thymeFile.InsertAsLastChild[ defnTextNode];
defnTextNode.SetFormat[ "unit"];
PrintSubcircuit[thymeFile, defnTextNode, cl.first.cellObj, globals, formatKey];
ENDLOOP;
thymeFile.Store[ thymeFileName ! FS.Error => {
IF error.group = user THEN {
IF error.code = $illegalName THEN {
thymeFile.Store[ "///temp/ThymeOut.thy" ];
TerminalIO.WriteRope[ Rope.Cat[ "\n\t", error.explanation, "\n\tExtracted output will appear in \"///temp/ThymeOut.thy\""]];
CONTINUE
}
ELSE { TerminalIO.WriteRope[error.explanation]; GOTO IOProblems }
};
} ];
TerminalIO.WriteRope[ " — done.\n"];
EXITS IOProblems => TerminalIO.WriteRope[ " — failed.\n"];
};
RoseMary
SpinifexAtoms.rosePrint => {
GenKey: INT ← 0;
rootName: Rope.ROPE ← CDDirectory.Name[HierarchyRoot[cellList]];
fullRootName: Rope.ROPE;
DFfile: IO.STREAM;
{ ENABLE FS.Error =>
IF error.group = user THEN {
IF error.code = $illegalName THEN {
rootName ← "ExtractedRoseOut";
fullRootName ← FS.ExpandName[rootName, desWDir].fullFName;
DFfile ← FS.StreamOpen[fullRootName.Cat[".df"], $create];
TerminalIO.WriteRope[ Rope.Cat[ "\n\t", error.explanation, "\n\tExtracted output will appear in \"", fullRootName, ".df\""]];
GOTO AbleToOutput
}
ELSE { TerminalIO.WriteRope[error.explanation]; GOTO IOProblems }
};
Try the cell name
fullRootName ← FS.ExpandName[rootName, desWDir].fullFName;
DFfile ← FS.StreamOpen[fullRootName.Cat[".df"], $create];
EXITS AbleToOutput => NULL
};
TerminalIO.WriteRope[ IO.PutR[ IO.rope["Commencing output rosemary file to \""], IO.rope[fullRootName], IO.rope[".df\""]] ];
DFfile.PutF["-- %g.df written by Spinifex rosemary structure capturer, %g\n\n\n", IO.rope[rootName], IO.time[]];
DFfile.PutF["Directory %g\n\t%g.df\n", IO.rope[desWDir], IO.rope[rootName]];
FOR cl: LIST OF REF LogicalCell ← cellList, cl.rest WHILE cl # NIL DO
cellFileName: Rope.ROPE ← CDDirectory.Name[cl.first.cellObj];
cellFile: TiogaFileOps.Ref ~ TiogaFileOps.CreateRoot[];
firstNode: TiogaFileOps.Ref ~ cellFile.InsertAsLastChild[];
cellFile.SetStyle["Cedar"];
firstNode.SetFormat[ "unit"];
PrintSubcircuit[cellFile, firstNode, cl.first.cellObj, globals, formatKey];
{ ENABLE FS.Error =>
IF error.group = user THEN {
IF error.code = $illegalName THEN {
cellFileName ← rootName.Cat["-", Convert.RopeFromInt[GenKey]];
GenKey ← GenKey.SUCC;
cellFile.Store[ FS.ExpandName[cellFileName.Cat[".sch"], desWDir].fullFName];
CONTINUE
}
ELSE { TerminalIO.WriteRope[error.explanation]; GOTO IOProblems }
};
fName: Rope.ROPE ~ FS.ExpandName[cellFileName.Cat[".sch"], desWDir].fullFName;
cellFile.Store[ fName]
};
DFfile.PutF["-- \"%g\"\n %g.sch\n", IO.rope[CDDirectory.Name[cl.first.cellObj]], IO.rope[cellFileName]];
ENDLOOP;
DFfile.Close[];
TerminalIO.WriteRope[ " — done.\n"];
EXITS IOProblems => TerminalIO.WriteRope[ " — failed.\n"];
};
ENDCASE => {
TerminalIO.WriteRope[ "Warning: Unknown output format, no file written.\n"];
};
ClearPorts[cellList];
};
PrintSubcircuit: PROCEDURE [root, circuitDefn: TiogaFileOps.Ref, cellObj: CD.ObPtr, GlobalNames: SymTab.Ref, formatKey: REF ANY] ~ {
Format specific routines.
PrintStrayProc: TYPE ~ PROCEDURE [ Stream: IO.STREAM, node: REF CircuitNode, specialName: Rope.ROPENIL];
PrintRoseStray: PrintStrayProc ~ {
NULL
};
PrintThymeStray: PrintStrayProc ~ {
startedAPList: BOOLEANFALSE;
FOR apList: LIST OF AreaPerimRec ← node.dim, apList.rest WHILE apList # NIL DO
r: Rope.ROPE ~ tech.spinifexLayerNames[ apList.first.layer].thymeName;
IF r = NIL THEN LOOP;
IF ~startedAPList THEN {
Stream.Put[ IO.rope[" ?: Stray["]];
IF specialName # NIL THEN
Stream.Put[ IO.rope[specialName]]
ELSE
PrintNode[Stream, node];
Stream.Put[IO.rope["|"]]
}
ELSE
Stream.Put[ IO.char[ ',]];
Stream.PutF[ " a%g←%g, p%g←%g", IO.rope[r], IO.int[apList.first.area/(CD.lambda*CD.lambda)], IO.rope[r], IO.int[apList.first.perim/CD.lambda]];
startedAPList ← TRUE
ENDLOOP;
IF startedAPList THEN
Stream.PutRope["];"];
};
QuoteProc: TYPE ~ PROCEDURE [name: Rope.ROPE] RETURNS [Rope.ROPE];
QuoteRose: QuoteProc ~ {
RETURN [Convert.RopeFromRope[name]]
};
QuoteThyme: QuoteProc ~ {
l: INT ~ name.Length[];
IF l = 0 THEN RETURN ["$$"];
FOR i: INT IN [0..l) DO
c: CHAR ~ name.Fetch[i];
IF ~Ascii.Letter[c] AND ~Ascii.Digit[c] THEN EXIT;
REPEAT FINISHED => RETURN [name]
ENDLOOP;
{
Name has non-alphanumerics.
constructedName: Rope.ROPE ← Rope.Cat["$", name];
dollarPosnSUCC: INT ← 1;
WHILE (dollarPosnSUCC ← constructedName.Find["$", dollarPosnSUCC]) # -1 DO
constructedName ← constructedName.Replace[dollarPosnSUCC, 1, "$$"];
dollarPosnSUCC ← dollarPosnSUCC + 2 -- Jump over inserted $$
ENDLOOP;
RETURN [constructedName.Cat["$"]]
}
};
SpinifexOutput.NodePrintProc
PrintRoseNode: SpinifexOutput.NodePrintProc -- [ stream: IO.STREAM, node: REF CircuitNode] -- ~ {
printName: REF ANY ~ node.properties.GetPropFromList[nodeName];
IF printName = NIL THEN ERROR;
WITH printName SELECT FROM
local: REF Local => stream.PutF[ Quote[Rope.Cat[ localBase, Convert.RopeFromInt[local.numL]]] ];
port: REF Port => stream.PutF[ Quote[Rope.Cat[ portBase, Convert.RopeFromInt[port.numP]]] ];
named: REF Named => stream.Put[ IO.rope[Quote[named.name]]];
ENDCASE => ERROR;
};
PrintThymeNode: SpinifexOutput.NodePrintProc -- [ stream: IO.STREAM, node: REF CircuitNode] -- ~ {
printName: REF ANY ~ node.properties.GetPropFromList[nodeName];
IF printName = NIL THEN ERROR;
WITH printName SELECT FROM
local: REF Local => stream.Put[ IO.rope[ localBase], IO.card[local.numL]];
port: REF Port => stream.Put[ IO.rope[ portBase], IO.card[port.numP]];
named: REF Named => stream.Put[ IO.rope[Quote[named.name]]];
ENDCASE => ERROR;
};
QNodeName: PROCEDURE [node: REF CircuitNode] RETURNS [name: Rope.ROPE] ~ {
Returns Quoted name of node.
quotedName: IO.STREAM ~ IO.ROS[];
PrintNode[ quotedName, node];
name ← quotedName.RopeFromROS[]
};
PortHead: TiogaFileOps.Ref;
PrintHeadProc: TYPE ~ PROCEDURE [ name: Rope.ROPE];
PrintRoseHead: PrintHeadProc ~ {
output.PutF[ "-- %g", IO.rope[ name]];
circuitDefn.SetContents[ output.RopeFromROS[]];
-- Following LOOPHOLE caused by `opaque type' compiler problems.
TRUSTED { TiogaOps.PutProp[LOOPHOLE[circuitDefn], $Comment, NEW[BOOLEANTRUE]] };
output ← output.ROS[];
output.PutF[ "(CreatingUser \"%g\")", IO.rope[UserCredentials.Get[].name]];
AppendTiogaNode[output];
output ← output.ROS[];
output.PutF[ "(CreationTime \"%g\")", IO.time[]];
AppendTiogaNode[output];
output ← output.ROS[];
output.PutF[ "(CreationSite \"%g\")", IO.rope[PupDefs.GetMyName[]]];
AppendTiogaNode[output];
output ← output.ROS[];
output.PutRope[ "(DerivingProgram \"Spinifex\" \"TrashForNow\")"];
AppendTiogaNode[output];
output ← output.ROS[];
output.PutF[ "(CellTypeName %g)", IO.rope[name]];
AppendTiogaNode[output];
output ← output.ROS[];
output.Put[IO.rope[ "(Ports"]];
AppendTiogaNode[output];
Introduce 3rd level sub-structure.
PortHead ← currLine;
lastNodeNode ← currLine;
output ← output.ROS[]
};
PrintThymeHead: PrintHeadProc ~ {
output.Put[ IO.rope[ name], IO.rope[ ": circuit["]];
};
PrintFormalProc: TYPE ~ PROCEDURE [ qName: Rope.ROPE, portNum: CARDINAL, node: REF CircuitNode ← NIL];
PrintRoseFormal: PrintFormalProc ~ {
portDef: TiogaFileOps.Ref ~ PortHead.InsertAsLastChild[];
INTERIM, EC if present should go here.
output.PutF[ "(%g)", IO.rope[qName] ];
portDef.SetContents[output.RopeFromROS[]];
portDef.SetFormat[ "code"];
output ← output.ROS[];
output.PutF[ "(N %g", IO.rope[qName]];
IF node # NIL THEN {
WITH node.properties.GetPropFromList[ nodeName] SELECT FROM
nameRec: REF Named => {
output.PutRope[" (G D)"];
IF nameRec.aliases # NIL THEN PrintNodeAlias[node, nameRec.aliases]
};
ENDCASE => output.PutRope[" (G P)"];
};
output.PutRope[")"];
AppendTiogaNode[output];
output ← output.ROS[];
Port node defs, e.g. (PN "Vdd" "Vdd")
output.PutF[ "(PN %g %g)", IO.rope[qName], IO.rope[qName]];
AppendTiogaNode[output];
output ← output.ROS[]
};
PrintThymeFormal: PrintFormalProc ~ {
output.Put[ IO.rope[IF portNum = CountBase THEN " " ELSE ", "], IO.rope[qName] ]
};
PrintStartBodyProc: TYPE ~ PROCEDURE [ cellName: Rope.ROPE];
PrintRoseStartBody: PrintStartBodyProc ~ {
portClose: TiogaFileOps.Ref ~ PortHead.InsertAsLastChild[];
privateStart: TiogaFileOps.Ref ~ PortHead.InsertNode[];
portClose.SetContents[")"];
portClose.SetFormat[ "code"];
privateStart.SetContents["(PrivateFollows)"];
portClose.SetFormat[ "code"];
};
PrintThymeStartBody: PrintStartBodyProc ~ {
output.Put[ IO.rope["] = {"]];
circuitDefn.SetContents[ output.RopeFromROS[]];
circuitDefn.AddLooks[0, cellName.Length[], 'b, root];
output ← output.ROS[]
};
PrintLocalNodeProc: TYPE ~ PROCEDURE [ node: REF CircuitNode];
PrintRoseLocalNode: PrintLocalNodeProc ~ {
Local node defs, e.g. (N "Vdd")
output.PutRope["(N "];
PrintNode[ output, node];
WITH node.properties.GetPropFromList[ nodeName] SELECT FROM
nameRec: REF Named => {
output.PutRope[" (G D)"];
IF nameRec.aliases # NIL THEN PrintNodeAlias[node, nameRec.aliases]
};
ENDCASE => output.PutRope[" (G P)"];
output.PutRope[")"];
AppendTiogaNode[output];
output ← output.ROS[];
lastNodeNode ← currLine;
};
PrintThymeLocalNode: PrintLocalNodeProc ~ {
WITH node.properties.GetPropFromList[ nodeName] SELECT FROM
nameRec: REF Named => IF nameRec.aliases # NIL THEN PrintNodeAlias[node, nameRec.aliases];
ENDCASE;
PrintNode[ output, node];
output.Put[ IO.rope[ ": node;"]];
PrintStray[ output, node];
AppendTiogaNode[output];
output ← output.ROS[];
};
PrintNodeAliasProc: TYPE ~ PROCEDURE [ node: REF CircuitNode, aliases: LIST OF Rope.ROPE];
PrintRoseNodeAlias: PrintNodeAliasProc ~ {
output.Put[ IO.rope[ " (A "]];
PrintNode[ output, node];
FOR al: LIST OF Rope.ROPE ← aliases, al.rest WHILE al # NIL DO
r: Rope.ROPE ← al.first;
output.Put[ IO.rope[ " "], IO.rope[ Quote[r]] ];
ENDLOOP;
output.Put[ IO.rope[ ")"]];
};
PrintThymeNodeAlias: PrintNodeAliasProc ~ {
IF node.properties.GetPropFromList[ isPort] = isPort THEN RETURN;
output.Put[ IO.rope[ "-- ALIAS[ "]];
PrintNode[ output, node];
FOR al: LIST OF Rope.ROPE ← aliases, al.rest WHILE al # NIL DO
output.Put[ IO.rope[ ", "], IO.rope[ Quote[al.first]] ];
ENDLOOP;
output.Put[ IO.rope[ "] --"]];
AppendTiogaNode[output];
-- Following LOOPHOLE caused by `opaque type' compiler problems.
TRUSTED { TiogaOps.PutProp[LOOPHOLE[currLine], $Comment, NEW[BOOLEANTRUE]] };
output ← output.ROS[]
};
PrintInstanceHeadProc: TYPE ~ PROCEDURE [ qInstName, defName: Rope.ROPE];
PrintRoseInstanceHead: PrintInstanceHeadProc ~ {
output.PutF[ "(CI %g %g (CIC", IO.rope[qInstName], IO.rope[Quote[defName]] ];
};
PrintThymeInstanceHead: PrintInstanceHeadProc ~ {
output.PutF[ "%g: %g[", IO.rope[qInstName], IO.rope[Quote[defName]]];
};
PrintActualProc: TYPE ~ PROCEDURE [ qActualNode, qFormalPort: Rope.ROPE, actualNum: CARDINAL];
PrintRoseActual: PrintActualProc ~ {
output.PutF[ " (%g %g)", IO.rope[qFormalPort], IO.rope[qActualNode] ]
};
PrintThymeActual: PrintActualProc ~ {
IF actualNum # CountBase THEN output.PutRope[ ", "];
output.PutRope[ qActualNode];
};
PrintInventedProc: TYPE ~ PROCEDURE [node: REF CircuitNode] RETURNS [Rope.ROPE];
lastNodeNode: TiogaFileOps.Ref; -- Set in PrintRoseHead & PrintRoseLocalNode
PrintRoseInvented: PrintInventedProc ~ {
tnName: Rope.ROPE;
nodeStopperDecls: IO.STREAMIO.ROS[];
[tnName, nodeStoppers] ← FindUnique[stopperBase, nodeStoppers];
tnName ← Quote[tnName];
nodeStopperDecls.Put[ IO.rope["(N "], IO.rope[tnName], IO.rope[")"]];
PrintStray[ nodeStopperDecls, node, tnName];
lastNodeNode ← lastNodeNode.InsertNode[];
lastNodeNode.SetContents[nodeStopperDecls.RopeFromROS[]];
lastNodeNode.SetFormat[ "code"];
RETURN [tnName]
};
PrintThymeInvented: PrintInventedProc ~ {
-- Declare `Node Stoppers' for nodes which are not part of current cell's circuit, but nevertheless appear on a subcircuit's parameter list due to mergings which occur in other applications of the subcircuit.
tnName: Rope.ROPE;
nodeStopperDecls: IO.STREAMIO.ROS[];
[tnName, nodeStoppers] ← FindUnique[stopperBase, nodeStoppers];
tnName ← Quote[tnName];
nodeStopperDecls.Put[ IO.rope[tnName], IO.rope[": node;"]];
PrintStray[ nodeStopperDecls, node, tnName];
AppendTiogaNode[nodeStopperDecls];
nodeStoppers ← nodeStoppers.SUCC;
RETURN [tnName]
};
PrintInstanceEndProc: TYPE ~ PROCEDURE [];
PrintRoseInstanceEnd: PrintInstanceEndProc ~ {
output.PutRope[ "))"];
AppendTiogaNode[output];
output ← output.ROS[]
};
PrintThymeInstanceEnd: PrintInstanceEndProc ~ {
output.PutRope[ "];"];
AppendTiogaNode[output];
output ← output.ROS[]
};
PrintBodyEndProc: TYPE ~ PROCEDURE [];
PrintRoseBodyEnd: PrintBodyEndProc ~ {
};
PrintThymeBodyEnd: PrintBodyEndProc ~ {
output.PutRope[ "};"];
AppendTiogaNode[output];
output ← output.ROS[]
};
AppendTiogaNode: PROCEDURE [Stream: IO.STREAM] ~ {
currLine ← circuitDefn.InsertAsLastChild[currLine];
currLine.SetContents[Stream.RopeFromROS[]];
currLine.SetFormat[ "code"]
};
Symbols: SymTab.Ref;
UsedSymbol: PROCEDURE [r: Rope.ROPE] RETURNS [BOOLEAN] ~ {
RETURN [GlobalNames.Fetch[r].found OR Symbols.Fetch[r].found]
};
FindUnique: PROCEDURE [ base: Rope.ROPE, start: INTEGER, val: REF ANYNIL] RETURNS [rope: Rope.ROPE, count: INTEGER] ~ {
-- Finds first string of form base-int where int>=start where base-int is not in Symbols. Enters the found string in Symbols.
count ← start;
DO
rope ← base.Cat[Convert.RopeFromInt[count]];
IF ~UsedSymbol[rope] THEN {
[] ← Symbols.Store[rope, val];
RETURN
};
count ← count.SUCC;
ENDLOOP;
};
InstanceName: PROCEDURE [appl: CD.ApplicationPtr, nonameBase: Rope.ROPE, nonameCount: CARDINAL] RETURNS [qInstName: Rope.ROPE, newCount: CARDINAL] ~ {
WITH CDProperties.GetPropFromApplication[ appl, SpinifexAtoms.InstanceName] SELECT FROM
r: Rope.ROPE => {
newCount ← nonameCount; -- Irrelevant in this case, so return old value.
IF ~UsedSymbol[r] THEN {
[] ← Symbols.Store[r, NIL];
qInstName ← r
}
ELSE qInstName ← FindUnique[r.Cat[CountSep], CountBase].rope
};
ENDCASE => [qInstName, newCount] ← FindUnique[nonameBase, nonameCount];
qInstName ← Quote[qInstName]
};
-- Output format customization
PrintStray: PrintStrayProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeStray,
SpinifexAtoms.rosePrint => PrintRoseStray,
ENDCASE => ERROR;
Quote: QuoteProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => QuoteThyme,
SpinifexAtoms.rosePrint => QuoteRose,
ENDCASE => ERROR;
PrintNode: SpinifexOutput.NodePrintProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeNode,
SpinifexAtoms.rosePrint => PrintRoseNode,
ENDCASE => ERROR;
PrintHead: PrintHeadProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeHead,
SpinifexAtoms.rosePrint => PrintRoseHead,
ENDCASE => ERROR;
PrintFormal: PrintFormalProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeFormal,
SpinifexAtoms.rosePrint => PrintRoseFormal,
ENDCASE => ERROR;
PrintStartBody: PrintStartBodyProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeStartBody,
SpinifexAtoms.rosePrint => PrintRoseStartBody,
ENDCASE => ERROR;
PrintLocalNode: PrintLocalNodeProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeLocalNode,
SpinifexAtoms.rosePrint => PrintRoseLocalNode,
ENDCASE => ERROR;
PrintNodeAlias: PrintNodeAliasProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeNodeAlias,
SpinifexAtoms.rosePrint => PrintRoseNodeAlias,
ENDCASE => ERROR;
PrintInstanceHead: PrintInstanceHeadProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeInstanceHead,
SpinifexAtoms.rosePrint => PrintRoseInstanceHead,
ENDCASE => ERROR;
PrintActual: PrintActualProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeActual,
SpinifexAtoms.rosePrint => PrintRoseActual,
ENDCASE => ERROR;
PrintInvented: PrintInventedProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeInvented,
SpinifexAtoms.rosePrint => PrintRoseInvented,
ENDCASE => ERROR;
PrintInstanceEnd: PrintInstanceEndProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeInstanceEnd,
SpinifexAtoms.rosePrint => PrintRoseInstanceEnd,
ENDCASE => ERROR;
PrintBodyEnd: PrintBodyEndProc ~ SELECT formatKey FROM
SpinifexAtoms.thymePrint => PrintThymeBodyEnd,
SpinifexAtoms.rosePrint => PrintRoseBodyEnd,
ENDCASE => ERROR;
ignoreChildNames: BOOLEAN ~ formatKey = SpinifexAtoms.rosePrint;
Local: TYPE ~ RECORD [numL: CARDINAL];
Port: TYPE ~ RECORD [numP: CARDINAL];
Named: TYPE ~ RECORD [name: Rope.ROPE, aliases: LIST OF Rope.ROPE ← NIL];
circuit: REF Circuit ~ NARROW[ CDProperties.GetPropFromObject[ from~cellObj, prop~SpinifexAtoms.spinifex]];
tech: REF TechHandle ~ circuit.technologyHandle;
localNodes: CARDINAL ← CountBase;
throughNodes: LIST OF CarryThrough ~ NARROW[ circuit.properties.GetPropFromList[ carryThroughNodes] ];
linkCount: CARDINAL ← CountBase;
subcellCount: CARDINAL ← CountBase;
nodeStoppers: CARDINAL ← CountBase;
output: IO.STREAMIO.ROS[];
currLine: TiogaFileOps.Ref ← NIL;
-- Name generator customization
CountSep: Rope.ROPE ~ "-";
CountBase: INTEGER ~ 1;
portBase: Rope.ROPE ~ "p";
localBase: Rope.ROPE ~ "n";
stopperBase: Rope.ROPE ~ "tn";
throughPortBase: Rope.ROPE ~ "tp";
transBase: Rope.ROPE ~ "Q";
circuitBase: Rope.ROPE ~ "C";
-- First we must count how many times each symbol is used. The reason we do this is to avoid suffixing counts to symbols which are used only once.
{
count: INTEGER ← 17;
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
count ← count.SUCC;
ENDLOOP;
Symbols ← SymTab.Create[mod~ count, case~ TRUE]
};
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
signalName: REF SignalName ~ NARROW[nl.first.properties.GetPropFromList[ SpinifexAtoms.SignalName]];
IF signalName # NIL THEN {
DisAmbiguate: PROCEDURE [ r: Rope.ROPE, use: REF ANY] RETURNS [nname: Rope.ROPE]~ {
found: BOOLEAN;
val: REF ANY;
IF UsedSymbol[r] THEN {
nameBase: Rope.ROPE ~ r.Cat[CountSep];
count: REF INTEGER;
[found, val] ← Symbols.Fetch[r];
IF found THEN {
WITH val SELECT FROM
c: REF INTEGER => count ← c;
n: REF CircuitNode => {
prevName: REF Named ~ NARROW[n.properties.GetPropFromList[nodeName]];
count ← NEW[INTEGER];
[] ← Symbols.Store[r, count];
[nname, count^] ← FindUnique[base~ nameBase, start~ CountBase, val~ count];
n.properties ← n.properties.PutPropOnList[prop~ nodeName, val~ NEW[Named ← [nname, prevName.aliases]] ]
};
al: LIST OF Rope.ROPE => {
count ← NEW[INTEGER];
[] ← Symbols.Store[r, count];
[nname, count^] ← FindUnique[base~ nameBase, start~ CountBase, val~ count];
al.first ← nname
};
ENDCASE => ERROR;
count^ ← count^.SUCC
}
ELSE
count ← NEW[INTEGER ← CountBase];
[nname, count^] ← FindUnique[base~ nameBase, start~ count^, val~ count];
}
ELSE {
[] ← Symbols.Store[r, use];
nname ← r
};
};
r: Rope.ROPE ~ signalName.name;
nameRec: REF Named;
IF ignoreChildNames AND signalName.depth # 0 THEN LOOP;
nl.first.properties ← nl.first.properties.PutPropOnList[prop~ nodeName, val~ (nameRec ← NEW[Named ← [DisAmbiguate[r, nl.first]]]) ];
-- Copy aliases.
FOR al: REF SignalName ← signalName.alias, al.alias WHILE al # NIL DO
IF ignoreChildNames AND al.depth # 0 THEN LOOP;
nameRec.aliases ← CONS[ NIL, nameRec.aliases];
SELECT formatKey FROM
SpinifexAtoms.thymePrint => nameRec.aliases.first ← al.name; -- Special last minute hack for Louis Monier at September 7, 1984 10:01:35 pm PDT. used to be the same as SpinifexAtoms.rosePrint case.
SpinifexAtoms.rosePrint => nameRec.aliases.first ← DisAmbiguate[al.name, nameRec.aliases];
ENDCASE => ERROR;
ENDLOOP
}
ENDLOOP;
{
Cell name and formal Parameter list (ports).
logicalCellName: Rope.ROPE ~ Quote[CDDirectory.Name[cellObj]];
ports: CARDINAL ← CountBase;
portCount: CARDINAL ← CountBase;
PrintHead[logicalCellName];
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
IF nl.first.properties.GetPropFromList[ isPort] = isPort THEN {
IF nl.first.properties.GetPropFromList[ nodeName] = NIL THEN {
ports ← FindUnique[portBase, ports].count;
nl.first.properties ← nl.first.properties.PutPropOnList[prop~ nodeName, val~ NEW[Port ← [ports]] ]
};
PrintFormal[ QNodeName[nl.first], portCount, nl.first];
ports ← ports.SUCC;
portCount ← portCount.SUCC;
}
ENDLOOP;
{
tpCount: INTEGER ← CountBase;
tpPorts: CARDINAL ← 0;
FOR ctl: LIST OF CarryThrough ← throughNodes, ctl.rest WHILE ctl # NIL DO
tpName: Rope.ROPE;
[tpName, tpCount] ← FindUnique[ throughPortBase, tpCount];
PrintFormal[ Quote[tpName], portCount + tpPorts];
ctl.first.numCT ← tpCount;
tpCount ← tpCount.SUCC;
tpPorts ← tpPorts.SUCC;
ENDLOOP
};
PrintStartBody[logicalCellName]
};
Declaration of local nodes.
FOR nl: LIST OF REF CircuitNode ← circuit.nodes, nl.rest WHILE nl # NIL DO
IF nl.first.properties.GetPropFromList[ isPort] = NIL THEN {
IF nl.first.properties.GetPropFromList[ nodeName] = NIL THEN {
localNodes ← FindUnique[localBase, localNodes].count;
nl.first.properties ← nl.first.properties.PutPropOnList[prop~ nodeName, val~ NEW[Local ← [localNodes]] ];
};
PrintLocalNode[nl.first];
localNodes ← localNodes.SUCC
}
ENDLOOP;
Declaration of linkages.
FOR links: LIST OF REF NodeLinkage ← circuit.linkages, links.rest WHILE links # NIL DO
PrintProc: REF ANY ← CDObjectProcs.FetchFurther[ p~links.first.source.ob.p, key~formatKey];
IF PrintProc # NIL THEN {
qTName: Rope.ROPE;
[qTName, linkCount] ← InstanceName[links.first.source, transBase, linkCount];
NARROW[ PrintProc, REF SpinifexOutput.LinkagePrintProc]^[ output, links.first, qTName, PrintNode];
linkCount ← linkCount.SUCC;
}
ELSE {
output.Put[ IO.rope["Mystery object in Linkage List; ObjType ~ "], IO.atom[links.first.source.ob.p.objectType]];
};
AppendTiogaNode[output];
output ← output.ROS[];
ENDLOOP;
Declaration of subcircuits.
FOR appls: CD.ApplicationList ← circuit.subcircuits, appls.rest WHILE appls # NIL DO
actualsCount: CARDINAL ← CountBase;
subcircuit: REF Circuit ~ NARROW[ CDProperties.GetPropFromObject[ from~appls.first.ob, prop~SpinifexAtoms.spinifex]];
subcircuitThroughNodes: LIST OF CarryThrough ~ NARROW[ subcircuit.properties.GetPropFromList[ carryThroughNodes]];
qCName: Rope.ROPE;
[qCName, subcellCount] ← InstanceName[appls.first, circuitBase, subcellCount];
PrintInstanceHead[ qCName, CDDirectory.Name[appls.first.ob] ];
FOR nl: LIST OF REF CircuitNode ← subcircuit.nodes, nl.rest WHILE nl # NIL DO
IF nl.first.properties.GetPropFromList[ isPort] # NIL THEN {
parentNode: REF CircuitNode;
IF circuit.mergeDirectory # NIL THEN {
qual: LIST OF CD.ApplicationPtr;
[node~ parentNode, rootQualifier~ qual] ← SpinifexCircuit.FindRootNode[ circuit~ circuit, subcircuitNode~ nl.first, qualifier~ LIST[appls.first]];
IF qual # NIL THEN parentNode ← NIL
}
ELSE
parentNode ← NIL;
IF parentNode # NIL THEN
PrintActual[QNodeName[parentNode], QNodeName[nl.first], actualsCount]
ELSE {
-- Search throughNodes for nl.first.
FOR ctl: LIST OF CarryThrough ← throughNodes, ctl.rest WHILE ctl # NIL DO
IF ctl.first.key = nl.first AND ctl.first.merge.first.applChain.first = appls.first THEN {
PrintActual[Quote[ Rope.Cat[throughPortBase, Convert.RopeFromInt[ ctl.first.numCT]]], QNodeName[nl.first], actualsCount];
EXIT
};
REPEAT FINISHED =>
-- Generate `Node Stopper'
PrintActual[PrintInvented[nl.first], QNodeName[nl.first], actualsCount];
ENDLOOP;
};
actualsCount ← actualsCount.SUCC;
}
ENDLOOP;
FOR subctl: LIST OF CarryThrough ← subcircuitThroughNodes, subctl.rest WHILE subctl # NIL DO
-- 3 Possiblities: 1) node of circuit 2) throughNode of circuit 3) Need NodeStopper.
-- for subctl.first.merge.first to end of subctl.first.merge find applChains whose key and chain match to chainTail if appl after chainTail = appls.first Then we have a matcher. IF chainTail matcher .rest.rest = NIL THEN Case1 ELSE Case2. If no matcher THEN case3.
{
FOR sml: MergeRecList ← subctl.first.merge, sml.rest WHILE sml # NIL DO
appl2: LIST OF CD.ApplicationPtr ← sml.first.applChain;
FOR appl1: LIST OF CD.ApplicationPtr ← subctl.first.merge.first.applChain, appl1.rest WHILE appl1 # subctl.first.chainTail DO
IF appl2 = NIL OR appl1.first # appl2.first THEN EXIT;
appl2 ← appl2.rest;
REPEAT FINISHED =>
IF appl2 # NIL AND appl2.first = appls.first THEN {
IF appl2.rest = NIL THEN
-- Case 1) node of circuit.
PrintActual[QNodeName[sml.first.becomes], Quote[ Rope.Cat[throughPortBase, Convert.RopeFromInt[ subctl.first.numCT]]], actualsCount]
ELSE {
-- Case 2) throughNode of circuit.
FOR ctl: LIST OF CarryThrough ← throughNodes, ctl.rest WHILE ctl # NIL DO
IF sml = ctl.first.merge THEN {
PrintActual[Quote[ Rope.Cat[throughPortBase, Convert.RopeFromInt[ ctl.first.numCT]]], Quote[ Rope.Cat[throughPortBase, Convert.RopeFromInt[ subctl.first.numCT]]], actualsCount];
EXIT
};
REPEAT FINISHED =>
ERROR
ENDLOOP
};
GOTO foundMatcher
}
ENDLOOP;
REPEAT FINISHED =>
-- Case 3) Need NodeStopper.
PrintActual[PrintInvented[subctl.first.key], Quote[ Rope.Cat[throughPortBase, Convert.RopeFromInt[ subctl.first.numCT]]], actualsCount];
ENDLOOP;
EXITS foundMatcher => NULL
};
actualsCount ← actualsCount.SUCC;
ENDLOOP;
subcellCount ← subcellCount.SUCC;
PrintInstanceEnd[];
ENDLOOP;
PrintBodyEnd[];
};
END.