DIRECTORY Atom USING [GetPName], CD USING [backgroundLayer, commentLayer, errorLayer, Layer, LayerKey, NewLayer, Number, Object, outlineLayer, Position, Rect, selectionLayer, shadeLayer, Technology, undefLayer], CDAtomicObjects USING [AtomicObsSpecific, DrawList], CDBasics USING [highposition, MapRect, minposition, NonEmpty], CDOps USING [LayerRope], CDProperties USING [GetObjectProp, PutObjectProp, RegisterProperty], CDRects USING [CreateRect], CDSimpleRules USING [MaxWidth, MinDist, MinWidth, NotKnown], CMosB USING [cmosB, cut, cut2, lambda, met, met2, ndif, nwell, nwellCont, ovg, pdif, pol, pwell, pwellCont, wndif, wpdif], CoreGeometry USING [BBox, CellInstance, EachInstanceProc, EnumerateGeometry, FlattenInstance, Instance, Instances, HasGeometry, Layer, Object, PutGeometry, Rect], CoreProperties USING [propPrint, PropPrintProc, Props, RegisterProperty, StoreProperties], CoreOps USING [GetShortWireName], CoreView USING [AddRectangle, debugViewer], CStitching USING [all, Area, ChangeRect, Rect, EnumerateArea, ResetTesselation, ChangeEnumerateArea, ListArea, NewTesselation, RectProc, TileProc, Region, Tesselation, Tile], Drc USING [AtomicWireHull, CellProc, CoreCell, MarkError, State, Tech, Transf, WirePairProc, WireProc], DrcCMOSB USING [], DrcDebug USING [break, debug, dLog, pause, trace], IO USING [atom, card, int, Put1, PutF, PutFR, rope], Rope USING [Cat, IsEmpty, ROPE], UserProfile USING [Boolean, CallWhenProfileChanges, ProfileChangedProc]; DrcCMOSBimpl: CEDAR PROGRAM IMPORTS Atom, CD, CDBasics, CDOps, CDProperties, CDRects, CDSimpleRules, CMosB, CoreGeometry, CoreOps, CoreProperties, CoreView, CStitching, Drc, DrcDebug, IO, Rope, UserProfile EXPORTS DrcCMOSB SHARES Drc ~ BEGIN OPEN CMosB, Drc; cMosBsimple, cMosBcomplete: PUBLIC Tech; simpleCheck: ATOM ~ CoreProperties.RegisterProperty [$simpleGenista]; completeCheck: ATOM ~ CoreProperties.RegisterProperty [$completeGenista]; CdInsts: TYPE ~ CoreGeometry.Instances; CdObj: TYPE ~ CoreGeometry.Object; CoreInst: TYPE ~ CoreGeometry.CellInstance; FakeInst: TYPE ~ CoreGeometry.Instance; Layer: TYPE ~ CoreGeometry.Layer; Rect: TYPE ~ CoreGeometry.Rect; ROPE: TYPE ~ Rope.ROPE; Region: TYPE ~ LIST OF REF CStitching.Region; Tess: TYPE ~ CStitching.Tesselation; Tile: TYPE ~ CStitching.Tile; empty: REF ~ NIL; nothing: REF INT ~ NEW [INT]; rectClass: ATOM ~ $Rect; aRectClassP: ATOM ~ $C2PDifRect; aRectClassN: ATOM ~ $C2NDifRect; 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 ~ CD.NewLayer [cmosB, gateKey]; fieldOxide: REF ANY ~ NIL; illegalLayer: ARRAY Layer OF BOOL _ ALL [TRUE]; specialLayers: Layer ~ MAX [CD.shadeLayer, CD.errorLayer, CD.backgroundLayer, CD.outlineLayer, CD.selectionLayer, CD.commentLayer]; maxSep: CD.Number; -- convenience lambda: CD.Number ~ CMosB.lambda; ignoreConnectivity: BOOL _ UserProfile.Boolean ["Genista.EmulateMayday", FALSE]; Rule: TYPE ~ RECORD [extent: CD.Number, msg: ROPE]; viaOnFieldOxideAvoidsDiff: Rule ~ [2 * lambda, "separation to diff (advisory)"]; viaOnFieldOxideAvoidsPoly: Rule ~ [2 * lambda, "separation to poly"]; fieldOxideSurroundsViaOnFieldOxide: Rule ~ [MAX [viaOnFieldOxideAvoidsDiff.extent, viaOnFieldOxideAvoidsPoly.extent], "separation to poly or diff"]; diffSurroundsViaOnDiff: Rule ~ [2 * lambda, "insufficient diff surround (advisory)"]; polySurroundsViaOnPoly: Rule ~ [3 * lambda, "insufficient poly surround"]; viaOnPolyAndDiff: Rule ~ [1 * lambda, "topology not flat"]; -- more for the sake of robustness viaSeparation: Rule ~ [1 * lambda, "via to via separation"]; -- only overlaps checked viaOverGate: Rule ~ [1 * lambda, "via not allowed over gate"]; viaOverPoly: Rule ~ [1 * lambda, "via not allowed over poly"]; diffCutToGate: CD.Number ~ 2 * lambda; -- rule 6.5.1.6 largeDiffCutToGate: CD.Number ~ 3 * lambda; -- rule 6.5.1.6 substrateContToGate: CD.Number ~ 3 * lambda; -- rule 6.5.2.3 wellContToGate: CD.Number ~ 3 * lambda; -- rule 6.5.2.3 gateToGate: CD.Number ~ (5 * lambda) / 2; -- 2.5 l [assume l = 0 (mod 2)] IsCut: PROC [layer: Layer] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(layer = cut) OR (layer = cut2)] END; -- IsCut IsWell: PROC [layer: Layer] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(layer = pwell) OR (layer = nwell)] END; -- IsWell IsAbstract: PROC [layer: Layer] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(layer = wndif) OR (layer = wpdif)] END; -- IsAbstract SameRect: PROC [r1, r2: Rect, l1, l2: Layer] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(l1 = l2) AND (r1 = r2)] END; -- SameRect Intersecting: PROC [r1, r2: Rect] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(r1.x1 <= r2.x2) AND (r2.x1 <= r1.x2) AND (r1.y1 <= r2.y2) AND (r2.y1 <= r1.y2)] END; -- Intersecting IntersectingOpen: PROC [r1, r2: Rect] RETURNS [BOOL] ~ INLINE BEGIN RETURN [(r1.x1 < r2.x2) AND (r2.x1 < r1.x2) AND (r1.y1 < r2.y2) AND (r2.y1 < r1.y2)] END; -- IntersectingOpen Intersection: PROC [r1, r2: Rect] RETURNS [Rect] ~ INLINE BEGIN RETURN [[MAX [r1.x1, r2.x1], MAX [r1.y1, r2.y1], MIN [r1.x2, r2.x2], MIN [r1.y2, r2.y2]]] END; -- Intersection Size: PROC [r: CD.Rect] RETURNS [s: CD.Position] ~ INLINE BEGIN s.x _ (r.x2 - r.x1); s.y _ (r.y2 - r.y1) END; -- Size Bloat: PROC [r: Rect, a: CD.Number] RETURNS [Rect] ~ INLINE BEGIN RETURN [[(r.x1 - a), (r.y1 - a), (r.x2 + a), (r.y2 + a)]] END; -- Bloat DeleteRect: PROC [plane: Tess, rect: Rect] ~ BEGIN plane.ChangeRect [rect, empty] END; LayerName: PROC [l: Layer] RETURNS [ROPE] ~ INLINE BEGIN RETURN [Atom.GetPName [CD.LayerKey [l]]] END; -- LayerName PrintChecked: CoreProperties.PropPrintProc ~ BEGIN to.Put1 [IO.rope ["Verified by Genista. "]] END; -- PrintChecked EmulateMayday: UserProfile.ProfileChangedProc ~ BEGIN ignoreConnectivity _ UserProfile.Boolean ["Genista.EmulateMayday", FALSE] END; -- EmulateMayday AddDrcProcs: PUBLIC PROC [tech: ATOM, w: WireProc _ NIL, wp: WirePairProc _ NIL, c: CellProc _ NIL] ~ BEGIN SELECT tech FROM cMosBsimple.checkedBy => BEGIN IF (w # NIL) THEN cMosBsimple.verifyWire _ w; IF (wp # NIL) THEN cMosBsimple.verifyWirePair _ wp; IF (c # NIL) THEN cMosBsimple.verifyCell _ c END; cMosBcomplete.checkedBy => BEGIN IF (w # NIL) THEN cMosBcomplete.verifyWire _ w; IF (wp # NIL) THEN cMosBcomplete.verifyWirePair _ wp; IF (c # NIL) THEN cMosBcomplete.verifyCell _ c END; ENDCASE => ERROR END; -- AddDrcProcs SimpleWidthCheck: WireProc ~ BEGIN VerifyRect: CoreGeometry.EachInstanceProc ~ BEGIN min, max, a, b: CD.Number; o: CdObj ~ instance.obj; l: Layer ~ o.layer; r: Rect ~ CoreGeometry.BBox [instance]; 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 illegalLayer[l] THEN BEGIN MarkError [cell, state, [r, Rope.Cat ["Illegal layer ", LayerName [l], " (wire ", CoreOps.GetShortWireName[w], ")"]]]; RETURN END; min _ CDSimpleRules.MinWidth [l]; max _ CDSimpleRules.MaxWidth [l]; 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, Rope.Cat ["Width violation on layer ", Atom.GetPName [CD.LayerKey [l]], " (wire ", CoreOps.GetShortWireName[w], ")"]]] END; -- VerifyRect [] _ state.attributes.EnumerateGeometry [w, VerifyRect] END; -- SimpleWidthCheck maxContSize: CD.Number ~ CDSimpleRules.MaxWidth [cut]; minContSize: CD.Number ~ CDSimpleRules.MinWidth [cut]; maxViaSize: CD.Number ~ CDSimpleRules.MaxWidth [cut2]; minViaSize: CD.Number ~ CDSimpleRules.MinWidth [cut2]; splitContWidth: CD.Number ~ minContSize; splitContHeight: CD.Number ~ maxContSize + lambda; minPadSize: CD.Number ~ 117 * lambda; FullWireCheck: WireProc ~ BEGIN VerifyRect: CoreGeometry.EachInstanceProc ~ BEGIN min, max, a, b: CD.Number; o: CdObj ~ instance.obj; l: Layer ~ o.layer; r: Rect ~ CoreGeometry.BBox [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 $C2SimpleCon, $C2WellSimpleCon, $C2LargeSimpleCon, $C2LargeWellSimpleCon, $C2DifShortCon, $C2WellDifShortCon, $C2Via, $C2LargeVia => BEGIN VerifyContact [o, r]; RETURN END; markClass, segmentClass, pinClass => RETURN; $CLWellTrans => BEGIN MarkError [cell, state, [r, "Antique transistor class $CLWellTrans is illegal"]]; RETURN END; $C2Trans, $C2WellTrans, $C2LTrans, $C2LWellTrans => BEGIN MakeTransistor [o, cell, state, r]; RETURN -- Atomic object correct by construction END; ENDCASE => BEGIN quit _ CoreGeometry.FlattenInstance [instance, VerifyRect]; RETURN END; IF DrcDebug.debug THEN CDProperties.PutObjectProp [o, DrcDebug.trace, DrcDebug.trace]; IF 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 ", CoreOps.GetShortWireName[w], ")"]]]; RETURN END; min _ CDSimpleRules.MinWidth [l]; max _ CDSimpleRules.MaxWidth [l]; 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 MarkError [cell, state, [r, Rope.Cat ["Width violation on layer ", Atom.GetPName [CD.LayerKey [l]], " (wire ", CoreOps.GetShortWireName[w], ")"]]] END; -- VerifyRect VerifyContact: PROC [contact: CdObj, bb: Rect] ~ BEGIN size: CD.Position; sizeExceeded: BOOL _ FALSE; classKey: ATOM ~ contact.class.objectType; 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, $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 ", CoreOps.GetShortWireName[w], ")"]]] END; -- VerifyContact [] _ state.attributes.EnumerateGeometry [w, VerifyRect] END; -- FullWireCheck MakeTransistor: PROC [obj: CdObj, cell: CoreCell, state: State, bb: Rect] ~ BEGIN MakeInst: PROC [r: Rect, l: Layer] RETURNS [CoreGeometry.Instance] ~ INLINE BEGIN RETURN [[CDRects.CreateRect [Size[r], l], [[r.x1, r.y1], original]]] END; -- MakeInst tClass: ATOM ~ obj.class.objectType; isNType: BOOL ~ (obj.layer = ndif); source, drain, channel: CoreGeometry.Instances; sep: CD.Number ~ CDSimpleRules.MinDist [ndif, pol]; difToPolExtSep: CD.Number ~ 0; -- polSpacing - extensionLength; extensionLength: CD.Number ~ 3 * lambda; -- source/drain extension [rule 6.3.18] extSep: CD.Number ~ difToPolExtSep; rect: Rect; polList, difList, chList, difListSouth: LIST OF Rect _ NIL; length, width, extL, extW: CD.Number; IF state.attributes.HasGeometry [cell.public[0]] AND state.attributes.HasGeometry [cell.public[1]] AND state.attributes.HasGeometry [cell.public[2]] THEN RETURN; IF ISTYPE [obj.specific, CDAtomicObjects.AtomicObsSpecific] THEN FOR geom: CDAtomicObjects.DrawList _ NARROW [obj.specific, CDAtomicObjects.AtomicObsSpecific].rList, geom.rest WHILE geom # NIL DO SELECT geom.first.layer FROM pol => polList _ CONS [geom.first.r, polList]; ndif, pdif => difList _ CONS [geom.first.r, difList]; nwell, pwell => NULL; ENDCASE => MarkError [cell, state, [geom.first.r, "Unknown transistor geometry"]] ENDLOOP ELSE MarkError [cell, state, [bb, "Replace this old Chipmonk transistor"]]; SELECT tClass FROM $C2Trans, $C2WellTrans => BEGIN -- straight transistors difRect, polRect, chRect, difExtRectNorth, difExtRectSouth, polExtEast, polExtWest: Rect; difRect _ difList.first; polRect _ polList.first; chRect _ [difRect.x1, polRect.y1, difRect.x2, polRect.y2]; difExtRectNorth _ difExtRectSouth _ difRect; difExtRectNorth.y1 _ polRect.y2; difExtRectSouth. y2 _ polRect.y1; polExtWest _ [polRect.x1, polRect.y1, difRect.x1, polRect.y2]; polExtEast _ [difRect.x2, polRect.y1, polRect.x2, polRect.y2]; length _ polRect.y2 - polRect.y1; width _ difRect.x2 - difRect.x1; extL _ polRect.y1 - difRect.y1; extW _ difRect.x1 - polRect.x1; IF (extL < extensionLength) THEN MarkError [cell, state, [bb, "Extension length too small"]]; channel _ LIST [MakeInst [polExtEast, pol], MakeInst [polExtWest, pol], MakeInst [chRect, gate]]; source _ LIST [MakeInst [difExtRectNorth, obj.layer]]; drain _ LIST [MakeInst [difExtRectSouth, obj.layer]]; END; -- case $CTrans $C2LTrans, $C2LWellTrans => BEGIN -- angle transistors diffNE: CD.Position _ CDBasics.minposition; diffSW, polSW: CD.Position _ CDBasics.highposition; polHor, polVert, polExtWest, polExtNorth, chRectH, chRectV: Rect; IF ((polList.first.y2-polList.first.y1) < (polList.rest.first.y2-polList.rest.first.y1)) THEN {polHor _ polList.first; polVert _ polList.rest.first} ELSE {polHor _ polList.rest.first; polVert _ polList.first}; FOR diff: LIST OF Rect _ difList, diff.rest WHILE diff # NIL DO IF (diff.first.x1 <= diffSW.x) AND (diff.first.y1 <= diffSW.y) THEN diffSW _ [diff.first.x1, diff.first.y1]; IF (diff.first.x2 >= diffNE.x) AND (diff.first.y2 >= diffNE.y) THEN diffNE _ [diff.first.x2, diff.first.y2]; ENDLOOP; polSW _ [polHor.x1, polHor.y1]; extW _ diffSW.x - polSW.x; extL _ polSW.y - diffSW.y; length _ polHor.y2 - polHor.y1; IF (extL < extensionLength) THEN MarkError [cell, state, [bb, "Extension length too small"]]; polExtWest _ [polSW.x, polSW.y, diffSW.x, polHor.y2]; polExtNorth _ [diffNE.x-extL-length, diffNE.y, diffNE.x-extL, polHor.y2]; chRectH _ polHor; chRectH.x1 _ chRectH.x1 + extW; chRectV _ polVert; chRectV.y1 _ chRectV.y1 + length; chRectV.y2 _ chRectV.y2 - extW; channel _ LIST [MakeInst [polExtWest, pol], MakeInst [polExtNorth, pol], MakeInst [chRectH, gate], MakeInst [chRectV, gate]]; BEGIN -- Bogus but first approx. for a fast impl. d: CD.Number _ extL + length + sep; rect _ [x1: diffSW.x, y1: diffSW.y+extL+length, x2: diffNE.x-extL-length, y2: diffSW.y+d]; source _ LIST [MakeInst [rect, obj.layer]]; -- North rect _ [x1: diffNE.x-d, y1: diffSW.y+extL+length, x2: diffNE.x-extL-length, y2: diffNE.y]; source _ CONS [MakeInst [rect, obj.layer], source]; -- West d _ extL - sep; rect _ [x1: diffSW.x, y1: diffSW.y+d, x2: diffNE.x-d, y2: diffSW.y+extL]; drain _ LIST [MakeInst [rect, obj.layer]]; -- South rect _ [x1: diffNE.x-extL, y1: diffSW.y+d, x2: diffNE.x-d, y2: diffNE.y]; drain _ CONS [MakeInst [rect, obj.layer], drain] -- East END -- ch lead-in END; -- case $C2LTrans, $C2LWellTrans ENDCASE => MarkError [cell, state, [bb, "Unknown or antique transistor class"]]; state.attributes.PutGeometry [cell.public[0], channel]; state.attributes.PutGeometry [cell.public[1], source]; state.attributes.PutGeometry [cell.public[2], drain] END; -- MakeTransistor SimpleMaterialSeparation: WirePairProc ~ BEGIN aequipotential: BOOL ~ (w1.global = w2.global); r1, r2, b1, b2: Rect; l1, l2: Layer; o1, o2: CdObj; 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 (illegalLayer[l2]) THEN RETURN; r2 _ CDBasics.MapRect [CoreGeometry.BBox [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 _ CDSimpleRules.MinDist [l1, l2 ! CDSimpleRules.NotKnown => {sep _ 0; ERROR}]; 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 msg: ROPE ~ "Separation violation between "; n1: ROPE ~ LayerName[l1].Cat [" (wire ", CoreOps.GetShortWireName[w1.local], ")"]; n2: ROPE ~ LayerName[l2].Cat [" (wire ", CoreOps.GetShortWireName[w2.local], ")"]; MarkError [cell, state, [Intersection [b1, b2], msg.Cat [n1, " 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 (illegalLayer[l1]) THEN RETURN; r1 _ CDBasics.MapRect [CoreGeometry.BBox [instance], w1.transf]; quit _ state.attributes.EnumerateGeometry [w2.local, VerifyInner] END; -- VerifyOuter IF (Intersecting [(Bloat [AtomicWireHull[w1, state], maxSep]), (Bloat [AtomicWireHull[w2, state], maxSep])]) THEN [] _ state.attributes.EnumerateGeometry [w1.local, VerifyOuter] END; -- SimpleMaterialSeparation cachedTess1, cachedTess2: Tess; -- Assume: no concurrency !!! 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: Tess ~ IF (cachedTess1 # NIL) THEN cachedTess1 ELSE CStitching.NewTesselation [stopFlag: state.abort]; materialTess: Tess ~ IF (cachedTess2 # NIL) THEN cachedTess2 ELSE CStitching.NewTesselation [stopFlag: state.abort]; currentTransf: Transf; impiccatiUno, impiccatiDue, strozzatiUno, strozzatiDue: BOOL _ FALSE; VerifyOuter: CoreGeometry.EachInstanceProc ~ BEGIN r1: Rect; o1: CdObj ~ instance.obj; l1: Layer ~ o1.layer; VerifyInner: CoreGeometry.EachInstanceProc ~ BEGIN r2, b1, b2: Rect; sep: CD.Number; o2: CdObj ~ instance.obj; l2: Layer ~ o2.layer; quit _ state.abort^; SELECT o2.class.objectType FROM rectClass => IF (l2 <= specialLayers) OR (illegalLayer[l2]) OR ((IsWell [l1]) AND (IsWell [l2])) THEN RETURN; aRectClassP, aRectClassN => BEGIN quit _ CoreGeometry.FlattenInstance [instance, VerifyInner]; RETURN END; markClass, segmentClass, pinClass => RETURN; ENDCASE => BEGIN -- vedasi commento al livello pi u esterno impiccatiDue _ ((o2.class.objectType = $C2SimpleCon) AND (l2 = ndif)) OR ((o2.class.objectType = $C2WellSimpleCon) AND (l2 = pdif)); strozzatiDue _ ((o2.class.objectType = $C2LargeSimpleCon) AND (l2 = ndif)) OR ((o2.class.objectType = $C2LargeWellSimpleCon) AND (l2 = pdif)); quit _ CoreGeometry.FlattenInstance [instance, VerifyInner]; RETURN END; IF (IsAbstract [l1] OR IsAbstract [l2]) OR ((o1.class.objectType # rectClass) OR (o2.class.objectType # rectClass)) THEN SIGNAL DrcDebug.break; -- should never happen r2 _ CDBasics.MapRect [CoreGeometry.BBox [instance], w2.transf]; IF (l2 = cut2) THEN CStitching.ChangeEnumerateArea [viaTess, r2, OccupyTile, NEW [ViaTileDataRec], nothing]; IF (IsCut [l1] AND IsCut [l2]) THEN {IF (SameRect [r1, r2, l1, l2]) THEN RETURN} ELSE BEGIN IF ignoreConnectivity THEN {IF (Intersecting [r1, r2]) THEN RETURN} ELSE {IF aequipotential THEN RETURN} END; IF (l1 = gate) OR (l2 = gate) THEN BEGIN otherLayer: Layer ~ IF (l1 = gate) THEN l2 ELSE l1; sep _ SELECT otherLayer FROM gate => gateToGate, nwellCont => wellContToGate, pwellCont => substrateContToGate, cut => SELECT TRUE FROM (impiccatiUno OR impiccatiDue) => diffCutToGate, (strozzatiUno OR strozzatiDue) => largeDiffCutToGate, ENDCASE => 0, ENDCASE => 0 END ELSE sep _ CDSimpleRules.MinDist [l1, l2 ! CDSimpleRules.NotKnown => {sep _ 0; DrcDebug.break}]; IF (sep = 0) THEN RETURN; b1 _ Bloat [r1, sep / 2]; b2 _ Bloat [r2, sep / 2]; 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]]; DrcDebug.break END; IF IntersectingOpen [b1, b2] THEN BEGIN msg: ROPE ~ "Separation violation between "; name1: ROPE _ CoreOps.GetShortWireName [w1.local]; name2: ROPE _ CoreOps.GetShortWireName [w2.local]; n1, n2: ROPE; IF name1.IsEmpty THEN name1 _ CoreOps.GetShortWireName [w1.global]; IF name2.IsEmpty THEN name2 _ CoreOps.GetShortWireName [w2.global]; 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; MarkError [cell, state, [Intersection [b1, b2], msg.Cat [n1, " and ", n2]]] END; quit _ state.abort^ END; -- VerifyInner quit _ state.abort^; SELECT o1.class.objectType FROM rectClass => IF (l1 <= specialLayers) OR (illegalLayer[l1]) THEN RETURN; aRectClassP, aRectClassN => BEGIN quit _ CoreGeometry.FlattenInstance [instance, VerifyOuter]; RETURN END; markClass, segmentClass, pinClass => RETURN; ENDCASE => BEGIN -- vedasi commento al livello pi u esterno impiccatiUno _ ((o1.class.objectType = $C2SimpleCon) AND (l1 = ndif)) OR ((o1.class.objectType = $C2WellSimpleCon) AND (l1 = pdif)); strozzatiUno _ ((o1.class.objectType = $C2LargeSimpleCon) AND (l1 = ndif)) OR ((o1.class.objectType = $C2LargeWellSimpleCon) AND (l1 = pdif)); quit _ CoreGeometry.FlattenInstance [instance, VerifyOuter]; RETURN END; r1 _ CDBasics.MapRect [CoreGeometry.BBox [instance], w1.transf]; IF (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 _ CDBasics.MapRect [CoreGeometry.BBox [instance], currentTransf]; IF NOT (CDBasics.NonEmpty [r]) THEN RETURN; -- empty rectangle SELECT instance.obj.layer FROM ndif, pdif, pwellCont, nwellCont => BEGIN bloatedRect _ Bloat [r, 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, viaOverGate.msg]]; DeleteRect [viaTess, v.first.rect] END ENDLOOP; bloatedRect _ Bloat [r, 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; bloatedRect _ Bloat [v.first.rect, diffSurroundsViaOnDiff.extent]; CStitching.ChangeEnumerateArea [materialTess, Intersection [bloatedRect, r], OccupyTile, data, nothing] ENDLOOP END; pol => BEGIN bloatedRect _ Bloat [r, 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]; IF via.hasDiff THEN BEGIN MarkError [cell, state, [v.first.rect, viaOverGate.msg]]; DeleteRect [viaTess, v.first.rect] END ENDLOOP; bloatedRect _ Bloat [r, 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, 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 genericDiff => via.hasDiff _ TRUE; polyKey => via.hasPoly _ TRUE; ENDCASE => ERROR END END; -- Accumulate via.hasFOx _ NOT (via.hasDiff OR via.hasPoly); SELECT TRUE FROM via.hasDiff => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, diffSurroundsViaOnDiff.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasFOx THEN IF IsOnFieldOxide[] THEN MarkError [cell, state, [rect, viaOnFieldOxideAvoidsDiff.msg]] ELSE MarkError [cell, state, [rect, diffSurroundsViaOnDiff.msg]] END; via.hasPoly => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, polySurroundsViaOnPoly.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasFOx THEN IF IsOnFieldOxide[] THEN MarkError [cell, state, [rect, viaOnFieldOxideAvoidsPoly.msg]] ELSE MarkError [cell, state, [rect, polySurroundsViaOnPoly.msg]] END; via.hasFOx => BEGIN CStitching.EnumerateArea [plane: materialTess, rect: Bloat [rect, fieldOxideSurroundsViaOnFieldOxide.extent], eachTile: Accumulate, data: via, skip: $doNotSkipAnything]; IF via.hasDiff THEN MarkError [cell, state, [rect, viaOnFieldOxideAvoidsDiff.msg]]; IF via.hasPoly THEN MarkError [cell, state, [rect, viaOnFieldOxideAvoidsPoly.msg]] END; ENDCASE => NULL -- no violation END; -- LookUnderneath IF (Intersecting [(Bloat [AtomicWireHull[w1, state], maxSep]), (Bloat [AtomicWireHull[w2, state], maxSep])]) THEN [] _ state.attributes.EnumerateGeometry [w1.local, VerifyOuter]; currentTransf _ w1.transf; [] _ state.attributes.EnumerateGeometry [w1.local, FindMaterial]; currentTransf _ w2.transf; [] _ state.attributes.EnumerateGeometry [w2.local, FindMaterial]; CStitching.EnumerateArea [plane: viaTess, rect: CStitching.all, eachTile: LookUnderneath, data: state, skip: empty]; CStitching.ResetTesselation [viaTess]; CStitching.ResetTesselation [materialTess] END; -- CompleteSeparation ComputeMaxSeparation: PROC [target: ATOM] RETURNS [max: CD.Number] ~ BEGIN sep: CD.Number; max _ 0; FOR s1: Layer IN Layer DO IF illegalLayer[s1] THEN LOOP; FOR s2: Layer IN Layer DO IF illegalLayer[s2] THEN LOOP; SELECT target FROM cMosBsimple.checkedBy => NULL; -- all standard cMosBcomplete.checkedBy => IF (IsWell [s1] AND IsWell [s2]) THEN LOOP; ENDCASE => ERROR; sep _ CDSimpleRules.MinDist [s1, s2 ! CDSimpleRules.NotKnown => LOOP]; max _ MAX [max, sep] ENDLOOP ENDLOOP END; -- ComputeMaxSeparation [] _ CDProperties.RegisterProperty [simpleCheck, $gbb]; [] _ CDProperties.RegisterProperty [completeCheck, $gbb]; [] _ CDProperties.RegisterProperty [gateKey, $gbb]; CoreProperties.StoreProperties [prop: simpleCheck, properties: CoreProperties.Props [[CoreProperties.propPrint, NEW [CoreProperties.PropPrintProc _ PrintChecked]]]]; CoreProperties.StoreProperties [prop: completeCheck, properties: CoreProperties.Props [[CoreProperties.propPrint, NEW [CoreProperties.PropPrintProc _ PrintChecked]]]]; IF (CD.undefLayer # 0) THEN ERROR; -- check the definition of specialLayers illegalLayer[ndif] _ illegalLayer[pdif] _ illegalLayer[pwell] _ illegalLayer[nwell] _ illegalLayer[pwellCont] _ illegalLayer[nwellCont] _ illegalLayer[pol] _ illegalLayer[met] _ illegalLayer[met2] _ illegalLayer[cut] _ illegalLayer[cut2] _ illegalLayer[ovg] _ illegalLayer[gate] _ FALSE; maxSep _ ComputeMaxSeparation [cMosBsimple.checkedBy]; cMosBsimple _ [simpleCheck, maxSep, lambda, SimpleWidthCheck, SimpleMaterialSeparation]; cMosBcomplete.checkedBy _ completeCheck; cMosBcomplete.maxSeparation _ ComputeMaxSeparation [cMosBcomplete.checkedBy]; cMosBcomplete.lambda _ lambda; cMosBcomplete.verifyWire _ FullWireCheck; cMosBcomplete.verifyWirePair _ CompleteSeparation; UserProfile.CallWhenProfileChanges [EmulateMayday] END. DrcCMOSBimpl.Mesa Copyright Ó 1987 by Xerox Corporation. All rights reserved. Written by gbb, January 12, 1987 11:55:49 am PST gbb March 27, 1987 12:10:10 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. Via flatness rules In  units from the minimal metal border of the via (not from the cut). In the following rules the extent is used only to determine the overlap of the error rectangle. Other rules Utilities r1 and r2 are assumed to be closed. r1 and r2 are assumed to be open. r1 and r2 are assumed to be closed and intersecting. r1 and r2 are assumed to be closed and intersecting. Only one implementation can own the variable, other have to use this procedure. If a proc is NIL, it is not set. 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. 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] aRectClassP, aRectClassN => BEGIN quit _ CoreGeometry.FlattenInstance [instance, VerifyRect]; RETURN END; VerifyContact does all necessary verifications, no "flattening" necessary. The width rules for cuts depend on the class. DrcImpl executes this procedure before it calls the WirePairProc. Ignore wells since all of Core ignores them, so what the heck, it's a hack anyway ! this constant used to be zero and was used to control the separation between transistor gates, the separation of well and substrate contacts to unrelated diffusion. Grow terms are packed and may not be negative. Therefore unmade change. Get the geometry. Streching information has already been procesed by ChipNDale. Process the geometry according to the transistor class. The ChipNDale transistors are fully supported for p substrate. Process channel lead-in Separation Verification Procedures [cell: CoreCell, w1, w2: WireInstance, 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, 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. 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 mi 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. Dato che uno e forzatamente un transistor, ce ne freghiamo. 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. We insert material in the whole influence area of a via. Note that via always is a single and non-degenerated via, since collisions of vias are detected when the vias are input. We insert material in the whole influence area of a via. Looks what is under a via cut. Is the via on field oxide ? At this point we know, what is immediately under the via cut and that there the rule viaOverGate is not violated. 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. Initialisation Conservative (looks at all layers, not only the legal ones). Extractor cannot handle wells adequately. Try to filter out inappropriate layers. Ê›˜codešœ™Kšœ<™Kšœœ ˜Kšœ œ2˜DKšœœ˜Kšœœ)˜˜>Nšœ>˜>—™ Lšœœ ˜6Nšœœ ˜;Nšœœ ˜˜’—Kšœ  ˜—Nšœ7˜7Kšœ ˜—Lšœ œ'˜6Kšœ œ'˜6Kšœ œ(˜6Kšœ œ(˜6Kšœœ˜(Kšœœ˜2Kšœ œ˜%š¢ œ ˜Kšœ'™'K™,š¢ œ"˜1Kšœ2œœœ™RK™´Kšœœ˜Kšœ˜Kšœ˜Lšœ'˜'Lšœœ˜šœœ˜Lšœ$œ˜BLš œLœ*œ*œœ'œ ˜ïšœ3œœ˜MKšœ/™/—Kšœ˜—šœ˜Kš œ œœ œ£œ '˜hšœ™!Kšœ<£™BKšœ™—šœ…˜ŠKšœ£˜KšŸ œ=™JKšœ˜—Kšœ$¤£œ˜,šœ˜KšœQ˜QKš£˜Kšœ˜—šœ4˜9Kšœ#˜#Kš£œ (˜/Kšœ˜—šœ˜Kšœ<£˜BKšœ˜——Nšœœ@˜Vš œœ œœœ˜aKšœv˜vKš£˜Kšœ˜—NšœC˜CKšœœ˜Kšœœ ˜8š œ œ œ œ ˜8KšœRœ>˜’—Kšœ  ˜—š¢ œœ˜6K™-Kšœœ ˜Kšœœœ˜Kšœ œ˜*š œ"œHœœ˜†šœ˜šœœ ˜Kšœ˜šœ ˜˜%Kš œœœ$œœ%˜t—Kš œ œœœœ˜Š—Kšœ˜—šœœ ˜Kšœ˜šœœ˜6Kš œœœœœ˜{—Kšœ˜—Kšœ˜—Kšœ˜—Kšœ œŽ˜¢Kšœ ˜—Nšœ7˜7Kšœ ˜—š¢œœ8˜QKšœ4Ÿ œU™•š ¢œœœœ˜QKšœ>˜DKšœ  ˜—Kšœœ˜$Kšœ œ˜#Kšœ/˜/Kšœœ,˜3šœœ   ˜?Kš í™í—Lšœœ '˜PKšœœ˜#Kšœ ˜ Kšœ(œœœ˜;Kšœœ˜%Nš œ/œ/œ/œ£œ˜¡N™Ošœœ3˜@š œ"œDœœ˜‚šœ˜Kšœœ˜.Kšœœ˜5Kšœœ˜KšœJ˜Q—Jš˜——KšœG˜KNšœv™všœ˜šœœ ˜7KšœY˜YKšœ1˜1Kšœ:˜:Kšœ,˜,KšœB˜BKšœ>˜>Kšœ>˜>KšœB˜BKšœ?˜?Nšœœ=˜]Kšœ œS˜aKšœ œ)˜6Kšœœ)˜5Kšœ ˜—šœœ ˜6Kšœœ!˜+Kšœœ"˜3KšœA˜AKšœVœ7˜”Kšœ8˜<š œœœœœ˜?šœœ˜CKšœ(˜(—šœœ˜CKšœ(˜(—Jšœ˜—Kšœ˜Kšœ˜Kšœ˜Kšœ˜Nšœœ=˜]Kšœ5˜5KšœI˜IKšœ1˜1Kšœ˜KšœA˜AKšœ œo˜}N™šœ +˜1Kšœœ˜#KšœZ˜ZKšœ œ ˜4KšœZ˜ZKšœ œ' ˜;Kšœ˜KšœI˜IKšœœ ˜3KšœI˜IKšœœ% ˜8Kšœ  ˜—Kšœ  ˜%—NšœI˜P—Kšœ7˜7Kšœ6˜6Kšœ4˜4Kšœ ˜——™"š¢œ˜.Kšœ4™4K™OKšœŸœbŸœŸœ™’Kšœœ˜/Kšœ˜K˜K˜š¢ œ"˜2Kšœœœœ™5š¢ œ"˜2Kšœœœœ™5Kšœœ*˜1Kšœ˜Kšœ#œœ œ˜`Kšœ@˜@š œœ œœ˜/šœ˜Kš œœœœ˜0—Kš œœœœœ˜,Kšœ˜—KšœJœ˜RKšœ œœ˜Kš œœœœ  ˜KKšœ3˜3Kšœœ<˜Ršœœ˜'Kšœœ#˜,KšœœJ˜RKšœœJ˜RKšœK˜KKšœ˜—Kšœ˜Kšœ ˜—Nšœ!˜!Kšœ˜Kšœ#œœ œ˜`Nšœ@˜@KšœA˜AKšœ ˜—šœj˜qKšœ?˜?—Kšœ ˜ —Nšœ  Ðbc ˜=Nšœ œœ˜'Kšœœœ œ œœ  œ œœ œœœ ˜Kšœ œœ˜'Kšœœœ œ˜Aš¢ œ˜'Kšœœ$œœ™>šœ œ˜Kšœœ /˜GKšœ-˜4—Kšœ  ˜—š¢œ˜(Kšœ4™4K™OKšœŸœbŸœŸœ™’Kšœœ˜/Kš œœœœ œ3˜oKš œœœœ œ3˜tKšœ˜šœ8œœ˜ELšœ ¢œŸœÙ™¢—š¢ œ"˜2Kšœœœœ™5Kšœ9˜9š¢ œ"˜2Kšœœœœ™5Kšœœ˜!Kšœ/˜/Kšœ˜šœ˜š œ œœœœœ£œ˜mKšœoÏdœ‚™ó—šœ˜!Kšœ=£˜CKšœ˜—Kšœ$¤£œ˜,šœœ *˜;Kšœ5œœ+œ˜„Kšœ:œœ0œ˜ŽKšœ<˜šœ˜šœ$˜)Kšœ:˜:Kšœ?˜?šœœœ˜-Kšœœ˜*šœ œ˜Kšœ9˜9Kšœ"˜"Kš˜—Jšœ˜—Jšœ7˜7Kšœ?˜?šœœœ˜-Kšœœ˜*Kšœœ'˜>Kšœ œœ˜:K™8KšœB˜BKšœg˜gKšœ Ÿœk™xJš˜—Jšœ˜—šœ˜ Kšœ:˜:Kšœ?˜?šœœœ˜-Kšœœ˜*šœ œ˜Kšœ9˜9Kšœ"˜"Kš˜—Jšœ˜—Jšœ7˜7Kšœ?˜?šœœœ˜-Kšœœ˜*Kšœœ#˜:Kšœ œœ˜:K™8KšœB˜BKšœg˜gJš˜—Jšœ˜—Kšœ˜—Kšœ ˜—š¢œœ #˜OK™Kšœœ˜'Kšœ/˜/š ¢œœœœœœ˜