{-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-missing-signatures #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LINE 43 "compiler/GHC/Parser/Lexer.x" #-}
{-# 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(..), getBit,
   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

-- base
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

-- ghc-boot
import qualified GHC.LanguageExtensions as LangExt

-- bytestring
import Data.ByteString (ByteString)

-- containers
import Data.Map (Map)
import qualified Data.Map as Map

-- compiler
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 ()
import GHC.Parser.String
#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\x03\x02\x00\x00\x81\x00\x00\x00\x82\x00\x00\x00\xfc\x00\x00\x00\xf7\xff\xff\xff\xfa\xff\xff\xff\x81\x02\x00\x00\x64\x01\x00\x00\xf7\x02\x00\x00\x39\x01\x00\x00\x37\x03\x00\x00\xb5\x03\x00\x00\x33\x04\x00\x00\xb1\x04\x00\x00\x2b\x05\x00\x00\xdb\xff\xff\xff\xc3\x00\x00\x00\xa5\x05\x00\x00\x1f\x06\x00\x00\x99\x06\x00\x00\x13\x07\x00\x00\x8d\x07\x00\x00\x07\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xdc\xff\xff\xff\x13\x01\x00\x00\xee\xff\xff\xff\x06\x00\x00\x00\x00\x00\x00\x00\x07\x00\x00\x00\x00\x00\x00\x00\xa0\xff\xff\xff\xb2\xff\xff\xff\xad\xff\xff\xff\xa8\xff\xff\xff\xb5\xff\xff\xff\x7d\x08\x00\x00\xe0\x07\x00\x00\xd3\x08\x00\x00\x0d\x09\x00\x00\x67\x09\x00\x00\xe7\xff\xff\xff\xde\x06\x00\x00\x40\x00\x00\x00\xc1\x09\x00\x00\xdd\xff\xff\xff\xda\xff\xff\xff\x4c\x00\x00\x00\x49\x00\x00\x00\x37\x00\x00\x00\x45\x00\x00\x00\x55\x00\x00\x00\x51\x00\x00\x00\x41\x00\x00\x00\x3f\x00\x00\x00\x85\x02\x00\x00\x8f\x00\x00\x00\x00\x00\x00\x00\x7f\x00\x00\x00\x31\x00\x00\x00\x2f\x00\x00\x00\x3c\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x0a\x00\x00\x00\x00\x00\x00\x98\x00\x00\x00\x00\x00\x00\x00\xbd\x0a\x00\x00\xf0\x00\x00\x00\x49\x01\x00\x00\x3b\x0b\x00\x00\xb9\x0b\x00\x00\x34\x0c\x00\x00\x5c\x0c\x00\x00\x9f\x0c\x00\x00\xc7\x0c\x00\x00\x76\x00\x00\x00\x0a\x0d\x00\x00\x32\x0d\x00\x00\x61\x0d\x00\x00\x88\x0d\x00\x00\x02\x0e\x00\x00\x84\x01\x00\x00\x53\x0e\x00\x00\xb5\x00\x00\x00\xa8\x00\x00\x00\xa6\x00\x00\x00\xd3\x00\x00\x00\xa9\x00\x00\x00\xd4\x00\x00\x00\xcb\x00\x00\x00\xb2\x0e\x00\x00\xc2\x00\x00\x00\xea\x00\x00\x00\x3e\x01\x00\x00\x09\x01\x00\x00\xf4\x00\x00\x00\xb4\x00\x00\x00\xee\x00\x00\x00\x33\x01\x00\x00\xfb\x00\x00\x00\xb2\x02\x00\x00\xd8\x00\x00\x00\xd7\x02\x00\x00\xe1\x01\x00\x00\x16\x0c\x00\x00\xed\x02\x00\x00\xdd\x0d\x00\x00\x63\x02\x00\x00\x0a\x0f\x00\x00\x88\x0e\x00\x00\x3d\x08\x00\x00\x48\x01\x00\x00\x41\x01\x00\x00\x43\x01\x00\x00\x40\x0f\x00\x00\xa1\x02\x00\x00\x9e\x0f\x00\x00\xb5\x04\x00\x00\x16\x10\x00\x00\x94\x10\x00\x00\x12\x11\x00\x00\x90\x11\x00\x00\xba\x00\x00\x00\xcc\x00\x00\x00\x6f\x01\x00\x00\x65\x01\x00\x00\x5f\x01\x00\x00\xba\x09\x00\x00\xf4\x02\x00\x00\x53\x01\x00\x00\x02\x05\x00\x00\x60\x01\x00\x00\x71\x01\x00\x00\x08\x03\x00\x00\x0a\x12\x00\x00\x68\x12\x00\x00\x09\x05\x00\x00\xb2\x12\x00\x00\x0f\x03\x00\x00\xe2\x12\x00\x00\x83\x05\x00\x00\x7c\x05\x00\x00\x7b\x01\x00\x00\x66\x01\x00\x00\x04\x05\x00\x00\x70\x01\x00\x00\x72\x01\x00\x00\x7e\x05\x00\x00\xef\x00\x00\x00\x67\x01\x00\x00\x7d\x05\x00\x00\x03\x05\x00\x00\x7f\x05\x00\x00\xd6\x00\x00\x00\x7f\x01\x00\x00\xbc\x04\x00\x00\xe2\x04\x00\x00\xf6\x05\x00\x00\x73\x01\x00\x00\xbd\x09\x00\x00\xd8\x01\x00\x00\xa1\x01\x00\x00\xab\x04\x00\x00\x3d\x13\x00\x00\xfe\x05\x00\x00\x86\x13\x00\x00\x78\x06\x00\x00\x6b\x07\x00\x00\x9d\x13\x00\x00\xd4\x13\x00\x00\x63\x09\x00\x00\x8d\x03\x00\x00\xfb\x13\x00\x00\xc9\x01\x00\x00\x96\x00\x00\x00\x9b\x00\x00\x00\x9e\x00\x00\x00\x57\x01\x00\x00\x5d\x02\x00\x00\xa4\x00\x00\x00\xa5\x00\x00\x00\x69\x02\x00\x00\xd2\x00\x00\x00\x01\x01\x00\x00\x02\x01\x00\x00\x56\x14\x00\x00\x9b\x08\x00\x00\x9b\x0c\x00\x00\xce\x14\x00\x00\x4c\x15\x00\x00\xca\x15\x00\x00\x44\x16\x00\x00\xbc\x16\x00\x00\x0b\x17\x00\x00\x95\x03\x00\x00\x32\x17\x00\x00\x8d\x17\x00\x00\x06\x0d\x00\x00\x05\x18\x00\x00\x6c\x02\x00\x00\x3c\x01\x00\x00\xce\x02\x00\x00\x3d\x01\x00\x00\xf2\x03\x00\x00\x68\x02\x00\x00\x5a\x01\x00\x00\x80\x03\x00\x00\x5c\x01\x00\x00\x5d\x01\x00\x00\x43\x0d\x00\x00\x7a\x18\x00\x00\xaa\x18\x00\x00\x7d\x02\x00\x00\x70\x06\x00\x00\xf8\x05\x00\x00\x99\x02\x00\x00\xfb\x05\x00\x00\x71\x06\x00\x00\xe3\x04\x00\x00\xe6\x04\x00\x00\x7b\x02\x00\x00\x72\x06\x00\x00\xd9\x05\x00\x00\x4f\x06\x00\x00\xd9\x02\x00\x00\xc0\x01\x00\x00\xd5\x01\x00\x00\x02\x03\x00\x00\xf7\x03\x00\x00\xd0\x01\x00\x00\xd1\x01\x00\x00\x6e\x02\x00\x00\xdb\x01\x00\x00\xcc\x01\x00\x00\xca\x01\x00\x00\x21\x0e\x00\x00\x09\x19\x00\x00\x87\x19\x00\x00\x2d\x03\x00\x00\x5c\x02\x00\x00\x9b\x06\x00\x00\x00\x00\x00\x00\x82\x02\x00\x00\x05\x1a\x00\x00\x7f\x1a\x00\x00\x00\x00\x00\x00\xbf\x1a\x00\x00\x3d\x1b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x86\x02\x00\x00\xbb\x1b\x00\x00\x39\x1c\x00\x00\x54\x02\x00\x00\x8b\x02\x00\x00\x76\x04\x00\x00\x92\x02\x00\x00\xf2\x02\x00\x00\x7e\x04\x00\x00\xcf\x02\x00\x00\x00\x04\x00\x00\x9b\x02\x00\x00\x1c\x04\x00\x00\xb7\x1c\x00\x00\x0b\x03\x00\x00\x5b\x05\x00\x00\x5c\x05\x00\x00\xf9\x05\x00\x00\x60\x05\x00\x00\x64\x07\x00\x00\xfe\x09\x00\x00\x0c\x03\x00\x00\x48\x05\x00\x00\x0e\x07\x00\x00\x4b\x0f\x00\x00\x31\x1d\x00\x00\xa9\x1d\x00\x00\x27\x1e\x00\x00\xc1\x05\x00\x00\xa5\x1e\x00\x00\x23\x1f\x00\x00\x0e\x12\x00\x00\xc0\x02\x00\x00\xe0\x02\x00\x00\x07\x03\x00\x00\x03\x04\x00\x00\x00\x03\x00\x00\x03\x03\x00\x00\x83\x04\x00\x00\x85\x04\x00\x00\x0d\x03\x00\x00\x78\x03\x00\x00\x77\x04\x00\x00\x45\x18\x00\x00\x7e\x07\x00\x00\x72\x1f\x00\x00\xb9\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x02\x20\x00\x00\x00\x00\x00\x00\x7a\x20\x00\x00\x28\x12\x00\x00\xf4\x20\x00\x00\xad\x03\x00\x00\xaa\x03\x00\x00\x7f\x03\x00\x00\xed\x03\x00\x00\xf9\x04\x00\x00\xfd\x03\x00\x00\x8b\x04\x00\x00\x45\x08\x00\x00\x04\x04\x00\x00\x85\x05\x00\x00\x0e\x04\x00\x00\x07\x06\x00\x00\x00\x00\x00\x00\x2f\x04\x00\x00\x00\x00\x00\x00\xb7\x04\x00\x00\x5a\x21\x00\x00\x00\x00\x00\x00\x94\x04\x00\x00\x00\x00\x00\x00\xad\x04\x00\x00\x00\x00\x00\x00\xb8\x04\x00\x00\x00\x00\x00\x00\xc8\x04\x00\x00\xd8\x21\x00\x00\x52\x22\x00\x00\xcc\x22\x00\x00\x46\x23\x00\x00\xc0\x23\x00\x00\x3a\x24\x00\x00\xb4\x24\x00\x00\x2e\x25\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa8\x25\x00\x00\x22\x26\x00\x00\x9c\x26\x00\x00\x16\x27\x00\x00\x90\x27\x00\x00\x0a\x28\x00\x00\x84\x28\x00\x00\xfe\x28\x00\x00\xc1\x13\x00\x00\x56\x29\x00\x00\xf7\x07\x00\x00\x97\x29\x00\x00\x9b\x0a\x00\x00\xb1\x21\x00\x00\xd8\x29\x00\x00\x65\x1a\x00\x00\x1c\x2a\x00\x00\x6b\x09\x00\x00\x5d\x2a\x00\x00\xc2\x07\x00\x00\x73\x06\x00\x00\x65\x07\x00\x00\x19\x06\x00\x00\xb3\x05\x00\x00\xe5\x04\x00\x00\xca\x04\x00\x00\x67\x07\x00\x00\x9f\x05\x00\x00\x91\x08\x00\x00\xde\x07\x00\x00\x1d\x06\x00\x00\xae\x2a\x00\x00\x23\x2b\x00\x00\x2b\x22\x00\x00\x54\x0e\x00\x00\xf9\x12\x00\x00\xfd\x12\x00\x00\x19\x0b\x00\x00\xa5\x22\x00\x00\x53\x2b\x00\x00\x70\x1a\x00\x00\x97\x0b\x00\x00\x4b\x0d\x00\x00\x21\x23\x00\x00\x1b\x13\x00\x00\x9b\x23\x00\x00\xf4\x0f\x00\x00\x97\x1f\x00\x00\xe7\x0d\x00\x00\x34\x14\x00\x00\x77\x10\x00\x00\x97\x2b\x00\x00\xd8\x2b\x00\x00\xb0\x0c\x00\x00\xc2\x09\x00\x00\x79\x08\x00\x00\x8b\x07\x00\x00\xf1\x2b\x00\x00\x12\x2c\x00\x00\x5b\x2c\x00\x00\x9c\x2c\x00\x00\x96\x0f\x00\x00\x02\x0f\x00\x00\x88\x08\x00\x00\x03\x08\x00\x00\xb5\x2c\x00\x00\xd6\x2c\x00\x00\x19\x2d\x00\x00\x3c\x2d\x00\x00\x98\x2d\x00\x00\xc0\x2d\x00\x00\xe3\x2d\x00\x00\xcb\x04\x00\x00\xce\x04\x00\x00\x20\x05\x00\x00\x22\x05\x00\x00\x26\x05\x00\x00\x30\x05\x00\x00\x23\x2e\x00\x00\x9d\x2e\x00\x00\x17\x2f\x00\x00\x91\x2f\x00\x00\x0b\x30\x00\x00\x85\x30\x00\x00\xff\x30\x00\x00\x79\x31\x00\x00\xf3\x31\x00\x00\x6d\x32\x00\x00\xa7\x32\x00\x00\x21\x33\x00\x00\x9b\x33\x00\x00\x15\x34\x00\x00\x8f\x34\x00\x00\x09\x35\x00\x00\x83\x35\x00\x00\xfd\x35\x00\x00\x77\x36\x00\x00\xf1\x36\x00\x00\x6b\x37\x00\x00\xe5\x37\x00\x00\x5f\x38\x00\x00\x00\x00\x00\x00\x21\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd9\x38\x00\x00\x00\x00\x00\x00\xac\x05\x00\x00\x00\x00\x00\x00\x57\x39\x00\x00\x01\x05\x00\x00\x08\x05\x00\x00\x3d\x09\x00\x00\x0f\x05\x00\x00\x8a\x05\x00\x00\x99\x08\x00\x00\x24\x05\x00\x00\x75\x06\x00\x00\x28\x05\x00\x00\xa2\x06\x00\x00\xd5\x39\x00\x00\x4f\x3a\x00\x00\x00\x00\x00\x00\xa9\x3a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe9\x3a\x00\x00\x00\x00\x00\x00\x65\x3b\x00\x00\xe1\x3b\x00\x00\x00\x00\x00\x00\x5d\x3c\x00\x00\x00\x00\x00\x00\xd9\x3c\x00\x00\x00\x00\x00\x00\x55\x3d\x00\x00\x00\x00\x00\x00\xeb\x04\x00\x00\x00\x00\x00\x00\xaf\x3d\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x45\x05\x00\x00\x0e\x3e\x00\x00\x00\x00\x00\x00\x18\x0c\x00\x00\x8c\x3e\x00\x00\x39\x0f\x00\x00\x00\x00\x00\x00\x5e\x05\x00\x00\x59\x05\x00\x00\x6a\x05\x00\x00\x74\x05\x00\x00\xe6\x3e\x00\x00\x67\x05\x00\x00\x0f\x06\x00\x00\x26\x3f\x00\x00\xa0\x3f\x00\x00\x00\x00\x00\x00\xc0\x05\x00\x00\x14\x06\x00\x00\x7b\x2d\x00\x00\xc5\x0e\x00\x00\x22\x16\x00\x00\x00\x00\x00\x00\xc5\x05\x00\x00\x2d\x06\x00\x00\x9e\x07\x00\x00\x1a\x40\x00\x00\x98\x40\x00\x00\xf1\x08\x00\x00\x6b\x17\x00\x00"#

alex_table :: AlexAddr
alex_table = AlexA#
  "\x00\x00\xff\xff\xb4\x01\x60\x00\xff\xff\xaa\x01\x27\x01\x50\x00\x1c\x00\xff\x01\x02\x01\x23\x00\x27\x01\x27\x01\x27\x01\x2a\x00\x2b\x00\x2d\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x47\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x27\x01\xaa\x01\x51\x01\xd5\x01\xaa\x01\xaa\x01\xaa\x01\x08\x01\xd7\x01\xd2\x01\xaa\x01\xaa\x01\xcf\x01\xab\x01\xaa\x01\xaa\x01\xa8\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa9\x01\xce\x01\xaa\x01\xaa\x01\xaa\x01\x3b\x00\xaa\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\x36\x00\xaa\x01\xd0\x01\xaa\x01\xb7\x01\xcd\x01\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\xcc\x01\xe7\x01\xcb\x01\xaa\x01\x27\x01\x52\x00\xd9\x01\xd9\x01\x02\x01\x4e\x00\x27\x01\x27\x01\x27\x01\x27\x01\x52\x00\xff\xff\xff\xff\x02\x01\x40\x00\x27\x01\x27\x01\x27\x01\xd9\x01\xd9\x01\xdd\x01\xd9\x01\x41\x00\xd9\x01\xd9\x01\x48\x00\x4b\x00\x28\x00\xd9\x01\x4c\x00\x49\x00\xd9\x01\x2c\x00\x4d\x00\xff\xff\x5d\x00\x27\x01\x27\x01\x52\x00\xd9\x01\x5c\x00\x02\x01\x26\x00\x27\x01\x27\x01\x27\x01\xff\x00\x5a\x00\xff\xff\x5c\x00\xff\xff\xff\xff\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\xff\xff\xff\xff\x27\x01\x27\x01\x52\x00\x04\x02\xff\xff\x02\x01\x26\x00\x27\x01\x27\x01\x27\x01\x27\x01\x52\x00\xff\xff\x5c\x00\x02\x01\x26\x00\x27\x01\x27\x01\x27\x01\x27\x01\x52\x00\xff\xff\xff\xff\x02\x01\x42\x01\x27\x01\x27\x01\x27\x01\x27\x01\xff\xff\xff\xff\x04\x02\xff\xff\x42\x01\xff\xff\xfd\x01\x42\x01\x27\x01\x1d\x00\xfc\x01\x04\x02\x5c\x00\x87\x00\x4a\x00\x87\x00\xfc\x01\x27\x01\x2e\x00\x42\x01\x42\x01\x5c\x00\x42\x01\xff\xff\x87\x00\x00\x01\x87\x00\xff\xff\xff\xff\xff\xff\x5c\x00\x27\x01\x52\x00\xff\xff\x00\x01\x02\x01\x0f\x00\x27\x01\x27\x01\x27\x01\xff\xff\xff\xff\x0f\x00\x0f\x00\x0f\x00\x0f\x00\x51\x00\x69\x00\x87\x00\x10\x00\xff\xff\x0f\x00\x0f\x00\x0f\x00\xff\xff\x8c\x00\x46\x01\x87\x00\x27\x01\x27\x01\x87\x00\x8c\x00\x27\x00\x0f\x00\x87\x00\x27\x01\x27\x01\x27\x01\xfc\x01\x87\x00\x87\x00\x5c\x00\x0f\x00\x87\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x76\x00\x0e\x00\x27\x01\x27\x01\x52\x00\x29\x00\x27\x00\x02\x01\x68\x00\x27\x01\x27\x01\x27\x01\xff\xff\x15\x00\xfc\x01\x27\x00\x24\x00\x87\x00\xcd\x00\x15\x00\x15\x00\x15\x00\x87\x00\xff\xff\x00\x01\x76\x00\xff\xff\x87\x00\xff\xff\x8c\x00\x27\x01\x27\x01\x52\x00\xff\xff\xff\xff\x02\x01\x42\x01\x27\x01\x27\x01\x27\x01\x15\x00\x42\x01\x16\x00\x5c\x00\xff\xff\x68\x00\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\xff\xff\xff\xff\x27\x01\x8c\x00\x8b\x00\x12\x02\xff\xff\xff\xff\xff\xff\x00\x01\x8b\x00\x87\x00\x87\x00\x87\x00\x87\x00\x13\x02\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x01\x29\x01\x0d\x00\x82\x00\x29\x01\x68\x00\x87\x00\xff\xff\x87\x00\xb5\x01\xb6\x01\xff\xff\x80\x00\x27\x01\x52\x00\x87\x00\xff\xff\x02\x01\x23\x00\x27\x01\x27\x01\x27\x01\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x89\x00\x42\x01\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x29\x01\x27\x01\x8b\x00\x89\x00\x07\x02\x00\x01\xff\xff\xcd\x00\x29\x01\xd3\x01\xd2\x01\x29\x01\x89\x00\xcf\x01\x5c\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xce\x01\xaf\x00\x13\x00\x89\x00\x8b\x00\x00\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xd1\x01\xff\xff\xd0\x01\xcd\x00\xb6\x01\xcd\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\x1b\x00\x0d\x01\xcb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x04\x01\x4f\x00\x0d\x01\x42\x01\x02\x01\xce\x00\x27\x01\xcf\x00\xcf\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x0d\x01\x0d\x01\xcd\x00\x11\x01\x0d\x01\x0d\x01\x42\x01\x0d\x01\x04\x01\x0d\x01\x0b\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0c\x01\x0d\x01\x0d\x01\x0d\x01\x20\x00\x20\x00\x20\x00\xff\xff\x12\x00\xff\xff\x20\x00\xff\x01\x46\x00\x21\x00\x12\x00\x12\x00\x12\x00\x46\x00\x46\x00\x46\x00\x46\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x29\x01\x29\x01\x29\x01\x29\x01\x12\x00\xc4\x00\xff\xff\xff\xff\x46\x00\x84\x00\x0d\x01\x0a\x01\xde\x00\xc5\x00\x3f\x01\x84\x00\x84\x00\x84\x00\xf7\x00\x42\x01\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x42\x01\xff\xff\x30\x01\x1d\x01\xfd\x00\x0d\x01\x84\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x0d\x01\x0d\x01\x0d\x01\xfd\x00\x20\x00\xd9\x01\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x15\x00\x85\x01\xff\xff\x87\x00\x74\x00\x6c\x00\x15\x00\x15\x00\x15\x00\x81\x00\x64\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\xd8\x00\xff\xff\x30\x01\x0d\x01\xff\xff\xff\xff\x15\x00\x29\x01\xff\xff\xdb\x00\x0d\x01\x98\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x14\x00\x0d\x01\x98\x01\x11\x01\x29\x01\x92\x00\x77\x00\xff\xff\x16\x00\x16\x00\x16\x00\x16\x00\x98\x01\x16\x00\x16\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xf6\x00\x0d\x01\x7e\x01\xde\x00\x8d\x00\x7a\x00\x7e\x01\x29\x01\x29\x01\x12\x00\xfd\x00\x98\x01\x29\x01\x8f\x00\x0d\x01\x13\x00\x16\x00\x16\x00\x17\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x29\x01\x16\x00\x16\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x29\x01\xe0\x00\x2c\x01\x3d\x01\x41\x01\x42\x01\xd9\x00\x35\x01\x16\x00\x16\x00\x17\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x16\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x18\x00\x29\x01\xf6\x00\xce\x00\x42\x01\xce\x00\xce\x00\x29\x01\x29\x01\x17\x01\x2f\x01\xf6\x00\x2b\x01\x34\x01\x42\x01\x42\x01\x0d\x01\x2f\x01\x14\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x42\x01\x4d\x01\x0d\x01\x0d\x01\x29\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x18\x00\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x1a\x00\x1a\x00\x1a\x00\xff\xff\x19\x00\x52\x01\x1a\x00\x29\x01\x86\x00\x19\x00\x19\x00\x19\x00\x19\x00\xfc\x00\x86\x00\x86\x00\x86\x00\x0d\x01\x0f\x01\xfa\x00\xff\xff\x0d\x01\x30\x01\x16\x01\xf1\x00\x29\x01\x46\x01\x0d\x01\x0d\x01\x29\x01\x54\x01\x19\x00\xfb\x00\xf2\x00\xff\xff\x86\x00\x29\x01\xf7\x00\x29\x01\x4f\x01\x4d\x01\x56\x01\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xc4\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x58\x01\xff\xff\xff\xff\xae\x01\xff\xff\xff\xff\xb1\x01\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\xff\xff\xff\xff\xff\xff\xcd\x00\x1a\x00\x87\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\xfd\x00\x09\x02\x89\x00\x1a\x00\xcd\x00\xfd\x00\x09\x02\x09\x02\x09\x02\x09\x02\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\xaf\x01\xaf\x00\xb1\x01\x42\x01\x44\x01\xc8\x00\xb2\x01\xcd\x00\x09\x02\x4b\x01\xbe\x00\x01\x01\x89\x00\x94\x00\x7a\x01\xff\xff\xb3\x01\xd9\x01\x8e\x00\x83\x01\xcd\x00\xa2\x00\xd9\x01\xd9\x01\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\xff\xff\xff\xff\xf4\x01\x99\x00\xd9\x01\xff\xff\xd9\x01\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x1a\x00\xfd\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1f\x00\x1f\x00\x1f\x00\xff\xff\x1e\x00\xfd\x00\x1f\x00\xfd\x00\xfd\x00\x1e\x00\x1e\x00\x1e\x00\x1e\x00\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\xff\xff\xcd\x00\xa3\x00\xb3\x00\xf9\x01\xa2\x00\x25\x00\xa2\x00\x1e\x00\x27\x01\x01\x02\x4c\x01\xb1\x00\xc4\x00\xdd\x01\x27\x01\x27\x01\x27\x01\xd6\x01\xcd\x00\x49\x01\xcd\x00\x02\x02\xcd\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x40\x00\x03\x02\x27\x01\x9d\x00\xff\xff\x00\x02\x89\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\xff\xff\x89\x00\xff\xff\xff\xff\x1f\x00\xff\xff\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\xff\xff\x1e\x00\x41\x01\x1f\x00\xff\xff\xe8\x01\x1e\x00\x1e\x00\x1e\x00\x1e\x00\xfd\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\x42\x01\x42\x01\x42\x01\x42\x01\x06\x02\x0a\x02\xfd\x00\x1e\x00\xeb\x00\x0b\x02\x10\x02\xcd\x00\xad\x00\xa5\x00\xfd\x00\x1b\x01\xef\x00\xb2\x00\x9e\x00\xfd\x00\x21\x01\xe6\x00\xfd\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\xff\xff\x11\x02\x00\x00\x92\x00\xb8\x00\x00\x00\x89\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x1f\x00\x00\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x00\x00\x09\x02\x41\x01\x1f\x00\x00\x00\x00\x00\x09\x02\x09\x02\x09\x02\x09\x02\xfd\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\x00\x00\x00\x00\xfd\x00\xec\x00\x22\x01\x00\x00\xeb\x00\x00\x00\xe3\x01\x09\x02\x40\x00\xfd\x01\x00\x00\x20\x01\xfe\x01\xfc\x01\x00\x00\xe0\x01\x00\x00\x00\x00\xfd\x00\xfc\x01\x00\x00\x89\x00\xfd\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xbb\x00\x00\x00\x00\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x00\xfc\x01\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x1f\x00\x20\x00\x20\x00\x20\x00\xfc\x01\xff\xff\x00\x00\x20\x00\x00\x00\x00\x00\xff\xff\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\xff\xff\xff\xff\x00\x00\xff\xff\x20\x00\x00\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x20\x00\x22\x00\x22\x00\x22\x00\x00\x00\x21\x00\x00\x00\x22\x00\x00\x00\x00\x00\x21\x00\x21\x00\x21\x00\x21\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\x1d\x01\x7d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7e\x01\x21\x00\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x00\x00\x89\x00\x00\x00\xeb\x00\x89\x00\x9d\x01\x9d\x01\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x00\x00\x00\x00\x00\x00\xb8\x00\x5d\x00\xff\xff\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\xff\xff\x00\x00\x9e\x01\x00\x00\x22\x00\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x00\x00\x00\x00\x00\x00\x22\x00\x00\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x89\x00\x10\x02\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x6e\x01\x00\x00\x00\x00\xa5\x01\xa5\x01\x00\x00\x89\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xff\xff\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\xa6\x01\x00\x00\x00\x00\x00\x00\x22\x00\x00\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x22\x00\x46\x00\x00\x00\x00\x00\x00\x00\x87\x00\x46\x00\x46\x00\x46\x00\x46\x00\x00\x00\x87\x00\x87\x00\x42\x01\x00\x00\x00\x00\x6d\x00\x65\x00\x00\x00\xc2\x00\x42\x01\x69\x00\x00\x00\x00\x00\xc9\x00\xbf\x00\xff\xff\x68\x01\x46\x00\xc5\x00\xd9\x01\xcb\x00\x00\x00\x00\x00\xd9\x01\xd9\x01\xfc\x00\xcb\x00\xcb\x00\xcb\x00\x9d\x01\x9d\x01\x6c\x01\x00\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x00\x00\xa5\x01\xa5\x01\x00\x00\xcb\x00\x00\x00\x00\x00\x43\x00\x3f\x00\x42\x00\xe1\x01\xdc\x01\x3e\x00\xda\x01\x44\x00\x00\x00\x00\x00\x00\x00\x3d\x00\x00\x00\xde\x01\x00\x00\x00\x00\x00\x00\xda\x01\xdf\x01\x00\x00\xda\x01\x44\x00\x35\x00\x35\x00\x35\x00\x89\x00\x9e\x01\xd9\x01\x35\x00\x39\x00\x00\x00\x00\x00\xd9\x01\xd9\x01\x00\x00\x00\x00\xd9\x01\xd9\x01\x89\x00\x00\x00\x00\x00\xa6\x01\xd9\x01\xd9\x01\x00\x00\xd9\x01\x38\x00\x45\x00\x3c\x00\xd9\x01\x00\x00\xd9\x01\x41\x00\xd9\x01\x00\x00\x34\x00\x16\x02\xcd\x00\x00\x00\x00\x00\x35\x00\x00\x00\x16\x02\x16\x02\x16\x02\x00\x00\x00\x00\x37\x00\x00\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x00\x00\x35\x00\xec\x01\x00\x00\x16\x02\x00\x00\x15\x02\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x00\x00\x00\x00\x00\x00\x00\x00\x35\x00\x00\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\xea\x01\x00\x00\x00\x00\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xf1\x01\xed\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xf3\x01\xec\x01\xec\x01\xec\x01\xef\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\xfa\x01\xd9\x01\xdb\x01\x44\x00\x00\x00\x00\x00\x00\x00\xe2\x01\x3a\x00\x00\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\xb7\x00\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x00\x00\x00\x00\x00\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\x35\x00\xbb\x00\xe5\x01\xff\xff\xaa\x01\xea\x01\xff\xff\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\x00\x00\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x89\x00\x00\x00\x00\x00\xcd\x00\x00\x00\xff\xff\x89\x00\x89\x00\x00\x00\xcd\x00\xcd\x00\x79\x01\x84\x01\x00\x00\xa6\x00\x9f\x00\x7d\x01\x00\x00\x00\x00\xa3\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xe5\x01\x9c\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfd\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xf0\x00\xe5\x00\x00\x00\x00\x00\x00\x00\xec\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x70\x01\xce\x00\x70\x01\xd7\x00\xd7\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\x00\x00\x00\x00\xfd\x00\xfd\x00\x00\x00\xfd\x00\x8a\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x8a\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x24\x01\xfd\x00\x8a\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x8a\x00\xfd\x00\xfd\x00\xcd\x00\xcd\x00\xcd\x00\x0d\x01\xcd\x00\xcd\x00\xcd\x00\x00\x00\x77\x01\xce\x00\x77\x01\x3e\x01\x3e\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x53\x00\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xcd\x00\xcd\x00\xcd\x00\x0d\x01\x0d\x01\xcd\x00\x57\x00\x0d\x01\x0d\x01\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x0d\x01\xcd\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xd0\x00\xcd\x00\x0d\x01\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x0d\x01\xcd\x00\x0d\x01\x87\x00\x87\x00\x87\x00\x0d\x01\x87\x00\x87\x00\x87\x00\x00\x00\x00\x00\xce\x00\x00\x00\x85\x01\x85\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x87\x00\x87\x00\x87\x00\x0d\x01\x0d\x01\x87\x00\x57\x00\x0d\x01\x0d\x01\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x0d\x01\x87\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\xd0\x00\x87\x00\x0d\x01\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x0d\x01\x87\x00\x0d\x01\xaa\x01\x59\x01\x00\x00\x00\x00\xfc\x01\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\xfc\x01\x00\x00\x00\x00\x00\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x79\x00\x00\x00\x00\x00\x00\x00\x00\x00\x55\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x98\x01\x00\x00\x00\x00\xaa\x01\xaa\x01\xaa\x01\x59\x00\xaa\x01\xaa\x01\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x77\x00\xfc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x98\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\x00\x00\x59\x00\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\x00\x00\xfc\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xcc\x00\x00\x00\x00\x00\x11\x00\x00\x00\x3f\x01\xcc\x00\xcc\x00\xcc\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xcc\x00\x00\x00\x00\x00\x00\x00\x54\x00\x11\x00\x00\x00\x11\x00\x11\x00\x11\x00\x11\x00\x00\x00\x00\x00\x00\x00\x11\x00\x11\x00\x11\x00\x5b\x00\x11\x00\x11\x00\x00\x00\x00\x00\xff\xff\x00\x00\x67\x01\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x11\x00\xaa\x01\x11\x00\x11\x00\x11\x00\x11\x00\x11\x00\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x9b\x01\x11\x00\x00\x00\x11\x00\x11\x00\x11\x00\x11\x00\x00\x00\x00\x00\x00\x00\x11\x00\x11\x00\x00\x00\x5b\x00\x11\x00\x11\x00\x3e\x01\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x11\x00\x11\x00\x11\x00\x11\x00\x11\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\x00\x00\xff\xff\x9c\x01\x3f\x01\xd6\x00\xd6\x00\xd6\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x11\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\x00\x00\x11\x00\xd6\x00\x00\x00\x00\x00\x00\x00\x55\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\x5e\x00\xff\xff\xff\xff\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x11\x00\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x5e\x00\xff\xff\xff\xff\xd7\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\xff\xff\x00\x00\x00\x00\xff\xff\xff\xff\x00\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x00\x00\xff\xff\x00\x00\xff\xff\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\xff\xff\x60\x00\xff\xff\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x00\x00\x90\x01\xb1\x01\x00\x00\x00\x00\xff\xff\x60\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x00\x00\x94\x01\x00\x00\x00\x00\xb1\x01\xfc\x00\x00\x00\x00\x00\x60\x00\x00\x00\xfc\x00\xfc\x00\xfc\x00\xfc\x00\x00\x00\x00\x00\x00\x00\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\x7b\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\x94\x01\x60\x00\x60\x00\x60\x00\x60\x00\xbb\x01\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\xff\xff\xff\xff\x00\x00\x00\x00\x61\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\xbb\x01\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\xbc\x01\xc2\x01\x00\x00\xad\x01\x00\x00\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x02\x00\x00\x00\x00\x94\x01\x00\x00\x0e\x02\x0e\x02\x0e\x02\x0e\x02\xad\x01\x00\x00\xad\x01\xad\x01\xad\x01\xad\x01\x00\x00\x00\x00\x00\x00\xad\x01\xad\x01\x00\x00\xad\x01\xad\x01\xad\x01\x00\x00\x00\x00\x00\x00\x0e\x02\x00\x00\x7e\x00\x0c\x02\x00\x00\x00\x00\x00\x00\xac\x01\x94\x01\xad\x01\xad\x01\xad\x01\xad\x01\xad\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\x00\x00\xad\x01\x00\x00\xad\x01\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc3\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc4\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x57\x01\xad\x01\x00\x00\xad\x01\x00\x00\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x7d\x00\x00\x00\x84\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x01\x84\x00\x84\x00\x84\x00\x00\x00\x94\x01\x23\x01\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\x23\x01\x23\x01\x23\x01\xfd\x01\x00\x00\x00\x00\x21\x00\xfc\x01\x00\x00\x00\x00\x84\x00\xa4\x01\x87\x00\xfc\x01\x00\x00\x00\x00\x87\x00\x87\x00\x00\x00\x7b\x00\x00\x00\x23\x01\x00\x00\x00\x00\x00\x00\x94\x01\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x00\x70\x00\x6a\x00\x6e\x00\x75\x00\x67\x00\x73\x00\x6c\x00\x00\x00\x00\x00\x00\x00\x66\x00\x00\x00\x6f\x00\x00\x00\x00\x00\x00\x00\x73\x00\x7f\x00\x00\x00\x73\x00\x6c\x00\xfc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x63\x00\x00\x00\x00\x00\x87\x00\x87\x00\x86\x00\x00\x00\x00\x00\x87\x00\xfd\x00\xfc\x00\x86\x00\x86\x00\x86\x00\x00\x00\x00\x00\x87\x00\x62\x00\x00\x00\x00\x00\x87\x00\x00\x00\x87\x00\xfc\x01\x87\x00\x00\x00\x5f\x00\x6b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x86\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x87\x00\x87\x00\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\xa3\x01\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x00\x70\x00\x6a\x00\x6e\x00\x75\x00\x67\x00\x73\x00\x6c\x00\x00\x00\x00\x00\x00\x00\x66\x00\x00\x00\x6f\x00\x00\x00\x00\x00\x00\x00\x73\x00\x7f\x00\x00\x00\x73\x00\x6c\x00\xa4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x63\x00\x00\x00\x00\x00\x87\x00\x87\x00\x00\x00\x00\x00\x00\x00\x87\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x62\x00\x00\x00\x00\x00\x87\x00\x00\x00\x87\x00\x00\x00\x87\x00\x00\x00\x5f\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x8f\x01\xce\x00\x8f\x01\x85\x01\x85\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x87\x00\x87\x00\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x85\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x88\x00\xce\x00\x00\x00\x88\x00\x88\x00\x96\x01\x00\x00\x96\x01\x00\x00\x00\x00\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x00\x00\x00\x00\x00\x00\x88\x00\x89\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x97\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\xce\x00\x00\x00\x88\x00\x88\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x98\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\xce\x00\x00\x00\x88\x00\x88\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x98\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x8a\x01\x00\x00\x00\x00\x00\x00\x2a\x01\x3f\x01\x8a\x01\x8a\x01\x8a\x01\x2a\x01\x2a\x01\x2a\x01\x2a\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\x8a\x01\x00\x00\x89\x00\x3f\x01\x2a\x01\x00\x00\x89\x00\x89\x00\x3f\x01\x3f\x01\x3f\x01\x3f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x01\x00\x00\x00\x00\x7c\x01\x80\x01\x7b\x01\x96\x00\x93\x00\x82\x01\x95\x00\x7a\x01\x00\x00\x00\x00\x00\x00\x81\x01\x00\x00\x91\x00\x00\x00\x00\x00\x00\x00\x95\x00\x90\x00\x00\x00\x95\x00\x7a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x00\x00\x86\x01\x00\x00\x29\x01\x89\x00\x89\x00\x89\x01\x00\x00\x00\x00\x89\x00\x00\x00\xfc\x00\x89\x01\x89\x01\x89\x01\x00\x00\x00\x00\x89\x00\x88\x01\x00\x00\x00\x00\x89\x00\x00\x00\x89\x00\x00\x00\x89\x00\x00\x00\x87\x01\x00\x00\xce\x00\x00\x00\x00\x00\x00\x00\x89\x01\x00\x00\x89\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7c\x01\x80\x01\x7b\x01\x96\x00\x93\x00\x82\x01\x95\x00\x7a\x01\x00\x00\x00\x00\x00\x00\x81\x01\x00\x00\x91\x00\x00\x00\x00\x00\x00\x00\x95\x00\x90\x00\xff\xff\x95\x00\x7a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x00\x00\x86\x01\x00\x00\x00\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x88\x01\x00\x00\x00\x00\x89\x00\x00\x00\x89\x00\x00\x00\x89\x00\x00\x00\x87\x01\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x01\x00\x00\x00\x00\x00\x00\x8a\x01\xfc\x00\x89\x01\x89\x01\x89\x01\x3f\x01\x8a\x01\x8a\x01\x8a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x89\x01\x00\x00\x00\x00\x00\x00\x8a\x01\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcc\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x01\xcc\x00\xcc\x00\xcc\x00\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x89\x00\x00\x00\x00\x00\x00\x00\x88\x00\x00\x00\x00\x00\x00\x00\xcc\x00\x00\x00\xcd\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x92\x01\x00\x00\x00\x00\x00\x00\xab\x00\xa9\x00\xa4\x00\xa7\x00\xae\x00\xa1\x00\xac\x00\xa5\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\xa8\x00\x00\x00\x00\x00\x00\x00\xac\x00\xb0\x00\x00\x00\xac\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x00\x00\x9c\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x9b\x00\x41\x01\x00\x00\xcd\x00\x00\x00\xcd\x00\x00\x00\xcd\x00\x00\x00\x9a\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x53\x01\xb9\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x00\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\xb9\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\xb6\x00\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\xcb\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\xcb\x00\xcb\x00\xcb\x00\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcb\x00\x00\x00\xcd\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x97\x01\x00\x00\x00\x00\x00\x00\xab\x00\xa9\x00\xa4\x00\xa7\x00\xae\x00\xa1\x00\xac\x00\xa5\x00\x00\x00\x00\x00\x00\x00\xa0\x00\x00\x00\xa8\x00\x00\x00\x00\x00\x00\x00\xac\x00\xb0\x00\x00\x00\xac\x00\xa5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x00\x00\x9c\x00\x00\x00\x00\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcd\x00\x9b\x00\x00\x00\x00\x00\xcd\x00\x00\x00\xcd\x00\x00\x00\xcd\x00\x00\x00\x9a\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x00\x00\x00\x00\xce\x00\x00\x00\x3e\x01\x3e\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\xcd\x00\xcd\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xca\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\xce\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xce\x00\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x40\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x04\x01\x0d\x01\x0d\x01\x00\x00\xce\x00\xce\x00\x27\x01\xcf\x00\xcf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xcf\x00\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x40\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfc\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\xfc\x00\xfc\x00\xfc\x00\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\x00\x00\x0d\x01\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x0f\x02\x00\x00\x00\x00\x00\x00\xf9\x00\xf5\x00\xf8\x00\x15\x01\x10\x01\xf4\x00\x0e\x01\xfa\x00\x00\x00\x00\x00\x00\x00\xf3\x00\x00\x00\x12\x01\x00\x00\x00\x00\x00\x00\x0e\x01\x13\x01\x00\x00\x0e\x01\xfa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x00\x00\xd4\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\xd3\x00\x00\x00\x00\x00\x0d\x01\x00\x00\x0d\x01\x00\x00\x0d\x01\x00\x00\xd2\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\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\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd6\x00\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x01\xd6\x00\xd6\x00\xd6\x00\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd6\x00\x00\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x17\x02\x00\x00\x00\x00\x00\x00\xed\x00\xe9\x00\xee\x00\xea\x00\x1c\x01\xe7\x00\x1a\x01\xef\x00\x00\x00\x00\x00\x00\x00\xe8\x00\x00\x00\x1e\x01\x00\x00\x00\x00\x00\x00\x1a\x01\x1f\x01\x00\x00\x1a\x01\xef\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\x00\x00\xe4\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xe2\x00\x00\x00\x00\x00\xfd\x00\x00\x00\xfd\x00\x00\x00\xfd\x00\x00\x00\xe3\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\xd7\x00\xce\x00\x00\x00\xd7\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\xd7\x00\xfd\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xd5\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xff\xff\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\xce\x00\x00\x00\xd7\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\xfd\x00\xfd\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x24\x01\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xd1\x00\x0d\x01\x00\x00\x26\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfb\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x04\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x27\x01\xcf\x00\xcf\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x16\x02\x00\x00\x00\x00\x00\x00\x55\x01\x00\x00\x16\x02\x16\x02\x16\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x57\x01\x00\x00\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x75\x01\x16\x02\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x8e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x05\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x06\x01\x06\x01\x06\x01\x06\x01\x99\x00\x06\x01\x06\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x90\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\x17\x02\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x00\x00\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x06\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\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\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x09\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x3c\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x42\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xfe\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x56\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x23\x01\x00\x00\x00\x00\x00\x00\x00\x00\xfc\x00\x23\x01\x23\x01\x23\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\x23\x01\x00\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xed\x00\xe9\x00\xee\x00\xea\x00\x1c\x01\xe7\x00\x1a\x01\xef\x00\x00\x00\x00\x00\x00\x00\xe8\x00\x00\x00\x1e\x01\x00\x00\x00\x00\x00\x00\x1a\x01\x1f\x01\x00\x00\x1a\x01\xef\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\x00\x00\xe4\x00\x00\x00\x00\x00\xfd\x00\xfd\x00\x00\x00\x00\x00\x00\x00\xfd\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfd\x00\xe2\x00\x00\x00\x00\x00\xfd\x00\x00\x00\xfd\x00\x00\x00\xfd\x00\x00\x00\xe3\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x26\x01\x0d\x01\x18\x00\x00\x00\xce\x00\x25\x01\x21\x00\x25\x01\x25\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\x25\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x40\x01\x0d\x01\x0d\x01\x18\x00\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x0d\x01\x26\x01\x0d\x01\x18\x00\x00\x00\x00\x00\x25\x01\x21\x00\x25\x01\x25\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\x26\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x18\x00\x0d\x01\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x18\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x28\x01\x29\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\x29\x01\x29\x01\x4e\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x39\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x28\x01\x29\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\x29\x01\x29\x01\x4e\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x39\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x00\x00\x59\x01\x00\x00\x00\x00\x00\x00\x2a\x01\x3a\x01\x00\x00\x00\x00\x00\x00\x2a\x01\x2a\x01\x2a\x01\x2a\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x95\x01\x00\x00\x00\x00\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x2a\x01\x00\x00\x29\x01\x00\x00\x00\x00\x00\x00\x29\x01\x29\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x00\x00\x00\x00\x00\x00\x97\x01\x00\x00\x00\x00\x00\x00\x2d\x01\x31\x01\x2e\x01\xda\x00\xdf\x00\x32\x01\xe1\x00\x2c\x01\x00\x00\x00\x00\x00\x00\x33\x01\x00\x00\xdd\x00\x3b\x01\x00\x00\x00\x00\xe1\x00\xdc\x00\x00\x00\xe1\x00\x2c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x01\x00\x00\x36\x01\x00\x00\x00\x00\x29\x01\x29\x01\x00\x00\x00\x00\x00\x00\x29\x01\x00\x00\x00\x00\x00\x00\x00\x00\x42\x01\x00\x00\x00\x00\x29\x01\x37\x01\x42\x01\x00\x00\x29\x01\x00\x00\x29\x01\x00\x00\x29\x01\x00\x00\x38\x01\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\xb5\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc7\x00\xc3\x00\xc6\x00\x4a\x01\x45\x01\xc1\x00\x43\x01\xc8\x00\x00\x00\x00\x00\x00\x00\xc0\x00\x00\x00\x47\x01\x00\x00\x00\x00\x00\x00\x43\x01\x48\x01\x00\x00\x43\x01\xc8\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x01\x00\x00\xbd\x00\x00\x00\x00\x00\x42\x01\x42\x01\x00\x00\x00\x00\x00\x00\x42\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x42\x01\xbc\x00\x00\x00\x00\x00\x42\x01\x00\x00\x42\x01\x00\x00\x42\x01\x00\x00\xba\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x00\x00\x3e\x01\xce\x00\x00\x00\x3e\x01\x3e\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\x3e\x01\xcd\x00\x00\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xb4\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\xcd\x00\x3f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x3f\x01\x3f\x01\x3f\x01\x3f\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\x3f\x01\x00\x00\x0d\x01\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf9\x00\xf5\x00\xf8\x00\x15\x01\x10\x01\xf4\x00\x0e\x01\xfa\x00\x00\x00\x00\x00\x00\x00\xf3\x00\x00\x00\x12\x01\x00\x00\x00\x00\x00\x00\x0e\x01\x13\x01\x00\x00\x0e\x01\xfa\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x01\x00\x00\xd4\x00\x00\x00\x00\x00\x0d\x01\x0d\x01\x00\x00\x00\x00\x00\x00\x0d\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x28\x01\x29\x01\x0d\x01\xd3\x00\x00\x00\x00\x00\x0d\x01\x00\x00\x0d\x01\x00\x00\x0d\x01\x00\x00\xd2\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x29\x01\x29\x01\x50\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x39\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x29\x01\x5a\x01\x5a\x01\x5a\x01\x00\x00\x00\x00\x00\x00\x5a\x01\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x00\x00\x00\x00\xff\xff\x00\x00\x5a\x01\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5b\x01\x5b\x01\x5b\x01\x00\x00\x00\x00\x00\x00\x5b\x01\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5c\x01\x5c\x01\x5c\x01\x00\x00\x00\x00\x00\x00\x5c\x01\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5d\x01\x5d\x01\x5d\x01\x00\x00\x00\x00\x00\x00\x5d\x01\x00\x00\x7c\x00\x00\x00\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x94\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x93\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x94\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x00\x00\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5e\x01\x5e\x01\x5e\x01\x00\x00\x00\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x91\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x94\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x93\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x94\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x00\x00\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x5f\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\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x60\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\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x61\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\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x5a\x01\x5a\x01\x5a\x01\x00\x00\x00\x00\x00\x00\x5a\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\x5a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5a\x01\x00\x00\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5a\x01\x5b\x01\x5b\x01\x5b\x01\x00\x00\x00\x00\x00\x00\x5b\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\x5b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5b\x01\x00\x00\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5b\x01\x5c\x01\x5c\x01\x5c\x01\x00\x00\x00\x00\x00\x00\x5c\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\x5c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5c\x01\x00\x00\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5c\x01\x5d\x01\x5d\x01\x5d\x01\x00\x00\x00\x00\x00\x00\x5d\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\x5d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5d\x01\x00\x00\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5d\x01\x5e\x01\x5e\x01\x5e\x01\x00\x00\x00\x00\x00\x00\x5e\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\x62\x01\x00\x00\x00\x00\x00\x00\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5e\x01\x00\x00\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5e\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x5f\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\x63\x01\x00\x00\x00\x00\x00\x00\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x5f\x01\x00\x00\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x5f\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x60\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\x64\x01\x00\x00\x00\x00\x00\x00\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x00\x00\x00\x00\x00\x00\x00\x00\x60\x01\x00\x00\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x60\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x61\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\x65\x01\x00\x00\x00\x00\x00\x00\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x00\x00\x00\x00\x00\x00\x00\x00\x61\x01\x00\x00\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x61\x01\x53\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\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\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\x74\x01\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\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\x71\x01\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\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\x74\x01\x00\x00\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x6f\x01\x55\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x01\x00\x00\x00\x00\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\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\x8d\x01\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x01\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x00\x00\x85\x01\xce\x00\x00\x00\x85\x01\x85\x01\x78\x01\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x01\x85\x01\x87\x00\x00\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x83\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\x00\x87\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x89\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\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\x8d\x01\x00\x00\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x76\x01\x66\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x01\x00\x00\x73\x01\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\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\x71\x01\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x72\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x00\x00\x69\x01\x00\x00\x00\x00\x00\x00\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x7c\x00\x00\x00\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x69\x01\x94\x01\x9a\x01\x00\x00\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x99\x01\x00\x00\x7c\x00\x00\x00\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x00\x00\x00\x00\x00\x00\x00\x00\x7e\x00\x00\x00\x00\x00\x00\x00\x9e\x01\x00\x00\x94\x01\x94\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x9a\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7e\x00\x00\x00\x00\x00\x9e\x01\x00\x00\x00\x00\x94\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6a\x01\x00\x00\x00\x00\x9c\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8c\x01\x9a\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\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\x78\x01\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x8b\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x00\x00\x6d\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x78\x00\x00\x00\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6d\x01\x98\x01\xa2\x01\x00\x00\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\xa1\x01\x00\x00\x78\x00\x00\x00\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\xa7\x01\x00\x00\x00\x00\x00\x00\x00\x00\x7a\x00\x00\x00\x00\x00\x00\x00\xa6\x01\x00\x00\x98\x01\x98\x01\x00\x00\xa9\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x7a\x00\x00\x00\x00\x00\xa6\x01\x00\x00\xa9\x01\x98\x01\xa9\x01\xa9\x01\xa9\x01\xa9\x01\xaa\x01\x00\x00\x00\x00\xa9\x01\xa9\x01\xa4\x01\xa9\x01\xa9\x01\xa9\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x01\x00\x00\xa9\x01\xa9\x01\xa9\x01\xa9\x01\xa9\x01\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x01\xaa\x01\xa9\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x0e\x02\x00\x00\x00\x00\x00\x00\x00\x00\x0e\x02\x0e\x02\x0e\x02\x0e\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xa9\x01\x00\x00\xa9\x01\xaa\x01\x00\x00\xaa\x01\x0e\x02\xaa\x01\x00\x00\x0c\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x0d\x02\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\xac\x01\x58\x00\xaa\x01\xaa\x01\xa0\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\x9f\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x0f\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xac\x01\x00\x00\xac\x01\xac\x01\xac\x01\xac\x01\xad\x01\x00\x00\x00\x00\xac\x01\xac\x01\x00\x00\xac\x01\xac\x01\xac\x01\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\x92\x01\x00\x00\x00\x00\xac\x01\x00\x00\xac\x01\xac\x01\xac\x01\xac\x01\xac\x01\x00\x00\x00\x00\x00\x00\xad\x01\x00\x00\xad\x01\xad\x01\xad\x01\xad\x01\x00\x00\x00\x00\x00\x00\xad\x01\xad\x01\x00\x00\xad\x01\xad\x01\xad\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xac\x01\xad\x01\xac\x01\xad\x01\xad\x01\xad\x01\xad\x01\xad\x01\xb4\x01\xb4\x01\xb4\x01\x00\x00\x00\x00\x00\x00\xb4\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\xac\x01\x00\x00\xac\x01\xad\x01\x00\x00\xad\x01\x00\x00\x00\x00\x00\x00\x00\x00\xae\x01\x00\x00\x00\x00\x00\x00\xb4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x00\x00\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\x00\x00\x00\x00\xad\x01\x00\x00\xad\x01\x00\x00\x00\x00\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb4\x01\x00\x00\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb4\x01\xb5\x01\xb5\x01\xb5\x01\x00\x00\x00\x00\x00\x00\xb5\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\xb5\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x01\x00\x00\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb5\x01\x00\x00\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb5\x01\xb6\x01\xb6\x01\xb6\x01\x00\x00\x00\x00\x00\x00\xb6\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\xb6\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\x00\x00\x00\x00\x00\x00\x00\x00\xb6\x01\x00\x00\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\xb6\x01\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb1\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb7\x01\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb0\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x01\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb1\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb9\x01\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb1\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x78\x00\x00\x00\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\xba\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\xbb\x01\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\xbb\x01\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xb1\x01\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x00\x00\x00\x00\x96\x01\x00\x00\x96\x01\x00\x00\x00\x00\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\xb8\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x00\x00\x00\x00\x00\x00\x00\x00\x60\x00\x00\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\x60\x00\xbc\x01\xbc\x01\xbc\x01\x00\x00\x00\x00\x00\x00\xbc\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\xb2\x01\x00\x00\x00\x00\x00\x00\xbc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x6b\x00\x00\x00\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbc\x01\x00\x00\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbc\x01\xbd\x01\xbd\x01\xbd\x01\x00\x00\x00\x00\x00\x00\xbd\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\xbd\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbe\x01\x00\x00\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\x00\x00\xbd\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbd\x01\x00\x00\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\xbd\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xc0\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc1\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc9\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xc6\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xca\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc8\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc5\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc7\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\xbf\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\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\x00\x00\x00\x00\x00\x00\x00\x00\xbf\x01\x00\x00\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xbf\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\xc2\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\xb3\x01\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\x00\x00\x00\x00\x00\x00\x00\x00\xc2\x01\x00\x00\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xc2\x01\xe4\x01\xe4\x01\xe4\x01\xaa\x01\x00\x00\x00\x00\xe4\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\xaa\x01\xd9\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xe4\x01\x00\x00\xd4\x01\xaa\x01\xaa\x01\x00\x00\x05\x02\xaa\x01\xaa\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\xe4\x01\x00\x00\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\x00\x00\xaa\x01\x00\x00\xaa\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\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\xd9\x01\xd9\x01\xd8\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\x33\x00\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xd9\x01\xe4\x01\xe4\x01\xe4\x01\x00\x00\x00\x00\x00\x00\xe4\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\xe4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\x00\x00\x00\x00\x00\x00\x00\x00\xe4\x01\x00\x00\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe4\x01\xe5\x01\xe5\x01\xe5\x01\x00\x00\x00\x00\x00\x00\xe5\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\xe5\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xe5\x01\x00\x00\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xe5\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\xe6\x01\xaa\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xea\x01\xea\x01\xea\x01\x00\x00\x00\x00\x00\x00\xea\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\xaa\x01\xf8\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xea\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\x00\x00\x00\x00\xf7\x01\x00\x00\xaa\x01\x00\x00\x00\x00\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\x00\x00\x00\x00\x00\x00\x00\x00\xea\x01\x00\x00\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\xea\x01\x00\x00\xe9\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xec\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\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\xeb\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xec\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\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\xf5\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xec\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\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\xee\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xec\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\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\xf0\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xec\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\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xec\x01\x00\x00\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xec\x01\xaa\x01\xf2\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\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\xaa\x01\xf6\x01\xaa\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x00\x00\x00\x00\xce\x00\x00\x00\xce\x00\xce\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\x0d\x01\x0d\x01\x00\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\xd0\x00\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x0d\x01\x1a\x00\x1a\x00\x1a\x00\x00\x00\x19\x00\x00\x00\x1a\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x00\x00\x00\x00\x00\x00\x00\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x1a\x00\x00\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\x1a\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\xaa\x01\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\x01\xaa\x01\xaa\x01\xaa\x01\xaa\x01\x08\x02\x08\x02\x08\x02\x00\x00\x00\x00\x00\x00\x08\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xaa\x01\x00\x00\xaa\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\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x00\x00\x00\x00\xaa\x01\x00\x02\xaa\x01\x00\x00\x00\x00\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x00\x00\x00\x00\x00\x00\x00\x00\x08\x02\x00\x00\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x00\x00\x09\x02\x00\x00\x08\x02\x00\x00\x00\x00\x09\x02\x09\x02\x09\x02\x09\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x09\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x00\x00\x00\x00\x00\x00\x00\x00\x08\x02\x00\x00\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x08\x02\x15\x02\x15\x02\x15\x02\x15\x02\x00\x00\x15\x02\x15\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x02\x15\x02\x14\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x00\x00\x15\x02\x15\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x15\x02\x15\x02\x14\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x15\x02\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\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\x0a\x00\x01\x00\x02\x00\x0a\x00\x04\x00\x05\x00\x06\x00\x2d\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x21\x00\x0a\x00\x0a\x00\x72\x00\x61\x00\x67\x00\x6d\x00\x61\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x42\x00\x46\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\x42\x00\x4c\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x0a\x00\x0a\x00\x09\x00\x45\x00\x0b\x00\x0c\x00\x0d\x00\x46\x00\x4e\x00\x43\x00\x54\x00\x41\x00\x58\x00\x58\x00\x0a\x00\x69\x00\x20\x00\x53\x00\x6e\x00\x23\x00\x53\x00\x21\x00\x65\x00\x0a\x00\x2d\x00\x20\x00\x05\x00\x06\x00\x52\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x2d\x00\x2d\x00\x0a\x00\x2d\x00\x0a\x00\x0a\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x0a\x00\x0a\x00\x20\x00\x05\x00\x06\x00\x23\x00\x0a\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x0a\x00\x2d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x0a\x00\x0a\x00\x09\x00\x42\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\x0a\x00\x0a\x00\x23\x00\x0a\x00\x46\x00\x0a\x00\x20\x00\x46\x00\x20\x00\x23\x00\x24\x00\x23\x00\x2d\x00\x42\x00\x6c\x00\x46\x00\x2a\x00\x20\x00\x70\x00\x4c\x00\x53\x00\x2d\x00\x4e\x00\x0a\x00\x4c\x00\x7b\x00\x42\x00\x0a\x00\x0a\x00\x0a\x00\x2d\x00\x05\x00\x06\x00\x0a\x00\x7b\x00\x09\x00\x05\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x05\x00\x06\x00\x41\x00\x58\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x24\x00\x43\x00\x54\x00\x20\x00\x05\x00\x46\x00\x2a\x00\x7b\x00\x20\x00\x52\x00\x0b\x00\x0c\x00\x0d\x00\x5e\x00\x4e\x00\x4b\x00\x2d\x00\x20\x00\x53\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x43\x00\x2d\x00\x20\x00\x05\x00\x06\x00\x23\x00\x7b\x00\x09\x00\x45\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x05\x00\x7c\x00\x7b\x00\x7c\x00\x58\x00\x54\x00\x0b\x00\x0c\x00\x0d\x00\x53\x00\x0a\x00\x7b\x00\x41\x00\x0a\x00\x51\x00\x0a\x00\x5e\x00\x20\x00\x05\x00\x06\x00\x0a\x00\x0a\x00\x09\x00\x54\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\x58\x00\x22\x00\x2d\x00\x0a\x00\x55\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x0a\x00\x0a\x00\x20\x00\x7c\x00\x24\x00\x23\x00\x0a\x00\x0a\x00\x0a\x00\x7b\x00\x2a\x00\x31\x00\x32\x00\x33\x00\x34\x00\x2d\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x27\x00\x43\x00\x7b\x00\x43\x00\x45\x00\x45\x00\x43\x00\x0a\x00\x53\x00\x01\x00\x02\x00\x0a\x00\x4c\x00\x05\x00\x06\x00\x45\x00\x0a\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\x4b\x00\x48\x00\x31\x00\x32\x00\x33\x00\x34\x00\x45\x00\x4b\x00\x20\x00\x5e\x00\x43\x00\x23\x00\x7b\x00\x0a\x00\x46\x00\x51\x00\x28\x00\x29\x00\x53\x00\x51\x00\x2c\x00\x2d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x4c\x00\x42\x00\x4b\x00\x58\x00\x4e\x00\x3b\x00\x43\x00\x5f\x00\x53\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\x0a\x00\x5d\x00\x43\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\x42\x00\x7d\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x42\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\x46\x00\x4c\x00\x45\x00\x43\x00\x4e\x00\x54\x00\x58\x00\x58\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\x0a\x00\x05\x00\x0a\x00\x07\x00\x2d\x00\x05\x00\x0a\x00\x0b\x00\x0c\x00\x0d\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\x31\x00\x32\x00\x33\x00\x34\x00\x20\x00\x45\x00\x0a\x00\x22\x00\x20\x00\x05\x00\x53\x00\x22\x00\x41\x00\x41\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x41\x00\x53\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x52\x00\x0a\x00\x55\x00\x43\x00\x42\x00\x52\x00\x20\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\x51\x00\x4b\x00\x43\x00\x46\x00\x5f\x00\x5c\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\x05\x00\x5c\x00\x0a\x00\x4d\x00\x4e\x00\x4f\x00\x0b\x00\x0c\x00\x0d\x00\x53\x00\x54\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x43\x00\x0a\x00\x45\x00\x45\x00\x0a\x00\x0a\x00\x20\x00\x58\x00\x0a\x00\x4c\x00\x42\x00\x45\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x58\x00\x45\x00\x41\x00\x54\x00\x41\x00\x5f\x00\x0a\x00\x01\x00\x02\x00\x03\x00\x04\x00\x65\x00\x06\x00\x07\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x55\x00\x46\x00\x55\x00\x43\x00\x43\x00\x5f\x00\x45\x00\x4e\x00\x4c\x00\x23\x00\x45\x00\x65\x00\x46\x00\x4c\x00\x53\x00\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\x42\x00\x06\x00\x07\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x4d\x00\x4e\x00\x4f\x00\x23\x00\x27\x00\x53\x00\x53\x00\x54\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\x05\x00\x06\x00\x07\x00\x49\x00\x45\x00\x0a\x00\x51\x00\x0c\x00\x0d\x00\x4f\x00\x50\x00\x43\x00\x41\x00\x45\x00\x54\x00\x55\x00\x4b\x00\x45\x00\x53\x00\x59\x00\x4c\x00\x31\x00\x32\x00\x33\x00\x34\x00\x43\x00\x23\x00\x20\x00\x21\x00\x52\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\x0a\x00\x05\x00\x23\x00\x07\x00\x42\x00\x05\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x4d\x00\x4e\x00\x4f\x00\x0a\x00\x49\x00\x45\x00\x53\x00\x54\x00\x46\x00\x41\x00\x4f\x00\x50\x00\x58\x00\x23\x00\x20\x00\x54\x00\x55\x00\x0a\x00\x20\x00\x53\x00\x59\x00\x53\x00\x22\x00\x23\x00\x23\x00\x31\x00\x32\x00\x33\x00\x34\x00\x55\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x23\x00\x0a\x00\x0a\x00\x23\x00\x0a\x00\x0a\x00\x23\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\x0a\x00\x0a\x00\x0a\x00\x53\x00\x5f\x00\x5c\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\x4c\x00\x05\x00\x4c\x00\x07\x00\x51\x00\x4e\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\x23\x00\x41\x00\x23\x00\x4d\x00\x4e\x00\x4f\x00\x23\x00\x46\x00\x20\x00\x53\x00\x54\x00\x2d\x00\x4d\x00\x4e\x00\x4f\x00\x0a\x00\x23\x00\x53\x00\x53\x00\x54\x00\x53\x00\x55\x00\x51\x00\x4b\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x0a\x00\x0a\x00\x7c\x00\x5f\x00\x45\x00\x0a\x00\x43\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\x0a\x00\x0a\x00\x0a\x00\x0a\x00\x5f\x00\x43\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\x0a\x00\x05\x00\x4b\x00\x07\x00\x51\x00\x53\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\x0a\x00\x42\x00\x41\x00\x43\x00\x7c\x00\x45\x00\x65\x00\x45\x00\x20\x00\x05\x00\x6e\x00\x43\x00\x4c\x00\x45\x00\x41\x00\x0b\x00\x0c\x00\x0d\x00\x23\x00\x52\x00\x4c\x00\x53\x00\x69\x00\x58\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x55\x00\x6c\x00\x20\x00\x5f\x00\x0a\x00\x7d\x00\x46\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\x0a\x00\x4e\x00\x0a\x00\x0a\x00\x5f\x00\x0a\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\x0a\x00\x05\x00\x27\x00\x07\x00\x0a\x00\x7c\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x54\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x31\x00\x32\x00\x33\x00\x34\x00\x2d\x00\x7d\x00\x46\x00\x20\x00\x45\x00\x2d\x00\x7d\x00\x4d\x00\x4e\x00\x4f\x00\x4d\x00\x4e\x00\x4f\x00\x53\x00\x54\x00\x53\x00\x53\x00\x54\x00\x53\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x0a\x00\x2d\x00\xff\xff\x43\x00\x5f\x00\xff\xff\x42\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\x0a\x00\x0a\x00\x0a\x00\x0a\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\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\x27\x00\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x58\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\xff\xff\x42\x00\x41\x00\x43\x00\xff\xff\x45\x00\xff\xff\x43\x00\x20\x00\x45\x00\x20\x00\xff\xff\x4c\x00\x23\x00\x24\x00\xff\xff\x4c\x00\xff\xff\xff\xff\x52\x00\x2a\x00\xff\xff\x54\x00\x58\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x31\x00\x32\x00\x33\x00\x34\x00\x5f\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\x5e\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x7c\x00\x0a\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\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\xff\xff\x31\x00\x32\x00\x33\x00\x34\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\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\x0a\x00\x0a\x00\xff\xff\x0a\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\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x41\x00\x41\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x45\x00\x20\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\x52\x00\xff\xff\x55\x00\x53\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\xff\xff\xff\xff\xff\xff\x5f\x00\x2d\x00\x0a\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\x0a\x00\xff\xff\x5f\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x58\x00\x7d\x00\xff\xff\xff\xff\xff\xff\xff\xff\x42\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\x30\x00\x31\x00\xff\xff\x58\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x0a\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\x5f\x00\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x05\x00\xff\xff\xff\xff\xff\xff\x49\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\x4f\x00\x50\x00\x49\x00\xff\xff\xff\xff\x54\x00\x55\x00\xff\xff\x4f\x00\x50\x00\x59\x00\xff\xff\xff\xff\x54\x00\x55\x00\x0a\x00\x23\x00\x20\x00\x59\x00\x22\x00\x05\x00\xff\xff\xff\xff\x26\x00\x27\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\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\x30\x00\x31\x00\xff\xff\x20\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\x01\x00\x02\x00\x03\x00\x46\x00\x5f\x00\x5c\x00\x07\x00\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\x49\x00\x66\x00\x53\x00\xff\xff\xff\xff\x5f\x00\x4f\x00\x50\x00\xff\xff\x6e\x00\x6f\x00\x54\x00\x55\x00\x72\x00\xff\xff\x74\x00\x59\x00\x76\x00\xff\xff\x78\x00\x05\x00\x5c\x00\xff\xff\xff\xff\x27\x00\xff\xff\x0b\x00\x0c\x00\x0d\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\xff\xff\x01\x00\x02\x00\xff\xff\x20\x00\xff\xff\x22\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x01\x00\x02\x00\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\x4d\x00\x4e\x00\x4f\x00\xff\xff\xff\xff\xff\xff\x53\x00\x54\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\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\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5f\x00\x02\x00\x0a\x00\x04\x00\x5f\x00\x0a\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\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\x49\x00\xff\xff\xff\xff\x49\x00\xff\xff\x0a\x00\x4f\x00\x50\x00\xff\xff\x4f\x00\x50\x00\x54\x00\x55\x00\xff\xff\x54\x00\x55\x00\x59\x00\xff\xff\xff\xff\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\x5f\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\xff\xff\x7e\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x49\x00\xff\xff\x0a\x00\xff\xff\x0c\x00\x0d\x00\x4f\x00\x50\x00\xff\xff\xff\xff\xff\xff\x54\x00\x55\x00\xff\xff\xff\xff\xff\xff\x59\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\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\x05\x00\x06\x00\x07\x00\xff\xff\x2b\x00\x0a\x00\x2d\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\x2b\x00\x0a\x00\x2d\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x04\x00\x23\x00\xff\xff\xff\xff\x24\x00\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\x2a\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\x20\x00\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x45\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\x0a\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x5f\x00\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\x65\x00\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\x7c\x00\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x05\x00\xff\xff\xff\xff\x04\x00\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\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\x20\x00\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\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x7c\x00\x3a\x00\x7e\x00\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\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\x5c\x00\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\x05\x00\xff\xff\xff\xff\x04\x00\x5f\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\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\x20\x00\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\x0a\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\x5c\x00\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x0a\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\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\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\x5c\x00\x07\x00\x5e\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\xff\xff\x5f\x00\x23\x00\xff\xff\xff\xff\x7c\x00\x27\x00\x7e\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\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x45\x00\xff\xff\xff\xff\x23\x00\x05\x00\xff\xff\xff\xff\x27\x00\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\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\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\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\x0a\x00\x0a\x00\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\x5c\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x01\x00\x02\x00\xff\xff\x04\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\xff\xff\x05\x00\xff\xff\xff\xff\x45\x00\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\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\x20\x00\xff\xff\x5f\x00\x23\x00\xff\xff\xff\xff\xff\xff\x3a\x00\x65\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\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\x23\x00\x7c\x00\xff\xff\x7e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\x45\x00\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x20\x00\xff\xff\xff\xff\x23\x00\x24\x00\xff\xff\xff\xff\x20\x00\x5f\x00\x22\x00\x2a\x00\xff\xff\xff\xff\x26\x00\x27\x00\xff\xff\x5f\x00\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\x65\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\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\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\x05\x00\xff\xff\xff\xff\x66\x00\x5c\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\x7c\x00\x76\x00\xff\xff\x78\x00\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\x27\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\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\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\x2b\x00\x0a\x00\x2d\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\x0a\x00\xff\xff\x0c\x00\x0d\x00\x2b\x00\xff\xff\x2d\x00\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\xff\xff\xff\xff\xff\xff\x05\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\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\x20\x00\xff\xff\x22\x00\x05\x00\x20\x00\xff\xff\x26\x00\x27\x00\x0a\x00\x0b\x00\x0c\x00\x0d\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\x20\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\x5c\x00\x61\x00\x62\x00\x05\x00\xff\xff\xff\xff\x66\x00\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\x0a\x00\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\xff\xff\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\xff\xff\xff\xff\xff\xff\xff\xff\x05\x00\xff\xff\xff\xff\xff\xff\x05\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x20\x00\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\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\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x5c\x00\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\x27\x00\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x23\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x5f\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\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\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\x21\x00\xff\xff\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\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x05\x00\xff\xff\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x0a\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\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\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\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\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\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\x21\x00\xff\xff\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\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\x23\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x20\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\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\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\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\xff\xff\xff\xff\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\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\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\x21\x00\xff\xff\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\x05\x00\x06\x00\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\x21\x00\xff\xff\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\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x05\x00\x06\x00\xff\xff\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x20\x00\xff\xff\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\x5f\x00\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\x06\x00\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\x22\x00\xff\xff\xff\xff\x6e\x00\x6f\x00\x27\x00\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\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\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\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\x0a\x00\xff\xff\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\x21\x00\xff\xff\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\xff\xff\xff\xff\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\x22\x00\xff\xff\xff\xff\xff\xff\x26\x00\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\xff\xff\xff\xff\xff\xff\x4c\x00\xff\xff\x4e\x00\xff\xff\xff\xff\xff\xff\x52\x00\x53\x00\xff\xff\x55\x00\x56\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\x61\x00\x62\x00\xff\xff\xff\xff\xff\xff\x66\x00\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\x6e\x00\x6f\x00\xff\xff\xff\xff\x72\x00\xff\xff\x74\x00\xff\xff\x76\x00\xff\xff\x78\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\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\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\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\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x0a\x00\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\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\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\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\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\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\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\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\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\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\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\x23\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\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\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\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\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\xff\xff\xff\xff\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\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\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\x09\x00\x0a\x00\xff\xff\x0c\x00\x0d\x00\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\x20\x00\x21\x00\xff\xff\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\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\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\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x70\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\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\xff\xff\xff\xff\xff\xff\x23\x00\x45\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x42\x00\xff\xff\x65\x00\x45\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\x62\x00\xff\xff\xff\xff\x65\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\x6f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\x78\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\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\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\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\xff\xff\xff\xff\xff\xff\x23\x00\x45\x00\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\x42\x00\xff\xff\x65\x00\x45\x00\xff\xff\x04\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x4f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x58\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\xff\xff\x62\x00\xff\xff\x21\x00\x65\x00\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\x6f\x00\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x78\x00\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\xff\xff\xff\xff\xff\xff\x05\x00\xff\xff\xff\xff\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\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\x20\x00\x04\x00\xff\xff\x23\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\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\x7c\x00\x21\x00\x7e\x00\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\x04\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\x5f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\x04\x00\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\xff\xff\x5e\x00\x5f\x00\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\xff\xff\xff\xff\xff\xff\x21\x00\xff\xff\x23\x00\x24\x00\x25\x00\x26\x00\xff\xff\xff\xff\xff\xff\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x3a\x00\x5e\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\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\x7c\x00\xff\xff\x7e\x00\x5c\x00\xff\xff\x5e\x00\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\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\x2b\x00\xff\xff\x2d\x00\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2e\x00\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\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\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\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\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\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x23\x00\xff\xff\xff\xff\xff\xff\x27\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\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\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\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\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\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\x29\x00\x2a\x00\x2b\x00\xff\xff\x2d\x00\x2e\x00\x2f\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x3a\x00\xff\xff\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x01\x00\x02\x00\x03\x00\xff\xff\xff\xff\xff\xff\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x5d\x00\x5e\x00\xff\xff\xff\xff\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\x7c\x00\xff\xff\x7e\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\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\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\x7c\x00\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x5c\x00\x5d\x00\x5e\x00\xff\xff\x01\x00\x02\x00\x03\x00\x04\x00\x05\x00\x06\x00\x07\x00\xff\xff\xff\xff\x0a\x00\xff\xff\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\x7c\x00\xff\xff\x7e\x00\x20\x00\x21\x00\xff\xff\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\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\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\x5c\x00\xff\xff\x5e\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\x7c\x00\x7d\x00\x7e\x00\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\xff\xff\x05\x00\xff\xff\x07\x00\xff\xff\xff\xff\x0a\x00\x0b\x00\x0c\x00\x0d\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\xff\xff\xff\xff\xff\xff\xff\xff\x5f\x00\xff\xff\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x01\x00\x02\x00\x03\x00\x04\x00\xff\xff\x06\x00\x07\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x20\x00\x21\x00\x22\x00\x23\x00\x24\x00\x25\x00\x26\x00\x27\x00\x28\x00\x29\x00\x2a\x00\x2b\x00\x2c\x00\x2d\x00\x2e\x00\x2f\x00\x30\x00\x31\x00\x32\x00\x33\x00\x34\x00\x35\x00\x36\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x3b\x00\x3c\x00\x3d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x42\x00\x43\x00\x44\x00\x45\x00\x46\x00\x47\x00\x48\x00\x49\x00\x4a\x00\x4b\x00\x4c\x00\x4d\x00\x4e\x00\x4f\x00\x50\x00\x51\x00\x52\x00\x53\x00\x54\x00\x55\x00\x56\x00\x57\x00\x58\x00\x59\x00\x5a\x00\x5b\x00\x5c\x00\x5d\x00\x5e\x00\x5f\x00\x60\x00\x61\x00\x62\x00\x63\x00\x64\x00\x65\x00\x66\x00\x67\x00\x68\x00\x69\x00\x6a\x00\x6b\x00\x6c\x00\x6d\x00\x6e\x00\x6f\x00\x70\x00\x71\x00\x72\x00\x73\x00\x74\x00\x75\x00\x76\x00\x77\x00\x78\x00\x79\x00\x7a\x00\x7b\x00\x7c\x00\x7d\x00\x7e\x00\x01\x00\x02\x00\x03\x00\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\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\x11\x00\x11\x00\x11\x00\x11\x00\x11\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\x11\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x2a\x00\xff\xff\x2c\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\x47\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x11\x00\xff\xff\x19\x01\x19\x01\x19\x01\xaa\x00\x71\x00\xaa\x00\x71\x00\xaa\x00\x71\x00\xff\xff\xaa\x00\x71\x00\x71\x00\xff\xff\xff\xff\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\xff\xff\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x71\x00\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x8c\x00\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\xff\xff\xaa\x00\xaa\x00\xaa\x00\xff\xff\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xaa\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\xaa\x00\xaa\x00\xaa\x00\xaa\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x19\x01\x19\x01\x19\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x19\x01\xff\xff\x11\x00\xff\xff\xff\xff\xff\xff\x06\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\x19\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xaa\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\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x71\x00\x7f\x01\x7f\x01\x7f\x01\x7f\x01\x7f\x01\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\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, 535)
  [ AlexAccNone
  , AlexAcc 359
  , AlexAccNone
  , AlexAcc 358
  , AlexAcc 357
  , AlexAcc 356
  , AlexAcc 355
  , AlexAcc 354
  , AlexAcc 353
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 352
  , AlexAcc 351
  , AlexAcc 350
  , AlexAccSkip
  , AlexAcc 349
  , AlexAcc 348
  , AlexAcc 347
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 346
  , AlexAccPred 345 (known_pragma linePrags)(AlexAcc 344)
  , AlexAccNone
  , AlexAccPred 343 (known_pragma linePrags)(AlexAccPred 342 (known_pragma oneWordPrags)(AlexAccPred 341 (known_pragma ignoredPrags)(AlexAccPred 340 (known_pragma fileHeaderPrags)(AlexAcc 339))))
  , AlexAcc 338
  , AlexAccPred 337 (isNormalComment)(AlexAccNone)
  , AlexAcc 336
  , AlexAccNone
  , AlexAccPred 335 (known_pragma linePrags)(AlexAccPred 334 (known_pragma oneWordPrags)(AlexAccPred 333 (known_pragma ignoredPrags)(AlexAccPred 332 (known_pragma fileHeaderPrags)(AlexAcc 331))))
  , AlexAccPred 330 (known_pragma linePrags)(AlexAcc 329)
  , AlexAccNone
  , AlexAccPred 328 (known_pragma linePrags)(AlexAccNone)
  , AlexAcc 327
  , AlexAccPred 326 (notFollowedBySymbol)(AlexAccNone)
  , AlexAccPred 325 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccSkip
  , AlexAccPred 324 (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
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 323
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 322
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccSkipPred (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccPred 321 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False) `alexAndPred` followedByDigit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 320 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAccSkip
  , AlexAccPred 319 (isSmartQuote)(AlexAcc 318)
  , AlexAccPred 317 (isSmartQuote)(AlexAccPred 316 (ifCurrentChar '⟦' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ThQuotesBit)(AlexAccPred 315 (ifCurrentChar '⟧' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ThQuotesBit)(AlexAccPred 314 (ifCurrentChar '⦇' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ArrowsBit)(AlexAccPred 313 (ifCurrentChar '⦈' `alexAndPred`
        ifExtension UnicodeSyntaxBit `alexAndPred`
        ifExtension ArrowsBit)(AlexAccNone)))))
  , AlexAccPred 312 (isSmartQuote)(AlexAcc 311)
  , AlexAccPred 310 (isSmartQuote)(AlexAccNone)
  , AlexAccPred 309 (atEOL)(AlexAcc 308)
  , AlexAccPred 307 (atEOL)(AlexAcc 306)
  , AlexAccPred 305 (atEOL)(AlexAccNone)
  , AlexAccPred 304 (atEOL)(AlexAcc 303)
  , AlexAccPred 302 (atEOL)(AlexAcc 301)
  , AlexAccPred 300 (atEOL)(AlexAcc 299)
  , AlexAccPred 298 (atEOL)(AlexAcc 297)
  , AlexAccPred 296 (atEOL)(AlexAcc 295)
  , AlexAccPred 294 (atEOL)(AlexAcc 293)
  , AlexAccNone
  , AlexAccPred 292 (atEOL)(AlexAccNone)
  , AlexAccPred 291 (atEOL)(AlexAccNone)
  , AlexAcc 290
  , AlexAcc 289
  , AlexAcc 288
  , AlexAcc 287
  , AlexAcc 286
  , AlexAcc 285
  , AlexAcc 284
  , AlexAcc 283
  , AlexAcc 282
  , AlexAcc 281
  , AlexAcc 280
  , AlexAcc 279
  , AlexAccNone
  , AlexAcc 278
  , AlexAcc 277
  , AlexAcc 276
  , AlexAcc 275
  , AlexAcc 274
  , AlexAcc 273
  , AlexAcc 272
  , AlexAcc 271
  , AlexAcc 270
  , AlexAcc 269
  , AlexAcc 268
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 267
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 266 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 265
  , AlexAcc 264
  , AlexAcc 263
  , AlexAcc 262
  , AlexAcc 261
  , AlexAcc 260
  , AlexAcc 259
  , AlexAcc 258
  , AlexAcc 257
  , AlexAccPred 256 (alexNotPred (ifExtension HaddockBit))(AlexAcc 255)
  , AlexAccPred 254 (alexNotPred (ifExtension HaddockBit))(AlexAcc 253)
  , AlexAccPred 252 (alexNotPred (ifExtension HaddockBit))(AlexAccPred 251 (ifExtension HaddockBit)(AlexAcc 250))
  , AlexAccPred 249 (alexNotPred (ifExtension HaddockBit))(AlexAccPred 248 (ifExtension HaddockBit)(AlexAccNone))
  , AlexAccPred 247 (alexNotPred (ifExtension HaddockBit))(AlexAcc 246)
  , AlexAccPred 245 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 244 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 243 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 242 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 241 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 240 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 239 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 238 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 237 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 236 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 235 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 234 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccNone
  , AlexAcc 233
  , AlexAcc 232
  , AlexAcc 231
  , AlexAccNone
  , AlexAcc 230
  , AlexAcc 229
  , AlexAcc 228
  , AlexAcc 227
  , AlexAcc 226
  , AlexAcc 225
  , AlexAcc 224
  , AlexAcc 223
  , AlexAcc 222
  , AlexAcc 221
  , AlexAcc 220
  , AlexAcc 219
  , AlexAcc 218
  , AlexAcc 217
  , AlexAcc 216
  , AlexAcc 215
  , AlexAcc 214
  , AlexAcc 213
  , AlexAcc 212
  , AlexAcc 211
  , AlexAcc 210
  , AlexAcc 209
  , AlexAcc 208
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 207
  , AlexAcc 206
  , AlexAcc 205
  , AlexAcc 204
  , AlexAcc 203
  , AlexAccSkip
  , AlexAccNone
  , AlexAcc 202
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 201
  , AlexAcc 200
  , AlexAcc 199
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 198
  , AlexAcc 197
  , AlexAcc 196
  , AlexAcc 195
  , AlexAcc 194
  , AlexAcc 193
  , AlexAcc 192
  , AlexAcc 191
  , AlexAcc 190
  , AlexAcc 189
  , AlexAcc 188
  , AlexAcc 187
  , AlexAcc 186
  , AlexAcc 185
  , AlexAcc 184
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 183
  , AlexAccPred 182 (isNormalComment)(AlexAcc 181)
  , AlexAccPred 180 (isNormalComment)(AlexAcc 179)
  , AlexAccNone
  , AlexAccPred 178 (isNormalComment)(AlexAccNone)
  , AlexAcc 177
  , AlexAccNone
  , AlexAccSkip
  , AlexAccNone
  , AlexAccSkip
  , AlexAccNone
  , AlexAccPred 176 (alexRightContext 263)(AlexAccNone)
  , AlexAcc 175
  , AlexAccPred 174 (alexRightContext 259)(AlexAccNone)
  , AlexAccPred 173 (alexRightContext 259)(AlexAccNone)
  , AlexAcc 172
  , AlexAcc 171
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 170
  , AlexAcc 169
  , AlexAcc 168
  , AlexAcc 167
  , AlexAcc 166
  , AlexAcc 165
  , AlexAcc 164
  , AlexAcc 163
  , AlexAcc 162
  , AlexAcc 161
  , AlexAcc 160
  , AlexAcc 159
  , AlexAcc 158
  , AlexAcc 157
  , AlexAcc 156
  , AlexAccSkip
  , AlexAccPred 155 (isSmartQuote)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 154 (isSmartQuote)(AlexAccNone)
  , AlexAccPred 153 (isSmartQuote)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 152 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 151
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 150
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 149 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 148
  , AlexAccPred 147 (ifExtension MultilineStringsBit)(AlexAccNone)
  , AlexAcc 146
  , AlexAccNone
  , AlexAccPred 145 (ifExtension HexFloatLiteralsBit `alexAndPred` negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 144 (ifExtension HexFloatLiteralsBit `alexAndPred` negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 143 (ifExtension MagicHashBit `alexAndPred` ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccPred 142 (ifExtension MagicHashBit `alexAndPred` ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccPred 141 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 140 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 139 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 138 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 137 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 136 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 135 (negHashLitPred ExtendedLiteralsBit `alexAndPred`
                                             ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 134 (negHashLitPred ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 133 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 132 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 131 (ifExtension ExtendedLiteralsBit `alexAndPred`
                                             ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 130 (ifExtension ExtendedLiteralsBit)(AlexAccNone)
  , AlexAccPred 129 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 128 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 127 (ifExtension MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 126 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 125 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 124 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 123 (negHashLitPred MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 122 (negHashLitPred MagicHashBit)(AlexAccNone)
  , AlexAccPred 121 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 120 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 119 (ifExtension MagicHashBit `alexAndPred`
                                      ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccPred 118 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 117 (ifExtension HexFloatLiteralsBit `alexAndPred`
                                           negLitPred)(AlexAccNone)
  , AlexAccPred 116 (ifExtension HexFloatLiteralsBit `alexAndPred`
                                           negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 115 (ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccPred 114 (ifExtension HexFloatLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 113 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 112 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 111 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 110 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 109 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 108 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 107 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 106 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 105 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 104 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 103 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 102 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAcc 101
  , AlexAccPred 100 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 99 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 98 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 97 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccPred 96 (alexNotPred (ifExtension HaddockBit))(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 95 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 94
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 93 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 92 (negLitPred)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 91 (negLitPred `alexAndPred`
                                ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 90 (negLitPred)(AlexAccNone)
  , AlexAccPred 89 (negLitPred)(AlexAccNone)
  , AlexAcc 88
  , AlexAccNone
  , AlexAcc 87
  , AlexAccNone
  , AlexAccPred 86 (ifExtension BinaryLiteralsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 85
  , AlexAcc 84
  , AlexAcc 83
  , AlexAcc 82
  , AlexAcc 81
  , AlexAcc 80
  , AlexAcc 79
  , AlexAccPred 78 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 77 (ifExtension MagicHashBit)(AlexAccPred 76 (ifExtension MagicHashBit)(AlexAccNone))
  , AlexAccPred 75 (ifExtension MagicHashBit)(AlexAccPred 74 (ifExtension MagicHashBit)(AlexAccNone))
  , AlexAccPred 73 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 72 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAccPred 71 (ifExtension MagicHashBit)(AlexAccNone)
  , AlexAcc 70
  , AlexAcc 69
  , AlexAcc 68
  , AlexAcc 67
  , AlexAcc 66
  , AlexAcc 65
  , AlexAcc 64
  , AlexAcc 63
  , AlexAcc 62
  , AlexAcc 61
  , AlexAccNone
  , AlexAcc 60
  , AlexAcc 59
  , AlexAcc 58
  , AlexAcc 57
  , AlexAcc 56
  , AlexAcc 55
  , AlexAccPred 54 (ifExtension RecursiveDoBit)(AlexAcc 53)
  , AlexAcc 52
  , AlexAccPred 51 (ifExtension RecursiveDoBit)(AlexAcc 50)
  , AlexAcc 49
  , AlexAcc 48
  , AlexAcc 47
  , AlexAcc 46
  , AlexAcc 45
  , AlexAcc 44
  , AlexAcc 43
  , AlexAcc 42
  , AlexAcc 41
  , AlexAcc 40
  , AlexAcc 39
  , AlexAcc 38
  , AlexAccPred 37 (ifExtension UnboxedParensBit)(AlexAccNone)
  , AlexAcc 36
  , AlexAccPred 35 (ifExtension UnboxedParensBit)(AlexAccNone)
  , AlexAcc 34
  , AlexAccPred 33 (ifExtension OverloadedLabelsBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 32 (ifExtension OverloadedLabelsBit)(AlexAccNone)
  , AlexAccPred 31 (ifExtension IpBit)(AlexAccNone)
  , AlexAccPred 30 (ifExtension ArrowsBit)(AlexAccNone)
  , AlexAcc 29
  , AlexAccPred 28 (ifExtension ArrowsBit `alexAndPred`
        notFollowedBySymbol)(AlexAccNone)
  , AlexAccPred 27 (ifExtension QqBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccPred 26 (ifExtension QqBit)(AlexAccNone)
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 25 (ifExtension ThQuotesBit)(AlexAccPred 24 (ifExtension QqBit)(AlexAccNone))
  , AlexAccNone
  , AlexAccPred 23 (ifExtension ThQuotesBit)(AlexAccPred 22 (ifExtension QqBit)(AlexAccNone))
  , AlexAccNone
  , AlexAccPred 21 (ifExtension ThQuotesBit)(AlexAccPred 20 (ifExtension QqBit)(AlexAccNone))
  , AlexAccNone
  , AlexAccPred 19 (ifExtension ThQuotesBit)(AlexAccNone)
  , AlexAccPred 18 (ifExtension ThQuotesBit)(AlexAccPred 17 (ifExtension QqBit)(AlexAccNone))
  , AlexAcc 16
  , AlexAcc 15
  , AlexAcc 14
  , AlexAcc 13
  , AlexAcc 12
  , AlexAccPred 11 (ifExtension HaddockBit)(AlexAcc 10)
  , AlexAccPred 9 (ifExtension HaddockBit)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 8
  , AlexAccPred 7 (isNormalComment)(AlexAccNone)
  , AlexAcc 6
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 5 (alexPrevCharMatches(\c -> c >= '\n' && c <= '\n' || False))(AlexAccNone)
  , AlexAcc 4
  , AlexAccNone
  , AlexAccNone
  , AlexAccPred 3 (known_pragma twoWordPrags)(AlexAccNone)
  , AlexAccNone
  , AlexAcc 2
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 1
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  , AlexAcc 0
  , AlexAccNone
  , AlexAccNone
  , AlexAccNone
  ]

alex_actions = array (0 :: Int, 360)
  [ (359,alex_action_16)
  , (358,alex_action_22)
  , (357,alex_action_23)
  , (356,alex_action_21)
  , (355,alex_action_24)
  , (354,alex_action_28)
  , (353,alex_action_29)
  , (352,alex_action_136)
  , (351,alex_action_29)
  , (350,alex_action_29)
  , (349,alex_action_1)
  , (348,alex_action_29)
  , (347,alex_action_29)
  , (346,alex_action_27)
  , (345,alex_action_26)
  , (344,alex_action_136)
  , (343,alex_action_26)
  , (342,alex_action_34)
  , (341,alex_action_35)
  , (340,alex_action_38)
  , (339,alex_action_39)
  , (338,alex_action_72)
  , (337,alex_action_2)
  , (336,alex_action_40)
  , (335,alex_action_26)
  , (334,alex_action_34)
  , (333,alex_action_35)
  , (332,alex_action_37)
  , (331,alex_action_39)
  , (330,alex_action_26)
  , (329,alex_action_29)
  , (328,alex_action_26)
  , (327,alex_action_25)
  , (326,alex_action_20)
  , (325,alex_action_19)
  , (324,alex_action_17)
  , (323,alex_action_67)
  , (322,alex_action_86)
  , (321,alex_action_12)
  , (320,alex_action_11)
  , (319,alex_action_9)
  , (318,alex_action_136)
  , (317,alex_action_9)
  , (316,alex_action_54)
  , (315,alex_action_55)
  , (314,alex_action_58)
  , (313,alex_action_59)
  , (312,alex_action_9)
  , (311,alex_action_29)
  , (310,alex_action_9)
  , (309,alex_action_8)
  , (308,alex_action_136)
  , (307,alex_action_8)
  , (306,alex_action_29)
  , (305,alex_action_8)
  , (304,alex_action_7)
  , (303,alex_action_136)
  , (302,alex_action_7)
  , (301,alex_action_136)
  , (300,alex_action_7)
  , (299,alex_action_86)
  , (298,alex_action_7)
  , (297,alex_action_86)
  , (296,alex_action_7)
  , (295,alex_action_29)
  , (294,alex_action_7)
  , (293,alex_action_29)
  , (292,alex_action_7)
  , (291,alex_action_7)
  , (290,alex_action_6)
  , (289,alex_action_78)
  , (288,alex_action_78)
  , (287,alex_action_6)
  , (286,alex_action_6)
  , (285,alex_action_6)
  , (284,alex_action_6)
  , (283,alex_action_6)
  , (282,alex_action_6)
  , (281,alex_action_6)
  , (280,alex_action_6)
  , (279,alex_action_6)
  , (278,alex_action_6)
  , (277,alex_action_6)
  , (276,alex_action_6)
  , (275,alex_action_6)
  , (274,alex_action_6)
  , (273,alex_action_6)
  , (272,alex_action_6)
  , (271,alex_action_6)
  , (270,alex_action_6)
  , (269,alex_action_6)
  , (268,alex_action_6)
  , (267,alex_action_96)
  , (266,alex_action_97)
  , (265,alex_action_6)
  , (264,alex_action_6)
  , (263,alex_action_6)
  , (262,alex_action_6)
  , (261,alex_action_6)
  , (260,alex_action_6)
  , (259,alex_action_6)
  , (258,alex_action_6)
  , (257,alex_action_6)
  , (256,alex_action_5)
  , (255,alex_action_136)
  , (254,alex_action_5)
  , (253,alex_action_136)
  , (252,alex_action_5)
  , (251,alex_action_41)
  , (250,alex_action_136)
  , (249,alex_action_5)
  , (248,alex_action_41)
  , (247,alex_action_5)
  , (246,alex_action_29)
  , (245,alex_action_5)
  , (244,alex_action_5)
  , (243,alex_action_5)
  , (242,alex_action_5)
  , (241,alex_action_5)
  , (240,alex_action_5)
  , (239,alex_action_5)
  , (238,alex_action_5)
  , (237,alex_action_5)
  , (236,alex_action_5)
  , (235,alex_action_5)
  , (234,alex_action_5)
  , (233,alex_action_4)
  , (232,alex_action_4)
  , (231,alex_action_4)
  , (230,alex_action_4)
  , (229,alex_action_4)
  , (228,alex_action_4)
  , (227,alex_action_4)
  , (226,alex_action_4)
  , (225,alex_action_4)
  , (224,alex_action_4)
  , (223,alex_action_4)
  , (222,alex_action_4)
  , (221,alex_action_4)
  , (220,alex_action_4)
  , (219,alex_action_4)
  , (218,alex_action_4)
  , (217,alex_action_4)
  , (216,alex_action_4)
  , (215,alex_action_4)
  , (214,alex_action_4)
  , (213,alex_action_4)
  , (212,alex_action_4)
  , (211,alex_action_4)
  , (210,alex_action_4)
  , (209,alex_action_4)
  , (208,alex_action_4)
  , (207,alex_action_4)
  , (206,alex_action_4)
  , (205,alex_action_4)
  , (204,alex_action_4)
  , (203,alex_action_136)
  , (202,alex_action_136)
  , (201,alex_action_3)
  , (200,alex_action_3)
  , (199,alex_action_3)
  , (198,alex_action_3)
  , (197,alex_action_3)
  , (196,alex_action_3)
  , (195,alex_action_3)
  , (194,alex_action_3)
  , (193,alex_action_3)
  , (192,alex_action_3)
  , (191,alex_action_3)
  , (190,alex_action_3)
  , (189,alex_action_3)
  , (188,alex_action_3)
  , (187,alex_action_3)
  , (186,alex_action_3)
  , (185,alex_action_3)
  , (184,alex_action_3)
  , (183,alex_action_3)
  , (182,alex_action_2)
  , (181,alex_action_136)
  , (180,alex_action_2)
  , (179,alex_action_29)
  , (178,alex_action_2)
  , (177,alex_action_1)
  , (176,alex_action_139)
  , (175,alex_action_138)
  , (174,alex_action_137)
  , (173,alex_action_137)
  , (172,alex_action_136)
  , (171,alex_action_136)
  , (170,alex_action_136)
  , (169,alex_action_3)
  , (168,alex_action_3)
  , (167,alex_action_3)
  , (166,alex_action_3)
  , (165,alex_action_3)
  , (164,alex_action_3)
  , (163,alex_action_3)
  , (162,alex_action_3)
  , (161,alex_action_3)
  , (160,alex_action_3)
  , (159,alex_action_3)
  , (158,alex_action_3)
  , (157,alex_action_136)
  , (156,alex_action_136)
  , (155,alex_action_135)
  , (154,alex_action_134)
  , (153,alex_action_133)
  , (152,alex_action_132)
  , (151,alex_action_4)
  , (150,alex_action_131)
  , (149,alex_action_130)
  , (148,alex_action_129)
  , (147,alex_action_128)
  , (146,alex_action_129)
  , (145,alex_action_127)
  , (144,alex_action_126)
  , (143,alex_action_125)
  , (142,alex_action_124)
  , (141,alex_action_123)
  , (140,alex_action_122)
  , (139,alex_action_121)
  , (138,alex_action_120)
  , (137,alex_action_119)
  , (136,alex_action_118)
  , (135,alex_action_117)
  , (134,alex_action_116)
  , (133,alex_action_115)
  , (132,alex_action_114)
  , (131,alex_action_113)
  , (130,alex_action_112)
  , (129,alex_action_111)
  , (128,alex_action_110)
  , (127,alex_action_109)
  , (126,alex_action_108)
  , (125,alex_action_107)
  , (124,alex_action_106)
  , (123,alex_action_105)
  , (122,alex_action_104)
  , (121,alex_action_103)
  , (120,alex_action_102)
  , (119,alex_action_101)
  , (118,alex_action_100)
  , (117,alex_action_99)
  , (116,alex_action_99)
  , (115,alex_action_98)
  , (114,alex_action_98)
  , (113,alex_action_5)
  , (112,alex_action_5)
  , (111,alex_action_5)
  , (110,alex_action_5)
  , (109,alex_action_5)
  , (108,alex_action_5)
  , (107,alex_action_5)
  , (106,alex_action_5)
  , (105,alex_action_5)
  , (104,alex_action_5)
  , (103,alex_action_5)
  , (102,alex_action_5)
  , (101,alex_action_6)
  , (100,alex_action_5)
  , (99,alex_action_5)
  , (98,alex_action_5)
  , (97,alex_action_5)
  , (96,alex_action_5)
  , (95,alex_action_97)
  , (94,alex_action_96)
  , (93,alex_action_95)
  , (92,alex_action_94)
  , (91,alex_action_93)
  , (90,alex_action_92)
  , (89,alex_action_92)
  , (88,alex_action_91)
  , (87,alex_action_90)
  , (86,alex_action_89)
  , (85,alex_action_88)
  , (84,alex_action_88)
  , (83,alex_action_87)
  , (82,alex_action_86)
  , (81,alex_action_86)
  , (80,alex_action_85)
  , (79,alex_action_84)
  , (78,alex_action_83)
  , (77,alex_action_82)
  , (76,alex_action_121)
  , (75,alex_action_82)
  , (74,alex_action_120)
  , (73,alex_action_82)
  , (72,alex_action_81)
  , (71,alex_action_80)
  , (70,alex_action_79)
  , (69,alex_action_79)
  , (68,alex_action_78)
  , (67,alex_action_78)
  , (66,alex_action_78)
  , (65,alex_action_78)
  , (64,alex_action_78)
  , (63,alex_action_78)
  , (62,alex_action_77)
  , (61,alex_action_77)
  , (60,alex_action_76)
  , (59,alex_action_76)
  , (58,alex_action_76)
  , (57,alex_action_76)
  , (56,alex_action_76)
  , (55,alex_action_76)
  , (54,alex_action_75)
  , (53,alex_action_76)
  , (52,alex_action_76)
  , (51,alex_action_75)
  , (50,alex_action_76)
  , (49,alex_action_76)
  , (48,alex_action_74)
  , (47,alex_action_74)
  , (46,alex_action_73)
  , (45,alex_action_72)
  , (44,alex_action_71)
  , (43,alex_action_70)
  , (42,alex_action_69)
  , (41,alex_action_68)
  , (40,alex_action_67)
  , (39,alex_action_66)
  , (38,alex_action_65)
  , (37,alex_action_64)
  , (36,alex_action_86)
  , (35,alex_action_63)
  , (34,alex_action_65)
  , (33,alex_action_62)
  , (32,alex_action_61)
  , (31,alex_action_60)
  , (30,alex_action_57)
  , (29,alex_action_86)
  , (28,alex_action_56)
  , (27,alex_action_53)
  , (26,alex_action_52)
  , (25,alex_action_51)
  , (24,alex_action_52)
  , (23,alex_action_50)
  , (22,alex_action_52)
  , (21,alex_action_49)
  , (20,alex_action_52)
  , (19,alex_action_48)
  , (18,alex_action_47)
  , (17,alex_action_52)
  , (16,alex_action_46)
  , (15,alex_action_86)
  , (14,alex_action_45)
  , (13,alex_action_44)
  , (12,alex_action_43)
  , (11,alex_action_42)
  , (10,alex_action_136)
  , (9,alex_action_42)
  , (8,alex_action_40)
  , (7,alex_action_2)
  , (6,alex_action_36)
  , (5,alex_action_19)
  , (4,alex_action_86)
  , (3,alex_action_33)
  , (2,alex_action_32)
  , (1,alex_action_31)
  , (0,alex_action_30)
  ]


bol,column_prag,layout,layout_do,layout_if,layout_left,line_prag1,line_prag1a,line_prag2,line_prag2a,option_prags,string_multi_content :: 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
string_multi_content = 12
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_53 :: Action
alex_action_11 = begin line_prag1
alex_action_54 :: Action
alex_action_12 = Token -> Action
begin line_prag1
alex_action_55 :: Action
alex_action_16 = do_bol
alex_action_56 :: Action
alex_action_17 = hopefully_open_brace
alex_action_57 :: Action
alex_action_19 = begin line_prag1
alex_action_58 :: Action
alex_action_20 = new_layout_context True dontGenerateSemic ITvbar
alex_action_59 :: Action
alex_action_21 = pop
alex_action_60 :: Action
alex_action_22 = new_layout_context True  generateSemic ITvocurly
alex_action_61 :: Action
alex_action_23 = (SourceText -> FastString -> Token) -> Action
new_layout_context False generateSemic ITvocurly
alex_action_62 :: Action
alex_action_24 = do_layout_left
alex_action_63 :: Action
alex_action_25 = Token -> Action
begin bol
alex_action_64 :: Action
alex_action_26 = dispatch_pragmas linePrags
alex_action_65 :: Action
alex_action_27 = setLineAndFile line_prag1a
alex_action_66 :: Action
alex_action_28 = failLinePrag1
alex_action_67 :: Action
alex_action_29 = popLinePrag1
alex_action_68 :: Action
alex_action_30 = setLineAndFile line_prag2a
alex_action_69 :: Action
alex_action_31 = pop
alex_action_70 :: Action
alex_action_32 = setColumn
alex_action_71 :: Action
alex_action_33 = dispatch_pragmas twoWordPrags
alex_action_72 :: Action
alex_action_34 = dispatch_pragmas oneWordPrags
alex_action_73 :: Action
alex_action_35 = dispatch_pragmas ignoredPrags
alex_action_74 :: Action
alex_action_36 = endPrag
alex_action_75 :: Action
alex_action_37 = dispatch_pragmas fileHeaderPrags
alex_action_76 :: Action
alex_action_38 = nested_comment
alex_action_77 :: Action
alex_action_39 = warn_unknown_prag (Map.unions [ oneWordPrags, fileHeaderPrags, ignoredPrags, linePrags ])
alex_action_78 :: Action
alex_action_40 = warn_unknown_prag Map.empty
alex_action_79 :: Action
alex_action_41 = multiline_doc_comment
alex_action_80 :: Action
alex_action_42 = nested_doc_comment
alex_action_81 :: Action
alex_action_43 = token (ITopenExpQuote NoE NormalSyntax)
alex_action_82 :: Action
alex_action_44 = Action
token (ITopenTExpQuote NoE)
alex_action_83 :: Action
alex_action_45 = token (ITcloseQuote NormalSyntax)
alex_action_84 :: Action
alex_action_46 = token ITcloseTExpQuote
alex_action_85 :: Action
alex_action_47 = token (ITopenExpQuote HasE NormalSyntax)
alex_action_86 :: Action
alex_action_48 = token (ITopenTExpQuote HasE)
alex_action_87 :: Action
alex_action_49 = token ITopenPatQuote
alex_action_88 :: Action
alex_action_50 = layout_token ITopenDecQuote
alex_action_89 :: Action
alex_action_51 = token ITopenTypQuote
alex_action_90 :: Action
alex_action_52 = lex_quasiquote_tok
alex_action_91 :: Action
alex_action_53 = lex_qquasiquote_tok
alex_action_92 :: Action
alex_action_54 = token (ITopenExpQuote NoE UnicodeSyntax)
alex_action_93 :: Action
alex_action_55 = token (ITcloseQuote UnicodeSyntax)
alex_action_94 :: Action
alex_action_56 = (Integer -> Integer)
-> Int -> Int -> (Integer, Char -> Int) -> Action
special (IToparenbar NormalSyntax)
alex_action_95 :: Action
alex_action_57 = (Integer -> Integer)
-> Int -> Int -> (Integer, Char -> Int) -> Action
special (ITcparenbar NormalSyntax)
alex_action_96 :: Action
alex_action_58 = special (IToparenbar UnicodeSyntax)
alex_action_97 :: Action
alex_action_59 = special (ITcparenbar UnicodeSyntax)
alex_action_98 :: Action
alex_action_60 = skip_one_varid ITdupipvarid
alex_action_99 :: Action
alex_action_61 = skip_one_varid_src ITlabelvarid
alex_action_62 = tok_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_138 :: Action
alex_action_100 = tok_primint positive 0 1 decimal
alex_action_139 :: Action
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_prim_num_ext positive 0 decimal
alex_action_113 = tok_prim_num_ext positive 2 binary
alex_action_114 = tok_prim_num_ext positive 2 octal
alex_action_115 = tok_prim_num_ext positive 2 hexadecimal
alex_action_116 = tok_prim_num_ext negative 1 decimal
alex_action_117 = tok_prim_num_ext negative 3 binary
alex_action_118 = tok_prim_num_ext negative 3 octal
alex_action_119 = tok_prim_num_ext negative 3 hexadecimal
alex_action_120 = tok_frac 1 tok_primfloat
alex_action_121 = tok_frac 2 tok_primdouble
alex_action_122 = tok_frac 1 tok_primfloat
alex_action_123 = tok_frac 2 tok_primdouble
alex_action_124 = tok_frac 1 tok_prim_hex_float
alex_action_125 = tok_frac 2 tok_prim_hex_double
alex_action_126 = tok_frac 1 tok_prim_hex_float
alex_action_127 = tok_frac 2 tok_prim_hex_double
alex_action_128 = tok_string_multi
alex_action_129 = tok_string
alex_action_130 = tok_string
alex_action_131 = tok_char
alex_action_132 = tok_char
alex_action_133 = smart_quote_error
alex_action_134 = smart_quote_error
alex_action_135 = smart_quote_error
alex_action_136 = tok_string_multi_content
alex_action_137 = tok_string_multi_content
alex_action_138 = token ITtyQuote
alex_action_139 = token ITsimpleQuote

#define ALEX_GHC 1
#define ALEX_LATIN1 1
-- -----------------------------------------------------------------------------
-- ALEX TEMPLATE
--
-- This code is in the PUBLIC DOMAIN; you may copy it freely and use
-- it for any purpose whatsoever.

-- -----------------------------------------------------------------------------
-- INTERNALS and main scanner engine

#ifdef ALEX_GHC
#  define ILIT(n) n#
#  define IBOX(n) (I# (n))
#  define FAST_INT Int#
-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#  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#
-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ < 503
uncheckedShiftL# = shiftL#
#endif

{-# INLINE alexIndexInt16OffAddr #-}
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 (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
-- GHC >= 503, unsafeAt is available from Data.Array.Base.
quickIndex = unsafeAt
#endif
#else
quickIndex arr i = arr ! i
#endif

-- -----------------------------------------------------------------------------
-- Main lexing routines

data AlexReturn a
  = AlexEOF
  | AlexError  !AlexInput
  | AlexSkip   !AlexInput !Int
  | AlexToken  !AlexInput !Int a

-- alexScan :: AlexInput -> StartCode -> AlexReturn 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)


-- Push the input through the DFA, remembering the most recent accepting
-- state it encountered.

alex_scan_tkn user__ orig_input len input__ s last_acc =
  input__ `seq` -- strict in the input
  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)

                new_s = if GTE(offset,ILIT(0))
                          && let check  = alexIndexInt16OffAddr alex_check offset
                             in  EQ(check,ord_c)
                          then alexIndexInt16OffAddr alex_table offset
                          else alexIndexInt16OffAddr alex_deflt s
        in
        case new_s of
            ILIT(-1) -> (new_acc, input__)
                -- on an error, we want to keep the input *before* the
                -- character that failed, not after.
            _ -> alex_scan_tkn user__ orig_input
#ifdef ALEX_LATIN1
                   PLUS(len,ILIT(1))
                   -- issue 119: in the latin1 encoding, *each* byte is one character
#else
                   (if c < 0x80 || c >= 0xC0 then PLUS(len,ILIT(1)) else len)
                   -- note that the length is increased ONLY if this is the 1st byte in a char encoding)
#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

-- -----------------------------------------------------------------------------
-- Predicates on a rule

alexAndPred p1 p2 user__ in1 len in2
  = p1 user__ in1 len in2 && p2 user__ in1 len in2

--alexPrevCharIsPred :: Char -> AlexAccPred _
alexPrevCharIs c _ input__ _ _ = c == alexInputPrevChar input__

alexPrevCharMatches f _ input__ _ _ = f (alexInputPrevChar input__)

--alexPrevCharIsOneOfPred :: Array Char Bool -> AlexAccPred _
alexPrevCharIsOneOf arr _ input__ _ _ = arr ! alexInputPrevChar input__

--alexRightContext :: Int -> AlexAccPred _
alexRightContext IBOX(sc) user__ _ _ input__ =
     case alex_scan_tkn user__ input__ ILIT(0) input__ sc AlexNone of
          (AlexNone, _) -> False
          _ -> True
        -- TODO: there's no need to find the longest
        -- match when checking the right context, just
        -- the first match will do.
#endif
{-# LINE 765 "compiler/GHC/Parser/Lexer.x" #-}
-- Operator whitespace occurrence. See Note [Whitespace-sensitive operator parsing].
data OpWs
  = OpWsPrefix         -- a !b
  | OpWsSuffix         -- a! b
  | OpWsTightInfix     -- a!b
  | OpWsLooseInfix     -- a ! b
  deriving Show

-- -----------------------------------------------------------------------------
-- The token type

data Token
  = ITas                        -- Haskell keywords
  | 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 -- GHC extension keywords
  | ITexport
  | ITlabel
  | ITdynamic
  | ITsafe
  | ITinterruptible
  | ITunsafe
  | ITstdcallconv
  | ITccallconv
  | ITcapiconv
  | ITprimcallconv
  | ITjavascriptcallconv
  | ITmdo (Maybe FastString)
  | ITfamily
  | ITrole
  | ITgroup
  | ITby
  | ITusing
  | ITpattern
  | ITstatic
  | ITstock
  | ITanyclass
  | ITvia

  -- Backpack tokens
  | ITunit
  | ITsignature
  | ITdependency
  | ITrequires

  -- Pragmas, see Note [Pragma source text] in "GHC.Types.SourceText"
  | ITinline_prag       SourceText InlineSpec RuleMatchInfo
  | ITopaque_prag       SourceText
  | ITspec_prag         SourceText                -- SPECIALISE
  | ITspec_inline_prag  SourceText Bool    -- SPECIALISE INLINE (or NOINLINE)
  | ITsource_prag       SourceText
  | ITrules_prag        SourceText
  | ITwarning_prag      SourceText
  | ITdeprecated_prag   SourceText
  | ITline_prag         SourceText  -- not usually produced, see 'UsePosPragsBit'
  | ITcolumn_prag       SourceText  -- not usually produced, see 'UsePosPragsBit'
  | 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  -- instance overlap mode
  | IToverlapping_prag  SourceText  -- instance overlap mode
  | IToverlaps_prag     SourceText  -- instance overlap mode
  | ITincoherent_prag   SourceText  -- instance overlap mode
  | ITctype             SourceText
  | ITcomment_line_prag         -- See Note [Nested comment line pragmas]

  | ITdotdot                    -- reserved symbols
  | ITcolon
  | ITdcolon            IsUnicodeSyntax
  | ITequal
  | ITlam
  | ITlcase
  | ITlcases
  | ITvbar
  | ITlarrow            IsUnicodeSyntax
  | ITrarrow            IsUnicodeSyntax
  | ITdarrow            IsUnicodeSyntax
  | ITlolly       -- The (⊸) arrow (for LinearTypes)
  | ITminus       -- See Note [Minus tokens]
  | ITprefixminus -- See Note [Minus tokens]
  | ITbang     -- Prefix (!) only, e.g. f !x = rhs
  | ITtilde    -- Prefix (~) only, e.g. f ~x = rhs
  | ITat       -- Tight infix (@) only, e.g. f x@pat = rhs
  | ITtypeApp  -- Prefix (@) only, e.g. f @t
  | ITpercent  -- Prefix (%) only, e.g. a %1 -> b
  | ITstar              IsUnicodeSyntax
  | ITdot
  | ITproj Bool -- Extension: OverloadedRecordDotBit

  | ITbiglam                    -- GHC-extension symbols

  | ITocurly                    -- special symbols
  | ITccurly
  | ITvocurly
  | ITvccurly
  | ITobrack
  | ITopabrack                  -- [:, for parallel arrays with -XParallelArrays
  | ITcpabrack                  -- :], for parallel arrays with -XParallelArrays
  | ITcbrack
  | IToparen
  | ITcparen
  | IToubxparen
  | ITcubxparen
  | ITsemi
  | ITcomma
  | ITunderscore
  | ITbackquote
  | ITsimpleQuote               --  '

  | ITvarid   FastString        -- identifiers
  | ITconid   FastString
  | ITvarsym  FastString
  | ITconsym  FastString
  | ITqvarid  (FastString,FastString)
  | ITqconid  (FastString,FastString)
  | ITqvarsym (FastString,FastString)
  | ITqconsym (FastString,FastString)

  | ITdupipvarid   FastString   -- GHC extension: implicit param: ?x
  | ITlabelvarid SourceText FastString   -- Overloaded label: #x
                                         -- The SourceText is required because we can
                                         -- have a string literal as a label
                                         -- Note [Literal source text] in "GHC.Types.SourceText"

  | ITchar     SourceText Char       -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITstring   SourceText FastString -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITstringMulti SourceText FastString -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITinteger  IntegralLit           -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITrational FractionalLit

  | ITprimchar   SourceText Char     -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimstring SourceText ByteString -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimint    SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimword   SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimint8   SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimint16  SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimint32  SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimint64  SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimword8  SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimword16 SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimword32 SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimword64 SourceText Integer  -- Note [Literal source text] in "GHC.Types.SourceText"
  | ITprimfloat  FractionalLit
  | ITprimdouble FractionalLit

  -- Template Haskell extension tokens
  | ITopenExpQuote HasE IsUnicodeSyntax --  [| or [e|
  | ITopenPatQuote                      --  [p|
  | ITopenDecQuote                      --  [d|
  | ITopenTypQuote                      --  [t|
  | ITcloseQuote IsUnicodeSyntax        --  |]
  | ITopenTExpQuote HasE                --  [|| or [e||
  | ITcloseTExpQuote                    --  ||]
  | ITdollar                            --  prefix $
  | ITdollardollar                      --  prefix $$
  | ITtyQuote                           --  ''
  | ITquasiQuote (FastString,FastString,PsSpan)
    -- ITquasiQuote(quoter, quote, loc)
    -- represents a quasi-quote of the form
    -- [quoter| quote |]
  | ITqQuasiQuote (FastString,FastString,FastString,PsSpan)
    -- ITqQuasiQuote(Qual, quoter, quote, loc)
    -- represents a qualified quasi-quote of the form
    -- [Qual.quoter| quote |]

  -- Arrow notation extension
  | ITproc
  | ITrec
  | IToparenbar  IsUnicodeSyntax -- ^ @(|@
  | ITcparenbar  IsUnicodeSyntax -- ^ @|)@
  | ITlarrowtail IsUnicodeSyntax -- ^ @-<@
  | ITrarrowtail IsUnicodeSyntax -- ^ @>-@
  | ITLarrowtail IsUnicodeSyntax -- ^ @-<<@
  | ITRarrowtail IsUnicodeSyntax -- ^ @>>-@

  | ITunknown String             -- ^ Used when the lexer can't make sense of it
  | ITeof                        -- ^ end of file token

  -- Documentation annotations. See Note [PsSpan in Comments]
  | ITdocComment   HsDocString PsSpan -- ^ The HsDocString contains more details about what
                                      -- this is and how to pretty print it
  | ITdocOptions   String      PsSpan -- ^ doc options (prune, ignore-exports, etc)
  | ITlineComment  String      PsSpan -- ^ comment starting by "--"
  | ITblockComment String      PsSpan -- ^ comment in {- -}

  deriving Show

instance Outputable Token where
  ppr x = text (show x)

{- Note [PsSpan in Comments]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When using the Api Annotations to exact print a modified AST, managing
the space before a comment is important.  The PsSpan in the comment
token allows this to happen, and this location is tracked in prev_loc
in PState.  This only tracks physical tokens, so is not updated for
zero-width ones.

We also use this to track the space before the end-of-file marker.
-}

{- Note [Minus tokens]
~~~~~~~~~~~~~~~~~~~~~~
A minus sign can be used in prefix form (-x) and infix form (a - b).

When LexicalNegation is on:
  * ITprefixminus  represents the prefix form
  * ITvarsym "-"   represents the infix form
  * ITminus        is not used

When LexicalNegation is off:
  * ITminus        represents all forms
  * ITprefixminus  is not used
  * ITvarsym "-"   is not used
-}

{- Note [Why not LexicalNegationBit]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
One might wonder why we define NoLexicalNegationBit instead of
LexicalNegationBit. The problem lies in the following line in reservedSymsFM:

    ,("-", ITminus, NormalSyntax, xbit NoLexicalNegationBit)

We want to generate ITminus only when LexicalNegation is off. How would one
do it if we had LexicalNegationBit? I (int-index) tried to use bitwise
complement:

    ,("-", ITminus, NormalSyntax, complement (xbit LexicalNegationBit))

This did not work, so I opted for NoLexicalNegationBit instead.
-}


-- the bitmap provided as the third component indicates whether the
-- corresponding extension keyword is valid under the extension options
-- provided to the compiler; if the extension corresponding to *any* of the
-- bits set in the bitmap is enabled, the keyword is valid (this setup
-- facilitates using a keyword in two different extensions that can be
-- activated independently)
--
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),
             -- See Note [Lexing type pseudo-keywords]
         ( "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)
     ]

{-----------------------------------
Note [Lexing type pseudo-keywords]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

One might think that we wish to treat 'family' and 'role' as regular old
varids whenever -XTypeFamilies and -XRoleAnnotations are off, respectively.
But, there is no need to do so. These pseudo-keywords are not stolen syntax:
they are only used after the keyword 'type' at the top-level, where varids are
not allowed. Furthermore, checks further downstream (GHC.Tc.TyCl) ensure that
type families and role annotations are never declared without their extensions
on. In fact, by unconditionally lexing these pseudo-keywords as special, we
can get better error messages.

Also, note that these are included in the `varid` production in the parser --
a key detail to make all this work.
-------------------------------------}

reservedSymsFM :: UniqFM FastString (Token, IsUnicodeSyntax, ExtsBitmap)
reservedSymsFM = listToUFM $
    map (\ (x,w,y,z) -> (mkFastString x,(w,y,z)))
      [ ("..",  ITdotdot,                   NormalSyntax,  0 )
        -- (:) is a reserved op, meaning only list cons
       ,(":",   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)

        -- ToDo: ideally, → and ∷ should be "specials", so that they cannot
        -- form part of a large operator.  This would let us have a better
        -- syntax for kinds: ɑ∷*→* would be a legal kind signature. (maybe).
       ]

-- -----------------------------------------------------------------------------
-- Lexer actions

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
-- See Note [Nested comment line pragmas]
failLinePrag1 :: Action
failLinePrag1 span _buf _len _buf2 = do
  b <- getBit InNestedCommentBit
  if b then return (L span ITcomment_line_prag)
       else lexError LexErrorInPragma

-- See Note [Nested comment line pragmas]
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

-- See Note [Whitespace-sensitive operator parsing]
followedByOpeningToken, precededByClosingToken :: AlexAccPred ExtsBitmap
followedByOpeningToken _ _ _ (AI _ buf) = followedByOpeningToken' buf
precededByClosingToken _ (AI _ buf) _ _ = precededByClosingToken' buf

-- The input is the buffer *after* the token.
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

-- The input is the buffer *before* the token.
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)

-- We must reject doc comments as being ordinary comments everywhere.
-- In some cases the doc comment will be selected as the lexeme due to
-- maximal munch, but not always, because the nested comment rule is
-- valid in all states, but the doc-comment rules are only valid in
-- the non-layout states.
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'

-- Check if we should parse a negative literal (e.g. -123) as a single token.
negLitPred :: AlexAccPred ExtsBitmap
negLitPred =
    prefix_minus `alexAndPred`
    (negative_literals `alexOrPred` lexical_negation)
  where
    negative_literals = ifExtension NegativeLiteralsBit

    lexical_negation  =
      -- See Note [Why not LexicalNegationBit]
      alexNotPred (ifExtension NoLexicalNegationBit)

    prefix_minus =
      -- Note [prefix_minus in negLitPred and negHashLitPred]
      alexNotPred precededByClosingToken

-- Check if we should parse an unboxed negative literal (e.g. -123#) as a single token.
negHashLitPred :: ExtBits -> AlexAccPred ExtsBitmap
negHashLitPred ext = prefix_minus `alexAndPred` magic_hash
  where
    magic_hash = ifExtension ext -- Either MagicHashBit or ExtendedLiteralsBit
    prefix_minus =
      -- Note [prefix_minus in negLitPred and negHashLitPred]
      alexNotPred precededByClosingToken

{- Note [prefix_minus in negLitPred and negHashLitPred]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We want to parse -1 as a single token, but x-1 as three tokens.
So in negLitPred (and negHashLitPred) we require that we have a prefix
occurrence of the minus sign. See Note [Whitespace-sensitive operator parsing]
for a detailed definition of a prefix occurrence.

The condition for a prefix occurrence of an operator is:

  not precededByClosingToken && followedByOpeningToken

but we don't check followedByOpeningToken when parsing a negative literal.
It holds simply because we immediately lex a literal after the minus.
-}

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 -- Start a new line
                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

    -- Check if the next line of input belongs to this doc comment as well.
    -- A doc comment continues onto the next line when the following
    -- conditions are met:
    --   * The line starts with "--"
    --   * The line doesn't start with "---".
    --   * The line doesn't start with "-- $", because that would be the
    --     start of a /new/ named haddock chunk (#10398).
    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 comments require traversing by hand, they can't be parsed
  using regular expressions.
-}
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
  -- Include decorator in comment
  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@(AI start_loc _) docType _checkNextLine = nested_comment_logic endComment "" input (mkPsSpan start_loc (psSpanEnd 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 #-}
-- | Includes the trailing '-}' decorators
-- drop the last two elements with the callback if you don't want them to be included
nested_comment_logic
  :: (AlexInput -> Located String -> P (PsLocated Token))  -- ^ Continuation that gets the rest of the input and the lexed comment
  -> String -- ^ starting value for accumulator (reversed) - When we want to include a decorator '{-' in the comment
  -> 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  -- '{' char
        Nothing  -> errBrace input (psRealSpan span)
        Just ('-',input) -> go ('-':'\123':commentAcc) (n+1) input
        Just (_,_)       -> go ('\123':commentAcc) n input
      -- See Note [Nested comment line pragmas]
      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

-- See Note [Nested comment line pragmas]
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'))

{-
Note [Nested comment line pragmas]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We used to ignore cpp-preprocessor-generated #line pragmas if they were inside
nested comments.

Now, when parsing a nested comment, if we encounter a line starting with '#' we
call parseNestedPragma, which executes the following:
1. Save the current lexer input (loc, buf) for later
2. Set the current lexer input to the beginning of the line starting with '#'
3. Turn the 'InNestedComment' extension on
4. Push the 'bol' lexer state
5. Lex a token. Due to (2), (3), and (4), this should always lex a single line
   or less and return the ITcomment_line_prag token. This may set source line
   and file location if a #line pragma is successfully parsed
6. Restore lexer input and state to what they were before we did all this
7. Return control to the function parsing a nested comment, informing it of
   what the lexer parsed

Regarding (5) above:
Every exit from the 'bol' lexer state (do_bol, popLinePrag1, failLinePrag1)
checks if the 'InNestedComment' extension is set. If it is, that function will
return control to parseNestedPragma by returning the ITcomment_line_prag token.

See #314 for more background on the bug this fixes.
-}

{-# 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
    -- The `Bool` argument to lexDocComment signals whether or not the next
    -- line of input might also belong to this doc comment.
    '|' -> lexDocComment input (mkHdkCommentNext l) True
    '^' -> lexDocComment input (mkHdkCommentPrev l) True
    '$' -> case lexDocName input of
       Nothing -> do setInput input; lexToken -- eof reached, lex it normally
       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 -- eof reached, lex it normally

    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)

-- RULES pragmas turn on the forall and '.' keywords, and we turn them
-- off again at the end of the pragma.
rulePrag :: Action
rulePrag span buf len _buf2 = do
  setExts (.|. xbit InRulePragBit)
  let !src = lexemeToFastString buf len
  return (L span (ITrules_prag (SourceText src)))

-- When 'UsePosPragsBit' is not set, it is expected that we emit a token instead
-- of updating the position in 'PState'
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)))

-- When 'UsePosPragsBit' is not set, it is expected that we emit a token instead
-- of updating the position in 'PState'
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)

-- docCommentEnd
-------------------------------------------------------------------------------
-- This function is quite tricky. We can't just return a new token, we also
-- need to update the state of the parser. Why? Because the token is longer
-- than what was lexed by Alex, and the lexToken function doesn't know this, so
-- it writes the wrong token length to the parser state. This function is
-- called afterwards, so it can just update the state.

{-# 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)
-- takes a StringBuffer and a length, and returns the module name
-- and identifier parts of a qualified name.  Splits at the *last* dot,
-- because of hierarchical module names.
--
-- Throws an error if the name is not qualified.
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

    -- careful, we might get names like M....
    -- so, if the character after the dot is not upper-case, this is
    -- the end of the qualifier part.
    found_dot buf -- buf points after the '.'
        | 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 -- Prelude.(+)
            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


errSuffixAt :: PsSpan -> P a
errSuffixAt span = do
    input <- getInput
    failLocMsgP start (go input start) (\srcSpan -> mkPlainErrorMsgEnvelope srcSpan $ PsErrSuffixAT)
  where
    start = psRealLoc (psSpanStart span)
    go inp loc
      | Just (c, i) <- alexGetChar inp
      , let next = advanceSrcLoc loc c =
          if c == ' '
          then go i next
          else next
      | otherwise = loc

-- See Note [Whitespace-sensitive operator parsing]
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  -- regardless of TypeApplications for better error messages
     | 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 -- Only when LexicalNegation is on, otherwise we get ITminus
                              -- and don't hit this code path. See Note [Minus tokens]
     | s == fsLit ".", OverloadedRecordDotBit `xtest` exts ->
         return (ITproj True) -- e.g. '(.x)'
     | 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 "@" -> errSuffixAt span
     | 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 an operator occurrence for unusual whitespace (prefix, suffix, tight infix).
-- This determines if -Woperator-whitespace is triggered.
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

-- Variations on the integral numeric literal.
tok_integral
  :: (SourceText -> Integer -> Token) -- ^ token constructor
  -> (Integer -> Integer)             -- ^ value transformation (e.g. negate)
  -> Int                              -- ^ Offset of the unsigned value (e.g. 1 when we parsed "-", 2 for "0x", etc.)
  -> Int                              -- ^ Number of non-numeric characters parsed (e.g. 6 in "-12#Int8")
  -> (Integer, (Char -> Int))         -- ^ (radix, char_to_int parsing function)
  -> Action
tok_integral mk_token transval offset translen (radix,char_to_int) span buf len _buf2 = do
  numericUnderscores <- getBit NumericUnderscoresBit  -- #14473
  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 $ mk_token (SourceText src)
       $! transval $ parseUnsignedInteger
       (offsetBytes offset buf) (subtract translen len) radix char_to_int

-- | Helper to parse ExtendedLiterals (e.g. -0x10#Word32)
--
-- This function finds the offset of the "#" character and checks that the
-- suffix is valid. Then it calls tok_integral with the appropriate suffix
-- length taken into account.
tok_prim_num_ext
  :: (Integer -> Integer)             -- ^ value transformation (e.g. negate)
  -> Int                              -- ^ Offset of the unsigned value (e.g. 1 when we parsed "-", 2 for "0x", etc.)
  -> (Integer, (Char -> Int))         -- ^ (radix, char_to_int parsing function)
  -> Action
tok_prim_num_ext transval offset (radix,char_to_int) span buf len buf2 = do
  let !suffix_offset = findHashOffset buf + 1
  let !suffix_len    = len - suffix_offset
  let !suffix        = lexemeToFastString (offsetBytes suffix_offset buf) suffix_len

  mk_token <- if
    | suffix == fsLit "Word"   -> pure ITprimword
    | suffix == fsLit "Word8"  -> pure ITprimword8
    | suffix == fsLit "Word16" -> pure ITprimword16
    | suffix == fsLit "Word32" -> pure ITprimword32
    | suffix == fsLit "Word64" -> pure ITprimword64
    | suffix == fsLit "Int"    -> pure ITprimint
    | suffix == fsLit "Int8"   -> pure ITprimint8
    | suffix == fsLit "Int16"  -> pure ITprimint16
    | suffix == fsLit "Int32"  -> pure ITprimint32
    | suffix == fsLit "Int64"  -> pure ITprimint64
    | otherwise                -> srcParseFail

  let !translen      = suffix_len+offset+1
  tok_integral mk_token transval offset translen (radix,char_to_int) span buf len buf2



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

binary, octal, decimal, hexadecimal :: (Integer, Char -> Int)
binary      = (2,octDecDigit)
octal       = (8,octDecDigit)
decimal     = (10,octDecDigit)
hexadecimal = (16,hexDigit)

-- readSignificandExponentPair can understand negative rationals, exponents, everything.
tok_frac :: Int -> (String -> Token) -> Action
tok_frac drop f span buf len _buf2 = do
  numericUnderscores <- getBit NumericUnderscoresBit  -- #14473
  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, tok_prim_hex_float, tok_prim_hex_double :: 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
tok_prim_hex_float  str = ITprimfloat $! readHexFractionalLit str
tok_prim_hex_double str = ITprimdouble $! readHexFractionalLit 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

-- -----------------------------------------------------------------------------
-- Layout processing

-- we're at the first token on a line, insert layout tokens if necessary
do_bol :: Action
do_bol span _str _len _buf2 = do
        -- See Note [Nested comment line pragmas]
        b <- getBit InNestedCommentBit
        if b then return (L span ITcomment_line_prag) else do
          (pos, gen_semic) <- getOffside
          case pos of
              LT -> do
                  --trace "layout: inserting '}'" $ do
                  popContext
                  -- do NOT pop the lex state, we might have a ';' to insert
                  return (L span ITvccurly)
              EQ | gen_semic -> do
                  --trace "layout: inserting ';'" $ do
                  _ <- popLexState
                  return (L span ITsemi)
              _ -> do
                  _ <- popLexState
                  lexToken

-- certain keywords put us in the "layout" state, where we might
-- add an opening curly brace.
maybe_layout :: Token -> P ()
maybe_layout t = do -- If the alternative layout rule is enabled then
                    -- we never create an implicit layout context here.
                    -- Layout is handled XXX instead.
                    -- The code for closing implicit contexts, or
                    -- inserting implicit semi-colons, is therefore
                    -- irrelevant as it only applies in an implicit
                    -- context.
                    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 ()

-- Pushing a new implicit layout context.  If the indentation of the
-- next token is not greater than the previous layout context, then
-- Haskell 98 says that the new layout context should be empty; that is
-- the lexer must generate {}.
--
-- We are slightly more lenient than this: when the new context is started
-- by a 'do', then we allow the new context to be at the same indentation as
-- the previous context.  This is what the 'strict' argument is for.
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
                -- token is indented to the left of the previous context.
                -- we must generate a {} sequence now.
                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  -- we must be at the start of a line
    return (L span ITvccurly)

-- -----------------------------------------------------------------------------
-- LINE pragmas

setLineAndFile :: Int -> Action
setLineAndFile code (PsSpan span _) buf len _buf2 = do
  let src = lexemeToString buf (len - 1)  -- drop trailing quotation mark
      linenumLen = length $ head $ words src
      linenum = parseUnsignedInteger buf linenumLen 10 octDecDigit
      file = mkFastString $ go $ drop 1 $ dropWhile (/= '"') src
          -- skip everything through first quotation mark to get to the filename
        where go ('\\':c:cs) = c : go cs
              go (c:cs)      = c : go cs
              go []          = []
              -- decode escapes in the filename.  e.g. on Windows
              -- when our filenames have backslashes in, gcc seems to
              -- escape the backslashes.  One symptom of not doing this
              -- is that filenames in error messages look a bit strange:
              --   C:\\foo\bar.hs
              -- only the first backslash is doubled, because we apply
              -- System.FilePath.normalise before printing out
              -- filenames and it does not remove duplicate
              -- backslashes after the drive letter (should it?).
  resetAlrLastLoc file
  setSrcLoc (mkRealSrcLoc file (fromIntegral linenum - 1) (srcSpanEndCol span))
      -- subtract one: the line number refers to the *following* line
  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" -- shouldn't happen
  setSrcLoc (mkRealSrcLoc (srcSpanFile span) (srcSpanEndLine span)
                          (fromIntegral (column :: Integer)))
  _ <- popLexState
  lexToken

alrInitialLoc :: FastString -> RealSrcSpan
alrInitialLoc file = mkRealSrcSpan loc loc
    where -- This is a hack to ensure that the first line in a file
          -- looks like it is after the initial location:
          loc = mkRealSrcLoc file (-1) (-1)

-- -----------------------------------------------------------------------------
-- Options, includes and language pragmas.


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)

-- -----------------------------------------------------------------------------
-- Strings & Chars

tok_string :: Action
tok_string span buf len _buf2 = do
  s <- lex_chars ("\"", "\"") span buf (if endsInHash then len - 1 else len)

  if endsInHash
    then do
      when (any (> '\xFF') s) $ do
        pState <- getPState
        let msg = PsErrPrimStringInvalidChar
        let err = mkPlainErrorMsgEnvelope (mkSrcSpanPs (last_loc pState)) msg
        addError err
      pure $ L span (ITprimstring src (unsafeMkByteString s))
    else
      pure $ L span (ITstring src (mkFastString s))
  where
    src = SourceText $ lexemeToFastString buf len
    endsInHash = currentChar (offsetBytes (len - 1) buf) == '#'

-- | Ideally, we would define this completely with Alex syntax, like normal strings.
-- Instead, this is defined as a hybrid solution by manually invoking lex states, which
-- we're doing for two reasons:
--   1. The multiline string should all be one lexical token, not multiple
--   2. We need to allow bare quotes, which can't be done with one regex
tok_string_multi :: Action
tok_string_multi startSpan startBuf _len _buf2 = do
  -- advance to the end of the multiline string
  let startLoc = psSpanStart startSpan
  let i@(AI _ contentStartBuf) =
        case lexDelim $ AI startLoc startBuf of
          Just i -> i
          Nothing -> panic "tok_string_multi did not start with a delimiter"
  (AI _ contentEndBuf, i'@(AI endLoc endBuf)) <- goContent i

  -- build the values pertaining to the entire multiline string, including delimiters
  let span = mkPsSpan startLoc endLoc
  let len = byteDiff startBuf endBuf
  let src = SourceText $ lexemeToFastString startBuf len

  -- load the content of the multiline string
  let contentLen = byteDiff contentStartBuf contentEndBuf
  s <-
    either (throwStringLexError (AI startLoc startBuf)) pure $
      lexMultilineString contentLen contentStartBuf

  setInput i'
  pure $ L span $ ITstringMulti src (mkFastString s)
  where
    goContent i0 =
      case alexScan i0 string_multi_content of
        AlexToken i1 len _
          | Just i2 <- lexDelim i1 -> pure (i1, i2)
          | -- is the next token a tab character?
            -- need this explicitly because there's a global rule matching $tab
            Just ('\t', _) <- alexGetChar' i1 -> setInput i1 >> lexError LexError
          | isEOF i1  -> checkSmartQuotes >> lexError LexError
          | len == 0  -> panic $ "parsing multiline string got into infinite loop at: " ++ show i0
          | otherwise -> goContent i1
        AlexSkip i1 _ -> goContent i1
        _ -> lexError LexError

    lexDelim =
      let go 0 i = Just i
          go n i =
            case alexGetChar' i of
              Just ('"', i') -> go (n - 1) i'
              _ -> Nothing
       in go (3 :: Int)

    -- See Note [Bare smart quote error]
    checkSmartQuotes = do
      let findSmartQuote i0@(AI loc _) =
            case alexGetChar' i0 of
              Just ('\\', i1) | Just (_, i2) <- alexGetChar' i1 -> findSmartQuote i2
              Just (c, i1)
                | isDoubleSmartQuote c -> Just (c, loc)
                | otherwise -> findSmartQuote i1
              _ -> Nothing
      case findSmartQuote (AI (psSpanStart startSpan) startBuf) of
        Just (c, loc) -> throwSmartQuoteError c loc
        Nothing -> pure ()

-- | Dummy action that should never be called. Should only be used in lex states
-- that are manually lexed in tok_string_multi.
tok_string_multi_content :: Action
tok_string_multi_content = panic "tok_string_multi_content unexpectedly invoked"

lex_chars :: (String, String) -> PsSpan -> StringBuffer -> Int -> P String
lex_chars (startDelim, endDelim) span buf len =
  either (throwStringLexError i0) pure $
    lexString contentLen contentBuf
  where
    i0@(AI _ contentBuf) = advanceInputBytes (length startDelim) $ AI (psSpanStart span) buf

    -- assumes delimiters are ASCII, with 1 byte per Char
    contentLen = len - length startDelim - length endDelim

throwStringLexError :: AlexInput -> StringLexError -> P a
throwStringLexError i (StringLexError e pos) = setInput (advanceInputTo pos i) >> lexError e


tok_quoted_label :: Action
tok_quoted_label span buf len _buf2 = do
  s <- lex_chars ("#\"", "\"") span buf len
  pure $ L span (ITlabelvarid src (mkFastString s))
  where
    -- skip leading '#'
    src = SourceText . mkFastString . drop 1 $ lexemeToString buf len


tok_char :: Action
tok_char span buf len _buf2 = do
  c <- lex_chars ("'", "'") span buf (if endsInHash then len - 1 else len) >>= \case
    [c] -> pure c
    s -> panic $ "tok_char expected exactly one character, got: " ++ show s
  pure . L span $
    if endsInHash
      then ITprimchar src c
      else ITchar src c
  where
    src = SourceText $ lexemeToFastString buf len
    endsInHash = currentChar (offsetBytes (len - 1) buf) == '#'


-- -----------------------------------------------------------------------------
-- QuasiQuote

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))
                -- 'tail' drops the initial '[',
                -- while the -1 drops the trailing '|'
  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

    -- NB: The string "|]" terminates the quasiquote,
    -- with absolutely no escaping. See the extensive
    -- discussion on #5348 for why there is no
    -- escape handling.
    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))

-- -----------------------------------------------------------------------------
-- Unicode Smart Quote detection (#21843)

isSmartQuote :: AlexAccPred ExtsBitmap
isSmartQuote _ _ _ (AI _ buf) = let c = prevChar buf ' ' in isSingleSmartQuote c || isDoubleSmartQuote c

throwSmartQuoteError :: Char -> PsLoc -> P a
throwSmartQuoteError c loc = addFatalError err
  where
    err =
      mkPlainErrorMsgEnvelope (mkSrcSpanPs (mkPsSpan loc loc)) $
        PsErrUnicodeCharLooksLike c correct_char correct_char_name
    (correct_char, correct_char_name) =
      if isSingleSmartQuote c
        then ('\'', "Single Quote")
        else ('"', "Quotation Mark")

-- | Throw a smart quote error, where the smart quote was the last character lexed
smart_quote_error :: Action
smart_quote_error span _ _ buf2 = do
  let c = prevChar buf2 (panic "smart_quote_error unexpectedly called on beginning of input")
  throwSmartQuoteError c (psSpanStart span)

-- Note [Bare smart quote error]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- A smart quote inside of a string is allowed, but if a complete valid string
-- couldn't be lexed, we want to see if there's a smart quote that the user
-- thought ended the string, but in fact didn't.

-- -----------------------------------------------------------------------------
-- Warnings

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

-- -----------------------------------------------------------------------------
-- The Parse Monad

-- | Do we want to generate ';' layout tokens? In some cases we just want to
-- generate '}', e.g. in MultiWayIf we don't need ';'s because '|' separates
-- alternatives (unlike a `case` expression where we need ';' to as a separator
-- between alternatives).
type GenSemic = Bool

generateSemic, dontGenerateSemic :: GenSemic
generateSemic     = True
dontGenerateSemic = False

data LayoutContext
  = NoLayout
  | Layout !Int !GenSemic
  deriving Show

-- | The result of running a parser.
newtype ParseResult a = PR (# (# PState, a #) | PState #)

-- | The parser has consumed a (possibly empty) prefix of the input and produced
-- a result. Use 'getPsMessages' to check for accumulated warnings and non-fatal
-- errors.
--
-- The carried parsing state can be used to resume parsing.
pattern POk :: PState -> a -> ParseResult a
pattern POk s a = PR (# (# s , a #) | #)

-- | The parser has consumed a (possibly empty) prefix of the input and failed.
--
-- The carried parsing state can be used to resume parsing. It is the state
-- right before failure, including the fatal parse error. 'getPsMessages' and
-- 'getPsErrorMessages' must return a non-empty bag of errors.
pattern PFailed :: PState -> ParseResult a
pattern PFailed s = PR (# | s #)

{-# COMPLETE POk, PFailed #-}

-- | Test whether a 'WarningFlag' is set
warnopt :: WarningFlag -> ParserOpts -> Bool
warnopt f options = f `EnumSet.member` pWarningFlags options

-- | Parser options.
--
-- See 'mkParserOpts' to construct this.
data ParserOpts = ParserOpts
  { pExtsBitmap     :: !ExtsBitmap -- ^ bitmap of permitted extensions
  , pDiagOpts       :: !DiagOpts
    -- ^ Options to construct diagnostic messages.
  , pSupportedExts  :: [String]
    -- ^ supported extensions (only used for suggestions in error messages)
  }

pWarningFlags :: ParserOpts -> EnumSet WarningFlag
pWarningFlags opts = diag_warning_flags (pDiagOpts opts)

-- | Haddock comment as produced by the lexer. These are accumulated in 'PState'
-- and then processed in "GHC.Parser.PostProcess.Haddock". The location of the
-- 'HsDocString's spans over the contents of the docstring - i.e. it does not
-- include the decorator ("-- |", "{-|" etc.)
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, -- pos of first tab warning in the file
        tab_count  :: !Word,             -- number of tab warnings in the file
        last_tk    :: Strict.Maybe (PsLocated Token), -- last non-comment token
        prev_loc   :: PsSpan,      -- pos of previous non-virtual token, including comments,
        last_loc   :: PsSpan,      -- pos of current token
        last_len   :: !Int,        -- len of current token
        loc        :: PsLoc,       -- current loc (end of prev token + 1)
        context    :: [LayoutContext],
        lex_state  :: [Int],
        srcfiles   :: [FastString],
        -- Used in the alternative layout rule:
        -- These tokens are the next ones to be sent out. They are
        -- just blindly emitted, without the rule looking at them again:
        alr_pending_implicit_tokens :: [PsLocated Token],
        -- This is the next token to be considered or, if it is Nothing,
        -- we need to get the next token from the input stream:
        alr_next_token :: Maybe (PsLocated Token),
        -- This is what we consider to be the location of the last token
        -- emitted:
        alr_last_loc :: PsSpan,
        -- The stack of layout contexts:
        alr_context :: [ALRContext],
        -- Are we expecting a '{'? If it's Just, then the ALRLayout tells
        -- us what sort of layout the '{' will open:
        alr_expecting_ocurly :: Maybe ALRLayout,
        -- Have we just had the '}' for a let block? If so, than an 'in'
        -- token doesn't need to close anything:
        alr_justClosedExplicitLetBlock :: Bool,

        -- The next three are used to implement Annotations giving the
        -- locations of 'noise' tokens in the source, so that users of
        -- the GHC API can do source to source conversions.
        -- See Note [exact print annotations] in GHC.Parser.Annotation
        eof_pos :: Strict.Maybe (Strict.Pair RealSrcSpan RealSrcSpan), -- pos, gap to prior token
        header_comments :: Strict.Maybe [LEpaComment],
        comment_q :: [LEpaComment],

        -- Haddock comments accumulated in ascending order of their location
        -- (BufPos). We use OrdList to get O(1) snoc.
        --
        -- See Note [Adding Haddock comments to the syntax tree] in GHC.Parser.PostProcess.Haddock
        hdk_comments :: OrdList (PsLocated HdkComment)
     }
        -- last_loc and last_len are used when generating error messages,
        -- and in pushCurrentContext only.  Sigh, if only Happy passed the
        -- current token to happyError, we could at least get rid of last_len.
        -- Getting rid of last_loc would require finding another way to
        -- implement pushCurrentContext (which is only called from one place).

        -- AZ question: setLastToken which sets last_loc and last_len
        -- is called when processing AlexToken, immediately prior to
        -- calling the action in the token.  So from the perspective
        -- of the action, it is the *current* token.  Do I understand
        -- correctly?

data ALRContext = ALRNoLayout Bool{- does it contain commas? -}
                              Bool{- is it a 'let' block? -}
                | ALRLayout ALRLayout Int
data ALRLayout = ALRLayoutLet
               | ALRLayoutWhere
               | ALRLayoutOf
               | ALRLayoutDo

-- | The parsing monad, isomorphic to @StateT PState Maybe@.
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

-- see Note [PsSpan in Comments]
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 deriving (Show)

{-
Note [Unicode in Alex]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Although newer versions of Alex support unicode, this grammar is processed with
the old style '--latin1' behaviour. This means that when implementing the
functions

    alexGetByte       :: AlexInput -> Maybe (Word8,AlexInput)
    alexInputPrevChar :: AlexInput -> Char

which Alex uses to take apart our 'AlexInput', we must

  * return a latin1 character in the 'Word8' that 'alexGetByte' expects
  * return a latin1 character in 'alexInputPrevChar'.

We handle this in 'adjustChar' by squishing entire classes of unicode
characters into single bytes.
-}

{-# INLINE adjustChar #-}
adjustChar :: Char -> Word8
adjustChar c = adj_c
  where non_graphic     = 0x00
        upper           = 0x01
        lower           = 0x02
        digit           = 0x03
        symbol          = 0x04
        space           = 0x05
        other_graphic   = 0x06
        uniidchar       = 0x07

        adj_c
          | c <= '\x07' = non_graphic
          | c <= '\x7f' = fromIntegral (ord c)
          -- Alex doesn't handle Unicode, so when Unicode
          -- character is encountered we output these values
          -- with the actual character value hidden in the state.
          | otherwise =
                -- NB: The logic behind these definitions is also reflected
                -- in "GHC.Utils.Lexeme"
                -- Any changes here should likely be reflected there.

                case generalCategory c of
                  UppercaseLetter       -> upper
                  LowercaseLetter       -> lower
                  TitlecaseLetter       -> upper
                  ModifierLetter        -> uniidchar -- see #10196
                  OtherLetter           -> lower -- see #1103
                  NonSpacingMark        -> uniidchar -- see #7650
                  SpacingCombiningMark  -> other_graphic
                  EnclosingMark         -> other_graphic
                  DecimalNumber         -> digit
                  LetterNumber          -> digit
                  OtherNumber           -> digit -- see #4373
                  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

-- Getting the previous 'Char' isn't enough here - we need to convert it into
-- the same format that 'alexGetByte' would have produced.
--
-- See Note [Unicode in Alex] and #13986.
alexInputPrevChar :: AlexInput -> Char
alexInputPrevChar (AI _ buf) = unsafeChr (fromIntegral (adjustChar pc))
  where pc = prevChar buf '\n'

unsafeChr :: Int -> Char
unsafeChr (I# c) = GHC.Exts.C# (GHC.Exts.chr# c)

-- backwards compatibility for Alex 2.x
alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar inp = case alexGetByte inp of
                    Nothing    -> Nothing
                    Just (b,i) -> c `seq` Just (c,i)
                       where c = unsafeChr $ fromIntegral b

-- See Note [Unicode in Alex]
alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
alexGetByte (AI loc s)
  | atEnd s   = Nothing
  | otherwise = byte `seq` loc' `seq` s' `seq`
                --trace (show (ord c)) $
                Just (byte, (AI loc' s'))
  where (c,s') = nextChar s
        loc'   = advancePsLoc loc c
        byte   = adjustChar c

{-# INLINE alexGetChar' #-}
-- This version does not squash unicode characters, it is used when
-- lexing strings.
alexGetChar' :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar' (AI loc s)
  | atEnd s   = Nothing
  | otherwise = c `seq` loc' `seq` s' `seq`
                --trace (show (ord c)) $
                Just (c, (AI loc' s'))
  where (c,s') = nextChar s
        loc'   = advancePsLoc loc c

-- | Advance the given input N bytes.
advanceInputBytes :: Int -> AlexInput -> AlexInput
advanceInputBytes n i0@(AI _ buf0) = advanceInputTo (cur buf0 + n) i0

-- | Advance the given input to the given position.
advanceInputTo :: Int -> AlexInput -> AlexInput
advanceInputTo pos = go
  where
    go i@(AI _ buf)
      | cur buf >= pos = i
      | Just (_, i') <- alexGetChar' i = go i'
      | otherwise = i -- reached the end, just return the last input

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 = isEOF <$> getInput

isEOF :: AlexInput -> Bool
isEOF (AI _ buf) = atEnd buf

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}) ()

-- | For reasons of efficiency, boolean parsing flags (eg, language extensions
-- or whether we are currently in a @RULE@ pragma) are represented by a bitmap
-- stored in a @Word64@.
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)

-- | Various boolean flags, mostly language extensions, that impact lexing and
-- parsing. Note that a handful of these can change during lexing/parsing.
data ExtBits
  -- Flags that are constant once parsing starts
  = FfiBit
  | InterruptibleFfiBit
  | CApiFfiBit
  | ArrowsBit
  | ThBit
  | ThQuotesBit
  | IpBit
  | OverloadedLabelsBit -- #x overloaded labels
  | ExplicitForallBit -- the 'forall' keyword
  | BangPatBit -- Tells the parser to understand bang-patterns
               -- (doesn't affect the lexer)
  | PatternSynonymsBit -- pattern synonyms
  | HaddockBit-- Lex and parse Haddock comments
  | MagicHashBit -- "#" in both functions and operators
  | RecursiveDoBit -- mdo
  | QualifiedDoBit -- .do and .mdo
  | UnicodeSyntaxBit -- the forall symbol, arrow symbols, etc
  | UnboxedParensBit -- (# and #)
  | DatatypeContextsBit
  | MonadComprehensionsBit
  | TransformComprehensionsBit
  | QqBit -- enable quasiquoting
  | RawTokenStreamBit -- producing a token stream with all comments included
  | AlternativeLayoutRuleBit
  | ALRTransitionalBit
  | RelaxedLayoutBit
  | NondecreasingIndentationBit
  | SafeHaskellBit
  | TraditionalRecordSyntaxBit
  | ExplicitNamespacesBit
  | LambdaCaseBit
  | BinaryLiteralsBit
  | NegativeLiteralsBit
  | HexFloatLiteralsBit
  | StaticPointersBit
  | NumericUnderscoresBit
  | StarIsTypeBit
  | BlockArgumentsBit
  | NPlusKPatternsBit
  | DoAndIfThenElseBit
  | MultiWayIfBit
  | GadtSyntaxBit
  | ImportQualifiedPostBit
  | LinearTypesBit
  | NoLexicalNegationBit   -- See Note [Why not LexicalNegationBit]
  | OverloadedRecordDotBit
  | OverloadedRecordUpdateBit
  | OrPatternsBit
  | ExtendedLiteralsBit
  | ListTuplePunsBit
  | ViewPatternsBit
  | RequiredTypeArgumentsBit
  | MultilineStringsBit

  -- Flags that are updated once parsing starts
  | InRulePragBit
  | InNestedCommentBit -- See Note [Nested comment line pragmas]
  | UsePosPragsBit
    -- ^ If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}'
    -- update the internal position. Otherwise, those pragmas are lexed as
    -- tokens of their own.
  deriving Enum

{-# INLINE mkParserOpts #-}
mkParserOpts
  :: EnumSet LangExt.Extension  -- ^ permitted language extensions enabled
  -> DiagOpts                   -- ^ diagnostic options
  -> [String]                   -- ^ Supported Languages and Extensions
  -> Bool                       -- ^ are safe imports on?
  -> Bool                       -- ^ keeping Haddock comment tokens
  -> Bool                       -- ^ keep regular comment tokens

  -> Bool
  -- ^ If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update
  -- the internal position kept by the parser. Otherwise, those pragmas are
  -- lexed as 'ITline_prag' and 'ITcolumn_prag' tokens.

  -> ParserOpts
-- ^ Given exactly the information needed, set up the '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 -- See Note [Why not LexicalNegationBit]
      .|. OverloadedRecordDotBit      `xoptBit` LangExt.OverloadedRecordDot
      .|. OverloadedRecordUpdateBit   `xoptBit` LangExt.OverloadedRecordUpdate  -- Enable testing via 'getBit OverloadedRecordUpdateBit' in the parser (RecordDotSyntax parsing uses that information).
      .|. OrPatternsBit               `xoptBit` LangExt.OrPatterns
      .|. ExtendedLiteralsBit         `xoptBit` LangExt.ExtendedLiterals
      .|. ListTuplePunsBit            `xoptBit` LangExt.ListTuplePuns
      .|. ViewPatternsBit             `xoptBit` LangExt.ViewPatterns
      .|. RequiredTypeArgumentsBit    `xoptBit` LangExt.RequiredTypeArguments
      .|. MultilineStringsBit         `xoptBit` LangExt.MultilineStrings
    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) }


-- | Set parser options for parsing OPTIONS pragmas
initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initPragState options buf loc = (initParserState options buf loc)
   { lex_state = [bol, option_prags, 0]
   }

-- | Creates a parse state from a 'ParserOpts' value
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)

-- | An mtl-style class for monads that support parsing-related operations.
-- For example, sometimes we make a second pass over the parsing results to validate,
-- disambiguate, or rearrange them, and we do so in the PV monad which cannot consume
-- input but can report parsing errors, check for extension bits, and accumulate
-- parsing annotations. Both P and PV are instances of MonadP.
--
-- MonadP grants us convenient overloading. The other option is to have separate operations
-- for each monad: addErrorP vs addErrorPV, getBitP vs getBitPV, and so on.
--
class Monad m => MonadP m where
  -- | Add a non-fatal error. Use this when the parser can produce a result
  --   despite the error.
  --
  --   For example, when GHC encounters a @forall@ in a type,
  --   but @-XExplicitForAll@ is disabled, the parser constructs @ForAllTy@
  --   as if @-XExplicitForAll@ was enabled, adding a non-fatal error to
  --   the accumulator.
  --
  --   Control flow wise, non-fatal errors act like warnings: they are added
  --   to the accumulator and parsing continues. This allows GHC to report
  --   more than one parse error per file.
  --
  addError :: MsgEnvelope PsMessage -> m ()

  -- | Add a warning to the accumulator.
  --   Use 'getPsMessages' to get the accumulated warnings.
  addWarning :: MsgEnvelope PsMessage -> m ()

  -- | Add a fatal error. This will be the last error reported by the parser, and
  --   the parser will not produce any result, ending in a 'PFailed' state.
  addFatalError :: MsgEnvelope PsMessage -> m a

  -- | Get parser options
  getParserOpts :: m ParserOpts

  -- | Go through the @comment_q@ in @PState@ and remove all comments
  -- that belong within the given span
  allocateCommentsP :: RealSrcSpan -> m EpAnnComments
  -- | Go through the @comment_q@ in @PState@ and remove all comments
  -- that come before or within the given span
  allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments
  -- | Go through the @comment_q@ in @PState@ and remove all comments
  -- that come after the given span
  allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments

instance MonadP P where
  addError err
   = P $ \s -> POk s { errors = err `addMessage` errors s} ()

  -- If the warning is meant to be suppressed, GHC will assign
  -- a `SevIgnore` severity and the message will be discarded,
  -- so we can simply add it no matter what.
  addWarning w
   = P $ \s -> POk (s { warnings = w `addMessage` warnings s }) ()

  addFatalError err =
    addError err >> P PFailed

  getParserOpts = P $ \s -> POk s $! options s

  allocateCommentsP ss = P $ \s ->
    if null (comment_q s) then POk s emptyComments else  -- fast path
    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)

-- | Check if a given flag is currently set in the bitmap.
getBit :: MonadP m => ExtBits -> m Bool
getBit ext = (\opts -> ext `xtest` pExtsBitmap opts) <$> getParserOpts

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 :: MonadP m => SrcSpan -> PsMessage -> m ()
addPsMessage srcspan msg = do
  diag_opts <- pDiagOpts <$> getParserOpts
  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' ()

-- | Get a bag of the errors that have been accumulated so far.
--   Does not take -Werror into account.
getPsErrorMessages :: PState -> Messages PsMessage
getPsErrorMessages p = errors p

-- | Get the warnings and errors accumulated so far.
--   Does not take -Werror into account.
getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage)
getPsMessages p =
  let ws = warnings p
      diag_opts = pDiagOpts (options p)
      -- we add the tabulation warning on the fly because
      -- we count the number of occurrences of tab characters
      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

-- Push a new layout context at the indentation of the last token read.
pushCurrentContext :: GenSemic -> P ()
pushCurrentContext gen_semic = P $ \ s@PState{ last_loc=loc, context=ctx } ->
    POk s{context = Layout (srcSpanStartCol (psRealSpan loc)) gen_semic : ctx} ()

-- This is only used at the outer level of a module when the 'module' keyword is
-- missing.
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 : _ ->
                              --trace ("layout: " ++ show n ++ ", offs: " ++ show offs) $
                              (compare offs n, gen_semic)
                            _ ->
                              (GT, dontGenerateSemic)
                in POk s ord

-- ---------------------------------------------------------------------------
-- Construct a parse error

srcParseErr
  :: ParserOpts
  -> StringBuffer       -- current buffer (placed just after the last token)
  -> Int                -- length of the previous token
  -> 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 "
     }

-- Report a parse failure, giving the span of the previous token as
-- the location of the error.  This is the entry point for errors
-- detected during parsing.
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

-- A lexical error is reported at a particular position in the source file,
-- not over a token range.
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)

-- -----------------------------------------------------------------------------
-- This is the top-level function: called from the parser each time a
-- new token is to be read from the input.

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
  --trace ("token: " ++ show tok) $ do

  if (queueComments && isComment tok)
    then queueComment (L (psRealSpan span) tok) >> lexer queueComments cont
    else cont (L (mkSrcSpanPs span) tok)

-- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
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
             -- This case handles a GHC extension to the original H98
             -- layout rule...
             (ITocurly, _, Just alrLayout) ->
                 do setAlrExpectingOCurly Nothing
                    let isLet = case alrLayout of
                                ALRLayoutLet -> True
                                _ -> False
                    setALRContext (ALRNoLayout (containsCommas ITocurly) isLet : context)
                    return t
             -- ...and makes this case unnecessary
             {-
             -- I think our implicit open-curly handling is slightly
             -- different to John's, in how it interacts with newlines
             -- and "in"
             (ITocurly, _, Just _) ->
                 do setAlrExpectingOCurly Nothing
                    setNextToken t
                    lexTokenAlr
             -}
             (_, 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)
             -- We do the [] cases earlier than in the spec, as we
             -- have an actual EOF token
             (ITeof, ALRLayout _ _ : ls, _) ->
                 do setALRContext ls
                    setNextToken t
                    return (L thisLoc ITvccurly)
             (ITeof, _, _) ->
                 return t
             -- the other ITeof case omitted; general case below covers it
             (ITin, _, _)
              | justClosedExplicitLetBlock ->
                 return t
             (ITin, ALRLayout ALRLayoutLet _ : ls, _)
              | newLine ->
                 do setPendingImplicitTokens [t]
                    setALRContext ls
                    return (L thisLoc ITvccurly)
             -- This next case is to handle a transitional issue:
             (ITwhere, ALRLayout _ col : ls, _)
              | newLine && thisCol == col && transitional ->
                 do addPsMessage
                      (mkSrcSpanPs thisLoc)
                      (PsWarnTransitionalLayout TransLayout_Where)
                    setALRContext ls
                    setNextToken t
                    -- Note that we use lastLoc, as we may need to close
                    -- more layouts, or give a semicolon
                    return (L lastLoc ITvccurly)
             -- This next case is to handle a transitional issue:
             (ITvbar, ALRLayout _ col : ls, _)
              | newLine && thisCol == col && transitional ->
                 do addPsMessage
                      (mkSrcSpanPs thisLoc)
                      (PsWarnTransitionalLayout TransLayout_Pipe)
                    setALRContext ls
                    setNextToken t
                    -- Note that we use lastLoc, as we may need to close
                    -- more layouts, or give a semicolon
                    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
                    -- Note that we use lastLoc, as we may need to close
                    -- more layouts, or give a semicolon
                    return (L lastLoc ITvccurly)
             -- We need to handle close before open, as 'then' is both
             -- an open and a close
             (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
                        -- XXX This is an error in John's code, but
                        -- it looks reachable to me at first glance
                        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)
             -- the other ITin case omitted; general case below covers it
             (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)
             -- the other ITwhere case omitted; general case below covers it
             (_, _, _) -> return t

isALRopen :: Token -> Bool
isALRopen ITcase          = True
isALRopen ITif            = True
isALRopen ITthen          = True
isALRopen IToparen        = True
isALRopen ITobrack        = True
isALRopen ITocurly        = True
-- GHC Extensions:
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
-- GHC Extensions:
isALRclose ITcubxparen = True
isALRclose _        = False

isNonDecreasingIndentation :: ALRLayout -> Bool
isNonDecreasingIndentation ALRLayoutDo = True
isNonDecreasingIndentation _           = False

containsCommas :: Token -> Bool
containsCommas IToparen = True
containsCommas ITobrack = True
-- John doesn't have {} as containing commas, but records contain them,
-- which caused a problem parsing Cabal's Distribution.Simple.InstallDirs
-- (defaultInstallDirs).
containsCommas ITocurly = True
-- GHC Extensions:
containsCommas IToubxparen = True
containsCommas _        = False

topNoLayoutContainsCommas :: [ALRContext] -> Bool
topNoLayoutContainsCommas [] = False
topNoLayoutContainsCommas (ALRLayout _ _ : ls) = topNoLayoutContainsCommas ls
topNoLayoutContainsCommas (ALRNoLayout b _ : _) = b

-- If the generated alexScan/alexScanUser functions are called multiple times
-- in this file, alexScanUser gets broken out into a separate function and
-- increases memory usage. Make sure GHC inlines this function and optimizes it.
{-# INLINE alexScanUser #-}

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' -- decoding errors are mapped to '\0', see utf8DecodeChar#
     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  -- parse LINE/COLUMN pragmas as tokens
                $ xset RawTokenStreamBit -- include comments
                $ 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
                     -- CFILES is a hugs-only thing.
                     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))),
                                    -- Spelling variant
     ("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

{-
%************************************************************************
%*                                                                      *
        Helper functions for generating annotations in the parser
%*                                                                      *
%************************************************************************
-}


-- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
-- 'AddEpAnn' values for the opening and closing bordering on the start
-- and end of the span
mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
                    AddEpAnn AnnCloseP (EpaSpan (RealSrcSpan 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)

-- Comments appearing without a line-break before the first
-- declaration are associated with the declaration
splitPriorComments
  :: RealSrcSpan
  -> [LEpaComment]
  -> ([LEpaComment], [LEpaComment])
splitPriorComments ss prior_comments =
  let
    -- True if there is only one line between the earlier and later span,
    -- And the token preceding the comment is on a different line
    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 =
  -- We ignore the RealSrcSpan as the parser currently provides a
  -- point span at (1,1).
  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"

-- see Note [PsSpan in Comments]
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