OnionCoreImpl.mesa 
Copyright Ó 1985, 1986, 1987 by Xerox Corporation. All rights reversed.
Created by Bertrand Serlet, February 10, 1986 9:31:47 pm PST
Bertrand Serlet, February 10, 1987 4:45:08 pm PST
DIRECTORY
CD, CDBasics, CDCells, CDRects, CDSimpleRules,
CMosB, CMosBObjects,
HashTable, IO,
OnionCore,
TerminalIO;
OnionCoreImpl: CEDAR PROGRAM
IMPORTS CD, CDBasics, CDCells, CDRects, CDSimpleRules, CMosB, CMosBObjects, HashTable, IO, TerminalIO
EXPORTS OnionCore =
BEGIN OPEN OnionCore;
Arcs
-- The projection of the point according to side is assumed to intersect the "ring" defined by the segment
PointInSeg: PROC [point: INT, thisSide: Side, seg: Seg, rect: CD.Rect] RETURNS [in: BOOLFALSE] = {
IsInThisBit: EachSegBitProc = {in ← in OR (side=thisSide AND min<=point AND point<=max)};
SegEnumerateSegBits[seg, rect, IsInThisBit];
};
SegLength: PROC [seg: Seg, rect: CD.Rect] RETURNS [length: INT 𡤀] = {
LengthSegBit: EachSegBitProc = {IF min>max THEN ERROR; length ← length + max - min};
SegEnumerateSegBits[seg, rect, LengthSegBit];
};
SegIntersect: PROC [seg1, seg2: Seg, rect: CD.Rect] RETURNS [intersect: BOOL] = {
intersect ← PointInSeg[seg1.point1, seg1.side1, seg2, rect] OR PointInSeg[seg2.point1, seg2.side1, seg1, rect];
};
Extends the segment after point2
SegExtent: PROC [seg: Seg, rect: CD.Rect, dist: INT] RETURNS [newSeg: Seg] = {
newPoint2: INT ← seg.point2;
newSide2: Side ← seg.side2;
SELECT seg.side2 FROM
bottom => IF newPoint2+dist<=rect.x2
THEN newPoint2 ← newPoint2+dist
ELSE {newPoint2 ← rect.y1+dist; newSide2 ← right};
right  => IF newPoint2+dist<=rect.y2
THEN newPoint2 ← newPoint2+dist
ELSE {newPoint2 ← rect.x2-dist; newSide2 ← top};
top  => IF newPoint2-dist>=rect.x1
THEN newPoint2 ← newPoint2-dist
ELSE {newPoint2 ← rect.y2-dist; newSide2 ← left};
left  => IF newPoint2-dist>=rect.y1
THEN newPoint2 ← newPoint2-dist
ELSE {newPoint2 ← rect.x1+dist; newSide2 ← bottom};
ENDCASE => ERROR;
newSeg ← NEW[SegRec ← [point1: seg.point1, side1: seg.side1, point2: newPoint2, side2: newSide2]];
};
SegEnumerateSegBits: PROC [seg: Seg, rect: CD.Rect, eachSegBit: EachSegBitProc] = {
point: INT ← seg.point1; side: Side ← seg.side1;
WHILE side#seg.side2 OR (SELECT side FROM bottom, right => seg.point2<point, top, left => seg.point2>point, ENDCASE => ERROR) DO
SELECT side FROM
bottom => {eachSegBit[point, rect.x2, bottom]; point ← rect.y1; side ← right};
right   => {eachSegBit[point, rect.y2, right]; point ← rect.x2; side ← top};
top  => {eachSegBit[rect.x1, point, top]; point ← rect.y2; side ← left};
left   => {eachSegBit[rect.y1, point, left]; point ← rect.x1; side ← bottom};
ENDCASE => ERROR;
ENDLOOP;
eachSegBit[MIN[point, seg.point2], MAX[point, seg.point2], side];
};
EmptyArc: PUBLIC PROC [rect: CD.Rect] RETURNS [arc: Arc] = {
arc ← NEW [ArcRec ← [rect: rect, segs: NIL]];
};
Length: PUBLIC PROC [arc: Arc] RETURNS [length: INT ← 0] = {
FOR segs: LIST OF Seg ← arc.segs, segs.rest WHILE segs#NIL DO
length ← length + SegLength[segs.first, arc.rect];
ENDLOOP;
};
Positive: PROC [side: Side] RETURNS [positive: BOOL] = {
positive ← SELECT side FROM
bottom, right  => TRUE,
left, top    => FALSE,
ENDCASE   => ERROR;
};
ConnectSegBitToArc: PUBLIC PROC [min, max: INT, side: Side, arc: Arc] RETURNS [connection: Arc] = {
rect: CD.Rect ← arc.rect;
segs: LIST OF Seg ← NIL;
seg: Seg;
Extend rect according to point
SELECT side FROM
bottom, top => {rect.x1 ← MIN[rect.x1, min]; rect.x2 ← MAX[rect.x2, max]};
right, left => {rect.y1 ← MIN[rect.y1, min]; rect.y2 ← MAX[rect.y2, max]};
ENDCASE  => ERROR;
IF ~Positive[side] THEN {w: INT ← min; min ← max; max ← w};
Test whether segs is empty
IF arc.segs=NIL THEN
seg ← NEW [SegRec ← [point1: min, point2: max, side1: side, side2: side]]
ELSE {
IF arc.segs.rest#NIL THEN ERROR;
seg ← arc.segs.first;
SELECT TRUE FROM
PointInSeg[min, side, seg, rect] AND PointInSeg[max, side, seg, rect]  => {};
PointInSeg[min, side, seg, rect]            =>
seg ← NEW[SegRec ← [point1: seg.point1, side1: seg.side1, point2: max, side2: side]];
PointInSeg[max, side, seg, rect]            =>
seg ← NEW[SegRec ← [point1: min, side1: side, point2: seg.point2, side2: seg.side2]];
ENDCASE                   => {
Estimates for each seg the price of extending the seg to point in both directions
possibleSeg1: Seg ← NEW[SegRec ← [point1: seg.point1, point2: max, side1: seg.side1, side2: side]];
possibleSeg2: Seg ← NEW[SegRec ← [point1: min, point2: seg.point2, side1: side, side2: seg.side2]];
seg ← IF SegLength[possibleSeg1, rect] < SegLength[possibleSeg2, rect] THEN possibleSeg1 ELSE possibleSeg2;
};
};
connection ← NEW [ArcRec ← [rect: rect, segs: LIST [seg]]];
RETURN;
};
The 2 arcs can be of different sizes
NotOverlapping: PUBLIC PROC [arc1, arc2: Arc, minDist: INT] RETURNS [notOverlapping: BOOLTRUE] = {
rect: CD.Rect ← CDBasics.Surround[arc1.rect, arc2.rect];
FOR segs1: LIST OF Seg ← arc1.segs, segs1.rest WHILE segs1#NIL DO
extSeg1: Seg ← SegExtent[segs1.first, rect, minDist];
FOR segs2: LIST OF Seg ← arc2.segs, segs2.rest WHILE segs2#NIL DO
IF SegIntersect[extSeg1, SegExtent[segs2.first, rect, minDist], rect] THEN {
RETURN[FALSE];
};
ENDLOOP;
ENDLOOP;
};
The union is positionned to fit on the largest rect.
Union: PUBLIC PROC [arc1, arc2: Arc] RETURNS [union: Arc] = {
rect: CD.Rect ← CDBasics.Surround[arc1.rect, arc2.rect];
segs: LIST OF Seg ← arc2.segs;
FOR segs1: LIST OF Seg ← arc1.segs, segs1.rest WHILE segs1#NIL DO
segs ← CONS[segs1.first, segs];
ENDLOOP;
union ← NEW[ArcRec ← [rect: rect, segs: segs]];
};
EnumerateSegBits: PUBLIC PROC [arc: Arc, eachSegBit: EachSegBitProc] = {
FOR segs: LIST OF Seg ← arc.segs, segs.rest WHILE segs#NIL DO
SegEnumerateSegBits[segs.first, arc.rect, eachSegBit];
ENDLOOP;
};
Parametrization of the layout
Returns the innerPos needed for centering the inner in the outer
Center: PUBLIC PROC [inner, outer: Object] RETURNS [innerPos: CD.Position] = {
innerPos ← CDBasics.SubPoints[
CDBasics.SizeOfRect[CD.InterestRect[outer]],
CDBasics.SizeOfRect[CD.InterestRect[inner]]];
innerPos.x ← innerPos.x/2; innerPos.y ← innerPos.y/2;
};
Geometric utilities
SegToMinMax: PROC [seg: Seg] RETURNS [min, max: INT] = {
min ← seg.point1;
max ← seg.point2;
IF seg.side1#seg.side2 THEN ERROR;
SELECT seg.side1 FROM
top, left    => {w: INT ← min; min ← max; max ← w};
bottom, right  => {};
ENDCASE   => ERROR;
IF min>=max THEN ERROR;
};
OppositeSide: PROC [side: Side] RETURNS [Side] = {
RETURN [SELECT side FROM
bottom => top,
right  => left,
top  => bottom,
left  => right,
ENDCASE => ERROR];
};
RotateSide: PROC [side: Side] RETURNS [Side] = {
RETURN [SELECT side FROM
bottom => right,
right  => top,
top  => left,
left  => bottom,
ENDCASE => ERROR];
};
IncludeRadialOb: PROC [outer: Object, seg: Seg, innerRect, outerRect: CD.Rect, ob: Object] = {
position: CD.Position = SELECT seg.side1 FROM
left  => [outerRect.x1, seg.point2],
right  => [innerRect.x2, seg.point1],
bottom => [seg.point1, outerRect.y1],
top  => [seg.point2, innerRect.y2],
ENDCASE => ERROR;
orientation: CD.Orientation = SELECT seg.side1 FROM
left, right  => rotate90,
bottom, top  => original,
ENDCASE => ERROR;
[] ← CDCells.IncludeOb[design: NIL, cell: outer, ob: ob, trans: [CDBasics.SubPoints[position, CDBasics.BaseOfRect[CDBasics.MapRect[CD.InterestRect[ob], [[0, 0], orientation]]]], orientation], mode: dontResize];
};
IncludeRadialWire: PROC [outer: Object, seg: Seg, innerRect, outerRect: CD.Rect, layer: CD.Layer] = {
width: INTSELECT seg.side1 FROM
bottom, right  => seg.point2-seg.point1,
top, left   => seg.point1-seg.point2,
ENDCASE   => ERROR;
length: INTSELECT seg.side1 FROM
left  => innerRect.x1-outerRect.x1,
right  => outerRect.x2-innerRect.x2,
bottom => innerRect.y1-outerRect.y1,
top  => outerRect.y2 - innerRect.y2,
ENDCASE => ERROR;
IF width<0 THEN ERROR;
IF length<0 THEN ERROR;
IF length#0 THEN IncludeRadialOb[outer, seg, innerRect, outerRect, CDRects.CreateRect[[width, length], layer]];
};
IncludeContact: PROC [outer: Object, seg: Seg, outerRect: CD.Rect, deep: INT, layer1, layer2: CD.Layer] = {
contactWidth: INTCD.InterestSize[CDSimpleRules.Contact[layer1, layer2]].x;
width: INTMAX [deep, contactWidth];
length: INTMAX [ABS [seg.point2 - seg.point1], contactWidth];
small: BOOL ← width<2*contactWidth AND length<2*contactWidth;
IncludeRadialOb[outer, seg, CDBasics.Extend[outerRect, - (IF small THEN contactWidth ELSE deep)], outerRect, IF small THEN CDSimpleRules.Contact[layer1, layer2] ELSE CMosBObjects.CreateLargeVia[[ABS [seg.point2 - seg.point1], deep]]]; -- Hack: is not technology independent
};
Faces: PROC [innerSeg, outerSeg: Seg] RETURNS [faces: BOOL] = {
IF innerSeg.side1#innerSeg.side2 THEN ERROR; -- pins should be on one side only
IF outerSeg.side1#outerSeg.side2 THEN ERROR; -- pins should be on one side only
faces ← innerSeg.side1=outerSeg.side1 AND innerSeg.point1=outerSeg.point1 AND innerSeg.point2=outerSeg.point2;
};
RoughlyFacesSomeNet: PROC [nets: HashTable.Table, net: Net, outerSeg: Seg, radialLayer, ringLayer: CD.Layer] RETURNS [faces: BOOLFALSE] = {
FindDifferentNetFacing: HashTable.EachPairAction = {
thisNet: Net ← NARROW [value];
IF thisNet.facing OR thisNet=net THEN RETURN;
quit ← RoughlyFacesInners[thisNet.innerSegs, outerSeg, radialLayer, ringLayer];
};
We look if a different net is facing
faces ← HashTable.Pairs[nets, FindDifferentNetFacing];
};
RoughlyFacesInners: PROC [innerSegs: LIST OF Seg, outerSeg: Seg, radialLayer, ringLayer: CD.Layer] RETURNS [faces: BOOLFALSE] = {
WHILE innerSegs#NIL DO
IF RoughlyFaces[innerSegs.first, outerSeg, radialLayer, ringLayer] THEN RETURN [TRUE];
innerSegs ← innerSegs.rest;
ENDLOOP;
};
-- Given two pins, checks if they faces each other, taking into account design rules
RoughlyFaces: PROC [innerSeg, outerSeg: Seg, radialLayer, ringLayer: CD.Layer] RETURNS [faces: BOOL] = {
contactWidth: INTCD.InterestSize[CDSimpleRules.Contact[radialLayer, ringLayer]].x;
minDist: INT ← CDSimpleRules.MinDist[ringLayer, ringLayer];
side: Side ← innerSeg.side1;
innerMin, innerMax, outerMin, outerMax: INT;
IF innerSeg.side1#innerSeg.side2 THEN ERROR; -- pins should be on one side only
IF outerSeg.side1#outerSeg.side2 THEN ERROR; -- pins should be on one side only
[innerMin, innerMax] ← SegToMinMax[innerSeg];
[outerMin, outerMax] ← SegToMinMax[outerSeg];
innerMax ← MAX [innerMax, innerMin + contactWidth] + minDist;
outerMax ← MAX [outerMax, outerMin + contactWidth] + minDist;
faces ← innerSeg.side1=outerSeg.side1 AND (innerMin IN [outerMin .. outerMax] OR outerMin IN [innerMin .. innerMax]);
};
Net level utilities
CopyNextInnerSegs: HashTable.EachPairAction = {
net: Net ← NARROW [value];
net.innerSegs ← net.newInnerSegs; net.newInnerSegs ← NIL; net.arc ← NIL; net.eval ← 0;
IF ~net.chosen THEN RETURN;
net.chosen ← FALSE; net.facing ← TRUE;
};
AllNetsFacing: PROC [nets: HashTable.Table] RETURNS [BOOLTRUE] = {
Fills the facing field of each Net, and returns TRUE if all Nets are facing.
ComputeFacing: HashTable.EachPairAction = {
net: Net ← NARROW [value];
allOuterPinsMatchSomeInnerPin: BOOLTRUE;
IF net.facing THEN RETURN;
FOR outerSegs: LIST OF Seg ← net.outerSegs, outerSegs.rest WHILE outerSegs#NIL DO
matches: BOOLFALSE;
FOR innerSegs: LIST OF Seg ← net.innerSegs, innerSegs.rest WHILE innerSegs#NIL DO
IF Faces[innerSegs.first, outerSegs.first] THEN {matches ← TRUE; EXIT};
ENDLOOP;
IF ~matches THEN {allOuterPinsMatchSomeInnerPin ← FALSE; EXIT};
ENDLOOP;
IF allOuterPinsMatchSomeInnerPin THEN {net.facing ← TRUE; RETURN};
};
NetFacing: HashTable.EachPairAction = {net: Net ← NARROW [value]; quit ← ~net.facing};
[] ← HashTable.Pairs[nets, ComputeFacing];
RETURN [~HashTable.Pairs[nets, NetFacing]];
};
The real one!
IncludeInOuter: PUBLIC PROC [outer: Object, nets: HashTable.Table, innerPos: CD.Position, innerSize, outerSize: CD.Position, radialLayer: CD.Layer ← CMosB.met, ringLayer: CD.Layer ← CMosB.met2] RETURNS [done: BOOL] = {
ExtendAllWires: HashTable.EachPairAction = {
net: Net ← NARROW [value];
FOR outerSegs: LIST OF Seg ← net.outerSegs, outerSegs.rest WHILE outerSegs#NIL DO
FOR innerSegs: LIST OF Seg ← net.innerSegs, innerSegs.rest WHILE innerSegs#NIL DO
IF Faces[innerSegs.first, outerSegs.first] THEN {
IncludeRadialWire[outer, innerSegs.first, CDBasics.RectAt[innerPos, innerSize], CDBasics.RectAt[[0, 0], outerSize], radialLayer];
EXIT;
};
ENDLOOP;
ENDLOOP;
};
Computation of the Arc of a Net
ComputeArc: HashTable.EachPairAction = {
net: Net ← NARROW [value];
ringWidth: INTIF net.width=0 THEN CDSimpleRules.MinWidth[ringLayer] ELSE net.width;
pitch: INT = MAX [contactWidth, ringWidth]+CDSimpleRules.MinDist[ringLayer, ringLayer];
net.arc ← EmptyArc[CDBasics.Extend[CDBasics.RectAt[innerPos, innerSize], pitch]];
FOR innerSegs: LIST OF Seg ← net.innerSegs, innerSegs.rest WHILE innerSegs#NIL DO
min, max: INT;
[min, max] ← SegToMinMax[innerSegs.first];
net.arc ← ConnectSegBitToArc[min, max, innerSegs.first.side1, net.arc];
ENDLOOP;
FOR outerSegs: LIST OF Seg ← net.outerSegs, outerSegs.rest WHILE outerSegs#NIL DO
min, max: INT;
[min, max] ← SegToMinMax[outerSegs.first];
SELECT outerSegs.first.side1 FROM
bottom, right  => max ← MAX[max, min+contactWidth];
top, left    => min ← MIN[min, max-contactWidth];
ENDCASE   => ERROR;
net.arc ← ConnectSegBitToArc[min, max, outerSegs.first.side1, net.arc];
ENDLOOP;
};
Computation of the evaluation function of a Net, i.e. LAST [INT]/2+Length if there is an innerPin roughly (less than design rules) in front of some outerPin of the net, LAST [INT] if all pins of the net are matching some pins of the same net, Length else. Length is Length[arc]+ Perimeter[Arc.rect].
ComputeEval: HashTable.EachPairAction = {
net: Net ← NARROW [value];
IF net.facing THEN {net.eval ← LAST [INT]; RETURN};
net.eval ← Length[net.arc] + net.width * 10 + net.arc.rect.x2 - net.arc.rect.x1 + net.arc.rect.y2 - net.arc.rect.y1;
FOR outerSegs: LIST OF Seg ← net.outerSegs, outerSegs.rest WHILE outerSegs#NIL DO
We look if a different net is facing
IF RoughlyFacesSomeNet[nets, net, outerSegs.first, radialLayer, ringLayer]
THEN {net.eval ← net.eval + LAST [INT] / (IF net.routeEveryOuterSeg THEN 2 ELSE 4); RETURN};
ENDLOOP;
};
Hack: PROC [cell: Object, obj: Object, position: CD.Position] = {
[] ← CDCells.IncludeOb[design: NIL, cell: cell, ob: obj, trans: [position], mode: dontResize];
};
DrawRingBit: EachSegBitProc = {
SELECT side FROM
bottom => Hack[outer, CDRects.CreateRect[[max-min, netRingWidth], ringLayer], [min, assignedArc.rect.y1]];
right  => Hack[outer, CDRects.CreateRect[[netRingWidth, max-min], ringLayer], [assignedArc.rect.x2-netRingWidth, min]];
top  => Hack[outer, CDRects.CreateRect[[max-min, netRingWidth], ringLayer], [min, assignedArc.rect.y2-netRingWidth]];
left  => Hack[outer, CDRects.CreateRect[[netRingWidth, max-min], ringLayer], [assignedArc.rect.x1, min]];
ENDCASE => ERROR;
};
DepositOuterContacts: HashTable.EachPairAction = {
DrawOuterPin: PROC [outerSeg: Seg] = {
Add a contact and a pin
IncludeContact[outer, outerSeg, assignedArc.rect, netRingWidth, radialLayer, ringLayer];
net.newInnerSegs ← CONS [outerSeg, net.newInnerSegs];
};
net: Net ← NARROW [value];
wrong: BOOLFALSE; nbOuterSegs, nbNonRoutedOuterSegs: INT ← 0;
IF ~net.chosen THEN {IF net.eval#LAST [INT] THEN TerminalIO.PutF["%g ", IO.rope[net.name]]; RETURN};
FOR outerSegs: LIST OF Seg ← net.outerSegs, outerSegs.rest WHILE outerSegs#NIL DO
nbOuterSegs ← nbOuterSegs+1;
IF RoughlyFacesSomeNet[nets, net, outerSegs.first, radialLayer, ringLayer]
THEN {nbNonRoutedOuterSegs ← nbNonRoutedOuterSegs + 1; IF net.routeEveryOuterSeg THEN wrong ← TRUE}
ELSE DrawOuterPin[outerSegs.first];
ENDLOOP;
IF wrong THEN TerminalIO.PutF["\n****** ROUTING IS WRONG for net %g: at least 2 different nets are facing each other. No cure possible until Dogleg is introduced in Onion!\n", IO.rope[net.name]];
IF nbNonRoutedOuterSegs#0 THEN TerminalIO.PutF["\n*** Warning for net %g: %g segments non routed out of %g segments. Check your result!\n", IO.rope[net.name], IO.int[nbNonRoutedOuterSegs], IO.int[nbOuterSegs]];
};
Draws wires in metal for inner pins, and if the pin belongs to the net, then add a contact, else add a pin.
DepositInnerWiresEtAl: HashTable.EachPairAction = {
DrawInnerPin: PROC [seg: Seg, chosen: BOOL] = {
IncludeRadialWire[outer, seg, CDBasics.RectAt[innerPos, innerSize], assignedArc.rect, radialLayer];
IF chosen
THEN -- add contact(s)
IncludeContact[outer, seg, assignedArc.rect, netRingWidth, radialLayer, ringLayer]
ELSE -- add a pin
net.newInnerSegs ← CONS [seg, net.newInnerSegs];
};
net: Net ← NARROW [value];
FOR innerSegs: LIST OF Seg ← net.innerSegs, innerSegs.rest WHILE innerSegs#NIL DO
DrawInnerPin[innerSegs.first, net.chosen];
ENDLOOP;
};
START
contactWidth: INTCD.InterestSize[CDSimpleRules.Contact[radialLayer, ringLayer]].x;
netRingWidth : INT ← 0; -- all nets on the same track have the same width
assignedArc: Arc ← NIL;
minEval: INTLAST [INT]; minNet: Net ← NIL; -- for choosing the first net
WHILE innerPos.x>=0 AND innerPos.y>=0 AND innerSize.x+innerPos.x<=outerSize.x AND innerSize.y+innerPos.y<=outerSize.y AND NOT AllNetsFacing[nets] DO
ChooseMinEval: HashTable.EachPairAction = {
net: Net ← NARROW [value];
IF net.facing OR net.eval>minEval OR net.eval=LAST [INT] THEN RETURN;
minEval ← net.eval; minNet ← net;
netRingWidth ← IF net.width=0 THEN CDSimpleRules.MinWidth[ringLayer] ELSE net.width;
assignedArc ← net.arc;
};
Length: PROC [list: LIST OF Seg] RETURNS [length: INT ← 0] = {
WHILE list#NIL DO length ← length+1; list ← list.rest ENDLOOP;
};
ChooseCompatibleOthers: HashTable.EachPairAction = {
net: Net ← NARROW [value];
ringWidth: INTIF net.width=0 THEN CDSimpleRules.MinWidth[ringLayer] ELSE net.width;
IF net.facing OR net.chosen OR net.eval>minEval OR net.eval=LAST [INT] THEN RETURN;
IF minNet#net AND (~CDBasics.Inside[net.arc.rect, assignedArc.rect] OR ~NotOverlapping[assignedArc, net.arc, CDSimpleRules.MinDist[ringLayer, ringLayer]+contactWidth] OR ringWidth#netRingWidth) THEN RETURN;
net.chosen ← TRUE; TerminalIO.PutF["Routing the net : %g innerPins: %g outerPins: %g Cost: %g\n", IO.rope[net.name], IO.int[Length[net.innerSegs]], IO.int[Length[net.outerSegs]], IO.int[net.eval]];
};
netRingWidth ← 0; assignedArc ← NIL; minEval ← LAST [INT]; minNet ← NIL;
-- We compute the Arc necessited by the net for being routed
[] ← HashTable.Pairs[nets, ComputeArc];
We compute evaluation function, i.e. LAST [INT]/2+Length[Arc] if there is an innerPin in front of some outerPin of the net, LAST [INT] if all pins of the net are matching some pins of the same net, Length[Arc] else.
[] ← HashTable.Pairs[nets, ComputeEval];
We choose the mininum of this evaluation function over each non-chosen net non intersecting (using the design rules) assignedArc and being inside assignedArc.rect (only if someNetAssigned), set assignedArc to the corresponding value, and set the chosen bit of the chosen net. We start again and again until no more net is found.
TerminalIO.PutF["Allocating a new track\n"];
[] ← HashTable.Pairs[nets, ChooseMinEval];
IF minEval=LAST [INT] THEN {
TerminalIO.PutF["*** Routing Impossible (Too big) ***\n*** Current state returned! ****\n"];
RETURN [FALSE];
};
[] ← HashTable.Pairs[nets, ChooseCompatibleOthers];
-- We now generate geometry
-- We shrink the assignedArc.rect if some sides are unused
IF NotOverlapping[assignedArc, NEW[ArcRec ← [rect: assignedArc.rect, segs: LIST [NEW[SegRec ← [assignedArc.rect.y2, assignedArc.rect.y1, left, left]]]]],
CDSimpleRules.MinDist[ringLayer, ringLayer]+contactWidth] THEN assignedArc.rect.x1 ← innerPos.x;
IF NotOverlapping[assignedArc, NEW[ArcRec ← [rect: assignedArc.rect, segs: LIST [NEW[SegRec ← [assignedArc.rect.y1, assignedArc.rect.y2, right, right]]]]], CDSimpleRules.MinDist[ringLayer, ringLayer]+contactWidth] THEN assignedArc.rect.x2 ← innerPos.x+innerSize.x;
IF NotOverlapping[assignedArc, NEW[ArcRec ← [rect: assignedArc.rect, segs: LIST [NEW[SegRec ← [assignedArc.rect.x1, assignedArc.rect.x2, bottom, bottom]]]]], CDSimpleRules.MinDist[ringLayer, ringLayer]+contactWidth] THEN assignedArc.rect.y1 ← innerPos.y;
IF NotOverlapping[assignedArc, NEW[ArcRec ← [rect: assignedArc.rect, segs: LIST [NEW[SegRec ← [assignedArc.rect.x2, assignedArc.rect.x1, top, top]]]]], CDSimpleRules.MinDist[ringLayer, ringLayer]+contactWidth] THEN assignedArc.rect.y2 ← innerPos.y+innerSize.y;
-- We place the sides of the routing (in metal2)
EnumerateSegBits[assignedArc, DrawRingBit];
-- We deposit contacts facing the outer pins which touch the routing ring. By the way we print the names of non-chosen nets
TerminalIO.PutF["Non routed nets: "];
[] ← HashTable.Pairs[nets, DepositOuterContacts];
TerminalIO.PutF["\n"];
-- We deposit wires in metal for inner pins and if the pin belongs to the net, then add a contact, else add a pin.
[] ← HashTable.Pairs[nets, DepositInnerWiresEtAl];
-- We affect parameters consequently
innerPos ← CDBasics.BaseOfRect[assignedArc.rect];
innerSize ← [assignedArc.rect.x2-assignedArc.rect.x1, assignedArc.rect.y2-assignedArc.rect.y1];
[] ← HashTable.Pairs[nets, CopyNextInnerSegs];
ENDLOOP;
IF innerPos.x<0 OR innerPos.y<0 OR innerSize.x+innerPos.x>outerSize.x OR innerSize.y+innerPos.y>outerSize.y THEN RETURN [FALSE];
Finished: now we extend all the wires
[] ← HashTable.Pairs[nets, ExtendAllWires];
RETURN [TRUE];
};
END.