module Data.Char.Unicode ( GeneralCategory (..), generalCategory, unicodeVersion, isControl, isPrint, isSpace, isUpper, isLower, isAlpha, isDigit, isAlphaNum, isNumber, isMark, isSeparator, isPunctuation, isSymbol, toTitle, toUpper, toLower, ) where import qualified Prelude(); import MiniPrelude import Primitives(primOrd, primUnsafeCoerce) import Data.Bits.Base import Data.Bounded import qualified Data.ByteString.Internal as BS import Data.ByteString.Internal(ByteString) import Data.Version import Data.Word.Word8(Word8) data GeneralCategory = UppercaseLetter -- Lu: Letter, Uppercase | LowercaseLetter -- Ll: Letter, Lowercase | TitlecaseLetter -- Lt: Letter, Titlecase | ModifierLetter -- Lm: Letter, Modifier | OtherLetter -- Lo: Letter, Other | NonSpacingMark -- Mn: Mark, Non-Spacing | SpacingCombiningMark -- Mc: Mark, Spacing Combining | EnclosingMark -- Me: Mark, Enclosing | DecimalNumber -- Nd: Number, Decimal | LetterNumber -- Nl: Number, Letter | OtherNumber -- No: Number, Other | ConnectorPunctuation -- Pc: Punctuation, Connector | DashPunctuation -- Pd: Punctuation, Dash | OpenPunctuation -- Ps: Punctuation, Open | ClosePunctuation -- Pe: Punctuation, Close | InitialQuote -- Pi: Punctuation, Initial quote | FinalQuote -- Pf: Punctuation, Final quote | OtherPunctuation -- Po: Punctuation, Other | MathSymbol -- Sm: Symbol, Math | CurrencySymbol -- Sc: Symbol, Currency | ModifierSymbol -- Sk: Symbol, Modifier | OtherSymbol -- So: Symbol, Other | Space -- Zs: Separator, Space | LineSeparator -- Zl: Separator, Line | ParagraphSeparator -- Zp: Separator, Paragraph | Control -- Cc: Other, Control | Format -- Cf: Other, Format | Surrogate -- Cs: Other, Surrogate | PrivateUse -- Co: Other, Private Use | NotAssigned -- Cn: Other, Not Assigned deriving (Show, Eq, Ord, Enum, Bounded) isControl :: Char -> Bool isControl c = case generalCategory c of Control -> True _ -> False isPrint :: Char -> Bool isPrint c = case generalCategory c of LineSeparator -> False ParagraphSeparator -> False Control -> False Format -> False Surrogate -> False PrivateUse -> False NotAssigned -> False _ -> True isSpace :: Char -> Bool isSpace c = generalCategory c == Space isUpper :: Char -> Bool isUpper c = case generalCategory c of UppercaseLetter -> True TitlecaseLetter -> True _ -> False isLower :: Char -> Bool isLower c = case generalCategory c of LowercaseLetter -> True _ -> False isAlpha :: Char -> Bool isAlpha c = case generalCategory c of UppercaseLetter -> True LowercaseLetter -> True TitlecaseLetter -> True ModifierLetter -> True OtherLetter -> True _ -> False isAlphaNum :: Char -> Bool isAlphaNum c = case generalCategory c of UppercaseLetter -> True LowercaseLetter -> True TitlecaseLetter -> True ModifierLetter -> True OtherLetter -> True DecimalNumber -> True LetterNumber -> True OtherNumber -> True _ -> False isNumber :: Char -> Bool isNumber c = case generalCategory c of DecimalNumber -> True LetterNumber -> True OtherNumber -> True _ -> False isMark :: Char -> Bool isMark c = case generalCategory c of NonSpacingMark -> True SpacingCombiningMark -> True EnclosingMark -> True _ -> False isSeparator :: Char -> Bool isSeparator c = case generalCategory c of Space -> True LineSeparator -> True ParagraphSeparator -> True _ -> False isPunctuation :: Char -> Bool isPunctuation c = case generalCategory c of ConnectorPunctuation -> True DashPunctuation -> True OpenPunctuation -> True ClosePunctuation -> True InitialQuote -> True FinalQuote -> True OtherPunctuation -> True _ -> False isSymbol :: Char -> Bool isSymbol c = case generalCategory c of MathSymbol -> True CurrencySymbol -> True ModifierSymbol -> True OtherSymbol -> True _ -> False toTitle :: Char -> Char toTitle c = convLU tcTable c toUpper :: Char -> Char toUpper c = convLU ucTable c toLower :: Char -> Char toLower c = convLU lcTable c -- XXX We could build a search tree and use binary search. -- The table is delta coded. The first Int is the distance from -- previous table entry. The second is the length of the span-1. -- The third is the offset to add doing the conversion. convLU :: [(Int, Int, Int)] -> Char -> Char convLU t c = conv 0 t where i = primOrd c conv _ [] = c conv o ((dl, dh, zd):lhds) | i < l = c | i <= h = chr (i + d) | otherwise = conv l lhds where l = o + dl h = l + dh d = zigZagDecode zd -- Do -- (x >> 1) ^ -(x & 1) -- This puts the sign bit back. -- Due to the range we know the incoming x is never negative. zigZagDecode :: Int -> Int zigZagDecode x = (x `unsafeShiftR` 1) `xor` (-(x .&. 1)) -- -- Same as in src/runtime/bfile.c. -- Run Length Encoding for ASCII -- Format -- c - c one ASCII character -- 0x80+n c - n+1 repetitions of ASCII character c, n > 1 -- 0x80+n 0x80+m c - n*128+m+1 repetitions of ASCII character c -- ... for longer run lengths -- Non-ASCII (i.e., >= 128) has a very poor encoding: -- 0x81 c-0x80 decompressRLE :: BS.ByteString -> BS.ByteString decompressRLE = BS.pack . de 0 . BS.unpack where de :: Int -> [Word8] -> [Word8] de _ [] = [] de 1 (x:xs) | x < 0x80 = x + 0x80 : de 0 xs de n (x:xs) | x < 0x80 = replicate (n + 1) x ++ de 0 xs | otherwise = de ((n * 128) + fromIntegral x - 0x80) xs -- XXX Instead of having a totally decompressed (large!) bytestring, -- we could build a search tree from the RLE encoding. generalCategory :: Char -> GeneralCategory generalCategory c = let i = primOrd c in if i < 0 || i >= BS.length bytestringGCTable then NotAssigned else toEnum (fromEnum (BS.primBSindex bytestringGCTable i)) bytestringGCTable :: BS.ByteString bytestringGCTable = decompressRLE compressedGCTable -- These tables are generated by unicode/UniParse.hs -- This is for Unicode 16.0.0 unicodeVersion :: Version unicodeVersion = makeVersion [16,0,0] compressedGCTable :: ByteString compressedGCTable = "\159\12\9\130\25\27\130\25\21\22\25\26\25\20\25\25\137\6\25\25\130\26\25\25\153\0\21\25\22\28\19\28\153\1\21\26\22\26\160\12\9\25\131\27\29\25\28\29\18\23\26\13\29\28\29\26\8\8\28\1\25\25\28\8\18\24\130\8\25\150\0\26\134\0\151\1\26\135\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\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\130\1\0\0\1\0\1\0\0\1\130\0\1\1\131\0\1\0\0\1\130\0\130\1\0\0\1\0\0\1\0\1\0\1\0\0\1\0\1\1\0\1\0\0\1\130\0\1\0\1\0\0\1\1\18\0\130\1\131\18\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\130\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\134\1\0\0\1\0\0\1\1\0\1\131\0\1\0\1\0\1\0\1\0\196\1\18\154\1\145\17\131\28\139\17\141\28\132\17\134\28\17\28\17\144\28\239\3\0\1\0\1\17\28\0\1\16\16\17\130\1\25\0\131\16\28\28\0\25\130\0\16\0\16\0\0\1\144\0\16\136\0\162\1\0\1\1\130\0\130\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\132\1\0\1\26\0\1\0\0\1\1\178\0\175\1\0\1\0\1\0\1\0\1\0\1\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\132\3\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\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\16\165\0\16\16\17\133\25\168\1\25\20\16\16\29\29\27\16\172\3\20\3\25\3\3\25\3\3\25\3\135\16\154\18\131\16\131\18\25\25\138\16\133\13\130\26\25\25\27\25\25\29\29\138\3\25\13\130\25\159\18\17\137\18\148\3\137\6\131\25\18\18\3\226\18\25\18\134\3\13\29\133\3\17\17\3\3\29\131\3\18\18\137\6\130\18\29\29\18\141\25\16\13\18\3\157\18\154\3\16\16\216\18\138\3\18\141\16\137\6\160\18\136\3\17\17\29\130\25\17\16\16\3\27\27\149\18\131\3\17\136\3\17\130\3\17\132\3\16\16\142\25\16\152\18\130\3\16\16\25\16\138\18\132\16\151\18\28\133\18\16\13\13\132\16\136\3\168\18\17\151\3\13\159\3\4\181\18\3\4\3\18\130\4\135\3\131\4\3\4\4\18\134\3\137\18\3\3\25\25\137\6\25\17\142\18\3\4\4\16\135\18\16\16\18\18\16\16\149\18\16\134\18\16\18\130\16\131\18\16\16\3\18\130\4\131\3\16\16\4\4\16\16\4\4\3\18\135\16\4\131\16\18\18\16\130\18\3\3\16\16\137\6\18\18\27\27\133\8\29\27\18\25\3\16\16\3\3\4\16\133\18\131\16\18\18\16\16\149\18\16\134\18\16\18\18\16\18\18\16\18\18\16\16\3\16\130\4\3\3\131\16\3\3\16\16\130\3\130\16\3\134\16\131\18\16\18\134\16\137\6\3\3\130\18\3\25\137\16\3\3\4\16\136\18\16\130\18\16\149\18\16\134\18\16\18\18\16\132\18\16\16\3\18\130\4\132\3\16\3\3\4\16\4\4\3\16\16\18\142\16\18\18\3\3\16\16\137\6\25\27\134\16\18\133\3\16\3\4\4\16\135\18\16\16\18\18\16\16\149\18\16\134\18\16\18\18\16\132\18\16\16\3\18\4\3\4\131\3\16\16\4\4\16\16\4\4\3\134\16\3\3\4\131\16\18\18\16\130\18\3\3\16\16\137\6\29\18\133\8\137\16\3\18\16\133\18\130\16\130\18\16\131\18\130\16\18\18\16\18\16\18\18\130\16\18\18\130\16\130\18\130\16\139\18\131\16\4\4\3\4\4\130\16\130\4\16\130\4\3\16\16\18\133\16\4\141\16\137\6\130\8\133\29\27\29\132\16\3\130\4\3\135\18\16\130\18\16\150\18\16\143\18\16\16\3\18\130\3\131\4\16\130\3\16\131\3\134\16\3\3\16\130\18\16\16\18\16\16\18\18\3\3\16\16\137\6\134\16\25\134\8\29\18\3\4\4\25\135\18\16\130\18\16\150\18\16\137\18\16\132\18\16\16\3\18\4\3\132\4\16\3\4\4\16\4\4\3\3\134\16\4\4\133\16\18\18\16\18\18\3\3\16\16\137\6\16\18\18\4\139\16\3\3\4\4\136\18\16\130\18\16\168\18\3\3\18\130\4\131\3\16\130\4\16\130\4\3\18\29\131\16\130\18\4\134\8\130\18\3\3\16\16\137\6\136\8\29\133\18\16\3\4\4\16\145\18\130\16\151\18\16\136\18\16\18\16\16\134\18\130\16\3\131\16\130\4\130\3\16\3\16\135\4\133\16\137\6\16\16\4\4\25\139\16\175\18\3\18\18\134\3\131\16\27\133\18\17\135\3\25\137\6\25\25\164\16\18\18\16\18\16\132\18\16\151\18\16\18\16\137\18\3\18\18\136\3\18\16\16\132\18\16\17\16\134\3\16\137\6\16\16\131\18\159\16\18\130\29\142\25\29\25\130\29\3\3\133\29\137\6\137\8\29\3\29\3\29\3\21\22\21\22\4\4\135\18\16\163\18\131\16\141\3\4\132\3\25\3\3\132\18\138\3\16\163\3\16\135\29\3\133\29\16\29\29\132\25\131\29\25\25\164\16\170\18\4\4\131\3\4\133\3\4\3\3\4\4\3\3\18\137\6\133\25\133\18\4\4\3\3\131\18\130\3\18\130\4\18\18\134\4\130\18\131\3\140\18\3\4\4\3\3\133\4\3\18\4\137\6\130\4\3\29\29\165\0\16\0\132\16\0\16\16\170\1\25\17\130\1\130\200\18\16\131\18\16\16\134\18\16\18\16\131\18\16\16\168\18\16\131\18\16\16\160\18\16\131\18\16\16\134\18\16\18\16\131\18\16\16\142\18\16\184\18\16\131\18\16\16\194\18\16\16\130\3\136\25\147\8\130\16\143\18\137\29\133\16\213\0\16\16\133\1\16\16\20\132\235\18\29\25\144\18\9\153\18\21\22\130\16\202\18\130\25\130\7\135\18\134\16\145\18\130\3\4\136\16\146\18\3\3\4\25\25\136\16\145\18\3\3\139\16\140\18\16\130\18\16\3\3\139\16\179\18\3\3\4\134\3\135\4\3\4\4\138\3\130\25\17\130\25\27\18\3\16\16\137\6\133\16\137\8\133\16\133\25\20\131\25\130\3\13\3\137\6\133\16\162\18\17\180\18\134\16\132\18\3\3\161\18\3\18\132\16\197\18\137\16\158\18\16\130\3\131\4\3\3\130\4\131\16\4\4\3\133\4\130\3\131\16\29\130\16\25\25\137\6\157\18\16\16\132\18\138\16\171\18\131\16\153\18\133\16\137\6\8\130\16\161\29\150\18\3\3\4\4\3\16\16\25\25\180\18\4\3\4\134\3\16\3\4\3\4\4\135\3\133\4\137\3\16\16\3\137\6\133\16\137\6\133\16\134\25\17\133\25\16\16\141\3\5\143\3\176\16\131\3\4\174\18\3\4\132\3\4\3\132\4\3\4\4\135\18\16\25\25\137\6\134\25\137\29\136\3\136\29\130\25\3\3\4\157\18\4\131\3\4\4\3\3\4\130\3\18\18\137\6\171\18\3\4\3\3\130\4\3\4\130\3\4\4\135\16\131\25\163\18\135\4\135\3\4\4\3\3\130\16\132\25\137\6\130\16\130\18\137\6\157\18\133\17\25\25\136\1\0\1\132\16\170\0\16\16\130\0\135\25\135\16\130\3\25\140\3\4\134\3\131\18\3\133\18\3\18\18\4\3\3\18\132\16\171\1\190\17\140\1\17\161\1\164\17\191\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\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\136\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\136\1\135\0\133\1\16\16\133\0\16\16\135\1\135\0\135\1\135\0\133\1\16\16\133\0\16\16\135\1\16\0\16\0\16\0\16\0\135\1\135\0\141\1\16\16\135\1\135\2\135\1\135\2\135\1\135\2\132\1\16\1\1\131\0\2\28\1\130\28\130\1\16\1\1\131\0\2\130\28\131\1\16\16\1\1\131\0\16\130\28\135\1\132\0\130\28\16\16\130\1\16\1\1\131\0\2\28\28\16\138\9\132\13\133\20\25\25\23\24\21\23\23\24\21\23\135\25\10\11\132\13\9\136\25\23\24\131\25\19\19\130\25\26\21\22\138\25\26\25\19\137\25\9\132\13\16\137\13\8\17\16\16\133\8\130\26\21\22\17\137\8\130\26\21\22\16\140\17\130\16\160\27\142\16\140\3\131\5\3\130\5\139\3\142\16\29\29\0\131\29\0\29\29\1\130\0\1\1\130\0\1\29\0\29\29\26\132\0\133\29\0\29\0\29\0\29\131\0\29\1\131\0\1\131\18\1\29\29\1\1\0\0\132\26\0\131\1\29\26\29\29\1\29\143\8\162\7\0\1\131\7\8\29\29\131\16\132\26\132\29\26\26\131\29\26\29\29\26\29\29\26\134\29\26\158\29\26\26\29\29\26\29\26\158\29\130\139\26\135\29\21\22\21\22\147\29\26\26\134\29\21\22\208\29\26\157\29\152\26\167\29\133\26\199\29\149\16\138\29\148\16\187\8\205\29\149\8\129\182\29\26\136\29\26\181\29\135\26\238\29\26\129\247\29\21\22\21\22\21\22\21\22\21\22\21\22\21\22\157\8\171\29\132\26\21\22\158\26\21\22\21\22\21\22\21\22\21\22\143\26\129\255\29\129\130\26\21\22\21\22\21\22\21\22\21\22\21\22\21\22\21\22\21\22\21\22\21\22\190\26\21\22\21\22\159\26\21\22\130\129\26\175\29\148\26\29\29\133\26\166\29\16\16\159\29\16\232\29\175\0\175\1\0\1\130\0\1\1\0\1\0\1\0\1\131\0\1\0\1\1\0\133\1\17\17\130\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\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\133\29\0\1\0\1\130\3\0\1\132\16\131\25\8\25\25\165\1\16\1\132\16\1\16\16\183\18\134\16\17\25\141\16\3\150\18\136\16\134\18\16\134\18\16\134\18\16\134\18\16\134\18\16\134\18\16\134\18\16\134\18\16\159\3\25\25\23\24\23\24\130\25\23\24\25\23\24\136\25\20\25\25\20\25\23\24\25\25\23\24\21\22\21\22\21\22\21\22\132\25\17\137\25\20\20\131\25\20\25\21\140\25\29\29\130\25\21\22\21\22\21\22\21\22\20\161\16\153\29\16\216\29\139\16\129\213\29\153\16\143\29\9\130\25\29\17\18\7\21\22\21\22\21\22\21\22\21\22\29\29\21\22\21\22\21\22\21\22\20\21\22\22\29\136\7\131\3\4\4\20\132\17\29\29\130\7\17\18\25\29\29\16\213\18\16\16\3\3\28\28\17\17\18\20\217\18\25\130\17\18\132\16\170\18\16\221\18\16\29\29\131\8\137\29\159\18\165\29\136\16\29\143\18\158\29\16\137\8\157\29\135\8\29\142\8\159\29\137\8\166\29\142\8\130\191\29\18\179\189\16\18\191\29\18\129\163\253\16\149\18\17\136\246\18\130\16\182\29\136\16\167\18\133\17\25\25\130\139\18\17\130\25\143\18\137\6\18\18\147\16\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\18\3\130\5\25\137\3\25\17\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\17\17\3\3\197\18\137\7\3\3\133\25\135\16\150\28\136\17\28\28\0\1\0\1\0\1\0\1\0\1\0\1\0\130\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\17\135\1\0\1\0\1\0\0\1\0\1\0\1\0\1\0\1\17\28\28\0\1\0\1\18\0\1\0\130\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\132\0\1\132\0\1\0\1\0\1\0\1\0\1\0\1\0\1\0\1\131\0\1\0\1\0\0\1\16\16\0\1\16\1\16\1\0\1\0\1\0\1\0\148\16\130\17\0\1\18\17\17\1\134\18\3\130\18\3\131\18\3\150\18\4\4\3\3\4\131\29\3\130\16\133\8\29\29\27\29\133\16\179\18\131\25\135\16\4\4\177\18\143\4\3\3\135\16\25\25\137\6\133\16\145\3\133\18\130\25\18\25\18\18\3\137\6\155\18\135\3\25\25\150\18\138\3\4\4\138\16\25\156\18\130\16\130\3\4\174\18\3\4\4\131\3\4\4\3\3\130\4\140\25\16\17\137\6\131\16\25\25\132\18\3\17\136\18\137\6\132\18\16\168\18\133\3\4\4\3\3\4\4\3\3\136\16\130\18\3\135\18\3\4\16\16\137\6\16\16\131\25\143\18\17\133\18\130\29\18\4\3\4\177\18\3\18\130\3\18\18\3\3\132\18\3\3\18\3\18\151\16\18\18\17\25\25\138\18\4\3\3\4\4\25\25\18\17\17\4\3\137\16\133\18\16\16\133\18\16\16\133\18\136\16\134\18\16\134\18\16\170\1\28\131\17\136\1\17\28\28\131\16\207\1\162\18\4\4\3\4\4\3\4\4\25\4\3\16\16\137\6\133\16\18\215\161\16\18\139\16\150\18\131\16\176\18\131\16\14\134\253\16\14\14\253\16\14\14\135\253\16\14\15\177\253\16\15\130\237\18\16\16\233\18\165\16\134\1\139\16\132\1\132\16\18\3\137\18\26\140\18\16\132\18\16\18\16\18\18\16\18\18\16\235\18\144\28\143\16\130\234\18\22\21\143\29\191\18\16\16\181\18\134\16\29\159\16\139\18\27\130\29\143\3\134\25\21\22\25\133\16\143\3\25\20\20\19\19\21\22\21\22\21\22\21\22\21\22\21\22\21\22\21\22\25\25\21\22\131\25\130\19\130\25\16\131\25\20\21\22\21\22\21\22\130\25\26\20\130\26\16\25\27\25\25\131\16\132\18\16\129\134\18\16\16\13\16\130\25\27\130\25\21\22\25\26\25\20\25\25\137\6\25\25\130\26\25\25\153\0\21\25\22\28\19\28\153\1\21\26\22\26\21\22\25\21\22\25\25\137\18\17\172\18\17\17\158\18\130\16\133\18\16\16\133\18\16\16\133\18\16\16\130\18\130\16\27\27\26\28\29\27\27\16\29\131\26\29\29\137\16\130\13\29\29\16\16\139\18\16\153\18\16\146\18\16\18\18\16\142\18\16\16\141\18\161\16\250\18\132\16\130\25\131\16\172\8\130\16\136\29\180\7\131\8\144\29\8\8\130\29\16\140\29\130\16\29\174\16\172\29\3\129\129\16\156\18\130\16\176\18\142\16\3\154\8\131\16\159\18\131\8\136\16\147\18\7\135\18\7\132\16\165\18\132\3\132\16\157\18\16\25\163\18\131\16\135\18\25\132\7\169\16\167\0\167\1\205\18\16\16\137\6\133\16\163\0\131\16\163\1\131\16\167\18\135\16\179\18\138\16\25\138\0\16\142\0\16\134\0\16\0\0\16\138\1\16\142\1\16\134\1\16\1\1\130\16\179\18\139\16\130\182\18\136\16\149\18\137\16\135\18\151\16\133\17\16\169\17\16\136\17\196\16\133\18\16\16\18\16\171\18\16\18\18\130\16\18\16\16\150\18\16\25\135\8\150\18\29\29\134\8\158\18\135\16\136\8\175\16\146\18\16\18\18\132\16\132\8\149\18\133\8\130\16\25\153\18\132\16\25\191\16\183\18\131\16\8\8\18\18\143\8\16\16\173\8\18\130\3\16\3\3\132\16\131\3\131\18\16\130\18\16\156\18\16\16\130\3\131\16\3\136\8\134\16\136\25\134\16\156\18\8\8\25\156\18\130\8\159\16\135\18\29\155\18\3\3\131\16\132\8\134\25\136\16\181\18\130\16\134\25\149\18\16\16\135\8\146\18\132\16\135\8\145\18\134\16\131\25\139\16\134\8\207\16\200\18\182\16\178\0\140\16\178\1\134\16\133\8\163\18\131\3\135\16\137\6\133\16\137\6\131\18\17\18\149\0\130\16\132\3\20\17\149\1\135\16\26\26\129\207\16\158\8\16\169\18\16\3\3\20\16\16\18\18\143\16\130\18\182\16\131\3\156\18\137\8\18\135\16\149\18\138\3\131\8\132\25\149\16\145\18\131\3\131\25\165\16\148\18\134\8\147\16\150\18\136\16\4\3\4\180\18\142\3\134\25\131\16\147\8\137\6\3\18\18\3\3\18\136\16\130\3\4\172\18\130\4\131\3\4\4\3\3\25\25\13\131\25\3\137\16\13\16\16\152\18\134\16\137\6\133\16\130\3\163\18\132\3\4\135\3\16\137\6\131\25\18\4\4\18\135\16\162\18\3\25\25\18\136\16\3\3\4\175\18\130\4\136\3\4\4\131\18\131\25\131\3\25\4\3\137\6\18\25\18\130\25\16\147\8\138\16\145\18\16\152\18\130\4\130\3\4\4\3\4\3\3\133\25\3\18\18\3\189\16\134\18\16\18\16\131\18\16\142\18\16\137\18\25\133\16\174\18\3\130\4\135\3\132\16\137\6\133\16\3\3\4\4\16\135\18\16\16\18\18\16\16\149\18\16\134\18\16\18\18\16\132\18\16\3\3\18\4\4\3\131\4\16\16\4\4\16\16\130\4\16\16\18\133\16\4\132\16\132\18\4\4\16\16\134\3\130\16\132\3\138\16\137\18\16\18\16\16\18\16\165\18\16\18\130\4\133\3\16\4\16\16\4\16\131\4\16\4\4\3\4\3\18\3\18\25\25\16\25\25\135\16\3\3\156\16\180\18\130\4\135\3\4\4\130\3\4\3\131\18\132\25\137\6\25\25\16\25\3\130\18\157\16\175\18\130\4\133\3\4\3\131\4\3\3\4\3\3\18\18\25\18\135\16\137\6\129\165\16\174\18\130\4\131\3\16\16\131\4\3\3\4\3\3\150\25\131\18\3\3\161\16\175\18\130\4\135\3\4\4\3\4\3\3\130\25\18\138\16\137\6\133\16\140\25\146\16\170\18\3\4\3\4\4\133\3\4\3\18\25\133\16\137\6\133\16\147\6\155\16\154\18\16\16\3\4\3\4\4\131\3\4\132\3\131\16\137\6\8\8\130\25\29\134\18\129\184\16\171\18\130\4\136\3\4\3\3\25\227\16\159\0\159\1\137\6\136\8\139\16\135\18\16\16\18\16\16\135\18\16\18\18\16\151\18\133\4\16\4\4\16\16\3\3\4\3\18\4\18\4\3\130\25\136\16\137\6\197\16\135\18\16\16\166\18\130\4\131\3\16\16\3\3\131\4\3\18\25\18\4\154\16\18\137\3\167\18\133\3\4\18\131\3\135\25\3\135\16\18\133\3\4\4\130\3\173\18\140\3\4\3\3\130\25\18\132\25\140\16\200\18\134\16\137\25\129\181\16\160\18\25\141\16\137\6\133\16\136\18\16\164\18\4\134\3\16\133\3\4\3\18\132\25\137\16\137\6\146\8\130\16\25\25\157\18\16\16\149\3\16\4\134\3\4\3\3\4\3\3\200\16\134\18\16\18\18\16\165\18\133\3\130\16\3\16\3\3\16\134\3\18\3\135\16\137\6\133\16\133\18\16\18\18\16\159\18\132\4\16\3\3\16\4\4\3\4\3\18\134\16\137\6\130\181\16\146\18\3\3\4\4\25\25\134\16\3\3\18\4\140\18\16\161\18\4\4\132\3\130\16\4\4\3\4\3\140\25\137\6\3\212\16\18\142\16\148\8\135\29\131\27\144\29\140\16\25\135\153\18\229\16\238\7\16\132\25\138\16\129\195\18\148\203\16\224\18\25\25\140\16\136\175\18\143\13\3\133\18\142\3\137\16\159\154\18\132\16\132\198\18\181\184\16\157\18\139\3\130\4\130\3\137\6\141\197\16\132\184\18\134\16\158\18\16\137\6\131\16\25\25\206\18\16\137\6\133\16\157\18\16\16\132\3\25\137\16\175\18\134\3\132\25\131\29\131\17\25\29\137\16\137\6\16\134\8\16\148\18\132\16\146\18\131\175\16\130\17\167\18\17\17\130\25\137\6\129\197\16\159\0\159\1\150\8\131\25\228\16\202\18\131\16\3\18\182\4\134\16\131\3\140\17\191\16\17\17\25\17\3\138\16\4\4\141\16\18\175\245\16\18\135\16\137\213\18\168\16\18\18\134\16\18\197\230\16\131\17\16\134\17\16\17\17\16\130\162\18\142\16\18\156\16\130\18\16\16\18\141\16\131\18\135\16\131\139\18\146\131\16\234\18\132\16\140\18\130\16\136\18\134\16\137\18\16\16\29\3\3\25\131\13\158\219\16\129\239\29\137\6\133\16\131\179\29\203\16\173\3\16\16\150\3\136\16\243\29\187\16\129\245\29\137\16\166\29\16\16\187\29\4\4\130\3\130\29\133\4\135\13\135\3\29\29\134\3\157\29\131\3\188\29\148\16\193\29\130\3\29\249\16\147\8\139\16\147\8\139\16\214\29\136\16\152\8\129\134\16\153\0\153\1\153\0\134\1\16\145\1\153\0\153\1\0\16\0\0\16\16\0\16\16\0\0\16\16\131\0\16\135\0\131\1\16\1\16\134\1\16\138\1\153\0\153\1\0\0\16\131\0\16\16\135\0\16\134\0\16\153\1\0\0\16\131\0\16\132\0\16\0\130\16\134\0\16\153\1\153\0\153\1\153\0\153\1\153\0\153\1\153\0\153\1\153\0\153\1\153\0\155\1\16\16\152\0\26\152\1\26\133\1\152\0\26\152\1\26\133\1\152\0\26\152\1\26\133\1\152\0\26\152\1\26\133\1\152\0\26\152\1\26\133\1\0\1\16\16\177\6\131\255\29\182\3\131\29\177\3\135\29\3\141\29\3\29\29\132\25\142\16\132\3\16\142\3\136\207\16\137\1\18\147\1\133\16\133\1\129\212\16\134\3\16\144\3\16\16\134\3\16\3\3\16\132\3\132\16\189\17\160\16\3\239\16\172\18\130\16\134\3\134\17\16\16\137\6\131\16\18\29\130\191\16\157\18\3\144\16\171\18\131\3\137\6\132\16\27\131\207\16\154\18\17\131\3\137\6\129\213\16\157\18\3\3\18\137\6\131\16\25\131\223\16\134\18\16\131\18\16\18\18\16\142\18\16\129\196\18\16\16\136\8\134\3\168\16\161\0\161\1\134\3\17\131\16\137\6\131\16\25\25\134\144\16\186\8\29\130\8\27\131\8\203\16\172\8\29\142\8\129\193\16\131\18\16\154\18\16\18\18\16\18\16\16\18\16\137\18\16\131\18\16\18\16\18\133\16\18\131\16\18\16\18\16\18\16\130\18\16\18\18\16\18\16\16\18\16\18\16\18\16\18\16\18\16\18\18\16\18\16\16\131\18\16\134\18\16\131\18\16\131\18\16\18\16\137\18\16\144\18\132\16\130\18\16\132\18\16\144\18\179\16\26\26\130\141\16\171\29\131\16\227\29\139\16\142\29\16\16\142\29\16\142\29\16\164\29\137\16\140\8\129\160\29\183\16\156\29\140\16\171\29\131\16\136\29\134\16\29\29\141\16\133\29\129\153\16\129\250\29\132\28\133\215\29\131\16\144\29\130\16\140\29\130\16\246\29\131\16\222\29\133\16\139\29\131\16\29\142\16\139\29\131\16\183\29\135\16\137\29\133\16\167\29\135\16\157\29\16\16\139\29\131\16\29\29\189\16\130\211\29\139\16\141\29\16\16\140\29\130\16\137\29\132\16\183\29\134\16\142\29\16\16\138\29\133\16\136\29\134\16\129\146\29\16\219\29\137\6\136\133\16\18\130\205\221\16\18\159\16\18\160\183\16\18\133\16\18\129\219\16\18\16\16\18\172\255\16\18\141\16\18\186\174\16\18\142\16\18\132\235\16\18\147\161\16\132\157\18\139\225\16\18\166\200\16\18\132\16\18\160\221\16\18\171\184\208\16\13\157\16\223\13\255\16\129\239\3\131\252\143\16\15\131\255\251\16\15\16\16\15\131\255\251\16\15" tcTable :: [(Int, Int, Int)] tcTable = [(97,25,63),(84,0,1486),(43,22,63),(24,6,63),(7,0,242),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,463),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(1,0,599),(1,0,390),(3,0,1),(2,0,1),(3,0,1),(4,0,1),(6,0,1),(3,0,194),(4,0,1),(1,0,326),(1,0,85122),(3,0,260),(3,0,1),(2,0,1),(2,0,1),(3,0,1),(5,0,1),(3,0,1),(4,0,1),(2,0,1),(3,0,1),(4,0,1),(2,0,112),(5,0,2),(1,0,0),(1,0,1),(1,0,2),(1,0,0),(1,0,1),(1,0,2),(1,0,0),(1,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,157),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,2),(1,0,0),(1,0,1),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(9,0,1),(3,1,21630),(3,0,1),(5,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,21566),(1,0,21560),(1,0,21564),(1,0,419),(1,0,411),(2,1,409),(3,0,403),(2,0,405),(1,0,84638),(4,0,409),(1,0,84630),(2,0,413),(1,0,84686),(1,0,84560),(1,0,84616),(2,0,417),(1,0,421),(1,0,84616),(1,0,21486),(1,0,84610),(3,0,421),(2,0,21498),(1,0,425),(3,0,427),(8,0,21454),(3,0,435),(2,0,84614),(1,0,435),(4,0,84564),(1,0,435),(1,0,137),(1,1,433),(2,0,141),(6,0,437),(11,0,84522),(1,0,84516),(167,0,168),(44,0,1),(2,0,1),(4,0,1),(4,2,260),(49,0,75),(1,2,73),(4,16,63),(17,0,61),(1,8,63),(9,0,127),(1,1,125),(3,0,123),(1,0,113),(4,0,93),(1,0,107),(1,0,15),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,171),(1,0,159),(1,0,14),(1,0,231),(2,0,191),(3,0,1),(3,0,1),(53,31,63),(32,15,159),(17,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(10,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,29),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(50,37,95),(2927,42,0),(45,2,0),(763,5,15),(2184,0,12507),(1,0,12505),(1,0,12487),(1,1,12483),(2,0,12485),(1,0,12471),(1,0,12361),(1,0,70532),(2,0,1),(239,0,70664),(4,0,7628),(17,0,70768),(115,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(6,0,117),(6,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,7,16),(16,5,16),(16,7,16),(16,7,16),(16,5,16),(17,0,16),(2,0,16),(2,0,16),(2,0,16),(9,7,16),(16,1,148),(2,3,172),(4,1,200),(2,1,256),(2,1,224),(2,1,252),(4,7,16),(16,7,16),(16,7,16),(16,1,16),(3,0,18),(11,0,14409),(5,0,18),(13,1,16),(16,1,16),(5,0,14),(14,0,18),(347,0,55),(34,15,31),(20,0,1),(844,25,51),(1888,47,95),(49,0,1),(4,0,21589),(1,0,21583),(2,0,1),(2,0,1),(2,0,1),(7,0,1),(3,0,1),(11,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(9,0,1),(2,0,1),(5,0,1),(13,37,14527),(39,0,14527),(6,0,14527),(30996,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(20,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(136,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(11,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(5,0,1),(5,0,1),(2,0,1),(1,0,96),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(12,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(5,0,1),(2,0,1),(3,0,1),(4,0,1),(6,0,1),(2,0,1),(2,0,1),(27,0,1),(861,0,1855),(29,79,77727),(21457,25,63),(1255,39,79),(176,35,79),(191,10,77),(12,14,77),(16,6,77),(8,1,77),(1797,50,127),(176,21,63),(2896,31,63),(21920,31,63),(31426,33,67)] ucTable :: [(Int, Int, Int)] ucTable = [(97,25,63),(84,0,1486),(43,22,63),(24,6,63),(7,0,242),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,463),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(1,0,599),(1,0,390),(3,0,1),(2,0,1),(3,0,1),(4,0,1),(6,0,1),(3,0,194),(4,0,1),(1,0,326),(1,0,85122),(3,0,260),(3,0,1),(2,0,1),(2,0,1),(3,0,1),(5,0,1),(3,0,1),(4,0,1),(2,0,1),(3,0,1),(4,0,1),(2,0,112),(6,0,1),(1,0,3),(2,0,1),(1,0,3),(2,0,1),(1,0,3),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,157),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(1,0,3),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(9,0,1),(3,1,21630),(3,0,1),(5,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,21566),(1,0,21560),(1,0,21564),(1,0,419),(1,0,411),(2,1,409),(3,0,403),(2,0,405),(1,0,84638),(4,0,409),(1,0,84630),(2,0,413),(1,0,84686),(1,0,84560),(1,0,84616),(2,0,417),(1,0,421),(1,0,84616),(1,0,21486),(1,0,84610),(3,0,421),(2,0,21498),(1,0,425),(3,0,427),(8,0,21454),(3,0,435),(2,0,84614),(1,0,435),(4,0,84564),(1,0,435),(1,0,137),(1,1,433),(2,0,141),(6,0,437),(11,0,84522),(1,0,84516),(167,0,168),(44,0,1),(2,0,1),(4,0,1),(4,2,260),(49,0,75),(1,2,73),(4,16,63),(17,0,61),(1,8,63),(9,0,127),(1,1,125),(3,0,123),(1,0,113),(4,0,93),(1,0,107),(1,0,15),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,171),(1,0,159),(1,0,14),(1,0,231),(2,0,191),(3,0,1),(3,0,1),(53,31,63),(32,15,159),(17,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(10,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,0,29),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(50,37,95),(2927,42,6016),(45,2,6016),(763,5,15),(2184,0,12507),(1,0,12505),(1,0,12487),(1,1,12483),(2,0,12485),(1,0,12471),(1,0,12361),(1,0,70532),(2,0,1),(239,0,70664),(4,0,7628),(17,0,70768),(115,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(6,0,117),(6,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(1,7,16),(16,5,16),(16,7,16),(16,7,16),(16,5,16),(17,0,16),(2,0,16),(2,0,16),(2,0,16),(9,7,16),(16,1,148),(2,3,172),(4,1,200),(2,1,256),(2,1,224),(2,1,252),(4,7,16),(16,7,16),(16,7,16),(16,1,16),(3,0,18),(11,0,14409),(5,0,18),(13,1,16),(16,1,16),(5,0,14),(14,0,18),(347,0,55),(34,15,31),(20,0,1),(844,25,51),(1888,47,95),(49,0,1),(4,0,21589),(1,0,21583),(2,0,1),(2,0,1),(2,0,1),(7,0,1),(3,0,1),(11,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(9,0,1),(2,0,1),(5,0,1),(13,37,14527),(39,0,14527),(6,0,14527),(30996,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(20,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(136,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(4,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(11,0,1),(2,0,1),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(5,0,1),(5,0,1),(2,0,1),(1,0,96),(3,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(12,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(2,0,1),(5,0,1),(2,0,1),(3,0,1),(4,0,1),(6,0,1),(2,0,1),(2,0,1),(27,0,1),(861,0,1855),(29,79,77727),(21457,25,63),(1255,39,79),(176,35,79),(191,10,77),(12,14,77),(16,6,77),(8,1,77),(1797,50,127),(176,21,63),(2896,31,63),(21920,31,63),(31426,33,67)] lcTable :: [(Int, Int, Int)] lcTable = [(65,25,64),(127,22,64),(24,6,64),(40,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,397),(2,0,2),(2,0,2),(2,0,2),(3,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(3,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,241),(1,0,2),(2,0,2),(2,0,2),(4,0,420),(1,0,2),(2,0,2),(2,0,412),(1,0,2),(2,1,410),(2,0,2),(3,0,158),(1,0,404),(1,0,406),(1,0,2),(2,0,410),(1,0,414),(2,0,422),(1,0,418),(1,0,2),(4,0,422),(1,0,426),(2,0,428),(1,0,2),(2,0,2),(2,0,2),(2,0,436),(1,0,2),(2,0,436),(3,0,2),(2,0,436),(1,0,2),(2,1,434),(2,0,2),(2,0,2),(2,0,438),(1,0,2),(4,0,2),(8,0,4),(1,0,2),(2,0,4),(1,0,2),(2,0,4),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(3,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(3,0,4),(1,0,2),(2,0,2),(2,0,193),(1,0,111),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,259),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(8,0,21590),(1,0,2),(2,0,325),(1,0,21584),(3,0,2),(2,0,389),(1,0,138),(1,0,142),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(290,0,2),(2,0,2),(4,0,2),(9,0,232),(7,0,76),(2,2,74),(4,0,128),(2,1,126),(3,16,64),(18,8,64),(44,0,16),(9,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(6,0,119),(3,0,2),(2,0,13),(1,0,2),(3,2,259),(3,15,160),(16,31,64),(80,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(10,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,30),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(3,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(3,37,96),(2927,37,14528),(39,0,14528),(6,0,14528),(723,79,77728),(80,5,16),(2201,0,2),(7,42,6015),(45,2,6015),(323,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(10,0,15229),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(10,7,15),(16,5,15),(16,7,15),(16,7,15),(16,5,15),(17,0,15),(2,0,15),(2,0,15),(2,0,15),(9,7,15),(32,7,15),(16,7,15),(16,7,15),(16,1,15),(2,1,147),(2,0,17),(12,3,171),(4,0,17),(12,1,15),(2,1,199),(14,1,15),(2,1,223),(2,0,13),(12,1,255),(2,1,251),(2,0,17),(298,0,15033),(4,0,16765),(1,0,16523),(7,0,56),(46,15,32),(35,0,2),(819,25,52),(1866,47,96),(96,0,2),(2,0,21485),(1,0,7627),(1,0,21453),(3,0,2),(2,0,2),(2,0,2),(2,0,21559),(1,0,21497),(1,0,21565),(1,0,21563),(2,0,2),(3,0,2),(9,1,21629),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(9,0,2),(2,0,2),(5,0,2),(31054,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(20,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(136,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(4,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(11,0,2),(2,0,2),(2,0,70663),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(5,0,2),(2,0,84559),(3,0,2),(2,0,2),(4,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,84615),(1,0,84637),(1,0,84629),(1,0,84609),(1,0,84615),(2,0,84515),(1,0,84563),(1,0,84521),(1,0,1856),(1,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,2),(2,0,95),(1,0,84613),(1,0,70767),(1,0,2),(2,0,2),(2,0,84685),(1,0,2),(4,0,2),(6,0,2),(2,0,2),(2,0,2),(2,0,85121),(25,0,2),(22316,25,64),(1247,39,80),(176,35,80),(192,10,78),(12,14,78),(16,6,78),(8,1,78),(1772,50,128),(208,21,64),(2896,31,64),(21920,31,64),(31424,33,68)]