never executed always true always false
1 {-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-missing-signatures #-}
2 {-# LANGUAGE CPP,MagicHash #-}
3 {-# LINE 43 "compiler/GHC/Parser/Lexer.x" #-}
4
5 {-# LANGUAGE BangPatterns #-}
6 {-# LANGUAGE DeriveDataTypeable #-}
7 {-# LANGUAGE LambdaCase #-}
8 {-# LANGUAGE MultiWayIf #-}
9 {-# LANGUAGE UnboxedTuples #-}
10 {-# LANGUAGE UnboxedSums #-}
11 {-# LANGUAGE UnliftedNewtypes #-}
12 {-# LANGUAGE PatternSynonyms #-}
13
14 {-# OPTIONS_GHC -funbox-strict-fields #-}
15 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
16
17 module GHC.Parser.Lexer (
18 Token(..), lexer, lexerDbg,
19 ParserOpts(..), mkParserOpts,
20 PState (..), initParserState, initPragState,
21 P(..), ParseResult(POk, PFailed),
22 allocateComments, allocatePriorComments, allocateFinalComments,
23 MonadP(..),
24 getRealSrcLoc, getPState,
25 failMsgP, failLocMsgP, srcParseFail,
26 getPsErrorMessages, getPsMessages,
27 popContext, pushModuleContext, setLastToken, setSrcLoc,
28 activeContext, nextIsEOF,
29 getLexState, popLexState, pushLexState,
30 ExtBits(..),
31 xtest, xunset, xset,
32 disableHaddock,
33 lexTokenStream,
34 mkParensEpAnn,
35 getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
36 getEofPos,
37 commentToAnnotation,
38 HdkComment(..),
39 warnopt,
40 addPsMessage
41 ) where
42
43 import GHC.Prelude
44 import qualified GHC.Data.Strict as Strict
45
46 -- base
47 import Control.Monad
48 import Control.Applicative
49 import Data.Char
50 import Data.List (stripPrefix, isInfixOf, partition)
51 import Data.Maybe
52 import Data.Word
53 import Debug.Trace (trace)
54
55 import GHC.Data.EnumSet as EnumSet
56
57 -- ghc-boot
58 import qualified GHC.LanguageExtensions as LangExt
59
60 -- bytestring
61 import Data.ByteString (ByteString)
62
63 -- containers
64 import Data.Map (Map)
65 import qualified Data.Map as Map
66
67 -- compiler
68 import GHC.Utils.Error
69 import GHC.Utils.Outputable
70 import GHC.Utils.Panic
71 import GHC.Data.StringBuffer
72 import GHC.Data.FastString
73 import GHC.Types.Error
74 import GHC.Types.Unique.FM
75 import GHC.Data.Maybe
76 import GHC.Data.OrdList
77 import GHC.Utils.Misc ( readSignificandExponentPair, readHexSignificandExponentPair )
78
79 import GHC.Types.SrcLoc
80 import GHC.Types.SourceText
81 import GHC.Types.Basic ( InlineSpec(..), RuleMatchInfo(..))
82 import GHC.Hs.Doc
83
84 import GHC.Parser.CharClass
85
86 import GHC.Parser.Annotation
87 import GHC.Driver.Flags
88 import GHC.Parser.Errors.Basic
89 import GHC.Parser.Errors.Types
90 import GHC.Parser.Errors.Ppr ()
91
92 #if __GLASGOW_HASKELL__ >= 603
93 #include "ghcconfig.h"
94 #elif defined(__GLASGOW_HASKELL__)
95 #include "config.h"
96 #endif
97 #if __GLASGOW_HASKELL__ >= 503
98 import Data.Array
99 #else
100 import Array
101 #endif
102 #if __GLASGOW_HASKELL__ >= 503
103 import Data.Array.Base (unsafeAt)
104 import GHC.Exts
105 #else
106 import GlaExts
107 #endif
108 alex_tab_size :: Int
109 alex_tab_size = 8
110 alex_base :: AlexAddr
111 alex_base = AlexA#
112 "\x01\x00\x00\x00\x7b\x00\x00\x00\x84\x00\x00\x00\xa0\x00\x00\x00\xbc\x00\x00\x00\xc5\x00\x00\x00\xce\x00\x00\x00\xec\x00\x00\x00\x06\x01\x00\x00\x22\x01\x00\x00\x3f\x01\x00\x00\x7b\x01\x00\x00\xd4\xff\xff\xff\x61\x00\x00\x00\xd7\xff\xff\xff\xa3\xff\xff\xff\xa4\xff\xff\xff\xf8\x01\x00\x00\x72\x02\x00\x00\xec\x02\x00\x00\x92\xff\xff\xff\x93\xff\xff\xff\x66\x03\x00\x00\x94\xff\xff\xff\xb1\xff\xff\xff\xf2\xff\xff\xff\xe7\xff\xff\xff\xe8\xff\xff\xff\xe9\xff\xff\xff\xd1\x00\x00\x00\xae\xff\xff\xff\xab\xff\xff\xff\xb0\xff\xff\xff\x59\x01\x00\x00\xdc\x03\x00\x00\xfc\x01\x00\x00\xe6\x03\x00\x00\xb3\xff\xff\xff\xba\xff\xff\xff\xaa\xff\xff\xff\x3d\x01\x00\x00\x7a\x01\x00\x00\x50\x02\x00\x00\xca\x02\x00\x00\x1f\x04\x00\x00\xfa\x03\x00\x00\x59\x04\x00\x00\x95\x01\x00\x00\x05\x02\x00\x00\xaf\xff\xff\xff\xb2\xff\xff\xff\xa4\x04\x00\x00\xe5\x04\x00\x00\x63\x02\x00\x00\x44\x03\x00\x00\xdd\x02\x00\x00\xfc\x04\x00\x00\x3d\x05\x00\x00\x57\x03\x00\x00\xc5\x04\x00\x00\x1d\x05\x00\x00\x59\x05\x00\x00\x63\x05\x00\x00\x79\x05\x00\x00\x83\x05\x00\x00\x99\x05\x00\x00\xa9\x05\x00\x00\xb3\x05\x00\x00\xbd\x05\x00\x00\xc9\x05\x00\x00\xd3\x05\x00\x00\xed\x05\x00\x00\x04\x06\x00\x00\x63\x00\x00\x00\x51\x00\x00\x00\x26\x06\x00\x00\x4b\x06\x00\x00\x62\x06\x00\x00\xc4\x03\x00\x00\x6c\x00\x00\x00\x84\x06\x00\x00\xbd\x06\x00\x00\x17\x07\x00\x00\x95\x07\x00\x00\x11\x08\x00\x00\x8d\x08\x00\x00\x09\x09\x00\x00\x85\x09\x00\x00\x01\x0a\x00\x00\xb9\x00\x00\x00\x7d\x0a\x00\x00\xfb\x0a\x00\x00\x14\x00\x00\x00\x15\x00\x00\x00\x79\x00\x00\x00\x2d\x01\x00\x00\x5e\x01\x00\x00\x16\x02\x00\x00\x00\x00\x00\x00\x80\x00\x00\x00\xfa\x01\x00\x00\xe0\x03\x00\x00\x94\x07\x00\x00\x9c\x00\x00\x00\x81\x00\x00\x00\x82\x00\x00\x00\x88\x00\x00\x00\x95\x00\x00\x00\x96\x00\x00\x00\x97\x00\x00\x00\x76\x0b\x00\x00\x9e\x0b\x00\x00\xe1\x0b\x00\x00\x09\x0c\x00\x00\x4c\x0c\x00\x00\x74\x0c\x00\x00\xe7\x04\x00\x00\x10\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x75\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x0c\x00\x00\x2e\x0d\x00\x00\xa8\x0d\x00\x00\x22\x0e\x00\x00\x9c\x0e\x00\x00\xa8\x00\x00\x00\xa9\x00\x00\x00\x1a\x0f\x00\x00\x9d\x00\x00\x00\x94\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x10\x00\x00\x00\x00\x00\x00\x8c\x10\x00\x00\x06\x11\x00\x00\x00\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80\x11\x00\x00\xfa\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9f\x00\x00\x00\xa7\x00\x00\x00\x00\x00\x00\x00\xb0\x12\x00\x00\x2a\x13\x00\x00\xa4\x13\x00\x00\x1e\x14\x00\x00\x98\x14\x00\x00\x12\x15\x00\x00\x8c\x15\x00\x00\x06\x16\x00\x00\x80\x16\x00\x00\xfa\x16\x00\x00\x74\x17\x00\x00\xee\x17\x00\x00\x68\x18\x00\x00\xe2\x18\x00\x00\x5c\x19\x00\x00\xd6\x19\x00\x00\x50\x1a\x00\x00\xca\x1a\x00\x00\x44\x1b\x00\x00\xbe\x1b\x00\x00\x38\x1c\x00\x00\xb2\x1c\x00\x00\x2c\x1d\x00\x00\xa6\x1d\x00\x00\xa1\x00\x00\x00\xbd\x00\x00\x00\xbe\x00\x00\x00\xbf\x00\x00\x00\xc1\x00\x00\x00\xc3\x00\x00\x00\x00\x1e\x00\x00\x28\x1e\x00\x00\x4b\x1e\x00\x00\x73\x1e\x00\x00\xb6\x1e\x00\x00\xdb\x1e\x00\x00\x54\x1f\x00\x00\xb0\x1f\x00\x00\xd3\x1f\x00\x00\xf6\x1f\x00\x00\x58\x0b\x00\x00\x14\x20\x00\x00\xdd\x00\x00\x00\xbb\x06\x00\x00\x5d\x20\x00\x00\x37\x1f\x00\x00\x82\x20\x00\x00\x6e\x02\x00\x00\x71\x07\x00\x00\xcb\x20\x00\x00\xef\x20\x00\x00\xf2\x07\x00\x00\x10\x21\x00\x00\x6e\x08\x00\x00\x26\x21\x00\x00\xe4\x08\x00\x00\x67\x21\x00\x00\x60\x09\x00\x00\xc4\x00\x00\x00\xc7\x00\x00\x00\xc8\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xca\x00\x00\x00\x00\x00\x00\x00\xcc\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
113
114 alex_table :: AlexAddr
115 alex_table = AlexA#
116 "\x00\x00\x66\x00\xc7\x00\xc0\x00\x6f\x00\xd3\x00\x60\x00\x9e\x00\x77\x00\x7e\x00\x62\x00\x81\x00\x60\x00\x60\x00\x60\x00\x8c\x00\x8d\x00\x8f\x00\x5e\x00\x5c\x00\x14\x00\x15\x00\x17\x00\x32\x00\x18\x00\x31\x00\x1f\x00\x25\x00\x26\x00\x10\x00\x7b\x00\x7a\x00\x0f\x00\x60\x00\xd3\x00\xfc\x00\xd4\x00\xd3\x00\xd3\x00\xd3\x00\xfb\x00\xa6\x00\xa7\x00\xd3\x00\xd3\x00\xab\x00\xcf\x00\xd3\x00\xd3\x00\xda\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd8\x00\xac\x00\xd3\x00\xd3\x00\xd3\x00\xd5\x00\xd3\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xa9\x00\xd3\x00\xaa\x00\xd3\x00\xc1\x00\xad\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xaf\x00\xd1\x00\xb0\x00\xd3\x00\x60\x00\xe0\x00\xe0\x00\x79\x00\x62\x00\x76\x00\x60\x00\x60\x00\x60\x00\x60\x00\xff\xff\xff\xff\xff\xff\x62\x00\x6f\x00\x60\x00\x60\x00\x60\x00\xff\xff\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\x5f\x00\xdb\x00\xdb\x00\x78\x00\xff\xff\xff\xff\xff\xff\x66\x00\x20\x00\x60\x00\x60\x00\xff\xff\xff\xff\x0e\x00\x62\x00\x7d\x00\x60\x00\x60\x00\x60\x00\x94\x00\x5d\x00\x4a\x00\x0e\x00\xff\xff\xff\xff\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x98\x00\x89\x00\x60\x00\x60\x00\x49\x00\x7f\x00\xc9\x00\x62\x00\x7d\x00\x60\x00\x60\x00\x60\x00\x60\x00\x4f\x00\x64\x00\x0e\x00\x62\x00\x7d\x00\x60\x00\x60\x00\x60\x00\x60\x00\x65\x00\x67\x00\x71\x00\x62\x00\xa3\x00\x60\x00\x60\x00\x60\x00\x60\x00\x92\x00\x8c\x00\x7f\x00\xca\x00\xcb\x00\xcd\x00\x92\x00\xcb\x00\x60\x00\xce\x00\xf3\x00\x7f\x00\x0e\x00\xf4\x00\xf5\x00\xf6\x00\xf8\x00\x60\x00\xfa\x00\x00\x00\x60\x00\x0e\x00\x00\x00\x00\x00\x62\x00\x0c\x00\x60\x00\x60\x00\x60\x00\x1e\x00\x0e\x00\x00\x00\x00\x00\x27\x00\x0c\x00\xec\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x61\x00\x60\x00\xdb\x00\xdb\x00\x63\x00\xff\xff\x61\x00\x61\x00\x61\x00\x00\x00\x00\x00\x3d\x00\x92\x00\x00\x00\x0e\x00\x00\x00\x7c\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x61\x00\x60\x00\x00\x00\x00\x00\x00\x00\x62\x00\x00\x00\x60\x00\x60\x00\x60\x00\x1d\x00\x9f\x00\x60\x00\x88\x00\x00\x00\x92\x00\x3d\x00\x7c\x00\x60\x00\x60\x00\x60\x00\x00\x00\x4f\x00\x00\x00\x00\x00\x00\x00\x7c\x00\x80\x00\x60\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x62\x00\x0c\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x0e\x00\x19\x00\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x00\x00\x00\x00\x30\x00\x60\x00\x00\x00\x00\x00\x1a\x00\x60\x00\x30\x00\x30\x00\x30\x00\x0c\x00\x00\x00\x60\x00\x60\x00\x60\x00\x0d\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\xc8\x00\xc6\x00\x60\x00\x00\x00\x60\x00\x87\x00\x00\x00\x00\x00\x62\x00\x81\x00\x60\x00\x60\x00\x60\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2f\x00\x60\x00\x28\x00\x0c\x00\x1c\x00\x00\x00\x2f\x00\x2f\x00\x2f\x00\xa5\x00\xa7\x00\x00\x00\x00\x00\xab\x00\x0e\x00\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x00\x00\x2f\x00\xac\x00\x5a\x00\x2a\x00\x00\x00\x0c\x00\x00\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xa8\x00\x00\x00\xaa\x00\x29\x00\xc6\x00\xad\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xae\x00\x00\x00\xb0\x00\x82\x00\x82\x00\x82\x00\x00\x00\x11\x00\x00\x00\x82\x00\x00\x00\x23\x00\x11\x00\x11\x00\x11\x00\x11\x00\x23\x00\x23\x00\x23\x00\x23\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x30\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x59\x00\x61\x00\x23\x00\x90\x00\x92\x00\x1b\x00\xff\xff\x61\x00\x61\x00\x61\x00\x92\x00\x30\x00\x00\x00\x5b\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x00\x00\x00\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x00\x92\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x84\x00\x84\x00\x84\x00\x92\x00\x12\x00\x00\x00\x84\x00\x00\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x00\x00\x00\x37\x00\xf0\x00\x12\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\x00\x00\xe0\x00\xe0\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x4a\x00\x00\x00\x00\x00\x00\x00\x84\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x85\x00\x85\x00\x85\x00\x00\x00\x13\x00\x00\x00\x85\x00\x00\x00\x00\x00\x13\x00\x13\x00\x13\x00\x13\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x2b\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x16\x00\x00\x00\x8e\x00\x00\x00\x00\x00\x16\x00\x16\x00\x16\x00\x16\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3c\x00\x00\x00\x16\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x36\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x2f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2f\x00\x2f\x00\x2f\x00\x00\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\x2f\x00\x00\x00\x00\x00\x00\x00\x59\x00\x00\x00\x00\x00\x91\x00\x92\x00\x00\x00\x23\x00\x00\x00\x00\x00\x1b\x00\x92\x00\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x24\x00\x2c\x00\x2c\x00\x2c\x00\x4e\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x41\x00\x00\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x00\x00\x00\x00\x00\x92\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2e\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x1d\x00\x2c\x00\x53\x00\x92\x00\x00\x00\x00\x00\x3d\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x00\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x35\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x6c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6c\x00\x00\x00\x00\x00\x35\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3b\x00\x00\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x6c\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x3a\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x6c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x40\x00\x00\x00\x40\x00\x00\x00\x00\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\x00\x00\x45\x00\x00\x00\x45\x00\x00\x00\x3f\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\x00\x00\x42\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x44\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x00\x00\x47\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x35\x00\x00\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\x00\x00\x00\x00\x00\x00\x48\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x00\x00\x4c\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x3a\x00\x00\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xbe\x00\xba\x00\x00\x00\x4d\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xed\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\xdc\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbd\x00\xb9\x00\x4e\x00\xd6\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xb6\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xbc\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb5\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xbb\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\xd6\x00\xf1\x00\xd6\x00\x53\x00\x53\x00\x53\x00\x00\x00\x00\x00\x00\x00\x53\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\xe1\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x59\x00\x00\x00\x00\x00\x11\x00\x92\x00\x00\x00\x00\x00\x00\x00\x53\x00\x00\x00\x92\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x00\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x00\x00\x00\x00\x92\x00\x00\x00\x53\x00\x00\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x53\x00\x92\x00\x9d\x00\x54\x00\x54\x00\x54\x00\xf7\x00\x00\x00\x00\x00\x54\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\xe4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x6b\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x6b\x00\x9c\x00\x54\x00\x54\x00\x54\x00\xf9\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\xe6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x9b\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\xe8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x9a\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\xea\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x36\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x99\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x97\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x00\x00\x5a\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x00\x5a\x00\x8b\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x00\x00\x5b\x00\x5b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5b\x00\x86\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\xff\xff\xeb\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x00\x00\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\x42\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\x6e\x00\xff\xff\xff\xff\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x74\x00\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\x00\x00\x6e\x00\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x8a\x00\x8a\x00\x70\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x8a\x00\xff\xff\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x75\x00\x8a\x00\x00\x00\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x8a\x00\x00\x00\x70\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\x00\x00\x8a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x72\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8a\x00\xd3\x00\x8a\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x74\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\x00\x00\x72\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x82\x00\x82\x00\x82\x00\x00\x00\x00\x00\x00\x00\x82\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x00\x00\x00\x00\x00\x00\x00\x00\x82\x00\x00\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x82\x00\x83\x00\x83\x00\x83\x00\x00\x00\x00\x00\x00\x00\x83\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x84\x00\x84\x00\x84\x00\x00\x00\x16\x00\x00\x00\x84\x00\x00\x00\x00\x00\x16\x00\x16\x00\x16\x00\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x85\x00\x85\x00\x85\x00\x00\x00\x16\x00\x00\x00\x85\x00\x00\x00\x00\x00\x16\x00\x16\x00\x16\x00\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x00\x00\x5b\x00\x5b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x00\x5b\x00\x86\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x5b\x00\x83\x00\x83\x00\x83\x00\x00\x00\x89\x00\x00\x00\x83\x00\x00\x00\x00\x00\x11\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x00\x00\x00\x00\x00\x00\x00\x00\x83\x00\x00\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x83\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x00\x00\x5a\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x00\x5a\x00\x8b\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x5a\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8e\x00\x00\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x8e\x00\x84\x00\x84\x00\x84\x00\x00\x00\x12\x00\x00\x00\x84\x00\x00\x00\x00\x00\x12\x00\x12\x00\x12\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x84\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x84\x00\x85\x00\x85\x00\x85\x00\x00\x00\x13\x00\x00\x00\x85\x00\x00\x00\x00\x00\x13\x00\x13\x00\x13\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x85\x00\x00\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\x85\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\x00\x00\x00\x00\xa1\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x00\x00\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa2\x00\xa2\x00\xa2\x00\x00\x00\x00\x00\x00\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\x00\x00\x2c\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x00\x00\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x54\x00\x00\x00\x54\x00\x54\x00\x54\x00\x56\x00\x58\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x57\x00\x54\x00\x54\x00\x54\x00\x55\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x54\x00\x00\x00\x93\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb1\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb2\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb3\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb4\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x00\x00\x00\xb9\x00\xb9\x00\xb9\x00\xb7\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xb9\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x00\x00\x00\xba\x00\xba\x00\xba\x00\xb8\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xba\x00\xbd\x00\xbd\x00\xbd\x00\x00\x00\x00\x00\x00\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xca\x00\x00\x00\x00\x00\x00\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x00\x00\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbd\x00\xbe\x00\xbe\x00\xbe\x00\x00\x00\x00\x00\x00\x00\xbe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x00\x00\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xbe\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc3\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc3\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc1\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x00\x00\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\xc2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc3\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc3\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x45\x00\x00\x00\x45\x00\x00\x00\x00\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc4\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcc\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\xc5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc4\x00\x00\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc0\x00\xc6\x00\xc6\x00\xc6\x00\x00\x00\x00\x00\x00\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc6\x00\x00\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc6\x00\xc7\x00\xc7\x00\xc7\x00\x00\x00\x00\x00\x00\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x00\x00\x00\x00\x00\x00\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\x00\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc7\x00\xc8\x00\xc8\x00\xc8\x00\x00\x00\x00\x00\x00\x00\xc8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xc8\x00\x00\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xc8\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x73\x00\xd3\x00\xd3\x00\xdf\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x2b\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\xa0\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\x8f\x00\xd3\x00\xd3\x00\x95\x00\xd3\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd2\x00\x00\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x96\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xa2\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\xa4\x00\xd3\x00\xd3\x00\x00\x00\xd0\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xa2\x00\x00\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa2\x00\xa1\x00\xd3\x00\xd3\x00\xd3\x00\xef\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x41\x00\x00\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x3d\x00\x00\x00\xd3\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\xd3\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd3\x00\x00\x00\xd3\x00\xa1\x00\xd6\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\xd3\x00\xd6\x00\xd3\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd7\x00\x00\x00\x00\x00\xd6\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x00\x00\xd7\x00\xd7\x00\xd7\x00\xd7\x00\xd8\x00\x00\x00\x00\x00\xd7\x00\xd7\x00\x00\x00\xd7\x00\xd7\x00\xd7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\xd7\x00\xd6\x00\xd7\x00\xd7\x00\xd7\x00\xd7\x00\xd7\x00\x00\x00\x00\x00\x00\x00\xd8\x00\x00\x00\xd8\x00\xd8\x00\xd8\x00\xd8\x00\x00\x00\x00\x00\x00\x00\xd8\x00\xd8\x00\x00\x00\xd8\x00\xd8\x00\xd8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xd6\x00\xd7\x00\xd8\x00\xd7\x00\xd8\x00\xd8\x00\xd8\x00\xd8\x00\xd8\x00\xeb\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x46\x00\x00\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\xd9\x00\x00\x00\xd7\x00\x00\x00\xd7\x00\xd8\x00\x00\x00\xd8\x00\x00\x00\x4f\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd8\x00\x50\x00\xd8\x00\x00\x00\x4f\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xee\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x39\x00\x4c\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x00\x00\xef\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x41\x00\x00\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\xde\x00\x4d\x00\x00\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\xdd\x00\x4a\x00\x00\x00\x00\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x47\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x4a\x00\x00\x00\x00\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf2\x00\x00\x00\x00\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x00\x47\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xf7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x00\x00\x00\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\xe3\x00\x00\x00\x48\x00\x00\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\xe2\x00\x00\x00\xf9\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\xe5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x3d\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x00\x00\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\xe7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x33\x00\x00\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
117
118 alex_check :: AlexAddr
119 alex_check = AlexA#
120 "\xff\xff\x2d\x00\x01\x00\x02\x00\x2d\x00\x04\x00\x05\x00\x06\x00\x65\x00\x65\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x7d\x00\x7d\x00\x7d\x00\x61\x00\x21\x00\x2d\x00\x2d\x00\x2d\x00\x69\x00\x6d\x00\x69\x00\x67\x00\x61\x00\x72\x00\x6e\x00\x0a\x00\x0a\x00\x6e\x00\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x05\x00\x30\x00\x31\x00\x0a\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x0a\x00\x0a\x00\x0a\x00\x09\x00\x2d\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x20\x00\x30\x00\x31\x00\x23\x00\x0a\x00\x0a\x00\x0a\x00\x2d\x00\x6c\x00\x20\x00\x05\x00\x0a\x00\x0a\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x7c\x00\x21\x00\x5f\x00\x2d\x00\x0a\x00\x0a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x7c\x00\x23\x00\x20\x00\x05\x00\x5f\x00\x23\x00\x23\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x5f\x00\x2d\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x2d\x00\x2d\x00\x2d\x00\x09\x00\x23\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\x24\x00\x7d\x00\x23\x00\x23\x00\x23\x00\x23\x00\x2a\x00\x23\x00\x20\x00\x23\x00\x23\x00\x23\x00\x2d\x00\x23\x00\x23\x00\x23\x00\x23\x00\x20\x00\x23\x00\xff\xff\x05\x00\x2d\x00\xff\xff\xff\xff\x09\x00\x7b\x00\x0b\x00\x0c\x00\x0d\x00\x6c\x00\x2d\x00\xff\xff\xff\xff\x70\x00\x7b\x00\x23\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x05\x00\x20\x00\x30\x00\x31\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\x45\x00\x5e\x00\xff\xff\x2d\x00\xff\xff\x7b\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x20\x00\x05\x00\xff\xff\xff\xff\xff\xff\x09\x00\xff\xff\x0b\x00\x0c\x00\x0d\x00\x5f\x00\x7c\x00\x05\x00\x2d\x00\xff\xff\x7c\x00\x65\x00\x7b\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x7b\x00\x7c\x00\x20\x00\xff\xff\x05\x00\xff\xff\xff\xff\xff\xff\x09\x00\x7b\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\xff\xff\x2d\x00\x23\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x05\x00\x20\x00\xff\xff\xff\xff\x23\x00\x05\x00\x0b\x00\x0c\x00\x0d\x00\x7b\x00\xff\xff\x0b\x00\x0c\x00\x0d\x00\x2d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\x01\x00\x02\x00\x20\x00\xff\xff\x05\x00\x7b\x00\xff\xff\xff\xff\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x05\x00\x20\x00\x5f\x00\x7b\x00\x23\x00\xff\xff\x0b\x00\x0c\x00\x0d\x00\x28\x00\x29\x00\xff\xff\xff\xff\x2c\x00\x2d\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x20\x00\x3b\x00\x22\x00\x5f\x00\xff\xff\x7b\x00\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\xff\xff\x5d\x00\x5f\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\xff\xff\x7d\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\x05\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x20\x00\x05\x00\x20\x00\x23\x00\x24\x00\x23\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x2a\x00\x20\x00\xff\xff\x22\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x5e\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x7c\x00\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x2b\x00\xff\xff\x2d\x00\x23\x00\x20\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x30\x00\x31\x00\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5f\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x2b\x00\xff\xff\x2d\x00\xff\xff\x20\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0b\x00\x0c\x00\x0d\x00\xff\xff\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x20\x00\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\x23\x00\x24\x00\xff\xff\x20\x00\xff\xff\xff\xff\x23\x00\x2a\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x01\x00\x02\x00\x03\x00\x5f\x00\xff\xff\xff\xff\x07\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\x5e\x00\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\x01\x00\x02\x00\x7c\x00\xff\xff\xff\xff\x65\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\x50\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2a\x00\xff\xff\xff\xff\x70\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\x5e\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x50\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x7c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\x45\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x2b\x00\xff\xff\x2d\x00\xff\xff\x5f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x45\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\x5f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x50\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x50\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x01\x00\x02\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x01\x00\x02\x00\x5f\x00\x04\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x23\x00\x7e\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\x23\x00\x24\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\x5e\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7c\x00\x7c\x00\x01\x00\x02\x00\x03\x00\x23\x00\xff\xff\xff\xff\x07\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x24\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\x2a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\x5e\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7c\x00\x7c\x00\x01\x00\x02\x00\x03\x00\x23\x00\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x04\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x45\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\x3a\x00\x7e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\x3a\x00\x7e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x01\x00\x02\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\x2b\x00\xff\xff\x2d\x00\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\x04\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\x29\x00\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x3a\x00\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\x7c\x00\x7d\x00\x7e\x00\x5c\x00\x5d\x00\x5e\x00\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x5d\x00\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x02\x00\xff\xff\x04\x00\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\x3a\x00\x7e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\x29\x00\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x02\x00\x7c\x00\x04\x00\x7e\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\x45\x00\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\x04\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\xff\xff\x7c\x00\x21\x00\x7e\x00\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x3a\x00\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\x3a\x00\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\xff\xff\x42\x00\xff\xff\xff\xff\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\x5f\x00\x7e\x00\xff\xff\x62\x00\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\x6f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\x78\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x42\x00\xff\xff\xff\xff\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\x4f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\x62\x00\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\x6f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\x78\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\x23\x00\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x45\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x50\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
121
122 alex_deflt :: AlexAddr
123 alex_deflt = AlexA#
124 "\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x8a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x5d\x00\x5e\x00\xff\xff\xff\xff\x8a\x00\xff\xff\x8a\x00\xff\xff\xff\xff\xff\xff\x8a\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6a\x00\x6d\x00\x6d\x00\x69\x00\x6d\x00\x69\x00\x6d\x00\x69\x00\x68\x00\x68\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x8a\x00\xff\xff\xff\xff\xff\xff\x8a\x00\x8a\x00\x8a\x00\x8a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
125
126 alex_accept = listArray (0 :: Int, 252)
127 [ AlexAccNone
128 , AlexAcc 209
129 , AlexAccNone
130 , AlexAcc 208
131 , AlexAcc 207
132 , AlexAcc 206
133 , AlexAcc 205
134 , AlexAcc 204
135 , AlexAcc 203
136 , AlexAccNone
137 , AlexAccNone
138 , AlexAccNone
139 , AlexAccNone
140 , AlexAccNone
141 , AlexAccNone
142 , AlexAccNone
143 , AlexAccNone
144 , AlexAccNone
145 , AlexAccNone
146 , AlexAccNone
147 , AlexAccNone
148 , AlexAccNone
149 , AlexAccNone
150 , AlexAccNone
151 , AlexAccNone
152 , AlexAccNone
153 , AlexAccNone
154 , AlexAccNone
155 , AlexAccNone
156 , AlexAccNone
157 , AlexAccNone
158 , AlexAccNone
159 , AlexAccNone
160 , AlexAccNone
161 , AlexAccNone
162 , AlexAccNone
163 , AlexAccNone
164 , AlexAccNone
165 , AlexAccNone
166 , AlexAccNone
167 , AlexAccNone
168 , AlexAccNone
169 , AlexAccNone
170 , AlexAccNone
171 , AlexAccNone
172 , AlexAccNone
173 , AlexAccNone
174 , AlexAccNone
175 , AlexAccNone
176 , AlexAccNone
177 , AlexAccNone
178 , AlexAccNone
179 , AlexAccNone
180 , AlexAccNone
181 , AlexAccNone
182 , AlexAccNone
183 , AlexAccNone
184 , AlexAccNone
185 , AlexAccNone
186 , AlexAccNone
187 , AlexAccNone
188 , AlexAccNone
189 , AlexAccNone
190 , AlexAccNone
191 , AlexAccNone
192 , AlexAccNone
193 , AlexAccNone
194 , AlexAccNone
195 , AlexAccNone
196 , AlexAccNone
197 , AlexAccNone
198 , AlexAccNone
199 , AlexAccNone
200 , AlexAccNone
201 , AlexAccNone
202 , AlexAccNone
203 , AlexAccNone
204 , AlexAccNone
205 , AlexAccNone
206 , AlexAccNone
207 , AlexAccNone
208 , AlexAccNone
209 , AlexAccNone
210 , AlexAccNone
211 , AlexAccNone
212 , AlexAccNone
213 , AlexAccNone
214 , AlexAccNone
215 , AlexAccNone
216 , AlexAccNone
217 , AlexAccNone
218 , AlexAccNone
219 , AlexAccNone
220 , AlexAccNone
221 , AlexAccNone
222 , AlexAccSkip
223 , AlexAccSkip
224 , AlexAccSkip
225 , AlexAcc 202
226 , AlexAcc 201
227 , AlexAccPred 200 ( isNormalComment )(AlexAccNone)
228 , AlexAccPred 199 ( isNormalComment )(AlexAccNone)
229 , AlexAccPred 198 ( isNormalComment )(AlexAccNone)
230 , AlexAccPred 197 ( isNormalComment )(AlexAcc 196)
231 , AlexAcc 195
232 , AlexAcc 194
233 , AlexAccPred 193 ( alexNotPred (ifExtension HaddockBit) )(AlexAccNone)
234 , AlexAccPred 192 ( alexNotPred (ifExtension HaddockBit) )(AlexAcc 191)
235 , AlexAccPred 190 ( alexNotPred (ifExtension HaddockBit) )(AlexAccPred 189 ( ifExtension HaddockBit )(AlexAccNone))
236 , AlexAcc 188
237 , AlexAccPred 187 ( atEOL )(AlexAccNone)
238 , AlexAccPred 186 ( atEOL )(AlexAccNone)
239 , AlexAccPred 185 ( atEOL )(AlexAcc 184)
240 , AlexAccPred 183 ( atEOL )(AlexAcc 182)
241 , AlexAccPred 181 ( atEOL )(AlexAccPred 180 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 179 ( followedByOpeningToken )(AlexAccPred 178 ( precededByClosingToken )(AlexAcc 177))))
242 , AlexAccPred 176 ( atEOL )(AlexAccPred 175 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 174 ( followedByOpeningToken )(AlexAccPred 173 ( precededByClosingToken )(AlexAcc 172))))
243 , AlexAccPred 171 ( atEOL )(AlexAccNone)
244 , AlexAccPred 170 ( atEOL )(AlexAcc 169)
245 , AlexAccSkip
246 , AlexAccPred 168 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
247 , AlexAccPred 167 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False) `alexAndPred` followedByDigit )(AlexAccNone)
248 , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
249 , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
250 , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
251 , AlexAccPred 166 ( notFollowedBy '-' )(AlexAccNone)
252 , AlexAccSkip
253 , AlexAccPred 165 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
254 , AlexAccPred 164 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
255 , AlexAccPred 163 ( notFollowedBySymbol )(AlexAccNone)
256 , AlexAcc 162
257 , AlexAccPred 161 ( known_pragma linePrags )(AlexAccNone)
258 , AlexAccPred 160 ( known_pragma linePrags )(AlexAcc 159)
259 , AlexAccPred 158 ( known_pragma linePrags )(AlexAccPred 157 ( known_pragma oneWordPrags )(AlexAccPred 156 ( known_pragma ignoredPrags )(AlexAccPred 155 ( known_pragma fileHeaderPrags )(AlexAccNone))))
260 , AlexAccPred 154 ( known_pragma linePrags )(AlexAccPred 153 ( known_pragma oneWordPrags )(AlexAccPred 152 ( known_pragma ignoredPrags )(AlexAccPred 151 ( known_pragma fileHeaderPrags )(AlexAccNone))))
261 , AlexAcc 150
262 , AlexAcc 149
263 , AlexAcc 148
264 , AlexAcc 147
265 , AlexAcc 146
266 , AlexAcc 145
267 , AlexAcc 144
268 , AlexAcc 143
269 , AlexAccPred 142 ( known_pragma twoWordPrags )(AlexAccNone)
270 , AlexAcc 141
271 , AlexAcc 140
272 , AlexAcc 139
273 , AlexAccPred 138 ( ifExtension HaddockBit )(AlexAccNone)
274 , AlexAcc 137
275 , AlexAcc 136
276 , AlexAcc 135
277 , AlexAcc 134
278 , AlexAccPred 133 ( ifExtension ThQuotesBit )(AlexAccPred 132 ( ifExtension QqBit )(AlexAccNone))
279 , AlexAccPred 131 ( ifExtension ThQuotesBit )(AlexAccNone)
280 , AlexAccPred 130 ( ifExtension ThQuotesBit )(AlexAccPred 129 ( ifExtension QqBit )(AlexAccNone))
281 , AlexAccPred 128 ( ifExtension ThQuotesBit )(AlexAccPred 127 ( ifExtension QqBit )(AlexAccNone))
282 , AlexAccPred 126 ( ifExtension ThQuotesBit )(AlexAccPred 125 ( ifExtension QqBit )(AlexAccNone))
283 , AlexAccPred 124 ( ifExtension QqBit )(AlexAccNone)
284 , AlexAccPred 123 ( ifExtension QqBit )(AlexAccNone)
285 , AlexAccPred 122 ( ifCurrentChar '⟦' `alexAndPred`
286 ifExtension UnicodeSyntaxBit `alexAndPred`
287 ifExtension ThQuotesBit )(AlexAccPred 121 ( ifCurrentChar '⟧' `alexAndPred`
288 ifExtension UnicodeSyntaxBit `alexAndPred`
289 ifExtension ThQuotesBit )(AlexAccPred 120 ( ifCurrentChar '⦇' `alexAndPred`
290 ifExtension UnicodeSyntaxBit `alexAndPred`
291 ifExtension ArrowsBit )(AlexAccPred 119 ( ifCurrentChar '⦈' `alexAndPred`
292 ifExtension UnicodeSyntaxBit `alexAndPred`
293 ifExtension ArrowsBit )(AlexAccNone))))
294 , AlexAccPred 118 ( ifExtension ArrowsBit `alexAndPred`
295 notFollowedBySymbol )(AlexAccNone)
296 , AlexAccPred 117 ( ifExtension ArrowsBit )(AlexAccNone)
297 , AlexAccPred 116 ( ifExtension IpBit )(AlexAccNone)
298 , AlexAccPred 115 ( ifExtension OverloadedLabelsBit )(AlexAccNone)
299 , AlexAccPred 114 ( ifExtension UnboxedTuplesBit `alexOrPred`
300 ifExtension UnboxedSumsBit )(AlexAccNone)
301 , AlexAccPred 113 ( ifExtension UnboxedTuplesBit `alexOrPred`
302 ifExtension UnboxedSumsBit )(AlexAccNone)
303 , AlexAcc 112
304 , AlexAcc 111
305 , AlexAcc 110
306 , AlexAcc 109
307 , AlexAcc 108
308 , AlexAcc 107
309 , AlexAcc 106
310 , AlexAcc 105
311 , AlexAcc 104
312 , AlexAcc 103
313 , AlexAcc 102
314 , AlexAcc 101
315 , AlexAcc 100
316 , AlexAcc 99
317 , AlexAccPred 98 ( ifExtension RecursiveDoBit )(AlexAcc 97)
318 , AlexAccPred 96 ( ifExtension RecursiveDoBit )(AlexAcc 95)
319 , AlexAcc 94
320 , AlexAcc 93
321 , AlexAcc 92
322 , AlexAcc 91
323 , AlexAcc 90
324 , AlexAcc 89
325 , AlexAcc 88
326 , AlexAcc 87
327 , AlexAcc 86
328 , AlexAcc 85
329 , AlexAcc 84
330 , AlexAcc 83
331 , AlexAcc 82
332 , AlexAcc 81
333 , AlexAcc 80
334 , AlexAcc 79
335 , AlexAcc 78
336 , AlexAcc 77
337 , AlexAcc 76
338 , AlexAcc 75
339 , AlexAccPred 74 ( ifExtension MagicHashBit )(AlexAccNone)
340 , AlexAccPred 73 ( ifExtension MagicHashBit )(AlexAccNone)
341 , AlexAccPred 72 ( ifExtension MagicHashBit )(AlexAccNone)
342 , AlexAccPred 71 ( ifExtension MagicHashBit )(AlexAccPred 70 ( ifExtension MagicHashBit )(AlexAccNone))
343 , AlexAccPred 69 ( ifExtension MagicHashBit )(AlexAccPred 68 ( ifExtension MagicHashBit )(AlexAccNone))
344 , AlexAccPred 67 ( ifExtension MagicHashBit )(AlexAccNone)
345 , AlexAccPred 66 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 65 ( followedByOpeningToken )(AlexAccPred 64 ( precededByClosingToken )(AlexAcc 63)))
346 , AlexAccPred 62 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 61 ( followedByOpeningToken )(AlexAccPred 60 ( precededByClosingToken )(AlexAcc 59)))
347 , AlexAccPred 58 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 57 ( followedByOpeningToken )(AlexAccPred 56 ( precededByClosingToken )(AlexAcc 55)))
348 , AlexAccPred 54 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 53 ( followedByOpeningToken )(AlexAccPred 52 ( precededByClosingToken )(AlexAcc 51)))
349 , AlexAccPred 50 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 49 ( followedByOpeningToken )(AlexAccPred 48 ( precededByClosingToken )(AlexAcc 47)))
350 , AlexAccPred 46 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 45 ( followedByOpeningToken )(AlexAccPred 44 ( precededByClosingToken )(AlexAcc 43)))
351 , AlexAccPred 42 ( precededByClosingToken `alexAndPred` followedByOpeningToken )(AlexAccPred 41 ( followedByOpeningToken )(AlexAccPred 40 ( precededByClosingToken )(AlexAcc 39)))
352 , AlexAcc 38
353 , AlexAcc 37
354 , AlexAcc 36
355 , AlexAcc 35
356 , AlexAcc 34
357 , AlexAccPred 33 ( ifExtension BinaryLiteralsBit )(AlexAccNone)
358 , AlexAcc 32
359 , AlexAcc 31
360 , AlexAccPred 30 ( negLitPred )(AlexAccNone)
361 , AlexAccPred 29 ( negLitPred )(AlexAccNone)
362 , AlexAccPred 28 ( negLitPred `alexAndPred`
363 ifExtension BinaryLiteralsBit )(AlexAccNone)
364 , AlexAccPred 27 ( negLitPred )(AlexAccNone)
365 , AlexAccPred 26 ( negLitPred )(AlexAccNone)
366 , AlexAcc 25
367 , AlexAcc 24
368 , AlexAccPred 23 ( negLitPred )(AlexAccNone)
369 , AlexAccPred 22 ( negLitPred )(AlexAccNone)
370 , AlexAccPred 21 ( ifExtension HexFloatLiteralsBit )(AlexAccNone)
371 , AlexAccPred 20 ( ifExtension HexFloatLiteralsBit )(AlexAccNone)
372 , AlexAccPred 19 ( ifExtension HexFloatLiteralsBit `alexAndPred`
373 negLitPred )(AlexAccNone)
374 , AlexAccPred 18 ( ifExtension HexFloatLiteralsBit `alexAndPred`
375 negLitPred )(AlexAccNone)
376 , AlexAccPred 17 ( ifExtension MagicHashBit )(AlexAccNone)
377 , AlexAccPred 16 ( ifExtension MagicHashBit `alexAndPred`
378 ifExtension BinaryLiteralsBit )(AlexAccNone)
379 , AlexAccPred 15 ( ifExtension MagicHashBit )(AlexAccNone)
380 , AlexAccPred 14 ( ifExtension MagicHashBit )(AlexAccNone)
381 , AlexAccPred 13 ( negHashLitPred )(AlexAccNone)
382 , AlexAccPred 12 ( negHashLitPred `alexAndPred`
383 ifExtension BinaryLiteralsBit )(AlexAccNone)
384 , AlexAccPred 11 ( negHashLitPred )(AlexAccNone)
385 , AlexAccPred 10 ( negHashLitPred )(AlexAccNone)
386 , AlexAccPred 9 ( ifExtension MagicHashBit )(AlexAccNone)
387 , AlexAccPred 8 ( ifExtension MagicHashBit `alexAndPred`
388 ifExtension BinaryLiteralsBit )(AlexAccNone)
389 , AlexAccPred 7 ( ifExtension MagicHashBit )(AlexAccNone)
390 , AlexAccPred 6 ( ifExtension MagicHashBit )(AlexAccNone)
391 , AlexAccPred 5 ( ifExtension MagicHashBit )(AlexAccNone)
392 , AlexAccPred 4 ( ifExtension MagicHashBit )(AlexAccNone)
393 , AlexAccPred 3 ( negHashLitPred )(AlexAccNone)
394 , AlexAccPred 2 ( negHashLitPred )(AlexAccNone)
395 , AlexAcc 1
396 , AlexAcc 0
397 ]
398
399 alex_actions = array (0 :: Int, 210)
400 [ (209,alex_action_15)
401 , (208,alex_action_21)
402 , (207,alex_action_22)
403 , (206,alex_action_20)
404 , (205,alex_action_23)
405 , (204,alex_action_27)
406 , (203,alex_action_28)
407 , (202,alex_action_1)
408 , (201,alex_action_1)
409 , (200,alex_action_2)
410 , (199,alex_action_2)
411 , (198,alex_action_2)
412 , (197,alex_action_2)
413 , (196,alex_action_28)
414 , (195,alex_action_3)
415 , (194,alex_action_4)
416 , (193,alex_action_5)
417 , (192,alex_action_5)
418 , (191,alex_action_28)
419 , (190,alex_action_5)
420 , (189,alex_action_39)
421 , (188,alex_action_6)
422 , (187,alex_action_7)
423 , (186,alex_action_7)
424 , (185,alex_action_7)
425 , (184,alex_action_28)
426 , (183,alex_action_7)
427 , (182,alex_action_28)
428 , (181,alex_action_7)
429 , (180,alex_action_81)
430 , (179,alex_action_82)
431 , (178,alex_action_83)
432 , (177,alex_action_84)
433 , (176,alex_action_7)
434 , (175,alex_action_81)
435 , (174,alex_action_82)
436 , (173,alex_action_83)
437 , (172,alex_action_84)
438 , (171,alex_action_8)
439 , (170,alex_action_8)
440 , (169,alex_action_28)
441 , (168,alex_action_10)
442 , (167,alex_action_11)
443 , (166,alex_action_16)
444 , (165,alex_action_18)
445 , (164,alex_action_18)
446 , (163,alex_action_19)
447 , (162,alex_action_24)
448 , (161,alex_action_25)
449 , (160,alex_action_25)
450 , (159,alex_action_28)
451 , (158,alex_action_25)
452 , (157,alex_action_33)
453 , (156,alex_action_34)
454 , (155,alex_action_36)
455 , (154,alex_action_25)
456 , (153,alex_action_33)
457 , (152,alex_action_34)
458 , (151,alex_action_37)
459 , (150,alex_action_26)
460 , (149,alex_action_28)
461 , (148,alex_action_28)
462 , (147,alex_action_28)
463 , (146,alex_action_28)
464 , (145,alex_action_29)
465 , (144,alex_action_30)
466 , (143,alex_action_31)
467 , (142,alex_action_32)
468 , (141,alex_action_35)
469 , (140,alex_action_38)
470 , (139,alex_action_38)
471 , (138,alex_action_40)
472 , (137,alex_action_41)
473 , (136,alex_action_42)
474 , (135,alex_action_43)
475 , (134,alex_action_44)
476 , (133,alex_action_45)
477 , (132,alex_action_50)
478 , (131,alex_action_46)
479 , (130,alex_action_47)
480 , (129,alex_action_50)
481 , (128,alex_action_48)
482 , (127,alex_action_50)
483 , (126,alex_action_49)
484 , (125,alex_action_50)
485 , (124,alex_action_50)
486 , (123,alex_action_51)
487 , (122,alex_action_52)
488 , (121,alex_action_53)
489 , (120,alex_action_56)
490 , (119,alex_action_57)
491 , (118,alex_action_54)
492 , (117,alex_action_55)
493 , (116,alex_action_58)
494 , (115,alex_action_59)
495 , (114,alex_action_60)
496 , (113,alex_action_61)
497 , (112,alex_action_62)
498 , (111,alex_action_62)
499 , (110,alex_action_63)
500 , (109,alex_action_64)
501 , (108,alex_action_64)
502 , (107,alex_action_65)
503 , (106,alex_action_66)
504 , (105,alex_action_67)
505 , (104,alex_action_68)
506 , (103,alex_action_69)
507 , (102,alex_action_69)
508 , (101,alex_action_70)
509 , (100,alex_action_71)
510 , (99,alex_action_71)
511 , (98,alex_action_72)
512 , (97,alex_action_73)
513 , (96,alex_action_72)
514 , (95,alex_action_73)
515 , (94,alex_action_73)
516 , (93,alex_action_73)
517 , (92,alex_action_73)
518 , (91,alex_action_73)
519 , (90,alex_action_73)
520 , (89,alex_action_73)
521 , (88,alex_action_73)
522 , (87,alex_action_73)
523 , (86,alex_action_74)
524 , (85,alex_action_74)
525 , (84,alex_action_75)
526 , (83,alex_action_75)
527 , (82,alex_action_75)
528 , (81,alex_action_75)
529 , (80,alex_action_75)
530 , (79,alex_action_75)
531 , (78,alex_action_75)
532 , (77,alex_action_75)
533 , (76,alex_action_76)
534 , (75,alex_action_76)
535 , (74,alex_action_77)
536 , (73,alex_action_78)
537 , (72,alex_action_79)
538 , (71,alex_action_79)
539 , (70,alex_action_112)
540 , (69,alex_action_79)
541 , (68,alex_action_113)
542 , (67,alex_action_80)
543 , (66,alex_action_81)
544 , (65,alex_action_82)
545 , (64,alex_action_83)
546 , (63,alex_action_84)
547 , (62,alex_action_81)
548 , (61,alex_action_82)
549 , (60,alex_action_83)
550 , (59,alex_action_84)
551 , (58,alex_action_81)
552 , (57,alex_action_82)
553 , (56,alex_action_83)
554 , (55,alex_action_84)
555 , (54,alex_action_81)
556 , (53,alex_action_82)
557 , (52,alex_action_83)
558 , (51,alex_action_84)
559 , (50,alex_action_81)
560 , (49,alex_action_82)
561 , (48,alex_action_83)
562 , (47,alex_action_84)
563 , (46,alex_action_81)
564 , (45,alex_action_82)
565 , (44,alex_action_83)
566 , (43,alex_action_84)
567 , (42,alex_action_81)
568 , (41,alex_action_82)
569 , (40,alex_action_83)
570 , (39,alex_action_84)
571 , (38,alex_action_85)
572 , (37,alex_action_86)
573 , (36,alex_action_87)
574 , (35,alex_action_88)
575 , (34,alex_action_88)
576 , (33,alex_action_89)
577 , (32,alex_action_90)
578 , (31,alex_action_91)
579 , (30,alex_action_92)
580 , (29,alex_action_92)
581 , (28,alex_action_93)
582 , (27,alex_action_94)
583 , (26,alex_action_95)
584 , (25,alex_action_96)
585 , (24,alex_action_96)
586 , (23,alex_action_97)
587 , (22,alex_action_97)
588 , (21,alex_action_98)
589 , (20,alex_action_98)
590 , (19,alex_action_99)
591 , (18,alex_action_99)
592 , (17,alex_action_100)
593 , (16,alex_action_101)
594 , (15,alex_action_102)
595 , (14,alex_action_103)
596 , (13,alex_action_104)
597 , (12,alex_action_105)
598 , (11,alex_action_106)
599 , (10,alex_action_107)
600 , (9,alex_action_108)
601 , (8,alex_action_109)
602 , (7,alex_action_110)
603 , (6,alex_action_111)
604 , (5,alex_action_112)
605 , (4,alex_action_113)
606 , (3,alex_action_114)
607 , (2,alex_action_115)
608 , (1,alex_action_116)
609 , (0,alex_action_117)
610 ]
611
612 {-# LINE 699 "compiler/GHC/Parser/Lexer.x" #-}
613
614
615 -- -----------------------------------------------------------------------------
616 -- The token type
617
618 data Token
619 = ITas -- Haskell keywords
620 | ITcase
621 | ITclass
622 | ITdata
623 | ITdefault
624 | ITderiving
625 | ITdo (Maybe FastString)
626 | ITelse
627 | IThiding
628 | ITforeign
629 | ITif
630 | ITimport
631 | ITin
632 | ITinfix
633 | ITinfixl
634 | ITinfixr
635 | ITinstance
636 | ITlet
637 | ITmodule
638 | ITnewtype
639 | ITof
640 | ITqualified
641 | ITthen
642 | ITtype
643 | ITwhere
644
645 | ITforall IsUnicodeSyntax -- GHC extension keywords
646 | ITexport
647 | ITlabel
648 | ITdynamic
649 | ITsafe
650 | ITinterruptible
651 | ITunsafe
652 | ITstdcallconv
653 | ITccallconv
654 | ITcapiconv
655 | ITprimcallconv
656 | ITjavascriptcallconv
657 | ITmdo (Maybe FastString)
658 | ITfamily
659 | ITrole
660 | ITgroup
661 | ITby
662 | ITusing
663 | ITpattern
664 | ITstatic
665 | ITstock
666 | ITanyclass
667 | ITvia
668
669 -- Backpack tokens
670 | ITunit
671 | ITsignature
672 | ITdependency
673 | ITrequires
674
675 -- Pragmas, see note [Pragma source text] in "GHC.Types.Basic"
676 | ITinline_prag SourceText InlineSpec RuleMatchInfo
677 | ITspec_prag SourceText -- SPECIALISE
678 | ITspec_inline_prag SourceText Bool -- SPECIALISE INLINE (or NOINLINE)
679 | ITsource_prag SourceText
680 | ITrules_prag SourceText
681 | ITwarning_prag SourceText
682 | ITdeprecated_prag SourceText
683 | ITline_prag SourceText -- not usually produced, see 'UsePosPragsBit'
684 | ITcolumn_prag SourceText -- not usually produced, see 'UsePosPragsBit'
685 | ITscc_prag SourceText
686 | ITunpack_prag SourceText
687 | ITnounpack_prag SourceText
688 | ITann_prag SourceText
689 | ITcomplete_prag SourceText
690 | ITclose_prag
691 | IToptions_prag String
692 | ITinclude_prag String
693 | ITlanguage_prag
694 | ITminimal_prag SourceText
695 | IToverlappable_prag SourceText -- instance overlap mode
696 | IToverlapping_prag SourceText -- instance overlap mode
697 | IToverlaps_prag SourceText -- instance overlap mode
698 | ITincoherent_prag SourceText -- instance overlap mode
699 | ITctype SourceText
700 | ITcomment_line_prag -- See Note [Nested comment line pragmas]
701
702 | ITdotdot -- reserved symbols
703 | ITcolon
704 | ITdcolon IsUnicodeSyntax
705 | ITequal
706 | ITlam
707 | ITlcase
708 | ITvbar
709 | ITlarrow IsUnicodeSyntax
710 | ITrarrow IsUnicodeSyntax
711 | ITdarrow IsUnicodeSyntax
712 | ITlolly -- The (⊸) arrow (for LinearTypes)
713 | ITminus -- See Note [Minus tokens]
714 | ITprefixminus -- See Note [Minus tokens]
715 | ITbang -- Prefix (!) only, e.g. f !x = rhs
716 | ITtilde -- Prefix (~) only, e.g. f ~x = rhs
717 | ITat -- Tight infix (@) only, e.g. f x@pat = rhs
718 | ITtypeApp -- Prefix (@) only, e.g. f @t
719 | ITpercent -- Prefix (%) only, e.g. a %1 -> b
720 | ITstar IsUnicodeSyntax
721 | ITdot
722 | ITproj Bool -- Extension: OverloadedRecordDotBit
723
724 | ITbiglam -- GHC-extension symbols
725
726 | ITocurly -- special symbols
727 | ITccurly
728 | ITvocurly
729 | ITvccurly
730 | ITobrack
731 | ITopabrack -- [:, for parallel arrays with -XParallelArrays
732 | ITcpabrack -- :], for parallel arrays with -XParallelArrays
733 | ITcbrack
734 | IToparen
735 | ITcparen
736 | IToubxparen
737 | ITcubxparen
738 | ITsemi
739 | ITcomma
740 | ITunderscore
741 | ITbackquote
742 | ITsimpleQuote -- '
743
744 | ITvarid FastString -- identifiers
745 | ITconid FastString
746 | ITvarsym FastString
747 | ITconsym FastString
748 | ITqvarid (FastString,FastString)
749 | ITqconid (FastString,FastString)
750 | ITqvarsym (FastString,FastString)
751 | ITqconsym (FastString,FastString)
752
753 | ITdupipvarid FastString -- GHC extension: implicit param: ?x
754 | ITlabelvarid FastString -- Overloaded label: #x
755
756 | ITchar SourceText Char -- Note [Literal source text] in "GHC.Types.Basic"
757 | ITstring SourceText FastString -- Note [Literal source text] in "GHC.Types.Basic"
758 | ITinteger IntegralLit -- Note [Literal source text] in "GHC.Types.Basic"
759 | ITrational FractionalLit
760
761 | ITprimchar SourceText Char -- Note [Literal source text] in "GHC.Types.Basic"
762 | ITprimstring SourceText ByteString -- Note [Literal source text] in "GHC.Types.Basic"
763 | ITprimint SourceText Integer -- Note [Literal source text] in "GHC.Types.Basic"
764 | ITprimword SourceText Integer -- Note [Literal source text] in "GHC.Types.Basic"
765 | ITprimfloat FractionalLit
766 | ITprimdouble FractionalLit
767
768 -- Template Haskell extension tokens
769 | ITopenExpQuote HasE IsUnicodeSyntax -- [| or [e|
770 | ITopenPatQuote -- [p|
771 | ITopenDecQuote -- [d|
772 | ITopenTypQuote -- [t|
773 | ITcloseQuote IsUnicodeSyntax -- |]
774 | ITopenTExpQuote HasE -- [|| or [e||
775 | ITcloseTExpQuote -- ||]
776 | ITdollar -- prefix $
777 | ITdollardollar -- prefix $$
778 | ITtyQuote -- ''
779 | ITquasiQuote (FastString,FastString,PsSpan)
780 -- ITquasiQuote(quoter, quote, loc)
781 -- represents a quasi-quote of the form
782 -- [quoter| quote |]
783 | ITqQuasiQuote (FastString,FastString,FastString,PsSpan)
784 -- ITqQuasiQuote(Qual, quoter, quote, loc)
785 -- represents a qualified quasi-quote of the form
786 -- [Qual.quoter| quote |]
787
788 -- Arrow notation extension
789 | ITproc
790 | ITrec
791 | IToparenbar IsUnicodeSyntax -- ^ @(|@
792 | ITcparenbar IsUnicodeSyntax -- ^ @|)@
793 | ITlarrowtail IsUnicodeSyntax -- ^ @-<@
794 | ITrarrowtail IsUnicodeSyntax -- ^ @>-@
795 | ITLarrowtail IsUnicodeSyntax -- ^ @-<<@
796 | ITRarrowtail IsUnicodeSyntax -- ^ @>>-@
797
798 | ITunknown String -- ^ Used when the lexer can't make sense of it
799 | ITeof -- ^ end of file token
800
801 -- Documentation annotations. See Note [PsSpan in Comments]
802 | ITdocCommentNext String PsSpan -- ^ something beginning @-- |@
803 | ITdocCommentPrev String PsSpan -- ^ something beginning @-- ^@
804 | ITdocCommentNamed String PsSpan -- ^ something beginning @-- $@
805 | ITdocSection Int String PsSpan -- ^ a section heading
806 | ITdocOptions String PsSpan -- ^ doc options (prune, ignore-exports, etc)
807 | ITlineComment String PsSpan -- ^ comment starting by "--"
808 | ITblockComment String PsSpan -- ^ comment in {- -}
809
810 deriving Show
811
812 instance Outputable Token where
813 ppr x = text (show x)
814
815 {- Note [PsSpan in Comments]
816 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
817 When using the Api Annotations to exact print a modified AST, managing
818 the space before a comment is important. The PsSpan in the comment
819 token allows this to happen.
820
821 We also need to track the space before the end of file. The normal
822 mechanism of using the previous token does not work, as the ITeof is
823 synthesised to come at the same location of the last token, and the
824 normal previous token updating has by then updated the required
825 location.
826
827 We track this using a 2-back location, prev_loc2. This adds extra
828 processing to every single token, which is a performance hit for
829 something needed only at the end of the file. This needs
830 improving. Perhaps a backward scan on eof?
831 -}
832
833 {- Note [Minus tokens]
834 ~~~~~~~~~~~~~~~~~~~~~~
835 A minus sign can be used in prefix form (-x) and infix form (a - b).
836
837 When LexicalNegation is on:
838 * ITprefixminus represents the prefix form
839 * ITvarsym "-" represents the infix form
840 * ITminus is not used
841
842 When LexicalNegation is off:
843 * ITminus represents all forms
844 * ITprefixminus is not used
845 * ITvarsym "-" is not used
846 -}
847
848 {- Note [Why not LexicalNegationBit]
849 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
850 One might wonder why we define NoLexicalNegationBit instead of
851 LexicalNegationBit. The problem lies in the following line in reservedSymsFM:
852
853 ,("-", ITminus, NormalSyntax, xbit NoLexicalNegationBit)
854
855 We want to generate ITminus only when LexicalNegation is off. How would one
856 do it if we had LexicalNegationBit? I (int-index) tried to use bitwise
857 complement:
858
859 ,("-", ITminus, NormalSyntax, complement (xbit LexicalNegationBit))
860
861 This did not work, so I opted for NoLexicalNegationBit instead.
862 -}
863
864
865 -- the bitmap provided as the third component indicates whether the
866 -- corresponding extension keyword is valid under the extension options
867 -- provided to the compiler; if the extension corresponding to *any* of the
868 -- bits set in the bitmap is enabled, the keyword is valid (this setup
869 -- facilitates using a keyword in two different extensions that can be
870 -- activated independently)
871 --
872 reservedWordsFM :: UniqFM FastString (Token, ExtsBitmap)
873 reservedWordsFM = listToUFM $
874 map (\(x, y, z) -> (mkFastString x, (y, z)))
875 [( "_", ITunderscore, 0 ),
876 ( "as", ITas, 0 ),
877 ( "case", ITcase, 0 ),
878 ( "class", ITclass, 0 ),
879 ( "data", ITdata, 0 ),
880 ( "default", ITdefault, 0 ),
881 ( "deriving", ITderiving, 0 ),
882 ( "do", ITdo Nothing, 0 ),
883 ( "else", ITelse, 0 ),
884 ( "hiding", IThiding, 0 ),
885 ( "if", ITif, 0 ),
886 ( "import", ITimport, 0 ),
887 ( "in", ITin, 0 ),
888 ( "infix", ITinfix, 0 ),
889 ( "infixl", ITinfixl, 0 ),
890 ( "infixr", ITinfixr, 0 ),
891 ( "instance", ITinstance, 0 ),
892 ( "let", ITlet, 0 ),
893 ( "module", ITmodule, 0 ),
894 ( "newtype", ITnewtype, 0 ),
895 ( "of", ITof, 0 ),
896 ( "qualified", ITqualified, 0 ),
897 ( "then", ITthen, 0 ),
898 ( "type", ITtype, 0 ),
899 ( "where", ITwhere, 0 ),
900
901 ( "forall", ITforall NormalSyntax, 0),
902 ( "mdo", ITmdo Nothing, xbit RecursiveDoBit),
903 -- See Note [Lexing type pseudo-keywords]
904 ( "family", ITfamily, 0 ),
905 ( "role", ITrole, 0 ),
906 ( "pattern", ITpattern, xbit PatternSynonymsBit),
907 ( "static", ITstatic, xbit StaticPointersBit ),
908 ( "stock", ITstock, 0 ),
909 ( "anyclass", ITanyclass, 0 ),
910 ( "via", ITvia, 0 ),
911 ( "group", ITgroup, xbit TransformComprehensionsBit),
912 ( "by", ITby, xbit TransformComprehensionsBit),
913 ( "using", ITusing, xbit TransformComprehensionsBit),
914
915 ( "foreign", ITforeign, xbit FfiBit),
916 ( "export", ITexport, xbit FfiBit),
917 ( "label", ITlabel, xbit FfiBit),
918 ( "dynamic", ITdynamic, xbit FfiBit),
919 ( "safe", ITsafe, xbit FfiBit .|.
920 xbit SafeHaskellBit),
921 ( "interruptible", ITinterruptible, xbit InterruptibleFfiBit),
922 ( "unsafe", ITunsafe, xbit FfiBit),
923 ( "stdcall", ITstdcallconv, xbit FfiBit),
924 ( "ccall", ITccallconv, xbit FfiBit),
925 ( "capi", ITcapiconv, xbit CApiFfiBit),
926 ( "prim", ITprimcallconv, xbit FfiBit),
927 ( "javascript", ITjavascriptcallconv, xbit FfiBit),
928
929 ( "unit", ITunit, 0 ),
930 ( "dependency", ITdependency, 0 ),
931 ( "signature", ITsignature, 0 ),
932
933 ( "rec", ITrec, xbit ArrowsBit .|.
934 xbit RecursiveDoBit),
935 ( "proc", ITproc, xbit ArrowsBit)
936 ]
937
938 {-----------------------------------
939 Note [Lexing type pseudo-keywords]
940 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
941
942 One might think that we wish to treat 'family' and 'role' as regular old
943 varids whenever -XTypeFamilies and -XRoleAnnotations are off, respectively.
944 But, there is no need to do so. These pseudo-keywords are not stolen syntax:
945 they are only used after the keyword 'type' at the top-level, where varids are
946 not allowed. Furthermore, checks further downstream (GHC.Tc.TyCl) ensure that
947 type families and role annotations are never declared without their extensions
948 on. In fact, by unconditionally lexing these pseudo-keywords as special, we
949 can get better error messages.
950
951 Also, note that these are included in the `varid` production in the parser --
952 a key detail to make all this work.
953 -------------------------------------}
954
955 reservedSymsFM :: UniqFM FastString (Token, IsUnicodeSyntax, ExtsBitmap)
956 reservedSymsFM = listToUFM $
957 map (\ (x,w,y,z) -> (mkFastString x,(w,y,z)))
958 [ ("..", ITdotdot, NormalSyntax, 0 )
959 -- (:) is a reserved op, meaning only list cons
960 ,(":", ITcolon, NormalSyntax, 0 )
961 ,("::", ITdcolon NormalSyntax, NormalSyntax, 0 )
962 ,("=", ITequal, NormalSyntax, 0 )
963 ,("\\", ITlam, NormalSyntax, 0 )
964 ,("|", ITvbar, NormalSyntax, 0 )
965 ,("<-", ITlarrow NormalSyntax, NormalSyntax, 0 )
966 ,("->", ITrarrow NormalSyntax, NormalSyntax, 0 )
967 ,("=>", ITdarrow NormalSyntax, NormalSyntax, 0 )
968 ,("-", ITminus, NormalSyntax, xbit NoLexicalNegationBit)
969
970 ,("*", ITstar NormalSyntax, NormalSyntax, xbit StarIsTypeBit)
971
972 -- For 'forall a . t'
973 ,(".", ITdot, NormalSyntax, 0 )
974
975 ,("-<", ITlarrowtail NormalSyntax, NormalSyntax, xbit ArrowsBit)
976 ,(">-", ITrarrowtail NormalSyntax, NormalSyntax, xbit ArrowsBit)
977 ,("-<<", ITLarrowtail NormalSyntax, NormalSyntax, xbit ArrowsBit)
978 ,(">>-", ITRarrowtail NormalSyntax, NormalSyntax, xbit ArrowsBit)
979
980 ,("∷", ITdcolon UnicodeSyntax, UnicodeSyntax, 0 )
981 ,("⇒", ITdarrow UnicodeSyntax, UnicodeSyntax, 0 )
982 ,("∀", ITforall UnicodeSyntax, UnicodeSyntax, 0 )
983 ,("→", ITrarrow UnicodeSyntax, UnicodeSyntax, 0 )
984 ,("←", ITlarrow UnicodeSyntax, UnicodeSyntax, 0 )
985
986 ,("⊸", ITlolly, UnicodeSyntax, 0)
987
988 ,("⤙", ITlarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
989 ,("⤚", ITrarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
990 ,("⤛", ITLarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
991 ,("⤜", ITRarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
992
993 ,("★", ITstar UnicodeSyntax, UnicodeSyntax, xbit StarIsTypeBit)
994
995 -- ToDo: ideally, → and ∷ should be "specials", so that they cannot
996 -- form part of a large operator. This would let us have a better
997 -- syntax for kinds: ɑ∷*→* would be a legal kind signature. (maybe).
998 ]
999
1000 -- -----------------------------------------------------------------------------
1001 -- Lexer actions
1002
1003 type Action = PsSpan -> StringBuffer -> Int -> P (PsLocated Token)
1004
1005 special :: Token -> Action
1006 special tok span _buf _len = return (L span tok)
1007
1008 token, layout_token :: Token -> Action
1009 token t span _buf _len = return (L span t)
1010 layout_token t span _buf _len = pushLexState layout >> return (L span t)
1011
1012 idtoken :: (StringBuffer -> Int -> Token) -> Action
1013 idtoken f span buf len = return (L span $! (f buf len))
1014
1015 qdo_token :: (Maybe FastString -> Token) -> Action
1016 qdo_token con span buf len = do
1017 maybe_layout token
1018 return (L span $! token)
1019 where
1020 !token = con $! Just $! fst $! splitQualName buf len False
1021
1022 skip_one_varid :: (FastString -> Token) -> Action
1023 skip_one_varid f span buf len
1024 = return (L span $! f (lexemeToFastString (stepOn buf) (len-1)))
1025
1026 skip_two_varid :: (FastString -> Token) -> Action
1027 skip_two_varid f span buf len
1028 = return (L span $! f (lexemeToFastString (stepOn (stepOn buf)) (len-2)))
1029
1030 strtoken :: (String -> Token) -> Action
1031 strtoken f span buf len =
1032 return (L span $! (f $! lexemeToString buf len))
1033
1034 begin :: Int -> Action
1035 begin code _span _str _len = do pushLexState code; lexToken
1036
1037 pop :: Action
1038 pop _span _buf _len = do _ <- popLexState
1039 lexToken
1040 -- See Note [Nested comment line pragmas]
1041 failLinePrag1 :: Action
1042 failLinePrag1 span _buf _len = do
1043 b <- getBit InNestedCommentBit
1044 if b then return (L span ITcomment_line_prag)
1045 else lexError LexErrorInPragma
1046
1047 -- See Note [Nested comment line pragmas]
1048 popLinePrag1 :: Action
1049 popLinePrag1 span _buf _len = do
1050 b <- getBit InNestedCommentBit
1051 if b then return (L span ITcomment_line_prag) else do
1052 _ <- popLexState
1053 lexToken
1054
1055 hopefully_open_brace :: Action
1056 hopefully_open_brace span buf len
1057 = do relaxed <- getBit RelaxedLayoutBit
1058 ctx <- getContext
1059 (AI l _) <- getInput
1060 let offset = srcLocCol (psRealLoc l)
1061 isOK = relaxed ||
1062 case ctx of
1063 Layout prev_off _ : _ -> prev_off < offset
1064 _ -> True
1065 if isOK then pop_and open_brace span buf len
1066 else addFatalError $
1067 mkPlainErrorMsgEnvelope (mkSrcSpanPs span) PsErrMissingBlock
1068
1069 pop_and :: Action -> Action
1070 pop_and act span buf len = do _ <- popLexState
1071 act span buf len
1072
1073 -- See Note [Whitespace-sensitive operator parsing]
1074 followedByOpeningToken :: AlexAccPred ExtsBitmap
1075 followedByOpeningToken _ _ _ (AI _ buf)
1076 | atEnd buf = False
1077 | otherwise =
1078 case nextChar buf of
1079 ('{', buf') -> nextCharIsNot buf' (== '-')
1080 ('(', _) -> True
1081 ('[', _) -> True
1082 ('\"', _) -> True
1083 ('\'', _) -> True
1084 ('_', _) -> True
1085 ('⟦', _) -> True
1086 ('⦇', _) -> True
1087 (c, _) -> isAlphaNum c
1088
1089 -- See Note [Whitespace-sensitive operator parsing]
1090 precededByClosingToken :: AlexAccPred ExtsBitmap
1091 precededByClosingToken _ (AI _ buf) _ _ =
1092 case prevChar buf '\n' of
1093 '}' -> decodePrevNChars 1 buf /= "-"
1094 ')' -> True
1095 ']' -> True
1096 '\"' -> True
1097 '\'' -> True
1098 '_' -> True
1099 '⟧' -> True
1100 '⦈' -> True
1101 c -> isAlphaNum c
1102
1103 {-# INLINE nextCharIs #-}
1104 nextCharIs :: StringBuffer -> (Char -> Bool) -> Bool
1105 nextCharIs buf p = not (atEnd buf) && p (currentChar buf)
1106
1107 {-# INLINE nextCharIsNot #-}
1108 nextCharIsNot :: StringBuffer -> (Char -> Bool) -> Bool
1109 nextCharIsNot buf p = not (nextCharIs buf p)
1110
1111 notFollowedBy :: Char -> AlexAccPred ExtsBitmap
1112 notFollowedBy char _ _ _ (AI _ buf)
1113 = nextCharIsNot buf (== char)
1114
1115 notFollowedBySymbol :: AlexAccPred ExtsBitmap
1116 notFollowedBySymbol _ _ _ (AI _ buf)
1117 = nextCharIsNot buf (`elem` "!#$%&*+./<=>?@\\^|-~")
1118
1119 followedByDigit :: AlexAccPred ExtsBitmap
1120 followedByDigit _ _ _ (AI _ buf)
1121 = afterOptionalSpace buf (\b -> nextCharIs b (`elem` ['0'..'9']))
1122
1123 ifCurrentChar :: Char -> AlexAccPred ExtsBitmap
1124 ifCurrentChar char _ (AI _ buf) _ _
1125 = nextCharIs buf (== char)
1126
1127 -- We must reject doc comments as being ordinary comments everywhere.
1128 -- In some cases the doc comment will be selected as the lexeme due to
1129 -- maximal munch, but not always, because the nested comment rule is
1130 -- valid in all states, but the doc-comment rules are only valid in
1131 -- the non-layout states.
1132 isNormalComment :: AlexAccPred ExtsBitmap
1133 isNormalComment bits _ _ (AI _ buf)
1134 | HaddockBit `xtest` bits = notFollowedByDocOrPragma
1135 | otherwise = nextCharIsNot buf (== '#')
1136 where
1137 notFollowedByDocOrPragma
1138 = afterOptionalSpace buf (\b -> nextCharIsNot b (`elem` "|^*$#"))
1139
1140 afterOptionalSpace :: StringBuffer -> (StringBuffer -> Bool) -> Bool
1141 afterOptionalSpace buf p
1142 = if nextCharIs buf (== ' ')
1143 then p (snd (nextChar buf))
1144 else p buf
1145
1146 atEOL :: AlexAccPred ExtsBitmap
1147 atEOL _ _ _ (AI _ buf) = atEnd buf || currentChar buf == '\n'
1148
1149 -- Check if we should parse a negative literal (e.g. -123) as a single token.
1150 negLitPred :: AlexAccPred ExtsBitmap
1151 negLitPred =
1152 prefix_minus `alexAndPred`
1153 (negative_literals `alexOrPred` lexical_negation)
1154 where
1155 negative_literals = ifExtension NegativeLiteralsBit
1156
1157 lexical_negation =
1158 -- See Note [Why not LexicalNegationBit]
1159 alexNotPred (ifExtension NoLexicalNegationBit)
1160
1161 prefix_minus =
1162 -- Note [prefix_minus in negLitPred and negHashLitPred]
1163 alexNotPred precededByClosingToken
1164
1165 -- Check if we should parse an unboxed negative literal (e.g. -123#) as a single token.
1166 negHashLitPred :: AlexAccPred ExtsBitmap
1167 negHashLitPred = prefix_minus `alexAndPred` magic_hash
1168 where
1169 magic_hash = ifExtension MagicHashBit
1170 prefix_minus =
1171 -- Note [prefix_minus in negLitPred and negHashLitPred]
1172 alexNotPred precededByClosingToken
1173
1174 {- Note [prefix_minus in negLitPred and negHashLitPred]
1175 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1176 We want to parse -1 as a single token, but x-1 as three tokens.
1177 So in negLitPred (and negHashLitPred) we require that we have a prefix
1178 occurrence of the minus sign. See Note [Whitespace-sensitive operator parsing]
1179 for a detailed definition of a prefix occurrence.
1180
1181 The condition for a prefix occurrence of an operator is:
1182
1183 not precededByClosingToken && followedByOpeningToken
1184
1185 but we don't check followedByOpeningToken when parsing a negative literal.
1186 It holds simply because we immediately lex a literal after the minus.
1187 -}
1188
1189 ifExtension :: ExtBits -> AlexAccPred ExtsBitmap
1190 ifExtension extBits bits _ _ _ = extBits `xtest` bits
1191
1192 alexNotPred p userState in1 len in2
1193 = not (p userState in1 len in2)
1194
1195 alexOrPred p1 p2 userState in1 len in2
1196 = p1 userState in1 len in2 || p2 userState in1 len in2
1197
1198 multiline_doc_comment :: Action
1199 multiline_doc_comment span buf _len = withLexedDocType (worker "")
1200 where
1201 worker commentAcc input docType checkNextLine = case alexGetChar' input of
1202 Just ('\n', input')
1203 | checkNextLine -> case checkIfCommentLine input' of
1204 Just input -> worker ('\n':commentAcc) input docType checkNextLine
1205 Nothing -> docCommentEnd input commentAcc docType buf span
1206 | otherwise -> docCommentEnd input commentAcc docType buf span
1207 Just (c, input) -> worker (c:commentAcc) input docType checkNextLine
1208 Nothing -> docCommentEnd input commentAcc docType buf span
1209
1210 -- Check if the next line of input belongs to this doc comment as well.
1211 -- A doc comment continues onto the next line when the following
1212 -- conditions are met:
1213 -- * The line starts with "--"
1214 -- * The line doesn't start with "---".
1215 -- * The line doesn't start with "-- $", because that would be the
1216 -- start of a /new/ named haddock chunk (#10398).
1217 checkIfCommentLine :: AlexInput -> Maybe AlexInput
1218 checkIfCommentLine input = check (dropNonNewlineSpace input)
1219 where
1220 check input = do
1221 ('-', input) <- alexGetChar' input
1222 ('-', input) <- alexGetChar' input
1223 (c, after_c) <- alexGetChar' input
1224 case c of
1225 '-' -> Nothing
1226 ' ' -> case alexGetChar' after_c of
1227 Just ('$', _) -> Nothing
1228 _ -> Just input
1229 _ -> Just input
1230
1231 dropNonNewlineSpace input = case alexGetChar' input of
1232 Just (c, input')
1233 | isSpace c && c /= '\n' -> dropNonNewlineSpace input'
1234 | otherwise -> input
1235 Nothing -> input
1236
1237 lineCommentToken :: Action
1238 lineCommentToken span buf len = do
1239 b <- getBit RawTokenStreamBit
1240 if b then do
1241 lt <- getLastLocComment
1242 strtoken (\s -> ITlineComment s lt) span buf len
1243 else lexToken
1244
1245
1246 {-
1247 nested comments require traversing by hand, they can't be parsed
1248 using regular expressions.
1249 -}
1250 nested_comment :: P (PsLocated Token) -> Action
1251 nested_comment cont span buf len = do
1252 input <- getInput
1253 go (reverse $ lexemeToString buf len) (1::Int) input
1254 where
1255 go commentAcc 0 input = do
1256 l <- getLastLocComment
1257 let finalizeComment str = (Nothing, ITblockComment str l)
1258 commentEnd cont input commentAcc finalizeComment buf span
1259 go commentAcc n input = case alexGetChar' input of
1260 Nothing -> errBrace input (psRealSpan span)
1261 Just ('-',input) -> case alexGetChar' input of
1262 Nothing -> errBrace input (psRealSpan span)
1263 Just ('\125',input) -> go ('\125':'-':commentAcc) (n-1) input -- '}'
1264 Just (_,_) -> go ('-':commentAcc) n input
1265 Just ('\123',input) -> case alexGetChar' input of -- '{' char
1266 Nothing -> errBrace input (psRealSpan span)
1267 Just ('-',input) -> go ('-':'\123':commentAcc) (n+1) input
1268 Just (_,_) -> go ('\123':commentAcc) n input
1269 -- See Note [Nested comment line pragmas]
1270 Just ('\n',input) -> case alexGetChar' input of
1271 Nothing -> errBrace input (psRealSpan span)
1272 Just ('#',_) -> do (parsedAcc,input) <- parseNestedPragma input
1273 go (parsedAcc ++ '\n':commentAcc) n input
1274 Just (_,_) -> go ('\n':commentAcc) n input
1275 Just (c,input) -> go (c:commentAcc) n input
1276
1277 nested_doc_comment :: Action
1278 nested_doc_comment span buf _len = withLexedDocType (go "")
1279 where
1280 go commentAcc input docType _ = case alexGetChar' input of
1281 Nothing -> errBrace input (psRealSpan span)
1282 Just ('-',input) -> case alexGetChar' input of
1283 Nothing -> errBrace input (psRealSpan span)
1284 Just ('\125',input) ->
1285 docCommentEnd input commentAcc docType buf span
1286 Just (_,_) -> go ('-':commentAcc) input docType False
1287 Just ('\123', input) -> case alexGetChar' input of
1288 Nothing -> errBrace input (psRealSpan span)
1289 Just ('-',input) -> do
1290 setInput input
1291 let cont = do input <- getInput; go commentAcc input docType False
1292 nested_comment cont span buf _len
1293 Just (_,_) -> go ('\123':commentAcc) input docType False
1294 -- See Note [Nested comment line pragmas]
1295 Just ('\n',input) -> case alexGetChar' input of
1296 Nothing -> errBrace input (psRealSpan span)
1297 Just ('#',_) -> do (parsedAcc,input) <- parseNestedPragma input
1298 go (parsedAcc ++ '\n':commentAcc) input docType False
1299 Just (_,_) -> go ('\n':commentAcc) input docType False
1300 Just (c,input) -> go (c:commentAcc) input docType False
1301
1302 -- See Note [Nested comment line pragmas]
1303 parseNestedPragma :: AlexInput -> P (String,AlexInput)
1304 parseNestedPragma input@(AI _ buf) = do
1305 origInput <- getInput
1306 setInput input
1307 setExts (.|. xbit InNestedCommentBit)
1308 pushLexState bol
1309 lt <- lexToken
1310 _ <- popLexState
1311 setExts (.&. complement (xbit InNestedCommentBit))
1312 postInput@(AI _ postBuf) <- getInput
1313 setInput origInput
1314 case unLoc lt of
1315 ITcomment_line_prag -> do
1316 let bytes = byteDiff buf postBuf
1317 diff = lexemeToString buf bytes
1318 return (reverse diff, postInput)
1319 lt' -> panic ("parseNestedPragma: unexpected token" ++ (show lt'))
1320
1321 {-
1322 Note [Nested comment line pragmas]
1323 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1324 We used to ignore cpp-preprocessor-generated #line pragmas if they were inside
1325 nested comments.
1326
1327 Now, when parsing a nested comment, if we encounter a line starting with '#' we
1328 call parseNestedPragma, which executes the following:
1329 1. Save the current lexer input (loc, buf) for later
1330 2. Set the current lexer input to the beginning of the line starting with '#'
1331 3. Turn the 'InNestedComment' extension on
1332 4. Push the 'bol' lexer state
1333 5. Lex a token. Due to (2), (3), and (4), this should always lex a single line
1334 or less and return the ITcomment_line_prag token. This may set source line
1335 and file location if a #line pragma is successfully parsed
1336 6. Restore lexer input and state to what they were before we did all this
1337 7. Return control to the function parsing a nested comment, informing it of
1338 what the lexer parsed
1339
1340 Regarding (5) above:
1341 Every exit from the 'bol' lexer state (do_bol, popLinePrag1, failLinePrag1)
1342 checks if the 'InNestedComment' extension is set. If it is, that function will
1343 return control to parseNestedPragma by returning the ITcomment_line_prag token.
1344
1345 See #314 for more background on the bug this fixes.
1346 -}
1347
1348 withLexedDocType :: (AlexInput -> (String -> (HdkComment, Token)) -> Bool -> P (PsLocated Token))
1349 -> P (PsLocated Token)
1350 withLexedDocType lexDocComment = do
1351 input@(AI _ buf) <- getInput
1352 l <- getLastLocComment
1353 case prevChar buf ' ' of
1354 -- The `Bool` argument to lexDocComment signals whether or not the next
1355 -- line of input might also belong to this doc comment.
1356 '|' -> lexDocComment input (mkHdkCommentNext l) True
1357 '^' -> lexDocComment input (mkHdkCommentPrev l) True
1358 '$' -> lexDocComment input (mkHdkCommentNamed l) True
1359 '*' -> lexDocSection l 1 input
1360 _ -> panic "withLexedDocType: Bad doc type"
1361 where
1362 lexDocSection l n input = case alexGetChar' input of
1363 Just ('*', input) -> lexDocSection l (n+1) input
1364 Just (_, _) -> lexDocComment input (mkHdkCommentSection l n) False
1365 Nothing -> do setInput input; lexToken -- eof reached, lex it normally
1366
1367 mkHdkCommentNext, mkHdkCommentPrev :: PsSpan -> String -> (HdkComment, Token)
1368 mkHdkCommentNext loc str = (HdkCommentNext (mkHsDocString str), ITdocCommentNext str loc)
1369 mkHdkCommentPrev loc str = (HdkCommentPrev (mkHsDocString str), ITdocCommentPrev str loc)
1370
1371 mkHdkCommentNamed :: PsSpan -> String -> (HdkComment, Token)
1372 mkHdkCommentNamed loc str =
1373 let (name, rest) = break isSpace str
1374 in (HdkCommentNamed name (mkHsDocString rest), ITdocCommentNamed str loc)
1375
1376 mkHdkCommentSection :: PsSpan -> Int -> String -> (HdkComment, Token)
1377 mkHdkCommentSection loc n str =
1378 (HdkCommentSection n (mkHsDocString str), ITdocSection n str loc)
1379
1380 -- RULES pragmas turn on the forall and '.' keywords, and we turn them
1381 -- off again at the end of the pragma.
1382 rulePrag :: Action
1383 rulePrag span buf len = do
1384 setExts (.|. xbit InRulePragBit)
1385 let !src = lexemeToString buf len
1386 return (L span (ITrules_prag (SourceText src)))
1387
1388 -- When 'UsePosPragsBit' is not set, it is expected that we emit a token instead
1389 -- of updating the position in 'PState'
1390 linePrag :: Action
1391 linePrag span buf len = do
1392 usePosPrags <- getBit UsePosPragsBit
1393 if usePosPrags
1394 then begin line_prag2 span buf len
1395 else let !src = lexemeToString buf len
1396 in return (L span (ITline_prag (SourceText src)))
1397
1398 -- When 'UsePosPragsBit' is not set, it is expected that we emit a token instead
1399 -- of updating the position in 'PState'
1400 columnPrag :: Action
1401 columnPrag span buf len = do
1402 usePosPrags <- getBit UsePosPragsBit
1403 let !src = lexemeToString buf len
1404 if usePosPrags
1405 then begin column_prag span buf len
1406 else let !src = lexemeToString buf len
1407 in return (L span (ITcolumn_prag (SourceText src)))
1408
1409 endPrag :: Action
1410 endPrag span _buf _len = do
1411 setExts (.&. complement (xbit InRulePragBit))
1412 return (L span ITclose_prag)
1413
1414 -- docCommentEnd
1415 -------------------------------------------------------------------------------
1416 -- This function is quite tricky. We can't just return a new token, we also
1417 -- need to update the state of the parser. Why? Because the token is longer
1418 -- than what was lexed by Alex, and the lexToken function doesn't know this, so
1419 -- it writes the wrong token length to the parser state. This function is
1420 -- called afterwards, so it can just update the state.
1421
1422 commentEnd :: P (PsLocated Token)
1423 -> AlexInput
1424 -> String
1425 -> (String -> (Maybe HdkComment, Token))
1426 -> StringBuffer
1427 -> PsSpan
1428 -> P (PsLocated Token)
1429 commentEnd cont input commentAcc finalizeComment buf span = do
1430 setInput input
1431 let (AI loc nextBuf) = input
1432 comment = reverse commentAcc
1433 span' = mkPsSpan (psSpanStart span) loc
1434 last_len = byteDiff buf nextBuf
1435 span `seq` setLastToken span' last_len
1436 let (m_hdk_comment, hdk_token) = finalizeComment comment
1437 whenIsJust m_hdk_comment $ \hdk_comment ->
1438 P $ \s -> POk (s {hdk_comments = hdk_comments s `snocOL` L span' hdk_comment}) ()
1439 b <- getBit RawTokenStreamBit
1440 if b then return (L span' hdk_token)
1441 else cont
1442
1443 docCommentEnd :: AlexInput -> String -> (String -> (HdkComment, Token)) -> StringBuffer ->
1444 PsSpan -> P (PsLocated Token)
1445 docCommentEnd input commentAcc docType buf span = do
1446 let finalizeComment str =
1447 let (hdk_comment, token) = docType str
1448 in (Just hdk_comment, token)
1449 commentEnd lexToken input commentAcc finalizeComment buf span
1450
1451 errBrace :: AlexInput -> RealSrcSpan -> P a
1452 errBrace (AI end _) span =
1453 failLocMsgP (realSrcSpanStart span)
1454 (psRealLoc end)
1455 (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc (PsErrLexer LexUnterminatedComment LexErrKind_EOF))
1456
1457 open_brace, close_brace :: Action
1458 open_brace span _str _len = do
1459 ctx <- getContext
1460 setContext (NoLayout:ctx)
1461 return (L span ITocurly)
1462 close_brace span _str _len = do
1463 popContext
1464 return (L span ITccurly)
1465
1466 qvarid, qconid :: StringBuffer -> Int -> Token
1467 qvarid buf len = ITqvarid $! splitQualName buf len False
1468 qconid buf len = ITqconid $! splitQualName buf len False
1469
1470 splitQualName :: StringBuffer -> Int -> Bool -> (FastString,FastString)
1471 -- takes a StringBuffer and a length, and returns the module name
1472 -- and identifier parts of a qualified name. Splits at the *last* dot,
1473 -- because of hierarchical module names.
1474 --
1475 -- Throws an error if the name is not qualified.
1476 splitQualName orig_buf len parens = split orig_buf orig_buf
1477 where
1478 split buf dot_buf
1479 | orig_buf `byteDiff` buf >= len = done dot_buf
1480 | c == '.' = found_dot buf'
1481 | otherwise = split buf' dot_buf
1482 where
1483 (c,buf') = nextChar buf
1484
1485 -- careful, we might get names like M....
1486 -- so, if the character after the dot is not upper-case, this is
1487 -- the end of the qualifier part.
1488 found_dot buf -- buf points after the '.'
1489 | isUpper c = split buf' buf
1490 | otherwise = done buf
1491 where
1492 (c,buf') = nextChar buf
1493
1494 done dot_buf
1495 | qual_size < 1 = error "splitQualName got an unqualified named"
1496 | otherwise =
1497 (lexemeToFastString orig_buf (qual_size - 1),
1498 if parens -- Prelude.(+)
1499 then lexemeToFastString (stepOn dot_buf) (len - qual_size - 2)
1500 else lexemeToFastString dot_buf (len - qual_size))
1501 where
1502 qual_size = orig_buf `byteDiff` dot_buf
1503
1504 varid :: Action
1505 varid span buf len =
1506 case lookupUFM reservedWordsFM fs of
1507 Just (ITcase, _) -> do
1508 lastTk <- getLastTk
1509 keyword <- case lastTk of
1510 Strict.Just (L _ ITlam) -> do
1511 lambdaCase <- getBit LambdaCaseBit
1512 unless lambdaCase $ do
1513 pState <- getPState
1514 addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) PsErrLambdaCase
1515 return ITlcase
1516 _ -> return ITcase
1517 maybe_layout keyword
1518 return $ L span keyword
1519 Just (keyword, 0) -> do
1520 maybe_layout keyword
1521 return $ L span keyword
1522 Just (keyword, i) -> do
1523 exts <- getExts
1524 if exts .&. i /= 0
1525 then do
1526 maybe_layout keyword
1527 return $ L span keyword
1528 else
1529 return $ L span $ ITvarid fs
1530 Nothing ->
1531 return $ L span $ ITvarid fs
1532 where
1533 !fs = lexemeToFastString buf len
1534
1535 conid :: StringBuffer -> Int -> Token
1536 conid buf len = ITconid $! lexemeToFastString buf len
1537
1538 qvarsym, qconsym :: StringBuffer -> Int -> Token
1539 qvarsym buf len = ITqvarsym $! splitQualName buf len False
1540 qconsym buf len = ITqconsym $! splitQualName buf len False
1541
1542 -- See Note [Whitespace-sensitive operator parsing]
1543 varsym_prefix :: Action
1544 varsym_prefix = sym $ \span exts s ->
1545 let warnExtConflict errtok =
1546 do { addPsMessage (mkSrcSpanPs span) (PsWarnOperatorWhitespaceExtConflict errtok)
1547 ; return (ITvarsym s) }
1548 in
1549 if | s == fsLit "@" ->
1550 return ITtypeApp -- regardless of TypeApplications for better error messages
1551 | s == fsLit "%" ->
1552 if xtest LinearTypesBit exts
1553 then return ITpercent
1554 else warnExtConflict OperatorWhitespaceSymbol_PrefixPercent
1555 | s == fsLit "$" ->
1556 if xtest ThQuotesBit exts
1557 then return ITdollar
1558 else warnExtConflict OperatorWhitespaceSymbol_PrefixDollar
1559 | s == fsLit "$$" ->
1560 if xtest ThQuotesBit exts
1561 then return ITdollardollar
1562 else warnExtConflict OperatorWhitespaceSymbol_PrefixDollarDollar
1563 | s == fsLit "-" ->
1564 return ITprefixminus -- Only when LexicalNegation is on, otherwise we get ITminus
1565 -- and don't hit this code path. See Note [Minus tokens]
1566 | s == fsLit ".", OverloadedRecordDotBit `xtest` exts ->
1567 return (ITproj True) -- e.g. '(.x)'
1568 | s == fsLit "." -> return ITdot
1569 | s == fsLit "!" -> return ITbang
1570 | s == fsLit "~" -> return ITtilde
1571 | otherwise ->
1572 do { addPsMessage
1573 (mkSrcSpanPs span)
1574 (PsWarnOperatorWhitespace s OperatorWhitespaceOccurrence_Prefix)
1575 ; return (ITvarsym s) }
1576
1577 -- See Note [Whitespace-sensitive operator parsing]
1578 varsym_suffix :: Action
1579 varsym_suffix = sym $ \span _ s ->
1580 if | s == fsLit "@" -> failMsgP (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrSuffixAT)
1581 | s == fsLit "." -> return ITdot
1582 | otherwise ->
1583 do { addPsMessage
1584 (mkSrcSpanPs span)
1585 (PsWarnOperatorWhitespace s OperatorWhitespaceOccurrence_Suffix)
1586 ; return (ITvarsym s) }
1587
1588 -- See Note [Whitespace-sensitive operator parsing]
1589 varsym_tight_infix :: Action
1590 varsym_tight_infix = sym $ \span exts s ->
1591 if | s == fsLit "@" -> return ITat
1592 | s == fsLit ".", OverloadedRecordDotBit `xtest` exts -> return (ITproj False)
1593 | s == fsLit "." -> return ITdot
1594 | otherwise ->
1595 do { addPsMessage
1596 (mkSrcSpanPs span)
1597 (PsWarnOperatorWhitespace s (OperatorWhitespaceOccurrence_TightInfix))
1598 ; return (ITvarsym s) }
1599
1600 -- See Note [Whitespace-sensitive operator parsing]
1601 varsym_loose_infix :: Action
1602 varsym_loose_infix = sym $ \_ _ s ->
1603 if | s == fsLit "."
1604 -> return ITdot
1605 | otherwise
1606 -> return $ ITvarsym s
1607
1608 consym :: Action
1609 consym = sym (\_span _exts s -> return $ ITconsym s)
1610
1611 sym :: (PsSpan -> ExtsBitmap -> FastString -> P Token) -> Action
1612 sym con span buf len =
1613 case lookupUFM reservedSymsFM fs of
1614 Just (keyword, NormalSyntax, 0) -> do
1615 exts <- getExts
1616 if fs == fsLit "." &&
1617 exts .&. (xbit OverloadedRecordDotBit) /= 0 &&
1618 xtest OverloadedRecordDotBit exts
1619 then L span <$!> con span exts fs -- Process by varsym_*.
1620 else return $ L span keyword
1621 Just (keyword, NormalSyntax, i) -> do
1622 exts <- getExts
1623 if exts .&. i /= 0
1624 then return $ L span keyword
1625 else L span <$!> con span exts fs
1626 Just (keyword, UnicodeSyntax, 0) -> do
1627 exts <- getExts
1628 if xtest UnicodeSyntaxBit exts
1629 then return $ L span keyword
1630 else L span <$!> con span exts fs
1631 Just (keyword, UnicodeSyntax, i) -> do
1632 exts <- getExts
1633 if exts .&. i /= 0 && xtest UnicodeSyntaxBit exts
1634 then return $ L span keyword
1635 else L span <$!> con span exts fs
1636 Nothing -> do
1637 exts <- getExts
1638 L span <$!> con span exts fs
1639 where
1640 !fs = lexemeToFastString buf len
1641
1642 -- Variations on the integral numeric literal.
1643 tok_integral :: (SourceText -> Integer -> Token)
1644 -> (Integer -> Integer)
1645 -> Int -> Int
1646 -> (Integer, (Char -> Int))
1647 -> Action
1648 tok_integral itint transint transbuf translen (radix,char_to_int) span buf len = do
1649 numericUnderscores <- getBit NumericUnderscoresBit -- #14473
1650 let src = lexemeToString buf len
1651 when ((not numericUnderscores) && ('_' `elem` src)) $ do
1652 pState <- getPState
1653 let msg = PsErrNumUnderscores NumUnderscore_Integral
1654 addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
1655 return $ L span $ itint (SourceText src)
1656 $! transint $ parseUnsignedInteger
1657 (offsetBytes transbuf buf) (subtract translen len) radix char_to_int
1658
1659 tok_num :: (Integer -> Integer)
1660 -> Int -> Int
1661 -> (Integer, (Char->Int)) -> Action
1662 tok_num = tok_integral $ \case
1663 st@(SourceText ('-':_)) -> itint st (const True)
1664 st@(SourceText _) -> itint st (const False)
1665 st@NoSourceText -> itint st (< 0)
1666 where
1667 itint :: SourceText -> (Integer -> Bool) -> Integer -> Token
1668 itint !st is_negative !val = ITinteger ((IL st $! is_negative val) val)
1669
1670 tok_primint :: (Integer -> Integer)
1671 -> Int -> Int
1672 -> (Integer, (Char->Int)) -> Action
1673 tok_primint = tok_integral ITprimint
1674
1675
1676 tok_primword :: Int -> Int
1677 -> (Integer, (Char->Int)) -> Action
1678 tok_primword = tok_integral ITprimword positive
1679 positive, negative :: (Integer -> Integer)
1680 positive = id
1681 negative = negate
1682 decimal, octal, hexadecimal :: (Integer, Char -> Int)
1683 decimal = (10,octDecDigit)
1684 binary = (2,octDecDigit)
1685 octal = (8,octDecDigit)
1686 hexadecimal = (16,hexDigit)
1687
1688 -- readSignificandExponentPair can understand negative rationals, exponents, everything.
1689 tok_frac :: Int -> (String -> Token) -> Action
1690 tok_frac drop f span buf len = do
1691 numericUnderscores <- getBit NumericUnderscoresBit -- #14473
1692 let src = lexemeToString buf (len-drop)
1693 when ((not numericUnderscores) && ('_' `elem` src)) $ do
1694 pState <- getPState
1695 let msg = PsErrNumUnderscores NumUnderscore_Float
1696 addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
1697 return (L span $! (f $! src))
1698
1699 tok_float, tok_primfloat, tok_primdouble :: String -> Token
1700 tok_float str = ITrational $! readFractionalLit str
1701 tok_hex_float str = ITrational $! readHexFractionalLit str
1702 tok_primfloat str = ITprimfloat $! readFractionalLit str
1703 tok_primdouble str = ITprimdouble $! readFractionalLit str
1704
1705 readFractionalLit, readHexFractionalLit :: String -> FractionalLit
1706 readHexFractionalLit = readFractionalLitX readHexSignificandExponentPair Base2
1707 readFractionalLit = readFractionalLitX readSignificandExponentPair Base10
1708
1709 readFractionalLitX :: (String -> (Integer, Integer))
1710 -> FractionalExponentBase
1711 -> String -> FractionalLit
1712 readFractionalLitX readStr b str =
1713 mkSourceFractionalLit str is_neg i e b
1714 where
1715 is_neg = case str of
1716 '-' : _ -> True
1717 _ -> False
1718 (i, e) = readStr str
1719
1720 -- -----------------------------------------------------------------------------
1721 -- Layout processing
1722
1723 -- we're at the first token on a line, insert layout tokens if necessary
1724 do_bol :: Action
1725 do_bol span _str _len = do
1726 -- See Note [Nested comment line pragmas]
1727 b <- getBit InNestedCommentBit
1728 if b then return (L span ITcomment_line_prag) else do
1729 (pos, gen_semic) <- getOffside
1730 case pos of
1731 LT -> do
1732 --trace "layout: inserting '}'" $ do
1733 popContext
1734 -- do NOT pop the lex state, we might have a ';' to insert
1735 return (L span ITvccurly)
1736 EQ | gen_semic -> do
1737 --trace "layout: inserting ';'" $ do
1738 _ <- popLexState
1739 return (L span ITsemi)
1740 _ -> do
1741 _ <- popLexState
1742 lexToken
1743
1744 -- certain keywords put us in the "layout" state, where we might
1745 -- add an opening curly brace.
1746 maybe_layout :: Token -> P ()
1747 maybe_layout t = do -- If the alternative layout rule is enabled then
1748 -- we never create an implicit layout context here.
1749 -- Layout is handled XXX instead.
1750 -- The code for closing implicit contexts, or
1751 -- inserting implicit semi-colons, is therefore
1752 -- irrelevant as it only applies in an implicit
1753 -- context.
1754 alr <- getBit AlternativeLayoutRuleBit
1755 unless alr $ f t
1756 where f (ITdo _) = pushLexState layout_do
1757 f (ITmdo _) = pushLexState layout_do
1758 f ITof = pushLexState layout
1759 f ITlcase = pushLexState layout
1760 f ITlet = pushLexState layout
1761 f ITwhere = pushLexState layout
1762 f ITrec = pushLexState layout
1763 f ITif = pushLexState layout_if
1764 f _ = return ()
1765
1766 -- Pushing a new implicit layout context. If the indentation of the
1767 -- next token is not greater than the previous layout context, then
1768 -- Haskell 98 says that the new layout context should be empty; that is
1769 -- the lexer must generate {}.
1770 --
1771 -- We are slightly more lenient than this: when the new context is started
1772 -- by a 'do', then we allow the new context to be at the same indentation as
1773 -- the previous context. This is what the 'strict' argument is for.
1774 new_layout_context :: Bool -> Bool -> Token -> Action
1775 new_layout_context strict gen_semic tok span _buf len = do
1776 _ <- popLexState
1777 (AI l _) <- getInput
1778 let offset = srcLocCol (psRealLoc l) - len
1779 ctx <- getContext
1780 nondecreasing <- getBit NondecreasingIndentationBit
1781 let strict' = strict || not nondecreasing
1782 case ctx of
1783 Layout prev_off _ : _ |
1784 (strict' && prev_off >= offset ||
1785 not strict' && prev_off > offset) -> do
1786 -- token is indented to the left of the previous context.
1787 -- we must generate a {} sequence now.
1788 pushLexState layout_left
1789 return (L span tok)
1790 _ -> do setContext (Layout offset gen_semic : ctx)
1791 return (L span tok)
1792
1793 do_layout_left :: Action
1794 do_layout_left span _buf _len = do
1795 _ <- popLexState
1796 pushLexState bol -- we must be at the start of a line
1797 return (L span ITvccurly)
1798
1799 -- -----------------------------------------------------------------------------
1800 -- LINE pragmas
1801
1802 setLineAndFile :: Int -> Action
1803 setLineAndFile code (PsSpan span _) buf len = do
1804 let src = lexemeToString buf (len - 1) -- drop trailing quotation mark
1805 linenumLen = length $ head $ words src
1806 linenum = parseUnsignedInteger buf linenumLen 10 octDecDigit
1807 file = mkFastString $ go $ drop 1 $ dropWhile (/= '"') src
1808 -- skip everything through first quotation mark to get to the filename
1809 where go ('\\':c:cs) = c : go cs
1810 go (c:cs) = c : go cs
1811 go [] = []
1812 -- decode escapes in the filename. e.g. on Windows
1813 -- when our filenames have backslashes in, gcc seems to
1814 -- escape the backslashes. One symptom of not doing this
1815 -- is that filenames in error messages look a bit strange:
1816 -- C:\\foo\bar.hs
1817 -- only the first backslash is doubled, because we apply
1818 -- System.FilePath.normalise before printing out
1819 -- filenames and it does not remove duplicate
1820 -- backslashes after the drive letter (should it?).
1821 resetAlrLastLoc file
1822 setSrcLoc (mkRealSrcLoc file (fromIntegral linenum - 1) (srcSpanEndCol span))
1823 -- subtract one: the line number refers to the *following* line
1824 addSrcFile file
1825 _ <- popLexState
1826 pushLexState code
1827 lexToken
1828
1829 setColumn :: Action
1830 setColumn (PsSpan span _) buf len = do
1831 let column =
1832 case reads (lexemeToString buf len) of
1833 [(column, _)] -> column
1834 _ -> error "setColumn: expected integer" -- shouldn't happen
1835 setSrcLoc (mkRealSrcLoc (srcSpanFile span) (srcSpanEndLine span)
1836 (fromIntegral (column :: Integer)))
1837 _ <- popLexState
1838 lexToken
1839
1840 alrInitialLoc :: FastString -> RealSrcSpan
1841 alrInitialLoc file = mkRealSrcSpan loc loc
1842 where -- This is a hack to ensure that the first line in a file
1843 -- looks like it is after the initial location:
1844 loc = mkRealSrcLoc file (-1) (-1)
1845
1846 -- -----------------------------------------------------------------------------
1847 -- Options, includes and language pragmas.
1848
1849
1850 lex_string_prag :: (String -> Token) -> Action
1851 lex_string_prag mkTok = lex_string_prag_comment mkTok'
1852 where
1853 mkTok' s _ = mkTok s
1854
1855 lex_string_prag_comment :: (String -> PsSpan -> Token) -> Action
1856 lex_string_prag_comment mkTok span _buf _len
1857 = do input <- getInput
1858 start <- getParsedLoc
1859 l <- getLastLocComment
1860 tok <- go l [] input
1861 end <- getParsedLoc
1862 return (L (mkPsSpan start end) tok)
1863 where go l acc input
1864 = if isString input "#-}"
1865 then do setInput input
1866 return (mkTok (reverse acc) l)
1867 else case alexGetChar input of
1868 Just (c,i) -> go l (c:acc) i
1869 Nothing -> err input
1870 isString _ [] = True
1871 isString i (x:xs)
1872 = case alexGetChar i of
1873 Just (c,i') | c == x -> isString i' xs
1874 _other -> False
1875 err (AI end _) = failLocMsgP (realSrcSpanStart (psRealSpan span))
1876 (psRealLoc end)
1877 (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer LexUnterminatedOptions LexErrKind_EOF)
1878
1879 -- -----------------------------------------------------------------------------
1880 -- Strings & Chars
1881
1882 -- This stuff is horrible. I hates it.
1883
1884 lex_string_tok :: Action
1885 lex_string_tok span buf _len = do
1886 tok <- lex_string ""
1887 (AI end bufEnd) <- getInput
1888 let
1889 tok' = case tok of
1890 ITprimstring _ bs -> ITprimstring (SourceText src) bs
1891 ITstring _ s -> ITstring (SourceText src) s
1892 _ -> panic "lex_string_tok"
1893 src = lexemeToString buf (cur bufEnd - cur buf)
1894 return (L (mkPsSpan (psSpanStart span) end) tok')
1895
1896 lex_string :: String -> P Token
1897 lex_string s = do
1898 i <- getInput
1899 case alexGetChar' i of
1900 Nothing -> lit_error i
1901
1902 Just ('"',i) -> do
1903 setInput i
1904 let s' = reverse s
1905 magicHash <- getBit MagicHashBit
1906 if magicHash
1907 then do
1908 i <- getInput
1909 case alexGetChar' i of
1910 Just ('#',i) -> do
1911 setInput i
1912 when (any (> '\xFF') s') $ do
1913 pState <- getPState
1914 let msg = PsErrPrimStringInvalidChar
1915 let err = mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
1916 addError err
1917 return (ITprimstring (SourceText s') (unsafeMkByteString s'))
1918 _other ->
1919 return (ITstring (SourceText s') (mkFastString s'))
1920 else
1921 return (ITstring (SourceText s') (mkFastString s'))
1922
1923 Just ('\\',i)
1924 | Just ('&',i) <- next -> do
1925 setInput i; lex_string s
1926 | Just (c,i) <- next, c <= '\x7f' && is_space c -> do
1927 -- is_space only works for <= '\x7f' (#3751, #5425)
1928 setInput i; lex_stringgap s
1929 where next = alexGetChar' i
1930
1931 Just (c, i1) -> do
1932 case c of
1933 '\\' -> do setInput i1; c' <- lex_escape; lex_string (c':s)
1934 c | isAny c -> do setInput i1; lex_string (c:s)
1935 _other -> lit_error i
1936
1937 lex_stringgap :: String -> P Token
1938 lex_stringgap s = do
1939 i <- getInput
1940 c <- getCharOrFail i
1941 case c of
1942 '\\' -> lex_string s
1943 c | c <= '\x7f' && is_space c -> lex_stringgap s
1944 -- is_space only works for <= '\x7f' (#3751, #5425)
1945 _other -> lit_error i
1946
1947
1948 lex_char_tok :: Action
1949 -- Here we are basically parsing character literals, such as 'x' or '\n'
1950 -- but we additionally spot 'x and ''T, returning ITsimpleQuote and
1951 -- ITtyQuote respectively, but WITHOUT CONSUMING the x or T part
1952 -- (the parser does that).
1953 -- So we have to do two characters of lookahead: when we see 'x we need to
1954 -- see if there's a trailing quote
1955 lex_char_tok span buf _len = do -- We've seen '
1956 i1 <- getInput -- Look ahead to first character
1957 let loc = psSpanStart span
1958 case alexGetChar' i1 of
1959 Nothing -> lit_error i1
1960
1961 Just ('\'', i2@(AI end2 _)) -> do -- We've seen ''
1962 setInput i2
1963 return (L (mkPsSpan loc end2) ITtyQuote)
1964
1965 Just ('\\', i2@(AI _end2 _)) -> do -- We've seen 'backslash
1966 setInput i2
1967 lit_ch <- lex_escape
1968 i3 <- getInput
1969 mc <- getCharOrFail i3 -- Trailing quote
1970 if mc == '\'' then finish_char_tok buf loc lit_ch
1971 else lit_error i3
1972
1973 Just (c, i2@(AI _end2 _))
1974 | not (isAny c) -> lit_error i1
1975 | otherwise ->
1976
1977 -- We've seen 'x, where x is a valid character
1978 -- (i.e. not newline etc) but not a quote or backslash
1979 case alexGetChar' i2 of -- Look ahead one more character
1980 Just ('\'', i3) -> do -- We've seen 'x'
1981 setInput i3
1982 finish_char_tok buf loc c
1983 _other -> do -- We've seen 'x not followed by quote
1984 -- (including the possibility of EOF)
1985 -- Just parse the quote only
1986 let (AI end _) = i1
1987 return (L (mkPsSpan loc end) ITsimpleQuote)
1988
1989 finish_char_tok :: StringBuffer -> PsLoc -> Char -> P (PsLocated Token)
1990 finish_char_tok buf loc ch -- We've already seen the closing quote
1991 -- Just need to check for trailing #
1992 = do magicHash <- getBit MagicHashBit
1993 i@(AI end bufEnd) <- getInput
1994 let src = lexemeToString buf (cur bufEnd - cur buf)
1995 if magicHash then do
1996 case alexGetChar' i of
1997 Just ('#',i@(AI end _)) -> do
1998 setInput i
1999 return (L (mkPsSpan loc end)
2000 (ITprimchar (SourceText src) ch))
2001 _other ->
2002 return (L (mkPsSpan loc end)
2003 (ITchar (SourceText src) ch))
2004 else do
2005 return (L (mkPsSpan loc end) (ITchar (SourceText src) ch))
2006
2007 isAny :: Char -> Bool
2008 isAny c | c > '\x7f' = isPrint c
2009 | otherwise = is_any c
2010
2011 lex_escape :: P Char
2012 lex_escape = do
2013 i0 <- getInput
2014 c <- getCharOrFail i0
2015 case c of
2016 'a' -> return '\a'
2017 'b' -> return '\b'
2018 'f' -> return '\f'
2019 'n' -> return '\n'
2020 'r' -> return '\r'
2021 't' -> return '\t'
2022 'v' -> return '\v'
2023 '\\' -> return '\\'
2024 '"' -> return '\"'
2025 '\'' -> return '\''
2026 '^' -> do i1 <- getInput
2027 c <- getCharOrFail i1
2028 if c >= '@' && c <= '_'
2029 then return (chr (ord c - ord '@'))
2030 else lit_error i1
2031
2032 'x' -> readNum is_hexdigit 16 hexDigit
2033 'o' -> readNum is_octdigit 8 octDecDigit
2034 x | is_decdigit x -> readNum2 is_decdigit 10 octDecDigit (octDecDigit x)
2035
2036 c1 -> do
2037 i <- getInput
2038 case alexGetChar' i of
2039 Nothing -> lit_error i0
2040 Just (c2,i2) ->
2041 case alexGetChar' i2 of
2042 Nothing -> do lit_error i0
2043 Just (c3,i3) ->
2044 let str = [c1,c2,c3] in
2045 case [ (c,rest) | (p,c) <- silly_escape_chars,
2046 Just rest <- [stripPrefix p str] ] of
2047 (escape_char,[]):_ -> do
2048 setInput i3
2049 return escape_char
2050 (escape_char,_:_):_ -> do
2051 setInput i2
2052 return escape_char
2053 [] -> lit_error i0
2054
2055 readNum :: (Char -> Bool) -> Int -> (Char -> Int) -> P Char
2056 readNum is_digit base conv = do
2057 i <- getInput
2058 c <- getCharOrFail i
2059 if is_digit c
2060 then readNum2 is_digit base conv (conv c)
2061 else lit_error i
2062
2063 readNum2 :: (Char -> Bool) -> Int -> (Char -> Int) -> Int -> P Char
2064 readNum2 is_digit base conv i = do
2065 input <- getInput
2066 read i input
2067 where read i input = do
2068 case alexGetChar' input of
2069 Just (c,input') | is_digit c -> do
2070 let i' = i*base + conv c
2071 if i' > 0x10ffff
2072 then setInput input >> lexError LexNumEscapeRange
2073 else read i' input'
2074 _other -> do
2075 setInput input; return (chr i)
2076
2077
2078 silly_escape_chars :: [(String, Char)]
2079 silly_escape_chars = [
2080 ("NUL", '\NUL'),
2081 ("SOH", '\SOH'),
2082 ("STX", '\STX'),
2083 ("ETX", '\ETX'),
2084 ("EOT", '\EOT'),
2085 ("ENQ", '\ENQ'),
2086 ("ACK", '\ACK'),
2087 ("BEL", '\BEL'),
2088 ("BS", '\BS'),
2089 ("HT", '\HT'),
2090 ("LF", '\LF'),
2091 ("VT", '\VT'),
2092 ("FF", '\FF'),
2093 ("CR", '\CR'),
2094 ("SO", '\SO'),
2095 ("SI", '\SI'),
2096 ("DLE", '\DLE'),
2097 ("DC1", '\DC1'),
2098 ("DC2", '\DC2'),
2099 ("DC3", '\DC3'),
2100 ("DC4", '\DC4'),
2101 ("NAK", '\NAK'),
2102 ("SYN", '\SYN'),
2103 ("ETB", '\ETB'),
2104 ("CAN", '\CAN'),
2105 ("EM", '\EM'),
2106 ("SUB", '\SUB'),
2107 ("ESC", '\ESC'),
2108 ("FS", '\FS'),
2109 ("GS", '\GS'),
2110 ("RS", '\RS'),
2111 ("US", '\US'),
2112 ("SP", '\SP'),
2113 ("DEL", '\DEL')
2114 ]
2115
2116 -- before calling lit_error, ensure that the current input is pointing to
2117 -- the position of the error in the buffer. This is so that we can report
2118 -- a correct location to the user, but also so we can detect UTF-8 decoding
2119 -- errors if they occur.
2120 lit_error :: AlexInput -> P a
2121 lit_error i = do setInput i; lexError LexStringCharLit
2122
2123 getCharOrFail :: AlexInput -> P Char
2124 getCharOrFail i = do
2125 case alexGetChar' i of
2126 Nothing -> lexError LexStringCharLitEOF
2127 Just (c,i) -> do setInput i; return c
2128
2129 -- -----------------------------------------------------------------------------
2130 -- QuasiQuote
2131
2132 lex_qquasiquote_tok :: Action
2133 lex_qquasiquote_tok span buf len = do
2134 let (qual, quoter) = splitQualName (stepOn buf) (len - 2) False
2135 quoteStart <- getParsedLoc
2136 quote <- lex_quasiquote (psRealLoc quoteStart) ""
2137 end <- getParsedLoc
2138 return (L (mkPsSpan (psSpanStart span) end)
2139 (ITqQuasiQuote (qual,
2140 quoter,
2141 mkFastString (reverse quote),
2142 mkPsSpan quoteStart end)))
2143
2144 lex_quasiquote_tok :: Action
2145 lex_quasiquote_tok span buf len = do
2146 let quoter = tail (lexemeToString buf (len - 1))
2147 -- 'tail' drops the initial '[',
2148 -- while the -1 drops the trailing '|'
2149 quoteStart <- getParsedLoc
2150 quote <- lex_quasiquote (psRealLoc quoteStart) ""
2151 end <- getParsedLoc
2152 return (L (mkPsSpan (psSpanStart span) end)
2153 (ITquasiQuote (mkFastString quoter,
2154 mkFastString (reverse quote),
2155 mkPsSpan quoteStart end)))
2156
2157 lex_quasiquote :: RealSrcLoc -> String -> P String
2158 lex_quasiquote start s = do
2159 i <- getInput
2160 case alexGetChar' i of
2161 Nothing -> quasiquote_error start
2162
2163 -- NB: The string "|]" terminates the quasiquote,
2164 -- with absolutely no escaping. See the extensive
2165 -- discussion on #5348 for why there is no
2166 -- escape handling.
2167 Just ('|',i)
2168 | Just (']',i) <- alexGetChar' i
2169 -> do { setInput i; return s }
2170
2171 Just (c, i) -> do
2172 setInput i; lex_quasiquote start (c : s)
2173
2174 quasiquote_error :: RealSrcLoc -> P a
2175 quasiquote_error start = do
2176 (AI end buf) <- getInput
2177 reportLexError start (psRealLoc end) buf
2178 (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc (PsErrLexer LexUnterminatedQQ k))
2179
2180 -- -----------------------------------------------------------------------------
2181 -- Warnings
2182
2183 warnTab :: Action
2184 warnTab srcspan _buf _len = do
2185 addTabWarning (psRealSpan srcspan)
2186 lexToken
2187
2188 warnThen :: PsMessage -> Action -> Action
2189 warnThen warning action srcspan buf len = do
2190 addPsMessage (RealSrcSpan (psRealSpan srcspan) Strict.Nothing) warning
2191 action srcspan buf len
2192
2193 -- -----------------------------------------------------------------------------
2194 -- The Parse Monad
2195
2196 -- | Do we want to generate ';' layout tokens? In some cases we just want to
2197 -- generate '}', e.g. in MultiWayIf we don't need ';'s because '|' separates
2198 -- alternatives (unlike a `case` expression where we need ';' to as a separator
2199 -- between alternatives).
2200 type GenSemic = Bool
2201
2202 generateSemic, dontGenerateSemic :: GenSemic
2203 generateSemic = True
2204 dontGenerateSemic = False
2205
2206 data LayoutContext
2207 = NoLayout
2208 | Layout !Int !GenSemic
2209 deriving Show
2210
2211 -- | The result of running a parser.
2212 newtype ParseResult a = PR (# (# PState, a #) | PState #)
2213
2214 -- | The parser has consumed a (possibly empty) prefix of the input and produced
2215 -- a result. Use 'getPsMessages' to check for accumulated warnings and non-fatal
2216 -- errors.
2217 --
2218 -- The carried parsing state can be used to resume parsing.
2219 pattern POk :: PState -> a -> ParseResult a
2220 pattern POk s a = PR (# (# s , a #) | #)
2221
2222 -- | The parser has consumed a (possibly empty) prefix of the input and failed.
2223 --
2224 -- The carried parsing state can be used to resume parsing. It is the state
2225 -- right before failure, including the fatal parse error. 'getPsMessages' and
2226 -- 'getPsErrorMessages' must return a non-empty bag of errors.
2227 pattern PFailed :: PState -> ParseResult a
2228 pattern PFailed s = PR (# | s #)
2229
2230 {-# COMPLETE POk, PFailed #-}
2231
2232 -- | Test whether a 'WarningFlag' is set
2233 warnopt :: WarningFlag -> ParserOpts -> Bool
2234 warnopt f options = f `EnumSet.member` pWarningFlags options
2235
2236 -- | Parser options.
2237 --
2238 -- See 'mkParserOpts' to construct this.
2239 data ParserOpts = ParserOpts
2240 { pExtsBitmap :: !ExtsBitmap -- ^ bitmap of permitted extensions
2241 , pDiagOpts :: !DiagOpts
2242 -- ^ Options to construct diagnostic messages.
2243 , pSupportedExts :: [String]
2244 -- ^ supported extensions (only used for suggestions in error messages)
2245 }
2246
2247 pWarningFlags :: ParserOpts -> EnumSet WarningFlag
2248 pWarningFlags opts = diag_warning_flags (pDiagOpts opts)
2249
2250 -- | Haddock comment as produced by the lexer. These are accumulated in
2251 -- 'PState' and then processed in "GHC.Parser.PostProcess.Haddock".
2252 data HdkComment
2253 = HdkCommentNext HsDocString
2254 | HdkCommentPrev HsDocString
2255 | HdkCommentNamed String HsDocString
2256 | HdkCommentSection Int HsDocString
2257 deriving Show
2258
2259 data PState = PState {
2260 buffer :: StringBuffer,
2261 options :: ParserOpts,
2262 warnings :: Messages PsMessage,
2263 errors :: Messages PsMessage,
2264 tab_first :: Strict.Maybe RealSrcSpan, -- pos of first tab warning in the file
2265 tab_count :: !Word, -- number of tab warnings in the file
2266 last_tk :: Strict.Maybe (PsLocated Token), -- last non-comment token
2267 prev_loc :: PsSpan, -- pos of previous token, including comments,
2268 prev_loc2 :: PsSpan, -- pos of two back token, including comments,
2269 -- see Note [PsSpan in Comments]
2270 last_loc :: PsSpan, -- pos of current token
2271 last_len :: !Int, -- len of current token
2272 loc :: PsLoc, -- current loc (end of prev token + 1)
2273 context :: [LayoutContext],
2274 lex_state :: [Int],
2275 srcfiles :: [FastString],
2276 -- Used in the alternative layout rule:
2277 -- These tokens are the next ones to be sent out. They are
2278 -- just blindly emitted, without the rule looking at them again:
2279 alr_pending_implicit_tokens :: [PsLocated Token],
2280 -- This is the next token to be considered or, if it is Nothing,
2281 -- we need to get the next token from the input stream:
2282 alr_next_token :: Maybe (PsLocated Token),
2283 -- This is what we consider to be the location of the last token
2284 -- emitted:
2285 alr_last_loc :: PsSpan,
2286 -- The stack of layout contexts:
2287 alr_context :: [ALRContext],
2288 -- Are we expecting a '{'? If it's Just, then the ALRLayout tells
2289 -- us what sort of layout the '{' will open:
2290 alr_expecting_ocurly :: Maybe ALRLayout,
2291 -- Have we just had the '}' for a let block? If so, than an 'in'
2292 -- token doesn't need to close anything:
2293 alr_justClosedExplicitLetBlock :: Bool,
2294
2295 -- The next three are used to implement Annotations giving the
2296 -- locations of 'noise' tokens in the source, so that users of
2297 -- the GHC API can do source to source conversions.
2298 -- See note [exact print annotations] in GHC.Parser.Annotation
2299 eof_pos :: Strict.Maybe (Strict.Pair RealSrcSpan RealSrcSpan), -- pos, gap to prior token
2300 header_comments :: Strict.Maybe [LEpaComment],
2301 comment_q :: [LEpaComment],
2302
2303 -- Haddock comments accumulated in ascending order of their location
2304 -- (BufPos). We use OrdList to get O(1) snoc.
2305 --
2306 -- See Note [Adding Haddock comments to the syntax tree] in GHC.Parser.PostProcess.Haddock
2307 hdk_comments :: OrdList (PsLocated HdkComment)
2308 }
2309 -- last_loc and last_len are used when generating error messages,
2310 -- and in pushCurrentContext only. Sigh, if only Happy passed the
2311 -- current token to happyError, we could at least get rid of last_len.
2312 -- Getting rid of last_loc would require finding another way to
2313 -- implement pushCurrentContext (which is only called from one place).
2314
2315 -- AZ question: setLastToken which sets last_loc and last_len
2316 -- is called whan processing AlexToken, immediately prior to
2317 -- calling the action in the token. So from the perspective
2318 -- of the action, it is the *current* token. Do I understand
2319 -- correctly?
2320
2321 data ALRContext = ALRNoLayout Bool{- does it contain commas? -}
2322 Bool{- is it a 'let' block? -}
2323 | ALRLayout ALRLayout Int
2324 data ALRLayout = ALRLayoutLet
2325 | ALRLayoutWhere
2326 | ALRLayoutOf
2327 | ALRLayoutDo
2328
2329 -- | The parsing monad, isomorphic to @StateT PState Maybe@.
2330 newtype P a = P { unP :: PState -> ParseResult a }
2331
2332 instance Functor P where
2333 fmap = liftM
2334
2335 instance Applicative P where
2336 pure = returnP
2337 (<*>) = ap
2338
2339 instance Monad P where
2340 (>>=) = thenP
2341
2342 returnP :: a -> P a
2343 returnP a = a `seq` (P $ \s -> POk s a)
2344
2345 thenP :: P a -> (a -> P b) -> P b
2346 (P m) `thenP` k = P $ \ s ->
2347 case m s of
2348 POk s1 a -> (unP (k a)) s1
2349 PFailed s1 -> PFailed s1
2350
2351 failMsgP :: (SrcSpan -> MsgEnvelope PsMessage) -> P a
2352 failMsgP f = do
2353 pState <- getPState
2354 addFatalError (f (mkSrcSpanPs (last_loc pState)))
2355
2356 failLocMsgP :: RealSrcLoc -> RealSrcLoc -> (SrcSpan -> MsgEnvelope PsMessage) -> P a
2357 failLocMsgP loc1 loc2 f =
2358 addFatalError (f (RealSrcSpan (mkRealSrcSpan loc1 loc2) Strict.Nothing))
2359
2360 getPState :: P PState
2361 getPState = P $ \s -> POk s s
2362
2363 getExts :: P ExtsBitmap
2364 getExts = P $ \s -> POk s (pExtsBitmap . options $ s)
2365
2366 setExts :: (ExtsBitmap -> ExtsBitmap) -> P ()
2367 setExts f = P $ \s -> POk s {
2368 options =
2369 let p = options s
2370 in p { pExtsBitmap = f (pExtsBitmap p) }
2371 } ()
2372
2373 setSrcLoc :: RealSrcLoc -> P ()
2374 setSrcLoc new_loc =
2375 P $ \s@(PState{ loc = PsLoc _ buf_loc }) ->
2376 POk s{ loc = PsLoc new_loc buf_loc } ()
2377
2378 getRealSrcLoc :: P RealSrcLoc
2379 getRealSrcLoc = P $ \s@(PState{ loc=loc }) -> POk s (psRealLoc loc)
2380
2381 getParsedLoc :: P PsLoc
2382 getParsedLoc = P $ \s@(PState{ loc=loc }) -> POk s loc
2383
2384 addSrcFile :: FastString -> P ()
2385 addSrcFile f = P $ \s -> POk s{ srcfiles = f : srcfiles s } ()
2386
2387 setEofPos :: RealSrcSpan -> RealSrcSpan -> P ()
2388 setEofPos span gap = P $ \s -> POk s{ eof_pos = Strict.Just (span `Strict.And` gap) } ()
2389
2390 setLastToken :: PsSpan -> Int -> P ()
2391 setLastToken loc len = P $ \s -> POk s {
2392 last_loc=loc,
2393 last_len=len
2394 } ()
2395
2396 setLastTk :: PsLocated Token -> P ()
2397 setLastTk tk@(L l _) = P $ \s -> POk s { last_tk = Strict.Just tk
2398 , prev_loc = l
2399 , prev_loc2 = prev_loc s} ()
2400
2401 setLastComment :: PsLocated Token -> P ()
2402 setLastComment (L l _) = P $ \s -> POk s { prev_loc = l
2403 , prev_loc2 = prev_loc s} ()
2404
2405 getLastTk :: P (Strict.Maybe (PsLocated Token))
2406 getLastTk = P $ \s@(PState { last_tk = last_tk }) -> POk s last_tk
2407
2408 -- see Note [PsSpan in Comments]
2409 getLastLocComment :: P PsSpan
2410 getLastLocComment = P $ \s@(PState { prev_loc = prev_loc }) -> POk s prev_loc
2411
2412 -- see Note [PsSpan in Comments]
2413 getLastLocEof :: P PsSpan
2414 getLastLocEof = P $ \s@(PState { prev_loc2 = prev_loc2 }) -> POk s prev_loc2
2415
2416 getLastLoc :: P PsSpan
2417 getLastLoc = P $ \s@(PState { last_loc = last_loc }) -> POk s last_loc
2418
2419 data AlexInput = AI !PsLoc !StringBuffer
2420
2421 {-
2422 Note [Unicode in Alex]
2423 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2424 Although newer versions of Alex support unicode, this grammar is processed with
2425 the old style '--latin1' behaviour. This means that when implementing the
2426 functions
2427
2428 alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
2429 alexInputPrevChar :: AlexInput -> Char
2430
2431 which Alex uses to take apart our 'AlexInput', we must
2432
2433 * return a latin1 character in the 'Word8' that 'alexGetByte' expects
2434 * return a latin1 character in 'alexInputPrevChar'.
2435
2436 We handle this in 'adjustChar' by squishing entire classes of unicode
2437 characters into single bytes.
2438 -}
2439
2440 {-# INLINE adjustChar #-}
2441 adjustChar :: Char -> Word8
2442 adjustChar c = fromIntegral $ ord adj_c
2443 where non_graphic = '\x00'
2444 upper = '\x01'
2445 lower = '\x02'
2446 digit = '\x03'
2447 symbol = '\x04'
2448 space = '\x05'
2449 other_graphic = '\x06'
2450 uniidchar = '\x07'
2451
2452 adj_c
2453 | c <= '\x07' = non_graphic
2454 | c <= '\x7f' = c
2455 -- Alex doesn't handle Unicode, so when Unicode
2456 -- character is encountered we output these values
2457 -- with the actual character value hidden in the state.
2458 | otherwise =
2459 -- NB: The logic behind these definitions is also reflected
2460 -- in "GHC.Utils.Lexeme"
2461 -- Any changes here should likely be reflected there.
2462
2463 case generalCategory c of
2464 UppercaseLetter -> upper
2465 LowercaseLetter -> lower
2466 TitlecaseLetter -> upper
2467 ModifierLetter -> uniidchar -- see #10196
2468 OtherLetter -> lower -- see #1103
2469 NonSpacingMark -> uniidchar -- see #7650
2470 SpacingCombiningMark -> other_graphic
2471 EnclosingMark -> other_graphic
2472 DecimalNumber -> digit
2473 LetterNumber -> digit
2474 OtherNumber -> digit -- see #4373
2475 ConnectorPunctuation -> symbol
2476 DashPunctuation -> symbol
2477 OpenPunctuation -> other_graphic
2478 ClosePunctuation -> other_graphic
2479 InitialQuote -> other_graphic
2480 FinalQuote -> other_graphic
2481 OtherPunctuation -> symbol
2482 MathSymbol -> symbol
2483 CurrencySymbol -> symbol
2484 ModifierSymbol -> symbol
2485 OtherSymbol -> symbol
2486 Space -> space
2487 _other -> non_graphic
2488
2489 -- Getting the previous 'Char' isn't enough here - we need to convert it into
2490 -- the same format that 'alexGetByte' would have produced.
2491 --
2492 -- See Note [Unicode in Alex] and #13986.
2493 alexInputPrevChar :: AlexInput -> Char
2494 alexInputPrevChar (AI _ buf) = chr (fromIntegral (adjustChar pc))
2495 where pc = prevChar buf '\n'
2496
2497 -- backwards compatibility for Alex 2.x
2498 alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
2499 alexGetChar inp = case alexGetByte inp of
2500 Nothing -> Nothing
2501 Just (b,i) -> c `seq` Just (c,i)
2502 where c = chr $ fromIntegral b
2503
2504 -- See Note [Unicode in Alex]
2505 alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
2506 alexGetByte (AI loc s)
2507 | atEnd s = Nothing
2508 | otherwise = byte `seq` loc' `seq` s' `seq`
2509 --trace (show (ord c)) $
2510 Just (byte, (AI loc' s'))
2511 where (c,s') = nextChar s
2512 loc' = advancePsLoc loc c
2513 byte = adjustChar c
2514
2515 -- This version does not squash unicode characters, it is used when
2516 -- lexing strings.
2517 alexGetChar' :: AlexInput -> Maybe (Char,AlexInput)
2518 alexGetChar' (AI loc s)
2519 | atEnd s = Nothing
2520 | otherwise = c `seq` loc' `seq` s' `seq`
2521 --trace (show (ord c)) $
2522 Just (c, (AI loc' s'))
2523 where (c,s') = nextChar s
2524 loc' = advancePsLoc loc c
2525
2526 getInput :: P AlexInput
2527 getInput = P $ \s@PState{ loc=l, buffer=b } -> POk s (AI l b)
2528
2529 setInput :: AlexInput -> P ()
2530 setInput (AI l b) = P $ \s -> POk s{ loc=l, buffer=b } ()
2531
2532 nextIsEOF :: P Bool
2533 nextIsEOF = do
2534 AI _ s <- getInput
2535 return $ atEnd s
2536
2537 pushLexState :: Int -> P ()
2538 pushLexState ls = P $ \s@PState{ lex_state=l } -> POk s{lex_state=ls:l} ()
2539
2540 popLexState :: P Int
2541 popLexState = P $ \s@PState{ lex_state=ls:l } -> POk s{ lex_state=l } ls
2542
2543 getLexState :: P Int
2544 getLexState = P $ \s@PState{ lex_state=ls:_ } -> POk s ls
2545
2546 popNextToken :: P (Maybe (PsLocated Token))
2547 popNextToken
2548 = P $ \s@PState{ alr_next_token = m } ->
2549 POk (s {alr_next_token = Nothing}) m
2550
2551 activeContext :: P Bool
2552 activeContext = do
2553 ctxt <- getALRContext
2554 expc <- getAlrExpectingOCurly
2555 impt <- implicitTokenPending
2556 case (ctxt,expc) of
2557 ([],Nothing) -> return impt
2558 _other -> return True
2559
2560 resetAlrLastLoc :: FastString -> P ()
2561 resetAlrLastLoc file =
2562 P $ \s@(PState {alr_last_loc = PsSpan _ buf_span}) ->
2563 POk s{ alr_last_loc = PsSpan (alrInitialLoc file) buf_span } ()
2564
2565 setAlrLastLoc :: PsSpan -> P ()
2566 setAlrLastLoc l = P $ \s -> POk (s {alr_last_loc = l}) ()
2567
2568 getAlrLastLoc :: P PsSpan
2569 getAlrLastLoc = P $ \s@(PState {alr_last_loc = l}) -> POk s l
2570
2571 getALRContext :: P [ALRContext]
2572 getALRContext = P $ \s@(PState {alr_context = cs}) -> POk s cs
2573
2574 setALRContext :: [ALRContext] -> P ()
2575 setALRContext cs = P $ \s -> POk (s {alr_context = cs}) ()
2576
2577 getJustClosedExplicitLetBlock :: P Bool
2578 getJustClosedExplicitLetBlock
2579 = P $ \s@(PState {alr_justClosedExplicitLetBlock = b}) -> POk s b
2580
2581 setJustClosedExplicitLetBlock :: Bool -> P ()
2582 setJustClosedExplicitLetBlock b
2583 = P $ \s -> POk (s {alr_justClosedExplicitLetBlock = b}) ()
2584
2585 setNextToken :: PsLocated Token -> P ()
2586 setNextToken t = P $ \s -> POk (s {alr_next_token = Just t}) ()
2587
2588 implicitTokenPending :: P Bool
2589 implicitTokenPending
2590 = P $ \s@PState{ alr_pending_implicit_tokens = ts } ->
2591 case ts of
2592 [] -> POk s False
2593 _ -> POk s True
2594
2595 popPendingImplicitToken :: P (Maybe (PsLocated Token))
2596 popPendingImplicitToken
2597 = P $ \s@PState{ alr_pending_implicit_tokens = ts } ->
2598 case ts of
2599 [] -> POk s Nothing
2600 (t : ts') -> POk (s {alr_pending_implicit_tokens = ts'}) (Just t)
2601
2602 setPendingImplicitTokens :: [PsLocated Token] -> P ()
2603 setPendingImplicitTokens ts = P $ \s -> POk (s {alr_pending_implicit_tokens = ts}) ()
2604
2605 getAlrExpectingOCurly :: P (Maybe ALRLayout)
2606 getAlrExpectingOCurly = P $ \s@(PState {alr_expecting_ocurly = b}) -> POk s b
2607
2608 setAlrExpectingOCurly :: Maybe ALRLayout -> P ()
2609 setAlrExpectingOCurly b = P $ \s -> POk (s {alr_expecting_ocurly = b}) ()
2610
2611 -- | For reasons of efficiency, boolean parsing flags (eg, language extensions
2612 -- or whether we are currently in a @RULE@ pragma) are represented by a bitmap
2613 -- stored in a @Word64@.
2614 type ExtsBitmap = Word64
2615
2616 xbit :: ExtBits -> ExtsBitmap
2617 xbit = bit . fromEnum
2618
2619 xtest :: ExtBits -> ExtsBitmap -> Bool
2620 xtest ext xmap = testBit xmap (fromEnum ext)
2621
2622 xset :: ExtBits -> ExtsBitmap -> ExtsBitmap
2623 xset ext xmap = setBit xmap (fromEnum ext)
2624
2625 xunset :: ExtBits -> ExtsBitmap -> ExtsBitmap
2626 xunset ext xmap = clearBit xmap (fromEnum ext)
2627
2628 -- | Various boolean flags, mostly language extensions, that impact lexing and
2629 -- parsing. Note that a handful of these can change during lexing/parsing.
2630 data ExtBits
2631 -- Flags that are constant once parsing starts
2632 = FfiBit
2633 | InterruptibleFfiBit
2634 | CApiFfiBit
2635 | ArrowsBit
2636 | ThBit
2637 | ThQuotesBit
2638 | IpBit
2639 | OverloadedLabelsBit -- #x overloaded labels
2640 | ExplicitForallBit -- the 'forall' keyword
2641 | BangPatBit -- Tells the parser to understand bang-patterns
2642 -- (doesn't affect the lexer)
2643 | PatternSynonymsBit -- pattern synonyms
2644 | HaddockBit-- Lex and parse Haddock comments
2645 | MagicHashBit -- "#" in both functions and operators
2646 | RecursiveDoBit -- mdo
2647 | QualifiedDoBit -- .do and .mdo
2648 | UnicodeSyntaxBit -- the forall symbol, arrow symbols, etc
2649 | UnboxedTuplesBit -- (# and #)
2650 | UnboxedSumsBit -- (# and #)
2651 | DatatypeContextsBit
2652 | MonadComprehensionsBit
2653 | TransformComprehensionsBit
2654 | QqBit -- enable quasiquoting
2655 | RawTokenStreamBit -- producing a token stream with all comments included
2656 | AlternativeLayoutRuleBit
2657 | ALRTransitionalBit
2658 | RelaxedLayoutBit
2659 | NondecreasingIndentationBit
2660 | SafeHaskellBit
2661 | TraditionalRecordSyntaxBit
2662 | ExplicitNamespacesBit
2663 | LambdaCaseBit
2664 | BinaryLiteralsBit
2665 | NegativeLiteralsBit
2666 | HexFloatLiteralsBit
2667 | StaticPointersBit
2668 | NumericUnderscoresBit
2669 | StarIsTypeBit
2670 | BlockArgumentsBit
2671 | NPlusKPatternsBit
2672 | DoAndIfThenElseBit
2673 | MultiWayIfBit
2674 | GadtSyntaxBit
2675 | ImportQualifiedPostBit
2676 | LinearTypesBit
2677 | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit]
2678 | OverloadedRecordDotBit
2679 | OverloadedRecordUpdateBit
2680
2681 -- Flags that are updated once parsing starts
2682 | InRulePragBit
2683 | InNestedCommentBit -- See Note [Nested comment line pragmas]
2684 | UsePosPragsBit
2685 -- ^ If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}'
2686 -- update the internal position. Otherwise, those pragmas are lexed as
2687 -- tokens of their own.
2688 deriving Enum
2689
2690 {-# INLINE mkParserOpts #-}
2691 mkParserOpts
2692 :: EnumSet LangExt.Extension -- ^ permitted language extensions enabled
2693 -> DiagOpts -- ^ diagnostic options
2694 -> [String] -- ^ Supported Languages and Extensions
2695 -> Bool -- ^ are safe imports on?
2696 -> Bool -- ^ keeping Haddock comment tokens
2697 -> Bool -- ^ keep regular comment tokens
2698
2699 -> Bool
2700 -- ^ If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update
2701 -- the internal position kept by the parser. Otherwise, those pragmas are
2702 -- lexed as 'ITline_prag' and 'ITcolumn_prag' tokens.
2703
2704 -> ParserOpts
2705 -- ^ Given exactly the information needed, set up the 'ParserOpts'
2706 mkParserOpts extensionFlags diag_opts supported
2707 safeImports isHaddock rawTokStream usePosPrags =
2708 ParserOpts {
2709 pDiagOpts = diag_opts
2710 , pExtsBitmap = safeHaskellBit .|. langExtBits .|. optBits
2711 , pSupportedExts = supported
2712 }
2713 where
2714 safeHaskellBit = SafeHaskellBit `setBitIf` safeImports
2715 langExtBits =
2716 FfiBit `xoptBit` LangExt.ForeignFunctionInterface
2717 .|. InterruptibleFfiBit `xoptBit` LangExt.InterruptibleFFI
2718 .|. CApiFfiBit `xoptBit` LangExt.CApiFFI
2719 .|. ArrowsBit `xoptBit` LangExt.Arrows
2720 .|. ThBit `xoptBit` LangExt.TemplateHaskell
2721 .|. ThQuotesBit `xoptBit` LangExt.TemplateHaskellQuotes
2722 .|. QqBit `xoptBit` LangExt.QuasiQuotes
2723 .|. IpBit `xoptBit` LangExt.ImplicitParams
2724 .|. OverloadedLabelsBit `xoptBit` LangExt.OverloadedLabels
2725 .|. ExplicitForallBit `xoptBit` LangExt.ExplicitForAll
2726 .|. BangPatBit `xoptBit` LangExt.BangPatterns
2727 .|. MagicHashBit `xoptBit` LangExt.MagicHash
2728 .|. RecursiveDoBit `xoptBit` LangExt.RecursiveDo
2729 .|. QualifiedDoBit `xoptBit` LangExt.QualifiedDo
2730 .|. UnicodeSyntaxBit `xoptBit` LangExt.UnicodeSyntax
2731 .|. UnboxedTuplesBit `xoptBit` LangExt.UnboxedTuples
2732 .|. UnboxedSumsBit `xoptBit` LangExt.UnboxedSums
2733 .|. DatatypeContextsBit `xoptBit` LangExt.DatatypeContexts
2734 .|. TransformComprehensionsBit `xoptBit` LangExt.TransformListComp
2735 .|. MonadComprehensionsBit `xoptBit` LangExt.MonadComprehensions
2736 .|. AlternativeLayoutRuleBit `xoptBit` LangExt.AlternativeLayoutRule
2737 .|. ALRTransitionalBit `xoptBit` LangExt.AlternativeLayoutRuleTransitional
2738 .|. RelaxedLayoutBit `xoptBit` LangExt.RelaxedLayout
2739 .|. NondecreasingIndentationBit `xoptBit` LangExt.NondecreasingIndentation
2740 .|. TraditionalRecordSyntaxBit `xoptBit` LangExt.TraditionalRecordSyntax
2741 .|. ExplicitNamespacesBit `xoptBit` LangExt.ExplicitNamespaces
2742 .|. LambdaCaseBit `xoptBit` LangExt.LambdaCase
2743 .|. BinaryLiteralsBit `xoptBit` LangExt.BinaryLiterals
2744 .|. NegativeLiteralsBit `xoptBit` LangExt.NegativeLiterals
2745 .|. HexFloatLiteralsBit `xoptBit` LangExt.HexFloatLiterals
2746 .|. PatternSynonymsBit `xoptBit` LangExt.PatternSynonyms
2747 .|. StaticPointersBit `xoptBit` LangExt.StaticPointers
2748 .|. NumericUnderscoresBit `xoptBit` LangExt.NumericUnderscores
2749 .|. StarIsTypeBit `xoptBit` LangExt.StarIsType
2750 .|. BlockArgumentsBit `xoptBit` LangExt.BlockArguments
2751 .|. NPlusKPatternsBit `xoptBit` LangExt.NPlusKPatterns
2752 .|. DoAndIfThenElseBit `xoptBit` LangExt.DoAndIfThenElse
2753 .|. MultiWayIfBit `xoptBit` LangExt.MultiWayIf
2754 .|. GadtSyntaxBit `xoptBit` LangExt.GADTSyntax
2755 .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost
2756 .|. LinearTypesBit `xoptBit` LangExt.LinearTypes
2757 .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit]
2758 .|. OverloadedRecordDotBit `xoptBit` LangExt.OverloadedRecordDot
2759 .|. OverloadedRecordUpdateBit `xoptBit` LangExt.OverloadedRecordUpdate -- Enable testing via 'getBit OverloadedRecordUpdateBit' in the parser (RecordDotSyntax parsing uses that information).
2760 optBits =
2761 HaddockBit `setBitIf` isHaddock
2762 .|. RawTokenStreamBit `setBitIf` rawTokStream
2763 .|. UsePosPragsBit `setBitIf` usePosPrags
2764
2765 xoptBit bit ext = bit `setBitIf` EnumSet.member ext extensionFlags
2766 xoptNotBit bit ext = bit `setBitIf` not (EnumSet.member ext extensionFlags)
2767
2768 setBitIf :: ExtBits -> Bool -> ExtsBitmap
2769 b `setBitIf` cond | cond = xbit b
2770 | otherwise = 0
2771
2772 disableHaddock :: ParserOpts -> ParserOpts
2773 disableHaddock opts = upd_bitmap (xunset HaddockBit)
2774 where
2775 upd_bitmap f = opts { pExtsBitmap = f (pExtsBitmap opts) }
2776
2777
2778 -- | Set parser options for parsing OPTIONS pragmas
2779 initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
2780 initPragState options buf loc = (initParserState options buf loc)
2781 { lex_state = [bol, option_prags, 0]
2782 }
2783
2784 -- | Creates a parse state from a 'ParserOpts' value
2785 initParserState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
2786 initParserState options buf loc =
2787 PState {
2788 buffer = buf,
2789 options = options,
2790 errors = emptyMessages,
2791 warnings = emptyMessages,
2792 tab_first = Strict.Nothing,
2793 tab_count = 0,
2794 last_tk = Strict.Nothing,
2795 prev_loc = mkPsSpan init_loc init_loc,
2796 prev_loc2 = mkPsSpan init_loc init_loc,
2797 last_loc = mkPsSpan init_loc init_loc,
2798 last_len = 0,
2799 loc = init_loc,
2800 context = [],
2801 lex_state = [bol, 0],
2802 srcfiles = [],
2803 alr_pending_implicit_tokens = [],
2804 alr_next_token = Nothing,
2805 alr_last_loc = PsSpan (alrInitialLoc (fsLit "<no file>")) (BufSpan (BufPos 0) (BufPos 0)),
2806 alr_context = [],
2807 alr_expecting_ocurly = Nothing,
2808 alr_justClosedExplicitLetBlock = False,
2809 eof_pos = Strict.Nothing,
2810 header_comments = Strict.Nothing,
2811 comment_q = [],
2812 hdk_comments = nilOL
2813 }
2814 where init_loc = PsLoc loc (BufPos 0)
2815
2816 -- | An mtl-style class for monads that support parsing-related operations.
2817 -- For example, sometimes we make a second pass over the parsing results to validate,
2818 -- disambiguate, or rearrange them, and we do so in the PV monad which cannot consume
2819 -- input but can report parsing errors, check for extension bits, and accumulate
2820 -- parsing annotations. Both P and PV are instances of MonadP.
2821 --
2822 -- MonadP grants us convenient overloading. The other option is to have separate operations
2823 -- for each monad: addErrorP vs addErrorPV, getBitP vs getBitPV, and so on.
2824 --
2825 class Monad m => MonadP m where
2826 -- | Add a non-fatal error. Use this when the parser can produce a result
2827 -- despite the error.
2828 --
2829 -- For example, when GHC encounters a @forall@ in a type,
2830 -- but @-XExplicitForAll@ is disabled, the parser constructs @ForAllTy@
2831 -- as if @-XExplicitForAll@ was enabled, adding a non-fatal error to
2832 -- the accumulator.
2833 --
2834 -- Control flow wise, non-fatal errors act like warnings: they are added
2835 -- to the accumulator and parsing continues. This allows GHC to report
2836 -- more than one parse error per file.
2837 --
2838 addError :: MsgEnvelope PsMessage -> m ()
2839
2840 -- | Add a warning to the accumulator.
2841 -- Use 'getPsMessages' to get the accumulated warnings.
2842 addWarning :: MsgEnvelope PsMessage -> m ()
2843
2844 -- | Add a fatal error. This will be the last error reported by the parser, and
2845 -- the parser will not produce any result, ending in a 'PFailed' state.
2846 addFatalError :: MsgEnvelope PsMessage -> m a
2847
2848 -- | Check if a given flag is currently set in the bitmap.
2849 getBit :: ExtBits -> m Bool
2850 -- | Go through the @comment_q@ in @PState@ and remove all comments
2851 -- that belong within the given span
2852 allocateCommentsP :: RealSrcSpan -> m EpAnnComments
2853 -- | Go through the @comment_q@ in @PState@ and remove all comments
2854 -- that come before or within the given span
2855 allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments
2856 -- | Go through the @comment_q@ in @PState@ and remove all comments
2857 -- that come after the given span
2858 allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments
2859
2860 instance MonadP P where
2861 addError err
2862 = P $ \s -> POk s { errors = err `addMessage` errors s} ()
2863
2864 -- If the warning is meant to be suppressed, GHC will assign
2865 -- a `SevIgnore` severity and the message will be discarded,
2866 -- so we can simply add it no matter what.
2867 addWarning w
2868 = P $ \s -> POk (s { warnings = w `addMessage` warnings s }) ()
2869
2870 addFatalError err =
2871 addError err >> P PFailed
2872
2873 getBit ext = P $ \s -> let b = ext `xtest` pExtsBitmap (options s)
2874 in b `seq` POk s b
2875 allocateCommentsP ss = P $ \s ->
2876 let (comment_q', newAnns) = allocateComments ss (comment_q s) in
2877 POk s {
2878 comment_q = comment_q'
2879 } (EpaComments newAnns)
2880 allocatePriorCommentsP ss = P $ \s ->
2881 let (header_comments', comment_q', newAnns)
2882 = allocatePriorComments ss (comment_q s) (header_comments s) in
2883 POk s {
2884 header_comments = header_comments',
2885 comment_q = comment_q'
2886 } (EpaComments newAnns)
2887 allocateFinalCommentsP ss = P $ \s ->
2888 let (header_comments', comment_q', newAnns)
2889 = allocateFinalComments ss (comment_q s) (header_comments s) in
2890 POk s {
2891 header_comments = header_comments',
2892 comment_q = comment_q'
2893 } (EpaCommentsBalanced (Strict.fromMaybe [] header_comments') (reverse newAnns))
2894
2895 getCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
2896 getCommentsFor (RealSrcSpan l _) = allocateCommentsP l
2897 getCommentsFor _ = return emptyComments
2898
2899 getPriorCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
2900 getPriorCommentsFor (RealSrcSpan l _) = allocatePriorCommentsP l
2901 getPriorCommentsFor _ = return emptyComments
2902
2903 getFinalCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
2904 getFinalCommentsFor (RealSrcSpan l _) = allocateFinalCommentsP l
2905 getFinalCommentsFor _ = return emptyComments
2906
2907 getEofPos :: P (Strict.Maybe (Strict.Pair RealSrcSpan RealSrcSpan))
2908 getEofPos = P $ \s@(PState { eof_pos = pos }) -> POk s pos
2909
2910 addPsMessage :: SrcSpan -> PsMessage -> P ()
2911 addPsMessage srcspan msg = do
2912 diag_opts <- (pDiagOpts . options) <$> getPState
2913 addWarning (mkPlainMsgEnvelope diag_opts srcspan msg)
2914
2915 addTabWarning :: RealSrcSpan -> P ()
2916 addTabWarning srcspan
2917 = P $ \s@PState{tab_first=tf, tab_count=tc, options=o} ->
2918 let tf' = tf <|> Strict.Just srcspan
2919 tc' = tc + 1
2920 s' = if warnopt Opt_WarnTabs o
2921 then s{tab_first = tf', tab_count = tc'}
2922 else s
2923 in POk s' ()
2924
2925 -- | Get a bag of the errors that have been accumulated so far.
2926 -- Does not take -Werror into account.
2927 getPsErrorMessages :: PState -> Messages PsMessage
2928 getPsErrorMessages p = errors p
2929
2930 -- | Get the warnings and errors accumulated so far.
2931 -- Does not take -Werror into account.
2932 getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage)
2933 getPsMessages p =
2934 let ws = warnings p
2935 diag_opts = pDiagOpts (options p)
2936 -- we add the tabulation warning on the fly because
2937 -- we count the number of occurrences of tab characters
2938 ws' = case tab_first p of
2939 Strict.Nothing -> ws
2940 Strict.Just tf ->
2941 let msg = mkPlainMsgEnvelope diag_opts
2942 (RealSrcSpan tf Strict.Nothing)
2943 (PsWarnTab (tab_count p))
2944 in msg `addMessage` ws
2945 in (ws', errors p)
2946
2947 getContext :: P [LayoutContext]
2948 getContext = P $ \s@PState{context=ctx} -> POk s ctx
2949
2950 setContext :: [LayoutContext] -> P ()
2951 setContext ctx = P $ \s -> POk s{context=ctx} ()
2952
2953 popContext :: P ()
2954 popContext = P $ \ s@(PState{ buffer = buf, options = o, context = ctx,
2955 last_len = len, last_loc = last_loc }) ->
2956 case ctx of
2957 (_:tl) ->
2958 POk s{ context = tl } ()
2959 [] ->
2960 unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
2961
2962 -- Push a new layout context at the indentation of the last token read.
2963 pushCurrentContext :: GenSemic -> P ()
2964 pushCurrentContext gen_semic = P $ \ s@PState{ last_loc=loc, context=ctx } ->
2965 POk s{context = Layout (srcSpanStartCol (psRealSpan loc)) gen_semic : ctx} ()
2966
2967 -- This is only used at the outer level of a module when the 'module' keyword is
2968 -- missing.
2969 pushModuleContext :: P ()
2970 pushModuleContext = pushCurrentContext generateSemic
2971
2972 getOffside :: P (Ordering, Bool)
2973 getOffside = P $ \s@PState{last_loc=loc, context=stk} ->
2974 let offs = srcSpanStartCol (psRealSpan loc) in
2975 let ord = case stk of
2976 Layout n gen_semic : _ ->
2977 --trace ("layout: " ++ show n ++ ", offs: " ++ show offs) $
2978 (compare offs n, gen_semic)
2979 _ ->
2980 (GT, dontGenerateSemic)
2981 in POk s ord
2982
2983 -- ---------------------------------------------------------------------------
2984 -- Construct a parse error
2985
2986 srcParseErr
2987 :: ParserOpts
2988 -> StringBuffer -- current buffer (placed just after the last token)
2989 -> Int -- length of the previous token
2990 -> SrcSpan
2991 -> MsgEnvelope PsMessage
2992 srcParseErr options buf len loc = mkPlainErrorMsgEnvelope loc (PsErrParse token details)
2993 where
2994 token = lexemeToString (offsetBytes (-len) buf) len
2995 pattern_ = decodePrevNChars 8 buf
2996 last100 = decodePrevNChars 100 buf
2997 doInLast100 = "do" `isInfixOf` last100
2998 mdoInLast100 = "mdo" `isInfixOf` last100
2999 th_enabled = ThQuotesBit `xtest` pExtsBitmap options
3000 ps_enabled = PatternSynonymsBit `xtest` pExtsBitmap options
3001 details = PsErrParseDetails {
3002 ped_th_enabled = th_enabled
3003 , ped_do_in_last_100 = doInLast100
3004 , ped_mdo_in_last_100 = mdoInLast100
3005 , ped_pat_syn_enabled = ps_enabled
3006 , ped_pattern_parsed = pattern_ == "pattern "
3007 }
3008
3009 -- Report a parse failure, giving the span of the previous token as
3010 -- the location of the error. This is the entry point for errors
3011 -- detected during parsing.
3012 srcParseFail :: P a
3013 srcParseFail = P $ \s@PState{ buffer = buf, options = o, last_len = len,
3014 last_loc = last_loc } ->
3015 unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
3016
3017 -- A lexical error is reported at a particular position in the source file,
3018 -- not over a token range.
3019 lexError :: LexErr -> P a
3020 lexError e = do
3021 loc <- getRealSrcLoc
3022 (AI end buf) <- getInput
3023 reportLexError loc (psRealLoc end) buf
3024 (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer e k)
3025
3026 -- -----------------------------------------------------------------------------
3027 -- This is the top-level function: called from the parser each time a
3028 -- new token is to be read from the input.
3029
3030 lexer, lexerDbg :: Bool -> (Located Token -> P a) -> P a
3031
3032 lexer queueComments cont = do
3033 alr <- getBit AlternativeLayoutRuleBit
3034 let lexTokenFun = if alr then lexTokenAlr else lexToken
3035 (L span tok) <- lexTokenFun
3036 --trace ("token: " ++ show tok) $ do
3037
3038 if (queueComments && isComment tok)
3039 then queueComment (L (psRealSpan span) tok) >> lexer queueComments cont
3040 else cont (L (mkSrcSpanPs span) tok)
3041
3042 -- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
3043 lexerDbg queueComments cont = lexer queueComments contDbg
3044 where
3045 contDbg tok = trace ("token: " ++ show (unLoc tok)) (cont tok)
3046
3047 lexTokenAlr :: P (PsLocated Token)
3048 lexTokenAlr = do mPending <- popPendingImplicitToken
3049 t <- case mPending of
3050 Nothing ->
3051 do mNext <- popNextToken
3052 t <- case mNext of
3053 Nothing -> lexToken
3054 Just next -> return next
3055 alternativeLayoutRuleToken t
3056 Just t ->
3057 return t
3058 setAlrLastLoc (getLoc t)
3059 case unLoc t of
3060 ITwhere -> setAlrExpectingOCurly (Just ALRLayoutWhere)
3061 ITlet -> setAlrExpectingOCurly (Just ALRLayoutLet)
3062 ITof -> setAlrExpectingOCurly (Just ALRLayoutOf)
3063 ITlcase -> setAlrExpectingOCurly (Just ALRLayoutOf)
3064 ITdo _ -> setAlrExpectingOCurly (Just ALRLayoutDo)
3065 ITmdo _ -> setAlrExpectingOCurly (Just ALRLayoutDo)
3066 ITrec -> setAlrExpectingOCurly (Just ALRLayoutDo)
3067 _ -> return ()
3068 return t
3069
3070 alternativeLayoutRuleToken :: PsLocated Token -> P (PsLocated Token)
3071 alternativeLayoutRuleToken t
3072 = do context <- getALRContext
3073 lastLoc <- getAlrLastLoc
3074 mExpectingOCurly <- getAlrExpectingOCurly
3075 transitional <- getBit ALRTransitionalBit
3076 justClosedExplicitLetBlock <- getJustClosedExplicitLetBlock
3077 setJustClosedExplicitLetBlock False
3078 let thisLoc = getLoc t
3079 thisCol = srcSpanStartCol (psRealSpan thisLoc)
3080 newLine = srcSpanStartLine (psRealSpan thisLoc) > srcSpanEndLine (psRealSpan lastLoc)
3081 case (unLoc t, context, mExpectingOCurly) of
3082 -- This case handles a GHC extension to the original H98
3083 -- layout rule...
3084 (ITocurly, _, Just alrLayout) ->
3085 do setAlrExpectingOCurly Nothing
3086 let isLet = case alrLayout of
3087 ALRLayoutLet -> True
3088 _ -> False
3089 setALRContext (ALRNoLayout (containsCommas ITocurly) isLet : context)
3090 return t
3091 -- ...and makes this case unnecessary
3092 {-
3093 -- I think our implicit open-curly handling is slightly
3094 -- different to John's, in how it interacts with newlines
3095 -- and "in"
3096 (ITocurly, _, Just _) ->
3097 do setAlrExpectingOCurly Nothing
3098 setNextToken t
3099 lexTokenAlr
3100 -}
3101 (_, ALRLayout _ col : _ls, Just expectingOCurly)
3102 | (thisCol > col) ||
3103 (thisCol == col &&
3104 isNonDecreasingIndentation expectingOCurly) ->
3105 do setAlrExpectingOCurly Nothing
3106 setALRContext (ALRLayout expectingOCurly thisCol : context)
3107 setNextToken t
3108 return (L thisLoc ITvocurly)
3109 | otherwise ->
3110 do setAlrExpectingOCurly Nothing
3111 setPendingImplicitTokens [L lastLoc ITvccurly]
3112 setNextToken t
3113 return (L lastLoc ITvocurly)
3114 (_, _, Just expectingOCurly) ->
3115 do setAlrExpectingOCurly Nothing
3116 setALRContext (ALRLayout expectingOCurly thisCol : context)
3117 setNextToken t
3118 return (L thisLoc ITvocurly)
3119 -- We do the [] cases earlier than in the spec, as we
3120 -- have an actual EOF token
3121 (ITeof, ALRLayout _ _ : ls, _) ->
3122 do setALRContext ls
3123 setNextToken t
3124 return (L thisLoc ITvccurly)
3125 (ITeof, _, _) ->
3126 return t
3127 -- the other ITeof case omitted; general case below covers it
3128 (ITin, _, _)
3129 | justClosedExplicitLetBlock ->
3130 return t
3131 (ITin, ALRLayout ALRLayoutLet _ : ls, _)
3132 | newLine ->
3133 do setPendingImplicitTokens [t]
3134 setALRContext ls
3135 return (L thisLoc ITvccurly)
3136 -- This next case is to handle a transitional issue:
3137 (ITwhere, ALRLayout _ col : ls, _)
3138 | newLine && thisCol == col && transitional ->
3139 do addPsMessage
3140 (mkSrcSpanPs thisLoc)
3141 (PsWarnTransitionalLayout TransLayout_Where)
3142 setALRContext ls
3143 setNextToken t
3144 -- Note that we use lastLoc, as we may need to close
3145 -- more layouts, or give a semicolon
3146 return (L lastLoc ITvccurly)
3147 -- This next case is to handle a transitional issue:
3148 (ITvbar, ALRLayout _ col : ls, _)
3149 | newLine && thisCol == col && transitional ->
3150 do addPsMessage
3151 (mkSrcSpanPs thisLoc)
3152 (PsWarnTransitionalLayout TransLayout_Pipe)
3153 setALRContext ls
3154 setNextToken t
3155 -- Note that we use lastLoc, as we may need to close
3156 -- more layouts, or give a semicolon
3157 return (L lastLoc ITvccurly)
3158 (_, ALRLayout _ col : ls, _)
3159 | newLine && thisCol == col ->
3160 do setNextToken t
3161 let loc = psSpanStart thisLoc
3162 zeroWidthLoc = mkPsSpan loc loc
3163 return (L zeroWidthLoc ITsemi)
3164 | newLine && thisCol < col ->
3165 do setALRContext ls
3166 setNextToken t
3167 -- Note that we use lastLoc, as we may need to close
3168 -- more layouts, or give a semicolon
3169 return (L lastLoc ITvccurly)
3170 -- We need to handle close before open, as 'then' is both
3171 -- an open and a close
3172 (u, _, _)
3173 | isALRclose u ->
3174 case context of
3175 ALRLayout _ _ : ls ->
3176 do setALRContext ls
3177 setNextToken t
3178 return (L thisLoc ITvccurly)
3179 ALRNoLayout _ isLet : ls ->
3180 do let ls' = if isALRopen u
3181 then ALRNoLayout (containsCommas u) False : ls
3182 else ls
3183 setALRContext ls'
3184 when isLet $ setJustClosedExplicitLetBlock True
3185 return t
3186 [] ->
3187 do let ls = if isALRopen u
3188 then [ALRNoLayout (containsCommas u) False]
3189 else []
3190 setALRContext ls
3191 -- XXX This is an error in John's code, but
3192 -- it looks reachable to me at first glance
3193 return t
3194 (u, _, _)
3195 | isALRopen u ->
3196 do setALRContext (ALRNoLayout (containsCommas u) False : context)
3197 return t
3198 (ITin, ALRLayout ALRLayoutLet _ : ls, _) ->
3199 do setALRContext ls
3200 setPendingImplicitTokens [t]
3201 return (L thisLoc ITvccurly)
3202 (ITin, ALRLayout _ _ : ls, _) ->
3203 do setALRContext ls
3204 setNextToken t
3205 return (L thisLoc ITvccurly)
3206 -- the other ITin case omitted; general case below covers it
3207 (ITcomma, ALRLayout _ _ : ls, _)
3208 | topNoLayoutContainsCommas ls ->
3209 do setALRContext ls
3210 setNextToken t
3211 return (L thisLoc ITvccurly)
3212 (ITwhere, ALRLayout ALRLayoutDo _ : ls, _) ->
3213 do setALRContext ls
3214 setPendingImplicitTokens [t]
3215 return (L thisLoc ITvccurly)
3216 -- the other ITwhere case omitted; general case below covers it
3217 (_, _, _) -> return t
3218
3219 isALRopen :: Token -> Bool
3220 isALRopen ITcase = True
3221 isALRopen ITif = True
3222 isALRopen ITthen = True
3223 isALRopen IToparen = True
3224 isALRopen ITobrack = True
3225 isALRopen ITocurly = True
3226 -- GHC Extensions:
3227 isALRopen IToubxparen = True
3228 isALRopen _ = False
3229
3230 isALRclose :: Token -> Bool
3231 isALRclose ITof = True
3232 isALRclose ITthen = True
3233 isALRclose ITelse = True
3234 isALRclose ITcparen = True
3235 isALRclose ITcbrack = True
3236 isALRclose ITccurly = True
3237 -- GHC Extensions:
3238 isALRclose ITcubxparen = True
3239 isALRclose _ = False
3240
3241 isNonDecreasingIndentation :: ALRLayout -> Bool
3242 isNonDecreasingIndentation ALRLayoutDo = True
3243 isNonDecreasingIndentation _ = False
3244
3245 containsCommas :: Token -> Bool
3246 containsCommas IToparen = True
3247 containsCommas ITobrack = True
3248 -- John doesn't have {} as containing commas, but records contain them,
3249 -- which caused a problem parsing Cabal's Distribution.Simple.InstallDirs
3250 -- (defaultInstallDirs).
3251 containsCommas ITocurly = True
3252 -- GHC Extensions:
3253 containsCommas IToubxparen = True
3254 containsCommas _ = False
3255
3256 topNoLayoutContainsCommas :: [ALRContext] -> Bool
3257 topNoLayoutContainsCommas [] = False
3258 topNoLayoutContainsCommas (ALRLayout _ _ : ls) = topNoLayoutContainsCommas ls
3259 topNoLayoutContainsCommas (ALRNoLayout b _ : _) = b
3260
3261 lexToken :: P (PsLocated Token)
3262 lexToken = do
3263 inp@(AI loc1 buf) <- getInput
3264 sc <- getLexState
3265 exts <- getExts
3266 case alexScanUser exts inp sc of
3267 AlexEOF -> do
3268 let span = mkPsSpan loc1 loc1
3269 lt <- getLastLocEof
3270 setEofPos (psRealSpan span) (psRealSpan lt)
3271 setLastToken span 0
3272 return (L span ITeof)
3273 AlexError (AI loc2 buf) ->
3274 reportLexError (psRealLoc loc1) (psRealLoc loc2) buf
3275 (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer LexError k)
3276 AlexSkip inp2 _ -> do
3277 setInput inp2
3278 lexToken
3279 AlexToken inp2@(AI end buf2) _ t -> do
3280 setInput inp2
3281 let span = mkPsSpan loc1 end
3282 let bytes = byteDiff buf buf2
3283 span `seq` setLastToken span bytes
3284 lt <- t span buf bytes
3285 let lt' = unLoc lt
3286 if (isComment lt') then setLastComment lt else setLastTk lt
3287 return lt
3288
3289 reportLexError :: RealSrcLoc
3290 -> RealSrcLoc
3291 -> StringBuffer
3292 -> (LexErrKind -> SrcSpan -> MsgEnvelope PsMessage)
3293 -> P a
3294 reportLexError loc1 loc2 buf f
3295 | atEnd buf = failLocMsgP loc1 loc2 (f LexErrKind_EOF)
3296 | otherwise =
3297 let c = fst (nextChar buf)
3298 in if c == '\0' -- decoding errors are mapped to '\0', see utf8DecodeChar#
3299 then failLocMsgP loc2 loc2 (f LexErrKind_UTF8)
3300 else failLocMsgP loc1 loc2 (f (LexErrKind_Char c))
3301
3302 lexTokenStream :: ParserOpts -> StringBuffer -> RealSrcLoc -> ParseResult [Located Token]
3303 lexTokenStream opts buf loc = unP go initState{ options = opts' }
3304 where
3305 new_exts = xunset HaddockBit -- disable Haddock
3306 $ xunset UsePosPragsBit -- parse LINE/COLUMN pragmas as tokens
3307 $ xset RawTokenStreamBit -- include comments
3308 $ pExtsBitmap opts
3309 opts' = opts { pExtsBitmap = new_exts }
3310 initState = initParserState opts' buf loc
3311 go = do
3312 ltok <- lexer False return
3313 case ltok of
3314 L _ ITeof -> return []
3315 _ -> liftM (ltok:) go
3316
3317 linePrags = Map.singleton "line" linePrag
3318
3319 fileHeaderPrags = Map.fromList([("options", lex_string_prag IToptions_prag),
3320 ("options_ghc", lex_string_prag IToptions_prag),
3321 ("options_haddock", lex_string_prag_comment ITdocOptions),
3322 ("language", token ITlanguage_prag),
3323 ("include", lex_string_prag ITinclude_prag)])
3324
3325 ignoredPrags = Map.fromList (map ignored pragmas)
3326 where ignored opt = (opt, nested_comment lexToken)
3327 impls = ["hugs", "nhc98", "jhc", "yhc", "catch", "derive"]
3328 options_pragmas = map ("options_" ++) impls
3329 -- CFILES is a hugs-only thing.
3330 pragmas = options_pragmas ++ ["cfiles", "contract"]
3331
3332 oneWordPrags = Map.fromList [
3333 ("rules", rulePrag),
3334 ("inline",
3335 strtoken (\s -> (ITinline_prag (SourceText s) (Inline (SourceText s)) FunLike))),
3336 ("inlinable",
3337 strtoken (\s -> (ITinline_prag (SourceText s) (Inlinable (SourceText s)) FunLike))),
3338 ("inlineable",
3339 strtoken (\s -> (ITinline_prag (SourceText s) (Inlinable (SourceText s)) FunLike))),
3340 -- Spelling variant
3341 ("notinline",
3342 strtoken (\s -> (ITinline_prag (SourceText s) (NoInline (SourceText s)) FunLike))),
3343 ("specialize", strtoken (\s -> ITspec_prag (SourceText s))),
3344 ("source", strtoken (\s -> ITsource_prag (SourceText s))),
3345 ("warning", strtoken (\s -> ITwarning_prag (SourceText s))),
3346 ("deprecated", strtoken (\s -> ITdeprecated_prag (SourceText s))),
3347 ("scc", strtoken (\s -> ITscc_prag (SourceText s))),
3348 ("unpack", strtoken (\s -> ITunpack_prag (SourceText s))),
3349 ("nounpack", strtoken (\s -> ITnounpack_prag (SourceText s))),
3350 ("ann", strtoken (\s -> ITann_prag (SourceText s))),
3351 ("minimal", strtoken (\s -> ITminimal_prag (SourceText s))),
3352 ("overlaps", strtoken (\s -> IToverlaps_prag (SourceText s))),
3353 ("overlappable", strtoken (\s -> IToverlappable_prag (SourceText s))),
3354 ("overlapping", strtoken (\s -> IToverlapping_prag (SourceText s))),
3355 ("incoherent", strtoken (\s -> ITincoherent_prag (SourceText s))),
3356 ("ctype", strtoken (\s -> ITctype (SourceText s))),
3357 ("complete", strtoken (\s -> ITcomplete_prag (SourceText s))),
3358 ("column", columnPrag)
3359 ]
3360
3361 twoWordPrags = Map.fromList [
3362 ("inline conlike",
3363 strtoken (\s -> (ITinline_prag (SourceText s) (Inline (SourceText s)) ConLike))),
3364 ("notinline conlike",
3365 strtoken (\s -> (ITinline_prag (SourceText s) (NoInline (SourceText s)) ConLike))),
3366 ("specialize inline",
3367 strtoken (\s -> (ITspec_inline_prag (SourceText s) True))),
3368 ("specialize notinline",
3369 strtoken (\s -> (ITspec_inline_prag (SourceText s) False)))
3370 ]
3371
3372 dispatch_pragmas :: Map String Action -> Action
3373 dispatch_pragmas prags span buf len = case Map.lookup (clean_pragma (lexemeToString buf len)) prags of
3374 Just found -> found span buf len
3375 Nothing -> lexError LexUnknownPragma
3376
3377 known_pragma :: Map String Action -> AlexAccPred ExtsBitmap
3378 known_pragma prags _ (AI _ startbuf) _ (AI _ curbuf)
3379 = isKnown && nextCharIsNot curbuf pragmaNameChar
3380 where l = lexemeToString startbuf (byteDiff startbuf curbuf)
3381 isKnown = isJust $ Map.lookup (clean_pragma l) prags
3382 pragmaNameChar c = isAlphaNum c || c == '_'
3383
3384 clean_pragma :: String -> String
3385 clean_pragma prag = canon_ws (map toLower (unprefix prag))
3386 where unprefix prag' = case stripPrefix "{-#" prag' of
3387 Just rest -> rest
3388 Nothing -> prag'
3389 canonical prag' = case prag' of
3390 "noinline" -> "notinline"
3391 "specialise" -> "specialize"
3392 "constructorlike" -> "conlike"
3393 _ -> prag'
3394 canon_ws s = unwords (map canonical (words s))
3395
3396
3397
3398 {-
3399 %************************************************************************
3400 %* *
3401 Helper functions for generating annotations in the parser
3402 %* *
3403 %************************************************************************
3404 -}
3405
3406
3407 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
3408 -- 'AddEpAnn' values for the opening and closing bordering on the start
3409 -- and end of the span
3410 mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
3411 mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan lo),AddEpAnn AnnCloseP (EpaSpan lc))
3412 where
3413 f = srcSpanFile ss
3414 sl = srcSpanStartLine ss
3415 sc = srcSpanStartCol ss
3416 el = srcSpanEndLine ss
3417 ec = srcSpanEndCol ss
3418 lo = mkRealSrcSpan (realSrcSpanStart ss) (mkRealSrcLoc f sl (sc+1))
3419 lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
3420
3421 queueComment :: RealLocated Token -> P()
3422 queueComment c = P $ \s -> POk s {
3423 comment_q = commentToAnnotation c : comment_q s
3424 } ()
3425
3426 allocateComments
3427 :: RealSrcSpan
3428 -> [LEpaComment]
3429 -> ([LEpaComment], [LEpaComment])
3430 allocateComments ss comment_q =
3431 let
3432 (before,rest) = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
3433 (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
3434 comment_q' = before ++ after
3435 newAnns = middle
3436 in
3437 (comment_q', newAnns)
3438
3439 allocatePriorComments
3440 :: RealSrcSpan
3441 -> [LEpaComment]
3442 -> Strict.Maybe [LEpaComment]
3443 -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
3444 allocatePriorComments ss comment_q mheader_comments =
3445 let
3446 cmp (L l _) = anchor l <= ss
3447 (before,after) = partition cmp comment_q
3448 newAnns = before
3449 comment_q'= after
3450 in
3451 case mheader_comments of
3452 Strict.Nothing -> (Strict.Just newAnns, comment_q', [])
3453 Strict.Just _ -> (mheader_comments, comment_q', newAnns)
3454
3455 allocateFinalComments
3456 :: RealSrcSpan
3457 -> [LEpaComment]
3458 -> Strict.Maybe [LEpaComment]
3459 -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
3460 allocateFinalComments ss comment_q mheader_comments =
3461 let
3462 cmp (L l _) = anchor l <= ss
3463 (before,after) = partition cmp comment_q
3464 newAnns = after
3465 comment_q'= before
3466 in
3467 case mheader_comments of
3468 Strict.Nothing -> (Strict.Just newAnns, [], comment_q')
3469 Strict.Just _ -> (mheader_comments, [], comment_q' ++ newAnns)
3470
3471 commentToAnnotation :: RealLocated Token -> LEpaComment
3472 commentToAnnotation (L l (ITdocCommentNext s ll)) = mkLEpaComment l ll (EpaDocCommentNext s)
3473 commentToAnnotation (L l (ITdocCommentPrev s ll)) = mkLEpaComment l ll (EpaDocCommentPrev s)
3474 commentToAnnotation (L l (ITdocCommentNamed s ll)) = mkLEpaComment l ll (EpaDocCommentNamed s)
3475 commentToAnnotation (L l (ITdocSection n s ll)) = mkLEpaComment l ll (EpaDocSection n s)
3476 commentToAnnotation (L l (ITdocOptions s ll)) = mkLEpaComment l ll (EpaDocOptions s)
3477 commentToAnnotation (L l (ITlineComment s ll)) = mkLEpaComment l ll (EpaLineComment s)
3478 commentToAnnotation (L l (ITblockComment s ll)) = mkLEpaComment l ll (EpaBlockComment s)
3479 commentToAnnotation _ = panic "commentToAnnotation"
3480
3481 -- see Note [PsSpan in Comments]
3482 mkLEpaComment :: RealSrcSpan -> PsSpan -> EpaCommentTok -> LEpaComment
3483 mkLEpaComment l ll tok = L (realSpanAsAnchor l) (EpaComment tok (psRealSpan ll))
3484
3485 -- ---------------------------------------------------------------------
3486
3487 isComment :: Token -> Bool
3488 isComment (ITlineComment _ _) = True
3489 isComment (ITblockComment _ _) = True
3490 isComment (ITdocCommentNext _ _) = True
3491 isComment (ITdocCommentPrev _ _) = True
3492 isComment (ITdocCommentNamed _ _) = True
3493 isComment (ITdocSection _ _ _) = True
3494 isComment (ITdocOptions _ _) = True
3495 isComment _ = False
3496
3497
3498 bol,column_prag,layout,layout_do,layout_if,layout_left,line_prag1,line_prag1a,line_prag2,line_prag2a,option_prags :: Int
3499 bol = 1
3500 column_prag = 2
3501 layout = 3
3502 layout_do = 4
3503 layout_if = 5
3504 layout_left = 6
3505 line_prag1 = 7
3506 line_prag1a = 8
3507 line_prag2 = 9
3508 line_prag2a = 10
3509 option_prags = 11
3510 alex_action_1 = warnTab
3511 alex_action_2 = nested_comment lexToken
3512 alex_action_3 = lineCommentToken
3513 alex_action_4 = lineCommentToken
3514 alex_action_5 = lineCommentToken
3515 alex_action_6 = lineCommentToken
3516 alex_action_7 = lineCommentToken
3517 alex_action_8 = lineCommentToken
3518 alex_action_10 = begin line_prag1
3519 alex_action_11 = begin line_prag1
3520 alex_action_15 = do_bol
3521 alex_action_16 = hopefully_open_brace
3522 alex_action_18 = begin line_prag1
3523 alex_action_19 = new_layout_context True dontGenerateSemic ITvbar
3524 alex_action_20 = pop
3525 alex_action_21 = new_layout_context True generateSemic ITvocurly
3526 alex_action_22 = new_layout_context False generateSemic ITvocurly
3527 alex_action_23 = do_layout_left
3528 alex_action_24 = begin bol
3529 alex_action_25 = dispatch_pragmas linePrags
3530 alex_action_26 = setLineAndFile line_prag1a
3531 alex_action_27 = failLinePrag1
3532 alex_action_28 = popLinePrag1
3533 alex_action_29 = setLineAndFile line_prag2a
3534 alex_action_30 = pop
3535 alex_action_31 = setColumn
3536 alex_action_32 = dispatch_pragmas twoWordPrags
3537 alex_action_33 = dispatch_pragmas oneWordPrags
3538 alex_action_34 = dispatch_pragmas ignoredPrags
3539 alex_action_35 = endPrag
3540 alex_action_36 = dispatch_pragmas fileHeaderPrags
3541 alex_action_37 = nested_comment lexToken
3542 alex_action_38 = warnThen PsWarnUnrecognisedPragma
3543 (nested_comment lexToken)
3544 alex_action_39 = multiline_doc_comment
3545 alex_action_40 = nested_doc_comment
3546 alex_action_41 = token (ITopenExpQuote NoE NormalSyntax)
3547 alex_action_42 = token (ITopenTExpQuote NoE)
3548 alex_action_43 = token (ITcloseQuote NormalSyntax)
3549 alex_action_44 = token ITcloseTExpQuote
3550 alex_action_45 = token (ITopenExpQuote HasE NormalSyntax)
3551 alex_action_46 = token (ITopenTExpQuote HasE)
3552 alex_action_47 = token ITopenPatQuote
3553 alex_action_48 = layout_token ITopenDecQuote
3554 alex_action_49 = token ITopenTypQuote
3555 alex_action_50 = lex_quasiquote_tok
3556 alex_action_51 = lex_qquasiquote_tok
3557 alex_action_52 = token (ITopenExpQuote NoE UnicodeSyntax)
3558 alex_action_53 = token (ITcloseQuote UnicodeSyntax)
3559 alex_action_54 = special (IToparenbar NormalSyntax)
3560 alex_action_55 = special (ITcparenbar NormalSyntax)
3561 alex_action_56 = special (IToparenbar UnicodeSyntax)
3562 alex_action_57 = special (ITcparenbar UnicodeSyntax)
3563 alex_action_58 = skip_one_varid ITdupipvarid
3564 alex_action_59 = skip_one_varid ITlabelvarid
3565 alex_action_60 = token IToubxparen
3566 alex_action_61 = token ITcubxparen
3567 alex_action_62 = special IToparen
3568 alex_action_63 = special ITcparen
3569 alex_action_64 = special ITobrack
3570 alex_action_65 = special ITcbrack
3571 alex_action_66 = special ITcomma
3572 alex_action_67 = special ITsemi
3573 alex_action_68 = special ITbackquote
3574 alex_action_69 = open_brace
3575 alex_action_70 = close_brace
3576 alex_action_71 = qdo_token ITdo
3577 alex_action_72 = qdo_token ITmdo
3578 alex_action_73 = idtoken qvarid
3579 alex_action_74 = idtoken qconid
3580 alex_action_75 = varid
3581 alex_action_76 = idtoken conid
3582 alex_action_77 = idtoken qvarid
3583 alex_action_78 = idtoken qconid
3584 alex_action_79 = varid
3585 alex_action_80 = idtoken conid
3586 alex_action_81 = varsym_tight_infix
3587 alex_action_82 = varsym_prefix
3588 alex_action_83 = varsym_suffix
3589 alex_action_84 = varsym_loose_infix
3590 alex_action_85 = idtoken qvarsym
3591 alex_action_86 = idtoken qconsym
3592 alex_action_87 = consym
3593 alex_action_88 = tok_num positive 0 0 decimal
3594 alex_action_89 = tok_num positive 2 2 binary
3595 alex_action_90 = tok_num positive 2 2 octal
3596 alex_action_91 = tok_num positive 2 2 hexadecimal
3597 alex_action_92 = tok_num negative 1 1 decimal
3598 alex_action_93 = tok_num negative 3 3 binary
3599 alex_action_94 = tok_num negative 3 3 octal
3600 alex_action_95 = tok_num negative 3 3 hexadecimal
3601 alex_action_96 = tok_frac 0 tok_float
3602 alex_action_97 = tok_frac 0 tok_float
3603 alex_action_98 = tok_frac 0 tok_hex_float
3604 alex_action_99 = tok_frac 0 tok_hex_float
3605 alex_action_100 = tok_primint positive 0 1 decimal
3606 alex_action_101 = tok_primint positive 2 3 binary
3607 alex_action_102 = tok_primint positive 2 3 octal
3608 alex_action_103 = tok_primint positive 2 3 hexadecimal
3609 alex_action_104 = tok_primint negative 1 2 decimal
3610 alex_action_105 = tok_primint negative 3 4 binary
3611 alex_action_106 = tok_primint negative 3 4 octal
3612 alex_action_107 = tok_primint negative 3 4 hexadecimal
3613 alex_action_108 = tok_primword 0 2 decimal
3614 alex_action_109 = tok_primword 2 4 binary
3615 alex_action_110 = tok_primword 2 4 octal
3616 alex_action_111 = tok_primword 2 4 hexadecimal
3617 alex_action_112 = tok_frac 1 tok_primfloat
3618 alex_action_113 = tok_frac 2 tok_primdouble
3619 alex_action_114 = tok_frac 1 tok_primfloat
3620 alex_action_115 = tok_frac 2 tok_primdouble
3621 alex_action_116 = lex_char_tok
3622 alex_action_117 = lex_string_tok
3623 {-# LINE 1 "templates/GenericTemplate.hs" #-}
3624 -- -----------------------------------------------------------------------------
3625 -- ALEX TEMPLATE
3626 --
3627 -- This code is in the PUBLIC DOMAIN; you may copy it freely and use
3628 -- it for any purpose whatsoever.
3629
3630 -- -----------------------------------------------------------------------------
3631 -- INTERNALS and main scanner engine
3632
3633
3634
3635
3636
3637
3638
3639
3640
3641
3642
3643
3644
3645
3646
3647
3648
3649
3650 -- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
3651 #if __GLASGOW_HASKELL__ > 706
3652 #define GTE(n,m) (tagToEnum# (n >=# m))
3653 #define EQ(n,m) (tagToEnum# (n ==# m))
3654 #else
3655 #define GTE(n,m) (n >=# m)
3656 #define EQ(n,m) (n ==# m)
3657 #endif
3658
3659
3660
3661
3662
3663
3664
3665
3666
3667
3668
3669
3670
3671
3672
3673
3674
3675
3676
3677 data AlexAddr = AlexA# Addr#
3678 -- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
3679 #if __GLASGOW_HASKELL__ < 503
3680 uncheckedShiftL# = shiftL#
3681 #endif
3682
3683 {-# INLINE alexIndexInt16OffAddr #-}
3684 alexIndexInt16OffAddr :: AlexAddr -> Int# -> Int#
3685 alexIndexInt16OffAddr (AlexA# arr) off =
3686 #ifdef WORDS_BIGENDIAN
3687 narrow16Int# i
3688 where
3689 i = word2Int# ((high `uncheckedShiftL#` 8#) `or#` low)
3690 high = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
3691 low = int2Word# (ord# (indexCharOffAddr# arr off'))
3692 off' = off *# 2#
3693 #else
3694 #if __GLASGOW_HASKELL__ >= 901
3695 int16ToInt#
3696 #endif
3697 (indexInt16OffAddr# arr off)
3698 #endif
3699
3700
3701
3702
3703
3704 {-# INLINE alexIndexInt32OffAddr #-}
3705 alexIndexInt32OffAddr :: AlexAddr -> Int# -> Int#
3706 alexIndexInt32OffAddr (AlexA# arr) off =
3707 #ifdef WORDS_BIGENDIAN
3708 narrow32Int# i
3709 where
3710 i = word2Int# ((b3 `uncheckedShiftL#` 24#) `or#`
3711 (b2 `uncheckedShiftL#` 16#) `or#`
3712 (b1 `uncheckedShiftL#` 8#) `or#` b0)
3713 b3 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 3#)))
3714 b2 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 2#)))
3715 b1 = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
3716 b0 = int2Word# (ord# (indexCharOffAddr# arr off'))
3717 off' = off *# 4#
3718 #else
3719 #if __GLASGOW_HASKELL__ >= 901
3720 int32ToInt#
3721 #endif
3722 (indexInt32OffAddr# arr off)
3723 #endif
3724
3725
3726
3727
3728
3729
3730 #if __GLASGOW_HASKELL__ < 503
3731 quickIndex arr i = arr ! i
3732 #else
3733 -- GHC >= 503, unsafeAt is available from Data.Array.Base.
3734 quickIndex = unsafeAt
3735 #endif
3736
3737
3738
3739
3740 -- -----------------------------------------------------------------------------
3741 -- Main lexing routines
3742
3743 data AlexReturn a
3744 = AlexEOF
3745 | AlexError !AlexInput
3746 | AlexSkip !AlexInput !Int
3747 | AlexToken !AlexInput !Int a
3748
3749 -- alexScan :: AlexInput -> StartCode -> AlexReturn a
3750 alexScan input__ (I# (sc))
3751 = alexScanUser undefined input__ (I# (sc))
3752
3753 alexScanUser user__ input__ (I# (sc))
3754 = case alex_scan_tkn user__ input__ 0# input__ sc AlexNone of
3755 (AlexNone, input__') ->
3756 case alexGetByte input__ of
3757 Nothing ->
3758
3759
3760
3761 AlexEOF
3762 Just _ ->
3763
3764
3765
3766 AlexError input__'
3767
3768 (AlexLastSkip input__'' len, _) ->
3769
3770
3771
3772 AlexSkip input__'' len
3773
3774 (AlexLastAcc k input__''' len, _) ->
3775
3776
3777
3778 AlexToken input__''' len (alex_actions ! k)
3779
3780
3781 -- Push the input through the DFA, remembering the most recent accepting
3782 -- state it encountered.
3783
3784 alex_scan_tkn user__ orig_input len input__ s last_acc =
3785 input__ `seq` -- strict in the input
3786 let
3787 new_acc = (check_accs (alex_accept `quickIndex` (I# (s))))
3788 in
3789 new_acc `seq`
3790 case alexGetByte input__ of
3791 Nothing -> (new_acc, input__)
3792 Just (c, new_input) ->
3793
3794
3795
3796 case fromIntegral c of { (I# (ord_c)) ->
3797 let
3798 base = alexIndexInt32OffAddr alex_base s
3799 offset = (base +# ord_c)
3800 check = alexIndexInt16OffAddr alex_check offset
3801
3802 new_s = if GTE(offset,0#) && EQ(check,ord_c)
3803 then alexIndexInt16OffAddr alex_table offset
3804 else alexIndexInt16OffAddr alex_deflt s
3805 in
3806 case new_s of
3807 -1# -> (new_acc, input__)
3808 -- on an error, we want to keep the input *before* the
3809 -- character that failed, not after.
3810 _ -> alex_scan_tkn user__ orig_input (if c < 0x80 || c >= 0xC0 then (len +# 1#) else len)
3811 -- note that the length is increased ONLY if this is the 1st byte in a char encoding)
3812 new_input new_s new_acc
3813 }
3814 where
3815 check_accs (AlexAccNone) = last_acc
3816 check_accs (AlexAcc a ) = AlexLastAcc a input__ (I# (len))
3817 check_accs (AlexAccSkip) = AlexLastSkip input__ (I# (len))
3818
3819 check_accs (AlexAccPred a predx rest)
3820 | predx user__ orig_input (I# (len)) input__
3821 = AlexLastAcc a input__ (I# (len))
3822 | otherwise
3823 = check_accs rest
3824 check_accs (AlexAccSkipPred predx rest)
3825 | predx user__ orig_input (I# (len)) input__
3826 = AlexLastSkip input__ (I# (len))
3827 | otherwise
3828 = check_accs rest
3829
3830
3831 data AlexLastAcc
3832 = AlexNone
3833 | AlexLastAcc !Int !AlexInput !Int
3834 | AlexLastSkip !AlexInput !Int
3835
3836 data AlexAcc user
3837 = AlexAccNone
3838 | AlexAcc Int
3839 | AlexAccSkip
3840
3841 | AlexAccPred Int (AlexAccPred user) (AlexAcc user)
3842 | AlexAccSkipPred (AlexAccPred user) (AlexAcc user)
3843
3844 type AlexAccPred user = user -> AlexInput -> Int -> AlexInput -> Bool
3845
3846 -- -----------------------------------------------------------------------------
3847 -- Predicates on a rule
3848
3849 alexAndPred p1 p2 user__ in1 len in2
3850 = p1 user__ in1 len in2 && p2 user__ in1 len in2
3851
3852 --alexPrevCharIsPred :: Char -> AlexAccPred _
3853 alexPrevCharIs c _ input__ _ _ = c == alexInputPrevChar input__
3854
3855 alexPrevCharMatches f _ input__ _ _ = f (alexInputPrevChar input__)
3856
3857 --alexPrevCharIsOneOfPred :: Array Char Bool -> AlexAccPred _
3858 alexPrevCharIsOneOf arr _ input__ _ _ = arr ! alexInputPrevChar input__
3859
3860 --alexRightContext :: Int -> AlexAccPred _
3861 alexRightContext (I# (sc)) user__ _ _ input__ =
3862 case alex_scan_tkn user__ input__ 0# input__ sc AlexNone of
3863 (AlexNone, _) -> False
3864 _ -> True
3865 -- TODO: there's no need to find the longest
3866 -- match when checking the right context, just
3867 -- the first match will do.
3868