MCDataPathMux.mesa,
Copyright c 1986 by Xerox Corporation. All rights reserved.
Don Curry November 10, 1987 1:05:28 pm PST
DIRECTORY CD, CDRects, CDSatellites, CDSimpleRules, CDTexts, CMosB, CMosBObjects, Core, CoreClasses, CoreGeometry, CoreOps, CoreProperties, CoreRoute, DataPath, IO, PW, PWCore, Rope, Sisyph, TerminalIO;
MCDataPathMux: CEDAR PROGRAM
IMPORTS CDRects, CDSatellites, CDSimpleRules, CDTexts, CMosB, CMosBObjects, CoreGeometry, CoreOps, CoreProperties, CoreRoute, DataPath, IO, PW, PWCore, Rope, Sisyph, TerminalIO =
BEGIN
Types and constants
Signal:   SIGNAL  = CODE;
MuxForm:  TYPE   = REF MuxFormRec;
MuxFormRec: TYPE   = RECORD[in, top, bot, ctl, out: Wire];
Wire:    TYPE   = Core.Wire;
Wires:    TYPE   = Core.Wires;
CellType:   TYPE   = Core.CellType;
muxFormProp: ATOM   ← $MCDataPathForm;
blank:    Wire   ← CoreOps.CreateWires[0, "Blank"];
textScale:  INT   ← 2;
font:   CDTexts.CDFont ← CDTexts.MakeFont["Xerox/TiogaFonts/Helvetica7", textScale];
dwText:  CD.Object   ← CDTexts.Create["driveWeak", font];
Vdd:   IO.ROPE  ← "Vdd";
Gnd:   IO.ROPE  ← "Gnd";
plus:   IO.ROPE  ← "+";
minus:  IO.ROPE  ← "-";
log:   IO.STREAM ← TerminalIO.TOS[];
lambda:  INT  ← CMosB.lambda;
topTail:  INT  ← 2* lambda;
botTail:  INT  ← 1* lambda;
cnctSize:   INT  ← 4* lambda;
layRules:  ATOM  ← $cmosB;
schDeco:  CoreGeometry.Decoration ← Sisyph.mode.decoration;
layDeco:  CoreGeometry.Decoration ← PWCore.extractMode.decoration;
Attribute and Layout procs
Heresy:
This Attribute procedure changes the source by giving names to unnamed publics. This is done so that names can be used to do the decorating. They also improve the legibility of the cellType when seen in the debugger or simulation. Other alternatives would be:
1. Write an extract proc for multiplexors (which would provide the names).
2. Write a variation of PWCore.DecorateValue that used some other property on the source public to do the binding.
3. Require that the designer always put valid names in the mux schematic.
I don't see any harm in providing the names here but I'm sure Bertrand would. He's not here though (heh heh).
MuxAttributes: PWCore.AttributesProc = {
OPEN CG: CoreGeometry;
spec:   DataPath.DPSpec     ← DataPath.NewCellTypeSpec[cellType];
data:  CoreClasses.RecordCellType ← NARROW[cellType.data];
wires:  Wires;
gnd:  Wire ← CoreOps.FindWire[cellType.public, "Gnd"];
vdd:  Wire ← CoreOps.FindWire[cellType.public, "Vdd"];
form:  MuxForm ← NEW[MuxFormRec];
char:  CHAR ← 'a;
EachSideWire:  CG.EachSortedPinProc = {wires ← CONS[wire, wires]};
EachChanWire: CG.EachSortedPinProc = { -- wire min max layer
count: INT ← 0;
chan: INT ← (DataPath.SchHalfBus[spec, (min+max)/2]-1)/2;
FOR ws: Wires ← wires, ws.rest WHILE ws#NIL DO count ← count+1 ENDLOOP;
FOR chanIndex: INT IN (count..chan] DO
wires ← CONS[blank, wires] ENDLOOP;
wires ← CONS[wire, wires]};
InsertGndVdd: PROC[orig: Wires] RETURNS[new: Wires ← NIL] = {
FOR index: INT ← 0, index + 1 DO
next: Wire;
IF MAX[spec.gndBus, spec.vddBus] < index AND orig=NIL THEN EXIT;
SELECT TRUE FROM
index = spec.gndBus => {next ← gnd;   IF gnd=NILTHEN ERROR};
index = spec.vddBus => {next ← vdd;   IF vdd=NILTHEN ERROR};
orig#NIL     => {next ← orig.first};
ENDCASE     => {next ← blank};
IF orig#NIL THEN
{IF next#orig.first AND orig.first#blank THEN ERROR; orig ← orig.rest};
new ← CONS[next, new]; ENDLOOP;
RETURN[CoreOps.Reverse[new]]};
Name: PROC[w: Wire, prefix: IO.ROPE, index: INT] = {
IF CoreOps.GetShortWireName[w].Length[]=0 THEN {
nm: IO.ROPEIO.PutFR["%g%g", IO.rope[prefix], IO.int[index]];
CheckForConflict: CoreOps.EachWireProc =
{IF nm.Equal[CoreOps.GetShortWireName[wire]] THEN ERROR};
[]𡤌oreOps.VisitWire[cellType.public, CheckForConflict];
[]𡤌oreOps.SetShortWireName[w, nm]}};
wires  ← NIL; []←CG.EnumerateSortedSides[schDeco, cellType, top,  EachChanWire];
form.top ← CoreOps.CreateWire[InsertGndVdd[ CoreOps.Reverse[wires]]];
wires  ← NIL; []←CG.EnumerateSortedSides[schDeco, cellType, bottom, EachChanWire];
form.bot ← CoreOps.CreateWire[InsertGndVdd[ CoreOps.Reverse[wires]]];
wires  ← NIL; []←CG.EnumerateSortedSides[schDeco, cellType, left,  EachSideWire];
form.ctl ← CoreOps.CreateWire[CoreOps.Reverse[wires]];
form.in ← CoreOps.CreateWires[form.ctl.size];
FOR child: NAT IN [0..data.size) DO
gate: Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "gate"]];
ch1: Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "ch1"]];
ch2: Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "ch2"]];
FOR index: INT IN [0..form.ctl.size) DO
IF form.ctl[index]#gate THEN LOOP;
IF form.in[index]#NIL     THEN Signal[]; form.in[index] ← ch1;
IF form.out#NIL AND form.out#ch2 THEN Signal[]; form.out ← ch2;
EXIT REPEAT FINISHED=> Signal[] ENDLOOP;
ENDLOOP;
FOR i: NAT IN [0..form.ctl.size) DO Name[form.ctl[i], "ctl", i] ENDLOOP;
FOR i: NAT IN [0..form.in.size)  DO Name[form.in[i], "in", i] ENDLOOP;
FOR i: NAT IN [0..form.top.size) DO Name[form.top[i], "top", i] ENDLOOP;
FOR i: NAT IN [0..form.bot.size) DO Name[form.bot[i], "bot", i] ENDLOOP;
Name[form.out, "out", 0];
CoreOps.FlushNameCaches[cellType.public];
CoreOps.FlushNameCaches[data.internal];
CoreProperties.PutCellTypeProp[cellType, muxFormProp, form]};
MuxLayout: PWCore.LayoutProc = {
spec:   DataPath.DPSpec     ← DataPath.NewCellTypeSpec[cellType];
data:   CoreClasses.RecordCellType ← NARROW[cellType.data];
f:    MuxForm ← NARROW[CoreProperties.GetCellTypeProp[cellType, muxFormProp]];
name:   IO.ROPE ← CoreOps.GetCellTypeName[cellType];
insts:   CD.InstanceList ← NIL;
cellWidth: INT   ← DataPath.BitWidth[spec];
xstrLgth:  INT   ← 8*lambda;
xstrWth:  INT   ← (4+4)*lambda;
xstrWthBig: INT   ← (4+8)*lambda;
tranBiasx:  INT   ← (xstrWth-spec.metW)/2;
tranBiasLtx: INT   ← tranBiasx + 4*lambda;
xstrHt:  INT   ← xstrLgth + 2*spec.difW;
pFrng:  INT   ← (spec.pwrW-spec.metW)/2;
topExtra:  INT   ← cnctSize/2 + topTail;
botExtra:  INT   ← cnctSize/2 + botTail;
cnctBiasx: INT   ← (cnctSize-spec.metW)/2;
viaPolSpace: INT   ← 3*cnctSize; -- actually 2+4+1+4+1 lambda
muxEvenDn: BOOL   = TRUE;
minTranUsd: BOOL   ← FALSE;
gnd:   INT   ← spec.gndBus;
vdd:   INT   ← spec.vddBus;
rangeXMax: INT   ← spec.buses+(spec.layDWidth - viaPolSpace)/spec.layBusW;
range:   CD.Position ← [MIN[rangeXMax, MAX[f.top.size, f.bot.size]+1], f.ctl.size];
pitch:   CD.Position ← [spec.metPitch, spec.met2Pitch];
Find and check outIndex
outIndex:  INT   ← WireIndexMax[f.top, f.out];
outIndexBot: INT   ← WireIndexMax[f.bot, f.out];
IF outIndex  # WireIndexMin[f.top, f.out] OR
outIndexBot  # WireIndexMin[f.bot, f.out] OR
outIndex#-1 AND outIndexBot#-1 AND outIndex#outIndexBot
THEN {log.PutF["*** Multiple column output\n"]; ERROR};
outIndex ← MAX[outIndex, outIndexBot];
IF f.out#blank AND WireIndexMax[f.in, f.out]#-1 THEN
{log.PutF["*** Output signal is also used as input\n"]; ERROR};
Vertical Metal
FOR i: INT IN [0..range.x) DO
loc:  CD.Position ← [i*pitch.x, 0];
topOut: BOOL ← f.out # blank AND IW[f.top, i] = f.out;
botOut: BOOL ← f.out # blank AND IW[f.bot, i] = f.out;
tY:   INTIF topOut
THEN WireNonBlankIndexMin[f.in] ELSE WireIndexMin[f.in, IW[f.top, i]];
bY:  INTIF botOut
THEN WireNonBlankIndexMax[f.in] ELSE WireIndexMax[f.in, IW[f.bot, i]];
tY ← tY  + ((tY + (IF topOut=muxEvenDn THEN 1 ELSE 2)) MOD 2);
bY ← bY  + ((bY + (IF botOut=muxEvenDn THEN 1 ELSE 2)) MOD 2);
IF tY=-1 AND bY=-1 THEN tY𡤋Y𡤀
IF ~(IW[f.top, i] = IW[f.bot, i]) AND tY<=bY AND IW[f.top, i]#blank AND IW[f.bot, i]#blank
THEN {log.PutF["*** 2 signals in same channel\n"]; ERROR};
IF IW[f.top, i]#blank THEN insts ← AddRetInst[
insts: insts, internal: data.internal, wire: f.top[i], level: CMosB.met,
size: [spec.metW, (range.y-tY) * pitch.y + topExtra ],
loc: [i*pitch.x,   tY  * pitch.y ]];
IF IW[f.bot, i]#blank THEN insts ← AddRetInst[
insts: insts, internal: data.internal, wire: f.bot[i], level: CMosB.met,
size: [spec.metW,    bY * pitch.y + botExtra ],
loc: [i*pitch.x,     0 * pitch.y - botExtra ]];
ENDLOOP;
IF gnd>-1 THEN {
gndWire: Wire ← CoreOps.FindWire[data.internal, "Gnd"];
insts ← AddRetInst[
insts: insts, internal: data.internal, wire: gndWire, level: CMosB.met,
size: [spec.pwrW, range.y * pitch.y + topExtra + botExtra ],
loc: [gnd*pitch.x-pFrng ,     - botExtra ]]};
IF vdd>-1 THEN {
vddWire: Wire ← CoreOps.FindWire[data.internal, "Vdd"];
insts ← AddRetInst[
insts: insts, internal: data.internal, wire: vddWire, level: CMosB.met,
size: [spec.pwrW, range.y * pitch.y + topExtra + botExtra ],
loc: [vdd*pitch.x-pFrng ,     - botExtra ]]};
BEGIN
xstr:  CD.Object ← CMosBObjects.CreateTransistor
[size: [xstrWth, xstrLgth], difLayer: CMosB.ndif];
xstrBig: CD.Object ← CMosBObjects.CreateTransistor
[size: [xstrWthBig, xstrLgth], difLayer: CMosB.ndif];
dcon:  CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.ndif];
pcon:  CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.pol];
vcon:  CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.met2];
scon:  CD.Object ← CMosBObjects.CreateDifCon[CMosB.pwellCont];
pvconn: CD.Object ← CDRects.CreateRect[[2*cnctSize, cnctSize], CMosB.met];
lstIONotGnd:  BOOL ← TRUE;
lstGndClear:  BOOL ← TRUE;
thsIONotGnd: BOOL ← TRUE;
thsGndClear:  BOOL ← TRUE;
FOR ctlIndex: INT IN [0..range.y) DO
Include: PROC[object: CD.Object, location: CD.Position] =
{insts ← CONS[ NEW[CD.InstanceRep ← [object, [location]]], insts]};
AddGndContact: PROC[updn: {up, dn}] = {IF updn=up
THEN Include[scon, [gnd*pitch.x-cnctBiasx, (ctlIndex+1)*pitch.y-cnctSize/2]]
ELSE Include[scon, [gnd*pitch.x-cnctBiasx, (ctlIndex+0)*pitch.y-cnctSize/2]]};
AddMux: PROC [index: CD.Position, lt, rt: BOOL] = {
dWL:  INT ← (ABS[outIndex-index.x])*pitch.x+cnctSize;
pWL:  INT ← (range.x-index.x)*pitch.x;
minX:  INT ← MIN[outIndex, index.x];
polX:  INT ← MIN[outIndex, index.x];
pol:  CD.Object ← CDRects.CreateRect[[pWL, spec.polW], CMosB.pol];
dif:  CD.Object ← CDRects.CreateRect[[dWL, spec.difW], CMosB.ndif];
dir:  INT ← IF ((index.y MOD 2)=0)=muxEvenDn THEN 1 ELSE -1;
yloc:  INT ← index.y*pitch.y + pitch.y/2;
Include[pcon, [range.x *pitch.x -cnctBiasx, yloc       -cnctSize/2 ]];
Include[pvconn, [range.x *pitch.x -cnctBiasx, yloc       -cnctSize/2 ]];
Include[vcon, [range.x *pitch.x -cnctBiasx+cnctSize+lambda, yloc -cnctSize/2 ]];
Include[pol,  [index.x *pitch.x -cnctBiasx, yloc       -spec.polW/2 ]];
Include[dif,  [minX  *pitch.x -cnctBiasx, yloc +dir*pitch.y/2  -spec.difW/2 ]];
Include[dcon, [outIndex *pitch.x -cnctBiasx, yloc +dir*pitch.y/2  -cnctSize/2 ]];
Include[dcon, [index.x *pitch.x -cnctBiasx, yloc -dir*pitch.y/2  -cnctSize/2 ]];
Include[dwText, [index.x *pitch.x -tranBiasx, yloc -lambda*textScale/2    ]];
SELECT TRUE FROM
lt   => Include[xstrBig, [index.x *pitch.x -tranBiasLtx, yloc -xstrLgth/2  ]];
rt   => Include[xstrBig, [index.x *pitch.x -tranBiasx, yloc -xstrLgth/2  ]];
ENDCASE => Include[xstr,  [index.x *pitch.x -tranBiasx, yloc -xstrLgth/2  ]];
CDSatellites.Associate[master: insts.first, text: insts.rest.first]};
size: CD.Position ← [DataPath.BitWidth[spec],  spec.met2W];
loc: CD.Position ← [spec.metW/2-spec.leftTail, ctlIndex*pitch.y+pitch.y/2-spec.met2W/2];
insts ← AddRetInst[insts: insts, internal: data.internal, wire: f.ctl[ctlIndex],
size:size, loc:loc, level: CMosB.met2];
IF f.out#blank
THEN {
ioIndex: INT ← IOIndex[ctlIndex, f];
IF ioIndex >=0 THEN {
First try to make the transistor larger
inDn:   BOOL ← ((ctlIndex MOD 2)=0)=muxEvenDn;
If inDn then there can be no clash above to making the transistor larger since that is the side of the output connection. In this case, ioIndexUp will get -1 even if the correcsponding control really does gate some input.
ioIndexUp: INTIF inDn THEN -1 ELSE IOIndex[ctlIndex+1, f];
ioIndexDn: INTIF ~inDn THEN -1 ELSE IOIndex[ctlIndex-1, f];
extLt:  BOOL ← ioIndex # (gnd+1) AND ioIndex # 0 AND
(ioIndexUp=-1 OR ioIndexUp#(ioIndex-1)) AND
(ioIndexDn=-1 OR ioIndexDn#(ioIndex-1));
extRt:  BOOL ← ioIndex # (gnd-1) AND ioIndex < (range.x-1) AND
(ioIndexUp=-1 OR ioIndexUp#(ioIndex+1)) AND
(ioIndexDn=-1 OR ioIndexDn#(ioIndex+1));
IF NOT(extLt OR extRt) THEN minTranUsd ← TRUE;
AddMux[[ioIndex, ctlIndex], extLt, extRt]};
thsIONotGnd ← ioIndex # gnd;
thsGndClear ← thsIONotGnd AND ((ioIndex<gnd)=(outIndex<gnd));
IF ((ctlIndex MOD 2)=0)=muxEvenDn
THEN {IF thsIONotGnd AND lstIONotGnd THEN AddGndContact[dn]}
ELSE {IF thsGndClear  AND lstGndClear THEN AddGndContact[dn]};
IF (ctlIndex+1) = range.y THEN IF ((ctlIndex MOD 2)=0)=muxEvenDn
THEN {IF thsGndClear        THEN AddGndContact[up]}
ELSE {IF thsIONotGnd       THEN AddGndContact[up]};
lstIONotGnd ← thsIONotGnd;
lstGndClear ← thsGndClear}
ELSE AddGndContact[dn];
ENDLOOP;
END;
obj ← PW.CreateCell[instances: insts, name: name, ir: [
x1: spec.metW/2-spec.leftTail,    y1: -botExtra,
x2: spec.metW/2-spec.leftTail+cellWidth, y2: range.y*pitch.y + topExtra]];
IF minTranUsd THEN TerminalIO.PutF["*** Using minimum transistor in mux\n"]};
Utilities
IOIndex: PROC[ctl: INT, form: MuxForm] RETURNS[ioIndex: INT] = {
IF ctl NOT IN[0..form.in.size) THEN RETURN[-1];
IF form.in[ctl]=blank THEN RETURN[-1];
ioIndex ← WireIndexMax[form.top, form.in[ctl]];
IF ioIndex > -1 THEN RETURN[ioIndex];
ioIndex ← WireIndexMax[form.bot, form.in[ctl]]};
IW: PROC[wire: Wire, index: INT] RETURNS[subwire: Wire] =
{RETURN[IF index IN [0..wire.size) THEN wire[index] ELSE blank]};
WireIndexMax: PROC[root, subWire: Wire] RETURNS[index: INT ← -1] =
{FOR i: INT DECREASING IN [0..root.size) DO IF root[i]=subWire THEN RETURN[i] ENDLOOP};
WireIndexMin: PROC[root, subWire: Wire] RETURNS[index: INT ← -1] =
{FOR i: INT IN [0..root.size) DO IF root[i]=subWire THEN RETURN[i] ENDLOOP};
WireNonBlankIndexMin: PUBLIC PROC [wire: Wire] RETURNS[index: INT] = {
FOR index IN [0..wire.size) DO
IF wire[index]#blank THEN RETURN[index] ENDLOOP;
RETURN[-1]};
WireNonBlankIndexMax: PUBLIC PROC [wire: Wire] RETURNS[index: INT] = {
FOR index DECREASING IN [0..wire.size) DO
IF wire[index]#blank THEN RETURN[index] ENDLOOP;
RETURN[-1]};
AddRetInst: PROC[insts: CD.InstanceList, internal, wire: Wire,
size: CD.Position, loc: CD.Position, level: CD.Layer]
RETURNS[CD.InstanceList] = {
name: IO.ROPE  ← CoreRoute.LabelInternal[internal, wire];
props: CD.PropList ← LIST[[$SignalName, name]];
IF size.x<0 OR size.y<0 THEN {
log.PutF["*** Strange rectangle size [%g, %g]\n", IO.int[size.x], IO.int[size.y] ];
Signal[]};
IF size.x=0 OR size.y=0 THEN RETURN[insts];
insts ← CONS[ NEW[CD.InstanceRep ← [
ob: CDRects.CreateRect[size, level],
trans: [loc],
properties: props ]],
insts];
RETURN[insts]};
Runtime
[] ← PWCore.RegisterLayoutAtom
[$MCDataPathMux, MuxLayout, PWCore.DecorateValue, MuxAttributes];
END.