AlpsTileImpl.mesa
Created by Bertrand Serlet, March 12, 1985 9:38:06 am PST
Last edited by Serlet July 2, 1985 4:03:43 pm PDT
Last Edited by: Sindhu, June 18, 1985 2:19:19 pm PDT
DIRECTORY
AlpsBool, AlpsTile, Convert, Rope, TerminalIO;
AlpsTileImpl: CEDAR PROGRAM
IMPORTS AlpsBool, Convert, Rope
EXPORTS AlpsTile =
BEGIN
OPEN AlpsTile;
-- Utilities
ROPE: TYPE = Rope.ROPE;
Output: PROC [t1, t2, t3, t4, t5, t6: ROPENIL] = AlpsBool.Output;
Reverse: PROC [list: LIST OF Tile] RETURNS [newList: LIST OF Tile ← NIL] = {
WHILE list#NIL DO
newList ← CONS [list.first, newList];
list ← list.rest;
ENDLOOP;
};
Append: PUBLIC PROC [context: Context, posNb: PosNb, horTileType: HorTileType, list2: LIST OF Tile] = {
list1: LIST OF Tile ← Reverse[context.tileArray[posNb][horTileType]];
IF ~context.columnsExistance[posNb][horTileType] THEN RETURN;
WHILE list1#NIL DO
list2 ← CONS[list1.first, list2]; list1 ← list1.rest;
ENDLOOP;
context.tileArray[posNb][horTileType] ← list2;
};
Appends a tile at top of the previous
Append1HorTileType: PROC [context: Context, posNb: PosNb, horTileType: HorTileType, tile: Tile] = {
reverse: LIST OF Tile ← Reverse[context.tileArray[posNb][horTileType]];
IF ~context.columnsExistance[posNb][horTileType] OR (horTileType=RightRoute AND posNb#context.table.size-1 AND ~context.shared) THEN RETURN;
context.tileArray[posNb][horTileType] ← Reverse[CONS [tile, reverse]];
};
EqualTile: PUBLIC PROC [tile1, tile2: Tile] RETURNS [sameTile: BOOLTRUE] = {
sameTile ← EqualTileRec[tile1^, tile2^]
};
EqualTileRec: PUBLIC PROC [tileRec1, tileRec2: TileRec] RETURNS [sameTileRec: BOOLTRUE] = {
IF tileRec1.special AND tileRec2.special THEN RETURN [Rope.Equal[tileRec1.name, tileRec2.name]];
tileRec1.name ← tileRec2.name ← NIL; -- so not to test the name with!
sameTileRec ← tileRec1=tileRec2;
};
TILE: PUBLIC PROC [tileRec: TileRec] RETURNS [tile: Tile] = {
IF ~(tileRec.special OR tileRec.input OR tileRec.route) THEN ERROR;
FOR list: LIST OF Tile ← tiles, list.rest WHILE list#NIL DO
tile ← list.first;
IF EqualTileRec[tile^, tileRec] THEN RETURN;
ENDLOOP;
tile ← NEW [TileRec ← tileRec];
IF tile.special THEN {
tile.leftPin ← ~Rope.Equal[tile.name, "NullVddGlue"] AND ~Rope.Equal[tile.name, "NullGndGlue"] AND ~Rope.Equal[tile.name, "LatchNull"];
tile.rightPin ← ~Rope.Equal[tile.name, "NullVddGlue"] AND ~Rope.Equal[tile.name, "NullGndGlue"] AND ~Rope.Equal[tile.name, "LatchNull"] AND ~Rope.Equal[tile.name, "LatchBetween"] AND ~Rope.Equal[tile.name, "LatchSend"];
};
tiles ← CONS [tile, tiles];
};
-- Generation of the TileArray
NilTile: PUBLIC PROC [i: HorTileType] RETURNS [tile: Tile] = {
tile ← SELECT i FROM
RightRoute    => TILE[[route: TRUE, noUpPoly: TRUE, noDownPoly: TRUE]],
LeftInput     => TILE[[input: TRUE, leftSide: TRUE]],
RightInput    => TILE[[input: TRUE]],
VddGlue     => TILE[[special: TRUE, name: "ThroughVddGlue"]],
GndGlue     => TILE[[special: TRUE, name: "ThroughGndGlue"]],
ENDCASE     => ERROR;
};
Coax: TYPE = REF CoaxRec;
CoaxRec: TYPE = RECORD [
expr: AlpsBool.Expression,    -- the expression to compute next (true/false if just Gnd to bring ????)
spin: BOOLTRUE,     -- the spin of the pair of wire. TRUE means value up, not value down
duplLeftInput: BOOLTRUE,    -- in case the expr is a duplicating one (CaseXNotX or CaseXY), this flag tells whether this Coax is supposed to compute the LeftInput or not. This flag is computed during Routing in RightRoute
ancesters: LIST OF AlpsBool.Expression ← NIL  -- the common ancesters, father first, with the sharability expressed by having one common ancester
];
ReverseCoaxes: PROC [list: LIST OF Coax] RETURNS [newList: LIST OF Coax ← NIL] = {
WHILE list#NIL DO newList ← CONS [list.first, newList]; list ← list.rest ENDLOOP;
};
RETURNS the distance of the next common ancester, LAST[INT] if none.
Consanguinity: PROC [coax1, coax2: Coax] RETURNS [distance: INT] = {
distance ← 0;
IF coax1.expr.varNb=0 OR coax2.expr.varNb=0 THEN RETURN[LAST[INT]];
FOR ancesters1: LIST OF AlpsBool.Expression ← coax1.ancesters, ancesters1.rest WHILE ancesters1#NIL DO
dist2: INT ← 0;
FOR ancesters2: LIST OF AlpsBool.Expression ← coax2.ancesters, ancesters2.rest WHILE ancesters2#NIL DO
IF ancesters1.first=ancesters2.first THEN RETURN[distance+dist2];
dist2 ← dist2+1;
ENDLOOP;
distance ← distance + 1;
ENDLOOP;
distance ← LAST[INT];
};
Sharable: PROC [context: Context, coax1, coax2: Coax] RETURNS [ok: BOOL] = {
ok ← (AlpsBool.Equal[context.table, coax1.expr, coax2.expr] OR AlpsBool.Equal[context.table, coax1.expr, coax2.expr, FALSE]) AND AlpsBool.NbOfCaseXY[context.table, coax1.expr]+AlpsBool.NbOfCaseXNotX[context.table, coax1.expr]>0 AND Consanguinity[coax1, coax2]#LAST[INT];
};
Spin: PROC [context: Context, coax1, coax2: Coax] RETURNS [spin: BOOL] = {
spin ← SELECT TRUE FROM
AlpsBool.Equal[context.table, coax1.expr, coax2.expr]    => coax1.spin=coax2.spin,
AlpsBool.Equal[context.table, coax1.expr, coax2.expr, FALSE] => coax1.spin#coax2.spin,
ENDCASE                => ERROR;
};
ExprToTiles: PROC [context: Context, expr: AlpsBool.Expression] = {
IF context.shared
THEN TileArrayAddRec[context, context.table.size-1, LIST[NEW[CoaxRec ← [expr: expr, spin: TRUE]]]]
ELSE {
nb: INT ← SmallTileRec[context, context.table.size-1, expr, TRUE]; -- from top to bottom
THROUGH [1..nb) DO
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: IF context.isLatched THEN "LatchNull" ELSE "NullVddGlue"]]];
ENDLOOP;
IF nb=1
THEN Append1HorTileType[context, context.table.size-1, RightRoute, TILE[[route: TRUE, noUpPoly: TRUE, noDownPoly: TRUE]]]
ELSE {
Append1HorTileType[context, context.table.size-1, RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noDownPoly: TRUE]]];
THROUGH (1..nb) DO
Append1HorTileType[context, context.table.size-1, RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noRightMetal: TRUE, rightPin: FALSE]]];
ENDLOOP;
Append1HorTileType[context, context.table.size-1, RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noUpPoly: TRUE, noRightMetal: TRUE, rightPin: FALSE]]];
};
};
};
-- spinList from top to bottom
SmallTileRec: PROC[context: Context, posNb: PosNb, expr: AlpsBool.Expression, norm: BOOLTRUE] RETURNS [nb: INT] = {
Add: PROC [i: HorTileType, tile: Tile, nb: INT] = {
THROUGH [1..nb] DO Append1HorTileType[context, posNb, i, tile] ENDLOOP;
};
IF expr.varNb>posNb THEN ERROR;
IF expr.varNb=posNb OR expr.varNb=0 THEN {
norm ← norm=expr.norm;
SELECT expr.case FROM
case11   => {
nb ← 1;
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: norm, low: ~norm, leftPin: FALSE]], nb]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: ~norm, low: norm]], nb];
};
case10    => {
nb ← 1;
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: ~norm, low: norm, leftPin: FALSE]], nb]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: norm, low: ~norm]], nb];
};
caseX1  => {
nb ← SmallTileRec[context, posNb-1, expr.subexpr1, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: norm, low: ~norm]], nb]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: ~norm, low: norm]], nb];
};
caseX0  => {
nb ← SmallTileRec[context, posNb-1, expr.subexpr1, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: ~norm, low: norm]], nb]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: norm, low: ~norm]], nb];
};
case1X  => {
nb ← SmallTileRec[context, posNb-1, expr.subexpr2, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: ~norm, low: norm]], nb]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: norm, low: ~norm]], nb];
};
case0X  => {
nb ← SmallTileRec[context, posNb-1, expr.subexpr2, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: norm, low: ~norm]], nb]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: ~norm, low: norm]], nb];
};
caseXNotX, caseXY  => {
nb1: INT ← SmallTileRec[context, posNb-1, expr.subexpr1, norm];
nb2: INT ← SmallTileRec[context, posNb-1, IF expr.case=caseXY THEN expr.subexpr2 ELSE AlpsBool.Not[expr.subexpr1], norm];
we have laid out first the subexpr1 then subexpr2, let's do the same thing for the muxes
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: TRUE, low: TRUE]], nb1]; Add[RightInput, TILE[[input: TRUE]], nb1];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE]], nb2]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: TRUE, low: TRUE]], nb2];
nb ← nb1+nb2;
};
ENDCASE  => ERROR;
}
ELSE {
nb ← SmallTileRec[context, posNb-1, expr, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE]], nb]; Add[RightInput, TILE[[input: TRUE]], nb];
};
IF posNb#context.table.size-1 THEN {
We can always add Glue, the low-level will intercept it if there is no glue
Add[VddGlue, TILE[[special: TRUE, name: "CascodeVddGlue"]], nb];
Add[GndGlue, TILE[[special: TRUE, name: "CascodeGndGlue"]], nb]
};
};
coaxes are from top to bottom iff reverse is FALSE
TileArrayAddRec: PROC [context: Context, posNb: PosNb, coaxes: LIST OF Coax] =
BEGIN
newCoaxes: LIST OF Coax ← NIL; -- copy of coaxes after sharing
nextCoaxes: LIST OF Coax ← NIL;
theseTiles: ARRAY HorTileType OF LIST OF Tile ← ALL[NIL];
Careful, Add constructs them from top to bottom
Add: PROC [i: HorTileType, tile: Tile] = {
IF i=VddGlue AND ~tile.layoutFlags[special] THEN ERROR;
theseTiles[i] ← CONS [tile, theseTiles[i]];
};
AddNil: PROC [i: HorTileType] = {Add[i, NilTile[i]]};
AddCoax: PROC [fatherCoax: Coax, expr: AlpsBool.Expression, spin: BOOL] = {
nextCoaxes ← CONS[NEW[CoaxRec ← [expr: expr, spin: spin, ancesters: CONS[fatherCoax.expr, fatherCoax.ancesters]]], nextCoaxes];
};
IF coaxes=NIL THEN RETURN;
RightRoute sharing of neighbours
WHILE coaxes#NIL DO
dupl: BOOL ← coaxes.first.expr.varNb=posNb AND (coaxes.first.expr.case=caseXNotX OR coaxes.first.expr.case=caseXY);
IF coaxes.rest#NIL AND Sharable[context, coaxes.first, coaxes.rest.first] THEN {
newAncesters: LIST OF AlpsBool.Expression ← NIL;
We know those 2 wires have a common ancester, we wipe off all the generations between the start and this common ancester (included)
MakeShared: PROC [ancesters1, ancesters2: LIST OF AlpsBool.Expression] RETURNS [newAncesters: LIST OF AlpsBool.Expression ← NIL] = {
WHILE ancesters1#NIL DO
WHILE ancesters2#NIL DO
IF ancesters1=ancesters2 THEN RETURN[ancesters2.rest];
ancesters2 ← ancesters2.rest;
ENDLOOP;
ancesters1 ← ancesters1.rest;
ENDLOOP;
};
lastSharable: Coax ← NIL; -- the last Coax (the only one which will result in a Coax after RightRoute). This is necessary, so that every other Coax can take its spin.
firstSpin: BOOL; -- This spin is necessary in case of a dupl
FOR auxCoaxes: LIST OF Coax ← coaxes, auxCoaxes.rest DO
IF auxCoaxes.rest=NIL OR ~Sharable[context, auxCoaxes.first, auxCoaxes.rest.first] THEN {lastSharable ← auxCoaxes.first; EXIT};
ENDLOOP;
newAncesters ← lastSharable.ancesters;
The first one
firstSpin ← Spin[context, coaxes.first, lastSharable];
Add[RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noUpPoly: TRUE, noLeftMetal: ~dupl, spin: firstSpin, leftPin: dupl]]];
newAncesters ← MakeShared[newAncesters, coaxes.first.ancesters];
Output["@", Convert.RopeFromInt[AlpsBool.NbOfCaseXY[context.table, coaxes.first.expr]], "@"];
coaxes ← coaxes.rest;
The intermediate ones
WHILE coaxes#NIL AND coaxes.first#lastSharable DO
Add[RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noLeftMetal: TRUE, spin: Spin[context, coaxes.first, lastSharable], leftPin: FALSE]]];
newAncesters ← MakeShared[newAncesters, coaxes.first.ancesters];
Output["@", Convert.RopeFromInt[AlpsBool.NbOfCaseXY[context.table, coaxes.first.expr]], "@"];
coaxes ← coaxes.rest;
ENDLOOP;
The last one
Add[RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noDownPoly: TRUE, spin: TRUE]]];
IF dupl THEN newCoaxes ← CONS[NEW[CoaxRec ← [expr: coaxes.first.expr, spin: firstSpin, duplLeftInput: FALSE, ancesters: newAncesters]], newCoaxes];
newCoaxes ← CONS[NEW[CoaxRec ← [expr: coaxes.first.expr, spin: coaxes.first.spin, ancesters: newAncesters]], newCoaxes];
} ELSE {
IF dupl THEN {
Add[RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noUpPoly: TRUE, noRightMetal: TRUE, spin: TRUE, rightPin: FALSE]]];
Add[RightRoute, TILE[[route: TRUE, contactPoly: TRUE, noDownPoly: TRUE, spin: TRUE]]];
newCoaxes ← CONS[NEW[CoaxRec ← [expr: coaxes.first.expr, spin: coaxes.first.spin, duplLeftInput: FALSE, ancesters: coaxes.first.ancesters]], newCoaxes];
} ELSE {
Add[RightRoute, TILE[[route: TRUE, noUpPoly: TRUE, noDownPoly: TRUE]]];
};
newCoaxes ← CONS[coaxes.first, newCoaxes];
};
coaxes ← coaxes.rest;
ENDLOOP;
FOR theseCoaxes: LIST OF Coax ← ReverseCoaxes[newCoaxes], theseCoaxes.rest WHILE theseCoaxes#NIL DO
expr: AlpsBool.Expression ← theseCoaxes.first.expr;
norm: BOOL ← theseCoaxes.first.spin;
duplLeftInput: BOOL ← theseCoaxes.first.duplLeftInput;
Output[AlpsBool.RopeFromExpression[context.table, expr], " "];
IF expr.varNb>posNb THEN ERROR;
IF expr.varNb=posNb OR expr.varNb=0 THEN {
norm ← norm=expr.norm;
SELECT expr.case FROM
case11   => {
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: norm, low: ~norm, leftPin: FALSE]]]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: ~norm, low: norm]]];
};
case10    => {
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: ~norm, low: norm, leftPin: FALSE]]]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: norm, low: ~norm]]];
};
caseX1  => {
AddCoax[theseCoaxes.first, expr.subexpr1, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: norm, low: ~norm]]]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: ~norm, low: norm]]];
};
caseX0  => {
AddCoax[theseCoaxes.first, expr.subexpr1, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: ~norm, low: norm]]]; Add[RightInput, TILE[[input: TRUE, gndTrans: TRUE, high: norm, low: ~norm]]];
};
case1X  => {
AddCoax[theseCoaxes.first, expr.subexpr2, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: ~norm, low: norm]]]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: norm, low: ~norm]]];
};
case0X  => {
AddCoax[theseCoaxes.first, expr.subexpr2, norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, gndTrans: TRUE, high: norm, low: ~norm]]]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: ~norm, low: norm]]];
};
caseXNotX, caseXY  => {
IF duplLeftInput THEN {
AddCoax[theseCoaxes.first, AlpsBool.WhenTrue[expr], norm];
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE, throughTrans: TRUE, high: TRUE, low: TRUE]]]; Add[RightInput, TILE[[input: TRUE]]];
} ELSE {
AddCoax[theseCoaxes.first, AlpsBool.WhenFalse[expr], norm]; --
Add[LeftInput, TILE[[input: TRUE, leftSide: TRUE]]]; Add[RightInput, TILE[[input: TRUE, throughTrans: TRUE, high: TRUE, low: TRUE]]];
};
};
ENDCASE  => ERROR;
Output["--**--"];
}
ELSE
BEGIN
AddNil[LeftInput]; AddNil[RightInput];
AddCoax[theseCoaxes.first, expr, norm];
Output["--XX--"];
END;
ENDLOOP;
from bottom to top
FOR coaxes: LIST OF Coax ← nextCoaxes, coaxes.rest WHILE coaxes#NIL DO
We can always add Glue, the low-level will intercept it if there is no glue
Append1HorTileType[context, posNb-1, VddGlue, TILE[[special: TRUE, name: "CascodeVddGlue"]]];
Append1HorTileType[context, posNb-1, GndGlue, TILE[[special: TRUE, name: "CascodeGndGlue"]]]
ENDLOOP;
theseTiles are from bottom to top
FOR i: HorTileType IN HorTileType DO Append[context, posNb, i, theseTiles[i]] ENDLOOP;
TileArrayAddRec[context, posNb-1, ReverseCoaxes[nextCoaxes]];
END;
FindNextGlue: PROC [context: Context, expr: AlpsBool.Expression, posNb: PosNb, distanceSinceLastGlue: INT] RETURNS [nextGluePos: PosNb] = {
IF expr=AlpsBool.true OR expr=AlpsBool.false OR posNb=0 THEN RETURN[0];
IF context.columnsExistance[posNb][VddGlue] THEN distanceSinceLastGlue ← 0;
IF expr.varNb<posNb THEN RETURN[FindNextGlue[context, expr, posNb-1, distanceSinceLastGlue]];
IF expr.varNb#posNb THEN ERROR;
IF distanceSinceLastGlue>=context.distanceBetweenGlue THEN RETURN[expr.varNb];
nextGluePos ← SELECT expr.case FROM
case10        => 0,
caseX1, caseX0, caseXNotX  => FindNextGlue[context, expr.subexpr1, posNb-1, distanceSinceLastGlue+1],
case1X, case0X     => FindNextGlue[context, expr.subexpr2, posNb-1, distanceSinceLastGlue+1],
caseXY       => MAX[FindNextGlue[context, expr.subexpr1, posNb-1, distanceSinceLastGlue+1], FindNextGlue[context, expr.subexpr2, posNb-1, distanceSinceLastGlue+1]]
ENDCASE  => ERROR;
};
-- Interface procs
TableAndPositionToTileArray: PUBLIC PROC [context: Context] = {
Type used for done array
SequenceOfBool: TYPE = RECORD [
contents: PACKED SEQUENCE size: AlpsBool.VarNb OF BOOL];
lastGluePos: PosNb ← context.table.size; -- last context.position where there is glue
Compute context.isLatched
FOR outs: LIST OF AlpsBool.OutputRef ← context.table.outputs, outs.rest WHILE outs#NIL DO
IF outs.first.type=latch OR outs.first.type=aux THEN context.isLatched ← TRUE;
ENDLOOP;
Creating the TileArray sequence
context.tileArray ← NEW [TileArrayRec[context.table.size+1]];
FOR i: PosNb IN [0..context.table.size] DO context.tileArray[i] ← ALL [NIL]; ENDLOOP;
Finding which columns are really useful
context.columnsExistance ← NEW[SequenceOfExistance[context.table.size]];
FOR i: PosNb IN [0..context.table.size) DO
context.columnsExistance[i] ← [TRUE, TRUE, TRUE, FALSE, FALSE];
ENDLOOP;
context.columnsExistance[context.table.size-1][VddGlue] ← TRUE;
We compute where we must have VddGlue and GndGlue for gluing expressions
IF context.debug THEN Output["Computing glue\n"];
DO
nextGluePos: PosNb ← 0;
FOR outs: LIST OF AlpsBool.OutputRef ← context.table.outputs, outs.rest WHILE outs#NIL DO
expr: AlpsBool.Expression = outs.first.expr;
nextGluePos ← MAX [nextGluePos, FindNextGlue[context, expr, expr.varNb, 0]];
ENDLOOP;
IF nextGluePos=0 THEN EXIT;
IF context.debug THEN Output["Gluing at pos: ", Convert.RopeFromInt[nextGluePos], "\n"];
context.columnsExistance[nextGluePos][VddGlue] ← TRUE;
context.columnsExistance[nextGluePos][GndGlue] ← TRUE;
lastGluePos ← nextGluePos;
ENDLOOP;
Output["Glue Computed\n"];
Allocation each VarNb
FOR outs: LIST OF AlpsBool.OutputRef ← context.table.outputs, outs.rest WHILE outs#NIL DO
SELECT outs.first.type FROM
output => {
Output["O"];
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: IF context.isLatched THEN "LatchSimple" ELSE "CascodeVddGlue"]]];
ExprToTiles[context, outs.first.expr];
};
latch  => {
fedBackInput: AlpsBool.VarNb ← outs.first.fedBackInput;
Output["L"];
Append1HorTileType[context, fedBackInput, LeftInput, TILE[[input: TRUE, leftSide: TRUE, contact: TRUE, low: TRUE, leftPin: FALSE]]]; Append1HorTileType[context, fedBackInput, RightInput, TILE[[input: TRUE, contact: TRUE, high: TRUE]]]; Append1HorTileType[context, fedBackInput, RightRoute, NilTile[RightRoute]];
FOR pos: PosNb IN [fedBackInput+1 .. context.table.size) DO
Append1HorTileType[context, pos-1, VddGlue, NilTile[VddGlue]]; Append1HorTileType[context, pos-1, GndGlue, NilTile[GndGlue]];
FOR i: HorTileType IN [LeftInput .. RightRoute] DO
Append1HorTileType[context, pos, i, NilTile[i]];
ENDLOOP;
ENDLOOP;
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: "LatchSend"]]];
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: "LatchReceive"]]];
ExprToTiles[context, outs.first.expr];
};
aux  => {
fedBackInput: AlpsBool.VarNb ← outs.first.fedBackInput;
Output["A"];
Append1HorTileType[context, fedBackInput, LeftInput, TILE[[input: TRUE, leftSide: TRUE, contact: TRUE, low: TRUE, leftPin: FALSE]]]; Append1HorTileType[context, fedBackInput, RightInput, TILE[[input: TRUE, contact: TRUE, high: TRUE]]]; Append1HorTileType[context, fedBackInput, RightRoute, NilTile[RightRoute]];
FOR pos: PosNb IN [fedBackInput+1 .. context.table.size) DO
Append1HorTileType[context, pos-1, VddGlue, NilTile[VddGlue]]; Append1HorTileType[context, pos-1, GndGlue, NilTile[GndGlue]];
FOR i: HorTileType IN [LeftInput .. RightRoute] DO
Append1HorTileType[context, pos, i, NilTile[i]];
ENDLOOP;
ENDLOOP;
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: "AuxSend"]]];
Append1HorTileType[context, context.table.size-1, VddGlue, TILE[[special: TRUE, name: "AuxReceive"]]];
ExprToTiles[context, outs.first.expr];
};
ENDCASE => ERROR;
ENDLOOP;
};
Global variable used to share same tiles
tiles: LIST OF Tile ← NIL;
END.