DIRECTORY Atom USING [GetPName], CD USING [backgroundLayer, commentLayer, CreateDrawRef, DrawProc, DrawContextProc, DrawRectProc, DrawRef, errorLayer, LayerKey, Number, Object, outlineLayer, Position, Rect, selectionLayer, shadeLayer, undefLayer], CDAtomicObjects USING [AtomicObsSpecific, DrawList], CDBasics USING [empty, NonEmpty], CDBasicsInline USING [MapRect], CDOps USING [LayerRope], CDProperties USING [GetObjectProp, PutObjectProp, RegisterProperty], CMosB USING [cut, cut2, lambda, met, met2, ndif, nwell, nwellCont, ovg, pdif, pol, pwell, pwellCont], CoreGeometry USING [CellInstance, EachInstanceProc, EnumerateGeometry, FlattenInstance, GetObject, InlineBBox, Instance, Instances, Object], CoreProperties USING [propPrint, PropPrintProc, Props, RegisterProperty, StoreProperties], CoreView USING [AddRectangle, debugViewer], CStitching USING [all, Area, ChangeEnumerateArea, ChangeRect, EEdge, EN, EnumerateArea, EnumerateNeighborhood, FindTile, IsEmpty, ListArea, NE, NEdge, NewTesselation, Rect, RectProc, Region, SEdge, SW, Tesselation, Tile, TileProc, TrustedDisposeTesselation, WEdge, WS], DesignRules USING [DesignRuleError, GetScaledValue, MaxWidth, MinSpace, MinWidth, Rules], Drc USING [AtomicWireHull, CellProc, CoreCell, MarkError, Rect, State, Tech, TechRec, Transf, Wire, WireInstance, WirePairProc, WireProc, WireSet], DrcCMOSB, DrcDebug USING [break, debug, dLog, pause, trace], DrcUtilities USING [Anathema, Bloat, Contains, CoreWireName, diffContactLayer, DoNotDrawContext, ignoreConnectivity, Intersecting, IntersectingOpen, Intersection, IsCut, IsDiffContact, IsLargeDiffContact, IsWell, Layer, LayerName, Normalize, PrintChecked, ROPE, SameLayer, SameRect, Size, Tess, WireName], IO USING [atom, card, int, PutF, PutFR, rope], Rope USING [Cat, Equal, ROPE], Saguaro USING [gate]; DrcCMOSBimpl: CEDAR PROGRAM IMPORTS Atom, CD, CDBasics, CDBasicsInline, CDOps, CDProperties, CMosB, CoreGeometry, CoreProperties, CoreView, CStitching, DesignRules, Drc, DrcDebug, DrcUtilities, IO, Rope, Saguaro EXPORTS DrcCMOSB SHARES Drc ~ BEGIN OPEN CMosB, Drc, DrcUtilities; cMosBsimpleKey: PUBLIC ATOM ~ CoreProperties.RegisterProperty [$simpleGenista]; cMosBcompleteKey: PUBLIC ATOM ~ CoreProperties.RegisterProperty [$completeGenista]; CdInsts: TYPE ~ CoreGeometry.Instances; CdObj: TYPE ~ CoreGeometry.Object; CoreInst: TYPE ~ CoreGeometry.CellInstance; FakeInst: TYPE ~ CoreGeometry.Instance; Region: TYPE ~ LIST OF REF CStitching.Region; Tile: TYPE ~ CStitching.Tile; empty: REF ~ NIL; nothing: REF INT ~ NEW [INT]; none: ATOM ~ NIL; universe: Rect ~ CStitching.all; rectClass: ATOM ~ $Rect; wellRectClass: ATOM ~ $WellRect; pinClass: ATOM ~ $PinOb0; markClass: ATOM ~ $AlignmentMarkOb; segmentClass: ATOM ~ $SymbolicSegment; cutKey: ATOM ~ CD.LayerKey [cut]; cut2Key: ATOM ~ CD.LayerKey [cut2]; genericDiff: ATOM ~ $diff; polyKey: ATOM ~ CD.LayerKey [pol]; gateKey: ATOM ~ CoreProperties.RegisterProperty [$gateGenista]; gate: Layer ~ Saguaro.gate; fieldOxide: REF ANY ~ NIL; notChannel: WireInstance ~ [NIL, NIL, [], NIL]; specialLayers: Layer ~ MAX [CD.shadeLayer, CD.errorLayer, CD.backgroundLayer, CD.outlineLayer, CD.selectionLayer, CD.commentLayer]; lambda: CD.Number ~ CMosB.lambda; cachedTech: RECORD [t: Tech _ NIL, tk: ATOM _ NIL]; CMosbTable: PUBLIC TYPE ~ REF CMosbTableRec; Rule: PUBLIC TYPE ~ RECORD [extent: CD.Number, msg: ROPE]; CMosbTableRec: PUBLIC TYPE ~ RECORD [ minWidth, maxWidth: ARRAY Layer OF Rule, separation: ARRAY Layer OF REF ARRAY Layer OF Rule, viaOnFieldOxideAvoidsDiff, viaOnFieldOxideAvoidsPoly, fieldOxideSurroundsViaOnFieldOxide, diffSurroundsViaOnDiff, polySurroundsViaOnPoly: Rule, viaOnPolyAndDiff, viaSeparation, viaOverGate, viaOverPoly: Rule, nWellSurround, pWellSurround, nWellContact, pWellContact, wellContactSpacing: Rule, wellConflict, NinN, PinP, isolatedWell: Rule, diffCutToGate, largeDiffCutToGate: Rule, difCutViaSpace, minPadSize: Rule]; NewTechnology: PUBLIC PROC [key: ATOM, rules: DesignRules.Rules] RETURNS [tech: Tech] ~ BEGIN rt: CMosbTable; toto: Rule; ComputeMaxSeparation: PROC [key: ATOM] RETURNS [max: CD.Number] ~ BEGIN sep: CD.Number; max _ 0; FOR s1: Layer IN Layer DO IF tech.illegalLayer[s1] THEN LOOP; FOR s2: Layer IN Layer DO IF tech.illegalLayer[s2] THEN LOOP; SELECT key FROM cMosBsimpleKey => NULL; -- all standard cMosBcompleteKey => IF (IsWell [s1] AND IsWell [s2]) THEN LOOP; ENDCASE => ERROR; sep _ DesignRules.MinSpace [rules, s1, s2 ! DesignRules.DesignRuleError => LOOP].s; max _ MAX [max, sep] ENDLOOP ENDLOOP END; -- ComputeMaxSeparation IF (key # cMosBsimpleKey) AND (key # cMosBcompleteKey) THEN RETURN [NIL]; IF (cachedTech.t # NIL) AND (key = cachedTech.t.checkedBy) AND (rules.id = cachedTech.tk) THEN BEGIN IF (key = cMosBcompleteKey) AND (cachedTech.t.verifyCell = NIL) THEN cachedTech.t.verifyCell _ VerifyWells; RETURN [cachedTech.t] END; tech _ NEW [TechRec]; tech.illegalLayer[ndif] _ tech.illegalLayer[pdif] _ tech.illegalLayer[nwell] _ tech.illegalLayer[pwellCont] _ tech.illegalLayer[nwellCont] _ tech.illegalLayer[pol] _ tech.illegalLayer[met] _ tech.illegalLayer[met2] _ tech.illegalLayer[cut] _ tech.illegalLayer[cut2] _ tech.illegalLayer[ovg] _ tech.illegalLayer[gate] _ FALSE; tech.lambda _ lambda; SELECT key FROM cMosBsimpleKey => BEGIN tech.checkedBy _ cMosBsimpleKey; tech.maxSeparation _ ComputeMaxSeparation [cMosBsimpleKey]; tech.ttMaxSep _ tech.ctMaxSep _ tech.maxSeparation; tech.verifyWire _ SimpleWidthCheck; tech.verifyWirePair _ SimpleMaterialSeparation END; cMosBcompleteKey => BEGIN tech.checkedBy _ cMosBcompleteKey; tech.maxSeparation _ ComputeMaxSeparation [cMosBcompleteKey]; tech.ttMaxSep _ tech.ctMaxSep _ tech.maxSeparation; -- fixed later tech.verifyWire _ FullWireCheck; tech.verifyWirePair _ CompleteSeparation; tech.verifyCell _ VerifyWells END; ENDCASE => ERROR; rt _ NEW [CMosbTableRec]; FOR i: Layer IN Layer DO rt.separation[i] _ NEW [ARRAY Layer OF Rule] ENDLOOP; FOR i: Layer IN Layer DO IF tech.illegalLayer[i] THEN LOOP; [toto.extent, toto.msg] _ DesignRules.MinWidth [rules, i ! DesignRules.DesignRuleError => LOOP]; rt.minWidth[i] _ toto; [toto.extent, toto.msg] _ DesignRules.MaxWidth [rules, i ! DesignRules.DesignRuleError => LOOP]; rt.maxWidth[i] _ toto; IF (rt.maxWidth[i].extent = 0) THEN rt.maxWidth[i].extent _ CD.Number.LAST / lambda; rt.separation[i] _ NEW [ARRAY Layer OF Rule]; FOR j: Layer IN [0 .. i] DO IF tech.illegalLayer[j] THEN LOOP; [toto.extent, toto.msg] _ DesignRules.MinSpace [rules, i, j ! DesignRules.DesignRuleError => LOOP]; rt.separation[i][j] _ rt.separation[j][i] _ toto ENDLOOP ENDLOOP; FOR i: Layer IN Layer DO IF tech.illegalLayer[i] THEN LOOP; rt.separation[i][gate] _ rt.separation[gate][i] _ rt.separation[pol][i] ENDLOOP; IF rt.separation[nwellCont][gate].extent = 0 THEN rt.separation[nwellCont][gate] _ rt.separation[pwellCont][gate] _ rt.separation[gate][nwellCont] _ rt.separation[gate][pwellCont] _ [3 * lambda, "VTI 6.5.2.3"]; rt.minWidth[gate] _ rt.minWidth[pol]; rt.maxWidth[gate] _ rt.maxWidth[pol]; rt.separation[nwell][nwell].msg _ "Well spacing or notch"; rt.minWidth[nwell].msg _ "Missing well (well width)"; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $DifViaSpace]; rt.viaOnFieldOxideAvoidsDiff _ toto; rt.viaOnFieldOxideAvoidsDiff.msg _ rt.viaOnFieldOxideAvoidsDiff.msg.Cat [" Separation to diff (advisory)"]; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $PolyViaSpace]; rt.viaOnFieldOxideAvoidsPoly _ toto; rt.viaOnFieldOxideAvoidsPoly.msg _ rt.viaOnFieldOxideAvoidsPoly.msg.Cat [" Separation to poly (advisory)"]; rt.fieldOxideSurroundsViaOnFieldOxide _ [MAX [rt.viaOnFieldOxideAvoidsDiff.extent, rt.viaOnFieldOxideAvoidsPoly.extent], "Separation to poly or diff (advisory)"]; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $DifViaSurround]; rt.diffSurroundsViaOnDiff _ toto; rt.diffSurroundsViaOnDiff.msg _ rt.diffSurroundsViaOnDiff.msg.Cat [" Insufficient diff surround (advisory)"]; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $PolyViaSurround]; rt.polySurroundsViaOnPoly _ toto; rt.polySurroundsViaOnPoly.msg _ rt.polySurroundsViaOnPoly.msg.Cat [" Insufficient poly surround (advisory)"]; rt.viaOnPolyAndDiff _ [1 * lambda, "Topology not flat (advisory)"]; -- more for the sake of robustness rt.viaSeparation _ [1 * lambda, "Via to via separation"]; -- only overlaps checked rt.viaOverGate _ [1 * lambda, "Via not allowed over gate"]; rt.viaOverPoly _ [1 * lambda, "Via not allowed over poly (advisory)"]; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $NWellPDifSurround]; rt.nWellSurround _ toto; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $NWellNWellDifSurround]; rt.nWellContact _ toto; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $NWellMaxConnect]; rt.wellContactSpacing _ toto; rt.wellContactSpacing.msg _ rt.wellContactSpacing.msg.Cat [" Well contact required (advisory)"]; -- 6.13.3.1 rt.wellConflict _ [2 * lambda, "p-well overlaps n-well"]; rt.NinN _ [2 * lambda, "n-diffusion in n-well"]; rt.PinP _ [2 * lambda, "p-diffusion in p-well"]; rt.isolatedWell _ [2 * lambda, "Isolated well"]; [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $ContactGateSpace]; -- rule 6.5.1.6 rt.diffCutToGate _ toto; -- rule 6.5.1.6 rt.largeDiffCutToGate _ rt.diffCutToGate; -- rule 6.5.1.6 [toto.extent, toto.msg] _ DesignRules.GetScaledValue [rules, $DifCutViaSpace]; -- rule 6.7.8 rt.difCutViaSpace _ toto; -- rule 6.7.8 rt.minPadSize.extent _ DesignRules.GetScaledValue [rules, $PadMetalWidth].v - 2 * DesignRules.GetScaledValue [rules, $PadMetalViaSurround].v; -- rule 6.9.2 - 2* 6.9.3 tech.ttMaxSep _ tech.ctMaxSep _ 0; FOR s: Layer IN Layer DO IF tech.illegalLayer[s] THEN LOOP; tech.ctMaxSep _ MAX [tech.ctMaxSep, rt.separation[pol][s].extent]; tech.ctMaxSep _ MAX [tech.ctMaxSep, rt.separation[gate][s].extent]; tech.ctMaxSep _ MAX [tech.ctMaxSep, rt.separation[pdif][s].extent] ENDLOOP; tech.ttMaxSep _ MAX [rt.separation[pol][pdif].extent, rt.separation[gate][pdif].extent, rt.separation[pol][pol].extent, rt.separation[pdif][pdif].extent]; tech.ruleTables _ rt; cachedTech _ [tech, rules.id] END; -- NewTechnology SimpleWidthCheck: WireProc ~ BEGIN VerifyRect: CoreGeometry.EachInstanceProc ~ BEGIN min, max, a, b: CD.Number; o: CdObj ~ instance.obj; l: Layer ~ o.layer; r: Rect ~ CoreGeometry.InlineBBox [instance]; rt: CMosbTable ~ NARROW [state.tech.ruleTables]; IF DrcDebug.debug THEN BEGIN DrcDebug.dLog.PutF ["Class = %g. ", IO.atom [o.class.objectType]]; DrcDebug.dLog.PutF [format: "Checking rectangle at [%g, %g] %l %g%l\n", v1: IO.int [instance.trans.off.x / lambda], v2: IO.int [instance.trans.off.y / lambda], v3: IO.rope ["b"], v4: IO.rope [CDOps.LayerRope [o.layer]], v5: IO.rope ["B"]]; IF (CDProperties.GetObjectProp [o, DrcDebug.pause] # NIL) THEN DrcDebug.break END; SELECT o.class.objectType FROM rectClass => IF (l <= specialLayers) THEN RETURN; markClass, segmentClass, pinClass => RETURN; ENDCASE => quit _ CoreGeometry.FlattenInstance [instance, VerifyRect]; IF DrcDebug.debug THEN CDProperties.PutObjectProp [o, DrcDebug.trace, DrcDebug.trace]; IF state.tech.illegalLayer[l] THEN BEGIN MarkError [cell, state, [r, Rope.Cat ["Illegal layer ", LayerName [l], " (wire ", CoreWireName [w], ")"]]]; RETURN END; min _ rt.minWidth[l].extent; max _ rt.maxWidth[l].extent; a _ MAX [(r.x2 - r.x1), (r.y2 - r.y1)]; b _ MIN [(r.x2 - r.x1), (r.y2 - r.y1)]; -- a and b are such that a > b IF (a < min) OR (b < min) OR (a > max) OR (b > max) THEN MarkError [cell, state, [r, rt.minWidth[l].msg.Cat [" (wire ", CoreWireName [w], ")"]]] END; -- VerifyRect [] _ state.attributes.EnumerateGeometry [w, VerifyRect] END; -- SimpleWidthCheck FullWireCheck: WireProc ~ BEGIN -- INTERIM rt: CMosbTable ~ NARROW [state.tech.ruleTables]; minPadSize: CD.Number ~ rt.minPadSize.extent; VerifyRect: CoreGeometry.EachInstanceProc ~ BEGIN min, max, a, b: CD.Number; o: CdObj ~ instance.obj; l: Layer ~ o.layer; r: Rect ~ CoreGeometry.InlineBBox [instance]; size: CD.Position ~ Size [r]; IF DrcDebug.debug THEN BEGIN DrcDebug.dLog.PutF ["Class = %g. ", IO.atom [o.class.objectType]]; DrcDebug.dLog.PutF [format: "Checking rectangle at [%g, %g] %l %g%l\n", v1: IO.int [instance.trans.off.x / lambda], v2: IO.int [instance.trans.off.y / lambda], v3: IO.rope ["b"], v4: IO.rope [CDOps.LayerRope [o.layer]], v5: IO.rope ["B"]]; IF (CDProperties.GetObjectProp [o, DrcDebug.pause] # NIL) THEN DrcDebug.break END; SELECT o.class.objectType FROM rectClass => IF (l <= specialLayers) OR (IsCut [l]) THEN RETURN; -- width rules for cuts depend on class wellRectClass => NULL; $C2SimpleCon, $C2WellSimpleCon, $C2LargeSimpleCon, $C2LargeWellSimpleCon, $C2DifShortCon, $C2WellDifShortCon, $C2DiffShortCon, $C2Via, $C2LargeVia => BEGIN VerifyContact [o, r]; RETURN END; markClass, segmentClass, pinClass => RETURN; ENDCASE => BEGIN quit _ CoreGeometry.FlattenInstance [instance, VerifyRect]; RETURN END; IF DrcDebug.debug THEN CDProperties.PutObjectProp [o, DrcDebug.trace, DrcDebug.trace]; IF state.tech.illegalLayer[l] OR ((l = ovg) AND ((size.x < minPadSize) OR (size.y < minPadSize))) THEN BEGIN MarkError [cell, state, [r, Rope.Cat ["Illegal layer ", LayerName [l], " (wire ", CoreWireName [w], ")"]]]; RETURN END; min _ rt.minWidth[l].extent; max _ rt.maxWidth[l].extent; a _ MAX [size.x, size.y]; b _ MIN [size.x, size.y]; -- a and b are such that a > b IF (a < min) OR (b < min) OR (a > max) OR (b > max) THEN BEGIN ruleHint: ROPE ~ IO.PutFR ["%g (%g%g ): %g (wire %g)", IO.rope [rt.minWidth[l].msg], IO.int [rt.minWidth[l].extent/lambda], IO.rope [IF (rt.minWidth[l].extent MOD lambda # 0) THEN ".5" ELSE NIL], IO.rope [LayerName [l]], IO.rope [CoreWireName [w]]]; MarkError [cell, state, [r, ruleHint]] END END; -- VerifyRect VerifyContact: PROC [contact: CdObj, bb: Rect] ~ BEGIN size: CD.Position; sizeExceeded: BOOL _ FALSE; classKey: ATOM ~ contact.class.objectType; maxContSize: CD.Number ~ rt.maxWidth[cut].extent; minContSize: CD.Number ~ rt.minWidth[cut].extent; maxViaSize: CD.Number ~ rt.maxWidth[cut2].extent; minViaSize: CD.Number ~ rt.minWidth[cut2].extent; splitContWidth: CD.Number ~ minContSize; splitContHeight: CD.Number ~ maxContSize + lambda; FOR geom: CDAtomicObjects.DrawList _ NARROW [contact.specific, CDAtomicObjects.AtomicObsSpecific].rList, geom.rest WHILE geom # NIL DO SELECT geom.first.layer FROM cut => BEGIN -- all but vias size _ Size [geom.first.r]; SELECT classKey FROM $C2DifShortCon, $C2DiffShortCon, $C2WellDifShortCon => sizeExceeded _ sizeExceeded OR ((MIN[size.x, size.y] # splitContWidth) OR (MAX[size.x, size.y] # splitContHeight)); ENDCASE => sizeExceeded _ sizeExceeded OR (size.x > maxContSize OR size.y > maxContSize) OR (size.x < minContSize OR size.y < minContSize) END; cut2 => BEGIN -- vias size _ Size [geom.first.r]; IF (size.x < minPadSize) OR (size.y < minPadSize) THEN sizeExceeded _ sizeExceeded OR (size.x > maxViaSize OR size.y > maxViaSize) OR (size.x < minViaSize OR size.y < minViaSize) END; ENDCASE => NULL ENDLOOP; IF sizeExceeded THEN MarkError [cell, state, [bb, Rope.Cat ["Contact size exceeded for ", Atom.GetPName [classKey], " (wire ", CoreWireName [w], ")"]]] END; -- VerifyContact [] _ state.attributes.EnumerateGeometry [w, VerifyRect] END; -- FullWireCheck SimpleMaterialSeparation: WirePairProc ~ BEGIN aequipotential: BOOL ~ (w1.global = w2.global); r1, r2, b1, b2: Rect; l1, l2: Layer; o1, o2: CdObj; rt: CMosbTable ~ NARROW [state.tech.ruleTables]; VerifyOuter: CoreGeometry.EachInstanceProc ~ BEGIN VerifyInner: CoreGeometry.EachInstanceProc ~ BEGIN sep: CD.Number; o2 _ instance.obj; l2 _ o2.layer; quit _ state.abort^; IF (o2.class.objectType # rectClass) OR (l2 <= specialLayers) OR (state.tech.illegalLayer[l2]) THEN RETURN; r2 _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w2.transf]; IF (NOT (IsCut [l1] AND IsCut [l2])) THEN BEGIN IF ignoreConnectivity THEN BEGIN IF (Intersecting [r1, r2]) THEN RETURN END ELSE BEGIN IF aequipotential THEN RETURN END END; sep _ rt.separation[l1][l2].extent; IF (sep = 0) THEN RETURN; IF aequipotential AND (SameRect [r1, r2, l1, l2]) THEN RETURN; -- e.g. cuts b1 _ Bloat [r1, sep / 2]; b2 _ Bloat [r2, sep / 2]; IF DrcDebug.debug THEN CoreView.AddRectangle [CoreView.debugViewer, r1, w1.local]; IF IntersectingOpen [b1, b2] THEN BEGIN n1: ROPE ~ rt.separation[l1][l2].msg.Cat [" (wire ", WireName [w1], ")"]; n2: ROPE ~ Rope.Cat [" (wire ", WireName [w2], ")"]; MarkError [cell, state, [Intersection [b1, b2], n1.Cat [" and ", n2]]] END; quit _ state.abort^ END; -- VerifyInner o1 _ instance.obj; l1 _ o1.layer; quit _ state.abort^; IF (o1.class.objectType # rectClass) OR (l1 <= specialLayers) OR (state.tech.illegalLayer[l1]) THEN RETURN; r1 _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w1.transf]; quit _ state.attributes.EnumerateGeometry [w2.local, VerifyInner] END; -- VerifyOuter IF (Intersecting [(Bloat [AtomicWireHull[w1, state], state.tech.maxSeparation]), (AtomicWireHull[w2, state])]) THEN [] _ state.attributes.EnumerateGeometry [w1.local, VerifyOuter] END; -- SimpleMaterialSeparation ViaTileData: TYPE ~ REF ViaTileDataRec; ViaTileDataRec: TYPE ~ RECORD [ hasDiff: BOOL _ FALSE, -- diffusion hasPoly: BOOL _ FALSE, -- polysilicide hasFOx: BOOL _ FALSE]; -- field oxide MatTileData: TYPE ~ REF MatTileDataRec; MatTileDataRec: TYPE ~ RECORD [layerKey: ATOM, via: ViaTileData]; OccupyTile: CStitching.RectProc = BEGIN WITH oldValue SELECT FROM v: ViaTileData => NULL; -- vias are often repeated on top of each other ENDCASE => CStitching.ChangeRect [plane, rect, data] END; -- OccupyTile CompleteSeparation: WirePairProc ~ BEGIN aequipotential: BOOL ~ (w1.global = w2.global); viaTess, materialTess: Tess; currentTransf: Transf; outer: FakeInst; outerIsDiffCont, outerIsLargeDiffCont, innerIsDiffCont, innerIsLargeDiffCont: BOOL _ FALSE; rt: CMosbTable ~ NARROW [state.tech.ruleTables]; VerifyOuter: CoreGeometry.EachInstanceProc ~ BEGIN r1, maxBloat1: Rect; o1: CdObj ~ instance.obj; l1: Layer ~ o1.layer; c1: ATOM ~ o1.class.objectType; VerifyInner: CoreGeometry.EachInstanceProc ~ BEGIN r2, b1, b2: Rect; sep: CD.Number; o2: CdObj ~ instance.obj; l2: Layer ~ o2.layer; c2: ATOM ~ o2.class.objectType; quit _ state.abort^; SELECT c2 FROM rectClass => IF (l2 <= specialLayers) OR (state.tech.illegalLayer[l2]) OR ((IsWell [l1]) AND (IsWell [l2])) THEN RETURN; wellRectClass => NULL; markClass, segmentClass, pinClass => RETURN; ENDCASE => BEGIN -- vedasi commento al livello pi u esterno r: Rect ~ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w2.transf]; IF (instance = outer) OR (NOT Intersecting [r, window]) OR (NOT IntersectingOpen [maxBloat1, r]) THEN RETURN; innerIsDiffCont _ IsDiffContact [c2, l2]; innerIsLargeDiffCont _ IsLargeDiffContact [c2, l2]; quit _ CoreGeometry.FlattenInstance [instance, VerifyInner]; RETURN END; r2 _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w2.transf]; IF NOT Intersecting [r2, window] THEN RETURN; IF state.viaFlatness AND (l2 = cut2) THEN CStitching.ChangeEnumerateArea [viaTess, r2, OccupyTile, NEW [ViaTileDataRec], nothing]; IF ((l1 = gate) AND ((l2 = pdif) OR (l2 = ndif))) OR ((l2 = gate) AND ((l1 = pdif) OR (l1 = ndif))) THEN {Anathema [2, state]; RETURN}; IF ((((l1 = pol) AND (diffContactLayer[l2])) OR ((diffContactLayer[l1]) AND (l2 = pol))) AND ((w1.gateHint # NIL) AND (w2.gateHint # NIL))) THEN {Anathema [2, state]; RETURN}; IF (aequipotential AND SameRect [r1, r2, l1, l2]) THEN RETURN; IF ((((l1 = pol) AND (l2 = cut2)) OR ((l1 = cut2) AND (l2 = pol))) AND (Intersecting [r1, r2])) THEN RETURN; IF NOT (IsCut [l1] AND IsCut [l2]) THEN BEGIN IF ignoreConnectivity THEN BEGIN IF (IntersectingOpen [r1, r2]) AND (SameLayer [l1, l2]) THEN BEGIN IF NOT aequipotential THEN BEGIN BothRec: TYPE ~ RECORD [a, b: WireInstance]; both: REF BothRec _ NEW [BothRec _ [w1, w2]]; msg: ROPE ~ IO.PutFR ["Short-cut: %g [%g] # %g [%g], but they are connected on layer %g", IO.rope [WireName [w1]], IO.card [LOOPHOLE [w1.global]], IO.rope [WireName [w2]], IO.card [LOOPHOLE [w2.global]], IO.rope [LayerName [l1]]]; MarkError [cell, state, [Bloat [Intersection [r1, r2], lambda], msg]] END ELSE BEGIN min: CD.Number ~ rt.minWidth[l1].extent; i: Rect _ Intersection [r1, r2]; IF (i.x2 - i.x1 < min) AND (i.y2 - i.y1 < min) THEN BEGIN dx: CD.Number ~ (min - i.x2 - i.x1) / 2; dy: CD.Number ~ (min - i.y2 - i.y1) / 2; i _ [i.x1 - dx, i.y1 - dy, i.x2 + dx, i.y2 + dy]; -- beat it if you can IF (GapIsFilled [i, l1, w1, state] = empty) THEN Anathema [1, state] ELSE MarkError [cell, state, [i, rt.minWidth[l1].msg.Cat [" width violation for intersection of rectangle pair on layer ", LayerName[l1]]]] END END; RETURN END END ELSE {IF aequipotential THEN RETURN} END; sep _ rt.separation[l1][l2].extent; IF (((l1 = cut) OR (l2 = cut)) AND ((innerIsDiffCont OR outerIsDiffCont OR innerIsLargeDiffCont OR outerIsLargeDiffCont))) THEN BEGIN SELECT TRUE FROM ((l1 = gate) OR (l2 = gate)) => SELECT TRUE FROM -- VTI 6.5.2.3 innerIsDiffCont, outerIsDiffCont => sep _ rt.diffCutToGate.extent; innerIsLargeDiffCont, outerIsLargeDiffCont => sep _rt.largeDiffCutToGate.extent; ENDCASE => NULL; (((l1 = cut) AND (l2 = cut2)) OR ((l1 = cut2) AND (l2 = cut))) => sep _ rt.difCutViaSpace.extent; -- 6.7.8 (((l1 = cut) AND (diffContactLayer[l2])) OR ((l2 = cut) AND (diffContactLayer[l1]))) => sep _ 0; -- VTI 6.5.1.7 ENDCASE => NULL END; IF (sep = 0) THEN RETURN; b1 _ Bloat [r1, sep]; IF DrcDebug.debug THEN BEGIN CoreView.AddRectangle [CoreView.debugViewer, r2, w2.global]; DrcDebug.dLog.PutF [" checking separation between rectangle on %g at [%g, %g, %g, %g]", IO.rope [LayerName[l1]], IO.int [r1.x1/lambda], IO.int [r1.y1/lambda], IO.int [r1.x2/lambda], IO.int [r1.y2/lambda]]; DrcDebug.dLog.PutF [" and %g at [%g, %g, %g, %g].\n", IO.rope [LayerName[l2]], IO.int [r2.x1/lambda], IO.int [r2.y1/lambda], IO.int [r2.x2/lambda], IO.int [r2.y2/lambda]]; END; IF IntersectingOpen [b1, r2] THEN BEGIN -- Separation violation errorRegion: LIST OF Rect; ruleType: ROPE _ ": Separation between "; name1: ROPE ~ WireName [w1]; name2: ROPE ~ WireName [w2]; n1, n2, layoutHint, ruleHint: ROPE; violationIsSeparation: BOOL _ TRUE; IF (aequipotential AND ((((l1 = ndif) AND (l2 = pwellCont)) OR ((l1 = pwellCont) AND (l2 = ndif)) AND name1.Equal ["Gnd"]) OR (((l1 = pdif) AND (l2 = nwellCont)) OR ((l1 = nwellCont) AND (l2 = pdif)) AND name1.Equal ["Vdd"])) AND (Intersecting [r1, r2] AND (NOT IntersectingOpen [r1, r2]))) THEN {Anathema [3, state]; RETURN}; IF DrcDebug.debug THEN BEGIN n1 _ IO.PutFR ["%g (wire %g [%g])", IO.rope [LayerName[l1]], IO.rope [name1], IO.card [LOOPHOLE[w1.local]]]; n2 _ IO.PutFR ["%g (wire %g [%g])", IO.rope [LayerName[l2]], IO.rope [name2], IO.card [LOOPHOLE[w2.local]]] END ELSE BEGIN n1 _ LayerName[l1].Cat [" (wire ", name1, ")"]; n2 _ LayerName[l2].Cat [" (wire ", name2, ")"]; END; layoutHint _ n1.Cat [" and ", n2]; b1 _ Bloat [r1, sep / 2]; b2 _ Bloat [r2, sep / 2]; errorRegion _ LIST [Intersection [b1, b2]]; IF NOT (IsCut [l1] AND IsCut [l2]) THEN IF ignoreConnectivity AND (SameLayer [l1, l2]) THEN BEGIN gap: Rect ~ Normalize [Bloat [errorRegion.first, -sep/2]]; IF diffContactLayer[l1] THEN BEGIN -- could be a channel a, b: WireInstance; IF (w1.gateHint # NIL) AND (w1.gateHint = w2.gateHint) THEN {Anathema [2, state]; RETURN}; a _ IF (w1.gateHint = NIL) THEN w1 ELSE w1.gateHint^; b _ IF (w2.gateHint = NIL) THEN w2 ELSE w2.gateHint^; IF ((GapIsFilled [gap, gate, a, state] = empty) OR (GapIsFilled [gap, gate, b, state] = empty)) THEN {Anathema [1, state]; RETURN}; WITH relatedWires SELECT FROM s: WireSet => -- channel fills diff gap FOR i: NAT IN [0 .. s.size) DO IF (s[i].global = w1.global) THEN IF (GapIsFilled [gap, l1, s[i], state] = empty) THEN {Anathema [0, state]; RETURN} ENDLOOP; sl: LIST OF WireSet => -- channel fills diff gap FOR l: LIST OF WireSet _ sl, l.rest WHILE l # NIL DO FOR i: NAT IN [0 .. l.first.size) DO IF (i = 0) OR (l.first[i].global = w1.global) THEN BEGIN IF (GapIsFilled [gap, l1, l.first[i], state] = empty) THEN {Anathema [0, state]; RETURN}; IF (GapIsFilled [gap, l1, w1, state, l.first[i]] = empty) THEN {Anathema [0, state]; Anathema [1, state]; RETURN} END ENDLOOP ENDLOOP; list: LIST OF WireInstance => -- diff gap separated by gate FOR gates: LIST OF WireInstance _ list, gates.rest WHILE gates # NIL DO IF (GapIsFilled [gap, gate, gates.first, state] = empty) THEN {Anathema [0, state]; RETURN} ENDLOOP; ENDCASE => IF (relatedWires # NIL) THEN ERROR END; errorRegion _ GapIsFilled [gap, l1, w1, state]; IF (errorRegion = empty) THEN BEGIN IF aequipotential THEN {Anathema [1, state]; RETURN} ELSE BEGIN BothRec: TYPE ~ RECORD [a, b: WireInstance]; both: REF BothRec _ NEW [BothRec _ [w1, w2]]; ruleType _ "Short-cut: w1 # w2, but they actually are connected"; IF DrcDebug.debug THEN DrcDebug.break END END; errorRegion _ GapIsFilled [gap, l2, w2, state]; IF (errorRegion = empty) THEN BEGIN IF aequipotential THEN {Anathema [1, state]; RETURN} ELSE BEGIN BothRec: TYPE ~ RECORD [a, b: WireInstance]; both: REF BothRec _ NEW [BothRec _ [w1, w2]]; ruleType _ "Short-cut: w1 # w2, but they actually are connected"; IF DrcDebug.debug THEN DrcDebug.break END END; ruleType _ ": Notch on "; violationIsSeparation _ FALSE; END; IF (diffContactLayer[l1] AND (l2 = pol)) OR (diffContactLayer[l2] AND (l1 = pol)) THEN BEGIN gap: Rect ~ Normalize [Bloat [errorRegion.first, -sep/2]]; WITH relatedWires SELECT FROM sl: LIST OF WireSet => -- gate allows poly FOR l: LIST OF WireSet _ sl, l.rest WHILE l # NIL DO IF (GapIsFilled [gap, l1, w1, state, l.first[0]] = empty) THEN {Anathema [2, state]; RETURN} ENDLOOP; ENDCASE => NULL END; IF violationIsSeparation THEN ruleHint _ IO.PutFR [" should be %g%g ", IO.int [sep/lambda], IO.rope [IF (sep MOD lambda # 0) THEN ".5" ELSE NIL]]; ruleHint _ rt.separation[l1][l2].msg.Cat [ruleType, layoutHint, ruleHint]; FOR r: LIST OF Rect _ errorRegion, r.rest WHILE r # NIL DO MarkError [cell, state, [Bloat [r.first, sep/2], ruleHint]] ENDLOOP END; quit _ state.abort^ END; -- VerifyInner quit _ state.abort^; SELECT c1 FROM rectClass => IF (l1 <= specialLayers) OR (state.tech.illegalLayer[l1]) THEN RETURN; wellRectClass => NULL; markClass, segmentClass, pinClass => RETURN; ENDCASE => BEGIN r: Rect ~ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w1.transf]; IF (NOT Intersecting [r, window]) THEN RETURN; outer _ instance; outerIsDiffCont _ IsDiffContact [c1, l1]; outerIsLargeDiffCont _ IsLargeDiffContact [c1, l1]; quit _ CoreGeometry.FlattenInstance [instance, VerifyOuter]; RETURN END; r1 _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], w1.transf]; IF NOT Intersecting [r1, window] THEN RETURN; maxBloat1 _ Bloat [r1, state.tech.maxSeparation]; IF state.viaFlatness AND (l1 = cut2) THEN CStitching.ChangeEnumerateArea [viaTess, r1, OccupyTile, NEW [ViaTileDataRec], nothing]; quit _ state.attributes.EnumerateGeometry [w2.local, VerifyInner] END; -- VerifyOuter FindMaterial: CoreGeometry.EachInstanceProc ~ BEGIN bloatedRect, r: Rect; vias: Region; IF (instance.obj.class.objectType # rectClass) THEN RETURN; IF state.abort^ THEN RETURN [TRUE]; r _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], currentTransf]; IF NOT (CDBasics.NonEmpty [r]) THEN RETURN; -- empty rectangle SELECT instance.obj.layer FROM pol => BEGIN bloatedRect _ Bloat [r, rt.viaOnFieldOxideAvoidsPoly.extent]; vias _ CStitching.ListArea [plane: viaTess, rect: bloatedRect]; FOR v: Region _ vias, v.rest WHILE v # NIL DO via: ViaTileData = NARROW [v.first.value]; ENDLOOP; bloatedRect _ Bloat [r, rt.polySurroundsViaOnPoly.extent]; vias _ CStitching.ListArea [plane: viaTess, rect: bloatedRect]; FOR v: Region _ vias, v.rest WHILE v # NIL DO via: ViaTileData ~ NARROW [v.first.value]; data: MatTileData ~ NEW [MatTileDataRec _ [polyKey, via]]; IF Intersecting [v.first.rect, r] THEN via.hasPoly _ TRUE; bloatedRect _ Bloat [v.first.rect, rt.polySurroundsViaOnPoly.extent]; CStitching.ChangeEnumerateArea [materialTess, Intersection [bloatedRect, r], OccupyTile, data, nothing] ENDLOOP END; ENDCASE => NULL END; -- FindMaterial LookUnderneath: CStitching.TileProc ~ BEGIN -- PROC [tile: REF Tile, data: REF] via: ViaTileData ~ NARROW [tile.value]; rect: CStitching.Rect ~ CStitching.Area [tile]; IsOnFieldOxide: PROC RETURNS [d: BOOL _ TRUE] ~ INLINE BEGIN FOR cut: Region _ CStitching.ListArea [materialTess, rect], cut.rest WHILE cut # NIL DO IF (cut.first.value # NIL) THEN RETURN [FALSE] ENDLOOP END; -- IsOnFieldOxide Accumulate: CStitching.TileProc ~ BEGIN via: ViaTileData ~ NARROW [data]; mat: MatTileData ~ NARROW [tile.value]; IF (mat = fieldOxide) THEN via.hasFOx _ TRUE -- [field oxide is represented by L] ELSE BEGIN IF (mat.via # via) THEN ERROR; -- Consistency test: Tesselation screwed up SELECT mat.layerKey FROM polyKey => via.hasPoly _ TRUE; ENDCASE => ERROR END END; -- Accumulate via.hasFOx _ NOT (via.hasDiff OR via.hasPoly); SELECT TRUE FROM via.hasPoly => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, rt.polySurroundsViaOnPoly.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasFOx THEN IF IsOnFieldOxide[] THEN MarkError [cell, state, [rect, rt.viaOnFieldOxideAvoidsPoly.msg]] ELSE MarkError [cell, state, [rect, rt.polySurroundsViaOnPoly.msg]] END; via.hasFOx => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, rt.fieldOxideSurroundsViaOnFieldOxide.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasPoly THEN MarkError [cell, state, [rect, rt.viaOnFieldOxideAvoidsPoly.msg]] END; ENDCASE => NULL -- no violation END; -- LookUnderneath GapIsFilled: PROC [gap: Rect, l: Layer, w: WireInstance, state: State, additionalWire: WireInstance _ notChannel] RETURNS [notch: LIST OF Rect] ~ BEGIN cracker: Tess _ CStitching.NewTesselation [stopFlag: state.abort]; nibbledCracker: Region; notchBB: Rect _ CDBasics.empty; transf: Transf _ w.transf; Nibble: CStitching.RectProc ~ BEGIN WITH oldValue SELECT FROM any: ATOM => cracker.ChangeRect [rect: rect, new: empty]; ENDCASE => NULL END; -- Nibble Bite: CStitching.RectProc ~ BEGIN WITH oldValue SELECT FROM any: ATOM => NULL; ENDCASE => cracker.ChangeRect [rect: rect, new: data] END; -- Bite FindPatch: CoreGeometry.EachInstanceProc ~ BEGIN SELECT instance.obj.class.objectType FROM rectClass, wellRectClass => IF (SameLayer [instance.obj.layer, l] OR (SameLayer [instance.obj.layer, gate] AND ((l = pdif) OR (l = ndif)))) THEN BEGIN r: Rect ~ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], transf]; IF Contains [r, gap] THEN {quit _ TRUE; notch _ NIL} END; markClass, segmentClass, pinClass => NULL; ENDCASE => quit _ CoreGeometry.FlattenInstance [instance, FindPatch] END; -- FindPatch FindFancyPatch: CoreGeometry.EachInstanceProc ~ BEGIN SELECT instance.obj.class.objectType FROM rectClass, wellRectClass => IF (SameLayer [instance.obj.layer, l] OR (SameLayer [instance.obj.layer, gate] AND ((l = pdif) OR (l = ndif)))) THEN BEGIN r: Rect _ CDBasicsInline.MapRect [CoreGeometry.InlineBBox [instance], transf]; r _ Bloat [r, 1]; IF Intersecting [r, gap] THEN cracker.ChangeEnumerateArea [Intersection [r, gap], Nibble, NIL, empty]; IF cracker.IsEmpty [] THEN quit _ TRUE END; markClass, segmentClass, pinClass => NULL; ENDCASE => quit _ CoreGeometry.FlattenInstance [instance, FindFancyPatch] END; -- FindFancyPatch IF (gap.x1 = gap.x2) OR (gap.y1 = gap.y2) THEN RETURN [NIL]; notch _ LIST [gap]; IF (w.local = NIL) THEN RETURN [notch]; IF state.attributes.EnumerateGeometry [w.local, FindPatch] THEN RETURN [NIL]; cracker _ CStitching.NewTesselation [stopFlag: state.abort]; cracker.ChangeEnumerateArea [gap, Bite, $gap, nothing]; [] _ state.attributes.EnumerateGeometry [w.local, FindFancyPatch]; IF (additionalWire.local # NIL) THEN BEGIN transf _ additionalWire.transf; IF state.attributes.EnumerateGeometry [additionalWire.local, FindPatch] THEN RETURN [NIL]; [] _ state.attributes.EnumerateGeometry [additionalWire.local, FindFancyPatch] END; nibbledCracker _ cracker.ListArea [universe]; notch _ NIL; FOR n: Region _ nibbledCracker, n.rest WHILE n # NIL DO notchBB.x1 _ MIN [notchBB.x1, n.first.rect.x1]; notchBB.y1 _ MIN [notchBB.y1, n.first.rect.y1]; notchBB.x2 _ MAX [notchBB.x2, n.first.rect.x2]; notchBB.y2 _ MAX [notchBB.y2, n.first.rect.y2]; notch _ CONS [n.first.rect, notch] ENDLOOP; IF CDBasics.NonEmpty [notchBB] THEN BEGIN nibbledEdges: CARDINAL _ 0; s, w, n, e: BOOL _ FALSE; IF notchBB.x1 > gap.x1 THEN {w _ TRUE; nibbledEdges _ nibbledEdges.SUCC}; IF notchBB.y1 > gap.y1 THEN {s _ TRUE; nibbledEdges _ nibbledEdges.SUCC}; IF notchBB.x2 < gap.x2 THEN {e _ TRUE; nibbledEdges _ nibbledEdges.SUCC}; IF notchBB.y2 < gap.y2 THEN {n _ TRUE; nibbledEdges _ nibbledEdges.SUCC}; IF (nibbledEdges = 2) AND ((w AND s) OR (s AND e) OR (e AND n) OR (n AND w)) THEN notch _ NIL END; cracker.TrustedDisposeTesselation [] END; -- GapIsFilled IF (Intersecting [(Bloat [AtomicWireHull[w1, state], state.tech.maxSeparation]), AtomicWireHull[w2, state]]) THEN BEGIN IF state.viaFlatness THEN BEGIN viaTess _ CStitching.NewTesselation [stopFlag: state.abort]; materialTess _ CStitching.NewTesselation [stopFlag: state.abort] END; [] _ state.attributes.EnumerateGeometry [w1.local, VerifyOuter]; IF state.viaFlatness THEN BEGIN currentTransf _ w1.transf; [] _ state.attributes.EnumerateGeometry [w1.local, FindMaterial]; currentTransf _ w2.transf; [] _ state.attributes.EnumerateGeometry [w2.local, FindMaterial]; viaTess.EnumerateArea [rect: CStitching.all, eachTile: LookUnderneath, data: state, skip: empty]; viaTess.TrustedDisposeTesselation []; materialTess.TrustedDisposeTesselation [] END END END; -- CompleteSeparation GenistaCMosBwells: PUBLIC Tech; LocalState: TYPE ~ REF LocalStateRec; -- needed to mark errors LocalStateRec: TYPE ~ RECORD [globalState: State, obj: CoreCell, wellTess: Tess]; CornerCheckData: TYPE ~ REF CornerCheckDataRec; CornerCheckDataRec: TYPE ~ RECORD [state: LocalState, key: ATOM, rule: Rule, detail: Rect _ universe]; doNotAnalyse: ATOM = $DoNotDRC; pWellKey: ATOM ~ CD.LayerKey [pwell]; nWellKey: ATOM ~ CD.LayerKey [nwell]; cachedTess: Tess; -- Assume: no concurrency !!! VerifyWells: CellProc ~ BEGIN rt: CMosbTable ~ NARROW [state.tech.ruleTables]; localState: LocalState ~ NEW [LocalStateRec _ [state, cell, NIL]]; cornerData: CornerCheckData ~ NEW [CornerCheckDataRec _ [state: localState]]; o: CD.Object ~ CoreGeometry.GetObject [state.attributes, cell]; localState.wellTess _ IF (cachedTess # NIL) THEN cachedTess ELSE CStitching.NewTesselation [stopFlag: state.abort]; EnumerateChipNDale [obj: o, state: localState, how: $getWells]; cornerData.key _ nWellKey; cornerData.rule _ rt.minWidth[nwell]; localState.wellTess.EnumerateArea [universe, CheckCorner, cornerData, none]; cornerData.key _ none; cornerData.rule _ rt.separation[nwell][nwell]; localState.wellTess.EnumerateArea [universe, CheckCorner, cornerData, nWellKey]; EnumerateChipNDale [obj: o, state: localState, how: $sex]; EnumerateChipNDale [obj: o, state: localState, how: $contactsPos]; EnumerateChipNDale [obj: o, state: localState, how: $connection]; localState.wellTess.ChangeEnumerateArea [universe, FlagIsland, localState, empty]; EnumerateChipNDale [obj: o, state: localState, how: $contactsInfl]; localState.wellTess.ChangeEnumerateArea [universe, FlagUnconnected, localState, empty]; CStitching.TrustedDisposeTesselation [localState.wellTess] END; -- VerifyWells ExtractWells: CD.DrawRectProc ~ BEGIN state: LocalState ~ NARROW [pr.devicePrivate]; IF (l = nwell) OR (l = pwell) THEN InsertWell [r: r, type: CD.LayerKey[l], state: state] END; -- ExtractWells InsertContact: CD.DrawRectProc ~ BEGIN state: LocalState ~ NARROW [pr.devicePrivate]; IF (l = pwellCont) OR (l = nwellCont) THEN ConnectTile [r: r, state: state] END; -- InsertContact PropagateContact: CD.DrawRectProc ~ BEGIN state: LocalState ~ NARROW [pr.devicePrivate]; IF (l = pwellCont) OR (l = nwellCont) THEN PercolateContact [r: r, state: state] END; -- PropagateContact DeleteContact: CD.DrawRectProc ~ BEGIN state: LocalState ~ NARROW [pr.devicePrivate]; IF (l = pwellCont) OR (l = nwellCont) THEN DeleteConnected [r: r, state: state] END; -- DeleteContact ExtractDiff: CD.DrawRectProc ~ BEGIN state: LocalState ~ NARROW [pr.devicePrivate]; IF (l = ndif) OR (l = pdif) OR (l = pwellCont) OR (l = nwellCont) THEN Inquire [r, l, state] END; -- ExtractDiff EnumerateChipNDale: PROC [obj: CD.Object, state: LocalState, how: ATOM] ~ BEGIN dr: CD.DrawRef = CD.CreateDrawRef [[]]; dr.drawRect _ SELECT how FROM $getWells => ExtractWells, $sex => ExtractDiff, $contactsPos => InsertContact, $connection => PropagateContact, $contactsInfl => DeleteContact, ENDCASE => ERROR; dr.drawContext _ DoNotDrawContext; dr.devicePrivate _ state; dr.stopFlag _ state.globalState.abort; obj.class.drawMe [dr, obj] END; -- EnumerateChipNDale InsertWell: PROC [r: Rect, state: LocalState, type: ATOM] ~ BEGIN rt: CMosbTable ~ NARROW [state.globalState.tech.ruleTables]; wellSpacingViolation: BOOL _ FALSE; errorRect: Rect; OccupyByWell: CStitching.RectProc ~ BEGIN WITH oldValue SELECT FROM well: ATOM => IF (well # type) THEN {wellSpacingViolation _ TRUE; errorRect _ rect}; ENDCASE => -- by Cedar definition we always come here if oldValue is NIL CStitching.ChangeRect [plane: state.wellTess, rect: rect, new: type] END; -- OccupyByWell state.wellTess.ChangeEnumerateArea [r, OccupyByWell, type, nothing]; IF wellSpacingViolation THEN MarkError [state.obj, state.globalState, [errorRect, rt.wellConflict.msg]] END; -- InsertWell ConnectTile: PROC [r: Rect, state: LocalState] ~ BEGIN Contact: CStitching.RectProc ~ BEGIN WITH oldValue SELECT FROM well: ATOM => state.wellTess.ChangeRect [rect: rect, new: $hasContact]; ENDCASE => NULL -- a well contact on substrate gave an error in the sex check, maximum separation of substrate contacts not checkd for the moment END; -- Contact state.wellTess.ChangeEnumerateArea [r, Contact, NIL, empty] END; -- ConnectTile PercolateContact: PROC [r: Rect, state: LocalState] ~ BEGIN DoTile: CStitching.RectProc ~ BEGIN tile: Tile ~ state.wellTess.FindTile [[rect.x1+1, rect.y1+1]]; WITH oldValue SELECT FROM cond: ATOM => IF (cond = $hasContact) THEN BEGIN tile.value _ $expanding; state.wellTess.EnumerateNeighborhood [tile, Expand, Expand, Expand, Expand, NIL, empty]; tile.value _ $expanded END; ENDCASE => ERROR END; -- DoTile Expand: CStitching.TileProc ~ BEGIN WITH tile.value SELECT FROM cond: ATOM => IF (cond = $expanded) OR (cond = $expanding) THEN NULL ELSE BEGIN tile.value _ $expanding; state.wellTess.EnumerateNeighborhood [tile, Expand, Expand, Expand, Expand, NIL, empty]; tile.value _ $expanded END; ENDCASE => NULL -- substrate stops expansion END; -- Expand state.wellTess.ChangeEnumerateArea [r, DoTile, NIL, empty] END; -- PercolateContact DeleteConnected: PROC [r: Rect, state: LocalState] ~ BEGIN rt: CMosbTable ~ NARROW [state.globalState.tech.ruleTables]; DeleteRectangle: CStitching.RectProc ~ BEGIN WITH oldValue SELECT FROM any: ATOM => state.wellTess.ChangeRect [rect: rect, new: empty]; ENDCASE => ERROR END; -- DeleteRectangle state.wellTess.ChangeEnumerateArea [Bloat [r, rt.wellContactSpacing.extent], DeleteRectangle, NIL, empty] END; -- DeleteConnected Inquire: PROC [r: Rect, layer: Layer, state: LocalState] ~ BEGIN rt: CMosbTable ~ NARROW [state.globalState.tech.ruleTables]; bloatedRect: Rect; wells: Region; ispDiff: BOOL ~ (layer = pdif); ispCont: BOOL ~ (layer = nwellCont); isnDiff: BOOL ~ (layer = ndif); isnCont: BOOL ~ (layer = pwellCont); isP: BOOL ~ (ispDiff OR ispCont); isN: BOOL ~ (isnDiff OR isnCont); IF NOT CDBasics.NonEmpty[r] THEN RETURN; -- empty rectangle wells _ state.wellTess.ListArea [rect: r, skip: nothing]; FOR w: Region _ wells, w.rest WHILE w # NIL DO well: ATOM _ NARROW [w.first.value]; IF (isP AND (well = fieldOxide)) OR (isP AND (well = pWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.PinP.msg]]; IF (isN AND (well = nWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.NinN.msg]] ENDLOOP; IF (ispDiff OR isnDiff) THEN BEGIN bloatedRect _ Bloat [r, rt.nWellSurround.extent]; wells _ state.wellTess.ListArea [rect: bloatedRect, skip: nothing]; FOR w: Region _ wells, w.rest WHILE w # NIL DO well: ATOM _ NARROW [w.first.value]; IF (ispDiff AND (well = fieldOxide)) OR (ispDiff AND (well = pWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.nWellSurround.msg]]; IF (isnDiff AND (well = nWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.pWellSurround.msg]] ENDLOOP END ELSE BEGIN -- is contact bloatedRect _ Bloat [r, rt.nWellContact.extent]; wells _ state.wellTess.ListArea [rect: bloatedRect, skip: nothing]; FOR w: Region _ wells, w.rest WHILE w # NIL DO well: ATOM _ NARROW [w.first.value]; IF (ispCont AND (well = fieldOxide)) OR (ispCont AND (well = pWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.nWellContact.msg]]; IF (isnCont AND (well = nWellKey)) THEN MarkError [state.obj, state.globalState, [w.first.rect, rt.pWellContact.msg]] ENDLOOP END END; -- Inquire CheckCorner: CStitching.TileProc ~ BEGIN t: ATOM ~ NARROW [tile.value]; task: CornerCheckData ~ NARROW [data]; IF (t = task.key) THEN IF (tile.value # tile.SW.value) AND (tile.value # tile.WS.value) THEN BEGIN task.detail _ [tile.WEdge, tile.SEdge, tile.WEdge + task.rule.extent, tile.SEdge + task.rule.extent]; task.state.wellTess.EnumerateArea [task.detail, FlagIfNot, task, nothing] END; IF (tile.value # tile.EN.value) AND (tile.value # tile.NE.value) THEN BEGIN task.detail _ [tile.EEdge - task.rule.extent, tile.NEdge - task.rule.extent, tile.EEdge, tile.NEdge]; task.state.wellTess.EnumerateArea [task.detail, FlagIfNot, task, nothing] END END; -- CheckCorner FlagIsland: CStitching.RectProc ~ BEGIN state: LocalState ~ NARROW [data]; rt: CMosbTable ~ NARROW [state.globalState.tech.ruleTables]; value: ATOM _ NARROW [oldValue]; IF (value = nWellKey) OR (value = pWellKey) THEN MarkError [state.obj, state.globalState, [rect, rt.isolatedWell.msg]] END; -- FlagIsland FlagUnconnected: CStitching.RectProc ~ BEGIN state: LocalState ~ NARROW [data]; rt: CMosbTable ~ NARROW [state.globalState.tech.ruleTables]; MarkError [state.obj, state.globalState, [rect, rt.wellContactSpacing.msg]] END; -- FlagUnconnected FlagIfNot: CStitching.TileProc ~ BEGIN task: CornerCheckData ~ NARROW [data]; IF (tile.value # task.key) THEN BEGIN r: Rect ~ Intersection [tile.Area, task.detail]; MarkError [task.state.obj, task.state.globalState, [r, task.rule.msg]] END END; -- FlagIfNot [] _ CDProperties.RegisterProperty [cMosBsimpleKey, $gbb]; [] _ CDProperties.RegisterProperty [cMosBcompleteKey, $gbb]; CoreProperties.StoreProperties [prop: cMosBsimpleKey, properties: CoreProperties.Props [[CoreProperties.propPrint, NEW [CoreProperties.PropPrintProc _ PrintChecked]]]]; CoreProperties.StoreProperties [prop: cMosBcompleteKey, properties: CoreProperties.Props [[CoreProperties.propPrint, NEW [CoreProperties.PropPrintProc _ PrintChecked]]]]; IF (CD.undefLayer # 0) THEN ERROR -- check the definition of specialLayers END. IDrcCMOSBimpl.Mesa Copyright Ó 1987, 1988 by Xerox Corporation. All rights reserved. Written by gbb, January 12, 1987 11:55:49 am PST gbb January 16, 1988 4:36:54 pm PST Genista is the grandson of Spinifex. It is a hierarchical design rule checker that monkeys around in a Core design and tries to find all the ChipNDale geometry in order to check as many design rules as it possibly can. Types and constants cMosBsimple does the same thing SoS did; cMosBcomplete verifies all VTI rules eccept for wells and transistors, which are not in Core. undefLayer, highLightShade, highLightError, pinRepresentation, outlineLayer, selectionLayer, commentLayer Warning: CD.undefLayer could not be included in the list because of a minor bug in the compiler, but it should so once the bug is fixed. Ze rulez Via flatness rules: In the following rules the extent is used only to determine the overlap of the error rectangle: WellsEtc: In the following rules the extent is used only to determine the overlap of the error rectangle: Exception to gate rules: Miscellaneous rules Allocation of technology records. Fills the rule tables for a given set of design rules. Must be called before calling CheckDesignRules. The key must be one of those exported from a technology dependent part of Genista. Returns NIL if a key is invalid. Conservative (looks at all layers, not only the legal ones). Extractor cannot handle wells adequately. Try to filter out inappropriate layers. Via flatness rules In  units from the minimal metal border of the via (not from the cut). rt.viaOnFieldOxideAvoidsDiff _ DesignRules.GetScaledValue [rules, $DifViaSpace]; rt.viaOnFieldOxideAvoidsPoly _ DesignRules.GetScaledValue [rules, $PolyViaSpace]; rt.diffSurroundsViaOnDiff _ DesignRules.GetScaledValue [rules, $DifViaSurround]; rt.polySurroundsViaOnPoly _ DesignRules.GetScaledValue [rules, $PolyViaSurround]; In the following rules the extent is used only to determine the overlap of the error rectangle. Well rules rt.pWellSurround _ DesignRules.GetScaledValue [rules, $NWellNDifSpace]; rt.pWellSurround.msg _ rt.pWellSurround.msg.Cat ["n-well too small or p-diffusion too close to p-well "]; rt.nWellSurround _ DesignRules.GetScaledValue [rules, $NWellPDifSurround]; rt.nWellContact _ DesignRules.GetScaledValue [rules, $NWellNWellDifSurround]; rt.pWellContact _ DesignRules.GetScaledValue [rules, $PWellDifNWellSpace]; rt.wellContactSpacing _ DesignRules.GetScaledValue [rules, $NWellMaxConnect]; In the following rules the extent is used only to determine the overlap of the error rectangle. Exception to gate rules: rt.diffCutToGate _ DesignRules.GetScaledValue [rules, $ContactGateSpace]; -- rule 6.5.1.6 Miscellaneous rules: rt.difCutViaSpace _ DesignRules.GetScaledValue [rules, $DifCutViaSpace]; -- rule 6.7.8 Compute max separation Width Verification Procedures [cell: CoreCell, w: Wire, state: State] At the moment our simplicistic approach does not have any knowledge of the topology. Therefore we cannot really test this rule. PROC [instance: [obj: Object, trans: Transformation]] RETURNS [quit: BOOL _ FALSE] Note, that although the rectangle r is examinated in isolation and his position is not relevant for verification purposes, the correct position is necessary to indicate violations. CDProperties.PutObjectProp [ob, $break, $break] IF (o.class.objectType # rectClass) OR (l <= specialLayers) OR (IsCut [l]) THEN RETURN; Note: the width rules for cuts depend on the class. [cell: CoreCell, w: Wire, state: State] Intendend to converge towards 100% coverage. It will throw everything in a set of corner stitched planes and check the width, separation on the same layer and find notches. PROC [instance: [obj: Object, trans: Transformation]] RETURNS [quit: BOOL _ FALSE] Note, that although the rectangle r is examinated in isolation and his position is not relevant for verification purposes, the correct position is necessary to indicate violations. CDProperties.PutObjectProp [ob, $break, $break] VerifyContact does all necessary verifications, no "flattening" necessary. The width rules for cuts depend on the class. Separation Verification Procedures [cell: CoreCell, w1, w2: WireInstance, relatedWires: REF ANY _ NIL, window: Rect, state: State] If two unrelated bloated rectangles of material intersect, an error is flagged. The parameter cell selects the cell receiving possible error messages. It must be the father of the cell containing w1 and the cell containing w2. PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] [cell: CoreCell, w1, w2: WireInstance, relatedWires: REF ANY _ NIL, window: Rect, state: State] If two unrelated bloated rectangles of material intersect, an error is flagged. The parameter cell selects the cell receiving possible error messages. It must be the father of the cell containing w1 and the cell containing w2. Storage of current context. La seconda gran coglionata della settimana: CoreGeometry.EachInstanceProc dovrebbe fornire come parametro la classe dell'oggetto che sta essendo traversato. Sfortunatamente per motivi pi u che altro politici, cio non viene concesso. Quindi non mi resta altro da fare che simularlo. PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] In Core wells are considered part of the node to which the diffusion that brought them with them came, not of VDD. Hence all wells automatically violate the separation rule. Wells in the sense of the well layer usually used in DA tools do not exist in Core, so nothing can go wrong simply filtering out wells altogether and treating them in a special hack bypassing Core. Prune "distant" contacts. IF (IsAbstract [l1] OR IsAbstract [l2]) OR ((o1.class.objectType # rectClass) OR (c2 # rectClass)) THEN SIGNAL DrcDebug.break; -- should never happen Special case for parallel transistors: a channel of one transistor may intersect the gate of another transistor. The ChipNDale atomic objects for transistors have fixed channels of length 3l. When transistors are put in series, they are placed at 2.5l. Therefore, a channel must be allowed to abut to a gate extension. In the current implementation we are very lax and do not check the separation among channels and gate extensions: Mirroed cells are quite frequent, especially in memories. Moreover, each cel is compared against itself in order to perform correctly the above statement for the via flatness. Note that this test is stronger than testing pointers. The VTI rule 6.7.1.2 allows vias over poly. However, rule 6.7.6. requires a spacing if there is no overlap. Hence, in the simple test the check for vias over poly is skipped. Rule 6.7.7. for minimum poly overlap of a via inside poly is verified by the via flatness check. Core data structure is incorrect: w1 = w2, but they actually are connected. IF DrcDebug.debug THEN coreInconsistent ["w1 # w2, but they actually are connected", both] ELSE BEGIN END Discrimination between poly and diff contacts. (VTI rules 6.3.3, 6.7.8, and 6.5.1.7) DrcDebug.break Special case VTI rule 6.3.4. If at this point we have two cuts, there is a mis-registration, which always is an error. Must renormalize because gap is smaller than separation rule. Transistors are atomic objects and used as such in ChipNDale, but cells in Core. This means that the requirement that cells be correct in isolation cannot be enforced for transistors. The variable relatedWires contains wires that could contain geometry that fixes a design rule violation at a different hierarchical level. Core data structure is incorrect: w1 = w2, but they actually are connected. coreInconsistent ["w1 # w2, but they actually are connected", both] Core data structure is incorrect: w1 = w2, but they actually are connected. coreInconsistent ["w1 # w2, but they actually are connected", both] PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] Algorithm: 1. If there is antagonist material in a viaOnFieldOxideAvoidsDiff-sphere from a via, then the topology cannot be flat. 2. If r is in a minSurround-sphere from a via, then insert it in the material tesselation. Date: Fri, 5 Jun 87 11:23:27 PDT From: Hoel.PA 1. Via Flatness: VTI's Greg Spadea says they no longer have a problem with vias that straddle field oxide and diffusion. So the advisory comment that recommended that vias on field oxide avoid diffusion by 2l and that diffusion surround vias on diffusion by 2l is withdrawn. ndif, pdif, pwellCont, nwellCont => BEGIN bloatedRect _ Bloat [r, rt.viaOnFieldOxideAvoidsDiff.extent]; vias _ CStitching.ListArea [plane: viaTess, rect: bloatedRect]; FOR v: Region _ vias, v.rest WHILE v # NIL DO via: ViaTileData _ NARROW [v.first.value]; IF via.hasPoly THEN BEGIN MarkError [cell, state, [v.first.rect, rt.viaOverGate.msg]]; DeleteRect [viaTess, v.first.rect] END ENDLOOP; bloatedRect _ Bloat [r, rt.diffSurroundsViaOnDiff.extent]; vias _ CStitching.ListArea [plane: viaTess, rect: bloatedRect]; FOR v: Region _ vias, v.rest WHILE v # NIL DO via: ViaTileData ~ NARROW [v.first.value]; data: MatTileData ~ NEW [MatTileDataRec _ [genericDiff, via]]; IF Intersecting [v.first.rect, r] THEN via.hasDiff _ TRUE; We insert material in the whole influence area of a via. bloatedRect _ Bloat [v.first.rect, rt.diffSurroundsViaOnDiff.extent]; CStitching.ChangeEnumerateArea [materialTess, Intersection [bloatedRect, r], OccupyTile, data, nothing] Note that via always is a single and non-degenerated via, since collisions of vias are detected when the vias are input. ENDLOOP END; IF via.hasDiff THEN BEGIN MarkError [cell, state, [v.first.rect, rt.viaOverGate.msg]]; DeleteRect [viaTess, v.first.rect] END We insert material in the whole influence area of a via. Looks what is under a via cut. Is the via on field oxide ? genericDiff => via.hasDiff _ TRUE; At this point we know, what is immediately under the via cut and that there the rule viaOverGate is not violated. via.hasDiff => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, rt.diffSurroundsViaOnDiff.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasFOx THEN IF IsOnFieldOxide[] THEN MarkError [cell, state, [rect, rt.viaOnFieldOxideAvoidsDiff.msg]] ELSE MarkError [cell, state, [rect, rt.diffSurroundsViaOnDiff.msg]] END; IF via.hasDiff THEN MarkError [cell, state, [rect, rt.viaOnFieldOxideAvoidsDiff.msg]]; Interim hack. Enumerates a two wire to determine whether the gap is filled somewhere. First the common case where the gap is filled by a single rectangle is examined. [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] This is the common case. PROC [instance: CdInsts] RETURNS [quit: BOOL _ FALSE] Recognize the case of osculating rectangles on two adjacent edges. Main You might think the following: I can make this faster by checking the via flatness for each wire in the per-wire procedure. Then here I just compare the vias of one wire with the material of the other wire. Since every wire is compared with all other wires, there is quite some redundancy the way the bloody first implementor did it. Well, you lose, because you have to look underneath everything to assess flatness. Wells, Etc. Does the checks concerning wells that cannot be made by Genista because of the lack of wells in the Core data structure. This implementation is "flat", because wells are not layed out hierarchically anyway. Warning: while I am writing this code I am physically exausted. It starts out to work for n-, p-, and twin-wells. I am making compromises to get the thing flying. Do not try to understand this code. Types and constants Verifies the wells and related stuff taking its information from the ChipNDale design. Interface In principio questa e una gran coglionata, pi u di natura politica che tecnica. Nella struttura Core non ci sono i cassoni, sostanzialmente perch e l'implentatore dell'estrattore sostiene che non servono a niente. A parte il fatto che non e vero (fanno parte di VDD fintanto che sono connessi), non essendo accessiblili ai clienti (CoreGeometry.EachInstanceProc, ecc. non chiamano i clienti sui cassoni) non possono venir verificati. Dato che nel C-MOS la meta della diffusione e in un cassone e che l'IFU ha dimostrato che errori del genere di diffusione e contatti del tipo sbagliato sono abbastanza frequenti, e vitale verificare queste cose. In pratica i cassoni di soliti non seguono la gerarchia, per cui questo modulo e "piatto". Dato che i cassoni di solito sono grandi aree connesse, questo non dovrebbe essere troppo grave per la memoria. Smash wells into a flat tesselation of interesting areas. Enumerate all diffusion rectangles and perform a query with bloated rectangles. For n-diff, an n-well is an a violation, while for p-dif both a pwell and fieldOxide are a violation. Operations on ChipNDale objects [r: Rect, l: Layer, pr: DrawRef] [r: Rect, l: Layer, pr: DrawRef] Ignores sex of contacts since it already has been verified. [r: Rect, l: Layer, pr: DrawRef] Ignores sex of contacts since it already has been verified. [r: Rect, l: Layer, pr: DrawRef] Ignores sex of contacts since it already has been verified. [r: Rect, l: Layer, pr: DrawRef] If wells is false, diffusion rectangles are enumerated. Operations on the corner-stitched plane Inserts a well. This procedure ensures that wells do not overlap. [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] Changes the value of the tile with a contact into a contact. Ignores sex of contacts since it already has been verified. [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] Propagates the connectedness of a tile in order to isolate islands. [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] [tile: Tile, data: REF] DESTRUCTIVE !!! Verifies that the maximum well contact spacing is fulfilled. Ignores sex of contacts since it already has been verified. [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] Implementation Algorithm: If there is antagonist material in a wellSurround-sphere from diffusion, then the a violation is flagged. Verify diffusion type. Verify surround. [tile: Tile, data: REF] for EnumerateArea [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] [plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF] [tile: Tile, data: REF] Initialisation gbb May 15, 1987 11:10:37 am PDT The VTI rule 6.7.1.2 allows vias over poly. However, rule 6.7.6. requires a spacing if there is no overlap. Hence, in the simple test the check for vias over poly is skipped. Rule 6.7.7. for minimum poly overlap of a via inside poly is verified by the via flatness check. changes to: VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb May 27, 1987 11:49:35 am PDT Changed the default for ignoring the connectivity information in Core. changes to: ignoreConnectivity: default = TRUE, EmulateMayday: idem. gbb May 28, 1987 1:38:01 pm PDT If a gap is found, the wires are re-traversed to determine whether the gap is patched. changes to: Contains, Intersection, VerifyInner (local of VerifyOuter, local of CompleteSeparation), GapIsFilled (local of CompleteSeparation), FindPatch (local of GapIsFilled, local of CompleteSeparation) gbb June 2, 1987 4:18:11 pm PDT Generalised gap finder to detect notches. changes to: DIRECTORY, VerifyInner (local of VerifyOuter, local of CompleteSeparation), GapIsFilled (local of CompleteSeparation), FindPatch (local of GapIsFilled, local of CompleteSeparation) gbb June 5, 1987 2:01:03 pm PDT Speed tweak in the inner loop; eliminated via flatness check of diffusion: VTI's Greg Spadea says they no longer have a problem with vias that straddle field oxide and diffusion. So the advisory comment that recommended that vias on field oxide avoid diffusion by 2l and that diffusion surround vias on diffusion by 2l is withdrawn. Hoel.PA Fri, 5 Jun 87 11:23:27 PDT; see [Indigo]Top>DragonCMOSDesignRules.df changes to: VerifyInner (local of VerifyOuter, local of CompleteSeparation), FindMaterial (local of CompleteSeparation), Accumulate (local of LookUnderneath, local of CompleteSeparation), LookUnderneath (local of CompleteSeparation) gbb June 8, 1987 6:20:21 pm PDT Sometimes contacts of the class $C2DifShortCon get an additional f: $C2DiffShortCon. Added correct handling of VTI rule 6.3.4 in the default Mayday emulation mode, which Dracula cannot handle. changes to: IsDiffContact: additional class $C2DiffShortCon, VerifyInner (local of VerifyOuter, local of CompleteSeparation): a very complex if statement of which I hope the compiler will not generate garbage. gbb June 24, 1987 3:40:51 pm PDT Added a check for misregistrations changes to: VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb June 29, 1987 6:19:19 pm PDT Optimized GapIsFilled. changes to: GapIsFilled (local of CompleteSeparation), FindPatch (local of GapIsFilled, local of CompleteSeparation), FindFancyPatch (local of GapIsFilled, local of CompleteSeparation) gbb September 21, 1987 11:20:46 am PDT The ChipNDale atomic objects for transistors have fixed channels of length 3l. When transistors are put in series, they are placed at 2.5l. Therefore, a channel must be allowed to abut to a gate extension. In the current implementation we are very lax and do not check the separation among channels and gate extensions. changes to: VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb September 23, 1987 5:42:26 pm PDT Display a message every time the violation of a violation of a dogma but not a rule is encountered. changes to: DoNotDrawObject, Anathema, VerifyInner (local of VerifyOuter, local of SimpleMaterialSeparation), VerifyOuter (local of SimpleMaterialSeparation), VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb September 25, 1987 4:35:39 pm PDT Relaxed dogma of pairwise width correctness because broken all to often in cell library. changes to: DIRECTORY, Layer, Anathema, VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb October 5, 1987 1:00:41 pm PDT Made nwellCont the same layer as pdif. changes to: SameLayer, VerifyInner (local of VerifyOuter, local of CompleteSeparation) gbb October 5, 1987 2:25:00 pm PDT Added wnwellCont and wpwellCont to the diffusion contact layers. changes to: diffContactLayer gbb January 4, 1988 2:31:24 pm PST Spinned off DrcUtilities because of a compiler problem: Storage overflow in Pass 4 changes to: DIRECTORY, DrcCMOSBimpl, ~, FakeInst, Region, NewTechnology Ê2‡˜codešœ™KšœB™BKšœ0™0K™#K˜—Icode2šœÚ™ÚšÏk ˜ Kšœœ ˜KšœœÎ˜ÖKšœœ˜4Kšœ œ˜!Kšœœ ˜Kšœœ ˜Kšœ œ2˜DKšœœZ˜eKšœ œz˜ŒKšœœF˜ZKšœ œ˜+Kš œ œ5œEœ8œAœ˜Kšœ œH˜YKšœœŠ˜“Kšœ ˜ Kšœ œ$˜2Kšœ œîœ-˜±Kšœœ&˜.Kšœœœ˜Kšœœ˜—šÐln œœ˜Lšœœ–œ˜·Lšœ ˜Lšœ˜ —Lšœœœ˜&head™Lšœœœ4˜Ošœœœ6˜SKšÏe œŸ œP™†—Lšœ œ˜'Kšœœ˜"Kšœ œ˜+Kšœ œ˜'Lš œœœœœ˜-Kšœœ˜Kšœœœ˜Kš œ œœœœ˜Kšœœœ˜Kšœ ˜ Lšœ œ ˜Kšœœ ˜ Kšœ œ ˜Kšœ œ˜#Kšœœ˜&Kšœœœ˜!Kšœ œœ˜#Kšœ œ ˜Kšœ œœ˜"Kšœ œ2˜?Kšœœ˜Kšœ œœœ˜Kšœœœœ˜/šœœœ œ œœœœ˜ƒKšœi™iKšœ œ}™ˆ—Lšœœ˜!—™Lš œ œ œœœ˜3Lšœ œœœ˜,Kš œœœœ œœ˜:šœœœœ˜%Kšœœœ˜(Kš œ œœœœœ˜3K™Kšœ˜K™_Kšœ@˜@K™ KšœS˜SK™_Kšœ-˜-Kšœ™Kšœ(˜(Kšœ™Kšœ"˜"—š Ïn œ œœœ˜]KšœwŸœŸœl™üKšœ˜K˜ unitš  œœœœœ ˜GK™Kšœ œœ%œœ%œœœ œœœœœ˜úKšœ&˜&Kš˜—Kšœ¡ ˜—š  œœ˜6K™-Kšœœ ˜Kšœœœ˜Kšœ œ˜*Lšœ œ"˜1Kšœ œ"˜1Kšœ œ#˜1Kšœ œ#˜1Kšœœ˜(Kšœœ˜2š œ"œHœœ˜†šœ˜šœœ¡˜Kšœ˜šœ ˜šœ6˜6Kš œœœ$œœ%˜t—Kš œ œœœœ˜Š—Kšœ˜—šœœ¡˜Kšœ˜šœœ˜6Kš œœœœœ˜{—Kšœ˜—Kšœ˜—Kšœ˜—Kšœœƒ˜—Kšœ¡˜—Nšœ7˜7Kšœ¡˜——™"š œ˜.Kšœ5œœœ™_K™OKšœŸœbŸœŸœ™’Kšœœ˜/Kšœ˜K˜K˜Lšœœ˜0š  œ"˜2Kšœœœœ™5š  œ"˜2Kšœœœœ™5Kšœœ*˜1Kšœ˜Kš œ#œœ¤œ˜kKšœL˜Lš œœ œœ˜/šœ˜Kš œœœ¤œ˜0—Kš œœœœ¤œ˜,Kšœ˜—Kšœ#˜#Kšœ œ¤œ˜Kš œœœ¤œ¡ ˜KKšœ3˜3Kš¢£¢£<˜Ršœœ˜'KšœœA˜IKšœœ,˜4KšœF˜FKšœ˜—Kšœ˜Kšœ¡˜—Nšœ!˜!Kšœ˜Kš œ#œœ¤œ˜kNšœL˜LKšœA˜AKšœ¡˜—šœl˜sKšœ?˜?—Kšœ¡˜ —Nšœ œœ˜'Kšœœœ¡œ œœ¡ œ œœ¡œœœ¡˜Kšœ œœ˜'Kšœœœ œ˜Aš  œ˜'Kšœœ$œœ™>šœ œ˜Kšœœ¡/˜GKšœ-˜4—Kšœ¡ ˜—š œ˜(Kšœ5œœœ™_K™OKšœŸœbŸœŸœ™’Kšœœ˜/Kšœ˜Kšœ˜Lšœ˜šœNœœ˜\LšœÐesš™¶—Lšœœ˜0š  œ"˜2Kšœœœœ™5Kšœ.˜.Kšœœ˜5š  œ"˜2Kšœœœœ™5Kšœœ˜!Kšœ4œ˜ONšœ˜šœ˜š œ œœœœœ¤œ˜xKšœoÏdœ‚™ó—Kšœœ˜Kšœ$¥¤œ˜,šœœ¡*˜;K™KšœQ˜QKšœœœœœ"œ¤œ˜mKšœ)˜)Kšœ3˜3Kšœ<˜Kšœœˆ™Kšœœœœœœ¤œ˜lš œœ œ œ˜-šœœ˜ šœœœ˜Bšœœœ˜ Kšœ%Ïmœ%™KKšœ œœ˜,Kšœœ œ˜-š¢£¢™Kš£C™C—Kšœ™ KšœœœLœœœœœœœ˜æšœE˜EKš™—Kš˜—šœ˜ Kšœœ!˜(Kšœ ˜ šœœœ˜9Kšœœ"˜(Kšœœ"˜(Kšœ2¡˜GKšœ)œ˜DKšœ‡˜‹Kš˜—Kšœ˜—Kš¤˜Kš˜—Kš˜—Kšœœœ¤œ˜$Kšœ˜—Kšœ$˜$Kšœ0œ¡œ™Tšœœ œœœœœœ˜†šœœ˜š œ œœœœ¡˜?KšœB˜BKšœP˜PKšœœ˜—Kšœ œœœ1¡˜jKšœ œœ œ&¡˜oKšœ˜—Kšœ˜—Kšœ œ¤œ˜Nšœ˜š¢£¢£¢˜Kš£<˜Kšœ+¤œ˜2—Kš˜—Kš˜—Jšœ˜——šœœœ¡˜;š œœœ!œ œ˜GJšœ7œ¤œ˜[Jšœ˜——Kš œœœœ˜-—Kšœ˜—Kšœ/˜/šœœ˜#Kšœœ¤œ˜4šœ˜ Kšœ%ªœ%™KKšœ œœ˜,Kšœœ œ˜-KšœA˜Aš¢£¢£˜%Kš£C™C—Kš˜—Kšœ˜—Kšœ/˜/šœœ˜#Kšœœ¤œ˜4šœ˜ Kšœ%ªœ%™KKšœ œœ˜,Kšœœ œ˜-KšœA˜Aš¢£¢£˜%Kš£C™C—Kš˜—Kšœ˜—Kšœ2œ˜8Kšœ˜——š œœ œœ œ˜\Kšœ:˜:šœœ˜šœœœ ¡˜*š œœœœœ˜4šœ8˜>Kšœ¤œ˜—Jšœ˜——Kšœ˜—Kšœ˜—Kšœœ œœœœœ œœœ˜“KšœJ˜Jš œœœœœ˜:Jšœ;˜;Jš˜—Kšœ˜—Kšœ˜Kšœ¡˜—Nšœ˜šœ˜Kš œ œœœ¤œ˜SKšœ¥œ˜Kšœ$¥¤œ˜,šœ˜KšœQ˜QKšœœœ¤œ˜.K˜Kšœ)˜)Kšœ3˜3Kšœ<˜šœ˜JšÐbsœ™!Jš®œ ™ IitemšœÒ©œ3©œ™•šœ$™)Kšœ=™=Kšœ?™?šœœœ™-Kšœœ™*šœ œ™Kšœ<™Kšœ œœ™:K™8KšœE™EKšœg™gKšœ Ÿœk™xJš™—Jšœ™—šœ˜ Kšœ=˜=Kšœ?˜?šœœœ˜-Kšœœ˜*šœ œ™Kšœ<™šœ œ˜Kšœœ1˜:Kšœ˜—Kšœ¡ ˜—š œ˜!Kšœœ$œœ™>šœ œ˜Kšœœœ˜Kšœ.˜5—Kšœ¡˜ —š  œ"˜0Kšœœœœ™5K™šœ˜)šœ˜š œ$œ'œ œœ˜zKšœN˜NKšœœ œ œ˜4Kšœ˜——Kšœ%œ˜*Kšœ=˜D—Kšœ¡ ˜—š œ"˜5Kšœœœœ™5šœ˜)šœ˜š œ$œ'œ œœ˜zKšœN˜NKšœB™BKšœ˜šœ˜Kšœ<œ ˜HKšœœ˜&—Kšœ˜——Kšœ%œ˜*KšœB˜I—Kšœ¡˜—Nš œœœ¤œœ˜šœ œ˜Kš œœœœœ˜Tšœ¡.Ðce¡˜HKšœD˜D——Kšœ¡˜—NšœD˜DKšœœK˜gKšœ¡ ˜—š  œœ ˜6Kšœx™xš œ˜$Kšœœ$œœ™>šœ œ˜Kšœœ>˜HKšœœ¡˜‘—Kšœ¡ ˜—Nšœ0œ˜;Kšœ¡˜—š œœ ˜;KšœC™Cš œ˜#Kšœœ$œœ™>Kšœ>˜>šœ œ˜šœœœœ˜0Kšœ˜KšœLœ ˜XKšœ˜Kšœ˜—Kšœ˜—Kšœ¡ ˜—š œ˜#Kšœœ™šœ œ˜š œœœœœ˜Dšœ˜ Kšœ˜KšœLœ ˜XKšœ˜Kšœ˜——Kšœœ¡˜,—Kšœ¡ ˜—Nšœ/œ˜:Kšœ¡˜—š œœ ˜:Kš°œz™‰Lšœœ%˜<š œ˜,Kšœœ$œœ™>šœ œ˜Kšœœ8˜AKšœ˜—Kšœ¡˜—Nšœ^œ˜iKšœ¡˜——™š œœ.˜@Kšœt™tLšœœ%˜Kšœœ˜"Lšœœ%˜Kšœœ˜"Lšœœ%˜