From 3555275e90b40abfbdf99dd4a4b515d21f21234d Mon Sep 17 00:00:00 2001 From: Pierre Le Marre Date: Tue, 11 Jun 2024 22:17:36 +0200 Subject: [PATCH] ucd2haskell: Compress further General Category Use Shamochu algorithm --- ucd2haskell/exe/UCD2Haskell/Generator.hs | 280 ++++- .../Modules/UnicodeData/GeneralCategory.hs | 35 +- ucd2haskell/ucd2haskell.cabal | 1 + unicode-data/lib/Unicode/Internal/Bits.hs | 28 +- .../Char/UnicodeData/GeneralCategory.hs | 1052 ++++------------- 5 files changed, 562 insertions(+), 834 deletions(-) diff --git a/ucd2haskell/exe/UCD2Haskell/Generator.hs b/ucd2haskell/exe/UCD2Haskell/Generator.hs index d058860..0920edd 100644 --- a/ucd2haskell/exe/UCD2Haskell/Generator.hs +++ b/ucd2haskell/exe/UCD2Haskell/Generator.hs @@ -19,6 +19,8 @@ module UCD2Haskell.Generator , chunkAddrLiteral , word32ToWord8s , splitPlanes + , genEnumBitmapShamochu + , generateShamochuBitmaps -- * Helpers , printCpuTime , unlinesBB @@ -30,18 +32,30 @@ import Data.Bits (Bits (..)) import qualified Data.ByteString as B import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy as BL +import Data.Char (toUpper) import Data.Fixed (Centi) import qualified Data.List as L +import qualified Data.List.NonEmpty as NE import Data.Maybe (mapMaybe) import Data.Ratio ((%)) import Data.Version (Version, showVersion) import Data.Word (Word32, Word8) +import Debug.Trace (trace) +import qualified GHC.Exts as Exts import GHC.Stack (HasCallStack) +import qualified Shamochu import System.CPUTime (getCPUTime) import System.Directory (createDirectoryIfMissing) import System.FilePath ((<.>), ()) -import UCD2Haskell.Common (Fold, showPaddedHeXB, showB, distribute, runFold, rmapFold) +import UCD2Haskell.Common ( + Fold, + distribute, + rmapFold, + runFold, + showB, + showPaddedHeXB, + ) -------------------------------------------------------------------------------- -- Recipe @@ -351,6 +365,38 @@ enumMapToAddrLiteral indentation chunkSize = then fromIntegral w else error $ "Cannot convert to Word8: " <> show a +-- | Encode a list of values as a byte map, using their 'Enum' instance. +enumMapToAddrLiteral' + :: forall a. (Bounded a, Enum a, Show a) + => Word8 + -- ^ Indentation + -> Int + -- ^ Chunk size + -> Word + -- ^ Word per value + -> [a] + -- ^ Values to encode + -> BB.Builder + -- ^ String to append + -> BB.Builder +enumMapToAddrLiteral' indentation chunkSize size = + chunkAddrLiteral indentation chunkSize addWords + + where + + upperBound = 1 `shiftL` (8 * fromIntegral size) + + addWords :: a -> BB.Builder -> BB.Builder + addWords x acc = foldMap (\w -> BB.char7 '\\' <> BB.word8Dec w) (toWord8LEs x) <> acc + + toWord8LEs :: a -> [Word8] + toWord8LEs a = let w = fromEnum a in if 0 <= w && w < upperBound + then go size w + else error $ "Cannot convert to Word8s: " <> show a <> " " <> show (size, upperBound) + + go 0 _ = [] + go k n = fromIntegral (n .&. 0xff) : go (k - 1) (n `shiftR` 8) + chunkAddrLiteral :: forall a. Word8 -- ^ Indentation @@ -396,6 +442,238 @@ chunksOf i = go word32ToWord8s :: Word32 -> [Word8] word32ToWord8s n = (\k -> fromIntegral ((n `shiftR` k) .&. 0xff)) <$> [0,8..24] +-------------------------------------------------------------------------------- +-- Bitmaps: Shamochu algorithm +-------------------------------------------------------------------------------- + +genEnumBitmapShamochu + :: forall a. (HasCallStack, Bounded a, Enum a, Eq a, Show a) + => String + -- ^ Function name + -> NE.NonEmpty Word + -- ^ Chunk size stage 1 + -> [Word] + -- ^ Chunk size stage 2 + -> (a -> Word8) + -- ^ Conversion + -> (a, BB.Builder) + -- ^ Value for planes 15-16 + -> (a, BB.Builder) + -- ^ Default value + -> [a] + -- ^ List of values to encode for planes 0 to 3 + -> [a] + -- ^ List of values to encode for plane 14 + -> BB.Builder +genEnumBitmapShamochu funcNameStr stage1 stage2 convert (defPUA, pPUA) (def, pDef) planes0To3 plane14 = + mconcat + [ "{-# INLINE ", funcName, " #-}\n" + , funcName, " :: Char -> Int\n" + , funcName, func + , "\n" + , generateShamochuBitmaps funcName03 stage1 stage2 convert bitmap03 + , "\n" + , case mBitmap14 of + Nothing -> mempty + Just bitmap14 -> generateShamochuBitmaps funcName14 stage1 stage2 convert bitmap14 <> "\n" + ] + where + funcName = BB.string7 funcNameStr + funcName03 = funcNameStr <> "Planes0To3" + funcName14 = funcNameStr <> "Plane14" + lookup03 = toLookupBitMapName funcName03 + lookup14 = toLookupBitMapName funcName14 + planes0To3' = L.dropWhileEnd (== def) planes0To3 + check = if length planes0To3 <= 0x40000 + then () + else error "genEnumBitmap: Cannot build" + (func, bitmap03, mBitmap14) = check `seq` if null plane14 && defPUA == def + -- Only planes 0-3 + then + ( mconcat + [ " = \\c -> let cp = ord c in if cp >= 0x" + , showPaddedHeXB (length planes0To3') + , " then " + , pDef + , " else ", lookup03, " cp\n" ] + , planes0To3' + , Nothing ) + -- All the planes + else + let plane14' = L.dropWhileEnd (== def) plane14 + bound1 = length planes0To3' + bound2 = 0xE0000 + length plane14' + in ( mconcat + [ " c\n" + , " -- Planes 0-3\n" + , " | cp < 0x", showPaddedHeXB bound1 + , " = ", lookup03, " cp\n" + , " -- Planes 4-13: ", showB def, "\n" + , " | cp < 0xE0000 = " <> pDef, "\n" + , " -- Plane 14\n" + , " | cp < 0x", showPaddedHeXB bound2 + , " = ", lookup14, " (cp - 0x" + , showPaddedHeXB 0xE0000 + , ")\n" + , if defPUA == def + then "" + else mconcat + [ " -- Plane 14: ", showB def, "\n" + , " | cp < 0xF0000 = ", pDef, "\n" + , " -- Plane 15: ", showB defPUA, "\n" + , " | cp < 0xFFFFE = ", pPUA, "\n" + , " -- Plane 15: ", showB def, "\n" + , " | cp < 0x100000 = ", pDef, "\n" + , " -- Plane 16: ", showB defPUA, "\n" + , " | cp < 0x10FFFE = ", pPUA, "\n" ] + , " -- Default: ", showB def, "\n" + , " | otherwise = " <> pDef, "\n" + , " where\n" + , " cp = ord c\n" ] + , planes0To3' + , Just plane14' ) + +generateShamochuBitmaps :: + String -> NE.NonEmpty Word -> [Word] -> (a -> Word8) -> [a] -> BB.Builder +generateShamochuBitmaps name powersStage1 powersStage2 convert xs = + case Shamochu.compress powersStage1 powersStage2 (Exts.fromList (convert <$> xs)) of + Shamochu.OneStage{..} -> trace' "OneStatege" stats $ mconcat + [ "{-# INLINE ", toLookupBitMapName name, " #-}\n" + , toLookupBitMapName name, " :: Int -> Int\n" + , toLookupBitMapName name, " n =\n" + -- Lookup: + -- mask = (1 << chunk_size_log2) - 1; + -- original[i] = data[offsets[i >> chunk_size_log2] + (i & mask)]; + , mkLookup (Shamochu.dataIntSize stats) "data" 1 . mconcat $ + [ mkLookup (Shamochu.offsets1IntSize stats) "offsets" 2 $ + mkIndent 3 <> mkShift "n" (Shamochu.dataChunkSizeLog2 stats) + , mkMask "n" "mask" ] + , "\n" + , " where\n" + , " mask = (1 `shiftL` ", BB.wordDec (Shamochu.dataChunkSizeLog2 stats), ") - 1\n" + , " !(Ptr data#) = ", dataBitMap, "\n" + , " !(Ptr offsets#) = ", offsetsBitMap, "\n" + , "\n" + , "{-# NOINLINE ", dataBitMap, " #-}\n" + , dataBitMap, " :: Ptr ", dataType, "\n" + , dataBitMap, " = Ptr\n" + , " \"", enumMapToAddrLiteral' + 4 + 50 + (Shamochu.dataIntSize stats `shiftR` 3) + (Exts.toList array) + "\"#\n" + , "\n" + , "{-# NOINLINE ", offsetsBitMap, " #-}\n" + , offsetsBitMap, " :: Ptr ", offsetType, "\n" + , offsetsBitMap, " = Ptr\n" + , " \"", enumMapToAddrLiteral' + 4 + 50 + (Shamochu.offsets1IntSize stats `shiftR` 3) + (Exts.toList offsets) + "\"#\n" + ] + where + Shamochu.CompressedArray{..} = array1 + dataBitMap = nameBB <> "DataBitMap" + offsetsBitMap = nameBB <> "OffsetsBitMap" + dataType = "Int" <> BB.wordDec (Shamochu.dataIntSize stats) + offsetType = "Word" <> BB.wordDec (Shamochu.offsets1IntSize stats) + Shamochu.TwoStages{..} -> trace' "TwoStages" stats $ mconcat + [ "{-# INLINE ", toLookupBitMapName name, " #-}\n" + , toLookupBitMapName name, " :: Int -> Int\n" + , toLookupBitMapName name, " n =\n" + -- Lookup: + -- mask_data = (1 << data_chunk_size_log2) - 1 + -- mask_offsets = (1 << offsets_chunk_size_log2) - 1 + -- data[ + -- offsets1[ + -- offsets2[ks >> (data_chunk_size_log2 + offsets_chunk_size_log2)] + + -- ((ks >> data_chunk_size_log2) & mask_offsets) + -- ] + + -- (ks & mask_data) + -- ]; + , mkLookup (Shamochu.dataIntSize stats) "data" 1 . mconcat $ + [ mkLookup (Shamochu.offsets1IntSize stats) "offsets1" 2 . mconcat $ + [ mkLookup (Shamochu.offsets2IntSize stats) "offsets2" 3 $ + mkIndent 4 <> + mkShift "n" (Shamochu.dataChunkSizeLog2 stats + Shamochu.offsets1ChunkSizeLog2 stats) + , mkMask ("(" <> mkShift "n" (Shamochu.dataChunkSizeLog2 stats) <> ")") "maskOffsets" + ] + , mkMask "n" "maskData" ] + , "\n" + , " where\n" + , " maskData = (1 `shiftL` ", BB.wordDec (Shamochu.dataChunkSizeLog2 stats), ") - 1\n" + , " maskOffsets = (1 `shiftL` ", BB.wordDec (Shamochu.offsets1ChunkSizeLog2 stats), ") - 1\n" + , " !(Ptr data#) = ", dataBitMap, "\n" + , " !(Ptr offsets1#) = ", offsets1BitMap, "\n" + , " !(Ptr offsets2#) = ", offsets2BitMap, "\n" + , "\n" + , "{-# NOINLINE ", dataBitMap, " #-}\n" + , dataBitMap, " :: Ptr ", dataType, "\n" + , dataBitMap, " = Ptr\n" + , " \"", enumMapToAddrLiteral' + 4 + 50 + (Shamochu.dataIntSize stats `shiftR` 3) + (Exts.toList dataArray) + "\"#\n" + , "\n" + , "{-# NOINLINE ", offsets1BitMap, " #-}\n" + , offsets1BitMap, " :: Ptr ", offset1Type, "\n" + , offsets1BitMap, " = Ptr\n" + , " \"", enumMapToAddrLiteral' + 4 + 50 + (Shamochu.offsets1IntSize stats `shiftR` 3) + (Exts.toList offset1Array) + "\"#\n" + , "\n" + , "{-# NOINLINE ", offsets2BitMap, " #-}\n" + , offsets2BitMap, " :: Ptr ", offset2Type, "\n" + , offsets2BitMap, " = Ptr\n" + , " \"", enumMapToAddrLiteral' + 4 + 50 + (Shamochu.offsets2IntSize stats `shiftR` 3) + (Exts.toList offsets2Array) + "\"#\n" + ] + where + Shamochu.CompressedArray{array=dataArray} = array1 + Shamochu.CompressedArray{array=offset1Array, offsets=offsets2Array} = array2 + dataBitMap = nameBB <> "DataBitMap" + offsets1BitMap = nameBB <> "Offsets1BitMap" + offsets2BitMap = nameBB <> "Offsets2BitMap" + dataType = "Int" <> BB.wordDec (Shamochu.dataIntSize stats) + offset1Type = "Word" <> BB.wordDec (Shamochu.offsets1IntSize stats) + offset2Type = "Word" <> BB.wordDec (Shamochu.offsets2IntSize stats) + where + trace' stages stats = trace $ mconcat + [ "* ", name, ": Shamochu: ", stages, "; savings: " + , show (fromRational (100 * (1 - 1 / toRational (Shamochu.ratio stats))) :: Centi) + , "%; " + , show stats ] + nameBB = BB.string7 name + mkIndent :: Word -> BB.Builder + mkIndent count = foldMap (const " ") [1..count] + mkLookup dataSize addrName indent index = mconcat + [ mkIndent indent + , "lookupWord", BB.wordDec dataSize, "AsInt ", addrName, "# (\n" + , index, "\n" + , mkIndent indent, ")" ] + mkShift n count = mconcat [n, " `shiftR` ", BB.wordDec count] + mkMask n mask = mconcat [" + (", n, " .&. ", mask, ")"] + +toTitle :: String -> String +toTitle = \case + c:cs -> toUpper c : cs + cs -> cs + +toLookupBitMapName :: String -> BB.Builder +toLookupBitMapName name = "lookup" <> BB.string7 (toTitle name) <> "BitMap" + -------------------------------------------------------------------------------- -- Helpers -------------------------------------------------------------------------------- diff --git a/ucd2haskell/exe/UCD2Haskell/Modules/UnicodeData/GeneralCategory.hs b/ucd2haskell/exe/UCD2Haskell/Modules/UnicodeData/GeneralCategory.hs index 48f2cd4..44ec06a 100644 --- a/ucd2haskell/exe/UCD2Haskell/Modules/UnicodeData/GeneralCategory.hs +++ b/ucd2haskell/exe/UCD2Haskell/Modules/UnicodeData/GeneralCategory.hs @@ -8,15 +8,22 @@ module UCD2Haskell.Modules.UnicodeData.GeneralCategory ( recipe ) where -import qualified Data.ByteString.Short as BS import qualified Data.ByteString.Builder as BB -import Data.Foldable (Foldable(..)) +import qualified Data.ByteString.Short as BS +import Data.Foldable (Foldable (..)) +import qualified Data.List as L +import qualified Data.List.NonEmpty as NE import qualified Unicode.CharacterDatabase.Parser.Common as U import qualified Unicode.CharacterDatabase.Parser.UnicodeData as UD -import UCD2Haskell.Generator (FileRecipe (..), unlinesBB, apacheLicense, genEnumBitmap) -import UCD2Haskell.Common (Fold (..), showHexCodepointB, showB) -import qualified Data.List as L +import UCD2Haskell.Common (Fold (..), showB, showHexCodepointB) +import UCD2Haskell.Generator ( + FileRecipe (..), + apacheLicense, + genEnumBitmapShamochu, + unlinesBB, + ) +import Control.Exception (assert) recipe :: FileRecipe UD.Entry recipe = ModuleRecipe @@ -100,10 +107,12 @@ genGeneralCategoryModule moduleName = Fold step initial done , foldMapWithNewLine mkCharBoundPatternExport charBoundPatterns , ") where" , "" + , "import Data.Bits (Bits(..))" , "import Data.Char (ord)" - , "import Data.Word (Word8)" + , "import Data.Int (Int8)" + , "import Data.Word (Word8, Word16)" , "import GHC.Exts (Ptr(..))" - , "import Unicode.Internal.Bits (lookupWord8AsInt)" + , "import Unicode.Internal.Bits (lookupWord8AsInt, lookupWord16AsInt)" , "" , "--------------------------------------------------------------------------------" , "-- General category patterns" @@ -122,19 +131,23 @@ genGeneralCategoryModule moduleName = Fold step initial done , "-- The caller of this function must ensure its parameter is \\< @0x40000@." , "{-# INLINE generalCategoryPlanes0To3 #-}" , "generalCategoryPlanes0To3 :: Int -> Int" - , "generalCategoryPlanes0To3 = lookupWord8AsInt bitmap#" - , " where" - , " !(Ptr bitmap#) = generalCategoryBitmap" + , "generalCategoryPlanes0To3 = lookupGeneralCategoryPlanes0To3BitMap" , "" , "-- | Return the general category of a character" - , genEnumBitmap + , genEnumBitmapShamochu "generalCategory" + (NE.singleton 3) + [5] + toWord8 (UD.Co, generalCategoryConstructor UD.Co) (UD.Cn, generalCategoryConstructor UD.Cn) (reverse acc1) (reverse acc2) ] where + toWord8 = + assert (fromEnum (maxBound :: UD.GeneralCategory) < 0xff) + (fromIntegral . fromEnum) foldMapWithNewLine f = mconcat . L.intersperse "\n" . fmap f mkExport p = ", pattern " <> p mkGeneralCategoryPatternExport = mkExport . generalCategoryConstructor diff --git a/ucd2haskell/ucd2haskell.cabal b/ucd2haskell/ucd2haskell.cabal index ecf70c1..d4ae755 100644 --- a/ucd2haskell/ucd2haskell.cabal +++ b/ucd2haskell/ucd2haskell.cabal @@ -101,6 +101,7 @@ executable ucd2haskell , directory >= 1.3.6 && < 1.4 , filepath >= 1.4.100 && < 1.5 , getopt-generics >= 0.13 && < 0.14 + , shamochu >= 0.1.0 && < 0.2 , unicode-data-parser >= 0.3.0 && < 0.4 else buildable: False diff --git a/unicode-data/lib/Unicode/Internal/Bits.hs b/unicode-data/lib/Unicode/Internal/Bits.hs index 5717d5c..5bc8ac1 100644 --- a/unicode-data/lib/Unicode/Internal/Bits.hs +++ b/unicode-data/lib/Unicode/Internal/Bits.hs @@ -14,6 +14,7 @@ module Unicode.Internal.Bits ( lookupBit64, lookupWord8AsInt, + lookupWord16AsInt, lookupWord32# ) where @@ -22,14 +23,17 @@ module Unicode.Internal.Bits import Data.Bits (finiteBitSize, popCount) import GHC.Exts (Addr#, Int(..), Int#, Word(..), Word#, - indexWordOffAddr#, indexWord8OffAddr#, indexWord32OffAddr#, + indexWordOffAddr#, indexWord8OffAddr#, + indexWord16OffAddr#, indexWord32OffAddr#, andI#, uncheckedIShiftRL#, and#, word2Int#, uncheckedShiftL#) #if MIN_VERSION_base(4,16,0) -import GHC.Exts (word8ToWord#, word32ToWord#) +import GHC.Exts (word8ToWord#, word16ToWord#, word32ToWord#) #endif #ifdef WORDS_BIGENDIAN -import GHC.Exts (byteSwap#, narrow32Word#, byteSwap32#) +import GHC.Exts + (byteSwap#, narrow16Word#, narrow32Word#, + byteSwap16#, byteSwap32#) #endif -- | @lookup64 addr index@ looks up the bit stored at bit index @index@ using a @@ -77,6 +81,24 @@ lookupWord8AsInt addr# (I# index#) = I# (word2Int# word##) word## = indexWord8OffAddr# addr# index# #endif +lookupWord16AsInt + :: Addr# -- ^ Bitmap address + -> Int -- ^ Word index + -> Int -- ^ Resulting word as `Int` +lookupWord16AsInt addr# (I# k#) = I# (word2Int# word##) + where +#ifdef WORDS_BIGENDIAN +#if MIN_VERSION_base(4,16,0) + word## = narrow16Word# (byteSwap16# (word16ToWord# (indexWord16OffAddr# addr# k#))) +#else + word## = narrow16Word# (byteSwap16# (indexWord16OffAddr# addr# k#)) +#endif +#elif MIN_VERSION_base(4,16,0) + word## = word16ToWord# (indexWord16OffAddr# addr# k#) +#else + word## = indexWord16OffAddr# addr# k# +#endif + {-| @lookupWord32# addr index@ looks up for the @index@-th 32-bits word in the bitmap starting at @addr@, then convert it to a 'Word#'. diff --git a/unicode-data/lib/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs b/unicode-data/lib/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs index 5bf745a..1f40a11 100644 --- a/unicode-data/lib/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs +++ b/unicode-data/lib/Unicode/Internal/Char/UnicodeData/GeneralCategory.hs @@ -56,10 +56,12 @@ module Unicode.Internal.Char.UnicodeData.GeneralCategory , pattern MaxIsSeparator ) where +import Data.Bits (Bits(..)) import Data.Char (ord) -import Data.Word (Word8) +import Data.Int (Int8) +import Data.Word (Word8, Word16) import GHC.Exts (Ptr(..)) -import Unicode.Internal.Bits (lookupWord8AsInt) +import Unicode.Internal.Bits (lookupWord8AsInt, lookupWord16AsInt) -------------------------------------------------------------------------------- -- General category patterns @@ -226,20 +228,18 @@ pattern MaxIsSeparator = 0x3000 -- The caller of this function must ensure its parameter is \< @0x40000@. {-# INLINE generalCategoryPlanes0To3 #-} generalCategoryPlanes0To3 :: Int -> Int -generalCategoryPlanes0To3 = lookupWord8AsInt bitmap# - where - !(Ptr bitmap#) = generalCategoryBitmap +generalCategoryPlanes0To3 = lookupGeneralCategoryPlanes0To3BitMap -- | Return the general category of a character {-# INLINE generalCategory #-} generalCategory :: Char -> Int generalCategory c -- Planes 0-3 - | cp < 0x323B0 = lookupWord8AsInt bitmap# cp + | cp < 0x323B0 = lookupGeneralCategoryPlanes0To3BitMap cp -- Planes 4-13: Cn | cp < 0xE0000 = NotAssigned -- Plane 14 - | cp < 0xE01F0 = lookupWord8AsInt bitmap# (cp - 0xADC50) + | cp < 0xE01F0 = lookupGeneralCategoryPlane14BitMap (cp - 0xE0000) -- Plane 14: Cn | cp < 0xF0000 = NotAssigned -- Plane 15: Co @@ -252,816 +252,230 @@ generalCategory c | otherwise = NotAssigned where cp = ord c - !(Ptr bitmap#) = generalCategoryBitmap -generalCategoryBitmap :: Ptr Word8 -generalCategoryBitmap = Ptr - "\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\22\17\17\17\19\17\17\17\13\14\17\18\17\12\17\17\8\8\8\8\8\8\8\8\8\8\17\17\18\18\18\17\17\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\13\17\14\20\11\20\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\13\18\14\18\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\25\22\17\19\19\19\19\21\17\20\21\4\15\18\26\21\20\21\18\10\10\20\1\17\17\20\10\4\16\10\10\10\17\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\1\ - \\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\0\1\0\1\0\1\1\1\0\0\1\0\1\0\0\1\0\0\0\1\1\0\0\0\0\1\0\0\1\0\0\0\1\1\1\0\0\1\0\0\1\0\1\0\1\0\0\1\0\1\1\0\1\0\0\1\0\0\0\1\0\1\0\0\1\1\4\0\1\1\1\4\4\4\4\0\2\1\0\2\1\0\2\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\0\2\1\0\1\0\0\0\1\0\1\0\1\ - \\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\1\1\1\1\1\0\0\1\0\0\1\1\0\1\0\0\0\0\1\0\1\0\1\0\1\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\4\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\20\20\20\20\3\3\3\3\3\3\3\3\3\3\3\3\20\20\20\20\20\20\20\20\20\20\20\20\20\20\3\3\3\3\3\20\20\20\20\20\20\20\3\20\3\20\20\20\20\20\20\20\20\20\20\20\20\20\20\ - \\20\20\20\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\0\1\0\1\3\20\0\1\29\29\3\1\1\1\17\0\29\29\29\29\20\20\0\17\0\0\0\29\0\29\0\0\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\1\1\0\0\0\1\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\1\1\1\0\1\18\0\1\0\0\1\ - \\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\21\5\5\5\5\5\7\7\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\ - \\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\29\3\17\17\17\17\17\17\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\17\12\29\29\21\21\19\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\12\5\17\5\5\17\5\5\17\5\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\4\4\4\4\17\17\29\29\29\29\29\ - \\29\29\29\29\29\29\26\26\26\26\26\26\18\18\18\17\17\19\17\17\21\21\5\5\5\5\5\5\5\5\5\5\5\17\26\17\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\8\8\8\8\8\8\8\8\8\8\17\17\17\17\4\4\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\17\4\5\5\5\5\5\5\5\26\21\5\5\5\5\5\5\3\3\5\5\21\5\5\5\5\4\4\8\8\8\8\8\8\8\8\8\ - \\8\4\4\4\21\21\4\17\17\17\17\17\17\17\17\17\17\17\17\17\17\29\26\4\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\3\3\21\17\ - \\17\17\3\29\29\5\19\19\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\3\5\5\5\5\5\5\5\5\5\3\5\5\5\3\5\5\5\5\5\29\29\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\29\29\17\29\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\20\4\4\4\4\4\4\29\26\26\29\29\29\29\29\29\5\5\5\5\5\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\26\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\ - \\5\5\5\5\5\5\5\5\5\5\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\5\4\6\6\6\5\5\5\5\5\5\5\5\6\6\6\6\5\6\6\4\5\5\5\5\5\5\5\4\4\4\4\4\4\4\4\4\4\5\5\17\17\8\8\8\8\8\8\8\8\8\8\17\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\6\29\4\4\4\4\4\4\4\4\29\29\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\29\29\29\4\4\4\4\29\29\5\4\6\6\6\5\5\5\5\29\29\6\6\29\29\6\6\5\4\29\29\29\29\29\29\29\29\6\29\29\29\29\4\4\29\4\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\4\4\19\19\10\10\ - \\10\10\10\10\21\19\4\17\5\29\29\5\5\6\29\4\4\4\4\4\4\29\29\29\29\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\29\4\4\29\4\4\29\29\5\29\6\6\6\5\5\29\29\29\29\5\5\29\29\5\5\5\29\29\29\5\29\29\29\29\29\29\29\4\4\4\4\29\4\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\5\5\4\4\4\5\17\29\29\29\29\29\29\29\29\29\29\5\5\6\29\4\4\4\4\4\4\4\4\4\29\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\29\29\5\4\6\6\6\5\5\5\5\5\29\5\5\6\29\6\6\5\29\29\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\17\19\29\29\29\ - \\29\29\29\29\4\5\5\5\5\5\5\29\5\6\6\29\4\4\4\4\4\4\4\4\29\29\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\29\29\5\4\6\5\6\5\5\5\5\29\29\6\6\29\29\6\6\5\29\29\29\29\29\29\29\5\5\6\29\29\29\29\4\4\29\4\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\21\4\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\5\4\29\4\4\4\4\4\4\29\29\29\4\4\4\29\4\4\4\4\29\29\29\4\4\29\4\29\4\4\29\29\29\4\4\29\29\29\4\4\4\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\6\6\5\6\6\29\29\29\6\6\6\29\6\6\6\5\29\29\4\29\29\29\29\29\29\6\29\29\29\29\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\10\10\10\21\ - \\21\21\21\21\21\19\21\29\29\29\29\29\5\6\6\6\5\4\4\4\4\4\4\4\4\29\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\4\5\5\5\6\6\6\6\29\5\5\5\29\5\5\5\5\29\29\29\29\29\29\29\5\5\29\4\4\4\29\29\4\29\29\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\17\10\10\10\10\10\10\10\21\4\5\6\6\17\4\4\4\4\4\4\4\4\29\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\29\29\5\4\6\5\6\6\6\6\6\29\5\6\6\29\6\6\5\5\29\29\29\29\29\29\29\6\6\29\29\29\29\29\29\4\4\29\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\29\4\4\ - \\6\29\29\29\29\29\29\29\29\29\29\29\29\5\5\6\6\4\4\4\4\4\4\4\4\4\29\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\4\6\6\6\5\5\5\5\29\6\6\6\29\6\6\6\5\4\21\29\29\29\29\4\4\4\6\10\10\10\10\10\10\10\4\4\4\5\5\29\29\8\8\8\8\8\8\8\8\8\8\10\10\10\10\10\10\10\10\10\21\4\4\4\4\4\4\29\5\6\6\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\29\4\29\29\4\4\4\4\4\4\4\29\29\29\5\29\29\29\29\6\6\6\5\5\5\29\5\29\6\6\6\6\6\6\6\6\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\ - \\6\6\17\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\4\4\5\5\5\5\5\5\5\29\29\29\29\19\4\4\4\4\4\4\3\5\5\5\5\5\5\5\5\17\8\8\8\8\8\8\8\8\8\8\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\29\4\29\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\29\4\4\4\4\4\4\4\4\4\4\5\4\4\5\5\5\5\5\5\5\5\5\4\29\29\4\4\4\4\4\29\3\29\5\5\5\5\5\5\5\29\8\8\8\8\8\8\8\8\8\8\29\29\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\21\21\21\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\21\17\21\21\21\5\5\21\21\21\21\21\21\8\8\8\8\8\8\8\8\8\8\10\10\10\10\10\10\10\10\10\10\21\5\21\5\21\5\13\14\13\14\6\6\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\6\5\5\5\5\5\17\5\5\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\21\21\21\21\21\21\21\21\5\21\21\21\21\21\21\29\21\21\17\17\17\17\17\21\21\21\21\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\5\5\5\5\6\5\5\5\5\5\5\6\5\5\6\6\5\5\4\8\8\8\8\8\8\8\8\8\8\17\17\17\17\17\17\4\4\4\4\4\4\6\6\5\5\4\4\4\4\5\5\5\4\6\6\6\4\4\6\6\6\6\6\6\6\4\4\4\5\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\6\5\5\6\6\6\6\6\6\5\4\6\8\8\8\8\8\8\8\8\8\8\6\6\6\5\21\21\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\0\29\29\29\29\29\0\29\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\1\1\1\1\1\1\1\1\1\1\1\1\17\3\1\1\1\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\29\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\29\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\5\17\17\17\17\17\17\17\17\17\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\ - \\0\0\0\0\0\0\0\0\0\0\29\29\1\1\1\1\1\1\29\29\12\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\22\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\13\14\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\17\17\17\9\9\9\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\6\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\6\17\17\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\29\5\5\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\6\5\5\5\5\5\5\5\6\6\6\6\6\6\6\6\5\6\6\5\5\5\5\5\5\5\5\5\5\5\17\17\17\3\17\17\17\19\4\5\29\29\8\8\8\8\8\8\8\8\ - \\8\8\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\17\17\17\17\17\17\12\17\17\17\17\5\5\5\26\5\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\4\4\4\4\4\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\5\5\5\6\6\6\6\5\5\6\6\6\29\29\29\29\6\6\5\6\6\6\6\6\6\5\5\5\29\29\29\29\21\29\29\29\17\17\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\10\29\29\29\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\6\6\5\29\29\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\5\6\5\5\5\5\5\5\5\29\5\6\5\6\6\5\5\5\5\5\5\5\5\6\6\6\6\6\6\5\5\5\5\5\5\5\5\5\5\29\29\5\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\17\17\17\17\17\17\17\3\17\17\17\17\17\17\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\7\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\5\5\5\5\5\6\5\6\6\6\6\6\5\6\6\4\4\4\4\4\4\4\4\29\29\29\8\8\8\8\8\8\8\8\8\8\17\17\17\17\17\17\17\21\21\21\21\21\21\21\21\21\21\5\5\5\5\5\5\5\5\5\21\21\21\21\21\21\21\21\21\17\17\29\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\5\5\5\5\6\6\5\5\6\5\5\5\4\4\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\5\6\5\5\6\6\6\5\6\5\5\5\6\6\29\29\29\29\29\29\29\29\17\17\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\6\6\6\6\6\5\5\5\5\5\5\5\5\6\6\5\5\29\29\29\17\17\17\17\17\8\8\8\8\8\8\8\8\8\8\29\29\29\4\4\4\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\3\3\3\3\3\17\17\1\1\1\1\1\1\1\1\1\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\29\0\0\0\17\17\17\17\17\17\17\17\29\29\29\29\29\29\29\29\5\5\5\17\5\5\5\5\5\5\5\5\5\5\5\5\5\6\5\ - \\5\5\5\5\5\5\4\4\4\4\5\4\4\4\4\4\4\5\4\4\6\5\5\4\29\29\29\29\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\1\1\1\1\1\1\1\1\1\1\1\1\1\3\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\ - \\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\1\1\1\1\1\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\ - \\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\1\1\1\1\1\1\29\29\0\0\0\0\0\0\29\29\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\1\1\1\1\1\1\29\29\0\0\0\0\0\0\29\29\1\1\1\1\1\1\1\1\29\0\29\0\29\0\29\0\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\29\29\1\1\1\1\1\1\1\1\2\2\2\2\2\2\2\2\1\1\1\1\1\1\1\1\2\2\2\2\2\2\2\2\1\1\1\1\1\1\1\1\2\2\2\2\2\2\2\2\1\1\1\1\1\29\1\1\0\0\0\0\2\20\1\20\20\20\1\1\1\29\1\1\0\0\0\0\2\20\20\20\1\1\1\1\29\29\1\1\0\0\0\0\29\20\20\20\ - \\1\1\1\1\1\1\1\1\0\0\0\0\0\20\20\20\29\29\1\1\1\29\1\1\0\0\0\0\2\20\20\29\22\22\22\22\22\22\22\22\22\22\22\26\26\26\26\26\12\12\12\12\12\12\17\17\15\16\13\15\15\16\13\15\17\17\17\17\17\17\17\17\23\24\26\26\26\26\26\22\17\17\17\17\17\17\17\17\17\15\16\17\17\17\17\11\11\17\17\17\18\13\14\17\17\17\17\17\17\17\17\17\17\17\18\17\11\17\17\17\17\17\17\17\17\17\17\22\26\26\26\26\26\29\26\26\26\26\26\26\26\26\26\26\10\3\29\29\10\10\10\10\10\10\18\18\18\13\14\3\10\10\10\10\10\10\10\10\10\10\18\18\18\13\14\29\3\3\3\3\3\3\3\3\3\3\3\3\3\29\29\29\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\19\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\7\7\ - \\7\7\5\7\7\7\5\5\5\5\5\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\0\21\21\21\21\0\21\21\1\0\0\0\1\1\0\0\0\1\21\0\21\21\18\0\0\0\0\0\21\21\21\21\21\21\0\21\0\21\0\21\0\0\0\0\21\1\0\0\0\0\1\4\4\4\4\1\21\21\1\1\0\0\18\18\18\18\18\0\1\1\1\1\21\18\21\21\1\21\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\0\1\9\9\9\9\10\21\21\29\29\29\29\18\18\18\18\18\21\21\21\21\21\18\18\21\21\21\21\18\21\21\18\21\21\18\21\21\21\21\21\21\21\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\21\21\18\21\18\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\ - \\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\21\21\21\21\21\21\21\21\13\14\13\14\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\21\21\21\21\21\21\21\13\14\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\21\21\21\21\21\21\21\21\21\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\13\14\13\14\13\14\13\14\13\14\13\14\13\14\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\13\14\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\ - \\18\18\18\18\18\18\18\18\18\18\18\18\18\18\13\14\13\14\13\14\13\14\13\14\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\13\14\13\14\13\14\13\14\13\14\13\14\13\14\13\14\13\14\13\14\13\14\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\ - \\18\18\13\14\13\14\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\13\14\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\ - \\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\21\21\18\18\18\18\18\18\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\1\0\0\0\1\1\0\1\0\1\0\1\0\0\0\0\1\0\1\1\0\1\1\1\1\1\1\3\3\0\0\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\ - \\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\21\21\21\21\21\21\0\1\0\1\5\5\5\0\1\29\29\29\29\29\17\17\17\17\10\17\17\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\29\1\29\29\29\29\29\1\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\3\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\ - \\4\4\4\4\4\29\4\4\4\4\4\4\4\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\17\17\15\16\15\16\17\17\17\15\16\17\15\16\17\17\17\17\17\17\17\17\17\12\17\17\12\17\15\16\17\17\15\16\13\14\13\14\13\14\13\14\17\17\17\17\17\3\17\17\17\17\17\17\17\17\17\17\12\12\17\17\17\17\12\17\13\17\17\17\17\17\17\17\17\17\17\17\17\17\21\21\17\17\17\13\14\13\14\13\14\13\14\12\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\22\17\17\17\21\3\4\9\13\14\13\14\13\14\13\14\13\14\21\21\13\14\13\14\13\14\13\14\12\13\14\14\21\9\9\9\9\9\9\9\9\9\5\5\5\5\6\6\12\3\3\3\3\3\21\21\9\9\9\3\4\17\21\21\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\20\20\3\3\4\12\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\17\3\3\3\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\21\21\10\10\10\10\21\21\21\21\21\21\21\21\21\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\10\10\10\10\10\10\10\10\21\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\3\3\3\3\3\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\17\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\8\8\8\8\8\8\8\8\8\8\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\ - \\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\4\5\7\7\7\17\5\5\5\5\5\5\5\5\5\5\17\3\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\3\3\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\9\9\9\9\9\9\9\9\9\9\5\5\17\17\17\17\17\17\29\29\29\29\29\29\29\29\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\3\3\3\3\3\3\3\3\3\20\20\0\1\0\1\0\1\0\1\0\1\0\1\0\1\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\ - \\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\3\1\1\1\1\1\1\1\1\0\1\0\1\0\0\1\0\1\0\1\0\1\0\1\3\20\20\0\1\0\1\4\0\1\0\1\1\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\0\0\0\0\1\0\0\0\0\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\0\0\0\1\0\1\29\29\29\29\29\0\1\29\1\29\1\0\1\0\1\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\3\3\3\0\1\4\3\3\1\4\4\4\4\4\4\4\5\4\4\4\5\4\4\4\4\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\5\5\6\21\21\21\21\5\29\29\29\10\10\10\10\10\10\21\21\19\21\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\17\17\17\17\29\29\29\29\29\29\29\29\6\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\5\5\29\29\29\29\29\29\29\29\17\17\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\4\4\4\4\4\4\17\17\17\4\17\4\4\5\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\6\6\29\29\ - \\29\29\29\29\29\29\29\29\29\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\5\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\6\5\5\5\5\6\6\5\5\6\6\6\17\17\17\17\17\17\17\17\17\17\17\17\17\29\3\8\8\8\8\8\8\8\8\8\8\29\29\29\29\17\17\4\4\4\4\4\5\3\4\4\4\4\4\4\4\4\4\8\8\8\8\8\8\8\8\8\8\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\6\6\5\5\6\6\5\5\29\29\29\29\29\29\29\29\29\4\4\4\5\4\4\4\4\4\4\4\4\5\6\29\29\8\8\8\8\8\ - \\8\8\8\8\8\29\29\17\17\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\4\4\4\4\4\4\21\21\21\4\6\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\4\5\5\5\4\4\5\5\4\4\4\4\4\5\5\4\5\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\3\17\17\4\4\4\4\4\4\4\4\4\4\4\6\5\5\6\6\17\17\4\3\3\6\5\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\29\29\4\4\4\4\4\4\29\29\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\1\1\1\1\1\1\1\20\3\3\3\3\1\1\1\1\1\1\1\1\1\3\20\20\29\29\29\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\5\6\6\5\6\6\17\6\5\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\ - \\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\27\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\ - \\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\28\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\1\1\1\1\ - \\1\1\1\29\29\29\29\29\29\29\29\29\29\29\29\1\1\1\1\1\29\29\29\29\29\4\5\4\4\4\4\4\4\4\4\4\4\18\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\29\4\29\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\20\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\14\13\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\19\21\21\21\5\ - \\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\17\17\17\17\17\17\17\13\14\17\29\29\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\17\12\12\11\11\13\14\13\14\13\14\13\14\13\14\13\14\13\14\13\14\17\17\13\14\17\17\17\17\11\11\11\17\17\17\29\17\17\17\17\12\13\14\13\14\13\14\17\17\17\18\12\18\18\18\29\17\19\17\17\29\29\29\29\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\26\ - \\29\17\17\17\19\17\17\17\13\14\17\18\17\12\17\17\8\8\8\8\8\8\8\8\8\8\17\17\18\18\18\17\17\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\13\17\14\20\11\20\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\13\18\14\18\13\14\17\13\14\17\17\4\4\4\4\4\4\4\4\4\4\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\4\4\4\4\4\4\29\29\4\4\4\4\4\4\29\29\4\4\4\4\4\4\29\29\4\4\4\29\29\29\19\19\18\20\21\19\19\29\21\18\18\18\18\21\21\29\29\29\29\29\29\29\29\29\29\26\26\26\21\21\29\ - \\29\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\ - \\29\29\17\17\17\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\21\21\21\21\21\21\21\21\21\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\10\10\10\10\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\10\10\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\ - \\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\10\10\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\9\4\4\4\4\4\4\4\4\9\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\4\4\4\4\4\4\4\4\17\9\9\9\9\9\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\29\29\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\1\1\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\17\0\0\0\0\0\0\0\0\0\0\0\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\0\0\0\0\0\0\0\29\0\0\29\1\1\1\1\1\1\1\1\1\1\1\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\29\1\1\1\1\1\1\1\29\1\1\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\3\3\3\3\3\3\29\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\29\3\3\3\3\3\3\3\3\3\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\29\29\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\29\29\29\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\17\10\10\10\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\21\21\10\10\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\ - \\29\29\29\29\29\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\10\10\10\10\29\29\29\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\10\10\4\4\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\ - \\10\10\10\10\10\10\10\10\10\10\10\4\5\5\5\29\5\5\29\29\29\29\29\5\5\5\5\4\4\4\4\29\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\5\29\29\29\29\5\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\17\17\17\17\17\17\17\17\17\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\21\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\29\29\29\29\10\10\10\10\10\17\17\17\17\ - \\17\17\17\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\17\17\17\17\17\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\10\10\10\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\10\10\10\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\29\29\29\29\29\29\29\29\29\29\29\29\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\1\29\29\29\29\29\29\29\10\10\10\10\10\10\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\5\5\12\29\29\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\10\10\10\10\10\10\10\10\4\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\10\10\10\10\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\6\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\17\17\17\17\17\17\17\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\8\8\8\8\8\8\8\8\8\8\5\4\4\5\5\4\29\29\29\29\29\29\29\29\29\5\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\6\6\5\5\17\17\26\17\17\17\17\5\29\29\29\29\29\29\29\29\29\29\26\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\ - \\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\6\5\5\5\5\5\5\5\5\29\8\8\8\8\8\8\8\8\8\8\17\17\17\17\4\6\6\4\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\17\17\4\29\29\29\29\29\29\29\29\29\5\5\6\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\5\5\5\5\5\6\6\4\4\4\4\17\17\17\17\5\5\5\5\17\6\5\8\8\8\8\8\8\8\8\8\8\4\17\4\17\17\17\29\10\10\10\10\10\10\10\10\10\10\10\10\ - \\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\6\6\5\6\5\5\17\17\17\17\17\17\5\4\4\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\29\4\29\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\17\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\6\6\5\5\5\5\5\5\5\5\29\ - \\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\5\5\6\6\29\4\4\4\4\4\4\4\4\29\29\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\29\5\5\4\6\6\5\6\6\6\6\29\29\6\6\29\29\6\6\6\29\29\4\29\29\29\29\29\29\6\29\29\29\29\29\4\4\4\4\4\6\6\29\29\5\5\5\5\5\5\5\29\29\29\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\5\5\5\5\6\6\5\5\5\6\5\4\4\4\4\17\17\17\17\17\8\8\8\8\8\8\8\8\8\8\17\17\29\17\5\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\5\5\6\5\6\6\6\6\5\5\6\5\5\4\4\17\4\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\29\29\6\6\6\6\5\5\6\5\5\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\17\4\4\4\4\5\5\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\5\5\5\5\6\6\5\6\5\5\17\17\17\4\29\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\17\17\17\17\17\17\17\17\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\6\5\6\6\5\5\5\5\5\5\6\5\4\17\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\5\6\6\5\5\5\5\6\5\5\5\5\5\29\29\29\29\8\8\8\8\8\8\8\8\8\8\10\10\17\17\17\21\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\5\5\5\5\5\6\5\5\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\8\8\8\8\8\8\ - \\8\8\8\8\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\29\29\4\29\29\4\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\6\6\6\29\6\6\29\29\5\5\6\5\4\6\4\6\5\17\17\17\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\5\5\5\5\29\29\5\5\6\6\6\6\5\4\17\4\6\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\5\5\5\5\5\5\5\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\6\4\5\5\5\5\17\17\17\17\17\17\17\17\5\29\29\29\29\29\29\29\29\4\5\5\5\5\5\5\6\6\5\5\5\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\5\5\6\5\5\17\17\17\4\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\17\17\17\17\17\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\5\5\5\5\5\5\5\29\5\5\5\5\5\5\6\5\4\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\6\5\5\5\5\5\5\5\6\5\5\6\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\29\29\29\5\29\5\5\29\5\5\5\5\5\5\5\4\5\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\4\4\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\6\6\6\29\5\5\29\6\6\5\6\5\4\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\6\6\17\17\29\29\29\29\29\29\29\5\5\4\6\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\6\6\5\5\5\5\5\29\29\29\6\6\5\6\5\17\17\17\17\17\17\17\17\17\17\17\17\17\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\21\21\21\21\21\21\21\19\19\ - \\19\19\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\9\29\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\5\4\4\4\4\4\4\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\17\17\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\5\5\5\5\5\17\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\5\5\5\17\17\17\17\17\21\21\21\21\3\3\3\3\17\21\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\10\10\10\10\10\10\10\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\ - \\10\10\10\10\10\10\10\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\5\4\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\6\29\29\29\29\29\29\29\ - \\5\5\5\5\3\3\3\3\3\3\3\3\3\3\3\3\3\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\3\3\17\3\5\29\29\29\29\29\29\29\29\29\29\29\6\6\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\3\3\3\3\29\3\3\3\3\3\3\3\29\3\3\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\4\4\4\29\29\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\29\29\21\5\5\17\26\26\26\26\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\ - \\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\6\6\5\5\5\21\21\21\6\6\6\6\6\6\26\26\26\26\26\26\26\26\5\5\5\5\5\5\5\5\21\21\5\5\5\5\5\5\5\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\5\5\5\5\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\5\5\5\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\29\0\0\29\29\0\29\29\0\0\29\29\0\0\0\0\29\0\0\0\0\0\0\0\0\1\1\1\1\29\1\29\1\1\1\1\1\1\1\29\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\29\0\0\0\0\29\29\0\0\0\0\0\0\0\0\29\0\0\0\0\0\0\0\29\1\1\1\1\1\1\1\1\1\1\1\ - \\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\29\0\0\0\0\29\0\0\0\0\0\29\0\29\29\29\0\0\0\0\0\0\0\29\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\ - \\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\ - \\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\18\1\1\1\1\1\1\0\1\29\29\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\8\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\ - \\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\21\21\21\21\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\21\21\21\21\21\21\21\21\5\21\21\21\21\21\21\21\21\21\21\21\21\21\21\5\21\21\17\17\17\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\5\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\1\1\1\1\1\1\1\1\1\1\4\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\ - \\29\29\29\29\29\29\1\1\1\1\1\1\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\5\5\5\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\29\29\5\5\5\ - \\5\5\5\5\29\5\5\29\5\5\5\5\5\29\29\29\29\29\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\3\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\5\5\5\5\5\5\5\3\3\3\3\3\3\3\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\4\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\5\5\5\5\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\19\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\3\5\5\5\5\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\29\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\10\10\10\10\10\10\10\10\10\5\5\5\5\5\5\5\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\ - \\0\0\0\0\0\0\0\0\0\0\0\0\0\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\1\5\5\5\5\5\5\5\3\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\17\17\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\10\10\10\19\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\ - \\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\21\10\10\10\10\10\10\10\10\10\10\10\10\10\10\10\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\4\4\29\4\29\29\4\29\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\29\4\29\4\29\29\29\29\29\29\4\29\29\29\29\4\29\4\29\4\29\4\4\4\29\4\4\29\4\29\29\4\29\4\29\4\29\4\29\4\29\4\4\29\4\29\29\4\4\4\4\29\4\4\4\4\4\4\4\29\4\4\4\4\29\4\4\4\4\29\4\29\4\4\4\4\4\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\4\4\4\29\4\4\4\4\4\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\18\18\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\10\10\10\10\10\10\10\10\10\10\10\10\10\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\20\20\20\20\20\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\ - \\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\21\21\21\ - \\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\8\8\8\8\8\8\8\8\8\8\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\ - \\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\29\29\29\29\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\ - \\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\29\26\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\26\26\26\26\26\26\26\26\26\ - \\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\26\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\29\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\ - \\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5\5"# +{-# INLINE lookupGeneralCategoryPlanes0To3BitMap #-} +lookupGeneralCategoryPlanes0To3BitMap :: Int -> Int +lookupGeneralCategoryPlanes0To3BitMap n = + lookupWord8AsInt data# ( + lookupWord16AsInt offsets1# ( + lookupWord16AsInt offsets2# ( + n `shiftR` 8 + ) + ((n `shiftR` 3) .&. maskOffsets) + ) + (n .&. maskData) + ) + where + maskData = (1 `shiftL` 3) - 1 + maskOffsets = (1 `shiftL` 5) - 1 + !(Ptr data#) = generalCategoryPlanes0To3DataBitMap + !(Ptr offsets1#) = generalCategoryPlanes0To3Offsets1BitMap + !(Ptr offsets2#) = generalCategoryPlanes0To3Offsets2BitMap + +{-# NOINLINE generalCategoryPlanes0To3DataBitMap #-} +generalCategoryPlanes0To3DataBitMap :: Ptr Int8 +generalCategoryPlanes0To3DataBitMap = Ptr + "\1\0\0\1\0\1\0\0\0\0\0\1\0\1\0\1\1\0\1\1\0\1\0\0\0\1\1\0\0\0\1\1\1\13\18\14\18\13\14\17\17\17\17\17\3\3\3\3\29\3\ + \\3\29\3\3\3\3\3\3\29\3\3\3\3\3\3\17\17\4\3\3\6\5\29\20\1\1\1\1\1\1\1\1\18\1\1\1\1\4\1\1\1\1\1\3\3\0\0\0\0\2\ + \\20\1\20\21\4\15\18\26\21\20\10\4\16\10\10\10\17\0\0\0\0\0\0\0\0\18\1\1\1\1\1\1\29\29\1\1\1\29\1\1\29\29\29\10\10\10\10\10\10\10\ + \\21\10\10\10\10\10\10\10\17\19\17\17\29\29\29\29\4\4\4\4\4\5\3\4\1\21\21\1\1\0\0\1\1\0\0\0\1\0\1\0\1\0\1\0\0\0\0\1\4\4\ + \\4\17\17\29\29\29\29\29\5\29\29\29\29\6\5\5\6\6\5\5\29\7\7\0\1\0\1\0\1\1\1\0\1\0\1\0\1\0\1\1\1\1\1\0\29\0\0\0\0\29\ + \\20\20\20\0\0\0\0\0\29\0\29\0\0\0\0\29\0\0\0\0\29\29\0\0\0\0\0\0\0\29\0\0\0\0\0\0\29\29\29\29\29\29\8\8\17\17\17\17\4\4\ + \\5\6\5\4\6\6\6\6\6\5\4\6\5\5\17\29\29\29\29\4\4\4\29\29\29\29\5\5\5\5\5\3\3\5\5\5\5\3\3\21\17\10\10\10\10\10\10\10\10\4\ + \\4\5\5\5\6\29\29\5\6\4\5\5\5\5\17\17\17\3\4\4\4\4\4\4\4\3\5\5\5\5\5\5\5\6\5\5\5\4\4\4\4\5\4\4\6\6\29\29\5\5\ + \\6\5\4\5\5\5\4\4\5\5\4\29\29\29\29\29\3\3\3\0\1\4\4\5\5\6\17\17\29\18\17\17\19\17\17\21\21\17\17\17\13\14\13\14\18\18\18\18\18\18\ + \\18\18\13\14\18\18\18\18\21\21\21\21\21\6\6\5\5\5\5\29\29\6\12\13\14\13\14\13\14\17\29\29\29\29\29\29\29\3\1\1\1\17\0\23\24\26\26\26\26\26\ + \\22\17\19\19\19\19\21\17\17\29\29\29\29\29\29\29\5\5\6\6\6\6\29\5\5\6\29\4\4\4\29\4\4\4\4\17\4\5\5\5\29\29\17\29\0\1\0\1\3\20\ + \\0\1\0\1\3\3\5\5\21\21\21\21\21\21\5\21\21\17\9\9\9\9\9\29\29\4\4\4\4\3\17\17\17\19\29\29\29\29\29\29\29\21\21\21\21\21\21\21\18\18\ + \\18\18\18\0\1\1\21\18\21\21\1\21\13\14\21\21\21\21\21\18\18\18\18\21\21\29\0\0\0\0\0\29\1\1\1\1\1\1\3\3\3\3\3\3\3\3\20\20\20\20\ + \\20\20\20\20\3\20\3\20\20\0\1\0\1\4\4\5\5\29\29\29\29\0\1\0\1\0\1\4\5\4\29\29\29\29\29\29\5\5\5\5\5\5\5\12\5\5\5\5\5\4\ + \\29\29\6\17\17\17\17\17\17\17\17\29\26\5\6\6\6\29\29\29\29\4\5\5\5\5\5\5\5\3\5\5\5\5\5\29\29\5\5\5\29\29\4\4\4\4\4\4\29\17\ + \\17\17\19\17\17\17\19\4\5\29\29\29\29\29\29\5\29\5\5\29\5\5\20\20\3\3\4\4\4\4\4\4\21\5\5\5\6\6\5\6\5\5\5\5\5\29\5\6\6\29\ + \\4\4\4\5\6\6\5\5\6\4\4\4\4\4\6\6\6\6\6\6\6\6\29\6\6\5\5\29\29\29\29\5\4\29\4\4\4\4\29\4\4\29\4\4\4\4\4\4\4\4\ + \\29\4\4\4\4\29\29\29\29\4\4\29\4\29\4\4\29\4\4\29\4\29\29\4\4\6\29\29\29\29\20\4\4\4\4\4\4\29\29\29\29\29\29\29\29\6\6\29\29\6\ + \\6\5\4\29\5\5\29\29\29\29\1\1\29\1\29\1\1\1\17\3\1\1\1\20\3\3\3\3\1\1\1\1\1\1\1\0\1\18\0\0\0\0\0\21\21\0\21\21\21\21\ + \\0\4\4\4\4\4\29\29\26\26\26\26\26\26\18\18\18\18\18\21\21\18\21\21\18\21\18\21\21\21\21\21\21\21\18\21\21\21\5\5\5\5\5\26\21\5\5\6\6\29\ + \\29\29\29\15\16\13\15\15\16\13\15\16\13\14\13\14\13\14\13\14\13\14\10\10\18\18\18\13\14\29\8\8\29\29\29\29\29\19\21\29\29\29\29\29\29\3\17\17\17\17\ + \\17\17\21\21\21\21\21\21\21\21\29\29\29\29\29\29\29\17\17\17\17\17\17\17\3\29\29\5\19\19\18\20\21\19\19\29\1\18\1\1\1\1\1\1\0\0\0\0\0\0\ + \\0\1\1\1\1\1\1\29\1\1\1\1\1\0\0\29\0\29\0\29\0\29\0\4\4\4\29\29\29\4\4\5\5\17\17\8\8\4\4\4\4\4\29\4\4\29\29\5\4\5\ + \\5\5\5\4\4\4\4\4\4\5\6\5\5\5\5\5\5\5\5\21\21\21\21\0\21\0\21\0\0\0\0\21\1\3\20\20\29\29\29\29\4\4\4\4\5\6\29\29\4\29\ + \\4\29\4\29\4\4\4\4\29\4\29\4\29\29\29\29\20\20\0\17\12\3\3\3\3\3\21\21\18\10\10\20\1\17\17\18\12\18\18\18\29\29\29\29\29\29\21\21\10\10\ + \\10\10\21\21\10\10\21\21\21\29\5\5\5\5\5\5\5\29\8\8\29\10\10\10\10\10\10\8\8\29\29\29\4\4\4\29\29\29\4\29\29\4\4\4\4\4\29\29\4\29\ + \\29\29\29\29\29\6\0\1\29\1\29\1\0\1\29\29\29\29\29\29\29\4\4\29\29\29\29\6\6\17\29\29\29\12\4\4\4\4\4\4\4\21\17\4\4\4\4\4\4\14\ + \\13\22\4\4\4\4\4\4\4\21\17\4\4\9\29\29\29\29\29\22\17\17\17\21\3\4\9\4\4\4\4\4\4\4\6\6\6\5\5\5\5\6\5\6\6\6\6\5\5\5\ + \\5\5\6\6\6\6\5\6\6\6\6\6\29\5\6\6\29\29\29\6\6\6\6\5\5\29\29\22\22\22\22\22\22\22\22\26\26\26\26\26\26\26\26\29\26\26\26\21\21\29\ + \\29\29\17\17\8\8\17\17\29\29\29\29\18\18\18\18\18\18\13\14\13\14\13\14\12\29\29\0\0\0\0\0\20\20\20\0\1\0\1\0\1\0\0\1\22\17\17\17\19\17\ + \\17\17\4\17\4\4\5\4\4\4\5\4\4\4\4\4\4\4\5\5\5\5\5\5\5\17\3\4\4\29\29\5\4\6\6\6\26\26\26\26\26\29\29\29\29\29\29\1\1\1\ + \\1\1\1\1\29\29\29\29\29\5\5\29\6\6\5\6\5\5\4\4\17\4\5\5\5\29\5\5\29\4\18\4\4\4\4\4\4\29\4\29\29\29\4\4\3\17\17\17\17\17\ + \\17\17\13\4\4\4\4\4\29\29\10\21\4\4\4\4\4\4\4\10\10\10\10\29\29\29\17\17\17\17\29\29\29\8\8\10\10\17\17\17\21\4\4\4\4\4\4\4\5\5\ + \\29\29\8\8\6\6\6\5\21\21\5\5\5\17\26\17\17\17\5\29\29\29\29\29\26\29\29\5\5\5\5\5\5\4\5\4\4\5\5\5\5\5\5\6\4\4\4\4\17\17\ + \\17\17\17\29\29\29\29\29\0\29\29\0\0\29\4\4\29\5\5\12\29\29\6\5\5\5\5\5\5\6\6\4\4\4\4\19\21\21\21\21\21\21\21\19\19\19\19\19\19\19\ + \\19\10\10\10\10\29\29\29\4\4\29\29\5\4\6\5\5\5\5\6\6\6\5\4\4\4\29\29\5\5\5\21\21\5\5\5\5\21\21\21\6\6\6\6\6\6\4\4\4\4\ + \\4\4\9\9\9\9\9\9\9\29\4\5\5\5\5\5\5\29\21\21\1\0\0\0\1\1\4\0\1\1\1\0\0\1\0\0\1\0\0\0\0\2\20\20\29\8\8\10\10\10\ + \\10\10\10\21\5\21\5\5\5\5\4\4\4\5\17\29\8\8\4\4\4\4\4\4\3\4\4\4\4\4\5\5\4\6\6\6\4\4\6\6\6\6\6\29\29\6\6\5\29\29\ + \\12\12\12\12\12\12\17\17\18\17\11\17\17\17\18\13\14\17\18\17\12\17\17\17\29\17\17\17\17\4\6\6\4\6\5\17\17\17\29\8\8\10\29\29\29\21\21\10\10\10\ + \\10\10\10\21\21\21\21\21\21\21\29\21\21\21\21\21\17\17\29\13\14\21\21\13\14\13\14\12\13\14\14\17\17\17\17\11\11\11\5\10\10\10\10\10\10\10\29\29\29\29\ + \\29\29\29\10\10\4\4\29\29\5\29\6\6\6\6\5\5\6\5\5\5\5\29\6\6\4\4\4\17\17\17\9\9\5\5\5\5\6\6\6\6\29\29\6\6\6\29\29\29\29\ + \\29\29\1\29\29\5\5\4\6\4\4\4\4\6\6\5\5\5\29\5\29\0\0\0\0\0\0\0\0\13\17\14\20\11\1\1\1\1\1\1\1\1\13\18\14\18\25\25\25\25\ + \\25\25\25\25\8\8\29\29\4\4\4\4\0\2\1\0\2\1\0\1\0\0\0\1\21\0\21\21\4\5\6\6\29\4\4\4\4\4\29\29\4\4\4\4\4\10\10\17\6\29\ + \\6\6\6\5\4\21\21\21\17\17\17\17\21\17\21\21\21\21\29\29\21\21\22\4\4\4\4\4\4\4\13\14\29\29\29\4\5\6\6\17\4\4\4\5\6\5\6\6\5\5\ + \\5\5\5\6\6\6\5\6\5\5\6\5\5\29\5\5\29\5\5\5\5\29\29\29\29\19\12\17\13\17\17\17\17\17\18\17\11\17\17\17\17\17\17\17\22\5\5\5\5\5\ + \\5\7\5\7\7\7\5\5\5\5\5\7\7\7\17\5\5\5\5\17\6\5\5\5\29\29\29\29\29\8\8\29\29\29\29\4\21\9\9\9\9\9\9\9\9\0\1\9\9\9\ + \\3\4\17\21\21\0\1\0\1\1\21\21\21\0\1\0\1\5\10\10\10\10\17\17\17\0\1\21\5\5\5\5\5\5\17\17\17\17\17\17\17\12\17\15\16\17\17\17\17\11\ + \\5\5\5\5\5\5\29\29\29\29\5\29\29\29\29\29\29\4\4\4\17\3\3\3\4\4\4\5\17\17\4\29\6\6\6\6\6\6\5\6\6\4\4\4\5\4\4\4\4\6\ + \\6\5\5\6\6\5\5\4\4\4\4\5\5\6\5\17\17\17\17\17\17\29\29\29\29\10\6\29\6\6\6\5\29\29\4\29\29\29\29\4\4\4\6\6\5\6\6\17\6\5\ + \\29\29\29\29\29\29\29\4\4\20\20\20\20\20\20\29\29\29\29\29\4\5\4\17\4\6\29\29\29\9\9\9\9\9\10\10\10\10\29\29\29\21\3\29\3\3\3\3\3\3\ + \\29\29\29\29\29\4\4\4\4\4\29\3\29\5\5\4\6\4\4\4\4\5\5\6\6\17\26\26\26\5\5\5\5\5\21\21\5\5\5\21\29\29\8\8\17\17\17\17\17\17\ + \\17\5\5\5\26\5\5\5\5\5\21\21\21\21\21\5\21\21\1\1\1\1\5\5\5\5\3\29\29\29\29\1\17\12\29\29\21\21\19\21\29\29\29\29\29\21\21\21\21\20\ + \\20\20\20\20\8\8\8\8\8\8\8\8\17\17\18\18\18\17\3\3\20\20\20\20\3\3\20\20\20\20\20\20\4\4\19\19\10\10\10\10\21\19\4\17\5\29\21\4\10\10\ + \\10\10\10\10\21\5\21\5\13\14\13\14\6\6\3\3\1\4\4\4\4\4\6\5\6\6\5\29\29\17\17\17\17\10\17\17\17\17\17\17\5\4\4\29\29\21\5\5\17\17\ + \\17\4\29\29\29\8\8\4\4\4\21\21\4\6\5\6\4\4\4\4\4\6\5\6\5\6\6\5\5\5\6\5\4\4\4\4\4\4\5\29\0\0\0\0\2\20\20\20\1\1\ + \\1\29\1\1\10\3\29\29\10\10\10\10\18\18\18\13\14\3\18\18\18\18\18\21\21\21\18\18\21\21\21\21\21\21\5\29\29\29\8\8\29\29\29\29\17\17\15\16\17\15\ + \\16\17\17\15\16\15\16\17\17\8\8\29\29\17\17\17\17\15\16\17\15\16\17\17\17\17\17\17\17\12\12\17\17\17\17\17\17\29\3\8\8\4\17\4\17\17\17\12\12\11\ + \\11\13\14\13\14\13\14\17\17\13\14\17\13\14\17\17\4\4\4\4\4\4\3\3\3\3\17\21\29\29\5\6\29\6\6\5\29\29\5\5\5\5\5\17\5\5\5\5\6\6\ + \\5\5\17\17\26\17\17\5\29\29\29\29\29\10\10\29\4\4\4\4\4\6\5\5\6\6\5\5\6\6\29\4\4\4\29\5\5\4\6\6\8\8\17\17\29\17\5\4\4\4\ + \\4\4\5\5\5\5\17\17\17\4\17\17\17\29\29\29\29\29\4\4\4\4\6\6\5\5\5\29\29\29\6\6\5\5\5\3\3\3\3\3\17\3\5\29\29\29\1\18\1\1\ + \\1\1\1\1\0\1\29\29\8\8\4\4\29\29\29\29\29\17\8\8\29\29\29\29\29\29\21\21\21\20\20\20\20\20\8\8\17\17\18\18\18\17\0\0\0\0\0\0\0\29\ + \\0\0\29\1\17\5\5\17\5\5\17\5\5\5\5\5\5\12\5\5\5\5\5\17\29\29\9\9\9\0\1\9\9\9\10\21\21\29\29\29\29\13\14\13\14\21\21\21\21\0\ + \\1\0\1\5\5\0\1\29\29\29\29\5\5\6\6\29\4\4\4\17\29\29\29\29\29\29\2\2\2\2\2\2\2\2\27\27\27\27\27\27\27\27\28\28\28\28\28\28\28\28"# + +{-# NOINLINE generalCategoryPlanes0To3Offsets1BitMap #-} +generalCategoryPlanes0To3Offsets1BitMap :: Ptr Word16 +generalCategoryPlanes0To3Offsets1BitMap = Ptr + "\237\5\126\4\74\3\74\3\74\3\74\3\235\5\101\1\240\9\119\3\150\6\127\1\74\3\74\3\74\3\74\3\74\3\236\5\120\1\138\11\164\6\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\118\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\54\0\44\0\58\9\74\3\74\3\74\3\74\3\74\3\73\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\75\3\222\4\28\4\74\3\74\3\74\3\74\3\28\4\28\4\28\4\28\4\32\4\119\3\74\3\74\3\77\7\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\30\4\119\3\119\3\119\3\28\4\32\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\119\3\28\4\34\4\28\4\28\4\28\4\28\4\28\4\119\3\28\4\28\4\28\4\30\4\34\4\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\81\3\75\3\81\3\ + \\74\3\74\3\74\3\74\3\74\3\81\3\74\3\74\3\74\3\74\3\81\3\75\3\81\3\74\3\75\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\117\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\115\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\214\9\223\1\ + \\74\3\78\3\74\3\74\3\75\3\74\3\74\3\67\3\74\3\113\3\74\3\113\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\116\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\115\3\36\4\117\0\20\1\117\0\20\1\230\11\74\0\81\4\74\0\81\4\135\0\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\113\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\117\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\113\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\117\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\75\3\119\5\201\2\124\5\222\8\168\5\44\10\74\3\74\3\74\3\113\3\114\3\119\3\74\3\74\3\74\3\74\3\74\3\115\3\74\3\74\3\74\3\117\3\44\10\147\7\28\4\28\4\28\4\28\4\28\4\28\4\188\1\188\1\196\3\208\10\28\4\28\4\28\4\28\4\116\8\ + \\28\4\28\4\28\4\162\7\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\209\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\209\3\28\4\207\3\28\4\28\4\28\4\28\4\28\4\28\4\188\1\ + \\191\2\251\1\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\200\0\119\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\155\5\155\5\128\4\137\4\46\9\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\200\0\119\3\74\3\74\3\74\3\74\3\116\3\119\3\ + \\16\5\119\3\119\3\119\3\13\5\119\3\197\9\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\115\3\119\3\74\3\74\3\75\3\198\9\74\3\74\3\74\3\74\3\74\3\ + \\115\3\74\3\74\3\74\3\74\3\74\3\114\3\210\2\190\9\44\10\231\8\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\172\10\119\3\119\3\74\3\74\3\74\3\74\3\74\3\234\5\44\10\6\4\74\3\74\3\77\7\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\114\3\28\4\28\4\28\4\28\4\28\4\28\4\29\4\119\3\74\3\74\3\74\3\74\3\74\3\59\0\239\8\239\8\239\8\239\8\239\8\239\8\ + \\239\8\239\8\239\8\239\8\239\8\239\8\239\8\10\7\162\6\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\117\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\114\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\118\3\119\3\196\7\85\1\85\1\200\7\117\0\117\0\117\0\117\0\75\4\74\0\74\0\74\0\8\10\13\10\44\10\228\10\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\142\0\85\1\85\1\85\1\85\1\85\1\ + \\85\1\146\0\214\6\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\97\5\207\1\219\7\29\9\191\2\191\2\108\6\119\3\119\3\119\3\119\3\142\0\85\1\85\1\85\1\85\1\144\0\85\1\198\7\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\142\0\85\1\85\1\85\1\85\1\85\1\85\1\146\0\214\6\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\74\3\74\3\74\3\116\1\44\10\202\11\53\5\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\56\5\74\3\74\3\71\5\74\3\74\3\129\8\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\233\7\96\5\118\3\28\4\28\4\28\4\29\4\85\1\159\7\28\4\28\4\28\4\85\1\150\0\85\1\28\4\28\4\28\4\28\4\85\1\159\7\28\4\28\4\28\4\28\4\150\0\85\1\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\209\3\28\4\28\4\28\4\ + \\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\246\3\248\3\85\1\85\1\85\1\157\7\28\4\28\4\28\4\28\4\28\4\191\1\188\1\188\1\188\1\190\1\246\3\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\ + \\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\185\5\245\3\245\3\187\1\188\1\188\1\188\1\188\1\188\1\188\1\188\1\184\1\188\1\188\1\188\1\192\1\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\246\3\248\3\85\1\85\1\85\1\157\7\28\4\28\4\28\4\28\4\28\4\191\1\188\1\188\1\188\1\190\1\246\3\188\1\188\1\85\4\11\1\18\1\114\2\74\0\74\0\74\0\7\1\253\0\14\1\118\2\74\0\74\0\66\4\117\0\117\0\71\4\74\0\74\0\ + \\74\0\117\0\117\0\117\0\75\4\74\0\74\0\66\4\117\0\117\0\71\4\74\0\74\0\74\0\117\0\117\0\117\0\75\4\74\0\74\0\126\0\117\0\117\0\117\0\124\0\74\0\74\0\79\0\68\4\117\0\117\0\122\0\74\3\74\3\74\3\74\3\234\5\119\3\44\10\202\11\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\85\1\85\1\85\1\197\7\74\3\74\3\74\3\74\3\74\3\178\6\117\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\169\2\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\117\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\118\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\117\0\117\0\117\0\27\1\119\3\74\0\ + \\74\0\74\0\74\0\74\0\74\0\15\6\141\0\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\239\8\10\7\162\6\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\115\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\75\3\66\3\74\3\75\3\7\5\66\3\74\3\74\3\74\3\48\3\139\1\139\7\119\3\44\10\202\11\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\228\2\74\3\74\3\74\3\74\3\103\5\2\2\167\9\ + \\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\238\5\24\4\56\11\119\3\44\10\244\4\97\11\74\3\74\3\58\9\74\3\74\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\117\0\74\0\74\0\74\0\74\0\85\1\85\1\151\0\164\6\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\113\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\117\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\113\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\ + \\117\0\117\0\117\0\74\0\74\0\74\0\74\0\74\0\74\0\185\0\185\0\185\0\185\0\21\9\221\0\185\0\185\0\185\0\185\0\185\0\185\0\184\0\232\0\185\0\185\0\185\0\185\0\185\0\185\0\15\1\117\0\117\0\117\0\16\1\20\4\74\0\74\0\74\0\74\0\74\0\21\10\173\2\137\4\137\4\137\4\137\4\175\2\238\11\119\3\74\3\ + \\74\3\74\3\84\3\198\0\119\3\11\6\119\3\8\6\161\9\74\3\43\6\75\3\46\6\68\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\153\9\134\2\158\9\119\3\198\9\74\3\74\3\74\3\74\3\74\3\74\3\74\3\63\5\28\4\28\4\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\228\2\74\3\74\3\74\3\74\3\74\3\74\3\72\2\119\3\119\3\119\3\119\3\74\3\195\6\28\4\19\12\28\4\28\4\216\10\99\2\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\212\3\28\4\28\4\28\4\83\2\188\1\188\1\198\1\28\4\28\4\28\4\28\4\82\2\216\10\28\4\28\4\28\4\28\4\29\4\119\3\119\3\ + \\119\3\28\4\33\4\119\3\119\3\85\1\85\1\85\1\85\1\85\1\85\1\85\1\157\7\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\153\7\85\1\85\1\74\3\74\3\77\6\83\6\74\3\74\3\74\3\194\11\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\207\7\85\1\ + \\85\1\141\0\85\1\85\1\85\1\85\1\85\1\156\7\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\30\4\119\3\119\3\119\3\119\3\119\3\119\3\216\4\28\4\28\4\28\4\28\4\28\4\32\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\28\4\32\4\119\3\28\4\29\4\78\2\28\4\78\2\28\4\78\2\28\4\28\4\28\4\30\4\119\3\53\5\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\81\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\237\6\191\2\84\1\85\1\199\7\74\3\74\3\28\4\34\4\117\0\117\0\117\0\117\0\117\0\117\0\117\0\117\0\117\0\117\0\24\1\126\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\233\0\161\3\185\0\ + \\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\186\0\186\0\229\0\185\0\185\0\185\0\185\0\185\0\9\0\0\0\21\0\39\7\35\7\187\0\16\0\182\0\31\7\60\8\65\8\186\0\11\0\185\0\185\0\66\8\185\0\185\0\185\0\185\0\185\0\185\0\235\0\37\7\190\0\185\0\74\0\74\0\74\0\74\0\74\0\ + \\74\0\74\0\74\0\83\0\74\0\74\0\74\0\126\2\126\2\58\10\126\2\132\2\134\2\129\2\138\2\134\2\134\2\135\2\126\2\203\5\185\0\229\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\159\3\206\5\185\0\144\2\225\0\185\0\185\0\4\0\6\0\185\0\189\0\31\5\26\5\32\5\119\3\119\3\158\1\104\10\74\3\74\3\74\3\ + \\78\6\86\1\119\3\74\3\74\3\232\5\137\4\13\9\251\1\119\3\119\3\74\3\74\3\134\11\251\1\119\3\119\3\119\3\119\3\74\3\74\3\78\6\200\7\119\3\119\3\74\3\74\3\75\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\85\1\85\1\85\1\197\7\74\3\74\3\74\3\74\3\74\3\178\6\ + \\117\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\169\2\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\63\1\45\3\46\3\46\3\46\3\46\3\46\3\46\3\253\1\166\11\126\2\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\172\11\119\3\252\7\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\ + \\117\0\117\0\117\0\74\0\74\0\74\0\74\0\85\1\85\1\151\0\164\6\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\48\8\48\8\48\8\48\8\214\5\123\7\44\10\50\10\116\0\117\0\117\0\28\8\73\0\74\0\74\0\41\8\48\8\48\8\48\8\48\8\244\1\102\0\203\4\109\0\117\0\117\0\118\0\ + \\70\4\74\0\74\0\75\0\74\0\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\32\2\229\1\188\4\255\0\69\4\117\0\21\1\73\4\74\0\74\0\74\0\160\3\25\0\185\0\185\0\185\0\163\3\178\0\190\3\173\1\137\4\124\6\74\3\74\3\74\3\74\3\111\1\235\5\137\4\137\4\44\10\ + \\36\1\230\5\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\19\2\220\3\70\1\62\7\44\10\145\10\191\2\193\2\229\5\74\3\74\3\74\3\137\4\137\4\137\4\225\2\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\232\5\137\4\166\2\119\3\44\10\74\7\74\3\74\3\74\3\235\5\77\1\ + \\48\4\74\3\74\3\232\5\215\2\213\2\217\2\191\2\192\2\74\3\74\3\74\3\24\2\74\3\116\3\74\3\74\3\74\3\112\3\3\6\137\4\74\3\74\3\74\3\74\3\74\3\118\1\137\4\137\4\248\9\137\4\137\4\137\4\154\6\74\3\74\3\74\3\74\3\74\3\74\3\42\1\136\4\121\5\237\5\74\3\105\4\44\10\110\1\74\3\80\8\ + \\11\5\8\5\74\3\74\3\72\3\50\6\247\5\208\1\128\3\120\3\87\3\110\6\44\10\72\10\78\10\10\2\84\3\8\5\74\3\74\3\72\3\94\3\213\7\56\3\222\2\55\9\179\4\30\1\44\10\66\7\119\3\10\2\76\3\71\3\74\3\74\3\72\3\69\3\247\5\21\3\64\11\118\3\119\3\110\6\44\10\70\2\208\2\27\3\11\5\8\5\ + \\74\3\74\3\72\3\69\3\222\6\208\1\100\7\255\1\87\3\110\6\44\10\86\10\119\3\61\3\99\4\81\3\90\3\38\5\99\4\74\3\41\5\133\5\122\9\18\5\119\3\30\1\44\10\158\7\27\10\232\6\77\3\72\3\74\3\74\3\72\3\74\3\119\4\5\2\167\8\18\6\13\5\110\6\44\10\36\4\143\0\137\8\77\3\72\3\74\3\74\3\ + \\72\3\78\3\222\6\127\5\53\3\122\3\36\5\110\6\44\10\104\3\119\3\191\6\77\3\72\3\74\3\74\3\74\3\74\3\85\7\225\7\100\8\131\9\86\1\110\6\44\10\85\1\74\6\27\3\74\3\75\3\228\2\74\3\74\3\71\3\47\6\75\3\206\0\15\8\46\3\30\1\44\10\45\5\119\3\73\3\74\3\74\3\74\3\74\3\74\3\147\6\ + \\170\8\113\1\238\5\44\10\174\5\119\3\119\3\119\3\119\3\90\3\79\3\74\3\74\3\180\4\74\3\147\6\182\2\201\9\236\4\44\10\56\8\119\3\119\3\119\3\119\3\106\8\191\2\111\8\44\2\44\10\53\7\57\7\96\10\74\3\73\3\74\3\74\3\74\3\114\3\173\2\120\1\72\11\233\5\137\4\173\2\137\4\137\4\137\4\20\7\46\2\ + \\163\7\23\4\250\1\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\12\8\135\4\96\9\44\10\238\9\98\5\101\9\89\7\254\6\124\4\74\3\33\3\48\1\44\10\116\6\117\0\117\0\117\0\117\0\17\1\167\6\74\0\74\0\74\0\74\0\74\0\147\3\74\3\74\3\93\1\34\5\74\3\74\3\165\1\119\3\74\3\74\3\151\2\ + \\119\3\74\3\77\3\134\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\103\9\187\6\78\9\136\4\104\1\241\2\44\10\202\11\85\1\202\7\31\9\244\9\44\10\202\11\74\3\74\3\74\3\74\3\79\7\74\3\74\3\74\3\74\3\74\3\74\3\118\3\83\7\74\3\74\3\74\3\74\3\165\2\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\113\3\119\3\74\3\74\3\231\5\113\10\74\3\74\3\74\3\74\3\74\3\74\3\107\10\236\4\145\8\117\5\114\5\218\2\44\10\202\11\44\10\202\11\43\4\111\9\137\4\197\8\137\4\236\4\119\3\119\3\119\3\119\3\119\3\119\3\153\6\74\3\74\3\74\3\74\3\74\3\131\4\108\5\82\9\114\3\44\10\238\9\27\4\217\3\141\4\ + \\169\7\38\3\74\3\74\3\74\3\227\6\125\1\44\10\74\7\74\3\74\3\74\3\74\3\129\4\153\8\227\3\39\4\74\3\74\3\74\3\74\3\42\3\113\5\78\11\40\4\44\10\253\4\44\10\74\7\74\3\74\3\74\3\59\0\74\0\33\5\117\0\117\0\117\0\117\0\117\0\11\1\191\2\119\3\74\11\137\4\135\4\130\1\131\1\152\1\74\0\ + \\74\0\74\0\74\0\74\0\122\2\126\2\126\2\126\2\126\2\126\2\126\2\126\2\157\3\74\0\159\3\74\0\74\0\74\0\123\2\126\2\126\2\126\2\126\2\137\4\137\4\137\4\137\4\137\4\137\4\137\4\137\4\74\0\117\0\126\0\24\1\74\0\117\0\74\0\117\0\126\0\24\1\74\0\91\4\74\0\117\0\74\0\126\0\74\0\54\12\74\0\ + \\54\12\74\0\54\12\78\4\95\0\186\10\180\10\128\0\245\0\74\0\197\5\132\0\45\7\147\5\152\5\108\7\235\3\191\2\237\1\191\2\38\9\118\7\191\2\114\7\189\8\158\5\155\5\194\10\200\10\85\1\254\3\126\2\191\9\207\6\207\6\207\6\207\6\71\2\119\3\137\4\208\8\203\8\137\4\145\9\119\3\175\3\26\7\72\8\169\3\145\4\ + \\151\4\193\0\173\0\86\2\92\2\85\1\85\1\239\8\239\8\239\8\239\8\244\8\11\12\208\10\214\10\200\3\210\3\28\4\28\4\28\4\80\2\204\3\28\4\28\4\28\4\82\2\188\1\117\0\117\0\117\0\117\0\117\0\117\0\74\0\74\0\74\0\74\0\74\0\74\0\20\0\188\0\12\0\89\0\185\0\185\0\185\0\185\0\185\0\185\0\185\0\ + \\185\0\185\0\185\0\185\0\185\0\1\9\6\9\31\12\118\10\74\0\74\0\74\0\74\0\77\4\255\7\74\3\74\3\74\3\74\3\74\3\74\3\74\3\224\1\223\1\253\1\74\3\74\3\75\3\119\3\75\3\75\3\75\3\75\3\75\3\75\3\75\3\75\3\137\4\137\4\137\4\137\4\241\10\235\10\30\9\35\9\242\3\37\0\191\2\11\11\178\8\ + \\191\2\179\1\189\5\119\3\119\3\119\3\119\3\28\4\28\4\28\4\166\7\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\32\4\119\3\89\5\246\3\177\7\181\7\238\8\239\7\196\4\249\8\73\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\75\3\1\3\53\5\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\63\9\74\3\63\2\74\3\74\3\44\10\192\11\119\3\119\3\185\0\185\0\185\0\185\0\185\0\159\2\213\8\239\5\185\0\185\0\185\0\38\2\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\4\7\239\8\28\9\119\3\224\5\227\5\74\3\74\3\92\9\220\10\155\7\13\4\74\3\74\3\74\3\74\3\74\3\ + \\74\3\158\6\119\3\2\7\74\3\74\3\74\3\74\3\74\3\42\3\46\3\139\5\37\4\44\10\202\11\137\4\137\4\127\4\219\5\44\10\74\7\74\3\74\3\232\5\24\9\74\3\74\3\231\5\137\4\227\3\36\4\74\3\74\3\74\3\114\3\154\6\74\3\74\3\74\3\74\3\74\3\32\3\106\11\190\2\15\11\44\10\228\10\166\0\74\3\44\10\ + \\111\4\74\3\74\3\74\3\74\3\74\3\150\6\213\0\119\3\227\5\166\4\44\10\249\10\74\3\74\3\7\3\150\10\74\3\74\3\74\3\74\3\74\3\74\3\145\1\130\11\165\2\119\3\119\3\53\6\74\3\102\11\65\0\119\3\229\2\229\2\229\2\119\3\75\3\75\3\74\0\74\0\74\0\74\0\74\0\152\3\74\0\158\4\74\0\74\0\74\0\ + \\74\0\74\0\74\0\74\0\74\0\74\0\74\0\74\3\74\3\74\3\74\3\135\9\140\9\44\10\202\11\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\62\12\70\12\70\12\70\12\ + \\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\70\12\137\4\137\4\59\6\222\1\137\4\137\4\30\11\245\3\36\11\188\7\129\7\216\1\209\4\158\0\77\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\183\3\236\2\123\7\44\10\50\10\116\0\117\0\117\0\28\8\73\0\74\0\74\0\30\0\44\11\74\3\111\1\74\3\74\3\74\3\74\3\50\11\74\3\74\3\74\3\75\3\228\2\228\2\228\2\0\5\54\4\106\2\119\3\163\5\114\9\85\1\85\1\85\1\85\1\85\1\180\9\ + \\28\4\239\8\239\8\239\8\239\8\239\8\239\8\175\9\160\7\28\4\228\4\28\4\31\4\35\4\119\3\119\3\119\3\119\3\119\3\28\4\28\4\28\4\28\4\28\4\219\10\74\3\74\3\74\3\74\3\200\7\58\9\74\3\74\3\95\5\81\5\74\3\74\3\74\3\74\3\232\5\223\8\74\3\74\3\74\3\230\2\74\3\74\3\74\3\74\3\115\3\ + \\74\3\55\2\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\117\0\117\0\74\0\74\0\74\0\74\0\74\0\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\113\3\44\10\202\11\117\0\117\0\117\0\117\0\26\1\74\0\74\0\74\0\74\0\14\6\74\3\74\3\74\3\74\3\74\3\74\3\75\3\119\3\74\3\74\3\113\3\ + \\119\3\74\3\119\3\119\3\119\3\52\0\126\2\126\2\126\2\126\2\126\2\50\0\193\9\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\113\3\72\3\74\3\74\3\74\3\74\3\76\3\4\5\74\3\74\3\230\2\85\1\74\3\74\3\54\5\150\0\74\3\74\3\74\3\75\3\204\7\85\1\119\3\119\3\119\3\119\3\119\3\119\3\74\3\ + \\74\3\115\4\140\0\35\6\170\2\78\3\73\3\74\3\74\3\113\3\49\9\85\1\203\7\191\2\223\1\74\3\74\3\74\3\92\8\74\3\74\3\74\3\78\6\119\3\119\3\119\3\119\3\74\3\75\6\74\3\74\3\107\6\140\0\192\2\119\3\74\3\74\3\74\3\74\3\74\3\74\3\113\3\42\4\74\3\74\3\113\3\85\1\74\3\74\3\116\3\ + \\85\1\74\3\74\3\117\3\89\6\119\3\142\0\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\153\10\74\3\74\3\74\3\74\3\74\3\74\3\137\4\238\5\111\9\141\0\85\1\247\4\44\10\149\1\253\1\38\3\74\3\74\3\74\3\74\3\74\3\104\5\83\11\130\6\133\6\74\3\74\3\74\3\118\3\44\10\202\11\126\4\ + \\74\3\74\3\74\3\231\5\123\1\238\4\44\10\133\7\119\3\74\3\74\3\74\3\74\3\70\9\119\3\38\3\74\3\74\3\74\3\74\3\74\3\101\5\120\1\157\6\216\8\44\10\23\11\142\0\85\1\199\7\119\3\74\3\74\3\71\3\74\3\74\3\100\5\16\3\124\10\245\2\119\3\119\3\119\3\119\3\119\3\119\3\119\3\75\3\64\3\74\3\ + \\76\3\74\3\46\12\74\3\74\3\74\3\74\3\74\3\231\5\114\5\223\8\44\10\202\11\110\11\11\5\8\5\74\3\74\3\72\3\69\3\116\11\244\7\248\7\18\5\58\9\136\1\47\9\47\9\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\99\5\137\4\165\10\159\6\44\10\124\11\117\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\114\5\110\5\28\6\119\3\44\10\202\11\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\114\5\15\3\137\10\119\3\44\10\202\11\191\2\162\6\119\3\119\3\74\3\74\3\74\3\74\3\74\3\142\8\121\1\ + \\46\12\44\10\202\11\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\237\6\105\5\169\8\44\10\97\6\75\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\100\5\137\4\55\1\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\117\0\74\0\74\0\74\0\74\0\44\10\53\7\201\7\34\5\74\3\72\3\74\3\74\3\74\3\97\5\236\4\121\1\161\6\119\3\44\10\53\7\85\1\199\7\48\11\74\3\74\3\74\3\172\2\137\4\137\4\185\6\158\8\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\119\3\119\3\75\3\71\3\74\3\74\3\74\3\74\3\18\7\251\2\141\6\119\3\44\10\202\11\76\3\72\3\74\3\74\3\74\3\94\7\23\6\118\3\44\10\202\11\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\7\8\74\3\72\3\74\3\74\3\74\3\11\8\158\11\108\9\191\2\44\10\202\11\119\3\ + \\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\118\3\119\3\85\1\85\1\156\7\202\6\199\6\28\4\34\4\36\4\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\75\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\118\3\74\3\74\3\74\3\75\3\44\10\228\10\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\75\3\44\10\202\11\74\3\74\3\74\3\113\3\252\11\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\116\3\74\3\114\3\74\3\ + \\118\3\74\3\131\10\1\6\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\137\4\137\4\137\4\137\4\137\4\46\9\137\4\137\4\236\4\119\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\32\4\119\3\119\3\119\3\119\3\119\3\119\3\119\3\28\4\28\4\28\4\ + \\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\30\4\119\3\28\4\28\4\28\4\28\4\29\4\78\2\28\4\28\4\28\4\28\4\28\4\28\4\202\1\249\6\253\5\222\9\242\6\141\4\28\4\28\4\28\4\ + \\245\6\28\4\28\4\28\4\28\4\28\4\28\4\28\4\33\4\119\3\119\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\230\9\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\85\1\85\1\200\7\119\3\85\1\85\1\200\7\119\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\28\4\29\4\119\3\85\1\85\1\85\1\203\7\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\117\0\117\0\117\0\75\4\74\0\74\0\66\4\117\0\117\0\71\4\78\4\74\0\74\0\117\0\117\0\117\0\75\4\74\0\74\0\239\0\170\6\4\1\71\4\142\3\79\4\ + \\74\0\117\0\117\0\117\0\75\4\74\0\74\0\74\0\74\0\77\0\66\4\117\0\117\0\120\0\74\0\74\0\75\0\64\4\117\0\117\0\118\0\74\0\74\0\74\0\62\4\117\0\117\0\117\0\124\0\74\0\74\0\79\0\186\11\44\10\44\10\44\10\44\10\44\10\44\10\137\4\137\4\137\4\137\4\137\4\137\4\138\4\217\3\137\4\137\4\137\4\ + \\137\4\137\4\140\4\47\2\28\4\48\2\163\6\119\3\171\2\173\2\137\4\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\0\85\0\74\0\11\6\6\6\15\6\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\ + \\119\3\119\3\119\3\236\4\137\4\137\4\69\11\163\8\223\8\126\2\126\2\126\2\126\2\126\2\126\2\126\2\190\9\119\3\119\3\119\3\253\1\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\ + \\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\74\3\67\6\85\1\236\4\119\3\119\3\119\3\119\3\119\3\78\3\74\3\74\3\74\3\98\3\73\3\79\3\184\4\128\9\175\4\98\3\173\4\98\3\79\3\79\3\179\4\74\3\71\3\74\3\115\3\14\2\71\3\74\3\115\3\119\3\119\3\119\3\119\3\119\3\119\3\214\4\119\3\33\4\ + \\119\3\28\4\28\4\28\4\28\4\28\4\32\4\28\4\35\4\34\4\119\3\30\4\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\119\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\36\10\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\75\2\28\4\31\4\28\4\31\4\28\4\28\4\28\4\28\4\28\4\ + \\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\29\4\76\2\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\34\4\28\4\32\4\35\4\119\3\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\32\4\119\3\28\4\30\4\28\4\31\4\28\4\35\4\28\4\28\4\28\4\28\4\28\4\ + \\162\7\30\4\216\4\28\4\32\4\28\4\35\4\28\4\35\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\28\4\165\7\28\4\28\4\28\4\28\4\28\4\28\4\33\4\119\3\119\3\119\3\119\3\44\10\202\11"# + +{-# NOINLINE generalCategoryPlanes0To3Offsets2BitMap #-} +generalCategoryPlanes0To3Offsets2BitMap :: Ptr Word16 +generalCategoryPlanes0To3Offsets2BitMap = Ptr + "\175\8\212\7\243\7\207\8\111\6\137\6\239\8\15\9\47\9\79\9\111\9\143\9\175\9\207\9\239\9\15\10\47\10\76\1\188\0\155\7\240\3\76\1\3\4\79\10\111\10\201\1\143\10\175\10\207\10\239\10\187\7\15\11\47\11\79\11\108\4\228\6\1\7\6\2\248\1\78\4\156\4\124\4\108\4\229\1\111\11\143\11\175\11\126\0\207\11\64\0\ + \\35\4\156\4\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\102\0\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\94\0\76\1\76\1\76\1\250\2\76\1\239\11\17\8\15\12\47\12\79\12\111\12\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\157\2\143\12\143\12\143\12\143\12\143\12\143\12\143\12\143\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\175\12\76\1\ + \\169\1\169\6\76\1\196\6\207\12\239\12\44\1\15\13\62\3\47\13\79\13\103\1\76\1\111\13\143\13\33\7\175\13\207\13\95\5\2\5\22\5\49\8\239\13\15\14\47\14\79\14\111\14\135\3\143\14\175\14\207\14\191\5\0\0\38\2\239\14\15\15\12\1\47\15\76\1\76\1\76\1\42\3\26\3\255\0\8\1\8\1\8\1\8\1\8\1\8\1\ + \\8\1\8\1\8\1\54\2\76\1\76\1\76\1\76\1\86\2\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\76\1\76\1\79\15\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\ + \\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\76\1\76\1\111\15\223\5\8\1\8\1\247\5\112\8\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\77\1\76\1\76\1\76\1\76\1\56\6\30\0\8\1\8\1\ + \\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\32\0\76\1\132\2\146\2\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\143\15\8\1\8\1\8\1\8\1\8\1\ + \\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\175\15\207\15\239\15\15\16\47\16\79\16\207\4\226\4\111\16\156\4\156\4\143\16\8\1\8\1\8\1\8\1\175\16\207\16\189\2\203\2\8\1\208\3\8\1\8\1\160\5\239\16\94\3\8\1\8\1\112\3\167\3\15\17\8\1\93\7\64\7\47\17\79\17\ + \\156\4\156\4\111\17\143\17\156\0\156\4\175\17\207\17\8\1\8\1\8\1\8\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\223\0\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\215\0\135\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\147\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\5\8\1\8\1\ + \\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\8\1\76\1\76\1\79\6\8\1\8\1\8\1\8\1\8\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\66\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\76\1\ + \\76\1\76\1\76\1\76\1"# + +{-# INLINE lookupGeneralCategoryPlane14BitMap #-} +lookupGeneralCategoryPlane14BitMap :: Int -> Int +lookupGeneralCategoryPlane14BitMap n = + lookupWord8AsInt data# ( + lookupWord8AsInt offsets# ( + n `shiftR` 3 + ) + (n .&. mask) + ) + where + mask = (1 `shiftL` 3) - 1 + !(Ptr data#) = generalCategoryPlane14DataBitMap + !(Ptr offsets#) = generalCategoryPlane14OffsetsBitMap + +{-# NOINLINE generalCategoryPlane14DataBitMap #-} +generalCategoryPlane14DataBitMap :: Ptr Int8 +generalCategoryPlane14DataBitMap = Ptr + "\29\26\29\29\29\29\29\29\29\29\26\26\26\26\26\26\26\26\5\5\5\5\5\5\5\5"# + +{-# NOINLINE generalCategoryPlane14OffsetsBitMap #-} +generalCategoryPlane14OffsetsBitMap :: Ptr Word8 +generalCategoryPlane14OffsetsBitMap = Ptr + "\0\2\2\2\10\10\10\10\10\10\10\10\10\10\10\10\2\2\2\2\2\2\2\2\2\2\2\2\2\2\2\2\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\18\ + \\18\18\18\18\18\18\18\18\18\18\18\18"# + +