CombinatorialImpl.mesa 
Copyright Ó 1987 by Xerox Corporation. All rights reversed.
Created by Bertrand Serlet August 24, 1987 9:59:31 pm PDT
Bertrand Serlet September 17, 1987 3:39:32 pm PDT
DIRECTORY
Combinatorial, Convert, Core, CoreClasses, CoreFlat, CoreOps, CoreProperties, GList, IO, List, Ports, Process, RefTab, Rope, Rosemary, SymTab, TerminalIO;
CombinatorialImpl: CEDAR PROGRAM
IMPORTS Convert, CoreClasses, CoreFlat, CoreOps, CoreProperties, GList, IO, List, Ports, Process, RefTab, Rope, Rosemary, SymTab, TerminalIO
EXPORTS Combinatorial
~ BEGIN OPEN Combinatorial;
Predicates
IsCombinatorial: PUBLIC PROC [cell: Core.CellType] RETURNS [BOOL] = {
value: REF BOOL = NARROW [CoreProperties.GetCellTypeProp[cell, $Combinatorial]];
RETURN [value#NIL AND value^];
};
IsNonCombinatorial: PUBLIC PROC [cell: Core.CellType] RETURNS [BOOL] = {
value: REF BOOL = NARROW [CoreProperties.GetCellTypeProp[cell, $Combinatorial]];
RETURN [value#NIL AND NOT value^];
};
NotCombinatorial: PUBLIC ERROR [cell: Core.CellType] = CODE;
Typing of wires
EnumerateTypedWires: PUBLIC PROC [cc: Core.CellType, each: PROC [Core.Wire, ROPE, WireType] RETURNS [quit: BOOLFALSE]] RETURNS [quit: BOOL] = {
EachWire: CoreOps.EachWireProc = {
name: ROPE = CoreOps.GetFullWireName[cc.public, wire];
SELECT TRUE FROM
wire.size#0    => RETURN;
Rope.Equal[name, "Gnd"]   => quit ← each[wire, name, gnd];
Rope.Equal[name, "Vdd"]   => quit ← each[wire, name, vdd];
GetOutput[wire]#NIL         => quit ← each[wire, name, output];
ENDCASE             => quit ← each[wire, name, input];
};
IF NOT IsCombinatorial[cc] THEN ERROR NotCombinatorial[cc];
quit ← CoreOps.VisitWireSeq[cc.public, EachWire];
};
GetTypedWires: PUBLIC PROC [cc: Core.CellType, type: WireType] RETURNS [wires: Core.Wires ← NIL] = {
Each: PROC [wire: Core.Wire, name: ROPE, tt: WireType] RETURNS [quit: BOOLFALSE] = {
IF tt=type AND NOT CoreOps.Member[wires, wire] THEN wires ← CONS [wire, wires];
};
[] ← EnumerateTypedWires[cc, Each];
};
GetWireType: PUBLIC PROC [cc: Core.CellType, wire: Core.Wire] RETURNS [type: WireType] = {
Each: PROC [ww: Core.Wire, name: ROPE, tt: WireType] RETURNS [quit: BOOLFALSE] = {
type ← tt; quit ← ww=wire;
};
[] ← EnumerateTypedWires[cc, Each];
};
PutOutput: PUBLIC PROC [wire: Core.Wire, expr: ROPE] = {
CoreProperties.PutWireProp[wire, $Output, expr];
};
GetOutput: PUBLIC PROC [wire: Core.Wire] RETURNS [ROPENIL] = {
RETURN [CoreOps.FixStupidRef[CoreProperties.GetWireProp[wire, $Output]]];
};
Creation Conveniences
Oper: PUBLIC PROC [oper: ROPE, params: ParseTrees] RETURNS [ParseTree] =
{RETURN [NEW [ParseOperRec ← [oper, params]]]};
Not: PUBLIC PROC [tree: ParseTree] RETURNS [ParseTree] =
{RETURN [Oper["~", LIST [tree]]]};
And: PUBLIC PROC [trees: ParseTrees] RETURNS [ParseTree] =
{RETURN [Oper["*", trees]]};
Or: PUBLIC PROC [trees: ParseTrees] RETURNS [ParseTree] =
{RETURN [Oper["+", trees]]};
And2: PUBLIC PROC [tree1, tree2: ParseTree] RETURNS [ParseTree] =
{RETURN [And[LIST [tree1, tree2]]]};
Or2: PUBLIC PROC [tree1, tree2: ParseTree] RETURNS [ParseTree] =
{RETURN [Or[LIST [tree1, tree2]]]};
Parsing of Expressions
IncorrectExpression: PUBLIC ERROR [expr, msg: ROPE] = CODE;
ParseExpression: PUBLIC PROC [expr: ROPE] RETURNS [tree: ParseTree ← NIL] = {
stream: IO.STREAMIO.RIS[expr];
tokenKind: IO.TokenKind; token: ROPE;
Scan: PROC = {
ENABLE IO.EndOfStream => {tokenKind ← tokenEOF; CONTINUE};
[tokenKind, token] ← IO.GetCedarTokenRope[stream];
};
IsChar: PROC [char: CHAR] RETURNS [ok: BOOL] = {
ok ← tokenKind=tokenSINGLE AND Rope.Length[token]=1 AND Rope.Fetch[token]=char;
};
assumes that tokenKind and token are already set. Leaves them set at the end.
ParseTerm: PROC RETURNS [tree: ParseTree] = {
SELECT TRUE FROM
tokenKind=tokenDECIMAL OR tokenKind=tokenOCTAL OR tokenKind=tokenHEX => tree ← NEW [INT ← Convert.IntFromRope[token]];
IsChar['(]     => {
Scan[]; tree ← ParseExpr[];
IF NOT IsChar[')] THEN ERROR IncorrectExpression[expr, "Missing )"];
};
IsChar['~]     => {
Scan[]; RETURN [Not[ParseTerm[]]];
};
IsChar['[] OR tokenKind=tokenID   => {
variable: ROPENIL;
params: ParseTrees ← NIL;
WHILE tokenKind=tokenID OR NOT (tokenKind=tokenEOF OR IsChar[',] OR IsChar['+] OR IsChar['*] OR IsChar['(] OR IsChar[')]) DO
variable ← Rope.Cat[variable, token]; Scan[];
ENDLOOP;
IF NOT IsChar['(] THEN RETURN [variable];
We have a function here!
Scan[];
UNTIL tokenKind=tokenEOF OR IsChar[')] DO
params ← CONS [ParseExpr[], params];
IF IsChar[')] THEN EXIT;
IF NOT IsChar[',] THEN ERROR IncorrectExpression[expr, ", or ) expected"];
Scan[];
ENDLOOP;
tree ← Oper[variable, List.Reverse[params]];
};
ENDCASE => ERROR IncorrectExpression[expr, Rope.Cat["Incorrect token :", token]];
Scan[];
};
ParseAnds: PROC RETURNS [tree: ParseTree] = {
ands: ParseTrees ← LIST [ParseTerm[]];
WHILE IsChar['*] DO Scan[]; ands ← CONS[ParseTerm[], ands] ENDLOOP;
tree ← IF ands.rest=NIL THEN ands.first ELSE And[List.Reverse[ands]];
};
ParseExpr: PROC RETURNS [tree: ParseTree] = {
ors: ParseTrees ← LIST [ParseAnds[]];
WHILE IsChar['+] DO Scan[]; ors ← CONS[ParseAnds[], ors] ENDLOOP;
tree ← IF ors.rest=NIL THEN ors.first ELSE Or[List.Reverse[ors]];
};
Scan[]; tree ← ParseExpr[];
IF ISTYPE [tree, REF INT] THEN ERROR IncorrectExpression[expr, "Cannot be just an integer"];
IF tokenKind#tokenEOF THEN ERROR IncorrectExpression[expr, "Too much left"];
};
UnParseExpression: PUBLIC PROC [tree: ParseTree] RETURNS [expr: ROPENIL] = {
WITH tree SELECT FROM
var: Rope.ROPE   => expr ← var;
refInt: REF INT   => expr ← IO.PutR1[IO.int[refInt^]];
rptr: REF ParseOperRec => IF Rope.Equal[rptr.oper, "~"]
THEN expr ← Rope.Cat["~", UnParseExpression[rptr.params.first]]
ELSE {
char: BOOL = Rope.Equal[rptr.oper, "*"] OR Rope.Equal[rptr.oper, "+"];
FOR params: ParseTrees ← rptr.params, params.rest WHILE params#NIL DO
expr ← IF expr=NIL
THEN IF char THEN "(" ELSE Rope.Cat[rptr.oper, "("]
ELSE IF char THEN Rope.Cat[expr, rptr.oper] ELSE Rope.Cat[expr, ", "];
expr ← Rope.Cat[expr, UnParseExpression[params.first]];
ENDLOOP;
expr ← Rope.Cat[expr, ")"];
};
ENDCASE     => ERROR;
};
RenameVariables: PUBLIC PROC [tree: ParseTree, var: PROC [ROPE] RETURNS [ROPE]] RETURNS [ParseTree] = {
WITH tree SELECT FROM
rope: ROPE    => RETURN [var[rope]];
refInt: REF INT   => RETURN [refInt];
rptr: REF ParseOperRec => {
news: ParseTrees ← NIL;
FOR params: ParseTrees ← rptr.params, params.rest WHILE params#NIL DO
news ← CONS [RenameVariables[params.first, var], news];
ENDLOOP;
RETURN [Oper[rptr.oper, List.Reverse[news]]];
};
ENDCASE     => ERROR;
};
ParseOutput: PUBLIC PROC [wire: Core.Wire] RETURNS [tree: ParseTree] = {
RETURN [ParseExpression[GetOutput[wire]]];
};
Defining new Operators
opers: SymTab.Ref ← SymTab.Create[];
RegisterOperator: PUBLIC PROC [oper: ROPE, recast: RecastProc] = {
[] ← SymTab.Store[opers, oper, NEW [RecastProc ← recast]];
};
FetchOperator: PUBLIC PROC [oper: ROPE] RETURNS [recast: RecastProc] = {
refProc: REF RecastProc ← NARROW [SymTab.Fetch[opers, oper].val];
recast ← IF refProc=NIL THEN NIL ELSE refProc^;
};
Recast: PUBLIC PROC [tree: ParseTree] RETURNS [ParseTree] = {
rptr: REF ParseOperRec = NARROW [tree];
RETURN [FetchOperator[rptr.oper][rptr.params]];
};
Simulation of Combinatorial cells
Why isn't this one in Rosemary???
FindPort: PROC [rootWire: Core.WireSeq, rootPort: Ports.Port, searched: Core.Wire] RETURNS [found: Ports.Port ← NIL] = {
SearchWire: Ports.EachWirePortPairProc = {
found ← port; quit ← wire=searched;
};
IF NOT Ports.VisitBinding[rootWire, rootPort, SearchWire] THEN found ← NIL;
};
FindPorts: PROC [rootWire: Core.WireSeq, rootPort: Ports.Port, searched: Core.Wires] RETURNS [ports: LIST OF Ports.Port ← NIL] = {
FOR wires: Core.Wires ← searched, wires.rest WHILE wires#NIL DO
port: Ports.Port = FindPort[rootWire, rootPort, wires.first];
IF port=NIL THEN ERROR;
ports ← CONS [port, ports];
ENDLOOP;
ports ← NARROW [GList.Reverse[ports]];
};
RosemaryState: TYPE = REF RosemaryStateRec;
RosemaryStateRec: TYPE = RECORD [
SEQUENCE size: NAT OF RECORD [port: Ports.Port, roseValue: RoseValue]
];
RoseValue: TYPE = REF; -- union of Ports.Port and NAndNode
NAndNode: TYPE = REF NAndNodeRec;
NAndNodeRec: TYPE = RECORD [nodes: SEQUENCE size: NAT OF RoseValue];
RoseMakeNot: PROC [roseValue: RoseValue] RETURNS [RoseValue] = {
notRoseValue: NAndNode;
WITH roseValue SELECT FROM
nand: NAndNode => IF nand.size=1 THEN RETURN [nand[0]];
ENDCASE  => {};
notRoseValue ← NEW [NAndNodeRec[1]];
notRoseValue[0] ← roseValue;
RETURN [notRoseValue];
};
RoseMakeMaybeNot: PROC [roseValue: RoseValue, negate: BOOLFALSE] RETURNS [RoseValue] = {
RETURN [IF negate THEN RoseMakeNot[roseValue] ELSE roseValue];
};
RoseMakeNand: PROC [roseValues: LIST OF RoseValue, negate: BOOLFALSE] RETURNS [RoseValue] = {
count: NAT ← List.Length[roseValues];
roseValue: NAndNode ← NEW [NAndNodeRec[count]];
IF count=1 THEN RETURN [RoseMakeMaybeNot[roseValues.first, NOT negate]];
FOR i: NAT IN [0 .. count) DO
roseValue[i] ← RoseMakeMaybeNot[roseValues.first, negate];
roseValues ← roseValues.rest;
ENDLOOP;
RETURN [roseValue];
};
RosemaryParses: PROC [params: ParseTrees, var: PROC [ROPE] RETURNS [RoseValue]] RETURNS [roseValues: LIST OF RoseValue ← NIL] = {
WHILE params#NIL DO
roseValues ← CONS [RosemaryParse[params.first, var], roseValues];
params ← params.rest;
ENDLOOP;
};
RosemaryParse: PROC [tree: ParseTree, var: PROC [ROPE] RETURNS [RoseValue]] RETURNS [roseValue: RoseValue] = {
roseValue ← WITH tree SELECT FROM
rope: ROPE    => var[rope],
rptr: REF ParseOperRec => SELECT TRUE FROM
Rope.Equal[rptr.oper, "~"]  =>
RoseMakeNot[RosemaryParse[rptr.params.first, var]],
Rope.Equal[rptr.oper, "*"]  =>
RoseMakeNot[RoseMakeNand[RosemaryParses[rptr.params, var]]],
Rope.Equal[rptr.oper, "+"]  =>
RoseMakeNand[RosemaryParses[rptr.params, var], TRUE],
ENDCASE       =>
RosemaryParse[Recast[tree], var],
ENDCASE     => ERROR;
};
RoseEval: PROC [roseValue: RoseValue] RETURNS [level: Ports.Level ← L] = {
note initialization to L important for the case when we have a nand!
WITH roseValue SELECT FROM
port: Ports.Port => level ← port.l;
nand: NAndNode => FOR i: NAT IN [0 .. nand.size) DO
SELECT RoseEval[nand[i]] FROM
L => RETURN [H];
H => {};
ENDCASE => level ← X;
ENDLOOP;
ENDCASE  => ERROR;
};
CombinatorialInit: Rosemary.InitProc = {
RoseVar: PROC [var: ROPE] RETURNS [roseValue: RoseValue] = {
roseValue ← FindPort[cellType.public, p, CoreOps.FindWire[cellType.public, var]];
IF roseValue=NIL THEN ERROR;
};
outputs: Core.Wires ← GetTypedWires[cellType, output];
count: NAT ← GList.Length[outputs];
state: RosemaryState ← NEW [RosemaryStateRec[count]];
FOR i: NAT IN [0 .. count) DO
state[i].port ← FindPort[cellType.public, p, outputs.first];
state[i].roseValue ← RosemaryParse[ParseOutput[outputs.first], RoseVar];
outputs ← outputs.rest;
ENDLOOP;
stateAny ← state;
};
CombinatorialEval: Rosemary.EvalProc = {
state: RosemaryState = NARROW [stateAny];
FOR i: NAT IN [0 .. state.size) DO state[i].port.l ← RoseEval[state[i].roseValue] ENDLOOP;
};
CheckUnsuccessful: PUBLIC SIGNAL [level1, level2: Ports.Level] = CODE;
BindCombinatorial: PUBLIC PROC [cc: Core.CellType] = {
BlastPortData: CoreOps.EachWireProc = {CoreProperties.PutWireProp[wire, $PortData, NIL]};
Each: PROC [wire: Core.Wire, name: ROPE, type: WireType] RETURNS [quit: BOOLFALSE] = {
SELECT type FROM
input => {
[] ← Ports.InitPort[wire: wire, levelType: l, initDrive: none];
Ports.InitTesterDrive[wire: wire, initDrive: force];
};
output => {
[] ← Ports.InitPort[wire: wire, levelType: l, initDrive: drive];
Ports.InitTesterDrive[wire: wire, initDrive: expect];
};
gnd => {
[] ← Ports.InitPort[wire: wire, levelType: l, initDrive: none];
[] ← Rosemary.SetFixedWire[wire, L];
};
vdd => {
[] ← Ports.InitPort[wire: wire, levelType: l, initDrive: none];
[] ← Rosemary.SetFixedWire[wire, H];
};
ENDCASE => ERROR;
};
Hack to get rid of properties added by Logic!
[] ← CoreOps.VisitWireSeq[cc.public, BlastPortData];
[] ← EnumerateTypedWires[cc, Each];
[] ← Rosemary.BindCellType[cellType: cc, roseClassName: "Combinatorial"];
[] ← CoreFlat.CellTypeCutLabels[cc, "LogicMacro", "Logic"];
};
CheckTransistorsAgainstExpressions: PUBLIC PROC [cc: Core.CellType, checkXValues: BOOLTRUE] = {
TryAll: PROC [inputsToFix: Core.Wires] = {
Process.Yield[];
IF inputsToFix=NIL THEN {
Rosemary.Settle[simulation1];
Rosemary.Settle[simulation2];
FOR outs: Core.Wires ← outputs, outs.rest WHILE outs#NIL DO
p1: Ports.Port = FindPort[cc.public, port1, outs.first];
p2: Ports.Port = FindPort[cc.public, port2, outs.first];
IF p1.l#p2.l THEN SIGNAL CheckUnsuccessful[p1.l, p2.l];
ENDLOOP;
} ELSE FOR level: Ports.Level IN Ports.Level DO
p1: Ports.Port = FindPort[cc.public, port1, inputsToFix.first];
p2: Ports.Port = FindPort[cc.public, port2, inputsToFix.first];
IF level=X AND NOT checkXValues THEN LOOP;
p1.l ← level; p2.l ← level;
TryAll[inputsToFix.rest];
ENDLOOP;
};
inputs: Core.Wires = GetTypedWires[cc, input];
outputs: Core.Wires = GetTypedWires[cc, output];
port1: Ports.Port = Ports.CreatePort[cc, TRUE];
port2: Ports.Port = Ports.CreatePort[cc, TRUE];
We create two simulations
simulation1: Rosemary.Simulation ← Rosemary.Instantiate[cc, port1];
simulation2: Rosemary.Simulation ← Rosemary.Instantiate[cc, port2, CoreFlat.CreateCutSet[flatCells: LIST [NEW [CoreFlat.FlatCellTypeRec ← CoreFlat.rootCellType]]]];
We initialize both
Rosemary.Initialize[simulation1];
Rosemary.Initialize[simulation2];
For each input, we loop
TryAll[inputs];
};
Statically Making Combinatorial Cells
InputOutputWarning: PROC [type: ATOM, root: Core.CellType, flatWire: CoreFlat.FlatWire] = {
TerminalIO.PutF["*** %g in cell %g with %g.\n", IO.atom[type], IO.rope[CoreOps.GetCellTypeName[root]], IO.rope[CoreFlat.WirePathRope[root, flatWire^]]];
SIGNAL InputOutputProblem[type, root, flatWire];
};
InputOutputProblem: PUBLIC SIGNAL [type: ATOM, root: Core.CellType, flatWire: CoreFlat.FlatWire] = CODE;
TranslateOutputs: PROC [root, actual, public: Core.WireSeq, eachOutput: PROC [act: Core.Wire, tree: ParseTree]] = {
table: RefTab.Ref ← CoreOps.CreateBindingTable[public, actual];
RenameVar: PROC [old: ROPE] RETURNS [new: ROPE] = {
pub: Core.Wire ← CoreOps.FindWire[public, old];
act: Core.Wire = NARROW [RefTab.Fetch[table, pub].val];
RETURN [CoreOps.GetFullWireName[root, act]];
};
EachWirePair: CoreOps.EachWirePairProc = {
IF GetOutput[publicWire]=NIL THEN RETURN;
eachOutput[actualWire, RenameVariables[ParseOutput[publicWire], RenameVar]];
};
[] ← CoreOps.VisitBindingSeq[actual, public, EachWirePair];
};
MakeCombinatorial: PUBLIC PROC [cell: Core.CellType] = {
signalled: Core.Wires ← NIL;
Process.Yield[];
IF IsCombinatorial[cell] THEN RETURN;
IF IsNonCombinatorial[cell] THEN ERROR NotCombinatorial[cell];
SELECT cell.class FROM
CoreClasses.transistorCellClass => ERROR NotCombinatorial[cell];
CoreClasses.unspecifiedCellClass => ERROR NotCombinatorial[cell];
CoreClasses.recordCellClass => {
table: RefTab.Ref ← RefTab.Create[]; -- maps internal wires to their ParseTree, expressed with variables as part of the internal
rct: CoreClasses.RecordCellType = NARROW [cell.data];
count: INT ← 0;
ReplaceVars: PROC [tree: ParseTree, forbidden: Core.Wires] RETURNS [ParseTree] = {
WITH tree SELECT FROM
rope: ROPE    => {
wire: Core.Wire ← CoreOps.FindWire[rct.internal, rope];
aux: ParseTree = RefTab.Fetch[table, wire].val;
IF wire=NIL THEN ERROR;
IF aux=NIL THEN {
it must be an input!
inputName: ROPE = CoreOps.GetFullWireName[cell.public, wire];
IF inputName=NIL THEN {
IF NOT CoreOps.Member[signalled, wire] THEN {
InputOutputWarning[$NonPublicInput, cell, NEW [CoreFlat.FlatWireRec ← [wire: wire]]];
signalled ← CONS [wire, signalled];
};
};
RETURN [inputName];
};
IF CoreOps.Member[forbidden, wire] THEN {
IF NOT CoreOps.Member[signalled, wire] THEN {
InputOutputWarning[$OutputLoop, cell, NEW [CoreFlat.FlatWireRec ← [wire: wire]]]; -- Loop!
signalled ← CONS [wire, signalled];
};
RETURN [rope];
};
RETURN [ReplaceVars[aux, CONS [wire, forbidden]]];
};
refInt: REF INT   => RETURN [refInt];
rptr: REF ParseOperRec => {
news: ParseTrees ← NIL;
FOR params: ParseTrees ← rptr.params, params.rest WHILE params#NIL DO
news ← CONS [ReplaceVars[params.first, forbidden], news];
ENDLOOP;
RETURN [Oper[rptr.oper, List.Reverse[news]]];
};
ENDCASE     => ERROR;
};
EachOutput: PROC [act: Core.Wire, tree: ParseTree] = {
prev: ParseTree = RefTab.Fetch[table, act].val;
IF prev#NIL THEN {
IF NOT CoreOps.Member[signalled, act] THEN {
InputOutputWarning[$OutputOfTwoCombinatorialCells, cell, NEW [CoreFlat.FlatWireRec ← [wire: act]]];
signalled ← CONS [act, signalled];
};
};
[] ← RefTab.Store[table, act, tree];
};
SetOutput: CoreOps.EachWireProc = {
tree: ParseTree = RefTab.Fetch[table, wire].val;
IF tree=NIL THEN RETURN; -- Not an output, proceed!
PutOutput[wire, UnParseExpression[ReplaceVars[tree, LIST [wire]]]];
count ← count + 1;
};
FOR i: NAT IN [0 .. rct.size) DO
MakeCombinatorial[rct[i].type];
TranslateOutputs[rct.internal, rct[i].actual, rct[i].type.public, EachOutput];
ENDLOOP;
IF signalled#NIL THEN ERROR NotCombinatorial[cell];
[] ← CoreOps.VisitWireSeq[cell.public, SetOutput];
IF count=0 THEN TerminalIO.PutF["*** Cell %g made combinatorial, but has no output.\n", IO.rope[CoreOps.GetCellTypeName[cell]]];
CoreProperties.PutCellTypeProp[cell, $Combinatorial, NEW [BOOLTRUE]];
BindCombinatorial[cell];
TerminalIO.PutF["Cell %g made combinatorial. %g outputs.\n", IO.rope[CoreOps.GetCellTypeName[cell]], IO.int[count]];
};
ENDCASE   => {
count: INT ← 0;
EachOutput: PROC [act: Core.Wire, tree: ParseTree] = {
PutOutput[act, UnParseExpression[tree]];
count ← count + 1;
};
recasted: Core.CellType ← CoreOps.Recast[cell];
MakeCombinatorial[recasted];
TranslateOutputs[cell.public, cell.public, recasted.public, EachOutput];
IF count=0 THEN TerminalIO.PutF["*** Cell %g made combinatorial, but has no output.\n", IO.rope[CoreOps.GetCellTypeName[cell]]];
CoreProperties.PutCellTypeProp[cell, $Combinatorial, NEW [BOOLTRUE]];
BindCombinatorial[cell];
TerminalIO.PutF["Cell %g made combinatorial. %g outputs.\n", IO.rope[CoreOps.GetCellTypeName[cell]], IO.int[count]];
};
};
AttemptMakeCombinatorial: PUBLIC PROC [cell: Core.CellType] RETURNS [trans, ok, notOK: INT ← 0] = {
Each: CoreFlat.UnboundFlatCellProc = {
IF IsCombinatorial[cell] OR IsNonCombinatorial[cell] THEN RETURN;
SELECT cell.class FROM
CoreClasses.transistorCellClass => trans ← trans + 1;
ENDCASE   => {
CoreFlat.NextUnboundCellType[cell: cell, target: target, flatCell: flatCell, instance: instance, index: index, parent: parent, flatParent: flatParent, data: data, proc: Each ! ANY => GOTO GRRR];
MakeCombinatorial[cell ! NotCombinatorial, InputOutputProblem => GOTO GRRR];
ok ← ok + 1;
EXITS GRRR => {notOK ← notOK + 1; CoreProperties.PutCellTypeProp[cell, $Combinatorial, NEW [BOOLFALSE]]};
};
};
Each[cell];
};
Splitting Combinatorial Cells
SearchRefTab: PROC [x: RefTab.Ref, val: RefTab.Val] RETURNS [found: BOOL, key: RefTab.Key ← NIL] = {
fval: RefTab.Val ← val;
fkey: RefTab.Key ← NIL;
EachPair: RefTab.EachPairAction = {fkey ← key; quit ← val=fval};
found ← RefTab.Pairs[x, EachPair];
key ← fkey;
};
InternalIsCombinatorial: PROC [cell: Core.CellType] RETURNS [BOOL] = {
MakeCombinatorial[cell ! NotCombinatorial, InputOutputProblem => GOTO GRRR];
RETURN [TRUE];
EXITS GRRR => {CoreProperties.PutCellTypeProp[cell, $Combinatorial, NEW [BOOLFALSE]]; RETURN [FALSE]};
};
ConsIfNotMember: PROC [wire: Core.Wire, wires: Core.Wires] RETURNS [Core.Wires] = {
FOR list: Core.Wires ← wires, list.rest WHILE list#NIL DO
IF list.first=wire OR CoreOps.RecursiveMember[list.first, wire] THEN RETURN [wires];
ENDLOOP;
RETURN [CONS [wire, wires]];
};
WireUse: TYPE = {PublicUse, CombUse, NonCombUse};
WireUses: TYPE = ARRAY WireUse OF BOOLALL [FALSE];
AddIntType: PROC [intType: RefTab.Ref, int: Core.Wire, type: WireUse] = {
wireUses: REF WireUses ← NARROW [RefTab.Fetch[intType, int].val];
IF wireUses=NIL THEN wireUses ← NEW [WireUses];
wireUses[type] ← TRUE;
[] ← RefTab.Store[intType, int, wireUses];
FOR i: NAT IN [0 .. int.size) DO AddIntType[intType, int[i], type] ENDLOOP;
};
MakeNewSeq: PROC [old: Core.WireSeq, oldToNew: RefTab.Ref] RETURNS [new: Core.WireSeq] = {
new ← CoreOps.CreateWires[size: old.size];
FOR j: NAT IN [0 .. new.size) DO
new[j] ← CoreOps.CopyWireUsingTable[old[j], oldToNew];
ENDLOOP;
};
SplitCombinatorial: PUBLIC PROC [record: Core.CellType] RETURNS [split: Core.CellType ← NIL] = {
rct: CoreClasses.RecordCellType = NARROW [record.data];
intTable: RefTab.Ref = RefTab.Create[]; -- maps internals of record to internals of split
public: Core.WireSeq = MakeNewSeq[record.public, intTable];
intType: RefTab.Ref = RefTab.Create[]; -- maps internals of split to WireUses
combs: LIST OF CoreClasses.CellInstance ← NIL; -- new combinatorial instances
nonCombs: LIST OF CoreClasses.CellInstance ← NIL; -- new non-combinatorial instances
combInt, combPub, combAct: Core.Wires ← NIL;
combCT: Core.CellType;
combInstance: CoreClasses.CellInstance;
combNewInt: RefTab.Ref = RefTab.Create[]; -- maps internals of split to internals of combCT
internals: Core.Wires ← NIL;
CreateNew: PROC [int: Core.Wire] RETURNS [new: Core.Wire] = {
new ← NARROW [RefTab.Fetch[combNewInt, int].val];
IF new#NIL THEN RETURN;
new ← CoreOps.CreateWires[int.size];
[] ← RefTab.Store[combNewInt, int, new];
FOR i: NAT IN [0 .. int.size) DO new[i] ← CreateNew[int[i]] ENDLOOP;
};
EachIntTypeCreateNew: RefTab.EachPairAction = {
wireUses: REF WireUses = NARROW [val];
IF wireUses[CombUse] THEN [] ← CreateNew[NARROW [key]];
};
EachIntType: RefTab.EachPairAction = {
int: Core.Wire = NARROW [key];
wireUses: REF WireUses = NARROW [val];
IF wireUses[CombUse]
THEN {
new: Core.Wire ← NARROW [RefTab.Fetch[combNewInt, int].val];
combInt ← ConsIfNotMember[new, combInt];
IF NOT wireUses[NonCombUse] AND NOT wireUses[PublicUse] THEN RETURN;
internals ← ConsIfNotMember[int, internals];
combInt ← ConsIfNotMember[new, combInt];
IF NOT CoreOps.Member[combPub, new] THEN {
combAct ← CONS [int, combAct];
combPub ← CONS [new, combPub];
};
}
ELSE internals ← ConsIfNotMember[int, internals];
};
FOR i: NAT IN [0 .. rct.size) DO
ct: Core.CellType = rct[i].type;
actual: Core.WireSeq = MakeNewSeq[rct[i].actual, intTable];
instance: CoreClasses.CellInstance = CoreClasses.CreateInstance[actual, ct];
IF InternalIsCombinatorial[ct]
THEN combs ← CONS [instance, combs]
ELSE nonCombs ← CONS [instance, nonCombs];
ENDLOOP;
FOR i: NAT IN [0 .. public.size) DO AddIntType[intType, public[i], PublicUse] ENDLOOP;
FOR list: LIST OF CoreClasses.CellInstance ← combs, list.rest WHILE list#NIL DO
FOR i: NAT IN [0 .. list.first.actual.size) DO AddIntType[intType, list.first.actual[i], CombUse] ENDLOOP;
ENDLOOP;
FOR list: LIST OF CoreClasses.CellInstance ← nonCombs, list.rest WHILE list#NIL DO
FOR i: NAT IN [0 .. list.first.actual.size) DO AddIntType[intType, list.first.actual[i], NonCombUse] ENDLOOP;
ENDLOOP;
[] ← RefTab.Pairs[intType, EachIntTypeCreateNew];
[] ← RefTab.Pairs[intType, EachIntType];
FOR list: LIST OF CoreClasses.CellInstance ← combs, list.rest WHILE list#NIL DO
actual: Core.WireSeq ← CoreOps.CreateWires[list.first.actual.size];
FOR i: NAT IN [0 .. actual.size) DO
actual[i] ← NARROW [RefTab.Fetch[combNewInt, list.first.actual[i]].val];
IF actual[i]=NIL THEN ERROR;
ENDLOOP;
list.first.actual ← actual;
ENDLOOP;
combCT ← CoreClasses.CreateRecordCell[
public: CoreOps.CreateWire[combPub], internal: CoreOps.CreateWire[combInt],
instances: combs, giveNames: TRUE
];
MakeCombinatorial[combCT ! InputOutputProblem => {
wire: Core.Wire ← flatWire.wire;
newInt: Core.Wire ← NARROW [SearchRefTab[combNewInt, wire].key];
oldInt: Core.Wire ← NARROW [SearchRefTab[intTable, newInt].key];
IF root#combCT OR oldInt=NIL THEN ERROR;
InputOutputWarning[type, record, NEW [CoreFlat.FlatWireRec ← [wire: oldInt]]];
RESUME;
}];
combInstance ← CoreClasses.CreateInstance[actual: CoreOps.CreateWire[combAct], type: combCT];
split ← CoreClasses.CreateRecordCell[
public: public,
internal: CoreOps.CreateWire[internals],
instances: CONS [combInstance, nonCombs],
giveNames: TRUE
];
TerminalIO.PutF[
"Splitting done for %g: combinatorial cell with %g outputs and %g non combinatorial cells.\n",
IO.rope[CoreOps.GetCellTypeName[record]],
IO.int[GList.Length[GetTypedWires[combCT, output]]],
IO.int[GList.Length[nonCombs]]
];
};
Initialization
Xor2Recast: RecastProc = {
p1: REF = params.first;
p2: REF = params.rest.first;
tree ← Or2[And2[p1, Not[p2]], And2[p2, Not[p1]]];
};
[] ← Rosemary.Register["Combinatorial", CombinatorialInit, CombinatorialEval];
RegisterOperator["xor2", Xor2Recast];
END.