<> <> <> <> <<>> DIRECTORY AlpsBool, AlpsTile, Convert, Rope, TerminalIO; AlpsTileImpl: CEDAR PROGRAM IMPORTS AlpsBool, Convert EXPORTS AlpsTile = BEGIN OPEN AlpsTile; <<>> <<-- Utilities>> ROPE: TYPE = Rope.ROPE; Output: PROC [t1, t2, t3, t4, t5: ROPE _ NIL] = 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; }; <> 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: BOOL _ TRUE] = { sameTile _ EqualTileRec[tile1^, tile2^] }; EqualTileRec: PUBLIC PROC [tileRec1, tileRec2: TileRec] RETURNS [sameTileRec: BOOL _ TRUE] = { IF tileRec1.special OR tileRec2.special THEN RETURN [tileRec1.name = tileRec2.name]; IF tileRec1.name#NIL OR tileRec2.name#NIL THEN ERROR; 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 _ tile.name#$NullVddGlue AND tile.name#$NullGndGlue AND tile.name#$LatchNull; tile.rightPin _ tile.name#$NullVddGlue AND tile.name#$NullGndGlue AND tile.name#$LatchNull AND tile.name#$LatchBetween AND 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: BOOL _ TRUE, -- the spin of the pair of wire. TRUE means value up, not value down duplLeftInput: BOOL _ TRUE, -- 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; }; <> 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: BOOL _ TRUE] 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]; <> 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 { <> Add[VddGlue, TILE[[special: TRUE, name: $CascodeVddGlue]], nb]; Add[GndGlue, TILE[[special: TRUE, name: $CascodeGndGlue]], nb] }; }; <> 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]; <> Add: PROC [i: HorTileType, tile: Tile] = { <> 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; <> 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; <> 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; <> 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; <> 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; <> 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; <> 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; <> } ELSE BEGIN AddNil[LeftInput]; AddNil[RightInput]; AddCoax[theseCoaxes.first, expr, norm]; <> END; ENDLOOP; <> FOR coaxes: LIST OF Coax _ nextCoaxes, coaxes.rest WHILE coaxes#NIL DO <> Append1HorTileType[context, posNb-1, VddGlue, TILE[[special: TRUE, name: $CascodeVddGlue]]]; Append1HorTileType[context, posNb-1, GndGlue, TILE[[special: TRUE, name: $CascodeGndGlue]]] ENDLOOP; <> 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=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] = { <> SequenceOfBool: TYPE = RECORD [ contents: PACKED SEQUENCE size: AlpsBool.VarNb OF BOOL]; lastGluePos: PosNb _ context.table.size; -- last context.position where there is glue <> 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; <<>> <> context.tileArray _ NEW [TileArrayRec[context.table.size+1]]; FOR i: PosNb IN [0..context.table.size] DO context.tileArray[i] _ ALL [NIL]; ENDLOOP; <<>> <> 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; <> 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"]; <<>> <> 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; <<>> }; <> tiles: LIST OF Tile _ NIL; <<>> END.