{-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-missing-signatures #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LINE 43 "compiler/GHC/Parser/Lexer.x" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnboxedSums #-}
{-# LANGUAGE UnliftedNewtypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Parser.Lexer (
   Token(..), lexer, lexerDbg,
   ParserOpts(..), mkParserOpts,
   PState (..), initParserState, initPragState,
   P(..), ParseResult(POk, PFailed),
   allocateComments, allocatePriorComments, allocateFinalComments,
   MonadP(..),
   getRealSrcLoc, getPState,
   failMsgP, failLocMsgP, srcParseFail,
   getPsErrorMessages, getPsMessages,
   popContext, pushModuleContext, setLastToken, setSrcLoc,
   activeContext, nextIsEOF,
   getLexState, popLexState, pushLexState,
   ExtBits(..),
   xtest, xunset, xset,
   disableHaddock,
   lexTokenStream,
   mkParensEpAnn,
   getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
   getEofPos,
   commentToAnnotation,
   HdkComment(..),
   warnopt,
   adjustChar,
   addPsMessage
  ) where
import GHC.Prelude
import qualified GHC.Data.Strict as Strict
import Control.Monad
import Control.Applicative
import Data.Char
import Data.List (stripPrefix, isInfixOf, partition)
import Data.List.NonEmpty ( NonEmpty(..) )
import qualified Data.List.NonEmpty as NE
import Data.Maybe
import Data.Word
import Debug.Trace (trace)
import GHC.Data.EnumSet as EnumSet
import qualified GHC.LanguageExtensions as LangExt
import Data.ByteString (ByteString)
import Data.Map (Map)
import qualified Data.Map as Map
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Data.StringBuffer
import GHC.Data.FastString
import GHC.Types.Error
import GHC.Types.Unique.FM
import GHC.Data.Maybe
import GHC.Data.OrdList
import GHC.Utils.Misc ( readSignificandExponentPair, readHexSignificandExponentPair )
import GHC.Types.SrcLoc
import GHC.Types.SourceText
import GHC.Types.Basic ( InlineSpec(..), RuleMatchInfo(..))
import GHC.Hs.Doc
import GHC.Parser.CharClass
import GHC.Parser.Annotation
import GHC.Driver.Flags
import GHC.Parser.Errors.Basic
import GHC.Parser.Errors.Types
import GHC.Parser.Errors.Ppr ()
#if __GLASGOW_HASKELL__ >= 603
#include "ghcconfig.h"
#elif defined(__GLASGOW_HASKELL__)
#include "config.h"
#endif
#if __GLASGOW_HASKELL__ >= 503
import Data.Array
#else
import Array
#endif
#if __GLASGOW_HASKELL__ >= 503
import Data.Array.Base (unsafeAt)
import GHC.Exts
#else
import GlaExts
#endif
alex_tab_size :: Int
alex_tab_size = 8
alex_base :: AlexAddr
alex_base = AlexA#
  "\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\xf7\x00\x00\x00\x05\x01\x00\x00\x2f\x01\x00\x00\x4b\x01\x00\x00\x86\x01\x00\x00\x75\x00\x00\x00\xd4\x01\x00\x00\xeb\x01\x00\x00\x64\x01\x00\x00\x2c\x02\x00\x00\x6d\x02\x00\x00\xe4\xff\xff\xff\x84\x02\x00\x00\x84\x01\x00\x00\xc5\x02\x00\x00\x0c\x02\x00\x00\x4d\x02\x00\x00\xa5\x02\x00\x00\xe8\x02\x00\x00\x06\x03\x00\x00\x1e\x03\x00\x00\x28\x03\x00\x00\x37\x03\x00\x00\x70\x03\x00\x00\x4b\x03\x00\x00\x58\x03\x00\x00\xc8\x03\x00\x00\xd2\x03\x00\x00\x16\x04\x00\x00\xec\x00\x00\x00\x64\x02\x00\x00\x3b\x04\x00\x00\x65\x00\x00\x00\x7e\x00\x00\x00\x84\x04\x00\x00\x9c\x04\x00\x00\xc1\x04\x00\x00\xfa\x04\x00\x00\xbc\x03\x00\x00\x7b\x04\x00\x00\x1f\x05\x00\x00\x82\x00\x00\x00\xbb\x00\x00\x00\x68\x05\x00\x00\x80\x05\x00\x00\xbd\x05\x00\x00\xf2\x05\x00\x00\x38\x06\x00\x00\x5b\x06\x00\x00\x83\x06\x00\x00\xe1\x06\x00\x00\x3d\x07\x00\x00\x62\x07\x00\x00\xbe\x07\x00\x00\xe1\x07\x00\x00\xde\xff\xff\xff\xe1\xff\xff\xff\x21\x08\x00\x00\xe5\xff\xff\xff\x9b\x08\x00\x00\x15\x09\x00\x00\xe6\xff\xff\xff\xed\xff\xff\xff\x8f\x09\x00\x00\x09\x0a\x00\x00\x83\x0a\x00\x00\xfd\x0a\x00\x00\x77\x0b\x00\x00\xf1\x0b\x00\x00\x6b\x0c\x00\x00\xc5\x0c\x00\x00\x43\x0d\x00\x00\xef\xff\xff\xff\xbd\x0d\x00\x00\x37\x0e\x00\x00\xb1\x0e\x00\x00\x2b\x0f\x00\x00\xa5\x0f\x00\x00\x1f\x10\x00\x00\x99\x10\x00\x00\x13\x11\x00\x00\x00\x00\x00\x00\xf1\xff\xff\xff\xf2\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc9\x11\x00\x00\x43\x12\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x12\x00\x00\x00\x00\x00\x00\x39\x13\x00\x00\x00\x00\x00\x00\xb5\x13\x00\x00\x00\x00\x00\x00\x31\x14\x00\x00\x00\x00\x00\x00\xad\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x15\x00\x00\x97\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\xff\xff\xff\x78\x00\x00\x00\x00\x00\x00\x00\xa5\x15\x00\x00\x23\x01\x00\x00\x1f\x16\x00\x00\x55\x00\x00\x00\x06\x00\x00\x00\x00\x00\x00\x00\x99\x16\x00\x00\x13\x17\x00\x00\xd8\x04\x00\x00\x6a\x01\x00\x00\x9f\x05\x00\x00\x5f\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x66\x00\x00\x00\x15\x00\x00\x00\x6a\x00\x00\x00\x00\x00\x00\x00\xe2\x04\x00\x00\x89\x17\x00\x00\xa0\x01\x00\x00\xc9\x17\x00\x00\x47\x18\x00\x00\xb5\x00\x00\x00\xcb\x00\x00\x00\x8f\x03\x00\x00\x8a\x00\x00\x00\x8f\x00\x00\x00\xc5\x18\x00\x00\xd4\x05\x00\x00\x3b\x19\x00\x00\x1e\x04\x00\x00\x7b\x19\x00\x00\xf9\x19\x00\x00\x77\x1a\x00\x00\xf1\x1a\x00\x00\x6b\x1b\x00\x00\xe5\x1b\x00\x00\x5f\x1c\x00\x00\x49\x01\x00\x00\xd9\x1c\x00\x00\x53\x1d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x7c\x04\x00\x00\x7c\x00\x00\x00\x95\x00\x00\x00\x00\x00\x00\x00\x96\x00\x00\x00\x00\x00\x00\x00\x31\x00\x00\x00\x46\x00\x00\x00\x49\x00\x00\x00\x6b\x00\x00\x00\x7f\x00\x00\x00\xd9\x00\x00\x00\x00\x00\x00\x00\xd2\x00\x00\x00\x7d\x00\x00\x00\x81\x00\x00\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe3\x00\x00\x00\x00\x00\x00\x00\x4f\x02\x00\x00\x02\x04\x00\x00\xca\x1d\x00\x00\xf2\x1d\x00\x00\x35\x1e\x00\x00\x5d\x1e\x00\x00\xc3\x00\x00\x00\xa0\x1e\x00\x00\xc8\x1e\x00\x00\xe7\x00\x00\x00\xeb\x00\x00\x00\xed\x00\x00\x00\xef\x00\x00\x00\xf0\x00\x00\x00\xf4\x00\x00\x00\x03\x01\x00\x00\xd4\x00\x00\x00\x48\x05\x00\x00\x00\x00\x00\x00\x23\x04\x00\x00\x0d\x06\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x01\x00\x00\xa1\x00\x00\x00\x94\x00\x00\x00\x98\x00\x00\x00\x22\x02\x00\x00\xa4\x00\x00\x00\x97\x00\x00\x00\x9d\x00\x00\x00\xba\x02\x00\x00\xaf\x00\x00\x00\xa2\x00\x00\x00\xa6\x00\x00\x00\xbb\x02\x00\x00\xb2\x00\x00\x00\xa7\x00\x00\x00\xa9\x00\x00\x00\x00\x00\x00\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xff\x00\x00\x00\x00\x00\x00\x00\x02\x01\x00\x00\x00\x00\x00\x00\x09\x01\x00\x00\x00\x00\x00\x00\x07\x01\x00\x00\x00\x00\x00\x00\x0d\x01\x00\x00\x00\x00\x00\x00\x12\x01\x00\x00\x00\x00\x00\x00\x13\x01\x00\x00\x00\x00\x00\x00\x14\x01\x00\x00\x00\x00\x00\x00\x16\x01\x00\x00\x00\x00\x00\x00\x18\x01\x00\x00\x00\x00\x00\x00\x1c\x01\x00\x00\x00\x00\x00\x00\xee\x00\x00\x00\xda\x00\x00\x00\xf1\x00\x00\x00\xe9\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdb\x02\x00\x00\xe5\x00\x00\x00\xfc\x00\x00\x00\xdc\x02\x00\x00\xea\x00\x00\x00\x0b\x01\x00\x00\xfb\x02\x00\x00\x06\x01\x00\x00\x0e\x01\x00\x00\x10\x03\x00\x00\x0a\x01\x00\x00\x15\x01\x00\x00\xe9\x03\x00\x00\x11\x01\x00\x00\x1b\x01\x00\x00\x09\x04\x00\x00\x1a\x01\x00\x00\x30\x01\x00\x00\x2c\x04\x00\x00\x2c\x01\x00\x00\x33\x01\x00\x00\x32\x04\x00\x00\x2e\x01\x00\x00\x35\x01\x00\x00\x00\x00\x00\x00\x27\x01\x00\x00\x00\x00\x00\x00\x29\x01\x00\x00\x00\x00\x00\x00\x3c\x01\x00\x00\x00\x00\x00\x00\x3d\x01\x00\x00\x00\x00\x00\x00\x47\x01\x00\x00\x00\x00\x00\x00\x52\x01\x00\x00\x00\x00\x00\x00\x70\x01\x00\x00\x00\x00\x00\x00\x74\x01\x00\x00\x00\x00\x00\x00\x7e\x01\x00\x00\x00\x00\x00\x00\x7f\x01\x00\x00\x00\x00\x00\x00\xe6\x1e\x00\x00\x60\x1f\x00\x00\x8c\x01\x00\x00\x00\x00\x00\x00\x8d\x01\x00\x00\x00\x00\x00\x00\x92\x01\x00\x00\x00\x00\x00\x00\xb0\x01\x00\x00\x00\x00\x00\x00\xb2\x01\x00\x00\x00\x00\x00\x00\xd0\x01\x00\x00\x00\x00\x00\x00\xd8\x01\x00\x00\x00\x00\x00\x00\xd9\x01\x00\x00\x00\x00\x00\x00\xda\x01\x00\x00\x00\x00\x00\x00\xda\x1f\x00\x00\x14\x20\x00\x00\xdb\x01\x00\x00\x00\x00\x00\x00\xdc\x01\x00\x00\x00\x00\x00\x00\xdd\x01\x00\x00\x00\x00\x00\x00\xde\x01\x00\x00\x00\x00\x00\x00\xef\x01\x00\x00\x8e\x20\x00\x00\x08\x21\x00\x00\x82\x21\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x02\x00\x00\x00\x00\x00\x00\x04\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdf\x01\x00\x00\xe0\x01\x00\x00\xe1\x01\x00\x00\xe2\x01\x00\x00\x1d\x03\x00\x00\x97\x06\x00\x00\xb9\x06\x00\x00\xfc\x07\x00\x00\x76\x08\x00\x00\x6f\x17\x00\x00\x73\x07\x00\x00\x7e\x07\x00\x00\xf0\x08\x00\x00\x55\x03\x00\x00\x56\x03\x00\x00\xcd\x21\x00\x00"#
alex_table :: AlexAddr
alex_table = AlexA#
  "\x00\x00\x3e\x00\x4c\x00\x51\x00\x44\x00\x3a\x00\xd6\x00\xc0\x00\x3f\x00\x44\x00\xd5\x00\xa8\x00\xd6\x00\xd6\x00\xd6\x00\x14\x00\x45\x00\x14\x00\x4f\x00\x75\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x7f\x00\xd4\x00\x7a\x00\xd6\x00\x3a\x00\xd8\x00\x39\x00\x3a\x00\x3a\x00\x3a\x00\xd9\x00\x62\x00\x61\x00\x3a\x00\x3a\x00\x5d\x00\x35\x00\x3a\x00\x3a\x00\x2f\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x34\x00\x5c\x00\x3a\x00\x3a\x00\x3a\x00\x3b\x00\x3a\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x5f\x00\x3a\x00\x5e\x00\x3a\x00\x58\x01\x5b\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x59\x00\x37\x00\x58\x00\x3a\x00\xd6\x00\xc2\x00\x82\x00\x83\x00\xd5\x00\xbf\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xc2\x00\x65\x00\x8a\x00\xd5\x00\x8b\x00\xd6\x00\xd6\x00\xd6\x00\x8f\x00\x8d\x00\xff\xff\x28\x00\x28\x00\xca\x00\x68\x01\xff\xff\xa5\x00\xad\x00\x7d\x00\xaf\x00\xba\x00\xb0\x00\xb2\x00\x6b\x01\x7d\x00\xb4\x00\xd6\x00\xd6\x00\xc2\x00\xb5\x00\xc9\x00\xd5\x00\xab\x00\xd6\x00\xd6\x00\xd6\x00\x28\x00\x28\x00\xb6\x00\xc9\x00\x31\x00\x31\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x21\x01\xff\xff\xd6\x00\xd6\x00\xc2\x00\x06\x01\x27\x00\xd5\x00\xab\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xc2\x00\xe9\x00\xc9\x00\xd5\x00\xab\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\xc2\x00\xff\xff\x7d\x00\xd5\x00\xb7\x00\xd6\x00\xd6\x00\xd6\x00\xd6\x00\x27\x00\x77\x01\x06\x01\xb8\x00\x30\x00\xd2\x00\xb9\x00\x6a\x00\xd6\x00\xbc\x00\x8f\x00\x06\x01\xc9\x00\xbe\x00\x31\x00\x31\x00\xff\xff\xd6\x00\xbd\x00\xca\x00\xff\xff\xc9\x00\xb1\x00\x7d\x00\xff\xff\xd3\x00\xff\xff\xc7\x00\xff\xff\xff\xff\xc9\x00\xd6\x00\xc2\x00\xff\xff\xd3\x00\xd5\x00\xa5\x00\xd6\x00\xd6\x00\xd6\x00\xda\x00\xdb\x00\xdc\x00\xde\x00\xdf\x00\x97\x00\xc1\x00\xe0\x00\xff\xff\x98\x00\xff\xff\x97\x00\x97\x00\x97\x00\xe2\x00\xe3\x00\xe4\x00\xe6\x00\xd6\x00\xe8\x00\xe7\x00\x30\x00\xac\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\xc9\x00\x97\x00\x9a\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\xea\x00\x96\x00\xec\x00\xd6\x00\xc2\x00\xee\x00\xac\x00\xd5\x00\xf2\x00\xd6\x00\xd6\x00\xd6\x00\xf0\x00\xbb\x00\xf4\x00\xac\x00\xa9\x00\xb3\x00\x7c\x00\xf6\x00\xf8\x00\x80\x00\x7d\x00\x03\x01\xd3\x00\xfa\x00\x24\x00\xfc\x00\x7d\x00\xfe\x00\xd6\x00\xd6\x00\xc2\x00\x00\x01\xaa\x00\xd5\x00\x05\x01\xd6\x00\xd6\x00\xd6\x00\x0a\x01\x04\x01\x22\x01\xc9\x00\x24\x01\x0d\x01\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x7c\x00\x0b\x01\xd6\x00\xa6\x00\x7d\x00\x8c\x00\x87\x00\x26\x01\x28\x01\xd3\x00\x7d\x00\x87\x00\x87\x00\x87\x00\x87\x00\x8e\x00\x0e\x01\x10\x01\x2a\x01\x11\x01\xfb\x00\x13\x01\xf3\x00\x95\x00\x7d\x00\xeb\x00\x14\x01\x02\x01\x16\x01\x2c\x01\x50\x00\x42\x00\x17\x01\x87\x00\xd6\x00\xc2\x00\x89\x00\x19\x01\xd5\x00\xa8\x00\xd6\x00\xd6\x00\xd6\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x1a\x01\x7d\x00\x1c\x01\x1d\x01\x1f\x01\x20\x01\x2e\x01\x92\x00\xd6\x00\x7d\x00\x30\x01\x81\x00\xd3\x00\x92\x00\x92\x00\x92\x00\x63\x00\x61\x00\x32\x01\x34\x01\x5d\x00\xc9\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x36\x01\x3a\x01\x92\x00\x5c\x00\x93\x00\xd7\x00\x3c\x01\x7d\x00\xd3\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x60\x00\x3e\x01\x5e\x00\x40\x01\x42\x00\x5b\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x5a\x00\x42\x01\x58\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x44\x01\x46\x01\x48\x01\x4a\x01\x4e\x01\x50\x01\x52\x01\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x54\x01\x61\x01\x63\x01\x0c\x01\x0f\x01\x12\x01\x15\x01\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x00\x00\x00\x00\x00\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\xd7\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x01\x00\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x00\x00\xfd\x00\x00\x00\xf5\x00\x00\x00\x00\x00\xed\x00\xff\xff\x07\x01\xd7\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x74\x01\x00\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1b\x00\xce\x00\x1b\x00\x00\x00\x12\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x6a\x01\x00\x00\x00\x00\x00\x00\x10\x00\x00\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x00\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x25\x00\x12\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\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\x00\x00\x24\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\xce\x00\x00\x00\x00\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x12\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x13\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\xff\x00\x01\x01\xf7\x00\xf9\x00\x00\x00\xef\x00\xf1\x00\x08\x01\x09\x01\x12\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x18\x00\x00\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x45\x01\x47\x01\x33\x01\x35\x01\x00\x00\x23\x01\x25\x01\x59\x01\x5a\x01\x12\x00\x73\x01\x00\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x00\x00\x00\x00\x10\x00\x00\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x15\x00\x49\x01\x17\x00\x39\x01\x00\x00\x00\x00\x27\x01\x00\x00\x5b\x01\x00\x00\x12\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x65\x01\x4d\x01\x00\x00\x3b\x01\x00\x00\x00\x00\x29\x01\x71\x01\x5c\x01\x00\x00\x00\x00\x62\x01\x00\x00\x17\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x1c\x00\x20\x00\x00\x00\x20\x00\x1a\x00\x18\x01\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x51\x00\x51\x00\x51\x00\xdd\x00\x00\x00\x00\x00\x51\x00\x66\x01\x67\x01\x00\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\x1a\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x00\x00\x44\x00\x97\x00\x00\x00\x00\x00\x51\x00\x00\x00\xff\xff\x97\x00\x97\x00\x97\x00\x00\x00\x1b\x01\x1e\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x1f\x00\x00\x00\xe1\x00\xe5\x00\x00\x00\x97\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x56\x01\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x56\x01\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x64\x01\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x21\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x00\x00\x4f\x01\x2d\x00\x3d\x01\x00\x00\x00\x00\x2b\x01\x00\x00\x5d\x01\xd7\x00\x9d\x00\x00\x00\x00\x00\xcd\x00\x1f\x00\xd6\x00\x9d\x00\x9d\x00\x9d\x00\xcd\x00\x00\x00\xd6\x00\xd6\x00\xd6\x00\x22\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x69\x01\x51\x01\x00\x00\x3f\x01\x00\x00\x9d\x00\x2d\x01\x9e\x00\x5e\x01\xd7\x00\xd6\x00\x0d\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x53\x01\x6c\x01\x41\x01\xcd\x00\x00\x00\x2f\x01\x55\x01\x5f\x01\x43\x01\xd7\x00\x00\x00\x31\x01\x73\x01\x60\x01\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x22\x00\x00\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x23\x00\x27\x00\xcd\x00\x00\x00\x17\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\xd6\x00\xd6\x00\xd6\x00\x24\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x22\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x00\x00\x00\xd6\x00\x27\x00\x76\x01\xae\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x24\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x2e\x00\x22\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x00\x00\x6c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x73\x01\x00\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x29\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x29\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x00\x00\x6d\x01\x00\x00\x00\x00\x2b\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x11\x00\x00\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\x86\x00\x00\x00\x00\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x90\x00\x0c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x12\x00\x00\x00\x00\x00\x6f\x01\x00\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x13\x00\x00\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x2c\x00\x30\x00\x00\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x00\x00\x7c\x00\x00\x00\x12\x00\x7e\x00\x7d\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x7d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x32\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x2b\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x00\x00\x0c\x00\x87\x00\x00\x00\x7d\x00\x00\x00\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x1d\x00\x6f\x01\x00\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x33\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x34\x00\x89\x00\x00\x00\x7d\x00\x1d\x00\x00\x00\x32\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x00\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x88\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x34\x00\x32\x00\x34\x00\x34\x00\x34\x00\x34\x00\x00\x00\x1d\x00\x00\x00\x34\x00\x34\x00\x00\x00\x34\x00\x34\x00\x34\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x34\x00\x00\x00\x34\x00\x34\x00\x34\x00\x34\x00\x34\x00\x86\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x34\x00\x00\x00\x34\x00\x3a\x00\x3a\x00\x00\x00\xc5\x00\x3a\x00\x3a\x00\x26\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x2a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x9b\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x34\x00\xd7\x00\x34\x00\x3a\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x18\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x69\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x83\x00\x3a\x00\x3a\x00\x79\x00\x3a\x00\x64\x01\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x3a\x00\x78\x00\x3a\x00\x67\x00\x67\x00\x67\x00\x3a\x00\x00\x00\x00\x00\x67\x00\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x00\x00\x00\x00\x00\x00\x70\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x66\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x67\x00\x00\x00\x64\x00\x3a\x00\x3a\x00\x00\x00\x36\x00\x3a\x00\x3a\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x67\x00\x3a\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x68\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x00\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x68\x00\x3c\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x74\x01\x3a\x00\x3c\x00\x3a\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3d\x00\x00\x00\x00\x00\x3c\x00\x3c\x00\x00\x00\x3c\x00\x3c\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x00\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x3d\x00\x00\x00\x3d\x00\x3d\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x3d\x00\x3c\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3c\x00\x3d\x00\x00\x00\x3d\x00\x00\x00\x1d\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x70\x01\x00\x00\x3d\x00\x00\x00\x3d\x00\x00\x00\x1d\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x42\x00\x42\x00\x42\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x00\x00\x00\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x19\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\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\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x71\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x00\x00\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x42\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x41\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x75\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x40\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x4a\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x48\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x4b\x00\x4b\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x45\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4c\x00\x4c\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3e\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4d\x00\x00\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4b\x00\x49\x00\x00\x00\x3d\x00\x4c\x00\x00\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x4c\x00\x3d\x00\x00\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x3d\x00\x00\x00\x3d\x00\x3d\x00\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3c\x00\x00\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x3d\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x4b\x00\x00\x00\x3d\x00\x00\x00\x3d\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x4e\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x46\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x3d\x00\x00\x00\x3d\x00\x49\x00\x49\x00\x49\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4f\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\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x00\x00\x00\x00\x00\x00\x00\x00\x49\x00\x00\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x47\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x49\x00\x50\x00\x50\x00\x50\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x01\x00\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x50\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x52\x00\x52\x00\x52\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x4c\x01\x00\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x52\x00\x00\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x57\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x56\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x38\x01\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x71\x00\x76\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x73\x00\x6d\x00\x6d\x00\x6d\x00\x6f\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x7b\x00\x67\x00\x67\x00\x67\x00\x00\x00\x00\x00\x00\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x00\x00\x00\x00\x00\x00\x00\x00\x67\x00\x00\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x67\x00\x68\x00\x68\x00\x68\x00\x00\x00\x00\x00\x00\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x00\x00\x00\x00\x00\x00\x00\x00\x68\x00\x00\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x68\x00\x6b\x00\x6b\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x00\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x00\x00\x6c\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x6e\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x70\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x72\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x74\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x00\x00\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x6d\x00\x00\x00\x77\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\xa2\x00\x00\x00\xa3\x00\x00\x00\x00\x00\xa2\x00\xa2\x00\xa2\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\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\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\xa0\x00\x00\x00\xa1\x00\x00\x00\x00\x00\xa0\x00\xa0\x00\xa0\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x00\x00\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\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\x85\x00\x85\x00\x85\x00\x00\x00\x84\x00\x00\x00\x85\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\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\x85\x00\x85\x00\x85\x00\x00\x00\x00\x00\x00\x00\x85\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x92\x00\x00\x00\x00\x00\x00\x00\x62\x01\x00\x00\x92\x00\x92\x00\x92\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x72\x01\x92\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x91\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x93\x00\x93\x00\x93\x00\x93\x00\x75\x01\x93\x00\x93\x00\x00\x00\x00\x00\x00\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\x00\x93\x00\x93\x00\x94\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x00\x00\x93\x00\x93\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x93\x00\x93\x00\x94\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\x93\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x9a\x00\x00\x00\xa4\x00\x00\x00\x00\x00\xa6\x00\x9a\x00\x9a\x00\x9a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x00\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x9d\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x9c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x00\x00\x9e\x00\x9e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9b\x00\x9e\x00\x9e\x00\x9f\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x00\x00\x9e\x00\x9e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9e\x00\x9e\x00\x9f\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\x9e\x00\xa1\x00\xa1\x00\xa1\x00\x00\x00\xa0\x00\x00\x00\xa1\x00\x00\x00\x00\x00\xa0\x00\xa0\x00\xa0\x00\xa0\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\x00\x00\x00\x00\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\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\xa1\x00\xa1\x00\xa1\x00\x00\x00\x84\x00\x00\x00\xa1\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\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\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\xa3\x00\xa3\x00\xa3\x00\x00\x00\xa2\x00\x00\x00\xa3\x00\x00\x00\x00\x00\xa2\x00\xa2\x00\xa2\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\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\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x84\x00\x00\x00\xa3\x00\x00\x00\x00\x00\x84\x00\x84\x00\x84\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa3\x00\x00\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa3\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x00\x00\x00\x00\xa4\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\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x00\x00\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa4\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\xa6\x00\x00\x00\xa7\x00\x00\x00\x00\x00\xa6\x00\xa6\x00\xa6\x00\xa6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\x00\x00\x00\x00\xa7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa7\x00\x00\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\xa7\x00\x3a\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc4\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\xc6\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x3a\x00\x00\x00\xc6\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\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\x3a\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x00\x00\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc3\x00\x99\x00\x00\x00\x99\x00\x99\x00\x99\x00\x99\x00\x00\x00\x00\x00\x00\x00\x99\x00\x99\x00\x99\x00\xc8\x00\x99\x00\x99\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3a\x00\x99\x00\x3a\x00\x99\x00\x99\x00\x99\x00\x99\x00\x99\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x00\x00\x00\x99\x00\x99\x00\x99\x00\x99\x00\x00\x00\x00\x00\x00\x00\x99\x00\x99\x00\x00\x00\xc8\x00\x99\x00\x99\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x00\x00\x00\x99\x00\x00\x00\x00\x00\x00\x00\x99\x00\x00\x00\x99\x00\x99\x00\x99\x00\x99\x00\x99\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x00\x00\x00\x99\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x00\x00\x00\x99\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc4\x00\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\xff\xff\xff\xff\xff\xff\xcb\x00\xff\xff\xff\xff\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x00\xff\xff\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x01\x6b\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\xcb\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x00\x00\x00\x00\x00\x00\xff\xff\x6b\x00\xff\xff\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x6b\x00\x38\x01\x38\x01\x38\x01\x00\x00\x00\x00\x00\x00\x38\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x37\x01\x00\x00\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x00\x00\x00\x00\x00\x00\x00\x00\x38\x01\x00\x00\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x38\x01\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x52\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x54\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x55\x00\x55\x00\x55\x00\x53\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x4b\x01\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x55\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x20\x00\x00\x00\x00\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x43\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x01\x00\x00\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x56\x01\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x56\x01\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x44\x00\x00\x00\x00\x00\x00\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x57\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x00\x00\x00\x00\x00\x00\x00\x00\x58\x01\x00\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x51\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x01\x00\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x0e\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd7\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
alex_check :: AlexAddr
alex_check = AlexA#
  "\xff\xff\x23\x00\x01\x00\x02\x00\x23\x00\x04\x00\x05\x00\x06\x00\x23\x00\x23\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x2b\x00\x23\x00\x2d\x00\x23\x00\x7c\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x2d\x00\x2d\x00\x7c\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\x06\x00\x2d\x00\x7d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x23\x00\x2d\x00\x09\x00\x7d\x00\x0b\x00\x0c\x00\x0d\x00\x7d\x00\x2d\x00\x0a\x00\x30\x00\x31\x00\x2d\x00\x23\x00\x0a\x00\x2d\x00\x20\x00\x24\x00\x21\x00\x23\x00\x0a\x00\x0a\x00\x23\x00\x2a\x00\x72\x00\x20\x00\x05\x00\x06\x00\x61\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x67\x00\x2d\x00\x30\x00\x31\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x49\x00\x0a\x00\x20\x00\x05\x00\x06\x00\x23\x00\x5f\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x57\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x0a\x00\x5e\x00\x09\x00\x6d\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\x5f\x00\x23\x00\x23\x00\x61\x00\x5f\x00\x2d\x00\x0a\x00\x7c\x00\x20\x00\x69\x00\x7d\x00\x23\x00\x2d\x00\x65\x00\x30\x00\x31\x00\x0a\x00\x20\x00\x6e\x00\x2d\x00\x0a\x00\x2d\x00\x21\x00\x7c\x00\x0a\x00\x7b\x00\x0a\x00\x2d\x00\x0a\x00\x0a\x00\x2d\x00\x05\x00\x06\x00\x0a\x00\x7b\x00\x09\x00\x2d\x00\x0b\x00\x0c\x00\x0d\x00\x64\x00\x72\x00\x6f\x00\x64\x00\x72\x00\x05\x00\x06\x00\x6f\x00\x0a\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x64\x00\x72\x00\x6f\x00\x64\x00\x20\x00\x6f\x00\x72\x00\x5f\x00\x7b\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x2d\x00\x20\x00\x23\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x34\x00\x2d\x00\x34\x00\x05\x00\x06\x00\x34\x00\x7b\x00\x09\x00\x32\x00\x0b\x00\x0c\x00\x0d\x00\x34\x00\x6c\x00\x32\x00\x7b\x00\x7c\x00\x70\x00\x20\x00\x32\x00\x32\x00\x23\x00\x24\x00\x6e\x00\x7b\x00\x36\x00\x5f\x00\x36\x00\x2a\x00\x36\x00\x20\x00\x05\x00\x06\x00\x36\x00\x65\x00\x09\x00\x6c\x00\x0b\x00\x0c\x00\x0d\x00\x74\x00\x69\x00\x34\x00\x2d\x00\x34\x00\x74\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x20\x00\x6e\x00\x20\x00\x23\x00\x24\x00\x23\x00\x05\x00\x34\x00\x34\x00\x7b\x00\x2a\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x2d\x00\x6e\x00\x74\x00\x34\x00\x6e\x00\x31\x00\x74\x00\x33\x00\x7b\x00\x5e\x00\x36\x00\x6e\x00\x38\x00\x74\x00\x34\x00\x01\x00\x02\x00\x6e\x00\x20\x00\x05\x00\x06\x00\x23\x00\x74\x00\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\x6e\x00\x7c\x00\x74\x00\x6e\x00\x74\x00\x6e\x00\x34\x00\x05\x00\x20\x00\x5e\x00\x34\x00\x23\x00\x7b\x00\x0b\x00\x0c\x00\x0d\x00\x28\x00\x29\x00\x32\x00\x32\x00\x2c\x00\x2d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x32\x00\x32\x00\x20\x00\x3b\x00\x22\x00\x5f\x00\x32\x00\x7c\x00\x7b\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\x32\x00\x5d\x00\x32\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\x32\x00\x7d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x36\x00\x36\x00\x36\x00\x36\x00\x36\x00\x36\x00\x36\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\x36\x00\x23\x00\x23\x00\x49\x00\x49\x00\x49\x00\x49\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\xff\xff\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\xff\xff\x31\x00\xff\xff\x33\x00\xff\xff\xff\xff\x36\x00\x0a\x00\x38\x00\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\x24\x00\xff\xff\xff\xff\xff\xff\xff\xff\x2b\x00\x2a\x00\x2d\x00\xff\xff\x50\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x23\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\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\x5e\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\x5f\x00\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x7c\x00\xff\xff\xff\xff\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\x31\x00\x31\x00\x33\x00\x33\x00\xff\xff\x36\x00\x36\x00\x38\x00\x38\x00\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\x31\x00\x31\x00\x33\x00\x33\x00\xff\xff\x36\x00\x36\x00\x38\x00\x38\x00\x50\x00\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\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x31\x00\x45\x00\x33\x00\xff\xff\xff\xff\x36\x00\xff\xff\x38\x00\xff\xff\x70\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x23\x00\x31\x00\xff\xff\x33\x00\xff\xff\xff\xff\x36\x00\x5f\x00\x38\x00\xff\xff\xff\xff\x23\x00\xff\xff\x65\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\x2b\x00\xff\xff\x2d\x00\x5f\x00\x49\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\x57\x00\xff\xff\xff\xff\x07\x00\x23\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\x5f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x23\x00\x05\x00\xff\xff\xff\xff\x27\x00\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\x49\x00\x49\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5f\x00\xff\xff\x57\x00\x57\x00\xff\xff\x20\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\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\x23\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x0a\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\xff\xff\x31\x00\x5f\x00\x33\x00\xff\xff\xff\xff\x36\x00\xff\xff\x38\x00\x50\x00\x05\x00\xff\xff\xff\xff\x24\x00\x5f\x00\x05\x00\x0b\x00\x0c\x00\x0d\x00\x2a\x00\xff\xff\x0b\x00\x0c\x00\x0d\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x23\x00\x31\x00\xff\xff\x33\x00\xff\xff\x20\x00\x36\x00\x22\x00\x38\x00\x70\x00\x20\x00\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\x31\x00\x23\x00\x33\x00\x5e\x00\xff\xff\x36\x00\x31\x00\x38\x00\x33\x00\x50\x00\xff\xff\x36\x00\x2e\x00\x38\x00\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\x7c\x00\xff\xff\x45\x00\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\x0b\x00\x0c\x00\x0d\x00\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\x20\x00\x62\x00\x23\x00\x23\x00\x65\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\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\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x45\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x45\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\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x23\x00\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x5f\x00\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\x20\x00\xff\xff\x70\x00\x23\x00\x24\x00\xff\xff\x4f\x00\xff\xff\xff\xff\xff\xff\x2a\x00\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\xff\xff\xff\xff\xff\xff\x6f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x78\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x23\x00\x05\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x45\x00\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\x20\x00\xff\xff\x04\x00\x23\x00\xff\xff\x7c\x00\x45\x00\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\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\x5f\x00\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\x65\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\x04\x00\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\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\x5c\x00\xff\xff\x5e\x00\x2a\x00\x2b\x00\xff\xff\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\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x2b\x00\x7c\x00\x2d\x00\x7e\x00\x04\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\x5c\x00\xff\xff\x5e\x00\x5f\x00\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\x5f\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\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\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\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\x23\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\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\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x45\x00\xff\xff\xff\xff\x5c\x00\x5d\x00\x5e\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\xff\xff\x07\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\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\x7c\x00\xff\xff\x7e\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\xff\xff\x29\x00\x2a\x00\x2b\x00\xff\xff\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\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\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\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\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\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\x5c\x00\xff\xff\x5e\x00\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\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\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\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\x5f\x00\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\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\x5c\x00\x3a\x00\x5e\x00\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\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\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\xff\xff\x45\x00\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\x5f\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\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\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\x45\x00\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\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\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\x45\x00\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\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\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\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\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\x01\x00\x02\x00\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\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\xff\xff\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\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\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\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\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\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\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\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\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\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\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\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\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\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\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\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\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\x05\x00\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\x0b\x00\x0c\x00\x0d\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\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x45\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\xff\xff\xff\xff\xff\xff\x01\x00\x02\x00\x03\x00\x04\x00\x5f\x00\x06\x00\x07\x00\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\x5f\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\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\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\xff\xff\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\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\x5f\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\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\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\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\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\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\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\xff\xff\xff\xff\xff\xff\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\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\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\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\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\x20\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\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\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\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\x20\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\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\x01\x00\x02\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\xff\xff\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\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\x7c\x00\x5f\x00\x7e\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\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\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\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\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\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"#
alex_deflt :: AlexAddr
alex_deflt = AlexA#
  "\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x99\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\x99\x00\x99\x00\x99\x00\x99\x00\x99\x00\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x99\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xaf\x00\xff\xff\xb1\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xb8\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x99\x00\xff\xff\xd1\x00\xd1\x00\xd0\x00\xcc\x00\xd0\x00\xcc\x00\xff\xff\xd0\x00\xcc\x00\xcc\x00\xcf\x00\xce\x00\xcf\x00\xd0\x00\xd1\x00\x99\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
alex_accept = listArray (0 :: Int, 376)
  [ AlexAccNone
  , AlexAcc 249
  , AlexAccNone
  , AlexAcc 248
  , AlexAcc 247
  , AlexAcc 246
  , AlexAcc 245
  , AlexAcc 244
  , AlexAcc 243
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 242 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 241 (ifExtension HexFloatLiteralsBit `alexAndPred`
                                           negLitPred)(AlexAccNone)
  , AlexAccPred 240 (ifExtension HexFloatLiteralsBit `alexAndPred`
                                           negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 239 (ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccPred 238 (ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 237 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 236
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 235
  , AlexAccNone
  , AlexAccPred 234 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 233 (negLitPred)(AlexAccNone)
  , AlexAccPred 232 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 231 (negLitPred `alexAndPred`
                                ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 230 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 229
  , AlexAccNone
  , AlexAcc 228
  , AlexAcc 227
  , AlexAccNone
  , AlexAccPred 226 (ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 225
  , AlexAcc 224
  , AlexAcc 223
  , AlexAcc 222
  , AlexAcc 221
  , AlexAcc 220
  , AlexAcc 219
  , AlexAcc 218
  , AlexAcc 217
  , AlexAcc 216
  , AlexAcc 215
  , AlexAccPred 214 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 213 (ifExtension MagicHashBit)(AlexAccPred 212 (ifExtension MagicHashBit)(AlexAccNone))
  , AlexAcc 211
  , AlexAccPred 210 (ifExtension MagicHashBit)(AlexAccPred 209 (ifExtension MagicHashBit)(AlexAccNone))
  , AlexAcc 208
  , AlexAcc 207
  , AlexAccPred 206 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 205 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 204
  , AlexAcc 203
  , AlexAccPred 202 (ifExtension RecursiveDoBit)(AlexAcc 201)
  , AlexAcc 200
  , AlexAcc 199
  , AlexAcc 198
  , AlexAcc 197
  , AlexAccNone
  , AlexAcc 196
  , AlexAccPred 195 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 194
  , AlexAcc 193
  , AlexAcc 192
  , AlexAcc 191
  , AlexAcc 190
  , AlexAcc 189
  , AlexAccPred 188 (ifExtension RecursiveDoBit)(AlexAcc 187)
  , AlexAcc 186
  , AlexAcc 185
  , AlexAcc 184
  , AlexAcc 183
  , AlexAcc 182
  , AlexAcc 181
  , AlexAcc 180
  , AlexAcc 179
  , AlexAcc 178
  , AlexAcc 177
  , AlexAcc 176
  , AlexAcc 175
  , AlexAcc 174
  , AlexAccPred 173 (ifExtension UnboxedParensBit)(AlexAccNone)
  , AlexAccPred 172 (ifExtension UnboxedParensBit)(AlexAccNone)
  , AlexAccPred 171 (ifExtension OverloadedLabelsBit)(AlexAccNone)
  , AlexAccPred 170 (ifExtension OverloadedLabelsBit)(AlexAccNone)
  , AlexAccPred 169 (ifExtension IpBit)(AlexAccNone)
  , AlexAccPred 168 (ifExtension ArrowsBit)(AlexAccNone)
  , AlexAccPred 167 (ifExtension ArrowsBit `alexAndPred`
        notFollowedBySymbol)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 166 (ifExtension QqBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 165 (ifExtension QqBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 164 (ifExtension ThQuotesBit)(AlexAccPred 163 (ifExtension QqBit)(AlexAccNone))
  , AlexAccNone
  , AlexAccPred 162 (ifExtension ThQuotesBit)(AlexAccPred 161 (ifExtension QqBit)(AlexAccNone))
  , AlexAccNone
  , AlexAccPred 160 (ifExtension ThQuotesBit)(AlexAccPred 159 (ifExtension QqBit)(AlexAccNone))
  , AlexAccPred 158 (ifExtension ThQuotesBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 157 (ifExtension ThQuotesBit)(AlexAccPred 156 (ifExtension QqBit)(AlexAccNone))
  , AlexAcc 155
  , AlexAcc 154
  , AlexAcc 153
  , AlexAcc 152
  , AlexAccNone
  , AlexAccPred 151 (ifExtension HaddockBit)(AlexAccNone)
  , AlexAcc 150
  , AlexAccPred 149 (isNormalComment)(AlexAccNone)
  , AlexAcc 148
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 147
  , AlexAccNone
  , AlexAccPred 146 (known_pragma twoWordPrags)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 145
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 144
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 143
  , AlexAcc 142
  , AlexAcc 141
  , AlexAccSkip
  , AlexAcc 140
  , AlexAcc 139
  , AlexAcc 138
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 137
  , AlexAccNone
  , AlexAccPred 136 (known_pragma linePrags)(AlexAccPred 135 (known_pragma oneWordPrags)(AlexAccPred 134 (known_pragma ignoredPrags)(AlexAccPred 133 (known_pragma fileHeaderPrags)(AlexAcc 132))))
  , AlexAccNone
  , AlexAccPred 131 (known_pragma linePrags)(AlexAccPred 130 (known_pragma oneWordPrags)(AlexAccPred 129 (known_pragma ignoredPrags)(AlexAccPred 128 (known_pragma fileHeaderPrags)(AlexAcc 127))))
  , AlexAccPred 126 (known_pragma linePrags)(AlexAcc 125)
  , AlexAccPred 124 (isNormalComment)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 123 (known_pragma linePrags)(AlexAccNone)
  , AlexAcc 122
  , AlexAccPred 121 (notFollowedBySymbol)(AlexAccNone)
  , AlexAccPred 120 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccSkip
  , AlexAccPred 119 (notFollowedBy '-')(AlexAccNone)
  , AlexAccSkip
  , AlexAccNone
  , AlexAccNone
  , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccNone
  , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccPred 118 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False) `alexAndPred` followedByDigit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 117 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccSkip
  , AlexAccPred 116 (isSmartQuote)(AlexAccPred 115 (ifCurrentChar '⟦' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ThQuotesBit)(AlexAccPred 114 (ifCurrentChar '⟧' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ThQuotesBit)(AlexAccPred 113 (ifCurrentChar '⦇' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ArrowsBit)(AlexAccPred 112 (ifCurrentChar '⦈' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ArrowsBit)(AlexAccNone)))))
  , AlexAccPred 111 (isSmartQuote)(AlexAcc 110)
  , AlexAccPred 109 (isSmartQuote)(AlexAccNone)
  , AlexAccPred 108 (atEOL)(AlexAcc 107)
  , AlexAccPred 106 (atEOL)(AlexAccNone)
  , AlexAccPred 105 (atEOL)(AlexAcc 104)
  , AlexAccPred 103 (atEOL)(AlexAcc 102)
  , AlexAccPred 101 (atEOL)(AlexAcc 100)
  , AlexAccPred 99 (atEOL)(AlexAcc 98)
  , AlexAccNone
  , AlexAccPred 97 (atEOL)(AlexAccNone)
  , AlexAccPred 96 (atEOL)(AlexAccNone)
  , AlexAcc 95
  , AlexAccPred 94 (alexNotPred (ifExtension HaddockBit))(AlexAccPred 93 (ifExtension HaddockBit)(AlexAccNone))
  , AlexAccPred 92 (alexNotPred (ifExtension HaddockBit))(AlexAcc 91)
  , AlexAccPred 90 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAcc 89
  , AlexAcc 88
  , AlexAccPred 87 (isNormalComment)(AlexAcc 86)
  , AlexAccNone
  , AlexAccPred 85 (isNormalComment)(AlexAccNone)
  , AlexAcc 84
  , AlexAccSkip
  , AlexAccNone
  , AlexAcc 83
  , AlexAcc 82
  , AlexAccPred 81 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 80 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 79 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 78 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 77 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 76 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 75 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 74 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 73 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 72 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 71 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 70 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 69 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 68 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 67 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 66 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 65 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 64 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccPred 63 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 62 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 61 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 60 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 59 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 58 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 57 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 56 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 55 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 54 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 53 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 52 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 51 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 50 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 49 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 48 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 47 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 46 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 45 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 44 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 43 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 42 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 41 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 40 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 39 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 38 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 37 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 36 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 35 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 34 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 33 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAcc 32
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 31 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 30 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 29 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 28 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 27
  , AlexAcc 26
  , AlexAcc 25
  , AlexAccPred 24 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 23 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 22 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 21 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 20 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 19 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 18 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                           ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 17 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 16 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 15 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 14 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 13 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 12 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 11 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 10 (ifExtension MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 9 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 8 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 7 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 6 (negHashLitPred MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 5 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 4 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 3
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 2 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 1 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 0 (ifExtension MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  ]
alex_actions = array (0 :: Int, 250)
  [ (249,alex_action_16)
  , (248,alex_action_22)
  , (247,alex_action_23)
  , (246,alex_action_21)
  , (245,alex_action_24)
  , (244,alex_action_28)
  , (243,alex_action_29)
  , (242,alex_action_100)
  , (241,alex_action_99)
  , (240,alex_action_99)
  , (239,alex_action_98)
  , (238,alex_action_98)
  , (237,alex_action_97)
  , (236,alex_action_78)
  , (235,alex_action_96)
  , (234,alex_action_95)
  , (233,alex_action_94)
  , (232,alex_action_92)
  , (231,alex_action_93)
  , (230,alex_action_92)
  , (229,alex_action_91)
  , (228,alex_action_90)
  , (227,alex_action_88)
  , (226,alex_action_89)
  , (225,alex_action_88)
  , (224,alex_action_87)
  , (223,alex_action_86)
  , (222,alex_action_86)
  , (221,alex_action_86)
  , (220,alex_action_86)
  , (219,alex_action_86)
  , (218,alex_action_86)
  , (217,alex_action_86)
  , (216,alex_action_85)
  , (215,alex_action_84)
  , (214,alex_action_83)
  , (213,alex_action_82)
  , (212,alex_action_113)
  , (211,alex_action_78)
  , (210,alex_action_82)
  , (209,alex_action_112)
  , (208,alex_action_78)
  , (207,alex_action_78)
  , (206,alex_action_82)
  , (205,alex_action_81)
  , (204,alex_action_76)
  , (203,alex_action_74)
  , (202,alex_action_75)
  , (201,alex_action_76)
  , (200,alex_action_76)
  , (199,alex_action_76)
  , (198,alex_action_77)
  , (197,alex_action_79)
  , (196,alex_action_76)
  , (195,alex_action_80)
  , (194,alex_action_79)
  , (193,alex_action_78)
  , (192,alex_action_77)
  , (191,alex_action_76)
  , (190,alex_action_76)
  , (189,alex_action_76)
  , (188,alex_action_75)
  , (187,alex_action_76)
  , (186,alex_action_74)
  , (185,alex_action_73)
  , (184,alex_action_72)
  , (183,alex_action_72)
  , (182,alex_action_71)
  , (181,alex_action_70)
  , (180,alex_action_69)
  , (179,alex_action_68)
  , (178,alex_action_67)
  , (177,alex_action_67)
  , (176,alex_action_66)
  , (175,alex_action_65)
  , (174,alex_action_65)
  , (173,alex_action_64)
  , (172,alex_action_63)
  , (171,alex_action_62)
  , (170,alex_action_61)
  , (169,alex_action_60)
  , (168,alex_action_57)
  , (167,alex_action_56)
  , (166,alex_action_53)
  , (165,alex_action_52)
  , (164,alex_action_51)
  , (163,alex_action_52)
  , (162,alex_action_50)
  , (161,alex_action_52)
  , (160,alex_action_49)
  , (159,alex_action_52)
  , (158,alex_action_48)
  , (157,alex_action_47)
  , (156,alex_action_52)
  , (155,alex_action_46)
  , (154,alex_action_45)
  , (153,alex_action_44)
  , (152,alex_action_43)
  , (151,alex_action_42)
  , (150,alex_action_40)
  , (149,alex_action_2)
  , (148,alex_action_40)
  , (147,alex_action_36)
  , (146,alex_action_33)
  , (145,alex_action_32)
  , (144,alex_action_31)
  , (143,alex_action_30)
  , (142,alex_action_29)
  , (141,alex_action_29)
  , (140,alex_action_1)
  , (139,alex_action_29)
  , (138,alex_action_29)
  , (137,alex_action_27)
  , (136,alex_action_26)
  , (135,alex_action_34)
  , (134,alex_action_35)
  , (133,alex_action_38)
  , (132,alex_action_39)
  , (131,alex_action_26)
  , (130,alex_action_34)
  , (129,alex_action_35)
  , (128,alex_action_37)
  , (127,alex_action_39)
  , (126,alex_action_26)
  , (125,alex_action_29)
  , (124,alex_action_2)
  , (123,alex_action_26)
  , (122,alex_action_25)
  , (121,alex_action_20)
  , (120,alex_action_19)
  , (119,alex_action_17)
  , (118,alex_action_12)
  , (117,alex_action_11)
  , (116,alex_action_9)
  , (115,alex_action_54)
  , (114,alex_action_55)
  , (113,alex_action_58)
  , (112,alex_action_59)
  , (111,alex_action_9)
  , (110,alex_action_29)
  , (109,alex_action_9)
  , (108,alex_action_8)
  , (107,alex_action_29)
  , (106,alex_action_8)
  , (105,alex_action_7)
  , (104,alex_action_86)
  , (103,alex_action_7)
  , (102,alex_action_86)
  , (101,alex_action_7)
  , (100,alex_action_29)
  , (99,alex_action_7)
  , (98,alex_action_29)
  , (97,alex_action_7)
  , (96,alex_action_7)
  , (95,alex_action_6)
  , (94,alex_action_5)
  , (93,alex_action_41)
  , (92,alex_action_5)
  , (91,alex_action_29)
  , (90,alex_action_5)
  , (89,alex_action_4)
  , (88,alex_action_3)
  , (87,alex_action_2)
  , (86,alex_action_29)
  , (85,alex_action_2)
  , (84,alex_action_1)
  , (83,alex_action_177)
  , (82,alex_action_176)
  , (81,alex_action_175)
  , (80,alex_action_174)
  , (79,alex_action_173)
  , (78,alex_action_172)
  , (77,alex_action_171)
  , (76,alex_action_170)
  , (75,alex_action_169)
  , (74,alex_action_168)
  , (73,alex_action_167)
  , (72,alex_action_166)
  , (71,alex_action_165)
  , (70,alex_action_164)
  , (69,alex_action_163)
  , (68,alex_action_162)
  , (67,alex_action_161)
  , (66,alex_action_160)
  , (65,alex_action_159)
  , (64,alex_action_19)
  , (63,alex_action_158)
  , (62,alex_action_157)
  , (61,alex_action_156)
  , (60,alex_action_155)
  , (59,alex_action_154)
  , (58,alex_action_153)
  , (57,alex_action_152)
  , (56,alex_action_151)
  , (55,alex_action_150)
  , (54,alex_action_149)
  , (53,alex_action_148)
  , (52,alex_action_147)
  , (51,alex_action_146)
  , (50,alex_action_145)
  , (49,alex_action_144)
  , (48,alex_action_143)
  , (47,alex_action_142)
  , (46,alex_action_141)
  , (45,alex_action_140)
  , (44,alex_action_139)
  , (43,alex_action_138)
  , (42,alex_action_137)
  , (41,alex_action_136)
  , (40,alex_action_135)
  , (39,alex_action_134)
  , (38,alex_action_133)
  , (37,alex_action_132)
  , (36,alex_action_131)
  , (35,alex_action_130)
  , (34,alex_action_129)
  , (33,alex_action_128)
  , (32,alex_action_76)
  , (31,alex_action_127)
  , (30,alex_action_126)
  , (29,alex_action_125)
  , (28,alex_action_124)
  , (27,alex_action_78)
  , (26,alex_action_78)
  , (25,alex_action_78)
  , (24,alex_action_123)
  , (23,alex_action_122)
  , (22,alex_action_121)
  , (21,alex_action_120)
  , (20,alex_action_119)
  , (19,alex_action_118)
  , (18,alex_action_117)
  , (17,alex_action_116)
  , (16,alex_action_115)
  , (15,alex_action_114)
  , (14,alex_action_113)
  , (13,alex_action_112)
  , (12,alex_action_111)
  , (11,alex_action_110)
  , (10,alex_action_109)
  , (9,alex_action_108)
  , (8,alex_action_107)
  , (7,alex_action_106)
  , (6,alex_action_105)
  , (5,alex_action_104)
  , (4,alex_action_103)
  , (3,alex_action_96)
  , (2,alex_action_97)
  , (1,alex_action_102)
  , (0,alex_action_101)
  ]
{-# LINE 794 "compiler/GHC/Parser/Lexer.x" #-}
data OpWs
  = OpWsPrefix         
  | OpWsSuffix         
  | OpWsTightInfix     
  | OpWsLooseInfix     
  deriving Show
data Token
  = ITas                        
  | ITcase
  | ITclass
  | ITdata
  | ITdefault
  | ITderiving
  | ITdo (Maybe FastString)
  | ITelse
  | IThiding
  | ITforeign
  | ITif
  | ITimport
  | ITin
  | ITinfix
  | ITinfixl
  | ITinfixr
  | ITinstance
  | ITlet
  | ITmodule
  | ITnewtype
  | ITof
  | ITqualified
  | ITthen
  | ITtype
  | ITwhere
  | ITforall            IsUnicodeSyntax 
  | ITexport
  | ITlabel
  | ITdynamic
  | ITsafe
  | ITinterruptible
  | ITunsafe
  | ITstdcallconv
  | ITccallconv
  | ITcapiconv
  | ITprimcallconv
  | ITjavascriptcallconv
  | ITmdo (Maybe FastString)
  | ITfamily
  | ITrole
  | ITgroup
  | ITby
  | ITusing
  | ITpattern
  | ITstatic
  | ITstock
  | ITanyclass
  | ITvia
  
  | ITunit
  | ITsignature
  | ITdependency
  | ITrequires
  
  | ITinline_prag       SourceText InlineSpec RuleMatchInfo
  | ITopaque_prag       SourceText
  | ITspec_prag         SourceText                
  | ITspec_inline_prag  SourceText Bool    
  | ITsource_prag       SourceText
  | ITrules_prag        SourceText
  | ITwarning_prag      SourceText
  | ITdeprecated_prag   SourceText
  | ITline_prag         SourceText  
  | ITcolumn_prag       SourceText  
  | ITscc_prag          SourceText
  | ITunpack_prag       SourceText
  | ITnounpack_prag     SourceText
  | ITann_prag          SourceText
  | ITcomplete_prag     SourceText
  | ITclose_prag
  | IToptions_prag String
  | ITinclude_prag String
  | ITlanguage_prag
  | ITminimal_prag      SourceText
  | IToverlappable_prag SourceText  
  | IToverlapping_prag  SourceText  
  | IToverlaps_prag     SourceText  
  | ITincoherent_prag   SourceText  
  | ITctype             SourceText
  | ITcomment_line_prag         
  | ITdotdot                    
  | ITcolon
  | ITdcolon            IsUnicodeSyntax
  | ITequal
  | ITlam
  | ITlcase
  | ITlcases
  | ITvbar
  | ITlarrow            IsUnicodeSyntax
  | ITrarrow            IsUnicodeSyntax
  | ITdarrow            IsUnicodeSyntax
  | ITlolly       
  | ITminus       
  | ITprefixminus 
  | ITbang     
  | ITtilde    
  | ITat       
  | ITtypeApp  
  | ITpercent  
  | ITstar              IsUnicodeSyntax
  | ITdot
  | ITproj Bool 
  | ITbiglam                    
  | ITocurly                    
  | ITccurly
  | ITvocurly
  | ITvccurly
  | ITobrack
  | ITopabrack                  
  | ITcpabrack                  
  | ITcbrack
  | IToparen
  | ITcparen
  | IToubxparen
  | ITcubxparen
  | ITsemi
  | ITcomma
  | ITunderscore
  | ITbackquote
  | ITsimpleQuote               
  | ITvarid   FastString        
  | ITconid   FastString
  | ITvarsym  FastString
  | ITconsym  FastString
  | ITqvarid  (FastString,FastString)
  | ITqconid  (FastString,FastString)
  | ITqvarsym (FastString,FastString)
  | ITqconsym (FastString,FastString)
  | ITdupipvarid   FastString   
  | ITlabelvarid SourceText FastString   
                                         
                                         
                                         
  | ITchar     SourceText Char       
  | ITstring   SourceText FastString 
  | ITinteger  IntegralLit           
  | ITrational FractionalLit
  | ITprimchar   SourceText Char     
  | ITprimstring SourceText ByteString 
  | ITprimint    SourceText Integer  
  | ITprimword   SourceText Integer  
  | ITprimint8   SourceText Integer  
  | ITprimint16  SourceText Integer  
  | ITprimint32  SourceText Integer  
  | ITprimint64  SourceText Integer  
  | ITprimword8  SourceText Integer  
  | ITprimword16 SourceText Integer  
  | ITprimword32 SourceText Integer  
  | ITprimword64 SourceText Integer  
  | ITprimfloat  FractionalLit
  | ITprimdouble FractionalLit
  
  | ITopenExpQuote HasE IsUnicodeSyntax 
  | ITopenPatQuote                      
  | ITopenDecQuote                      
  | ITopenTypQuote                      
  | ITcloseQuote IsUnicodeSyntax        
  | ITopenTExpQuote HasE                
  | ITcloseTExpQuote                    
  | ITdollar                            
  | ITdollardollar                      
  | ITtyQuote                           
  | ITquasiQuote (FastString,FastString,PsSpan)
    
    
    
  | ITqQuasiQuote (FastString,FastString,FastString,PsSpan)
    
    
    
  
  | ITproc
  | ITrec
  | IToparenbar  IsUnicodeSyntax 
  | ITcparenbar  IsUnicodeSyntax 
  | ITlarrowtail IsUnicodeSyntax 
  | ITrarrowtail IsUnicodeSyntax 
  | ITLarrowtail IsUnicodeSyntax 
  | ITRarrowtail IsUnicodeSyntax 
  | ITunknown String             
  | ITeof                        
  
  | ITdocComment   HsDocString PsSpan 
                                      
  | ITdocOptions   String      PsSpan 
  | ITlineComment  String      PsSpan 
  | ITblockComment String      PsSpan 
  deriving Show
instance Outputable Token where
  ppr x = text (show x)
reservedWordsFM :: UniqFM FastString (Token, ExtsBitmap)
reservedWordsFM = listToUFM $
    map (\(x, y, z) -> (mkFastString x, (y, z)))
        [( "_",              ITunderscore,    0 ),
         ( "as",             ITas,            0 ),
         ( "case",           ITcase,          0 ),
         ( "cases",          ITlcases,        xbit LambdaCaseBit ),
         ( "class",          ITclass,         0 ),
         ( "data",           ITdata,          0 ),
         ( "default",        ITdefault,       0 ),
         ( "deriving",       ITderiving,      0 ),
         ( "do",             ITdo Nothing,    0 ),
         ( "else",           ITelse,          0 ),
         ( "hiding",         IThiding,        0 ),
         ( "if",             ITif,            0 ),
         ( "import",         ITimport,        0 ),
         ( "in",             ITin,            0 ),
         ( "infix",          ITinfix,         0 ),
         ( "infixl",         ITinfixl,        0 ),
         ( "infixr",         ITinfixr,        0 ),
         ( "instance",       ITinstance,      0 ),
         ( "let",            ITlet,           0 ),
         ( "module",         ITmodule,        0 ),
         ( "newtype",        ITnewtype,       0 ),
         ( "of",             ITof,            0 ),
         ( "qualified",      ITqualified,     0 ),
         ( "then",           ITthen,          0 ),
         ( "type",           ITtype,          0 ),
         ( "where",          ITwhere,         0 ),
         ( "forall",         ITforall NormalSyntax, 0),
         ( "mdo",            ITmdo Nothing,   xbit RecursiveDoBit),
             
         ( "family",         ITfamily,        0 ),
         ( "role",           ITrole,          0 ),
         ( "pattern",        ITpattern,       xbit PatternSynonymsBit),
         ( "static",         ITstatic,        xbit StaticPointersBit ),
         ( "stock",          ITstock,         0 ),
         ( "anyclass",       ITanyclass,      0 ),
         ( "via",            ITvia,           0 ),
         ( "group",          ITgroup,         xbit TransformComprehensionsBit),
         ( "by",             ITby,            xbit TransformComprehensionsBit),
         ( "using",          ITusing,         xbit TransformComprehensionsBit),
         ( "foreign",        ITforeign,       xbit FfiBit),
         ( "export",         ITexport,        xbit FfiBit),
         ( "label",          ITlabel,         xbit FfiBit),
         ( "dynamic",        ITdynamic,       xbit FfiBit),
         ( "safe",           ITsafe,          xbit FfiBit .|.
                                              xbit SafeHaskellBit),
         ( "interruptible",  ITinterruptible, xbit InterruptibleFfiBit),
         ( "unsafe",         ITunsafe,        xbit FfiBit),
         ( "stdcall",        ITstdcallconv,   xbit FfiBit),
         ( "ccall",          ITccallconv,     xbit FfiBit),
         ( "capi",           ITcapiconv,      xbit CApiFfiBit),
         ( "prim",           ITprimcallconv,  xbit FfiBit),
         ( "javascript",     ITjavascriptcallconv, xbit FfiBit),
         ( "unit",           ITunit,          0 ),
         ( "dependency",     ITdependency,       0 ),
         ( "signature",      ITsignature,     0 ),
         ( "rec",            ITrec,           xbit ArrowsBit .|.
                                              xbit RecursiveDoBit),
         ( "proc",           ITproc,          xbit ArrowsBit)
     ]
reservedSymsFM :: UniqFM FastString (Token, IsUnicodeSyntax, ExtsBitmap)
reservedSymsFM = listToUFM $
    map (\ (x,w,y,z) -> (mkFastString x,(w,y,z)))
      [ ("..",  ITdotdot,                   NormalSyntax,  0 )
        
       ,(":",   ITcolon,                    NormalSyntax,  0 )
       ,("::",  ITdcolon NormalSyntax,      NormalSyntax,  0 )
       ,("=",   ITequal,                    NormalSyntax,  0 )
       ,("\\",  ITlam,                      NormalSyntax,  0 )
       ,("|",   ITvbar,                     NormalSyntax,  0 )
       ,("<-",  ITlarrow NormalSyntax,      NormalSyntax,  0 )
       ,("->",  ITrarrow NormalSyntax,      NormalSyntax,  0 )
       ,("=>",  ITdarrow NormalSyntax,      NormalSyntax,  0 )
       ,("-",   ITminus,                    NormalSyntax,  xbit NoLexicalNegationBit)
       ,("*",   ITstar NormalSyntax,        NormalSyntax,  xbit StarIsTypeBit)
       ,("-<",  ITlarrowtail NormalSyntax,  NormalSyntax,  xbit ArrowsBit)
       ,(">-",  ITrarrowtail NormalSyntax,  NormalSyntax,  xbit ArrowsBit)
       ,("-<<", ITLarrowtail NormalSyntax,  NormalSyntax,  xbit ArrowsBit)
       ,(">>-", ITRarrowtail NormalSyntax,  NormalSyntax,  xbit ArrowsBit)
       ,("∷",   ITdcolon UnicodeSyntax,     UnicodeSyntax, 0 )
       ,("⇒",   ITdarrow UnicodeSyntax,     UnicodeSyntax, 0 )
       ,("∀",   ITforall UnicodeSyntax,     UnicodeSyntax, 0 )
       ,("→",   ITrarrow UnicodeSyntax,     UnicodeSyntax, 0 )
       ,("←",   ITlarrow UnicodeSyntax,     UnicodeSyntax, 0 )
       ,("⊸",   ITlolly, UnicodeSyntax, 0)
       ,("⤙",   ITlarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
       ,("⤚",   ITrarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
       ,("⤛",   ITLarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
       ,("⤜",   ITRarrowtail UnicodeSyntax, UnicodeSyntax, xbit ArrowsBit)
       ,("★",   ITstar UnicodeSyntax,       UnicodeSyntax, xbit StarIsTypeBit)
        
        
        
       ]
type Action = PsSpan -> StringBuffer -> Int -> StringBuffer -> P (PsLocated Token)
special :: Token -> Action
special tok span _buf _len _buf2 = return (L span tok)
token, layout_token :: Token -> Action
token t span _buf _len _buf2 = return (L span t)
layout_token t span _buf _len _buf2 = pushLexState layout >> return (L span t)
idtoken :: (StringBuffer -> Int -> Token) -> Action
idtoken f span buf len _buf2 = return (L span $! (f buf len))
qdo_token :: (Maybe FastString -> Token) -> Action
qdo_token con span buf len _buf2 = do
    maybe_layout token
    return (L span $! token)
  where
    !token = con $! Just $! fst $! splitQualName buf len False
skip_one_varid :: (FastString -> Token) -> Action
skip_one_varid f span buf len _buf2
  = return (L span $! f (lexemeToFastString (stepOn buf) (len-1)))
skip_one_varid_src :: (SourceText -> FastString -> Token) -> Action
skip_one_varid_src f span buf len _buf2
  = return (L span $! f (SourceText $ lexemeToFastString (stepOn buf) (len-1))
                        (lexemeToFastString (stepOn buf) (len-1)))
skip_two_varid :: (FastString -> Token) -> Action
skip_two_varid f span buf len _buf2
  = return (L span $! f (lexemeToFastString (stepOn (stepOn buf)) (len-2)))
strtoken :: (String -> Token) -> Action
strtoken f span buf len _buf2 =
  return (L span $! (f $! lexemeToString buf len))
fstrtoken :: (FastString -> Token) -> Action
fstrtoken f span buf len _buf2 =
  return (L span $! (f $! lexemeToFastString buf len))
begin :: Int -> Action
begin code _span _str _len _buf2 = do pushLexState code; lexToken
pop :: Action
pop _span _buf _len _buf2 =
  do _ <- popLexState
     lexToken
failLinePrag1 :: Action
failLinePrag1 span _buf _len _buf2 = do
  b <- getBit InNestedCommentBit
  if b then return (L span ITcomment_line_prag)
       else lexError LexErrorInPragma
popLinePrag1 :: Action
popLinePrag1 span _buf _len _buf2 = do
  b <- getBit InNestedCommentBit
  if b then return (L span ITcomment_line_prag) else do
    _ <- popLexState
    lexToken
hopefully_open_brace :: Action
hopefully_open_brace span buf len buf2
 = do relaxed <- getBit RelaxedLayoutBit
      ctx <- getContext
      (AI l _) <- getInput
      let offset = srcLocCol (psRealLoc l)
          isOK = relaxed ||
                 case ctx of
                 Layout prev_off _ : _ -> prev_off < offset
                 _                     -> True
      if isOK then pop_and open_brace span buf len buf2
              else addFatalError $
                     mkPlainErrorMsgEnvelope (mkSrcSpanPs span) PsErrMissingBlock
pop_and :: Action -> Action
pop_and act span buf len buf2 =
  do _ <- popLexState
     act span buf len buf2
followedByOpeningToken, precededByClosingToken :: AlexAccPred ExtsBitmap
followedByOpeningToken _ _ _ (AI _ buf) = followedByOpeningToken' buf
precededByClosingToken _ (AI _ buf) _ _ = precededByClosingToken' buf
followedByOpeningToken' :: StringBuffer -> Bool
followedByOpeningToken' buf
  | atEnd buf = False
  | otherwise =
      case nextChar buf of
        ('{', buf') -> nextCharIsNot buf' (== '-')
        ('(', _) -> True
        ('[', _) -> True
        ('\"', _) -> True
        ('\'', _) -> True
        ('_', _) -> True
        ('⟦', _) -> True
        ('⦇', _) -> True
        (c, _) -> isAlphaNum c
precededByClosingToken' :: StringBuffer -> Bool
precededByClosingToken' buf =
  case prevChar buf '\n' of
    '}' -> decodePrevNChars 1 buf /= "-"
    ')' -> True
    ']' -> True
    '\"' -> True
    '\'' -> True
    '_' -> True
    '⟧' -> True
    '⦈' -> True
    c -> isAlphaNum c
get_op_ws :: StringBuffer -> StringBuffer -> OpWs
get_op_ws buf1 buf2 =
    mk_op_ws (precededByClosingToken' buf1) (followedByOpeningToken' buf2)
  where
    mk_op_ws False True  = OpWsPrefix
    mk_op_ws True  False = OpWsSuffix
    mk_op_ws True  True  = OpWsTightInfix
    mk_op_ws False False = OpWsLooseInfix
{-# INLINE with_op_ws #-}
with_op_ws :: (OpWs -> Action) -> Action
with_op_ws act span buf len buf2 = act (get_op_ws buf buf2) span buf len buf2
{-# INLINE nextCharIs #-}
nextCharIs :: StringBuffer -> (Char -> Bool) -> Bool
nextCharIs buf p = not (atEnd buf) && p (currentChar buf)
{-# INLINE nextCharIsNot #-}
nextCharIsNot :: StringBuffer -> (Char -> Bool) -> Bool
nextCharIsNot buf p = not (nextCharIs buf p)
notFollowedBy :: Char -> AlexAccPred ExtsBitmap
notFollowedBy char _ _ _ (AI _ buf)
  = nextCharIsNot buf (== char)
notFollowedBySymbol :: AlexAccPred ExtsBitmap
notFollowedBySymbol _ _ _ (AI _ buf)
  = nextCharIsNot buf (`elem` "!#$%&*+./<=>?@\\^|-~")
followedByDigit :: AlexAccPred ExtsBitmap
followedByDigit _ _ _ (AI _ buf)
  = afterOptionalSpace buf (\b -> nextCharIs b (`elem` ['0'..'9']))
ifCurrentChar :: Char -> AlexAccPred ExtsBitmap
ifCurrentChar char _ (AI _ buf) _ _
  = nextCharIs buf (== char)
isNormalComment :: AlexAccPred ExtsBitmap
isNormalComment bits _ _ (AI _ buf)
  | HaddockBit `xtest` bits = notFollowedByDocOrPragma
  | otherwise               = nextCharIsNot buf (== '#')
  where
    notFollowedByDocOrPragma
       = afterOptionalSpace buf (\b -> nextCharIsNot b (`elem` "|^*$#"))
afterOptionalSpace :: StringBuffer -> (StringBuffer -> Bool) -> Bool
afterOptionalSpace buf p
    = if nextCharIs buf (== ' ')
      then p (snd (nextChar buf))
      else p buf
atEOL :: AlexAccPred ExtsBitmap
atEOL _ _ _ (AI _ buf) = atEnd buf || currentChar buf == '\n'
negLitPred :: AlexAccPred ExtsBitmap
negLitPred =
    prefix_minus `alexAndPred`
    (negative_literals `alexOrPred` lexical_negation)
  where
    negative_literals = ifExtension NegativeLiteralsBit
    lexical_negation  =
      
      alexNotPred (ifExtension NoLexicalNegationBit)
    prefix_minus =
      
      alexNotPred precededByClosingToken
negHashLitPred :: ExtBits -> AlexAccPred ExtsBitmap
negHashLitPred ext = prefix_minus `alexAndPred` magic_hash
  where
    magic_hash = ifExtension ext 
    prefix_minus =
      
      alexNotPred precededByClosingToken
ifExtension :: ExtBits -> AlexAccPred ExtsBitmap
ifExtension extBits bits _ _ _ = extBits `xtest` bits
alexNotPred p userState in1 len in2
  = not (p userState in1 len in2)
alexOrPred p1 p2 userState in1 len in2
  = p1 userState in1 len in2 || p2 userState in1 len in2
multiline_doc_comment :: Action
multiline_doc_comment span buf _len _buf2 = {-# SCC "multiline_doc_comment" #-} withLexedDocType worker
  where
    worker input@(AI start_loc _) docType checkNextLine = go start_loc "" [] input
      where
        go start_loc curLine prevLines input@(AI end_loc _) = case alexGetChar' input of
            Just ('\n', input')
              | checkNextLine -> case checkIfCommentLine input' of
                Just input@(AI next_start _) ->  go next_start "" (locatedLine : prevLines) input 
                Nothing -> endComment
              | otherwise -> endComment
            Just (c, input) -> go start_loc (c:curLine) prevLines input
            Nothing -> endComment
          where
            lineSpan = mkSrcSpanPs $ mkPsSpan start_loc end_loc
            locatedLine = L lineSpan (mkHsDocStringChunk $ reverse curLine)
            commentLines = NE.reverse $ locatedLine :| prevLines
            endComment = docCommentEnd input (docType (\dec -> MultiLineDocString dec commentLines)) buf span
    
    
    
    
    
    
    
    checkIfCommentLine :: AlexInput -> Maybe AlexInput
    checkIfCommentLine input = check (dropNonNewlineSpace input)
      where
        check input = do
          ('-', input) <- alexGetChar' input
          ('-', input) <- alexGetChar' input
          (c, after_c) <- alexGetChar' input
          case c of
            '-' -> Nothing
            ' ' -> case alexGetChar' after_c of
                     Just ('$', _) -> Nothing
                     _ -> Just input
            _   -> Just input
        dropNonNewlineSpace input = case alexGetChar' input of
          Just (c, input')
            | isSpace c && c /= '\n' -> dropNonNewlineSpace input'
            | otherwise -> input
          Nothing -> input
lineCommentToken :: Action
lineCommentToken span buf len buf2 = do
  b <- getBit RawTokenStreamBit
  if b then do
         lt <- getLastLocIncludingComments
         strtoken (\s -> ITlineComment s lt) span buf len buf2
       else lexToken
nested_comment :: Action
nested_comment span buf len _buf2 = {-# SCC "nested_comment" #-} do
  l <- getLastLocIncludingComments
  let endComment input (L _ comment) = commentEnd lexToken input (Nothing, ITblockComment comment l) buf span
  input <- getInput
  
  let start_decorator = reverse $ lexemeToString buf len
  nested_comment_logic endComment start_decorator input span
nested_doc_comment :: Action
nested_doc_comment span buf _len _buf2 = {-# SCC "nested_doc_comment" #-} withLexedDocType worker
  where
    worker input docType _checkNextLine = nested_comment_logic endComment "" input span
      where
        endComment input lcomment
          = docCommentEnd input (docType (\d -> NestedDocString d (mkHsDocStringChunk . dropTrailingDec <$> lcomment))) buf span
        dropTrailingDec [] = []
        dropTrailingDec "-}" = ""
        dropTrailingDec (x:xs) = x:dropTrailingDec xs
{-# INLINE nested_comment_logic #-}
nested_comment_logic
  :: (AlexInput -> Located String -> P (PsLocated Token))  
  -> String 
  -> AlexInput
  -> PsSpan
  -> P (PsLocated Token)
nested_comment_logic endComment commentAcc input span = go commentAcc (1::Int) input
  where
    go commentAcc 0 input@(AI end_loc _) = do
      let comment = reverse commentAcc
          cspan = mkSrcSpanPs $ mkPsSpan (psSpanStart span) end_loc
          lcomment = L cspan comment
      endComment input lcomment
    go commentAcc n input = case alexGetChar' input of
      Nothing -> errBrace input (psRealSpan span)
      Just ('-',input) -> case alexGetChar' input of
        Nothing  -> errBrace input (psRealSpan span)
        Just ('\125',input) -> go ('\125':'-':commentAcc) (n-1) input 
        Just (_,_)          -> go ('-':commentAcc) n input
      Just ('\123',input) -> case alexGetChar' input of  
        Nothing  -> errBrace input (psRealSpan span)
        Just ('-',input) -> go ('-':'\123':commentAcc) (n+1) input
        Just (_,_)       -> go ('\123':commentAcc) n input
      
      Just ('\n',input) -> case alexGetChar' input of
        Nothing  -> errBrace input (psRealSpan span)
        Just ('#',_) -> do (parsedAcc,input) <- parseNestedPragma input
                           go (parsedAcc ++ '\n':commentAcc) n input
        Just (_,_)   -> go ('\n':commentAcc) n input
      Just (c,input) -> go (c:commentAcc) n input
parseNestedPragma :: AlexInput -> P (String,AlexInput)
parseNestedPragma input@(AI _ buf) = do
  origInput <- getInput
  setInput input
  setExts (.|. xbit InNestedCommentBit)
  pushLexState bol
  lt <- lexToken
  _ <- popLexState
  setExts (.&. complement (xbit InNestedCommentBit))
  postInput@(AI _ postBuf) <- getInput
  setInput origInput
  case unLoc lt of
    ITcomment_line_prag -> do
      let bytes = byteDiff buf postBuf
          diff  = lexemeToString buf bytes
      return (reverse diff, postInput)
    lt' -> panic ("parseNestedPragma: unexpected token" ++ (show lt'))
{-# INLINE withLexedDocType #-}
withLexedDocType :: (AlexInput -> ((HsDocStringDecorator -> HsDocString) -> (HdkComment, Token)) -> Bool -> P (PsLocated Token))
                 -> P (PsLocated Token)
withLexedDocType lexDocComment = do
  input@(AI _ buf) <- getInput
  l <- getLastLocIncludingComments
  case prevChar buf ' ' of
    
    
    '|' -> lexDocComment input (mkHdkCommentNext l) True
    '^' -> lexDocComment input (mkHdkCommentPrev l) True
    '$' -> case lexDocName input of
       Nothing -> do setInput input; lexToken 
       Just (name, input) -> lexDocComment input (mkHdkCommentNamed l name) True
    '*' -> lexDocSection l 1 input
    _ -> panic "withLexedDocType: Bad doc type"
 where
    lexDocSection l n input = case alexGetChar' input of
      Just ('*', input) -> lexDocSection l (n+1) input
      Just (_,   _)     -> lexDocComment input (mkHdkCommentSection l n) False
      Nothing -> do setInput input; lexToken 
    lexDocName :: AlexInput -> Maybe (String, AlexInput)
    lexDocName = go ""
      where
        go acc input = case alexGetChar' input of
          Just (c, input')
            | isSpace c -> Just (reverse acc, input)
            | otherwise -> go (c:acc) input'
          Nothing -> Nothing
mkHdkCommentNext, mkHdkCommentPrev  :: PsSpan -> (HsDocStringDecorator -> HsDocString) -> (HdkComment, Token)
mkHdkCommentNext loc mkDS =  (HdkCommentNext ds,ITdocComment ds loc)
  where ds = mkDS HsDocStringNext
mkHdkCommentPrev loc mkDS =  (HdkCommentPrev ds,ITdocComment ds loc)
  where ds = mkDS HsDocStringPrevious
mkHdkCommentNamed :: PsSpan -> String -> (HsDocStringDecorator -> HsDocString) -> (HdkComment, Token)
mkHdkCommentNamed loc name mkDS = (HdkCommentNamed name ds, ITdocComment ds loc)
  where ds = mkDS (HsDocStringNamed name)
mkHdkCommentSection :: PsSpan -> Int -> (HsDocStringDecorator -> HsDocString) -> (HdkComment, Token)
mkHdkCommentSection loc n mkDS = (HdkCommentSection n ds, ITdocComment ds loc)
  where ds = mkDS (HsDocStringGroup n)
rulePrag :: Action
rulePrag span buf len _buf2 = do
  setExts (.|. xbit InRulePragBit)
  let !src = lexemeToFastString buf len
  return (L span (ITrules_prag (SourceText src)))
linePrag :: Action
linePrag span buf len buf2 = do
  usePosPrags <- getBit UsePosPragsBit
  if usePosPrags
    then begin line_prag2 span buf len buf2
    else let !src = lexemeToFastString buf len
         in return (L span (ITline_prag (SourceText src)))
columnPrag :: Action
columnPrag span buf len buf2 = do
  usePosPrags <- getBit UsePosPragsBit
  if usePosPrags
    then begin column_prag span buf len buf2
    else let !src = lexemeToFastString buf len
         in return (L span (ITcolumn_prag (SourceText src)))
endPrag :: Action
endPrag span _buf _len _buf2 = do
  setExts (.&. complement (xbit InRulePragBit))
  return (L span ITclose_prag)
{-# INLINE commentEnd #-}
commentEnd :: P (PsLocated Token)
           -> AlexInput
           -> (Maybe HdkComment, Token)
           -> StringBuffer
           -> PsSpan
           -> P (PsLocated Token)
commentEnd cont input (m_hdk_comment, hdk_token) buf span = do
  setInput input
  let (AI loc nextBuf) = input
      span' = mkPsSpan (psSpanStart span) loc
      last_len = byteDiff buf nextBuf
  span `seq` setLastToken span' last_len
  whenIsJust m_hdk_comment $ \hdk_comment ->
    P $ \s -> POk (s {hdk_comments = hdk_comments s `snocOL` L span' hdk_comment}) ()
  b <- getBit RawTokenStreamBit
  if b then return (L span' hdk_token)
       else cont
{-# INLINE docCommentEnd #-}
docCommentEnd :: AlexInput -> (HdkComment, Token) -> StringBuffer ->
                 PsSpan -> P (PsLocated Token)
docCommentEnd input (hdk_comment, tok) buf span
  = commentEnd lexToken input (Just hdk_comment, tok) buf span
errBrace :: AlexInput -> RealSrcSpan -> P a
errBrace (AI end _) span =
  failLocMsgP (realSrcSpanStart span)
              (psRealLoc end)
              (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc (PsErrLexer LexUnterminatedComment LexErrKind_EOF))
open_brace, close_brace :: Action
open_brace span _str _len _buf2 = do
  ctx <- getContext
  setContext (NoLayout:ctx)
  return (L span ITocurly)
close_brace span _str _len _buf2 = do
  popContext
  return (L span ITccurly)
qvarid, qconid :: StringBuffer -> Int -> Token
qvarid buf len = ITqvarid $! splitQualName buf len False
qconid buf len = ITqconid $! splitQualName buf len False
splitQualName :: StringBuffer -> Int -> Bool -> (FastString,FastString)
splitQualName orig_buf len parens = split orig_buf orig_buf
  where
    split buf dot_buf
        | orig_buf `byteDiff` buf >= len  = done dot_buf
        | c == '.'                        = found_dot buf'
        | otherwise                       = split buf' dot_buf
      where
       (c,buf') = nextChar buf
    
    
    
    found_dot buf 
        | isUpper c    = split buf' buf
        | otherwise    = done buf
      where
       (c,buf') = nextChar buf
    done dot_buf
        | qual_size < 1 = error "splitQualName got an unqualified named"
        | otherwise =
        (lexemeToFastString orig_buf (qual_size - 1),
         if parens 
            then lexemeToFastString (stepOn dot_buf) (len - qual_size - 2)
            else lexemeToFastString dot_buf (len - qual_size))
      where
        qual_size = orig_buf `byteDiff` dot_buf
varid :: Action
varid span buf len _buf2 =
  case lookupUFM reservedWordsFM fs of
    Just (ITcase, _) -> do
      lastTk <- getLastTk
      keyword <- case lastTk of
        Strict.Just (L _ ITlam) -> do
          lambdaCase <- getBit LambdaCaseBit
          unless lambdaCase $ do
            pState <- getPState
            addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) PsErrLambdaCase
          return ITlcase
        _ -> return ITcase
      maybe_layout keyword
      return $ L span keyword
    Just (ITlcases, _) -> do
      lastTk <- getLastTk
      lambdaCase <- getBit LambdaCaseBit
      token <- case lastTk of
        Strict.Just (L _ ITlam) | lambdaCase -> return ITlcases
        _ -> return $ ITvarid fs
      maybe_layout token
      return $ L span token
    Just (keyword, 0) -> do
      maybe_layout keyword
      return $ L span keyword
    Just (keyword, i) -> do
      exts <- getExts
      if exts .&. i /= 0
        then do
          maybe_layout keyword
          return $ L span keyword
        else
          return $ L span $ ITvarid fs
    Nothing ->
      return $ L span $ ITvarid fs
  where
    !fs = lexemeToFastString buf len
conid :: StringBuffer -> Int -> Token
conid buf len = ITconid $! lexemeToFastString buf len
qvarsym, qconsym :: StringBuffer -> Int -> Token
qvarsym buf len = ITqvarsym $! splitQualName buf len False
qconsym buf len = ITqconsym $! splitQualName buf len False
varsym :: OpWs -> Action
varsym opws@OpWsPrefix = sym $ \span exts s ->
  let warnExtConflict errtok =
        do { addPsMessage (mkSrcSpanPs span) (PsWarnOperatorWhitespaceExtConflict errtok)
           ; return (ITvarsym s) }
  in
  if | s == fsLit "@" ->
         return ITtypeApp  
     | s == fsLit "%" ->
         if xtest LinearTypesBit exts
         then return ITpercent
         else warnExtConflict OperatorWhitespaceSymbol_PrefixPercent
     | s == fsLit "$" ->
         if xtest ThQuotesBit exts
         then return ITdollar
         else warnExtConflict OperatorWhitespaceSymbol_PrefixDollar
     | s == fsLit "$$" ->
         if xtest ThQuotesBit exts
         then return ITdollardollar
         else warnExtConflict OperatorWhitespaceSymbol_PrefixDollarDollar
     | s == fsLit "-" ->
         return ITprefixminus 
                              
     | s == fsLit ".", OverloadedRecordDotBit `xtest` exts ->
         return (ITproj True) 
     | s == fsLit "." -> return ITdot
     | s == fsLit "!" -> return ITbang
     | s == fsLit "~" -> return ITtilde
     | otherwise ->
         do { warnOperatorWhitespace opws span s
            ; return (ITvarsym s) }
varsym opws@OpWsSuffix = sym $ \span _ s ->
  if | s == fsLit "@" -> failMsgP (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrSuffixAT)
     | s == fsLit "." -> return ITdot
     | otherwise ->
         do { warnOperatorWhitespace opws span s
            ; return (ITvarsym s) }
varsym opws@OpWsTightInfix = sym $ \span exts s ->
  if | s == fsLit "@" -> return ITat
     | s == fsLit ".", OverloadedRecordDotBit `xtest` exts  -> return (ITproj False)
     | s == fsLit "." -> return ITdot
     | otherwise ->
         do { warnOperatorWhitespace opws span s
            ; return (ITvarsym s) }
varsym OpWsLooseInfix = sym $ \_ _ s ->
  if | s == fsLit "."
     -> return ITdot
     | otherwise
     -> return $ ITvarsym s
consym :: OpWs -> Action
consym opws = sym $ \span _exts s ->
  do { warnOperatorWhitespace opws span s
     ; return (ITconsym s) }
warnOperatorWhitespace :: OpWs -> PsSpan -> FastString -> P ()
warnOperatorWhitespace opws span s =
  whenIsJust (check_unusual_opws opws) $ \opws' ->
    addPsMessage
      (mkSrcSpanPs span)
      (PsWarnOperatorWhitespace s opws')
check_unusual_opws :: OpWs -> Maybe OperatorWhitespaceOccurrence
check_unusual_opws opws =
  case opws of
    OpWsPrefix     -> Just OperatorWhitespaceOccurrence_Prefix
    OpWsSuffix     -> Just OperatorWhitespaceOccurrence_Suffix
    OpWsTightInfix -> Just OperatorWhitespaceOccurrence_TightInfix
    OpWsLooseInfix -> Nothing
sym :: (PsSpan -> ExtsBitmap -> FastString -> P Token) -> Action
sym con span buf len _buf2 =
  case lookupUFM reservedSymsFM fs of
    Just (keyword, NormalSyntax, 0) ->
      return $ L span keyword
    Just (keyword, NormalSyntax, i) -> do
      exts <- getExts
      if exts .&. i /= 0
        then return $ L span keyword
        else L span <$!> con span exts fs
    Just (keyword, UnicodeSyntax, 0) -> do
      exts <- getExts
      if xtest UnicodeSyntaxBit exts
        then return $ L span keyword
        else L span <$!> con span exts fs
    Just (keyword, UnicodeSyntax, i) -> do
      exts <- getExts
      if exts .&. i /= 0 && xtest UnicodeSyntaxBit exts
        then return $ L span keyword
        else L span <$!> con span exts fs
    Nothing -> do
      exts <- getExts
      L span <$!> con span exts fs
  where
    !fs = lexemeToFastString buf len
tok_integral :: (SourceText -> Integer -> Token)
             -> (Integer -> Integer)
             -> Int -> Int
             -> (Integer, (Char -> Int))
             -> Action
tok_integral itint transint transbuf translen (radix,char_to_int) span buf len _buf2 = do
  numericUnderscores <- getBit NumericUnderscoresBit  
  let src = lexemeToFastString buf len
  when ((not numericUnderscores) && ('_' `elem` unpackFS src)) $ do
    pState <- getPState
    let msg = PsErrNumUnderscores NumUnderscore_Integral
    addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
  return $ L span $ itint (SourceText src)
       $! transint $ parseUnsignedInteger
       (offsetBytes transbuf buf) (subtract translen len) radix char_to_int
tok_num :: (Integer -> Integer)
        -> Int -> Int
        -> (Integer, (Char->Int)) -> Action
tok_num = tok_integral $ \case
    st@(SourceText (unconsFS -> Just ('-',_))) -> itint st (const True)
    st@(SourceText _)       -> itint st (const False)
    st@NoSourceText         -> itint st (< 0)
  where
    itint :: SourceText -> (Integer -> Bool) -> Integer -> Token
    itint !st is_negative !val = ITinteger ((IL st $! is_negative val) val)
tok_primint :: (Integer -> Integer)
            -> Int -> Int
            -> (Integer, (Char->Int)) -> Action
tok_primint = tok_integral ITprimint
tok_primword :: Int -> Int
             -> (Integer, (Char->Int)) -> Action
tok_primword = tok_integral ITprimword positive
positive, negative :: (Integer -> Integer)
positive = id
negative = negate
decimal, octal, hexadecimal :: (Integer, Char -> Int)
decimal = (10,octDecDigit)
binary = (2,octDecDigit)
octal = (8,octDecDigit)
hexadecimal = (16,hexDigit)
tok_primintX :: (SourceText -> Integer -> Token)
             -> Int
             -> (Integer -> Integer)
             -> Int
             -> (Integer, (Char->Int)) -> Action
tok_primintX itint addlen transint transbuf =
    tok_integral itint transint transbuf (transbuf+addlen)
tok_primint8,     tok_primint16,  tok_primint32,  tok_primint64
    :: (Integer -> Integer)
    -> Int -> (Integer, (Char->Int)) -> Action
tok_primint8  = tok_primintX ITprimint8   5
tok_primint16 = tok_primintX ITprimint16  6
tok_primint32 = tok_primintX ITprimint32  6
tok_primint64 = tok_primintX ITprimint64  6
tok_primwordX :: (SourceText -> Integer -> Token)
              -> Int
              -> Int
              -> (Integer, (Char->Int)) -> Action
tok_primwordX itint addlen transbuf =
    tok_integral itint positive transbuf (transbuf+addlen)
tok_primword8, tok_primword16, tok_primword32, tok_primword64
    :: Int -> (Integer, (Char->Int)) -> Action
tok_primword8  = tok_primwordX ITprimword8  6
tok_primword16 = tok_primwordX ITprimword16 7
tok_primword32 = tok_primwordX ITprimword32 7
tok_primword64 = tok_primwordX ITprimword64 7
tok_frac :: Int -> (String -> Token) -> Action
tok_frac drop f span buf len _buf2 = do
  numericUnderscores <- getBit NumericUnderscoresBit  
  let src = lexemeToString buf (len-drop)
  when ((not numericUnderscores) && ('_' `elem` src)) $ do
    pState <- getPState
    let msg = PsErrNumUnderscores NumUnderscore_Float
    addError $ mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
  return (L span $! (f $! src))
tok_float, tok_primfloat, tok_primdouble :: String -> Token
tok_float        str = ITrational   $! readFractionalLit str
tok_hex_float    str = ITrational   $! readHexFractionalLit str
tok_primfloat    str = ITprimfloat  $! readFractionalLit str
tok_primdouble   str = ITprimdouble $! readFractionalLit str
readFractionalLit, readHexFractionalLit :: String -> FractionalLit
readHexFractionalLit = readFractionalLitX readHexSignificandExponentPair Base2
readFractionalLit = readFractionalLitX readSignificandExponentPair Base10
readFractionalLitX :: (String -> (Integer, Integer))
                   -> FractionalExponentBase
                   -> String -> FractionalLit
readFractionalLitX readStr b str =
  mkSourceFractionalLit str is_neg i e b
  where
    is_neg = case str of
                    '-' : _ -> True
                    _      -> False
    (i, e) = readStr str
do_bol :: Action
do_bol span _str _len _buf2 = do
        
        b <- getBit InNestedCommentBit
        if b then return (L span ITcomment_line_prag) else do
          (pos, gen_semic) <- getOffside
          case pos of
              LT -> do
                  
                  popContext
                  
                  return (L span ITvccurly)
              EQ | gen_semic -> do
                  
                  _ <- popLexState
                  return (L span ITsemi)
              _ -> do
                  _ <- popLexState
                  lexToken
maybe_layout :: Token -> P ()
maybe_layout t = do 
                    
                    
                    
                    
                    
                    
                    alr <- getBit AlternativeLayoutRuleBit
                    unless alr $ f t
    where f (ITdo _)    = pushLexState layout_do
          f (ITmdo _)   = pushLexState layout_do
          f ITof        = pushLexState layout
          f ITlcase     = pushLexState layout
          f ITlcases    = pushLexState layout
          f ITlet       = pushLexState layout
          f ITwhere     = pushLexState layout
          f ITrec       = pushLexState layout
          f ITif        = pushLexState layout_if
          f _           = return ()
new_layout_context :: Bool -> Bool -> Token -> Action
new_layout_context strict gen_semic tok span _buf len _buf2 = do
    _ <- popLexState
    (AI l _) <- getInput
    let offset = srcLocCol (psRealLoc l) - len
    ctx <- getContext
    nondecreasing <- getBit NondecreasingIndentationBit
    let strict' = strict || not nondecreasing
    case ctx of
        Layout prev_off _ : _  |
           (strict'     && prev_off >= offset  ||
            not strict' && prev_off > offset) -> do
                
                
                pushLexState layout_left
                return (L span tok)
        _ -> do setContext (Layout offset gen_semic : ctx)
                return (L span tok)
do_layout_left :: Action
do_layout_left span _buf _len _buf2 = do
    _ <- popLexState
    pushLexState bol  
    return (L span ITvccurly)
setLineAndFile :: Int -> Action
setLineAndFile code (PsSpan span _) buf len _buf2 = do
  let src = lexemeToString buf (len - 1)  
      linenumLen = length $ head $ words src
      linenum = parseUnsignedInteger buf linenumLen 10 octDecDigit
      file = mkFastString $ go $ drop 1 $ dropWhile (/= '"') src
          
        where go ('\\':c:cs) = c : go cs
              go (c:cs)      = c : go cs
              go []          = []
              
              
              
              
              
              
              
              
              
  resetAlrLastLoc file
  setSrcLoc (mkRealSrcLoc file (fromIntegral linenum - 1) (srcSpanEndCol span))
      
  addSrcFile file
  _ <- popLexState
  pushLexState code
  lexToken
setColumn :: Action
setColumn (PsSpan span _) buf len _buf2 = do
  let column =
        case reads (lexemeToString buf len) of
          [(column, _)] -> column
          _ -> error "setColumn: expected integer" 
  setSrcLoc (mkRealSrcLoc (srcSpanFile span) (srcSpanEndLine span)
                          (fromIntegral (column :: Integer)))
  _ <- popLexState
  lexToken
alrInitialLoc :: FastString -> RealSrcSpan
alrInitialLoc file = mkRealSrcSpan loc loc
    where 
          
          loc = mkRealSrcLoc file (-1) (-1)
lex_string_prag :: (String -> Token) -> Action
lex_string_prag mkTok = lex_string_prag_comment mkTok'
  where
    mkTok' s _ = mkTok s
lex_string_prag_comment :: (String -> PsSpan -> Token) -> Action
lex_string_prag_comment mkTok span _buf _len _buf2
    = do input <- getInput
         start <- getParsedLoc
         l <- getLastLocIncludingComments
         tok <- go l [] input
         end <- getParsedLoc
         return (L (mkPsSpan start end) tok)
    where go l acc input
              = if isString input "#-}"
                   then do setInput input
                           return (mkTok (reverse acc) l)
                   else case alexGetChar input of
                          Just (c,i) -> go l (c:acc) i
                          Nothing -> err input
          isString _ [] = True
          isString i (x:xs)
              = case alexGetChar i of
                  Just (c,i') | c == x    -> isString i' xs
                  _other -> False
          err (AI end _) = failLocMsgP (realSrcSpanStart (psRealSpan span))
                                       (psRealLoc end)
                                       (\srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer LexUnterminatedOptions LexErrKind_EOF)
lex_string_tok :: Action
lex_string_tok span buf _len _buf2 = do
  lexed <- lex_string
  (AI end bufEnd) <- getInput
  let
    tok = case lexed of
      LexedPrimString s -> ITprimstring (SourceText src) (unsafeMkByteString s)
      LexedRegularString s -> ITstring (SourceText src) (mkFastString s)
    src = lexemeToFastString buf (cur bufEnd - cur buf)
  return $ L (mkPsSpan (psSpanStart span) end) tok
lex_quoted_label :: Action
lex_quoted_label span buf _len _buf2 = do
  start <- getInput
  s <- lex_string_helper "" start
  (AI end bufEnd) <- getInput
  let
    token = ITlabelvarid (SourceText src) (mkFastString s)
    src = lexemeToFastString (stepOn buf) (cur bufEnd - cur buf - 1)
    start = psSpanStart span
  return $ L (mkPsSpan start end) token
data LexedString = LexedRegularString String | LexedPrimString String
lex_string :: P LexedString
lex_string = do
  start <- getInput
  s <- lex_string_helper "" start
  magicHash <- getBit MagicHashBit
  if magicHash
    then do
      i <- getInput
      case alexGetChar' i of
        Just ('#',i) -> do
          setInput i
          when (any (> '\xFF') s) $ do
            pState <- getPState
            let msg = PsErrPrimStringInvalidChar
            let err = mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
            addError err
          return $ LexedPrimString s
        _other ->
          return $ LexedRegularString s
    else
      return $ LexedRegularString s
lex_string_helper :: String -> AlexInput -> P String
lex_string_helper s start = do
  i <- getInput
  case alexGetChar' i of
    Nothing -> lit_error i
    Just ('"',i)  -> do
      setInput i
      return (reverse s)
    Just ('\\',i)
        | Just ('&',i) <- next -> do
                setInput i; lex_string_helper s start
        | Just (c,i) <- next, c <= '\x7f' && is_space c -> do
                           
                setInput i; lex_stringgap s start
        where next = alexGetChar' i
    Just (c, i1) -> do
        case c of
          '\\' -> do setInput i1; c' <- lex_escape; lex_string_helper (c':s) start
          c | isAny c -> do setInput i1; lex_string_helper (c:s) start
          _other | any isDoubleSmartQuote s -> do
            
            
            setInput start 
                           
            advance_to_smart_quote_character
            i2@(AI loc _) <- getInput
            case alexGetChar' i2 of
              Just (c, _) -> do add_nonfatal_smart_quote_error c loc; lit_error i
              Nothing -> lit_error i 
          _other -> lit_error i
lex_stringgap :: String -> AlexInput -> P String
lex_stringgap s start = do
  i <- getInput
  c <- getCharOrFail i
  case c of
    '\\' -> lex_string_helper s start
    c | c <= '\x7f' && is_space c -> lex_stringgap s start
                           
    _other -> lit_error i
lex_char_tok :: Action
lex_char_tok span buf _len _buf2 = do        
   i1 <- getInput       
   let loc = psSpanStart span
   case alexGetChar' i1 of
        Nothing -> lit_error  i1
        Just ('\'', i2@(AI end2 _)) -> do       
                   setInput i2
                   return (L (mkPsSpan loc end2)  ITtyQuote)
        Just ('\\', i2@(AI end2 _)) -> do      
                  setInput i2
                  lit_ch <- lex_escape
                  i3 <- getInput
                  mc <- getCharOrFail i3 
                  if mc == '\'' then finish_char_tok buf loc lit_ch
                  else if isSingleSmartQuote mc then add_smart_quote_error mc end2
                  else lit_error i3
        Just (c, i2@(AI end2 _))
                | not (isAny c) -> lit_error i1
                | otherwise ->
                
                
           case alexGetChar' i2 of      
                Just ('\'', i3) -> do   
                        setInput i3
                        finish_char_tok buf loc c
                Just (c, _) | isSingleSmartQuote c -> add_smart_quote_error c end2
                _other -> do            
                                        
                                        
                        let (AI end _) = i1
                        return (L (mkPsSpan loc end) ITsimpleQuote)
finish_char_tok :: StringBuffer -> PsLoc -> Char -> P (PsLocated Token)
finish_char_tok buf loc ch  
                        
  = do  magicHash <- getBit MagicHashBit
        i@(AI end bufEnd) <- getInput
        let src = lexemeToFastString buf (cur bufEnd - cur buf)
        if magicHash then do
            case alexGetChar' i of
              Just ('#',i@(AI end bufEnd')) -> do
                setInput i
                
                let src' = lexemeToFastString buf (cur bufEnd' - cur buf)
                return (L (mkPsSpan loc end)
                          (ITprimchar (SourceText src') ch))
              _other ->
                return (L (mkPsSpan loc end)
                          (ITchar (SourceText src) ch))
            else do
              return (L (mkPsSpan loc end) (ITchar (SourceText src) ch))
isAny :: Char -> Bool
isAny c | c > '\x7f' = isPrint c
        | otherwise  = is_any c
lex_escape :: P Char
lex_escape = do
  i0@(AI loc _) <- getInput
  c <- getCharOrFail i0
  case c of
        'a'   -> return '\a'
        'b'   -> return '\b'
        'f'   -> return '\f'
        'n'   -> return '\n'
        'r'   -> return '\r'
        't'   -> return '\t'
        'v'   -> return '\v'
        '\\'  -> return '\\'
        '"'   -> return '\"'
        '\''  -> return '\''
        
        smart_double_quote | isDoubleSmartQuote smart_double_quote ->
          add_smart_quote_error smart_double_quote loc
        smart_single_quote | isSingleSmartQuote smart_single_quote ->
          add_smart_quote_error smart_single_quote loc
        '^'   -> do i1 <- getInput
                    c <- getCharOrFail i1
                    if c >= '@' && c <= '_'
                        then return (chr (ord c - ord '@'))
                        else lit_error i1
        'x'   -> readNum is_hexdigit 16 hexDigit
        'o'   -> readNum is_octdigit  8 octDecDigit
        x | is_decdigit x -> readNum2 is_decdigit 10 octDecDigit (octDecDigit x)
        c1 ->  do
           i <- getInput
           case alexGetChar' i of
            Nothing -> lit_error i0
            Just (c2,i2) ->
              case alexGetChar' i2 of
                Nothing -> do lit_error i0
                Just (c3,i3) ->
                   let str = [c1,c2,c3] in
                   case [ (c,rest) | (p,c) <- silly_escape_chars,
                                     Just rest <- [stripPrefix p str] ] of
                          (escape_char,[]):_ -> do
                                setInput i3
                                return escape_char
                          (escape_char,_:_):_ -> do
                                setInput i2
                                return escape_char
                          [] -> lit_error i0
readNum :: (Char -> Bool) -> Int -> (Char -> Int) -> P Char
readNum is_digit base conv = do
  i <- getInput
  c <- getCharOrFail i
  if is_digit c
        then readNum2 is_digit base conv (conv c)
        else lit_error i
readNum2 :: (Char -> Bool) -> Int -> (Char -> Int) -> Int -> P Char
readNum2 is_digit base conv i = do
  input <- getInput
  read i input
  where read i input = do
          case alexGetChar' input of
            Just (c,input') | is_digit c -> do
               let i' = i*base + conv c
               if i' > 0x10ffff
                  then setInput input >> lexError LexNumEscapeRange
                  else read i' input'
            _other -> do
              setInput input; return (chr i)
silly_escape_chars :: [(String, Char)]
silly_escape_chars = [
        ("NUL", '\NUL'),
        ("SOH", '\SOH'),
        ("STX", '\STX'),
        ("ETX", '\ETX'),
        ("EOT", '\EOT'),
        ("ENQ", '\ENQ'),
        ("ACK", '\ACK'),
        ("BEL", '\BEL'),
        ("BS", '\BS'),
        ("HT", '\HT'),
        ("LF", '\LF'),
        ("VT", '\VT'),
        ("FF", '\FF'),
        ("CR", '\CR'),
        ("SO", '\SO'),
        ("SI", '\SI'),
        ("DLE", '\DLE'),
        ("DC1", '\DC1'),
        ("DC2", '\DC2'),
        ("DC3", '\DC3'),
        ("DC4", '\DC4'),
        ("NAK", '\NAK'),
        ("SYN", '\SYN'),
        ("ETB", '\ETB'),
        ("CAN", '\CAN'),
        ("EM", '\EM'),
        ("SUB", '\SUB'),
        ("ESC", '\ESC'),
        ("FS", '\FS'),
        ("GS", '\GS'),
        ("RS", '\RS'),
        ("US", '\US'),
        ("SP", '\SP'),
        ("DEL", '\DEL')
        ]
lit_error :: AlexInput -> P a
lit_error i = do setInput i; lexError LexStringCharLit
getCharOrFail :: AlexInput -> P Char
getCharOrFail i =  do
  case alexGetChar' i of
        Nothing -> lexError LexStringCharLitEOF
        Just (c,i)  -> do setInput i; return c
lex_qquasiquote_tok :: Action
lex_qquasiquote_tok span buf len _buf2 = do
  let (qual, quoter) = splitQualName (stepOn buf) (len - 2) False
  quoteStart <- getParsedLoc
  quote <- lex_quasiquote (psRealLoc quoteStart) ""
  end <- getParsedLoc
  return (L (mkPsSpan (psSpanStart span) end)
           (ITqQuasiQuote (qual,
                           quoter,
                           mkFastString (reverse quote),
                           mkPsSpan quoteStart end)))
lex_quasiquote_tok :: Action
lex_quasiquote_tok span buf len _buf2 = do
  let quoter = tail (lexemeToString buf (len - 1))
                
                
  quoteStart <- getParsedLoc
  quote <- lex_quasiquote (psRealLoc quoteStart) ""
  end <- getParsedLoc
  return (L (mkPsSpan (psSpanStart span) end)
           (ITquasiQuote (mkFastString quoter,
                          mkFastString (reverse quote),
                          mkPsSpan quoteStart end)))
lex_quasiquote :: RealSrcLoc -> String -> P String
lex_quasiquote start s = do
  i <- getInput
  case alexGetChar' i of
    Nothing -> quasiquote_error start
    
    
    
    
    Just ('|',i)
        | Just (']',i) <- alexGetChar' i
        -> do { setInput i; return s }
    Just (c, i) -> do
         setInput i; lex_quasiquote start (c : s)
quasiquote_error :: RealSrcLoc -> P a
quasiquote_error start = do
  (AI end buf) <- getInput
  reportLexError start (psRealLoc end) buf
    (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc (PsErrLexer LexUnterminatedQQ k))
isDoubleSmartQuote :: Char -> Bool
isDoubleSmartQuote '“' = True
isDoubleSmartQuote '”' = True
isDoubleSmartQuote _ = False
isSingleSmartQuote :: Char -> Bool
isSingleSmartQuote '‘' = True
isSingleSmartQuote '’' = True
isSingleSmartQuote _ = False
isSmartQuote :: AlexAccPred ExtsBitmap
isSmartQuote _ _ _ (AI _ buf) = let c = prevChar buf ' ' in isSingleSmartQuote c || isDoubleSmartQuote c
smart_quote_error_message :: Char -> PsLoc -> MsgEnvelope PsMessage
smart_quote_error_message c loc =
  let (correct_char, correct_char_name) =
         if isSingleSmartQuote c then ('\'', "Single Quote") else ('"', "Quotation Mark")
      err = mkPlainErrorMsgEnvelope (mkSrcSpanPs (mkPsSpan loc loc)) $
              PsErrUnicodeCharLooksLike c correct_char correct_char_name in
    err
smart_quote_error :: Action
smart_quote_error span buf _len _buf2 = do
  let c = currentChar buf
  addFatalError (smart_quote_error_message c (psSpanStart span))
add_smart_quote_error :: Char -> PsLoc -> P a
add_smart_quote_error c loc = addFatalError (smart_quote_error_message c loc)
add_nonfatal_smart_quote_error :: Char -> PsLoc -> P ()
add_nonfatal_smart_quote_error c loc = addError (smart_quote_error_message c loc)
advance_to_smart_quote_character :: P ()
advance_to_smart_quote_character  = do
  i <- getInput
  case alexGetChar' i of
    Just (c, _) | isDoubleSmartQuote c -> return ()
    Just (_, i2) -> do setInput i2; advance_to_smart_quote_character
    Nothing -> return () 
warnTab :: Action
warnTab srcspan _buf _len _buf2 = do
    addTabWarning (psRealSpan srcspan)
    lexToken
warnThen :: PsMessage -> Action -> Action
warnThen warning action srcspan buf len buf2 = do
    addPsMessage (RealSrcSpan (psRealSpan srcspan) Strict.Nothing) warning
    action srcspan buf len buf2
type GenSemic = Bool
generateSemic, dontGenerateSemic :: GenSemic
generateSemic     = True
dontGenerateSemic = False
data LayoutContext
  = NoLayout
  | Layout !Int !GenSemic
  deriving Show
newtype ParseResult a = PR (# (# PState, a #) | PState #)
pattern POk :: PState -> a -> ParseResult a
pattern POk s a = PR (# (# s , a #) | #)
pattern PFailed :: PState -> ParseResult a
pattern PFailed s = PR (# | s #)
{-# COMPLETE POk, PFailed #-}
warnopt :: WarningFlag -> ParserOpts -> Bool
warnopt f options = f `EnumSet.member` pWarningFlags options
data ParserOpts = ParserOpts
  { pExtsBitmap     :: !ExtsBitmap 
  , pDiagOpts       :: !DiagOpts
    
  , pSupportedExts  :: [String]
    
  }
pWarningFlags :: ParserOpts -> EnumSet WarningFlag
pWarningFlags opts = diag_warning_flags (pDiagOpts opts)
data HdkComment
  = HdkCommentNext HsDocString
  | HdkCommentPrev HsDocString
  | HdkCommentNamed String HsDocString
  | HdkCommentSection Int HsDocString
  deriving Show
data PState = PState {
        buffer     :: StringBuffer,
        options    :: ParserOpts,
        warnings   :: Messages PsMessage,
        errors     :: Messages PsMessage,
        tab_first  :: Strict.Maybe RealSrcSpan, 
        tab_count  :: !Word,             
        last_tk    :: Strict.Maybe (PsLocated Token), 
        prev_loc   :: PsSpan,      
        last_loc   :: PsSpan,      
        last_len   :: !Int,        
        loc        :: PsLoc,       
        context    :: [LayoutContext],
        lex_state  :: [Int],
        srcfiles   :: [FastString],
        
        
        
        alr_pending_implicit_tokens :: [PsLocated Token],
        
        
        alr_next_token :: Maybe (PsLocated Token),
        
        
        alr_last_loc :: PsSpan,
        
        alr_context :: [ALRContext],
        
        
        alr_expecting_ocurly :: Maybe ALRLayout,
        
        
        alr_justClosedExplicitLetBlock :: Bool,
        
        
        
        
        eof_pos :: Strict.Maybe (Strict.Pair RealSrcSpan RealSrcSpan), 
        header_comments :: Strict.Maybe [LEpaComment],
        comment_q :: [LEpaComment],
        
        
        
        
        hdk_comments :: OrdList (PsLocated HdkComment)
     }
        
        
        
        
        
        
        
        
        
        
data ALRContext = ALRNoLayout Bool
                              Bool
                | ALRLayout ALRLayout Int
data ALRLayout = ALRLayoutLet
               | ALRLayoutWhere
               | ALRLayoutOf
               | ALRLayoutDo
newtype P a = P { unP :: PState -> ParseResult a }
instance Functor P where
  fmap = liftM
instance Applicative P where
  pure = returnP
  (<*>) = ap
instance Monad P where
  (>>=) = thenP
returnP :: a -> P a
returnP a = a `seq` (P $ \s -> POk s a)
thenP :: P a -> (a -> P b) -> P b
(P m) `thenP` k = P $ \ s ->
        case m s of
                POk s1 a         -> (unP (k a)) s1
                PFailed s1 -> PFailed s1
failMsgP :: (SrcSpan -> MsgEnvelope PsMessage) -> P a
failMsgP f = do
  pState <- getPState
  addFatalError (f (mkSrcSpanPs (last_loc pState)))
failLocMsgP :: RealSrcLoc -> RealSrcLoc -> (SrcSpan -> MsgEnvelope PsMessage) -> P a
failLocMsgP loc1 loc2 f =
  addFatalError (f (RealSrcSpan (mkRealSrcSpan loc1 loc2) Strict.Nothing))
getPState :: P PState
getPState = P $ \s -> POk s s
getExts :: P ExtsBitmap
getExts = P $ \s -> POk s (pExtsBitmap . options $ s)
setExts :: (ExtsBitmap -> ExtsBitmap) -> P ()
setExts f = P $ \s -> POk s {
  options =
    let p = options s
    in  p { pExtsBitmap = f (pExtsBitmap p) }
  } ()
setSrcLoc :: RealSrcLoc -> P ()
setSrcLoc new_loc =
  P $ \s@(PState{ loc = PsLoc _ buf_loc }) ->
  POk s{ loc = PsLoc new_loc buf_loc } ()
getRealSrcLoc :: P RealSrcLoc
getRealSrcLoc = P $ \s@(PState{ loc=loc }) -> POk s (psRealLoc loc)
getParsedLoc :: P PsLoc
getParsedLoc  = P $ \s@(PState{ loc=loc }) -> POk s loc
addSrcFile :: FastString -> P ()
addSrcFile f = P $ \s -> POk s{ srcfiles = f : srcfiles s } ()
setEofPos :: RealSrcSpan -> RealSrcSpan -> P ()
setEofPos span gap = P $ \s -> POk s{ eof_pos = Strict.Just (span `Strict.And` gap) } ()
setLastToken :: PsSpan -> Int -> P ()
setLastToken loc len = P $ \s -> POk s {
  last_loc=loc,
  last_len=len
  } ()
setLastTk :: PsLocated Token -> P ()
setLastTk tk@(L l _) = P $ \s ->
  if isPointRealSpan (psRealSpan l)
    then POk s { last_tk = Strict.Just tk } ()
    else POk s { last_tk = Strict.Just tk
               , prev_loc = l } ()
setLastComment :: PsLocated Token -> P ()
setLastComment (L l _) = P $ \s -> POk s { prev_loc = l } ()
getLastTk :: P (Strict.Maybe (PsLocated Token))
getLastTk = P $ \s@(PState { last_tk = last_tk }) -> POk s last_tk
getLastLocIncludingComments :: P PsSpan
getLastLocIncludingComments = P $ \s@(PState { prev_loc = prev_loc }) -> POk s prev_loc
getLastLoc :: P PsSpan
getLastLoc = P $ \s@(PState { last_loc = last_loc }) -> POk s last_loc
data AlexInput = AI !PsLoc !StringBuffer
{-# INLINE adjustChar #-}
adjustChar :: Char -> Word8
adjustChar c = fromIntegral $ ord adj_c
  where non_graphic     = '\x00'
        upper           = '\x01'
        lower           = '\x02'
        digit           = '\x03'
        symbol          = '\x04'
        space           = '\x05'
        other_graphic   = '\x06'
        uniidchar       = '\x07'
        adj_c
          | c <= '\x07' = non_graphic
          | c <= '\x7f' = c
          
          
          
          | otherwise =
                
                
                
                case generalCategory c of
                  UppercaseLetter       -> upper
                  LowercaseLetter       -> lower
                  TitlecaseLetter       -> upper
                  ModifierLetter        -> uniidchar 
                  OtherLetter           -> lower 
                  NonSpacingMark        -> uniidchar 
                  SpacingCombiningMark  -> other_graphic
                  EnclosingMark         -> other_graphic
                  DecimalNumber         -> digit
                  LetterNumber          -> digit
                  OtherNumber           -> digit 
                  ConnectorPunctuation  -> symbol
                  DashPunctuation       -> symbol
                  OpenPunctuation       -> other_graphic
                  ClosePunctuation      -> other_graphic
                  InitialQuote          -> other_graphic
                  FinalQuote            -> other_graphic
                  OtherPunctuation      -> symbol
                  MathSymbol            -> symbol
                  CurrencySymbol        -> symbol
                  ModifierSymbol        -> symbol
                  OtherSymbol           -> symbol
                  Space                 -> space
                  _other                -> non_graphic
alexInputPrevChar :: AlexInput -> Char
alexInputPrevChar (AI _ buf) = chr (fromIntegral (adjustChar pc))
  where pc = prevChar buf '\n'
alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar inp = case alexGetByte inp of
                    Nothing    -> Nothing
                    Just (b,i) -> c `seq` Just (c,i)
                       where c = chr $ fromIntegral b
alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
alexGetByte (AI loc s)
  | atEnd s   = Nothing
  | otherwise = byte `seq` loc' `seq` s' `seq`
                
                Just (byte, (AI loc' s'))
  where (c,s') = nextChar s
        loc'   = advancePsLoc loc c
        byte   = adjustChar c
{-# INLINE alexGetChar' #-}
alexGetChar' :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar' (AI loc s)
  | atEnd s   = Nothing
  | otherwise = c `seq` loc' `seq` s' `seq`
                
                Just (c, (AI loc' s'))
  where (c,s') = nextChar s
        loc'   = advancePsLoc loc c
getInput :: P AlexInput
getInput = P $ \s@PState{ loc=l, buffer=b } -> POk s (AI l b)
setInput :: AlexInput -> P ()
setInput (AI l b) = P $ \s -> POk s{ loc=l, buffer=b } ()
nextIsEOF :: P Bool
nextIsEOF = do
  AI _ s <- getInput
  return $ atEnd s
pushLexState :: Int -> P ()
pushLexState ls = P $ \s@PState{ lex_state=l } -> POk s{lex_state=ls:l} ()
popLexState :: P Int
popLexState = P $ \s@PState{ lex_state=ls:l } -> POk s{ lex_state=l } ls
getLexState :: P Int
getLexState = P $ \s@PState{ lex_state=ls:_ } -> POk s ls
popNextToken :: P (Maybe (PsLocated Token))
popNextToken
    = P $ \s@PState{ alr_next_token = m } ->
              POk (s {alr_next_token = Nothing}) m
activeContext :: P Bool
activeContext = do
  ctxt <- getALRContext
  expc <- getAlrExpectingOCurly
  impt <- implicitTokenPending
  case (ctxt,expc) of
    ([],Nothing) -> return impt
    _other       -> return True
resetAlrLastLoc :: FastString -> P ()
resetAlrLastLoc file =
  P $ \s@(PState {alr_last_loc = PsSpan _ buf_span}) ->
  POk s{ alr_last_loc = PsSpan (alrInitialLoc file) buf_span } ()
setAlrLastLoc :: PsSpan -> P ()
setAlrLastLoc l = P $ \s -> POk (s {alr_last_loc = l}) ()
getAlrLastLoc :: P PsSpan
getAlrLastLoc = P $ \s@(PState {alr_last_loc = l}) -> POk s l
getALRContext :: P [ALRContext]
getALRContext = P $ \s@(PState {alr_context = cs}) -> POk s cs
setALRContext :: [ALRContext] -> P ()
setALRContext cs = P $ \s -> POk (s {alr_context = cs}) ()
getJustClosedExplicitLetBlock :: P Bool
getJustClosedExplicitLetBlock
 = P $ \s@(PState {alr_justClosedExplicitLetBlock = b}) -> POk s b
setJustClosedExplicitLetBlock :: Bool -> P ()
setJustClosedExplicitLetBlock b
 = P $ \s -> POk (s {alr_justClosedExplicitLetBlock = b}) ()
setNextToken :: PsLocated Token -> P ()
setNextToken t = P $ \s -> POk (s {alr_next_token = Just t}) ()
implicitTokenPending :: P Bool
implicitTokenPending
    = P $ \s@PState{ alr_pending_implicit_tokens = ts } ->
              case ts of
              [] -> POk s False
              _  -> POk s True
popPendingImplicitToken :: P (Maybe (PsLocated Token))
popPendingImplicitToken
    = P $ \s@PState{ alr_pending_implicit_tokens = ts } ->
              case ts of
              [] -> POk s Nothing
              (t : ts') -> POk (s {alr_pending_implicit_tokens = ts'}) (Just t)
setPendingImplicitTokens :: [PsLocated Token] -> P ()
setPendingImplicitTokens ts = P $ \s -> POk (s {alr_pending_implicit_tokens = ts}) ()
getAlrExpectingOCurly :: P (Maybe ALRLayout)
getAlrExpectingOCurly = P $ \s@(PState {alr_expecting_ocurly = b}) -> POk s b
setAlrExpectingOCurly :: Maybe ALRLayout -> P ()
setAlrExpectingOCurly b = P $ \s -> POk (s {alr_expecting_ocurly = b}) ()
type ExtsBitmap = Word64
xbit :: ExtBits -> ExtsBitmap
xbit = bit . fromEnum
xtest :: ExtBits -> ExtsBitmap -> Bool
xtest ext xmap = testBit xmap (fromEnum ext)
xset :: ExtBits -> ExtsBitmap -> ExtsBitmap
xset ext xmap = setBit xmap (fromEnum ext)
xunset :: ExtBits -> ExtsBitmap -> ExtsBitmap
xunset ext xmap = clearBit xmap (fromEnum ext)
data ExtBits
  
  = FfiBit
  | InterruptibleFfiBit
  | CApiFfiBit
  | ArrowsBit
  | ThBit
  | ThQuotesBit
  | IpBit
  | OverloadedLabelsBit 
  | ExplicitForallBit 
  | BangPatBit 
               
  | PatternSynonymsBit 
  | HaddockBit
  | MagicHashBit 
  | RecursiveDoBit 
  | QualifiedDoBit 
  | UnicodeSyntaxBit 
  | UnboxedParensBit 
  | DatatypeContextsBit
  | MonadComprehensionsBit
  | TransformComprehensionsBit
  | QqBit 
  | RawTokenStreamBit 
  | AlternativeLayoutRuleBit
  | ALRTransitionalBit
  | RelaxedLayoutBit
  | NondecreasingIndentationBit
  | SafeHaskellBit
  | TraditionalRecordSyntaxBit
  | ExplicitNamespacesBit
  | LambdaCaseBit
  | BinaryLiteralsBit
  | NegativeLiteralsBit
  | HexFloatLiteralsBit
  | StaticPointersBit
  | NumericUnderscoresBit
  | StarIsTypeBit
  | BlockArgumentsBit
  | NPlusKPatternsBit
  | DoAndIfThenElseBit
  | MultiWayIfBit
  | GadtSyntaxBit
  | ImportQualifiedPostBit
  | LinearTypesBit
  | NoLexicalNegationBit   
  | OverloadedRecordDotBit
  | OverloadedRecordUpdateBit
  | ExtendedLiteralsBit
  
  | InRulePragBit
  | InNestedCommentBit 
  | UsePosPragsBit
    
    
    
  deriving Enum
{-# INLINE mkParserOpts #-}
mkParserOpts
  :: EnumSet LangExt.Extension  
  -> DiagOpts                   
  -> [String]                   
  -> Bool                       
  -> Bool                       
  -> Bool                       
  -> Bool
  
  
  
  -> ParserOpts
mkParserOpts extensionFlags diag_opts supported
  safeImports isHaddock rawTokStream usePosPrags =
    ParserOpts {
      pDiagOpts      = diag_opts
    , pExtsBitmap    = safeHaskellBit .|. langExtBits .|. optBits
    , pSupportedExts = supported
    }
  where
    safeHaskellBit = SafeHaskellBit `setBitIf` safeImports
    langExtBits =
          FfiBit                      `xoptBit` LangExt.ForeignFunctionInterface
      .|. InterruptibleFfiBit         `xoptBit` LangExt.InterruptibleFFI
      .|. CApiFfiBit                  `xoptBit` LangExt.CApiFFI
      .|. ArrowsBit                   `xoptBit` LangExt.Arrows
      .|. ThBit                       `xoptBit` LangExt.TemplateHaskell
      .|. ThQuotesBit                 `xoptBit` LangExt.TemplateHaskellQuotes
      .|. QqBit                       `xoptBit` LangExt.QuasiQuotes
      .|. IpBit                       `xoptBit` LangExt.ImplicitParams
      .|. OverloadedLabelsBit         `xoptBit` LangExt.OverloadedLabels
      .|. ExplicitForallBit           `xoptBit` LangExt.ExplicitForAll
      .|. BangPatBit                  `xoptBit` LangExt.BangPatterns
      .|. MagicHashBit                `xoptBit` LangExt.MagicHash
      .|. RecursiveDoBit              `xoptBit` LangExt.RecursiveDo
      .|. QualifiedDoBit              `xoptBit` LangExt.QualifiedDo
      .|. UnicodeSyntaxBit            `xoptBit` LangExt.UnicodeSyntax
      .|. UnboxedParensBit            `orXoptsBit` [LangExt.UnboxedTuples, LangExt.UnboxedSums]
      .|. DatatypeContextsBit         `xoptBit` LangExt.DatatypeContexts
      .|. TransformComprehensionsBit  `xoptBit` LangExt.TransformListComp
      .|. MonadComprehensionsBit      `xoptBit` LangExt.MonadComprehensions
      .|. AlternativeLayoutRuleBit    `xoptBit` LangExt.AlternativeLayoutRule
      .|. ALRTransitionalBit          `xoptBit` LangExt.AlternativeLayoutRuleTransitional
      .|. RelaxedLayoutBit            `xoptBit` LangExt.RelaxedLayout
      .|. NondecreasingIndentationBit `xoptBit` LangExt.NondecreasingIndentation
      .|. TraditionalRecordSyntaxBit  `xoptBit` LangExt.TraditionalRecordSyntax
      .|. ExplicitNamespacesBit       `xoptBit` LangExt.ExplicitNamespaces
      .|. LambdaCaseBit               `xoptBit` LangExt.LambdaCase
      .|. BinaryLiteralsBit           `xoptBit` LangExt.BinaryLiterals
      .|. NegativeLiteralsBit         `xoptBit` LangExt.NegativeLiterals
      .|. HexFloatLiteralsBit         `xoptBit` LangExt.HexFloatLiterals
      .|. PatternSynonymsBit          `xoptBit` LangExt.PatternSynonyms
      .|. StaticPointersBit           `xoptBit` LangExt.StaticPointers
      .|. NumericUnderscoresBit       `xoptBit` LangExt.NumericUnderscores
      .|. StarIsTypeBit               `xoptBit` LangExt.StarIsType
      .|. BlockArgumentsBit           `xoptBit` LangExt.BlockArguments
      .|. NPlusKPatternsBit           `xoptBit` LangExt.NPlusKPatterns
      .|. DoAndIfThenElseBit          `xoptBit` LangExt.DoAndIfThenElse
      .|. MultiWayIfBit               `xoptBit` LangExt.MultiWayIf
      .|. GadtSyntaxBit               `xoptBit` LangExt.GADTSyntax
      .|. ImportQualifiedPostBit      `xoptBit` LangExt.ImportQualifiedPost
      .|. LinearTypesBit              `xoptBit` LangExt.LinearTypes
      .|. NoLexicalNegationBit        `xoptNotBit` LangExt.LexicalNegation 
      .|. OverloadedRecordDotBit      `xoptBit` LangExt.OverloadedRecordDot
      .|. OverloadedRecordUpdateBit   `xoptBit` LangExt.OverloadedRecordUpdate  
      .|. ExtendedLiteralsBit         `xoptBit` LangExt.ExtendedLiterals
    optBits =
          HaddockBit        `setBitIf` isHaddock
      .|. RawTokenStreamBit `setBitIf` rawTokStream
      .|. UsePosPragsBit    `setBitIf` usePosPrags
    xoptBit bit ext = bit `setBitIf` EnumSet.member ext extensionFlags
    xoptNotBit bit ext = bit `setBitIf` not (EnumSet.member ext extensionFlags)
    orXoptsBit bit exts = bit `setBitIf` any (`EnumSet.member` extensionFlags) exts
    setBitIf :: ExtBits -> Bool -> ExtsBitmap
    b `setBitIf` cond | cond      = xbit b
                      | otherwise = 0
disableHaddock :: ParserOpts -> ParserOpts
disableHaddock opts = upd_bitmap (xunset HaddockBit)
  where
    upd_bitmap f = opts { pExtsBitmap = f (pExtsBitmap opts) }
initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initPragState options buf loc = (initParserState options buf loc)
   { lex_state = [bol, option_prags, 0]
   }
initParserState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initParserState options buf loc =
  PState {
      buffer        = buf,
      options       = options,
      errors        = emptyMessages,
      warnings      = emptyMessages,
      tab_first     = Strict.Nothing,
      tab_count     = 0,
      last_tk       = Strict.Nothing,
      prev_loc      = mkPsSpan init_loc init_loc,
      last_loc      = mkPsSpan init_loc init_loc,
      last_len      = 0,
      loc           = init_loc,
      context       = [],
      lex_state     = [bol, 0],
      srcfiles      = [],
      alr_pending_implicit_tokens = [],
      alr_next_token = Nothing,
      alr_last_loc = PsSpan (alrInitialLoc (fsLit "<no file>")) (BufSpan (BufPos 0) (BufPos 0)),
      alr_context = [],
      alr_expecting_ocurly = Nothing,
      alr_justClosedExplicitLetBlock = False,
      eof_pos = Strict.Nothing,
      header_comments = Strict.Nothing,
      comment_q = [],
      hdk_comments = nilOL
    }
  where init_loc = PsLoc loc (BufPos 0)
class Monad m => MonadP m where
  
  
  
  
  
  
  
  
  
  
  
  
  addError :: MsgEnvelope PsMessage -> m ()
  
  
  addWarning :: MsgEnvelope PsMessage -> m ()
  
  
  addFatalError :: MsgEnvelope PsMessage -> m a
  
  getBit :: ExtBits -> m Bool
  
  
  allocateCommentsP :: RealSrcSpan -> m EpAnnComments
  
  
  allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments
  
  
  allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments
instance MonadP P where
  addError err
   = P $ \s -> POk s { errors = err `addMessage` errors s} ()
  
  
  
  addWarning w
   = P $ \s -> POk (s { warnings = w `addMessage` warnings s }) ()
  addFatalError err =
    addError err >> P PFailed
  getBit ext = P $ \s -> let b =  ext `xtest` pExtsBitmap (options s)
                         in b `seq` POk s b
  allocateCommentsP ss = P $ \s ->
    let (comment_q', newAnns) = allocateComments ss (comment_q s) in
      POk s {
         comment_q = comment_q'
       } (EpaComments newAnns)
  allocatePriorCommentsP ss = P $ \s ->
    let (header_comments', comment_q', newAnns)
             = allocatePriorComments ss (comment_q s) (header_comments s) in
      POk s {
         header_comments = header_comments',
         comment_q = comment_q'
       } (EpaComments newAnns)
  allocateFinalCommentsP ss = P $ \s ->
    let (header_comments', comment_q', newAnns)
             = allocateFinalComments ss (comment_q s) (header_comments s) in
      POk s {
         header_comments = header_comments',
         comment_q = comment_q'
       } (EpaCommentsBalanced (Strict.fromMaybe [] header_comments') newAnns)
getCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
getCommentsFor (RealSrcSpan l _) = allocateCommentsP l
getCommentsFor _ = return emptyComments
getPriorCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
getPriorCommentsFor (RealSrcSpan l _) = allocatePriorCommentsP l
getPriorCommentsFor _ = return emptyComments
getFinalCommentsFor :: (MonadP m) => SrcSpan -> m EpAnnComments
getFinalCommentsFor (RealSrcSpan l _) = allocateFinalCommentsP l
getFinalCommentsFor _ = return emptyComments
getEofPos :: P (Strict.Maybe (Strict.Pair RealSrcSpan RealSrcSpan))
getEofPos = P $ \s@(PState { eof_pos = pos }) -> POk s pos
addPsMessage :: SrcSpan -> PsMessage -> P ()
addPsMessage srcspan msg = do
  diag_opts <- (pDiagOpts . options) <$> getPState
  addWarning (mkPlainMsgEnvelope diag_opts srcspan msg)
addTabWarning :: RealSrcSpan -> P ()
addTabWarning srcspan
 = P $ \s@PState{tab_first=tf, tab_count=tc, options=o} ->
       let tf' = tf <|> Strict.Just srcspan
           tc' = tc + 1
           s' = if warnopt Opt_WarnTabs o
                then s{tab_first = tf', tab_count = tc'}
                else s
       in POk s' ()
getPsErrorMessages :: PState -> Messages PsMessage
getPsErrorMessages p = errors p
getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage)
getPsMessages p =
  let ws = warnings p
      diag_opts = pDiagOpts (options p)
      
      
      ws' = case tab_first p of
        Strict.Nothing -> ws
        Strict.Just tf ->
          let msg = mkPlainMsgEnvelope diag_opts
                          (RealSrcSpan tf Strict.Nothing)
                          (PsWarnTab (tab_count p))
          in msg `addMessage` ws
  in (ws', errors p)
getContext :: P [LayoutContext]
getContext = P $ \s@PState{context=ctx} -> POk s ctx
setContext :: [LayoutContext] -> P ()
setContext ctx = P $ \s -> POk s{context=ctx} ()
popContext :: P ()
popContext = P $ \ s@(PState{ buffer = buf, options = o, context = ctx,
                              last_len = len, last_loc = last_loc }) ->
  case ctx of
        (_:tl) ->
          POk s{ context = tl } ()
        []     ->
          unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
pushCurrentContext :: GenSemic -> P ()
pushCurrentContext gen_semic = P $ \ s@PState{ last_loc=loc, context=ctx } ->
    POk s{context = Layout (srcSpanStartCol (psRealSpan loc)) gen_semic : ctx} ()
pushModuleContext :: P ()
pushModuleContext = pushCurrentContext generateSemic
getOffside :: P (Ordering, Bool)
getOffside = P $ \s@PState{last_loc=loc, context=stk} ->
                let offs = srcSpanStartCol (psRealSpan loc) in
                let ord = case stk of
                            Layout n gen_semic : _ ->
                              
                              (compare offs n, gen_semic)
                            _ ->
                              (GT, dontGenerateSemic)
                in POk s ord
srcParseErr
  :: ParserOpts
  -> StringBuffer       
  -> Int                
  -> SrcSpan
  -> MsgEnvelope PsMessage
srcParseErr options buf len loc = mkPlainErrorMsgEnvelope loc (PsErrParse token details)
  where
   token = lexemeToString (offsetBytes (-len) buf) len
   pattern_ = decodePrevNChars 8 buf
   last100 = decodePrevNChars 100 buf
   doInLast100 = "do" `isInfixOf` last100
   mdoInLast100 = "mdo" `isInfixOf` last100
   th_enabled = ThQuotesBit `xtest` pExtsBitmap options
   ps_enabled = PatternSynonymsBit `xtest` pExtsBitmap options
   details = PsErrParseDetails {
       ped_th_enabled      = th_enabled
     , ped_do_in_last_100  = doInLast100
     , ped_mdo_in_last_100 = mdoInLast100
     , ped_pat_syn_enabled = ps_enabled
     , ped_pattern_parsed  = pattern_ == "pattern "
     }
srcParseFail :: P a
srcParseFail = P $ \s@PState{ buffer = buf, options = o, last_len = len,
                            last_loc = last_loc } ->
    unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
lexError :: LexErr -> P a
lexError e = do
  loc <- getRealSrcLoc
  (AI end buf) <- getInput
  reportLexError loc (psRealLoc end) buf
    (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer e k)
lexer, lexerDbg :: Bool -> (Located Token -> P a) -> P a
lexer queueComments cont = do
  alr <- getBit AlternativeLayoutRuleBit
  let lexTokenFun = if alr then lexTokenAlr else lexToken
  (L span tok) <- lexTokenFun
  
  if (queueComments && isComment tok)
    then queueComment (L (psRealSpan span) tok) >> lexer queueComments cont
    else cont (L (mkSrcSpanPs span) tok)
lexerDbg queueComments cont = lexer queueComments contDbg
  where
    contDbg tok = trace ("token: " ++ show (unLoc tok)) (cont tok)
lexTokenAlr :: P (PsLocated Token)
lexTokenAlr = do mPending <- popPendingImplicitToken
                 t <- case mPending of
                      Nothing ->
                          do mNext <- popNextToken
                             t <- case mNext of
                                  Nothing -> lexToken
                                  Just next -> return next
                             alternativeLayoutRuleToken t
                      Just t ->
                          return t
                 setAlrLastLoc (getLoc t)
                 case unLoc t of
                     ITwhere  -> setAlrExpectingOCurly (Just ALRLayoutWhere)
                     ITlet    -> setAlrExpectingOCurly (Just ALRLayoutLet)
                     ITof     -> setAlrExpectingOCurly (Just ALRLayoutOf)
                     ITlcase  -> setAlrExpectingOCurly (Just ALRLayoutOf)
                     ITlcases -> setAlrExpectingOCurly (Just ALRLayoutOf)
                     ITdo  _  -> setAlrExpectingOCurly (Just ALRLayoutDo)
                     ITmdo _  -> setAlrExpectingOCurly (Just ALRLayoutDo)
                     ITrec    -> setAlrExpectingOCurly (Just ALRLayoutDo)
                     _        -> return ()
                 return t
alternativeLayoutRuleToken :: PsLocated Token -> P (PsLocated Token)
alternativeLayoutRuleToken t
    = do context <- getALRContext
         lastLoc <- getAlrLastLoc
         mExpectingOCurly <- getAlrExpectingOCurly
         transitional <- getBit ALRTransitionalBit
         justClosedExplicitLetBlock <- getJustClosedExplicitLetBlock
         setJustClosedExplicitLetBlock False
         let thisLoc = getLoc t
             thisCol = srcSpanStartCol (psRealSpan thisLoc)
             newLine = srcSpanStartLine (psRealSpan thisLoc) > srcSpanEndLine (psRealSpan lastLoc)
         case (unLoc t, context, mExpectingOCurly) of
             
             
             (ITocurly, _, Just alrLayout) ->
                 do setAlrExpectingOCurly Nothing
                    let isLet = case alrLayout of
                                ALRLayoutLet -> True
                                _ -> False
                    setALRContext (ALRNoLayout (containsCommas ITocurly) isLet : context)
                    return t
             
             
             (_, ALRLayout _ col : _ls, Just expectingOCurly)
              | (thisCol > col) ||
                (thisCol == col &&
                 isNonDecreasingIndentation expectingOCurly) ->
                 do setAlrExpectingOCurly Nothing
                    setALRContext (ALRLayout expectingOCurly thisCol : context)
                    setNextToken t
                    return (L thisLoc ITvocurly)
              | otherwise ->
                 do setAlrExpectingOCurly Nothing
                    setPendingImplicitTokens [L lastLoc ITvccurly]
                    setNextToken t
                    return (L lastLoc ITvocurly)
             (_, _, Just expectingOCurly) ->
                 do setAlrExpectingOCurly Nothing
                    setALRContext (ALRLayout expectingOCurly thisCol : context)
                    setNextToken t
                    return (L thisLoc ITvocurly)
             
             
             (ITeof, ALRLayout _ _ : ls, _) ->
                 do setALRContext ls
                    setNextToken t
                    return (L thisLoc ITvccurly)
             (ITeof, _, _) ->
                 return t
             
             (ITin, _, _)
              | justClosedExplicitLetBlock ->
                 return t
             (ITin, ALRLayout ALRLayoutLet _ : ls, _)
              | newLine ->
                 do setPendingImplicitTokens [t]
                    setALRContext ls
                    return (L thisLoc ITvccurly)
             
             (ITwhere, ALRLayout _ col : ls, _)
              | newLine && thisCol == col && transitional ->
                 do addPsMessage
                      (mkSrcSpanPs thisLoc)
                      (PsWarnTransitionalLayout TransLayout_Where)
                    setALRContext ls
                    setNextToken t
                    
                    
                    return (L lastLoc ITvccurly)
             
             (ITvbar, ALRLayout _ col : ls, _)
              | newLine && thisCol == col && transitional ->
                 do addPsMessage
                      (mkSrcSpanPs thisLoc)
                      (PsWarnTransitionalLayout TransLayout_Pipe)
                    setALRContext ls
                    setNextToken t
                    
                    
                    return (L lastLoc ITvccurly)
             (_, ALRLayout _ col : ls, _)
              | newLine && thisCol == col ->
                 do setNextToken t
                    let loc = psSpanStart thisLoc
                        zeroWidthLoc = mkPsSpan loc loc
                    return (L zeroWidthLoc ITsemi)
              | newLine && thisCol < col ->
                 do setALRContext ls
                    setNextToken t
                    
                    
                    return (L lastLoc ITvccurly)
             
             
             (u, _, _)
              | isALRclose u ->
                 case context of
                 ALRLayout _ _ : ls ->
                     do setALRContext ls
                        setNextToken t
                        return (L thisLoc ITvccurly)
                 ALRNoLayout _ isLet : ls ->
                     do let ls' = if isALRopen u
                                     then ALRNoLayout (containsCommas u) False : ls
                                     else ls
                        setALRContext ls'
                        when isLet $ setJustClosedExplicitLetBlock True
                        return t
                 [] ->
                     do let ls = if isALRopen u
                                    then [ALRNoLayout (containsCommas u) False]
                                    else []
                        setALRContext ls
                        
                        
                        return t
             (u, _, _)
              | isALRopen u ->
                 do setALRContext (ALRNoLayout (containsCommas u) False : context)
                    return t
             (ITin, ALRLayout ALRLayoutLet _ : ls, _) ->
                 do setALRContext ls
                    setPendingImplicitTokens [t]
                    return (L thisLoc ITvccurly)
             (ITin, ALRLayout _ _ : ls, _) ->
                 do setALRContext ls
                    setNextToken t
                    return (L thisLoc ITvccurly)
             
             (ITcomma, ALRLayout _ _ : ls, _)
              | topNoLayoutContainsCommas ls ->
                 do setALRContext ls
                    setNextToken t
                    return (L thisLoc ITvccurly)
             (ITwhere, ALRLayout ALRLayoutDo _ : ls, _) ->
                 do setALRContext ls
                    setPendingImplicitTokens [t]
                    return (L thisLoc ITvccurly)
             
             (_, _, _) -> return t
isALRopen :: Token -> Bool
isALRopen ITcase          = True
isALRopen ITif            = True
isALRopen ITthen          = True
isALRopen IToparen        = True
isALRopen ITobrack        = True
isALRopen ITocurly        = True
isALRopen IToubxparen     = True
isALRopen _               = False
isALRclose :: Token -> Bool
isALRclose ITof     = True
isALRclose ITthen   = True
isALRclose ITelse   = True
isALRclose ITcparen = True
isALRclose ITcbrack = True
isALRclose ITccurly = True
isALRclose ITcubxparen = True
isALRclose _        = False
isNonDecreasingIndentation :: ALRLayout -> Bool
isNonDecreasingIndentation ALRLayoutDo = True
isNonDecreasingIndentation _           = False
containsCommas :: Token -> Bool
containsCommas IToparen = True
containsCommas ITobrack = True
containsCommas ITocurly = True
containsCommas IToubxparen = True
containsCommas _        = False
topNoLayoutContainsCommas :: [ALRContext] -> Bool
topNoLayoutContainsCommas [] = False
topNoLayoutContainsCommas (ALRLayout _ _ : ls) = topNoLayoutContainsCommas ls
topNoLayoutContainsCommas (ALRNoLayout b _ : _) = b
lexToken :: P (PsLocated Token)
lexToken = do
  inp@(AI loc1 buf) <- getInput
  sc <- getLexState
  exts <- getExts
  case alexScanUser exts inp sc of
    AlexEOF -> do
        let span = mkPsSpan loc1 loc1
        lc <- getLastLocIncludingComments
        setEofPos (psRealSpan span) (psRealSpan lc)
        setLastToken span 0
        return (L span ITeof)
    AlexError (AI loc2 buf) ->
        reportLexError (psRealLoc loc1) (psRealLoc loc2) buf
          (\k srcLoc -> mkPlainErrorMsgEnvelope srcLoc $ PsErrLexer LexError k)
    AlexSkip inp2 _ -> do
        setInput inp2
        lexToken
    AlexToken inp2@(AI end buf2) _ t -> do
        setInput inp2
        let span = mkPsSpan loc1 end
        let bytes = byteDiff buf buf2
        span `seq` setLastToken span bytes
        lt <- t span buf bytes buf2
        let lt' = unLoc lt
        if (isComment lt') then setLastComment lt else setLastTk lt
        return lt
reportLexError :: RealSrcLoc
               -> RealSrcLoc
               -> StringBuffer
               -> (LexErrKind -> SrcSpan -> MsgEnvelope PsMessage)
               -> P a
reportLexError loc1 loc2 buf f
  | atEnd buf = failLocMsgP loc1 loc2 (f LexErrKind_EOF)
  | otherwise =
  let c = fst (nextChar buf)
  in if c == '\0' 
     then failLocMsgP loc2 loc2 (f LexErrKind_UTF8)
     else failLocMsgP loc1 loc2 (f (LexErrKind_Char c))
lexTokenStream :: ParserOpts -> StringBuffer -> RealSrcLoc -> ParseResult [Located Token]
lexTokenStream opts buf loc = unP go initState{ options = opts' }
    where
    new_exts  =   xunset UsePosPragsBit  
                $ xset RawTokenStreamBit 
                $ pExtsBitmap opts
    opts'     = opts { pExtsBitmap = new_exts }
    initState = initParserState opts' buf loc
    go = do
      ltok <- lexer False return
      case ltok of
        L _ ITeof -> return []
        _ -> liftM (ltok:) go
linePrags = Map.singleton "line" linePrag
fileHeaderPrags = Map.fromList([("options", lex_string_prag IToptions_prag),
                                 ("options_ghc", lex_string_prag IToptions_prag),
                                 ("options_haddock", lex_string_prag_comment ITdocOptions),
                                 ("language", token ITlanguage_prag),
                                 ("include", lex_string_prag ITinclude_prag)])
ignoredPrags = Map.fromList (map ignored pragmas)
               where ignored opt = (opt, nested_comment)
                     impls = ["hugs", "nhc98", "jhc", "yhc", "catch", "derive"]
                     options_pragmas = map ("options_" ++) impls
                     
                     pragmas = options_pragmas ++ ["cfiles", "contract"]
oneWordPrags = Map.fromList [
     ("rules", rulePrag),
     ("inline",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (Inline (SourceText s)) FunLike))),
     ("inlinable",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (Inlinable (SourceText s)) FunLike))),
     ("inlineable",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (Inlinable (SourceText s)) FunLike))),
                                    
     ("notinline",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (NoInline (SourceText s)) FunLike))),
     ("opaque", fstrtoken (\s -> ITopaque_prag (SourceText s))),
     ("specialize", fstrtoken (\s -> ITspec_prag (SourceText s))),
     ("source", fstrtoken (\s -> ITsource_prag (SourceText s))),
     ("warning", fstrtoken (\s -> ITwarning_prag (SourceText s))),
     ("deprecated", fstrtoken (\s -> ITdeprecated_prag (SourceText s))),
     ("scc", fstrtoken (\s -> ITscc_prag (SourceText s))),
     ("unpack", fstrtoken (\s -> ITunpack_prag (SourceText s))),
     ("nounpack", fstrtoken (\s -> ITnounpack_prag (SourceText s))),
     ("ann", fstrtoken (\s -> ITann_prag (SourceText s))),
     ("minimal", fstrtoken (\s -> ITminimal_prag (SourceText s))),
     ("overlaps", fstrtoken (\s -> IToverlaps_prag (SourceText s))),
     ("overlappable", fstrtoken (\s -> IToverlappable_prag (SourceText s))),
     ("overlapping", fstrtoken (\s -> IToverlapping_prag (SourceText s))),
     ("incoherent", fstrtoken (\s -> ITincoherent_prag (SourceText s))),
     ("ctype", fstrtoken (\s -> ITctype (SourceText s))),
     ("complete", fstrtoken (\s -> ITcomplete_prag (SourceText s))),
     ("column", columnPrag)
     ]
twoWordPrags = Map.fromList [
     ("inline conlike",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (Inline (SourceText s)) ConLike))),
     ("notinline conlike",
         fstrtoken (\s -> (ITinline_prag (SourceText s) (NoInline (SourceText s)) ConLike))),
     ("specialize inline",
         fstrtoken (\s -> (ITspec_inline_prag (SourceText s) True))),
     ("specialize notinline",
         fstrtoken (\s -> (ITspec_inline_prag (SourceText s) False)))
     ]
dispatch_pragmas :: Map String Action -> Action
dispatch_pragmas prags span buf len buf2 =
  case Map.lookup (clean_pragma (lexemeToString buf len)) prags of
    Just found -> found span buf len buf2
    Nothing -> lexError LexUnknownPragma
known_pragma :: Map String Action -> AlexAccPred ExtsBitmap
known_pragma prags _ (AI _ startbuf) _ (AI _ curbuf)
 = isKnown && nextCharIsNot curbuf pragmaNameChar
    where l = lexemeToString startbuf (byteDiff startbuf curbuf)
          isKnown = isJust $ Map.lookup (clean_pragma l) prags
          pragmaNameChar c = isAlphaNum c || c == '_'
clean_pragma :: String -> String
clean_pragma prag = canon_ws (map toLower (unprefix prag))
                    where unprefix prag' = case stripPrefix "{-#" prag' of
                                             Just rest -> rest
                                             Nothing -> prag'
                          canonical prag' = case prag' of
                                              "noinline" -> "notinline"
                                              "specialise" -> "specialize"
                                              "constructorlike" -> "conlike"
                                              _ -> prag'
                          canon_ws s = unwords (map canonical (words s))
warn_unknown_prag :: Map String Action -> Action
warn_unknown_prag prags span buf len buf2 = do
  let uppercase    = map toUpper
      unknown_prag = uppercase (clean_pragma (lexemeToString buf len))
      suggestions  = map uppercase (Map.keys prags)
  addPsMessage (RealSrcSpan (psRealSpan span) Strict.Nothing) $
    PsWarnUnrecognisedPragma unknown_prag suggestions
  nested_comment span buf len buf2
mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan lo Strict.Nothing),AddEpAnn AnnCloseP (EpaSpan lc Strict.Nothing))
  where
    f = srcSpanFile ss
    sl = srcSpanStartLine ss
    sc = srcSpanStartCol ss
    el = srcSpanEndLine ss
    ec = srcSpanEndCol ss
    lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
    lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
queueComment :: RealLocated Token -> P()
queueComment c = P $ \s -> POk s {
  comment_q = commentToAnnotation c : comment_q s
  } ()
allocateComments
  :: RealSrcSpan
  -> [LEpaComment]
  -> ([LEpaComment], [LEpaComment])
allocateComments ss comment_q =
  let
    (before,rest)  = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
    comment_q' = before ++ after
    newAnns = middle
  in
    (comment_q', reverse newAnns)
splitPriorComments
  :: RealSrcSpan
  -> [LEpaComment]
  -> ([LEpaComment], [LEpaComment])
splitPriorComments ss prior_comments =
  let
    
    
    cmp :: RealSrcSpan -> LEpaComment -> Bool
    cmp later (L l c)
         = srcSpanStartLine later - srcSpanEndLine (anchor l) == 1
          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (anchor l)
    go :: [LEpaComment] -> RealSrcSpan -> [LEpaComment]
       -> ([LEpaComment], [LEpaComment])
    go decl_comments _ [] = ([],decl_comments)
    go decl_comments r (c@(L l _):cs) = if cmp r c
                              then go (c:decl_comments) (anchor l) cs
                              else (reverse (c:cs), decl_comments)
  in
    go [] ss prior_comments
allocatePriorComments
  :: RealSrcSpan
  -> [LEpaComment]
  -> Strict.Maybe [LEpaComment]
  -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
allocatePriorComments ss comment_q mheader_comments =
  let
    cmp (L l _) = anchor l <= ss
    (newAnns,after) = partition cmp comment_q
    comment_q'= after
    (prior_comments, decl_comments) = splitPriorComments ss newAnns
  in
    case mheader_comments of
      Strict.Nothing -> (Strict.Just prior_comments, comment_q', decl_comments)
      Strict.Just _ -> (mheader_comments, comment_q', reverse newAnns)
allocateFinalComments
  :: RealSrcSpan
  -> [LEpaComment]
  -> Strict.Maybe [LEpaComment]
  -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
allocateFinalComments _ss comment_q mheader_comments =
  
  
  case mheader_comments of
    Strict.Nothing -> (Strict.Just (reverse comment_q), [], [])
    Strict.Just _ -> (mheader_comments, [], reverse comment_q)
commentToAnnotation :: RealLocated Token -> LEpaComment
commentToAnnotation (L l (ITdocComment s ll))   = mkLEpaComment l ll (EpaDocComment s)
commentToAnnotation (L l (ITdocOptions s ll))   = mkLEpaComment l ll (EpaDocOptions s)
commentToAnnotation (L l (ITlineComment s ll))  = mkLEpaComment l ll (EpaLineComment s)
commentToAnnotation (L l (ITblockComment s ll)) = mkLEpaComment l ll (EpaBlockComment s)
commentToAnnotation _                           = panic "commentToAnnotation"
mkLEpaComment :: RealSrcSpan -> PsSpan -> EpaCommentTok -> LEpaComment
mkLEpaComment l ll tok = L (realSpanAsAnchor l) (EpaComment tok (psRealSpan ll))
isComment :: Token -> Bool
isComment (ITlineComment  _ _) = True
isComment (ITblockComment _ _) = True
isComment (ITdocComment   _ _) = True
isComment (ITdocOptions   _ _) = True
isComment _                    = False
bol,column_prag,layout,layout_do,layout_if,layout_left,line_prag1,line_prag1a,line_prag2,line_prag2a,option_prags :: Int
bol = 1
column_prag = 2
layout = 3
layout_do = 4
layout_if = 5
layout_left = 6
line_prag1 = 7
line_prag1a = 8
line_prag2 = 9
line_prag2a = 10
option_prags = 11
alex_action_1 = warnTab
alex_action_2 = nested_comment
alex_action_3 = lineCommentToken
alex_action_4 = lineCommentToken
alex_action_5 = lineCommentToken
alex_action_6 = lineCommentToken
alex_action_7 = lineCommentToken
alex_action_8 = lineCommentToken
alex_action_9 = smart_quote_error
alex_action_11 = begin line_prag1
alex_action_12 = begin line_prag1
alex_action_16 = do_bol
alex_action_17 = hopefully_open_brace
alex_action_19 = begin line_prag1
alex_action_20 = new_layout_context True dontGenerateSemic ITvbar
alex_action_21 = pop
alex_action_22 = new_layout_context True  generateSemic ITvocurly
alex_action_23 = new_layout_context False generateSemic ITvocurly
alex_action_24 = do_layout_left
alex_action_25 = begin bol
alex_action_26 = dispatch_pragmas linePrags
alex_action_27 = setLineAndFile line_prag1a
alex_action_28 = failLinePrag1
alex_action_29 = popLinePrag1
alex_action_30 = setLineAndFile line_prag2a
alex_action_31 = pop
alex_action_32 = setColumn
alex_action_33 = dispatch_pragmas twoWordPrags
alex_action_34 = dispatch_pragmas oneWordPrags
alex_action_35 = dispatch_pragmas ignoredPrags
alex_action_36 = endPrag
alex_action_37 = dispatch_pragmas fileHeaderPrags
alex_action_38 = nested_comment
alex_action_39 = warn_unknown_prag (Map.unions [ oneWordPrags, fileHeaderPrags, ignoredPrags, linePrags ])
alex_action_40 = warn_unknown_prag Map.empty
alex_action_41 = multiline_doc_comment
alex_action_42 = nested_doc_comment
alex_action_43 = token (ITopenExpQuote NoE NormalSyntax)
alex_action_44 = token (ITopenTExpQuote NoE)
alex_action_45 = token (ITcloseQuote NormalSyntax)
alex_action_46 = token ITcloseTExpQuote
alex_action_47 = token (ITopenExpQuote HasE NormalSyntax)
alex_action_48 = token (ITopenTExpQuote HasE)
alex_action_49 = token ITopenPatQuote
alex_action_50 = layout_token ITopenDecQuote
alex_action_51 = token ITopenTypQuote
alex_action_52 = lex_quasiquote_tok
alex_action_53 = lex_qquasiquote_tok
alex_action_54 = token (ITopenExpQuote NoE UnicodeSyntax)
alex_action_55 = token (ITcloseQuote UnicodeSyntax)
alex_action_56 = special (IToparenbar NormalSyntax)
alex_action_57 = special (ITcparenbar NormalSyntax)
alex_action_58 = special (IToparenbar UnicodeSyntax)
alex_action_59 = special (ITcparenbar UnicodeSyntax)
alex_action_60 = skip_one_varid ITdupipvarid
alex_action_61 = skip_one_varid_src ITlabelvarid
alex_action_62 = lex_quoted_label
alex_action_63 = token IToubxparen
alex_action_64 = token ITcubxparen
alex_action_65 = special IToparen
alex_action_66 = special ITcparen
alex_action_67 = special ITobrack
alex_action_68 = special ITcbrack
alex_action_69 = special ITcomma
alex_action_70 = special ITsemi
alex_action_71 = special ITbackquote
alex_action_72 = open_brace
alex_action_73 = close_brace
alex_action_74 = qdo_token ITdo
alex_action_75 = qdo_token ITmdo
alex_action_76 = idtoken qvarid
alex_action_77 = idtoken qconid
alex_action_78 = varid
alex_action_79 = idtoken conid
alex_action_80 = idtoken qvarid
alex_action_81 = idtoken qconid
alex_action_82 = varid
alex_action_83 = idtoken conid
alex_action_84 = idtoken qvarsym
alex_action_85 = idtoken qconsym
alex_action_86 = with_op_ws varsym
alex_action_87 = with_op_ws consym
alex_action_88 = tok_num positive 0 0 decimal
alex_action_89 = tok_num positive 2 2 binary
alex_action_90 = tok_num positive 2 2 octal
alex_action_91 = tok_num positive 2 2 hexadecimal
alex_action_92 = tok_num negative 1 1 decimal
alex_action_93 = tok_num negative 3 3 binary
alex_action_94 = tok_num negative 3 3 octal
alex_action_95 = tok_num negative 3 3 hexadecimal
alex_action_96 = tok_frac 0 tok_float
alex_action_97 = tok_frac 0 tok_float
alex_action_98 = tok_frac 0 tok_hex_float
alex_action_99 = tok_frac 0 tok_hex_float
alex_action_100 = tok_primint positive 0 1 decimal
alex_action_101 = tok_primint positive 2 3 binary
alex_action_102 = tok_primint positive 2 3 octal
alex_action_103 = tok_primint positive 2 3 hexadecimal
alex_action_104 = tok_primint negative 1 2 decimal
alex_action_105 = tok_primint negative 3 4 binary
alex_action_106 = tok_primint negative 3 4 octal
alex_action_107 = tok_primint negative 3 4 hexadecimal
alex_action_108 = tok_primword 0 2 decimal
alex_action_109 = tok_primword 2 4 binary
alex_action_110 = tok_primword 2 4 octal
alex_action_111 = tok_primword 2 4 hexadecimal
alex_action_112 = tok_frac 1 tok_primfloat
alex_action_113 = tok_frac 2 tok_primdouble
alex_action_114 = tok_frac 1 tok_primfloat
alex_action_115 = tok_frac 2 tok_primdouble
alex_action_116 = tok_primint8 positive 0 decimal
alex_action_117 = tok_primint8 positive 2 binary
alex_action_118 = tok_primint8 positive 2 octal
alex_action_119 = tok_primint8 positive 2 hexadecimal
alex_action_120 = tok_primint8 negative 1 decimal
alex_action_121 = tok_primint8 negative 3 binary
alex_action_122 = tok_primint8 negative 3 octal
alex_action_123 = tok_primint8 negative 3 hexadecimal
alex_action_124 = tok_primint16 positive 0 decimal
alex_action_125 = tok_primint16 positive 2 binary
alex_action_126 = tok_primint16 positive 2 octal
alex_action_127 = tok_primint16 positive 2 hexadecimal
alex_action_128 = tok_primint16 negative 1 decimal
alex_action_129 = tok_primint16 negative 3 binary
alex_action_130 = tok_primint16 negative 3 octal
alex_action_131 = tok_primint16 negative 3 hexadecimal
alex_action_132 = tok_primint32 positive 0 decimal
alex_action_133 = tok_primint32 positive 2 binary
alex_action_134 = tok_primint32 positive 2 octal
alex_action_135 = tok_primint32 positive 2 hexadecimal
alex_action_136 = tok_primint32 negative 1 decimal
alex_action_137 = tok_primint32 negative 3 binary
alex_action_138 = tok_primint32 negative 3 octal
alex_action_139 = tok_primint32 negative 3 hexadecimal
alex_action_140 = tok_primint64 positive 0 decimal
alex_action_141 = tok_primint64 positive 2 binary
alex_action_142 = tok_primint64 positive 2 octal
alex_action_143 = tok_primint64 positive 2 hexadecimal
alex_action_144 = tok_primint64 negative 1 decimal
alex_action_145 = tok_primint64 negative 3 binary
alex_action_146 = tok_primint64 negative 3 octal
alex_action_147 = tok_primint64 negative 3 hexadecimal
alex_action_148 = tok_primint positive 0 4 decimal
alex_action_149 = tok_primint positive 2 6 binary
alex_action_150 = tok_primint positive 2 6 octal
alex_action_151 = tok_primint positive 2 6 hexadecimal
alex_action_152 = tok_primint negative 1 5 decimal
alex_action_153 = tok_primint negative 3 7 binary
alex_action_154 = tok_primint negative 3 7 octal
alex_action_155 = tok_primint negative 3 7 hexadecimal
alex_action_156 = tok_primword8 0 decimal
alex_action_157 = tok_primword8 2 binary
alex_action_158 = tok_primword8 2 octal
alex_action_159 = tok_primword8 2 hexadecimal
alex_action_160 = tok_primword16 0 decimal
alex_action_161 = tok_primword16 2 binary
alex_action_162 = tok_primword16 2 octal
alex_action_163 = tok_primword16 2 hexadecimal
alex_action_164 = tok_primword32 0 decimal
alex_action_165 = tok_primword32 2 binary
alex_action_166 = tok_primword32 2 octal
alex_action_167 = tok_primword32 2 hexadecimal
alex_action_168 = tok_primword64 0 decimal
alex_action_169 = tok_primword64 2 binary
alex_action_170 = tok_primword64 2 octal
alex_action_171 = tok_primword64 2 hexadecimal
alex_action_172 = tok_primword 0 5 decimal
alex_action_173 = tok_primword 2 7 binary
alex_action_174 = tok_primword 2 7 octal
alex_action_175 = tok_primword 2 7 hexadecimal
alex_action_176 = lex_char_tok
alex_action_177 = lex_string_tok
#define ALEX_GHC 1
#define ALEX_LATIN1 1
#ifdef ALEX_GHC
#  define ILIT(n) n#
#  define IBOX(n) (I# (n))
#  define FAST_INT Int#
#  if __GLASGOW_HASKELL__ > 706
#    define GTE(n,m) (tagToEnum# (n >=# m))
#    define EQ(n,m) (tagToEnum# (n ==# m))
#  else
#    define GTE(n,m) (n >=# m)
#    define EQ(n,m) (n ==# m)
#  endif
#  define PLUS(n,m) (n +# m)
#  define MINUS(n,m) (n -# m)
#  define TIMES(n,m) (n *# m)
#  define NEGATE(n) (negateInt# (n))
#  define IF_GHC(x) (x)
#else
#  define ILIT(n) (n)
#  define IBOX(n) (n)
#  define FAST_INT Int
#  define GTE(n,m) (n >= m)
#  define EQ(n,m) (n == m)
#  define PLUS(n,m) (n + m)
#  define MINUS(n,m) (n - m)
#  define TIMES(n,m) (n * m)
#  define NEGATE(n) (negate (n))
#  define IF_GHC(x)
#endif
#ifdef ALEX_GHC
data AlexAddr = AlexA# Addr#
#if __GLASGOW_HASKELL__ < 503
uncheckedShiftL# = shiftL#
#endif
{-# INLINE alexIndexInt16OffAddr #-}
alexIndexInt16OffAddr :: AlexAddr -> Int# -> Int#
alexIndexInt16OffAddr :: AlexAddr -> Int# -> Int#
alexIndexInt16OffAddr (AlexA# arr) off =
#ifdef WORDS_BIGENDIAN
  narrow16Int# i
  where
        i    = word2Int# ((high `uncheckedShiftL#` 8#) `or#` low)
        high = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
        low  = int2Word# (ord# (indexCharOffAddr# arr off'))
        off' = off *# 2#
#else
#if __GLASGOW_HASKELL__ >= 901
  int16ToInt#
#endif
    (indexInt16OffAddr# arr off)
#endif
#else
alexIndexInt16OffAddr arr off = arr ! off
#endif
#ifdef ALEX_GHC
{-# INLINE alexIndexInt32OffAddr #-}
alexIndexInt32OffAddr :: AlexAddr -> Int# -> Int#
alexIndexInt32OffAddr :: AlexAddr -> Int# -> Int#
alexIndexInt32OffAddr (AlexA# arr) off =
#ifdef WORDS_BIGENDIAN
  narrow32Int# i
  where
   i    = word2Int# ((b3 `uncheckedShiftL#` 24#) `or#`
                     (b2 `uncheckedShiftL#` 16#) `or#`
                     (b1 `uncheckedShiftL#` 8#) `or#` b0)
   b3   = int2Word# (ord# (indexCharOffAddr# arr (off' +# 3#)))
   b2   = int2Word# (ord# (indexCharOffAddr# arr (off' +# 2#)))
   b1   = int2Word# (ord# (indexCharOffAddr# arr (off' +# 1#)))
   b0   = int2Word# (ord# (indexCharOffAddr# arr off'))
   off' = off *# 4#
#else
#if __GLASGOW_HASKELL__ >= 901
  int32ToInt#
#endif
    (indexInt32OffAddr# arr off)
#endif
#else
alexIndexInt32OffAddr arr off = arr ! off
#endif
#ifdef ALEX_GHC
#if __GLASGOW_HASKELL__ < 503
quickIndex arr i = arr ! i
#else
quickIndex = unsafeAt
#endif
#else
quickIndex arr i = arr ! i
#endif
data AlexReturn a
  = AlexEOF
  | AlexError  !AlexInput
  | AlexSkip   !AlexInput !Int
  | AlexToken  !AlexInput !Int a
alexScan input__ IBOX(sc)
  = alexScanUser undefined input__ IBOX(sc)
alexScanUser user__ input__ IBOX(sc)
  = case alex_scan_tkn user__ input__ ILIT(0) input__ sc AlexNone of
  (AlexNone, input__') ->
    case alexGetByte input__ of
      Nothing ->
#ifdef ALEX_DEBUG
                                   trace ("End of input.") $
#endif
                                   AlexEOF
      Just _ ->
#ifdef ALEX_DEBUG
                                   trace ("Error.") $
#endif
                                   AlexError input__'
  (AlexLastSkip input__'' len, _) ->
#ifdef ALEX_DEBUG
    trace ("Skipping.") $
#endif
    AlexSkip input__'' len
  (AlexLastAcc k input__''' len, _) ->
#ifdef ALEX_DEBUG
    trace ("Accept.") $
#endif
    AlexToken input__''' len (alex_actions ! k)
alex_scan_tkn user__ orig_input len input__ s last_acc =
  input__ `seq` 
  let
  new_acc = (check_accs (alex_accept `quickIndex` IBOX(s)))
  in
  new_acc `seq`
  case alexGetByte input__ of
     Nothing -> (new_acc, input__)
     Just (c, new_input) ->
#ifdef ALEX_DEBUG
      trace ("State: " ++ show IBOX(s) ++ ", char: " ++ show c) $
#endif
      case fromIntegral c of { IBOX(ord_c) ->
        let
                base   = alexIndexInt32OffAddr alex_base s
                offset = PLUS(base,ord_c)
                check  = alexIndexInt16OffAddr alex_check offset
                new_s = if GTE(offset,ILIT(0)) && EQ(check,ord_c)
                          then alexIndexInt16OffAddr alex_table offset
                          else alexIndexInt16OffAddr alex_deflt s
        in
        case new_s of
            ILIT(-1) -> (new_acc, input__)
                
                
            _ -> alex_scan_tkn user__ orig_input
#ifdef ALEX_LATIN1
                   PLUS(len,ILIT(1))
                   
#else
                   (if c < 0x80 || c >= 0xC0 then PLUS(len,ILIT(1)) else len)
                   
#endif
                   new_input new_s new_acc
      }
  where
        check_accs (AlexAccNone) = last_acc
        check_accs (AlexAcc a  ) = AlexLastAcc a input__ IBOX(len)
        check_accs (AlexAccSkip) = AlexLastSkip  input__ IBOX(len)
#ifndef ALEX_NOPRED
        check_accs (AlexAccPred a predx rest)
           | predx user__ orig_input IBOX(len) input__
           = AlexLastAcc a input__ IBOX(len)
           | otherwise
           = check_accs rest
        check_accs (AlexAccSkipPred predx rest)
           | predx user__ orig_input IBOX(len) input__
           = AlexLastSkip input__ IBOX(len)
           | otherwise
           = check_accs rest
#endif
data AlexLastAcc
  = AlexNone
  | AlexLastAcc !Int !AlexInput !Int
  | AlexLastSkip     !AlexInput !Int
data AlexAcc user
  = AlexAccNone
  | AlexAcc Int
  | AlexAccSkip
#ifndef ALEX_NOPRED
  | AlexAccPred Int (AlexAccPred user) (AlexAcc user)
  | AlexAccSkipPred (AlexAccPred user) (AlexAcc user)
type AlexAccPred user = user -> AlexInput -> Int -> AlexInput -> Bool
alexAndPred p1 p2 user__ in1 len in2
  = p1 user__ in1 len in2 && p2 user__ in1 len in2
alexPrevCharIs c _ input__ _ _ = c == alexInputPrevChar input__
alexPrevCharMatches f _ input__ _ _ = f (alexInputPrevChar input__)
alexPrevCharIsOneOf arr _ input__ _ _ = arr ! alexInputPrevChar input__
alexRightContext IBOX(sc) user__ _ _ input__ =
     case alex_scan_tkn user__ input__ ILIT(0) input__ sc AlexNone of
          (AlexNone, _) -> False
          _ -> True
        
        
        
#endif