DIRECTORY Asserting, AssertingIO, Basics, Convert, IO, LichenDataStructure, LichenOps, LichenTransforms, LichenTransformsPrivate, RedBlackTree, Rope; LichenRecognizeArrays: CEDAR PROGRAM IMPORTS Asserting, AssertingIO, Convert, IO, LichenDataStructure, LichenOps, LichenTransformsPrivate, RedBlackTree, Rope EXPORTS LichenDataStructure, LichenOps = BEGIN OPEN LichenDataStructure, LichenOps, LichenTransforms, LichenTransformsPrivate; JointAccount: TYPE = LIST OF JointAccounting; JointAccounting: TYPE = REF JointAccountingRep; JointAccountingRep: TYPE = RECORD [ low, high: PortIndex, eo: EO, used: SEQUENCE length: NAT OF BOOL ]; notPorted: PUBLIC Porting _ NEW [ROPE _ "Not ported"]; unknownPorting: PUBLIC Porting _ NEW [ROPE _ "Unknown porting"]; EOName: PUBLIC ARRAY EO OF ROPE _ [Even: "even", Odd: "odd"]; DimName: PUBLIC ARRAY Dim OF ROPE _ [Foo: "Foo", Bar: "Bar"]; EndName: PUBLIC ARRAY End OF ROPE _ [low: "low", high: "high"]; Fail: ERROR [why: ROPE] = CODE; indexFn: REF ANY _ NEW [ROPE _ "the function from a cell Vertex to its index"]; joinFns: ARRAY EO OF ARRAY BOOL--to high-- OF REF ANY _ [ Even: [ TRUE: NEW [ROPE _ "from low to high across even joint"], FALSE: NEW [ROPE _ "from high to low across even joint"]], Odd: [ TRUE: NEW [ROPE _ "from low to high across odd joint"], FALSE: NEW [ROPE _ "from high to low across odd joint"]]]; Arrayify: PROC [ct: CellType] RETURNS [whyNot: ROPE _ NIL] = { ENABLE Fail => {whyNot _ why; CONTINUE}; a: Array; elts: VertexS; EnsureParts[ct]; IF NOT ExpansionKnown[ct] THEN ERROR; [a, elts] _ InitialSurvey[ct]; MakeConnections[ct, a, elts]; ct.parts _ NIL; ct.mirror _ NIL; ct.asArray _ a; }; InitialSurvey: PROC [ct: CellType] RETURNS [a: Array, elts: VertexS] = { et: CellType; prefix, postfix: ROPE _ NIL; prefixLength, postfixLength: INT _ 0; insides: SymbolTable _ RedBlackTree.Create[GetIDKey, CompareRopes]; nCells, nNets: INT _ 0; SurveyPart: PROC [v: Vertex] = { name: ROPE _ PickAName[v.names]; SELECT v.class FROM net => { nNets _ nNets + 1; }; cell => { nCells _ nCells + 1; v.other _ Asserting.AssertFn1[fn: indexFn, val: NIL, inAdditionTo: v.other]; SELECT nCells FROM =1 => { et _ v.type; prefix _ name; prefixLength _ prefix.Length[]; }; =2 => { nameLength: INT _ name.Length[]; prematch, postmatch: INT; middle: ROPE; IF et # v.type THEN Fail[IO.PutFR["Non-homogeneous (cell types %g and %g present)", IO.rope[PickAName[et.names]], IO.rope[PickAName[v.type.names]]]]; FOR prematch _ 0, prematch + 1 WHILE (prematch < nameLength) AND (prematch < prefixLength) AND (prefix.Fetch[prematch] = name.Fetch[prematch]) DO NULL ENDLOOP; FOR postmatch _ 0, postmatch + 1 WHILE (postmatch < nameLength) AND (postmatch < prefixLength) AND (prefix.Fetch[prefixLength-1-postmatch] = name.Fetch[nameLength-1-postmatch]) DO NULL ENDLOOP; IF prematch + postmatch > nameLength THEN Fail[IO.PutFR["Overlapping match between %g and %g", IO.rope[prefix], IO.rope[name]]]; middle _ prefix.Substr[start: prematch, len: prefixLength - (prematch + postmatch)]; insides.Insert[middle, middle]; postfix _ prefix.Substr[start: prefixLength - postmatch]; prefix _ prefix.Substr[len: prematch]; middle _ name.Substr[start: prematch, len: nameLength - (prematch + postmatch)]; insides.Insert[middle, middle]; prefixLength _ prematch; postfixLength _ postmatch; }; >2 => { nameLength: INT _ name.Length[]; prematch, postmatch: INT; middle: ROPE; IF et # v.type THEN Fail[IO.PutFR["Non-homogeneous (cell types %g and %g present)", IO.rope[PickAName[et.names]], IO.rope[PickAName[v.type.names]]]]; FOR prematch _ 0, prematch + 1 WHILE (prematch < nameLength) AND (prematch < prefixLength) AND (prefix.Fetch[prematch] = name.Fetch[prematch]) DO NULL ENDLOOP; FOR postmatch _ 0, postmatch + 1 WHILE (postmatch < nameLength) AND (postmatch < postfixLength) AND (postfix.Fetch[postfixLength-1-postmatch] = name.Fetch[nameLength-1-postmatch]) DO NULL ENDLOOP; IF prematch + postmatch > nameLength THEN Fail[IO.PutFR["Overlapping match between <%g,,%g> and %g", IO.rope[prefix], IO.rope[postfix], IO.rope[name]]]; IF prematch < prefixLength OR postmatch < postfixLength THEN { newInsides: SymbolTable _ RedBlackTree.Create[GetIDKey, CompareRopes]; pretail: ROPE _ prefix.Substr[start: prematch]; posthead: ROPE _ postfix.Substr[len: postfixLength - postmatch]; Enlarge: PROC [ra: REF ANY] RETURNS [stop: BOOL] = { oldInside: ROPE _ NARROW[ra]; newInside: ROPE _ pretail.Cat[oldInside, posthead]; newInsides.Insert[newInside, newInside]; stop _ FALSE}; insides.EnumerateIncreasing[Enlarge]; insides _ newInsides; prefix _ prefix.Substr[len: prematch]; postfix _ postfix.Substr[start: postfixLength - postmatch]; prefixLength_ prematch; postfixLength _ postmatch; }; middle _ name.Substr[start: prematch, len: nameLength - (prematch + postmatch)]; insides.Insert[middle, middle]; }; ENDCASE => ERROR; }; ENDCASE => ERROR; }; IndexIt: PROC [ra: REF ANY] RETURNS [stop: BOOL] = { inside: ROPE _ NARROW[ra]; name: ROPE _ prefix.Cat[inside, postfix]; index: INT _ Convert.CardFromDecimalLiteral[inside !Convert.Error => Fail[IO.PutFR["Couldn't parse integer in %g[%g]%g", IO.rope[prefix], IO.rope[inside], IO.rope[postfix]]]]; v: Vertex _ ToVertex[ct, name]; IF v = NIL OR v.class # cell THEN ERROR; stop _ FALSE; v.other _ Asserting.AssertFn1[fn: indexFn, val: NEW [INT _ index], inAdditionTo: v.other]; IF a.shape[Foo].min >= a.shape[Foo].maxPlusOne THEN { a.shape[Foo].min _ index; a.shape[Foo].maxPlusOne _ index + 1; elts[0] _ v; } ELSE { IF index < a.shape[Foo].min THEN { delta: NAT _ a.shape[Foo].min - index; FOR i: NAT DECREASING IN [delta .. elts.length) DO elts[i] _ elts[i - delta]; ENDLOOP; FOR i: NAT IN [0 .. delta) DO elts[i] _ NIL ENDLOOP; a.shape[Foo].min _ a.shape[Foo].min - delta; a.shape[Foo].maxPlusOne _ a.shape[Foo].maxPlusOne - delta; }; IF index >= a.shape[Foo].maxPlusOne THEN { a.shape[Foo].maxPlusOne _ index + 1; IF a.shape[Foo].maxPlusOne - a.shape[Foo].min > elts.length THEN Fail[IO.PutFR["Non dense index set: at least [%g .. %g)", IO.int[a.shape[Foo].min], IO.int[a.shape[Foo].maxPlusOne]]] }; IF elts[index - a.shape[Foo].min] # NIL THEN Fail[IO.PutFR["Double occupancy of index %g", IO.int[index]]]; elts[index - a.shape[Foo].min] _ v; }; }; EnumerateParts[ct, SurveyPart]; a _ NEW [ArrayRep[et.ports.length]]; a.eltType _ et; a.shape _ [Foo: [0, 0], Bar: [0, 1]]; a.joints _ ALL[ALL[ALL[NIL]]]; a.portConnections _ NEW [ArrayPortConnectionSeq[ct.ports.length]]; FOR pi: PortIndex IN [0 .. ct.ports.length) DO a.portConnections[pi] _ ALL[ALL[[[0, 0], NIL]]] ENDLOOP; FOR pi: PortIndex IN [0 .. a.eltPorts) DO a[pi] _ unknownPorting ENDLOOP; elts _ NEW [VertexSeq[nCells]]; FOR i: NAT IN [0 .. elts.length) DO elts[i] _ NIL ENDLOOP; insides.EnumerateIncreasing[IndexIt]; IF a.shape[Foo].maxPlusOne - a.shape[Foo].min # nCells THEN ERROR --should have been guaranteed by code in IndexIt--; }; MakeConnections: PROC [ct: CellType, a: Array, elts: VertexS] = { accounts: JointAccount _ NIL; vpSize: NAT _ a.shape[Foo].maxPlusOne - a.shape[Foo].min - 2; Describe: PROC [ja: JointAccounting] RETURNS [r: ROPE] = {r _ IF ja = NIL THEN "notYetConnected" ELSE IO.PutFR["%g - %g [Foo, Even, %g]", IO.refAny[PickAName[a.eltType.ports[ja.low].names]], IO.refAny[PickAName[a.eltType.ports[ja.high].names]], IO.rope[EOName[ja.eo]]]}; ClearIndex: PROC [v: Vertex] = {v.other _ Asserting.AssertFn1[fn: indexFn, val: NIL, inAdditionTo: v.other]}; PerPart: PROC [v: Vertex] = { edges: SymbolTable _ RedBlackTree.Create[GetIDKey, CompareEdgesByIndex]; lastCellIndex: INT; lastPortIndex: PortIndex; first: BOOL _ TRUE; exportIndex: PortIndex _ NullPortIndex; EnsureJointed: PROC [ra: REF ANY] RETURNS [stop: BOOL] = { e: Edge _ NARROW[ra]; cell: Vertex _ e.sides[cell].v; nextCellIndex: INT _ CellIndex[cell]; nextPortIndex: INT _ e.portIndex; dp: DetailedPorting _ NARROW[a.porting[nextPortIndex]]; s1: NAT _ dp.sideIndices[low][Bar].firstSlot; s2: NAT _ dp.sideIndices[high][Bar].firstSlot; stop _ FALSE; SELECT nextCellIndex FROM a.shape[Foo].min => { dp.corners[low] _ ALL[exportIndex]; IF exportIndex # NullPortIndex THEN a.portConnections[exportIndex][low][Foo].sockets _ InsertAS[[[nextCellIndex, 0], nextPortIndex], a.portConnections[exportIndex][low][Foo].sockets]; }; a.shape[Foo].maxPlusOne-1 => { dp.corners[high] _ ALL[exportIndex]; IF exportIndex # NullPortIndex THEN a.portConnections[exportIndex][high][Foo].sockets _ InsertAS[[[nextCellIndex, 0], nextPortIndex], a.portConnections[exportIndex][high][Foo].sockets]; }; IN (a.shape[Foo].min .. a.shape[Foo].maxPlusOne-1) => { dp.slots[s1 + nextCellIndex - (a.shape[Foo].min+1)] _ dp.slots[s2 + nextCellIndex - (a.shape[Foo].min+1)] _ exportIndex; }; ENDCASE => ERROR; IF exportIndex # NullPortIndex THEN { a.portConnections[exportIndex][low][Bar].sockets _ InsertAS[[[nextCellIndex, 0], nextPortIndex], a.portConnections[exportIndex][low][Bar].sockets]; a.portConnections[exportIndex][high][Bar].sockets _ InsertAS[[[nextCellIndex, 0], nextPortIndex], a.portConnections[exportIndex][high][Bar].sockets]; }; IF first THEN first _ FALSE ELSE { eo: EO _ EOOfInt[nextCellIndex]; Bitch: PROC = {Fail[IO.PutFR["Non-uniform connection across %g joint: %g-%g, %g, and %g", IO.rope[EOName[eo]], IO.rope[PickAName[lowPort.names]], IO.rope[PickAName[highPort.names]], IO.rope[Describe[toLow]], IO.rope[Describe[toHigh]]]]}; toLow, toHigh: JointAccounting _ NIL; lowPort: Port _ a.eltType.ports[lastPortIndex]; highPort: Port _ a.eltType.ports[nextPortIndex]; ui: NAT _ UseIndex[a, lastCellIndex]; IF nextCellIndex # lastCellIndex + 1 THEN Fail[IO.PutFR["Non neighborly connection between %g.%g and %g.%g", IO.int[lastCellIndex], IO.rope[PickAName[lowPort.names]], IO.int[nextCellIndex], IO.rope[PickAName[highPort.names]]]]; toHigh _ NARROW[Asserting.FnVal[fn: joinFns[eo][TRUE], from: lowPort.other]]; toLow _ NARROW[Asserting.FnVal[fn: joinFns[eo][FALSE], from: highPort.other]]; IF toHigh # toLow THEN Bitch[] ELSE IF toHigh = NIL THEN { jaSize: NAT _ JASize[a, eo]; ja: JointAccounting _ NEW [JointAccountingRep[jaSize]]; ja.low _ lastPortIndex; ja.high _ nextPortIndex; ja.eo _ eo; FOR i: NAT IN [0 .. ja.length) DO ja[i] _ i = ui ENDLOOP; IF a.joints[Foo][Even][eo] = NIL THEN { a.joints[Foo][Even][eo] _ NEW [JointSeq[a.eltType.ports.length]]; FOR pi: PortIndex IN [0 .. a.eltType.ports.length) DO a.joints[Foo][Even][eo][pi] _ [NullPortIndex, NullPortIndex]; ENDLOOP; }; IF a.joints[Foo][Even][eo][lastPortIndex].high # NullPortIndex OR a.joints[Foo][Even][eo][nextPortIndex].low # NullPortIndex THEN ERROR; a.joints[Foo][Even][eo][lastPortIndex].high _ nextPortIndex; a.joints[Foo][Even][eo][nextPortIndex].low _ lastPortIndex; accounts _ CONS[ja, accounts]; a.eltType.ports[lastPortIndex].other _ Asserting.AssertFn1[fn: joinFns[eo][TRUE], val: ja, inAdditionTo: lowPort.other]; a.eltType.ports[nextPortIndex].other _ Asserting.AssertFn1[fn: joinFns[eo][FALSE], val: ja, inAdditionTo: highPort.other]; } ELSE { IF toHigh.high # nextPortIndex OR toHigh.low # lastPortIndex THEN Bitch[]; IF toHigh.used[ui] THEN ERROR; toHigh.used[ui] _ TRUE; }; }; lastCellIndex _ nextCellIndex; lastPortIndex _ nextPortIndex; }; SELECT v.class FROM net => NULL; cell => RETURN; ENDCASE => ERROR; FOR e: Edge _ v.firstEdge, e.sides[net].next WHILE e # NIL DO IF e.sides[net].v # v THEN ERROR; IF IsMirror[e.sides[cell].v] THEN { IF exportIndex # NullPortIndex THEN ERROR --we assume ANPortsMergedI--; exportIndex _ e.portIndex; } ELSE edges.Insert[e, e !RedBlackTree.DuplicateKey => Fail[IO.PutFR["Multiple connections to the same element: %g", IO.rope[PickAName[e.sides[cell].v.names]]]]]; ENDLOOP; edges.EnumerateIncreasing[EnsureJointed]; }; ClearPortAssocs: PROC = { FOR pi: PortIndex IN [0 .. a.eltType.ports.length) DO FOR eo: EO IN EO DO FOR b: BOOL IN BOOL DO a.eltType.ports[pi].other _ Asserting.AssertFn1[fn: joinFns[eo][b], val: NIL, inAdditionTo: a.eltType.ports[pi].other]; ENDLOOP ENDLOOP; ENDLOOP; }; FOR pi: PortIndex IN [0 .. a.eltType.ports.length) DO a.porting[pi] _ NewDetailedPorting[a.shape]; ENDLOOP; IF a.joints # ALL[ALL[ALL[NIL]]] THEN ERROR; ClearPortAssocs[]; EnumerateParts[ct, PerPart]; FOR accounts _ accounts, accounts.rest WHILE accounts # NIL DO ja: JointAccounting _ accounts.first; FOR i: NAT IN [0 .. ja.length) DO IF NOT ja.used[i] THEN Fail[IO.PutFR["Failed to use %'th instance of %g", IO.int[i], IO.rope[Describe[ja]]]]; ENDLOOP; ENDLOOP; FOR pi: PortIndex IN [0 .. a.eltType.ports.length) DO dp: DetailedPorting _ NARROW[a.porting[pi]]; none: BOOL _ dp.corners = ALL[ALL[NullPortIndex]]; FOR e: End IN End DO FOR d: Dim IN Dim DO s0: NAT _ dp.sideIndices[e][d].firstSlot; inners: NAT _ MAX[a.shape[d].maxPlusOne - a.shape[d].min, 2] - 2; thePort: PortIndex _ IF inners>0 THEN dp.slots[s0] ELSE NullPortIndex; midsSame: BOOL _ TRUE; midsNull: BOOL _ thePort = NullPortIndex; Check: PROC [epi: PortIndex] = { midsSame _ midsSame AND epi = thePort; midsNull _ midsNull AND epi = NullPortIndex; }; FOR i: NAT IN (0 .. inners) DO Check[dp.slots[s0+i]] ENDLOOP; dp.sideIndices[e][d].same _ midsSame; IF NOT midsNull THEN none _ FALSE; ENDLOOP ENDLOOP; IF none THEN a.porting[pi] _ notPorted; ENDLOOP; FOR pi: PortIndex IN [0 .. ct.ports.length) DO FOR e: End IN End DO FOR d: Dim IN Dim DO a.portConnections[pi][e][d].range _ SummarizeASL[a.portConnections[pi][e][d].sockets, OtherDim[d]]; ENDLOOP ENDLOOP; ENDLOOP; }; NewDetailedPorting: PUBLIC PROC [shape: ARRAY Dim OF Range] RETURNS [dp: DetailedPorting] = { inner: ARRAY Dim OF NAT _ [ Foo: MAX[shape[Foo].maxPlusOne - shape[Foo].min, 2] - 2, Bar: MAX[shape[Bar].maxPlusOne - shape[Bar].min, 2] - 2]; fullDetails: NAT _ 2 * (inner[Foo] + inner[Bar]); s0: NAT _ 0; dp _ NEW [DetailedPortingRep[fullDetails]]; FOR e: End IN End DO FOR d: Dim IN Dim DO dp.sideIndices[e][d] _ [FALSE, s0]; s0 _ s0 + inner[OtherDim[d]]; ENDLOOP; ENDLOOP; dp.corners _ ALL[ALL[NullPortIndex]]; FOR s: NAT IN [0 .. s0) DO dp[s] _ NullPortIndex ENDLOOP; }; InsertAS: PROC [as: ArraySocket, asl: ArraySocketList] RETURNS [bsl: ArraySocketList] = { LE: PROC [a, b: ArrayIndex] RETURNS [le: BOOL] = {le _ a[Foo] <= b[Foo] AND a[Bar] <= b[Bar]}; last: ArraySocketList _ NIL; this: ArraySocketList _ LIST[as]; bsl _ asl; FOR asl _ asl, asl.rest UNTIL asl = NIL OR LE[as.ai, asl.first.ai] DO last _ asl ENDLOOP; IF last = NIL THEN bsl _ this ELSE last.rest _ this; this.rest _ asl; }; SummarizeASL: PROC [asl: ArraySocketList, d: Dim] RETURNS [r: Range] = { n: INT _ 0; r _ [0, 0]; FOR asl _ asl, asl.rest WHILE asl # NIL DO SELECT n FROM =0 => r.maxPlusOne _ 1 + (r.min _ asl.first.ai[d]); >0 => r.maxPlusOne _ MAX[r.maxPlusOne, asl.first.ai[d]+1]; ENDCASE => ERROR; n _ n + 1; ENDLOOP; SELECT r.maxPlusOne - r.min FROM 1 => NULL; n => NULL; ENDCASE => ERROR; }; EqualJoints: PROC [a, b: Joint] RETURNS [equal: BOOL] = { minLen: NAT _ MIN[a.eltPorts, b.eltPorts]; EndCheck: PROC [j: Joint] = { FOR p: PortIndex IN [minLen .. j.eltPorts) DO IF j[p] # [NullPortIndex, NullPortIndex] THEN {equal _ FALSE; EXIT}; ENDLOOP; }; equal _ TRUE; FOR p: PortIndex IN [0 .. minLen) DO IF a[p].low # b[p].low OR a[p].high # b[p].high THEN RETURN [FALSE]; ENDLOOP; IF a.eltPorts > minLen THEN EndCheck[a]; IF b.eltPorts > minLen THEN EndCheck[b]; }; CellIndex: PROC [cell: Vertex] RETURNS [index: INT] = { ri: REF INT _ NARROW[Asserting.FnVal[fn: indexFn, from: cell.other]]; index _ ri^}; UseIndex: PROC [a: Array, lowCellIndex: INT] RETURNS [ui: NAT] = { ui _ (lowCellIndex - (a.shape[Foo].min+1))/2; }; JASize: PROC [a: Array, eo: EO] RETURNS [length: NAT] = { highMod: [0 .. 1] _ Mods[eo]; lowMod: [0 .. 1] _ 1 - Mods[eo]; highest: INT _ a.shape[Foo].maxPlusOne - (IF ((a.shape[Foo].maxPlusOne-1) MOD 2) = highMod THEN 1 ELSE 2); lowest: INT _ a.shape[Foo].min + (IF ((a.shape[Foo].min) MOD 2) = lowMod THEN 0 ELSE 1); length _ (highest + 1 - lowest)/2; }; CompareEdgesByIndex: PROC [k, data: REF ANY] RETURNS [c: Basics.Comparison] --RedBlackTree.Compare-- = { Key: PROC [ref: REF ANY] RETURNS [index: INT] = { e: Edge _ NARROW[ref]; index _ CellIndex[e.sides[cell].v]}; k1: INT _ Key[k]; k2: INT _ Key[data]; c _ SELECT k1 FROM < k2 => less, = k2 => equal, > k2 => greater, ENDCASE => ERROR; }; EOOfInt: PROC [i: INT] RETURNS [eo: EO] = {eo _ SELECT i MOD 2 FROM 0 => Even, 1 => Odd, ENDCASE => ERROR}; Mods: ARRAY EO OF [0 .. 1] _ [Even: 0, Odd: 1]; Start: PROC = { dontWrite: REF ANY _ NEW [AssertingIO.WriteProc _ AssertingIO.DontWrite]; AssertingIO.writers _ Asserting.AssertFn1[indexFn, dontWrite, AssertingIO.writers, NIL, TRUE]; FOR eo: EO IN EO DO FOR b: BOOL IN BOOL DO AssertingIO.writers _ Asserting.AssertFn1[joinFns[eo][b], dontWrite, AssertingIO.writers, NIL, TRUE]; ENDLOOP ENDLOOP; }; Start[]; END. ˆLichenRecognizeArrays.Mesa Last Edited by: Spreitzer, July 11, 1985 9:23:32 pm PDT used[ui] says whether e[i].pl f e[i+1].ph seen Κ~– "cedar" style˜Icode™J™7K˜KšΟk œ*œ`˜•K˜šΠbxœœ˜$Kšœ"œM˜xKšœ˜&K˜KšœœœK˜WK˜Kšœœœœ˜-Kšœœœ˜/šœœœ˜#K˜Kšœœ˜šœœ œœ˜"KšœΟmœ™.—Kšœ˜—K˜Kšœ œ œœ˜6Kšœœ œœ˜@K˜Kš œœœœœœ˜=Kš œ œœœœ˜=Kš œ œœœœ˜?K˜Kšœœœœ˜K˜Kš œ œœœœ3˜OK˜šœ œœœœΟc œœœœ˜9˜Kšœœœ)˜8Kšœœœ*˜:—˜Kšœœœ(˜7Kšœœœ*˜:——K˜š Οnœœœ œœ˜>Kšœœ˜(K˜ K˜Kšœ˜Kšœœœœ˜%K˜K˜Kšœ œ˜Kšœ œ˜K˜K˜—K˜š‘ œœœ˜HK˜ Kšœœœ˜Kšœœ˜%KšœC˜CKšœœ˜š‘ œœ˜ Kšœœ˜ šœ ˜˜Kšœ˜K˜—˜ Kšœ˜Kšœ0œ˜Lšœ˜˜K˜ K˜Kšœ˜K˜—˜Kšœ œ˜ Kšœœ˜Kšœœ˜ Kš œ œœ9œœ!˜•š˜Kšœ˜š˜Kšœ˜Kšœ˜Kšœ/˜/—Kšœœœ˜—š˜Kšœ˜š˜Kšœ˜Kšœ˜KšœM˜M—Kšœœœ˜—Kš œ#œœ.œœ˜€KšœT˜TKšœ˜K˜9K˜&K˜PK˜K˜K˜K˜—˜Kšœ œ˜ Kšœœ˜Kšœœ˜ Kš œ œœ9œœ!˜•š˜Kšœ˜š˜Kšœ˜Kšœ˜Kšœ/˜/—Kšœœœ˜—š˜Kšœ˜š˜Kšœ˜Kšœ˜KšœO˜O—Kšœœœ˜—Kš œ#œœ4œœœ˜˜šœœœ˜>KšœF˜FKšœ œ"˜/Kšœ œ2˜@š ‘œœœœœœ˜4Kšœ œœ˜Kšœ œ$˜3K˜(Kšœœ˜—K˜%K˜K˜&K˜;K˜K˜K˜—K˜PK˜K˜—Kšœœ˜—K˜—Kšœœ˜—K˜—š ‘œœœœœœ˜4Kšœœœ˜Kšœœ˜)Kš œœ@œ-œœœ˜―K˜Kš œœœœœ˜(Kšœœ˜ Kšœ0œœ"˜Zšœ-œ˜5K˜K˜$K˜ K˜—šœ˜šœœ˜"Kšœœ˜&š œœ œœ˜2K˜Kšœ˜—Kš œœœœ œœ˜4Kšœ,˜,Kšœ:˜:K˜—šœ"œ˜*Kšœ$˜$Kš œ:œœ3œœ˜ΆK˜—Kš œ"œœœ'œ˜kKšœ#˜#K˜—K˜—Kšœ˜Kšœœ˜$K˜Kšœ%˜%Kš œ œœœœ˜Kšœœ+˜BKšœœœœœ œœ˜gKšœœœœ˜IKšœœ˜Kš œœœœ œœ˜:K˜%Kšœ5œœ 2œ˜uK˜—K˜š‘œœ,˜AKšœœ˜Kšœœ2˜=š‘œœœœ˜8Kšœœœœœœ"œ3œ4œ˜Υ—Kš‘ œœ@œ˜mš‘œœ˜KšœH˜HKšœœ˜K˜Kšœœœ˜K˜'š ‘ œœœœœœ˜:Kšœ œ˜K˜Kšœœ˜%Kšœœ˜!Kšœœ˜7Kšœœ&˜-Kšœœ'˜.Kšœœ˜ šœ˜šœ˜Kšœœ˜#Kšœœ”˜·Kšœ˜—šœ˜Kšœœ˜$Kšœœ–˜ΉKšœ˜—šœ5˜7Kšœx˜xKšœ˜—Kšœœ˜—šœœ˜%Kšœ“˜“Kšœ•˜•K˜—šœœ œœ˜"Kšœœ˜ š‘œœ˜ Kš œœDœœ!œ"œœ˜ί—Kšœ!œ˜%Kšœ/˜/Kšœ0˜0Kšœœ˜%Kšœ#œœ<œœ!œœ#˜γKšœ œ!œ˜MKšœœ!œ˜NKšœœ˜šœœ œœ˜Kšœœ˜Kšœœ˜7Kšœ˜Kšœ˜K˜ Kš œœœœœ˜9šœœœ˜'Kšœœ$˜Ašœœ˜5Kšœ=˜=Kšœ˜—K˜—Kšœ=œ<œœ˜ˆKšœ<˜K˜%šœœœ˜!Kš œœ œœ,œ œ˜mKšœ˜—Kšœ˜—šœœ˜5Kšœœ˜,Kšœœœœ˜2š œœœœœ˜)Kšœœ"˜)Kšœœœ0˜AKšœœ œœ˜FKšœ œœ˜Kšœ œ˜)š‘œœ˜ Kšœœ˜&Kšœœ˜,K˜—Kš œœœœœ˜=Kšœ%˜%Kšœœ œœ˜"Kšœœ˜—Kšœœ˜'Kšœ˜—šœœ˜.š œœœœœ˜)Kšœc˜cKšœœ˜—Kšœ˜—K˜—K˜š ‘œœœ œœœ˜]šœœœœ˜Kšœœ0˜8Kšœœ1˜9—Kšœ œ!˜1Kšœœ˜ Kšœœ#˜+šœœ˜šœœ˜Kšœœ˜#K˜Kšœ˜—Kšœ˜—Kšœ œœ˜%Kš œœœ œœ˜9K˜—K˜š‘œœ)œ˜YKš œœœœœ˜^Kšœœ˜Kšœœ˜!K˜ Kšœœœœœœ œ˜YKšœœœ œ˜4K˜K˜—K˜š‘ œœ œ˜HKšœœ˜ K˜ šœœœ˜*šœ˜ Kšœ3˜3Kšœœ"˜:Kšœœ˜—K˜ Kšœ˜—šœ˜ Kšœœ˜ Kšœœ˜ Kšœœ˜—K˜—K˜š‘ œœœ œ˜9Kšœœœ˜*š‘œœ˜šœœ˜-Kšœ'œ œœ˜DKšœ˜—K˜—Kšœœ˜ šœœ˜$Kš œœœœœ˜DKšœ˜—Kšœœ ˜(Kšœœ ˜(K˜—K˜š‘ œœœ œ˜7Kšœœœœ1˜EK˜ —K˜š ‘œœœœœ˜BK˜-K˜—K˜š ‘œœœœ œ˜9K˜K˜ Kš œ œœœœœ˜jKš œœœœ œœ˜XK˜"K˜—K˜š ‘œœ œœœ œ˜hš ‘œœœœœ œ˜1Kšœ œ˜K˜$—Kšœœ ˜Kšœœ ˜šœœ˜Kšœ ˜ Kšœ˜Kšœ˜Kšœœ˜—K˜—K˜š ‘œœœœœ˜)Kš œœœœœœ˜A—K˜Kšœœœœ˜/K˜š‘œœ˜Kšœ œœœ1˜IKšœSœœ˜^šœœœœœœœœœ˜*KšœZœœ˜eKšœœ˜—K˜—K˜K˜K˜Kšœ˜——…—A4U: