DIRECTORY Basics USING [DIVMOD], FS USING [ComponentPositions, ComponentRopes, maxFNameLength, Position], FSBackdoor USING [highestVersion, lowestVersion, ProduceError, Version], FSFileOps USING [GetVolumeDesc, VolumeDesc], FSName USING [ParsedFName, VersionInfo], List USING [Assoc], ProcessProps USING [GetPropList], Rope USING [Cat, Concat, Fetch, Flatten, Index, Length, Match, NewText, Replace, Substr, ROPE, Text]; FSNameImpl: CEDAR PROGRAM IMPORTS Basics, FSBackdoor, FSFileOps, List, ProcessProps, Rope EXPORTS FS, FSBackdoor, FSName SHARES Rope = { ROPE: TYPE = Rope.ROPE; Version: TYPE = FSBackdoor.Version; initialDefaultWDir: ROPE = "[]<>"; validNameChars: ROPE _ "$-+'_"; defaultWDir: ROPE _ initialDefaultWDir; SetDefaultWDir: PUBLIC PROC [dir: ROPE] = { IF Rope.Length[dir] = 0 THEN dir _ initialDefaultWDir ELSE { places: Places; [dir, places] _ ExpandAndFindPlaces[dir, GetDefaultWDir[], directory]; IF places.serverEnd # 1 THEN DirNotLocal[dir]; IF places.dirEnd = places.serverEnd THEN NoVolumePart[dir]; dir _ Rope.Flatten[dir]; }; defaultWDir _ dir; }; GetDefaultWDir: PUBLIC PROC RETURNS [ROPE] = { RETURN [defaultWDir]; }; ExpandName: PUBLIC PROC[name: ROPE, wDir: ROPE] RETURNS [fullFName: ROPE, cp: FS.ComponentPositions, dirOmitted: BOOL _ FALSE] = { places: Places; fNLen: INT; [fullFName, places] _ ExpandAndFindPlaces[name, wDir, pattern]; fNLen _ Rope.Length[fullFName]; cp.server _ [1, places.serverEnd-1]; IF places.dirEnd >= places.serverEnd+2 THEN cp.dir _ [places.serverEnd+2, places.dirEnd-places.serverEnd-2] ELSE { dirOmitted _ TRUE; cp.dir _ [places.serverEnd+1, 0] }; cp.subDirs _ IF places.subDirEnd > places.dirEnd THEN [places.dirEnd+1, places.subDirEnd-places.dirEnd-1] ELSE [places.dirEnd+1, 0]; cp.base _ [places.subDirEnd+1, places.rootEnd-places.subDirEnd-1]; cp.ext _ IF places.bang > places.rootEnd THEN [places.rootEnd+1, places.bang-places.rootEnd-1] ELSE [places.rootEnd, 0]; IF places.bang < fNLen THEN { [] _ ParseVersion[fullFName, places.bang+1, TRUE]; cp.ver _ [places.bang+1, fNLen-places.bang-1]; } ELSE cp.ver _ [fNLen, 0]; }; ConstructFName: PUBLIC PROC [cr: FS.ComponentRopes, omitDir: BOOL] RETURNS [fName: ROPE] = { fName _ Rope.Cat[ "[", cr.server, "]" ]; IF NOT omitDir THEN fName _ Rope.Cat[ fName, "<", cr.dir, ">" ]; IF Rope.Length[cr.subDirs] > 0 THEN fName _ Rope.Cat[ fName, cr.subDirs, ">" ]; fName _ Rope.Cat[ fName, cr.base ]; IF Rope.Length[cr.ext] > 0 THEN fName _ Rope.Cat[ fName, ".", cr.ext ]; IF Rope.Length[cr.ver] > 0 THEN fName _ Rope.Cat[ fName, "!", cr.ver ]; }; MakeFName: PUBLIC PROC [nameBody: ROPE, version: Version, prefix: ROPE] RETURNS [ROPE] = { con: ROPE _ Rope.Concat [ nameBody, VersionPartFromVersion[version] ]; IF NOT Rope.Match["[*", nameBody] THEN { IF prefix = NIL THEN prefix _ initialDefaultWDir; con _ Rope.Concat [ prefix, con ]; }; RETURN [con]; }; ParseClientName: PUBLIC PROC [clientName, wDir: ROPE, defaultVersionHigh, pattern: BOOL] RETURNS [pn: FSName.ParsedFName, vI: FSName.VersionInfo] = { vName: ROPE _ NIL; places: Places; [pn.fullName, places] _ ExpandAndFindPlaces[clientName, wDir, IF pattern THEN pattern ELSE fName]; IF places.bang < Rope.Length[pn.fullName] THEN [pn.version, vI] _ ParseVersion[pn.fullName, places.bang+1, pattern] ELSE { vI _ missing; pn.version _ IF defaultVersionHigh THEN FSBackdoor.highestVersion ELSE FSBackdoor.lowestVersion; }; IF IsLocal[pn.fullName] THEN { vL: CARDINAL _ places.dirEnd - places.serverEnd - 2; IF vL # 0 THEN vName _ Rope.Substr[pn.fullName, places.serverEnd + 2, vL]; pn.nameBody _ Rope.Flatten[ Rope.Substr[pn.fullName, places.dirEnd + 1, places.bang - places.dirEnd - 1] ]; } ELSE pn.nameBody _ Rope.Flatten[ Rope.Substr[pn.fullName, 0, places.bang] ]; pn.volDesc _ FSFileOps.GetVolumeDesc[vName]; }; ParseCacheName: PUBLIC PROC [volName, cacheName: ROPE, pattern: BOOL] RETURNS [pn: FSName.ParsedFName, vI: FSName.VersionInfo] = { firstChar: CHARACTER; length, bangIndex: CARDINAL; nameUse: NameUse = IF pattern THEN pattern ELSE fName; pn _ [NIL, NIL, FSBackdoor.highestVersion, FSFileOps.GetVolumeDesc[volName]]; vI _ missing; IF Rope.Length[cacheName] = 0 THEN { IF pattern THEN { pn.nameBody _ "[*"; RETURN } ELSE IllegalName[cacheName, nameUse]; }; FOR i: INT IN [0 .. Rope.Length[cacheName]) DO -- determine syntax convention SELECT Rope.Fetch[cacheName, i] FROM '[, '], '<, '> => EXIT; '/ => { cacheName _ ConvertSlashName[cacheName]; EXIT }; ENDCASE; ENDLOOP; firstChar _ Rope.Fetch[cacheName, 0]; IF firstChar # '[ THEN { IF firstChar = '* THEN cacheName _ Rope.Concat["[", cacheName] ELSE IllegalName[cacheName, nameUse]; }; length _ Rope.Length[cacheName]; bangIndex _ Rope.Index[cacheName, IF length > 6 THEN length - 6 ELSE 0, "!"]; IF bangIndex # length AND NOT (bangIndex = length-2 AND Rope.Fetch[cacheName, length-1] = '*) THEN [pn.version, vI] _ ParseVersion[cacheName, bangIndex+1, pattern]; pn.nameBody _ Rope.Flatten[ Rope.Substr[cacheName, 0, bangIndex] ]; }; ConvertNamebodyPattern: PUBLIC PROC [nbP: ROPE] RETURNS [Rope.Text] = { RETURN [ IF Rope.Length[nbP] = 0 THEN "*" ELSE ConvertSlashName[nbP] ] }; ParseName: PUBLIC PROC [volName, fName: ROPE] RETURNS [p: FSName.ParsedFName] = { length: CARDINAL = Rope.Length[fName]; bangIndex: CARDINAL = Rope.Index[fName, IF length > 6 THEN length - 6 ELSE 0, "!"]; IF bangIndex = length THEN p.version _ FSBackdoor.highestVersion ELSE [p.version, ] _ ParseVersion[fName, bangIndex+1, FALSE]; p.nameBody _ Rope.Flatten[ Rope.Substr[fName, 0, bangIndex] ]; p.fullName _ fName; p.volDesc _ FSFileOps.GetVolumeDesc[volName]; }; IsLocal: PUBLIC PROC [name: ROPE] RETURNS [BOOL] = { RETURN[ Rope.Length[name]=0 OR Rope.Fetch[name, 0]#'[ OR Rope.Fetch[name, 1]='] ]}; ServerAndFileRopes: PUBLIC PROC [gName: ROPE] RETURNS [server, file: ROPE] = { closingBracket: CARDINAL = Rope.Index[gName, 0, "]"]; server _ Rope.Substr[gName, 1, closingBracket-1]; file _ Rope.Substr[gName, closingBracket+1]; }; BangStarFile: PUBLIC PROC [file: ROPE] RETURNS [ROPE] = { length: CARDINAL = Rope.Length[file]; bangIndex: CARDINAL = Rope.Index[file, IF length > 6 THEN length - 6 ELSE 0, "!"]; RETURN [ Rope.Replace [ file, bangIndex, length - bangIndex, "!*" ] ]; }; BangVersionFile: PUBLIC PROC [file: ROPE, version: Version] RETURNS [ROPE] = { length: CARDINAL = Rope.Length[file]; bangIndex: CARDINAL = Rope.Index[file, IF length > 6 THEN length - 6 ELSE 0, "!"]; RETURN [ Rope.Replace [ file, bangIndex, length - bangIndex, VersionPartFromVersion[version] ] ]; }; VersionFromRope: PUBLIC PROC [r: ROPE] RETURNS [v: Version] = { IF Rope.Length[r] = 0 THEN v _ FSBackdoor.highestVersion ELSE [v, ] _ ParseVersion[r, 0, FALSE]; }; VersionPartFromVersion: PUBLIC PROC [version: Version] RETURNS [r: Rope.Text] = { Decimate: PROC [num: CARDINAL] = { q, r: CARDINAL; [q, r] _ Basics.DIVMOD[num, 10]; IF q # 0 THEN Decimate[q]; AppendChar[t, r+'0]; }; t: REF TEXT; SELECT version FROM FSBackdoor.lowestVersion, FSBackdoor.highestVersion => r _ NIL; ENDCASE => TRUSTED { r _ Rope.NewText[6]; t _ LOOPHOLE[r]; t[0] _ '!; t.length _ 1; Decimate[version]; }; }; NameUse: TYPE = {fName, pattern, directory}; Places: TYPE = RECORD[serverEnd, dirEnd, subDirEnd, bang, rootEnd, firstStar: CARDINAL _ 0]; ExpandAndFindPlaces: PROC [name, wDir: ROPE, nameUse: NameUse] RETURNS [fN: ROPE, p: Places] = { i: INT; leftPoint: BOOL _ FALSE; fNLen: CARDINAL _ Rope.Length[name]; fN _ name; IF fNLen # 0 THEN SELECT Rope.Fetch[fN, 0] FROM '[ => NULL; '/ => fN _ ConvertSlashName[fN]; ENDCASE => { IF Rope.Length[wDir] = 0 THEN { ref: REF _ List.Assoc[key: $WorkingDirectory, aList: ProcessProps.GetPropList[]]; WITH ref SELECT FROM wd: ROPE => wDir _ wd; ENDCASE; }; IF Rope.Length[wDir] = 0 THEN wDir _ GetDefaultWDir[] ELSE wDir _ ConvertWDir[wDir]; FOR i IN [1 .. fNLen) DO -- convert the name part if necessary SELECT Rope.Fetch[fN, i] FROM '], '<, '>, '! => NULL; '/ => fN _ ConvertSlashName[fN]; ENDCASE => LOOP; EXIT; ENDLOOP; fN _ Rope.Cat[wDir, fN]; }; -- of need a working directory fNLen _ Rope.Length[fN]; i _ 0; DO c: CHAR _ 0C; i _ i + 1; IF i >= fNLen THEN EXIT; c _ Rope.Fetch[fN, i]; SELECT c FROM IN ['a .. 'z], IN ['A .. 'Z], IN ['0 .. '9] => {}; '] => IF p.serverEnd = 0 THEN p.subDirEnd _ p.dirEnd _ p.serverEnd _ i ELSE IllegalName[fN, nameUse]; -- this is the second '] '< => IF p.serverEnd = i - 1 THEN leftPoint _ TRUE ELSE IllegalName[fN, nameUse]; -- '< does not immediately follow '] '> => IF leftPoint AND ( i > p.subDirEnd + 1 ) THEN { IF p.dirEnd = p.serverEnd THEN p.dirEnd _ i; -- end of directory part p.subDirEnd _ i; -- end of subdirectory part } ELSE IllegalName[fN, nameUse]; -- '> in the wrong place '. => p.rootEnd _ i; '! => { p.bang _ i; EXIT}; '# => IF p.serverEnd # 0 THEN { IF p.serverEnd = 1 AND leftPoint AND i = 3 THEN DO -- LName with a max 20 digit hex number as a volume id i _ i + 1; IF i >= fNLen THEN EXIT; IF i > 23 THEN IllegalName[fN, nameUse]; SELECT Rope.Fetch[fN, i] FROM IN ['0 .. '9], IN ['A .. 'H] => NULL; ENDCASE => IllegalName[fN, nameUse]; ENDLOOP ELSE IllegalName[fN, nameUse]; -- sharpSign in the wrong place }; '* => IF nameUse = pattern THEN { IF p.firstStar = 0 THEN p.firstStar _ i } ELSE NoPatterns[fN]; -- star and we're not parsing a pattern ENDCASE => { valid: Rope.Text = Rope.Flatten[validNameChars]; IF valid # NIL THEN FOR j: NAT IN [0..valid.length) DO IF valid[j] = c THEN GO TO legal; ENDLOOP; IllegalCharacter[fN]; EXITS legal => {}; }; ENDLOOP; IF p.serverEnd = 0 THEN IllegalName[fN, nameUse]; -- server part didn't end IF p.bang = 0 THEN p.bang _ fNLen; IF p.bang > FS.maxFNameLength - 6 THEN TooLong[fN]; IF p.firstStar = 0 THEN { IF p.serverEnd = 1 AND nameUse # directory AND p.subDirEnd+1 >= p.bang THEN IllegalName[fN, nameUse]; } ELSE { IF (p.serverEnd = 1 AND p.firstStar < p.dirEnd) OR (p.firstStar < p.serverEnd) THEN IllegalName[fN, nameUse]; }; IF p.rootEnd <= p.subDirEnd THEN p.rootEnd _ p.bang; }; ParseVersion: PROC [name: ROPE, index: CARDINAL, pattern: BOOL _ FALSE] RETURNS [value: Version, vI: FSName.VersionInfo] = { c: CHAR; lastIndex: CARDINAL = Rope.Length[name] - 1; IF lastIndex IN [index .. index+4] THEN SELECT c _ Rope.Fetch[name, index] FROM IN ['0 .. '9] => { num: LONG CARDINAL _ 0; DO num _ num*10 + (c - '0); IF index = lastIndex THEN { IF num NOT IN (FSBackdoor.lowestVersion .. FSBackdoor.highestVersion) THEN EXIT; value _ [num]; vI _ number; RETURN; }; index _ index + 1; c _ Rope.Fetch[name, index]; IF c NOT IN ['0 .. '9] THEN EXIT; ENDLOOP; }; 'H, 'h => IF index = lastIndex THEN { value _ FSBackdoor.highestVersion; vI _ bangH; RETURN }; 'L, 'l => IF index = lastIndex THEN { value _ FSBackdoor.lowestVersion; vI _ bangL; RETURN }; '* => IF index = lastIndex AND pattern THEN { value _ FSBackdoor.highestVersion; vI _ bangStar; RETURN }; ENDCASE; IllegalVersion[name]; }; QuotedName: PROC [n: ROPE] RETURNS [ROPE] = { quoteRope: ROPE = "\""; RETURN [ Rope.Cat[quoteRope, n, quoteRope] ]; }; DirNotLocal: PROC [n: ROPE] = { FSBackdoor.ProduceError[badWorkingDir, Rope.Concat[QuotedName[n], " is not a local directory."] ] }; NoVolumePart: PROC [n: ROPE] = { FSBackdoor.ProduceError[badWorkingDir, Rope.Concat[QuotedName[n], " needs a volume part."] ] }; TooLong: PROC [n: ROPE] = { FSBackdoor.ProduceError[ illegalName, Rope.Concat[QuotedName[n], " has more than 120 characters."] ] }; IllegalCharacter: PROC [n: ROPE] = { FSBackdoor.ProduceError[ illegalName, Rope.Concat[QuotedName[n], " contains an illegal character."] ] }; IllegalVersion: PROC [n: ROPE] = { FSBackdoor.ProduceError[ illegalName, Rope.Concat[QuotedName[n], " has an illegal version part."] ] }; IllegalName: PROC [n: ROPE, nameUse: NameUse] = { e: ROPE = SELECT nameUse FROM fName => " is not a legal FName.", pattern => " is not a legal pattern.", directory => " is not a legal directory name", ENDCASE => ERROR; FSBackdoor.ProduceError [illegalName, Rope.Concat[QuotedName[n], e] ]; }; NoPatterns: PROC [n: ROPE] = { FSBackdoor.ProduceError[ patternNotAllowed, Rope.Concat[QuotedName[n], " contains a \"*\", but patterns are not allow for this operation."] ] }; AppendChar: PROC [text: REF TEXT, c: CHAR] = INLINE { text[text.length] _ c; text.length _ text.length + 1; }; ConvertWDir: PROC [wDir: ROPE] RETURNS [w: ROPE] = { SELECT Rope.Fetch[wDir, 0] FROM '[ => { c: CHAR = Rope.Fetch[wDir, Rope.Length[wDir] - 1]; IF c # '> AND c # '] THEN wDir _ Rope.Cat[wDir, ">"]; w _ wDir; }; '/ => { c: CHAR = Rope.Fetch[wDir, Rope.Length[wDir] - 1]; IF c # '/ THEN wDir _ Rope.Cat[wDir, "/"]; w _ ConvertSlashName[wDir]; }; ENDCASE => IllegalName[wDir, directory]; }; ConvertSlashName: PROC [r: ROPE] RETURNS [t: Rope.Text] = TRUSTED { rL: INT = Rope.Length[r]; text: REF TEXT; slashCount: CARDINAL _ IF Rope.Fetch[r, 0] = '/ THEN 0 ELSE 2; t _ Rope.NewText[rL+1]; text _ LOOPHOLE[t]; text.length _ 0; FOR i: INT IN [0 .. rL) DO c: CHAR = Rope.Fetch[r, i]; SELECT c FROM '/ => { slashCount _ slashCount + 1; SELECT slashCount FROM 1 => AppendChar[text, '[]; 2 => { -- end of server part AppendChar[text, ']]; FOR j: INT IN [i+1 .. rL) DO -- see if we also need a "<" SELECT Rope.Fetch[r, j] FROM '/, '*, '> => {AppendChar[text, '<]; EXIT}; '! => EXIT; ENDCASE; ENDLOOP; }; ENDCASE => AppendChar[text, '>]; }; '* => { -- "*" can hide any number of slashes IF slashCount < 2 THEN slashCount _ 2; AppendChar[text, c]; }; ENDCASE => AppendChar[text, c]; ENDLOOP; }; }. €FSNameImpl.Mesa Copyright c 1984 by Xerox Corporation. All rights reserved. Russ Atkinson, November 7, 1984 7:19:26 pm PST HGM, February 7, 1984 11:24:30 pm PST (Allow ' in names) Schroeder, December 15, 1983 9:26 am Levin, August 9, 1983 11:28 am Global State The valid name characters are in {A..Z, a..z, 0..9}, or in this set. Since the normal formatting characters are examined first, putting them in this set has no effect. Note that the normal formatting characters are in the set {'[, '], '<, '>, '., '!, '#, '*} RRA: This does not need to be protected by a monitor, since RC assignments must be atomic for storage safety reasons. Exported to FS Exported to FSBackdoor Exported to FSName Internal procedures If an FS.Error is not generated then the full FName is returned as "fN" and the parts of this FName are located by the indexes in "p" according to the following rules (first means left-most, last means right-most, and after means to-the-right-of): p.serverEnd = index of the "]"; p.dirEnd = IF no ">" THEN p.serverEnd ELSE index of first ">"; p.subDirEnd = IF no ">" THEN p.dirEnd ELSE index of last ">"; p.bang = IF no "!" THEN Rope.Length[fN] ELSE index of first "!"; p.rootEnd = IF no "." after p.subDirEnd THEN p.bang ELSE index of last "." after p.subDirEnd; p.firstStar = index of the first "*". Note that all parsing stops when the first "!" is encountered. It is the client's responsibility to verify that the characters following the "!" constitute a valid version part. need a working directory not in server part not a pattern LName has no simple name part have a pattern first star is in volume part of LName or in server part ΚA– "cedar" style˜code1šœ™Jšœ Οmœ1™žœ žœ žœ˜bšžœ'˜)LšžœE˜Išžœ˜Lšœ ˜ Lšœ žœžœžœ˜`Lšœ˜——šžœ˜šžœ˜Lšœžœ(˜4Lšžœžœ<˜JLšœk˜kLšœ˜—LšžœH˜L—Lšœ,˜,Lšœ˜—š Ÿœžœžœžœ žœžœ5˜‚Lšœ ž œ˜Lšœžœ˜Lšœžœ žœ žœ˜6Lšœžœžœ?˜ML˜ šžœžœ˜$šžœ˜ Lšžœžœ˜#Lšžœ!˜%—Lšœ˜—š žœžœžœžœΟc˜Mšžœž˜$Lšœžœ˜Lšœ1žœ˜8Lšžœ˜—Lšžœ˜—Lšœ%˜%šžœžœ˜šžœ˜Lšžœ(˜,Lšžœ!˜%—Lšœ˜—Lšœ ˜ Lšœ"žœ žœ žœ ˜Mš žœžœžœžœ&ž˜bLšœA˜A—LšœC˜CLšœ˜—š Ÿœžœžœžœžœ˜GLšžœžœžœžœ˜I—š Ÿ œžœžœžœžœ˜QLšœžœ˜&Lš œ žœžœ žœ žœ ˜Sšžœ˜Lšžœ&˜*Lšžœ2žœ˜=—Lšœ>˜>Lšœ˜Lšœ-˜-Lšœ˜—šŸœžœžœžœžœžœžœ˜4Lšžœžœžœ˜S—š Ÿœž œ žœžœžœ˜NLšœžœ˜5Lšœ1˜1Lšœ,˜,Lšœ˜—š Ÿ œž œžœžœžœ˜9Lšœžœ˜%Lš œ žœžœ žœ žœ ˜RLšžœ@˜FLšœ˜—š Ÿœžœžœžœžœžœ˜NLšœžœ˜%Lš œ žœžœ žœ žœ ˜RLšžœ[˜aLšœ˜—šŸœž œžœžœ˜?Lšžœ˜Lšžœ˜"Lšžœžœ˜'Lšœ˜—šŸœžœžœžœ˜QšŸœžœžœ˜"Lšœžœ˜Lšœžœ ˜ Lšžœžœ ˜Lšœ˜Lšœ˜—Lšœžœžœ˜ šžœ ž˜Lšœ;žœ˜?šžœžœ˜L˜Lšœžœ˜L˜ L˜ Lšœ˜Lšœ˜——Lšœ˜——™Lšœ žœ˜,Lšœžœžœ9žœ˜\š Ÿœžœžœžœžœ˜`šœžœο™χLšœ™Lšœ žœžœ žœ™>Lšœžœžœ žœ™=Lšœ žœžœžœ™@Lšœ žœžœžœ%™]Lšœ%™%—L™²Lšœžœ˜Lšœ žœžœ˜Lšœž œ˜$Lšœ ˜ šžœ žœžœž˜/Lšœžœ˜ Lšœ ˜ šžœ˜ Lšœ™šžœžœ˜LšœžœI˜Qšžœžœž˜Lšœžœ˜Lšžœ˜—L˜—šžœ˜Lšžœ˜Lšžœ˜—šžœžœžœ %˜>šžœž˜Lšœžœ˜Lšœ ˜ Lšžœžœ˜—Lšžœ˜Lšžœ˜—Lšœ˜Lšœ ˜!——Lšœ˜L˜šž˜Lšœžœ˜ L˜ Lšžœ žœžœ˜Lšœ˜šžœž˜ Lšžœ žœ žœ˜2šœ˜šžœ˜Lšžœ)˜-Lšžœ ˜8——šœ˜šžœ˜Lšžœ ž˜Lšžœ $˜C——šœ˜šžœ žœ˜(šžœ˜Lšžœ˜Lšžœ ˜+Lšœ ˜,Lšœ˜—Lšžœ œ ˜7——šœ˜Lšœ˜—šœ˜Lšœ žœ˜—šœ˜šžœžœ˜Lšœ™šžœžœ žœ˜*šžœžœ 6˜>L˜ Lšžœ žœžœ˜Lšžœžœ˜(šžœž˜Lšžœ žœžœ˜%Lšžœ˜$—Lšž˜—Lšžœ ˜>—Lšœ˜——šœ˜šžœ˜Lšžœžœžœ˜0Lšžœ '˜<——šžœ˜ Lšœ0˜0šžœ žœž˜šžœžœžœž˜"Lšžœžœžœžœ˜!Lšžœ˜——Lšœ˜Lšžœ ˜L˜——Lšžœ˜—Lšžœžœ ˜KLšžœ žœ˜"Lšžœ žœžœ ˜3šžœ˜šžœ˜Lšœ ™ šžœžœžœž˜KLšœ™Lšœ˜—Lšœ˜—šžœ˜Lšœ™šžœžœžœž˜TLšœ7™7Lšœ˜—Lšœ˜——Lšžœžœ˜4Lšœ˜—šŸ œžœžœ žœ žœžœžœ-˜|Lšœžœ˜Lšœ žœ˜,š žœ žœžœžœž˜Ošžœ˜Lšœžœžœ˜šž˜Lšœ˜šžœžœ˜šžœžœžœ8˜ELšžœžœ˜ —Lšœ˜Lšœ ˜ Lšžœ˜Lšœ˜—Lšœ˜Lšœ˜Lšžœžœžœ ˜Lšžœžœ˜ Lšžœ˜—Lšœ˜—šœ ˜ šžœžœ˜Lšœ0žœ˜9——šœ ˜ šžœžœ˜Lšœ.žœ˜7——šœ˜šžœžœžœ˜'Lšœ2žœ˜;——Lšžœ˜—Lšœ˜Lšœ˜—š Ÿ œžœžœžœžœ˜-Lšœ žœ˜Lšžœ'˜-Lšœ˜—šŸ œžœžœ˜Lšœd˜d—šŸ œžœžœ˜ Lšœ_˜_—šŸœžœžœ˜Lšœg˜g—šŸœžœžœ˜$Lšœh˜h—šŸœžœžœ˜"Lšœf˜f—šŸ œžœžœ˜1šœžœžœ ž˜Lšœ"˜"Lšœ&˜&Lšœ.˜.Lšžœžœ˜—LšœF˜FLšœ˜—šŸ œžœžœ˜Lšœ˜—š Ÿ œžœžœžœžœžœ˜5L˜L˜Lšœ˜—š Ÿ œžœžœžœžœ˜4šžœž˜šœ˜Lšœžœ+˜2Lšžœžœžœ˜6Lšœ ˜ Lšœ˜—šœ˜Lšœžœ+˜2Lšžœžœ˜*Lšœ˜Lšœ˜—Lšžœ!˜(—Lšœ˜—š Ÿœžœžœžœžœ˜CLšœžœ˜Lšœžœžœ˜Lš œ žœžœžœžœ˜>Lšœ˜Lšœžœ˜L˜šžœžœžœ ž˜Lšœžœ˜šžœž˜ šœ˜Lšœ˜šžœ ž˜Lšœ˜šœ ˜Lšœ˜š žœžœžœ žœ ˜9šžœž˜Lšœ%žœ˜+Lšœžœ˜ Lšžœ˜—Lšžœ˜—Lšœ˜—Lšžœ˜ —Lšœ˜—šœ %˜-Lšžœžœ˜&Lšœ˜Lšœ˜—Lšžœ˜—Lšžœ˜—Lšœ˜——Lšœ˜—…—46Lχ