{-# LANGUAGE OverloadedLists #-}
{-# OPTIONS_HADDOCK hide #-}
module Unicode.Internal.Char.Security.IdentifierType
(IdentifierType(..), identifierTypes, decodeIdentifierTypes)
where
import Data.Bits (Bits(..))
import Data.Char (ord)
import Data.Int (Int8)
import Data.List.NonEmpty (NonEmpty)
import Data.Word (Word16)
import GHC.Exts (Ptr(..))
import Unicode.Internal.Bits (lookupWord16AsInt, lookupWord8AsInt)
data IdentifierType
= NotCharacter
| Deprecated
| DefaultIgnorable
| NotNFKC
| NotXID
| Exclusion
| Obsolete
| Technical
| UncommonUse
| LimitedUse
| Inclusion
| Recommended
deriving (IdentifierType -> IdentifierType -> Bool
(IdentifierType -> IdentifierType -> Bool)
-> (IdentifierType -> IdentifierType -> Bool) -> Eq IdentifierType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IdentifierType -> IdentifierType -> Bool
== :: IdentifierType -> IdentifierType -> Bool
$c/= :: IdentifierType -> IdentifierType -> Bool
/= :: IdentifierType -> IdentifierType -> Bool
Eq, Eq IdentifierType
Eq IdentifierType =>
(IdentifierType -> IdentifierType -> Ordering)
-> (IdentifierType -> IdentifierType -> Bool)
-> (IdentifierType -> IdentifierType -> Bool)
-> (IdentifierType -> IdentifierType -> Bool)
-> (IdentifierType -> IdentifierType -> Bool)
-> (IdentifierType -> IdentifierType -> IdentifierType)
-> (IdentifierType -> IdentifierType -> IdentifierType)
-> Ord IdentifierType
IdentifierType -> IdentifierType -> Bool
IdentifierType -> IdentifierType -> Ordering
IdentifierType -> IdentifierType -> IdentifierType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IdentifierType -> IdentifierType -> Ordering
compare :: IdentifierType -> IdentifierType -> Ordering
$c< :: IdentifierType -> IdentifierType -> Bool
< :: IdentifierType -> IdentifierType -> Bool
$c<= :: IdentifierType -> IdentifierType -> Bool
<= :: IdentifierType -> IdentifierType -> Bool
$c> :: IdentifierType -> IdentifierType -> Bool
> :: IdentifierType -> IdentifierType -> Bool
$c>= :: IdentifierType -> IdentifierType -> Bool
>= :: IdentifierType -> IdentifierType -> Bool
$cmax :: IdentifierType -> IdentifierType -> IdentifierType
max :: IdentifierType -> IdentifierType -> IdentifierType
$cmin :: IdentifierType -> IdentifierType -> IdentifierType
min :: IdentifierType -> IdentifierType -> IdentifierType
Ord, IdentifierType
IdentifierType -> IdentifierType -> Bounded IdentifierType
forall a. a -> a -> Bounded a
$cminBound :: IdentifierType
minBound :: IdentifierType
$cmaxBound :: IdentifierType
maxBound :: IdentifierType
Bounded, Int -> IdentifierType
IdentifierType -> Int
IdentifierType -> [IdentifierType]
IdentifierType -> IdentifierType
IdentifierType -> IdentifierType -> [IdentifierType]
IdentifierType
-> IdentifierType -> IdentifierType -> [IdentifierType]
(IdentifierType -> IdentifierType)
-> (IdentifierType -> IdentifierType)
-> (Int -> IdentifierType)
-> (IdentifierType -> Int)
-> (IdentifierType -> [IdentifierType])
-> (IdentifierType -> IdentifierType -> [IdentifierType])
-> (IdentifierType -> IdentifierType -> [IdentifierType])
-> (IdentifierType
-> IdentifierType -> IdentifierType -> [IdentifierType])
-> Enum IdentifierType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: IdentifierType -> IdentifierType
succ :: IdentifierType -> IdentifierType
$cpred :: IdentifierType -> IdentifierType
pred :: IdentifierType -> IdentifierType
$ctoEnum :: Int -> IdentifierType
toEnum :: Int -> IdentifierType
$cfromEnum :: IdentifierType -> Int
fromEnum :: IdentifierType -> Int
$cenumFrom :: IdentifierType -> [IdentifierType]
enumFrom :: IdentifierType -> [IdentifierType]
$cenumFromThen :: IdentifierType -> IdentifierType -> [IdentifierType]
enumFromThen :: IdentifierType -> IdentifierType -> [IdentifierType]
$cenumFromTo :: IdentifierType -> IdentifierType -> [IdentifierType]
enumFromTo :: IdentifierType -> IdentifierType -> [IdentifierType]
$cenumFromThenTo :: IdentifierType
-> IdentifierType -> IdentifierType -> [IdentifierType]
enumFromThenTo :: IdentifierType
-> IdentifierType -> IdentifierType -> [IdentifierType]
Enum, Int -> IdentifierType -> ShowS
[IdentifierType] -> ShowS
IdentifierType -> String
(Int -> IdentifierType -> ShowS)
-> (IdentifierType -> String)
-> ([IdentifierType] -> ShowS)
-> Show IdentifierType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IdentifierType -> ShowS
showsPrec :: Int -> IdentifierType -> ShowS
$cshow :: IdentifierType -> String
show :: IdentifierType -> String
$cshowList :: [IdentifierType] -> ShowS
showList :: [IdentifierType] -> ShowS
Show)
decodeIdentifierTypes :: Int -> NonEmpty IdentifierType
decodeIdentifierTypes :: Int -> NonEmpty IdentifierType
decodeIdentifierTypes = \case
Int
0 -> [Item (NonEmpty IdentifierType)
IdentifierType
NotCharacter]
Int
1 -> [Item (NonEmpty IdentifierType)
IdentifierType
Deprecated]
Int
2 -> [Item (NonEmpty IdentifierType)
IdentifierType
DefaultIgnorable]
Int
3 -> [Item (NonEmpty IdentifierType)
IdentifierType
NotNFKC]
Int
4 -> [Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
5 -> [Item (NonEmpty IdentifierType)
IdentifierType
Exclusion]
Int
6 -> [Item (NonEmpty IdentifierType)
IdentifierType
Exclusion,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
7 -> [Item (NonEmpty IdentifierType)
IdentifierType
Obsolete]
Int
8 -> [Item (NonEmpty IdentifierType)
IdentifierType
Obsolete,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
9 -> [Item (NonEmpty IdentifierType)
IdentifierType
Technical]
Int
10 -> [Item (NonEmpty IdentifierType)
IdentifierType
Technical,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
11 -> [Item (NonEmpty IdentifierType)
IdentifierType
Technical,Item (NonEmpty IdentifierType)
IdentifierType
Exclusion]
Int
12 -> [Item (NonEmpty IdentifierType)
IdentifierType
Technical,Item (NonEmpty IdentifierType)
IdentifierType
Obsolete]
Int
13 -> [Item (NonEmpty IdentifierType)
IdentifierType
Technical,Item (NonEmpty IdentifierType)
IdentifierType
Obsolete,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
14 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse]
Int
15 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
16 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
Exclusion]
Int
17 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
Obsolete]
Int
18 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
Obsolete,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
19 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
Technical]
Int
20 -> [Item (NonEmpty IdentifierType)
IdentifierType
UncommonUse,Item (NonEmpty IdentifierType)
IdentifierType
Technical,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
21 -> [Item (NonEmpty IdentifierType)
IdentifierType
LimitedUse]
Int
22 -> [Item (NonEmpty IdentifierType)
IdentifierType
LimitedUse,Item (NonEmpty IdentifierType)
IdentifierType
NotXID]
Int
23 -> [Item (NonEmpty IdentifierType)
IdentifierType
LimitedUse,Item (NonEmpty IdentifierType)
IdentifierType
Exclusion]
Int
24 -> [Item (NonEmpty IdentifierType)
IdentifierType
LimitedUse,Item (NonEmpty IdentifierType)
IdentifierType
Obsolete]
Int
25 -> [Item (NonEmpty IdentifierType)
IdentifierType
LimitedUse,Item (NonEmpty IdentifierType)
IdentifierType
Technical]
Int
26 -> [Item (NonEmpty IdentifierType)
IdentifierType
Inclusion]
Int
27 -> [Item (NonEmpty IdentifierType)
IdentifierType
Recommended]
Int
_ -> [Item (NonEmpty IdentifierType)
IdentifierType
NotCharacter]
{-# INLINE identifierTypes #-}
identifierTypes :: Char -> Int
identifierTypes :: Char -> Int
identifierTypes Char
c
| Int
cp Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0x323B0 = Int -> Int
lookupIdentifierTypesBitMap Int
cp
| Int
cp Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xE0000 = Int
0
| Int
cp Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0xE01F0 = Int -> Int
lookupIdentifierTypesBitMap (Int
cp Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xADC50)
| Bool
otherwise = Int
0
where
cp :: Int
cp = Char -> Int
ord Char
c
{-# INLINE lookupIdentifierTypesBitMap #-}
lookupIdentifierTypesBitMap :: Int -> Int
lookupIdentifierTypesBitMap :: Int -> Int
lookupIdentifierTypesBitMap Int
n =
Addr# -> Int -> Int
lookupWord8AsInt Addr#
data# (
Addr# -> Int -> Int
lookupWord16AsInt Addr#
offsets1# (
Addr# -> Int -> Int
lookupWord16AsInt Addr#
offsets2# (
Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
8
) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` Int
3) Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
maskOffsets)
) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
n Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
maskData)
)
where
maskData :: Int
maskData = (Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
maskOffsets :: Int
maskOffsets = (Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
5) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
!(Ptr Addr#
data#) = Ptr Int8
identifierTypesDataBitMap
!(Ptr Addr#
offsets1#) = Ptr Word16
identifierTypesOffsets1BitMap
!(Ptr Addr#
offsets2#) = Ptr Word16
identifierTypesOffsets2BitMap
identifierTypesDataBitMap :: Ptr Int8
identifierTypesDataBitMap :: Ptr Int8
identifierTypesDataBitMap = Addr# -> Ptr Int8
forall a. Addr# -> Ptr a
Ptr
Addr#
"\14\7\12\12\14\14\12\7\7\14\14\14\14\14\14\27\14\14\14\14\14\14\4\14\14\14\14\14\14\27\27\14\9\14\27\14\9\9\9\9\9\9\9\7\7\7\7\7\7\4\
\\9\9\9\9\9\3\4\4\0\0\0\0\1\0\0\0\0\0\0\27\0\0\27\27\27\27\27\27\19\27\27\27\27\27\27\0\27\27\0\27\27\27\0\0\27\0\27\27\0\27\
\\0\27\27\3\27\3\3\1\5\5\5\0\0\0\5\5\5\4\4\4\5\5\5\0\5\5\0\5\5\5\5\0\5\5\0\0\0\0\0\6\6\5\5\5\5\6\5\5\0\0\
\\0\5\0\0\5\5\5\5\5\0\0\5\5\5\0\0\0\0\5\5\5\5\6\6\5\0\5\5\0\27\27\5\5\5\5\5\5\6\5\6\6\6\2\2\2\2\2\9\9\9\
\\9\9\10\10\9\9\9\9\10\10\10\10\27\3\27\3\27\3\3\0\10\10\10\10\10\10\10\0\0\3\3\3\0\0\0\3\0\0\3\3\0\9\9\10\10\10\9\9\9\19\
\\9\9\9\9\12\12\12\12\12\12\12\12\9\9\9\9\3\3\3\9\3\0\3\3\0\3\0\0\3\27\27\27\3\7\3\3\3\3\3\10\10\3\3\3\3\4\3\3\4\3\
\\3\3\3\9\3\3\3\3\4\3\3\3\3\3\3\3\27\3\27\27\3\3\27\27\27\27\27\27\27\3\27\3\3\3\27\27\7\7\7\7\27\27\7\7\7\7\7\7\27\7\
\\7\7\9\9\9\9\3\3\7\7\4\4\4\4\4\4\14\4\8\3\4\3\4\4\2\4\3\3\3\12\3\3\4\7\9\9\9\9\9\9\19\19\9\9\9\9\9\9\19\9\
\\9\9\9\9\9\12\9\9\9\19\19\9\19\19\9\4\26\0\0\4\4\4\3\3\3\3\3\3\3\3\4\4\4\4\7\8\8\8\8\8\7\0\0\14\14\9\9\9\9\9\
\\9\9\2\2\2\2\2\0\2\2\1\1\1\1\1\1\27\1\27\27\27\27\27\27\7\7\27\27\27\0\27\27\27\27\27\27\27\0\27\27\27\27\0\0\0\0\27\27\0\0\
\\0\0\0\0\27\7\0\16\16\0\0\0\0\6\6\6\6\6\6\6\6\0\0\0\6\4\14\4\4\4\4\27\27\0\0\3\3\27\27\27\27\14\0\27\27\14\14\0\0\27\
\\27\27\27\27\14\27\27\26\4\4\4\4\4\26\3\4\4\4\4\27\27\27\27\27\27\0\0\27\27\27\27\0\27\0\0\0\27\27\27\0\27\27\27\4\4\4\4\27\3\3\
\\3\2\2\2\2\2\7\7\7\7\7\7\7\2\2\2\2\2\2\2\2\0\0\0\0\6\6\6\5\5\5\5\5\5\5\5\0\0\0\0\0\0\0\5\5\5\5\5\5\0\
\\6\14\14\14\14\14\7\7\7\14\0\0\27\0\0\27\27\27\0\0\0\0\0\0\22\22\22\22\22\22\22\21\0\0\0\0\3\3\0\3\3\3\3\3\0\0\2\21\21\21\
\\0\0\0\0\21\22\0\0\0\0\0\0\0\3\19\3\21\21\0\0\0\0\0\22\0\0\0\0\0\0\0\21\21\21\22\22\0\22\21\21\21\0\0\0\22\22\24\0\0\21\
\\22\22\3\3\9\7\7\7\7\7\5\5\5\5\5\5\0\5\5\5\5\5\5\5\6\6\0\0\0\0\0\0\0\10\5\5\5\5\6\6\6\0\5\5\5\5\5\6\6\6\
\\6\6\6\6\5\5\5\5\5\0\0\6\6\6\6\0\0\0\0\0\27\0\0\0\0\27\19\4\0\0\0\0\3\3\0\27\0\27\0\27\0\27\3\0\27\3\0\21\21\0\
\\21\21\21\21\21\21\21\21\22\22\21\21\21\21\21\0\0\21\16\16\16\16\16\16\16\16\0\3\3\7\3\3\3\3\3\2\3\3\3\3\3\3\3\9\9\9\9\9\9\9\
\\9\0\0\0\0\0\0\0\5\5\0\6\6\6\6\6\5\6\6\6\5\0\0\0\0\0\0\5\0\5\5\0\5\5\6\0\0\0\0\0\0\7\3\7\7\27\27\27\27\0\
\\0\0\0\4\4\4\4\4\0\0\4\4\3\3\3\3\4\26\4\4\4\4\4\4\3\0\0\0\0\26\3\4\4\4\4\4\3\4\4\4\4\3\3\3\4\4\4\4\4\4\
\\4\26\26\4\27\3\27\27\27\4\27\27\14\14\14\14\14\14\14\14\0\14\14\14\4\2\4\4\4\4\4\27\4\27\27\7\27\27\4\27\27\27\27\27\27\27\27\7\27\27\
\\27\27\27\27\27\14\14\27\27\27\27\27\14\9\27\24\24\24\21\21\21\21\21\22\22\22\22\22\22\22\22\0\22\11\11\5\5\0\0\0\0\9\27\27\0\27\27\27\27\3\
\\27\27\27\27\3\0\0\27\27\3\3\27\27\3\3\9\9\27\9\21\21\0\0\0\21\21\21\22\21\21\0\0\22\22\22\22\21\21\21\21\21\21\21\0\0\0\0\0\0\0\
\\0\27\27\27\27\27\27\0\27\0\27\27\27\27\27\4\27\14\14\14\14\7\7\27\27\27\27\27\14\4\0\27\3\27\3\27\3\27\3\0\0\8\8\8\7\18\17\7\7\5\
\\0\0\0\0\0\3\0\0\0\0\3\3\3\3\3\3\3\0\0\0\0\0\0\0\4\4\2\2\2\2\2\3\13\13\13\13\13\13\13\13\8\8\8\8\8\8\8\3\27\3\
\\27\27\27\0\4\4\8\8\8\8\8\8\8\4\27\12\27\7\4\4\4\27\4\4\4\4\4\4\8\4\4\4\4\4\4\0\0\0\0\0\0\0\6\0\0\9\9\4\4\4\
\\4\9\9\9\9\9\9\9\12\12\21\0\21\21\21\21\21\21\0\21\21\24\24\0\0\0\0\3\9\9\27\27\9\9\9\9\9\9\10\10\10\10\10\10\10\10\0\0\0\0\
\\0\4\0\0\5\5\5\5\5\6\0\0\0\0\10\10\10\10\10\10\10\3\3\3\3\3\27\27\27\0\27\27\27\27\27\27\27\19\10\9\10\10\10\9\9\9\9\10\10\10\
\\10\10\10\10\27\3\27\3\27\27\3\3\3\3\3\3\3\10\10\10\10\10\10\10\20\20\9\27\9\19\9\9\9\9\3\3\3\3\3\3\0\3\3\3\3\0\3\3\0\3\
\\3\3\4\3\3\3\4\3\4\3\8\8\12\12\12\8\0\0\14\3\3\3\3\3\0\3\0\3\0\3\0\3\3\3\27\0\3\0\3\0\0\0\0\8\8\27\27\27\27\27\
\\27\26\27\27\27\3\0\3\3\3\0\3\3\3\3\3\3\9\3\3\3\3\3\4\4\12\12\12\12\12\12\27\4\4\14\14\27\9\14\14\14\14\14\14\14\12\14\27\5\5\
\\4\7\5\0\0\0\14\0\0\0\0\0\0\14\14\14\14\14\14\14\14\12\14\27\9\9\25\9\9\9\9\9\27\9\9\9\9\7\7\7\7\7\7\7\7\9\9\14\14\27\
\\27\27\27\27\3\27\27\27\0\0\0\27\27\27\7\27\27\12\27\27\27\1\27\3\3\3\9\9\4\4\4\4\4\4\3\4\3\9\4\1\1\4\4\4\4\4\4\4\0\4\
\\4\4\4\3\3\3\26\3\1\27\27\27\27\27\27\26\26\0\0\0\7\7\7\7\7\7\7\0\27\26\27\27\27\27\27\27\27\4\3\27\27\27\0\0\27\0\0\0\0\0\
\\0\0\7\7\7\7\7\4\4\4\0\27\4\4\4\4\4\4\4\4\27\4\9\4\27\27\4\4\4\4\7\7\7\7\7\7\7\7\3\26\7\7\14\14\17\14\14\14\14\14\
\\27\14\14\14\14\14\4\4\14\9\27\27\27\27\27\27\27\4\4\4\4\4\4\7\4\27\0\0\14\27\27\27\27\27\27\14\0\0\27\22\22\22\25\25\25\25\25\22\22\22\
\\22\22\22\0\0\0\22\22\21\21\21\21\21\21\4\22\7\7\8\7\12\12\12\12\7\7\7\7\8\7\7\7\7\4\3\3\3\3\0\0\3\3\3\3\3\3\3\0\3\0\
\\3\3\3\3\0\3\0\4\1\1\4\4\4\4\4\3\3\4\3\3\3\3\3\3\27\27\8\8\8\4\4\8\4\4\4\4\4\4\4\7\8\8\8\8\8\8\8\8\7\7\
\\7\7\7\7\7\14\14\4\27\5\16\5\0\0\0\0\0\7\7\7\7\7\0\0\0\0\0\0\0\27\27\0\27\27\27\4\4\4\4\0\7\8\8\8\8\8\8\8\0\0\
\\0\0\3\3\27\3\3\27\9\9\9\9\27\27\9\27\27\9\14\9\27\27\4\4\0\0\0\0\4\4\4\4\4\4\4\15\15\15\15\27\3\27\3\27\3\3\3\3\3\4\
\\4\4\4\27\4\9\4\25\25\25\25\25\25\25\25\0\0\21\21\21\21\0\0\22\0\7\3\15\15\0\0\0\0\3\3\3\7\7\7\7\7\7\7\27\14\14\27\27\27\27\
\\27\7\7\7\7\3\3\17\7\27\7\7\9\9\14\27\27\27\27\27\27\27\9\9\9\14\27\27\27\1\1\27\27\27\27\2\2\27\27\4\4\8\8\8\8\8\8\4\4\8\
\\4\4\4\27\12\0\0\5\27\5\27\0\5\5\5\5\5\0\0\5\5\5\0\0\6\5\5\6\6\6\5\6\6\6\6\6\0\0\0\0\6\27\27\14\14\14\14\14\14\12\
\\12\14\14\14\27\14\14\14\14\14\14\4\14\14\4\14\17\8\19\14\4\14\14\14\14\27\27\27\27\27\26\26\27\27\7\7\9\9\14\27\27\27\27\4\4\27\27\13\13\13\
\\13\13\13\8\8\8\8\8\8\8\4\21\21\0\0\0\0\22\22\22\22\22\22\0\23\10\10\10\10\10\10\20\20\20\20\20\20\20\20\14\14\14\14\0\14\14\0\0\27\0\
\\0\0\0\0\20\20\20\20\20\20\20\20\10\10\0\0\0\0\0"#
identifierTypesOffsets1BitMap :: Ptr Word16
identifierTypesOffsets1BitMap :: Ptr Word16
identifierTypesOffsets1BitMap = Addr# -> Ptr Word16
forall a. Addr# -> Ptr a
Ptr
Addr#
"\154\5\43\7\155\5\155\5\166\1\166\1\166\1\158\5\50\7\184\4\229\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\155\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\155\5\233\0\160\5\166\1\53\7\156\5\166\1\166\1\166\1\
\\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\187\4\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\42\7\166\1\166\1\166\1\166\1\166\1\166\1\
\\187\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\184\3\119\4\119\4\226\3\228\3\15\4\43\2\14\4\15\4\15\4\78\2\14\4\15\4\15\4\140\7\66\5\119\4\119\4\119\4\225\3\113\1\
\\192\3\169\5\15\4\15\4\224\6\15\4\15\4\15\4\224\6\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\229\6\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\225\6\51\6\51\6\51\6\51\6\135\6\47\3\15\4\15\4\15\4\15\4\85\1\148\6\111\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\
\\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\114\4\49\4\49\4\49\4\49\4\49\4\49\4\50\4\119\4\82\3\82\3\82\3\82\3\82\3\84\3\116\2\116\2\116\2\116\2\116\2\116\2\116\2\255\2\29\3\119\4\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\77\8\44\3\119\4\82\3\82\3\116\2\116\2\116\2\116\2\116\2\116\2\116\2\123\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\248\3\191\8\15\4\15\4\15\4\57\2\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\
\\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\221\0\119\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\230\1\224\1\230\1\15\4\15\4\15\4\15\4\15\4\230\1\15\4\15\4\15\4\15\4\230\1\224\1\230\1\15\4\224\1\
\\15\4\15\4\15\4\15\4\15\4\15\4\15\4\154\2\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\119\4\119\4\119\4\119\4\48\1\165\1\35\1\237\5\173\5\41\1\109\3\73\7\218\3\172\1\
\\166\1\166\1\166\1\166\1\166\1\166\1\28\7\233\7\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\186\7\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\
\\181\3\176\6\0\5\176\6\0\5\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\153\2\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\61\0\119\4\119\4\119\4\101\2\101\2\101\2\101\2\101\2\101\2\166\1\191\4\125\3\
\\128\1\166\1\166\1\28\1\166\1\157\5\166\1\186\4\189\4\10\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\177\2\154\5\43\7\155\5\155\5\166\1\166\1\166\1\158\5\50\7\184\4\229\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\
\\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\187\4\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\131\5\58\5\58\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\184\4\166\1\166\1\166\1\166\1\166\1\166\1\8\3\119\4\119\4\119\4\119\4\166\1\132\5\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\116\2\120\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\5\3\119\4\116\2\116\2\116\2\116\2\116\2\116\2\1\2\1\2\
\\116\2\116\2\118\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\5\3\119\4\122\4\15\4\15\4\15\4\15\4\17\4\185\4\166\1\166\1\166\1\166\1\166\1\
\\113\3\166\1\166\1\166\1\166\1\186\4\164\1\166\1\15\4\15\4\15\4\15\4\176\6\176\6\176\6\176\6\1\5\193\4\51\6\51\6\51\6\244\7\153\2\119\4\156\6\119\4\119\4\119\4\153\6\119\4\123\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\120\2\82\3\82\3\82\3\82\3\82\3\114\4\82\3\113\4\82\3\186\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\117\2\
\\119\4\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\204\2\186\4\119\4\183\4\196\2\166\1\166\1\186\4\50\7\163\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\135\5\58\5\63\5\119\4\183\4\166\1\166\1\166\1\166\1\166\1\186\4\166\1\166\1\166\1\166\1\166\1\176\6\166\1\
\\166\1\166\1\166\1\166\1\130\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\187\4\119\4\119\4\119\4\176\6\176\6\244\3\253\3\15\4\15\4\15\4\15\4\23\4\
\\15\4\25\4\244\3\15\4\188\6\82\6\65\1\15\4\17\4\15\4\15\4\22\4\15\4\15\4\15\4\15\4\15\4\137\4\215\6\24\0\121\8\15\4\127\8\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\116\2\116\2\117\2\4\2\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\122\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\255\2\7\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\115\4\82\3\163\8\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\185\7\176\6\176\6\176\6\
\\176\6\176\6\176\6\176\6\0\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\119\2\116\2\116\2\116\2\116\2\116\2\116\2\123\2\119\4\148\7\98\7\98\7\152\7\185\7\176\6\176\6\176\6\176\6\176\6\176\6\255\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\185\7\176\6\176\6\176\6\176\6\176\6\176\6\176\6\0\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\
\\118\2\116\2\28\3\1\2\1\2\118\2\119\4\119\4\119\4\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\85\3\82\3\82\3\115\2\116\2\116\2\3\3\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\114\0\116\2\123\2\82\3\82\3\82\3\82\3\82\3\119\4\82\3\117\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\176\6\176\6\176\6\105\6\116\2\116\2\116\2\
\\116\2\116\2\161\3\122\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\22\6\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\51\6\51\6\51\6\51\6\24\7\213\5\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\
\\15\4\154\2\119\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\158\6\119\4\15\4\15\4\15\4\15\4\15\4\15\4\62\1\66\1\65\1\210\1\15\4\15\4\15\4\15\4\15\4\66\1\1\6\
\\4\6\244\3\244\3\242\3\99\8\243\3\0\0\150\5\91\5\15\4\37\2\27\4\15\4\74\1\15\4\15\4\230\1\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\60\2\176\6\193\6\102\1\0\5\15\4\15\4\176\6\3\5\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\113\4\113\4\101\2\101\2\101\2\101\2\
\\101\2\101\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\117\2\4\2\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\120\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\
\\116\2\116\2\122\2\116\2\116\2\116\2\116\2\116\2\116\2\255\2\1\2\2\3\119\4\116\2\140\3\21\3\116\2\116\2\126\2\116\2\116\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\1\2\1\2\1\2\44\3\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\224\1\81\0\15\4\224\1\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\
\\15\4\61\0\119\4\119\4\119\4\101\2\101\2\101\2\101\2\101\2\101\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\101\2\82\3\82\3\82\3\112\4\82\3\115\4\82\3\115\4\10\7\82\3\82\3\82\3\82\3\
\\113\4\114\4\119\4\82\3\82\3\82\3\82\3\82\3\115\4\82\3\82\3\82\3\117\4\82\3\226\2\176\6\176\6\176\6\176\6\176\6\69\7\225\3\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\102\6\176\6\176\6\
\\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\109\6\176\6\176\6\176\6\176\6\176\6\176\6\2\5\119\4\119\4\119\4\119\4\166\1\191\4\15\4\15\4\15\4\214\1\23\0\15\4\
\\20\8\244\3\244\3\244\3\150\1\146\5\139\1\134\1\247\0\145\1\125\3\141\1\140\1\143\1\125\3\125\3\166\1\47\5\15\5\125\3\90\6\168\1\169\1\180\6\176\6\176\6\176\6\176\6\176\6\102\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\
\\176\6\176\6\176\6\176\6\176\6\176\6\105\6\119\4\119\4\119\4\176\6\2\5\119\4\119\4\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\134\5\58\5\58\5\58\5\58\5\220\0\219\0\58\5\58\5\58\5\58\5\58\5\85\5\120\3\241\0\193\1\194\0\199\0\204\0\
\\58\5\58\5\58\5\111\5\58\5\88\5\136\5\58\5\58\5\138\5\183\8\213\8\119\4\119\4\176\6\214\3\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\219\3\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\214\3\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\
\\176\6\176\6\176\6\176\6\176\6\176\6\186\3\176\6\176\6\176\6\106\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\189\7\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\105\6\182\3\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\3\5\
\\176\6\1\5\4\5\119\4\51\6\51\6\51\6\51\6\135\6\47\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\194\2\193\2\212\2\15\4\15\4\224\1\119\4\224\1\224\1\224\1\224\1\224\1\224\1\224\1\224\1\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\94\2\93\2\51\6\51\6\51\6\51\6\51\6\
\\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\51\6\244\7\153\2\119\4\156\6\119\4\119\4\119\4\153\6\119\4\123\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\116\2\118\2\116\2\122\2\82\3\82\3\82\3\82\3\115\4\82\3\82\3\82\3\82\3\115\4\166\1\223\3\166\1\166\1\166\1\167\1\166\1\166\1\166\1\166\1\176\6\176\6\176\6\221\3\176\6\176\6\176\6\176\6\225\3\176\6\176\6\255\4\119\4\119\4\119\4\119\4\119\4\119\4\194\4\176\6\
\\176\6\176\6\176\6\176\6\1\5\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\1\5\119\4\176\6\105\6\185\7\176\6\185\7\176\6\185\7\176\6\176\6\176\6\255\4\119\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\
\\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\158\6\119\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\57\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\24\3\29\3\119\4\116\2\
\\116\2\116\2\116\2\28\3\6\3\119\4\119\4\116\2\116\2\0\3\6\3\119\4\119\4\119\4\119\4\116\2\116\2\24\3\84\8\119\4\119\4\116\2\116\2\117\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\176\6\176\6\176\6\105\6\116\2\116\2\116\2\116\2\116\2\161\3\122\2\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\22\6\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\185\2\82\3\82\3\82\3\82\3\82\3\82\3\82\3\212\2\82\3\82\3\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\12\6\119\4\154\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\1\2\1\2\1\2\44\3\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\37\2\33\4\170\7\43\6\60\6\165\7\29\0\50\5\160\7\189\1\125\3\35\0\40\0\51\6\198\6\20\1\156\7\130\4\15\4\15\4\221\1\15\4\15\4\15\4\15\4\17\8\118\3\51\6\246\2\116\2\120\1\
\\173\3\51\6\51\6\15\4\15\4\15\4\78\1\223\1\15\4\15\4\15\4\224\1\174\6\223\6\15\4\15\4\15\4\66\1\158\1\26\6\244\3\206\6\244\3\11\0\16\0\113\8\119\4\15\4\15\4\15\4\233\1\126\6\119\4\49\4\51\4\82\3\82\3\82\3\82\3\82\3\82\3\215\7\220\7\15\4\15\4\15\4\15\4\15\4\15\4\15\4\
\\15\4\15\4\15\4\15\4\15\4\154\2\119\4\82\3\82\3\82\3\82\3\82\3\41\4\84\3\232\2\116\2\116\2\116\2\116\2\116\2\118\2\1\2\2\2\82\3\82\3\82\3\225\7\82\3\116\4\15\4\15\4\15\4\56\2\3\5\244\3\15\4\254\7\249\7\15\4\15\4\242\3\244\3\244\3\20\0\244\3\244\3\244\3\16\8\15\4\15\4\
\\15\4\15\4\15\4\15\4\15\4\15\4\17\4\11\8\166\1\141\8\15\4\14\4\23\4\219\1\58\2\69\0\15\4\15\4\222\1\68\2\61\2\58\2\62\2\120\4\170\2\59\2\15\4\229\6\233\6\73\2\233\1\69\0\15\4\15\4\222\1\71\3\90\0\233\1\150\2\19\6\200\5\121\4\15\4\149\4\119\4\73\2\225\1\221\1\15\4\15\4\
\\222\1\84\0\61\2\225\1\86\0\158\6\119\4\59\2\15\4\3\5\241\6\73\2\58\2\69\0\15\4\15\4\222\1\84\0\61\2\245\6\150\2\122\4\60\3\31\2\15\4\246\4\119\4\135\7\69\6\230\1\95\0\237\1\69\6\15\4\234\1\69\6\230\1\241\1\119\4\121\4\15\4\176\6\2\5\23\4\226\1\222\1\15\4\15\4\222\1\19\4\
\\61\2\226\1\230\1\132\7\145\2\31\2\15\4\193\4\176\6\10\4\226\1\222\1\15\4\15\4\222\1\227\1\61\2\226\1\230\1\132\7\243\1\59\2\15\4\152\2\119\4\77\6\226\1\222\1\15\4\15\4\15\4\15\4\215\1\25\2\134\4\123\4\90\7\31\2\15\4\176\6\55\2\66\4\100\5\78\0\70\0\72\0\15\4\221\1\65\2\224\1\
\\50\3\128\4\100\5\160\6\51\6\55\3\119\4\223\1\15\4\15\4\15\4\15\4\15\4\72\4\178\3\15\4\224\6\15\4\178\7\119\4\119\4\119\4\119\4\95\0\228\1\15\4\15\4\129\4\15\4\72\4\57\2\128\4\224\1\15\4\19\2\119\4\119\4\119\4\119\4\175\6\48\2\176\6\90\6\15\4\229\6\2\4\13\2\72\4\70\4\73\4\
\\71\4\15\4\67\6\100\0\121\6\236\3\15\4\72\4\70\4\73\4\71\4\15\4\224\4\178\6\107\6\176\6\2\5\119\4\119\4\119\4\119\4\116\2\116\2\118\2\124\2\116\2\116\2\1\3\119\4\116\2\116\2\120\2\119\4\116\2\249\2\130\0\119\4\15\4\15\4\15\4\15\4\28\8\23\4\33\8\15\4\15\4\18\8\240\4\51\8\15\4\
\\154\2\176\6\3\5\1\2\189\0\116\2\122\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\123\2\116\2\116\2\116\2\116\2\116\2\117\7\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\113\4\119\4\116\2\116\2\116\2\37\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\112\4\82\3\82\3\82\3\
\\92\3\82\3\117\4\82\3\117\4\162\2\5\7\51\6\43\0\1\6\245\3\119\4\119\4\119\4\119\4\119\4\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\114\4\82\3\47\4\49\4\253\6\1\7\50\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\115\4\158\2\82\3\
\\82\3\82\3\82\3\82\3\82\3\82\3\159\2\82\3\95\4\82\3\82\3\82\3\82\3\82\3\84\3\51\6\129\7\15\4\15\4\15\4\15\4\15\4\60\2\49\4\119\4\33\7\51\6\51\6\51\6\51\6\173\4\125\3\125\3\125\3\125\3\125\3\6\1\166\1\234\5\166\1\231\5\166\1\166\1\166\1\122\3\125\3\124\3\125\3\125\3\125\3\
\\151\5\166\1\166\1\166\1\166\1\2\1\143\1\253\0\254\0\255\0\125\3\125\3\38\6\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\87\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\50\5\15\4\15\4\57\2\57\2\15\4\
\\15\4\15\4\15\4\57\2\57\2\15\4\66\3\15\4\15\4\157\4\159\4\15\4\15\4\15\4\15\4\15\4\15\4\226\1\70\1\94\5\197\7\77\4\222\5\72\4\70\1\72\2\212\0\166\1\86\2\211\3\198\3\113\6\200\4\70\7\94\6\91\6\224\3\106\1\216\4\196\1\202\1\44\7\166\1\166\1\186\4\166\1\188\4\176\6\225\3\176\6\
\\176\6\4\5\119\4\125\3\53\5\108\5\125\3\132\3\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\125\3\139\2\52\6\96\1\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\24\3\113\2\59\4\0\2\208\4\210\4\232\4\176\6\176\6\230\4\84\7\253\4\176\6\
\\176\6\176\6\255\4\119\4\119\4\119\4\119\4\176\6\176\6\176\6\110\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\203\3\119\4\52\2\176\6\176\6\248\4\20\5\22\5\49\0\87\6\223\1\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\224\1\82\4\143\6\15\4\15\4\15\4\15\4\15\4\15\4\
\\15\4\15\4\15\4\15\4\218\5\82\3\44\4\41\4\82\3\82\3\39\5\119\4\119\4\51\6\51\6\51\6\51\6\51\6\106\7\102\7\109\7\51\6\51\6\51\6\3\8\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\47\4\119\4\98\7\58\5\117\5\15\4\243\5\254\0\51\6\51\6\51\6\51\6\51\6\51\6\51\6\
\\51\6\243\7\51\6\51\6\251\5\82\1\51\6\51\6\90\1\7\0\187\1\15\4\153\2\131\4\154\2\119\4\119\4\239\7\240\2\82\3\82\3\82\3\82\3\82\3\165\2\176\6\3\5\116\2\116\2\116\2\116\2\116\2\116\2\25\3\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\113\4\156\2\82\3\117\4\51\6\51\6\51\6\
\\167\4\82\3\82\3\82\3\82\3\82\3\16\7\116\2\116\2\116\2\116\2\120\2\5\5\51\6\51\6\51\6\125\7\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\48\4\169\8\82\3\163\8\244\7\15\4\15\4\224\1\82\3\82\3\82\3\82\3\82\3\82\3\112\4\119\4\82\3\113\4\82\3\104\4\15\4\15\4\224\6\55\2\82\3\
\\82\3\82\3\82\3\82\3\82\3\82\3\82\3\116\4\119\4\119\4\216\2\82\3\82\3\90\3\119\4\126\4\126\4\126\4\119\4\224\1\224\1\51\6\51\6\51\6\51\6\51\6\38\7\143\4\54\0\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\100\4\82\3\117\4\15\4\15\4\15\4\
\\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\15\4\232\1\119\4\51\6\51\6\134\6\131\6\51\6\51\6\51\6\51\6\51\6\126\7\166\1\76\7\125\5\53\1\59\1\128\5\166\1\166\1\166\1\166\1\166\1\166\1\166\1\187\4\166\1\166\1\166\1\166\1\166\1\166\1\166\1\
\\166\1\166\1\166\1\166\1\166\1\166\1\191\4\119\4\119\4\119\4\119\4\185\4\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\166\1\117\3\166\1\166\1\186\4\184\4\184\4\184\4\227\0\186\4\186\4\119\4\184\3\116\2\250\2\116\2\116\2\117\2\116\2\116\2\
\\120\0\116\2\118\2\116\2\118\2\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\121\2\85\8\1\2\1\2\1\2\1\2\1\2\5\2\1\2\51\6\51\6\51\6\51\6\51\6\51\6\166\6\176\6\176\6\105\6\176\6\0\5\4\5\119\4\119\4\119\4\119\4\
\\119\4\98\7\98\7\98\7\98\7\98\7\179\1\116\2\116\2\116\2\116\2\84\8\126\2\116\2\116\2\116\2\121\2\116\2\116\2\116\2\116\2\116\2\121\2\116\2\116\2\116\2\131\2\116\2\116\2\116\2\116\2\120\2\116\2\35\3\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\119\4\116\2\116\2\116\2\116\2\116\2\
\\116\2\120\2\5\5\116\2\251\2\116\2\251\2\120\0\116\2\252\2\116\2\252\2\129\0\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\117\2\119\4\116\2\116\2\118\2\119\4\116\2\119\4\119\4\119\4\188\5\166\1\166\1\166\1\166\1\166\1\229\5\190\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\118\2\253\2\116\2\116\2\116\2\116\2\248\2\147\0\116\2\116\2\131\2\1\2\116\2\116\2\255\2\1\2\116\2\116\2\116\2\117\2\5\5\1\2\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\128\0\254\1\116\2\116\2\0\3\5\2\116\2\116\2\116\2\132\0\119\4\119\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\135\0\1\2\1\2\255\1\1\2\1\2\1\2\1\2\1\2\127\0\127\2\250\2\254\2\116\2\116\2\118\2\161\0\1\2\7\3\1\2\7\3\116\2\116\2\116\2\24\3\116\2\116\2\116\2\24\3\119\4\119\4\119\4\119\4\116\2\115\2\116\2\116\2\117\2\254\1\2\2\119\4\116\2\
\\116\2\116\2\116\2\116\2\116\2\118\2\0\2\116\2\116\2\118\2\1\2\116\2\116\2\121\2\1\2\116\2\116\2\122\2\42\3\119\4\0\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\123\2\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\
\\116\2\116\2\116\2\121\2\119\4\116\2\116\2\116\2\116\2\116\2\116\2\121\2\255\1\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\255\2\3\2\255\1\1\2\30\3\116\2\118\2\124\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\26\3\150\3\7\5\116\2\116\2\116\2\123\2\116\2\122\2\82\3\82\3\82\3\82\3\82\3\
\\82\3\33\5\82\3\108\4\119\4\116\2\116\2\116\2\116\2\168\0\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\24\3\140\0\116\2\184\0\185\7\176\6\0\5\119\4\116\2\116\2\252\2\116\2\116\2\116\2\116\2\30\3\122\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\117\2\125\0\116\2\248\2\116\2\165\3\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\121\2\116\2\122\2\59\8\154\0\151\0\116\2\116\2\253\2\122\0\176\0\154\0\158\0\152\3\126\2\155\0\119\2\119\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\82\3\
\\46\4\82\3\220\2\117\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\181\0\119\4\116\2\122\2\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\148\3\119\4\116\2\122\2\1\2\4\2\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\165\3\116\2\122\2\119\4\
\\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\156\0\116\2\120\2\116\2\27\3\117\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\76\5\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\27\3\44\3\124\2\117\2\150\0\127\0\116\2\116\2\116\2\248\2\151\0\16\3\119\4\116\2\122\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\129\2\116\2\116\2\116\2\116\2\116\2\129\2\143\0\119\4\119\4\
\\119\4\176\6\3\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\253\2\116\2\116\2\116\2\116\2\117\2\116\2\82\8\119\4\116\2\27\3\1\2\4\2\114\2\116\2\116\2\
\\116\2\129\2\116\2\116\2\254\2\117\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\117\2\252\2\116\2\116\2\116\2\116\2\117\2\157\3\116\2\119\4\116\2\122\2\32\5\80\3\82\3\82\3\82\3\112\4\79\3\118\4\82\3\117\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\253\2\
\\116\2\116\2\116\2\116\2\108\0\26\3\1\2\116\2\122\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\118\4\119\4\176\6\176\6\176\6\176\6\176\6\176\6\3\5\193\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\117\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\82\3\82\3\82\3\82\3\82\3\82\3\82\3\118\4\100\3\100\3\100\3\101\3\100\3\251\1\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\117\2\116\2\122\2\116\2\116\2\116\2\118\2\74\5\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\
\\116\2\118\2\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\121\2\116\2\119\2\116\2\123\2\116\2\72\8\105\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\125\3\125\3\125\3\125\3\125\3\127\3\125\3\125\3\126\3\119\4\58\5\
\\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\62\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\98\7\98\7\98\7\98\7\98\7\98\7\98\7\98\7\180\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\176\6\176\6\1\5\119\4\176\6\
\\176\6\1\5\119\4\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\58\5\220\0\119\4\176\6\176\6\176\6\4\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\
\\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\1\2\116\2\116\2\116\2\116\2\116\2\116\2\255\2\113\2\116\2\116\2\116\2\116\2\116\2\24\3\143\3\1\2\144\3\84\8\119\4\128\2\254\2\116\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\15\4\
\\15\4\15\4\224\1\122\4\153\2\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\117\2\116\2\116\2\151\0\121\0\121\2\166\1\166\1\166\1\166\1\166\1\166\1\166\1\187\4\119\4\119\4\119\4\120\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\116\2\36\3\1\2\117\2\119\4\119\4\119\4\119\4\119\4\156\5\166\1\166\1\166\1\15\1\
\\185\4\157\5\205\5\179\4\196\5\15\1\194\5\15\1\157\5\157\5\57\7\166\1\228\5\166\1\189\4\226\5\228\5\166\1\189\4\119\4\119\4\119\4\119\4\119\4\119\4\3\5\119\4\190\4\119\4\166\1\166\1\166\1\166\1\166\1\189\4\166\1\192\4\191\4\119\4\255\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\
\\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\176\6\1\5\176\6\176\6\176\6\176\6\176\6\176\6\176\6\119\4\176\6\3\5\176\6\176\6\176\6\176\6\176\6\119\4\176\6\176\6\176\6\255\4\3\5\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\119\4\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\176\6\
\\176\6\1\5\119\4\176\6\255\4\176\6\0\5\176\6\4\5\176\6\176\6\176\6\176\6\176\6\106\6\255\4\194\4\176\6\1\5\176\6\4\5\176\6\4\5"#
identifierTypesOffsets2BitMap :: Ptr Word16
identifierTypesOffsets2BitMap :: Ptr Word16
identifierTypesOffsets2BitMap = Addr# -> Ptr Word16
forall a. Addr# -> Ptr a
Ptr
Addr#
"\128\0\103\5\2\7\65\9\33\5\97\9\173\3\129\9\161\9\193\9\225\9\1\10\33\10\65\10\97\10\129\10\159\0\240\7\117\1\134\5\191\0\192\0\205\4\161\10\193\10\151\6\225\10\1\11\33\11\65\11\97\11\129\11\161\11\184\1\179\6\206\6\60\7\212\6\212\6\212\6\83\1\212\6\122\7\150\7\193\11\212\7\225\11\143\3\1\12\226\2\
\\121\3\137\3\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\59\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\192\0\192\0\192\0\192\0\207\0\192\0\33\12\65\12\97\12\129\12\161\12\193\12\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\225\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\137\3\
\\1\13\92\3\137\3\102\2\33\2\33\13\65\13\97\13\81\4\129\13\40\8\161\13\205\3\193\13\225\13\1\14\33\14\65\14\97\14\237\4\1\5\195\8\129\14\161\14\193\14\225\14\1\15\154\4\33\15\65\15\97\15\129\15\239\0\161\15\193\15\225\15\8\4\1\16\205\3\205\3\205\3\240\3\224\3\134\2\4\4\4\4\4\4\4\4\4\4\4\4\
\\4\4\4\4\4\4\148\2\205\3\205\3\205\3\205\3\180\2\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\205\3\205\3\33\16\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\
\\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\192\0\192\0\65\16\17\6\4\4\4\4\41\6\2\9\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\205\3\97\16\205\3\205\3\205\3\205\3\129\16\13\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\15\1\253\7\0\3\14\3\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\161\16\4\4\4\4\4\4\4\4\4\4\
\\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\193\16\85\1\90\7\225\16\1\17\22\0\0\0\47\0\68\0\33\17\33\17\65\17\4\4\4\4\4\4\4\4\97\17\129\17\46\3\60\3\4\4\241\5\4\4\4\4\61\6\161\17\40\4\4\4\4\4\58\4\113\4\193\17\4\4\101\8\72\8\225\17\212\6\
\\212\6\207\1\217\1\180\7\1\18\212\6\33\18\226\6\4\4\4\4\4\4\4\4\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\152\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\144\1\47\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\5\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\73\5\51\1\51\1\
\\163\8\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\4\137\3\137\3\97\0\4\4\4\4\4\4\4\4\4\4\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\249\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\51\1\
\\51\1\51\1\51\1\3\2\166\5\188\5"#